1/* tc-mips.c -- assemble code for a MIPS chip.
2   Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002,
3   2003, 2004, 2005 Free Software Foundation, Inc.
4   Contributed by the OSF and Ralph Campbell.
5   Written by Keith Knowles and Ralph Campbell, working independently.
6   Modified for ECOFF and R4000 support by Ian Lance Taylor of Cygnus
7   Support.
8
9   This file is part of GAS.
10
11   GAS is free software; you can redistribute it and/or modify
12   it under the terms of the GNU General Public License as published by
13   the Free Software Foundation; either version 2, or (at your option)
14   any later version.
15
16   GAS is distributed in the hope that it will be useful,
17   but WITHOUT ANY WARRANTY; without even the implied warranty of
18   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
19   GNU General Public License for more details.
20
21   You should have received a copy of the GNU General Public License
22   along with GAS; see the file COPYING.  If not, write to the Free
23   Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
24   02110-1301, USA.  */
25
26#include "as.h"
27#include "config.h"
28#include "subsegs.h"
29#include "safe-ctype.h"
30
31#include <stdarg.h>
32
33#include "opcode/mips.h"
34#include "itbl-ops.h"
35#include "dwarf2dbg.h"
36#include "dw2gencfi.h"
37
38#ifdef DEBUG
39#define DBG(x) printf x
40#else
41#define DBG(x)
42#endif
43
44#ifdef OBJ_MAYBE_ELF
45/* Clean up namespace so we can include obj-elf.h too.  */
46static int mips_output_flavor (void);
47static int mips_output_flavor (void) { return OUTPUT_FLAVOR; }
48#undef OBJ_PROCESS_STAB
49#undef OUTPUT_FLAVOR
50#undef S_GET_ALIGN
51#undef S_GET_SIZE
52#undef S_SET_ALIGN
53#undef S_SET_SIZE
54#undef obj_frob_file
55#undef obj_frob_file_after_relocs
56#undef obj_frob_symbol
57#undef obj_pop_insert
58#undef obj_sec_sym_ok_for_reloc
59#undef OBJ_COPY_SYMBOL_ATTRIBUTES
60
61#include "obj-elf.h"
62/* Fix any of them that we actually care about.  */
63#undef OUTPUT_FLAVOR
64#define OUTPUT_FLAVOR mips_output_flavor()
65#endif
66
67#if defined (OBJ_ELF)
68#include "elf/mips.h"
69#endif
70
71#ifndef ECOFF_DEBUGGING
72#define NO_ECOFF_DEBUGGING
73#define ECOFF_DEBUGGING 0
74#endif
75
76int mips_flag_mdebug = -1;
77
78/* Control generation of .pdr sections.  Off by default on IRIX: the native
79   linker doesn't know about and discards them, but relocations against them
80   remain, leading to rld crashes.  */
81#ifdef TE_IRIX
82int mips_flag_pdr = FALSE;
83#else
84int mips_flag_pdr = TRUE;
85#endif
86
87#include "ecoff.h"
88
89#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
90static char *mips_regmask_frag;
91#endif
92
93#define ZERO 0
94#define AT  1
95#define TREG 24
96#define PIC_CALL_REG 25
97#define KT0 26
98#define KT1 27
99#define GP  28
100#define SP  29
101#define FP  30
102#define RA  31
103
104#define ILLEGAL_REG (32)
105
106/* Allow override of standard little-endian ECOFF format.  */
107
108#ifndef ECOFF_LITTLE_FORMAT
109#define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
110#endif
111
112extern int target_big_endian;
113
114/* The name of the readonly data section.  */
115#define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
116			    ? ".rdata" \
117			    : OUTPUT_FLAVOR == bfd_target_coff_flavour \
118			    ? ".rdata" \
119			    : OUTPUT_FLAVOR == bfd_target_elf_flavour \
120			    ? ".rodata" \
121			    : (abort (), ""))
122
123/* Information about an instruction, including its format, operands
124   and fixups.  */
125struct mips_cl_insn
126{
127  /* The opcode's entry in mips_opcodes or mips16_opcodes.  */
128  const struct mips_opcode *insn_mo;
129
130  /* True if this is a mips16 instruction and if we want the extended
131     form of INSN_MO.  */
132  bfd_boolean use_extend;
133
134  /* The 16-bit extension instruction to use when USE_EXTEND is true.  */
135  unsigned short extend;
136
137  /* The 16-bit or 32-bit bitstring of the instruction itself.  This is
138     a copy of INSN_MO->match with the operands filled in.  */
139  unsigned long insn_opcode;
140
141  /* The frag that contains the instruction.  */
142  struct frag *frag;
143
144  /* The offset into FRAG of the first instruction byte.  */
145  long where;
146
147  /* The relocs associated with the instruction, if any.  */
148  fixS *fixp[3];
149
150  /* True if this entry cannot be moved from its current position.  */
151  unsigned int fixed_p : 1;
152
153  /* True if this instruction occured in a .set noreorder block.  */
154  unsigned int noreorder_p : 1;
155
156  /* True for mips16 instructions that jump to an absolute address.  */
157  unsigned int mips16_absolute_jump_p : 1;
158};
159
160/* The ABI to use.  */
161enum mips_abi_level
162{
163  NO_ABI = 0,
164  O32_ABI,
165  O64_ABI,
166  N32_ABI,
167  N64_ABI,
168  EABI_ABI
169};
170
171/* MIPS ABI we are using for this output file.  */
172static enum mips_abi_level mips_abi = NO_ABI;
173
174/* Whether or not we have code that can call pic code.  */
175int mips_abicalls = FALSE;
176
177/* Whether or not we have code which can be put into a shared
178   library.  */
179static bfd_boolean mips_in_shared = TRUE;
180
181/* This is the set of options which may be modified by the .set
182   pseudo-op.  We use a struct so that .set push and .set pop are more
183   reliable.  */
184
185struct mips_set_options
186{
187  /* MIPS ISA (Instruction Set Architecture) level.  This is set to -1
188     if it has not been initialized.  Changed by `.set mipsN', and the
189     -mipsN command line option, and the default CPU.  */
190  int isa;
191  /* Enabled Application Specific Extensions (ASEs).  These are set to -1
192     if they have not been initialized.  Changed by `.set <asename>', by
193     command line options, and based on the default architecture.  */
194  int ase_mips3d;
195  int ase_mdmx;
196  int ase_dsp;
197  int ase_mt;
198  /* Whether we are assembling for the mips16 processor.  0 if we are
199     not, 1 if we are, and -1 if the value has not been initialized.
200     Changed by `.set mips16' and `.set nomips16', and the -mips16 and
201     -nomips16 command line options, and the default CPU.  */
202  int mips16;
203  /* Non-zero if we should not reorder instructions.  Changed by `.set
204     reorder' and `.set noreorder'.  */
205  int noreorder;
206  /* Non-zero if we should not permit the $at ($1) register to be used
207     in instructions.  Changed by `.set at' and `.set noat'.  */
208  int noat;
209  /* Non-zero if we should warn when a macro instruction expands into
210     more than one machine instruction.  Changed by `.set nomacro' and
211     `.set macro'.  */
212  int warn_about_macros;
213  /* Non-zero if we should not move instructions.  Changed by `.set
214     move', `.set volatile', `.set nomove', and `.set novolatile'.  */
215  int nomove;
216  /* Non-zero if we should not optimize branches by moving the target
217     of the branch into the delay slot.  Actually, we don't perform
218     this optimization anyhow.  Changed by `.set bopt' and `.set
219     nobopt'.  */
220  int nobopt;
221  /* Non-zero if we should not autoextend mips16 instructions.
222     Changed by `.set autoextend' and `.set noautoextend'.  */
223  int noautoextend;
224  /* Restrict general purpose registers and floating point registers
225     to 32 bit.  This is initially determined when -mgp32 or -mfp32
226     is passed but can changed if the assembler code uses .set mipsN.  */
227  int gp32;
228  int fp32;
229  /* MIPS architecture (CPU) type.  Changed by .set arch=FOO, the -march
230     command line option, and the default CPU.  */
231  int arch;
232  /* True if ".set sym32" is in effect.  */
233  bfd_boolean sym32;
234};
235
236/* True if -mgp32 was passed.  */
237static int file_mips_gp32 = -1;
238
239/* True if -mfp32 was passed.  */
240static int file_mips_fp32 = -1;
241
242/* This is the struct we use to hold the current set of options.  Note
243   that we must set the isa field to ISA_UNKNOWN and the ASE fields to
244   -1 to indicate that they have not been initialized.  */
245
246static struct mips_set_options mips_opts =
247{
248  ISA_UNKNOWN, -1, -1, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0, CPU_UNKNOWN, FALSE
249};
250
251/* These variables are filled in with the masks of registers used.
252   The object format code reads them and puts them in the appropriate
253   place.  */
254unsigned long mips_gprmask;
255unsigned long mips_cprmask[4];
256
257/* MIPS ISA we are using for this output file.  */
258static int file_mips_isa = ISA_UNKNOWN;
259
260/* True if -mips16 was passed or implied by arguments passed on the
261   command line (e.g., by -march).  */
262static int file_ase_mips16;
263
264/* True if -mips3d was passed or implied by arguments passed on the
265   command line (e.g., by -march).  */
266static int file_ase_mips3d;
267
268/* True if -mdmx was passed or implied by arguments passed on the
269   command line (e.g., by -march).  */
270static int file_ase_mdmx;
271
272/* True if -mdsp was passed or implied by arguments passed on the
273   command line (e.g., by -march).  */
274static int file_ase_dsp;
275
276/* True if -mmt was passed or implied by arguments passed on the
277   command line (e.g., by -march).  */
278static int file_ase_mt;
279
280/* The argument of the -march= flag.  The architecture we are assembling.  */
281static int file_mips_arch = CPU_UNKNOWN;
282static const char *mips_arch_string;
283
284/* The argument of the -mtune= flag.  The architecture for which we
285   are optimizing.  */
286static int mips_tune = CPU_UNKNOWN;
287static const char *mips_tune_string;
288
289/* True when generating 32-bit code for a 64-bit processor.  */
290static int mips_32bitmode = 0;
291
292/* True if the given ABI requires 32-bit registers.  */
293#define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
294
295/* Likewise 64-bit registers.  */
296#define ABI_NEEDS_64BIT_REGS(ABI) \
297  ((ABI) == N32_ABI 		  \
298   || (ABI) == N64_ABI		  \
299   || (ABI) == O64_ABI)
300
301/*  Return true if ISA supports 64 bit gp register instructions.  */
302#define ISA_HAS_64BIT_REGS(ISA) (    \
303   (ISA) == ISA_MIPS3                \
304   || (ISA) == ISA_MIPS4             \
305   || (ISA) == ISA_MIPS5             \
306   || (ISA) == ISA_MIPS64            \
307   || (ISA) == ISA_MIPS64R2          \
308   )
309
310/* Return true if ISA supports 64-bit right rotate (dror et al.)
311   instructions.  */
312#define ISA_HAS_DROR(ISA) (	\
313   (ISA) == ISA_MIPS64R2	\
314   )
315
316/* Return true if ISA supports 32-bit right rotate (ror et al.)
317   instructions.  */
318#define ISA_HAS_ROR(ISA) (	\
319   (ISA) == ISA_MIPS32R2	\
320   || (ISA) == ISA_MIPS64R2	\
321   )
322
323#define HAVE_32BIT_GPRS		                   \
324    (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
325
326#define HAVE_32BIT_FPRS                            \
327    (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
328
329#define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
330#define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
331
332#define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
333
334#define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
335
336/* True if relocations are stored in-place.  */
337#define HAVE_IN_PLACE_ADDENDS (!HAVE_NEWABI)
338
339/* The ABI-derived address size.  */
340#define HAVE_64BIT_ADDRESSES \
341  (HAVE_64BIT_GPRS && (mips_abi == EABI_ABI || mips_abi == N64_ABI))
342#define HAVE_32BIT_ADDRESSES (!HAVE_64BIT_ADDRESSES)
343
344/* The size of symbolic constants (i.e., expressions of the form
345   "SYMBOL" or "SYMBOL + OFFSET").  */
346#define HAVE_32BIT_SYMBOLS \
347  (HAVE_32BIT_ADDRESSES || !HAVE_64BIT_OBJECTS || mips_opts.sym32)
348#define HAVE_64BIT_SYMBOLS (!HAVE_32BIT_SYMBOLS)
349
350/* Addresses are loaded in different ways, depending on the address size
351   in use.  The n32 ABI Documentation also mandates the use of additions
352   with overflow checking, but existing implementations don't follow it.  */
353#define ADDRESS_ADD_INSN						\
354   (HAVE_32BIT_ADDRESSES ? "addu" : "daddu")
355
356#define ADDRESS_ADDI_INSN						\
357   (HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu")
358
359#define ADDRESS_LOAD_INSN						\
360   (HAVE_32BIT_ADDRESSES ? "lw" : "ld")
361
362#define ADDRESS_STORE_INSN						\
363   (HAVE_32BIT_ADDRESSES ? "sw" : "sd")
364
365/* Return true if the given CPU supports the MIPS16 ASE.  */
366#define CPU_HAS_MIPS16(cpu)						\
367   (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0		\
368    || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
369
370/* Return true if the given CPU supports the MIPS3D ASE.  */
371#define CPU_HAS_MIPS3D(cpu)	((cpu) == CPU_SB1      \
372				 )
373
374/* Return true if the given CPU supports the MDMX ASE.  */
375#define CPU_HAS_MDMX(cpu)	(FALSE                 \
376				 )
377
378/* Return true if the given CPU supports the DSP ASE.  */
379#define CPU_HAS_DSP(cpu)	(FALSE                 \
380				 )
381
382/* Return true if the given CPU supports the MT ASE.  */
383#define CPU_HAS_MT(cpu)		(FALSE                 \
384				 )
385
386/* True if CPU has a dror instruction.  */
387#define CPU_HAS_DROR(CPU)	((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
388
389/* True if CPU has a ror instruction.  */
390#define CPU_HAS_ROR(CPU)	CPU_HAS_DROR (CPU)
391
392/* True if mflo and mfhi can be immediately followed by instructions
393   which write to the HI and LO registers.
394
395   According to MIPS specifications, MIPS ISAs I, II, and III need
396   (at least) two instructions between the reads of HI/LO and
397   instructions which write them, and later ISAs do not.  Contradicting
398   the MIPS specifications, some MIPS IV processor user manuals (e.g.
399   the UM for the NEC Vr5000) document needing the instructions between
400   HI/LO reads and writes, as well.  Therefore, we declare only MIPS32,
401   MIPS64 and later ISAs to have the interlocks, plus any specific
402   earlier-ISA CPUs for which CPU documentation declares that the
403   instructions are really interlocked.  */
404#define hilo_interlocks \
405  (mips_opts.isa == ISA_MIPS32                        \
406   || mips_opts.isa == ISA_MIPS32R2                   \
407   || mips_opts.isa == ISA_MIPS64                     \
408   || mips_opts.isa == ISA_MIPS64R2                   \
409   || mips_opts.arch == CPU_R4010                     \
410   || mips_opts.arch == CPU_R10000                    \
411   || mips_opts.arch == CPU_R12000                    \
412   || mips_opts.arch == CPU_RM7000                    \
413   || mips_opts.arch == CPU_VR5500                    \
414   )
415
416/* Whether the processor uses hardware interlocks to protect reads
417   from the GPRs after they are loaded from memory, and thus does not
418   require nops to be inserted.  This applies to instructions marked
419   INSN_LOAD_MEMORY_DELAY.  These nops are only required at MIPS ISA
420   level I.  */
421#define gpr_interlocks \
422  (mips_opts.isa != ISA_MIPS1  \
423   || mips_opts.arch == CPU_R3900)
424
425/* Whether the processor uses hardware interlocks to avoid delays
426   required by coprocessor instructions, and thus does not require
427   nops to be inserted.  This applies to instructions marked
428   INSN_LOAD_COPROC_DELAY, INSN_COPROC_MOVE_DELAY, and to delays
429   between instructions marked INSN_WRITE_COND_CODE and ones marked
430   INSN_READ_COND_CODE.  These nops are only required at MIPS ISA
431   levels I, II, and III.  */
432/* Itbl support may require additional care here.  */
433#define cop_interlocks                                \
434  ((mips_opts.isa != ISA_MIPS1                        \
435    && mips_opts.isa != ISA_MIPS2                     \
436    && mips_opts.isa != ISA_MIPS3)                    \
437   || mips_opts.arch == CPU_R4300                     \
438   )
439
440/* Whether the processor uses hardware interlocks to protect reads
441   from coprocessor registers after they are loaded from memory, and
442   thus does not require nops to be inserted.  This applies to
443   instructions marked INSN_COPROC_MEMORY_DELAY.  These nops are only
444   requires at MIPS ISA level I.  */
445#define cop_mem_interlocks (mips_opts.isa != ISA_MIPS1)
446
447/* Is this a mfhi or mflo instruction?  */
448#define MF_HILO_INSN(PINFO) \
449          ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
450
451/* MIPS PIC level.  */
452
453enum mips_pic_level mips_pic;
454
455/* 1 if we should generate 32 bit offsets from the $gp register in
456   SVR4_PIC mode.  Currently has no meaning in other modes.  */
457static int mips_big_got = 0;
458
459/* 1 if trap instructions should used for overflow rather than break
460   instructions.  */
461static int mips_trap = 0;
462
463/* 1 if double width floating point constants should not be constructed
464   by assembling two single width halves into two single width floating
465   point registers which just happen to alias the double width destination
466   register.  On some architectures this aliasing can be disabled by a bit
467   in the status register, and the setting of this bit cannot be determined
468   automatically at assemble time.  */
469static int mips_disable_float_construction;
470
471/* Non-zero if any .set noreorder directives were used.  */
472
473static int mips_any_noreorder;
474
475/* Non-zero if nops should be inserted when the register referenced in
476   an mfhi/mflo instruction is read in the next two instructions.  */
477static int mips_7000_hilo_fix;
478
479/* The size of the small data section.  */
480static unsigned int g_switch_value = 8;
481/* Whether the -G option was used.  */
482static int g_switch_seen = 0;
483
484#define N_RMASK 0xc4
485#define N_VFP   0xd4
486
487/* If we can determine in advance that GP optimization won't be
488   possible, we can skip the relaxation stuff that tries to produce
489   GP-relative references.  This makes delay slot optimization work
490   better.
491
492   This function can only provide a guess, but it seems to work for
493   gcc output.  It needs to guess right for gcc, otherwise gcc
494   will put what it thinks is a GP-relative instruction in a branch
495   delay slot.
496
497   I don't know if a fix is needed for the SVR4_PIC mode.  I've only
498   fixed it for the non-PIC mode.  KR 95/04/07  */
499static int nopic_need_relax (symbolS *, int);
500
501/* handle of the OPCODE hash table */
502static struct hash_control *op_hash = NULL;
503
504/* The opcode hash table we use for the mips16.  */
505static struct hash_control *mips16_op_hash = NULL;
506
507/* This array holds the chars that always start a comment.  If the
508    pre-processor is disabled, these aren't very useful */
509const char comment_chars[] = "#";
510
511/* This array holds the chars that only start a comment at the beginning of
512   a line.  If the line seems to have the form '# 123 filename'
513   .line and .file directives will appear in the pre-processed output */
514/* Note that input_file.c hand checks for '#' at the beginning of the
515   first line of the input file.  This is because the compiler outputs
516   #NO_APP at the beginning of its output.  */
517/* Also note that C style comments are always supported.  */
518const char line_comment_chars[] = "#";
519
520/* This array holds machine specific line separator characters.  */
521const char line_separator_chars[] = ";";
522
523/* Chars that can be used to separate mant from exp in floating point nums */
524const char EXP_CHARS[] = "eE";
525
526/* Chars that mean this number is a floating point constant */
527/* As in 0f12.456 */
528/* or    0d1.2345e12 */
529const char FLT_CHARS[] = "rRsSfFdDxXpP";
530
531/* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
532   changed in read.c .  Ideally it shouldn't have to know about it at all,
533   but nothing is ideal around here.
534 */
535
536static char *insn_error;
537
538static int auto_align = 1;
539
540/* When outputting SVR4 PIC code, the assembler needs to know the
541   offset in the stack frame from which to restore the $gp register.
542   This is set by the .cprestore pseudo-op, and saved in this
543   variable.  */
544static offsetT mips_cprestore_offset = -1;
545
546/* Similar for NewABI PIC code, where $gp is callee-saved.  NewABI has some
547   more optimizations, it can use a register value instead of a memory-saved
548   offset and even an other register than $gp as global pointer.  */
549static offsetT mips_cpreturn_offset = -1;
550static int mips_cpreturn_register = -1;
551static int mips_gp_register = GP;
552static int mips_gprel_offset = 0;
553
554/* Whether mips_cprestore_offset has been set in the current function
555   (or whether it has already been warned about, if not).  */
556static int mips_cprestore_valid = 0;
557
558/* This is the register which holds the stack frame, as set by the
559   .frame pseudo-op.  This is needed to implement .cprestore.  */
560static int mips_frame_reg = SP;
561
562/* Whether mips_frame_reg has been set in the current function
563   (or whether it has already been warned about, if not).  */
564static int mips_frame_reg_valid = 0;
565
566/* To output NOP instructions correctly, we need to keep information
567   about the previous two instructions.  */
568
569/* Whether we are optimizing.  The default value of 2 means to remove
570   unneeded NOPs and swap branch instructions when possible.  A value
571   of 1 means to not swap branches.  A value of 0 means to always
572   insert NOPs.  */
573static int mips_optimize = 2;
574
575/* Debugging level.  -g sets this to 2.  -gN sets this to N.  -g0 is
576   equivalent to seeing no -g option at all.  */
577static int mips_debug = 0;
578
579/* The maximum number of NOPs needed to avoid the VR4130 mflo/mfhi errata.  */
580#define MAX_VR4130_NOPS 4
581
582/* The maximum number of NOPs needed to fill delay slots.  */
583#define MAX_DELAY_NOPS 2
584
585/* The maximum number of NOPs needed for any purpose.  */
586#define MAX_NOPS 4
587
588/* A list of previous instructions, with index 0 being the most recent.
589   We need to look back MAX_NOPS instructions when filling delay slots
590   or working around processor errata.  We need to look back one
591   instruction further if we're thinking about using history[0] to
592   fill a branch delay slot.  */
593static struct mips_cl_insn history[1 + MAX_NOPS];
594
595/* Nop instructions used by emit_nop.  */
596static struct mips_cl_insn nop_insn, mips16_nop_insn;
597
598/* The appropriate nop for the current mode.  */
599#define NOP_INSN (mips_opts.mips16 ? &mips16_nop_insn : &nop_insn)
600
601/* If this is set, it points to a frag holding nop instructions which
602   were inserted before the start of a noreorder section.  If those
603   nops turn out to be unnecessary, the size of the frag can be
604   decreased.  */
605static fragS *prev_nop_frag;
606
607/* The number of nop instructions we created in prev_nop_frag.  */
608static int prev_nop_frag_holds;
609
610/* The number of nop instructions that we know we need in
611   prev_nop_frag.  */
612static int prev_nop_frag_required;
613
614/* The number of instructions we've seen since prev_nop_frag.  */
615static int prev_nop_frag_since;
616
617/* For ECOFF and ELF, relocations against symbols are done in two
618   parts, with a HI relocation and a LO relocation.  Each relocation
619   has only 16 bits of space to store an addend.  This means that in
620   order for the linker to handle carries correctly, it must be able
621   to locate both the HI and the LO relocation.  This means that the
622   relocations must appear in order in the relocation table.
623
624   In order to implement this, we keep track of each unmatched HI
625   relocation.  We then sort them so that they immediately precede the
626   corresponding LO relocation.  */
627
628struct mips_hi_fixup
629{
630  /* Next HI fixup.  */
631  struct mips_hi_fixup *next;
632  /* This fixup.  */
633  fixS *fixp;
634  /* The section this fixup is in.  */
635  segT seg;
636};
637
638/* The list of unmatched HI relocs.  */
639
640static struct mips_hi_fixup *mips_hi_fixup_list;
641
642/* The frag containing the last explicit relocation operator.
643   Null if explicit relocations have not been used.  */
644
645static fragS *prev_reloc_op_frag;
646
647/* Map normal MIPS register numbers to mips16 register numbers.  */
648
649#define X ILLEGAL_REG
650static const int mips32_to_16_reg_map[] =
651{
652  X, X, 2, 3, 4, 5, 6, 7,
653  X, X, X, X, X, X, X, X,
654  0, 1, X, X, X, X, X, X,
655  X, X, X, X, X, X, X, X
656};
657#undef X
658
659/* Map mips16 register numbers to normal MIPS register numbers.  */
660
661static const unsigned int mips16_to_32_reg_map[] =
662{
663  16, 17, 2, 3, 4, 5, 6, 7
664};
665
666/* Classifies the kind of instructions we're interested in when
667   implementing -mfix-vr4120.  */
668enum fix_vr4120_class {
669  FIX_VR4120_MACC,
670  FIX_VR4120_DMACC,
671  FIX_VR4120_MULT,
672  FIX_VR4120_DMULT,
673  FIX_VR4120_DIV,
674  FIX_VR4120_MTHILO,
675  NUM_FIX_VR4120_CLASSES
676};
677
678/* Given two FIX_VR4120_* values X and Y, bit Y of element X is set if
679   there must be at least one other instruction between an instruction
680   of type X and an instruction of type Y.  */
681static unsigned int vr4120_conflicts[NUM_FIX_VR4120_CLASSES];
682
683/* True if -mfix-vr4120 is in force.  */
684static int mips_fix_vr4120;
685
686/* ...likewise -mfix-vr4130.  */
687static int mips_fix_vr4130;
688
689/* We don't relax branches by default, since this causes us to expand
690   `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
691   fail to compute the offset before expanding the macro to the most
692   efficient expansion.  */
693
694static int mips_relax_branch;
695
696/* The expansion of many macros depends on the type of symbol that
697   they refer to.  For example, when generating position-dependent code,
698   a macro that refers to a symbol may have two different expansions,
699   one which uses GP-relative addresses and one which uses absolute
700   addresses.  When generating SVR4-style PIC, a macro may have
701   different expansions for local and global symbols.
702
703   We handle these situations by generating both sequences and putting
704   them in variant frags.  In position-dependent code, the first sequence
705   will be the GP-relative one and the second sequence will be the
706   absolute one.  In SVR4 PIC, the first sequence will be for global
707   symbols and the second will be for local symbols.
708
709   The frag's "subtype" is RELAX_ENCODE (FIRST, SECOND), where FIRST and
710   SECOND are the lengths of the two sequences in bytes.  These fields
711   can be extracted using RELAX_FIRST() and RELAX_SECOND().  In addition,
712   the subtype has the following flags:
713
714   RELAX_USE_SECOND
715	Set if it has been decided that we should use the second
716	sequence instead of the first.
717
718   RELAX_SECOND_LONGER
719	Set in the first variant frag if the macro's second implementation
720	is longer than its first.  This refers to the macro as a whole,
721	not an individual relaxation.
722
723   RELAX_NOMACRO
724	Set in the first variant frag if the macro appeared in a .set nomacro
725	block and if one alternative requires a warning but the other does not.
726
727   RELAX_DELAY_SLOT
728	Like RELAX_NOMACRO, but indicates that the macro appears in a branch
729	delay slot.
730
731   The frag's "opcode" points to the first fixup for relaxable code.
732
733   Relaxable macros are generated using a sequence such as:
734
735      relax_start (SYMBOL);
736      ... generate first expansion ...
737      relax_switch ();
738      ... generate second expansion ...
739      relax_end ();
740
741   The code and fixups for the unwanted alternative are discarded
742   by md_convert_frag.  */
743#define RELAX_ENCODE(FIRST, SECOND) (((FIRST) << 8) | (SECOND))
744
745#define RELAX_FIRST(X) (((X) >> 8) & 0xff)
746#define RELAX_SECOND(X) ((X) & 0xff)
747#define RELAX_USE_SECOND 0x10000
748#define RELAX_SECOND_LONGER 0x20000
749#define RELAX_NOMACRO 0x40000
750#define RELAX_DELAY_SLOT 0x80000
751
752/* Branch without likely bit.  If label is out of range, we turn:
753
754 	beq reg1, reg2, label
755	delay slot
756
757   into
758
759        bne reg1, reg2, 0f
760        nop
761        j label
762     0: delay slot
763
764   with the following opcode replacements:
765
766	beq <-> bne
767	blez <-> bgtz
768	bltz <-> bgez
769	bc1f <-> bc1t
770
771	bltzal <-> bgezal  (with jal label instead of j label)
772
773   Even though keeping the delay slot instruction in the delay slot of
774   the branch would be more efficient, it would be very tricky to do
775   correctly, because we'd have to introduce a variable frag *after*
776   the delay slot instruction, and expand that instead.  Let's do it
777   the easy way for now, even if the branch-not-taken case now costs
778   one additional instruction.  Out-of-range branches are not supposed
779   to be common, anyway.
780
781   Branch likely.  If label is out of range, we turn:
782
783	beql reg1, reg2, label
784	delay slot (annulled if branch not taken)
785
786   into
787
788        beql reg1, reg2, 1f
789        nop
790        beql $0, $0, 2f
791        nop
792     1: j[al] label
793        delay slot (executed only if branch taken)
794     2:
795
796   It would be possible to generate a shorter sequence by losing the
797   likely bit, generating something like:
798
799	bne reg1, reg2, 0f
800	nop
801	j[al] label
802	delay slot (executed only if branch taken)
803     0:
804
805	beql -> bne
806	bnel -> beq
807	blezl -> bgtz
808	bgtzl -> blez
809	bltzl -> bgez
810	bgezl -> bltz
811	bc1fl -> bc1t
812	bc1tl -> bc1f
813
814	bltzall -> bgezal  (with jal label instead of j label)
815	bgezall -> bltzal  (ditto)
816
817
818   but it's not clear that it would actually improve performance.  */
819#define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
820  ((relax_substateT) \
821   (0xc0000000 \
822    | ((toofar) ? 1 : 0) \
823    | ((link) ? 2 : 0) \
824    | ((likely) ? 4 : 0) \
825    | ((uncond) ? 8 : 0)))
826#define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
827#define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
828#define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
829#define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
830#define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
831
832/* For mips16 code, we use an entirely different form of relaxation.
833   mips16 supports two versions of most instructions which take
834   immediate values: a small one which takes some small value, and a
835   larger one which takes a 16 bit value.  Since branches also follow
836   this pattern, relaxing these values is required.
837
838   We can assemble both mips16 and normal MIPS code in a single
839   object.  Therefore, we need to support this type of relaxation at
840   the same time that we support the relaxation described above.  We
841   use the high bit of the subtype field to distinguish these cases.
842
843   The information we store for this type of relaxation is the
844   argument code found in the opcode file for this relocation, whether
845   the user explicitly requested a small or extended form, and whether
846   the relocation is in a jump or jal delay slot.  That tells us the
847   size of the value, and how it should be stored.  We also store
848   whether the fragment is considered to be extended or not.  We also
849   store whether this is known to be a branch to a different section,
850   whether we have tried to relax this frag yet, and whether we have
851   ever extended a PC relative fragment because of a shift count.  */
852#define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot)	\
853  (0x80000000							\
854   | ((type) & 0xff)						\
855   | ((small) ? 0x100 : 0)					\
856   | ((ext) ? 0x200 : 0)					\
857   | ((dslot) ? 0x400 : 0)					\
858   | ((jal_dslot) ? 0x800 : 0))
859#define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
860#define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
861#define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
862#define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
863#define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
864#define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
865#define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
866#define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
867#define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
868#define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
869#define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
870#define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
871
872/* Is the given value a sign-extended 32-bit value?  */
873#define IS_SEXT_32BIT_NUM(x)						\
874  (((x) &~ (offsetT) 0x7fffffff) == 0					\
875   || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
876
877/* Is the given value a sign-extended 16-bit value?  */
878#define IS_SEXT_16BIT_NUM(x)						\
879  (((x) &~ (offsetT) 0x7fff) == 0					\
880   || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
881
882/* Is the given value a zero-extended 32-bit value?  Or a negated one?  */
883#define IS_ZEXT_32BIT_NUM(x)						\
884  (((x) &~ (offsetT) 0xffffffff) == 0					\
885   || (((x) &~ (offsetT) 0xffffffff) == ~ (offsetT) 0xffffffff))
886
887/* Replace bits MASK << SHIFT of STRUCT with the equivalent bits in
888   VALUE << SHIFT.  VALUE is evaluated exactly once.  */
889#define INSERT_BITS(STRUCT, VALUE, MASK, SHIFT) \
890  (STRUCT) = (((STRUCT) & ~((MASK) << (SHIFT))) \
891	      | (((VALUE) & (MASK)) << (SHIFT)))
892
893/* Extract bits MASK << SHIFT from STRUCT and shift them right
894   SHIFT places.  */
895#define EXTRACT_BITS(STRUCT, MASK, SHIFT) \
896  (((STRUCT) >> (SHIFT)) & (MASK))
897
898/* Change INSN's opcode so that the operand given by FIELD has value VALUE.
899   INSN is a mips_cl_insn structure and VALUE is evaluated exactly once.
900
901   include/opcode/mips.h specifies operand fields using the macros
902   OP_MASK_<FIELD> and OP_SH_<FIELD>.  The MIPS16 equivalents start
903   with "MIPS16OP" instead of "OP".  */
904#define INSERT_OPERAND(FIELD, INSN, VALUE) \
905  INSERT_BITS ((INSN).insn_opcode, VALUE, OP_MASK_##FIELD, OP_SH_##FIELD)
906#define MIPS16_INSERT_OPERAND(FIELD, INSN, VALUE) \
907  INSERT_BITS ((INSN).insn_opcode, VALUE, \
908		MIPS16OP_MASK_##FIELD, MIPS16OP_SH_##FIELD)
909
910/* Extract the operand given by FIELD from mips_cl_insn INSN.  */
911#define EXTRACT_OPERAND(FIELD, INSN) \
912  EXTRACT_BITS ((INSN).insn_opcode, OP_MASK_##FIELD, OP_SH_##FIELD)
913#define MIPS16_EXTRACT_OPERAND(FIELD, INSN) \
914  EXTRACT_BITS ((INSN).insn_opcode, \
915		MIPS16OP_MASK_##FIELD, \
916		MIPS16OP_SH_##FIELD)
917
918/* Global variables used when generating relaxable macros.  See the
919   comment above RELAX_ENCODE for more details about how relaxation
920   is used.  */
921static struct {
922  /* 0 if we're not emitting a relaxable macro.
923     1 if we're emitting the first of the two relaxation alternatives.
924     2 if we're emitting the second alternative.  */
925  int sequence;
926
927  /* The first relaxable fixup in the current frag.  (In other words,
928     the first fixup that refers to relaxable code.)  */
929  fixS *first_fixup;
930
931  /* sizes[0] says how many bytes of the first alternative are stored in
932     the current frag.  Likewise sizes[1] for the second alternative.  */
933  unsigned int sizes[2];
934
935  /* The symbol on which the choice of sequence depends.  */
936  symbolS *symbol;
937} mips_relax;
938
939/* Global variables used to decide whether a macro needs a warning.  */
940static struct {
941  /* True if the macro is in a branch delay slot.  */
942  bfd_boolean delay_slot_p;
943
944  /* For relaxable macros, sizes[0] is the length of the first alternative
945     in bytes and sizes[1] is the length of the second alternative.
946     For non-relaxable macros, both elements give the length of the
947     macro in bytes.  */
948  unsigned int sizes[2];
949
950  /* The first variant frag for this macro.  */
951  fragS *first_frag;
952} mips_macro_warning;
953
954/* Prototypes for static functions.  */
955
956#define internalError()							\
957    as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
958
959enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
960
961static void append_insn
962  (struct mips_cl_insn *ip, expressionS *p, bfd_reloc_code_real_type *r);
963static void mips_no_prev_insn (void);
964static void mips16_macro_build
965  (expressionS *, const char *, const char *, va_list);
966static void load_register (int, expressionS *, int);
967static void macro_start (void);
968static void macro_end (void);
969static void macro (struct mips_cl_insn * ip);
970static void mips16_macro (struct mips_cl_insn * ip);
971#ifdef LOSING_COMPILER
972static void macro2 (struct mips_cl_insn * ip);
973#endif
974static void mips_ip (char *str, struct mips_cl_insn * ip);
975static void mips16_ip (char *str, struct mips_cl_insn * ip);
976static void mips16_immed
977  (char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean, bfd_boolean,
978   unsigned long *, bfd_boolean *, unsigned short *);
979static size_t my_getSmallExpression
980  (expressionS *, bfd_reloc_code_real_type *, char *);
981static void my_getExpression (expressionS *, char *);
982static void s_align (int);
983static void s_change_sec (int);
984static void s_change_section (int);
985static void s_cons (int);
986static void s_float_cons (int);
987static void s_mips_globl (int);
988static void s_option (int);
989static void s_mipsset (int);
990static void s_abicalls (int);
991static void s_cpload (int);
992static void s_cpsetup (int);
993static void s_cplocal (int);
994static void s_cprestore (int);
995static void s_cpreturn (int);
996static void s_gpvalue (int);
997static void s_gpword (int);
998static void s_gpdword (int);
999static void s_cpadd (int);
1000static void s_insn (int);
1001static void md_obj_begin (void);
1002static void md_obj_end (void);
1003static void s_mips_ent (int);
1004static void s_mips_end (int);
1005static void s_mips_frame (int);
1006static void s_mips_mask (int reg_type);
1007static void s_mips_stab (int);
1008static void s_mips_weakext (int);
1009static void s_mips_file (int);
1010static void s_mips_loc (int);
1011static bfd_boolean pic_need_relax (symbolS *, asection *);
1012static int relaxed_branch_length (fragS *, asection *, int);
1013static int validate_mips_insn (const struct mips_opcode *);
1014
1015/* Table and functions used to map between CPU/ISA names, and
1016   ISA levels, and CPU numbers.  */
1017
1018struct mips_cpu_info
1019{
1020  const char *name;           /* CPU or ISA name.  */
1021  int is_isa;                 /* Is this an ISA?  (If 0, a CPU.) */
1022  int isa;                    /* ISA level.  */
1023  int cpu;                    /* CPU number (default CPU if ISA).  */
1024};
1025
1026static const struct mips_cpu_info *mips_parse_cpu (const char *, const char *);
1027static const struct mips_cpu_info *mips_cpu_info_from_isa (int);
1028static const struct mips_cpu_info *mips_cpu_info_from_arch (int);
1029
1030/* Pseudo-op table.
1031
1032   The following pseudo-ops from the Kane and Heinrich MIPS book
1033   should be defined here, but are currently unsupported: .alias,
1034   .galive, .gjaldef, .gjrlive, .livereg, .noalias.
1035
1036   The following pseudo-ops from the Kane and Heinrich MIPS book are
1037   specific to the type of debugging information being generated, and
1038   should be defined by the object format: .aent, .begin, .bend,
1039   .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
1040   .vreg.
1041
1042   The following pseudo-ops from the Kane and Heinrich MIPS book are
1043   not MIPS CPU specific, but are also not specific to the object file
1044   format.  This file is probably the best place to define them, but
1045   they are not currently supported: .asm0, .endr, .lab, .repeat,
1046   .struct.  */
1047
1048static const pseudo_typeS mips_pseudo_table[] =
1049{
1050  /* MIPS specific pseudo-ops.  */
1051  {"option", s_option, 0},
1052  {"set", s_mipsset, 0},
1053  {"rdata", s_change_sec, 'r'},
1054  {"sdata", s_change_sec, 's'},
1055  {"livereg", s_ignore, 0},
1056  {"abicalls", s_abicalls, 0},
1057  {"cpload", s_cpload, 0},
1058  {"cpsetup", s_cpsetup, 0},
1059  {"cplocal", s_cplocal, 0},
1060  {"cprestore", s_cprestore, 0},
1061  {"cpreturn", s_cpreturn, 0},
1062  {"gpvalue", s_gpvalue, 0},
1063  {"gpword", s_gpword, 0},
1064  {"gpdword", s_gpdword, 0},
1065  {"cpadd", s_cpadd, 0},
1066  {"insn", s_insn, 0},
1067
1068  /* Relatively generic pseudo-ops that happen to be used on MIPS
1069     chips.  */
1070  {"asciiz", stringer, 1},
1071  {"bss", s_change_sec, 'b'},
1072  {"err", s_err, 0},
1073  {"half", s_cons, 1},
1074  {"dword", s_cons, 3},
1075  {"weakext", s_mips_weakext, 0},
1076
1077  /* These pseudo-ops are defined in read.c, but must be overridden
1078     here for one reason or another.  */
1079  {"align", s_align, 0},
1080  {"byte", s_cons, 0},
1081  {"data", s_change_sec, 'd'},
1082  {"double", s_float_cons, 'd'},
1083  {"float", s_float_cons, 'f'},
1084  {"globl", s_mips_globl, 0},
1085  {"global", s_mips_globl, 0},
1086  {"hword", s_cons, 1},
1087  {"int", s_cons, 2},
1088  {"long", s_cons, 2},
1089  {"octa", s_cons, 4},
1090  {"quad", s_cons, 3},
1091  {"section", s_change_section, 0},
1092  {"short", s_cons, 1},
1093  {"single", s_float_cons, 'f'},
1094  {"stabn", s_mips_stab, 'n'},
1095  {"text", s_change_sec, 't'},
1096  {"word", s_cons, 2},
1097
1098  { "extern", ecoff_directive_extern, 0},
1099
1100  { NULL, NULL, 0 },
1101};
1102
1103static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1104{
1105  /* These pseudo-ops should be defined by the object file format.
1106     However, a.out doesn't support them, so we have versions here.  */
1107  {"aent", s_mips_ent, 1},
1108  {"bgnb", s_ignore, 0},
1109  {"end", s_mips_end, 0},
1110  {"endb", s_ignore, 0},
1111  {"ent", s_mips_ent, 0},
1112  {"file", s_mips_file, 0},
1113  {"fmask", s_mips_mask, 'F'},
1114  {"frame", s_mips_frame, 0},
1115  {"loc", s_mips_loc, 0},
1116  {"mask", s_mips_mask, 'R'},
1117  {"verstamp", s_ignore, 0},
1118  { NULL, NULL, 0 },
1119};
1120
1121extern void pop_insert (const pseudo_typeS *);
1122
1123void
1124mips_pop_insert (void)
1125{
1126  pop_insert (mips_pseudo_table);
1127  if (! ECOFF_DEBUGGING)
1128    pop_insert (mips_nonecoff_pseudo_table);
1129}
1130
1131/* Symbols labelling the current insn.  */
1132
1133struct insn_label_list
1134{
1135  struct insn_label_list *next;
1136  symbolS *label;
1137};
1138
1139static struct insn_label_list *insn_labels;
1140static struct insn_label_list *free_insn_labels;
1141
1142static void mips_clear_insn_labels (void);
1143
1144static inline void
1145mips_clear_insn_labels (void)
1146{
1147  register struct insn_label_list **pl;
1148
1149  for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1150    ;
1151  *pl = insn_labels;
1152  insn_labels = NULL;
1153}
1154
1155static char *expr_end;
1156
1157/* Expressions which appear in instructions.  These are set by
1158   mips_ip.  */
1159
1160static expressionS imm_expr;
1161static expressionS imm2_expr;
1162static expressionS offset_expr;
1163
1164/* Relocs associated with imm_expr and offset_expr.  */
1165
1166static bfd_reloc_code_real_type imm_reloc[3]
1167  = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1168static bfd_reloc_code_real_type offset_reloc[3]
1169  = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1170
1171/* These are set by mips16_ip if an explicit extension is used.  */
1172
1173static bfd_boolean mips16_small, mips16_ext;
1174
1175#ifdef OBJ_ELF
1176/* The pdr segment for per procedure frame/regmask info.  Not used for
1177   ECOFF debugging.  */
1178
1179static segT pdr_seg;
1180#endif
1181
1182/* The default target format to use.  */
1183
1184const char *
1185mips_target_format (void)
1186{
1187  switch (OUTPUT_FLAVOR)
1188    {
1189    case bfd_target_ecoff_flavour:
1190      return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1191    case bfd_target_coff_flavour:
1192      return "pe-mips";
1193    case bfd_target_elf_flavour:
1194#ifdef TE_VXWORKS
1195      if (!HAVE_64BIT_OBJECTS && !HAVE_NEWABI)
1196	return (target_big_endian
1197		? "elf32-bigmips-vxworks"
1198		: "elf32-littlemips-vxworks");
1199#endif
1200#ifdef TE_TMIPS
1201      /* This is traditional mips.  */
1202      return (target_big_endian
1203	      ? (HAVE_64BIT_OBJECTS
1204		 ? "elf64-tradbigmips"
1205		 : (HAVE_NEWABI
1206		    ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1207	      : (HAVE_64BIT_OBJECTS
1208		 ? "elf64-tradlittlemips"
1209		 : (HAVE_NEWABI
1210		    ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1211#else
1212      return (target_big_endian
1213	      ? (HAVE_64BIT_OBJECTS
1214		 ? "elf64-bigmips"
1215		 : (HAVE_NEWABI
1216		    ? "elf32-nbigmips" : "elf32-bigmips"))
1217	      : (HAVE_64BIT_OBJECTS
1218		 ? "elf64-littlemips"
1219		 : (HAVE_NEWABI
1220		    ? "elf32-nlittlemips" : "elf32-littlemips")));
1221#endif
1222    default:
1223      abort ();
1224      return NULL;
1225    }
1226}
1227
1228/* Return the length of instruction INSN.  */
1229
1230static inline unsigned int
1231insn_length (const struct mips_cl_insn *insn)
1232{
1233  if (!mips_opts.mips16)
1234    return 4;
1235  return insn->mips16_absolute_jump_p || insn->use_extend ? 4 : 2;
1236}
1237
1238/* Initialise INSN from opcode entry MO.  Leave its position unspecified.  */
1239
1240static void
1241create_insn (struct mips_cl_insn *insn, const struct mips_opcode *mo)
1242{
1243  size_t i;
1244
1245  insn->insn_mo = mo;
1246  insn->use_extend = FALSE;
1247  insn->extend = 0;
1248  insn->insn_opcode = mo->match;
1249  insn->frag = NULL;
1250  insn->where = 0;
1251  for (i = 0; i < ARRAY_SIZE (insn->fixp); i++)
1252    insn->fixp[i] = NULL;
1253  insn->fixed_p = (mips_opts.noreorder > 0);
1254  insn->noreorder_p = (mips_opts.noreorder > 0);
1255  insn->mips16_absolute_jump_p = 0;
1256}
1257
1258/* Install INSN at the location specified by its "frag" and "where" fields.  */
1259
1260static void
1261install_insn (const struct mips_cl_insn *insn)
1262{
1263  char *f = insn->frag->fr_literal + insn->where;
1264  if (!mips_opts.mips16)
1265    md_number_to_chars (f, insn->insn_opcode, 4);
1266  else if (insn->mips16_absolute_jump_p)
1267    {
1268      md_number_to_chars (f, insn->insn_opcode >> 16, 2);
1269      md_number_to_chars (f + 2, insn->insn_opcode & 0xffff, 2);
1270    }
1271  else
1272    {
1273      if (insn->use_extend)
1274	{
1275	  md_number_to_chars (f, 0xf000 | insn->extend, 2);
1276	  f += 2;
1277	}
1278      md_number_to_chars (f, insn->insn_opcode, 2);
1279    }
1280}
1281
1282/* Move INSN to offset WHERE in FRAG.  Adjust the fixups accordingly
1283   and install the opcode in the new location.  */
1284
1285static void
1286move_insn (struct mips_cl_insn *insn, fragS *frag, long where)
1287{
1288  size_t i;
1289
1290  insn->frag = frag;
1291  insn->where = where;
1292  for (i = 0; i < ARRAY_SIZE (insn->fixp); i++)
1293    if (insn->fixp[i] != NULL)
1294      {
1295	insn->fixp[i]->fx_frag = frag;
1296	insn->fixp[i]->fx_where = where;
1297      }
1298  install_insn (insn);
1299}
1300
1301/* Add INSN to the end of the output.  */
1302
1303static void
1304add_fixed_insn (struct mips_cl_insn *insn)
1305{
1306  char *f = frag_more (insn_length (insn));
1307  move_insn (insn, frag_now, f - frag_now->fr_literal);
1308}
1309
1310/* Start a variant frag and move INSN to the start of the variant part,
1311   marking it as fixed.  The other arguments are as for frag_var.  */
1312
1313static void
1314add_relaxed_insn (struct mips_cl_insn *insn, int max_chars, int var,
1315		  relax_substateT subtype, symbolS *symbol, offsetT offset)
1316{
1317  frag_grow (max_chars);
1318  move_insn (insn, frag_now, frag_more (0) - frag_now->fr_literal);
1319  insn->fixed_p = 1;
1320  frag_var (rs_machine_dependent, max_chars, var,
1321	    subtype, symbol, offset, NULL);
1322}
1323
1324/* Insert N copies of INSN into the history buffer, starting at
1325   position FIRST.  Neither FIRST nor N need to be clipped.  */
1326
1327static void
1328insert_into_history (unsigned int first, unsigned int n,
1329		     const struct mips_cl_insn *insn)
1330{
1331  if (mips_relax.sequence != 2)
1332    {
1333      unsigned int i;
1334
1335      for (i = ARRAY_SIZE (history); i-- > first;)
1336	if (i >= first + n)
1337	  history[i] = history[i - n];
1338	else
1339	  history[i] = *insn;
1340    }
1341}
1342
1343/* Emit a nop instruction, recording it in the history buffer.  */
1344
1345static void
1346emit_nop (void)
1347{
1348  add_fixed_insn (NOP_INSN);
1349  insert_into_history (0, 1, NOP_INSN);
1350}
1351
1352/* Initialize vr4120_conflicts.  There is a bit of duplication here:
1353   the idea is to make it obvious at a glance that each errata is
1354   included.  */
1355
1356static void
1357init_vr4120_conflicts (void)
1358{
1359#define CONFLICT(FIRST, SECOND) \
1360    vr4120_conflicts[FIX_VR4120_##FIRST] |= 1 << FIX_VR4120_##SECOND
1361
1362  /* Errata 21 - [D]DIV[U] after [D]MACC */
1363  CONFLICT (MACC, DIV);
1364  CONFLICT (DMACC, DIV);
1365
1366  /* Errata 23 - Continuous DMULT[U]/DMACC instructions.  */
1367  CONFLICT (DMULT, DMULT);
1368  CONFLICT (DMULT, DMACC);
1369  CONFLICT (DMACC, DMULT);
1370  CONFLICT (DMACC, DMACC);
1371
1372  /* Errata 24 - MT{LO,HI} after [D]MACC */
1373  CONFLICT (MACC, MTHILO);
1374  CONFLICT (DMACC, MTHILO);
1375
1376  /* VR4181A errata MD(1): "If a MULT, MULTU, DMULT or DMULTU
1377     instruction is executed immediately after a MACC or DMACC
1378     instruction, the result of [either instruction] is incorrect."  */
1379  CONFLICT (MACC, MULT);
1380  CONFLICT (MACC, DMULT);
1381  CONFLICT (DMACC, MULT);
1382  CONFLICT (DMACC, DMULT);
1383
1384  /* VR4181A errata MD(4): "If a MACC or DMACC instruction is
1385     executed immediately after a DMULT, DMULTU, DIV, DIVU,
1386     DDIV or DDIVU instruction, the result of the MACC or
1387     DMACC instruction is incorrect.".  */
1388  CONFLICT (DMULT, MACC);
1389  CONFLICT (DMULT, DMACC);
1390  CONFLICT (DIV, MACC);
1391  CONFLICT (DIV, DMACC);
1392
1393#undef CONFLICT
1394}
1395
1396/* This function is called once, at assembler startup time.  It should
1397   set up all the tables, etc. that the MD part of the assembler will need.  */
1398
1399void
1400md_begin (void)
1401{
1402  register const char *retval = NULL;
1403  int i = 0;
1404  int broken = 0;
1405
1406  if (mips_pic != NO_PIC)
1407    {
1408      if (g_switch_seen && g_switch_value != 0)
1409	as_bad (_("-G may not be used in position-independent code"));
1410      g_switch_value = 0;
1411    }
1412
1413  if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, file_mips_arch))
1414    as_warn (_("Could not set architecture and machine"));
1415
1416  op_hash = hash_new ();
1417
1418  for (i = 0; i < NUMOPCODES;)
1419    {
1420      const char *name = mips_opcodes[i].name;
1421
1422      retval = hash_insert (op_hash, name, (void *) &mips_opcodes[i]);
1423      if (retval != NULL)
1424	{
1425	  fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1426		   mips_opcodes[i].name, retval);
1427	  /* Probably a memory allocation problem?  Give up now.  */
1428	  as_fatal (_("Broken assembler.  No assembly attempted."));
1429	}
1430      do
1431	{
1432	  if (mips_opcodes[i].pinfo != INSN_MACRO)
1433	    {
1434	      if (!validate_mips_insn (&mips_opcodes[i]))
1435		broken = 1;
1436	      if (nop_insn.insn_mo == NULL && strcmp (name, "nop") == 0)
1437		{
1438		  create_insn (&nop_insn, mips_opcodes + i);
1439		  nop_insn.fixed_p = 1;
1440		}
1441	    }
1442	  ++i;
1443	}
1444      while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1445    }
1446
1447  mips16_op_hash = hash_new ();
1448
1449  i = 0;
1450  while (i < bfd_mips16_num_opcodes)
1451    {
1452      const char *name = mips16_opcodes[i].name;
1453
1454      retval = hash_insert (mips16_op_hash, name, (void *) &mips16_opcodes[i]);
1455      if (retval != NULL)
1456	as_fatal (_("internal: can't hash `%s': %s"),
1457		  mips16_opcodes[i].name, retval);
1458      do
1459	{
1460	  if (mips16_opcodes[i].pinfo != INSN_MACRO
1461	      && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1462		  != mips16_opcodes[i].match))
1463	    {
1464	      fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1465		       mips16_opcodes[i].name, mips16_opcodes[i].args);
1466	      broken = 1;
1467	    }
1468	  if (mips16_nop_insn.insn_mo == NULL && strcmp (name, "nop") == 0)
1469	    {
1470	      create_insn (&mips16_nop_insn, mips16_opcodes + i);
1471	      mips16_nop_insn.fixed_p = 1;
1472	    }
1473	  ++i;
1474	}
1475      while (i < bfd_mips16_num_opcodes
1476	     && strcmp (mips16_opcodes[i].name, name) == 0);
1477    }
1478
1479  if (broken)
1480    as_fatal (_("Broken assembler.  No assembly attempted."));
1481
1482  /* We add all the general register names to the symbol table.  This
1483     helps us detect invalid uses of them.  */
1484  for (i = 0; i < 32; i++)
1485    {
1486      char buf[5];
1487
1488      sprintf (buf, "$%d", i);
1489      symbol_table_insert (symbol_new (buf, reg_section, i,
1490				       &zero_address_frag));
1491    }
1492  symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1493				   &zero_address_frag));
1494  symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1495				   &zero_address_frag));
1496  symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1497				   &zero_address_frag));
1498  symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1499				   &zero_address_frag));
1500  symbol_table_insert (symbol_new ("$at", reg_section, AT,
1501				   &zero_address_frag));
1502  symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1503				   &zero_address_frag));
1504  symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1505				   &zero_address_frag));
1506  symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1507				   &zero_address_frag));
1508  symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1509				   &zero_address_frag));
1510
1511  /* If we don't add these register names to the symbol table, they
1512     may end up being added as regular symbols by operand(), and then
1513     make it to the object file as undefined in case they're not
1514     regarded as local symbols.  They're local in o32, since `$' is a
1515     local symbol prefix, but not in n32 or n64.  */
1516  for (i = 0; i < 8; i++)
1517    {
1518      char buf[6];
1519
1520      sprintf (buf, "$fcc%i", i);
1521      symbol_table_insert (symbol_new (buf, reg_section, -1,
1522				       &zero_address_frag));
1523    }
1524
1525  mips_no_prev_insn ();
1526
1527  mips_gprmask = 0;
1528  mips_cprmask[0] = 0;
1529  mips_cprmask[1] = 0;
1530  mips_cprmask[2] = 0;
1531  mips_cprmask[3] = 0;
1532
1533  /* set the default alignment for the text section (2**2) */
1534  record_alignment (text_section, 2);
1535
1536  bfd_set_gp_size (stdoutput, g_switch_value);
1537
1538  if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1539    {
1540      /* On a native system other than VxWorks, sections must be aligned
1541	 to 16 byte boundaries.  When configured for an embedded ELF
1542	 target, we don't bother.  */
1543      if (strcmp (TARGET_OS, "elf") != 0
1544	  && strcmp (TARGET_OS, "vxworks") != 0)
1545	{
1546	  (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1547	  (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1548	  (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1549	}
1550
1551      /* Create a .reginfo section for register masks and a .mdebug
1552	 section for debugging information.  */
1553      {
1554	segT seg;
1555	subsegT subseg;
1556	flagword flags;
1557	segT sec;
1558
1559	seg = now_seg;
1560	subseg = now_subseg;
1561
1562	/* The ABI says this section should be loaded so that the
1563	   running program can access it.  However, we don't load it
1564	   if we are configured for an embedded target */
1565	flags = SEC_READONLY | SEC_DATA;
1566	if (strcmp (TARGET_OS, "elf") != 0)
1567	  flags |= SEC_ALLOC | SEC_LOAD;
1568
1569	if (mips_abi != N64_ABI)
1570	  {
1571	    sec = subseg_new (".reginfo", (subsegT) 0);
1572
1573	    bfd_set_section_flags (stdoutput, sec, flags);
1574	    bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1575
1576#ifdef OBJ_ELF
1577	    mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1578#endif
1579	  }
1580	else
1581	  {
1582	    /* The 64-bit ABI uses a .MIPS.options section rather than
1583               .reginfo section.  */
1584	    sec = subseg_new (".MIPS.options", (subsegT) 0);
1585	    bfd_set_section_flags (stdoutput, sec, flags);
1586	    bfd_set_section_alignment (stdoutput, sec, 3);
1587
1588#ifdef OBJ_ELF
1589	    /* Set up the option header.  */
1590	    {
1591	      Elf_Internal_Options opthdr;
1592	      char *f;
1593
1594	      opthdr.kind = ODK_REGINFO;
1595	      opthdr.size = (sizeof (Elf_External_Options)
1596			     + sizeof (Elf64_External_RegInfo));
1597	      opthdr.section = 0;
1598	      opthdr.info = 0;
1599	      f = frag_more (sizeof (Elf_External_Options));
1600	      bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1601					     (Elf_External_Options *) f);
1602
1603	      mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1604	    }
1605#endif
1606	  }
1607
1608	if (ECOFF_DEBUGGING)
1609	  {
1610	    sec = subseg_new (".mdebug", (subsegT) 0);
1611	    (void) bfd_set_section_flags (stdoutput, sec,
1612					  SEC_HAS_CONTENTS | SEC_READONLY);
1613	    (void) bfd_set_section_alignment (stdoutput, sec, 2);
1614	  }
1615#ifdef OBJ_ELF
1616	else if (OUTPUT_FLAVOR == bfd_target_elf_flavour && mips_flag_pdr)
1617	  {
1618	    pdr_seg = subseg_new (".pdr", (subsegT) 0);
1619	    (void) bfd_set_section_flags (stdoutput, pdr_seg,
1620					  SEC_READONLY | SEC_RELOC
1621					  | SEC_DEBUGGING);
1622	    (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1623	  }
1624#endif
1625
1626	subseg_set (seg, subseg);
1627      }
1628    }
1629
1630  if (! ECOFF_DEBUGGING)
1631    md_obj_begin ();
1632
1633  if (mips_fix_vr4120)
1634    init_vr4120_conflicts ();
1635}
1636
1637void
1638md_mips_end (void)
1639{
1640  if (! ECOFF_DEBUGGING)
1641    md_obj_end ();
1642}
1643
1644void
1645md_assemble (char *str)
1646{
1647  struct mips_cl_insn insn;
1648  bfd_reloc_code_real_type unused_reloc[3]
1649    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1650
1651  imm_expr.X_op = O_absent;
1652  imm2_expr.X_op = O_absent;
1653  offset_expr.X_op = O_absent;
1654  imm_reloc[0] = BFD_RELOC_UNUSED;
1655  imm_reloc[1] = BFD_RELOC_UNUSED;
1656  imm_reloc[2] = BFD_RELOC_UNUSED;
1657  offset_reloc[0] = BFD_RELOC_UNUSED;
1658  offset_reloc[1] = BFD_RELOC_UNUSED;
1659  offset_reloc[2] = BFD_RELOC_UNUSED;
1660
1661  if (mips_opts.mips16)
1662    mips16_ip (str, &insn);
1663  else
1664    {
1665      mips_ip (str, &insn);
1666      DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1667	    str, insn.insn_opcode));
1668    }
1669
1670  if (insn_error)
1671    {
1672      as_bad ("%s `%s'", insn_error, str);
1673      return;
1674    }
1675
1676  if (insn.insn_mo->pinfo == INSN_MACRO)
1677    {
1678      macro_start ();
1679      if (mips_opts.mips16)
1680	mips16_macro (&insn);
1681      else
1682	macro (&insn);
1683      macro_end ();
1684    }
1685  else
1686    {
1687      if (imm_expr.X_op != O_absent)
1688	append_insn (&insn, &imm_expr, imm_reloc);
1689      else if (offset_expr.X_op != O_absent)
1690	append_insn (&insn, &offset_expr, offset_reloc);
1691      else
1692	append_insn (&insn, NULL, unused_reloc);
1693    }
1694}
1695
1696/* Return true if the given relocation might need a matching %lo().
1697   This is only "might" because SVR4 R_MIPS_GOT16 relocations only
1698   need a matching %lo() when applied to local symbols.  */
1699
1700static inline bfd_boolean
1701reloc_needs_lo_p (bfd_reloc_code_real_type reloc)
1702{
1703  return (HAVE_IN_PLACE_ADDENDS
1704	  && (reloc == BFD_RELOC_HI16_S
1705	      || reloc == BFD_RELOC_MIPS16_HI16_S
1706	      /* VxWorks R_MIPS_GOT16 relocs never need a matching %lo();
1707		 all GOT16 relocations evaluate to "G".  */
1708	      || (reloc == BFD_RELOC_MIPS_GOT16 && mips_pic != VXWORKS_PIC)));
1709}
1710
1711/* Return true if the given fixup is followed by a matching R_MIPS_LO16
1712   relocation.  */
1713
1714static inline bfd_boolean
1715fixup_has_matching_lo_p (fixS *fixp)
1716{
1717  return (fixp->fx_next != NULL
1718	  && (fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1719	     || fixp->fx_next->fx_r_type == BFD_RELOC_MIPS16_LO16)
1720	  && fixp->fx_addsy == fixp->fx_next->fx_addsy
1721	  && fixp->fx_offset == fixp->fx_next->fx_offset);
1722}
1723
1724/* See whether instruction IP reads register REG.  CLASS is the type
1725   of register.  */
1726
1727static int
1728insn_uses_reg (const struct mips_cl_insn *ip, unsigned int reg,
1729	       enum mips_regclass class)
1730{
1731  if (class == MIPS16_REG)
1732    {
1733      assert (mips_opts.mips16);
1734      reg = mips16_to_32_reg_map[reg];
1735      class = MIPS_GR_REG;
1736    }
1737
1738  /* Don't report on general register ZERO, since it never changes.  */
1739  if (class == MIPS_GR_REG && reg == ZERO)
1740    return 0;
1741
1742  if (class == MIPS_FP_REG)
1743    {
1744      assert (! mips_opts.mips16);
1745      /* If we are called with either $f0 or $f1, we must check $f0.
1746	 This is not optimal, because it will introduce an unnecessary
1747	 NOP between "lwc1 $f0" and "swc1 $f1".  To fix this we would
1748	 need to distinguish reading both $f0 and $f1 or just one of
1749	 them.  Note that we don't have to check the other way,
1750	 because there is no instruction that sets both $f0 and $f1
1751	 and requires a delay.  */
1752      if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1753	  && ((EXTRACT_OPERAND (FS, *ip) & ~(unsigned) 1)
1754	      == (reg &~ (unsigned) 1)))
1755	return 1;
1756      if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1757	  && ((EXTRACT_OPERAND (FT, *ip) & ~(unsigned) 1)
1758	      == (reg &~ (unsigned) 1)))
1759	return 1;
1760    }
1761  else if (! mips_opts.mips16)
1762    {
1763      if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1764	  && EXTRACT_OPERAND (RS, *ip) == reg)
1765	return 1;
1766      if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1767	  && EXTRACT_OPERAND (RT, *ip) == reg)
1768	return 1;
1769    }
1770  else
1771    {
1772      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1773	  && mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RX, *ip)] == reg)
1774	return 1;
1775      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1776	  && mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RY, *ip)] == reg)
1777	return 1;
1778      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1779	  && (mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (MOVE32Z, *ip)]
1780	      == reg))
1781	return 1;
1782      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1783	return 1;
1784      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1785	return 1;
1786      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1787	return 1;
1788      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1789	  && MIPS16_EXTRACT_OPERAND (REGR32, *ip) == reg)
1790	return 1;
1791    }
1792
1793  return 0;
1794}
1795
1796/* This function returns true if modifying a register requires a
1797   delay.  */
1798
1799static int
1800reg_needs_delay (unsigned int reg)
1801{
1802  unsigned long prev_pinfo;
1803
1804  prev_pinfo = history[0].insn_mo->pinfo;
1805  if (! mips_opts.noreorder
1806      && (((prev_pinfo & INSN_LOAD_MEMORY_DELAY)
1807	   && ! gpr_interlocks)
1808	  || ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1809	      && ! cop_interlocks)))
1810    {
1811      /* A load from a coprocessor or from memory.  All load delays
1812	 delay the use of general register rt for one instruction.  */
1813      /* Itbl support may require additional care here.  */
1814      know (prev_pinfo & INSN_WRITE_GPR_T);
1815      if (reg == EXTRACT_OPERAND (RT, history[0]))
1816	return 1;
1817    }
1818
1819  return 0;
1820}
1821
1822/* Move all labels in insn_labels to the current insertion point.  */
1823
1824static void
1825mips_move_labels (void)
1826{
1827  struct insn_label_list *l;
1828  valueT val;
1829
1830  for (l = insn_labels; l != NULL; l = l->next)
1831    {
1832      assert (S_GET_SEGMENT (l->label) == now_seg);
1833      symbol_set_frag (l->label, frag_now);
1834      val = (valueT) frag_now_fix ();
1835      /* mips16 text labels are stored as odd.  */
1836      if (mips_opts.mips16)
1837	++val;
1838      S_SET_VALUE (l->label, val);
1839    }
1840}
1841
1842/* Mark instruction labels in mips16 mode.  This permits the linker to
1843   handle them specially, such as generating jalx instructions when
1844   needed.  We also make them odd for the duration of the assembly, in
1845   order to generate the right sort of code.  We will make them even
1846   in the adjust_symtab routine, while leaving them marked.  This is
1847   convenient for the debugger and the disassembler.  The linker knows
1848   to make them odd again.  */
1849
1850static void
1851mips16_mark_labels (void)
1852{
1853  if (mips_opts.mips16)
1854    {
1855      struct insn_label_list *l;
1856      valueT val;
1857
1858      for (l = insn_labels; l != NULL; l = l->next)
1859	{
1860#ifdef OBJ_ELF
1861	  if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1862	    S_SET_OTHER (l->label, STO_MIPS16);
1863#endif
1864	  val = S_GET_VALUE (l->label);
1865	  if ((val & 1) == 0)
1866	    S_SET_VALUE (l->label, val + 1);
1867	}
1868    }
1869}
1870
1871/* End the current frag.  Make it a variant frag and record the
1872   relaxation info.  */
1873
1874static void
1875relax_close_frag (void)
1876{
1877  mips_macro_warning.first_frag = frag_now;
1878  frag_var (rs_machine_dependent, 0, 0,
1879	    RELAX_ENCODE (mips_relax.sizes[0], mips_relax.sizes[1]),
1880	    mips_relax.symbol, 0, (char *) mips_relax.first_fixup);
1881
1882  memset (&mips_relax.sizes, 0, sizeof (mips_relax.sizes));
1883  mips_relax.first_fixup = 0;
1884}
1885
1886/* Start a new relaxation sequence whose expansion depends on SYMBOL.
1887   See the comment above RELAX_ENCODE for more details.  */
1888
1889static void
1890relax_start (symbolS *symbol)
1891{
1892  assert (mips_relax.sequence == 0);
1893  mips_relax.sequence = 1;
1894  mips_relax.symbol = symbol;
1895}
1896
1897/* Start generating the second version of a relaxable sequence.
1898   See the comment above RELAX_ENCODE for more details.  */
1899
1900static void
1901relax_switch (void)
1902{
1903  assert (mips_relax.sequence == 1);
1904  mips_relax.sequence = 2;
1905}
1906
1907/* End the current relaxable sequence.  */
1908
1909static void
1910relax_end (void)
1911{
1912  assert (mips_relax.sequence == 2);
1913  relax_close_frag ();
1914  mips_relax.sequence = 0;
1915}
1916
1917/* Classify an instruction according to the FIX_VR4120_* enumeration.
1918   Return NUM_FIX_VR4120_CLASSES if the instruction isn't affected
1919   by VR4120 errata.  */
1920
1921static unsigned int
1922classify_vr4120_insn (const char *name)
1923{
1924  if (strncmp (name, "macc", 4) == 0)
1925    return FIX_VR4120_MACC;
1926  if (strncmp (name, "dmacc", 5) == 0)
1927    return FIX_VR4120_DMACC;
1928  if (strncmp (name, "mult", 4) == 0)
1929    return FIX_VR4120_MULT;
1930  if (strncmp (name, "dmult", 5) == 0)
1931    return FIX_VR4120_DMULT;
1932  if (strstr (name, "div"))
1933    return FIX_VR4120_DIV;
1934  if (strcmp (name, "mtlo") == 0 || strcmp (name, "mthi") == 0)
1935    return FIX_VR4120_MTHILO;
1936  return NUM_FIX_VR4120_CLASSES;
1937}
1938
1939/* Return the number of instructions that must separate INSN1 and INSN2,
1940   where INSN1 is the earlier instruction.  Return the worst-case value
1941   for any INSN2 if INSN2 is null.  */
1942
1943static unsigned int
1944insns_between (const struct mips_cl_insn *insn1,
1945	       const struct mips_cl_insn *insn2)
1946{
1947  unsigned long pinfo1, pinfo2;
1948
1949  /* This function needs to know which pinfo flags are set for INSN2
1950     and which registers INSN2 uses.  The former is stored in PINFO2 and
1951     the latter is tested via INSN2_USES_REG.  If INSN2 is null, PINFO2
1952     will have every flag set and INSN2_USES_REG will always return true.  */
1953  pinfo1 = insn1->insn_mo->pinfo;
1954  pinfo2 = insn2 ? insn2->insn_mo->pinfo : ~0U;
1955
1956#define INSN2_USES_REG(REG, CLASS) \
1957   (insn2 == NULL || insn_uses_reg (insn2, REG, CLASS))
1958
1959  /* For most targets, write-after-read dependencies on the HI and LO
1960     registers must be separated by at least two instructions.  */
1961  if (!hilo_interlocks)
1962    {
1963      if ((pinfo1 & INSN_READ_LO) && (pinfo2 & INSN_WRITE_LO))
1964	return 2;
1965      if ((pinfo1 & INSN_READ_HI) && (pinfo2 & INSN_WRITE_HI))
1966	return 2;
1967    }
1968
1969  /* If we're working around r7000 errata, there must be two instructions
1970     between an mfhi or mflo and any instruction that uses the result.  */
1971  if (mips_7000_hilo_fix
1972      && MF_HILO_INSN (pinfo1)
1973      && INSN2_USES_REG (EXTRACT_OPERAND (RD, *insn1), MIPS_GR_REG))
1974    return 2;
1975
1976  /* If working around VR4120 errata, check for combinations that need
1977     a single intervening instruction.  */
1978  if (mips_fix_vr4120)
1979    {
1980      unsigned int class1, class2;
1981
1982      class1 = classify_vr4120_insn (insn1->insn_mo->name);
1983      if (class1 != NUM_FIX_VR4120_CLASSES && vr4120_conflicts[class1] != 0)
1984	{
1985	  if (insn2 == NULL)
1986	    return 1;
1987	  class2 = classify_vr4120_insn (insn2->insn_mo->name);
1988	  if (vr4120_conflicts[class1] & (1 << class2))
1989	    return 1;
1990	}
1991    }
1992
1993  if (!mips_opts.mips16)
1994    {
1995      /* Check for GPR or coprocessor load delays.  All such delays
1996	 are on the RT register.  */
1997      /* Itbl support may require additional care here.  */
1998      if ((!gpr_interlocks && (pinfo1 & INSN_LOAD_MEMORY_DELAY))
1999	  || (!cop_interlocks && (pinfo1 & INSN_LOAD_COPROC_DELAY)))
2000	{
2001	  know (pinfo1 & INSN_WRITE_GPR_T);
2002	  if (INSN2_USES_REG (EXTRACT_OPERAND (RT, *insn1), MIPS_GR_REG))
2003	    return 1;
2004	}
2005
2006      /* Check for generic coprocessor hazards.
2007
2008	 This case is not handled very well.  There is no special
2009	 knowledge of CP0 handling, and the coprocessors other than
2010	 the floating point unit are not distinguished at all.  */
2011      /* Itbl support may require additional care here. FIXME!
2012	 Need to modify this to include knowledge about
2013	 user specified delays!  */
2014      else if ((!cop_interlocks && (pinfo1 & INSN_COPROC_MOVE_DELAY))
2015	       || (!cop_mem_interlocks && (pinfo1 & INSN_COPROC_MEMORY_DELAY)))
2016	{
2017	  /* Handle cases where INSN1 writes to a known general coprocessor
2018	     register.  There must be a one instruction delay before INSN2
2019	     if INSN2 reads that register, otherwise no delay is needed.  */
2020	  if (pinfo1 & INSN_WRITE_FPR_T)
2021	    {
2022	      if (INSN2_USES_REG (EXTRACT_OPERAND (FT, *insn1), MIPS_FP_REG))
2023		return 1;
2024	    }
2025	  else if (pinfo1 & INSN_WRITE_FPR_S)
2026	    {
2027	      if (INSN2_USES_REG (EXTRACT_OPERAND (FS, *insn1), MIPS_FP_REG))
2028		return 1;
2029	    }
2030	  else
2031	    {
2032	      /* Read-after-write dependencies on the control registers
2033		 require a two-instruction gap.  */
2034	      if ((pinfo1 & INSN_WRITE_COND_CODE)
2035		  && (pinfo2 & INSN_READ_COND_CODE))
2036		return 2;
2037
2038	      /* We don't know exactly what INSN1 does.  If INSN2 is
2039		 also a coprocessor instruction, assume there must be
2040		 a one instruction gap.  */
2041	      if (pinfo2 & INSN_COP)
2042		return 1;
2043	    }
2044	}
2045
2046      /* Check for read-after-write dependencies on the coprocessor
2047	 control registers in cases where INSN1 does not need a general
2048	 coprocessor delay.  This means that INSN1 is a floating point
2049	 comparison instruction.  */
2050      /* Itbl support may require additional care here.  */
2051      else if (!cop_interlocks
2052	       && (pinfo1 & INSN_WRITE_COND_CODE)
2053	       && (pinfo2 & INSN_READ_COND_CODE))
2054	return 1;
2055    }
2056
2057#undef INSN2_USES_REG
2058
2059  return 0;
2060}
2061
2062/* Return the number of nops that would be needed to work around the
2063   VR4130 mflo/mfhi errata if instruction INSN immediately followed
2064   the MAX_VR4130_NOPS instructions described by HISTORY.  */
2065
2066static int
2067nops_for_vr4130 (const struct mips_cl_insn *history,
2068		 const struct mips_cl_insn *insn)
2069{
2070  int i, j, reg;
2071
2072  /* Check if the instruction writes to HI or LO.  MTHI and MTLO
2073     are not affected by the errata.  */
2074  if (insn != 0
2075      && ((insn->insn_mo->pinfo & (INSN_WRITE_HI | INSN_WRITE_LO)) == 0
2076	  || strcmp (insn->insn_mo->name, "mtlo") == 0
2077	  || strcmp (insn->insn_mo->name, "mthi") == 0))
2078    return 0;
2079
2080  /* Search for the first MFLO or MFHI.  */
2081  for (i = 0; i < MAX_VR4130_NOPS; i++)
2082    if (!history[i].noreorder_p && MF_HILO_INSN (history[i].insn_mo->pinfo))
2083      {
2084	/* Extract the destination register.  */
2085	if (mips_opts.mips16)
2086	  reg = mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RX, history[i])];
2087	else
2088	  reg = EXTRACT_OPERAND (RD, history[i]);
2089
2090	/* No nops are needed if INSN reads that register.  */
2091	if (insn != NULL && insn_uses_reg (insn, reg, MIPS_GR_REG))
2092	  return 0;
2093
2094	/* ...or if any of the intervening instructions do.  */
2095	for (j = 0; j < i; j++)
2096	  if (insn_uses_reg (&history[j], reg, MIPS_GR_REG))
2097	    return 0;
2098
2099	return MAX_VR4130_NOPS - i;
2100      }
2101  return 0;
2102}
2103
2104/* Return the number of nops that would be needed if instruction INSN
2105   immediately followed the MAX_NOPS instructions given by HISTORY,
2106   where HISTORY[0] is the most recent instruction.  If INSN is null,
2107   return the worse-case number of nops for any instruction.  */
2108
2109static int
2110nops_for_insn (const struct mips_cl_insn *history,
2111	       const struct mips_cl_insn *insn)
2112{
2113  int i, nops, tmp_nops;
2114
2115  nops = 0;
2116  for (i = 0; i < MAX_DELAY_NOPS; i++)
2117    if (!history[i].noreorder_p)
2118      {
2119	tmp_nops = insns_between (history + i, insn) - i;
2120	if (tmp_nops > nops)
2121	  nops = tmp_nops;
2122      }
2123
2124  if (mips_fix_vr4130)
2125    {
2126      tmp_nops = nops_for_vr4130 (history, insn);
2127      if (tmp_nops > nops)
2128	nops = tmp_nops;
2129    }
2130
2131  return nops;
2132}
2133
2134/* The variable arguments provide NUM_INSNS extra instructions that
2135   might be added to HISTORY.  Return the largest number of nops that
2136   would be needed after the extended sequence.  */
2137
2138static int
2139nops_for_sequence (int num_insns, const struct mips_cl_insn *history, ...)
2140{
2141  va_list args;
2142  struct mips_cl_insn buffer[MAX_NOPS];
2143  struct mips_cl_insn *cursor;
2144  int nops;
2145
2146  va_start (args, history);
2147  cursor = buffer + num_insns;
2148  memcpy (cursor, history, (MAX_NOPS - num_insns) * sizeof (*cursor));
2149  while (cursor > buffer)
2150    *--cursor = *va_arg (args, const struct mips_cl_insn *);
2151
2152  nops = nops_for_insn (buffer, NULL);
2153  va_end (args);
2154  return nops;
2155}
2156
2157/* Like nops_for_insn, but if INSN is a branch, take into account the
2158   worst-case delay for the branch target.  */
2159
2160static int
2161nops_for_insn_or_target (const struct mips_cl_insn *history,
2162			 const struct mips_cl_insn *insn)
2163{
2164  int nops, tmp_nops;
2165
2166  nops = nops_for_insn (history, insn);
2167  if (insn->insn_mo->pinfo & (INSN_UNCOND_BRANCH_DELAY
2168			      | INSN_COND_BRANCH_DELAY
2169			      | INSN_COND_BRANCH_LIKELY))
2170    {
2171      tmp_nops = nops_for_sequence (2, history, insn, NOP_INSN);
2172      if (tmp_nops > nops)
2173	nops = tmp_nops;
2174    }
2175  else if (mips_opts.mips16 && (insn->insn_mo->pinfo & MIPS16_INSN_BRANCH))
2176    {
2177      tmp_nops = nops_for_sequence (1, history, insn);
2178      if (tmp_nops > nops)
2179	nops = tmp_nops;
2180    }
2181  return nops;
2182}
2183
2184/* Output an instruction.  IP is the instruction information.
2185   ADDRESS_EXPR is an operand of the instruction to be used with
2186   RELOC_TYPE.  */
2187
2188static void
2189append_insn (struct mips_cl_insn *ip, expressionS *address_expr,
2190	     bfd_reloc_code_real_type *reloc_type)
2191{
2192  register unsigned long prev_pinfo, pinfo;
2193  relax_stateT prev_insn_frag_type = 0;
2194  bfd_boolean relaxed_branch = FALSE;
2195
2196  /* Mark instruction labels in mips16 mode.  */
2197  mips16_mark_labels ();
2198
2199  prev_pinfo = history[0].insn_mo->pinfo;
2200  pinfo = ip->insn_mo->pinfo;
2201
2202  if (mips_relax.sequence != 2 && !mips_opts.noreorder)
2203    {
2204      /* There are a lot of optimizations we could do that we don't.
2205	 In particular, we do not, in general, reorder instructions.
2206	 If you use gcc with optimization, it will reorder
2207	 instructions and generally do much more optimization then we
2208	 do here; repeating all that work in the assembler would only
2209	 benefit hand written assembly code, and does not seem worth
2210	 it.  */
2211      int nops = (mips_optimize == 0
2212		  ? nops_for_insn (history, NULL)
2213		  : nops_for_insn_or_target (history, ip));
2214      if (nops > 0)
2215	{
2216	  fragS *old_frag;
2217	  unsigned long old_frag_offset;
2218	  int i;
2219
2220	  old_frag = frag_now;
2221	  old_frag_offset = frag_now_fix ();
2222
2223	  for (i = 0; i < nops; i++)
2224	    emit_nop ();
2225
2226	  if (listing)
2227	    {
2228	      listing_prev_line ();
2229	      /* We may be at the start of a variant frag.  In case we
2230                 are, make sure there is enough space for the frag
2231                 after the frags created by listing_prev_line.  The
2232                 argument to frag_grow here must be at least as large
2233                 as the argument to all other calls to frag_grow in
2234                 this file.  We don't have to worry about being in the
2235                 middle of a variant frag, because the variants insert
2236                 all needed nop instructions themselves.  */
2237	      frag_grow (40);
2238	    }
2239
2240	  mips_move_labels ();
2241
2242#ifndef NO_ECOFF_DEBUGGING
2243	  if (ECOFF_DEBUGGING)
2244	    ecoff_fix_loc (old_frag, old_frag_offset);
2245#endif
2246	}
2247    }
2248  else if (mips_relax.sequence != 2 && prev_nop_frag != NULL)
2249    {
2250      /* Work out how many nops in prev_nop_frag are needed by IP.  */
2251      int nops = nops_for_insn_or_target (history, ip);
2252      assert (nops <= prev_nop_frag_holds);
2253
2254      /* Enforce NOPS as a minimum.  */
2255      if (nops > prev_nop_frag_required)
2256	prev_nop_frag_required = nops;
2257
2258      if (prev_nop_frag_holds == prev_nop_frag_required)
2259	{
2260	  /* Settle for the current number of nops.  Update the history
2261	     accordingly (for the benefit of any future .set reorder code).  */
2262	  prev_nop_frag = NULL;
2263	  insert_into_history (prev_nop_frag_since,
2264			       prev_nop_frag_holds, NOP_INSN);
2265	}
2266      else
2267	{
2268	  /* Allow this instruction to replace one of the nops that was
2269	     tentatively added to prev_nop_frag.  */
2270	  prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2271	  prev_nop_frag_holds--;
2272	  prev_nop_frag_since++;
2273	}
2274    }
2275
2276#ifdef OBJ_ELF
2277  /* The value passed to dwarf2_emit_insn is the distance between
2278     the beginning of the current instruction and the address that
2279     should be recorded in the debug tables.  For MIPS16 debug info
2280     we want to use ISA-encoded addresses, so we pass -1 for an
2281     address higher by one than the current.  */
2282  dwarf2_emit_insn (mips_opts.mips16 ? -1 : 0);
2283#endif
2284
2285  /* Record the frag type before frag_var.  */
2286  if (history[0].frag)
2287    prev_insn_frag_type = history[0].frag->fr_type;
2288
2289  if (address_expr
2290      && *reloc_type == BFD_RELOC_16_PCREL_S2
2291      && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2292	  || pinfo & INSN_COND_BRANCH_LIKELY)
2293      && mips_relax_branch
2294      /* Don't try branch relaxation within .set nomacro, or within
2295	 .set noat if we use $at for PIC computations.  If it turns
2296	 out that the branch was out-of-range, we'll get an error.  */
2297      && !mips_opts.warn_about_macros
2298      && !(mips_opts.noat && mips_pic != NO_PIC)
2299      && !mips_opts.mips16)
2300    {
2301      relaxed_branch = TRUE;
2302      add_relaxed_insn (ip, (relaxed_branch_length
2303			     (NULL, NULL,
2304			      (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2305			      : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1
2306			      : 0)), 4,
2307			RELAX_BRANCH_ENCODE
2308			(pinfo & INSN_UNCOND_BRANCH_DELAY,
2309			 pinfo & INSN_COND_BRANCH_LIKELY,
2310			 pinfo & INSN_WRITE_GPR_31,
2311			 0),
2312			address_expr->X_add_symbol,
2313			address_expr->X_add_number);
2314      *reloc_type = BFD_RELOC_UNUSED;
2315    }
2316  else if (*reloc_type > BFD_RELOC_UNUSED)
2317    {
2318      /* We need to set up a variant frag.  */
2319      assert (mips_opts.mips16 && address_expr != NULL);
2320      add_relaxed_insn (ip, 4, 0,
2321			RELAX_MIPS16_ENCODE
2322			(*reloc_type - BFD_RELOC_UNUSED,
2323			 mips16_small, mips16_ext,
2324			 prev_pinfo & INSN_UNCOND_BRANCH_DELAY,
2325			 history[0].mips16_absolute_jump_p),
2326			make_expr_symbol (address_expr), 0);
2327    }
2328  else if (mips_opts.mips16
2329	   && ! ip->use_extend
2330	   && *reloc_type != BFD_RELOC_MIPS16_JMP)
2331    {
2332      if ((pinfo & INSN_UNCOND_BRANCH_DELAY) == 0)
2333	/* Make sure there is enough room to swap this instruction with
2334	   a following jump instruction.  */
2335	frag_grow (6);
2336      add_fixed_insn (ip);
2337    }
2338  else
2339    {
2340      if (mips_opts.mips16
2341	  && mips_opts.noreorder
2342	  && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2343	as_warn (_("extended instruction in delay slot"));
2344
2345      if (mips_relax.sequence)
2346	{
2347	  /* If we've reached the end of this frag, turn it into a variant
2348	     frag and record the information for the instructions we've
2349	     written so far.  */
2350	  if (frag_room () < 4)
2351	    relax_close_frag ();
2352	  mips_relax.sizes[mips_relax.sequence - 1] += 4;
2353	}
2354
2355      if (mips_relax.sequence != 2)
2356	mips_macro_warning.sizes[0] += 4;
2357      if (mips_relax.sequence != 1)
2358	mips_macro_warning.sizes[1] += 4;
2359
2360      if (mips_opts.mips16)
2361	{
2362	  ip->fixed_p = 1;
2363	  ip->mips16_absolute_jump_p = (*reloc_type == BFD_RELOC_MIPS16_JMP);
2364	}
2365      add_fixed_insn (ip);
2366    }
2367
2368  if (address_expr != NULL && *reloc_type <= BFD_RELOC_UNUSED)
2369    {
2370      if (address_expr->X_op == O_constant)
2371	{
2372	  unsigned int tmp;
2373
2374	  switch (*reloc_type)
2375	    {
2376	    case BFD_RELOC_32:
2377	      ip->insn_opcode |= address_expr->X_add_number;
2378	      break;
2379
2380	    case BFD_RELOC_MIPS_HIGHEST:
2381	      tmp = (address_expr->X_add_number + 0x800080008000ull) >> 48;
2382	      ip->insn_opcode |= tmp & 0xffff;
2383	      break;
2384
2385	    case BFD_RELOC_MIPS_HIGHER:
2386	      tmp = (address_expr->X_add_number + 0x80008000ull) >> 32;
2387	      ip->insn_opcode |= tmp & 0xffff;
2388	      break;
2389
2390	    case BFD_RELOC_HI16_S:
2391	      tmp = (address_expr->X_add_number + 0x8000) >> 16;
2392	      ip->insn_opcode |= tmp & 0xffff;
2393	      break;
2394
2395	    case BFD_RELOC_HI16:
2396	      ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2397	      break;
2398
2399	    case BFD_RELOC_UNUSED:
2400	    case BFD_RELOC_LO16:
2401	    case BFD_RELOC_MIPS_GOT_DISP:
2402	      ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2403	      break;
2404
2405	    case BFD_RELOC_MIPS_JMP:
2406	      if ((address_expr->X_add_number & 3) != 0)
2407		as_bad (_("jump to misaligned address (0x%lx)"),
2408			(unsigned long) address_expr->X_add_number);
2409	      ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2410	      break;
2411
2412	    case BFD_RELOC_MIPS16_JMP:
2413	      if ((address_expr->X_add_number & 3) != 0)
2414		as_bad (_("jump to misaligned address (0x%lx)"),
2415			(unsigned long) address_expr->X_add_number);
2416	      ip->insn_opcode |=
2417		(((address_expr->X_add_number & 0x7c0000) << 3)
2418		 | ((address_expr->X_add_number & 0xf800000) >> 7)
2419		 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2420	      break;
2421
2422	    case BFD_RELOC_16_PCREL_S2:
2423	      if ((address_expr->X_add_number & 3) != 0)
2424		as_bad (_("branch to misaligned address (0x%lx)"),
2425			(unsigned long) address_expr->X_add_number);
2426	      if (mips_relax_branch)
2427		goto need_reloc;
2428	      if ((address_expr->X_add_number + 0x20000) & ~0x3ffff)
2429		as_bad (_("branch address range overflow (0x%lx)"),
2430			(unsigned long) address_expr->X_add_number);
2431	      ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0xffff;
2432	      break;
2433
2434	    default:
2435	      internalError ();
2436	    }
2437	}
2438      else if (*reloc_type < BFD_RELOC_UNUSED)
2439	need_reloc:
2440	{
2441	  reloc_howto_type *howto;
2442	  int i;
2443
2444	  /* In a compound relocation, it is the final (outermost)
2445	     operator that determines the relocated field.  */
2446	  for (i = 1; i < 3; i++)
2447	    if (reloc_type[i] == BFD_RELOC_UNUSED)
2448	      break;
2449
2450	  howto = bfd_reloc_type_lookup (stdoutput, reloc_type[i - 1]);
2451	  ip->fixp[0] = fix_new_exp (ip->frag, ip->where,
2452				     bfd_get_reloc_size (howto),
2453				     address_expr,
2454				     reloc_type[0] == BFD_RELOC_16_PCREL_S2,
2455				     reloc_type[0]);
2456
2457	  /* These relocations can have an addend that won't fit in
2458	     4 octets for 64bit assembly.  */
2459	  if (HAVE_64BIT_GPRS
2460	      && ! howto->partial_inplace
2461	      && (reloc_type[0] == BFD_RELOC_16
2462		  || reloc_type[0] == BFD_RELOC_32
2463		  || reloc_type[0] == BFD_RELOC_MIPS_JMP
2464		  || reloc_type[0] == BFD_RELOC_HI16_S
2465		  || reloc_type[0] == BFD_RELOC_LO16
2466		  || reloc_type[0] == BFD_RELOC_GPREL16
2467		  || reloc_type[0] == BFD_RELOC_MIPS_LITERAL
2468		  || reloc_type[0] == BFD_RELOC_GPREL32
2469		  || reloc_type[0] == BFD_RELOC_64
2470		  || reloc_type[0] == BFD_RELOC_CTOR
2471		  || reloc_type[0] == BFD_RELOC_MIPS_SUB
2472		  || reloc_type[0] == BFD_RELOC_MIPS_HIGHEST
2473		  || reloc_type[0] == BFD_RELOC_MIPS_HIGHER
2474		  || reloc_type[0] == BFD_RELOC_MIPS_SCN_DISP
2475		  || reloc_type[0] == BFD_RELOC_MIPS_REL16
2476		  || reloc_type[0] == BFD_RELOC_MIPS_RELGOT
2477		  || reloc_type[0] == BFD_RELOC_MIPS16_GPREL
2478		  || reloc_type[0] == BFD_RELOC_MIPS16_HI16_S
2479		  || reloc_type[0] == BFD_RELOC_MIPS16_LO16))
2480	    ip->fixp[0]->fx_no_overflow = 1;
2481
2482	  if (mips_relax.sequence)
2483	    {
2484	      if (mips_relax.first_fixup == 0)
2485		mips_relax.first_fixup = ip->fixp[0];
2486	    }
2487	  else if (reloc_needs_lo_p (*reloc_type))
2488	    {
2489	      struct mips_hi_fixup *hi_fixup;
2490
2491	      /* Reuse the last entry if it already has a matching %lo.  */
2492	      hi_fixup = mips_hi_fixup_list;
2493	      if (hi_fixup == 0
2494		  || !fixup_has_matching_lo_p (hi_fixup->fixp))
2495		{
2496		  hi_fixup = ((struct mips_hi_fixup *)
2497			      xmalloc (sizeof (struct mips_hi_fixup)));
2498		  hi_fixup->next = mips_hi_fixup_list;
2499		  mips_hi_fixup_list = hi_fixup;
2500		}
2501	      hi_fixup->fixp = ip->fixp[0];
2502	      hi_fixup->seg = now_seg;
2503	    }
2504
2505	  /* Add fixups for the second and third relocations, if given.
2506	     Note that the ABI allows the second relocation to be
2507	     against RSS_UNDEF, RSS_GP, RSS_GP0 or RSS_LOC.  At the
2508	     moment we only use RSS_UNDEF, but we could add support
2509	     for the others if it ever becomes necessary.  */
2510	  for (i = 1; i < 3; i++)
2511	    if (reloc_type[i] != BFD_RELOC_UNUSED)
2512	      {
2513		ip->fixp[i] = fix_new (ip->frag, ip->where,
2514				       ip->fixp[0]->fx_size, NULL, 0,
2515				       FALSE, reloc_type[i]);
2516
2517		/* Use fx_tcbit to mark compound relocs.  */
2518		ip->fixp[0]->fx_tcbit = 1;
2519		ip->fixp[i]->fx_tcbit = 1;
2520	      }
2521	}
2522    }
2523  install_insn (ip);
2524
2525  /* Update the register mask information.  */
2526  if (! mips_opts.mips16)
2527    {
2528      if (pinfo & INSN_WRITE_GPR_D)
2529	mips_gprmask |= 1 << EXTRACT_OPERAND (RD, *ip);
2530      if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2531	mips_gprmask |= 1 << EXTRACT_OPERAND (RT, *ip);
2532      if (pinfo & INSN_READ_GPR_S)
2533	mips_gprmask |= 1 << EXTRACT_OPERAND (RS, *ip);
2534      if (pinfo & INSN_WRITE_GPR_31)
2535	mips_gprmask |= 1 << RA;
2536      if (pinfo & INSN_WRITE_FPR_D)
2537	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FD, *ip);
2538      if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2539	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FS, *ip);
2540      if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2541	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FT, *ip);
2542      if ((pinfo & INSN_READ_FPR_R) != 0)
2543	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FR, *ip);
2544      if (pinfo & INSN_COP)
2545	{
2546	  /* We don't keep enough information to sort these cases out.
2547	     The itbl support does keep this information however, although
2548	     we currently don't support itbl fprmats as part of the cop
2549	     instruction.  May want to add this support in the future.  */
2550	}
2551      /* Never set the bit for $0, which is always zero.  */
2552      mips_gprmask &= ~1 << 0;
2553    }
2554  else
2555    {
2556      if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2557	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RX, *ip);
2558      if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2559	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RY, *ip);
2560      if (pinfo & MIPS16_INSN_WRITE_Z)
2561	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RZ, *ip);
2562      if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2563	mips_gprmask |= 1 << TREG;
2564      if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2565	mips_gprmask |= 1 << SP;
2566      if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2567	mips_gprmask |= 1 << RA;
2568      if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2569	mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2570      if (pinfo & MIPS16_INSN_READ_Z)
2571	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (MOVE32Z, *ip);
2572      if (pinfo & MIPS16_INSN_READ_GPR_X)
2573	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (REGR32, *ip);
2574    }
2575
2576  if (mips_relax.sequence != 2 && !mips_opts.noreorder)
2577    {
2578      /* Filling the branch delay slot is more complex.  We try to
2579	 switch the branch with the previous instruction, which we can
2580	 do if the previous instruction does not set up a condition
2581	 that the branch tests and if the branch is not itself the
2582	 target of any branch.  */
2583      if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2584	  || (pinfo & INSN_COND_BRANCH_DELAY))
2585	{
2586	  if (mips_optimize < 2
2587	      /* If we have seen .set volatile or .set nomove, don't
2588		 optimize.  */
2589	      || mips_opts.nomove != 0
2590	      /* We can't swap if the previous instruction's position
2591		 is fixed.  */
2592	      || history[0].fixed_p
2593	      /* If the previous previous insn was in a .set
2594		 noreorder, we can't swap.  Actually, the MIPS
2595		 assembler will swap in this situation.  However, gcc
2596		 configured -with-gnu-as will generate code like
2597		   .set noreorder
2598		   lw	$4,XXX
2599		   .set	reorder
2600		   INSN
2601		   bne	$4,$0,foo
2602		 in which we can not swap the bne and INSN.  If gcc is
2603		 not configured -with-gnu-as, it does not output the
2604		 .set pseudo-ops.  */
2605	      || history[1].noreorder_p
2606	      /* If the branch is itself the target of a branch, we
2607		 can not swap.  We cheat on this; all we check for is
2608		 whether there is a label on this instruction.  If
2609		 there are any branches to anything other than a
2610		 label, users must use .set noreorder.  */
2611	      || insn_labels != NULL
2612	      /* If the previous instruction is in a variant frag
2613		 other than this branch's one, we cannot do the swap.
2614		 This does not apply to the mips16, which uses variant
2615		 frags for different purposes.  */
2616	      || (! mips_opts.mips16
2617		  && prev_insn_frag_type == rs_machine_dependent)
2618	      /* Check for conflicts between the branch and the instructions
2619		 before the candidate delay slot.  */
2620	      || nops_for_insn (history + 1, ip) > 0
2621	      /* Check for conflicts between the swapped sequence and the
2622		 target of the branch.  */
2623	      || nops_for_sequence (2, history + 1, ip, history) > 0
2624	      /* We do not swap with a trap instruction, since it
2625		 complicates trap handlers to have the trap
2626		 instruction be in a delay slot.  */
2627	      || (prev_pinfo & INSN_TRAP)
2628	      /* If the branch reads a register that the previous
2629		 instruction sets, we can not swap.  */
2630	      || (! mips_opts.mips16
2631		  && (prev_pinfo & INSN_WRITE_GPR_T)
2632		  && insn_uses_reg (ip, EXTRACT_OPERAND (RT, history[0]),
2633				    MIPS_GR_REG))
2634	      || (! mips_opts.mips16
2635		  && (prev_pinfo & INSN_WRITE_GPR_D)
2636		  && insn_uses_reg (ip, EXTRACT_OPERAND (RD, history[0]),
2637				    MIPS_GR_REG))
2638	      || (mips_opts.mips16
2639		  && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2640		       && (insn_uses_reg
2641			   (ip, MIPS16_EXTRACT_OPERAND (RX, history[0]),
2642			    MIPS16_REG)))
2643		      || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2644			  && (insn_uses_reg
2645			      (ip, MIPS16_EXTRACT_OPERAND (RY, history[0]),
2646			       MIPS16_REG)))
2647		      || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2648			  && (insn_uses_reg
2649			      (ip, MIPS16_EXTRACT_OPERAND (RZ, history[0]),
2650			       MIPS16_REG)))
2651		      || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2652			  && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2653		      || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2654			  && insn_uses_reg (ip, RA, MIPS_GR_REG))
2655		      || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2656			  && insn_uses_reg (ip,
2657					    MIPS16OP_EXTRACT_REG32R
2658					      (history[0].insn_opcode),
2659					    MIPS_GR_REG))))
2660	      /* If the branch writes a register that the previous
2661		 instruction sets, we can not swap (we know that
2662		 branches write only to RD or to $31).  */
2663	      || (! mips_opts.mips16
2664		  && (prev_pinfo & INSN_WRITE_GPR_T)
2665		  && (((pinfo & INSN_WRITE_GPR_D)
2666		       && (EXTRACT_OPERAND (RT, history[0])
2667			   == EXTRACT_OPERAND (RD, *ip)))
2668		      || ((pinfo & INSN_WRITE_GPR_31)
2669			  && EXTRACT_OPERAND (RT, history[0]) == RA)))
2670	      || (! mips_opts.mips16
2671		  && (prev_pinfo & INSN_WRITE_GPR_D)
2672		  && (((pinfo & INSN_WRITE_GPR_D)
2673		       && (EXTRACT_OPERAND (RD, history[0])
2674			   == EXTRACT_OPERAND (RD, *ip)))
2675		      || ((pinfo & INSN_WRITE_GPR_31)
2676			  && EXTRACT_OPERAND (RD, history[0]) == RA)))
2677	      || (mips_opts.mips16
2678		  && (pinfo & MIPS16_INSN_WRITE_31)
2679		  && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2680		      || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2681			  && (MIPS16OP_EXTRACT_REG32R (history[0].insn_opcode)
2682			      == RA))))
2683	      /* If the branch writes a register that the previous
2684		 instruction reads, we can not swap (we know that
2685		 branches only write to RD or to $31).  */
2686	      || (! mips_opts.mips16
2687		  && (pinfo & INSN_WRITE_GPR_D)
2688		  && insn_uses_reg (&history[0],
2689				    EXTRACT_OPERAND (RD, *ip),
2690				    MIPS_GR_REG))
2691	      || (! mips_opts.mips16
2692		  && (pinfo & INSN_WRITE_GPR_31)
2693		  && insn_uses_reg (&history[0], RA, MIPS_GR_REG))
2694	      || (mips_opts.mips16
2695		  && (pinfo & MIPS16_INSN_WRITE_31)
2696		  && insn_uses_reg (&history[0], RA, MIPS_GR_REG))
2697	      /* If one instruction sets a condition code and the
2698                 other one uses a condition code, we can not swap.  */
2699	      || ((pinfo & INSN_READ_COND_CODE)
2700		  && (prev_pinfo & INSN_WRITE_COND_CODE))
2701	      || ((pinfo & INSN_WRITE_COND_CODE)
2702		  && (prev_pinfo & INSN_READ_COND_CODE))
2703	      /* If the previous instruction uses the PC, we can not
2704                 swap.  */
2705	      || (mips_opts.mips16
2706		  && (prev_pinfo & MIPS16_INSN_READ_PC))
2707	      /* If the previous instruction had a fixup in mips16
2708                 mode, we can not swap.  This normally means that the
2709                 previous instruction was a 4 byte branch anyhow.  */
2710	      || (mips_opts.mips16 && history[0].fixp[0])
2711	      /* If the previous instruction is a sync, sync.l, or
2712		 sync.p, we can not swap.  */
2713	      || (prev_pinfo & INSN_SYNC))
2714	    {
2715	      if (mips_opts.mips16
2716		  && (pinfo & INSN_UNCOND_BRANCH_DELAY)
2717		  && (pinfo & (MIPS16_INSN_READ_X | MIPS16_INSN_READ_31))
2718		  && (mips_opts.isa == ISA_MIPS32
2719		      || mips_opts.isa == ISA_MIPS32R2
2720		      || mips_opts.isa == ISA_MIPS64
2721		      || mips_opts.isa == ISA_MIPS64R2))
2722		{
2723		  /* Convert MIPS16 jr/jalr into a "compact" jump.  */
2724		  ip->insn_opcode |= 0x0080;
2725		  install_insn (ip);
2726		  insert_into_history (0, 1, ip);
2727		}
2728	      else
2729		{
2730		  /* We could do even better for unconditional branches to
2731		     portions of this object file; we could pick up the
2732		     instruction at the destination, put it in the delay
2733		     slot, and bump the destination address.  */
2734		  insert_into_history (0, 1, ip);
2735		  emit_nop ();
2736		}
2737
2738	      if (mips_relax.sequence)
2739		mips_relax.sizes[mips_relax.sequence - 1] += 4;
2740	    }
2741	  else
2742	    {
2743	      /* It looks like we can actually do the swap.  */
2744	      struct mips_cl_insn delay = history[0];
2745	      if (mips_opts.mips16)
2746		{
2747		  know (delay.frag == ip->frag);
2748                  move_insn (ip, delay.frag, delay.where);
2749		  move_insn (&delay, ip->frag, ip->where + insn_length (ip));
2750		}
2751	      else if (relaxed_branch)
2752		{
2753		  /* Add the delay slot instruction to the end of the
2754		     current frag and shrink the fixed part of the
2755		     original frag.  If the branch occupies the tail of
2756		     the latter, move it backwards to cover the gap.  */
2757		  delay.frag->fr_fix -= 4;
2758		  if (delay.frag == ip->frag)
2759		    move_insn (ip, ip->frag, ip->where - 4);
2760		  add_fixed_insn (&delay);
2761		}
2762	      else
2763		{
2764		  move_insn (&delay, ip->frag, ip->where);
2765		  move_insn (ip, history[0].frag, history[0].where);
2766		}
2767	      history[0] = *ip;
2768	      delay.fixed_p = 1;
2769	      insert_into_history (0, 1, &delay);
2770	    }
2771
2772	  /* If that was an unconditional branch, forget the previous
2773	     insn information.  */
2774	  if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2775	    mips_no_prev_insn ();
2776	}
2777      else if (pinfo & INSN_COND_BRANCH_LIKELY)
2778	{
2779	  /* We don't yet optimize a branch likely.  What we should do
2780	     is look at the target, copy the instruction found there
2781	     into the delay slot, and increment the branch to jump to
2782	     the next instruction.  */
2783	  insert_into_history (0, 1, ip);
2784	  emit_nop ();
2785	}
2786      else
2787	insert_into_history (0, 1, ip);
2788    }
2789  else
2790    insert_into_history (0, 1, ip);
2791
2792  /* We just output an insn, so the next one doesn't have a label.  */
2793  mips_clear_insn_labels ();
2794}
2795
2796/* Forget that there was any previous instruction or label.  */
2797
2798static void
2799mips_no_prev_insn (void)
2800{
2801  prev_nop_frag = NULL;
2802  insert_into_history (0, ARRAY_SIZE (history), NOP_INSN);
2803  mips_clear_insn_labels ();
2804}
2805
2806/* This function must be called before we emit something other than
2807   instructions.  It is like mips_no_prev_insn except that it inserts
2808   any NOPS that might be needed by previous instructions.  */
2809
2810void
2811mips_emit_delays (void)
2812{
2813  if (! mips_opts.noreorder)
2814    {
2815      int nops = nops_for_insn (history, NULL);
2816      if (nops > 0)
2817	{
2818	  while (nops-- > 0)
2819	    add_fixed_insn (NOP_INSN);
2820	  mips_move_labels ();
2821	}
2822    }
2823  mips_no_prev_insn ();
2824}
2825
2826/* Start a (possibly nested) noreorder block.  */
2827
2828static void
2829start_noreorder (void)
2830{
2831  if (mips_opts.noreorder == 0)
2832    {
2833      unsigned int i;
2834      int nops;
2835
2836      /* None of the instructions before the .set noreorder can be moved.  */
2837      for (i = 0; i < ARRAY_SIZE (history); i++)
2838	history[i].fixed_p = 1;
2839
2840      /* Insert any nops that might be needed between the .set noreorder
2841	 block and the previous instructions.  We will later remove any
2842	 nops that turn out not to be needed.  */
2843      nops = nops_for_insn (history, NULL);
2844      if (nops > 0)
2845	{
2846	  if (mips_optimize != 0)
2847	    {
2848	      /* Record the frag which holds the nop instructions, so
2849                 that we can remove them if we don't need them.  */
2850	      frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2851	      prev_nop_frag = frag_now;
2852	      prev_nop_frag_holds = nops;
2853	      prev_nop_frag_required = 0;
2854	      prev_nop_frag_since = 0;
2855	    }
2856
2857	  for (; nops > 0; --nops)
2858	    add_fixed_insn (NOP_INSN);
2859
2860	  /* Move on to a new frag, so that it is safe to simply
2861	     decrease the size of prev_nop_frag.  */
2862	  frag_wane (frag_now);
2863	  frag_new (0);
2864	  mips_move_labels ();
2865	}
2866      mips16_mark_labels ();
2867      mips_clear_insn_labels ();
2868    }
2869  mips_opts.noreorder++;
2870  mips_any_noreorder = 1;
2871}
2872
2873/* End a nested noreorder block.  */
2874
2875static void
2876end_noreorder (void)
2877{
2878  mips_opts.noreorder--;
2879  if (mips_opts.noreorder == 0 && prev_nop_frag != NULL)
2880    {
2881      /* Commit to inserting prev_nop_frag_required nops and go back to
2882	 handling nop insertion the .set reorder way.  */
2883      prev_nop_frag->fr_fix -= ((prev_nop_frag_holds - prev_nop_frag_required)
2884				* (mips_opts.mips16 ? 2 : 4));
2885      insert_into_history (prev_nop_frag_since,
2886			   prev_nop_frag_required, NOP_INSN);
2887      prev_nop_frag = NULL;
2888    }
2889}
2890
2891/* Set up global variables for the start of a new macro.  */
2892
2893static void
2894macro_start (void)
2895{
2896  memset (&mips_macro_warning.sizes, 0, sizeof (mips_macro_warning.sizes));
2897  mips_macro_warning.delay_slot_p = (mips_opts.noreorder
2898				     && (history[0].insn_mo->pinfo
2899					 & (INSN_UNCOND_BRANCH_DELAY
2900					    | INSN_COND_BRANCH_DELAY
2901					    | INSN_COND_BRANCH_LIKELY)) != 0);
2902}
2903
2904/* Given that a macro is longer than 4 bytes, return the appropriate warning
2905   for it.  Return null if no warning is needed.  SUBTYPE is a bitmask of
2906   RELAX_DELAY_SLOT and RELAX_NOMACRO.  */
2907
2908static const char *
2909macro_warning (relax_substateT subtype)
2910{
2911  if (subtype & RELAX_DELAY_SLOT)
2912    return _("Macro instruction expanded into multiple instructions"
2913	     " in a branch delay slot");
2914  else if (subtype & RELAX_NOMACRO)
2915    return _("Macro instruction expanded into multiple instructions");
2916  else
2917    return 0;
2918}
2919
2920/* Finish up a macro.  Emit warnings as appropriate.  */
2921
2922static void
2923macro_end (void)
2924{
2925  if (mips_macro_warning.sizes[0] > 4 || mips_macro_warning.sizes[1] > 4)
2926    {
2927      relax_substateT subtype;
2928
2929      /* Set up the relaxation warning flags.  */
2930      subtype = 0;
2931      if (mips_macro_warning.sizes[1] > mips_macro_warning.sizes[0])
2932	subtype |= RELAX_SECOND_LONGER;
2933      if (mips_opts.warn_about_macros)
2934	subtype |= RELAX_NOMACRO;
2935      if (mips_macro_warning.delay_slot_p)
2936	subtype |= RELAX_DELAY_SLOT;
2937
2938      if (mips_macro_warning.sizes[0] > 4 && mips_macro_warning.sizes[1] > 4)
2939	{
2940	  /* Either the macro has a single implementation or both
2941	     implementations are longer than 4 bytes.  Emit the
2942	     warning now.  */
2943	  const char *msg = macro_warning (subtype);
2944	  if (msg != 0)
2945	    as_warn (msg);
2946	}
2947      else
2948	{
2949	  /* One implementation might need a warning but the other
2950	     definitely doesn't.  */
2951	  mips_macro_warning.first_frag->fr_subtype |= subtype;
2952	}
2953    }
2954}
2955
2956/* Read a macro's relocation codes from *ARGS and store them in *R.
2957   The first argument in *ARGS will be either the code for a single
2958   relocation or -1 followed by the three codes that make up a
2959   composite relocation.  */
2960
2961static void
2962macro_read_relocs (va_list *args, bfd_reloc_code_real_type *r)
2963{
2964  int i, next;
2965
2966  next = va_arg (*args, int);
2967  if (next >= 0)
2968    r[0] = (bfd_reloc_code_real_type) next;
2969  else
2970    for (i = 0; i < 3; i++)
2971      r[i] = (bfd_reloc_code_real_type) va_arg (*args, int);
2972}
2973
2974/* Build an instruction created by a macro expansion.  This is passed
2975   a pointer to the count of instructions created so far, an
2976   expression, the name of the instruction to build, an operand format
2977   string, and corresponding arguments.  */
2978
2979static void
2980macro_build (expressionS *ep, const char *name, const char *fmt, ...)
2981{
2982  const struct mips_opcode *mo;
2983  struct mips_cl_insn insn;
2984  bfd_reloc_code_real_type r[3];
2985  va_list args;
2986
2987  va_start (args, fmt);
2988
2989  if (mips_opts.mips16)
2990    {
2991      mips16_macro_build (ep, name, fmt, args);
2992      va_end (args);
2993      return;
2994    }
2995
2996  r[0] = BFD_RELOC_UNUSED;
2997  r[1] = BFD_RELOC_UNUSED;
2998  r[2] = BFD_RELOC_UNUSED;
2999  mo = (struct mips_opcode *) hash_find (op_hash, name);
3000  assert (mo);
3001  assert (strcmp (name, mo->name) == 0);
3002
3003  /* Search until we get a match for NAME.  It is assumed here that
3004     macros will never generate MDMX or MIPS-3D instructions.  */
3005  while (strcmp (fmt, mo->args) != 0
3006	 || mo->pinfo == INSN_MACRO
3007	 || !OPCODE_IS_MEMBER (mo,
3008			       (mips_opts.isa
3009				| (file_ase_mips16 ? INSN_MIPS16 : 0)),
3010			       mips_opts.arch)
3011	 || (mips_opts.arch == CPU_R4650 && (mo->pinfo & FP_D) != 0))
3012    {
3013      ++mo;
3014      assert (mo->name);
3015      assert (strcmp (name, mo->name) == 0);
3016    }
3017
3018  create_insn (&insn, mo);
3019  for (;;)
3020    {
3021      switch (*fmt++)
3022	{
3023	case '\0':
3024	  break;
3025
3026	case ',':
3027	case '(':
3028	case ')':
3029	  continue;
3030
3031	case '+':
3032	  switch (*fmt++)
3033	    {
3034	    case 'A':
3035	    case 'E':
3036	      INSERT_OPERAND (SHAMT, insn, va_arg (args, int));
3037	      continue;
3038
3039	    case 'B':
3040	    case 'F':
3041	      /* Note that in the macro case, these arguments are already
3042		 in MSB form.  (When handling the instruction in the
3043		 non-macro case, these arguments are sizes from which
3044		 MSB values must be calculated.)  */
3045	      INSERT_OPERAND (INSMSB, insn, va_arg (args, int));
3046	      continue;
3047
3048	    case 'C':
3049	    case 'G':
3050	    case 'H':
3051	      /* Note that in the macro case, these arguments are already
3052		 in MSBD form.  (When handling the instruction in the
3053		 non-macro case, these arguments are sizes from which
3054		 MSBD values must be calculated.)  */
3055	      INSERT_OPERAND (EXTMSBD, insn, va_arg (args, int));
3056	      continue;
3057
3058	    default:
3059	      internalError ();
3060	    }
3061	  continue;
3062
3063	case 't':
3064	case 'w':
3065	case 'E':
3066	  INSERT_OPERAND (RT, insn, va_arg (args, int));
3067	  continue;
3068
3069	case 'c':
3070	  INSERT_OPERAND (CODE, insn, va_arg (args, int));
3071	  continue;
3072
3073	case 'T':
3074	case 'W':
3075	  INSERT_OPERAND (FT, insn, va_arg (args, int));
3076	  continue;
3077
3078	case 'd':
3079	case 'G':
3080	case 'K':
3081	  INSERT_OPERAND (RD, insn, va_arg (args, int));
3082	  continue;
3083
3084	case 'U':
3085	  {
3086	    int tmp = va_arg (args, int);
3087
3088	    INSERT_OPERAND (RT, insn, tmp);
3089	    INSERT_OPERAND (RD, insn, tmp);
3090	    continue;
3091	  }
3092
3093	case 'V':
3094	case 'S':
3095	  INSERT_OPERAND (FS, insn, va_arg (args, int));
3096	  continue;
3097
3098	case 'z':
3099	  continue;
3100
3101	case '<':
3102	  INSERT_OPERAND (SHAMT, insn, va_arg (args, int));
3103	  continue;
3104
3105	case 'D':
3106	  INSERT_OPERAND (FD, insn, va_arg (args, int));
3107	  continue;
3108
3109	case 'B':
3110	  INSERT_OPERAND (CODE20, insn, va_arg (args, int));
3111	  continue;
3112
3113	case 'J':
3114	  INSERT_OPERAND (CODE19, insn, va_arg (args, int));
3115	  continue;
3116
3117	case 'q':
3118	  INSERT_OPERAND (CODE2, insn, va_arg (args, int));
3119	  continue;
3120
3121	case 'b':
3122	case 's':
3123	case 'r':
3124	case 'v':
3125	  INSERT_OPERAND (RS, insn, va_arg (args, int));
3126	  continue;
3127
3128	case 'i':
3129	case 'j':
3130	case 'o':
3131	  macro_read_relocs (&args, r);
3132	  assert (*r == BFD_RELOC_GPREL16
3133		  || *r == BFD_RELOC_MIPS_LITERAL
3134		  || *r == BFD_RELOC_MIPS_HIGHER
3135		  || *r == BFD_RELOC_HI16_S
3136		  || *r == BFD_RELOC_LO16
3137		  || *r == BFD_RELOC_MIPS_GOT16
3138		  || *r == BFD_RELOC_MIPS_CALL16
3139		  || *r == BFD_RELOC_MIPS_GOT_DISP
3140		  || *r == BFD_RELOC_MIPS_GOT_PAGE
3141		  || *r == BFD_RELOC_MIPS_GOT_OFST
3142		  || *r == BFD_RELOC_MIPS_GOT_LO16
3143		  || *r == BFD_RELOC_MIPS_CALL_LO16);
3144	  continue;
3145
3146	case 'u':
3147	  macro_read_relocs (&args, r);
3148	  assert (ep != NULL
3149		  && (ep->X_op == O_constant
3150		      || (ep->X_op == O_symbol
3151			  && (*r == BFD_RELOC_MIPS_HIGHEST
3152			      || *r == BFD_RELOC_HI16_S
3153			      || *r == BFD_RELOC_HI16
3154			      || *r == BFD_RELOC_GPREL16
3155			      || *r == BFD_RELOC_MIPS_GOT_HI16
3156			      || *r == BFD_RELOC_MIPS_CALL_HI16))));
3157	  continue;
3158
3159	case 'p':
3160	  assert (ep != NULL);
3161
3162	  /*
3163	   * This allows macro() to pass an immediate expression for
3164	   * creating short branches without creating a symbol.
3165	   *
3166	   * We don't allow branch relaxation for these branches, as
3167	   * they should only appear in ".set nomacro" anyway.
3168	   */
3169	  if (ep->X_op == O_constant)
3170	    {
3171	      if ((ep->X_add_number & 3) != 0)
3172		as_bad (_("branch to misaligned address (0x%lx)"),
3173			(unsigned long) ep->X_add_number);
3174	      if ((ep->X_add_number + 0x20000) & ~0x3ffff)
3175		as_bad (_("branch address range overflow (0x%lx)"),
3176			(unsigned long) ep->X_add_number);
3177	      insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3178	      ep = NULL;
3179	    }
3180	  else
3181	    *r = BFD_RELOC_16_PCREL_S2;
3182	  continue;
3183
3184	case 'a':
3185	  assert (ep != NULL);
3186	  *r = BFD_RELOC_MIPS_JMP;
3187	  continue;
3188
3189	case 'C':
3190	  insn.insn_opcode |= va_arg (args, unsigned long);
3191	  continue;
3192
3193	default:
3194	  internalError ();
3195	}
3196      break;
3197    }
3198  va_end (args);
3199  assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3200
3201  append_insn (&insn, ep, r);
3202}
3203
3204static void
3205mips16_macro_build (expressionS *ep, const char *name, const char *fmt,
3206		    va_list args)
3207{
3208  struct mips_opcode *mo;
3209  struct mips_cl_insn insn;
3210  bfd_reloc_code_real_type r[3]
3211    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3212
3213  mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3214  assert (mo);
3215  assert (strcmp (name, mo->name) == 0);
3216
3217  while (strcmp (fmt, mo->args) != 0 || mo->pinfo == INSN_MACRO)
3218    {
3219      ++mo;
3220      assert (mo->name);
3221      assert (strcmp (name, mo->name) == 0);
3222    }
3223
3224  create_insn (&insn, mo);
3225  for (;;)
3226    {
3227      int c;
3228
3229      c = *fmt++;
3230      switch (c)
3231	{
3232	case '\0':
3233	  break;
3234
3235	case ',':
3236	case '(':
3237	case ')':
3238	  continue;
3239
3240	case 'y':
3241	case 'w':
3242	  MIPS16_INSERT_OPERAND (RY, insn, va_arg (args, int));
3243	  continue;
3244
3245	case 'x':
3246	case 'v':
3247	  MIPS16_INSERT_OPERAND (RX, insn, va_arg (args, int));
3248	  continue;
3249
3250	case 'z':
3251	  MIPS16_INSERT_OPERAND (RZ, insn, va_arg (args, int));
3252	  continue;
3253
3254	case 'Z':
3255	  MIPS16_INSERT_OPERAND (MOVE32Z, insn, va_arg (args, int));
3256	  continue;
3257
3258	case '0':
3259	case 'S':
3260	case 'P':
3261	case 'R':
3262	  continue;
3263
3264	case 'X':
3265	  MIPS16_INSERT_OPERAND (REGR32, insn, va_arg (args, int));
3266	  continue;
3267
3268	case 'Y':
3269	  {
3270	    int regno;
3271
3272	    regno = va_arg (args, int);
3273	    regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3274	    insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3275	  }
3276	  continue;
3277
3278	case '<':
3279	case '>':
3280	case '4':
3281	case '5':
3282	case 'H':
3283	case 'W':
3284	case 'D':
3285	case 'j':
3286	case '8':
3287	case 'V':
3288	case 'C':
3289	case 'U':
3290	case 'k':
3291	case 'K':
3292	case 'p':
3293	case 'q':
3294	  {
3295	    assert (ep != NULL);
3296
3297	    if (ep->X_op != O_constant)
3298	      *r = (int) BFD_RELOC_UNUSED + c;
3299	    else
3300	      {
3301		mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3302			      FALSE, &insn.insn_opcode, &insn.use_extend,
3303			      &insn.extend);
3304		ep = NULL;
3305		*r = BFD_RELOC_UNUSED;
3306	      }
3307	  }
3308	  continue;
3309
3310	case '6':
3311	  MIPS16_INSERT_OPERAND (IMM6, insn, va_arg (args, int));
3312	  continue;
3313	}
3314
3315      break;
3316    }
3317
3318  assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3319
3320  append_insn (&insn, ep, r);
3321}
3322
3323/*
3324 * Sign-extend 32-bit mode constants that have bit 31 set and all
3325 * higher bits unset.
3326 */
3327static void
3328normalize_constant_expr (expressionS *ex)
3329{
3330  if (ex->X_op == O_constant
3331      && IS_ZEXT_32BIT_NUM (ex->X_add_number))
3332    ex->X_add_number = (((ex->X_add_number & 0xffffffff) ^ 0x80000000)
3333			- 0x80000000);
3334}
3335
3336/*
3337 * Sign-extend 32-bit mode address offsets that have bit 31 set and
3338 * all higher bits unset.
3339 */
3340static void
3341normalize_address_expr (expressionS *ex)
3342{
3343  if (((ex->X_op == O_constant && HAVE_32BIT_ADDRESSES)
3344	|| (ex->X_op == O_symbol && HAVE_32BIT_SYMBOLS))
3345      && IS_ZEXT_32BIT_NUM (ex->X_add_number))
3346    ex->X_add_number = (((ex->X_add_number & 0xffffffff) ^ 0x80000000)
3347			- 0x80000000);
3348}
3349
3350/*
3351 * Generate a "jalr" instruction with a relocation hint to the called
3352 * function.  This occurs in NewABI PIC code.
3353 */
3354static void
3355macro_build_jalr (expressionS *ep)
3356{
3357  char *f = NULL;
3358
3359  if (HAVE_NEWABI)
3360    {
3361      frag_grow (8);
3362      f = frag_more (0);
3363    }
3364  macro_build (NULL, "jalr", "d,s", RA, PIC_CALL_REG);
3365  if (HAVE_NEWABI)
3366    fix_new_exp (frag_now, f - frag_now->fr_literal,
3367		 4, ep, FALSE, BFD_RELOC_MIPS_JALR);
3368}
3369
3370/*
3371 * Generate a "lui" instruction.
3372 */
3373static void
3374macro_build_lui (expressionS *ep, int regnum)
3375{
3376  expressionS high_expr;
3377  const struct mips_opcode *mo;
3378  struct mips_cl_insn insn;
3379  bfd_reloc_code_real_type r[3]
3380    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3381  const char *name = "lui";
3382  const char *fmt = "t,u";
3383
3384  assert (! mips_opts.mips16);
3385
3386  high_expr = *ep;
3387
3388  if (high_expr.X_op == O_constant)
3389    {
3390      /* we can compute the instruction now without a relocation entry */
3391      high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3392				>> 16) & 0xffff;
3393      *r = BFD_RELOC_UNUSED;
3394    }
3395  else
3396    {
3397      assert (ep->X_op == O_symbol);
3398      /* _gp_disp is a special case, used from s_cpload.
3399	 __gnu_local_gp is used if mips_no_shared.  */
3400      assert (mips_pic == NO_PIC
3401	      || (! HAVE_NEWABI
3402		  && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0)
3403	      || (! mips_in_shared
3404		  && strcmp (S_GET_NAME (ep->X_add_symbol),
3405                             "__gnu_local_gp") == 0));
3406      *r = BFD_RELOC_HI16_S;
3407    }
3408
3409  mo = hash_find (op_hash, name);
3410  assert (strcmp (name, mo->name) == 0);
3411  assert (strcmp (fmt, mo->args) == 0);
3412  create_insn (&insn, mo);
3413
3414  insn.insn_opcode = insn.insn_mo->match;
3415  INSERT_OPERAND (RT, insn, regnum);
3416  if (*r == BFD_RELOC_UNUSED)
3417    {
3418      insn.insn_opcode |= high_expr.X_add_number;
3419      append_insn (&insn, NULL, r);
3420    }
3421  else
3422    append_insn (&insn, &high_expr, r);
3423}
3424
3425/* Generate a sequence of instructions to do a load or store from a constant
3426   offset off of a base register (breg) into/from a target register (treg),
3427   using AT if necessary.  */
3428static void
3429macro_build_ldst_constoffset (expressionS *ep, const char *op,
3430			      int treg, int breg, int dbl)
3431{
3432  assert (ep->X_op == O_constant);
3433
3434  /* Sign-extending 32-bit constants makes their handling easier.  */
3435  if (!dbl)
3436    normalize_constant_expr (ep);
3437
3438  /* Right now, this routine can only handle signed 32-bit constants.  */
3439  if (! IS_SEXT_32BIT_NUM(ep->X_add_number + 0x8000))
3440    as_warn (_("operand overflow"));
3441
3442  if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3443    {
3444      /* Signed 16-bit offset will fit in the op.  Easy!  */
3445      macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, breg);
3446    }
3447  else
3448    {
3449      /* 32-bit offset, need multiple instructions and AT, like:
3450	   lui      $tempreg,const_hi       (BFD_RELOC_HI16_S)
3451	   addu     $tempreg,$tempreg,$breg
3452           <op>     $treg,const_lo($tempreg)   (BFD_RELOC_LO16)
3453         to handle the complete offset.  */
3454      macro_build_lui (ep, AT);
3455      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
3456      macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, AT);
3457
3458      if (mips_opts.noat)
3459	as_bad (_("Macro used $at after \".set noat\""));
3460    }
3461}
3462
3463/*			set_at()
3464 * Generates code to set the $at register to true (one)
3465 * if reg is less than the immediate expression.
3466 */
3467static void
3468set_at (int reg, int unsignedp)
3469{
3470  if (imm_expr.X_op == O_constant
3471      && imm_expr.X_add_number >= -0x8000
3472      && imm_expr.X_add_number < 0x8000)
3473    macro_build (&imm_expr, unsignedp ? "sltiu" : "slti", "t,r,j",
3474		 AT, reg, BFD_RELOC_LO16);
3475  else
3476    {
3477      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
3478      macro_build (NULL, unsignedp ? "sltu" : "slt", "d,v,t", AT, reg, AT);
3479    }
3480}
3481
3482/* Warn if an expression is not a constant.  */
3483
3484static void
3485check_absolute_expr (struct mips_cl_insn *ip, expressionS *ex)
3486{
3487  if (ex->X_op == O_big)
3488    as_bad (_("unsupported large constant"));
3489  else if (ex->X_op != O_constant)
3490    as_bad (_("Instruction %s requires absolute expression"),
3491	    ip->insn_mo->name);
3492
3493  if (HAVE_32BIT_GPRS)
3494    normalize_constant_expr (ex);
3495}
3496
3497/* Count the leading zeroes by performing a binary chop. This is a
3498   bulky bit of source, but performance is a LOT better for the
3499   majority of values than a simple loop to count the bits:
3500       for (lcnt = 0; (lcnt < 32); lcnt++)
3501         if ((v) & (1 << (31 - lcnt)))
3502           break;
3503  However it is not code size friendly, and the gain will drop a bit
3504  on certain cached systems.
3505*/
3506#define COUNT_TOP_ZEROES(v)             \
3507  (((v) & ~0xffff) == 0                 \
3508   ? ((v) & ~0xff) == 0                 \
3509     ? ((v) & ~0xf) == 0                \
3510       ? ((v) & ~0x3) == 0              \
3511         ? ((v) & ~0x1) == 0            \
3512           ? !(v)                       \
3513             ? 32                       \
3514             : 31                       \
3515           : 30                         \
3516         : ((v) & ~0x7) == 0            \
3517           ? 29                         \
3518           : 28                         \
3519       : ((v) & ~0x3f) == 0             \
3520         ? ((v) & ~0x1f) == 0           \
3521           ? 27                         \
3522           : 26                         \
3523         : ((v) & ~0x7f) == 0           \
3524           ? 25                         \
3525           : 24                         \
3526     : ((v) & ~0xfff) == 0              \
3527       ? ((v) & ~0x3ff) == 0            \
3528         ? ((v) & ~0x1ff) == 0          \
3529           ? 23                         \
3530           : 22                         \
3531         : ((v) & ~0x7ff) == 0          \
3532           ? 21                         \
3533           : 20                         \
3534       : ((v) & ~0x3fff) == 0           \
3535         ? ((v) & ~0x1fff) == 0         \
3536           ? 19                         \
3537           : 18                         \
3538         : ((v) & ~0x7fff) == 0         \
3539           ? 17                         \
3540           : 16                         \
3541   : ((v) & ~0xffffff) == 0             \
3542     ? ((v) & ~0xfffff) == 0            \
3543       ? ((v) & ~0x3ffff) == 0          \
3544         ? ((v) & ~0x1ffff) == 0        \
3545           ? 15                         \
3546           : 14                         \
3547         : ((v) & ~0x7ffff) == 0        \
3548           ? 13                         \
3549           : 12                         \
3550       : ((v) & ~0x3fffff) == 0         \
3551         ? ((v) & ~0x1fffff) == 0       \
3552           ? 11                         \
3553           : 10                         \
3554         : ((v) & ~0x7fffff) == 0       \
3555           ? 9                          \
3556           : 8                          \
3557     : ((v) & ~0xfffffff) == 0          \
3558       ? ((v) & ~0x3ffffff) == 0        \
3559         ? ((v) & ~0x1ffffff) == 0      \
3560           ? 7                          \
3561           : 6                          \
3562         : ((v) & ~0x7ffffff) == 0      \
3563           ? 5                          \
3564           : 4                          \
3565       : ((v) & ~0x3fffffff) == 0       \
3566         ? ((v) & ~0x1fffffff) == 0     \
3567           ? 3                          \
3568           : 2                          \
3569         : ((v) & ~0x7fffffff) == 0     \
3570           ? 1                          \
3571           : 0)
3572
3573/*			load_register()
3574 *  This routine generates the least number of instructions necessary to load
3575 *  an absolute expression value into a register.
3576 */
3577static void
3578load_register (int reg, expressionS *ep, int dbl)
3579{
3580  int freg;
3581  expressionS hi32, lo32;
3582
3583  if (ep->X_op != O_big)
3584    {
3585      assert (ep->X_op == O_constant);
3586
3587      /* Sign-extending 32-bit constants makes their handling easier.  */
3588      if (!dbl)
3589	normalize_constant_expr (ep);
3590
3591      if (IS_SEXT_16BIT_NUM (ep->X_add_number))
3592	{
3593	  /* We can handle 16 bit signed values with an addiu to
3594	     $zero.  No need to ever use daddiu here, since $zero and
3595	     the result are always correct in 32 bit mode.  */
3596	  macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3597	  return;
3598	}
3599      else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3600	{
3601	  /* We can handle 16 bit unsigned values with an ori to
3602             $zero.  */
3603	  macro_build (ep, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
3604	  return;
3605	}
3606      else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)))
3607	{
3608	  /* 32 bit values require an lui.  */
3609	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_HI16);
3610	  if ((ep->X_add_number & 0xffff) != 0)
3611	    macro_build (ep, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
3612	  return;
3613	}
3614    }
3615
3616  /* The value is larger than 32 bits.  */
3617
3618  if (!dbl || HAVE_32BIT_GPRS)
3619    {
3620      char value[32];
3621
3622      sprintf_vma (value, ep->X_add_number);
3623      as_bad (_("Number (0x%s) larger than 32 bits"), value);
3624      macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3625      return;
3626    }
3627
3628  if (ep->X_op != O_big)
3629    {
3630      hi32 = *ep;
3631      hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3632      hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3633      hi32.X_add_number &= 0xffffffff;
3634      lo32 = *ep;
3635      lo32.X_add_number &= 0xffffffff;
3636    }
3637  else
3638    {
3639      assert (ep->X_add_number > 2);
3640      if (ep->X_add_number == 3)
3641	generic_bignum[3] = 0;
3642      else if (ep->X_add_number > 4)
3643	as_bad (_("Number larger than 64 bits"));
3644      lo32.X_op = O_constant;
3645      lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3646      hi32.X_op = O_constant;
3647      hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3648    }
3649
3650  if (hi32.X_add_number == 0)
3651    freg = 0;
3652  else
3653    {
3654      int shift, bit;
3655      unsigned long hi, lo;
3656
3657      if (hi32.X_add_number == (offsetT) 0xffffffff)
3658	{
3659	  if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3660	    {
3661	      macro_build (&lo32, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3662	      return;
3663	    }
3664	  if (lo32.X_add_number & 0x80000000)
3665	    {
3666	      macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
3667	      if (lo32.X_add_number & 0xffff)
3668		macro_build (&lo32, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
3669	      return;
3670	    }
3671	}
3672
3673      /* Check for 16bit shifted constant.  We know that hi32 is
3674         non-zero, so start the mask on the first bit of the hi32
3675         value.  */
3676      shift = 17;
3677      do
3678	{
3679	  unsigned long himask, lomask;
3680
3681	  if (shift < 32)
3682	    {
3683	      himask = 0xffff >> (32 - shift);
3684	      lomask = (0xffff << shift) & 0xffffffff;
3685	    }
3686	  else
3687	    {
3688	      himask = 0xffff << (shift - 32);
3689	      lomask = 0;
3690	    }
3691	  if ((hi32.X_add_number & ~(offsetT) himask) == 0
3692	      && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3693	    {
3694	      expressionS tmp;
3695
3696	      tmp.X_op = O_constant;
3697	      if (shift < 32)
3698		tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3699				    | (lo32.X_add_number >> shift));
3700	      else
3701		tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3702	      macro_build (&tmp, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
3703	      macro_build (NULL, (shift >= 32) ? "dsll32" : "dsll", "d,w,<",
3704			   reg, reg, (shift >= 32) ? shift - 32 : shift);
3705	      return;
3706	    }
3707	  ++shift;
3708	}
3709      while (shift <= (64 - 16));
3710
3711      /* Find the bit number of the lowest one bit, and store the
3712         shifted value in hi/lo.  */
3713      hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3714      lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3715      if (lo != 0)
3716	{
3717	  bit = 0;
3718	  while ((lo & 1) == 0)
3719	    {
3720	      lo >>= 1;
3721	      ++bit;
3722	    }
3723	  lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3724	  hi >>= bit;
3725	}
3726      else
3727	{
3728	  bit = 32;
3729	  while ((hi & 1) == 0)
3730	    {
3731	      hi >>= 1;
3732	      ++bit;
3733	    }
3734	  lo = hi;
3735	  hi = 0;
3736	}
3737
3738      /* Optimize if the shifted value is a (power of 2) - 1.  */
3739      if ((hi == 0 && ((lo + 1) & lo) == 0)
3740	  || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3741	{
3742	  shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3743	  if (shift != 0)
3744	    {
3745	      expressionS tmp;
3746
3747	      /* This instruction will set the register to be all
3748                 ones.  */
3749	      tmp.X_op = O_constant;
3750	      tmp.X_add_number = (offsetT) -1;
3751	      macro_build (&tmp, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3752	      if (bit != 0)
3753		{
3754		  bit += shift;
3755		  macro_build (NULL, (bit >= 32) ? "dsll32" : "dsll", "d,w,<",
3756			       reg, reg, (bit >= 32) ? bit - 32 : bit);
3757		}
3758	      macro_build (NULL, (shift >= 32) ? "dsrl32" : "dsrl", "d,w,<",
3759			   reg, reg, (shift >= 32) ? shift - 32 : shift);
3760	      return;
3761	    }
3762	}
3763
3764      /* Sign extend hi32 before calling load_register, because we can
3765         generally get better code when we load a sign extended value.  */
3766      if ((hi32.X_add_number & 0x80000000) != 0)
3767	hi32.X_add_number |= ~(offsetT) 0xffffffff;
3768      load_register (reg, &hi32, 0);
3769      freg = reg;
3770    }
3771  if ((lo32.X_add_number & 0xffff0000) == 0)
3772    {
3773      if (freg != 0)
3774	{
3775	  macro_build (NULL, "dsll32", "d,w,<", reg, freg, 0);
3776	  freg = reg;
3777	}
3778    }
3779  else
3780    {
3781      expressionS mid16;
3782
3783      if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3784	{
3785	  macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
3786	  macro_build (NULL, "dsrl32", "d,w,<", reg, reg, 0);
3787	  return;
3788	}
3789
3790      if (freg != 0)
3791	{
3792	  macro_build (NULL, "dsll", "d,w,<", reg, freg, 16);
3793	  freg = reg;
3794	}
3795      mid16 = lo32;
3796      mid16.X_add_number >>= 16;
3797      macro_build (&mid16, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
3798      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3799      freg = reg;
3800    }
3801  if ((lo32.X_add_number & 0xffff) != 0)
3802    macro_build (&lo32, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
3803}
3804
3805static inline void
3806load_delay_nop (void)
3807{
3808  if (!gpr_interlocks)
3809    macro_build (NULL, "nop", "");
3810}
3811
3812/* Load an address into a register.  */
3813
3814static void
3815load_address (int reg, expressionS *ep, int *used_at)
3816{
3817  if (ep->X_op != O_constant
3818      && ep->X_op != O_symbol)
3819    {
3820      as_bad (_("expression too complex"));
3821      ep->X_op = O_constant;
3822    }
3823
3824  if (ep->X_op == O_constant)
3825    {
3826      load_register (reg, ep, HAVE_64BIT_ADDRESSES);
3827      return;
3828    }
3829
3830  if (mips_pic == NO_PIC)
3831    {
3832      /* If this is a reference to a GP relative symbol, we want
3833	   addiu	$reg,$gp,<sym>		(BFD_RELOC_GPREL16)
3834	 Otherwise we want
3835	   lui		$reg,<sym>		(BFD_RELOC_HI16_S)
3836	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
3837	 If we have an addend, we always use the latter form.
3838
3839	 With 64bit address space and a usable $at we want
3840	   lui		$reg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
3841	   lui		$at,<sym>		(BFD_RELOC_HI16_S)
3842	   daddiu	$reg,<sym>		(BFD_RELOC_MIPS_HIGHER)
3843	   daddiu	$at,<sym>		(BFD_RELOC_LO16)
3844	   dsll32	$reg,0
3845	   daddu	$reg,$reg,$at
3846
3847	 If $at is already in use, we use a path which is suboptimal
3848	 on superscalar processors.
3849	   lui		$reg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
3850	   daddiu	$reg,<sym>		(BFD_RELOC_MIPS_HIGHER)
3851	   dsll		$reg,16
3852	   daddiu	$reg,<sym>		(BFD_RELOC_HI16_S)
3853	   dsll		$reg,16
3854	   daddiu	$reg,<sym>		(BFD_RELOC_LO16)
3855
3856	 For GP relative symbols in 64bit address space we can use
3857	 the same sequence as in 32bit address space.  */
3858      if (HAVE_64BIT_SYMBOLS)
3859	{
3860	  if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3861	      && !nopic_need_relax (ep->X_add_symbol, 1))
3862	    {
3863	      relax_start (ep->X_add_symbol);
3864	      macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg,
3865			   mips_gp_register, BFD_RELOC_GPREL16);
3866	      relax_switch ();
3867	    }
3868
3869	  if (*used_at == 0 && !mips_opts.noat)
3870	    {
3871	      macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
3872	      macro_build (ep, "lui", "t,u", AT, BFD_RELOC_HI16_S);
3873	      macro_build (ep, "daddiu", "t,r,j", reg, reg,
3874			   BFD_RELOC_MIPS_HIGHER);
3875	      macro_build (ep, "daddiu", "t,r,j", AT, AT, BFD_RELOC_LO16);
3876	      macro_build (NULL, "dsll32", "d,w,<", reg, reg, 0);
3877	      macro_build (NULL, "daddu", "d,v,t", reg, reg, AT);
3878	      *used_at = 1;
3879	    }
3880	  else
3881	    {
3882	      macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
3883	      macro_build (ep, "daddiu", "t,r,j", reg, reg,
3884			   BFD_RELOC_MIPS_HIGHER);
3885	      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3886	      macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_HI16_S);
3887	      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3888	      macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_LO16);
3889	    }
3890
3891	  if (mips_relax.sequence)
3892	    relax_end ();
3893	}
3894      else
3895	{
3896	  if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3897	      && !nopic_need_relax (ep->X_add_symbol, 1))
3898	    {
3899	      relax_start (ep->X_add_symbol);
3900	      macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg,
3901			   mips_gp_register, BFD_RELOC_GPREL16);
3902	      relax_switch ();
3903	    }
3904	  macro_build_lui (ep, reg);
3905	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j",
3906		       reg, reg, BFD_RELOC_LO16);
3907	  if (mips_relax.sequence)
3908	    relax_end ();
3909	}
3910    }
3911  else if (!mips_big_got)
3912    {
3913      expressionS ex;
3914
3915      /* If this is a reference to an external symbol, we want
3916	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
3917	 Otherwise we want
3918	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
3919	   nop
3920	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
3921	 If there is a constant, it must be added in after.
3922
3923	 If we have NewABI, we want
3924	   lw		$reg,<sym+cst>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
3925         unless we're referencing a global symbol with a non-zero
3926         offset, in which case cst must be added separately.  */
3927      if (HAVE_NEWABI)
3928	{
3929	  if (ep->X_add_number)
3930	    {
3931	      ex.X_add_number = ep->X_add_number;
3932	      ep->X_add_number = 0;
3933	      relax_start (ep->X_add_symbol);
3934	      macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3935			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3936	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3937		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3938	      ex.X_op = O_constant;
3939	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
3940			   reg, reg, BFD_RELOC_LO16);
3941	      ep->X_add_number = ex.X_add_number;
3942	      relax_switch ();
3943	    }
3944	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3945		       BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3946	  if (mips_relax.sequence)
3947	    relax_end ();
3948	}
3949      else
3950	{
3951	  ex.X_add_number = ep->X_add_number;
3952	  ep->X_add_number = 0;
3953	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3954		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
3955	  load_delay_nop ();
3956	  relax_start (ep->X_add_symbol);
3957	  relax_switch ();
3958	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
3959		       BFD_RELOC_LO16);
3960	  relax_end ();
3961
3962	  if (ex.X_add_number != 0)
3963	    {
3964	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3965		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3966	      ex.X_op = O_constant;
3967	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
3968			   reg, reg, BFD_RELOC_LO16);
3969	    }
3970	}
3971    }
3972  else if (mips_big_got)
3973    {
3974      expressionS ex;
3975
3976      /* This is the large GOT case.  If this is a reference to an
3977	 external symbol, we want
3978	   lui		$reg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
3979	   addu		$reg,$reg,$gp
3980	   lw		$reg,<sym>($reg)	(BFD_RELOC_MIPS_GOT_LO16)
3981
3982	 Otherwise, for a reference to a local symbol in old ABI, we want
3983	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
3984	   nop
3985	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
3986	 If there is a constant, it must be added in after.
3987
3988	 In the NewABI, for local symbols, with or without offsets, we want:
3989	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT_PAGE)
3990	   addiu	$reg,$reg,<sym>		(BFD_RELOC_MIPS_GOT_OFST)
3991      */
3992      if (HAVE_NEWABI)
3993	{
3994	  ex.X_add_number = ep->X_add_number;
3995	  ep->X_add_number = 0;
3996	  relax_start (ep->X_add_symbol);
3997	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
3998	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
3999		       reg, reg, mips_gp_register);
4000	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
4001		       reg, BFD_RELOC_MIPS_GOT_LO16, reg);
4002	  if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4003	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4004	  else if (ex.X_add_number)
4005	    {
4006	      ex.X_op = O_constant;
4007	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4008			   BFD_RELOC_LO16);
4009	    }
4010
4011	  ep->X_add_number = ex.X_add_number;
4012	  relax_switch ();
4013	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4014		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
4015	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4016		       BFD_RELOC_MIPS_GOT_OFST);
4017	  relax_end ();
4018	}
4019      else
4020	{
4021	  ex.X_add_number = ep->X_add_number;
4022	  ep->X_add_number = 0;
4023	  relax_start (ep->X_add_symbol);
4024	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
4025	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
4026		       reg, reg, mips_gp_register);
4027	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
4028		       reg, BFD_RELOC_MIPS_GOT_LO16, reg);
4029	  relax_switch ();
4030	  if (reg_needs_delay (mips_gp_register))
4031	    {
4032	      /* We need a nop before loading from $gp.  This special
4033		 check is required because the lui which starts the main
4034		 instruction stream does not refer to $gp, and so will not
4035		 insert the nop which may be required.  */
4036	      macro_build (NULL, "nop", "");
4037	    }
4038	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4039		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4040	  load_delay_nop ();
4041	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4042		       BFD_RELOC_LO16);
4043	  relax_end ();
4044
4045	  if (ex.X_add_number != 0)
4046	    {
4047	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4048		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4049	      ex.X_op = O_constant;
4050	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4051			   BFD_RELOC_LO16);
4052	    }
4053	}
4054    }
4055  else
4056    abort ();
4057
4058  if (mips_opts.noat && *used_at == 1)
4059    as_bad (_("Macro used $at after \".set noat\""));
4060}
4061
4062/* Move the contents of register SOURCE into register DEST.  */
4063
4064static void
4065move_register (int dest, int source)
4066{
4067  macro_build (NULL, HAVE_32BIT_GPRS ? "addu" : "daddu", "d,v,t",
4068	       dest, source, 0);
4069}
4070
4071/* Emit an SVR4 PIC sequence to load address LOCAL into DEST, where
4072   LOCAL is the sum of a symbol and a 16-bit or 32-bit displacement.
4073   The two alternatives are:
4074
4075   Global symbol		Local sybmol
4076   -------------		------------
4077   lw DEST,%got(SYMBOL)		lw DEST,%got(SYMBOL + OFFSET)
4078   ...				...
4079   addiu DEST,DEST,OFFSET	addiu DEST,DEST,%lo(SYMBOL + OFFSET)
4080
4081   load_got_offset emits the first instruction and add_got_offset
4082   emits the second for a 16-bit offset or add_got_offset_hilo emits
4083   a sequence to add a 32-bit offset using a scratch register.  */
4084
4085static void
4086load_got_offset (int dest, expressionS *local)
4087{
4088  expressionS global;
4089
4090  global = *local;
4091  global.X_add_number = 0;
4092
4093  relax_start (local->X_add_symbol);
4094  macro_build (&global, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4095	       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4096  relax_switch ();
4097  macro_build (local, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4098	       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4099  relax_end ();
4100}
4101
4102static void
4103add_got_offset (int dest, expressionS *local)
4104{
4105  expressionS global;
4106
4107  global.X_op = O_constant;
4108  global.X_op_symbol = NULL;
4109  global.X_add_symbol = NULL;
4110  global.X_add_number = local->X_add_number;
4111
4112  relax_start (local->X_add_symbol);
4113  macro_build (&global, ADDRESS_ADDI_INSN, "t,r,j",
4114	       dest, dest, BFD_RELOC_LO16);
4115  relax_switch ();
4116  macro_build (local, ADDRESS_ADDI_INSN, "t,r,j", dest, dest, BFD_RELOC_LO16);
4117  relax_end ();
4118}
4119
4120static void
4121add_got_offset_hilo (int dest, expressionS *local, int tmp)
4122{
4123  expressionS global;
4124  int hold_mips_optimize;
4125
4126  global.X_op = O_constant;
4127  global.X_op_symbol = NULL;
4128  global.X_add_symbol = NULL;
4129  global.X_add_number = local->X_add_number;
4130
4131  relax_start (local->X_add_symbol);
4132  load_register (tmp, &global, HAVE_64BIT_ADDRESSES);
4133  relax_switch ();
4134  /* Set mips_optimize around the lui instruction to avoid
4135     inserting an unnecessary nop after the lw.  */
4136  hold_mips_optimize = mips_optimize;
4137  mips_optimize = 2;
4138  macro_build_lui (&global, tmp);
4139  mips_optimize = hold_mips_optimize;
4140  macro_build (local, ADDRESS_ADDI_INSN, "t,r,j", tmp, tmp, BFD_RELOC_LO16);
4141  relax_end ();
4142
4143  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dest, dest, tmp);
4144}
4145
4146/*
4147 *			Build macros
4148 *   This routine implements the seemingly endless macro or synthesized
4149 * instructions and addressing modes in the mips assembly language. Many
4150 * of these macros are simple and are similar to each other. These could
4151 * probably be handled by some kind of table or grammar approach instead of
4152 * this verbose method. Others are not simple macros but are more like
4153 * optimizing code generation.
4154 *   One interesting optimization is when several store macros appear
4155 * consecutively that would load AT with the upper half of the same address.
4156 * The ensuing load upper instructions are ommited. This implies some kind
4157 * of global optimization. We currently only optimize within a single macro.
4158 *   For many of the load and store macros if the address is specified as a
4159 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4160 * first load register 'at' with zero and use it as the base register. The
4161 * mips assembler simply uses register $zero. Just one tiny optimization
4162 * we're missing.
4163 */
4164static void
4165macro (struct mips_cl_insn *ip)
4166{
4167  register int treg, sreg, dreg, breg;
4168  int tempreg;
4169  int mask;
4170  int used_at = 0;
4171  expressionS expr1;
4172  const char *s;
4173  const char *s2;
4174  const char *fmt;
4175  int likely = 0;
4176  int dbl = 0;
4177  int coproc = 0;
4178  int lr = 0;
4179  int imm = 0;
4180  int call = 0;
4181  int off;
4182  offsetT maxnum;
4183  bfd_reloc_code_real_type r;
4184  int hold_mips_optimize;
4185
4186  assert (! mips_opts.mips16);
4187
4188  treg = (ip->insn_opcode >> 16) & 0x1f;
4189  dreg = (ip->insn_opcode >> 11) & 0x1f;
4190  sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4191  mask = ip->insn_mo->mask;
4192
4193  expr1.X_op = O_constant;
4194  expr1.X_op_symbol = NULL;
4195  expr1.X_add_symbol = NULL;
4196  expr1.X_add_number = 1;
4197
4198  switch (mask)
4199    {
4200    case M_DABS:
4201      dbl = 1;
4202    case M_ABS:
4203      /* bgez $a0,.+12
4204	 move v0,$a0
4205	 sub v0,$zero,$a0
4206	 */
4207
4208      start_noreorder ();
4209
4210      expr1.X_add_number = 8;
4211      macro_build (&expr1, "bgez", "s,p", sreg);
4212      if (dreg == sreg)
4213	macro_build (NULL, "nop", "", 0);
4214      else
4215	move_register (dreg, sreg);
4216      macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4217
4218      end_noreorder ();
4219      break;
4220
4221    case M_ADD_I:
4222      s = "addi";
4223      s2 = "add";
4224      goto do_addi;
4225    case M_ADDU_I:
4226      s = "addiu";
4227      s2 = "addu";
4228      goto do_addi;
4229    case M_DADD_I:
4230      dbl = 1;
4231      s = "daddi";
4232      s2 = "dadd";
4233      goto do_addi;
4234    case M_DADDU_I:
4235      dbl = 1;
4236      s = "daddiu";
4237      s2 = "daddu";
4238    do_addi:
4239      if (imm_expr.X_op == O_constant
4240	  && imm_expr.X_add_number >= -0x8000
4241	  && imm_expr.X_add_number < 0x8000)
4242	{
4243	  macro_build (&imm_expr, s, "t,r,j", treg, sreg, BFD_RELOC_LO16);
4244	  break;
4245	}
4246      used_at = 1;
4247      load_register (AT, &imm_expr, dbl);
4248      macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
4249      break;
4250
4251    case M_AND_I:
4252      s = "andi";
4253      s2 = "and";
4254      goto do_bit;
4255    case M_OR_I:
4256      s = "ori";
4257      s2 = "or";
4258      goto do_bit;
4259    case M_NOR_I:
4260      s = "";
4261      s2 = "nor";
4262      goto do_bit;
4263    case M_XOR_I:
4264      s = "xori";
4265      s2 = "xor";
4266    do_bit:
4267      if (imm_expr.X_op == O_constant
4268	  && imm_expr.X_add_number >= 0
4269	  && imm_expr.X_add_number < 0x10000)
4270	{
4271	  if (mask != M_NOR_I)
4272	    macro_build (&imm_expr, s, "t,r,i", treg, sreg, BFD_RELOC_LO16);
4273	  else
4274	    {
4275	      macro_build (&imm_expr, "ori", "t,r,i",
4276			   treg, sreg, BFD_RELOC_LO16);
4277	      macro_build (NULL, "nor", "d,v,t", treg, treg, 0);
4278	    }
4279	  break;
4280	}
4281
4282      used_at = 1;
4283      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
4284      macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
4285      break;
4286
4287    case M_BEQ_I:
4288      s = "beq";
4289      goto beq_i;
4290    case M_BEQL_I:
4291      s = "beql";
4292      likely = 1;
4293      goto beq_i;
4294    case M_BNE_I:
4295      s = "bne";
4296      goto beq_i;
4297    case M_BNEL_I:
4298      s = "bnel";
4299      likely = 1;
4300    beq_i:
4301      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4302	{
4303	  macro_build (&offset_expr, s, "s,t,p", sreg, 0);
4304	  break;
4305	}
4306      used_at = 1;
4307      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
4308      macro_build (&offset_expr, s, "s,t,p", sreg, AT);
4309      break;
4310
4311    case M_BGEL:
4312      likely = 1;
4313    case M_BGE:
4314      if (treg == 0)
4315	{
4316	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
4317	  break;
4318	}
4319      if (sreg == 0)
4320	{
4321	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", treg);
4322	  break;
4323	}
4324      used_at = 1;
4325      macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
4326      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4327      break;
4328
4329    case M_BGTL_I:
4330      likely = 1;
4331    case M_BGT_I:
4332      /* check for > max integer */
4333      maxnum = 0x7fffffff;
4334      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4335	{
4336	  maxnum <<= 16;
4337	  maxnum |= 0xffff;
4338	  maxnum <<= 16;
4339	  maxnum |= 0xffff;
4340	}
4341      if (imm_expr.X_op == O_constant
4342	  && imm_expr.X_add_number >= maxnum
4343	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4344	{
4345	do_false:
4346	  /* result is always false */
4347	  if (! likely)
4348	    macro_build (NULL, "nop", "", 0);
4349	  else
4350	    macro_build (&offset_expr, "bnel", "s,t,p", 0, 0);
4351	  break;
4352	}
4353      if (imm_expr.X_op != O_constant)
4354	as_bad (_("Unsupported large constant"));
4355      ++imm_expr.X_add_number;
4356      /* FALLTHROUGH */
4357    case M_BGE_I:
4358    case M_BGEL_I:
4359      if (mask == M_BGEL_I)
4360	likely = 1;
4361      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4362	{
4363	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
4364	  break;
4365	}
4366      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4367	{
4368	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
4369	  break;
4370	}
4371      maxnum = 0x7fffffff;
4372      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4373	{
4374	  maxnum <<= 16;
4375	  maxnum |= 0xffff;
4376	  maxnum <<= 16;
4377	  maxnum |= 0xffff;
4378	}
4379      maxnum = - maxnum - 1;
4380      if (imm_expr.X_op == O_constant
4381	  && imm_expr.X_add_number <= maxnum
4382	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4383	{
4384	do_true:
4385	  /* result is always true */
4386	  as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4387	  macro_build (&offset_expr, "b", "p");
4388	  break;
4389	}
4390      used_at = 1;
4391      set_at (sreg, 0);
4392      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4393      break;
4394
4395    case M_BGEUL:
4396      likely = 1;
4397    case M_BGEU:
4398      if (treg == 0)
4399	goto do_true;
4400      if (sreg == 0)
4401	{
4402	  macro_build (&offset_expr, likely ? "beql" : "beq",
4403		       "s,t,p", 0, treg);
4404	  break;
4405	}
4406      used_at = 1;
4407      macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
4408      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4409      break;
4410
4411    case M_BGTUL_I:
4412      likely = 1;
4413    case M_BGTU_I:
4414      if (sreg == 0
4415	  || (HAVE_32BIT_GPRS
4416	      && imm_expr.X_op == O_constant
4417	      && imm_expr.X_add_number == (offsetT) 0xffffffff))
4418	goto do_false;
4419      if (imm_expr.X_op != O_constant)
4420	as_bad (_("Unsupported large constant"));
4421      ++imm_expr.X_add_number;
4422      /* FALLTHROUGH */
4423    case M_BGEU_I:
4424    case M_BGEUL_I:
4425      if (mask == M_BGEUL_I)
4426	likely = 1;
4427      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4428	goto do_true;
4429      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4430	{
4431	  macro_build (&offset_expr, likely ? "bnel" : "bne",
4432		       "s,t,p", sreg, 0);
4433	  break;
4434	}
4435      used_at = 1;
4436      set_at (sreg, 1);
4437      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4438      break;
4439
4440    case M_BGTL:
4441      likely = 1;
4442    case M_BGT:
4443      if (treg == 0)
4444	{
4445	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
4446	  break;
4447	}
4448      if (sreg == 0)
4449	{
4450	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", treg);
4451	  break;
4452	}
4453      used_at = 1;
4454      macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
4455      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4456      break;
4457
4458    case M_BGTUL:
4459      likely = 1;
4460    case M_BGTU:
4461      if (treg == 0)
4462	{
4463	  macro_build (&offset_expr, likely ? "bnel" : "bne",
4464		       "s,t,p", sreg, 0);
4465	  break;
4466	}
4467      if (sreg == 0)
4468	goto do_false;
4469      used_at = 1;
4470      macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
4471      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4472      break;
4473
4474    case M_BLEL:
4475      likely = 1;
4476    case M_BLE:
4477      if (treg == 0)
4478	{
4479	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
4480	  break;
4481	}
4482      if (sreg == 0)
4483	{
4484	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", treg);
4485	  break;
4486	}
4487      used_at = 1;
4488      macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
4489      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4490      break;
4491
4492    case M_BLEL_I:
4493      likely = 1;
4494    case M_BLE_I:
4495      maxnum = 0x7fffffff;
4496      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4497	{
4498	  maxnum <<= 16;
4499	  maxnum |= 0xffff;
4500	  maxnum <<= 16;
4501	  maxnum |= 0xffff;
4502	}
4503      if (imm_expr.X_op == O_constant
4504	  && imm_expr.X_add_number >= maxnum
4505	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4506	goto do_true;
4507      if (imm_expr.X_op != O_constant)
4508	as_bad (_("Unsupported large constant"));
4509      ++imm_expr.X_add_number;
4510      /* FALLTHROUGH */
4511    case M_BLT_I:
4512    case M_BLTL_I:
4513      if (mask == M_BLTL_I)
4514	likely = 1;
4515      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4516	{
4517	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
4518	  break;
4519	}
4520      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4521	{
4522	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
4523	  break;
4524	}
4525      used_at = 1;
4526      set_at (sreg, 0);
4527      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4528      break;
4529
4530    case M_BLEUL:
4531      likely = 1;
4532    case M_BLEU:
4533      if (treg == 0)
4534	{
4535	  macro_build (&offset_expr, likely ? "beql" : "beq",
4536		       "s,t,p", sreg, 0);
4537	  break;
4538	}
4539      if (sreg == 0)
4540	goto do_true;
4541      used_at = 1;
4542      macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
4543      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4544      break;
4545
4546    case M_BLEUL_I:
4547      likely = 1;
4548    case M_BLEU_I:
4549      if (sreg == 0
4550	  || (HAVE_32BIT_GPRS
4551	      && imm_expr.X_op == O_constant
4552	      && imm_expr.X_add_number == (offsetT) 0xffffffff))
4553	goto do_true;
4554      if (imm_expr.X_op != O_constant)
4555	as_bad (_("Unsupported large constant"));
4556      ++imm_expr.X_add_number;
4557      /* FALLTHROUGH */
4558    case M_BLTU_I:
4559    case M_BLTUL_I:
4560      if (mask == M_BLTUL_I)
4561	likely = 1;
4562      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4563	goto do_false;
4564      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4565	{
4566	  macro_build (&offset_expr, likely ? "beql" : "beq",
4567		       "s,t,p", sreg, 0);
4568	  break;
4569	}
4570      used_at = 1;
4571      set_at (sreg, 1);
4572      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4573      break;
4574
4575    case M_BLTL:
4576      likely = 1;
4577    case M_BLT:
4578      if (treg == 0)
4579	{
4580	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
4581	  break;
4582	}
4583      if (sreg == 0)
4584	{
4585	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", treg);
4586	  break;
4587	}
4588      used_at = 1;
4589      macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
4590      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4591      break;
4592
4593    case M_BLTUL:
4594      likely = 1;
4595    case M_BLTU:
4596      if (treg == 0)
4597	goto do_false;
4598      if (sreg == 0)
4599	{
4600	  macro_build (&offset_expr, likely ? "bnel" : "bne",
4601		       "s,t,p", 0, treg);
4602	  break;
4603	}
4604      used_at = 1;
4605      macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
4606      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4607      break;
4608
4609    case M_DEXT:
4610      {
4611	unsigned long pos;
4612	unsigned long size;
4613
4614        if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
4615	  {
4616	    as_bad (_("Unsupported large constant"));
4617	    pos = size = 1;
4618	  }
4619	else
4620	  {
4621	    pos = (unsigned long) imm_expr.X_add_number;
4622	    size = (unsigned long) imm2_expr.X_add_number;
4623	  }
4624
4625	if (pos > 63)
4626	  {
4627	    as_bad (_("Improper position (%lu)"), pos);
4628	    pos = 1;
4629	  }
4630        if (size == 0 || size > 64
4631	    || (pos + size - 1) > 63)
4632	  {
4633	    as_bad (_("Improper extract size (%lu, position %lu)"),
4634		    size, pos);
4635	    size = 1;
4636	  }
4637
4638	if (size <= 32 && pos < 32)
4639	  {
4640	    s = "dext";
4641	    fmt = "t,r,+A,+C";
4642	  }
4643	else if (size <= 32)
4644	  {
4645	    s = "dextu";
4646	    fmt = "t,r,+E,+H";
4647	  }
4648	else
4649	  {
4650	    s = "dextm";
4651	    fmt = "t,r,+A,+G";
4652	  }
4653	macro_build ((expressionS *) NULL, s, fmt, treg, sreg, pos, size - 1);
4654      }
4655      break;
4656
4657    case M_DINS:
4658      {
4659	unsigned long pos;
4660	unsigned long size;
4661
4662        if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
4663	  {
4664	    as_bad (_("Unsupported large constant"));
4665	    pos = size = 1;
4666	  }
4667	else
4668	  {
4669	    pos = (unsigned long) imm_expr.X_add_number;
4670	    size = (unsigned long) imm2_expr.X_add_number;
4671	  }
4672
4673	if (pos > 63)
4674	  {
4675	    as_bad (_("Improper position (%lu)"), pos);
4676	    pos = 1;
4677	  }
4678        if (size == 0 || size > 64
4679	    || (pos + size - 1) > 63)
4680	  {
4681	    as_bad (_("Improper insert size (%lu, position %lu)"),
4682		    size, pos);
4683	    size = 1;
4684	  }
4685
4686	if (pos < 32 && (pos + size - 1) < 32)
4687	  {
4688	    s = "dins";
4689	    fmt = "t,r,+A,+B";
4690	  }
4691	else if (pos >= 32)
4692	  {
4693	    s = "dinsu";
4694	    fmt = "t,r,+E,+F";
4695	  }
4696	else
4697	  {
4698	    s = "dinsm";
4699	    fmt = "t,r,+A,+F";
4700	  }
4701	macro_build ((expressionS *) NULL, s, fmt, treg, sreg, pos,
4702		     pos + size - 1);
4703      }
4704      break;
4705
4706    case M_DDIV_3:
4707      dbl = 1;
4708    case M_DIV_3:
4709      s = "mflo";
4710      goto do_div3;
4711    case M_DREM_3:
4712      dbl = 1;
4713    case M_REM_3:
4714      s = "mfhi";
4715    do_div3:
4716      if (treg == 0)
4717	{
4718	  as_warn (_("Divide by zero."));
4719	  if (mips_trap)
4720	    macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
4721	  else
4722	    macro_build (NULL, "break", "c", 7);
4723	  break;
4724	}
4725
4726      start_noreorder ();
4727      if (mips_trap)
4728	{
4729	  macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
4730	  macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4731	}
4732      else
4733	{
4734	  expr1.X_add_number = 8;
4735	  macro_build (&expr1, "bne", "s,t,p", treg, 0);
4736	  macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4737	  macro_build (NULL, "break", "c", 7);
4738	}
4739      expr1.X_add_number = -1;
4740      used_at = 1;
4741      load_register (AT, &expr1, dbl);
4742      expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4743      macro_build (&expr1, "bne", "s,t,p", treg, AT);
4744      if (dbl)
4745	{
4746	  expr1.X_add_number = 1;
4747	  load_register (AT, &expr1, dbl);
4748	  macro_build (NULL, "dsll32", "d,w,<", AT, AT, 31);
4749	}
4750      else
4751	{
4752	  expr1.X_add_number = 0x80000000;
4753	  macro_build (&expr1, "lui", "t,u", AT, BFD_RELOC_HI16);
4754	}
4755      if (mips_trap)
4756	{
4757	  macro_build (NULL, "teq", "s,t,q", sreg, AT, 6);
4758	  /* We want to close the noreorder block as soon as possible, so
4759	     that later insns are available for delay slot filling.  */
4760	  end_noreorder ();
4761	}
4762      else
4763	{
4764	  expr1.X_add_number = 8;
4765	  macro_build (&expr1, "bne", "s,t,p", sreg, AT);
4766	  macro_build (NULL, "nop", "", 0);
4767
4768	  /* We want to close the noreorder block as soon as possible, so
4769	     that later insns are available for delay slot filling.  */
4770	  end_noreorder ();
4771
4772	  macro_build (NULL, "break", "c", 6);
4773	}
4774      macro_build (NULL, s, "d", dreg);
4775      break;
4776
4777    case M_DIV_3I:
4778      s = "div";
4779      s2 = "mflo";
4780      goto do_divi;
4781    case M_DIVU_3I:
4782      s = "divu";
4783      s2 = "mflo";
4784      goto do_divi;
4785    case M_REM_3I:
4786      s = "div";
4787      s2 = "mfhi";
4788      goto do_divi;
4789    case M_REMU_3I:
4790      s = "divu";
4791      s2 = "mfhi";
4792      goto do_divi;
4793    case M_DDIV_3I:
4794      dbl = 1;
4795      s = "ddiv";
4796      s2 = "mflo";
4797      goto do_divi;
4798    case M_DDIVU_3I:
4799      dbl = 1;
4800      s = "ddivu";
4801      s2 = "mflo";
4802      goto do_divi;
4803    case M_DREM_3I:
4804      dbl = 1;
4805      s = "ddiv";
4806      s2 = "mfhi";
4807      goto do_divi;
4808    case M_DREMU_3I:
4809      dbl = 1;
4810      s = "ddivu";
4811      s2 = "mfhi";
4812    do_divi:
4813      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4814	{
4815	  as_warn (_("Divide by zero."));
4816	  if (mips_trap)
4817	    macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
4818	  else
4819	    macro_build (NULL, "break", "c", 7);
4820	  break;
4821	}
4822      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4823	{
4824	  if (strcmp (s2, "mflo") == 0)
4825	    move_register (dreg, sreg);
4826	  else
4827	    move_register (dreg, 0);
4828	  break;
4829	}
4830      if (imm_expr.X_op == O_constant
4831	  && imm_expr.X_add_number == -1
4832	  && s[strlen (s) - 1] != 'u')
4833	{
4834	  if (strcmp (s2, "mflo") == 0)
4835	    {
4836	      macro_build (NULL, dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4837	    }
4838	  else
4839	    move_register (dreg, 0);
4840	  break;
4841	}
4842
4843      used_at = 1;
4844      load_register (AT, &imm_expr, dbl);
4845      macro_build (NULL, s, "z,s,t", sreg, AT);
4846      macro_build (NULL, s2, "d", dreg);
4847      break;
4848
4849    case M_DIVU_3:
4850      s = "divu";
4851      s2 = "mflo";
4852      goto do_divu3;
4853    case M_REMU_3:
4854      s = "divu";
4855      s2 = "mfhi";
4856      goto do_divu3;
4857    case M_DDIVU_3:
4858      s = "ddivu";
4859      s2 = "mflo";
4860      goto do_divu3;
4861    case M_DREMU_3:
4862      s = "ddivu";
4863      s2 = "mfhi";
4864    do_divu3:
4865      start_noreorder ();
4866      if (mips_trap)
4867	{
4868	  macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
4869	  macro_build (NULL, s, "z,s,t", sreg, treg);
4870	  /* We want to close the noreorder block as soon as possible, so
4871	     that later insns are available for delay slot filling.  */
4872	  end_noreorder ();
4873	}
4874      else
4875	{
4876	  expr1.X_add_number = 8;
4877	  macro_build (&expr1, "bne", "s,t,p", treg, 0);
4878	  macro_build (NULL, s, "z,s,t", sreg, treg);
4879
4880	  /* We want to close the noreorder block as soon as possible, so
4881	     that later insns are available for delay slot filling.  */
4882	  end_noreorder ();
4883	  macro_build (NULL, "break", "c", 7);
4884	}
4885      macro_build (NULL, s2, "d", dreg);
4886      break;
4887
4888    case M_DLCA_AB:
4889      dbl = 1;
4890    case M_LCA_AB:
4891      call = 1;
4892      goto do_la;
4893    case M_DLA_AB:
4894      dbl = 1;
4895    case M_LA_AB:
4896    do_la:
4897      /* Load the address of a symbol into a register.  If breg is not
4898	 zero, we then add a base register to it.  */
4899
4900      if (dbl && HAVE_32BIT_GPRS)
4901	as_warn (_("dla used to load 32-bit register"));
4902
4903      if (! dbl && HAVE_64BIT_OBJECTS)
4904	as_warn (_("la used to load 64-bit address"));
4905
4906      if (offset_expr.X_op == O_constant
4907	  && offset_expr.X_add_number >= -0x8000
4908	  && offset_expr.X_add_number < 0x8000)
4909	{
4910	  macro_build (&offset_expr, ADDRESS_ADDI_INSN,
4911		       "t,r,j", treg, sreg, BFD_RELOC_LO16);
4912	  break;
4913	}
4914
4915      if (!mips_opts.noat && (treg == breg))
4916	{
4917	  tempreg = AT;
4918	  used_at = 1;
4919	}
4920      else
4921	{
4922	  tempreg = treg;
4923	}
4924
4925      if (offset_expr.X_op != O_symbol
4926	  && offset_expr.X_op != O_constant)
4927	{
4928	  as_bad (_("expression too complex"));
4929	  offset_expr.X_op = O_constant;
4930	}
4931
4932      if (offset_expr.X_op == O_constant)
4933	load_register (tempreg, &offset_expr, HAVE_64BIT_ADDRESSES);
4934      else if (mips_pic == NO_PIC)
4935	{
4936	  /* If this is a reference to a GP relative symbol, we want
4937	       addiu	$tempreg,$gp,<sym>	(BFD_RELOC_GPREL16)
4938	     Otherwise we want
4939	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
4940	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
4941	     If we have a constant, we need two instructions anyhow,
4942	     so we may as well always use the latter form.
4943
4944	     With 64bit address space and a usable $at we want
4945	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
4946	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
4947	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
4948	       daddiu	$at,<sym>		(BFD_RELOC_LO16)
4949	       dsll32	$tempreg,0
4950	       daddu	$tempreg,$tempreg,$at
4951
4952	     If $at is already in use, we use a path which is suboptimal
4953	     on superscalar processors.
4954	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
4955	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
4956	       dsll	$tempreg,16
4957	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
4958	       dsll	$tempreg,16
4959	       daddiu	$tempreg,<sym>		(BFD_RELOC_LO16)
4960
4961	     For GP relative symbols in 64bit address space we can use
4962	     the same sequence as in 32bit address space.  */
4963	  if (HAVE_64BIT_SYMBOLS)
4964	    {
4965	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4966		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
4967		{
4968		  relax_start (offset_expr.X_add_symbol);
4969		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
4970			       tempreg, mips_gp_register, BFD_RELOC_GPREL16);
4971		  relax_switch ();
4972		}
4973
4974	      if (used_at == 0 && !mips_opts.noat)
4975		{
4976		  macro_build (&offset_expr, "lui", "t,u",
4977			       tempreg, BFD_RELOC_MIPS_HIGHEST);
4978		  macro_build (&offset_expr, "lui", "t,u",
4979			       AT, BFD_RELOC_HI16_S);
4980		  macro_build (&offset_expr, "daddiu", "t,r,j",
4981			       tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
4982		  macro_build (&offset_expr, "daddiu", "t,r,j",
4983			       AT, AT, BFD_RELOC_LO16);
4984		  macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
4985		  macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
4986		  used_at = 1;
4987		}
4988	      else
4989		{
4990		  macro_build (&offset_expr, "lui", "t,u",
4991			       tempreg, BFD_RELOC_MIPS_HIGHEST);
4992		  macro_build (&offset_expr, "daddiu", "t,r,j",
4993			       tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
4994		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
4995		  macro_build (&offset_expr, "daddiu", "t,r,j",
4996			       tempreg, tempreg, BFD_RELOC_HI16_S);
4997		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
4998		  macro_build (&offset_expr, "daddiu", "t,r,j",
4999			       tempreg, tempreg, BFD_RELOC_LO16);
5000		}
5001
5002	      if (mips_relax.sequence)
5003		relax_end ();
5004	    }
5005	  else
5006	    {
5007	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5008		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
5009		{
5010		  relax_start (offset_expr.X_add_symbol);
5011		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5012			       tempreg, mips_gp_register, BFD_RELOC_GPREL16);
5013		  relax_switch ();
5014		}
5015	      if (!IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
5016		as_bad (_("offset too large"));
5017	      macro_build_lui (&offset_expr, tempreg);
5018	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5019			   tempreg, tempreg, BFD_RELOC_LO16);
5020	      if (mips_relax.sequence)
5021		relax_end ();
5022	    }
5023	}
5024      else if (!mips_big_got && !HAVE_NEWABI)
5025	{
5026	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5027
5028	  /* If this is a reference to an external symbol, and there
5029	     is no constant, we want
5030	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5031	     or for lca or if tempreg is PIC_CALL_REG
5032	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_CALL16)
5033	     For a local symbol, we want
5034	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5035	       nop
5036	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
5037
5038	     If we have a small constant, and this is a reference to
5039	     an external symbol, we want
5040	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5041	       nop
5042	       addiu	$tempreg,$tempreg,<constant>
5043	     For a local symbol, we want the same instruction
5044	     sequence, but we output a BFD_RELOC_LO16 reloc on the
5045	     addiu instruction.
5046
5047	     If we have a large constant, and this is a reference to
5048	     an external symbol, we want
5049	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5050	       lui	$at,<hiconstant>
5051	       addiu	$at,$at,<loconstant>
5052	       addu	$tempreg,$tempreg,$at
5053	     For a local symbol, we want the same instruction
5054	     sequence, but we output a BFD_RELOC_LO16 reloc on the
5055	     addiu instruction.
5056	   */
5057
5058	  if (offset_expr.X_add_number == 0)
5059	    {
5060	      if (mips_pic == SVR4_PIC
5061		  && breg == 0
5062		  && (call || tempreg == PIC_CALL_REG))
5063		lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5064
5065	      relax_start (offset_expr.X_add_symbol);
5066	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5067			   lw_reloc_type, mips_gp_register);
5068	      if (breg != 0)
5069		{
5070		  /* We're going to put in an addu instruction using
5071		     tempreg, so we may as well insert the nop right
5072		     now.  */
5073		  load_delay_nop ();
5074		}
5075	      relax_switch ();
5076	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5077			   tempreg, BFD_RELOC_MIPS_GOT16, mips_gp_register);
5078	      load_delay_nop ();
5079	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5080			   tempreg, tempreg, BFD_RELOC_LO16);
5081	      relax_end ();
5082	      /* FIXME: If breg == 0, and the next instruction uses
5083		 $tempreg, then if this variant case is used an extra
5084		 nop will be generated.  */
5085	    }
5086	  else if (offset_expr.X_add_number >= -0x8000
5087		   && offset_expr.X_add_number < 0x8000)
5088	    {
5089	      load_got_offset (tempreg, &offset_expr);
5090	      load_delay_nop ();
5091	      add_got_offset (tempreg, &offset_expr);
5092	    }
5093	  else
5094	    {
5095	      expr1.X_add_number = offset_expr.X_add_number;
5096	      offset_expr.X_add_number =
5097		((offset_expr.X_add_number + 0x8000) & 0xffff) - 0x8000;
5098	      load_got_offset (tempreg, &offset_expr);
5099	      offset_expr.X_add_number = expr1.X_add_number;
5100	      /* If we are going to add in a base register, and the
5101		 target register and the base register are the same,
5102		 then we are using AT as a temporary register.  Since
5103		 we want to load the constant into AT, we add our
5104		 current AT (from the global offset table) and the
5105		 register into the register now, and pretend we were
5106		 not using a base register.  */
5107	      if (breg == treg)
5108		{
5109		  load_delay_nop ();
5110		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5111			       treg, AT, breg);
5112		  breg = 0;
5113		  tempreg = treg;
5114		}
5115	      add_got_offset_hilo (tempreg, &offset_expr, AT);
5116	      used_at = 1;
5117	    }
5118	}
5119      else if (!mips_big_got && HAVE_NEWABI)
5120	{
5121	  int add_breg_early = 0;
5122
5123	  /* If this is a reference to an external, and there is no
5124	     constant, or local symbol (*), with or without a
5125	     constant, we want
5126	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5127	     or for lca or if tempreg is PIC_CALL_REG
5128	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_CALL16)
5129
5130	     If we have a small constant, and this is a reference to
5131	     an external symbol, we want
5132	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5133	       addiu	$tempreg,$tempreg,<constant>
5134
5135	     If we have a large constant, and this is a reference to
5136	     an external symbol, we want
5137	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5138	       lui	$at,<hiconstant>
5139	       addiu	$at,$at,<loconstant>
5140	       addu	$tempreg,$tempreg,$at
5141
5142	     (*) Other assemblers seem to prefer GOT_PAGE/GOT_OFST for
5143	     local symbols, even though it introduces an additional
5144	     instruction.  */
5145
5146	  if (offset_expr.X_add_number)
5147	    {
5148	      expr1.X_add_number = offset_expr.X_add_number;
5149	      offset_expr.X_add_number = 0;
5150
5151	      relax_start (offset_expr.X_add_symbol);
5152	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5153			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5154
5155	      if (expr1.X_add_number >= -0x8000
5156		  && expr1.X_add_number < 0x8000)
5157		{
5158		  macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5159			       tempreg, tempreg, BFD_RELOC_LO16);
5160		}
5161	      else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
5162		{
5163		  int dreg;
5164
5165		  /* If we are going to add in a base register, and the
5166		     target register and the base register are the same,
5167		     then we are using AT as a temporary register.  Since
5168		     we want to load the constant into AT, we add our
5169		     current AT (from the global offset table) and the
5170		     register into the register now, and pretend we were
5171		     not using a base register.  */
5172		  if (breg != treg)
5173		    dreg = tempreg;
5174		  else
5175		    {
5176		      assert (tempreg == AT);
5177		      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5178				   treg, AT, breg);
5179		      dreg = treg;
5180		      add_breg_early = 1;
5181		    }
5182
5183		  load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
5184		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5185			       dreg, dreg, AT);
5186
5187		  used_at = 1;
5188		}
5189	      else
5190		as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5191
5192	      relax_switch ();
5193	      offset_expr.X_add_number = expr1.X_add_number;
5194
5195	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5196			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5197	      if (add_breg_early)
5198		{
5199		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5200			       treg, tempreg, breg);
5201		  breg = 0;
5202		  tempreg = treg;
5203		}
5204	      relax_end ();
5205	    }
5206	  else if (breg == 0 && (call || tempreg == PIC_CALL_REG))
5207	    {
5208	      relax_start (offset_expr.X_add_symbol);
5209	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5210			   BFD_RELOC_MIPS_CALL16, mips_gp_register);
5211	      relax_switch ();
5212	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5213			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5214	      relax_end ();
5215	    }
5216	  else
5217	    {
5218	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5219			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5220	    }
5221	}
5222      else if (mips_big_got && !HAVE_NEWABI)
5223	{
5224	  int gpdelay;
5225	  int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5226	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5227	  int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5228
5229	  /* This is the large GOT case.  If this is a reference to an
5230	     external symbol, and there is no constant, we want
5231	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5232	       addu	$tempreg,$tempreg,$gp
5233	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5234	     or for lca or if tempreg is PIC_CALL_REG
5235	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
5236	       addu	$tempreg,$tempreg,$gp
5237	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5238	     For a local symbol, we want
5239	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5240	       nop
5241	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
5242
5243	     If we have a small constant, and this is a reference to
5244	     an external symbol, we want
5245	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5246	       addu	$tempreg,$tempreg,$gp
5247	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5248	       nop
5249	       addiu	$tempreg,$tempreg,<constant>
5250	     For a local symbol, we want
5251	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5252	       nop
5253	       addiu	$tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5254
5255	     If we have a large constant, and this is a reference to
5256	     an external symbol, we want
5257	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5258	       addu	$tempreg,$tempreg,$gp
5259	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5260	       lui	$at,<hiconstant>
5261	       addiu	$at,$at,<loconstant>
5262	       addu	$tempreg,$tempreg,$at
5263	     For a local symbol, we want
5264	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5265	       lui	$at,<hiconstant>
5266	       addiu	$at,$at,<loconstant>	(BFD_RELOC_LO16)
5267	       addu	$tempreg,$tempreg,$at
5268	  */
5269
5270	  expr1.X_add_number = offset_expr.X_add_number;
5271	  offset_expr.X_add_number = 0;
5272	  relax_start (offset_expr.X_add_symbol);
5273	  gpdelay = reg_needs_delay (mips_gp_register);
5274	  if (expr1.X_add_number == 0 && breg == 0
5275	      && (call || tempreg == PIC_CALL_REG))
5276	    {
5277	      lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5278	      lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5279	    }
5280	  macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
5281	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5282		       tempreg, tempreg, mips_gp_register);
5283	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5284		       tempreg, lw_reloc_type, tempreg);
5285	  if (expr1.X_add_number == 0)
5286	    {
5287	      if (breg != 0)
5288		{
5289		  /* We're going to put in an addu instruction using
5290		     tempreg, so we may as well insert the nop right
5291		     now.  */
5292		  load_delay_nop ();
5293		}
5294	    }
5295	  else if (expr1.X_add_number >= -0x8000
5296		   && expr1.X_add_number < 0x8000)
5297	    {
5298	      load_delay_nop ();
5299	      macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5300			   tempreg, tempreg, BFD_RELOC_LO16);
5301	    }
5302	  else
5303	    {
5304	      int dreg;
5305
5306	      /* If we are going to add in a base register, and the
5307		 target register and the base register are the same,
5308		 then we are using AT as a temporary register.  Since
5309		 we want to load the constant into AT, we add our
5310		 current AT (from the global offset table) and the
5311		 register into the register now, and pretend we were
5312		 not using a base register.  */
5313	      if (breg != treg)
5314		dreg = tempreg;
5315	      else
5316		{
5317		  assert (tempreg == AT);
5318		  load_delay_nop ();
5319		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5320			       treg, AT, breg);
5321		  dreg = treg;
5322		}
5323
5324	      load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
5325	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5326
5327	      used_at = 1;
5328	    }
5329	  offset_expr.X_add_number =
5330	    ((expr1.X_add_number + 0x8000) & 0xffff) - 0x8000;
5331	  relax_switch ();
5332
5333	  if (gpdelay)
5334	    {
5335	      /* This is needed because this instruction uses $gp, but
5336		 the first instruction on the main stream does not.  */
5337	      macro_build (NULL, "nop", "");
5338	    }
5339
5340	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5341		       local_reloc_type, mips_gp_register);
5342	  if (expr1.X_add_number >= -0x8000
5343	      && expr1.X_add_number < 0x8000)
5344	    {
5345	      load_delay_nop ();
5346	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5347			   tempreg, tempreg, BFD_RELOC_LO16);
5348	      /* FIXME: If add_number is 0, and there was no base
5349		 register, the external symbol case ended with a load,
5350		 so if the symbol turns out to not be external, and
5351		 the next instruction uses tempreg, an unnecessary nop
5352		 will be inserted.  */
5353	    }
5354	  else
5355	    {
5356	      if (breg == treg)
5357		{
5358		  /* We must add in the base register now, as in the
5359		     external symbol case.  */
5360		  assert (tempreg == AT);
5361		  load_delay_nop ();
5362		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5363			       treg, AT, breg);
5364		  tempreg = treg;
5365		  /* We set breg to 0 because we have arranged to add
5366		     it in in both cases.  */
5367		  breg = 0;
5368		}
5369
5370	      macro_build_lui (&expr1, AT);
5371	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5372			   AT, AT, BFD_RELOC_LO16);
5373	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5374			   tempreg, tempreg, AT);
5375	      used_at = 1;
5376	    }
5377	  relax_end ();
5378	}
5379      else if (mips_big_got && HAVE_NEWABI)
5380	{
5381	  int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5382	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5383	  int add_breg_early = 0;
5384
5385	  /* This is the large GOT case.  If this is a reference to an
5386	     external symbol, and there is no constant, we want
5387	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5388	       add	$tempreg,$tempreg,$gp
5389	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5390	     or for lca or if tempreg is PIC_CALL_REG
5391	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
5392	       add	$tempreg,$tempreg,$gp
5393	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5394
5395	     If we have a small constant, and this is a reference to
5396	     an external symbol, we want
5397	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5398	       add	$tempreg,$tempreg,$gp
5399	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5400	       addi	$tempreg,$tempreg,<constant>
5401
5402	     If we have a large constant, and this is a reference to
5403	     an external symbol, we want
5404	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5405	       addu	$tempreg,$tempreg,$gp
5406	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5407	       lui	$at,<hiconstant>
5408	       addi	$at,$at,<loconstant>
5409	       add	$tempreg,$tempreg,$at
5410
5411	     If we have NewABI, and we know it's a local symbol, we want
5412	       lw	$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT_PAGE)
5413	       addiu	$reg,$reg,<sym>		(BFD_RELOC_MIPS_GOT_OFST)
5414	     otherwise we have to resort to GOT_HI16/GOT_LO16.  */
5415
5416	  relax_start (offset_expr.X_add_symbol);
5417
5418	  expr1.X_add_number = offset_expr.X_add_number;
5419	  offset_expr.X_add_number = 0;
5420
5421	  if (expr1.X_add_number == 0 && breg == 0
5422	      && (call || tempreg == PIC_CALL_REG))
5423	    {
5424	      lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5425	      lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5426	    }
5427	  macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
5428	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5429		       tempreg, tempreg, mips_gp_register);
5430	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5431		       tempreg, lw_reloc_type, tempreg);
5432
5433	  if (expr1.X_add_number == 0)
5434	    ;
5435	  else if (expr1.X_add_number >= -0x8000
5436		   && expr1.X_add_number < 0x8000)
5437	    {
5438	      macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5439			   tempreg, tempreg, BFD_RELOC_LO16);
5440	    }
5441	  else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
5442	    {
5443	      int dreg;
5444
5445	      /* If we are going to add in a base register, and the
5446		 target register and the base register are the same,
5447		 then we are using AT as a temporary register.  Since
5448		 we want to load the constant into AT, we add our
5449		 current AT (from the global offset table) and the
5450		 register into the register now, and pretend we were
5451		 not using a base register.  */
5452	      if (breg != treg)
5453		dreg = tempreg;
5454	      else
5455		{
5456		  assert (tempreg == AT);
5457		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5458			       treg, AT, breg);
5459		  dreg = treg;
5460		  add_breg_early = 1;
5461		}
5462
5463	      load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
5464	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5465
5466	      used_at = 1;
5467	    }
5468	  else
5469	    as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5470
5471	  relax_switch ();
5472	  offset_expr.X_add_number = expr1.X_add_number;
5473	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5474		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
5475	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
5476		       tempreg, BFD_RELOC_MIPS_GOT_OFST);
5477	  if (add_breg_early)
5478	    {
5479	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5480			   treg, tempreg, breg);
5481	      breg = 0;
5482	      tempreg = treg;
5483	    }
5484	  relax_end ();
5485	}
5486      else
5487	abort ();
5488
5489      if (breg != 0)
5490	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", treg, tempreg, breg);
5491      break;
5492
5493    case M_J_A:
5494      /* The j instruction may not be used in PIC code, since it
5495	 requires an absolute address.  We convert it to a b
5496	 instruction.  */
5497      if (mips_pic == NO_PIC)
5498	macro_build (&offset_expr, "j", "a");
5499      else
5500	macro_build (&offset_expr, "b", "p");
5501      break;
5502
5503      /* The jal instructions must be handled as macros because when
5504	 generating PIC code they expand to multi-instruction
5505	 sequences.  Normally they are simple instructions.  */
5506    case M_JAL_1:
5507      dreg = RA;
5508      /* Fall through.  */
5509    case M_JAL_2:
5510      if (mips_pic == NO_PIC)
5511	macro_build (NULL, "jalr", "d,s", dreg, sreg);
5512      else
5513	{
5514	  if (sreg != PIC_CALL_REG)
5515	    as_warn (_("MIPS PIC call to register other than $25"));
5516
5517	  macro_build (NULL, "jalr", "d,s", dreg, sreg);
5518	  if (mips_pic == SVR4_PIC && !HAVE_NEWABI)
5519	    {
5520	      if (mips_cprestore_offset < 0)
5521		as_warn (_("No .cprestore pseudo-op used in PIC code"));
5522	      else
5523		{
5524		  if (! mips_frame_reg_valid)
5525		    {
5526		      as_warn (_("No .frame pseudo-op used in PIC code"));
5527		      /* Quiet this warning.  */
5528		      mips_frame_reg_valid = 1;
5529		    }
5530		  if (! mips_cprestore_valid)
5531		    {
5532		      as_warn (_("No .cprestore pseudo-op used in PIC code"));
5533		      /* Quiet this warning.  */
5534		      mips_cprestore_valid = 1;
5535		    }
5536		  expr1.X_add_number = mips_cprestore_offset;
5537  		  macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
5538						mips_gp_register,
5539						mips_frame_reg,
5540						HAVE_64BIT_ADDRESSES);
5541		}
5542	    }
5543	}
5544
5545      break;
5546
5547    case M_JAL_A:
5548      if (mips_pic == NO_PIC)
5549	macro_build (&offset_expr, "jal", "a");
5550      else if (mips_pic == SVR4_PIC)
5551	{
5552	  /* If this is a reference to an external symbol, and we are
5553	     using a small GOT, we want
5554	       lw	$25,<sym>($gp)		(BFD_RELOC_MIPS_CALL16)
5555	       nop
5556	       jalr	$ra,$25
5557	       nop
5558	       lw	$gp,cprestore($sp)
5559	     The cprestore value is set using the .cprestore
5560	     pseudo-op.  If we are using a big GOT, we want
5561	       lui	$25,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
5562	       addu	$25,$25,$gp
5563	       lw	$25,<sym>($25)		(BFD_RELOC_MIPS_CALL_LO16)
5564	       nop
5565	       jalr	$ra,$25
5566	       nop
5567	       lw	$gp,cprestore($sp)
5568	     If the symbol is not external, we want
5569	       lw	$25,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
5570	       nop
5571	       addiu	$25,$25,<sym>		(BFD_RELOC_LO16)
5572	       jalr	$ra,$25
5573	       nop
5574	       lw $gp,cprestore($sp)
5575
5576	     For NewABI, we use the same CALL16 or CALL_HI16/CALL_LO16
5577	     sequences above, minus nops, unless the symbol is local,
5578	     which enables us to use GOT_PAGE/GOT_OFST (big got) or
5579	     GOT_DISP.  */
5580	  if (HAVE_NEWABI)
5581	    {
5582	      if (! mips_big_got)
5583		{
5584		  relax_start (offset_expr.X_add_symbol);
5585		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5586			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
5587			       mips_gp_register);
5588		  relax_switch ();
5589		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5590			       PIC_CALL_REG, BFD_RELOC_MIPS_GOT_DISP,
5591			       mips_gp_register);
5592		  relax_end ();
5593		}
5594	      else
5595		{
5596		  relax_start (offset_expr.X_add_symbol);
5597		  macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
5598			       BFD_RELOC_MIPS_CALL_HI16);
5599		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5600			       PIC_CALL_REG, mips_gp_register);
5601		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5602			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
5603			       PIC_CALL_REG);
5604		  relax_switch ();
5605		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5606			       PIC_CALL_REG, BFD_RELOC_MIPS_GOT_PAGE,
5607			       mips_gp_register);
5608		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5609			       PIC_CALL_REG, PIC_CALL_REG,
5610			       BFD_RELOC_MIPS_GOT_OFST);
5611		  relax_end ();
5612		}
5613
5614	      macro_build_jalr (&offset_expr);
5615	    }
5616	  else
5617	    {
5618	      relax_start (offset_expr.X_add_symbol);
5619	      if (! mips_big_got)
5620		{
5621		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5622			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
5623			       mips_gp_register);
5624		  load_delay_nop ();
5625		  relax_switch ();
5626		}
5627	      else
5628		{
5629		  int gpdelay;
5630
5631		  gpdelay = reg_needs_delay (mips_gp_register);
5632		  macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
5633			       BFD_RELOC_MIPS_CALL_HI16);
5634		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5635			       PIC_CALL_REG, mips_gp_register);
5636		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5637			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
5638			       PIC_CALL_REG);
5639		  load_delay_nop ();
5640		  relax_switch ();
5641		  if (gpdelay)
5642		    macro_build (NULL, "nop", "");
5643		}
5644	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5645			   PIC_CALL_REG, BFD_RELOC_MIPS_GOT16,
5646			   mips_gp_register);
5647	      load_delay_nop ();
5648	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5649			   PIC_CALL_REG, PIC_CALL_REG, BFD_RELOC_LO16);
5650	      relax_end ();
5651	      macro_build_jalr (&offset_expr);
5652
5653	      if (mips_cprestore_offset < 0)
5654		as_warn (_("No .cprestore pseudo-op used in PIC code"));
5655	      else
5656		{
5657		  if (! mips_frame_reg_valid)
5658		    {
5659		      as_warn (_("No .frame pseudo-op used in PIC code"));
5660		      /* Quiet this warning.  */
5661		      mips_frame_reg_valid = 1;
5662		    }
5663		  if (! mips_cprestore_valid)
5664		    {
5665		      as_warn (_("No .cprestore pseudo-op used in PIC code"));
5666		      /* Quiet this warning.  */
5667		      mips_cprestore_valid = 1;
5668		    }
5669		  if (mips_opts.noreorder)
5670		    macro_build (NULL, "nop", "");
5671		  expr1.X_add_number = mips_cprestore_offset;
5672  		  macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
5673						mips_gp_register,
5674						mips_frame_reg,
5675						HAVE_64BIT_ADDRESSES);
5676		}
5677	    }
5678	}
5679      else if (mips_pic == VXWORKS_PIC)
5680	as_bad (_("Non-PIC jump used in PIC library"));
5681      else
5682	abort ();
5683
5684      break;
5685
5686    case M_LB_AB:
5687      s = "lb";
5688      goto ld;
5689    case M_LBU_AB:
5690      s = "lbu";
5691      goto ld;
5692    case M_LH_AB:
5693      s = "lh";
5694      goto ld;
5695    case M_LHU_AB:
5696      s = "lhu";
5697      goto ld;
5698    case M_LW_AB:
5699      s = "lw";
5700      goto ld;
5701    case M_LWC0_AB:
5702      s = "lwc0";
5703      /* Itbl support may require additional care here.  */
5704      coproc = 1;
5705      goto ld;
5706    case M_LWC1_AB:
5707      s = "lwc1";
5708      /* Itbl support may require additional care here.  */
5709      coproc = 1;
5710      goto ld;
5711    case M_LWC2_AB:
5712      s = "lwc2";
5713      /* Itbl support may require additional care here.  */
5714      coproc = 1;
5715      goto ld;
5716    case M_LWC3_AB:
5717      s = "lwc3";
5718      /* Itbl support may require additional care here.  */
5719      coproc = 1;
5720      goto ld;
5721    case M_LWL_AB:
5722      s = "lwl";
5723      lr = 1;
5724      goto ld;
5725    case M_LWR_AB:
5726      s = "lwr";
5727      lr = 1;
5728      goto ld;
5729    case M_LDC1_AB:
5730      if (mips_opts.arch == CPU_R4650)
5731	{
5732	  as_bad (_("opcode not supported on this processor"));
5733	  break;
5734	}
5735      s = "ldc1";
5736      /* Itbl support may require additional care here.  */
5737      coproc = 1;
5738      goto ld;
5739    case M_LDC2_AB:
5740      s = "ldc2";
5741      /* Itbl support may require additional care here.  */
5742      coproc = 1;
5743      goto ld;
5744    case M_LDC3_AB:
5745      s = "ldc3";
5746      /* Itbl support may require additional care here.  */
5747      coproc = 1;
5748      goto ld;
5749    case M_LDL_AB:
5750      s = "ldl";
5751      lr = 1;
5752      goto ld;
5753    case M_LDR_AB:
5754      s = "ldr";
5755      lr = 1;
5756      goto ld;
5757    case M_LL_AB:
5758      s = "ll";
5759      goto ld;
5760    case M_LLD_AB:
5761      s = "lld";
5762      goto ld;
5763    case M_LWU_AB:
5764      s = "lwu";
5765    ld:
5766      if (breg == treg || coproc || lr)
5767	{
5768	  tempreg = AT;
5769	  used_at = 1;
5770	}
5771      else
5772	{
5773	  tempreg = treg;
5774	}
5775      goto ld_st;
5776    case M_SB_AB:
5777      s = "sb";
5778      goto st;
5779    case M_SH_AB:
5780      s = "sh";
5781      goto st;
5782    case M_SW_AB:
5783      s = "sw";
5784      goto st;
5785    case M_SWC0_AB:
5786      s = "swc0";
5787      /* Itbl support may require additional care here.  */
5788      coproc = 1;
5789      goto st;
5790    case M_SWC1_AB:
5791      s = "swc1";
5792      /* Itbl support may require additional care here.  */
5793      coproc = 1;
5794      goto st;
5795    case M_SWC2_AB:
5796      s = "swc2";
5797      /* Itbl support may require additional care here.  */
5798      coproc = 1;
5799      goto st;
5800    case M_SWC3_AB:
5801      s = "swc3";
5802      /* Itbl support may require additional care here.  */
5803      coproc = 1;
5804      goto st;
5805    case M_SWL_AB:
5806      s = "swl";
5807      goto st;
5808    case M_SWR_AB:
5809      s = "swr";
5810      goto st;
5811    case M_SC_AB:
5812      s = "sc";
5813      goto st;
5814    case M_SCD_AB:
5815      s = "scd";
5816      goto st;
5817    case M_SDC1_AB:
5818      if (mips_opts.arch == CPU_R4650)
5819	{
5820	  as_bad (_("opcode not supported on this processor"));
5821	  break;
5822	}
5823      s = "sdc1";
5824      coproc = 1;
5825      /* Itbl support may require additional care here.  */
5826      goto st;
5827    case M_SDC2_AB:
5828      s = "sdc2";
5829      /* Itbl support may require additional care here.  */
5830      coproc = 1;
5831      goto st;
5832    case M_SDC3_AB:
5833      s = "sdc3";
5834      /* Itbl support may require additional care here.  */
5835      coproc = 1;
5836      goto st;
5837    case M_SDL_AB:
5838      s = "sdl";
5839      goto st;
5840    case M_SDR_AB:
5841      s = "sdr";
5842    st:
5843      tempreg = AT;
5844      used_at = 1;
5845    ld_st:
5846      /* Itbl support may require additional care here.  */
5847      if (mask == M_LWC1_AB
5848	  || mask == M_SWC1_AB
5849	  || mask == M_LDC1_AB
5850	  || mask == M_SDC1_AB
5851	  || mask == M_L_DAB
5852	  || mask == M_S_DAB)
5853	fmt = "T,o(b)";
5854      else if (coproc)
5855	fmt = "E,o(b)";
5856      else
5857	fmt = "t,o(b)";
5858
5859      if (offset_expr.X_op != O_constant
5860	  && offset_expr.X_op != O_symbol)
5861	{
5862	  as_bad (_("expression too complex"));
5863	  offset_expr.X_op = O_constant;
5864	}
5865
5866      if (HAVE_32BIT_ADDRESSES
5867	  && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
5868	{
5869	  char value [32];
5870
5871	  sprintf_vma (value, offset_expr.X_add_number);
5872	  as_bad (_("Number (0x%s) larger than 32 bits"), value);
5873	}
5874
5875      /* A constant expression in PIC code can be handled just as it
5876	 is in non PIC code.  */
5877      if (offset_expr.X_op == O_constant)
5878	{
5879	  expr1.X_add_number = ((offset_expr.X_add_number + 0x8000)
5880				& ~(bfd_vma) 0xffff);
5881	  normalize_address_expr (&expr1);
5882	  load_register (tempreg, &expr1, HAVE_64BIT_ADDRESSES);
5883	  if (breg != 0)
5884	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5885			 tempreg, tempreg, breg);
5886	  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_LO16, tempreg);
5887	}
5888      else if (mips_pic == NO_PIC)
5889	{
5890	  /* If this is a reference to a GP relative symbol, and there
5891	     is no base register, we want
5892	       <op>	$treg,<sym>($gp)	(BFD_RELOC_GPREL16)
5893	     Otherwise, if there is no base register, we want
5894	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5895	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5896	     If we have a constant, we need two instructions anyhow,
5897	     so we always use the latter form.
5898
5899	     If we have a base register, and this is a reference to a
5900	     GP relative symbol, we want
5901	       addu	$tempreg,$breg,$gp
5902	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_GPREL16)
5903	     Otherwise we want
5904	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5905	       addu	$tempreg,$tempreg,$breg
5906	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5907	     With a constant we always use the latter case.
5908
5909	     With 64bit address space and no base register and $at usable,
5910	     we want
5911	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5912	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
5913	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5914	       dsll32	$tempreg,0
5915	       daddu	$tempreg,$at
5916	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5917	     If we have a base register, we want
5918	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5919	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
5920	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5921	       daddu	$at,$breg
5922	       dsll32	$tempreg,0
5923	       daddu	$tempreg,$at
5924	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5925
5926	     Without $at we can't generate the optimal path for superscalar
5927	     processors here since this would require two temporary registers.
5928	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5929	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5930	       dsll	$tempreg,16
5931	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5932	       dsll	$tempreg,16
5933	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5934	     If we have a base register, we want
5935	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5936	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5937	       dsll	$tempreg,16
5938	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5939	       dsll	$tempreg,16
5940	       daddu	$tempreg,$tempreg,$breg
5941	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5942
5943	     For GP relative symbols in 64bit address space we can use
5944	     the same sequence as in 32bit address space.  */
5945	  if (HAVE_64BIT_SYMBOLS)
5946	    {
5947	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5948		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
5949		{
5950		  relax_start (offset_expr.X_add_symbol);
5951		  if (breg == 0)
5952		    {
5953		      macro_build (&offset_expr, s, fmt, treg,
5954				   BFD_RELOC_GPREL16, mips_gp_register);
5955		    }
5956		  else
5957		    {
5958		      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5959				   tempreg, breg, mips_gp_register);
5960		      macro_build (&offset_expr, s, fmt, treg,
5961				   BFD_RELOC_GPREL16, tempreg);
5962		    }
5963		  relax_switch ();
5964		}
5965
5966	      if (used_at == 0 && !mips_opts.noat)
5967		{
5968		  macro_build (&offset_expr, "lui", "t,u", tempreg,
5969			       BFD_RELOC_MIPS_HIGHEST);
5970		  macro_build (&offset_expr, "lui", "t,u", AT,
5971			       BFD_RELOC_HI16_S);
5972		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
5973			       tempreg, BFD_RELOC_MIPS_HIGHER);
5974		  if (breg != 0)
5975		    macro_build (NULL, "daddu", "d,v,t", AT, AT, breg);
5976		  macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
5977		  macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
5978		  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_LO16,
5979			       tempreg);
5980		  used_at = 1;
5981		}
5982	      else
5983		{
5984		  macro_build (&offset_expr, "lui", "t,u", tempreg,
5985			       BFD_RELOC_MIPS_HIGHEST);
5986		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
5987			       tempreg, BFD_RELOC_MIPS_HIGHER);
5988		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
5989		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
5990			       tempreg, BFD_RELOC_HI16_S);
5991		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
5992		  if (breg != 0)
5993		    macro_build (NULL, "daddu", "d,v,t",
5994				 tempreg, tempreg, breg);
5995		  macro_build (&offset_expr, s, fmt, treg,
5996			       BFD_RELOC_LO16, tempreg);
5997		}
5998
5999	      if (mips_relax.sequence)
6000		relax_end ();
6001	      break;
6002	    }
6003
6004	  if (breg == 0)
6005	    {
6006	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6007		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6008		{
6009		  relax_start (offset_expr.X_add_symbol);
6010		  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_GPREL16,
6011			       mips_gp_register);
6012		  relax_switch ();
6013		}
6014	      macro_build_lui (&offset_expr, tempreg);
6015	      macro_build (&offset_expr, s, fmt, treg,
6016			   BFD_RELOC_LO16, tempreg);
6017	      if (mips_relax.sequence)
6018		relax_end ();
6019	    }
6020	  else
6021	    {
6022	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6023		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6024		{
6025		  relax_start (offset_expr.X_add_symbol);
6026		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6027			       tempreg, breg, mips_gp_register);
6028		  macro_build (&offset_expr, s, fmt, treg,
6029			       BFD_RELOC_GPREL16, tempreg);
6030		  relax_switch ();
6031		}
6032	      macro_build_lui (&offset_expr, tempreg);
6033	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6034			   tempreg, tempreg, breg);
6035	      macro_build (&offset_expr, s, fmt, treg,
6036			   BFD_RELOC_LO16, tempreg);
6037	      if (mips_relax.sequence)
6038		relax_end ();
6039	    }
6040	}
6041      else if (!mips_big_got)
6042	{
6043	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
6044
6045	  /* If this is a reference to an external symbol, we want
6046	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6047	       nop
6048	       <op>	$treg,0($tempreg)
6049	     Otherwise we want
6050	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6051	       nop
6052	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
6053	       <op>	$treg,0($tempreg)
6054
6055	     For NewABI, we want
6056	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_PAGE)
6057	       <op>	$treg,<sym>($tempreg)   (BFD_RELOC_MIPS_GOT_OFST)
6058
6059	     If there is a base register, we add it to $tempreg before
6060	     the <op>.  If there is a constant, we stick it in the
6061	     <op> instruction.  We don't handle constants larger than
6062	     16 bits, because we have no way to load the upper 16 bits
6063	     (actually, we could handle them for the subset of cases
6064	     in which we are not using $at).  */
6065	  assert (offset_expr.X_op == O_symbol);
6066	  if (HAVE_NEWABI)
6067	    {
6068	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6069			   BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6070	      if (breg != 0)
6071		macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6072			     tempreg, tempreg, breg);
6073	      macro_build (&offset_expr, s, fmt, treg,
6074			   BFD_RELOC_MIPS_GOT_OFST, tempreg);
6075	      break;
6076	    }
6077	  expr1.X_add_number = offset_expr.X_add_number;
6078	  offset_expr.X_add_number = 0;
6079	  if (expr1.X_add_number < -0x8000
6080	      || expr1.X_add_number >= 0x8000)
6081	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6082	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6083		       lw_reloc_type, mips_gp_register);
6084	  load_delay_nop ();
6085	  relax_start (offset_expr.X_add_symbol);
6086	  relax_switch ();
6087	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6088		       tempreg, BFD_RELOC_LO16);
6089	  relax_end ();
6090	  if (breg != 0)
6091	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6092			 tempreg, tempreg, breg);
6093	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6094	}
6095      else if (mips_big_got && !HAVE_NEWABI)
6096	{
6097	  int gpdelay;
6098
6099	  /* If this is a reference to an external symbol, we want
6100	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6101	       addu	$tempreg,$tempreg,$gp
6102	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6103	       <op>	$treg,0($tempreg)
6104	     Otherwise we want
6105	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6106	       nop
6107	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
6108	       <op>	$treg,0($tempreg)
6109	     If there is a base register, we add it to $tempreg before
6110	     the <op>.  If there is a constant, we stick it in the
6111	     <op> instruction.  We don't handle constants larger than
6112	     16 bits, because we have no way to load the upper 16 bits
6113	     (actually, we could handle them for the subset of cases
6114	     in which we are not using $at).  */
6115	  assert (offset_expr.X_op == O_symbol);
6116	  expr1.X_add_number = offset_expr.X_add_number;
6117	  offset_expr.X_add_number = 0;
6118	  if (expr1.X_add_number < -0x8000
6119	      || expr1.X_add_number >= 0x8000)
6120	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6121	  gpdelay = reg_needs_delay (mips_gp_register);
6122	  relax_start (offset_expr.X_add_symbol);
6123	  macro_build (&offset_expr, "lui", "t,u", tempreg,
6124		       BFD_RELOC_MIPS_GOT_HI16);
6125	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6126		       mips_gp_register);
6127	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6128		       BFD_RELOC_MIPS_GOT_LO16, tempreg);
6129	  relax_switch ();
6130	  if (gpdelay)
6131	    macro_build (NULL, "nop", "");
6132	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6133		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
6134	  load_delay_nop ();
6135	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6136		       tempreg, BFD_RELOC_LO16);
6137	  relax_end ();
6138
6139	  if (breg != 0)
6140	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6141			 tempreg, tempreg, breg);
6142	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6143	}
6144      else if (mips_big_got && HAVE_NEWABI)
6145	{
6146	  /* If this is a reference to an external symbol, we want
6147	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6148	       add	$tempreg,$tempreg,$gp
6149	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6150	       <op>	$treg,<ofst>($tempreg)
6151	     Otherwise, for local symbols, we want:
6152	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_PAGE)
6153	       <op>	$treg,<sym>($tempreg)   (BFD_RELOC_MIPS_GOT_OFST)  */
6154	  assert (offset_expr.X_op == O_symbol);
6155	  expr1.X_add_number = offset_expr.X_add_number;
6156	  offset_expr.X_add_number = 0;
6157	  if (expr1.X_add_number < -0x8000
6158	      || expr1.X_add_number >= 0x8000)
6159	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6160	  relax_start (offset_expr.X_add_symbol);
6161	  macro_build (&offset_expr, "lui", "t,u", tempreg,
6162		       BFD_RELOC_MIPS_GOT_HI16);
6163	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6164		       mips_gp_register);
6165	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6166		       BFD_RELOC_MIPS_GOT_LO16, tempreg);
6167	  if (breg != 0)
6168	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6169			 tempreg, tempreg, breg);
6170	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6171
6172	  relax_switch ();
6173	  offset_expr.X_add_number = expr1.X_add_number;
6174	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6175		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6176	  if (breg != 0)
6177	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6178			 tempreg, tempreg, breg);
6179	  macro_build (&offset_expr, s, fmt, treg,
6180		       BFD_RELOC_MIPS_GOT_OFST, tempreg);
6181	  relax_end ();
6182	}
6183      else
6184	abort ();
6185
6186      break;
6187
6188    case M_LI:
6189    case M_LI_S:
6190      load_register (treg, &imm_expr, 0);
6191      break;
6192
6193    case M_DLI:
6194      load_register (treg, &imm_expr, 1);
6195      break;
6196
6197    case M_LI_SS:
6198      if (imm_expr.X_op == O_constant)
6199	{
6200	  used_at = 1;
6201	  load_register (AT, &imm_expr, 0);
6202	  macro_build (NULL, "mtc1", "t,G", AT, treg);
6203	  break;
6204	}
6205      else
6206	{
6207	  assert (offset_expr.X_op == O_symbol
6208		  && strcmp (segment_name (S_GET_SEGMENT
6209					   (offset_expr.X_add_symbol)),
6210			     ".lit4") == 0
6211		  && offset_expr.X_add_number == 0);
6212	  macro_build (&offset_expr, "lwc1", "T,o(b)", treg,
6213		       BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6214	  break;
6215	}
6216
6217    case M_LI_D:
6218      /* Check if we have a constant in IMM_EXPR.  If the GPRs are 64 bits
6219         wide, IMM_EXPR is the entire value.  Otherwise IMM_EXPR is the high
6220         order 32 bits of the value and the low order 32 bits are either
6221         zero or in OFFSET_EXPR.  */
6222      if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6223	{
6224	  if (HAVE_64BIT_GPRS)
6225	    load_register (treg, &imm_expr, 1);
6226	  else
6227	    {
6228	      int hreg, lreg;
6229
6230	      if (target_big_endian)
6231		{
6232		  hreg = treg;
6233		  lreg = treg + 1;
6234		}
6235	      else
6236		{
6237		  hreg = treg + 1;
6238		  lreg = treg;
6239		}
6240
6241	      if (hreg <= 31)
6242		load_register (hreg, &imm_expr, 0);
6243	      if (lreg <= 31)
6244		{
6245		  if (offset_expr.X_op == O_absent)
6246		    move_register (lreg, 0);
6247		  else
6248		    {
6249		      assert (offset_expr.X_op == O_constant);
6250		      load_register (lreg, &offset_expr, 0);
6251		    }
6252		}
6253	    }
6254	  break;
6255	}
6256
6257      /* We know that sym is in the .rdata section.  First we get the
6258	 upper 16 bits of the address.  */
6259      if (mips_pic == NO_PIC)
6260	{
6261	  macro_build_lui (&offset_expr, AT);
6262	  used_at = 1;
6263	}
6264      else
6265	{
6266	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6267		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
6268	  used_at = 1;
6269	}
6270
6271      /* Now we load the register(s).  */
6272      if (HAVE_64BIT_GPRS)
6273	{
6274	  used_at = 1;
6275	  macro_build (&offset_expr, "ld", "t,o(b)", treg, BFD_RELOC_LO16, AT);
6276	}
6277      else
6278	{
6279	  used_at = 1;
6280	  macro_build (&offset_expr, "lw", "t,o(b)", treg, BFD_RELOC_LO16, AT);
6281	  if (treg != RA)
6282	    {
6283	      /* FIXME: How in the world do we deal with the possible
6284		 overflow here?  */
6285	      offset_expr.X_add_number += 4;
6286	      macro_build (&offset_expr, "lw", "t,o(b)",
6287			   treg + 1, BFD_RELOC_LO16, AT);
6288	    }
6289	}
6290      break;
6291
6292    case M_LI_DD:
6293      /* Check if we have a constant in IMM_EXPR.  If the FPRs are 64 bits
6294         wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6295         bits wide as well.  Otherwise IMM_EXPR is the high order 32 bits of
6296         the value and the low order 32 bits are either zero or in
6297         OFFSET_EXPR.  */
6298      if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6299	{
6300	  used_at = 1;
6301	  load_register (AT, &imm_expr, HAVE_64BIT_FPRS);
6302	  if (HAVE_64BIT_FPRS)
6303	    {
6304	      assert (HAVE_64BIT_GPRS);
6305	      macro_build (NULL, "dmtc1", "t,S", AT, treg);
6306	    }
6307	  else
6308	    {
6309	      macro_build (NULL, "mtc1", "t,G", AT, treg + 1);
6310	      if (offset_expr.X_op == O_absent)
6311		macro_build (NULL, "mtc1", "t,G", 0, treg);
6312	      else
6313		{
6314		  assert (offset_expr.X_op == O_constant);
6315		  load_register (AT, &offset_expr, 0);
6316		  macro_build (NULL, "mtc1", "t,G", AT, treg);
6317		}
6318	    }
6319	  break;
6320	}
6321
6322      assert (offset_expr.X_op == O_symbol
6323	      && offset_expr.X_add_number == 0);
6324      s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6325      if (strcmp (s, ".lit8") == 0)
6326	{
6327	  if (mips_opts.isa != ISA_MIPS1)
6328	    {
6329	      macro_build (&offset_expr, "ldc1", "T,o(b)", treg,
6330			   BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6331	      break;
6332	    }
6333	  breg = mips_gp_register;
6334	  r = BFD_RELOC_MIPS_LITERAL;
6335	  goto dob;
6336	}
6337      else
6338	{
6339	  assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6340	  used_at = 1;
6341	  if (mips_pic != NO_PIC)
6342	    macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6343			 BFD_RELOC_MIPS_GOT16, mips_gp_register);
6344	  else
6345	    {
6346	      /* FIXME: This won't work for a 64 bit address.  */
6347	      macro_build_lui (&offset_expr, AT);
6348	    }
6349
6350	  if (mips_opts.isa != ISA_MIPS1)
6351	    {
6352	      macro_build (&offset_expr, "ldc1", "T,o(b)",
6353			   treg, BFD_RELOC_LO16, AT);
6354	      break;
6355	    }
6356	  breg = AT;
6357	  r = BFD_RELOC_LO16;
6358	  goto dob;
6359	}
6360
6361    case M_L_DOB:
6362      if (mips_opts.arch == CPU_R4650)
6363	{
6364	  as_bad (_("opcode not supported on this processor"));
6365	  break;
6366	}
6367      /* Even on a big endian machine $fn comes before $fn+1.  We have
6368	 to adjust when loading from memory.  */
6369      r = BFD_RELOC_LO16;
6370    dob:
6371      assert (mips_opts.isa == ISA_MIPS1);
6372      macro_build (&offset_expr, "lwc1", "T,o(b)",
6373		   target_big_endian ? treg + 1 : treg, r, breg);
6374      /* FIXME: A possible overflow which I don't know how to deal
6375	 with.  */
6376      offset_expr.X_add_number += 4;
6377      macro_build (&offset_expr, "lwc1", "T,o(b)",
6378		   target_big_endian ? treg : treg + 1, r, breg);
6379      break;
6380
6381    case M_L_DAB:
6382      /*
6383       * The MIPS assembler seems to check for X_add_number not
6384       * being double aligned and generating:
6385       *	lui	at,%hi(foo+1)
6386       *	addu	at,at,v1
6387       *	addiu	at,at,%lo(foo+1)
6388       *	lwc1	f2,0(at)
6389       *	lwc1	f3,4(at)
6390       * But, the resulting address is the same after relocation so why
6391       * generate the extra instruction?
6392       */
6393      if (mips_opts.arch == CPU_R4650)
6394	{
6395	  as_bad (_("opcode not supported on this processor"));
6396	  break;
6397	}
6398      /* Itbl support may require additional care here.  */
6399      coproc = 1;
6400      if (mips_opts.isa != ISA_MIPS1)
6401	{
6402	  s = "ldc1";
6403	  goto ld;
6404	}
6405
6406      s = "lwc1";
6407      fmt = "T,o(b)";
6408      goto ldd_std;
6409
6410    case M_S_DAB:
6411      if (mips_opts.arch == CPU_R4650)
6412	{
6413	  as_bad (_("opcode not supported on this processor"));
6414	  break;
6415	}
6416
6417      if (mips_opts.isa != ISA_MIPS1)
6418	{
6419	  s = "sdc1";
6420	  goto st;
6421	}
6422
6423      s = "swc1";
6424      fmt = "T,o(b)";
6425      /* Itbl support may require additional care here.  */
6426      coproc = 1;
6427      goto ldd_std;
6428
6429    case M_LD_AB:
6430      if (HAVE_64BIT_GPRS)
6431	{
6432	  s = "ld";
6433	  goto ld;
6434	}
6435
6436      s = "lw";
6437      fmt = "t,o(b)";
6438      goto ldd_std;
6439
6440    case M_SD_AB:
6441      if (HAVE_64BIT_GPRS)
6442	{
6443	  s = "sd";
6444	  goto st;
6445	}
6446
6447      s = "sw";
6448      fmt = "t,o(b)";
6449
6450    ldd_std:
6451      if (offset_expr.X_op != O_symbol
6452	  && offset_expr.X_op != O_constant)
6453	{
6454	  as_bad (_("expression too complex"));
6455	  offset_expr.X_op = O_constant;
6456	}
6457
6458      if (HAVE_32BIT_ADDRESSES
6459	  && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
6460	{
6461	  char value [32];
6462
6463	  sprintf_vma (value, offset_expr.X_add_number);
6464	  as_bad (_("Number (0x%s) larger than 32 bits"), value);
6465	}
6466
6467      /* Even on a big endian machine $fn comes before $fn+1.  We have
6468	 to adjust when loading from memory.  We set coproc if we must
6469	 load $fn+1 first.  */
6470      /* Itbl support may require additional care here.  */
6471      if (! target_big_endian)
6472	coproc = 0;
6473
6474      if (mips_pic == NO_PIC
6475	  || offset_expr.X_op == O_constant)
6476	{
6477	  /* If this is a reference to a GP relative symbol, we want
6478	       <op>	$treg,<sym>($gp)	(BFD_RELOC_GPREL16)
6479	       <op>	$treg+1,<sym>+4($gp)	(BFD_RELOC_GPREL16)
6480	     If we have a base register, we use this
6481	       addu	$at,$breg,$gp
6482	       <op>	$treg,<sym>($at)	(BFD_RELOC_GPREL16)
6483	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_GPREL16)
6484	     If this is not a GP relative symbol, we want
6485	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
6486	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
6487	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
6488	     If there is a base register, we add it to $at after the
6489	     lui instruction.  If there is a constant, we always use
6490	     the last case.  */
6491	  if (offset_expr.X_op == O_symbol
6492	      && (valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6493	      && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6494	    {
6495	      relax_start (offset_expr.X_add_symbol);
6496	      if (breg == 0)
6497		{
6498		  tempreg = mips_gp_register;
6499		}
6500	      else
6501		{
6502		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6503			       AT, breg, mips_gp_register);
6504		  tempreg = AT;
6505		  used_at = 1;
6506		}
6507
6508	      /* Itbl support may require additional care here.  */
6509	      macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6510			   BFD_RELOC_GPREL16, tempreg);
6511	      offset_expr.X_add_number += 4;
6512
6513	      /* Set mips_optimize to 2 to avoid inserting an
6514                 undesired nop.  */
6515	      hold_mips_optimize = mips_optimize;
6516	      mips_optimize = 2;
6517	      /* Itbl support may require additional care here.  */
6518	      macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6519			   BFD_RELOC_GPREL16, tempreg);
6520	      mips_optimize = hold_mips_optimize;
6521
6522	      relax_switch ();
6523
6524	      /* We just generated two relocs.  When tc_gen_reloc
6525		 handles this case, it will skip the first reloc and
6526		 handle the second.  The second reloc already has an
6527		 extra addend of 4, which we added above.  We must
6528		 subtract it out, and then subtract another 4 to make
6529		 the first reloc come out right.  The second reloc
6530		 will come out right because we are going to add 4 to
6531		 offset_expr when we build its instruction below.
6532
6533		 If we have a symbol, then we don't want to include
6534		 the offset, because it will wind up being included
6535		 when we generate the reloc.  */
6536
6537	      if (offset_expr.X_op == O_constant)
6538		offset_expr.X_add_number -= 8;
6539	      else
6540		{
6541		  offset_expr.X_add_number = -4;
6542		  offset_expr.X_op = O_constant;
6543		}
6544	    }
6545	  used_at = 1;
6546	  macro_build_lui (&offset_expr, AT);
6547	  if (breg != 0)
6548	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6549	  /* Itbl support may require additional care here.  */
6550	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6551		       BFD_RELOC_LO16, AT);
6552	  /* FIXME: How do we handle overflow here?  */
6553	  offset_expr.X_add_number += 4;
6554	  /* Itbl support may require additional care here.  */
6555	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6556		       BFD_RELOC_LO16, AT);
6557	  if (mips_relax.sequence)
6558	    relax_end ();
6559	}
6560      else if (!mips_big_got)
6561	{
6562	  /* If this is a reference to an external symbol, we want
6563	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
6564	       nop
6565	       <op>	$treg,0($at)
6566	       <op>	$treg+1,4($at)
6567	     Otherwise we want
6568	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
6569	       nop
6570	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
6571	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
6572	     If there is a base register we add it to $at before the
6573	     lwc1 instructions.  If there is a constant we include it
6574	     in the lwc1 instructions.  */
6575	  used_at = 1;
6576	  expr1.X_add_number = offset_expr.X_add_number;
6577	  if (expr1.X_add_number < -0x8000
6578	      || expr1.X_add_number >= 0x8000 - 4)
6579	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6580	  load_got_offset (AT, &offset_expr);
6581	  load_delay_nop ();
6582	  if (breg != 0)
6583	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6584
6585	  /* Set mips_optimize to 2 to avoid inserting an undesired
6586             nop.  */
6587	  hold_mips_optimize = mips_optimize;
6588	  mips_optimize = 2;
6589
6590	  /* Itbl support may require additional care here.  */
6591	  relax_start (offset_expr.X_add_symbol);
6592	  macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
6593		       BFD_RELOC_LO16, AT);
6594	  expr1.X_add_number += 4;
6595	  macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
6596		       BFD_RELOC_LO16, AT);
6597	  relax_switch ();
6598	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6599		       BFD_RELOC_LO16, AT);
6600	  offset_expr.X_add_number += 4;
6601	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6602		       BFD_RELOC_LO16, AT);
6603	  relax_end ();
6604
6605	  mips_optimize = hold_mips_optimize;
6606	}
6607      else if (mips_big_got)
6608	{
6609	  int gpdelay;
6610
6611	  /* If this is a reference to an external symbol, we want
6612	       lui	$at,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6613	       addu	$at,$at,$gp
6614	       lw	$at,<sym>($at)		(BFD_RELOC_MIPS_GOT_LO16)
6615	       nop
6616	       <op>	$treg,0($at)
6617	       <op>	$treg+1,4($at)
6618	     Otherwise we want
6619	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
6620	       nop
6621	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
6622	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
6623	     If there is a base register we add it to $at before the
6624	     lwc1 instructions.  If there is a constant we include it
6625	     in the lwc1 instructions.  */
6626	  used_at = 1;
6627	  expr1.X_add_number = offset_expr.X_add_number;
6628	  offset_expr.X_add_number = 0;
6629	  if (expr1.X_add_number < -0x8000
6630	      || expr1.X_add_number >= 0x8000 - 4)
6631	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6632	  gpdelay = reg_needs_delay (mips_gp_register);
6633	  relax_start (offset_expr.X_add_symbol);
6634	  macro_build (&offset_expr, "lui", "t,u",
6635		       AT, BFD_RELOC_MIPS_GOT_HI16);
6636	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6637		       AT, AT, mips_gp_register);
6638	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6639		       AT, BFD_RELOC_MIPS_GOT_LO16, AT);
6640	  load_delay_nop ();
6641	  if (breg != 0)
6642	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6643	  /* Itbl support may require additional care here.  */
6644	  macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
6645		       BFD_RELOC_LO16, AT);
6646	  expr1.X_add_number += 4;
6647
6648	  /* Set mips_optimize to 2 to avoid inserting an undesired
6649             nop.  */
6650	  hold_mips_optimize = mips_optimize;
6651	  mips_optimize = 2;
6652	  /* Itbl support may require additional care here.  */
6653	  macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
6654		       BFD_RELOC_LO16, AT);
6655	  mips_optimize = hold_mips_optimize;
6656	  expr1.X_add_number -= 4;
6657
6658	  relax_switch ();
6659	  offset_expr.X_add_number = expr1.X_add_number;
6660	  if (gpdelay)
6661	    macro_build (NULL, "nop", "");
6662	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6663		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
6664	  load_delay_nop ();
6665	  if (breg != 0)
6666	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6667	  /* Itbl support may require additional care here.  */
6668	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6669		       BFD_RELOC_LO16, AT);
6670	  offset_expr.X_add_number += 4;
6671
6672	  /* Set mips_optimize to 2 to avoid inserting an undesired
6673             nop.  */
6674	  hold_mips_optimize = mips_optimize;
6675	  mips_optimize = 2;
6676	  /* Itbl support may require additional care here.  */
6677	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6678		       BFD_RELOC_LO16, AT);
6679	  mips_optimize = hold_mips_optimize;
6680	  relax_end ();
6681	}
6682      else
6683	abort ();
6684
6685      break;
6686
6687    case M_LD_OB:
6688      s = "lw";
6689      goto sd_ob;
6690    case M_SD_OB:
6691      s = "sw";
6692    sd_ob:
6693      assert (HAVE_32BIT_ADDRESSES);
6694      macro_build (&offset_expr, s, "t,o(b)", treg, BFD_RELOC_LO16, breg);
6695      offset_expr.X_add_number += 4;
6696      macro_build (&offset_expr, s, "t,o(b)", treg + 1, BFD_RELOC_LO16, breg);
6697      break;
6698
6699   /* New code added to support COPZ instructions.
6700      This code builds table entries out of the macros in mip_opcodes.
6701      R4000 uses interlocks to handle coproc delays.
6702      Other chips (like the R3000) require nops to be inserted for delays.
6703
6704      FIXME: Currently, we require that the user handle delays.
6705      In order to fill delay slots for non-interlocked chips,
6706      we must have a way to specify delays based on the coprocessor.
6707      Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
6708      What are the side-effects of the cop instruction?
6709      What cache support might we have and what are its effects?
6710      Both coprocessor & memory require delays. how long???
6711      What registers are read/set/modified?
6712
6713      If an itbl is provided to interpret cop instructions,
6714      this knowledge can be encoded in the itbl spec.  */
6715
6716    case M_COP0:
6717      s = "c0";
6718      goto copz;
6719    case M_COP1:
6720      s = "c1";
6721      goto copz;
6722    case M_COP2:
6723      s = "c2";
6724      goto copz;
6725    case M_COP3:
6726      s = "c3";
6727    copz:
6728      /* For now we just do C (same as Cz).  The parameter will be
6729         stored in insn_opcode by mips_ip.  */
6730      macro_build (NULL, s, "C", ip->insn_opcode);
6731      break;
6732
6733    case M_MOVE:
6734      move_register (dreg, sreg);
6735      break;
6736
6737#ifdef LOSING_COMPILER
6738    default:
6739      /* Try and see if this is a new itbl instruction.
6740         This code builds table entries out of the macros in mip_opcodes.
6741         FIXME: For now we just assemble the expression and pass it's
6742         value along as a 32-bit immediate.
6743         We may want to have the assembler assemble this value,
6744         so that we gain the assembler's knowledge of delay slots,
6745         symbols, etc.
6746         Would it be more efficient to use mask (id) here? */
6747      if (itbl_have_entries
6748	  && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
6749	{
6750	  s = ip->insn_mo->name;
6751	  s2 = "cop3";
6752	  coproc = ITBL_DECODE_PNUM (immed_expr);;
6753	  macro_build (&immed_expr, s, "C");
6754	  break;
6755	}
6756      macro2 (ip);
6757      break;
6758    }
6759  if (mips_opts.noat && used_at)
6760    as_bad (_("Macro used $at after \".set noat\""));
6761}
6762
6763static void
6764macro2 (struct mips_cl_insn *ip)
6765{
6766  register int treg, sreg, dreg, breg;
6767  int tempreg;
6768  int mask;
6769  int used_at;
6770  expressionS expr1;
6771  const char *s;
6772  const char *s2;
6773  const char *fmt;
6774  int likely = 0;
6775  int dbl = 0;
6776  int coproc = 0;
6777  int lr = 0;
6778  int imm = 0;
6779  int off;
6780  offsetT maxnum;
6781  bfd_reloc_code_real_type r;
6782
6783  treg = (ip->insn_opcode >> 16) & 0x1f;
6784  dreg = (ip->insn_opcode >> 11) & 0x1f;
6785  sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
6786  mask = ip->insn_mo->mask;
6787
6788  expr1.X_op = O_constant;
6789  expr1.X_op_symbol = NULL;
6790  expr1.X_add_symbol = NULL;
6791  expr1.X_add_number = 1;
6792
6793  switch (mask)
6794    {
6795#endif /* LOSING_COMPILER */
6796
6797    case M_DMUL:
6798      dbl = 1;
6799    case M_MUL:
6800      macro_build (NULL, dbl ? "dmultu" : "multu", "s,t", sreg, treg);
6801      macro_build (NULL, "mflo", "d", dreg);
6802      break;
6803
6804    case M_DMUL_I:
6805      dbl = 1;
6806    case M_MUL_I:
6807      /* The MIPS assembler some times generates shifts and adds.  I'm
6808	 not trying to be that fancy. GCC should do this for us
6809	 anyway.  */
6810      used_at = 1;
6811      load_register (AT, &imm_expr, dbl);
6812      macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, AT);
6813      macro_build (NULL, "mflo", "d", dreg);
6814      break;
6815
6816    case M_DMULO_I:
6817      dbl = 1;
6818    case M_MULO_I:
6819      imm = 1;
6820      goto do_mulo;
6821
6822    case M_DMULO:
6823      dbl = 1;
6824    case M_MULO:
6825    do_mulo:
6826      start_noreorder ();
6827      used_at = 1;
6828      if (imm)
6829	load_register (AT, &imm_expr, dbl);
6830      macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
6831      macro_build (NULL, "mflo", "d", dreg);
6832      macro_build (NULL, dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
6833      macro_build (NULL, "mfhi", "d", AT);
6834      if (mips_trap)
6835	macro_build (NULL, "tne", "s,t,q", dreg, AT, 6);
6836      else
6837	{
6838	  expr1.X_add_number = 8;
6839	  macro_build (&expr1, "beq", "s,t,p", dreg, AT);
6840	  macro_build (NULL, "nop", "", 0);
6841	  macro_build (NULL, "break", "c", 6);
6842	}
6843      end_noreorder ();
6844      macro_build (NULL, "mflo", "d", dreg);
6845      break;
6846
6847    case M_DMULOU_I:
6848      dbl = 1;
6849    case M_MULOU_I:
6850      imm = 1;
6851      goto do_mulou;
6852
6853    case M_DMULOU:
6854      dbl = 1;
6855    case M_MULOU:
6856    do_mulou:
6857      start_noreorder ();
6858      used_at = 1;
6859      if (imm)
6860	load_register (AT, &imm_expr, dbl);
6861      macro_build (NULL, dbl ? "dmultu" : "multu", "s,t",
6862		   sreg, imm ? AT : treg);
6863      macro_build (NULL, "mfhi", "d", AT);
6864      macro_build (NULL, "mflo", "d", dreg);
6865      if (mips_trap)
6866	macro_build (NULL, "tne", "s,t,q", AT, 0, 6);
6867      else
6868	{
6869	  expr1.X_add_number = 8;
6870	  macro_build (&expr1, "beq", "s,t,p", AT, 0);
6871	  macro_build (NULL, "nop", "", 0);
6872	  macro_build (NULL, "break", "c", 6);
6873	}
6874      end_noreorder ();
6875      break;
6876
6877    case M_DROL:
6878      if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
6879	{
6880	  if (dreg == sreg)
6881	    {
6882	      tempreg = AT;
6883	      used_at = 1;
6884	    }
6885	  else
6886	    {
6887	      tempreg = dreg;
6888	    }
6889	  macro_build (NULL, "dnegu", "d,w", tempreg, treg);
6890	  macro_build (NULL, "drorv", "d,t,s", dreg, sreg, tempreg);
6891	  break;
6892	}
6893      used_at = 1;
6894      macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
6895      macro_build (NULL, "dsrlv", "d,t,s", AT, sreg, AT);
6896      macro_build (NULL, "dsllv", "d,t,s", dreg, sreg, treg);
6897      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
6898      break;
6899
6900    case M_ROL:
6901      if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
6902	{
6903	  if (dreg == sreg)
6904	    {
6905	      tempreg = AT;
6906	      used_at = 1;
6907	    }
6908	  else
6909	    {
6910	      tempreg = dreg;
6911	    }
6912	  macro_build (NULL, "negu", "d,w", tempreg, treg);
6913	  macro_build (NULL, "rorv", "d,t,s", dreg, sreg, tempreg);
6914	  break;
6915	}
6916      used_at = 1;
6917      macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
6918      macro_build (NULL, "srlv", "d,t,s", AT, sreg, AT);
6919      macro_build (NULL, "sllv", "d,t,s", dreg, sreg, treg);
6920      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
6921      break;
6922
6923    case M_DROL_I:
6924      {
6925	unsigned int rot;
6926	char *l, *r;
6927
6928	if (imm_expr.X_op != O_constant)
6929	  as_bad (_("Improper rotate count"));
6930	rot = imm_expr.X_add_number & 0x3f;
6931	if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
6932	  {
6933	    rot = (64 - rot) & 0x3f;
6934	    if (rot >= 32)
6935	      macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
6936	    else
6937	      macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
6938	    break;
6939	  }
6940	if (rot == 0)
6941	  {
6942	    macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
6943	    break;
6944	  }
6945	l = (rot < 0x20) ? "dsll" : "dsll32";
6946	r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
6947	rot &= 0x1f;
6948	used_at = 1;
6949	macro_build (NULL, l, "d,w,<", AT, sreg, rot);
6950	macro_build (NULL, r, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
6951	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
6952      }
6953      break;
6954
6955    case M_ROL_I:
6956      {
6957	unsigned int rot;
6958
6959	if (imm_expr.X_op != O_constant)
6960	  as_bad (_("Improper rotate count"));
6961	rot = imm_expr.X_add_number & 0x1f;
6962	if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
6963	  {
6964	    macro_build (NULL, "ror", "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
6965	    break;
6966	  }
6967	if (rot == 0)
6968	  {
6969	    macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
6970	    break;
6971	  }
6972	used_at = 1;
6973	macro_build (NULL, "sll", "d,w,<", AT, sreg, rot);
6974	macro_build (NULL, "srl", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
6975	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
6976      }
6977      break;
6978
6979    case M_DROR:
6980      if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
6981	{
6982	  macro_build (NULL, "drorv", "d,t,s", dreg, sreg, treg);
6983	  break;
6984	}
6985      used_at = 1;
6986      macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
6987      macro_build (NULL, "dsllv", "d,t,s", AT, sreg, AT);
6988      macro_build (NULL, "dsrlv", "d,t,s", dreg, sreg, treg);
6989      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
6990      break;
6991
6992    case M_ROR:
6993      if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
6994	{
6995	  macro_build (NULL, "rorv", "d,t,s", dreg, sreg, treg);
6996	  break;
6997	}
6998      used_at = 1;
6999      macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
7000      macro_build (NULL, "sllv", "d,t,s", AT, sreg, AT);
7001      macro_build (NULL, "srlv", "d,t,s", dreg, sreg, treg);
7002      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7003      break;
7004
7005    case M_DROR_I:
7006      {
7007	unsigned int rot;
7008	char *l, *r;
7009
7010	if (imm_expr.X_op != O_constant)
7011	  as_bad (_("Improper rotate count"));
7012	rot = imm_expr.X_add_number & 0x3f;
7013	if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7014	  {
7015	    if (rot >= 32)
7016	      macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
7017	    else
7018	      macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
7019	    break;
7020	  }
7021	if (rot == 0)
7022	  {
7023	    macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
7024	    break;
7025	  }
7026	r = (rot < 0x20) ? "dsrl" : "dsrl32";
7027	l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7028	rot &= 0x1f;
7029	used_at = 1;
7030	macro_build (NULL, r, "d,w,<", AT, sreg, rot);
7031	macro_build (NULL, l, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7032	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7033      }
7034      break;
7035
7036    case M_ROR_I:
7037      {
7038	unsigned int rot;
7039
7040	if (imm_expr.X_op != O_constant)
7041	  as_bad (_("Improper rotate count"));
7042	rot = imm_expr.X_add_number & 0x1f;
7043	if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7044	  {
7045	    macro_build (NULL, "ror", "d,w,<", dreg, sreg, rot);
7046	    break;
7047	  }
7048	if (rot == 0)
7049	  {
7050	    macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
7051	    break;
7052	  }
7053	used_at = 1;
7054	macro_build (NULL, "srl", "d,w,<", AT, sreg, rot);
7055	macro_build (NULL, "sll", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7056	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7057      }
7058      break;
7059
7060    case M_S_DOB:
7061      if (mips_opts.arch == CPU_R4650)
7062	{
7063	  as_bad (_("opcode not supported on this processor"));
7064	  break;
7065	}
7066      assert (mips_opts.isa == ISA_MIPS1);
7067      /* Even on a big endian machine $fn comes before $fn+1.  We have
7068	 to adjust when storing to memory.  */
7069      macro_build (&offset_expr, "swc1", "T,o(b)",
7070		   target_big_endian ? treg + 1 : treg, BFD_RELOC_LO16, breg);
7071      offset_expr.X_add_number += 4;
7072      macro_build (&offset_expr, "swc1", "T,o(b)",
7073		   target_big_endian ? treg : treg + 1, BFD_RELOC_LO16, breg);
7074      break;
7075
7076    case M_SEQ:
7077      if (sreg == 0)
7078	macro_build (&expr1, "sltiu", "t,r,j", dreg, treg, BFD_RELOC_LO16);
7079      else if (treg == 0)
7080	macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7081      else
7082	{
7083	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7084	  macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7085	}
7086      break;
7087
7088    case M_SEQ_I:
7089      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7090	{
7091	  macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7092	  break;
7093	}
7094      if (sreg == 0)
7095	{
7096	  as_warn (_("Instruction %s: result is always false"),
7097		   ip->insn_mo->name);
7098	  move_register (dreg, 0);
7099	  break;
7100	}
7101      if (imm_expr.X_op == O_constant
7102	  && imm_expr.X_add_number >= 0
7103	  && imm_expr.X_add_number < 0x10000)
7104	{
7105	  macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7106	}
7107      else if (imm_expr.X_op == O_constant
7108	       && imm_expr.X_add_number > -0x8000
7109	       && imm_expr.X_add_number < 0)
7110	{
7111	  imm_expr.X_add_number = -imm_expr.X_add_number;
7112	  macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7113		       "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7114	}
7115      else
7116	{
7117	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7118	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
7119	  used_at = 1;
7120	}
7121      macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7122      break;
7123
7124    case M_SGE:		/* sreg >= treg <==> not (sreg < treg) */
7125      s = "slt";
7126      goto sge;
7127    case M_SGEU:
7128      s = "sltu";
7129    sge:
7130      macro_build (NULL, s, "d,v,t", dreg, sreg, treg);
7131      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7132      break;
7133
7134    case M_SGE_I:		/* sreg >= I <==> not (sreg < I) */
7135    case M_SGEU_I:
7136      if (imm_expr.X_op == O_constant
7137	  && imm_expr.X_add_number >= -0x8000
7138	  && imm_expr.X_add_number < 0x8000)
7139	{
7140	  macro_build (&imm_expr, mask == M_SGE_I ? "slti" : "sltiu", "t,r,j",
7141		       dreg, sreg, BFD_RELOC_LO16);
7142	}
7143      else
7144	{
7145	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7146	  macro_build (NULL, mask == M_SGE_I ? "slt" : "sltu", "d,v,t",
7147		       dreg, sreg, AT);
7148	  used_at = 1;
7149	}
7150      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7151      break;
7152
7153    case M_SGT:		/* sreg > treg  <==>  treg < sreg */
7154      s = "slt";
7155      goto sgt;
7156    case M_SGTU:
7157      s = "sltu";
7158    sgt:
7159      macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7160      break;
7161
7162    case M_SGT_I:		/* sreg > I  <==>  I < sreg */
7163      s = "slt";
7164      goto sgti;
7165    case M_SGTU_I:
7166      s = "sltu";
7167    sgti:
7168      used_at = 1;
7169      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7170      macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7171      break;
7172
7173    case M_SLE:	/* sreg <= treg  <==>  treg >= sreg  <==>  not (treg < sreg) */
7174      s = "slt";
7175      goto sle;
7176    case M_SLEU:
7177      s = "sltu";
7178    sle:
7179      macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7180      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7181      break;
7182
7183    case M_SLE_I:	/* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7184      s = "slt";
7185      goto slei;
7186    case M_SLEU_I:
7187      s = "sltu";
7188    slei:
7189      used_at = 1;
7190      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7191      macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7192      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7193      break;
7194
7195    case M_SLT_I:
7196      if (imm_expr.X_op == O_constant
7197	  && imm_expr.X_add_number >= -0x8000
7198	  && imm_expr.X_add_number < 0x8000)
7199	{
7200	  macro_build (&imm_expr, "slti", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7201	  break;
7202	}
7203      used_at = 1;
7204      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7205      macro_build (NULL, "slt", "d,v,t", dreg, sreg, AT);
7206      break;
7207
7208    case M_SLTU_I:
7209      if (imm_expr.X_op == O_constant
7210	  && imm_expr.X_add_number >= -0x8000
7211	  && imm_expr.X_add_number < 0x8000)
7212	{
7213	  macro_build (&imm_expr, "sltiu", "t,r,j", dreg, sreg,
7214		       BFD_RELOC_LO16);
7215	  break;
7216	}
7217      used_at = 1;
7218      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7219      macro_build (NULL, "sltu", "d,v,t", dreg, sreg, AT);
7220      break;
7221
7222    case M_SNE:
7223      if (sreg == 0)
7224	macro_build (NULL, "sltu", "d,v,t", dreg, 0, treg);
7225      else if (treg == 0)
7226	macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7227      else
7228	{
7229	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7230	  macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
7231	}
7232      break;
7233
7234    case M_SNE_I:
7235      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7236	{
7237	  macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7238	  break;
7239	}
7240      if (sreg == 0)
7241	{
7242	  as_warn (_("Instruction %s: result is always true"),
7243		   ip->insn_mo->name);
7244	  macro_build (&expr1, HAVE_32BIT_GPRS ? "addiu" : "daddiu", "t,r,j",
7245		       dreg, 0, BFD_RELOC_LO16);
7246	  break;
7247	}
7248      if (imm_expr.X_op == O_constant
7249	  && imm_expr.X_add_number >= 0
7250	  && imm_expr.X_add_number < 0x10000)
7251	{
7252	  macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7253	}
7254      else if (imm_expr.X_op == O_constant
7255	       && imm_expr.X_add_number > -0x8000
7256	       && imm_expr.X_add_number < 0)
7257	{
7258	  imm_expr.X_add_number = -imm_expr.X_add_number;
7259	  macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7260		       "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7261	}
7262      else
7263	{
7264	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7265	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
7266	  used_at = 1;
7267	}
7268      macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
7269      break;
7270
7271    case M_DSUB_I:
7272      dbl = 1;
7273    case M_SUB_I:
7274      if (imm_expr.X_op == O_constant
7275	  && imm_expr.X_add_number > -0x8000
7276	  && imm_expr.X_add_number <= 0x8000)
7277	{
7278	  imm_expr.X_add_number = -imm_expr.X_add_number;
7279	  macro_build (&imm_expr, dbl ? "daddi" : "addi", "t,r,j",
7280		       dreg, sreg, BFD_RELOC_LO16);
7281	  break;
7282	}
7283      used_at = 1;
7284      load_register (AT, &imm_expr, dbl);
7285      macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7286      break;
7287
7288    case M_DSUBU_I:
7289      dbl = 1;
7290    case M_SUBU_I:
7291      if (imm_expr.X_op == O_constant
7292	  && imm_expr.X_add_number > -0x8000
7293	  && imm_expr.X_add_number <= 0x8000)
7294	{
7295	  imm_expr.X_add_number = -imm_expr.X_add_number;
7296	  macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "t,r,j",
7297		       dreg, sreg, BFD_RELOC_LO16);
7298	  break;
7299	}
7300      used_at = 1;
7301      load_register (AT, &imm_expr, dbl);
7302      macro_build (NULL, dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7303      break;
7304
7305    case M_TEQ_I:
7306      s = "teq";
7307      goto trap;
7308    case M_TGE_I:
7309      s = "tge";
7310      goto trap;
7311    case M_TGEU_I:
7312      s = "tgeu";
7313      goto trap;
7314    case M_TLT_I:
7315      s = "tlt";
7316      goto trap;
7317    case M_TLTU_I:
7318      s = "tltu";
7319      goto trap;
7320    case M_TNE_I:
7321      s = "tne";
7322    trap:
7323      used_at = 1;
7324      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7325      macro_build (NULL, s, "s,t", sreg, AT);
7326      break;
7327
7328    case M_TRUNCWS:
7329    case M_TRUNCWD:
7330      assert (mips_opts.isa == ISA_MIPS1);
7331      used_at = 1;
7332      sreg = (ip->insn_opcode >> 11) & 0x1f;	/* floating reg */
7333      dreg = (ip->insn_opcode >> 06) & 0x1f;	/* floating reg */
7334
7335      /*
7336       * Is the double cfc1 instruction a bug in the mips assembler;
7337       * or is there a reason for it?
7338       */
7339      start_noreorder ();
7340      macro_build (NULL, "cfc1", "t,G", treg, RA);
7341      macro_build (NULL, "cfc1", "t,G", treg, RA);
7342      macro_build (NULL, "nop", "");
7343      expr1.X_add_number = 3;
7344      macro_build (&expr1, "ori", "t,r,i", AT, treg, BFD_RELOC_LO16);
7345      expr1.X_add_number = 2;
7346      macro_build (&expr1, "xori", "t,r,i", AT, AT, BFD_RELOC_LO16);
7347      macro_build (NULL, "ctc1", "t,G", AT, RA);
7348      macro_build (NULL, "nop", "");
7349      macro_build (NULL, mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S",
7350		   dreg, sreg);
7351      macro_build (NULL, "ctc1", "t,G", treg, RA);
7352      macro_build (NULL, "nop", "");
7353      end_noreorder ();
7354      break;
7355
7356    case M_ULH:
7357      s = "lb";
7358      goto ulh;
7359    case M_ULHU:
7360      s = "lbu";
7361    ulh:
7362      used_at = 1;
7363      if (offset_expr.X_add_number >= 0x7fff)
7364	as_bad (_("operand overflow"));
7365      if (! target_big_endian)
7366	++offset_expr.X_add_number;
7367      macro_build (&offset_expr, s, "t,o(b)", AT, BFD_RELOC_LO16, breg);
7368      if (! target_big_endian)
7369	--offset_expr.X_add_number;
7370      else
7371	++offset_expr.X_add_number;
7372      macro_build (&offset_expr, "lbu", "t,o(b)", treg, BFD_RELOC_LO16, breg);
7373      macro_build (NULL, "sll", "d,w,<", AT, AT, 8);
7374      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7375      break;
7376
7377    case M_ULD:
7378      s = "ldl";
7379      s2 = "ldr";
7380      off = 7;
7381      goto ulw;
7382    case M_ULW:
7383      s = "lwl";
7384      s2 = "lwr";
7385      off = 3;
7386    ulw:
7387      if (offset_expr.X_add_number >= 0x8000 - off)
7388	as_bad (_("operand overflow"));
7389      if (treg != breg)
7390	tempreg = treg;
7391      else
7392	{
7393	  used_at = 1;
7394	  tempreg = AT;
7395	}
7396      if (! target_big_endian)
7397	offset_expr.X_add_number += off;
7398      macro_build (&offset_expr, s, "t,o(b)", tempreg, BFD_RELOC_LO16, breg);
7399      if (! target_big_endian)
7400	offset_expr.X_add_number -= off;
7401      else
7402	offset_expr.X_add_number += off;
7403      macro_build (&offset_expr, s2, "t,o(b)", tempreg, BFD_RELOC_LO16, breg);
7404
7405      /* If necessary, move the result in tempreg the final destination.  */
7406      if (treg == tempreg)
7407        break;
7408      /* Protect second load's delay slot.  */
7409      load_delay_nop ();
7410      move_register (treg, tempreg);
7411      break;
7412
7413    case M_ULD_A:
7414      s = "ldl";
7415      s2 = "ldr";
7416      off = 7;
7417      goto ulwa;
7418    case M_ULW_A:
7419      s = "lwl";
7420      s2 = "lwr";
7421      off = 3;
7422    ulwa:
7423      used_at = 1;
7424      load_address (AT, &offset_expr, &used_at);
7425      if (breg != 0)
7426	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7427      if (! target_big_endian)
7428	expr1.X_add_number = off;
7429      else
7430	expr1.X_add_number = 0;
7431      macro_build (&expr1, s, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7432      if (! target_big_endian)
7433	expr1.X_add_number = 0;
7434      else
7435	expr1.X_add_number = off;
7436      macro_build (&expr1, s2, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7437      break;
7438
7439    case M_ULH_A:
7440    case M_ULHU_A:
7441      used_at = 1;
7442      load_address (AT, &offset_expr, &used_at);
7443      if (breg != 0)
7444	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7445      if (target_big_endian)
7446	expr1.X_add_number = 0;
7447      macro_build (&expr1, mask == M_ULH_A ? "lb" : "lbu", "t,o(b)",
7448		   treg, BFD_RELOC_LO16, AT);
7449      if (target_big_endian)
7450	expr1.X_add_number = 1;
7451      else
7452	expr1.X_add_number = 0;
7453      macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
7454      macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
7455      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7456      break;
7457
7458    case M_USH:
7459      used_at = 1;
7460      if (offset_expr.X_add_number >= 0x7fff)
7461	as_bad (_("operand overflow"));
7462      if (target_big_endian)
7463	++offset_expr.X_add_number;
7464      macro_build (&offset_expr, "sb", "t,o(b)", treg, BFD_RELOC_LO16, breg);
7465      macro_build (NULL, "srl", "d,w,<", AT, treg, 8);
7466      if (target_big_endian)
7467	--offset_expr.X_add_number;
7468      else
7469	++offset_expr.X_add_number;
7470      macro_build (&offset_expr, "sb", "t,o(b)", AT, BFD_RELOC_LO16, breg);
7471      break;
7472
7473    case M_USD:
7474      s = "sdl";
7475      s2 = "sdr";
7476      off = 7;
7477      goto usw;
7478    case M_USW:
7479      s = "swl";
7480      s2 = "swr";
7481      off = 3;
7482    usw:
7483      if (offset_expr.X_add_number >= 0x8000 - off)
7484	as_bad (_("operand overflow"));
7485      if (! target_big_endian)
7486	offset_expr.X_add_number += off;
7487      macro_build (&offset_expr, s, "t,o(b)", treg, BFD_RELOC_LO16, breg);
7488      if (! target_big_endian)
7489	offset_expr.X_add_number -= off;
7490      else
7491	offset_expr.X_add_number += off;
7492      macro_build (&offset_expr, s2, "t,o(b)", treg, BFD_RELOC_LO16, breg);
7493      break;
7494
7495    case M_USD_A:
7496      s = "sdl";
7497      s2 = "sdr";
7498      off = 7;
7499      goto uswa;
7500    case M_USW_A:
7501      s = "swl";
7502      s2 = "swr";
7503      off = 3;
7504    uswa:
7505      used_at = 1;
7506      load_address (AT, &offset_expr, &used_at);
7507      if (breg != 0)
7508	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7509      if (! target_big_endian)
7510	expr1.X_add_number = off;
7511      else
7512	expr1.X_add_number = 0;
7513      macro_build (&expr1, s, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7514      if (! target_big_endian)
7515	expr1.X_add_number = 0;
7516      else
7517	expr1.X_add_number = off;
7518      macro_build (&expr1, s2, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7519      break;
7520
7521    case M_USH_A:
7522      used_at = 1;
7523      load_address (AT, &offset_expr, &used_at);
7524      if (breg != 0)
7525	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7526      if (! target_big_endian)
7527	expr1.X_add_number = 0;
7528      macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7529      macro_build (NULL, "srl", "d,w,<", treg, treg, 8);
7530      if (! target_big_endian)
7531	expr1.X_add_number = 1;
7532      else
7533	expr1.X_add_number = 0;
7534      macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7535      if (! target_big_endian)
7536	expr1.X_add_number = 0;
7537      else
7538	expr1.X_add_number = 1;
7539      macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
7540      macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
7541      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7542      break;
7543
7544    default:
7545      /* FIXME: Check if this is one of the itbl macros, since they
7546	 are added dynamically.  */
7547      as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
7548      break;
7549    }
7550  if (mips_opts.noat && used_at)
7551    as_bad (_("Macro used $at after \".set noat\""));
7552}
7553
7554/* Implement macros in mips16 mode.  */
7555
7556static void
7557mips16_macro (struct mips_cl_insn *ip)
7558{
7559  int mask;
7560  int xreg, yreg, zreg, tmp;
7561  expressionS expr1;
7562  int dbl;
7563  const char *s, *s2, *s3;
7564
7565  mask = ip->insn_mo->mask;
7566
7567  xreg = MIPS16_EXTRACT_OPERAND (RX, *ip);
7568  yreg = MIPS16_EXTRACT_OPERAND (RY, *ip);
7569  zreg = MIPS16_EXTRACT_OPERAND (RZ, *ip);
7570
7571  expr1.X_op = O_constant;
7572  expr1.X_op_symbol = NULL;
7573  expr1.X_add_symbol = NULL;
7574  expr1.X_add_number = 1;
7575
7576  dbl = 0;
7577
7578  switch (mask)
7579    {
7580    default:
7581      internalError ();
7582
7583    case M_DDIV_3:
7584      dbl = 1;
7585    case M_DIV_3:
7586      s = "mflo";
7587      goto do_div3;
7588    case M_DREM_3:
7589      dbl = 1;
7590    case M_REM_3:
7591      s = "mfhi";
7592    do_div3:
7593      start_noreorder ();
7594      macro_build (NULL, dbl ? "ddiv" : "div", "0,x,y", xreg, yreg);
7595      expr1.X_add_number = 2;
7596      macro_build (&expr1, "bnez", "x,p", yreg);
7597      macro_build (NULL, "break", "6", 7);
7598
7599      /* FIXME: The normal code checks for of -1 / -0x80000000 here,
7600         since that causes an overflow.  We should do that as well,
7601         but I don't see how to do the comparisons without a temporary
7602         register.  */
7603      end_noreorder ();
7604      macro_build (NULL, s, "x", zreg);
7605      break;
7606
7607    case M_DIVU_3:
7608      s = "divu";
7609      s2 = "mflo";
7610      goto do_divu3;
7611    case M_REMU_3:
7612      s = "divu";
7613      s2 = "mfhi";
7614      goto do_divu3;
7615    case M_DDIVU_3:
7616      s = "ddivu";
7617      s2 = "mflo";
7618      goto do_divu3;
7619    case M_DREMU_3:
7620      s = "ddivu";
7621      s2 = "mfhi";
7622    do_divu3:
7623      start_noreorder ();
7624      macro_build (NULL, s, "0,x,y", xreg, yreg);
7625      expr1.X_add_number = 2;
7626      macro_build (&expr1, "bnez", "x,p", yreg);
7627      macro_build (NULL, "break", "6", 7);
7628      end_noreorder ();
7629      macro_build (NULL, s2, "x", zreg);
7630      break;
7631
7632    case M_DMUL:
7633      dbl = 1;
7634    case M_MUL:
7635      macro_build (NULL, dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
7636      macro_build (NULL, "mflo", "x", zreg);
7637      break;
7638
7639    case M_DSUBU_I:
7640      dbl = 1;
7641      goto do_subu;
7642    case M_SUBU_I:
7643    do_subu:
7644      if (imm_expr.X_op != O_constant)
7645	as_bad (_("Unsupported large constant"));
7646      imm_expr.X_add_number = -imm_expr.X_add_number;
7647      macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
7648      break;
7649
7650    case M_SUBU_I_2:
7651      if (imm_expr.X_op != O_constant)
7652	as_bad (_("Unsupported large constant"));
7653      imm_expr.X_add_number = -imm_expr.X_add_number;
7654      macro_build (&imm_expr, "addiu", "x,k", xreg);
7655      break;
7656
7657    case M_DSUBU_I_2:
7658      if (imm_expr.X_op != O_constant)
7659	as_bad (_("Unsupported large constant"));
7660      imm_expr.X_add_number = -imm_expr.X_add_number;
7661      macro_build (&imm_expr, "daddiu", "y,j", yreg);
7662      break;
7663
7664    case M_BEQ:
7665      s = "cmp";
7666      s2 = "bteqz";
7667      goto do_branch;
7668    case M_BNE:
7669      s = "cmp";
7670      s2 = "btnez";
7671      goto do_branch;
7672    case M_BLT:
7673      s = "slt";
7674      s2 = "btnez";
7675      goto do_branch;
7676    case M_BLTU:
7677      s = "sltu";
7678      s2 = "btnez";
7679      goto do_branch;
7680    case M_BLE:
7681      s = "slt";
7682      s2 = "bteqz";
7683      goto do_reverse_branch;
7684    case M_BLEU:
7685      s = "sltu";
7686      s2 = "bteqz";
7687      goto do_reverse_branch;
7688    case M_BGE:
7689      s = "slt";
7690      s2 = "bteqz";
7691      goto do_branch;
7692    case M_BGEU:
7693      s = "sltu";
7694      s2 = "bteqz";
7695      goto do_branch;
7696    case M_BGT:
7697      s = "slt";
7698      s2 = "btnez";
7699      goto do_reverse_branch;
7700    case M_BGTU:
7701      s = "sltu";
7702      s2 = "btnez";
7703
7704    do_reverse_branch:
7705      tmp = xreg;
7706      xreg = yreg;
7707      yreg = tmp;
7708
7709    do_branch:
7710      macro_build (NULL, s, "x,y", xreg, yreg);
7711      macro_build (&offset_expr, s2, "p");
7712      break;
7713
7714    case M_BEQ_I:
7715      s = "cmpi";
7716      s2 = "bteqz";
7717      s3 = "x,U";
7718      goto do_branch_i;
7719    case M_BNE_I:
7720      s = "cmpi";
7721      s2 = "btnez";
7722      s3 = "x,U";
7723      goto do_branch_i;
7724    case M_BLT_I:
7725      s = "slti";
7726      s2 = "btnez";
7727      s3 = "x,8";
7728      goto do_branch_i;
7729    case M_BLTU_I:
7730      s = "sltiu";
7731      s2 = "btnez";
7732      s3 = "x,8";
7733      goto do_branch_i;
7734    case M_BLE_I:
7735      s = "slti";
7736      s2 = "btnez";
7737      s3 = "x,8";
7738      goto do_addone_branch_i;
7739    case M_BLEU_I:
7740      s = "sltiu";
7741      s2 = "btnez";
7742      s3 = "x,8";
7743      goto do_addone_branch_i;
7744    case M_BGE_I:
7745      s = "slti";
7746      s2 = "bteqz";
7747      s3 = "x,8";
7748      goto do_branch_i;
7749    case M_BGEU_I:
7750      s = "sltiu";
7751      s2 = "bteqz";
7752      s3 = "x,8";
7753      goto do_branch_i;
7754    case M_BGT_I:
7755      s = "slti";
7756      s2 = "bteqz";
7757      s3 = "x,8";
7758      goto do_addone_branch_i;
7759    case M_BGTU_I:
7760      s = "sltiu";
7761      s2 = "bteqz";
7762      s3 = "x,8";
7763
7764    do_addone_branch_i:
7765      if (imm_expr.X_op != O_constant)
7766	as_bad (_("Unsupported large constant"));
7767      ++imm_expr.X_add_number;
7768
7769    do_branch_i:
7770      macro_build (&imm_expr, s, s3, xreg);
7771      macro_build (&offset_expr, s2, "p");
7772      break;
7773
7774    case M_ABS:
7775      expr1.X_add_number = 0;
7776      macro_build (&expr1, "slti", "x,8", yreg);
7777      if (xreg != yreg)
7778	move_register (xreg, yreg);
7779      expr1.X_add_number = 2;
7780      macro_build (&expr1, "bteqz", "p");
7781      macro_build (NULL, "neg", "x,w", xreg, xreg);
7782    }
7783}
7784
7785/* For consistency checking, verify that all bits are specified either
7786   by the match/mask part of the instruction definition, or by the
7787   operand list.  */
7788static int
7789validate_mips_insn (const struct mips_opcode *opc)
7790{
7791  const char *p = opc->args;
7792  char c;
7793  unsigned long used_bits = opc->mask;
7794
7795  if ((used_bits & opc->match) != opc->match)
7796    {
7797      as_bad (_("internal: bad mips opcode (mask error): %s %s"),
7798	      opc->name, opc->args);
7799      return 0;
7800    }
7801#define USE_BITS(mask,shift)	(used_bits |= ((mask) << (shift)))
7802  while (*p)
7803    switch (c = *p++)
7804      {
7805      case ',': break;
7806      case '(': break;
7807      case ')': break;
7808      case '+':
7809    	switch (c = *p++)
7810	  {
7811	  case 'A': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7812	  case 'B': USE_BITS (OP_MASK_INSMSB,	OP_SH_INSMSB);	break;
7813	  case 'C': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
7814	  case 'D': USE_BITS (OP_MASK_RD,	OP_SH_RD);
7815		    USE_BITS (OP_MASK_SEL,	OP_SH_SEL);	break;
7816	  case 'E': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7817	  case 'F': USE_BITS (OP_MASK_INSMSB,	OP_SH_INSMSB);	break;
7818	  case 'G': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
7819	  case 'H': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
7820	  case 'I': break;
7821	  case 't': USE_BITS (OP_MASK_RT,	OP_SH_RT);	break;
7822	  case 'T': USE_BITS (OP_MASK_RT,	OP_SH_RT);
7823		    USE_BITS (OP_MASK_SEL,	OP_SH_SEL);	break;
7824	  default:
7825	    as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
7826		    c, opc->name, opc->args);
7827	    return 0;
7828	  }
7829	break;
7830      case '<': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7831      case '>':	USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7832      case 'A': break;
7833      case 'B': USE_BITS (OP_MASK_CODE20,       OP_SH_CODE20);  break;
7834      case 'C':	USE_BITS (OP_MASK_COPZ,		OP_SH_COPZ);	break;
7835      case 'D':	USE_BITS (OP_MASK_FD,		OP_SH_FD);	break;
7836      case 'E':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
7837      case 'F': break;
7838      case 'G':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
7839      case 'H': USE_BITS (OP_MASK_SEL,		OP_SH_SEL);	break;
7840      case 'I': break;
7841      case 'J': USE_BITS (OP_MASK_CODE19,       OP_SH_CODE19);  break;
7842      case 'K':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
7843      case 'L': break;
7844      case 'M':	USE_BITS (OP_MASK_CCC,		OP_SH_CCC);	break;
7845      case 'N':	USE_BITS (OP_MASK_BCC,		OP_SH_BCC);	break;
7846      case 'O':	USE_BITS (OP_MASK_ALN,		OP_SH_ALN);	break;
7847      case 'Q':	USE_BITS (OP_MASK_VSEL,		OP_SH_VSEL);
7848		USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
7849      case 'R':	USE_BITS (OP_MASK_FR,		OP_SH_FR);	break;
7850      case 'S':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
7851      case 'T':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
7852      case 'V':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
7853      case 'W':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
7854      case 'X':	USE_BITS (OP_MASK_FD,		OP_SH_FD);	break;
7855      case 'Y':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
7856      case 'Z':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
7857      case 'a':	USE_BITS (OP_MASK_TARGET,	OP_SH_TARGET);	break;
7858      case 'b':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
7859      case 'c':	USE_BITS (OP_MASK_CODE,		OP_SH_CODE);	break;
7860      case 'd':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
7861      case 'f': break;
7862      case 'h':	USE_BITS (OP_MASK_PREFX,	OP_SH_PREFX);	break;
7863      case 'i':	USE_BITS (OP_MASK_IMMEDIATE,	OP_SH_IMMEDIATE); break;
7864      case 'j':	USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
7865      case 'k':	USE_BITS (OP_MASK_CACHE,	OP_SH_CACHE);	break;
7866      case 'l': break;
7867      case 'o': USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
7868      case 'p':	USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
7869      case 'q':	USE_BITS (OP_MASK_CODE2,	OP_SH_CODE2);	break;
7870      case 'r': USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
7871      case 's':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
7872      case 't':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
7873      case 'u':	USE_BITS (OP_MASK_IMMEDIATE,	OP_SH_IMMEDIATE); break;
7874      case 'v':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
7875      case 'w':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
7876      case 'x': break;
7877      case 'z': break;
7878      case 'P': USE_BITS (OP_MASK_PERFREG,	OP_SH_PERFREG);	break;
7879      case 'U': USE_BITS (OP_MASK_RD,           OP_SH_RD);
7880	        USE_BITS (OP_MASK_RT,           OP_SH_RT);	break;
7881      case 'e': USE_BITS (OP_MASK_VECBYTE,	OP_SH_VECBYTE);	break;
7882      case '%': USE_BITS (OP_MASK_VECALIGN,	OP_SH_VECALIGN); break;
7883      case '[': break;
7884      case ']': break;
7885      case '3': USE_BITS (OP_MASK_SA3,  	OP_SH_SA3);	break;
7886      case '4': USE_BITS (OP_MASK_SA4,  	OP_SH_SA4);	break;
7887      case '5': USE_BITS (OP_MASK_IMM8, 	OP_SH_IMM8);	break;
7888      case '6': USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
7889      case '7': USE_BITS (OP_MASK_DSPACC,	OP_SH_DSPACC);	break;
7890      case '8': USE_BITS (OP_MASK_WRDSP,	OP_SH_WRDSP);	break;
7891      case '9': USE_BITS (OP_MASK_DSPACC_S,	OP_SH_DSPACC_S);break;
7892      case '0': USE_BITS (OP_MASK_DSPSFT,	OP_SH_DSPSFT);	break;
7893      case '\'': USE_BITS (OP_MASK_RDDSP,	OP_SH_RDDSP);	break;
7894      case ':': USE_BITS (OP_MASK_DSPSFT_7,	OP_SH_DSPSFT_7);break;
7895      case '@': USE_BITS (OP_MASK_IMM10,	OP_SH_IMM10);	break;
7896      case '!': USE_BITS (OP_MASK_MT_U,		OP_SH_MT_U);	break;
7897      case '$': USE_BITS (OP_MASK_MT_H,		OP_SH_MT_H);	break;
7898      case '*': USE_BITS (OP_MASK_MTACC_T,	OP_SH_MTACC_T);	break;
7899      case '&': USE_BITS (OP_MASK_MTACC_D,	OP_SH_MTACC_D);	break;
7900      case 'g': USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
7901      default:
7902	as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
7903		c, opc->name, opc->args);
7904	return 0;
7905      }
7906#undef USE_BITS
7907  if (used_bits != 0xffffffff)
7908    {
7909      as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
7910	      ~used_bits & 0xffffffff, opc->name, opc->args);
7911      return 0;
7912    }
7913  return 1;
7914}
7915
7916/* This routine assembles an instruction into its binary format.  As a
7917   side effect, it sets one of the global variables imm_reloc or
7918   offset_reloc to the type of relocation to do if one of the operands
7919   is an address expression.  */
7920
7921static void
7922mips_ip (char *str, struct mips_cl_insn *ip)
7923{
7924  char *s;
7925  const char *args;
7926  char c = 0;
7927  struct mips_opcode *insn;
7928  char *argsStart;
7929  unsigned int regno;
7930  unsigned int lastregno = 0;
7931  unsigned int lastpos = 0;
7932  unsigned int limlo, limhi;
7933  char *s_reset;
7934  char save_c = 0;
7935  offsetT min_range, max_range;
7936
7937  insn_error = NULL;
7938
7939  /* If the instruction contains a '.', we first try to match an instruction
7940     including the '.'.  Then we try again without the '.'.  */
7941  insn = NULL;
7942  for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
7943    continue;
7944
7945  /* If we stopped on whitespace, then replace the whitespace with null for
7946     the call to hash_find.  Save the character we replaced just in case we
7947     have to re-parse the instruction.  */
7948  if (ISSPACE (*s))
7949    {
7950      save_c = *s;
7951      *s++ = '\0';
7952    }
7953
7954  insn = (struct mips_opcode *) hash_find (op_hash, str);
7955
7956  /* If we didn't find the instruction in the opcode table, try again, but
7957     this time with just the instruction up to, but not including the
7958     first '.'.  */
7959  if (insn == NULL)
7960    {
7961      /* Restore the character we overwrite above (if any).  */
7962      if (save_c)
7963	*(--s) = save_c;
7964
7965      /* Scan up to the first '.' or whitespace.  */
7966      for (s = str;
7967	   *s != '\0' && *s != '.' && !ISSPACE (*s);
7968	   ++s)
7969	continue;
7970
7971      /* If we did not find a '.', then we can quit now.  */
7972      if (*s != '.')
7973	{
7974	  insn_error = "unrecognized opcode";
7975	  return;
7976	}
7977
7978      /* Lookup the instruction in the hash table.  */
7979      *s++ = '\0';
7980      if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
7981	{
7982	  insn_error = "unrecognized opcode";
7983	  return;
7984	}
7985    }
7986
7987  argsStart = s;
7988  for (;;)
7989    {
7990      bfd_boolean ok;
7991
7992      assert (strcmp (insn->name, str) == 0);
7993
7994      if (OPCODE_IS_MEMBER (insn,
7995			    (mips_opts.isa
7996			     | (file_ase_mips16 ? INSN_MIPS16 : 0)
7997	      		     | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
7998	      		     | (mips_opts.ase_dsp ? INSN_DSP : 0)
7999	      		     | (mips_opts.ase_mt ? INSN_MT : 0)
8000			     | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8001			    mips_opts.arch))
8002	ok = TRUE;
8003      else
8004	ok = FALSE;
8005
8006      if (insn->pinfo != INSN_MACRO)
8007	{
8008	  if (mips_opts.arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8009	    ok = FALSE;
8010	}
8011
8012      if (! ok)
8013	{
8014	  if (insn + 1 < &mips_opcodes[NUMOPCODES]
8015	      && strcmp (insn->name, insn[1].name) == 0)
8016	    {
8017	      ++insn;
8018	      continue;
8019	    }
8020	  else
8021	    {
8022	      if (!insn_error)
8023		{
8024		  static char buf[100];
8025		  sprintf (buf,
8026			   _("opcode not supported on this processor: %s (%s)"),
8027			   mips_cpu_info_from_arch (mips_opts.arch)->name,
8028			   mips_cpu_info_from_isa (mips_opts.isa)->name);
8029		  insn_error = buf;
8030		}
8031	      if (save_c)
8032		*(--s) = save_c;
8033	      return;
8034	    }
8035	}
8036
8037      create_insn (ip, insn);
8038      insn_error = NULL;
8039      for (args = insn->args;; ++args)
8040	{
8041	  int is_mdmx;
8042
8043	  s += strspn (s, " \t");
8044	  is_mdmx = 0;
8045	  switch (*args)
8046	    {
8047	    case '\0':		/* end of args */
8048	      if (*s == '\0')
8049		return;
8050	      break;
8051
8052	    case '3': /* dsp 3-bit unsigned immediate in bit 21 */
8053	      my_getExpression (&imm_expr, s);
8054	      check_absolute_expr (ip, &imm_expr);
8055	      if (imm_expr.X_add_number & ~OP_MASK_SA3)
8056		{
8057		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8058			   OP_MASK_SA3, (unsigned long) imm_expr.X_add_number);
8059		  imm_expr.X_add_number &= OP_MASK_SA3;
8060		}
8061	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SA3;
8062	      imm_expr.X_op = O_absent;
8063	      s = expr_end;
8064	      continue;
8065
8066	    case '4': /* dsp 4-bit unsigned immediate in bit 21 */
8067	      my_getExpression (&imm_expr, s);
8068	      check_absolute_expr (ip, &imm_expr);
8069	      if (imm_expr.X_add_number & ~OP_MASK_SA4)
8070		{
8071		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8072			   OP_MASK_SA4, (unsigned long) imm_expr.X_add_number);
8073		  imm_expr.X_add_number &= OP_MASK_SA4;
8074		}
8075	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SA4;
8076	      imm_expr.X_op = O_absent;
8077	      s = expr_end;
8078	      continue;
8079
8080	    case '5': /* dsp 8-bit unsigned immediate in bit 16 */
8081	      my_getExpression (&imm_expr, s);
8082	      check_absolute_expr (ip, &imm_expr);
8083	      if (imm_expr.X_add_number & ~OP_MASK_IMM8)
8084		{
8085		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8086			   OP_MASK_IMM8, (unsigned long) imm_expr.X_add_number);
8087		  imm_expr.X_add_number &= OP_MASK_IMM8;
8088		}
8089	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_IMM8;
8090	      imm_expr.X_op = O_absent;
8091	      s = expr_end;
8092	      continue;
8093
8094	    case '6': /* dsp 5-bit unsigned immediate in bit 21 */
8095	      my_getExpression (&imm_expr, s);
8096	      check_absolute_expr (ip, &imm_expr);
8097	      if (imm_expr.X_add_number & ~OP_MASK_RS)
8098		{
8099		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8100			   OP_MASK_RS, (unsigned long) imm_expr.X_add_number);
8101		  imm_expr.X_add_number &= OP_MASK_RS;
8102		}
8103	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_RS;
8104	      imm_expr.X_op = O_absent;
8105	      s = expr_end;
8106	      continue;
8107
8108	    case '7': /* four dsp accumulators in bits 11,12 */
8109	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8110		  s[3] >= '0' && s[3] <= '3')
8111		{
8112		  regno = s[3] - '0';
8113		  s += 4;
8114		  ip->insn_opcode |= regno << OP_SH_DSPACC;
8115		  continue;
8116		}
8117	      else
8118		as_bad (_("Invalid dsp acc register"));
8119	      break;
8120
8121	    case '8': /* dsp 6-bit unsigned immediate in bit 11 */
8122	      my_getExpression (&imm_expr, s);
8123	      check_absolute_expr (ip, &imm_expr);
8124	      if (imm_expr.X_add_number & ~OP_MASK_WRDSP)
8125		{
8126		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8127			   OP_MASK_WRDSP,
8128			   (unsigned long) imm_expr.X_add_number);
8129		  imm_expr.X_add_number &= OP_MASK_WRDSP;
8130		}
8131	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_WRDSP;
8132	      imm_expr.X_op = O_absent;
8133	      s = expr_end;
8134	      continue;
8135
8136	    case '9': /* four dsp accumulators in bits 21,22 */
8137	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8138		  s[3] >= '0' && s[3] <= '3')
8139		{
8140		  regno = s[3] - '0';
8141		  s += 4;
8142		  ip->insn_opcode |= regno << OP_SH_DSPACC_S;
8143		  continue;
8144		}
8145	      else
8146		as_bad (_("Invalid dsp acc register"));
8147	      break;
8148
8149	    case '0': /* dsp 6-bit signed immediate in bit 20 */
8150	      my_getExpression (&imm_expr, s);
8151	      check_absolute_expr (ip, &imm_expr);
8152	      min_range = -((OP_MASK_DSPSFT + 1) >> 1);
8153	      max_range = ((OP_MASK_DSPSFT + 1) >> 1) - 1;
8154	      if (imm_expr.X_add_number < min_range ||
8155		  imm_expr.X_add_number > max_range)
8156		{
8157		  as_warn (_("DSP immediate not in range %ld..%ld (%ld)"),
8158			   (long) min_range, (long) max_range,
8159			   (long) imm_expr.X_add_number);
8160		}
8161	      imm_expr.X_add_number &= OP_MASK_DSPSFT;
8162	      ip->insn_opcode |= ((unsigned long) imm_expr.X_add_number
8163				  << OP_SH_DSPSFT);
8164	      imm_expr.X_op = O_absent;
8165	      s = expr_end;
8166	      continue;
8167
8168	    case '\'': /* dsp 6-bit unsigned immediate in bit 16 */
8169	      my_getExpression (&imm_expr, s);
8170	      check_absolute_expr (ip, &imm_expr);
8171	      if (imm_expr.X_add_number & ~OP_MASK_RDDSP)
8172		{
8173		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8174			   OP_MASK_RDDSP,
8175			   (unsigned long) imm_expr.X_add_number);
8176		  imm_expr.X_add_number &= OP_MASK_RDDSP;
8177		}
8178	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_RDDSP;
8179	      imm_expr.X_op = O_absent;
8180	      s = expr_end;
8181	      continue;
8182
8183	    case ':': /* dsp 7-bit signed immediate in bit 19 */
8184	      my_getExpression (&imm_expr, s);
8185	      check_absolute_expr (ip, &imm_expr);
8186	      min_range = -((OP_MASK_DSPSFT_7 + 1) >> 1);
8187	      max_range = ((OP_MASK_DSPSFT_7 + 1) >> 1) - 1;
8188	      if (imm_expr.X_add_number < min_range ||
8189		  imm_expr.X_add_number > max_range)
8190		{
8191		  as_warn (_("DSP immediate not in range %ld..%ld (%ld)"),
8192			   (long) min_range, (long) max_range,
8193			   (long) imm_expr.X_add_number);
8194		}
8195	      imm_expr.X_add_number &= OP_MASK_DSPSFT_7;
8196	      ip->insn_opcode |= ((unsigned long) imm_expr.X_add_number
8197				  << OP_SH_DSPSFT_7);
8198	      imm_expr.X_op = O_absent;
8199	      s = expr_end;
8200	      continue;
8201
8202	    case '@': /* dsp 10-bit signed immediate in bit 16 */
8203	      my_getExpression (&imm_expr, s);
8204	      check_absolute_expr (ip, &imm_expr);
8205	      min_range = -((OP_MASK_IMM10 + 1) >> 1);
8206	      max_range = ((OP_MASK_IMM10 + 1) >> 1) - 1;
8207	      if (imm_expr.X_add_number < min_range ||
8208		  imm_expr.X_add_number > max_range)
8209		{
8210		  as_warn (_("DSP immediate not in range %ld..%ld (%ld)"),
8211			   (long) min_range, (long) max_range,
8212			   (long) imm_expr.X_add_number);
8213		}
8214	      imm_expr.X_add_number &= OP_MASK_IMM10;
8215	      ip->insn_opcode |= ((unsigned long) imm_expr.X_add_number
8216				  << OP_SH_IMM10);
8217	      imm_expr.X_op = O_absent;
8218	      s = expr_end;
8219	      continue;
8220
8221            case '!': /* mt 1-bit unsigned immediate in bit 5 */
8222	      my_getExpression (&imm_expr, s);
8223	      check_absolute_expr (ip, &imm_expr);
8224	      if (imm_expr.X_add_number & ~OP_MASK_MT_U)
8225		{
8226		  as_warn (_("MT immediate not in range 0..%d (%lu)"),
8227			   OP_MASK_MT_U, (unsigned long) imm_expr.X_add_number);
8228		  imm_expr.X_add_number &= OP_MASK_MT_U;
8229		}
8230	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_MT_U;
8231	      imm_expr.X_op = O_absent;
8232	      s = expr_end;
8233	      continue;
8234
8235            case '$': /* mt 1-bit unsigned immediate in bit 4 */
8236	      my_getExpression (&imm_expr, s);
8237	      check_absolute_expr (ip, &imm_expr);
8238	      if (imm_expr.X_add_number & ~OP_MASK_MT_H)
8239		{
8240		  as_warn (_("MT immediate not in range 0..%d (%lu)"),
8241			   OP_MASK_MT_H, (unsigned long) imm_expr.X_add_number);
8242		  imm_expr.X_add_number &= OP_MASK_MT_H;
8243		}
8244	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_MT_H;
8245	      imm_expr.X_op = O_absent;
8246	      s = expr_end;
8247	      continue;
8248
8249	    case '*': /* four dsp accumulators in bits 18,19 */
8250	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8251		  s[3] >= '0' && s[3] <= '3')
8252		{
8253		  regno = s[3] - '0';
8254		  s += 4;
8255		  ip->insn_opcode |= regno << OP_SH_MTACC_T;
8256		  continue;
8257		}
8258	      else
8259		as_bad (_("Invalid dsp/smartmips acc register"));
8260	      break;
8261
8262	    case '&': /* four dsp accumulators in bits 13,14 */
8263	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8264		  s[3] >= '0' && s[3] <= '3')
8265		{
8266		  regno = s[3] - '0';
8267		  s += 4;
8268		  ip->insn_opcode |= regno << OP_SH_MTACC_D;
8269		  continue;
8270		}
8271	      else
8272		as_bad (_("Invalid dsp/smartmips acc register"));
8273	      break;
8274
8275	    case ',':
8276	      if (*s++ == *args)
8277		continue;
8278	      s--;
8279	      switch (*++args)
8280		{
8281		case 'r':
8282		case 'v':
8283		  INSERT_OPERAND (RS, *ip, lastregno);
8284		  continue;
8285
8286		case 'w':
8287		  INSERT_OPERAND (RT, *ip, lastregno);
8288		  continue;
8289
8290		case 'W':
8291		  INSERT_OPERAND (FT, *ip, lastregno);
8292		  continue;
8293
8294		case 'V':
8295		  INSERT_OPERAND (FS, *ip, lastregno);
8296		  continue;
8297		}
8298	      break;
8299
8300	    case '(':
8301	      /* Handle optional base register.
8302		 Either the base register is omitted or
8303		 we must have a left paren.  */
8304	      /* This is dependent on the next operand specifier
8305		 is a base register specification.  */
8306	      assert (args[1] == 'b' || args[1] == '5'
8307		      || args[1] == '-' || args[1] == '4');
8308	      if (*s == '\0')
8309		return;
8310
8311	    case ')':		/* these must match exactly */
8312	    case '[':
8313	    case ']':
8314	      if (*s++ == *args)
8315		continue;
8316	      break;
8317
8318	    case '+':		/* Opcode extension character.  */
8319	      switch (*++args)
8320		{
8321		case 'A':		/* ins/ext position, becomes LSB.  */
8322		  limlo = 0;
8323		  limhi = 31;
8324		  goto do_lsb;
8325		case 'E':
8326		  limlo = 32;
8327		  limhi = 63;
8328		  goto do_lsb;
8329do_lsb:
8330		  my_getExpression (&imm_expr, s);
8331		  check_absolute_expr (ip, &imm_expr);
8332		  if ((unsigned long) imm_expr.X_add_number < limlo
8333		      || (unsigned long) imm_expr.X_add_number > limhi)
8334		    {
8335		      as_bad (_("Improper position (%lu)"),
8336			      (unsigned long) imm_expr.X_add_number);
8337		      imm_expr.X_add_number = limlo;
8338		    }
8339		  lastpos = imm_expr.X_add_number;
8340		  INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number);
8341		  imm_expr.X_op = O_absent;
8342		  s = expr_end;
8343		  continue;
8344
8345		case 'B':		/* ins size, becomes MSB.  */
8346		  limlo = 1;
8347		  limhi = 32;
8348		  goto do_msb;
8349		case 'F':
8350		  limlo = 33;
8351		  limhi = 64;
8352		  goto do_msb;
8353do_msb:
8354		  my_getExpression (&imm_expr, s);
8355		  check_absolute_expr (ip, &imm_expr);
8356		  /* Check for negative input so that small negative numbers
8357		     will not succeed incorrectly.  The checks against
8358		     (pos+size) transitively check "size" itself,
8359		     assuming that "pos" is reasonable.  */
8360		  if ((long) imm_expr.X_add_number < 0
8361		      || ((unsigned long) imm_expr.X_add_number
8362			  + lastpos) < limlo
8363		      || ((unsigned long) imm_expr.X_add_number
8364			  + lastpos) > limhi)
8365		    {
8366		      as_bad (_("Improper insert size (%lu, position %lu)"),
8367			      (unsigned long) imm_expr.X_add_number,
8368			      (unsigned long) lastpos);
8369		      imm_expr.X_add_number = limlo - lastpos;
8370		    }
8371		  INSERT_OPERAND (INSMSB, *ip,
8372				 lastpos + imm_expr.X_add_number - 1);
8373		  imm_expr.X_op = O_absent;
8374		  s = expr_end;
8375		  continue;
8376
8377		case 'C':		/* ext size, becomes MSBD.  */
8378		  limlo = 1;
8379		  limhi = 32;
8380		  goto do_msbd;
8381		case 'G':
8382		  limlo = 33;
8383		  limhi = 64;
8384		  goto do_msbd;
8385		case 'H':
8386		  limlo = 33;
8387		  limhi = 64;
8388		  goto do_msbd;
8389do_msbd:
8390		  my_getExpression (&imm_expr, s);
8391		  check_absolute_expr (ip, &imm_expr);
8392		  /* Check for negative input so that small negative numbers
8393		     will not succeed incorrectly.  The checks against
8394		     (pos+size) transitively check "size" itself,
8395		     assuming that "pos" is reasonable.  */
8396		  if ((long) imm_expr.X_add_number < 0
8397		      || ((unsigned long) imm_expr.X_add_number
8398			  + lastpos) < limlo
8399		      || ((unsigned long) imm_expr.X_add_number
8400			  + lastpos) > limhi)
8401		    {
8402		      as_bad (_("Improper extract size (%lu, position %lu)"),
8403			      (unsigned long) imm_expr.X_add_number,
8404			      (unsigned long) lastpos);
8405		      imm_expr.X_add_number = limlo - lastpos;
8406		    }
8407		  INSERT_OPERAND (EXTMSBD, *ip, imm_expr.X_add_number - 1);
8408		  imm_expr.X_op = O_absent;
8409		  s = expr_end;
8410		  continue;
8411
8412		case 'D':
8413		  /* +D is for disassembly only; never match.  */
8414		  break;
8415
8416		case 'I':
8417		  /* "+I" is like "I", except that imm2_expr is used.  */
8418		  my_getExpression (&imm2_expr, s);
8419		  if (imm2_expr.X_op != O_big
8420		      && imm2_expr.X_op != O_constant)
8421		  insn_error = _("absolute expression required");
8422		  if (HAVE_32BIT_GPRS)
8423		    normalize_constant_expr (&imm2_expr);
8424		  s = expr_end;
8425		  continue;
8426
8427		case 'T': /* Coprocessor register */
8428		  /* +T is for disassembly only; never match.  */
8429		  break;
8430
8431		case 't': /* Coprocessor register number */
8432		  if (s[0] == '$' && ISDIGIT (s[1]))
8433		    {
8434		      ++s;
8435		      regno = 0;
8436		      do
8437		        {
8438			  regno *= 10;
8439			  regno += *s - '0';
8440			  ++s;
8441			}
8442		      while (ISDIGIT (*s));
8443		      if (regno > 31)
8444			as_bad (_("Invalid register number (%d)"), regno);
8445		      else
8446			{
8447			  ip->insn_opcode |= regno << OP_SH_RT;
8448			  continue;
8449			}
8450		    }
8451		  else
8452		    as_bad (_("Invalid coprocessor 0 register number"));
8453		  break;
8454
8455		default:
8456		  as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8457		    *args, insn->name, insn->args);
8458		  /* Further processing is fruitless.  */
8459		  return;
8460		}
8461	      break;
8462
8463	    case '<':		/* must be at least one digit */
8464	      /*
8465	       * According to the manual, if the shift amount is greater
8466	       * than 31 or less than 0, then the shift amount should be
8467	       * mod 32.  In reality the mips assembler issues an error.
8468	       * We issue a warning and mask out all but the low 5 bits.
8469	       */
8470	      my_getExpression (&imm_expr, s);
8471	      check_absolute_expr (ip, &imm_expr);
8472	      if ((unsigned long) imm_expr.X_add_number > 31)
8473		as_warn (_("Improper shift amount (%lu)"),
8474			 (unsigned long) imm_expr.X_add_number);
8475	      INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number);
8476	      imm_expr.X_op = O_absent;
8477	      s = expr_end;
8478	      continue;
8479
8480	    case '>':		/* shift amount minus 32 */
8481	      my_getExpression (&imm_expr, s);
8482	      check_absolute_expr (ip, &imm_expr);
8483	      if ((unsigned long) imm_expr.X_add_number < 32
8484		  || (unsigned long) imm_expr.X_add_number > 63)
8485		break;
8486	      INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number - 32);
8487	      imm_expr.X_op = O_absent;
8488	      s = expr_end;
8489	      continue;
8490
8491	    case 'k':		/* cache code */
8492	    case 'h':		/* prefx code */
8493	      my_getExpression (&imm_expr, s);
8494	      check_absolute_expr (ip, &imm_expr);
8495	      if ((unsigned long) imm_expr.X_add_number > 31)
8496		as_warn (_("Invalid value for `%s' (%lu)"),
8497			 ip->insn_mo->name,
8498			 (unsigned long) imm_expr.X_add_number);
8499	      if (*args == 'k')
8500		INSERT_OPERAND (CACHE, *ip, imm_expr.X_add_number);
8501	      else
8502		INSERT_OPERAND (PREFX, *ip, imm_expr.X_add_number);
8503	      imm_expr.X_op = O_absent;
8504	      s = expr_end;
8505	      continue;
8506
8507	    case 'c':		/* break code */
8508	      my_getExpression (&imm_expr, s);
8509	      check_absolute_expr (ip, &imm_expr);
8510	      if ((unsigned long) imm_expr.X_add_number > 1023)
8511		as_warn (_("Illegal break code (%lu)"),
8512			 (unsigned long) imm_expr.X_add_number);
8513	      INSERT_OPERAND (CODE, *ip, imm_expr.X_add_number);
8514	      imm_expr.X_op = O_absent;
8515	      s = expr_end;
8516	      continue;
8517
8518	    case 'q':		/* lower break code */
8519	      my_getExpression (&imm_expr, s);
8520	      check_absolute_expr (ip, &imm_expr);
8521	      if ((unsigned long) imm_expr.X_add_number > 1023)
8522		as_warn (_("Illegal lower break code (%lu)"),
8523			 (unsigned long) imm_expr.X_add_number);
8524	      INSERT_OPERAND (CODE2, *ip, imm_expr.X_add_number);
8525	      imm_expr.X_op = O_absent;
8526	      s = expr_end;
8527	      continue;
8528
8529	    case 'B':           /* 20-bit syscall/break code.  */
8530	      my_getExpression (&imm_expr, s);
8531	      check_absolute_expr (ip, &imm_expr);
8532	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8533		as_warn (_("Illegal 20-bit code (%lu)"),
8534			 (unsigned long) imm_expr.X_add_number);
8535	      INSERT_OPERAND (CODE20, *ip, imm_expr.X_add_number);
8536	      imm_expr.X_op = O_absent;
8537	      s = expr_end;
8538	      continue;
8539
8540	    case 'C':           /* Coprocessor code */
8541	      my_getExpression (&imm_expr, s);
8542	      check_absolute_expr (ip, &imm_expr);
8543	      if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8544		{
8545		  as_warn (_("Coproccesor code > 25 bits (%lu)"),
8546			   (unsigned long) imm_expr.X_add_number);
8547		  imm_expr.X_add_number &= ((1 << 25) - 1);
8548		}
8549	      ip->insn_opcode |= imm_expr.X_add_number;
8550	      imm_expr.X_op = O_absent;
8551	      s = expr_end;
8552	      continue;
8553
8554	    case 'J':           /* 19-bit wait code.  */
8555	      my_getExpression (&imm_expr, s);
8556	      check_absolute_expr (ip, &imm_expr);
8557	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8558		as_warn (_("Illegal 19-bit code (%lu)"),
8559			 (unsigned long) imm_expr.X_add_number);
8560	      INSERT_OPERAND (CODE19, *ip, imm_expr.X_add_number);
8561	      imm_expr.X_op = O_absent;
8562	      s = expr_end;
8563	      continue;
8564
8565	    case 'P':		/* Performance register */
8566	      my_getExpression (&imm_expr, s);
8567	      check_absolute_expr (ip, &imm_expr);
8568	      if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8569		as_warn (_("Invalid performance register (%lu)"),
8570			 (unsigned long) imm_expr.X_add_number);
8571	      INSERT_OPERAND (PERFREG, *ip, imm_expr.X_add_number);
8572	      imm_expr.X_op = O_absent;
8573	      s = expr_end;
8574	      continue;
8575
8576	    case 'b':		/* base register */
8577	    case 'd':		/* destination register */
8578	    case 's':		/* source register */
8579	    case 't':		/* target register */
8580	    case 'r':		/* both target and source */
8581	    case 'v':		/* both dest and source */
8582	    case 'w':		/* both dest and target */
8583	    case 'E':		/* coprocessor target register */
8584	    case 'G':		/* coprocessor destination register */
8585	    case 'K':		/* 'rdhwr' destination register */
8586	    case 'x':		/* ignore register name */
8587	    case 'z':		/* must be zero register */
8588	    case 'U':           /* destination register (clo/clz).  */
8589	    case 'g':		/* coprocessor destination register */
8590	      s_reset = s;
8591	      if (s[0] == '$')
8592		{
8593		  if (ISDIGIT (s[1]))
8594		    {
8595		      ++s;
8596		      regno = 0;
8597		      do
8598			{
8599			  regno *= 10;
8600			  regno += *s - '0';
8601			  ++s;
8602			}
8603		      while (ISDIGIT (*s));
8604		      if (regno > 31)
8605			as_bad (_("Invalid register number (%d)"), regno);
8606		    }
8607		  else if (*args == 'E' || *args == 'G' || *args == 'K')
8608		    goto notreg;
8609		  else
8610		    {
8611		      if (s[1] == 'r' && s[2] == 'a')
8612			{
8613			  s += 3;
8614			  regno = RA;
8615			}
8616		      else if (s[1] == 'f' && s[2] == 'p')
8617			{
8618			  s += 3;
8619			  regno = FP;
8620			}
8621		      else if (s[1] == 's' && s[2] == 'p')
8622			{
8623			  s += 3;
8624			  regno = SP;
8625			}
8626		      else if (s[1] == 'g' && s[2] == 'p')
8627			{
8628			  s += 3;
8629			  regno = GP;
8630			}
8631		      else if (s[1] == 'a' && s[2] == 't')
8632			{
8633			  s += 3;
8634			  regno = AT;
8635			}
8636		      else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8637			{
8638			  s += 4;
8639			  regno = KT0;
8640			}
8641		      else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8642			{
8643			  s += 4;
8644			  regno = KT1;
8645			}
8646		      else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8647			{
8648			  s += 5;
8649			  regno = ZERO;
8650			}
8651		      else if (itbl_have_entries)
8652			{
8653			  char *p, *n;
8654			  unsigned long r;
8655
8656			  p = s + 1; 	/* advance past '$' */
8657			  n = itbl_get_field (&p);  /* n is name */
8658
8659			  /* See if this is a register defined in an
8660			     itbl entry.  */
8661			  if (itbl_get_reg_val (n, &r))
8662			    {
8663			      /* Get_field advances to the start of
8664				 the next field, so we need to back
8665				 rack to the end of the last field.  */
8666			      if (p)
8667				s = p - 1;
8668			      else
8669				s = strchr (s, '\0');
8670			      regno = r;
8671			    }
8672			  else
8673			    goto notreg;
8674			}
8675		      else
8676			goto notreg;
8677		    }
8678		  if (regno == AT
8679		      && ! mips_opts.noat
8680		      && *args != 'E'
8681		      && *args != 'G'
8682		      && *args != 'K')
8683		    as_warn (_("Used $at without \".set noat\""));
8684		  c = *args;
8685		  if (*s == ' ')
8686		    ++s;
8687		  if (args[1] != *s)
8688		    {
8689		      if (c == 'r' || c == 'v' || c == 'w')
8690			{
8691			  regno = lastregno;
8692			  s = s_reset;
8693			  ++args;
8694			}
8695		    }
8696		  /* 'z' only matches $0.  */
8697		  if (c == 'z' && regno != 0)
8698		    break;
8699
8700	/* Now that we have assembled one operand, we use the args string
8701	 * to figure out where it goes in the instruction.  */
8702		  switch (c)
8703		    {
8704		    case 'r':
8705		    case 's':
8706		    case 'v':
8707		    case 'b':
8708		      INSERT_OPERAND (RS, *ip, regno);
8709		      break;
8710		    case 'd':
8711		    case 'G':
8712		    case 'K':
8713		    case 'g':
8714		      INSERT_OPERAND (RD, *ip, regno);
8715		      break;
8716		    case 'U':
8717		      INSERT_OPERAND (RD, *ip, regno);
8718		      INSERT_OPERAND (RT, *ip, regno);
8719		      break;
8720		    case 'w':
8721		    case 't':
8722		    case 'E':
8723		      INSERT_OPERAND (RT, *ip, regno);
8724		      break;
8725		    case 'x':
8726		      /* This case exists because on the r3000 trunc
8727			 expands into a macro which requires a gp
8728			 register.  On the r6000 or r4000 it is
8729			 assembled into a single instruction which
8730			 ignores the register.  Thus the insn version
8731			 is MIPS_ISA2 and uses 'x', and the macro
8732			 version is MIPS_ISA1 and uses 't'.  */
8733		      break;
8734		    case 'z':
8735		      /* This case is for the div instruction, which
8736			 acts differently if the destination argument
8737			 is $0.  This only matches $0, and is checked
8738			 outside the switch.  */
8739		      break;
8740		    case 'D':
8741		      /* Itbl operand; not yet implemented. FIXME ?? */
8742		      break;
8743		      /* What about all other operands like 'i', which
8744			 can be specified in the opcode table? */
8745		    }
8746		  lastregno = regno;
8747		  continue;
8748		}
8749	    notreg:
8750	      switch (*args++)
8751		{
8752		case 'r':
8753		case 'v':
8754		  INSERT_OPERAND (RS, *ip, lastregno);
8755		  continue;
8756		case 'w':
8757		  INSERT_OPERAND (RT, *ip, lastregno);
8758		  continue;
8759		}
8760	      break;
8761
8762	    case 'O':		/* MDMX alignment immediate constant.  */
8763	      my_getExpression (&imm_expr, s);
8764	      check_absolute_expr (ip, &imm_expr);
8765	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
8766		as_warn ("Improper align amount (%ld), using low bits",
8767			 (long) imm_expr.X_add_number);
8768	      INSERT_OPERAND (ALN, *ip, imm_expr.X_add_number);
8769	      imm_expr.X_op = O_absent;
8770	      s = expr_end;
8771	      continue;
8772
8773	    case 'Q':		/* MDMX vector, element sel, or const.  */
8774	      if (s[0] != '$')
8775		{
8776		  /* MDMX Immediate.  */
8777		  my_getExpression (&imm_expr, s);
8778		  check_absolute_expr (ip, &imm_expr);
8779		  if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
8780		    as_warn (_("Invalid MDMX Immediate (%ld)"),
8781			     (long) imm_expr.X_add_number);
8782		  INSERT_OPERAND (FT, *ip, imm_expr.X_add_number);
8783		  if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8784		    ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
8785		  else
8786		    ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
8787		  imm_expr.X_op = O_absent;
8788		  s = expr_end;
8789		  continue;
8790		}
8791	      /* Not MDMX Immediate.  Fall through.  */
8792	    case 'X':           /* MDMX destination register.  */
8793	    case 'Y':           /* MDMX source register.  */
8794	    case 'Z':           /* MDMX target register.  */
8795	      is_mdmx = 1;
8796	    case 'D':		/* floating point destination register */
8797	    case 'S':		/* floating point source register */
8798	    case 'T':		/* floating point target register */
8799	    case 'R':		/* floating point source register */
8800	    case 'V':
8801	    case 'W':
8802	      s_reset = s;
8803	      /* Accept $fN for FP and MDMX register numbers, and in
8804                 addition accept $vN for MDMX register numbers.  */
8805	      if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
8806		  || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
8807		      && ISDIGIT (s[2])))
8808		{
8809		  s += 2;
8810		  regno = 0;
8811		  do
8812		    {
8813		      regno *= 10;
8814		      regno += *s - '0';
8815		      ++s;
8816		    }
8817		  while (ISDIGIT (*s));
8818
8819		  if (regno > 31)
8820		    as_bad (_("Invalid float register number (%d)"), regno);
8821
8822		  if ((regno & 1) != 0
8823		      && HAVE_32BIT_FPRS
8824		      && ! (strcmp (str, "mtc1") == 0
8825			    || strcmp (str, "mfc1") == 0
8826			    || strcmp (str, "lwc1") == 0
8827			    || strcmp (str, "swc1") == 0
8828			    || strcmp (str, "l.s") == 0
8829			    || strcmp (str, "s.s") == 0
8830			    || strcmp (str, "mftc1") == 0
8831			    || strcmp (str, "mfthc1") == 0
8832			    || strcmp (str, "cftc1") == 0
8833			    || strcmp (str, "mttc1") == 0
8834			    || strcmp (str, "mtthc1") == 0
8835			    || strcmp (str, "cttc1") == 0))
8836		    as_warn (_("Float register should be even, was %d"),
8837			     regno);
8838
8839		  c = *args;
8840		  if (*s == ' ')
8841		    ++s;
8842		  if (args[1] != *s)
8843		    {
8844		      if (c == 'V' || c == 'W')
8845			{
8846			  regno = lastregno;
8847			  s = s_reset;
8848			  ++args;
8849			}
8850		    }
8851		  switch (c)
8852		    {
8853		    case 'D':
8854		    case 'X':
8855		      INSERT_OPERAND (FD, *ip, regno);
8856		      break;
8857		    case 'V':
8858		    case 'S':
8859		    case 'Y':
8860		      INSERT_OPERAND (FS, *ip, regno);
8861		      break;
8862		    case 'Q':
8863		      /* This is like 'Z', but also needs to fix the MDMX
8864			 vector/scalar select bits.  Note that the
8865			 scalar immediate case is handled above.  */
8866		      if (*s == '[')
8867			{
8868			  int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
8869			  int max_el = (is_qh ? 3 : 7);
8870			  s++;
8871			  my_getExpression(&imm_expr, s);
8872			  check_absolute_expr (ip, &imm_expr);
8873			  s = expr_end;
8874			  if (imm_expr.X_add_number > max_el)
8875			    as_bad(_("Bad element selector %ld"),
8876				   (long) imm_expr.X_add_number);
8877			  imm_expr.X_add_number &= max_el;
8878			  ip->insn_opcode |= (imm_expr.X_add_number
8879					      << (OP_SH_VSEL +
8880						  (is_qh ? 2 : 1)));
8881			  imm_expr.X_op = O_absent;
8882			  if (*s != ']')
8883			    as_warn(_("Expecting ']' found '%s'"), s);
8884			  else
8885			    s++;
8886			}
8887		      else
8888                        {
8889                          if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8890                            ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
8891						<< OP_SH_VSEL);
8892			  else
8893			    ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
8894						OP_SH_VSEL);
8895			}
8896                      /* Fall through */
8897		    case 'W':
8898		    case 'T':
8899		    case 'Z':
8900		      INSERT_OPERAND (FT, *ip, regno);
8901		      break;
8902		    case 'R':
8903		      INSERT_OPERAND (FR, *ip, regno);
8904		      break;
8905		    }
8906		  lastregno = regno;
8907		  continue;
8908		}
8909
8910	      switch (*args++)
8911		{
8912		case 'V':
8913		  INSERT_OPERAND (FS, *ip, lastregno);
8914		  continue;
8915		case 'W':
8916		  INSERT_OPERAND (FT, *ip, lastregno);
8917		  continue;
8918		}
8919	      break;
8920
8921	    case 'I':
8922	      my_getExpression (&imm_expr, s);
8923	      if (imm_expr.X_op != O_big
8924		  && imm_expr.X_op != O_constant)
8925		insn_error = _("absolute expression required");
8926	      if (HAVE_32BIT_GPRS)
8927		normalize_constant_expr (&imm_expr);
8928	      s = expr_end;
8929	      continue;
8930
8931	    case 'A':
8932	      my_getExpression (&offset_expr, s);
8933	      normalize_address_expr (&offset_expr);
8934	      *imm_reloc = BFD_RELOC_32;
8935	      s = expr_end;
8936	      continue;
8937
8938	    case 'F':
8939	    case 'L':
8940	    case 'f':
8941	    case 'l':
8942	      {
8943		int f64;
8944		int using_gprs;
8945		char *save_in;
8946		char *err;
8947		unsigned char temp[8];
8948		int len;
8949		unsigned int length;
8950		segT seg;
8951		subsegT subseg;
8952		char *p;
8953
8954		/* These only appear as the last operand in an
8955		   instruction, and every instruction that accepts
8956		   them in any variant accepts them in all variants.
8957		   This means we don't have to worry about backing out
8958		   any changes if the instruction does not match.
8959
8960		   The difference between them is the size of the
8961		   floating point constant and where it goes.  For 'F'
8962		   and 'L' the constant is 64 bits; for 'f' and 'l' it
8963		   is 32 bits.  Where the constant is placed is based
8964		   on how the MIPS assembler does things:
8965		    F -- .rdata
8966		    L -- .lit8
8967		    f -- immediate value
8968		    l -- .lit4
8969
8970		    The .lit4 and .lit8 sections are only used if
8971		    permitted by the -G argument.
8972
8973		    The code below needs to know whether the target register
8974		    is 32 or 64 bits wide.  It relies on the fact 'f' and
8975		    'F' are used with GPR-based instructions and 'l' and
8976		    'L' are used with FPR-based instructions.  */
8977
8978		f64 = *args == 'F' || *args == 'L';
8979		using_gprs = *args == 'F' || *args == 'f';
8980
8981		save_in = input_line_pointer;
8982		input_line_pointer = s;
8983		err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
8984		length = len;
8985		s = input_line_pointer;
8986		input_line_pointer = save_in;
8987		if (err != NULL && *err != '\0')
8988		  {
8989		    as_bad (_("Bad floating point constant: %s"), err);
8990		    memset (temp, '\0', sizeof temp);
8991		    length = f64 ? 8 : 4;
8992		  }
8993
8994		assert (length == (unsigned) (f64 ? 8 : 4));
8995
8996		if (*args == 'f'
8997		    || (*args == 'l'
8998			&& (g_switch_value < 4
8999			    || (temp[0] == 0 && temp[1] == 0)
9000			    || (temp[2] == 0 && temp[3] == 0))))
9001		  {
9002		    imm_expr.X_op = O_constant;
9003		    if (! target_big_endian)
9004		      imm_expr.X_add_number = bfd_getl32 (temp);
9005		    else
9006		      imm_expr.X_add_number = bfd_getb32 (temp);
9007		  }
9008		else if (length > 4
9009			 && ! mips_disable_float_construction
9010			 /* Constants can only be constructed in GPRs and
9011			    copied to FPRs if the GPRs are at least as wide
9012			    as the FPRs.  Force the constant into memory if
9013			    we are using 64-bit FPRs but the GPRs are only
9014			    32 bits wide.  */
9015			 && (using_gprs
9016			     || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
9017			 && ((temp[0] == 0 && temp[1] == 0)
9018			     || (temp[2] == 0 && temp[3] == 0))
9019			 && ((temp[4] == 0 && temp[5] == 0)
9020			     || (temp[6] == 0 && temp[7] == 0)))
9021		  {
9022		    /* The value is simple enough to load with a couple of
9023                       instructions.  If using 32-bit registers, set
9024                       imm_expr to the high order 32 bits and offset_expr to
9025                       the low order 32 bits.  Otherwise, set imm_expr to
9026                       the entire 64 bit constant.  */
9027		    if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
9028		      {
9029			imm_expr.X_op = O_constant;
9030			offset_expr.X_op = O_constant;
9031			if (! target_big_endian)
9032			  {
9033			    imm_expr.X_add_number = bfd_getl32 (temp + 4);
9034			    offset_expr.X_add_number = bfd_getl32 (temp);
9035			  }
9036			else
9037			  {
9038			    imm_expr.X_add_number = bfd_getb32 (temp);
9039			    offset_expr.X_add_number = bfd_getb32 (temp + 4);
9040			  }
9041			if (offset_expr.X_add_number == 0)
9042			  offset_expr.X_op = O_absent;
9043		      }
9044		    else if (sizeof (imm_expr.X_add_number) > 4)
9045		      {
9046			imm_expr.X_op = O_constant;
9047			if (! target_big_endian)
9048			  imm_expr.X_add_number = bfd_getl64 (temp);
9049			else
9050			  imm_expr.X_add_number = bfd_getb64 (temp);
9051		      }
9052		    else
9053		      {
9054			imm_expr.X_op = O_big;
9055			imm_expr.X_add_number = 4;
9056			if (! target_big_endian)
9057			  {
9058			    generic_bignum[0] = bfd_getl16 (temp);
9059			    generic_bignum[1] = bfd_getl16 (temp + 2);
9060			    generic_bignum[2] = bfd_getl16 (temp + 4);
9061			    generic_bignum[3] = bfd_getl16 (temp + 6);
9062			  }
9063			else
9064			  {
9065			    generic_bignum[0] = bfd_getb16 (temp + 6);
9066			    generic_bignum[1] = bfd_getb16 (temp + 4);
9067			    generic_bignum[2] = bfd_getb16 (temp + 2);
9068			    generic_bignum[3] = bfd_getb16 (temp);
9069			  }
9070		      }
9071		  }
9072		else
9073		  {
9074		    const char *newname;
9075		    segT new_seg;
9076
9077		    /* Switch to the right section.  */
9078		    seg = now_seg;
9079		    subseg = now_subseg;
9080		    switch (*args)
9081		      {
9082		      default: /* unused default case avoids warnings.  */
9083		      case 'L':
9084			newname = RDATA_SECTION_NAME;
9085			if (g_switch_value >= 8)
9086			  newname = ".lit8";
9087			break;
9088		      case 'F':
9089			newname = RDATA_SECTION_NAME;
9090			break;
9091		      case 'l':
9092			assert (g_switch_value >= 4);
9093			newname = ".lit4";
9094			break;
9095		      }
9096		    new_seg = subseg_new (newname, (subsegT) 0);
9097		    if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9098		      bfd_set_section_flags (stdoutput, new_seg,
9099					     (SEC_ALLOC
9100					      | SEC_LOAD
9101					      | SEC_READONLY
9102					      | SEC_DATA));
9103		    frag_align (*args == 'l' ? 2 : 3, 0, 0);
9104		    if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9105			&& strcmp (TARGET_OS, "elf") != 0)
9106		      record_alignment (new_seg, 4);
9107		    else
9108		      record_alignment (new_seg, *args == 'l' ? 2 : 3);
9109		    if (seg == now_seg)
9110		      as_bad (_("Can't use floating point insn in this section"));
9111
9112		    /* Set the argument to the current address in the
9113		       section.  */
9114		    offset_expr.X_op = O_symbol;
9115		    offset_expr.X_add_symbol =
9116		      symbol_new ("L0\001", now_seg,
9117				  (valueT) frag_now_fix (), frag_now);
9118		    offset_expr.X_add_number = 0;
9119
9120		    /* Put the floating point number into the section.  */
9121		    p = frag_more ((int) length);
9122		    memcpy (p, temp, length);
9123
9124		    /* Switch back to the original section.  */
9125		    subseg_set (seg, subseg);
9126		  }
9127	      }
9128	      continue;
9129
9130	    case 'i':		/* 16 bit unsigned immediate */
9131	    case 'j':		/* 16 bit signed immediate */
9132	      *imm_reloc = BFD_RELOC_LO16;
9133	      if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9134		{
9135		  int more;
9136		  offsetT minval, maxval;
9137
9138		  more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9139			  && strcmp (insn->name, insn[1].name) == 0);
9140
9141		  /* If the expression was written as an unsigned number,
9142		     only treat it as signed if there are no more
9143		     alternatives.  */
9144		  if (more
9145		      && *args == 'j'
9146		      && sizeof (imm_expr.X_add_number) <= 4
9147		      && imm_expr.X_op == O_constant
9148		      && imm_expr.X_add_number < 0
9149		      && imm_expr.X_unsigned
9150		      && HAVE_64BIT_GPRS)
9151		    break;
9152
9153		  /* For compatibility with older assemblers, we accept
9154		     0x8000-0xffff as signed 16-bit numbers when only
9155		     signed numbers are allowed.  */
9156		  if (*args == 'i')
9157		    minval = 0, maxval = 0xffff;
9158		  else if (more)
9159		    minval = -0x8000, maxval = 0x7fff;
9160		  else
9161		    minval = -0x8000, maxval = 0xffff;
9162
9163		  if (imm_expr.X_op != O_constant
9164		      || imm_expr.X_add_number < minval
9165		      || imm_expr.X_add_number > maxval)
9166		    {
9167		      if (more)
9168			break;
9169		      if (imm_expr.X_op == O_constant
9170			  || imm_expr.X_op == O_big)
9171			as_bad (_("expression out of range"));
9172		    }
9173		}
9174	      s = expr_end;
9175	      continue;
9176
9177	    case 'o':		/* 16 bit offset */
9178	      /* Check whether there is only a single bracketed expression
9179		 left.  If so, it must be the base register and the
9180		 constant must be zero.  */
9181	      if (*s == '(' && strchr (s + 1, '(') == 0)
9182		{
9183		  offset_expr.X_op = O_constant;
9184		  offset_expr.X_add_number = 0;
9185		  continue;
9186		}
9187
9188	      /* If this value won't fit into a 16 bit offset, then go
9189		 find a macro that will generate the 32 bit offset
9190		 code pattern.  */
9191	      if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9192		  && (offset_expr.X_op != O_constant
9193		      || offset_expr.X_add_number >= 0x8000
9194		      || offset_expr.X_add_number < -0x8000))
9195		break;
9196
9197	      s = expr_end;
9198	      continue;
9199
9200	    case 'p':		/* pc relative offset */
9201	      *offset_reloc = BFD_RELOC_16_PCREL_S2;
9202	      my_getExpression (&offset_expr, s);
9203	      s = expr_end;
9204	      continue;
9205
9206	    case 'u':		/* upper 16 bits */
9207	      if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9208		  && imm_expr.X_op == O_constant
9209		  && (imm_expr.X_add_number < 0
9210		      || imm_expr.X_add_number >= 0x10000))
9211		as_bad (_("lui expression not in range 0..65535"));
9212	      s = expr_end;
9213	      continue;
9214
9215	    case 'a':		/* 26 bit address */
9216	      my_getExpression (&offset_expr, s);
9217	      s = expr_end;
9218	      *offset_reloc = BFD_RELOC_MIPS_JMP;
9219	      continue;
9220
9221	    case 'N':		/* 3 bit branch condition code */
9222	    case 'M':		/* 3 bit compare condition code */
9223	      if (strncmp (s, "$fcc", 4) != 0)
9224		break;
9225	      s += 4;
9226	      regno = 0;
9227	      do
9228		{
9229		  regno *= 10;
9230		  regno += *s - '0';
9231		  ++s;
9232		}
9233	      while (ISDIGIT (*s));
9234	      if (regno > 7)
9235		as_bad (_("Invalid condition code register $fcc%d"), regno);
9236	      if ((strcmp(str + strlen(str) - 3, ".ps") == 0
9237		   || strcmp(str + strlen(str) - 5, "any2f") == 0
9238		   || strcmp(str + strlen(str) - 5, "any2t") == 0)
9239		  && (regno & 1) != 0)
9240		as_warn(_("Condition code register should be even for %s, was %d"),
9241			str, regno);
9242	      if ((strcmp(str + strlen(str) - 5, "any4f") == 0
9243		   || strcmp(str + strlen(str) - 5, "any4t") == 0)
9244		  && (regno & 3) != 0)
9245		as_warn(_("Condition code register should be 0 or 4 for %s, was %d"),
9246			str, regno);
9247	      if (*args == 'N')
9248		INSERT_OPERAND (BCC, *ip, regno);
9249	      else
9250		INSERT_OPERAND (CCC, *ip, regno);
9251	      continue;
9252
9253	    case 'H':
9254	      if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9255		s += 2;
9256	      if (ISDIGIT (*s))
9257		{
9258		  c = 0;
9259		  do
9260		    {
9261		      c *= 10;
9262		      c += *s - '0';
9263		      ++s;
9264		    }
9265		  while (ISDIGIT (*s));
9266		}
9267	      else
9268		c = 8; /* Invalid sel value.  */
9269
9270	      if (c > 7)
9271		as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9272	      ip->insn_opcode |= c;
9273	      continue;
9274
9275	    case 'e':
9276	      /* Must be at least one digit.  */
9277	      my_getExpression (&imm_expr, s);
9278	      check_absolute_expr (ip, &imm_expr);
9279
9280	      if ((unsigned long) imm_expr.X_add_number
9281		  > (unsigned long) OP_MASK_VECBYTE)
9282		{
9283		  as_bad (_("bad byte vector index (%ld)"),
9284			   (long) imm_expr.X_add_number);
9285		  imm_expr.X_add_number = 0;
9286		}
9287
9288	      INSERT_OPERAND (VECBYTE, *ip, imm_expr.X_add_number);
9289	      imm_expr.X_op = O_absent;
9290	      s = expr_end;
9291	      continue;
9292
9293	    case '%':
9294	      my_getExpression (&imm_expr, s);
9295	      check_absolute_expr (ip, &imm_expr);
9296
9297	      if ((unsigned long) imm_expr.X_add_number
9298		  > (unsigned long) OP_MASK_VECALIGN)
9299		{
9300		  as_bad (_("bad byte vector index (%ld)"),
9301			   (long) imm_expr.X_add_number);
9302		  imm_expr.X_add_number = 0;
9303		}
9304
9305	      INSERT_OPERAND (VECALIGN, *ip, imm_expr.X_add_number);
9306	      imm_expr.X_op = O_absent;
9307	      s = expr_end;
9308	      continue;
9309
9310	    default:
9311	      as_bad (_("bad char = '%c'\n"), *args);
9312	      internalError ();
9313	    }
9314	  break;
9315	}
9316      /* Args don't match.  */
9317      if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9318	  !strcmp (insn->name, insn[1].name))
9319	{
9320	  ++insn;
9321	  s = argsStart;
9322	  insn_error = _("illegal operands");
9323	  continue;
9324	}
9325      if (save_c)
9326	*(--s) = save_c;
9327      insn_error = _("illegal operands");
9328      return;
9329    }
9330}
9331
9332#define SKIP_SPACE_TABS(S) { while (*(S) == ' ' || *(S) == '\t') ++(S); }
9333
9334/* This routine assembles an instruction into its binary format when
9335   assembling for the mips16.  As a side effect, it sets one of the
9336   global variables imm_reloc or offset_reloc to the type of
9337   relocation to do if one of the operands is an address expression.
9338   It also sets mips16_small and mips16_ext if the user explicitly
9339   requested a small or extended instruction.  */
9340
9341static void
9342mips16_ip (char *str, struct mips_cl_insn *ip)
9343{
9344  char *s;
9345  const char *args;
9346  struct mips_opcode *insn;
9347  char *argsstart;
9348  unsigned int regno;
9349  unsigned int lastregno = 0;
9350  char *s_reset;
9351  size_t i;
9352
9353  insn_error = NULL;
9354
9355  mips16_small = FALSE;
9356  mips16_ext = FALSE;
9357
9358  for (s = str; ISLOWER (*s); ++s)
9359    ;
9360  switch (*s)
9361    {
9362    case '\0':
9363      break;
9364
9365    case ' ':
9366      *s++ = '\0';
9367      break;
9368
9369    case '.':
9370      if (s[1] == 't' && s[2] == ' ')
9371	{
9372	  *s = '\0';
9373	  mips16_small = TRUE;
9374	  s += 3;
9375	  break;
9376	}
9377      else if (s[1] == 'e' && s[2] == ' ')
9378	{
9379	  *s = '\0';
9380	  mips16_ext = TRUE;
9381	  s += 3;
9382	  break;
9383	}
9384      /* Fall through.  */
9385    default:
9386      insn_error = _("unknown opcode");
9387      return;
9388    }
9389
9390  if (mips_opts.noautoextend && ! mips16_ext)
9391    mips16_small = TRUE;
9392
9393  if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9394    {
9395      insn_error = _("unrecognized opcode");
9396      return;
9397    }
9398
9399  argsstart = s;
9400  for (;;)
9401    {
9402      assert (strcmp (insn->name, str) == 0);
9403
9404      create_insn (ip, insn);
9405      imm_expr.X_op = O_absent;
9406      imm_reloc[0] = BFD_RELOC_UNUSED;
9407      imm_reloc[1] = BFD_RELOC_UNUSED;
9408      imm_reloc[2] = BFD_RELOC_UNUSED;
9409      imm2_expr.X_op = O_absent;
9410      offset_expr.X_op = O_absent;
9411      offset_reloc[0] = BFD_RELOC_UNUSED;
9412      offset_reloc[1] = BFD_RELOC_UNUSED;
9413      offset_reloc[2] = BFD_RELOC_UNUSED;
9414      for (args = insn->args; 1; ++args)
9415	{
9416	  int c;
9417
9418	  if (*s == ' ')
9419	    ++s;
9420
9421	  /* In this switch statement we call break if we did not find
9422             a match, continue if we did find a match, or return if we
9423             are done.  */
9424
9425	  c = *args;
9426	  switch (c)
9427	    {
9428	    case '\0':
9429	      if (*s == '\0')
9430		{
9431		  /* Stuff the immediate value in now, if we can.  */
9432		  if (imm_expr.X_op == O_constant
9433		      && *imm_reloc > BFD_RELOC_UNUSED
9434		      && insn->pinfo != INSN_MACRO)
9435		    {
9436		      valueT tmp;
9437
9438		      switch (*offset_reloc)
9439			{
9440			  case BFD_RELOC_MIPS16_HI16_S:
9441			    tmp = (imm_expr.X_add_number + 0x8000) >> 16;
9442			    break;
9443
9444			  case BFD_RELOC_MIPS16_HI16:
9445			    tmp = imm_expr.X_add_number >> 16;
9446			    break;
9447
9448			  case BFD_RELOC_MIPS16_LO16:
9449			    tmp = ((imm_expr.X_add_number + 0x8000) & 0xffff)
9450				  - 0x8000;
9451			    break;
9452
9453			  case BFD_RELOC_UNUSED:
9454			    tmp = imm_expr.X_add_number;
9455			    break;
9456
9457			  default:
9458			    internalError ();
9459			}
9460		      *offset_reloc = BFD_RELOC_UNUSED;
9461
9462		      mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9463				    tmp, TRUE, mips16_small,
9464				    mips16_ext, &ip->insn_opcode,
9465				    &ip->use_extend, &ip->extend);
9466		      imm_expr.X_op = O_absent;
9467		      *imm_reloc = BFD_RELOC_UNUSED;
9468		    }
9469
9470		  return;
9471		}
9472	      break;
9473
9474	    case ',':
9475	      if (*s++ == c)
9476		continue;
9477	      s--;
9478	      switch (*++args)
9479		{
9480		case 'v':
9481		  MIPS16_INSERT_OPERAND (RX, *ip, lastregno);
9482		  continue;
9483		case 'w':
9484		  MIPS16_INSERT_OPERAND (RY, *ip, lastregno);
9485		  continue;
9486		}
9487	      break;
9488
9489	    case '(':
9490	    case ')':
9491	      if (*s++ == c)
9492		continue;
9493	      break;
9494
9495	    case 'v':
9496	    case 'w':
9497	      if (s[0] != '$')
9498		{
9499		  if (c == 'v')
9500		    MIPS16_INSERT_OPERAND (RX, *ip, lastregno);
9501		  else
9502		    MIPS16_INSERT_OPERAND (RY, *ip, lastregno);
9503		  ++args;
9504		  continue;
9505		}
9506	      /* Fall through.  */
9507	    case 'x':
9508	    case 'y':
9509	    case 'z':
9510	    case 'Z':
9511	    case '0':
9512	    case 'S':
9513	    case 'R':
9514	    case 'X':
9515	    case 'Y':
9516	      if (s[0] != '$')
9517		break;
9518	      s_reset = s;
9519	      if (ISDIGIT (s[1]))
9520		{
9521		  ++s;
9522		  regno = 0;
9523		  do
9524		    {
9525		      regno *= 10;
9526		      regno += *s - '0';
9527		      ++s;
9528		    }
9529		  while (ISDIGIT (*s));
9530		  if (regno > 31)
9531		    {
9532		      as_bad (_("invalid register number (%d)"), regno);
9533		      regno = 2;
9534		    }
9535		}
9536	      else
9537		{
9538		  if (s[1] == 'r' && s[2] == 'a')
9539		    {
9540		      s += 3;
9541		      regno = RA;
9542		    }
9543		  else if (s[1] == 'f' && s[2] == 'p')
9544		    {
9545		      s += 3;
9546		      regno = FP;
9547		    }
9548		  else if (s[1] == 's' && s[2] == 'p')
9549		    {
9550		      s += 3;
9551		      regno = SP;
9552		    }
9553		  else if (s[1] == 'g' && s[2] == 'p')
9554		    {
9555		      s += 3;
9556		      regno = GP;
9557		    }
9558		  else if (s[1] == 'a' && s[2] == 't')
9559		    {
9560		      s += 3;
9561		      regno = AT;
9562		    }
9563		  else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9564		    {
9565		      s += 4;
9566		      regno = KT0;
9567		    }
9568		  else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9569		    {
9570		      s += 4;
9571		      regno = KT1;
9572		    }
9573		  else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9574		    {
9575		      s += 5;
9576		      regno = ZERO;
9577		    }
9578		  else
9579		    break;
9580		}
9581
9582	      if (*s == ' ')
9583		++s;
9584	      if (args[1] != *s)
9585		{
9586		  if (c == 'v' || c == 'w')
9587		    {
9588		      regno = mips16_to_32_reg_map[lastregno];
9589		      s = s_reset;
9590		      ++args;
9591		    }
9592		}
9593
9594	      switch (c)
9595		{
9596		case 'x':
9597		case 'y':
9598		case 'z':
9599		case 'v':
9600		case 'w':
9601		case 'Z':
9602		  regno = mips32_to_16_reg_map[regno];
9603		  break;
9604
9605		case '0':
9606		  if (regno != 0)
9607		    regno = ILLEGAL_REG;
9608		  break;
9609
9610		case 'S':
9611		  if (regno != SP)
9612		    regno = ILLEGAL_REG;
9613		  break;
9614
9615		case 'R':
9616		  if (regno != RA)
9617		    regno = ILLEGAL_REG;
9618		  break;
9619
9620		case 'X':
9621		case 'Y':
9622		  if (regno == AT && ! mips_opts.noat)
9623		    as_warn (_("used $at without \".set noat\""));
9624		  break;
9625
9626		default:
9627		  internalError ();
9628		}
9629
9630	      if (regno == ILLEGAL_REG)
9631		break;
9632
9633	      switch (c)
9634		{
9635		case 'x':
9636		case 'v':
9637		  MIPS16_INSERT_OPERAND (RX, *ip, regno);
9638		  break;
9639		case 'y':
9640		case 'w':
9641		  MIPS16_INSERT_OPERAND (RY, *ip, regno);
9642		  break;
9643		case 'z':
9644		  MIPS16_INSERT_OPERAND (RZ, *ip, regno);
9645		  break;
9646		case 'Z':
9647		  MIPS16_INSERT_OPERAND (MOVE32Z, *ip, regno);
9648		case '0':
9649		case 'S':
9650		case 'R':
9651		  break;
9652		case 'X':
9653		  MIPS16_INSERT_OPERAND (REGR32, *ip, regno);
9654		  break;
9655		case 'Y':
9656		  regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9657		  MIPS16_INSERT_OPERAND (REG32R, *ip, regno);
9658		  break;
9659		default:
9660		  internalError ();
9661		}
9662
9663	      lastregno = regno;
9664	      continue;
9665
9666	    case 'P':
9667	      if (strncmp (s, "$pc", 3) == 0)
9668		{
9669		  s += 3;
9670		  continue;
9671		}
9672	      break;
9673
9674	    case '5':
9675	    case 'H':
9676	    case 'W':
9677	    case 'D':
9678	    case 'j':
9679	    case 'V':
9680	    case 'C':
9681	    case 'U':
9682	    case 'k':
9683	    case 'K':
9684	      i = my_getSmallExpression (&imm_expr, imm_reloc, s);
9685	      if (i > 0)
9686		{
9687		  if (imm_expr.X_op != O_constant)
9688		    {
9689		      mips16_ext = TRUE;
9690		      ip->use_extend = TRUE;
9691		      ip->extend = 0;
9692		    }
9693		  else
9694		    {
9695		      /* We need to relax this instruction.  */
9696		      *offset_reloc = *imm_reloc;
9697		      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9698		    }
9699		  s = expr_end;
9700		  continue;
9701		}
9702	      *imm_reloc = BFD_RELOC_UNUSED;
9703	      /* Fall through.  */
9704	    case '<':
9705	    case '>':
9706	    case '[':
9707	    case ']':
9708	    case '4':
9709	    case '8':
9710	      my_getExpression (&imm_expr, s);
9711	      if (imm_expr.X_op == O_register)
9712		{
9713		  /* What we thought was an expression turned out to
9714                     be a register.  */
9715
9716		  if (s[0] == '(' && args[1] == '(')
9717		    {
9718		      /* It looks like the expression was omitted
9719			 before a register indirection, which means
9720			 that the expression is implicitly zero.  We
9721			 still set up imm_expr, so that we handle
9722			 explicit extensions correctly.  */
9723		      imm_expr.X_op = O_constant;
9724		      imm_expr.X_add_number = 0;
9725		      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9726		      continue;
9727		    }
9728
9729		  break;
9730		}
9731
9732	      /* We need to relax this instruction.  */
9733	      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9734	      s = expr_end;
9735	      continue;
9736
9737	    case 'p':
9738	    case 'q':
9739	    case 'A':
9740	    case 'B':
9741	    case 'E':
9742	      /* We use offset_reloc rather than imm_reloc for the PC
9743                 relative operands.  This lets macros with both
9744                 immediate and address operands work correctly.  */
9745	      my_getExpression (&offset_expr, s);
9746
9747	      if (offset_expr.X_op == O_register)
9748		break;
9749
9750	      /* We need to relax this instruction.  */
9751	      *offset_reloc = (int) BFD_RELOC_UNUSED + c;
9752	      s = expr_end;
9753	      continue;
9754
9755	    case '6':		/* break code */
9756	      my_getExpression (&imm_expr, s);
9757	      check_absolute_expr (ip, &imm_expr);
9758	      if ((unsigned long) imm_expr.X_add_number > 63)
9759		as_warn (_("Invalid value for `%s' (%lu)"),
9760			 ip->insn_mo->name,
9761			 (unsigned long) imm_expr.X_add_number);
9762	      MIPS16_INSERT_OPERAND (IMM6, *ip, imm_expr.X_add_number);
9763	      imm_expr.X_op = O_absent;
9764	      s = expr_end;
9765	      continue;
9766
9767	    case 'a':		/* 26 bit address */
9768	      my_getExpression (&offset_expr, s);
9769	      s = expr_end;
9770	      *offset_reloc = BFD_RELOC_MIPS16_JMP;
9771	      ip->insn_opcode <<= 16;
9772	      continue;
9773
9774	    case 'l':		/* register list for entry macro */
9775	    case 'L':		/* register list for exit macro */
9776	      {
9777		int mask;
9778
9779		if (c == 'l')
9780		  mask = 0;
9781		else
9782		  mask = 7 << 3;
9783		while (*s != '\0')
9784		  {
9785		    int freg, reg1, reg2;
9786
9787		    while (*s == ' ' || *s == ',')
9788		      ++s;
9789		    if (*s != '$')
9790		      {
9791			as_bad (_("can't parse register list"));
9792			break;
9793		      }
9794		    ++s;
9795		    if (*s != 'f')
9796		      freg = 0;
9797		    else
9798		      {
9799			freg = 1;
9800			++s;
9801		      }
9802		    reg1 = 0;
9803		    while (ISDIGIT (*s))
9804		      {
9805			reg1 *= 10;
9806			reg1 += *s - '0';
9807			++s;
9808		      }
9809		    if (*s == ' ')
9810		      ++s;
9811		    if (*s != '-')
9812		      reg2 = reg1;
9813		    else
9814		      {
9815			++s;
9816			if (*s != '$')
9817			  break;
9818			++s;
9819			if (freg)
9820			  {
9821			    if (*s == 'f')
9822			      ++s;
9823			    else
9824			      {
9825				as_bad (_("invalid register list"));
9826				break;
9827			      }
9828			  }
9829			reg2 = 0;
9830			while (ISDIGIT (*s))
9831			  {
9832			    reg2 *= 10;
9833			    reg2 += *s - '0';
9834			    ++s;
9835			  }
9836		      }
9837		    if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
9838		      {
9839			mask &= ~ (7 << 3);
9840			mask |= 5 << 3;
9841		      }
9842		    else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
9843		      {
9844			mask &= ~ (7 << 3);
9845			mask |= 6 << 3;
9846		      }
9847		    else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
9848		      mask |= (reg2 - 3) << 3;
9849		    else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
9850		      mask |= (reg2 - 15) << 1;
9851		    else if (reg1 == RA && reg2 == RA)
9852		      mask |= 1;
9853		    else
9854		      {
9855			as_bad (_("invalid register list"));
9856			break;
9857		      }
9858		  }
9859		/* The mask is filled in in the opcode table for the
9860                   benefit of the disassembler.  We remove it before
9861                   applying the actual mask.  */
9862		ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
9863		ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
9864	      }
9865	    continue;
9866
9867	    case 'm':		/* Register list for save insn.  */
9868	    case 'M':		/* Register list for restore insn.  */
9869	      {
9870		int opcode = 0;
9871		int framesz = 0, seen_framesz = 0;
9872		int args = 0, statics = 0, sregs = 0;
9873
9874		while (*s != '\0')
9875		  {
9876		    unsigned int reg1, reg2;
9877
9878		    SKIP_SPACE_TABS (s);
9879		    while (*s == ',')
9880		      ++s;
9881		    SKIP_SPACE_TABS (s);
9882
9883		    my_getExpression (&imm_expr, s);
9884		    if (imm_expr.X_op == O_constant)
9885		      {
9886			/* Handle the frame size.  */
9887			if (seen_framesz)
9888			  {
9889			    as_bad (_("more than one frame size in list"));
9890			    break;
9891			  }
9892			seen_framesz = 1;
9893			framesz = imm_expr.X_add_number;
9894			imm_expr.X_op = O_absent;
9895			s = expr_end;
9896			continue;
9897		      }
9898
9899		    if (*s != '$')
9900		      {
9901			as_bad (_("can't parse register list"));
9902			break;
9903		      }
9904		    ++s;
9905
9906		    reg1 = 0;
9907		    while (ISDIGIT (*s))
9908		      {
9909			reg1 *= 10;
9910			reg1 += *s - '0';
9911			++s;
9912		      }
9913		    SKIP_SPACE_TABS (s);
9914		    if (*s != '-')
9915		      reg2 = reg1;
9916		    else
9917		      {
9918			++s;
9919			if (*s != '$')
9920			  {
9921			    as_bad (_("can't parse register list"));
9922			    break;
9923			  }
9924			++s;
9925			reg2 = 0;
9926			while (ISDIGIT (*s))
9927			  {
9928			    reg2 *= 10;
9929			    reg2 += *s - '0';
9930			    ++s;
9931			  }
9932		      }
9933
9934		    while (reg1 <= reg2)
9935		      {
9936			if (reg1 >= 4 && reg1 <= 7)
9937			  {
9938			    if (c == 'm' && !seen_framesz)
9939				/* args $a0-$a3 */
9940				args |= 1 << (reg1 - 4);
9941			    else
9942				/* statics $a0-$a3 */
9943				statics |= 1 << (reg1 - 4);
9944			  }
9945			else if ((reg1 >= 16 && reg1 <= 23) || reg1 == 30)
9946			  {
9947			    /* $s0-$s8 */
9948			    sregs |= 1 << ((reg1 == 30) ? 8 : (reg1 - 16));
9949			  }
9950			else if (reg1 == 31)
9951			  {
9952			    /* Add $ra to insn.  */
9953			    opcode |= 0x40;
9954			  }
9955			else
9956			  {
9957			    as_bad (_("unexpected register in list"));
9958			    break;
9959			  }
9960			if (++reg1 == 24)
9961			  reg1 = 30;
9962		      }
9963		  }
9964
9965		/* Encode args/statics combination.  */
9966		if (args & statics)
9967		  as_bad (_("arg/static registers overlap"));
9968		else if (args == 0xf)
9969		  /* All $a0-$a3 are args.  */
9970		  opcode |= MIPS16_ALL_ARGS << 16;
9971		else if (statics == 0xf)
9972		  /* All $a0-$a3 are statics.  */
9973		  opcode |= MIPS16_ALL_STATICS << 16;
9974		else
9975		  {
9976		    int narg = 0, nstat = 0;
9977
9978		    /* Count arg registers.  */
9979		    while (args & 0x1)
9980		      {
9981			args >>= 1;
9982			narg++;
9983		      }
9984		    if (args != 0)
9985		      as_bad (_("invalid arg register list"));
9986
9987		    /* Count static registers.  */
9988		    while (statics & 0x8)
9989		      {
9990			statics = (statics << 1) & 0xf;
9991			nstat++;
9992		      }
9993		    if (statics != 0)
9994		      as_bad (_("invalid static register list"));
9995
9996		    /* Encode args/statics.  */
9997		    opcode |= ((narg << 2) | nstat) << 16;
9998		  }
9999
10000		/* Encode $s0/$s1.  */
10001		if (sregs & (1 << 0))		/* $s0 */
10002		  opcode |= 0x20;
10003		if (sregs & (1 << 1))		/* $s1 */
10004		  opcode |= 0x10;
10005		sregs >>= 2;
10006
10007		if (sregs != 0)
10008		  {
10009		    /* Count regs $s2-$s8.  */
10010		    int nsreg = 0;
10011		    while (sregs & 1)
10012		      {
10013			sregs >>= 1;
10014			nsreg++;
10015		      }
10016		    if (sregs != 0)
10017		      as_bad (_("invalid static register list"));
10018		    /* Encode $s2-$s8. */
10019		    opcode |= nsreg << 24;
10020		  }
10021
10022		/* Encode frame size.  */
10023		if (!seen_framesz)
10024		  as_bad (_("missing frame size"));
10025		else if ((framesz & 7) != 0 || framesz < 0
10026			 || framesz > 0xff * 8)
10027		  as_bad (_("invalid frame size"));
10028		else if (framesz != 128 || (opcode >> 16) != 0)
10029		  {
10030		    framesz /= 8;
10031		    opcode |= (((framesz & 0xf0) << 16)
10032			     | (framesz & 0x0f));
10033		  }
10034
10035		/* Finally build the instruction.  */
10036		if ((opcode >> 16) != 0 || framesz == 0)
10037		  {
10038		    ip->use_extend = TRUE;
10039		    ip->extend = opcode >> 16;
10040		  }
10041		ip->insn_opcode |= opcode & 0x7f;
10042	      }
10043	    continue;
10044
10045	    case 'e':		/* extend code */
10046	      my_getExpression (&imm_expr, s);
10047	      check_absolute_expr (ip, &imm_expr);
10048	      if ((unsigned long) imm_expr.X_add_number > 0x7ff)
10049		{
10050		  as_warn (_("Invalid value for `%s' (%lu)"),
10051			   ip->insn_mo->name,
10052			   (unsigned long) imm_expr.X_add_number);
10053		  imm_expr.X_add_number &= 0x7ff;
10054		}
10055	      ip->insn_opcode |= imm_expr.X_add_number;
10056	      imm_expr.X_op = O_absent;
10057	      s = expr_end;
10058	      continue;
10059
10060	    default:
10061	      internalError ();
10062	    }
10063	  break;
10064	}
10065
10066      /* Args don't match.  */
10067      if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
10068	  strcmp (insn->name, insn[1].name) == 0)
10069	{
10070	  ++insn;
10071	  s = argsstart;
10072	  continue;
10073	}
10074
10075      insn_error = _("illegal operands");
10076
10077      return;
10078    }
10079}
10080
10081/* This structure holds information we know about a mips16 immediate
10082   argument type.  */
10083
10084struct mips16_immed_operand
10085{
10086  /* The type code used in the argument string in the opcode table.  */
10087  int type;
10088  /* The number of bits in the short form of the opcode.  */
10089  int nbits;
10090  /* The number of bits in the extended form of the opcode.  */
10091  int extbits;
10092  /* The amount by which the short form is shifted when it is used;
10093     for example, the sw instruction has a shift count of 2.  */
10094  int shift;
10095  /* The amount by which the short form is shifted when it is stored
10096     into the instruction code.  */
10097  int op_shift;
10098  /* Non-zero if the short form is unsigned.  */
10099  int unsp;
10100  /* Non-zero if the extended form is unsigned.  */
10101  int extu;
10102  /* Non-zero if the value is PC relative.  */
10103  int pcrel;
10104};
10105
10106/* The mips16 immediate operand types.  */
10107
10108static const struct mips16_immed_operand mips16_immed_operands[] =
10109{
10110  { '<',  3,  5, 0, MIPS16OP_SH_RZ,   1, 1, 0 },
10111  { '>',  3,  5, 0, MIPS16OP_SH_RX,   1, 1, 0 },
10112  { '[',  3,  6, 0, MIPS16OP_SH_RZ,   1, 1, 0 },
10113  { ']',  3,  6, 0, MIPS16OP_SH_RX,   1, 1, 0 },
10114  { '4',  4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
10115  { '5',  5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
10116  { 'H',  5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
10117  { 'W',  5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
10118  { 'D',  5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
10119  { 'j',  5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
10120  { '8',  8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
10121  { 'V',  8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
10122  { 'C',  8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
10123  { 'U',  8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
10124  { 'k',  8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
10125  { 'K',  8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
10126  { 'p',  8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10127  { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10128  { 'A',  8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
10129  { 'B',  5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
10130  { 'E',  5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
10131};
10132
10133#define MIPS16_NUM_IMMED \
10134  (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
10135
10136/* Handle a mips16 instruction with an immediate value.  This or's the
10137   small immediate value into *INSN.  It sets *USE_EXTEND to indicate
10138   whether an extended value is needed; if one is needed, it sets
10139   *EXTEND to the value.  The argument type is TYPE.  The value is VAL.
10140   If SMALL is true, an unextended opcode was explicitly requested.
10141   If EXT is true, an extended opcode was explicitly requested.  If
10142   WARN is true, warn if EXT does not match reality.  */
10143
10144static void
10145mips16_immed (char *file, unsigned int line, int type, offsetT val,
10146	      bfd_boolean warn, bfd_boolean small, bfd_boolean ext,
10147	      unsigned long *insn, bfd_boolean *use_extend,
10148	      unsigned short *extend)
10149{
10150  register const struct mips16_immed_operand *op;
10151  int mintiny, maxtiny;
10152  bfd_boolean needext;
10153
10154  op = mips16_immed_operands;
10155  while (op->type != type)
10156    {
10157      ++op;
10158      assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
10159    }
10160
10161  if (op->unsp)
10162    {
10163      if (type == '<' || type == '>' || type == '[' || type == ']')
10164	{
10165	  mintiny = 1;
10166	  maxtiny = 1 << op->nbits;
10167	}
10168      else
10169	{
10170	  mintiny = 0;
10171	  maxtiny = (1 << op->nbits) - 1;
10172	}
10173    }
10174  else
10175    {
10176      mintiny = - (1 << (op->nbits - 1));
10177      maxtiny = (1 << (op->nbits - 1)) - 1;
10178    }
10179
10180  /* Branch offsets have an implicit 0 in the lowest bit.  */
10181  if (type == 'p' || type == 'q')
10182    val /= 2;
10183
10184  if ((val & ((1 << op->shift) - 1)) != 0
10185      || val < (mintiny << op->shift)
10186      || val > (maxtiny << op->shift))
10187    needext = TRUE;
10188  else
10189    needext = FALSE;
10190
10191  if (warn && ext && ! needext)
10192    as_warn_where (file, line,
10193		   _("extended operand requested but not required"));
10194  if (small && needext)
10195    as_bad_where (file, line, _("invalid unextended operand value"));
10196
10197  if (small || (! ext && ! needext))
10198    {
10199      int insnval;
10200
10201      *use_extend = FALSE;
10202      insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
10203      insnval <<= op->op_shift;
10204      *insn |= insnval;
10205    }
10206  else
10207    {
10208      long minext, maxext;
10209      int extval;
10210
10211      if (op->extu)
10212	{
10213	  minext = 0;
10214	  maxext = (1 << op->extbits) - 1;
10215	}
10216      else
10217	{
10218	  minext = - (1 << (op->extbits - 1));
10219	  maxext = (1 << (op->extbits - 1)) - 1;
10220	}
10221      if (val < minext || val > maxext)
10222	as_bad_where (file, line,
10223		      _("operand value out of range for instruction"));
10224
10225      *use_extend = TRUE;
10226      if (op->extbits == 16)
10227	{
10228	  extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
10229	  val &= 0x1f;
10230	}
10231      else if (op->extbits == 15)
10232	{
10233	  extval = ((val >> 11) & 0xf) | (val & 0x7f0);
10234	  val &= 0xf;
10235	}
10236      else
10237	{
10238	  extval = ((val & 0x1f) << 6) | (val & 0x20);
10239	  val = 0;
10240	}
10241
10242      *extend = (unsigned short) extval;
10243      *insn |= val;
10244    }
10245}
10246
10247struct percent_op_match
10248{
10249  const char *str;
10250  bfd_reloc_code_real_type reloc;
10251};
10252
10253static const struct percent_op_match mips_percent_op[] =
10254{
10255  {"%lo", BFD_RELOC_LO16},
10256#ifdef OBJ_ELF
10257  {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
10258  {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
10259  {"%call16", BFD_RELOC_MIPS_CALL16},
10260  {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
10261  {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
10262  {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
10263  {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
10264  {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
10265  {"%got", BFD_RELOC_MIPS_GOT16},
10266  {"%gp_rel", BFD_RELOC_GPREL16},
10267  {"%half", BFD_RELOC_16},
10268  {"%highest", BFD_RELOC_MIPS_HIGHEST},
10269  {"%higher", BFD_RELOC_MIPS_HIGHER},
10270  {"%neg", BFD_RELOC_MIPS_SUB},
10271  {"%tlsgd", BFD_RELOC_MIPS_TLS_GD},
10272  {"%tlsldm", BFD_RELOC_MIPS_TLS_LDM},
10273  {"%dtprel_hi", BFD_RELOC_MIPS_TLS_DTPREL_HI16},
10274  {"%dtprel_lo", BFD_RELOC_MIPS_TLS_DTPREL_LO16},
10275  {"%tprel_hi", BFD_RELOC_MIPS_TLS_TPREL_HI16},
10276  {"%tprel_lo", BFD_RELOC_MIPS_TLS_TPREL_LO16},
10277  {"%gottprel", BFD_RELOC_MIPS_TLS_GOTTPREL},
10278#endif
10279  {"%hi", BFD_RELOC_HI16_S}
10280};
10281
10282static const struct percent_op_match mips16_percent_op[] =
10283{
10284  {"%lo", BFD_RELOC_MIPS16_LO16},
10285  {"%gprel", BFD_RELOC_MIPS16_GPREL},
10286  {"%hi", BFD_RELOC_MIPS16_HI16_S}
10287};
10288
10289
10290/* Return true if *STR points to a relocation operator.  When returning true,
10291   move *STR over the operator and store its relocation code in *RELOC.
10292   Leave both *STR and *RELOC alone when returning false.  */
10293
10294static bfd_boolean
10295parse_relocation (char **str, bfd_reloc_code_real_type *reloc)
10296{
10297  const struct percent_op_match *percent_op;
10298  size_t limit, i;
10299
10300  if (mips_opts.mips16)
10301    {
10302      percent_op = mips16_percent_op;
10303      limit = ARRAY_SIZE (mips16_percent_op);
10304    }
10305  else
10306    {
10307      percent_op = mips_percent_op;
10308      limit = ARRAY_SIZE (mips_percent_op);
10309    }
10310
10311  for (i = 0; i < limit; i++)
10312    if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
10313      {
10314	int len = strlen (percent_op[i].str);
10315
10316	if (!ISSPACE ((*str)[len]) && (*str)[len] != '(')
10317	  continue;
10318
10319	*str += strlen (percent_op[i].str);
10320	*reloc = percent_op[i].reloc;
10321
10322	/* Check whether the output BFD supports this relocation.
10323	   If not, issue an error and fall back on something safe.  */
10324	if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
10325	  {
10326	    as_bad ("relocation %s isn't supported by the current ABI",
10327		    percent_op[i].str);
10328	    *reloc = BFD_RELOC_UNUSED;
10329	  }
10330	return TRUE;
10331      }
10332  return FALSE;
10333}
10334
10335
10336/* Parse string STR as a 16-bit relocatable operand.  Store the
10337   expression in *EP and the relocations in the array starting
10338   at RELOC.  Return the number of relocation operators used.
10339
10340   On exit, EXPR_END points to the first character after the expression.  */
10341
10342static size_t
10343my_getSmallExpression (expressionS *ep, bfd_reloc_code_real_type *reloc,
10344		       char *str)
10345{
10346  bfd_reloc_code_real_type reversed_reloc[3];
10347  size_t reloc_index, i;
10348  int crux_depth, str_depth;
10349  char *crux;
10350
10351  /* Search for the start of the main expression, recoding relocations
10352     in REVERSED_RELOC.  End the loop with CRUX pointing to the start
10353     of the main expression and with CRUX_DEPTH containing the number
10354     of open brackets at that point.  */
10355  reloc_index = -1;
10356  str_depth = 0;
10357  do
10358    {
10359      reloc_index++;
10360      crux = str;
10361      crux_depth = str_depth;
10362
10363      /* Skip over whitespace and brackets, keeping count of the number
10364	 of brackets.  */
10365      while (*str == ' ' || *str == '\t' || *str == '(')
10366	if (*str++ == '(')
10367	  str_depth++;
10368    }
10369  while (*str == '%'
10370	 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10371	 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10372
10373  my_getExpression (ep, crux);
10374  str = expr_end;
10375
10376  /* Match every open bracket.  */
10377  while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10378    if (*str++ == ')')
10379      crux_depth--;
10380
10381  if (crux_depth > 0)
10382    as_bad ("unclosed '('");
10383
10384  expr_end = str;
10385
10386  if (reloc_index != 0)
10387    {
10388      prev_reloc_op_frag = frag_now;
10389      for (i = 0; i < reloc_index; i++)
10390	reloc[i] = reversed_reloc[reloc_index - 1 - i];
10391    }
10392
10393  return reloc_index;
10394}
10395
10396static void
10397my_getExpression (expressionS *ep, char *str)
10398{
10399  char *save_in;
10400  valueT val;
10401
10402  save_in = input_line_pointer;
10403  input_line_pointer = str;
10404  expression (ep);
10405  expr_end = input_line_pointer;
10406  input_line_pointer = save_in;
10407
10408  /* If we are in mips16 mode, and this is an expression based on `.',
10409     then we bump the value of the symbol by 1 since that is how other
10410     text symbols are handled.  We don't bother to handle complex
10411     expressions, just `.' plus or minus a constant.  */
10412  if (mips_opts.mips16
10413      && ep->X_op == O_symbol
10414      && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10415      && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10416      && symbol_get_frag (ep->X_add_symbol) == frag_now
10417      && symbol_constant_p (ep->X_add_symbol)
10418      && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10419    S_SET_VALUE (ep->X_add_symbol, val + 1);
10420}
10421
10422/* Turn a string in input_line_pointer into a floating point constant
10423   of type TYPE, and store the appropriate bytes in *LITP.  The number
10424   of LITTLENUMS emitted is stored in *SIZEP.  An error message is
10425   returned, or NULL on OK.  */
10426
10427char *
10428md_atof (int type, char *litP, int *sizeP)
10429{
10430  int prec;
10431  LITTLENUM_TYPE words[4];
10432  char *t;
10433  int i;
10434
10435  switch (type)
10436    {
10437    case 'f':
10438      prec = 2;
10439      break;
10440
10441    case 'd':
10442      prec = 4;
10443      break;
10444
10445    default:
10446      *sizeP = 0;
10447      return _("bad call to md_atof");
10448    }
10449
10450  t = atof_ieee (input_line_pointer, type, words);
10451  if (t)
10452    input_line_pointer = t;
10453
10454  *sizeP = prec * 2;
10455
10456  if (! target_big_endian)
10457    {
10458      for (i = prec - 1; i >= 0; i--)
10459	{
10460	  md_number_to_chars (litP, words[i], 2);
10461	  litP += 2;
10462	}
10463    }
10464  else
10465    {
10466      for (i = 0; i < prec; i++)
10467	{
10468	  md_number_to_chars (litP, words[i], 2);
10469	  litP += 2;
10470	}
10471    }
10472
10473  return NULL;
10474}
10475
10476void
10477md_number_to_chars (char *buf, valueT val, int n)
10478{
10479  if (target_big_endian)
10480    number_to_chars_bigendian (buf, val, n);
10481  else
10482    number_to_chars_littleendian (buf, val, n);
10483}
10484
10485#ifdef OBJ_ELF
10486static int support_64bit_objects(void)
10487{
10488  const char **list, **l;
10489  int yes;
10490
10491  list = bfd_target_list ();
10492  for (l = list; *l != NULL; l++)
10493#ifdef TE_TMIPS
10494    /* This is traditional mips */
10495    if (strcmp (*l, "elf64-tradbigmips") == 0
10496	|| strcmp (*l, "elf64-tradlittlemips") == 0)
10497#else
10498    if (strcmp (*l, "elf64-bigmips") == 0
10499	|| strcmp (*l, "elf64-littlemips") == 0)
10500#endif
10501      break;
10502  yes = (*l != NULL);
10503  free (list);
10504  return yes;
10505}
10506#endif /* OBJ_ELF */
10507
10508const char *md_shortopts = "O::g::G:";
10509
10510struct option md_longopts[] =
10511{
10512  /* Options which specify architecture.  */
10513#define OPTION_ARCH_BASE    (OPTION_MD_BASE)
10514#define OPTION_MARCH (OPTION_ARCH_BASE + 0)
10515  {"march", required_argument, NULL, OPTION_MARCH},
10516#define OPTION_MTUNE (OPTION_ARCH_BASE + 1)
10517  {"mtune", required_argument, NULL, OPTION_MTUNE},
10518#define OPTION_MIPS1 (OPTION_ARCH_BASE + 2)
10519  {"mips0", no_argument, NULL, OPTION_MIPS1},
10520  {"mips1", no_argument, NULL, OPTION_MIPS1},
10521#define OPTION_MIPS2 (OPTION_ARCH_BASE + 3)
10522  {"mips2", no_argument, NULL, OPTION_MIPS2},
10523#define OPTION_MIPS3 (OPTION_ARCH_BASE + 4)
10524  {"mips3", no_argument, NULL, OPTION_MIPS3},
10525#define OPTION_MIPS4 (OPTION_ARCH_BASE + 5)
10526  {"mips4", no_argument, NULL, OPTION_MIPS4},
10527#define OPTION_MIPS5 (OPTION_ARCH_BASE + 6)
10528  {"mips5", no_argument, NULL, OPTION_MIPS5},
10529#define OPTION_MIPS32 (OPTION_ARCH_BASE + 7)
10530  {"mips32", no_argument, NULL, OPTION_MIPS32},
10531#define OPTION_MIPS64 (OPTION_ARCH_BASE + 8)
10532  {"mips64", no_argument, NULL, OPTION_MIPS64},
10533#define OPTION_MIPS32R2 (OPTION_ARCH_BASE + 9)
10534  {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10535#define OPTION_MIPS64R2 (OPTION_ARCH_BASE + 10)
10536  {"mips64r2", no_argument, NULL, OPTION_MIPS64R2},
10537
10538  /* Options which specify Application Specific Extensions (ASEs).  */
10539#define OPTION_ASE_BASE (OPTION_ARCH_BASE + 11)
10540#define OPTION_MIPS16 (OPTION_ASE_BASE + 0)
10541  {"mips16", no_argument, NULL, OPTION_MIPS16},
10542#define OPTION_NO_MIPS16 (OPTION_ASE_BASE + 1)
10543  {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10544#define OPTION_MIPS3D (OPTION_ASE_BASE + 2)
10545  {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10546#define OPTION_NO_MIPS3D (OPTION_ASE_BASE + 3)
10547  {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10548#define OPTION_MDMX (OPTION_ASE_BASE + 4)
10549  {"mdmx", no_argument, NULL, OPTION_MDMX},
10550#define OPTION_NO_MDMX (OPTION_ASE_BASE + 5)
10551  {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10552#define OPTION_DSP (OPTION_ASE_BASE + 6)
10553  {"mdsp", no_argument, NULL, OPTION_DSP},
10554#define OPTION_NO_DSP (OPTION_ASE_BASE + 7)
10555  {"mno-dsp", no_argument, NULL, OPTION_NO_DSP},
10556#define OPTION_MT (OPTION_ASE_BASE + 8)
10557  {"mmt", no_argument, NULL, OPTION_MT},
10558#define OPTION_NO_MT (OPTION_ASE_BASE + 9)
10559  {"mno-mt", no_argument, NULL, OPTION_NO_MT},
10560
10561  /* Old-style architecture options.  Don't add more of these.  */
10562#define OPTION_COMPAT_ARCH_BASE (OPTION_ASE_BASE + 10)
10563#define OPTION_M4650 (OPTION_COMPAT_ARCH_BASE + 0)
10564  {"m4650", no_argument, NULL, OPTION_M4650},
10565#define OPTION_NO_M4650 (OPTION_COMPAT_ARCH_BASE + 1)
10566  {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10567#define OPTION_M4010 (OPTION_COMPAT_ARCH_BASE + 2)
10568  {"m4010", no_argument, NULL, OPTION_M4010},
10569#define OPTION_NO_M4010 (OPTION_COMPAT_ARCH_BASE + 3)
10570  {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10571#define OPTION_M4100 (OPTION_COMPAT_ARCH_BASE + 4)
10572  {"m4100", no_argument, NULL, OPTION_M4100},
10573#define OPTION_NO_M4100 (OPTION_COMPAT_ARCH_BASE + 5)
10574  {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10575#define OPTION_M3900 (OPTION_COMPAT_ARCH_BASE + 6)
10576  {"m3900", no_argument, NULL, OPTION_M3900},
10577#define OPTION_NO_M3900 (OPTION_COMPAT_ARCH_BASE + 7)
10578  {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10579
10580  /* Options which enable bug fixes.  */
10581#define OPTION_FIX_BASE    (OPTION_COMPAT_ARCH_BASE + 8)
10582#define OPTION_M7000_HILO_FIX (OPTION_FIX_BASE + 0)
10583  {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10584#define OPTION_MNO_7000_HILO_FIX (OPTION_FIX_BASE + 1)
10585  {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10586  {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10587#define OPTION_FIX_VR4120 (OPTION_FIX_BASE + 2)
10588#define OPTION_NO_FIX_VR4120 (OPTION_FIX_BASE + 3)
10589  {"mfix-vr4120",    no_argument, NULL, OPTION_FIX_VR4120},
10590  {"mno-fix-vr4120", no_argument, NULL, OPTION_NO_FIX_VR4120},
10591#define OPTION_FIX_VR4130 (OPTION_FIX_BASE + 4)
10592#define OPTION_NO_FIX_VR4130 (OPTION_FIX_BASE + 5)
10593  {"mfix-vr4130",    no_argument, NULL, OPTION_FIX_VR4130},
10594  {"mno-fix-vr4130", no_argument, NULL, OPTION_NO_FIX_VR4130},
10595
10596  /* Miscellaneous options.  */
10597#define OPTION_MISC_BASE (OPTION_FIX_BASE + 6)
10598#define OPTION_TRAP (OPTION_MISC_BASE + 0)
10599  {"trap", no_argument, NULL, OPTION_TRAP},
10600  {"no-break", no_argument, NULL, OPTION_TRAP},
10601#define OPTION_BREAK (OPTION_MISC_BASE + 1)
10602  {"break", no_argument, NULL, OPTION_BREAK},
10603  {"no-trap", no_argument, NULL, OPTION_BREAK},
10604#define OPTION_EB (OPTION_MISC_BASE + 2)
10605  {"EB", no_argument, NULL, OPTION_EB},
10606#define OPTION_EL (OPTION_MISC_BASE + 3)
10607  {"EL", no_argument, NULL, OPTION_EL},
10608#define OPTION_FP32 (OPTION_MISC_BASE + 4)
10609  {"mfp32", no_argument, NULL, OPTION_FP32},
10610#define OPTION_GP32 (OPTION_MISC_BASE + 5)
10611  {"mgp32", no_argument, NULL, OPTION_GP32},
10612#define OPTION_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 6)
10613  {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10614#define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 7)
10615  {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10616#define OPTION_FP64 (OPTION_MISC_BASE + 8)
10617  {"mfp64", no_argument, NULL, OPTION_FP64},
10618#define OPTION_GP64 (OPTION_MISC_BASE + 9)
10619  {"mgp64", no_argument, NULL, OPTION_GP64},
10620#define OPTION_RELAX_BRANCH (OPTION_MISC_BASE + 10)
10621#define OPTION_NO_RELAX_BRANCH (OPTION_MISC_BASE + 11)
10622  {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10623  {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10624#define OPTION_MSHARED (OPTION_MISC_BASE + 12)
10625#define OPTION_MNO_SHARED (OPTION_MISC_BASE + 13)
10626  {"mshared", no_argument, NULL, OPTION_MSHARED},
10627  {"mno-shared", no_argument, NULL, OPTION_MNO_SHARED},
10628#define OPTION_MSYM32 (OPTION_MISC_BASE + 14)
10629#define OPTION_MNO_SYM32 (OPTION_MISC_BASE + 15)
10630  {"msym32", no_argument, NULL, OPTION_MSYM32},
10631  {"mno-sym32", no_argument, NULL, OPTION_MNO_SYM32},
10632
10633  /* ELF-specific options.  */
10634#ifdef OBJ_ELF
10635#define OPTION_ELF_BASE    (OPTION_MISC_BASE + 16)
10636#define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10637  {"KPIC",        no_argument, NULL, OPTION_CALL_SHARED},
10638  {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10639#define OPTION_NON_SHARED  (OPTION_ELF_BASE + 1)
10640  {"non_shared",  no_argument, NULL, OPTION_NON_SHARED},
10641#define OPTION_XGOT        (OPTION_ELF_BASE + 2)
10642  {"xgot",        no_argument, NULL, OPTION_XGOT},
10643#define OPTION_MABI        (OPTION_ELF_BASE + 3)
10644  {"mabi", required_argument, NULL, OPTION_MABI},
10645#define OPTION_32 	   (OPTION_ELF_BASE + 4)
10646  {"32",          no_argument, NULL, OPTION_32},
10647#define OPTION_N32 	   (OPTION_ELF_BASE + 5)
10648  {"n32",         no_argument, NULL, OPTION_N32},
10649#define OPTION_64          (OPTION_ELF_BASE + 6)
10650  {"64",          no_argument, NULL, OPTION_64},
10651#define OPTION_MDEBUG      (OPTION_ELF_BASE + 7)
10652  {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10653#define OPTION_NO_MDEBUG   (OPTION_ELF_BASE + 8)
10654  {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10655#define OPTION_PDR	   (OPTION_ELF_BASE + 9)
10656  {"mpdr", no_argument, NULL, OPTION_PDR},
10657#define OPTION_NO_PDR	   (OPTION_ELF_BASE + 10)
10658  {"mno-pdr", no_argument, NULL, OPTION_NO_PDR},
10659#define OPTION_MVXWORKS_PIC (OPTION_ELF_BASE + 11)
10660  {"mvxworks-pic", no_argument, NULL, OPTION_MVXWORKS_PIC},
10661#endif /* OBJ_ELF */
10662
10663  {NULL, no_argument, NULL, 0}
10664};
10665size_t md_longopts_size = sizeof (md_longopts);
10666
10667/* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10668   NEW_VALUE.  Warn if another value was already specified.  Note:
10669   we have to defer parsing the -march and -mtune arguments in order
10670   to handle 'from-abi' correctly, since the ABI might be specified
10671   in a later argument.  */
10672
10673static void
10674mips_set_option_string (const char **string_ptr, const char *new_value)
10675{
10676  if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10677    as_warn (_("A different %s was already specified, is now %s"),
10678	     string_ptr == &mips_arch_string ? "-march" : "-mtune",
10679	     new_value);
10680
10681  *string_ptr = new_value;
10682}
10683
10684int
10685md_parse_option (int c, char *arg)
10686{
10687  switch (c)
10688    {
10689    case OPTION_CONSTRUCT_FLOATS:
10690      mips_disable_float_construction = 0;
10691      break;
10692
10693    case OPTION_NO_CONSTRUCT_FLOATS:
10694      mips_disable_float_construction = 1;
10695      break;
10696
10697    case OPTION_TRAP:
10698      mips_trap = 1;
10699      break;
10700
10701    case OPTION_BREAK:
10702      mips_trap = 0;
10703      break;
10704
10705    case OPTION_EB:
10706      target_big_endian = 1;
10707      break;
10708
10709    case OPTION_EL:
10710      target_big_endian = 0;
10711      break;
10712
10713    case 'O':
10714      if (arg && arg[1] == '0')
10715	mips_optimize = 1;
10716      else
10717	mips_optimize = 2;
10718      break;
10719
10720    case 'g':
10721      if (arg == NULL)
10722	mips_debug = 2;
10723      else
10724	mips_debug = atoi (arg);
10725      /* When the MIPS assembler sees -g or -g2, it does not do
10726         optimizations which limit full symbolic debugging.  We take
10727         that to be equivalent to -O0.  */
10728      if (mips_debug == 2)
10729	mips_optimize = 1;
10730      break;
10731
10732    case OPTION_MIPS1:
10733      file_mips_isa = ISA_MIPS1;
10734      break;
10735
10736    case OPTION_MIPS2:
10737      file_mips_isa = ISA_MIPS2;
10738      break;
10739
10740    case OPTION_MIPS3:
10741      file_mips_isa = ISA_MIPS3;
10742      break;
10743
10744    case OPTION_MIPS4:
10745      file_mips_isa = ISA_MIPS4;
10746      break;
10747
10748    case OPTION_MIPS5:
10749      file_mips_isa = ISA_MIPS5;
10750      break;
10751
10752    case OPTION_MIPS32:
10753      file_mips_isa = ISA_MIPS32;
10754      break;
10755
10756    case OPTION_MIPS32R2:
10757      file_mips_isa = ISA_MIPS32R2;
10758      break;
10759
10760    case OPTION_MIPS64R2:
10761      file_mips_isa = ISA_MIPS64R2;
10762      break;
10763
10764    case OPTION_MIPS64:
10765      file_mips_isa = ISA_MIPS64;
10766      break;
10767
10768    case OPTION_MTUNE:
10769      mips_set_option_string (&mips_tune_string, arg);
10770      break;
10771
10772    case OPTION_MARCH:
10773      mips_set_option_string (&mips_arch_string, arg);
10774      break;
10775
10776    case OPTION_M4650:
10777      mips_set_option_string (&mips_arch_string, "4650");
10778      mips_set_option_string (&mips_tune_string, "4650");
10779      break;
10780
10781    case OPTION_NO_M4650:
10782      break;
10783
10784    case OPTION_M4010:
10785      mips_set_option_string (&mips_arch_string, "4010");
10786      mips_set_option_string (&mips_tune_string, "4010");
10787      break;
10788
10789    case OPTION_NO_M4010:
10790      break;
10791
10792    case OPTION_M4100:
10793      mips_set_option_string (&mips_arch_string, "4100");
10794      mips_set_option_string (&mips_tune_string, "4100");
10795      break;
10796
10797    case OPTION_NO_M4100:
10798      break;
10799
10800    case OPTION_M3900:
10801      mips_set_option_string (&mips_arch_string, "3900");
10802      mips_set_option_string (&mips_tune_string, "3900");
10803      break;
10804
10805    case OPTION_NO_M3900:
10806      break;
10807
10808    case OPTION_MDMX:
10809      mips_opts.ase_mdmx = 1;
10810      break;
10811
10812    case OPTION_NO_MDMX:
10813      mips_opts.ase_mdmx = 0;
10814      break;
10815
10816    case OPTION_DSP:
10817      mips_opts.ase_dsp = 1;
10818      break;
10819
10820    case OPTION_NO_DSP:
10821      mips_opts.ase_dsp = 0;
10822      break;
10823
10824    case OPTION_MT:
10825      mips_opts.ase_mt = 1;
10826      break;
10827
10828    case OPTION_NO_MT:
10829      mips_opts.ase_mt = 0;
10830      break;
10831
10832    case OPTION_MIPS16:
10833      mips_opts.mips16 = 1;
10834      mips_no_prev_insn ();
10835      break;
10836
10837    case OPTION_NO_MIPS16:
10838      mips_opts.mips16 = 0;
10839      mips_no_prev_insn ();
10840      break;
10841
10842    case OPTION_MIPS3D:
10843      mips_opts.ase_mips3d = 1;
10844      break;
10845
10846    case OPTION_NO_MIPS3D:
10847      mips_opts.ase_mips3d = 0;
10848      break;
10849
10850    case OPTION_FIX_VR4120:
10851      mips_fix_vr4120 = 1;
10852      break;
10853
10854    case OPTION_NO_FIX_VR4120:
10855      mips_fix_vr4120 = 0;
10856      break;
10857
10858    case OPTION_FIX_VR4130:
10859      mips_fix_vr4130 = 1;
10860      break;
10861
10862    case OPTION_NO_FIX_VR4130:
10863      mips_fix_vr4130 = 0;
10864      break;
10865
10866    case OPTION_RELAX_BRANCH:
10867      mips_relax_branch = 1;
10868      break;
10869
10870    case OPTION_NO_RELAX_BRANCH:
10871      mips_relax_branch = 0;
10872      break;
10873
10874    case OPTION_MSHARED:
10875      mips_in_shared = TRUE;
10876      break;
10877
10878    case OPTION_MNO_SHARED:
10879      mips_in_shared = FALSE;
10880      break;
10881
10882    case OPTION_MSYM32:
10883      mips_opts.sym32 = TRUE;
10884      break;
10885
10886    case OPTION_MNO_SYM32:
10887      mips_opts.sym32 = FALSE;
10888      break;
10889
10890#ifdef OBJ_ELF
10891      /* When generating ELF code, we permit -KPIC and -call_shared to
10892	 select SVR4_PIC, and -non_shared to select no PIC.  This is
10893	 intended to be compatible with Irix 5.  */
10894    case OPTION_CALL_SHARED:
10895      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10896	{
10897	  as_bad (_("-call_shared is supported only for ELF format"));
10898	  return 0;
10899	}
10900      mips_pic = SVR4_PIC;
10901      mips_abicalls = TRUE;
10902      break;
10903
10904    case OPTION_NON_SHARED:
10905      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10906	{
10907	  as_bad (_("-non_shared is supported only for ELF format"));
10908	  return 0;
10909	}
10910      mips_pic = NO_PIC;
10911      mips_abicalls = FALSE;
10912      break;
10913
10914      /* The -xgot option tells the assembler to use 32 bit offsets
10915         when accessing the got in SVR4_PIC mode.  It is for Irix
10916         compatibility.  */
10917    case OPTION_XGOT:
10918      mips_big_got = 1;
10919      break;
10920#endif /* OBJ_ELF */
10921
10922    case 'G':
10923      g_switch_value = atoi (arg);
10924      g_switch_seen = 1;
10925      break;
10926
10927#ifdef OBJ_ELF
10928      /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
10929	 and -mabi=64.  */
10930    case OPTION_32:
10931      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10932	{
10933	  as_bad (_("-32 is supported for ELF format only"));
10934	  return 0;
10935	}
10936      mips_abi = O32_ABI;
10937      break;
10938
10939    case OPTION_N32:
10940      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10941	{
10942	  as_bad (_("-n32 is supported for ELF format only"));
10943	  return 0;
10944	}
10945      mips_abi = N32_ABI;
10946      break;
10947
10948    case OPTION_64:
10949      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10950	{
10951	  as_bad (_("-64 is supported for ELF format only"));
10952	  return 0;
10953	}
10954      mips_abi = N64_ABI;
10955      if (! support_64bit_objects())
10956	as_fatal (_("No compiled in support for 64 bit object file format"));
10957      break;
10958#endif /* OBJ_ELF */
10959
10960    case OPTION_GP32:
10961      file_mips_gp32 = 1;
10962      break;
10963
10964    case OPTION_GP64:
10965      file_mips_gp32 = 0;
10966      break;
10967
10968    case OPTION_FP32:
10969      file_mips_fp32 = 1;
10970      break;
10971
10972    case OPTION_FP64:
10973      file_mips_fp32 = 0;
10974      break;
10975
10976#ifdef OBJ_ELF
10977    case OPTION_MABI:
10978      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10979	{
10980	  as_bad (_("-mabi is supported for ELF format only"));
10981	  return 0;
10982	}
10983      if (strcmp (arg, "32") == 0)
10984	mips_abi = O32_ABI;
10985      else if (strcmp (arg, "o64") == 0)
10986	mips_abi = O64_ABI;
10987      else if (strcmp (arg, "n32") == 0)
10988	mips_abi = N32_ABI;
10989      else if (strcmp (arg, "64") == 0)
10990	{
10991	  mips_abi = N64_ABI;
10992	  if (! support_64bit_objects())
10993	    as_fatal (_("No compiled in support for 64 bit object file "
10994			"format"));
10995	}
10996      else if (strcmp (arg, "eabi") == 0)
10997	mips_abi = EABI_ABI;
10998      else
10999	{
11000	  as_fatal (_("invalid abi -mabi=%s"), arg);
11001	  return 0;
11002	}
11003      break;
11004#endif /* OBJ_ELF */
11005
11006    case OPTION_M7000_HILO_FIX:
11007      mips_7000_hilo_fix = TRUE;
11008      break;
11009
11010    case OPTION_MNO_7000_HILO_FIX:
11011      mips_7000_hilo_fix = FALSE;
11012      break;
11013
11014#ifdef OBJ_ELF
11015    case OPTION_MDEBUG:
11016      mips_flag_mdebug = TRUE;
11017      break;
11018
11019    case OPTION_NO_MDEBUG:
11020      mips_flag_mdebug = FALSE;
11021      break;
11022
11023    case OPTION_PDR:
11024      mips_flag_pdr = TRUE;
11025      break;
11026
11027    case OPTION_NO_PDR:
11028      mips_flag_pdr = FALSE;
11029      break;
11030
11031    case OPTION_MVXWORKS_PIC:
11032      mips_pic = VXWORKS_PIC;
11033      break;
11034#endif /* OBJ_ELF */
11035
11036    default:
11037      return 0;
11038    }
11039
11040  return 1;
11041}
11042
11043/* Set up globals to generate code for the ISA or processor
11044   described by INFO.  */
11045
11046static void
11047mips_set_architecture (const struct mips_cpu_info *info)
11048{
11049  if (info != 0)
11050    {
11051      file_mips_arch = info->cpu;
11052      mips_opts.arch = info->cpu;
11053      mips_opts.isa = info->isa;
11054    }
11055}
11056
11057
11058/* Likewise for tuning.  */
11059
11060static void
11061mips_set_tune (const struct mips_cpu_info *info)
11062{
11063  if (info != 0)
11064    mips_tune = info->cpu;
11065}
11066
11067
11068void
11069mips_after_parse_args (void)
11070{
11071  const struct mips_cpu_info *arch_info = 0;
11072  const struct mips_cpu_info *tune_info = 0;
11073
11074  /* GP relative stuff not working for PE */
11075  if (strncmp (TARGET_OS, "pe", 2) == 0)
11076    {
11077      if (g_switch_seen && g_switch_value != 0)
11078	as_bad (_("-G not supported in this configuration."));
11079      g_switch_value = 0;
11080    }
11081
11082  if (mips_abi == NO_ABI)
11083    mips_abi = MIPS_DEFAULT_ABI;
11084
11085  /* The following code determines the architecture and register size.
11086     Similar code was added to GCC 3.3 (see override_options() in
11087     config/mips/mips.c).  The GAS and GCC code should be kept in sync
11088     as much as possible.  */
11089
11090  if (mips_arch_string != 0)
11091    arch_info = mips_parse_cpu ("-march", mips_arch_string);
11092
11093  if (file_mips_isa != ISA_UNKNOWN)
11094    {
11095      /* Handle -mipsN.  At this point, file_mips_isa contains the
11096	 ISA level specified by -mipsN, while arch_info->isa contains
11097	 the -march selection (if any).  */
11098      if (arch_info != 0)
11099	{
11100	  /* -march takes precedence over -mipsN, since it is more descriptive.
11101	     There's no harm in specifying both as long as the ISA levels
11102	     are the same.  */
11103	  if (file_mips_isa != arch_info->isa)
11104	    as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
11105		    mips_cpu_info_from_isa (file_mips_isa)->name,
11106		    mips_cpu_info_from_isa (arch_info->isa)->name);
11107	}
11108      else
11109	arch_info = mips_cpu_info_from_isa (file_mips_isa);
11110    }
11111
11112  if (arch_info == 0)
11113    arch_info = mips_parse_cpu ("default CPU", MIPS_CPU_STRING_DEFAULT);
11114
11115  if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (arch_info->isa))
11116    as_bad ("-march=%s is not compatible with the selected ABI",
11117	    arch_info->name);
11118
11119  mips_set_architecture (arch_info);
11120
11121  /* Optimize for file_mips_arch, unless -mtune selects a different processor.  */
11122  if (mips_tune_string != 0)
11123    tune_info = mips_parse_cpu ("-mtune", mips_tune_string);
11124
11125  if (tune_info == 0)
11126    mips_set_tune (arch_info);
11127  else
11128    mips_set_tune (tune_info);
11129
11130  if (file_mips_gp32 >= 0)
11131    {
11132      /* The user specified the size of the integer registers.  Make sure
11133	 it agrees with the ABI and ISA.  */
11134      if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11135	as_bad (_("-mgp64 used with a 32-bit processor"));
11136      else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
11137	as_bad (_("-mgp32 used with a 64-bit ABI"));
11138      else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
11139	as_bad (_("-mgp64 used with a 32-bit ABI"));
11140    }
11141  else
11142    {
11143      /* Infer the integer register size from the ABI and processor.
11144	 Restrict ourselves to 32-bit registers if that's all the
11145	 processor has, or if the ABI cannot handle 64-bit registers.  */
11146      file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
11147			|| !ISA_HAS_64BIT_REGS (mips_opts.isa));
11148    }
11149
11150  /* ??? GAS treats single-float processors as though they had 64-bit
11151     float registers (although it complains when double-precision
11152     instructions are used).  As things stand, saying they have 32-bit
11153     registers would lead to spurious "register must be even" messages.
11154     So here we assume float registers are always the same size as
11155     integer ones, unless the user says otherwise.  */
11156  if (file_mips_fp32 < 0)
11157    file_mips_fp32 = file_mips_gp32;
11158
11159  /* End of GCC-shared inference code.  */
11160
11161  /* This flag is set when we have a 64-bit capable CPU but use only
11162     32-bit wide registers.  Note that EABI does not use it.  */
11163  if (ISA_HAS_64BIT_REGS (mips_opts.isa)
11164      && ((mips_abi == NO_ABI && file_mips_gp32 == 1)
11165	  || mips_abi == O32_ABI))
11166    mips_32bitmode = 1;
11167
11168  if (mips_opts.isa == ISA_MIPS1 && mips_trap)
11169    as_bad (_("trap exception not supported at ISA 1"));
11170
11171  /* If the selected architecture includes support for ASEs, enable
11172     generation of code for them.  */
11173  if (mips_opts.mips16 == -1)
11174    mips_opts.mips16 = (CPU_HAS_MIPS16 (file_mips_arch)) ? 1 : 0;
11175  if (mips_opts.ase_mips3d == -1)
11176    mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (file_mips_arch)) ? 1 : 0;
11177  if (mips_opts.ase_mdmx == -1)
11178    mips_opts.ase_mdmx = (CPU_HAS_MDMX (file_mips_arch)) ? 1 : 0;
11179  if (mips_opts.ase_dsp == -1)
11180    mips_opts.ase_dsp = (CPU_HAS_DSP (file_mips_arch)) ? 1 : 0;
11181  if (mips_opts.ase_mt == -1)
11182    mips_opts.ase_mt = (CPU_HAS_MT (file_mips_arch)) ? 1 : 0;
11183
11184  file_mips_isa = mips_opts.isa;
11185  file_ase_mips16 = mips_opts.mips16;
11186  file_ase_mips3d = mips_opts.ase_mips3d;
11187  file_ase_mdmx = mips_opts.ase_mdmx;
11188  file_ase_dsp = mips_opts.ase_dsp;
11189  file_ase_mt = mips_opts.ase_mt;
11190  mips_opts.gp32 = file_mips_gp32;
11191  mips_opts.fp32 = file_mips_fp32;
11192
11193  if (mips_flag_mdebug < 0)
11194    {
11195#ifdef OBJ_MAYBE_ECOFF
11196      if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
11197	mips_flag_mdebug = 1;
11198      else
11199#endif /* OBJ_MAYBE_ECOFF */
11200	mips_flag_mdebug = 0;
11201    }
11202}
11203
11204void
11205mips_init_after_args (void)
11206{
11207  /* initialize opcodes */
11208  bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
11209  mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
11210}
11211
11212long
11213md_pcrel_from (fixS *fixP)
11214{
11215  valueT addr = fixP->fx_where + fixP->fx_frag->fr_address;
11216  switch (fixP->fx_r_type)
11217    {
11218    case BFD_RELOC_16_PCREL_S2:
11219    case BFD_RELOC_MIPS_JMP:
11220      /* Return the address of the delay slot.  */
11221      return addr + 4;
11222    default:
11223      return addr;
11224    }
11225}
11226
11227/* This is called before the symbol table is processed.  In order to
11228   work with gcc when using mips-tfile, we must keep all local labels.
11229   However, in other cases, we want to discard them.  If we were
11230   called with -g, but we didn't see any debugging information, it may
11231   mean that gcc is smuggling debugging information through to
11232   mips-tfile, in which case we must generate all local labels.  */
11233
11234void
11235mips_frob_file_before_adjust (void)
11236{
11237#ifndef NO_ECOFF_DEBUGGING
11238  if (ECOFF_DEBUGGING
11239      && mips_debug != 0
11240      && ! ecoff_debugging_seen)
11241    flag_keep_locals = 1;
11242#endif
11243}
11244
11245/* Sort any unmatched HI16 and GOT16 relocs so that they immediately precede
11246   the corresponding LO16 reloc.  This is called before md_apply_fix and
11247   tc_gen_reloc.  Unmatched relocs can only be generated by use of explicit
11248   relocation operators.
11249
11250   For our purposes, a %lo() expression matches a %got() or %hi()
11251   expression if:
11252
11253      (a) it refers to the same symbol; and
11254      (b) the offset applied in the %lo() expression is no lower than
11255	  the offset applied in the %got() or %hi().
11256
11257   (b) allows us to cope with code like:
11258
11259	lui	$4,%hi(foo)
11260	lh	$4,%lo(foo+2)($4)
11261
11262   ...which is legal on RELA targets, and has a well-defined behaviour
11263   if the user knows that adding 2 to "foo" will not induce a carry to
11264   the high 16 bits.
11265
11266   When several %lo()s match a particular %got() or %hi(), we use the
11267   following rules to distinguish them:
11268
11269     (1) %lo()s with smaller offsets are a better match than %lo()s with
11270         higher offsets.
11271
11272     (2) %lo()s with no matching %got() or %hi() are better than those
11273         that already have a matching %got() or %hi().
11274
11275     (3) later %lo()s are better than earlier %lo()s.
11276
11277   These rules are applied in order.
11278
11279   (1) means, among other things, that %lo()s with identical offsets are
11280   chosen if they exist.
11281
11282   (2) means that we won't associate several high-part relocations with
11283   the same low-part relocation unless there's no alternative.  Having
11284   several high parts for the same low part is a GNU extension; this rule
11285   allows careful users to avoid it.
11286
11287   (3) is purely cosmetic.  mips_hi_fixup_list is is in reverse order,
11288   with the last high-part relocation being at the front of the list.
11289   It therefore makes sense to choose the last matching low-part
11290   relocation, all other things being equal.  It's also easier
11291   to code that way.  */
11292
11293void
11294mips_frob_file (void)
11295{
11296  struct mips_hi_fixup *l;
11297
11298  for (l = mips_hi_fixup_list; l != NULL; l = l->next)
11299    {
11300      segment_info_type *seginfo;
11301      bfd_boolean matched_lo_p;
11302      fixS **hi_pos, **lo_pos, **pos;
11303
11304      assert (reloc_needs_lo_p (l->fixp->fx_r_type));
11305
11306      /* If a GOT16 relocation turns out to be against a global symbol,
11307	 there isn't supposed to be a matching LO.  */
11308      if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
11309	  && !pic_need_relax (l->fixp->fx_addsy, l->seg))
11310	continue;
11311
11312      /* Check quickly whether the next fixup happens to be a matching %lo.  */
11313      if (fixup_has_matching_lo_p (l->fixp))
11314	continue;
11315
11316      seginfo = seg_info (l->seg);
11317
11318      /* Set HI_POS to the position of this relocation in the chain.
11319	 Set LO_POS to the position of the chosen low-part relocation.
11320	 MATCHED_LO_P is true on entry to the loop if *POS is a low-part
11321	 relocation that matches an immediately-preceding high-part
11322	 relocation.  */
11323      hi_pos = NULL;
11324      lo_pos = NULL;
11325      matched_lo_p = FALSE;
11326      for (pos = &seginfo->fix_root; *pos != NULL; pos = &(*pos)->fx_next)
11327	{
11328	  if (*pos == l->fixp)
11329	    hi_pos = pos;
11330
11331	  if (((*pos)->fx_r_type == BFD_RELOC_LO16
11332	       || (*pos)->fx_r_type == BFD_RELOC_MIPS16_LO16)
11333	      && (*pos)->fx_addsy == l->fixp->fx_addsy
11334	      && (*pos)->fx_offset >= l->fixp->fx_offset
11335	      && (lo_pos == NULL
11336		  || (*pos)->fx_offset < (*lo_pos)->fx_offset
11337		  || (!matched_lo_p
11338		      && (*pos)->fx_offset == (*lo_pos)->fx_offset)))
11339	    lo_pos = pos;
11340
11341	  matched_lo_p = (reloc_needs_lo_p ((*pos)->fx_r_type)
11342			  && fixup_has_matching_lo_p (*pos));
11343	}
11344
11345      /* If we found a match, remove the high-part relocation from its
11346	 current position and insert it before the low-part relocation.
11347	 Make the offsets match so that fixup_has_matching_lo_p()
11348	 will return true.
11349
11350	 We don't warn about unmatched high-part relocations since some
11351	 versions of gcc have been known to emit dead "lui ...%hi(...)"
11352	 instructions.  */
11353      if (lo_pos != NULL)
11354	{
11355	  l->fixp->fx_offset = (*lo_pos)->fx_offset;
11356	  if (l->fixp->fx_next != *lo_pos)
11357	    {
11358	      *hi_pos = l->fixp->fx_next;
11359	      l->fixp->fx_next = *lo_pos;
11360	      *lo_pos = l->fixp;
11361	    }
11362	}
11363    }
11364}
11365
11366/* We may have combined relocations without symbols in the N32/N64 ABI.
11367   We have to prevent gas from dropping them.  */
11368
11369int
11370mips_force_relocation (fixS *fixp)
11371{
11372  if (generic_force_reloc (fixp))
11373    return 1;
11374
11375  if (HAVE_NEWABI
11376      && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11377      && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11378	  || fixp->fx_r_type == BFD_RELOC_HI16_S
11379	  || fixp->fx_r_type == BFD_RELOC_LO16))
11380    return 1;
11381
11382  return 0;
11383}
11384
11385/* Apply a fixup to the object file.  */
11386
11387void
11388md_apply_fix (fixS *fixP, valueT *valP, segT seg ATTRIBUTE_UNUSED)
11389{
11390  bfd_byte *buf;
11391  long insn;
11392  reloc_howto_type *howto;
11393
11394  /* We ignore generic BFD relocations we don't know about.  */
11395  howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11396  if (! howto)
11397    return;
11398
11399  assert (fixP->fx_size == 4
11400	  || fixP->fx_r_type == BFD_RELOC_16
11401	  || fixP->fx_r_type == BFD_RELOC_64
11402	  || fixP->fx_r_type == BFD_RELOC_CTOR
11403	  || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11404	  || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11405	  || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY);
11406
11407  buf = (bfd_byte *) (fixP->fx_frag->fr_literal + fixP->fx_where);
11408
11409  assert (! fixP->fx_pcrel || fixP->fx_r_type == BFD_RELOC_16_PCREL_S2);
11410
11411  /* Don't treat parts of a composite relocation as done.  There are two
11412     reasons for this:
11413
11414     (1) The second and third parts will be against 0 (RSS_UNDEF) but
11415	 should nevertheless be emitted if the first part is.
11416
11417     (2) In normal usage, composite relocations are never assembly-time
11418	 constants.  The easiest way of dealing with the pathological
11419	 exceptions is to generate a relocation against STN_UNDEF and
11420	 leave everything up to the linker.  */
11421  if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel && fixP->fx_tcbit == 0)
11422    fixP->fx_done = 1;
11423
11424  switch (fixP->fx_r_type)
11425    {
11426    case BFD_RELOC_MIPS_TLS_GD:
11427    case BFD_RELOC_MIPS_TLS_LDM:
11428    case BFD_RELOC_MIPS_TLS_DTPREL_HI16:
11429    case BFD_RELOC_MIPS_TLS_DTPREL_LO16:
11430    case BFD_RELOC_MIPS_TLS_GOTTPREL:
11431    case BFD_RELOC_MIPS_TLS_TPREL_HI16:
11432    case BFD_RELOC_MIPS_TLS_TPREL_LO16:
11433      S_SET_THREAD_LOCAL (fixP->fx_addsy);
11434      /* fall through */
11435
11436    case BFD_RELOC_MIPS_JMP:
11437    case BFD_RELOC_MIPS_SHIFT5:
11438    case BFD_RELOC_MIPS_SHIFT6:
11439    case BFD_RELOC_MIPS_GOT_DISP:
11440    case BFD_RELOC_MIPS_GOT_PAGE:
11441    case BFD_RELOC_MIPS_GOT_OFST:
11442    case BFD_RELOC_MIPS_SUB:
11443    case BFD_RELOC_MIPS_INSERT_A:
11444    case BFD_RELOC_MIPS_INSERT_B:
11445    case BFD_RELOC_MIPS_DELETE:
11446    case BFD_RELOC_MIPS_HIGHEST:
11447    case BFD_RELOC_MIPS_HIGHER:
11448    case BFD_RELOC_MIPS_SCN_DISP:
11449    case BFD_RELOC_MIPS_REL16:
11450    case BFD_RELOC_MIPS_RELGOT:
11451    case BFD_RELOC_MIPS_JALR:
11452    case BFD_RELOC_HI16:
11453    case BFD_RELOC_HI16_S:
11454    case BFD_RELOC_GPREL16:
11455    case BFD_RELOC_MIPS_LITERAL:
11456    case BFD_RELOC_MIPS_CALL16:
11457    case BFD_RELOC_MIPS_GOT16:
11458    case BFD_RELOC_GPREL32:
11459    case BFD_RELOC_MIPS_GOT_HI16:
11460    case BFD_RELOC_MIPS_GOT_LO16:
11461    case BFD_RELOC_MIPS_CALL_HI16:
11462    case BFD_RELOC_MIPS_CALL_LO16:
11463    case BFD_RELOC_MIPS16_GPREL:
11464    case BFD_RELOC_MIPS16_HI16:
11465    case BFD_RELOC_MIPS16_HI16_S:
11466      /* Nothing needed to do. The value comes from the reloc entry */
11467      break;
11468
11469    case BFD_RELOC_MIPS16_JMP:
11470      /* We currently always generate a reloc against a symbol, which
11471         means that we don't want an addend even if the symbol is
11472         defined.  */
11473      *valP = 0;
11474      break;
11475
11476    case BFD_RELOC_64:
11477      /* This is handled like BFD_RELOC_32, but we output a sign
11478         extended value if we are only 32 bits.  */
11479      if (fixP->fx_done)
11480	{
11481	  if (8 <= sizeof (valueT))
11482	    md_number_to_chars ((char *) buf, *valP, 8);
11483	  else
11484	    {
11485	      valueT hiv;
11486
11487	      if ((*valP & 0x80000000) != 0)
11488		hiv = 0xffffffff;
11489	      else
11490		hiv = 0;
11491	      md_number_to_chars ((char *)(buf + (target_big_endian ? 4 : 0)),
11492				  *valP, 4);
11493	      md_number_to_chars ((char *)(buf + (target_big_endian ? 0 : 4)),
11494				  hiv, 4);
11495	    }
11496	}
11497      break;
11498
11499    case BFD_RELOC_RVA:
11500    case BFD_RELOC_32:
11501      /* If we are deleting this reloc entry, we must fill in the
11502	 value now.  This can happen if we have a .word which is not
11503	 resolved when it appears but is later defined.   */
11504      if (fixP->fx_done)
11505	md_number_to_chars ((char *) buf, *valP, 4);
11506      break;
11507
11508    case BFD_RELOC_16:
11509      /* If we are deleting this reloc entry, we must fill in the
11510         value now.  */
11511      if (fixP->fx_done)
11512	md_number_to_chars ((char *) buf, *valP, 2);
11513      break;
11514
11515    case BFD_RELOC_LO16:
11516    case BFD_RELOC_MIPS16_LO16:
11517      /* FIXME: Now that embedded-PIC is gone, some of this code/comment
11518	 may be safe to remove, but if so it's not obvious.  */
11519      /* When handling an embedded PIC switch statement, we can wind
11520	 up deleting a LO16 reloc.  See the 'o' case in mips_ip.  */
11521      if (fixP->fx_done)
11522	{
11523	  if (*valP + 0x8000 > 0xffff)
11524	    as_bad_where (fixP->fx_file, fixP->fx_line,
11525			  _("relocation overflow"));
11526	  if (target_big_endian)
11527	    buf += 2;
11528	  md_number_to_chars ((char *) buf, *valP, 2);
11529	}
11530      break;
11531
11532    case BFD_RELOC_16_PCREL_S2:
11533      if ((*valP & 0x3) != 0)
11534	as_bad_where (fixP->fx_file, fixP->fx_line,
11535		      _("Branch to misaligned address (%lx)"), (long) *valP);
11536
11537      /*
11538       * We need to save the bits in the instruction since fixup_segment()
11539       * might be deleting the relocation entry (i.e., a branch within
11540       * the current segment).
11541       */
11542      if (! fixP->fx_done)
11543	break;
11544
11545      /* update old instruction data */
11546      if (target_big_endian)
11547	insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11548      else
11549	insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11550
11551      if (*valP + 0x20000 <= 0x3ffff)
11552	{
11553	  insn |= (*valP >> 2) & 0xffff;
11554	  md_number_to_chars ((char *) buf, insn, 4);
11555	}
11556      else if (mips_pic == NO_PIC
11557	       && fixP->fx_done
11558	       && fixP->fx_frag->fr_address >= text_section->vma
11559	       && (fixP->fx_frag->fr_address
11560		   < text_section->vma + bfd_get_section_size (text_section))
11561	       && ((insn & 0xffff0000) == 0x10000000	 /* beq $0,$0 */
11562		   || (insn & 0xffff0000) == 0x04010000	 /* bgez $0 */
11563		   || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11564	{
11565	  /* The branch offset is too large.  If this is an
11566             unconditional branch, and we are not generating PIC code,
11567             we can convert it to an absolute jump instruction.  */
11568	  if ((insn & 0xffff0000) == 0x04110000)	 /* bgezal $0 */
11569	    insn = 0x0c000000;	/* jal */
11570	  else
11571	    insn = 0x08000000;	/* j */
11572	  fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11573	  fixP->fx_done = 0;
11574	  fixP->fx_addsy = section_symbol (text_section);
11575	  *valP += md_pcrel_from (fixP);
11576	  md_number_to_chars ((char *) buf, insn, 4);
11577	}
11578      else
11579	{
11580	  /* If we got here, we have branch-relaxation disabled,
11581	     and there's nothing we can do to fix this instruction
11582	     without turning it into a longer sequence.  */
11583	  as_bad_where (fixP->fx_file, fixP->fx_line,
11584			_("Branch out of range"));
11585	}
11586      break;
11587
11588    case BFD_RELOC_VTABLE_INHERIT:
11589      fixP->fx_done = 0;
11590      if (fixP->fx_addsy
11591          && !S_IS_DEFINED (fixP->fx_addsy)
11592          && !S_IS_WEAK (fixP->fx_addsy))
11593        S_SET_WEAK (fixP->fx_addsy);
11594      break;
11595
11596    case BFD_RELOC_VTABLE_ENTRY:
11597      fixP->fx_done = 0;
11598      break;
11599
11600    default:
11601      internalError ();
11602    }
11603
11604  /* Remember value for tc_gen_reloc.  */
11605  fixP->fx_addnumber = *valP;
11606}
11607
11608static symbolS *
11609get_symbol (void)
11610{
11611  int c;
11612  char *name;
11613  symbolS *p;
11614
11615  name = input_line_pointer;
11616  c = get_symbol_end ();
11617  p = (symbolS *) symbol_find_or_make (name);
11618  *input_line_pointer = c;
11619  return p;
11620}
11621
11622/* Align the current frag to a given power of two.  The MIPS assembler
11623   also automatically adjusts any preceding label.  */
11624
11625static void
11626mips_align (int to, int fill, symbolS *label)
11627{
11628  mips_emit_delays ();
11629  frag_align (to, fill, 0);
11630  record_alignment (now_seg, to);
11631  if (label != NULL)
11632    {
11633      assert (S_GET_SEGMENT (label) == now_seg);
11634      symbol_set_frag (label, frag_now);
11635      S_SET_VALUE (label, (valueT) frag_now_fix ());
11636    }
11637}
11638
11639/* Align to a given power of two.  .align 0 turns off the automatic
11640   alignment used by the data creating pseudo-ops.  */
11641
11642static void
11643s_align (int x ATTRIBUTE_UNUSED)
11644{
11645  register int temp;
11646  register long temp_fill;
11647  long max_alignment = 15;
11648
11649  /*
11650
11651    o  Note that the assembler pulls down any immediately preceding label
11652       to the aligned address.
11653    o  It's not documented but auto alignment is reinstated by
11654       a .align pseudo instruction.
11655    o  Note also that after auto alignment is turned off the mips assembler
11656       issues an error on attempt to assemble an improperly aligned data item.
11657       We don't.
11658
11659    */
11660
11661  temp = get_absolute_expression ();
11662  if (temp > max_alignment)
11663    as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11664  else if (temp < 0)
11665    {
11666      as_warn (_("Alignment negative: 0 assumed."));
11667      temp = 0;
11668    }
11669  if (*input_line_pointer == ',')
11670    {
11671      ++input_line_pointer;
11672      temp_fill = get_absolute_expression ();
11673    }
11674  else
11675    temp_fill = 0;
11676  if (temp)
11677    {
11678      auto_align = 1;
11679      mips_align (temp, (int) temp_fill,
11680		  insn_labels != NULL ? insn_labels->label : NULL);
11681    }
11682  else
11683    {
11684      auto_align = 0;
11685    }
11686
11687  demand_empty_rest_of_line ();
11688}
11689
11690static void
11691s_change_sec (int sec)
11692{
11693  segT seg;
11694
11695#ifdef OBJ_ELF
11696  /* The ELF backend needs to know that we are changing sections, so
11697     that .previous works correctly.  We could do something like check
11698     for an obj_section_change_hook macro, but that might be confusing
11699     as it would not be appropriate to use it in the section changing
11700     functions in read.c, since obj-elf.c intercepts those.  FIXME:
11701     This should be cleaner, somehow.  */
11702  obj_elf_section_change_hook ();
11703#endif
11704
11705  mips_emit_delays ();
11706  switch (sec)
11707    {
11708    case 't':
11709      s_text (0);
11710      break;
11711    case 'd':
11712      s_data (0);
11713      break;
11714    case 'b':
11715      subseg_set (bss_section, (subsegT) get_absolute_expression ());
11716      demand_empty_rest_of_line ();
11717      break;
11718
11719    case 'r':
11720      seg = subseg_new (RDATA_SECTION_NAME,
11721			(subsegT) get_absolute_expression ());
11722      if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11723	{
11724	  bfd_set_section_flags (stdoutput, seg, (SEC_ALLOC | SEC_LOAD
11725						  | SEC_READONLY | SEC_RELOC
11726						  | SEC_DATA));
11727	  if (strcmp (TARGET_OS, "elf") != 0)
11728	    record_alignment (seg, 4);
11729	}
11730      demand_empty_rest_of_line ();
11731      break;
11732
11733    case 's':
11734      seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
11735      if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11736	{
11737	  bfd_set_section_flags (stdoutput, seg,
11738				 SEC_ALLOC | SEC_LOAD | SEC_RELOC | SEC_DATA);
11739	  if (strcmp (TARGET_OS, "elf") != 0)
11740	    record_alignment (seg, 4);
11741	}
11742      demand_empty_rest_of_line ();
11743      break;
11744    }
11745
11746  auto_align = 1;
11747}
11748
11749void
11750s_change_section (int ignore ATTRIBUTE_UNUSED)
11751{
11752#ifdef OBJ_ELF
11753  char *section_name;
11754  char c;
11755  char next_c = 0;
11756  int section_type;
11757  int section_flag;
11758  int section_entry_size;
11759  int section_alignment;
11760
11761  if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11762    return;
11763
11764  section_name = input_line_pointer;
11765  c = get_symbol_end ();
11766  if (c)
11767    next_c = *(input_line_pointer + 1);
11768
11769  /* Do we have .section Name<,"flags">?  */
11770  if (c != ',' || (c == ',' && next_c == '"'))
11771    {
11772      /* just after name is now '\0'.  */
11773      *input_line_pointer = c;
11774      input_line_pointer = section_name;
11775      obj_elf_section (ignore);
11776      return;
11777    }
11778  input_line_pointer++;
11779
11780  /* Do we have .section Name<,type><,flag><,entry_size><,alignment>  */
11781  if (c == ',')
11782    section_type = get_absolute_expression ();
11783  else
11784    section_type = 0;
11785  if (*input_line_pointer++ == ',')
11786    section_flag = get_absolute_expression ();
11787  else
11788    section_flag = 0;
11789  if (*input_line_pointer++ == ',')
11790    section_entry_size = get_absolute_expression ();
11791  else
11792    section_entry_size = 0;
11793  if (*input_line_pointer++ == ',')
11794    section_alignment = get_absolute_expression ();
11795  else
11796    section_alignment = 0;
11797
11798  section_name = xstrdup (section_name);
11799
11800  /* When using the generic form of .section (as implemented by obj-elf.c),
11801     there's no way to set the section type to SHT_MIPS_DWARF.  Users have
11802     traditionally had to fall back on the more common @progbits instead.
11803
11804     There's nothing really harmful in this, since bfd will correct
11805     SHT_PROGBITS to SHT_MIPS_DWARF before writing out the file.  But it
11806     means that, for backwards compatibiltiy, the special_section entries
11807     for dwarf sections must use SHT_PROGBITS rather than SHT_MIPS_DWARF.
11808
11809     Even so, we shouldn't force users of the MIPS .section syntax to
11810     incorrectly label the sections as SHT_PROGBITS.  The best compromise
11811     seems to be to map SHT_MIPS_DWARF to SHT_PROGBITS before calling the
11812     generic type-checking code.  */
11813  if (section_type == SHT_MIPS_DWARF)
11814    section_type = SHT_PROGBITS;
11815
11816  obj_elf_change_section (section_name, section_type, section_flag,
11817			  section_entry_size, 0, 0, 0);
11818
11819  if (now_seg->name != section_name)
11820    free (section_name);
11821#endif /* OBJ_ELF */
11822}
11823
11824void
11825mips_enable_auto_align (void)
11826{
11827  auto_align = 1;
11828}
11829
11830static void
11831s_cons (int log_size)
11832{
11833  symbolS *label;
11834
11835  label = insn_labels != NULL ? insn_labels->label : NULL;
11836  mips_emit_delays ();
11837  if (log_size > 0 && auto_align)
11838    mips_align (log_size, 0, label);
11839  mips_clear_insn_labels ();
11840  cons (1 << log_size);
11841}
11842
11843static void
11844s_float_cons (int type)
11845{
11846  symbolS *label;
11847
11848  label = insn_labels != NULL ? insn_labels->label : NULL;
11849
11850  mips_emit_delays ();
11851
11852  if (auto_align)
11853    {
11854      if (type == 'd')
11855	mips_align (3, 0, label);
11856      else
11857	mips_align (2, 0, label);
11858    }
11859
11860  mips_clear_insn_labels ();
11861
11862  float_cons (type);
11863}
11864
11865/* Handle .globl.  We need to override it because on Irix 5 you are
11866   permitted to say
11867       .globl foo .text
11868   where foo is an undefined symbol, to mean that foo should be
11869   considered to be the address of a function.  */
11870
11871static void
11872s_mips_globl (int x ATTRIBUTE_UNUSED)
11873{
11874  char *name;
11875  int c;
11876  symbolS *symbolP;
11877  flagword flag;
11878
11879  do
11880    {
11881      name = input_line_pointer;
11882      c = get_symbol_end ();
11883      symbolP = symbol_find_or_make (name);
11884      S_SET_EXTERNAL (symbolP);
11885
11886      *input_line_pointer = c;
11887      SKIP_WHITESPACE ();
11888
11889      /* On Irix 5, every global symbol that is not explicitly labelled as
11890         being a function is apparently labelled as being an object.  */
11891      flag = BSF_OBJECT;
11892
11893      if (!is_end_of_line[(unsigned char) *input_line_pointer]
11894	  && (*input_line_pointer != ','))
11895	{
11896	  char *secname;
11897	  asection *sec;
11898
11899	  secname = input_line_pointer;
11900	  c = get_symbol_end ();
11901	  sec = bfd_get_section_by_name (stdoutput, secname);
11902	  if (sec == NULL)
11903	    as_bad (_("%s: no such section"), secname);
11904	  *input_line_pointer = c;
11905
11906	  if (sec != NULL && (sec->flags & SEC_CODE) != 0)
11907	    flag = BSF_FUNCTION;
11908	}
11909
11910      symbol_get_bfdsym (symbolP)->flags |= flag;
11911
11912      c = *input_line_pointer;
11913      if (c == ',')
11914	{
11915	  input_line_pointer++;
11916	  SKIP_WHITESPACE ();
11917	  if (is_end_of_line[(unsigned char) *input_line_pointer])
11918	    c = '\n';
11919	}
11920    }
11921  while (c == ',');
11922
11923  demand_empty_rest_of_line ();
11924}
11925
11926static void
11927s_option (int x ATTRIBUTE_UNUSED)
11928{
11929  char *opt;
11930  char c;
11931
11932  opt = input_line_pointer;
11933  c = get_symbol_end ();
11934
11935  if (*opt == 'O')
11936    {
11937      /* FIXME: What does this mean?  */
11938    }
11939  else if (strncmp (opt, "pic", 3) == 0)
11940    {
11941      int i;
11942
11943      i = atoi (opt + 3);
11944      if (i == 0)
11945	mips_pic = NO_PIC;
11946      else if (i == 2)
11947	{
11948	mips_pic = SVR4_PIC;
11949	  mips_abicalls = TRUE;
11950	}
11951      else
11952	as_bad (_(".option pic%d not supported"), i);
11953
11954      if (mips_pic == SVR4_PIC)
11955	{
11956	  if (g_switch_seen && g_switch_value != 0)
11957	    as_warn (_("-G may not be used with SVR4 PIC code"));
11958	  g_switch_value = 0;
11959	  bfd_set_gp_size (stdoutput, 0);
11960	}
11961    }
11962  else
11963    as_warn (_("Unrecognized option \"%s\""), opt);
11964
11965  *input_line_pointer = c;
11966  demand_empty_rest_of_line ();
11967}
11968
11969/* This structure is used to hold a stack of .set values.  */
11970
11971struct mips_option_stack
11972{
11973  struct mips_option_stack *next;
11974  struct mips_set_options options;
11975};
11976
11977static struct mips_option_stack *mips_opts_stack;
11978
11979/* Handle the .set pseudo-op.  */
11980
11981static void
11982s_mipsset (int x ATTRIBUTE_UNUSED)
11983{
11984  char *name = input_line_pointer, ch;
11985
11986  while (!is_end_of_line[(unsigned char) *input_line_pointer])
11987    ++input_line_pointer;
11988  ch = *input_line_pointer;
11989  *input_line_pointer = '\0';
11990
11991  if (strcmp (name, "reorder") == 0)
11992    {
11993      if (mips_opts.noreorder)
11994	end_noreorder ();
11995    }
11996  else if (strcmp (name, "noreorder") == 0)
11997    {
11998      if (!mips_opts.noreorder)
11999	start_noreorder ();
12000    }
12001  else if (strcmp (name, "at") == 0)
12002    {
12003      mips_opts.noat = 0;
12004    }
12005  else if (strcmp (name, "noat") == 0)
12006    {
12007      mips_opts.noat = 1;
12008    }
12009  else if (strcmp (name, "macro") == 0)
12010    {
12011      mips_opts.warn_about_macros = 0;
12012    }
12013  else if (strcmp (name, "nomacro") == 0)
12014    {
12015      if (mips_opts.noreorder == 0)
12016	as_bad (_("`noreorder' must be set before `nomacro'"));
12017      mips_opts.warn_about_macros = 1;
12018    }
12019  else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
12020    {
12021      mips_opts.nomove = 0;
12022    }
12023  else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
12024    {
12025      mips_opts.nomove = 1;
12026    }
12027  else if (strcmp (name, "bopt") == 0)
12028    {
12029      mips_opts.nobopt = 0;
12030    }
12031  else if (strcmp (name, "nobopt") == 0)
12032    {
12033      mips_opts.nobopt = 1;
12034    }
12035  else if (strcmp (name, "mips16") == 0
12036	   || strcmp (name, "MIPS-16") == 0)
12037    mips_opts.mips16 = 1;
12038  else if (strcmp (name, "nomips16") == 0
12039	   || strcmp (name, "noMIPS-16") == 0)
12040    mips_opts.mips16 = 0;
12041  else if (strcmp (name, "mips3d") == 0)
12042    mips_opts.ase_mips3d = 1;
12043  else if (strcmp (name, "nomips3d") == 0)
12044    mips_opts.ase_mips3d = 0;
12045  else if (strcmp (name, "mdmx") == 0)
12046    mips_opts.ase_mdmx = 1;
12047  else if (strcmp (name, "nomdmx") == 0)
12048    mips_opts.ase_mdmx = 0;
12049  else if (strcmp (name, "dsp") == 0)
12050    mips_opts.ase_dsp = 1;
12051  else if (strcmp (name, "nodsp") == 0)
12052    mips_opts.ase_dsp = 0;
12053  else if (strcmp (name, "mt") == 0)
12054    mips_opts.ase_mt = 1;
12055  else if (strcmp (name, "nomt") == 0)
12056    mips_opts.ase_mt = 0;
12057  else if (strncmp (name, "mips", 4) == 0 || strncmp (name, "arch=", 5) == 0)
12058    {
12059      int reset = 0;
12060
12061      /* Permit the user to change the ISA and architecture on the fly.
12062	 Needless to say, misuse can cause serious problems.  */
12063      if (strcmp (name, "mips0") == 0 || strcmp (name, "arch=default") == 0)
12064	{
12065	  reset = 1;
12066	  mips_opts.isa = file_mips_isa;
12067	  mips_opts.arch = file_mips_arch;
12068	}
12069      else if (strncmp (name, "arch=", 5) == 0)
12070	{
12071	  const struct mips_cpu_info *p;
12072
12073	  p = mips_parse_cpu("internal use", name + 5);
12074	  if (!p)
12075	    as_bad (_("unknown architecture %s"), name + 5);
12076	  else
12077	    {
12078	      mips_opts.arch = p->cpu;
12079	      mips_opts.isa = p->isa;
12080	    }
12081	}
12082      else if (strncmp (name, "mips", 4) == 0)
12083	{
12084	  const struct mips_cpu_info *p;
12085
12086	  p = mips_parse_cpu("internal use", name);
12087	  if (!p)
12088	    as_bad (_("unknown ISA level %s"), name + 4);
12089	  else
12090	    {
12091	      mips_opts.arch = p->cpu;
12092	      mips_opts.isa = p->isa;
12093	    }
12094	}
12095      else
12096	as_bad (_("unknown ISA or architecture %s"), name);
12097
12098      switch (mips_opts.isa)
12099	{
12100	case  0:
12101	  break;
12102	case ISA_MIPS1:
12103	case ISA_MIPS2:
12104	case ISA_MIPS32:
12105	case ISA_MIPS32R2:
12106	  mips_opts.gp32 = 1;
12107	  mips_opts.fp32 = 1;
12108	  break;
12109	case ISA_MIPS3:
12110	case ISA_MIPS4:
12111	case ISA_MIPS5:
12112	case ISA_MIPS64:
12113	case ISA_MIPS64R2:
12114	  mips_opts.gp32 = 0;
12115	  mips_opts.fp32 = 0;
12116	  break;
12117	default:
12118	  as_bad (_("unknown ISA level %s"), name + 4);
12119	  break;
12120	}
12121      if (reset)
12122	{
12123	  mips_opts.gp32 = file_mips_gp32;
12124	  mips_opts.fp32 = file_mips_fp32;
12125	}
12126    }
12127  else if (strcmp (name, "autoextend") == 0)
12128    mips_opts.noautoextend = 0;
12129  else if (strcmp (name, "noautoextend") == 0)
12130    mips_opts.noautoextend = 1;
12131  else if (strcmp (name, "push") == 0)
12132    {
12133      struct mips_option_stack *s;
12134
12135      s = (struct mips_option_stack *) xmalloc (sizeof *s);
12136      s->next = mips_opts_stack;
12137      s->options = mips_opts;
12138      mips_opts_stack = s;
12139    }
12140  else if (strcmp (name, "pop") == 0)
12141    {
12142      struct mips_option_stack *s;
12143
12144      s = mips_opts_stack;
12145      if (s == NULL)
12146	as_bad (_(".set pop with no .set push"));
12147      else
12148	{
12149	  /* If we're changing the reorder mode we need to handle
12150             delay slots correctly.  */
12151	  if (s->options.noreorder && ! mips_opts.noreorder)
12152	    start_noreorder ();
12153	  else if (! s->options.noreorder && mips_opts.noreorder)
12154	    end_noreorder ();
12155
12156	  mips_opts = s->options;
12157	  mips_opts_stack = s->next;
12158	  free (s);
12159	}
12160    }
12161  else if (strcmp (name, "sym32") == 0)
12162    mips_opts.sym32 = TRUE;
12163  else if (strcmp (name, "nosym32") == 0)
12164    mips_opts.sym32 = FALSE;
12165  else
12166    {
12167      as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12168    }
12169  *input_line_pointer = ch;
12170  demand_empty_rest_of_line ();
12171}
12172
12173/* Handle the .abicalls pseudo-op.  I believe this is equivalent to
12174   .option pic2.  It means to generate SVR4 PIC calls.  */
12175
12176static void
12177s_abicalls (int ignore ATTRIBUTE_UNUSED)
12178{
12179  mips_pic = SVR4_PIC;
12180  mips_abicalls = TRUE;
12181
12182  if (g_switch_seen && g_switch_value != 0)
12183    as_warn (_("-G may not be used with SVR4 PIC code"));
12184  g_switch_value = 0;
12185
12186  bfd_set_gp_size (stdoutput, 0);
12187  demand_empty_rest_of_line ();
12188}
12189
12190/* Handle the .cpload pseudo-op.  This is used when generating SVR4
12191   PIC code.  It sets the $gp register for the function based on the
12192   function address, which is in the register named in the argument.
12193   This uses a relocation against _gp_disp, which is handled specially
12194   by the linker.  The result is:
12195	lui	$gp,%hi(_gp_disp)
12196	addiu	$gp,$gp,%lo(_gp_disp)
12197	addu	$gp,$gp,.cpload argument
12198   The .cpload argument is normally $25 == $t9.
12199
12200   The -mno-shared option changes this to:
12201	lui	$gp,%hi(__gnu_local_gp)
12202	addiu	$gp,$gp,%lo(__gnu_local_gp)
12203   and the argument is ignored.  This saves an instruction, but the
12204   resulting code is not position independent; it uses an absolute
12205   address for __gnu_local_gp.  Thus code assembled with -mno-shared
12206   can go into an ordinary executable, but not into a shared library.  */
12207
12208static void
12209s_cpload (int ignore ATTRIBUTE_UNUSED)
12210{
12211  expressionS ex;
12212  int reg;
12213  int in_shared;
12214
12215  /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12216     .cpload is ignored.  */
12217  if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12218    {
12219      s_ignore (0);
12220      return;
12221    }
12222
12223  /* .cpload should be in a .set noreorder section.  */
12224  if (mips_opts.noreorder == 0)
12225    as_warn (_(".cpload not in noreorder section"));
12226
12227  reg = tc_get_register (0);
12228
12229  /* If we need to produce a 64-bit address, we are better off using
12230     the default instruction sequence.  */
12231  in_shared = mips_in_shared || HAVE_64BIT_SYMBOLS;
12232
12233  ex.X_op = O_symbol;
12234  ex.X_add_symbol = symbol_find_or_make (in_shared ? "_gp_disp" :
12235                                         "__gnu_local_gp");
12236  ex.X_op_symbol = NULL;
12237  ex.X_add_number = 0;
12238
12239  /* In ELF, this symbol is implicitly an STT_OBJECT symbol.  */
12240  symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12241
12242  macro_start ();
12243  macro_build_lui (&ex, mips_gp_register);
12244  macro_build (&ex, "addiu", "t,r,j", mips_gp_register,
12245	       mips_gp_register, BFD_RELOC_LO16);
12246  if (in_shared)
12247    macro_build (NULL, "addu", "d,v,t", mips_gp_register,
12248		 mips_gp_register, reg);
12249  macro_end ();
12250
12251  demand_empty_rest_of_line ();
12252}
12253
12254/* Handle the .cpsetup pseudo-op defined for NewABI PIC code.  The syntax is:
12255     .cpsetup $reg1, offset|$reg2, label
12256
12257   If offset is given, this results in:
12258     sd		$gp, offset($sp)
12259     lui	$gp, %hi(%neg(%gp_rel(label)))
12260     addiu	$gp, $gp, %lo(%neg(%gp_rel(label)))
12261     daddu	$gp, $gp, $reg1
12262
12263   If $reg2 is given, this results in:
12264     daddu	$reg2, $gp, $0
12265     lui	$gp, %hi(%neg(%gp_rel(label)))
12266     addiu	$gp, $gp, %lo(%neg(%gp_rel(label)))
12267     daddu	$gp, $gp, $reg1
12268   $reg1 is normally $25 == $t9.
12269
12270   The -mno-shared option replaces the last three instructions with
12271	lui	$gp,%hi(_gp)
12272	addiu	$gp,$gp,%lo(_gp)
12273   */
12274
12275static void
12276s_cpsetup (int ignore ATTRIBUTE_UNUSED)
12277{
12278  expressionS ex_off;
12279  expressionS ex_sym;
12280  int reg1;
12281
12282  /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12283     We also need NewABI support.  */
12284  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12285    {
12286      s_ignore (0);
12287      return;
12288    }
12289
12290  reg1 = tc_get_register (0);
12291  SKIP_WHITESPACE ();
12292  if (*input_line_pointer != ',')
12293    {
12294      as_bad (_("missing argument separator ',' for .cpsetup"));
12295      return;
12296    }
12297  else
12298    ++input_line_pointer;
12299  SKIP_WHITESPACE ();
12300  if (*input_line_pointer == '$')
12301    {
12302      mips_cpreturn_register = tc_get_register (0);
12303      mips_cpreturn_offset = -1;
12304    }
12305  else
12306    {
12307      mips_cpreturn_offset = get_absolute_expression ();
12308      mips_cpreturn_register = -1;
12309    }
12310  SKIP_WHITESPACE ();
12311  if (*input_line_pointer != ',')
12312    {
12313      as_bad (_("missing argument separator ',' for .cpsetup"));
12314      return;
12315    }
12316  else
12317    ++input_line_pointer;
12318  SKIP_WHITESPACE ();
12319  expression (&ex_sym);
12320
12321  macro_start ();
12322  if (mips_cpreturn_register == -1)
12323    {
12324      ex_off.X_op = O_constant;
12325      ex_off.X_add_symbol = NULL;
12326      ex_off.X_op_symbol = NULL;
12327      ex_off.X_add_number = mips_cpreturn_offset;
12328
12329      macro_build (&ex_off, "sd", "t,o(b)", mips_gp_register,
12330		   BFD_RELOC_LO16, SP);
12331    }
12332  else
12333    macro_build (NULL, "daddu", "d,v,t", mips_cpreturn_register,
12334		 mips_gp_register, 0);
12335
12336  if (mips_in_shared || HAVE_64BIT_SYMBOLS)
12337    {
12338      macro_build (&ex_sym, "lui", "t,u", mips_gp_register,
12339		   -1, BFD_RELOC_GPREL16, BFD_RELOC_MIPS_SUB,
12340		   BFD_RELOC_HI16_S);
12341
12342      macro_build (&ex_sym, "addiu", "t,r,j", mips_gp_register,
12343		   mips_gp_register, -1, BFD_RELOC_GPREL16,
12344		   BFD_RELOC_MIPS_SUB, BFD_RELOC_LO16);
12345
12346      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", mips_gp_register,
12347		   mips_gp_register, reg1);
12348    }
12349  else
12350    {
12351      expressionS ex;
12352
12353      ex.X_op = O_symbol;
12354      ex.X_add_symbol = symbol_find_or_make ("__gnu_local_gp");
12355      ex.X_op_symbol = NULL;
12356      ex.X_add_number = 0;
12357
12358      /* In ELF, this symbol is implicitly an STT_OBJECT symbol.  */
12359      symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12360
12361      macro_build_lui (&ex, mips_gp_register);
12362      macro_build (&ex, "addiu", "t,r,j", mips_gp_register,
12363		   mips_gp_register, BFD_RELOC_LO16);
12364    }
12365
12366  macro_end ();
12367
12368  demand_empty_rest_of_line ();
12369}
12370
12371static void
12372s_cplocal (int ignore ATTRIBUTE_UNUSED)
12373{
12374  /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12375   .cplocal is ignored.  */
12376  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12377    {
12378      s_ignore (0);
12379      return;
12380    }
12381
12382  mips_gp_register = tc_get_register (0);
12383  demand_empty_rest_of_line ();
12384}
12385
12386/* Handle the .cprestore pseudo-op.  This stores $gp into a given
12387   offset from $sp.  The offset is remembered, and after making a PIC
12388   call $gp is restored from that location.  */
12389
12390static void
12391s_cprestore (int ignore ATTRIBUTE_UNUSED)
12392{
12393  expressionS ex;
12394
12395  /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12396     .cprestore is ignored.  */
12397  if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12398    {
12399      s_ignore (0);
12400      return;
12401    }
12402
12403  mips_cprestore_offset = get_absolute_expression ();
12404  mips_cprestore_valid = 1;
12405
12406  ex.X_op = O_constant;
12407  ex.X_add_symbol = NULL;
12408  ex.X_op_symbol = NULL;
12409  ex.X_add_number = mips_cprestore_offset;
12410
12411  macro_start ();
12412  macro_build_ldst_constoffset (&ex, ADDRESS_STORE_INSN, mips_gp_register,
12413				SP, HAVE_64BIT_ADDRESSES);
12414  macro_end ();
12415
12416  demand_empty_rest_of_line ();
12417}
12418
12419/* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12420   was given in the preceding .cpsetup, it results in:
12421     ld		$gp, offset($sp)
12422
12423   If a register $reg2 was given there, it results in:
12424     daddu	$gp, $reg2, $0
12425 */
12426static void
12427s_cpreturn (int ignore ATTRIBUTE_UNUSED)
12428{
12429  expressionS ex;
12430
12431  /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12432     We also need NewABI support.  */
12433  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12434    {
12435      s_ignore (0);
12436      return;
12437    }
12438
12439  macro_start ();
12440  if (mips_cpreturn_register == -1)
12441    {
12442      ex.X_op = O_constant;
12443      ex.X_add_symbol = NULL;
12444      ex.X_op_symbol = NULL;
12445      ex.X_add_number = mips_cpreturn_offset;
12446
12447      macro_build (&ex, "ld", "t,o(b)", mips_gp_register, BFD_RELOC_LO16, SP);
12448    }
12449  else
12450    macro_build (NULL, "daddu", "d,v,t", mips_gp_register,
12451		 mips_cpreturn_register, 0);
12452  macro_end ();
12453
12454  demand_empty_rest_of_line ();
12455}
12456
12457/* Handle the .gpvalue pseudo-op.  This is used when generating NewABI PIC
12458   code.  It sets the offset to use in gp_rel relocations.  */
12459
12460static void
12461s_gpvalue (int ignore ATTRIBUTE_UNUSED)
12462{
12463  /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12464     We also need NewABI support.  */
12465  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12466    {
12467      s_ignore (0);
12468      return;
12469    }
12470
12471  mips_gprel_offset = get_absolute_expression ();
12472
12473  demand_empty_rest_of_line ();
12474}
12475
12476/* Handle the .gpword pseudo-op.  This is used when generating PIC
12477   code.  It generates a 32 bit GP relative reloc.  */
12478
12479static void
12480s_gpword (int ignore ATTRIBUTE_UNUSED)
12481{
12482  symbolS *label;
12483  expressionS ex;
12484  char *p;
12485
12486  /* When not generating PIC code, this is treated as .word.  */
12487  if (mips_pic != SVR4_PIC)
12488    {
12489      s_cons (2);
12490      return;
12491    }
12492
12493  label = insn_labels != NULL ? insn_labels->label : NULL;
12494  mips_emit_delays ();
12495  if (auto_align)
12496    mips_align (2, 0, label);
12497  mips_clear_insn_labels ();
12498
12499  expression (&ex);
12500
12501  if (ex.X_op != O_symbol || ex.X_add_number != 0)
12502    {
12503      as_bad (_("Unsupported use of .gpword"));
12504      ignore_rest_of_line ();
12505    }
12506
12507  p = frag_more (4);
12508  md_number_to_chars (p, 0, 4);
12509  fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12510	       BFD_RELOC_GPREL32);
12511
12512  demand_empty_rest_of_line ();
12513}
12514
12515static void
12516s_gpdword (int ignore ATTRIBUTE_UNUSED)
12517{
12518  symbolS *label;
12519  expressionS ex;
12520  char *p;
12521
12522  /* When not generating PIC code, this is treated as .dword.  */
12523  if (mips_pic != SVR4_PIC)
12524    {
12525      s_cons (3);
12526      return;
12527    }
12528
12529  label = insn_labels != NULL ? insn_labels->label : NULL;
12530  mips_emit_delays ();
12531  if (auto_align)
12532    mips_align (3, 0, label);
12533  mips_clear_insn_labels ();
12534
12535  expression (&ex);
12536
12537  if (ex.X_op != O_symbol || ex.X_add_number != 0)
12538    {
12539      as_bad (_("Unsupported use of .gpdword"));
12540      ignore_rest_of_line ();
12541    }
12542
12543  p = frag_more (8);
12544  md_number_to_chars (p, 0, 8);
12545  fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12546	       BFD_RELOC_GPREL32)->fx_tcbit = 1;
12547
12548  /* GPREL32 composed with 64 gives a 64-bit GP offset.  */
12549  fix_new (frag_now, p - frag_now->fr_literal, 8, NULL, 0,
12550	   FALSE, BFD_RELOC_64)->fx_tcbit = 1;
12551
12552  demand_empty_rest_of_line ();
12553}
12554
12555/* Handle the .cpadd pseudo-op.  This is used when dealing with switch
12556   tables in SVR4 PIC code.  */
12557
12558static void
12559s_cpadd (int ignore ATTRIBUTE_UNUSED)
12560{
12561  int reg;
12562
12563  /* This is ignored when not generating SVR4 PIC code.  */
12564  if (mips_pic != SVR4_PIC)
12565    {
12566      s_ignore (0);
12567      return;
12568    }
12569
12570  /* Add $gp to the register named as an argument.  */
12571  macro_start ();
12572  reg = tc_get_register (0);
12573  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", reg, reg, mips_gp_register);
12574  macro_end ();
12575
12576  demand_empty_rest_of_line ();
12577}
12578
12579/* Handle the .insn pseudo-op.  This marks instruction labels in
12580   mips16 mode.  This permits the linker to handle them specially,
12581   such as generating jalx instructions when needed.  We also make
12582   them odd for the duration of the assembly, in order to generate the
12583   right sort of code.  We will make them even in the adjust_symtab
12584   routine, while leaving them marked.  This is convenient for the
12585   debugger and the disassembler.  The linker knows to make them odd
12586   again.  */
12587
12588static void
12589s_insn (int ignore ATTRIBUTE_UNUSED)
12590{
12591  mips16_mark_labels ();
12592
12593  demand_empty_rest_of_line ();
12594}
12595
12596/* Handle a .stabn directive.  We need these in order to mark a label
12597   as being a mips16 text label correctly.  Sometimes the compiler
12598   will emit a label, followed by a .stabn, and then switch sections.
12599   If the label and .stabn are in mips16 mode, then the label is
12600   really a mips16 text label.  */
12601
12602static void
12603s_mips_stab (int type)
12604{
12605  if (type == 'n')
12606    mips16_mark_labels ();
12607
12608  s_stab (type);
12609}
12610
12611/* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12612 */
12613
12614static void
12615s_mips_weakext (int ignore ATTRIBUTE_UNUSED)
12616{
12617  char *name;
12618  int c;
12619  symbolS *symbolP;
12620  expressionS exp;
12621
12622  name = input_line_pointer;
12623  c = get_symbol_end ();
12624  symbolP = symbol_find_or_make (name);
12625  S_SET_WEAK (symbolP);
12626  *input_line_pointer = c;
12627
12628  SKIP_WHITESPACE ();
12629
12630  if (! is_end_of_line[(unsigned char) *input_line_pointer])
12631    {
12632      if (S_IS_DEFINED (symbolP))
12633	{
12634	  as_bad ("ignoring attempt to redefine symbol %s",
12635		  S_GET_NAME (symbolP));
12636	  ignore_rest_of_line ();
12637	  return;
12638	}
12639
12640      if (*input_line_pointer == ',')
12641	{
12642	  ++input_line_pointer;
12643	  SKIP_WHITESPACE ();
12644	}
12645
12646      expression (&exp);
12647      if (exp.X_op != O_symbol)
12648	{
12649	  as_bad ("bad .weakext directive");
12650	  ignore_rest_of_line ();
12651	  return;
12652	}
12653      symbol_set_value_expression (symbolP, &exp);
12654    }
12655
12656  demand_empty_rest_of_line ();
12657}
12658
12659/* Parse a register string into a number.  Called from the ECOFF code
12660   to parse .frame.  The argument is non-zero if this is the frame
12661   register, so that we can record it in mips_frame_reg.  */
12662
12663int
12664tc_get_register (int frame)
12665{
12666  int reg;
12667
12668  SKIP_WHITESPACE ();
12669  if (*input_line_pointer++ != '$')
12670    {
12671      as_warn (_("expected `$'"));
12672      reg = ZERO;
12673    }
12674  else if (ISDIGIT (*input_line_pointer))
12675    {
12676      reg = get_absolute_expression ();
12677      if (reg < 0 || reg >= 32)
12678	{
12679	  as_warn (_("Bad register number"));
12680	  reg = ZERO;
12681	}
12682    }
12683  else
12684    {
12685      if (strncmp (input_line_pointer, "ra", 2) == 0)
12686	{
12687	  reg = RA;
12688	  input_line_pointer += 2;
12689	}
12690      else if (strncmp (input_line_pointer, "fp", 2) == 0)
12691	{
12692	  reg = FP;
12693	  input_line_pointer += 2;
12694	}
12695      else if (strncmp (input_line_pointer, "sp", 2) == 0)
12696	{
12697	  reg = SP;
12698	  input_line_pointer += 2;
12699	}
12700      else if (strncmp (input_line_pointer, "gp", 2) == 0)
12701	{
12702	  reg = GP;
12703	  input_line_pointer += 2;
12704	}
12705      else if (strncmp (input_line_pointer, "at", 2) == 0)
12706	{
12707	  reg = AT;
12708	  input_line_pointer += 2;
12709	}
12710      else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12711	{
12712	  reg = KT0;
12713	  input_line_pointer += 3;
12714	}
12715      else if (strncmp (input_line_pointer, "kt1", 3) == 0)
12716	{
12717	  reg = KT1;
12718	  input_line_pointer += 3;
12719	}
12720      else if (strncmp (input_line_pointer, "zero", 4) == 0)
12721	{
12722	  reg = ZERO;
12723	  input_line_pointer += 4;
12724	}
12725      else
12726	{
12727	  as_warn (_("Unrecognized register name"));
12728	  reg = ZERO;
12729	  while (ISALNUM(*input_line_pointer))
12730	   input_line_pointer++;
12731	}
12732    }
12733  if (frame)
12734    {
12735      mips_frame_reg = reg != 0 ? reg : SP;
12736      mips_frame_reg_valid = 1;
12737      mips_cprestore_valid = 0;
12738    }
12739  return reg;
12740}
12741
12742valueT
12743md_section_align (asection *seg, valueT addr)
12744{
12745  int align = bfd_get_section_alignment (stdoutput, seg);
12746
12747#ifdef OBJ_ELF
12748  /* We don't need to align ELF sections to the full alignment.
12749     However, Irix 5 may prefer that we align them at least to a 16
12750     byte boundary.  We don't bother to align the sections if we are
12751     targeted for an embedded system.  */
12752  if (strcmp (TARGET_OS, "elf") == 0)
12753    return addr;
12754  if (align > 4)
12755    align = 4;
12756#endif
12757
12758  return ((addr + (1 << align) - 1) & (-1 << align));
12759}
12760
12761/* Utility routine, called from above as well.  If called while the
12762   input file is still being read, it's only an approximation.  (For
12763   example, a symbol may later become defined which appeared to be
12764   undefined earlier.)  */
12765
12766static int
12767nopic_need_relax (symbolS *sym, int before_relaxing)
12768{
12769  if (sym == 0)
12770    return 0;
12771
12772  if (g_switch_value > 0)
12773    {
12774      const char *symname;
12775      int change;
12776
12777      /* Find out whether this symbol can be referenced off the $gp
12778	 register.  It can be if it is smaller than the -G size or if
12779	 it is in the .sdata or .sbss section.  Certain symbols can
12780	 not be referenced off the $gp, although it appears as though
12781	 they can.  */
12782      symname = S_GET_NAME (sym);
12783      if (symname != (const char *) NULL
12784	  && (strcmp (symname, "eprol") == 0
12785	      || strcmp (symname, "etext") == 0
12786	      || strcmp (symname, "_gp") == 0
12787	      || strcmp (symname, "edata") == 0
12788	      || strcmp (symname, "_fbss") == 0
12789	      || strcmp (symname, "_fdata") == 0
12790	      || strcmp (symname, "_ftext") == 0
12791	      || strcmp (symname, "end") == 0
12792	      || strcmp (symname, "_gp_disp") == 0))
12793	change = 1;
12794      else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
12795	       && (0
12796#ifndef NO_ECOFF_DEBUGGING
12797		   || (symbol_get_obj (sym)->ecoff_extern_size != 0
12798		       && (symbol_get_obj (sym)->ecoff_extern_size
12799			   <= g_switch_value))
12800#endif
12801		   /* We must defer this decision until after the whole
12802		      file has been read, since there might be a .extern
12803		      after the first use of this symbol.  */
12804		   || (before_relaxing
12805#ifndef NO_ECOFF_DEBUGGING
12806		       && symbol_get_obj (sym)->ecoff_extern_size == 0
12807#endif
12808		       && S_GET_VALUE (sym) == 0)
12809		   || (S_GET_VALUE (sym) != 0
12810		       && S_GET_VALUE (sym) <= g_switch_value)))
12811	change = 0;
12812      else
12813	{
12814	  const char *segname;
12815
12816	  segname = segment_name (S_GET_SEGMENT (sym));
12817	  assert (strcmp (segname, ".lit8") != 0
12818		  && strcmp (segname, ".lit4") != 0);
12819	  change = (strcmp (segname, ".sdata") != 0
12820		    && strcmp (segname, ".sbss") != 0
12821		    && strncmp (segname, ".sdata.", 7) != 0
12822		    && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
12823	}
12824      return change;
12825    }
12826  else
12827    /* We are not optimizing for the $gp register.  */
12828    return 1;
12829}
12830
12831
12832/* Return true if the given symbol should be considered local for SVR4 PIC.  */
12833
12834static bfd_boolean
12835pic_need_relax (symbolS *sym, asection *segtype)
12836{
12837  asection *symsec;
12838  bfd_boolean linkonce;
12839
12840  /* Handle the case of a symbol equated to another symbol.  */
12841  while (symbol_equated_reloc_p (sym))
12842    {
12843      symbolS *n;
12844
12845      /* It's possible to get a loop here in a badly written
12846	 program.  */
12847      n = symbol_get_value_expression (sym)->X_add_symbol;
12848      if (n == sym)
12849	break;
12850      sym = n;
12851    }
12852
12853  symsec = S_GET_SEGMENT (sym);
12854
12855  /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
12856  linkonce = FALSE;
12857  if (symsec != segtype && ! S_IS_LOCAL (sym))
12858    {
12859      if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
12860	  != 0)
12861	linkonce = TRUE;
12862
12863      /* The GNU toolchain uses an extension for ELF: a section
12864	 beginning with the magic string .gnu.linkonce is a linkonce
12865	 section.  */
12866      if (strncmp (segment_name (symsec), ".gnu.linkonce",
12867		   sizeof ".gnu.linkonce" - 1) == 0)
12868	linkonce = TRUE;
12869    }
12870
12871  /* This must duplicate the test in adjust_reloc_syms.  */
12872  return (symsec != &bfd_und_section
12873	  && symsec != &bfd_abs_section
12874	  && ! bfd_is_com_section (symsec)
12875	  && !linkonce
12876#ifdef OBJ_ELF
12877	  /* A global or weak symbol is treated as external.  */
12878	  && (OUTPUT_FLAVOR != bfd_target_elf_flavour
12879	      || (! S_IS_WEAK (sym) && ! S_IS_EXTERNAL (sym)))
12880#endif
12881	  );
12882}
12883
12884
12885/* Given a mips16 variant frag FRAGP, return non-zero if it needs an
12886   extended opcode.  SEC is the section the frag is in.  */
12887
12888static int
12889mips16_extended_frag (fragS *fragp, asection *sec, long stretch)
12890{
12891  int type;
12892  register const struct mips16_immed_operand *op;
12893  offsetT val;
12894  int mintiny, maxtiny;
12895  segT symsec;
12896  fragS *sym_frag;
12897
12898  if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
12899    return 0;
12900  if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
12901    return 1;
12902
12903  type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
12904  op = mips16_immed_operands;
12905  while (op->type != type)
12906    {
12907      ++op;
12908      assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
12909    }
12910
12911  if (op->unsp)
12912    {
12913      if (type == '<' || type == '>' || type == '[' || type == ']')
12914	{
12915	  mintiny = 1;
12916	  maxtiny = 1 << op->nbits;
12917	}
12918      else
12919	{
12920	  mintiny = 0;
12921	  maxtiny = (1 << op->nbits) - 1;
12922	}
12923    }
12924  else
12925    {
12926      mintiny = - (1 << (op->nbits - 1));
12927      maxtiny = (1 << (op->nbits - 1)) - 1;
12928    }
12929
12930  sym_frag = symbol_get_frag (fragp->fr_symbol);
12931  val = S_GET_VALUE (fragp->fr_symbol);
12932  symsec = S_GET_SEGMENT (fragp->fr_symbol);
12933
12934  if (op->pcrel)
12935    {
12936      addressT addr;
12937
12938      /* We won't have the section when we are called from
12939         mips_relax_frag.  However, we will always have been called
12940         from md_estimate_size_before_relax first.  If this is a
12941         branch to a different section, we mark it as such.  If SEC is
12942         NULL, and the frag is not marked, then it must be a branch to
12943         the same section.  */
12944      if (sec == NULL)
12945	{
12946	  if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
12947	    return 1;
12948	}
12949      else
12950	{
12951	  /* Must have been called from md_estimate_size_before_relax.  */
12952	  if (symsec != sec)
12953	    {
12954	      fragp->fr_subtype =
12955		RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12956
12957	      /* FIXME: We should support this, and let the linker
12958                 catch branches and loads that are out of range.  */
12959	      as_bad_where (fragp->fr_file, fragp->fr_line,
12960			    _("unsupported PC relative reference to different section"));
12961
12962	      return 1;
12963	    }
12964	  if (fragp != sym_frag && sym_frag->fr_address == 0)
12965	    /* Assume non-extended on the first relaxation pass.
12966	       The address we have calculated will be bogus if this is
12967	       a forward branch to another frag, as the forward frag
12968	       will have fr_address == 0.  */
12969	    return 0;
12970	}
12971
12972      /* In this case, we know for sure that the symbol fragment is in
12973	 the same section.  If the relax_marker of the symbol fragment
12974	 differs from the relax_marker of this fragment, we have not
12975	 yet adjusted the symbol fragment fr_address.  We want to add
12976	 in STRETCH in order to get a better estimate of the address.
12977	 This particularly matters because of the shift bits.  */
12978      if (stretch != 0
12979	  && sym_frag->relax_marker != fragp->relax_marker)
12980	{
12981	  fragS *f;
12982
12983	  /* Adjust stretch for any alignment frag.  Note that if have
12984             been expanding the earlier code, the symbol may be
12985             defined in what appears to be an earlier frag.  FIXME:
12986             This doesn't handle the fr_subtype field, which specifies
12987             a maximum number of bytes to skip when doing an
12988             alignment.  */
12989	  for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
12990	    {
12991	      if (f->fr_type == rs_align || f->fr_type == rs_align_code)
12992		{
12993		  if (stretch < 0)
12994		    stretch = - ((- stretch)
12995				 & ~ ((1 << (int) f->fr_offset) - 1));
12996		  else
12997		    stretch &= ~ ((1 << (int) f->fr_offset) - 1);
12998		  if (stretch == 0)
12999		    break;
13000		}
13001	    }
13002	  if (f != NULL)
13003	    val += stretch;
13004	}
13005
13006      addr = fragp->fr_address + fragp->fr_fix;
13007
13008      /* The base address rules are complicated.  The base address of
13009         a branch is the following instruction.  The base address of a
13010         PC relative load or add is the instruction itself, but if it
13011         is in a delay slot (in which case it can not be extended) use
13012         the address of the instruction whose delay slot it is in.  */
13013      if (type == 'p' || type == 'q')
13014	{
13015	  addr += 2;
13016
13017	  /* If we are currently assuming that this frag should be
13018	     extended, then, the current address is two bytes
13019	     higher.  */
13020	  if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13021	    addr += 2;
13022
13023	  /* Ignore the low bit in the target, since it will be set
13024             for a text label.  */
13025	  if ((val & 1) != 0)
13026	    --val;
13027	}
13028      else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13029	addr -= 4;
13030      else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13031	addr -= 2;
13032
13033      val -= addr & ~ ((1 << op->shift) - 1);
13034
13035      /* Branch offsets have an implicit 0 in the lowest bit.  */
13036      if (type == 'p' || type == 'q')
13037	val /= 2;
13038
13039      /* If any of the shifted bits are set, we must use an extended
13040         opcode.  If the address depends on the size of this
13041         instruction, this can lead to a loop, so we arrange to always
13042         use an extended opcode.  We only check this when we are in
13043         the main relaxation loop, when SEC is NULL.  */
13044      if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
13045	{
13046	  fragp->fr_subtype =
13047	    RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13048	  return 1;
13049	}
13050
13051      /* If we are about to mark a frag as extended because the value
13052         is precisely maxtiny + 1, then there is a chance of an
13053         infinite loop as in the following code:
13054	     la	$4,foo
13055	     .skip	1020
13056	     .align	2
13057	   foo:
13058	 In this case when the la is extended, foo is 0x3fc bytes
13059	 away, so the la can be shrunk, but then foo is 0x400 away, so
13060	 the la must be extended.  To avoid this loop, we mark the
13061	 frag as extended if it was small, and is about to become
13062	 extended with a value of maxtiny + 1.  */
13063      if (val == ((maxtiny + 1) << op->shift)
13064	  && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
13065	  && sec == NULL)
13066	{
13067	  fragp->fr_subtype =
13068	    RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13069	  return 1;
13070	}
13071    }
13072  else if (symsec != absolute_section && sec != NULL)
13073    as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
13074
13075  if ((val & ((1 << op->shift) - 1)) != 0
13076      || val < (mintiny << op->shift)
13077      || val > (maxtiny << op->shift))
13078    return 1;
13079  else
13080    return 0;
13081}
13082
13083/* Compute the length of a branch sequence, and adjust the
13084   RELAX_BRANCH_TOOFAR bit accordingly.  If FRAGP is NULL, the
13085   worst-case length is computed, with UPDATE being used to indicate
13086   whether an unconditional (-1), branch-likely (+1) or regular (0)
13087   branch is to be computed.  */
13088static int
13089relaxed_branch_length (fragS *fragp, asection *sec, int update)
13090{
13091  bfd_boolean toofar;
13092  int length;
13093
13094  if (fragp
13095      && S_IS_DEFINED (fragp->fr_symbol)
13096      && sec == S_GET_SEGMENT (fragp->fr_symbol))
13097    {
13098      addressT addr;
13099      offsetT val;
13100
13101      val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13102
13103      addr = fragp->fr_address + fragp->fr_fix + 4;
13104
13105      val -= addr;
13106
13107      toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13108    }
13109  else if (fragp)
13110    /* If the symbol is not defined or it's in a different segment,
13111       assume the user knows what's going on and emit a short
13112       branch.  */
13113    toofar = FALSE;
13114  else
13115    toofar = TRUE;
13116
13117  if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13118    fragp->fr_subtype
13119      = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13120			     RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13121			     RELAX_BRANCH_LINK (fragp->fr_subtype),
13122			     toofar);
13123
13124  length = 4;
13125  if (toofar)
13126    {
13127      if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13128	length += 8;
13129
13130      if (mips_pic != NO_PIC)
13131	{
13132	  /* Additional space for PIC loading of target address.  */
13133	  length += 8;
13134	  if (mips_opts.isa == ISA_MIPS1)
13135	    /* Additional space for $at-stabilizing nop.  */
13136	    length += 4;
13137	}
13138
13139      /* If branch is conditional.  */
13140      if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13141	length += 8;
13142    }
13143
13144  return length;
13145}
13146
13147/* Estimate the size of a frag before relaxing.  Unless this is the
13148   mips16, we are not really relaxing here, and the final size is
13149   encoded in the subtype information.  For the mips16, we have to
13150   decide whether we are using an extended opcode or not.  */
13151
13152int
13153md_estimate_size_before_relax (fragS *fragp, asection *segtype)
13154{
13155  int change;
13156
13157  if (RELAX_BRANCH_P (fragp->fr_subtype))
13158    {
13159
13160      fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13161
13162      return fragp->fr_var;
13163    }
13164
13165  if (RELAX_MIPS16_P (fragp->fr_subtype))
13166    /* We don't want to modify the EXTENDED bit here; it might get us
13167       into infinite loops.  We change it only in mips_relax_frag().  */
13168    return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13169
13170  if (mips_pic == NO_PIC)
13171    change = nopic_need_relax (fragp->fr_symbol, 0);
13172  else if (mips_pic == SVR4_PIC)
13173    change = pic_need_relax (fragp->fr_symbol, segtype);
13174  else if (mips_pic == VXWORKS_PIC)
13175    /* For vxworks, GOT16 relocations never have a corresponding LO16.  */
13176    change = 0;
13177  else
13178    abort ();
13179
13180  if (change)
13181    {
13182      fragp->fr_subtype |= RELAX_USE_SECOND;
13183      return -RELAX_FIRST (fragp->fr_subtype);
13184    }
13185  else
13186    return -RELAX_SECOND (fragp->fr_subtype);
13187}
13188
13189/* This is called to see whether a reloc against a defined symbol
13190   should be converted into a reloc against a section.  */
13191
13192int
13193mips_fix_adjustable (fixS *fixp)
13194{
13195  /* Don't adjust MIPS16 jump relocations, so we don't have to worry
13196     about the format of the offset in the .o file. */
13197  if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13198    return 0;
13199
13200  if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13201      || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13202    return 0;
13203
13204  if (fixp->fx_addsy == NULL)
13205    return 1;
13206
13207  /* If symbol SYM is in a mergeable section, relocations of the form
13208     SYM + 0 can usually be made section-relative.  The mergeable data
13209     is then identified by the section offset rather than by the symbol.
13210
13211     However, if we're generating REL LO16 relocations, the offset is split
13212     between the LO16 and parterning high part relocation.  The linker will
13213     need to recalculate the complete offset in order to correctly identify
13214     the merge data.
13215
13216     The linker has traditionally not looked for the parterning high part
13217     relocation, and has thus allowed orphaned R_MIPS_LO16 relocations to be
13218     placed anywhere.  Rather than break backwards compatibility by changing
13219     this, it seems better not to force the issue, and instead keep the
13220     original symbol.  This will work with either linker behavior.  */
13221  if ((fixp->fx_r_type == BFD_RELOC_LO16
13222       || fixp->fx_r_type == BFD_RELOC_MIPS16_LO16
13223       || reloc_needs_lo_p (fixp->fx_r_type))
13224      && HAVE_IN_PLACE_ADDENDS
13225      && (S_GET_SEGMENT (fixp->fx_addsy)->flags & SEC_MERGE) != 0)
13226    return 0;
13227
13228#ifdef OBJ_ELF
13229  /* Don't adjust relocations against mips16 symbols, so that the linker
13230     can find them if it needs to set up a stub.  */
13231  if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13232      && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13233      && fixp->fx_subsy == NULL)
13234    return 0;
13235#endif
13236
13237  return 1;
13238}
13239
13240/* Translate internal representation of relocation info to BFD target
13241   format.  */
13242
13243arelent **
13244tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixp)
13245{
13246  static arelent *retval[4];
13247  arelent *reloc;
13248  bfd_reloc_code_real_type code;
13249
13250  memset (retval, 0, sizeof(retval));
13251  reloc = retval[0] = (arelent *) xcalloc (1, sizeof (arelent));
13252  reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13253  *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13254  reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13255
13256  if (fixp->fx_pcrel)
13257    {
13258      assert (fixp->fx_r_type == BFD_RELOC_16_PCREL_S2);
13259
13260      /* At this point, fx_addnumber is "symbol offset - pcrel address".
13261	 Relocations want only the symbol offset.  */
13262      reloc->addend = fixp->fx_addnumber + reloc->address;
13263      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13264	{
13265	  /* A gruesome hack which is a result of the gruesome gas
13266	     reloc handling.  What's worse, for COFF (as opposed to
13267	     ECOFF), we might need yet another copy of reloc->address.
13268	     See bfd_install_relocation.  */
13269	  reloc->addend += reloc->address;
13270	}
13271    }
13272  else
13273    reloc->addend = fixp->fx_addnumber;
13274
13275  /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13276     entry to be used in the relocation's section offset.  */
13277  if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13278    {
13279      reloc->address = reloc->addend;
13280      reloc->addend = 0;
13281    }
13282
13283  code = fixp->fx_r_type;
13284
13285  reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13286  if (reloc->howto == NULL)
13287    {
13288      as_bad_where (fixp->fx_file, fixp->fx_line,
13289		    _("Can not represent %s relocation in this object file format"),
13290		    bfd_get_reloc_code_name (code));
13291      retval[0] = NULL;
13292    }
13293
13294  return retval;
13295}
13296
13297/* Relax a machine dependent frag.  This returns the amount by which
13298   the current size of the frag should change.  */
13299
13300int
13301mips_relax_frag (asection *sec, fragS *fragp, long stretch)
13302{
13303  if (RELAX_BRANCH_P (fragp->fr_subtype))
13304    {
13305      offsetT old_var = fragp->fr_var;
13306
13307      fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13308
13309      return fragp->fr_var - old_var;
13310    }
13311
13312  if (! RELAX_MIPS16_P (fragp->fr_subtype))
13313    return 0;
13314
13315  if (mips16_extended_frag (fragp, NULL, stretch))
13316    {
13317      if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13318	return 0;
13319      fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13320      return 2;
13321    }
13322  else
13323    {
13324      if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13325	return 0;
13326      fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13327      return -2;
13328    }
13329
13330  return 0;
13331}
13332
13333/* Convert a machine dependent frag.  */
13334
13335void
13336md_convert_frag (bfd *abfd ATTRIBUTE_UNUSED, segT asec, fragS *fragp)
13337{
13338  if (RELAX_BRANCH_P (fragp->fr_subtype))
13339    {
13340      bfd_byte *buf;
13341      unsigned long insn;
13342      expressionS exp;
13343      fixS *fixp;
13344
13345      buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13346
13347      if (target_big_endian)
13348	insn = bfd_getb32 (buf);
13349      else
13350	insn = bfd_getl32 (buf);
13351
13352      if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13353	{
13354	  /* We generate a fixup instead of applying it right now
13355	     because, if there are linker relaxations, we're going to
13356	     need the relocations.  */
13357	  exp.X_op = O_symbol;
13358	  exp.X_add_symbol = fragp->fr_symbol;
13359	  exp.X_add_number = fragp->fr_offset;
13360
13361	  fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13362			      4, &exp, 1, BFD_RELOC_16_PCREL_S2);
13363	  fixp->fx_file = fragp->fr_file;
13364	  fixp->fx_line = fragp->fr_line;
13365
13366	  md_number_to_chars ((char *) buf, insn, 4);
13367	  buf += 4;
13368	}
13369      else
13370	{
13371	  int i;
13372
13373	  as_warn_where (fragp->fr_file, fragp->fr_line,
13374			 _("relaxed out-of-range branch into a jump"));
13375
13376	  if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13377	    goto uncond;
13378
13379	  if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13380	    {
13381	      /* Reverse the branch.  */
13382	      switch ((insn >> 28) & 0xf)
13383		{
13384		case 4:
13385		  /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13386		     have the condition reversed by tweaking a single
13387		     bit, and their opcodes all have 0x4???????.  */
13388		  assert ((insn & 0xf1000000) == 0x41000000);
13389		  insn ^= 0x00010000;
13390		  break;
13391
13392		case 0:
13393		  /* bltz	0x04000000	bgez	0x04010000
13394		     bltzal	0x04100000	bgezal	0x04110000 */
13395		  assert ((insn & 0xfc0e0000) == 0x04000000);
13396		  insn ^= 0x00010000;
13397		  break;
13398
13399		case 1:
13400		  /* beq	0x10000000	bne	0x14000000
13401		     blez	0x18000000	bgtz	0x1c000000 */
13402		  insn ^= 0x04000000;
13403		  break;
13404
13405		default:
13406		  abort ();
13407		}
13408	    }
13409
13410	  if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13411	    {
13412	      /* Clear the and-link bit.  */
13413	      assert ((insn & 0xfc1c0000) == 0x04100000);
13414
13415	      /* bltzal	0x04100000	bgezal	0x04110000
13416		bltzall	0x04120000     bgezall	0x04130000 */
13417	      insn &= ~0x00100000;
13418	    }
13419
13420	  /* Branch over the branch (if the branch was likely) or the
13421	     full jump (not likely case).  Compute the offset from the
13422	     current instruction to branch to.  */
13423	  if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13424	    i = 16;
13425	  else
13426	    {
13427	      /* How many bytes in instructions we've already emitted?  */
13428	      i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13429	      /* How many bytes in instructions from here to the end?  */
13430	      i = fragp->fr_var - i;
13431	    }
13432	  /* Convert to instruction count.  */
13433	  i >>= 2;
13434	  /* Branch counts from the next instruction.  */
13435	  i--;
13436	  insn |= i;
13437	  /* Branch over the jump.  */
13438	  md_number_to_chars ((char *) buf, insn, 4);
13439	  buf += 4;
13440
13441	  /* Nop */
13442	  md_number_to_chars ((char *) buf, 0, 4);
13443	  buf += 4;
13444
13445	  if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13446	    {
13447	      /* beql $0, $0, 2f */
13448	      insn = 0x50000000;
13449	      /* Compute the PC offset from the current instruction to
13450		 the end of the variable frag.  */
13451	      /* How many bytes in instructions we've already emitted?  */
13452	      i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13453	      /* How many bytes in instructions from here to the end?  */
13454	      i = fragp->fr_var - i;
13455	      /* Convert to instruction count.  */
13456	      i >>= 2;
13457	      /* Don't decrement i, because we want to branch over the
13458		 delay slot.  */
13459
13460	      insn |= i;
13461	      md_number_to_chars ((char *) buf, insn, 4);
13462	      buf += 4;
13463
13464	      md_number_to_chars ((char *) buf, 0, 4);
13465	      buf += 4;
13466	    }
13467
13468	uncond:
13469	  if (mips_pic == NO_PIC)
13470	    {
13471	      /* j or jal.  */
13472	      insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13473		      ? 0x0c000000 : 0x08000000);
13474	      exp.X_op = O_symbol;
13475	      exp.X_add_symbol = fragp->fr_symbol;
13476	      exp.X_add_number = fragp->fr_offset;
13477
13478	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13479				  4, &exp, 0, BFD_RELOC_MIPS_JMP);
13480	      fixp->fx_file = fragp->fr_file;
13481	      fixp->fx_line = fragp->fr_line;
13482
13483	      md_number_to_chars ((char *) buf, insn, 4);
13484	      buf += 4;
13485	    }
13486	  else
13487	    {
13488	      /* lw/ld $at, <sym>($gp)  R_MIPS_GOT16 */
13489	      insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13490	      exp.X_op = O_symbol;
13491	      exp.X_add_symbol = fragp->fr_symbol;
13492	      exp.X_add_number = fragp->fr_offset;
13493
13494	      if (fragp->fr_offset)
13495		{
13496		  exp.X_add_symbol = make_expr_symbol (&exp);
13497		  exp.X_add_number = 0;
13498		}
13499
13500	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13501				  4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13502	      fixp->fx_file = fragp->fr_file;
13503	      fixp->fx_line = fragp->fr_line;
13504
13505	      md_number_to_chars ((char *) buf, insn, 4);
13506	      buf += 4;
13507
13508	      if (mips_opts.isa == ISA_MIPS1)
13509		{
13510		  /* nop */
13511		  md_number_to_chars ((char *) buf, 0, 4);
13512		  buf += 4;
13513		}
13514
13515	      /* d/addiu $at, $at, <sym>  R_MIPS_LO16 */
13516	      insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
13517
13518	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13519				  4, &exp, 0, BFD_RELOC_LO16);
13520	      fixp->fx_file = fragp->fr_file;
13521	      fixp->fx_line = fragp->fr_line;
13522
13523	      md_number_to_chars ((char *) buf, insn, 4);
13524	      buf += 4;
13525
13526	      /* j(al)r $at.  */
13527	      if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13528		insn = 0x0020f809;
13529	      else
13530		insn = 0x00200008;
13531
13532	      md_number_to_chars ((char *) buf, insn, 4);
13533	      buf += 4;
13534	    }
13535	}
13536
13537      assert (buf == (bfd_byte *)fragp->fr_literal
13538	      + fragp->fr_fix + fragp->fr_var);
13539
13540      fragp->fr_fix += fragp->fr_var;
13541
13542      return;
13543    }
13544
13545  if (RELAX_MIPS16_P (fragp->fr_subtype))
13546    {
13547      int type;
13548      register const struct mips16_immed_operand *op;
13549      bfd_boolean small, ext;
13550      offsetT val;
13551      bfd_byte *buf;
13552      unsigned long insn;
13553      bfd_boolean use_extend;
13554      unsigned short extend;
13555
13556      type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13557      op = mips16_immed_operands;
13558      while (op->type != type)
13559	++op;
13560
13561      if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13562	{
13563	  small = FALSE;
13564	  ext = TRUE;
13565	}
13566      else
13567	{
13568	  small = TRUE;
13569	  ext = FALSE;
13570	}
13571
13572      resolve_symbol_value (fragp->fr_symbol);
13573      val = S_GET_VALUE (fragp->fr_symbol);
13574      if (op->pcrel)
13575	{
13576	  addressT addr;
13577
13578	  addr = fragp->fr_address + fragp->fr_fix;
13579
13580	  /* The rules for the base address of a PC relative reloc are
13581             complicated; see mips16_extended_frag.  */
13582	  if (type == 'p' || type == 'q')
13583	    {
13584	      addr += 2;
13585	      if (ext)
13586		addr += 2;
13587	      /* Ignore the low bit in the target, since it will be
13588                 set for a text label.  */
13589	      if ((val & 1) != 0)
13590		--val;
13591	    }
13592	  else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13593	    addr -= 4;
13594	  else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13595	    addr -= 2;
13596
13597	  addr &= ~ (addressT) ((1 << op->shift) - 1);
13598	  val -= addr;
13599
13600	  /* Make sure the section winds up with the alignment we have
13601             assumed.  */
13602	  if (op->shift > 0)
13603	    record_alignment (asec, op->shift);
13604	}
13605
13606      if (ext
13607	  && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
13608	      || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
13609	as_warn_where (fragp->fr_file, fragp->fr_line,
13610		       _("extended instruction in delay slot"));
13611
13612      buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
13613
13614      if (target_big_endian)
13615	insn = bfd_getb16 (buf);
13616      else
13617	insn = bfd_getl16 (buf);
13618
13619      mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
13620		    RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
13621		    small, ext, &insn, &use_extend, &extend);
13622
13623      if (use_extend)
13624	{
13625	  md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
13626	  fragp->fr_fix += 2;
13627	  buf += 2;
13628	}
13629
13630      md_number_to_chars ((char *) buf, insn, 2);
13631      fragp->fr_fix += 2;
13632      buf += 2;
13633    }
13634  else
13635    {
13636      int first, second;
13637      fixS *fixp;
13638
13639      first = RELAX_FIRST (fragp->fr_subtype);
13640      second = RELAX_SECOND (fragp->fr_subtype);
13641      fixp = (fixS *) fragp->fr_opcode;
13642
13643      /* Possibly emit a warning if we've chosen the longer option.  */
13644      if (((fragp->fr_subtype & RELAX_USE_SECOND) != 0)
13645	  == ((fragp->fr_subtype & RELAX_SECOND_LONGER) != 0))
13646	{
13647	  const char *msg = macro_warning (fragp->fr_subtype);
13648	  if (msg != 0)
13649	    as_warn_where (fragp->fr_file, fragp->fr_line, msg);
13650	}
13651
13652      /* Go through all the fixups for the first sequence.  Disable them
13653	 (by marking them as done) if we're going to use the second
13654	 sequence instead.  */
13655      while (fixp
13656	     && fixp->fx_frag == fragp
13657	     && fixp->fx_where < fragp->fr_fix - second)
13658	{
13659	  if (fragp->fr_subtype & RELAX_USE_SECOND)
13660	    fixp->fx_done = 1;
13661	  fixp = fixp->fx_next;
13662	}
13663
13664      /* Go through the fixups for the second sequence.  Disable them if
13665	 we're going to use the first sequence, otherwise adjust their
13666	 addresses to account for the relaxation.  */
13667      while (fixp && fixp->fx_frag == fragp)
13668	{
13669	  if (fragp->fr_subtype & RELAX_USE_SECOND)
13670	    fixp->fx_where -= first;
13671	  else
13672	    fixp->fx_done = 1;
13673	  fixp = fixp->fx_next;
13674	}
13675
13676      /* Now modify the frag contents.  */
13677      if (fragp->fr_subtype & RELAX_USE_SECOND)
13678	{
13679	  char *start;
13680
13681	  start = fragp->fr_literal + fragp->fr_fix - first - second;
13682	  memmove (start, start + first, second);
13683	  fragp->fr_fix -= first;
13684	}
13685      else
13686	fragp->fr_fix -= second;
13687    }
13688}
13689
13690#ifdef OBJ_ELF
13691
13692/* This function is called after the relocs have been generated.
13693   We've been storing mips16 text labels as odd.  Here we convert them
13694   back to even for the convenience of the debugger.  */
13695
13696void
13697mips_frob_file_after_relocs (void)
13698{
13699  asymbol **syms;
13700  unsigned int count, i;
13701
13702  if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13703    return;
13704
13705  syms = bfd_get_outsymbols (stdoutput);
13706  count = bfd_get_symcount (stdoutput);
13707  for (i = 0; i < count; i++, syms++)
13708    {
13709      if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
13710	  && ((*syms)->value & 1) != 0)
13711	{
13712	  (*syms)->value &= ~1;
13713	  /* If the symbol has an odd size, it was probably computed
13714	     incorrectly, so adjust that as well.  */
13715	  if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
13716	    ++elf_symbol (*syms)->internal_elf_sym.st_size;
13717	}
13718    }
13719}
13720
13721#endif
13722
13723/* This function is called whenever a label is defined.  It is used
13724   when handling branch delays; if a branch has a label, we assume we
13725   can not move it.  */
13726
13727void
13728mips_define_label (symbolS *sym)
13729{
13730  struct insn_label_list *l;
13731
13732  if (free_insn_labels == NULL)
13733    l = (struct insn_label_list *) xmalloc (sizeof *l);
13734  else
13735    {
13736      l = free_insn_labels;
13737      free_insn_labels = l->next;
13738    }
13739
13740  l->label = sym;
13741  l->next = insn_labels;
13742  insn_labels = l;
13743
13744#ifdef OBJ_ELF
13745  dwarf2_emit_label (sym);
13746#endif
13747}
13748
13749#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
13750
13751/* Some special processing for a MIPS ELF file.  */
13752
13753void
13754mips_elf_final_processing (void)
13755{
13756  /* Write out the register information.  */
13757  if (mips_abi != N64_ABI)
13758    {
13759      Elf32_RegInfo s;
13760
13761      s.ri_gprmask = mips_gprmask;
13762      s.ri_cprmask[0] = mips_cprmask[0];
13763      s.ri_cprmask[1] = mips_cprmask[1];
13764      s.ri_cprmask[2] = mips_cprmask[2];
13765      s.ri_cprmask[3] = mips_cprmask[3];
13766      /* The gp_value field is set by the MIPS ELF backend.  */
13767
13768      bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
13769				       ((Elf32_External_RegInfo *)
13770					mips_regmask_frag));
13771    }
13772  else
13773    {
13774      Elf64_Internal_RegInfo s;
13775
13776      s.ri_gprmask = mips_gprmask;
13777      s.ri_pad = 0;
13778      s.ri_cprmask[0] = mips_cprmask[0];
13779      s.ri_cprmask[1] = mips_cprmask[1];
13780      s.ri_cprmask[2] = mips_cprmask[2];
13781      s.ri_cprmask[3] = mips_cprmask[3];
13782      /* The gp_value field is set by the MIPS ELF backend.  */
13783
13784      bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
13785				       ((Elf64_External_RegInfo *)
13786					mips_regmask_frag));
13787    }
13788
13789  /* Set the MIPS ELF flag bits.  FIXME: There should probably be some
13790     sort of BFD interface for this.  */
13791  if (mips_any_noreorder)
13792    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
13793  if (mips_pic != NO_PIC)
13794    {
13795    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
13796      elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
13797    }
13798  if (mips_abicalls)
13799    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
13800
13801  /* Set MIPS ELF flags for ASEs.  */
13802  /* We may need to define a new flag for DSP ASE, and set this flag when
13803     file_ase_dsp is true.  */
13804  /* We may need to define a new flag for MT ASE, and set this flag when
13805     file_ase_mt is true.  */
13806  if (file_ase_mips16)
13807    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
13808#if 0 /* XXX FIXME */
13809  if (file_ase_mips3d)
13810    elf_elfheader (stdoutput)->e_flags |= ???;
13811#endif
13812  if (file_ase_mdmx)
13813    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
13814
13815  /* Set the MIPS ELF ABI flags.  */
13816  if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
13817    elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
13818  else if (mips_abi == O64_ABI)
13819    elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
13820  else if (mips_abi == EABI_ABI)
13821    {
13822      if (!file_mips_gp32)
13823	elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
13824      else
13825	elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
13826    }
13827  else if (mips_abi == N32_ABI)
13828    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
13829
13830  /* Nothing to do for N64_ABI.  */
13831
13832  if (mips_32bitmode)
13833    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
13834}
13835
13836#endif /* OBJ_ELF || OBJ_MAYBE_ELF */
13837
13838typedef struct proc {
13839  symbolS *func_sym;
13840  symbolS *func_end_sym;
13841  unsigned long reg_mask;
13842  unsigned long reg_offset;
13843  unsigned long fpreg_mask;
13844  unsigned long fpreg_offset;
13845  unsigned long frame_offset;
13846  unsigned long frame_reg;
13847  unsigned long pc_reg;
13848} procS;
13849
13850static procS cur_proc;
13851static procS *cur_proc_ptr;
13852static int numprocs;
13853
13854/* Fill in an rs_align_code fragment.  */
13855
13856void
13857mips_handle_align (fragS *fragp)
13858{
13859  if (fragp->fr_type != rs_align_code)
13860    return;
13861
13862  if (mips_opts.mips16)
13863    {
13864      static const unsigned char be_nop[] = { 0x65, 0x00 };
13865      static const unsigned char le_nop[] = { 0x00, 0x65 };
13866
13867      int bytes;
13868      char *p;
13869
13870      bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
13871      p = fragp->fr_literal + fragp->fr_fix;
13872
13873      if (bytes & 1)
13874	{
13875	  *p++ = 0;
13876	  fragp->fr_fix++;
13877	}
13878
13879      memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
13880      fragp->fr_var = 2;
13881    }
13882
13883  /* For mips32, a nop is a zero, which we trivially get by doing nothing.  */
13884}
13885
13886static void
13887md_obj_begin (void)
13888{
13889}
13890
13891static void
13892md_obj_end (void)
13893{
13894  /* check for premature end, nesting errors, etc */
13895  if (cur_proc_ptr)
13896    as_warn (_("missing .end at end of assembly"));
13897}
13898
13899static long
13900get_number (void)
13901{
13902  int negative = 0;
13903  long val = 0;
13904
13905  if (*input_line_pointer == '-')
13906    {
13907      ++input_line_pointer;
13908      negative = 1;
13909    }
13910  if (!ISDIGIT (*input_line_pointer))
13911    as_bad (_("expected simple number"));
13912  if (input_line_pointer[0] == '0')
13913    {
13914      if (input_line_pointer[1] == 'x')
13915	{
13916	  input_line_pointer += 2;
13917	  while (ISXDIGIT (*input_line_pointer))
13918	    {
13919	      val <<= 4;
13920	      val |= hex_value (*input_line_pointer++);
13921	    }
13922	  return negative ? -val : val;
13923	}
13924      else
13925	{
13926	  ++input_line_pointer;
13927	  while (ISDIGIT (*input_line_pointer))
13928	    {
13929	      val <<= 3;
13930	      val |= *input_line_pointer++ - '0';
13931	    }
13932	  return negative ? -val : val;
13933	}
13934    }
13935  if (!ISDIGIT (*input_line_pointer))
13936    {
13937      printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
13938	      *input_line_pointer, *input_line_pointer);
13939      as_warn (_("invalid number"));
13940      return -1;
13941    }
13942  while (ISDIGIT (*input_line_pointer))
13943    {
13944      val *= 10;
13945      val += *input_line_pointer++ - '0';
13946    }
13947  return negative ? -val : val;
13948}
13949
13950/* The .file directive; just like the usual .file directive, but there
13951   is an initial number which is the ECOFF file index.  In the non-ECOFF
13952   case .file implies DWARF-2.  */
13953
13954static void
13955s_mips_file (int x ATTRIBUTE_UNUSED)
13956{
13957  static int first_file_directive = 0;
13958
13959  if (ECOFF_DEBUGGING)
13960    {
13961      get_number ();
13962      s_app_file (0);
13963    }
13964  else
13965    {
13966      char *filename;
13967
13968      filename = dwarf2_directive_file (0);
13969
13970      /* Versions of GCC up to 3.1 start files with a ".file"
13971	 directive even for stabs output.  Make sure that this
13972	 ".file" is handled.  Note that you need a version of GCC
13973         after 3.1 in order to support DWARF-2 on MIPS.  */
13974      if (filename != NULL && ! first_file_directive)
13975	{
13976	  (void) new_logical_line (filename, -1);
13977	  s_app_file_string (filename, 0);
13978	}
13979      first_file_directive = 1;
13980    }
13981}
13982
13983/* The .loc directive, implying DWARF-2.  */
13984
13985static void
13986s_mips_loc (int x ATTRIBUTE_UNUSED)
13987{
13988  if (!ECOFF_DEBUGGING)
13989    dwarf2_directive_loc (0);
13990}
13991
13992/* The .end directive.  */
13993
13994static void
13995s_mips_end (int x ATTRIBUTE_UNUSED)
13996{
13997  symbolS *p;
13998
13999  /* Following functions need their own .frame and .cprestore directives.  */
14000  mips_frame_reg_valid = 0;
14001  mips_cprestore_valid = 0;
14002
14003  if (!is_end_of_line[(unsigned char) *input_line_pointer])
14004    {
14005      p = get_symbol ();
14006      demand_empty_rest_of_line ();
14007    }
14008  else
14009    p = NULL;
14010
14011  if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14012    as_warn (_(".end not in text section"));
14013
14014  if (!cur_proc_ptr)
14015    {
14016      as_warn (_(".end directive without a preceding .ent directive."));
14017      demand_empty_rest_of_line ();
14018      return;
14019    }
14020
14021  if (p != NULL)
14022    {
14023      assert (S_GET_NAME (p));
14024      if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->func_sym)))
14025	as_warn (_(".end symbol does not match .ent symbol."));
14026
14027      if (debug_type == DEBUG_STABS)
14028	stabs_generate_asm_endfunc (S_GET_NAME (p),
14029				    S_GET_NAME (p));
14030    }
14031  else
14032    as_warn (_(".end directive missing or unknown symbol"));
14033
14034#ifdef OBJ_ELF
14035  /* Create an expression to calculate the size of the function.  */
14036  if (p && cur_proc_ptr)
14037    {
14038      OBJ_SYMFIELD_TYPE *obj = symbol_get_obj (p);
14039      expressionS *exp = xmalloc (sizeof (expressionS));
14040
14041      obj->size = exp;
14042      exp->X_op = O_subtract;
14043      exp->X_add_symbol = symbol_temp_new_now ();
14044      exp->X_op_symbol = p;
14045      exp->X_add_number = 0;
14046
14047      cur_proc_ptr->func_end_sym = exp->X_add_symbol;
14048    }
14049
14050  /* Generate a .pdr section.  */
14051  if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING
14052      && mips_flag_pdr)
14053    {
14054      segT saved_seg = now_seg;
14055      subsegT saved_subseg = now_subseg;
14056      valueT dot;
14057      expressionS exp;
14058      char *fragp;
14059
14060      dot = frag_now_fix ();
14061
14062#ifdef md_flush_pending_output
14063      md_flush_pending_output ();
14064#endif
14065
14066      assert (pdr_seg);
14067      subseg_set (pdr_seg, 0);
14068
14069      /* Write the symbol.  */
14070      exp.X_op = O_symbol;
14071      exp.X_add_symbol = p;
14072      exp.X_add_number = 0;
14073      emit_expr (&exp, 4);
14074
14075      fragp = frag_more (7 * 4);
14076
14077      md_number_to_chars (fragp, cur_proc_ptr->reg_mask, 4);
14078      md_number_to_chars (fragp + 4, cur_proc_ptr->reg_offset, 4);
14079      md_number_to_chars (fragp + 8, cur_proc_ptr->fpreg_mask, 4);
14080      md_number_to_chars (fragp + 12, cur_proc_ptr->fpreg_offset, 4);
14081      md_number_to_chars (fragp + 16, cur_proc_ptr->frame_offset, 4);
14082      md_number_to_chars (fragp + 20, cur_proc_ptr->frame_reg, 4);
14083      md_number_to_chars (fragp + 24, cur_proc_ptr->pc_reg, 4);
14084
14085      subseg_set (saved_seg, saved_subseg);
14086    }
14087#endif /* OBJ_ELF */
14088
14089  cur_proc_ptr = NULL;
14090}
14091
14092/* The .aent and .ent directives.  */
14093
14094static void
14095s_mips_ent (int aent)
14096{
14097  symbolS *symbolP;
14098
14099  symbolP = get_symbol ();
14100  if (*input_line_pointer == ',')
14101    ++input_line_pointer;
14102  SKIP_WHITESPACE ();
14103  if (ISDIGIT (*input_line_pointer)
14104      || *input_line_pointer == '-')
14105    get_number ();
14106
14107  if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14108    as_warn (_(".ent or .aent not in text section."));
14109
14110  if (!aent && cur_proc_ptr)
14111    as_warn (_("missing .end"));
14112
14113  if (!aent)
14114    {
14115      /* This function needs its own .frame and .cprestore directives.  */
14116      mips_frame_reg_valid = 0;
14117      mips_cprestore_valid = 0;
14118
14119      cur_proc_ptr = &cur_proc;
14120      memset (cur_proc_ptr, '\0', sizeof (procS));
14121
14122      cur_proc_ptr->func_sym = symbolP;
14123
14124      symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14125
14126      ++numprocs;
14127
14128      if (debug_type == DEBUG_STABS)
14129        stabs_generate_asm_func (S_GET_NAME (symbolP),
14130				 S_GET_NAME (symbolP));
14131    }
14132
14133  demand_empty_rest_of_line ();
14134}
14135
14136/* The .frame directive. If the mdebug section is present (IRIX 5 native)
14137   then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14138   s_mips_frame is used so that we can set the PDR information correctly.
14139   We can't use the ecoff routines because they make reference to the ecoff
14140   symbol table (in the mdebug section).  */
14141
14142static void
14143s_mips_frame (int ignore ATTRIBUTE_UNUSED)
14144{
14145#ifdef OBJ_ELF
14146  if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14147    {
14148      long val;
14149
14150      if (cur_proc_ptr == (procS *) NULL)
14151	{
14152	  as_warn (_(".frame outside of .ent"));
14153	  demand_empty_rest_of_line ();
14154	  return;
14155	}
14156
14157      cur_proc_ptr->frame_reg = tc_get_register (1);
14158
14159      SKIP_WHITESPACE ();
14160      if (*input_line_pointer++ != ','
14161	  || get_absolute_expression_and_terminator (&val) != ',')
14162	{
14163	  as_warn (_("Bad .frame directive"));
14164	  --input_line_pointer;
14165	  demand_empty_rest_of_line ();
14166	  return;
14167	}
14168
14169      cur_proc_ptr->frame_offset = val;
14170      cur_proc_ptr->pc_reg = tc_get_register (0);
14171
14172      demand_empty_rest_of_line ();
14173    }
14174  else
14175#endif /* OBJ_ELF */
14176    s_ignore (ignore);
14177}
14178
14179/* The .fmask and .mask directives. If the mdebug section is present
14180   (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14181   embedded targets, s_mips_mask is used so that we can set the PDR
14182   information correctly. We can't use the ecoff routines because they
14183   make reference to the ecoff symbol table (in the mdebug section).  */
14184
14185static void
14186s_mips_mask (int reg_type)
14187{
14188#ifdef OBJ_ELF
14189  if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14190    {
14191      long mask, off;
14192
14193      if (cur_proc_ptr == (procS *) NULL)
14194	{
14195	  as_warn (_(".mask/.fmask outside of .ent"));
14196	  demand_empty_rest_of_line ();
14197	  return;
14198	}
14199
14200      if (get_absolute_expression_and_terminator (&mask) != ',')
14201	{
14202	  as_warn (_("Bad .mask/.fmask directive"));
14203	  --input_line_pointer;
14204	  demand_empty_rest_of_line ();
14205	  return;
14206	}
14207
14208      off = get_absolute_expression ();
14209
14210      if (reg_type == 'F')
14211	{
14212	  cur_proc_ptr->fpreg_mask = mask;
14213	  cur_proc_ptr->fpreg_offset = off;
14214	}
14215      else
14216	{
14217	  cur_proc_ptr->reg_mask = mask;
14218	  cur_proc_ptr->reg_offset = off;
14219	}
14220
14221      demand_empty_rest_of_line ();
14222    }
14223  else
14224#endif /* OBJ_ELF */
14225    s_ignore (reg_type);
14226}
14227
14228/* A table describing all the processors gas knows about.  Names are
14229   matched in the order listed.
14230
14231   To ease comparison, please keep this table in the same order as
14232   gcc's mips_cpu_info_table[].  */
14233static const struct mips_cpu_info mips_cpu_info_table[] =
14234{
14235  /* Entries for generic ISAs */
14236  { "mips1",          1,      ISA_MIPS1,      CPU_R3000 },
14237  { "mips2",          1,      ISA_MIPS2,      CPU_R6000 },
14238  { "mips3",          1,      ISA_MIPS3,      CPU_R4000 },
14239  { "mips4",          1,      ISA_MIPS4,      CPU_R8000 },
14240  { "mips5",          1,      ISA_MIPS5,      CPU_MIPS5 },
14241  { "mips32",         1,      ISA_MIPS32,     CPU_MIPS32 },
14242  { "mips32r2",       1,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14243  { "mips64",         1,      ISA_MIPS64,     CPU_MIPS64 },
14244  { "mips64r2",       1,      ISA_MIPS64R2,   CPU_MIPS64R2 },
14245
14246  /* MIPS I */
14247  { "r3000",          0,      ISA_MIPS1,      CPU_R3000 },
14248  { "r2000",          0,      ISA_MIPS1,      CPU_R3000 },
14249  { "r3900",          0,      ISA_MIPS1,      CPU_R3900 },
14250
14251  /* MIPS II */
14252  { "r6000",          0,      ISA_MIPS2,      CPU_R6000 },
14253
14254  /* MIPS III */
14255  { "r4000",          0,      ISA_MIPS3,      CPU_R4000 },
14256  { "r4010",          0,      ISA_MIPS2,      CPU_R4010 },
14257  { "vr4100",         0,      ISA_MIPS3,      CPU_VR4100 },
14258  { "vr4111",         0,      ISA_MIPS3,      CPU_R4111 },
14259  { "vr4120",         0,      ISA_MIPS3,      CPU_VR4120 },
14260  { "vr4130",         0,      ISA_MIPS3,      CPU_VR4120 },
14261  { "vr4181",         0,      ISA_MIPS3,      CPU_R4111 },
14262  { "vr4300",         0,      ISA_MIPS3,      CPU_R4300 },
14263  { "r4400",          0,      ISA_MIPS3,      CPU_R4400 },
14264  { "r4600",          0,      ISA_MIPS3,      CPU_R4600 },
14265  { "orion",          0,      ISA_MIPS3,      CPU_R4600 },
14266  { "r4650",          0,      ISA_MIPS3,      CPU_R4650 },
14267
14268  /* MIPS IV */
14269  { "r8000",          0,      ISA_MIPS4,      CPU_R8000 },
14270  { "r10000",         0,      ISA_MIPS4,      CPU_R10000 },
14271  { "r12000",         0,      ISA_MIPS4,      CPU_R12000 },
14272  { "vr5000",         0,      ISA_MIPS4,      CPU_R5000 },
14273  { "vr5400",         0,      ISA_MIPS4,      CPU_VR5400 },
14274  { "vr5500",         0,      ISA_MIPS4,      CPU_VR5500 },
14275  { "rm5200",         0,      ISA_MIPS4,      CPU_R5000 },
14276  { "rm5230",         0,      ISA_MIPS4,      CPU_R5000 },
14277  { "rm5231",         0,      ISA_MIPS4,      CPU_R5000 },
14278  { "rm5261",         0,      ISA_MIPS4,      CPU_R5000 },
14279  { "rm5721",         0,      ISA_MIPS4,      CPU_R5000 },
14280  { "rm7000",         0,      ISA_MIPS4,      CPU_RM7000 },
14281  { "rm9000",         0,      ISA_MIPS4,      CPU_RM9000 },
14282
14283  /* MIPS 32 */
14284  { "4kc",            0,      ISA_MIPS32,     CPU_MIPS32 },
14285  { "4km",            0,      ISA_MIPS32,     CPU_MIPS32 },
14286  { "4kp",            0,      ISA_MIPS32,     CPU_MIPS32 },
14287
14288  /* MIPS32 Release 2 */
14289  { "m4k",            0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14290  { "24k",            0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14291  { "24kc",           0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14292  { "24kf",           0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14293  { "24kx",           0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14294
14295  /* MIPS 64 */
14296  { "5kc",            0,      ISA_MIPS64,     CPU_MIPS64 },
14297  { "5kf",            0,      ISA_MIPS64,     CPU_MIPS64 },
14298  { "20kc",           0,      ISA_MIPS64,     CPU_MIPS64 },
14299
14300  /* Broadcom SB-1 CPU core */
14301  { "sb1",            0,      ISA_MIPS64,     CPU_SB1 },
14302
14303  /* End marker */
14304  { NULL, 0, 0, 0 }
14305};
14306
14307
14308/* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14309   with a final "000" replaced by "k".  Ignore case.
14310
14311   Note: this function is shared between GCC and GAS.  */
14312
14313static bfd_boolean
14314mips_strict_matching_cpu_name_p (const char *canonical, const char *given)
14315{
14316  while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14317    given++, canonical++;
14318
14319  return ((*given == 0 && *canonical == 0)
14320	  || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14321}
14322
14323
14324/* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14325   CPU name.  We've traditionally allowed a lot of variation here.
14326
14327   Note: this function is shared between GCC and GAS.  */
14328
14329static bfd_boolean
14330mips_matching_cpu_name_p (const char *canonical, const char *given)
14331{
14332  /* First see if the name matches exactly, or with a final "000"
14333     turned into "k".  */
14334  if (mips_strict_matching_cpu_name_p (canonical, given))
14335    return TRUE;
14336
14337  /* If not, try comparing based on numerical designation alone.
14338     See if GIVEN is an unadorned number, or 'r' followed by a number.  */
14339  if (TOLOWER (*given) == 'r')
14340    given++;
14341  if (!ISDIGIT (*given))
14342    return FALSE;
14343
14344  /* Skip over some well-known prefixes in the canonical name,
14345     hoping to find a number there too.  */
14346  if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14347    canonical += 2;
14348  else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14349    canonical += 2;
14350  else if (TOLOWER (canonical[0]) == 'r')
14351    canonical += 1;
14352
14353  return mips_strict_matching_cpu_name_p (canonical, given);
14354}
14355
14356
14357/* Parse an option that takes the name of a processor as its argument.
14358   OPTION is the name of the option and CPU_STRING is the argument.
14359   Return the corresponding processor enumeration if the CPU_STRING is
14360   recognized, otherwise report an error and return null.
14361
14362   A similar function exists in GCC.  */
14363
14364static const struct mips_cpu_info *
14365mips_parse_cpu (const char *option, const char *cpu_string)
14366{
14367  const struct mips_cpu_info *p;
14368
14369  /* 'from-abi' selects the most compatible architecture for the given
14370     ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs.  For the
14371     EABIs, we have to decide whether we're using the 32-bit or 64-bit
14372     version.  Look first at the -mgp options, if given, otherwise base
14373     the choice on MIPS_DEFAULT_64BIT.
14374
14375     Treat NO_ABI like the EABIs.  One reason to do this is that the
14376     plain 'mips' and 'mips64' configs have 'from-abi' as their default
14377     architecture.  This code picks MIPS I for 'mips' and MIPS III for
14378     'mips64', just as we did in the days before 'from-abi'.  */
14379  if (strcasecmp (cpu_string, "from-abi") == 0)
14380    {
14381      if (ABI_NEEDS_32BIT_REGS (mips_abi))
14382	return mips_cpu_info_from_isa (ISA_MIPS1);
14383
14384      if (ABI_NEEDS_64BIT_REGS (mips_abi))
14385	return mips_cpu_info_from_isa (ISA_MIPS3);
14386
14387      if (file_mips_gp32 >= 0)
14388	return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14389
14390      return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14391				     ? ISA_MIPS3
14392				     : ISA_MIPS1);
14393    }
14394
14395  /* 'default' has traditionally been a no-op.  Probably not very useful.  */
14396  if (strcasecmp (cpu_string, "default") == 0)
14397    return 0;
14398
14399  for (p = mips_cpu_info_table; p->name != 0; p++)
14400    if (mips_matching_cpu_name_p (p->name, cpu_string))
14401      return p;
14402
14403  as_bad ("Bad value (%s) for %s", cpu_string, option);
14404  return 0;
14405}
14406
14407/* Return the canonical processor information for ISA (a member of the
14408   ISA_MIPS* enumeration).  */
14409
14410static const struct mips_cpu_info *
14411mips_cpu_info_from_isa (int isa)
14412{
14413  int i;
14414
14415  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14416    if (mips_cpu_info_table[i].is_isa
14417	&& isa == mips_cpu_info_table[i].isa)
14418      return (&mips_cpu_info_table[i]);
14419
14420  return NULL;
14421}
14422
14423static const struct mips_cpu_info *
14424mips_cpu_info_from_arch (int arch)
14425{
14426  int i;
14427
14428  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14429    if (arch == mips_cpu_info_table[i].cpu)
14430      return (&mips_cpu_info_table[i]);
14431
14432  return NULL;
14433}
14434
14435static void
14436show (FILE *stream, const char *string, int *col_p, int *first_p)
14437{
14438  if (*first_p)
14439    {
14440      fprintf (stream, "%24s", "");
14441      *col_p = 24;
14442    }
14443  else
14444    {
14445      fprintf (stream, ", ");
14446      *col_p += 2;
14447    }
14448
14449  if (*col_p + strlen (string) > 72)
14450    {
14451      fprintf (stream, "\n%24s", "");
14452      *col_p = 24;
14453    }
14454
14455  fprintf (stream, "%s", string);
14456  *col_p += strlen (string);
14457
14458  *first_p = 0;
14459}
14460
14461void
14462md_show_usage (FILE *stream)
14463{
14464  int column, first;
14465  size_t i;
14466
14467  fprintf (stream, _("\
14468MIPS options:\n\
14469-EB			generate big endian output\n\
14470-EL			generate little endian output\n\
14471-g, -g2			do not remove unneeded NOPs or swap branches\n\
14472-G NUM			allow referencing objects up to NUM bytes\n\
14473			implicitly with the gp register [default 8]\n"));
14474  fprintf (stream, _("\
14475-mips1			generate MIPS ISA I instructions\n\
14476-mips2			generate MIPS ISA II instructions\n\
14477-mips3			generate MIPS ISA III instructions\n\
14478-mips4			generate MIPS ISA IV instructions\n\
14479-mips5                  generate MIPS ISA V instructions\n\
14480-mips32                 generate MIPS32 ISA instructions\n\
14481-mips32r2               generate MIPS32 release 2 ISA instructions\n\
14482-mips64                 generate MIPS64 ISA instructions\n\
14483-mips64r2               generate MIPS64 release 2 ISA instructions\n\
14484-march=CPU/-mtune=CPU	generate code/schedule for CPU, where CPU is one of:\n"));
14485
14486  first = 1;
14487
14488  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14489    show (stream, mips_cpu_info_table[i].name, &column, &first);
14490  show (stream, "from-abi", &column, &first);
14491  fputc ('\n', stream);
14492
14493  fprintf (stream, _("\
14494-mCPU			equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14495-no-mCPU		don't generate code specific to CPU.\n\
14496			For -mCPU and -no-mCPU, CPU must be one of:\n"));
14497
14498  first = 1;
14499
14500  show (stream, "3900", &column, &first);
14501  show (stream, "4010", &column, &first);
14502  show (stream, "4100", &column, &first);
14503  show (stream, "4650", &column, &first);
14504  fputc ('\n', stream);
14505
14506  fprintf (stream, _("\
14507-mips16			generate mips16 instructions\n\
14508-no-mips16		do not generate mips16 instructions\n"));
14509  fprintf (stream, _("\
14510-mdsp			generate DSP instructions\n\
14511-mno-dsp		do not generate DSP instructions\n"));
14512  fprintf (stream, _("\
14513-mmt			generate MT instructions\n\
14514-mno-mt			do not generate MT instructions\n"));
14515  fprintf (stream, _("\
14516-mfix-vr4120		work around certain VR4120 errata\n\
14517-mfix-vr4130		work around VR4130 mflo/mfhi errata\n\
14518-mgp32			use 32-bit GPRs, regardless of the chosen ISA\n\
14519-mfp32			use 32-bit FPRs, regardless of the chosen ISA\n\
14520-mno-shared		optimize output for executables\n\
14521-msym32			assume all symbols have 32-bit values\n\
14522-O0			remove unneeded NOPs, do not swap branches\n\
14523-O			remove unneeded NOPs and swap branches\n\
14524--[no-]construct-floats [dis]allow floating point values to be constructed\n\
14525--trap, --no-break	trap exception on div by 0 and mult overflow\n\
14526--break, --no-trap	break exception on div by 0 and mult overflow\n"));
14527#ifdef OBJ_ELF
14528  fprintf (stream, _("\
14529-KPIC, -call_shared	generate SVR4 position independent code\n\
14530-non_shared		do not generate position independent code\n\
14531-xgot			assume a 32 bit GOT\n\
14532-mpdr, -mno-pdr		enable/disable creation of .pdr sections\n\
14533-mshared, -mno-shared   disable/enable .cpload optimization for\n\
14534                        non-shared code\n\
14535-mabi=ABI		create ABI conformant object file for:\n"));
14536
14537  first = 1;
14538
14539  show (stream, "32", &column, &first);
14540  show (stream, "o64", &column, &first);
14541  show (stream, "n32", &column, &first);
14542  show (stream, "64", &column, &first);
14543  show (stream, "eabi", &column, &first);
14544
14545  fputc ('\n', stream);
14546
14547  fprintf (stream, _("\
14548-32			create o32 ABI object file (default)\n\
14549-n32			create n32 ABI object file\n\
14550-64			create 64 ABI object file\n"));
14551#endif
14552}
14553
14554enum dwarf2_format
14555mips_dwarf2_format (void)
14556{
14557  if (mips_abi == N64_ABI)
14558    {
14559#ifdef TE_IRIX
14560      return dwarf2_format_64bit_irix;
14561#else
14562      return dwarf2_format_64bit;
14563#endif
14564    }
14565  else
14566    return dwarf2_format_32bit;
14567}
14568
14569int
14570mips_dwarf2_addr_size (void)
14571{
14572  if (mips_abi == N64_ABI)
14573    return 8;
14574  else
14575    return 4;
14576}
14577
14578/* Standard calling conventions leave the CFA at SP on entry.  */
14579void
14580mips_cfi_frame_initial_instructions (void)
14581{
14582  cfi_add_CFA_def_cfa_register (SP);
14583}
14584
14585