1/* Subroutines used for MIPS code generation.
2   Copyright (C) 1989, 1990, 1991, 1993, 1994, 1995, 1996, 1997, 1998,
3   1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
4   Contributed by A. Lichnewsky, lich@inria.inria.fr.
5   Changes by Michael Meissner, meissner@osf.org.
6   64 bit r4000 support by Ian Lance Taylor, ian@cygnus.com, and
7   Brendan Eich, brendan@microunity.com.
8
9This file is part of GCC.
10
11GCC is free software; you can redistribute it and/or modify
12it under the terms of the GNU General Public License as published by
13the Free Software Foundation; either version 2, or (at your option)
14any later version.
15
16GCC is distributed in the hope that it will be useful,
17but WITHOUT ANY WARRANTY; without even the implied warranty of
18MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
19GNU General Public License for more details.
20
21You should have received a copy of the GNU General Public License
22along with GCC; see the file COPYING.  If not, write to
23the Free Software Foundation, 51 Franklin Street, Fifth Floor,
24Boston, MA 02110-1301, USA.  */
25
26#include "config.h"
27#include "system.h"
28#include "coretypes.h"
29#include "tm.h"
30#include <signal.h>
31#include "rtl.h"
32#include "regs.h"
33#include "hard-reg-set.h"
34#include "real.h"
35#include "insn-config.h"
36#include "conditions.h"
37#include "insn-attr.h"
38#include "recog.h"
39#include "toplev.h"
40#include "output.h"
41#include "tree.h"
42#include "function.h"
43#include "expr.h"
44#include "optabs.h"
45#include "flags.h"
46#include "reload.h"
47#include "tm_p.h"
48#include "ggc.h"
49#include "gstab.h"
50#include "hashtab.h"
51#include "debug.h"
52#include "target.h"
53#include "target-def.h"
54#include "integrate.h"
55#include "langhooks.h"
56#include "cfglayout.h"
57#include "sched-int.h"
58#include "tree-gimple.h"
59#include "bitmap.h"
60
61/* True if X is an unspec wrapper around a SYMBOL_REF or LABEL_REF.  */
62#define UNSPEC_ADDRESS_P(X)					\
63  (GET_CODE (X) == UNSPEC					\
64   && XINT (X, 1) >= UNSPEC_ADDRESS_FIRST			\
65   && XINT (X, 1) < UNSPEC_ADDRESS_FIRST + NUM_SYMBOL_TYPES)
66
67/* Extract the symbol or label from UNSPEC wrapper X.  */
68#define UNSPEC_ADDRESS(X) \
69  XVECEXP (X, 0, 0)
70
71/* Extract the symbol type from UNSPEC wrapper X.  */
72#define UNSPEC_ADDRESS_TYPE(X) \
73  ((enum mips_symbol_type) (XINT (X, 1) - UNSPEC_ADDRESS_FIRST))
74
75/* The maximum distance between the top of the stack frame and the
76   value $sp has when we save & restore registers.
77
78   Use a maximum gap of 0x100 in the mips16 case.  We can then use
79   unextended instructions to save and restore registers, and to
80   allocate and deallocate the top part of the frame.
81
82   The value in the !mips16 case must be a SMALL_OPERAND and must
83   preserve the maximum stack alignment.  */
84#define MIPS_MAX_FIRST_STACK_STEP (TARGET_MIPS16 ? 0x100 : 0x7ff0)
85
86/* True if INSN is a mips.md pattern or asm statement.  */
87#define USEFUL_INSN_P(INSN)						\
88  (INSN_P (INSN)							\
89   && GET_CODE (PATTERN (INSN)) != USE					\
90   && GET_CODE (PATTERN (INSN)) != CLOBBER				\
91   && GET_CODE (PATTERN (INSN)) != ADDR_VEC				\
92   && GET_CODE (PATTERN (INSN)) != ADDR_DIFF_VEC)
93
94/* If INSN is a delayed branch sequence, return the first instruction
95   in the sequence, otherwise return INSN itself.  */
96#define SEQ_BEGIN(INSN)							\
97  (INSN_P (INSN) && GET_CODE (PATTERN (INSN)) == SEQUENCE		\
98   ? XVECEXP (PATTERN (INSN), 0, 0)					\
99   : (INSN))
100
101/* Likewise for the last instruction in a delayed branch sequence.  */
102#define SEQ_END(INSN)							\
103  (INSN_P (INSN) && GET_CODE (PATTERN (INSN)) == SEQUENCE		\
104   ? XVECEXP (PATTERN (INSN), 0, XVECLEN (PATTERN (INSN), 0) - 1)	\
105   : (INSN))
106
107/* Execute the following loop body with SUBINSN set to each instruction
108   between SEQ_BEGIN (INSN) and SEQ_END (INSN) inclusive.  */
109#define FOR_EACH_SUBINSN(SUBINSN, INSN)					\
110  for ((SUBINSN) = SEQ_BEGIN (INSN);					\
111       (SUBINSN) != NEXT_INSN (SEQ_END (INSN));				\
112       (SUBINSN) = NEXT_INSN (SUBINSN))
113
114/* Classifies an address.
115
116   ADDRESS_REG
117       A natural register + offset address.  The register satisfies
118       mips_valid_base_register_p and the offset is a const_arith_operand.
119
120   ADDRESS_LO_SUM
121       A LO_SUM rtx.  The first operand is a valid base register and
122       the second operand is a symbolic address.
123
124   ADDRESS_CONST_INT
125       A signed 16-bit constant address.
126
127   ADDRESS_SYMBOLIC:
128       A constant symbolic address (equivalent to CONSTANT_SYMBOLIC).  */
129enum mips_address_type {
130  ADDRESS_REG,
131  ADDRESS_LO_SUM,
132  ADDRESS_CONST_INT,
133  ADDRESS_SYMBOLIC
134};
135
136/* Classifies the prototype of a builtin function.  */
137enum mips_function_type
138{
139  MIPS_V2SF_FTYPE_V2SF,
140  MIPS_V2SF_FTYPE_V2SF_V2SF,
141  MIPS_V2SF_FTYPE_V2SF_V2SF_INT,
142  MIPS_V2SF_FTYPE_V2SF_V2SF_V2SF_V2SF,
143  MIPS_V2SF_FTYPE_SF_SF,
144  MIPS_INT_FTYPE_V2SF_V2SF,
145  MIPS_INT_FTYPE_V2SF_V2SF_V2SF_V2SF,
146  MIPS_INT_FTYPE_SF_SF,
147  MIPS_INT_FTYPE_DF_DF,
148  MIPS_SF_FTYPE_V2SF,
149  MIPS_SF_FTYPE_SF,
150  MIPS_SF_FTYPE_SF_SF,
151  MIPS_DF_FTYPE_DF,
152  MIPS_DF_FTYPE_DF_DF,
153
154  /* For MIPS DSP ASE  */
155  MIPS_DI_FTYPE_DI_SI,
156  MIPS_DI_FTYPE_DI_SI_SI,
157  MIPS_DI_FTYPE_DI_V2HI_V2HI,
158  MIPS_DI_FTYPE_DI_V4QI_V4QI,
159  MIPS_SI_FTYPE_DI_SI,
160  MIPS_SI_FTYPE_PTR_SI,
161  MIPS_SI_FTYPE_SI,
162  MIPS_SI_FTYPE_SI_SI,
163  MIPS_SI_FTYPE_V2HI,
164  MIPS_SI_FTYPE_V2HI_V2HI,
165  MIPS_SI_FTYPE_V4QI,
166  MIPS_SI_FTYPE_V4QI_V4QI,
167  MIPS_SI_FTYPE_VOID,
168  MIPS_V2HI_FTYPE_SI,
169  MIPS_V2HI_FTYPE_SI_SI,
170  MIPS_V2HI_FTYPE_V2HI,
171  MIPS_V2HI_FTYPE_V2HI_SI,
172  MIPS_V2HI_FTYPE_V2HI_V2HI,
173  MIPS_V2HI_FTYPE_V4QI,
174  MIPS_V2HI_FTYPE_V4QI_V2HI,
175  MIPS_V4QI_FTYPE_SI,
176  MIPS_V4QI_FTYPE_V2HI_V2HI,
177  MIPS_V4QI_FTYPE_V4QI_SI,
178  MIPS_V4QI_FTYPE_V4QI_V4QI,
179  MIPS_VOID_FTYPE_SI_SI,
180  MIPS_VOID_FTYPE_V2HI_V2HI,
181  MIPS_VOID_FTYPE_V4QI_V4QI,
182
183  /* The last type.  */
184  MIPS_MAX_FTYPE_MAX
185};
186
187/* Specifies how a builtin function should be converted into rtl.  */
188enum mips_builtin_type
189{
190  /* The builtin corresponds directly to an .md pattern.  The return
191     value is mapped to operand 0 and the arguments are mapped to
192     operands 1 and above.  */
193  MIPS_BUILTIN_DIRECT,
194
195  /* The builtin corresponds directly to an .md pattern.  There is no return
196     value and the arguments are mapped to operands 0 and above.  */
197  MIPS_BUILTIN_DIRECT_NO_TARGET,
198
199  /* The builtin corresponds to a comparison instruction followed by
200     a mips_cond_move_tf_ps pattern.  The first two arguments are the
201     values to compare and the second two arguments are the vector
202     operands for the movt.ps or movf.ps instruction (in assembly order).  */
203  MIPS_BUILTIN_MOVF,
204  MIPS_BUILTIN_MOVT,
205
206  /* The builtin corresponds to a V2SF comparison instruction.  Operand 0
207     of this instruction is the result of the comparison, which has mode
208     CCV2 or CCV4.  The function arguments are mapped to operands 1 and
209     above.  The function's return value is an SImode boolean that is
210     true under the following conditions:
211
212     MIPS_BUILTIN_CMP_ANY: one of the registers is true
213     MIPS_BUILTIN_CMP_ALL: all of the registers are true
214     MIPS_BUILTIN_CMP_LOWER: the first register is true
215     MIPS_BUILTIN_CMP_UPPER: the second register is true.  */
216  MIPS_BUILTIN_CMP_ANY,
217  MIPS_BUILTIN_CMP_ALL,
218  MIPS_BUILTIN_CMP_UPPER,
219  MIPS_BUILTIN_CMP_LOWER,
220
221  /* As above, but the instruction only sets a single $fcc register.  */
222  MIPS_BUILTIN_CMP_SINGLE,
223
224  /* For generating bposge32 branch instructions in MIPS32 DSP ASE.  */
225  MIPS_BUILTIN_BPOSGE32
226};
227
228/* Invokes MACRO (COND) for each c.cond.fmt condition.  */
229#define MIPS_FP_CONDITIONS(MACRO) \
230  MACRO (f),	\
231  MACRO (un),	\
232  MACRO (eq),	\
233  MACRO (ueq),	\
234  MACRO (olt),	\
235  MACRO (ult),	\
236  MACRO (ole),	\
237  MACRO (ule),	\
238  MACRO (sf),	\
239  MACRO (ngle),	\
240  MACRO (seq),	\
241  MACRO (ngl),	\
242  MACRO (lt),	\
243  MACRO (nge),	\
244  MACRO (le),	\
245  MACRO (ngt)
246
247/* Enumerates the codes above as MIPS_FP_COND_<X>.  */
248#define DECLARE_MIPS_COND(X) MIPS_FP_COND_ ## X
249enum mips_fp_condition {
250  MIPS_FP_CONDITIONS (DECLARE_MIPS_COND)
251};
252
253/* Index X provides the string representation of MIPS_FP_COND_<X>.  */
254#define STRINGIFY(X) #X
255static const char *const mips_fp_conditions[] = {
256  MIPS_FP_CONDITIONS (STRINGIFY)
257};
258
259/* A function to save or store a register.  The first argument is the
260   register and the second is the stack slot.  */
261typedef void (*mips_save_restore_fn) (rtx, rtx);
262
263struct mips16_constant;
264struct mips_arg_info;
265struct mips_address_info;
266struct mips_integer_op;
267struct mips_sim;
268
269static enum mips_symbol_type mips_classify_symbol (rtx);
270static void mips_split_const (rtx, rtx *, HOST_WIDE_INT *);
271static bool mips_offset_within_object_p (rtx, HOST_WIDE_INT);
272static bool mips_valid_base_register_p (rtx, enum machine_mode, int);
273static bool mips_symbolic_address_p (enum mips_symbol_type, enum machine_mode);
274static bool mips_classify_address (struct mips_address_info *, rtx,
275				   enum machine_mode, int);
276static bool mips_cannot_force_const_mem (rtx);
277static bool mips_use_blocks_for_constant_p (enum machine_mode, rtx);
278static int mips_symbol_insns (enum mips_symbol_type);
279static bool mips16_unextended_reference_p (enum machine_mode mode, rtx, rtx);
280static rtx mips_force_temporary (rtx, rtx);
281static rtx mips_unspec_offset_high (rtx, rtx, rtx, enum mips_symbol_type);
282static rtx mips_add_offset (rtx, rtx, HOST_WIDE_INT);
283static unsigned int mips_build_shift (struct mips_integer_op *, HOST_WIDE_INT);
284static unsigned int mips_build_lower (struct mips_integer_op *,
285				      unsigned HOST_WIDE_INT);
286static unsigned int mips_build_integer (struct mips_integer_op *,
287					unsigned HOST_WIDE_INT);
288static void mips_legitimize_const_move (enum machine_mode, rtx, rtx);
289static int m16_check_op (rtx, int, int, int);
290static bool mips_rtx_costs (rtx, int, int, int *);
291static int mips_address_cost (rtx);
292static void mips_emit_compare (enum rtx_code *, rtx *, rtx *, bool);
293static void mips_load_call_address (rtx, rtx, int);
294static bool mips_function_ok_for_sibcall (tree, tree);
295static void mips_block_move_straight (rtx, rtx, HOST_WIDE_INT);
296static void mips_adjust_block_mem (rtx, HOST_WIDE_INT, rtx *, rtx *);
297static void mips_block_move_loop (rtx, rtx, HOST_WIDE_INT);
298static void mips_arg_info (const CUMULATIVE_ARGS *, enum machine_mode,
299			   tree, int, struct mips_arg_info *);
300static bool mips_get_unaligned_mem (rtx *, unsigned int, int, rtx *, rtx *);
301static void mips_set_architecture (const struct mips_cpu_info *);
302static void mips_set_tune (const struct mips_cpu_info *);
303static bool mips_handle_option (size_t, const char *, int);
304static struct machine_function *mips_init_machine_status (void);
305static void print_operand_reloc (FILE *, rtx, const char **);
306#if TARGET_IRIX
307static void irix_output_external_libcall (rtx);
308#endif
309static void mips_file_start (void);
310static void mips_file_end (void);
311static bool mips_rewrite_small_data_p (rtx);
312static int mips_small_data_pattern_1 (rtx *, void *);
313static int mips_rewrite_small_data_1 (rtx *, void *);
314static bool mips_function_has_gp_insn (void);
315static unsigned int mips_global_pointer	(void);
316static bool mips_save_reg_p (unsigned int);
317static void mips_save_restore_reg (enum machine_mode, int, HOST_WIDE_INT,
318				   mips_save_restore_fn);
319static void mips_for_each_saved_reg (HOST_WIDE_INT, mips_save_restore_fn);
320static void mips_output_cplocal (void);
321static void mips_emit_loadgp (void);
322static void mips_output_function_prologue (FILE *, HOST_WIDE_INT);
323static void mips_set_frame_expr (rtx);
324static rtx mips_frame_set (rtx, rtx);
325static void mips_save_reg (rtx, rtx);
326static void mips_output_function_epilogue (FILE *, HOST_WIDE_INT);
327static void mips_restore_reg (rtx, rtx);
328static void mips_output_mi_thunk (FILE *, tree, HOST_WIDE_INT,
329				  HOST_WIDE_INT, tree);
330static int symbolic_expression_p (rtx);
331static section *mips_select_rtx_section (enum machine_mode, rtx,
332					 unsigned HOST_WIDE_INT);
333static section *mips_function_rodata_section (tree);
334static bool mips_in_small_data_p (tree);
335static bool mips_use_anchors_for_symbol_p (rtx);
336static int mips_fpr_return_fields (tree, tree *);
337static bool mips_return_in_msb (tree);
338static rtx mips_return_fpr_pair (enum machine_mode mode,
339				 enum machine_mode mode1, HOST_WIDE_INT,
340				 enum machine_mode mode2, HOST_WIDE_INT);
341static rtx mips16_gp_pseudo_reg (void);
342static void mips16_fp_args (FILE *, int, int);
343static void build_mips16_function_stub (FILE *);
344static rtx dump_constants_1 (enum machine_mode, rtx, rtx);
345static void dump_constants (struct mips16_constant *, rtx);
346static int mips16_insn_length (rtx);
347static int mips16_rewrite_pool_refs (rtx *, void *);
348static void mips16_lay_out_constants (void);
349static void mips_sim_reset (struct mips_sim *);
350static void mips_sim_init (struct mips_sim *, state_t);
351static void mips_sim_next_cycle (struct mips_sim *);
352static void mips_sim_wait_reg (struct mips_sim *, rtx, rtx);
353static int mips_sim_wait_regs_2 (rtx *, void *);
354static void mips_sim_wait_regs_1 (rtx *, void *);
355static void mips_sim_wait_regs (struct mips_sim *, rtx);
356static void mips_sim_wait_units (struct mips_sim *, rtx);
357static void mips_sim_wait_insn (struct mips_sim *, rtx);
358static void mips_sim_record_set (rtx, rtx, void *);
359static void mips_sim_issue_insn (struct mips_sim *, rtx);
360static void mips_sim_issue_nop (struct mips_sim *);
361static void mips_sim_finish_insn (struct mips_sim *, rtx);
362static void vr4130_avoid_branch_rt_conflict (rtx);
363static void vr4130_align_insns (void);
364static void mips_avoid_hazard (rtx, rtx, int *, rtx *, rtx);
365static void mips_avoid_hazards (void);
366static void mips_reorg (void);
367static bool mips_strict_matching_cpu_name_p (const char *, const char *);
368static bool mips_matching_cpu_name_p (const char *, const char *);
369static const struct mips_cpu_info *mips_parse_cpu (const char *);
370static const struct mips_cpu_info *mips_cpu_info_from_isa (int);
371static bool mips_return_in_memory (tree, tree);
372static bool mips_strict_argument_naming (CUMULATIVE_ARGS *);
373static void mips_macc_chains_record (rtx);
374static void mips_macc_chains_reorder (rtx *, int);
375static void vr4130_true_reg_dependence_p_1 (rtx, rtx, void *);
376static bool vr4130_true_reg_dependence_p (rtx);
377static bool vr4130_swap_insns_p (rtx, rtx);
378static void vr4130_reorder (rtx *, int);
379static void mips_promote_ready (rtx *, int, int);
380static int mips_sched_reorder (FILE *, int, rtx *, int *, int);
381static int mips_variable_issue (FILE *, int, rtx, int);
382static int mips_adjust_cost (rtx, rtx, rtx, int);
383static int mips_issue_rate (void);
384static int mips_multipass_dfa_lookahead (void);
385static void mips_init_libfuncs (void);
386static void mips_setup_incoming_varargs (CUMULATIVE_ARGS *, enum machine_mode,
387					 tree, int *, int);
388static tree mips_build_builtin_va_list (void);
389static tree mips_gimplify_va_arg_expr (tree, tree, tree *, tree *);
390static bool mips_pass_by_reference (CUMULATIVE_ARGS *, enum machine_mode mode,
391				    tree, bool);
392static bool mips_callee_copies (CUMULATIVE_ARGS *, enum machine_mode mode,
393				tree, bool);
394static int mips_arg_partial_bytes (CUMULATIVE_ARGS *, enum machine_mode mode,
395				   tree, bool);
396static bool mips_valid_pointer_mode (enum machine_mode);
397static bool mips_vector_mode_supported_p (enum machine_mode);
398static rtx mips_prepare_builtin_arg (enum insn_code, unsigned int, tree *);
399static rtx mips_prepare_builtin_target (enum insn_code, unsigned int, rtx);
400static rtx mips_expand_builtin (tree, rtx, rtx, enum machine_mode, int);
401static void mips_init_builtins (void);
402static rtx mips_expand_builtin_direct (enum insn_code, rtx, tree, bool);
403static rtx mips_expand_builtin_movtf (enum mips_builtin_type,
404				      enum insn_code, enum mips_fp_condition,
405				      rtx, tree);
406static rtx mips_expand_builtin_compare (enum mips_builtin_type,
407					enum insn_code, enum mips_fp_condition,
408					rtx, tree);
409static rtx mips_expand_builtin_bposge (enum mips_builtin_type, rtx);
410static void mips_encode_section_info (tree, rtx, int);
411static void mips_extra_live_on_entry (bitmap);
412static int mips_mode_rep_extended (enum machine_mode, enum machine_mode);
413
414/* Structure to be filled in by compute_frame_size with register
415   save masks, and offsets for the current function.  */
416
417struct mips_frame_info GTY(())
418{
419  HOST_WIDE_INT total_size;	/* # bytes that the entire frame takes up */
420  HOST_WIDE_INT var_size;	/* # bytes that variables take up */
421  HOST_WIDE_INT args_size;	/* # bytes that outgoing arguments take up */
422  HOST_WIDE_INT cprestore_size;	/* # bytes that the .cprestore slot takes up */
423  HOST_WIDE_INT gp_reg_size;	/* # bytes needed to store gp regs */
424  HOST_WIDE_INT fp_reg_size;	/* # bytes needed to store fp regs */
425  unsigned int mask;		/* mask of saved gp registers */
426  unsigned int fmask;		/* mask of saved fp registers */
427  HOST_WIDE_INT gp_save_offset;	/* offset from vfp to store gp registers */
428  HOST_WIDE_INT fp_save_offset;	/* offset from vfp to store fp registers */
429  HOST_WIDE_INT gp_sp_offset;	/* offset from new sp to store gp registers */
430  HOST_WIDE_INT fp_sp_offset;	/* offset from new sp to store fp registers */
431  bool initialized;		/* true if frame size already calculated */
432  int num_gp;			/* number of gp registers saved */
433  int num_fp;			/* number of fp registers saved */
434};
435
436struct machine_function GTY(()) {
437  /* Pseudo-reg holding the value of $28 in a mips16 function which
438     refers to GP relative global variables.  */
439  rtx mips16_gp_pseudo_rtx;
440
441  /* The number of extra stack bytes taken up by register varargs.
442     This area is allocated by the callee at the very top of the frame.  */
443  int varargs_size;
444
445  /* Current frame information, calculated by compute_frame_size.  */
446  struct mips_frame_info frame;
447
448  /* The register to use as the global pointer within this function.  */
449  unsigned int global_pointer;
450
451  /* True if mips_adjust_insn_length should ignore an instruction's
452     hazard attribute.  */
453  bool ignore_hazard_length_p;
454
455  /* True if the whole function is suitable for .set noreorder and
456     .set nomacro.  */
457  bool all_noreorder_p;
458
459  /* True if the function is known to have an instruction that needs $gp.  */
460  bool has_gp_insn_p;
461};
462
463/* Information about a single argument.  */
464struct mips_arg_info
465{
466  /* True if the argument is passed in a floating-point register, or
467     would have been if we hadn't run out of registers.  */
468  bool fpr_p;
469
470  /* The number of words passed in registers, rounded up.  */
471  unsigned int reg_words;
472
473  /* For EABI, the offset of the first register from GP_ARG_FIRST or
474     FP_ARG_FIRST.  For other ABIs, the offset of the first register from
475     the start of the ABI's argument structure (see the CUMULATIVE_ARGS
476     comment for details).
477
478     The value is MAX_ARGS_IN_REGISTERS if the argument is passed entirely
479     on the stack.  */
480  unsigned int reg_offset;
481
482  /* The number of words that must be passed on the stack, rounded up.  */
483  unsigned int stack_words;
484
485  /* The offset from the start of the stack overflow area of the argument's
486     first stack word.  Only meaningful when STACK_WORDS is nonzero.  */
487  unsigned int stack_offset;
488};
489
490
491/* Information about an address described by mips_address_type.
492
493   ADDRESS_CONST_INT
494       No fields are used.
495
496   ADDRESS_REG
497       REG is the base register and OFFSET is the constant offset.
498
499   ADDRESS_LO_SUM
500       REG is the register that contains the high part of the address,
501       OFFSET is the symbolic address being referenced and SYMBOL_TYPE
502       is the type of OFFSET's symbol.
503
504   ADDRESS_SYMBOLIC
505       SYMBOL_TYPE is the type of symbol being referenced.  */
506
507struct mips_address_info
508{
509  enum mips_address_type type;
510  rtx reg;
511  rtx offset;
512  enum mips_symbol_type symbol_type;
513};
514
515
516/* One stage in a constant building sequence.  These sequences have
517   the form:
518
519	A = VALUE[0]
520	A = A CODE[1] VALUE[1]
521	A = A CODE[2] VALUE[2]
522	...
523
524   where A is an accumulator, each CODE[i] is a binary rtl operation
525   and each VALUE[i] is a constant integer.  */
526struct mips_integer_op {
527  enum rtx_code code;
528  unsigned HOST_WIDE_INT value;
529};
530
531
532/* The largest number of operations needed to load an integer constant.
533   The worst accepted case for 64-bit constants is LUI,ORI,SLL,ORI,SLL,ORI.
534   When the lowest bit is clear, we can try, but reject a sequence with
535   an extra SLL at the end.  */
536#define MIPS_MAX_INTEGER_OPS 7
537
538
539/* Global variables for machine-dependent things.  */
540
541/* Threshold for data being put into the small data/bss area, instead
542   of the normal data area.  */
543int mips_section_threshold = -1;
544
545/* Count the number of .file directives, so that .loc is up to date.  */
546int num_source_filenames = 0;
547
548/* Count the number of sdb related labels are generated (to find block
549   start and end boundaries).  */
550int sdb_label_count = 0;
551
552/* Next label # for each statement for Silicon Graphics IRIS systems.  */
553int sym_lineno = 0;
554
555/* Linked list of all externals that are to be emitted when optimizing
556   for the global pointer if they haven't been declared by the end of
557   the program with an appropriate .comm or initialization.  */
558
559struct extern_list GTY (())
560{
561  struct extern_list *next;	/* next external */
562  const char *name;		/* name of the external */
563  int size;			/* size in bytes */
564};
565
566static GTY (()) struct extern_list *extern_head = 0;
567
568/* Name of the file containing the current function.  */
569const char *current_function_file = "";
570
571/* Number of nested .set noreorder, noat, nomacro, and volatile requests.  */
572int set_noreorder;
573int set_noat;
574int set_nomacro;
575int set_volatile;
576
577/* The next branch instruction is a branch likely, not branch normal.  */
578int mips_branch_likely;
579
580/* The operands passed to the last cmpMM expander.  */
581rtx cmp_operands[2];
582
583/* The target cpu for code generation.  */
584enum processor_type mips_arch;
585const struct mips_cpu_info *mips_arch_info;
586
587/* The target cpu for optimization and scheduling.  */
588enum processor_type mips_tune;
589const struct mips_cpu_info *mips_tune_info;
590
591/* Which instruction set architecture to use.  */
592int mips_isa;
593
594/* Which ABI to use.  */
595int mips_abi = MIPS_ABI_DEFAULT;
596
597/* Cost information to use.  */
598const struct mips_rtx_cost_data *mips_cost;
599
600/* Whether we are generating mips16 hard float code.  In mips16 mode
601   we always set TARGET_SOFT_FLOAT; this variable is nonzero if
602   -msoft-float was not specified by the user, which means that we
603   should arrange to call mips32 hard floating point code.  */
604int mips16_hard_float;
605
606/* The architecture selected by -mipsN.  */
607static const struct mips_cpu_info *mips_isa_info;
608
609/* If TRUE, we split addresses into their high and low parts in the RTL.  */
610int mips_split_addresses;
611
612/* Mode used for saving/restoring general purpose registers.  */
613static enum machine_mode gpr_mode;
614
615/* Array giving truth value on whether or not a given hard register
616   can support a given mode.  */
617char mips_hard_regno_mode_ok[(int)MAX_MACHINE_MODE][FIRST_PSEUDO_REGISTER];
618
619/* List of all MIPS punctuation characters used by print_operand.  */
620char mips_print_operand_punct[256];
621
622/* Map GCC register number to debugger register number.  */
623int mips_dbx_regno[FIRST_PSEUDO_REGISTER];
624
625/* A copy of the original flag_delayed_branch: see override_options.  */
626static int mips_flag_delayed_branch;
627
628static GTY (()) int mips_output_filename_first_time = 1;
629
630/* mips_split_p[X] is true if symbols of type X can be split by
631   mips_split_symbol().  */
632bool mips_split_p[NUM_SYMBOL_TYPES];
633
634/* mips_lo_relocs[X] is the relocation to use when a symbol of type X
635   appears in a LO_SUM.  It can be null if such LO_SUMs aren't valid or
636   if they are matched by a special .md file pattern.  */
637static const char *mips_lo_relocs[NUM_SYMBOL_TYPES];
638
639/* Likewise for HIGHs.  */
640static const char *mips_hi_relocs[NUM_SYMBOL_TYPES];
641
642/* Map hard register number to register class */
643const enum reg_class mips_regno_to_class[] =
644{
645  LEA_REGS,	LEA_REGS,	M16_NA_REGS,	V1_REG,
646  M16_REGS,	M16_REGS,	M16_REGS,	M16_REGS,
647  LEA_REGS,	LEA_REGS,	LEA_REGS,	LEA_REGS,
648  LEA_REGS,	LEA_REGS,	LEA_REGS,	LEA_REGS,
649  M16_NA_REGS,	M16_NA_REGS,	LEA_REGS,	LEA_REGS,
650  LEA_REGS,	LEA_REGS,	LEA_REGS,	LEA_REGS,
651  T_REG,	PIC_FN_ADDR_REG, LEA_REGS,	LEA_REGS,
652  LEA_REGS,	LEA_REGS,	LEA_REGS,	LEA_REGS,
653  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
654  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
655  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
656  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
657  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
658  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
659  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
660  FP_REGS,	FP_REGS,	FP_REGS,	FP_REGS,
661  HI_REG,	LO_REG,		NO_REGS,	ST_REGS,
662  ST_REGS,	ST_REGS,	ST_REGS,	ST_REGS,
663  ST_REGS,	ST_REGS,	ST_REGS,	NO_REGS,
664  NO_REGS,	ALL_REGS,	ALL_REGS,	NO_REGS,
665  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
666  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
667  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
668  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
669  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
670  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
671  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
672  COP0_REGS,	COP0_REGS,	COP0_REGS,	COP0_REGS,
673  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
674  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
675  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
676  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
677  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
678  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
679  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
680  COP2_REGS,	COP2_REGS,	COP2_REGS,	COP2_REGS,
681  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
682  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
683  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
684  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
685  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
686  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
687  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
688  COP3_REGS,	COP3_REGS,	COP3_REGS,	COP3_REGS,
689  DSP_ACC_REGS,	DSP_ACC_REGS,	DSP_ACC_REGS,	DSP_ACC_REGS,
690  DSP_ACC_REGS,	DSP_ACC_REGS,	ALL_REGS,	ALL_REGS,
691  ALL_REGS,	ALL_REGS,	ALL_REGS,	ALL_REGS
692};
693
694/* Table of machine dependent attributes.  */
695const struct attribute_spec mips_attribute_table[] =
696{
697  { "long_call",   0, 0, false, true,  true,  NULL },
698  { NULL,	   0, 0, false, false, false, NULL }
699};
700
701/* A table describing all the processors gcc knows about.  Names are
702   matched in the order listed.  The first mention of an ISA level is
703   taken as the canonical name for that ISA.
704
705   To ease comparison, please keep this table in the same order as
706   gas's mips_cpu_info_table[].  */
707const struct mips_cpu_info mips_cpu_info_table[] = {
708  /* Entries for generic ISAs */
709  { "mips1", PROCESSOR_R3000, 1 },
710  { "mips2", PROCESSOR_R6000, 2 },
711  { "mips3", PROCESSOR_R4000, 3 },
712  { "mips4", PROCESSOR_R8000, 4 },
713  { "mips32", PROCESSOR_4KC, 32 },
714  { "mips32r2", PROCESSOR_M4K, 33 },
715  { "mips64", PROCESSOR_5KC, 64 },
716  { "mips64r2", PROCESSOR_5KC, 65 },
717
718  /* MIPS I */
719  { "r3000", PROCESSOR_R3000, 1 },
720  { "r2000", PROCESSOR_R3000, 1 }, /* = r3000 */
721  { "r3900", PROCESSOR_R3900, 1 },
722
723  /* MIPS II */
724  { "r6000", PROCESSOR_R6000, 2 },
725
726  /* MIPS III */
727  { "r4000", PROCESSOR_R4000, 3 },
728  { "vr4100", PROCESSOR_R4100, 3 },
729  { "vr4111", PROCESSOR_R4111, 3 },
730  { "vr4120", PROCESSOR_R4120, 3 },
731  { "vr4130", PROCESSOR_R4130, 3 },
732  { "vr4300", PROCESSOR_R4300, 3 },
733  { "r4400", PROCESSOR_R4000, 3 }, /* = r4000 */
734  { "r4600", PROCESSOR_R4600, 3 },
735  { "orion", PROCESSOR_R4600, 3 }, /* = r4600 */
736  { "r4650", PROCESSOR_R4650, 3 },
737
738  /* MIPS IV */
739  { "r8000", PROCESSOR_R8000, 4 },
740  { "vr5000", PROCESSOR_R5000, 4 },
741  { "vr5400", PROCESSOR_R5400, 4 },
742  { "vr5500", PROCESSOR_R5500, 4 },
743  { "rm7000", PROCESSOR_R7000, 4 },
744  { "rm9000", PROCESSOR_R9000, 4 },
745
746  /* MIPS32 */
747  { "4kc", PROCESSOR_4KC, 32 },
748  { "4km", PROCESSOR_4KC, 32 }, /* = 4kc */
749  { "4kp", PROCESSOR_4KP, 32 },
750
751  /* MIPS32 Release 2 */
752  { "m4k", PROCESSOR_M4K, 33 },
753  { "24k", PROCESSOR_24K, 33 },
754  { "24kc", PROCESSOR_24K, 33 },  /* 24K  no FPU */
755  { "24kf", PROCESSOR_24K, 33 },  /* 24K 1:2 FPU */
756  { "24kx", PROCESSOR_24KX, 33 }, /* 24K 1:1 FPU */
757
758  /* MIPS64 */
759  { "5kc", PROCESSOR_5KC, 64 },
760  { "5kf", PROCESSOR_5KF, 64 },
761  { "20kc", PROCESSOR_20KC, 64 },
762  { "sb1", PROCESSOR_SB1, 64 },
763  { "sb1a", PROCESSOR_SB1A, 64 },
764  { "sr71000", PROCESSOR_SR71000, 64 },
765
766  /* MIPS64R2 */
767  { "octeon", PROCESSOR_OCTEON, 65 },
768
769  /* End marker */
770  { 0, 0, 0 }
771};
772
773/* Default costs. If these are used for a processor we should look
774   up the actual costs.  */
775#define DEFAULT_COSTS COSTS_N_INSNS (6),  /* fp_add */       \
776                      COSTS_N_INSNS (7),  /* fp_mult_sf */   \
777                      COSTS_N_INSNS (8),  /* fp_mult_df */   \
778                      COSTS_N_INSNS (23), /* fp_div_sf */    \
779                      COSTS_N_INSNS (36), /* fp_div_df */    \
780                      COSTS_N_INSNS (10), /* int_mult_si */  \
781                      COSTS_N_INSNS (10), /* int_mult_di */  \
782                      COSTS_N_INSNS (69), /* int_div_si */   \
783                      COSTS_N_INSNS (69), /* int_div_di */   \
784                                       2, /* branch_cost */  \
785                                       4  /* memory_latency */
786
787/* Need to replace these with the costs of calling the appropriate
788   libgcc routine.  */
789#define SOFT_FP_COSTS COSTS_N_INSNS (256), /* fp_add */       \
790                      COSTS_N_INSNS (256), /* fp_mult_sf */   \
791                      COSTS_N_INSNS (256), /* fp_mult_df */   \
792                      COSTS_N_INSNS (256), /* fp_div_sf */    \
793                      COSTS_N_INSNS (256)  /* fp_div_df */
794
795static struct mips_rtx_cost_data const mips_rtx_cost_data[PROCESSOR_MAX] =
796  {
797    { /* R3000 */
798      COSTS_N_INSNS (2),            /* fp_add */
799      COSTS_N_INSNS (4),            /* fp_mult_sf */
800      COSTS_N_INSNS (5),            /* fp_mult_df */
801      COSTS_N_INSNS (12),           /* fp_div_sf */
802      COSTS_N_INSNS (19),           /* fp_div_df */
803      COSTS_N_INSNS (12),           /* int_mult_si */
804      COSTS_N_INSNS (12),           /* int_mult_di */
805      COSTS_N_INSNS (35),           /* int_div_si */
806      COSTS_N_INSNS (35),           /* int_div_di */
807                       1,           /* branch_cost */
808                       4            /* memory_latency */
809
810    },
811    { /* 4KC */
812      SOFT_FP_COSTS,
813      COSTS_N_INSNS (6),            /* int_mult_si */
814      COSTS_N_INSNS (6),            /* int_mult_di */
815      COSTS_N_INSNS (36),           /* int_div_si */
816      COSTS_N_INSNS (36),           /* int_div_di */
817                       1,           /* branch_cost */
818                       4            /* memory_latency */
819    },
820    { /* 4KP */
821      SOFT_FP_COSTS,
822      COSTS_N_INSNS (36),           /* int_mult_si */
823      COSTS_N_INSNS (36),           /* int_mult_di */
824      COSTS_N_INSNS (37),           /* int_div_si */
825      COSTS_N_INSNS (37),           /* int_div_di */
826                       1,           /* branch_cost */
827                       4            /* memory_latency */
828    },
829    { /* 5KC */
830      SOFT_FP_COSTS,
831      COSTS_N_INSNS (4),            /* int_mult_si */
832      COSTS_N_INSNS (11),           /* int_mult_di */
833      COSTS_N_INSNS (36),           /* int_div_si */
834      COSTS_N_INSNS (68),           /* int_div_di */
835                       1,           /* branch_cost */
836                       4            /* memory_latency */
837    },
838    { /* 5KF */
839      COSTS_N_INSNS (4),            /* fp_add */
840      COSTS_N_INSNS (4),            /* fp_mult_sf */
841      COSTS_N_INSNS (5),            /* fp_mult_df */
842      COSTS_N_INSNS (17),           /* fp_div_sf */
843      COSTS_N_INSNS (32),           /* fp_div_df */
844      COSTS_N_INSNS (4),            /* int_mult_si */
845      COSTS_N_INSNS (11),           /* int_mult_di */
846      COSTS_N_INSNS (36),           /* int_div_si */
847      COSTS_N_INSNS (68),           /* int_div_di */
848                       1,           /* branch_cost */
849                       4            /* memory_latency */
850    },
851    { /* 20KC */
852      DEFAULT_COSTS
853    },
854    { /* 24k */
855      COSTS_N_INSNS (8),            /* fp_add */
856      COSTS_N_INSNS (8),            /* fp_mult_sf */
857      COSTS_N_INSNS (10),           /* fp_mult_df */
858      COSTS_N_INSNS (34),           /* fp_div_sf */
859      COSTS_N_INSNS (64),           /* fp_div_df */
860      COSTS_N_INSNS (5),            /* int_mult_si */
861      COSTS_N_INSNS (5),            /* int_mult_di */
862      COSTS_N_INSNS (41),           /* int_div_si */
863      COSTS_N_INSNS (41),           /* int_div_di */
864                       1,           /* branch_cost */
865                       4            /* memory_latency */
866    },
867    { /* 24kx */
868      COSTS_N_INSNS (4),            /* fp_add */
869      COSTS_N_INSNS (4),            /* fp_mult_sf */
870      COSTS_N_INSNS (5),            /* fp_mult_df */
871      COSTS_N_INSNS (17),           /* fp_div_sf */
872      COSTS_N_INSNS (32),           /* fp_div_df */
873      COSTS_N_INSNS (5),            /* int_mult_si */
874      COSTS_N_INSNS (5),            /* int_mult_di */
875      COSTS_N_INSNS (41),           /* int_div_si */
876      COSTS_N_INSNS (41),           /* int_div_di */
877                       1,           /* branch_cost */
878                       4            /* memory_latency */
879    },
880    { /* M4k */
881      DEFAULT_COSTS
882    },
883    { /* R3900 */
884      COSTS_N_INSNS (2),            /* fp_add */
885      COSTS_N_INSNS (4),            /* fp_mult_sf */
886      COSTS_N_INSNS (5),            /* fp_mult_df */
887      COSTS_N_INSNS (12),           /* fp_div_sf */
888      COSTS_N_INSNS (19),           /* fp_div_df */
889      COSTS_N_INSNS (2),            /* int_mult_si */
890      COSTS_N_INSNS (2),            /* int_mult_di */
891      COSTS_N_INSNS (35),           /* int_div_si */
892      COSTS_N_INSNS (35),           /* int_div_di */
893                       1,           /* branch_cost */
894                       4            /* memory_latency */
895    },
896    { /* R6000 */
897      COSTS_N_INSNS (3),            /* fp_add */
898      COSTS_N_INSNS (5),            /* fp_mult_sf */
899      COSTS_N_INSNS (6),            /* fp_mult_df */
900      COSTS_N_INSNS (15),           /* fp_div_sf */
901      COSTS_N_INSNS (16),           /* fp_div_df */
902      COSTS_N_INSNS (17),           /* int_mult_si */
903      COSTS_N_INSNS (17),           /* int_mult_di */
904      COSTS_N_INSNS (38),           /* int_div_si */
905      COSTS_N_INSNS (38),           /* int_div_di */
906                       2,           /* branch_cost */
907                       6            /* memory_latency */
908    },
909    { /* R4000 */
910       COSTS_N_INSNS (6),           /* fp_add */
911       COSTS_N_INSNS (7),           /* fp_mult_sf */
912       COSTS_N_INSNS (8),           /* fp_mult_df */
913       COSTS_N_INSNS (23),          /* fp_div_sf */
914       COSTS_N_INSNS (36),          /* fp_div_df */
915       COSTS_N_INSNS (10),          /* int_mult_si */
916       COSTS_N_INSNS (10),          /* int_mult_di */
917       COSTS_N_INSNS (69),          /* int_div_si */
918       COSTS_N_INSNS (69),          /* int_div_di */
919                        2,          /* branch_cost */
920                        6           /* memory_latency */
921    },
922    { /* R4100 */
923      DEFAULT_COSTS
924    },
925    { /* R4111 */
926      DEFAULT_COSTS
927    },
928    { /* R4120 */
929      DEFAULT_COSTS
930    },
931    { /* R4130 */
932      /* The only costs that appear to be updated here are
933	 integer multiplication.  */
934      SOFT_FP_COSTS,
935      COSTS_N_INSNS (4),            /* int_mult_si */
936      COSTS_N_INSNS (6),            /* int_mult_di */
937      COSTS_N_INSNS (69),           /* int_div_si */
938      COSTS_N_INSNS (69),           /* int_div_di */
939                       1,           /* branch_cost */
940                       4            /* memory_latency */
941    },
942    { /* R4300 */
943      DEFAULT_COSTS
944    },
945    { /* R4600 */
946      DEFAULT_COSTS
947    },
948    { /* R4650 */
949      DEFAULT_COSTS
950    },
951    { /* R5000 */
952      COSTS_N_INSNS (6),            /* fp_add */
953      COSTS_N_INSNS (4),            /* fp_mult_sf */
954      COSTS_N_INSNS (5),            /* fp_mult_df */
955      COSTS_N_INSNS (23),           /* fp_div_sf */
956      COSTS_N_INSNS (36),           /* fp_div_df */
957      COSTS_N_INSNS (5),            /* int_mult_si */
958      COSTS_N_INSNS (5),            /* int_mult_di */
959      COSTS_N_INSNS (36),           /* int_div_si */
960      COSTS_N_INSNS (36),           /* int_div_di */
961                       1,           /* branch_cost */
962                       4            /* memory_latency */
963    },
964    { /* R5400 */
965      COSTS_N_INSNS (6),            /* fp_add */
966      COSTS_N_INSNS (5),            /* fp_mult_sf */
967      COSTS_N_INSNS (6),            /* fp_mult_df */
968      COSTS_N_INSNS (30),           /* fp_div_sf */
969      COSTS_N_INSNS (59),           /* fp_div_df */
970      COSTS_N_INSNS (3),            /* int_mult_si */
971      COSTS_N_INSNS (4),            /* int_mult_di */
972      COSTS_N_INSNS (42),           /* int_div_si */
973      COSTS_N_INSNS (74),           /* int_div_di */
974                       1,           /* branch_cost */
975                       4            /* memory_latency */
976    },
977    { /* R5500 */
978      COSTS_N_INSNS (6),            /* fp_add */
979      COSTS_N_INSNS (5),            /* fp_mult_sf */
980      COSTS_N_INSNS (6),            /* fp_mult_df */
981      COSTS_N_INSNS (30),           /* fp_div_sf */
982      COSTS_N_INSNS (59),           /* fp_div_df */
983      COSTS_N_INSNS (5),            /* int_mult_si */
984      COSTS_N_INSNS (9),            /* int_mult_di */
985      COSTS_N_INSNS (42),           /* int_div_si */
986      COSTS_N_INSNS (74),           /* int_div_di */
987                       1,           /* branch_cost */
988                       4            /* memory_latency */
989    },
990    { /* R7000 */
991      /* The only costs that are changed here are
992	 integer multiplication.  */
993      COSTS_N_INSNS (6),            /* fp_add */
994      COSTS_N_INSNS (7),            /* fp_mult_sf */
995      COSTS_N_INSNS (8),            /* fp_mult_df */
996      COSTS_N_INSNS (23),           /* fp_div_sf */
997      COSTS_N_INSNS (36),           /* fp_div_df */
998      COSTS_N_INSNS (5),            /* int_mult_si */
999      COSTS_N_INSNS (9),            /* int_mult_di */
1000      COSTS_N_INSNS (69),           /* int_div_si */
1001      COSTS_N_INSNS (69),           /* int_div_di */
1002                       1,           /* branch_cost */
1003                       4            /* memory_latency */
1004    },
1005    { /* R8000 */
1006      DEFAULT_COSTS
1007    },
1008    { /* R9000 */
1009      /* The only costs that are changed here are
1010	 integer multiplication.  */
1011      COSTS_N_INSNS (6),            /* fp_add */
1012      COSTS_N_INSNS (7),            /* fp_mult_sf */
1013      COSTS_N_INSNS (8),            /* fp_mult_df */
1014      COSTS_N_INSNS (23),           /* fp_div_sf */
1015      COSTS_N_INSNS (36),           /* fp_div_df */
1016      COSTS_N_INSNS (3),            /* int_mult_si */
1017      COSTS_N_INSNS (8),            /* int_mult_di */
1018      COSTS_N_INSNS (69),           /* int_div_si */
1019      COSTS_N_INSNS (69),           /* int_div_di */
1020                       1,           /* branch_cost */
1021                       4            /* memory_latency */
1022    },
1023    { /* SB1 */
1024      /* These costs are the same as the SB-1A below.  */
1025      COSTS_N_INSNS (4),            /* fp_add */
1026      COSTS_N_INSNS (4),            /* fp_mult_sf */
1027      COSTS_N_INSNS (4),            /* fp_mult_df */
1028      COSTS_N_INSNS (24),           /* fp_div_sf */
1029      COSTS_N_INSNS (32),           /* fp_div_df */
1030      COSTS_N_INSNS (3),            /* int_mult_si */
1031      COSTS_N_INSNS (4),            /* int_mult_di */
1032      COSTS_N_INSNS (36),           /* int_div_si */
1033      COSTS_N_INSNS (68),           /* int_div_di */
1034                       1,           /* branch_cost */
1035                       4            /* memory_latency */
1036    },
1037    { /* SB1-A */
1038      /* These costs are the same as the SB-1 above.  */
1039      COSTS_N_INSNS (4),            /* fp_add */
1040      COSTS_N_INSNS (4),            /* fp_mult_sf */
1041      COSTS_N_INSNS (4),            /* fp_mult_df */
1042      COSTS_N_INSNS (24),           /* fp_div_sf */
1043      COSTS_N_INSNS (32),           /* fp_div_df */
1044      COSTS_N_INSNS (3),            /* int_mult_si */
1045      COSTS_N_INSNS (4),            /* int_mult_di */
1046      COSTS_N_INSNS (36),           /* int_div_si */
1047      COSTS_N_INSNS (68),           /* int_div_di */
1048                       1,           /* branch_cost */
1049                       4            /* memory_latency */
1050    },
1051    { /* SR71000 */
1052      DEFAULT_COSTS
1053    },
1054  };
1055
1056
1057/* Nonzero if -march should decide the default value of MASK_SOFT_FLOAT.  */
1058#ifndef MIPS_MARCH_CONTROLS_SOFT_FLOAT
1059#define MIPS_MARCH_CONTROLS_SOFT_FLOAT 0
1060#endif
1061
1062/* Initialize the GCC target structure.  */
1063#undef TARGET_ASM_ALIGNED_HI_OP
1064#define TARGET_ASM_ALIGNED_HI_OP "\t.half\t"
1065#undef TARGET_ASM_ALIGNED_SI_OP
1066#define TARGET_ASM_ALIGNED_SI_OP "\t.word\t"
1067#undef TARGET_ASM_ALIGNED_DI_OP
1068#define TARGET_ASM_ALIGNED_DI_OP "\t.dword\t"
1069
1070#undef TARGET_ASM_FUNCTION_PROLOGUE
1071#define TARGET_ASM_FUNCTION_PROLOGUE mips_output_function_prologue
1072#undef TARGET_ASM_FUNCTION_EPILOGUE
1073#define TARGET_ASM_FUNCTION_EPILOGUE mips_output_function_epilogue
1074#undef TARGET_ASM_SELECT_RTX_SECTION
1075#define TARGET_ASM_SELECT_RTX_SECTION mips_select_rtx_section
1076#undef TARGET_ASM_FUNCTION_RODATA_SECTION
1077#define TARGET_ASM_FUNCTION_RODATA_SECTION mips_function_rodata_section
1078
1079#undef TARGET_SCHED_REORDER
1080#define TARGET_SCHED_REORDER mips_sched_reorder
1081#undef TARGET_SCHED_VARIABLE_ISSUE
1082#define TARGET_SCHED_VARIABLE_ISSUE mips_variable_issue
1083#undef TARGET_SCHED_ADJUST_COST
1084#define TARGET_SCHED_ADJUST_COST mips_adjust_cost
1085#undef TARGET_SCHED_ISSUE_RATE
1086#define TARGET_SCHED_ISSUE_RATE mips_issue_rate
1087#undef TARGET_SCHED_FIRST_CYCLE_MULTIPASS_DFA_LOOKAHEAD
1088#define TARGET_SCHED_FIRST_CYCLE_MULTIPASS_DFA_LOOKAHEAD \
1089  mips_multipass_dfa_lookahead
1090
1091#undef TARGET_DEFAULT_TARGET_FLAGS
1092#define TARGET_DEFAULT_TARGET_FLAGS		\
1093  (TARGET_DEFAULT				\
1094   | TARGET_CPU_DEFAULT				\
1095   | TARGET_ENDIAN_DEFAULT			\
1096   | TARGET_FP_EXCEPTIONS_DEFAULT		\
1097   | MASK_CHECK_ZERO_DIV			\
1098   | MASK_FUSED_MADD)
1099#undef TARGET_HANDLE_OPTION
1100#define TARGET_HANDLE_OPTION mips_handle_option
1101
1102#undef TARGET_FUNCTION_OK_FOR_SIBCALL
1103#define TARGET_FUNCTION_OK_FOR_SIBCALL mips_function_ok_for_sibcall
1104
1105#undef TARGET_VALID_POINTER_MODE
1106#define TARGET_VALID_POINTER_MODE mips_valid_pointer_mode
1107#undef TARGET_RTX_COSTS
1108#define TARGET_RTX_COSTS mips_rtx_costs
1109#undef TARGET_ADDRESS_COST
1110#define TARGET_ADDRESS_COST mips_address_cost
1111
1112#undef TARGET_IN_SMALL_DATA_P
1113#define TARGET_IN_SMALL_DATA_P mips_in_small_data_p
1114
1115#undef TARGET_MACHINE_DEPENDENT_REORG
1116#define TARGET_MACHINE_DEPENDENT_REORG mips_reorg
1117
1118#undef TARGET_ASM_FILE_START
1119#undef TARGET_ASM_FILE_END
1120#define TARGET_ASM_FILE_START mips_file_start
1121#define TARGET_ASM_FILE_END mips_file_end
1122#undef TARGET_ASM_FILE_START_FILE_DIRECTIVE
1123#define TARGET_ASM_FILE_START_FILE_DIRECTIVE true
1124
1125#undef TARGET_INIT_LIBFUNCS
1126#define TARGET_INIT_LIBFUNCS mips_init_libfuncs
1127
1128#undef TARGET_BUILD_BUILTIN_VA_LIST
1129#define TARGET_BUILD_BUILTIN_VA_LIST mips_build_builtin_va_list
1130#undef TARGET_GIMPLIFY_VA_ARG_EXPR
1131#define TARGET_GIMPLIFY_VA_ARG_EXPR mips_gimplify_va_arg_expr
1132
1133#undef TARGET_PROMOTE_FUNCTION_ARGS
1134#define TARGET_PROMOTE_FUNCTION_ARGS hook_bool_tree_true
1135#undef TARGET_PROMOTE_FUNCTION_RETURN
1136#define TARGET_PROMOTE_FUNCTION_RETURN hook_bool_tree_true
1137#undef TARGET_PROMOTE_PROTOTYPES
1138#define TARGET_PROMOTE_PROTOTYPES hook_bool_tree_true
1139
1140#undef TARGET_RETURN_IN_MEMORY
1141#define TARGET_RETURN_IN_MEMORY mips_return_in_memory
1142#undef TARGET_RETURN_IN_MSB
1143#define TARGET_RETURN_IN_MSB mips_return_in_msb
1144
1145#undef TARGET_ASM_OUTPUT_MI_THUNK
1146#define TARGET_ASM_OUTPUT_MI_THUNK mips_output_mi_thunk
1147#undef TARGET_ASM_CAN_OUTPUT_MI_THUNK
1148#define TARGET_ASM_CAN_OUTPUT_MI_THUNK hook_bool_tree_hwi_hwi_tree_true
1149
1150#undef TARGET_SETUP_INCOMING_VARARGS
1151#define TARGET_SETUP_INCOMING_VARARGS mips_setup_incoming_varargs
1152#undef TARGET_STRICT_ARGUMENT_NAMING
1153#define TARGET_STRICT_ARGUMENT_NAMING mips_strict_argument_naming
1154#undef TARGET_MUST_PASS_IN_STACK
1155#define TARGET_MUST_PASS_IN_STACK must_pass_in_stack_var_size
1156#undef TARGET_PASS_BY_REFERENCE
1157#define TARGET_PASS_BY_REFERENCE mips_pass_by_reference
1158#undef TARGET_CALLEE_COPIES
1159#define TARGET_CALLEE_COPIES mips_callee_copies
1160#undef TARGET_ARG_PARTIAL_BYTES
1161#define TARGET_ARG_PARTIAL_BYTES mips_arg_partial_bytes
1162
1163#undef TARGET_MODE_REP_EXTENDED
1164#define TARGET_MODE_REP_EXTENDED mips_mode_rep_extended
1165
1166#undef TARGET_VECTOR_MODE_SUPPORTED_P
1167#define TARGET_VECTOR_MODE_SUPPORTED_P mips_vector_mode_supported_p
1168
1169#undef TARGET_INIT_BUILTINS
1170#define TARGET_INIT_BUILTINS mips_init_builtins
1171#undef TARGET_EXPAND_BUILTIN
1172#define TARGET_EXPAND_BUILTIN mips_expand_builtin
1173
1174#undef TARGET_HAVE_TLS
1175#define TARGET_HAVE_TLS HAVE_AS_TLS
1176
1177#undef TARGET_CANNOT_FORCE_CONST_MEM
1178#define TARGET_CANNOT_FORCE_CONST_MEM mips_cannot_force_const_mem
1179
1180#undef TARGET_ENCODE_SECTION_INFO
1181#define TARGET_ENCODE_SECTION_INFO mips_encode_section_info
1182
1183#undef TARGET_ATTRIBUTE_TABLE
1184#define TARGET_ATTRIBUTE_TABLE mips_attribute_table
1185
1186#undef TARGET_EXTRA_LIVE_ON_ENTRY
1187#define TARGET_EXTRA_LIVE_ON_ENTRY mips_extra_live_on_entry
1188
1189#undef TARGET_MIN_ANCHOR_OFFSET
1190#define TARGET_MIN_ANCHOR_OFFSET -32768
1191#undef TARGET_MAX_ANCHOR_OFFSET
1192#define TARGET_MAX_ANCHOR_OFFSET 32767
1193#undef TARGET_USE_BLOCKS_FOR_CONSTANT_P
1194#define TARGET_USE_BLOCKS_FOR_CONSTANT_P mips_use_blocks_for_constant_p
1195#undef TARGET_USE_ANCHORS_FOR_SYMBOL_P
1196#define TARGET_USE_ANCHORS_FOR_SYMBOL_P mips_use_anchors_for_symbol_p
1197
1198struct gcc_target targetm = TARGET_INITIALIZER;
1199
1200/* Classify symbol X, which must be a SYMBOL_REF or a LABEL_REF.  */
1201
1202static enum mips_symbol_type
1203mips_classify_symbol (rtx x)
1204{
1205  if (GET_CODE (x) == LABEL_REF)
1206    {
1207      if (TARGET_MIPS16)
1208	return SYMBOL_CONSTANT_POOL;
1209      if (TARGET_ABICALLS && !TARGET_ABSOLUTE_ABICALLS)
1210	return SYMBOL_GOT_LOCAL;
1211      return SYMBOL_GENERAL;
1212    }
1213
1214  gcc_assert (GET_CODE (x) == SYMBOL_REF);
1215
1216  if (SYMBOL_REF_TLS_MODEL (x))
1217    return SYMBOL_TLS;
1218
1219  if (CONSTANT_POOL_ADDRESS_P (x))
1220    {
1221      if (TARGET_MIPS16)
1222	return SYMBOL_CONSTANT_POOL;
1223
1224      if (GET_MODE_SIZE (get_pool_mode (x)) <= mips_section_threshold)
1225	return SYMBOL_SMALL_DATA;
1226    }
1227
1228  /* Do not use small-data accesses for weak symbols; they may end up
1229     being zero.  */
1230  if (SYMBOL_REF_SMALL_P (x)
1231      && !SYMBOL_REF_WEAK (x))
1232    return SYMBOL_SMALL_DATA;
1233
1234  if (TARGET_ABICALLS)
1235    {
1236      if (SYMBOL_REF_DECL (x) == 0)
1237	{
1238	  if (!SYMBOL_REF_LOCAL_P (x))
1239	    return SYMBOL_GOT_GLOBAL;
1240	}
1241      else
1242	{
1243	  /* Don't use GOT accesses for locally-binding symbols if
1244	     TARGET_ABSOLUTE_ABICALLS.  Otherwise, there are three
1245	     cases to consider:
1246
1247		- o32 PIC (either with or without explicit relocs)
1248		- n32/n64 PIC without explicit relocs
1249		- n32/n64 PIC with explicit relocs
1250
1251	     In the first case, both local and global accesses will use an
1252	     R_MIPS_GOT16 relocation.  We must correctly predict which of
1253	     the two semantics (local or global) the assembler and linker
1254	     will apply.  The choice doesn't depend on the symbol's
1255	     visibility, so we deliberately ignore decl_visibility and
1256	     binds_local_p here.
1257
1258	     In the second case, the assembler will not use R_MIPS_GOT16
1259	     relocations, but it chooses between local and global accesses
1260	     in the same way as for o32 PIC.
1261
1262	     In the third case we have more freedom since both forms of
1263	     access will work for any kind of symbol.  However, there seems
1264	     little point in doing things differently.  */
1265	  if (DECL_P (SYMBOL_REF_DECL (x))
1266	      && TREE_PUBLIC (SYMBOL_REF_DECL (x))
1267	      && !(TARGET_ABSOLUTE_ABICALLS
1268		   && targetm.binds_local_p (SYMBOL_REF_DECL (x))))
1269	    return SYMBOL_GOT_GLOBAL;
1270	}
1271
1272      if (!TARGET_ABSOLUTE_ABICALLS)
1273	return SYMBOL_GOT_LOCAL;
1274    }
1275
1276  return SYMBOL_GENERAL;
1277}
1278
1279
1280/* Split X into a base and a constant offset, storing them in *BASE
1281   and *OFFSET respectively.  */
1282
1283static void
1284mips_split_const (rtx x, rtx *base, HOST_WIDE_INT *offset)
1285{
1286  *offset = 0;
1287
1288  if (GET_CODE (x) == CONST)
1289    {
1290      x = XEXP (x, 0);
1291      if (GET_CODE (x) == PLUS && GET_CODE (XEXP (x, 1)) == CONST_INT)
1292	{
1293	  *offset += INTVAL (XEXP (x, 1));
1294	  x = XEXP (x, 0);
1295	}
1296    }
1297  *base = x;
1298}
1299
1300/* Classify symbolic expression X, given that it appears in context
1301   CONTEXT.  */
1302
1303static enum mips_symbol_type
1304mips_classify_symbolic_expression (rtx x)
1305{
1306  HOST_WIDE_INT offset;
1307
1308  mips_split_const (x, &x, &offset);
1309  if (UNSPEC_ADDRESS_P (x))
1310    return UNSPEC_ADDRESS_TYPE (x);
1311
1312  return mips_classify_symbol (x);
1313}
1314
1315/* Return true if SYMBOL is a SYMBOL_REF and OFFSET + SYMBOL points
1316   to the same object as SYMBOL, or to the same object_block.  */
1317
1318static bool
1319mips_offset_within_object_p (rtx symbol, HOST_WIDE_INT offset)
1320{
1321  if (GET_CODE (symbol) != SYMBOL_REF)
1322    return false;
1323
1324  if (CONSTANT_POOL_ADDRESS_P (symbol)
1325      && offset >= 0
1326      && offset < (int) GET_MODE_SIZE (get_pool_mode (symbol)))
1327    return true;
1328
1329  if (SYMBOL_REF_DECL (symbol) != 0
1330      && offset >= 0
1331      && offset < int_size_in_bytes (TREE_TYPE (SYMBOL_REF_DECL (symbol))))
1332    return true;
1333
1334  if (SYMBOL_REF_HAS_BLOCK_INFO_P (symbol)
1335      && SYMBOL_REF_BLOCK (symbol)
1336      && SYMBOL_REF_BLOCK_OFFSET (symbol) >= 0
1337      && ((unsigned HOST_WIDE_INT) offset + SYMBOL_REF_BLOCK_OFFSET (symbol)
1338	  < (unsigned HOST_WIDE_INT) SYMBOL_REF_BLOCK (symbol)->size))
1339    return true;
1340
1341  return false;
1342}
1343
1344
1345/* Return true if X is a symbolic constant that can be calculated in
1346   the same way as a bare symbol.  If it is, store the type of the
1347   symbol in *SYMBOL_TYPE.  */
1348
1349bool
1350mips_symbolic_constant_p (rtx x, enum mips_symbol_type *symbol_type)
1351{
1352  HOST_WIDE_INT offset;
1353
1354  mips_split_const (x, &x, &offset);
1355  if (UNSPEC_ADDRESS_P (x))
1356    *symbol_type = UNSPEC_ADDRESS_TYPE (x);
1357  else if (GET_CODE (x) == SYMBOL_REF || GET_CODE (x) == LABEL_REF)
1358    {
1359      *symbol_type = mips_classify_symbol (x);
1360      if (*symbol_type == SYMBOL_TLS)
1361	return false;
1362    }
1363  else
1364    return false;
1365
1366  if (offset == 0)
1367    return true;
1368
1369  /* Check whether a nonzero offset is valid for the underlying
1370     relocations.  */
1371  switch (*symbol_type)
1372    {
1373    case SYMBOL_GENERAL:
1374    case SYMBOL_64_HIGH:
1375    case SYMBOL_64_MID:
1376    case SYMBOL_64_LOW:
1377      /* If the target has 64-bit pointers and the object file only
1378	 supports 32-bit symbols, the values of those symbols will be
1379	 sign-extended.  In this case we can't allow an arbitrary offset
1380	 in case the 32-bit value X + OFFSET has a different sign from X.  */
1381      if (Pmode == DImode && !ABI_HAS_64BIT_SYMBOLS)
1382	return mips_offset_within_object_p (x, offset);
1383
1384      /* In other cases the relocations can handle any offset.  */
1385      return true;
1386
1387    case SYMBOL_CONSTANT_POOL:
1388      /* Allow constant pool references to be converted to LABEL+CONSTANT.
1389	 In this case, we no longer have access to the underlying constant,
1390	 but the original symbol-based access was known to be valid.  */
1391      if (GET_CODE (x) == LABEL_REF)
1392	return true;
1393
1394      /* Fall through.  */
1395
1396    case SYMBOL_SMALL_DATA:
1397      /* Make sure that the offset refers to something within the
1398	 underlying object.  This should guarantee that the final
1399	 PC- or GP-relative offset is within the 16-bit limit.  */
1400      return mips_offset_within_object_p (x, offset);
1401
1402    case SYMBOL_GOT_LOCAL:
1403    case SYMBOL_GOTOFF_PAGE:
1404      /* The linker should provide enough local GOT entries for a
1405	 16-bit offset.  Larger offsets may lead to GOT overflow.  */
1406      return SMALL_OPERAND (offset);
1407
1408    case SYMBOL_GOT_GLOBAL:
1409    case SYMBOL_GOTOFF_GLOBAL:
1410    case SYMBOL_GOTOFF_CALL:
1411    case SYMBOL_GOTOFF_LOADGP:
1412    case SYMBOL_TLSGD:
1413    case SYMBOL_TLSLDM:
1414    case SYMBOL_DTPREL:
1415    case SYMBOL_TPREL:
1416    case SYMBOL_GOTTPREL:
1417    case SYMBOL_TLS:
1418      return false;
1419    }
1420  gcc_unreachable ();
1421}
1422
1423
1424/* This function is used to implement REG_MODE_OK_FOR_BASE_P.  */
1425
1426int
1427mips_regno_mode_ok_for_base_p (int regno, enum machine_mode mode, int strict)
1428{
1429  if (regno >= FIRST_PSEUDO_REGISTER)
1430    {
1431      if (!strict)
1432	return true;
1433      regno = reg_renumber[regno];
1434    }
1435
1436  /* These fake registers will be eliminated to either the stack or
1437     hard frame pointer, both of which are usually valid base registers.
1438     Reload deals with the cases where the eliminated form isn't valid.  */
1439  if (regno == ARG_POINTER_REGNUM || regno == FRAME_POINTER_REGNUM)
1440    return true;
1441
1442  /* In mips16 mode, the stack pointer can only address word and doubleword
1443     values, nothing smaller.  There are two problems here:
1444
1445       (a) Instantiating virtual registers can introduce new uses of the
1446	   stack pointer.  If these virtual registers are valid addresses,
1447	   the stack pointer should be too.
1448
1449       (b) Most uses of the stack pointer are not made explicit until
1450	   FRAME_POINTER_REGNUM and ARG_POINTER_REGNUM have been eliminated.
1451	   We don't know until that stage whether we'll be eliminating to the
1452	   stack pointer (which needs the restriction) or the hard frame
1453	   pointer (which doesn't).
1454
1455     All in all, it seems more consistent to only enforce this restriction
1456     during and after reload.  */
1457  if (TARGET_MIPS16 && regno == STACK_POINTER_REGNUM)
1458    return !strict || GET_MODE_SIZE (mode) == 4 || GET_MODE_SIZE (mode) == 8;
1459
1460  return TARGET_MIPS16 ? M16_REG_P (regno) : GP_REG_P (regno);
1461}
1462
1463
1464/* Return true if X is a valid base register for the given mode.
1465   Allow only hard registers if STRICT.  */
1466
1467static bool
1468mips_valid_base_register_p (rtx x, enum machine_mode mode, int strict)
1469{
1470  if (!strict && GET_CODE (x) == SUBREG)
1471    x = SUBREG_REG (x);
1472
1473  return (REG_P (x)
1474	  && mips_regno_mode_ok_for_base_p (REGNO (x), mode, strict));
1475}
1476
1477
1478/* Return true if symbols of type SYMBOL_TYPE can directly address a value
1479   with mode MODE.  This is used for both symbolic and LO_SUM addresses.  */
1480
1481static bool
1482mips_symbolic_address_p (enum mips_symbol_type symbol_type,
1483			 enum machine_mode mode)
1484{
1485  switch (symbol_type)
1486    {
1487    case SYMBOL_GENERAL:
1488      return !TARGET_MIPS16;
1489
1490    case SYMBOL_SMALL_DATA:
1491      return true;
1492
1493    case SYMBOL_CONSTANT_POOL:
1494      /* PC-relative addressing is only available for lw and ld.  */
1495      return GET_MODE_SIZE (mode) == 4 || GET_MODE_SIZE (mode) == 8;
1496
1497    case SYMBOL_GOT_LOCAL:
1498      return true;
1499
1500    case SYMBOL_GOT_GLOBAL:
1501      /* The address will have to be loaded from the GOT first.  */
1502      return false;
1503
1504    case SYMBOL_GOTOFF_PAGE:
1505    case SYMBOL_GOTOFF_GLOBAL:
1506    case SYMBOL_GOTOFF_CALL:
1507    case SYMBOL_GOTOFF_LOADGP:
1508    case SYMBOL_TLS:
1509    case SYMBOL_TLSGD:
1510    case SYMBOL_TLSLDM:
1511    case SYMBOL_DTPREL:
1512    case SYMBOL_GOTTPREL:
1513    case SYMBOL_TPREL:
1514    case SYMBOL_64_HIGH:
1515    case SYMBOL_64_MID:
1516    case SYMBOL_64_LOW:
1517      return true;
1518    }
1519  gcc_unreachable ();
1520}
1521
1522
1523/* Return true if X is a valid address for machine mode MODE.  If it is,
1524   fill in INFO appropriately.  STRICT is true if we should only accept
1525   hard base registers.  */
1526
1527static bool
1528mips_classify_address (struct mips_address_info *info, rtx x,
1529		       enum machine_mode mode, int strict)
1530{
1531  switch (GET_CODE (x))
1532    {
1533    case REG:
1534    case SUBREG:
1535      info->type = ADDRESS_REG;
1536      info->reg = x;
1537      info->offset = const0_rtx;
1538      return mips_valid_base_register_p (info->reg, mode, strict);
1539
1540    case PLUS:
1541      info->type = ADDRESS_REG;
1542      info->reg = XEXP (x, 0);
1543      info->offset = XEXP (x, 1);
1544      return (mips_valid_base_register_p (info->reg, mode, strict)
1545	      && const_arith_operand (info->offset, VOIDmode));
1546
1547    case LO_SUM:
1548      info->type = ADDRESS_LO_SUM;
1549      info->reg = XEXP (x, 0);
1550      info->offset = XEXP (x, 1);
1551      /* We have to trust the creator of the LO_SUM to do something vaguely
1552	 sane.  Target-independent code that creates a LO_SUM should also
1553	 create and verify the matching HIGH.  Target-independent code that
1554	 adds an offset to a LO_SUM must prove that the offset will not
1555	 induce a carry.  Failure to do either of these things would be
1556	 a bug, and we are not required to check for it here.  The MIPS
1557	 backend itself should only create LO_SUMs for valid symbolic
1558	 constants, with the high part being either a HIGH or a copy
1559	 of _gp. */
1560      info->symbol_type = mips_classify_symbolic_expression (info->offset);
1561      return (mips_valid_base_register_p (info->reg, mode, strict)
1562	      && mips_symbolic_address_p (info->symbol_type, mode)
1563	      && mips_lo_relocs[info->symbol_type] != 0);
1564
1565    case CONST_INT:
1566      /* Small-integer addresses don't occur very often, but they
1567	 are legitimate if $0 is a valid base register.  */
1568      info->type = ADDRESS_CONST_INT;
1569      return !TARGET_MIPS16 && SMALL_INT (x);
1570
1571    case CONST:
1572    case LABEL_REF:
1573    case SYMBOL_REF:
1574      info->type = ADDRESS_SYMBOLIC;
1575      return (mips_symbolic_constant_p (x, &info->symbol_type)
1576	      && mips_symbolic_address_p (info->symbol_type, mode)
1577	      && !mips_split_p[info->symbol_type]);
1578
1579    default:
1580      return false;
1581    }
1582}
1583
1584/* Return true if X is a thread-local symbol.  */
1585
1586static bool
1587mips_tls_operand_p (rtx x)
1588{
1589  return GET_CODE (x) == SYMBOL_REF && SYMBOL_REF_TLS_MODEL (x) != 0;
1590}
1591
1592/* Return true if X can not be forced into a constant pool.  */
1593
1594static int
1595mips_tls_symbol_ref_1 (rtx *x, void *data ATTRIBUTE_UNUSED)
1596{
1597  return mips_tls_operand_p (*x);
1598}
1599
1600/* Return true if X can not be forced into a constant pool.  */
1601
1602static bool
1603mips_cannot_force_const_mem (rtx x)
1604{
1605  rtx base;
1606  HOST_WIDE_INT offset;
1607
1608  if (!TARGET_MIPS16)
1609    {
1610      /* As an optimization, reject constants that mips_legitimize_move
1611	 can expand inline.
1612
1613	 Suppose we have a multi-instruction sequence that loads constant C
1614	 into register R.  If R does not get allocated a hard register, and
1615	 R is used in an operand that allows both registers and memory
1616	 references, reload will consider forcing C into memory and using
1617	 one of the instruction's memory alternatives.  Returning false
1618	 here will force it to use an input reload instead.  */
1619      if (GET_CODE (x) == CONST_INT)
1620	return true;
1621
1622      mips_split_const (x, &base, &offset);
1623      if (symbolic_operand (base, VOIDmode) && SMALL_OPERAND (offset))
1624	return true;
1625    }
1626
1627  if (TARGET_HAVE_TLS && for_each_rtx (&x, &mips_tls_symbol_ref_1, 0))
1628    return true;
1629
1630  return false;
1631}
1632
1633/* Implement TARGET_USE_BLOCKS_FOR_CONSTANT_P.  MIPS16 uses per-function
1634   constant pools, but normal-mode code doesn't need to.  */
1635
1636static bool
1637mips_use_blocks_for_constant_p (enum machine_mode mode ATTRIBUTE_UNUSED,
1638				rtx x ATTRIBUTE_UNUSED)
1639{
1640  return !TARGET_MIPS16;
1641}
1642
1643/* Return the number of instructions needed to load a symbol of the
1644   given type into a register.  If valid in an address, the same number
1645   of instructions are needed for loads and stores.  Treat extended
1646   mips16 instructions as two instructions.  */
1647
1648static int
1649mips_symbol_insns (enum mips_symbol_type type)
1650{
1651  switch (type)
1652    {
1653    case SYMBOL_GENERAL:
1654      /* In mips16 code, general symbols must be fetched from the
1655	 constant pool.  */
1656      if (TARGET_MIPS16)
1657	return 0;
1658
1659      /* When using 64-bit symbols, we need 5 preparatory instructions,
1660	 such as:
1661
1662	     lui     $at,%highest(symbol)
1663	     daddiu  $at,$at,%higher(symbol)
1664	     dsll    $at,$at,16
1665	     daddiu  $at,$at,%hi(symbol)
1666	     dsll    $at,$at,16
1667
1668	 The final address is then $at + %lo(symbol).  With 32-bit
1669	 symbols we just need a preparatory lui.  */
1670      return (ABI_HAS_64BIT_SYMBOLS ? 6 : 2);
1671
1672    case SYMBOL_SMALL_DATA:
1673      return 1;
1674
1675    case SYMBOL_CONSTANT_POOL:
1676      /* This case is for mips16 only.  Assume we'll need an
1677	 extended instruction.  */
1678      return 2;
1679
1680    case SYMBOL_GOT_LOCAL:
1681    case SYMBOL_GOT_GLOBAL:
1682      /* Unless -funit-at-a-time is in effect, we can't be sure whether
1683	 the local/global classification is accurate.  See override_options
1684	 for details.
1685
1686	 The worst cases are:
1687
1688	 (1) For local symbols when generating o32 or o64 code.  The assembler
1689	     will use:
1690
1691		 lw	      $at,%got(symbol)
1692		 nop
1693
1694	     ...and the final address will be $at + %lo(symbol).
1695
1696	 (2) For global symbols when -mxgot.  The assembler will use:
1697
1698	         lui     $at,%got_hi(symbol)
1699	         (d)addu $at,$at,$gp
1700
1701	     ...and the final address will be $at + %got_lo(symbol).  */
1702      return 3;
1703
1704    case SYMBOL_GOTOFF_PAGE:
1705    case SYMBOL_GOTOFF_GLOBAL:
1706    case SYMBOL_GOTOFF_CALL:
1707    case SYMBOL_GOTOFF_LOADGP:
1708    case SYMBOL_64_HIGH:
1709    case SYMBOL_64_MID:
1710    case SYMBOL_64_LOW:
1711    case SYMBOL_TLSGD:
1712    case SYMBOL_TLSLDM:
1713    case SYMBOL_DTPREL:
1714    case SYMBOL_GOTTPREL:
1715    case SYMBOL_TPREL:
1716      /* Check whether the offset is a 16- or 32-bit value.  */
1717      return mips_split_p[type] ? 2 : 1;
1718
1719    case SYMBOL_TLS:
1720      /* We don't treat a bare TLS symbol as a constant.  */
1721      return 0;
1722    }
1723  gcc_unreachable ();
1724}
1725
1726/* Return true if X is a legitimate $sp-based address for mode MDOE.  */
1727
1728bool
1729mips_stack_address_p (rtx x, enum machine_mode mode)
1730{
1731  struct mips_address_info addr;
1732
1733  return (mips_classify_address (&addr, x, mode, false)
1734	  && addr.type == ADDRESS_REG
1735	  && addr.reg == stack_pointer_rtx);
1736}
1737
1738/* Return true if a value at OFFSET bytes from BASE can be accessed
1739   using an unextended mips16 instruction.  MODE is the mode of the
1740   value.
1741
1742   Usually the offset in an unextended instruction is a 5-bit field.
1743   The offset is unsigned and shifted left once for HIs, twice
1744   for SIs, and so on.  An exception is SImode accesses off the
1745   stack pointer, which have an 8-bit immediate field.  */
1746
1747static bool
1748mips16_unextended_reference_p (enum machine_mode mode, rtx base, rtx offset)
1749{
1750  if (TARGET_MIPS16
1751      && GET_CODE (offset) == CONST_INT
1752      && INTVAL (offset) >= 0
1753      && (INTVAL (offset) & (GET_MODE_SIZE (mode) - 1)) == 0)
1754    {
1755      if (GET_MODE_SIZE (mode) == 4 && base == stack_pointer_rtx)
1756	return INTVAL (offset) < 256 * GET_MODE_SIZE (mode);
1757      return INTVAL (offset) < 32 * GET_MODE_SIZE (mode);
1758    }
1759  return false;
1760}
1761
1762
1763/* Return the number of instructions needed to load or store a value
1764   of mode MODE at X.  Return 0 if X isn't valid for MODE.
1765
1766   For mips16 code, count extended instructions as two instructions.  */
1767
1768int
1769mips_address_insns (rtx x, enum machine_mode mode)
1770{
1771  struct mips_address_info addr;
1772  int factor;
1773
1774  if (mode == BLKmode)
1775    /* BLKmode is used for single unaligned loads and stores.  */
1776    factor = 1;
1777  else
1778    /* Each word of a multi-word value will be accessed individually.  */
1779    factor = (GET_MODE_SIZE (mode) + UNITS_PER_WORD - 1) / UNITS_PER_WORD;
1780
1781  if (mips_classify_address (&addr, x, mode, false))
1782    switch (addr.type)
1783      {
1784      case ADDRESS_REG:
1785	if (TARGET_MIPS16
1786	    && !mips16_unextended_reference_p (mode, addr.reg, addr.offset))
1787	  return factor * 2;
1788	return factor;
1789
1790      case ADDRESS_LO_SUM:
1791	return (TARGET_MIPS16 ? factor * 2 : factor);
1792
1793      case ADDRESS_CONST_INT:
1794	return factor;
1795
1796      case ADDRESS_SYMBOLIC:
1797	return factor * mips_symbol_insns (addr.symbol_type);
1798      }
1799  return 0;
1800}
1801
1802
1803/* Likewise for constant X.  */
1804
1805int
1806mips_const_insns (rtx x)
1807{
1808  struct mips_integer_op codes[MIPS_MAX_INTEGER_OPS];
1809  enum mips_symbol_type symbol_type;
1810  HOST_WIDE_INT offset;
1811
1812  switch (GET_CODE (x))
1813    {
1814    case HIGH:
1815      if (TARGET_MIPS16
1816	  || !mips_symbolic_constant_p (XEXP (x, 0), &symbol_type)
1817	  || !mips_split_p[symbol_type])
1818	return 0;
1819
1820      return 1;
1821
1822    case CONST_INT:
1823      if (TARGET_MIPS16)
1824	/* Unsigned 8-bit constants can be loaded using an unextended
1825	   LI instruction.  Unsigned 16-bit constants can be loaded
1826	   using an extended LI.  Negative constants must be loaded
1827	   using LI and then negated.  */
1828	return (INTVAL (x) >= 0 && INTVAL (x) < 256 ? 1
1829		: SMALL_OPERAND_UNSIGNED (INTVAL (x)) ? 2
1830		: INTVAL (x) > -256 && INTVAL (x) < 0 ? 2
1831		: SMALL_OPERAND_UNSIGNED (-INTVAL (x)) ? 3
1832		: 0);
1833
1834      return mips_build_integer (codes, INTVAL (x));
1835
1836    case CONST_DOUBLE:
1837    case CONST_VECTOR:
1838      return (!TARGET_MIPS16 && x == CONST0_RTX (GET_MODE (x)) ? 1 : 0);
1839
1840    case CONST:
1841      if (CONST_GP_P (x))
1842	return 1;
1843
1844      /* See if we can refer to X directly.  */
1845      if (mips_symbolic_constant_p (x, &symbol_type))
1846	return mips_symbol_insns (symbol_type);
1847
1848      /* Otherwise try splitting the constant into a base and offset.
1849	 16-bit offsets can be added using an extra addiu.  Larger offsets
1850	 must be calculated separately and then added to the base.  */
1851      mips_split_const (x, &x, &offset);
1852      if (offset != 0)
1853	{
1854	  int n = mips_const_insns (x);
1855	  if (n != 0)
1856	    {
1857	      if (SMALL_OPERAND (offset))
1858		return n + 1;
1859	      else
1860		return n + 1 + mips_build_integer (codes, offset);
1861	    }
1862	}
1863      return 0;
1864
1865    case SYMBOL_REF:
1866    case LABEL_REF:
1867      return mips_symbol_insns (mips_classify_symbol (x));
1868
1869    default:
1870      return 0;
1871    }
1872}
1873
1874
1875/* Return the number of instructions needed for memory reference X.
1876   Count extended mips16 instructions as two instructions.  */
1877
1878int
1879mips_fetch_insns (rtx x)
1880{
1881  gcc_assert (MEM_P (x));
1882  return mips_address_insns (XEXP (x, 0), GET_MODE (x));
1883}
1884
1885
1886/* Return the number of instructions needed for an integer division.  */
1887
1888int
1889mips_idiv_insns (void)
1890{
1891  int count;
1892
1893  count = 1;
1894  if (TARGET_CHECK_ZERO_DIV)
1895    {
1896      if (GENERATE_DIVIDE_TRAPS)
1897        count++;
1898      else
1899        count += 2;
1900    }
1901
1902  if (TARGET_FIX_R4000 || TARGET_FIX_R4400)
1903    count++;
1904  return count;
1905}
1906
1907/* This function is used to implement GO_IF_LEGITIMATE_ADDRESS.  It
1908   returns a nonzero value if X is a legitimate address for a memory
1909   operand of the indicated MODE.  STRICT is nonzero if this function
1910   is called during reload.  */
1911
1912bool
1913mips_legitimate_address_p (enum machine_mode mode, rtx x, int strict)
1914{
1915  struct mips_address_info addr;
1916
1917  return mips_classify_address (&addr, x, mode, strict);
1918}
1919
1920
1921/* Copy VALUE to a register and return that register.  If new psuedos
1922   are allowed, copy it into a new register, otherwise use DEST.  */
1923
1924static rtx
1925mips_force_temporary (rtx dest, rtx value)
1926{
1927  if (!no_new_pseudos)
1928    return force_reg (Pmode, value);
1929  else
1930    {
1931      emit_move_insn (copy_rtx (dest), value);
1932      return dest;
1933    }
1934}
1935
1936
1937/* Return a LO_SUM expression for ADDR.  TEMP is as for mips_force_temporary
1938   and is used to load the high part into a register.  */
1939
1940rtx
1941mips_split_symbol (rtx temp, rtx addr)
1942{
1943  rtx high;
1944
1945  if (TARGET_MIPS16)
1946    high = mips16_gp_pseudo_reg ();
1947  else
1948    high = mips_force_temporary (temp, gen_rtx_HIGH (Pmode, copy_rtx (addr)));
1949  return gen_rtx_LO_SUM (Pmode, high, addr);
1950}
1951
1952
1953/* Return an UNSPEC address with underlying address ADDRESS and symbol
1954   type SYMBOL_TYPE.  */
1955
1956rtx
1957mips_unspec_address (rtx address, enum mips_symbol_type symbol_type)
1958{
1959  rtx base;
1960  HOST_WIDE_INT offset;
1961
1962  mips_split_const (address, &base, &offset);
1963  base = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, base),
1964			 UNSPEC_ADDRESS_FIRST + symbol_type);
1965  return plus_constant (gen_rtx_CONST (Pmode, base), offset);
1966}
1967
1968
1969/* If mips_unspec_address (ADDR, SYMBOL_TYPE) is a 32-bit value, add the
1970   high part to BASE and return the result.  Just return BASE otherwise.
1971   TEMP is available as a temporary register if needed.
1972
1973   The returned expression can be used as the first operand to a LO_SUM.  */
1974
1975static rtx
1976mips_unspec_offset_high (rtx temp, rtx base, rtx addr,
1977			 enum mips_symbol_type symbol_type)
1978{
1979  if (mips_split_p[symbol_type])
1980    {
1981      addr = gen_rtx_HIGH (Pmode, mips_unspec_address (addr, symbol_type));
1982      addr = mips_force_temporary (temp, addr);
1983      return mips_force_temporary (temp, gen_rtx_PLUS (Pmode, addr, base));
1984    }
1985  return base;
1986}
1987
1988
1989/* Return a legitimate address for REG + OFFSET.  TEMP is as for
1990   mips_force_temporary; it is only needed when OFFSET is not a
1991   SMALL_OPERAND.  */
1992
1993static rtx
1994mips_add_offset (rtx temp, rtx reg, HOST_WIDE_INT offset)
1995{
1996  if (!SMALL_OPERAND (offset))
1997    {
1998      rtx high;
1999      if (TARGET_MIPS16)
2000	{
2001	  /* Load the full offset into a register so that we can use
2002	     an unextended instruction for the address itself.  */
2003	  high = GEN_INT (offset);
2004	  offset = 0;
2005	}
2006      else
2007	{
2008	  /* Leave OFFSET as a 16-bit offset and put the excess in HIGH.  */
2009	  high = GEN_INT (CONST_HIGH_PART (offset));
2010	  offset = CONST_LOW_PART (offset);
2011	}
2012      high = mips_force_temporary (temp, high);
2013      reg = mips_force_temporary (temp, gen_rtx_PLUS (Pmode, high, reg));
2014    }
2015  return plus_constant (reg, offset);
2016}
2017
2018/* Emit a call to __tls_get_addr.  SYM is the TLS symbol we are
2019   referencing, and TYPE is the symbol type to use (either global
2020   dynamic or local dynamic).  V0 is an RTX for the return value
2021   location.  The entire insn sequence is returned.  */
2022
2023static GTY(()) rtx mips_tls_symbol;
2024
2025static rtx
2026mips_call_tls_get_addr (rtx sym, enum mips_symbol_type type, rtx v0)
2027{
2028  rtx insn, loc, tga, a0;
2029
2030  a0 = gen_rtx_REG (Pmode, GP_ARG_FIRST);
2031
2032  if (!mips_tls_symbol)
2033    mips_tls_symbol = init_one_libfunc ("__tls_get_addr");
2034
2035  loc = mips_unspec_address (sym, type);
2036
2037  start_sequence ();
2038
2039  emit_insn (gen_rtx_SET (Pmode, a0,
2040			  gen_rtx_LO_SUM (Pmode, pic_offset_table_rtx, loc)));
2041  tga = gen_rtx_MEM (Pmode, mips_tls_symbol);
2042  insn = emit_call_insn (gen_call_value (v0, tga, const0_rtx, const0_rtx));
2043  CONST_OR_PURE_CALL_P (insn) = 1;
2044  use_reg (&CALL_INSN_FUNCTION_USAGE (insn), v0);
2045  use_reg (&CALL_INSN_FUNCTION_USAGE (insn), a0);
2046  insn = get_insns ();
2047
2048  end_sequence ();
2049
2050  return insn;
2051}
2052
2053/* Generate the code to access LOC, a thread local SYMBOL_REF.  The
2054   return value will be a valid address and move_operand (either a REG
2055   or a LO_SUM).  */
2056
2057static rtx
2058mips_legitimize_tls_address (rtx loc)
2059{
2060  rtx dest, insn, v0, v1, tmp1, tmp2, eqv;
2061  enum tls_model model;
2062
2063  v0 = gen_rtx_REG (Pmode, GP_RETURN);
2064  v1 = gen_rtx_REG (Pmode, GP_RETURN + 1);
2065
2066  model = SYMBOL_REF_TLS_MODEL (loc);
2067  /* Only TARGET_ABICALLS code can have more than one module; other
2068     code must be be static and should not use a GOT.  All TLS models
2069     reduce to local exec in this situation.  */
2070  if (!TARGET_ABICALLS)
2071    model = TLS_MODEL_LOCAL_EXEC;
2072
2073  switch (model)
2074    {
2075    case TLS_MODEL_GLOBAL_DYNAMIC:
2076      insn = mips_call_tls_get_addr (loc, SYMBOL_TLSGD, v0);
2077      dest = gen_reg_rtx (Pmode);
2078      emit_libcall_block (insn, dest, v0, loc);
2079      break;
2080
2081    case TLS_MODEL_LOCAL_DYNAMIC:
2082      insn = mips_call_tls_get_addr (loc, SYMBOL_TLSLDM, v0);
2083      tmp1 = gen_reg_rtx (Pmode);
2084
2085      /* Attach a unique REG_EQUIV, to allow the RTL optimizers to
2086	 share the LDM result with other LD model accesses.  */
2087      eqv = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, const0_rtx),
2088			    UNSPEC_TLS_LDM);
2089      emit_libcall_block (insn, tmp1, v0, eqv);
2090
2091      tmp2 = mips_unspec_offset_high (NULL, tmp1, loc, SYMBOL_DTPREL);
2092      dest = gen_rtx_LO_SUM (Pmode, tmp2,
2093			     mips_unspec_address (loc, SYMBOL_DTPREL));
2094      break;
2095
2096    case TLS_MODEL_INITIAL_EXEC:
2097      tmp1 = gen_reg_rtx (Pmode);
2098      tmp2 = mips_unspec_address (loc, SYMBOL_GOTTPREL);
2099      if (Pmode == DImode)
2100	{
2101	  emit_insn (gen_tls_get_tp_di (v1));
2102	  emit_insn (gen_load_gotdi (tmp1, pic_offset_table_rtx, tmp2));
2103	}
2104      else
2105	{
2106	  emit_insn (gen_tls_get_tp_si (v1));
2107	  emit_insn (gen_load_gotsi (tmp1, pic_offset_table_rtx, tmp2));
2108	}
2109      dest = gen_reg_rtx (Pmode);
2110      emit_insn (gen_add3_insn (dest, tmp1, v1));
2111      break;
2112
2113    case TLS_MODEL_LOCAL_EXEC:
2114      if (Pmode == DImode)
2115	emit_insn (gen_tls_get_tp_di (v1));
2116      else
2117	emit_insn (gen_tls_get_tp_si (v1));
2118
2119      tmp1 = mips_unspec_offset_high (NULL, v1, loc, SYMBOL_TPREL);
2120      dest = gen_rtx_LO_SUM (Pmode, tmp1,
2121			     mips_unspec_address (loc, SYMBOL_TPREL));
2122      break;
2123
2124    default:
2125      gcc_unreachable ();
2126    }
2127
2128  return dest;
2129}
2130
2131/* This function is used to implement LEGITIMIZE_ADDRESS.  If *XLOC can
2132   be legitimized in a way that the generic machinery might not expect,
2133   put the new address in *XLOC and return true.  MODE is the mode of
2134   the memory being accessed.  */
2135
2136bool
2137mips_legitimize_address (rtx *xloc, enum machine_mode mode)
2138{
2139  enum mips_symbol_type symbol_type;
2140
2141  if (mips_tls_operand_p (*xloc))
2142    {
2143      *xloc = mips_legitimize_tls_address (*xloc);
2144      return true;
2145    }
2146
2147  /* See if the address can split into a high part and a LO_SUM.  */
2148  if (mips_symbolic_constant_p (*xloc, &symbol_type)
2149      && mips_symbolic_address_p (symbol_type, mode)
2150      && mips_split_p[symbol_type])
2151    {
2152      *xloc = mips_split_symbol (0, *xloc);
2153      return true;
2154    }
2155
2156  if (GET_CODE (*xloc) == PLUS && GET_CODE (XEXP (*xloc, 1)) == CONST_INT)
2157    {
2158      /* Handle REG + CONSTANT using mips_add_offset.  */
2159      rtx reg;
2160
2161      reg = XEXP (*xloc, 0);
2162      if (!mips_valid_base_register_p (reg, mode, 0))
2163	reg = copy_to_mode_reg (Pmode, reg);
2164      *xloc = mips_add_offset (0, reg, INTVAL (XEXP (*xloc, 1)));
2165      return true;
2166    }
2167
2168  return false;
2169}
2170
2171
2172/* Subroutine of mips_build_integer (with the same interface).
2173   Assume that the final action in the sequence should be a left shift.  */
2174
2175static unsigned int
2176mips_build_shift (struct mips_integer_op *codes, HOST_WIDE_INT value)
2177{
2178  unsigned int i, shift;
2179
2180  /* Shift VALUE right until its lowest bit is set.  Shift arithmetically
2181     since signed numbers are easier to load than unsigned ones.  */
2182  shift = 0;
2183  while ((value & 1) == 0)
2184    value /= 2, shift++;
2185
2186  i = mips_build_integer (codes, value);
2187  codes[i].code = ASHIFT;
2188  codes[i].value = shift;
2189  return i + 1;
2190}
2191
2192
2193/* As for mips_build_shift, but assume that the final action will be
2194   an IOR or PLUS operation.  */
2195
2196static unsigned int
2197mips_build_lower (struct mips_integer_op *codes, unsigned HOST_WIDE_INT value)
2198{
2199  unsigned HOST_WIDE_INT high;
2200  unsigned int i;
2201
2202  high = value & ~(unsigned HOST_WIDE_INT) 0xffff;
2203  if (!LUI_OPERAND (high) && (value & 0x18000) == 0x18000)
2204    {
2205      /* The constant is too complex to load with a simple lui/ori pair
2206	 so our goal is to clear as many trailing zeros as possible.
2207	 In this case, we know bit 16 is set and that the low 16 bits
2208	 form a negative number.  If we subtract that number from VALUE,
2209	 we will clear at least the lowest 17 bits, maybe more.  */
2210      i = mips_build_integer (codes, CONST_HIGH_PART (value));
2211      codes[i].code = PLUS;
2212      codes[i].value = CONST_LOW_PART (value);
2213    }
2214  else
2215    {
2216      i = mips_build_integer (codes, high);
2217      codes[i].code = IOR;
2218      codes[i].value = value & 0xffff;
2219    }
2220  return i + 1;
2221}
2222
2223
2224/* Fill CODES with a sequence of rtl operations to load VALUE.
2225   Return the number of operations needed.  */
2226
2227static unsigned int
2228mips_build_integer (struct mips_integer_op *codes,
2229		    unsigned HOST_WIDE_INT value)
2230{
2231  if (SMALL_OPERAND (value)
2232      || SMALL_OPERAND_UNSIGNED (value)
2233      || LUI_OPERAND (value))
2234    {
2235      /* The value can be loaded with a single instruction.  */
2236      codes[0].code = UNKNOWN;
2237      codes[0].value = value;
2238      return 1;
2239    }
2240  else if ((value & 1) != 0 || LUI_OPERAND (CONST_HIGH_PART (value)))
2241    {
2242      /* Either the constant is a simple LUI/ORI combination or its
2243	 lowest bit is set.  We don't want to shift in this case.  */
2244      return mips_build_lower (codes, value);
2245    }
2246  else if ((value & 0xffff) == 0)
2247    {
2248      /* The constant will need at least three actions.  The lowest
2249	 16 bits are clear, so the final action will be a shift.  */
2250      return mips_build_shift (codes, value);
2251    }
2252  else
2253    {
2254      /* The final action could be a shift, add or inclusive OR.
2255	 Rather than use a complex condition to select the best
2256	 approach, try both mips_build_shift and mips_build_lower
2257	 and pick the one that gives the shortest sequence.
2258	 Note that this case is only used once per constant.  */
2259      struct mips_integer_op alt_codes[MIPS_MAX_INTEGER_OPS];
2260      unsigned int cost, alt_cost;
2261
2262      cost = mips_build_shift (codes, value);
2263      alt_cost = mips_build_lower (alt_codes, value);
2264      if (alt_cost < cost)
2265	{
2266	  memcpy (codes, alt_codes, alt_cost * sizeof (codes[0]));
2267	  cost = alt_cost;
2268	}
2269      return cost;
2270    }
2271}
2272
2273
2274/* Load VALUE into DEST, using TEMP as a temporary register if need be.  */
2275
2276void
2277mips_move_integer (rtx dest, rtx temp, unsigned HOST_WIDE_INT value)
2278{
2279  struct mips_integer_op codes[MIPS_MAX_INTEGER_OPS];
2280  enum machine_mode mode;
2281  unsigned int i, cost;
2282  rtx x;
2283
2284  mode = GET_MODE (dest);
2285  cost = mips_build_integer (codes, value);
2286
2287  /* Apply each binary operation to X.  Invariant: X is a legitimate
2288     source operand for a SET pattern.  */
2289  x = GEN_INT (codes[0].value);
2290  for (i = 1; i < cost; i++)
2291    {
2292      if (no_new_pseudos)
2293	{
2294	  emit_insn (gen_rtx_SET (VOIDmode, temp, x));
2295	  x = temp;
2296	}
2297      else
2298	x = force_reg (mode, x);
2299      x = gen_rtx_fmt_ee (codes[i].code, mode, x, GEN_INT (codes[i].value));
2300    }
2301
2302  emit_insn (gen_rtx_SET (VOIDmode, dest, x));
2303}
2304
2305
2306/* Subroutine of mips_legitimize_move.  Move constant SRC into register
2307   DEST given that SRC satisfies immediate_operand but doesn't satisfy
2308   move_operand.  */
2309
2310static void
2311mips_legitimize_const_move (enum machine_mode mode, rtx dest, rtx src)
2312{
2313  rtx base;
2314  HOST_WIDE_INT offset;
2315
2316  /* Split moves of big integers into smaller pieces.  */
2317  if (splittable_const_int_operand (src, mode))
2318    {
2319      mips_move_integer (dest, dest, INTVAL (src));
2320      return;
2321    }
2322
2323  /* Split moves of symbolic constants into high/low pairs.  */
2324  if (splittable_symbolic_operand (src, mode))
2325    {
2326      emit_insn (gen_rtx_SET (VOIDmode, dest, mips_split_symbol (dest, src)));
2327      return;
2328    }
2329
2330  if (mips_tls_operand_p (src))
2331    {
2332      emit_move_insn (dest, mips_legitimize_tls_address (src));
2333      return;
2334    }
2335
2336  /* If we have (const (plus symbol offset)), load the symbol first
2337     and then add in the offset.  This is usually better than forcing
2338     the constant into memory, at least in non-mips16 code.  */
2339  mips_split_const (src, &base, &offset);
2340  if (!TARGET_MIPS16
2341      && offset != 0
2342      && (!no_new_pseudos || SMALL_OPERAND (offset)))
2343    {
2344      base = mips_force_temporary (dest, base);
2345      emit_move_insn (dest, mips_add_offset (0, base, offset));
2346      return;
2347    }
2348
2349  src = force_const_mem (mode, src);
2350
2351  /* When using explicit relocs, constant pool references are sometimes
2352     not legitimate addresses.  */
2353  if (!memory_operand (src, VOIDmode))
2354    src = replace_equiv_address (src, mips_split_symbol (dest, XEXP (src, 0)));
2355  emit_move_insn (dest, src);
2356}
2357
2358
2359/* If (set DEST SRC) is not a valid instruction, emit an equivalent
2360   sequence that is valid.  */
2361
2362bool
2363mips_legitimize_move (enum machine_mode mode, rtx dest, rtx src)
2364{
2365  if (!register_operand (dest, mode) && !reg_or_0_operand (src, mode))
2366    {
2367      emit_move_insn (dest, force_reg (mode, src));
2368      return true;
2369    }
2370
2371  /* Check for individual, fully-reloaded mflo and mfhi instructions.  */
2372  if (GET_MODE_SIZE (mode) <= UNITS_PER_WORD
2373      && REG_P (src) && MD_REG_P (REGNO (src))
2374      && REG_P (dest) && GP_REG_P (REGNO (dest)))
2375    {
2376      int other_regno = REGNO (src) == HI_REGNUM ? LO_REGNUM : HI_REGNUM;
2377      if (GET_MODE_SIZE (mode) <= 4)
2378	emit_insn (gen_mfhilo_si (gen_rtx_REG (SImode, REGNO (dest)),
2379				  gen_rtx_REG (SImode, REGNO (src)),
2380				  gen_rtx_REG (SImode, other_regno)));
2381      else
2382	emit_insn (gen_mfhilo_di (gen_rtx_REG (DImode, REGNO (dest)),
2383				  gen_rtx_REG (DImode, REGNO (src)),
2384				  gen_rtx_REG (DImode, other_regno)));
2385      return true;
2386    }
2387
2388  /* We need to deal with constants that would be legitimate
2389     immediate_operands but not legitimate move_operands.  */
2390  if (CONSTANT_P (src) && !move_operand (src, mode))
2391    {
2392      mips_legitimize_const_move (mode, dest, src);
2393      set_unique_reg_note (get_last_insn (), REG_EQUAL, copy_rtx (src));
2394      return true;
2395    }
2396  return false;
2397}
2398
2399/* We need a lot of little routines to check constant values on the
2400   mips16.  These are used to figure out how long the instruction will
2401   be.  It would be much better to do this using constraints, but
2402   there aren't nearly enough letters available.  */
2403
2404static int
2405m16_check_op (rtx op, int low, int high, int mask)
2406{
2407  return (GET_CODE (op) == CONST_INT
2408	  && INTVAL (op) >= low
2409	  && INTVAL (op) <= high
2410	  && (INTVAL (op) & mask) == 0);
2411}
2412
2413int
2414m16_uimm3_b (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2415{
2416  return m16_check_op (op, 0x1, 0x8, 0);
2417}
2418
2419int
2420m16_simm4_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2421{
2422  return m16_check_op (op, - 0x8, 0x7, 0);
2423}
2424
2425int
2426m16_nsimm4_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2427{
2428  return m16_check_op (op, - 0x7, 0x8, 0);
2429}
2430
2431int
2432m16_simm5_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2433{
2434  return m16_check_op (op, - 0x10, 0xf, 0);
2435}
2436
2437int
2438m16_nsimm5_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2439{
2440  return m16_check_op (op, - 0xf, 0x10, 0);
2441}
2442
2443int
2444m16_uimm5_4 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2445{
2446  return m16_check_op (op, (- 0x10) << 2, 0xf << 2, 3);
2447}
2448
2449int
2450m16_nuimm5_4 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2451{
2452  return m16_check_op (op, (- 0xf) << 2, 0x10 << 2, 3);
2453}
2454
2455int
2456m16_simm8_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2457{
2458  return m16_check_op (op, - 0x80, 0x7f, 0);
2459}
2460
2461int
2462m16_nsimm8_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2463{
2464  return m16_check_op (op, - 0x7f, 0x80, 0);
2465}
2466
2467int
2468m16_uimm8_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2469{
2470  return m16_check_op (op, 0x0, 0xff, 0);
2471}
2472
2473int
2474m16_nuimm8_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2475{
2476  return m16_check_op (op, - 0xff, 0x0, 0);
2477}
2478
2479int
2480m16_uimm8_m1_1 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2481{
2482  return m16_check_op (op, - 0x1, 0xfe, 0);
2483}
2484
2485int
2486m16_uimm8_4 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2487{
2488  return m16_check_op (op, 0x0, 0xff << 2, 3);
2489}
2490
2491int
2492m16_nuimm8_4 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2493{
2494  return m16_check_op (op, (- 0xff) << 2, 0x0, 3);
2495}
2496
2497int
2498m16_simm8_8 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2499{
2500  return m16_check_op (op, (- 0x80) << 3, 0x7f << 3, 7);
2501}
2502
2503int
2504m16_nsimm8_8 (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
2505{
2506  return m16_check_op (op, (- 0x7f) << 3, 0x80 << 3, 7);
2507}
2508
2509static bool
2510mips_rtx_costs (rtx x, int code, int outer_code, int *total)
2511{
2512  enum machine_mode mode = GET_MODE (x);
2513  bool float_mode_p = FLOAT_MODE_P (mode);
2514
2515  switch (code)
2516    {
2517    case CONST_INT:
2518      if (TARGET_MIPS16)
2519        {
2520	  /* A number between 1 and 8 inclusive is efficient for a shift.
2521	     Otherwise, we will need an extended instruction.  */
2522	  if ((outer_code) == ASHIFT || (outer_code) == ASHIFTRT
2523	      || (outer_code) == LSHIFTRT)
2524	    {
2525	      if (INTVAL (x) >= 1 && INTVAL (x) <= 8)
2526		*total = 0;
2527	      else
2528		*total = COSTS_N_INSNS (1);
2529	      return true;
2530	    }
2531
2532	  /* We can use cmpi for an xor with an unsigned 16 bit value.  */
2533	  if ((outer_code) == XOR
2534	      && INTVAL (x) >= 0 && INTVAL (x) < 0x10000)
2535	    {
2536	      *total = 0;
2537	      return true;
2538	    }
2539
2540	  /* We may be able to use slt or sltu for a comparison with a
2541	     signed 16 bit value.  (The boundary conditions aren't quite
2542	     right, but this is just a heuristic anyhow.)  */
2543	  if (((outer_code) == LT || (outer_code) == LE
2544	       || (outer_code) == GE || (outer_code) == GT
2545	       || (outer_code) == LTU || (outer_code) == LEU
2546	       || (outer_code) == GEU || (outer_code) == GTU)
2547	      && INTVAL (x) >= -0x8000 && INTVAL (x) < 0x8000)
2548	    {
2549	      *total = 0;
2550	      return true;
2551	    }
2552
2553	  /* Equality comparisons with 0 are cheap.  */
2554	  if (((outer_code) == EQ || (outer_code) == NE)
2555	      && INTVAL (x) == 0)
2556	    {
2557	      *total = 0;
2558	      return true;
2559	    }
2560
2561	  /* Constants in the range 0...255 can be loaded with an unextended
2562	     instruction.  They are therefore as cheap as a register move.
2563
2564	     Given the choice between "li R1,0...255" and "move R1,R2"
2565	     (where R2 is a known constant), it is usually better to use "li",
2566	     since we do not want to unnecessarily extend the lifetime
2567	     of R2.  */
2568	  if (outer_code == SET
2569	      && INTVAL (x) >= 0
2570	      && INTVAL (x) < 256)
2571	    {
2572	      *total = 0;
2573	      return true;
2574	    }
2575	}
2576      else
2577	{
2578	  /* These can be used anywhere. */
2579	  *total = 0;
2580	  return true;
2581	}
2582
2583      /* Otherwise fall through to the handling below because
2584	 we'll need to construct the constant.  */
2585
2586    case CONST:
2587    case SYMBOL_REF:
2588    case LABEL_REF:
2589    case CONST_DOUBLE:
2590      if (LEGITIMATE_CONSTANT_P (x))
2591	{
2592	  *total = COSTS_N_INSNS (1);
2593	  return true;
2594	}
2595      else
2596	{
2597	  /* The value will need to be fetched from the constant pool.  */
2598	  *total = CONSTANT_POOL_COST;
2599	  return true;
2600	}
2601
2602    case MEM:
2603      {
2604	/* If the address is legitimate, return the number of
2605	   instructions it needs, otherwise use the default handling.  */
2606	int n = mips_address_insns (XEXP (x, 0), GET_MODE (x));
2607	if (n > 0)
2608	  {
2609	    *total = COSTS_N_INSNS (n + 1);
2610	    return true;
2611	  }
2612	return false;
2613      }
2614
2615    case FFS:
2616      *total = COSTS_N_INSNS (6);
2617      return true;
2618
2619    case NOT:
2620      *total = COSTS_N_INSNS ((mode == DImode && !TARGET_64BIT) ? 2 : 1);
2621      return true;
2622
2623    case AND:
2624    case IOR:
2625    case XOR:
2626      if (mode == DImode && !TARGET_64BIT)
2627        {
2628          *total = COSTS_N_INSNS (2);
2629          return true;
2630        }
2631      return false;
2632
2633    case ASHIFT:
2634    case ASHIFTRT:
2635    case LSHIFTRT:
2636      if (mode == DImode && !TARGET_64BIT)
2637        {
2638          *total = COSTS_N_INSNS ((GET_CODE (XEXP (x, 1)) == CONST_INT)
2639                                  ? 4 : 12);
2640          return true;
2641        }
2642      return false;
2643
2644    case ABS:
2645      if (float_mode_p)
2646        *total = COSTS_N_INSNS (1);
2647      else
2648        *total = COSTS_N_INSNS (4);
2649      return true;
2650
2651    case LO_SUM:
2652      *total = COSTS_N_INSNS (1);
2653      return true;
2654
2655    case PLUS:
2656    case MINUS:
2657      if (float_mode_p)
2658	{
2659	  *total = mips_cost->fp_add;
2660	  return true;
2661	}
2662
2663      else if (mode == DImode && !TARGET_64BIT)
2664        {
2665          *total = COSTS_N_INSNS (4);
2666          return true;
2667        }
2668      return false;
2669
2670    case NEG:
2671      if (mode == DImode && !TARGET_64BIT)
2672        {
2673          *total = COSTS_N_INSNS (4);
2674          return true;
2675        }
2676      return false;
2677
2678    case MULT:
2679      if (mode == SFmode)
2680	*total = mips_cost->fp_mult_sf;
2681
2682      else if (mode == DFmode)
2683	*total = mips_cost->fp_mult_df;
2684
2685      else if (mode == SImode)
2686	*total = mips_cost->int_mult_si;
2687
2688      else
2689	*total = mips_cost->int_mult_di;
2690
2691      return true;
2692
2693    case DIV:
2694    case MOD:
2695      if (float_mode_p)
2696	{
2697	  if (mode == SFmode)
2698	    *total = mips_cost->fp_div_sf;
2699	  else
2700	    *total = mips_cost->fp_div_df;
2701
2702	  return true;
2703	}
2704      /* Fall through.  */
2705
2706    case UDIV:
2707    case UMOD:
2708      if (mode == DImode)
2709        *total = mips_cost->int_div_di;
2710      else
2711	*total = mips_cost->int_div_si;
2712
2713      return true;
2714
2715    case SIGN_EXTEND:
2716      /* A sign extend from SImode to DImode in 64 bit mode is often
2717         zero instructions, because the result can often be used
2718         directly by another instruction; we'll call it one.  */
2719      if (TARGET_64BIT && mode == DImode
2720          && GET_MODE (XEXP (x, 0)) == SImode)
2721        *total = COSTS_N_INSNS (1);
2722      else
2723        *total = COSTS_N_INSNS (2);
2724      return true;
2725
2726    case ZERO_EXTEND:
2727      if (TARGET_64BIT && mode == DImode
2728          && GET_MODE (XEXP (x, 0)) == SImode)
2729        *total = COSTS_N_INSNS (2);
2730      else
2731        *total = COSTS_N_INSNS (1);
2732      return true;
2733
2734    case FLOAT:
2735    case UNSIGNED_FLOAT:
2736    case FIX:
2737    case FLOAT_EXTEND:
2738    case FLOAT_TRUNCATE:
2739    case SQRT:
2740      *total = mips_cost->fp_add;
2741      return true;
2742
2743    default:
2744      return false;
2745    }
2746}
2747
2748/* Provide the costs of an addressing mode that contains ADDR.
2749   If ADDR is not a valid address, its cost is irrelevant.  */
2750
2751static int
2752mips_address_cost (rtx addr)
2753{
2754  return mips_address_insns (addr, SImode);
2755}
2756
2757/* Return one word of double-word value OP, taking into account the fixed
2758   endianness of certain registers.  HIGH_P is true to select the high part,
2759   false to select the low part.  */
2760
2761rtx
2762mips_subword (rtx op, int high_p)
2763{
2764  unsigned int byte;
2765  enum machine_mode mode;
2766
2767  mode = GET_MODE (op);
2768  if (mode == VOIDmode)
2769    mode = DImode;
2770
2771  if (TARGET_BIG_ENDIAN ? !high_p : high_p)
2772    byte = UNITS_PER_WORD;
2773  else
2774    byte = 0;
2775
2776  if (REG_P (op))
2777    {
2778      if (FP_REG_P (REGNO (op)))
2779	return gen_rtx_REG (word_mode, high_p ? REGNO (op) + 1 : REGNO (op));
2780      if (ACC_HI_REG_P (REGNO (op)))
2781	return gen_rtx_REG (word_mode, high_p ? REGNO (op) : REGNO (op) + 1);
2782    }
2783
2784  if (MEM_P (op))
2785    return mips_rewrite_small_data (adjust_address (op, word_mode, byte));
2786
2787  return simplify_gen_subreg (word_mode, op, mode, byte);
2788}
2789
2790
2791/* Return true if a 64-bit move from SRC to DEST should be split into two.  */
2792
2793bool
2794mips_split_64bit_move_p (rtx dest, rtx src)
2795{
2796  if (TARGET_64BIT)
2797    return false;
2798
2799  /* FP->FP moves can be done in a single instruction.  */
2800  if (FP_REG_RTX_P (src) && FP_REG_RTX_P (dest))
2801    return false;
2802
2803  /* Check for floating-point loads and stores.  They can be done using
2804     ldc1 and sdc1 on MIPS II and above.  */
2805  if (mips_isa > 1)
2806    {
2807      if (FP_REG_RTX_P (dest) && MEM_P (src))
2808	return false;
2809      if (FP_REG_RTX_P (src) && MEM_P (dest))
2810	return false;
2811    }
2812  return true;
2813}
2814
2815
2816/* Split a 64-bit move from SRC to DEST assuming that
2817   mips_split_64bit_move_p holds.
2818
2819   Moves into and out of FPRs cause some difficulty here.  Such moves
2820   will always be DFmode, since paired FPRs are not allowed to store
2821   DImode values.  The most natural representation would be two separate
2822   32-bit moves, such as:
2823
2824	(set (reg:SI $f0) (mem:SI ...))
2825	(set (reg:SI $f1) (mem:SI ...))
2826
2827   However, the second insn is invalid because odd-numbered FPRs are
2828   not allowed to store independent values.  Use the patterns load_df_low,
2829   load_df_high and store_df_high instead.  */
2830
2831void
2832mips_split_64bit_move (rtx dest, rtx src)
2833{
2834  if (FP_REG_RTX_P (dest))
2835    {
2836      /* Loading an FPR from memory or from GPRs.  */
2837      emit_insn (gen_load_df_low (copy_rtx (dest), mips_subword (src, 0)));
2838      emit_insn (gen_load_df_high (dest, mips_subword (src, 1),
2839				   copy_rtx (dest)));
2840    }
2841  else if (FP_REG_RTX_P (src))
2842    {
2843      /* Storing an FPR into memory or GPRs.  */
2844      emit_move_insn (mips_subword (dest, 0), mips_subword (src, 0));
2845      emit_insn (gen_store_df_high (mips_subword (dest, 1), src));
2846    }
2847  else
2848    {
2849      /* The operation can be split into two normal moves.  Decide in
2850	 which order to do them.  */
2851      rtx low_dest;
2852
2853      low_dest = mips_subword (dest, 0);
2854      if (REG_P (low_dest)
2855	  && reg_overlap_mentioned_p (low_dest, src))
2856	{
2857	  emit_move_insn (mips_subword (dest, 1), mips_subword (src, 1));
2858	  emit_move_insn (low_dest, mips_subword (src, 0));
2859	}
2860      else
2861	{
2862	  emit_move_insn (low_dest, mips_subword (src, 0));
2863	  emit_move_insn (mips_subword (dest, 1), mips_subword (src, 1));
2864	}
2865    }
2866}
2867
2868/* Return the appropriate instructions to move SRC into DEST.  Assume
2869   that SRC is operand 1 and DEST is operand 0.  */
2870
2871const char *
2872mips_output_move (rtx dest, rtx src)
2873{
2874  enum rtx_code dest_code, src_code;
2875  bool dbl_p;
2876
2877  dest_code = GET_CODE (dest);
2878  src_code = GET_CODE (src);
2879  dbl_p = (GET_MODE_SIZE (GET_MODE (dest)) == 8);
2880
2881  if (dbl_p && mips_split_64bit_move_p (dest, src))
2882    return "#";
2883
2884  if ((src_code == REG && GP_REG_P (REGNO (src)))
2885      || (!TARGET_MIPS16 && src == CONST0_RTX (GET_MODE (dest))))
2886    {
2887      if (dest_code == REG)
2888	{
2889	  if (GP_REG_P (REGNO (dest)))
2890	    return "move\t%0,%z1";
2891
2892	  if (MD_REG_P (REGNO (dest)))
2893	    return "mt%0\t%z1";
2894
2895	  if (DSP_ACC_REG_P (REGNO (dest)))
2896	    {
2897	      static char retval[] = "mt__\t%z1,%q0";
2898	      retval[2] = reg_names[REGNO (dest)][4];
2899	      retval[3] = reg_names[REGNO (dest)][5];
2900	      return retval;
2901	    }
2902
2903	  if (FP_REG_P (REGNO (dest)))
2904	    return (dbl_p ? "dmtc1\t%z1,%0" : "mtc1\t%z1,%0");
2905
2906	  if (ALL_COP_REG_P (REGNO (dest)))
2907	    {
2908	      static char retval[] = "dmtc_\t%z1,%0";
2909
2910	      retval[4] = COPNUM_AS_CHAR_FROM_REGNUM (REGNO (dest));
2911	      return (dbl_p ? retval : retval + 1);
2912	    }
2913	}
2914      if (dest_code == MEM)
2915	return (dbl_p ? "sd\t%z1,%0" : "sw\t%z1,%0");
2916    }
2917  if (dest_code == REG && GP_REG_P (REGNO (dest)))
2918    {
2919      if (src_code == REG)
2920	{
2921	  if (DSP_ACC_REG_P (REGNO (src)))
2922	    {
2923	      static char retval[] = "mf__\t%0,%q1";
2924	      retval[2] = reg_names[REGNO (src)][4];
2925	      retval[3] = reg_names[REGNO (src)][5];
2926	      return retval;
2927	    }
2928
2929	  if (ST_REG_P (REGNO (src)) && ISA_HAS_8CC)
2930	    return "lui\t%0,0x3f80\n\tmovf\t%0,%.,%1";
2931
2932	  if (FP_REG_P (REGNO (src)))
2933	    return (dbl_p ? "dmfc1\t%0,%1" : "mfc1\t%0,%1");
2934
2935	  if (ALL_COP_REG_P (REGNO (src)))
2936	    {
2937	      static char retval[] = "dmfc_\t%0,%1";
2938
2939	      retval[4] = COPNUM_AS_CHAR_FROM_REGNUM (REGNO (src));
2940	      return (dbl_p ? retval : retval + 1);
2941	    }
2942	}
2943
2944      if (src_code == MEM)
2945	return (dbl_p ? "ld\t%0,%1" : "lw\t%0,%1");
2946
2947      if (src_code == CONST_INT)
2948	{
2949	  /* Don't use the X format, because that will give out of
2950	     range numbers for 64 bit hosts and 32 bit targets.  */
2951	  if (!TARGET_MIPS16)
2952	    return "li\t%0,%1\t\t\t# %X1";
2953
2954	  if (INTVAL (src) >= 0 && INTVAL (src) <= 0xffff)
2955	    return "li\t%0,%1";
2956
2957	  if (INTVAL (src) < 0 && INTVAL (src) >= -0xffff)
2958	    return "#";
2959	}
2960
2961      if (src_code == HIGH)
2962	return "lui\t%0,%h1";
2963
2964      if (CONST_GP_P (src))
2965	return "move\t%0,%1";
2966
2967      if (symbolic_operand (src, VOIDmode))
2968	return (dbl_p ? "dla\t%0,%1" : "la\t%0,%1");
2969    }
2970  if (src_code == REG && FP_REG_P (REGNO (src)))
2971    {
2972      if (dest_code == REG && FP_REG_P (REGNO (dest)))
2973	{
2974	  if (GET_MODE (dest) == V2SFmode)
2975	    return "mov.ps\t%0,%1";
2976	  else
2977	    return (dbl_p ? "mov.d\t%0,%1" : "mov.s\t%0,%1");
2978	}
2979
2980      if (dest_code == MEM)
2981	return (dbl_p ? "sdc1\t%1,%0" : "swc1\t%1,%0");
2982    }
2983  if (dest_code == REG && FP_REG_P (REGNO (dest)))
2984    {
2985      if (src_code == MEM)
2986	return (dbl_p ? "ldc1\t%0,%1" : "lwc1\t%0,%1");
2987    }
2988  if (dest_code == REG && ALL_COP_REG_P (REGNO (dest)) && src_code == MEM)
2989    {
2990      static char retval[] = "l_c_\t%0,%1";
2991
2992      retval[1] = (dbl_p ? 'd' : 'w');
2993      retval[3] = COPNUM_AS_CHAR_FROM_REGNUM (REGNO (dest));
2994      return retval;
2995    }
2996  if (dest_code == MEM && src_code == REG && ALL_COP_REG_P (REGNO (src)))
2997    {
2998      static char retval[] = "s_c_\t%1,%0";
2999
3000      retval[1] = (dbl_p ? 'd' : 'w');
3001      retval[3] = COPNUM_AS_CHAR_FROM_REGNUM (REGNO (src));
3002      return retval;
3003    }
3004  gcc_unreachable ();
3005}
3006
3007/* Restore $gp from its save slot.  Valid only when using o32 or
3008   o64 abicalls.  */
3009
3010void
3011mips_restore_gp (void)
3012{
3013  rtx address, slot;
3014
3015  gcc_assert (TARGET_ABICALLS && TARGET_OLDABI);
3016
3017  address = mips_add_offset (pic_offset_table_rtx,
3018			     frame_pointer_needed
3019			     ? hard_frame_pointer_rtx
3020			     : stack_pointer_rtx,
3021			     current_function_outgoing_args_size);
3022  slot = gen_rtx_MEM (Pmode, address);
3023
3024  emit_move_insn (pic_offset_table_rtx, slot);
3025  if (!TARGET_EXPLICIT_RELOCS)
3026    emit_insn (gen_blockage ());
3027}
3028
3029/* Emit an instruction of the form (set TARGET (CODE OP0 OP1)).  */
3030
3031static void
3032mips_emit_binary (enum rtx_code code, rtx target, rtx op0, rtx op1)
3033{
3034  emit_insn (gen_rtx_SET (VOIDmode, target,
3035			  gen_rtx_fmt_ee (code, GET_MODE (target), op0, op1)));
3036}
3037
3038/* Return true if CMP1 is a suitable second operand for relational
3039   operator CODE.  See also the *sCC patterns in mips.md.  */
3040
3041static bool
3042mips_relational_operand_ok_p (enum rtx_code code, rtx cmp1)
3043{
3044  switch (code)
3045    {
3046    case GT:
3047    case GTU:
3048      return reg_or_0_operand (cmp1, VOIDmode);
3049
3050    case GE:
3051    case GEU:
3052      return !TARGET_MIPS16 && cmp1 == const1_rtx;
3053
3054    case LT:
3055    case LTU:
3056      return arith_operand (cmp1, VOIDmode);
3057
3058    case LE:
3059      return sle_operand (cmp1, VOIDmode);
3060
3061    case LEU:
3062      return sleu_operand (cmp1, VOIDmode);
3063
3064    default:
3065      gcc_unreachable ();
3066    }
3067}
3068
3069/* Canonicalize LE or LEU comparisons into LT comparisons when
3070   possible to avoid extra instructions or inverting the
3071   comparison.  */
3072
3073static bool
3074mips_canonicalize_comparison (enum rtx_code *code, rtx *cmp1,
3075			      enum machine_mode mode)
3076{
3077  HOST_WIDE_INT original, plus_one;
3078
3079  if (GET_CODE (*cmp1) != CONST_INT)
3080    return false;
3081
3082  original = INTVAL (*cmp1);
3083  plus_one = trunc_int_for_mode ((unsigned HOST_WIDE_INT) original + 1, mode);
3084
3085  switch (*code)
3086    {
3087    case LE:
3088      if (original < plus_one)
3089	{
3090	  *code = LT;
3091	  *cmp1 = force_reg (mode, GEN_INT (plus_one));
3092	  return true;
3093	}
3094      break;
3095
3096    case LEU:
3097      if (plus_one != 0)
3098	{
3099	  *code = LTU;
3100	  *cmp1 = force_reg (mode, GEN_INT (plus_one));
3101	  return true;
3102	}
3103      break;
3104
3105    default:
3106      return false;
3107   }
3108
3109  return false;
3110
3111}
3112
3113/* Compare CMP0 and CMP1 using relational operator CODE and store the
3114   result in TARGET.  CMP0 and TARGET are register_operands that have
3115   the same integer mode.  If INVERT_PTR is nonnull, it's OK to set
3116   TARGET to the inverse of the result and flip *INVERT_PTR instead.  */
3117
3118static void
3119mips_emit_int_relational (enum rtx_code code, bool *invert_ptr,
3120			  rtx target, rtx cmp0, rtx cmp1)
3121{
3122  /* First see if there is a MIPS instruction that can do this operation
3123     with CMP1 in its current form. If not, try to canonicalize the
3124     comparison to LT. If that fails, try doing the same for the
3125     inverse operation.  If that also fails, force CMP1 into a register
3126     and try again.  */
3127  if (mips_relational_operand_ok_p (code, cmp1))
3128    mips_emit_binary (code, target, cmp0, cmp1);
3129  else if (mips_canonicalize_comparison (&code, &cmp1, GET_MODE (target)))
3130    mips_emit_binary (code, target, cmp0, cmp1);
3131  else
3132    {
3133      enum rtx_code inv_code = reverse_condition (code);
3134      if (!mips_relational_operand_ok_p (inv_code, cmp1))
3135	{
3136	  cmp1 = force_reg (GET_MODE (cmp0), cmp1);
3137	  mips_emit_int_relational (code, invert_ptr, target, cmp0, cmp1);
3138	}
3139      else if (invert_ptr == 0)
3140	{
3141	  rtx inv_target = gen_reg_rtx (GET_MODE (target));
3142	  mips_emit_binary (inv_code, inv_target, cmp0, cmp1);
3143	  mips_emit_binary (XOR, target, inv_target, const1_rtx);
3144	}
3145      else
3146	{
3147	  *invert_ptr = !*invert_ptr;
3148	  mips_emit_binary (inv_code, target, cmp0, cmp1);
3149	}
3150    }
3151}
3152
3153/* Return a register that is zero iff CMP0 and CMP1 are equal.
3154   The register will have the same mode as CMP0.  */
3155
3156static rtx
3157mips_zero_if_equal (rtx cmp0, rtx cmp1)
3158{
3159  if (cmp1 == const0_rtx)
3160    return cmp0;
3161
3162  if (uns_arith_operand (cmp1, VOIDmode))
3163    return expand_binop (GET_MODE (cmp0), xor_optab,
3164			 cmp0, cmp1, 0, 0, OPTAB_DIRECT);
3165
3166  return expand_binop (GET_MODE (cmp0), sub_optab,
3167		       cmp0, cmp1, 0, 0, OPTAB_DIRECT);
3168}
3169
3170/* Convert *CODE into a code that can be used in a floating-point
3171   scc instruction (c.<cond>.<fmt>).  Return true if the values of
3172   the condition code registers will be inverted, with 0 indicating
3173   that the condition holds.  */
3174
3175static bool
3176mips_reverse_fp_cond_p (enum rtx_code *code)
3177{
3178  switch (*code)
3179    {
3180    case NE:
3181    case LTGT:
3182    case ORDERED:
3183      *code = reverse_condition_maybe_unordered (*code);
3184      return true;
3185
3186    default:
3187      return false;
3188    }
3189}
3190
3191/* Convert a comparison into something that can be used in a branch or
3192   conditional move.  cmp_operands[0] and cmp_operands[1] are the values
3193   being compared and *CODE is the code used to compare them.
3194
3195   Update *CODE, *OP0 and *OP1 so that they describe the final comparison.
3196   If NEED_EQ_NE_P, then only EQ/NE comparisons against zero are possible,
3197   otherwise any standard branch condition can be used.  The standard branch
3198   conditions are:
3199
3200      - EQ/NE between two registers.
3201      - any comparison between a register and zero.  */
3202
3203static void
3204mips_emit_compare (enum rtx_code *code, rtx *op0, rtx *op1, bool need_eq_ne_p)
3205{
3206  if (GET_MODE_CLASS (GET_MODE (cmp_operands[0])) == MODE_INT)
3207    {
3208      if (!need_eq_ne_p && cmp_operands[1] == const0_rtx)
3209	{
3210	  *op0 = cmp_operands[0];
3211	  *op1 = cmp_operands[1];
3212	}
3213      else if (*code == EQ || *code == NE)
3214	{
3215	  if (need_eq_ne_p)
3216	    {
3217	      *op0 = mips_zero_if_equal (cmp_operands[0], cmp_operands[1]);
3218	      *op1 = const0_rtx;
3219	    }
3220	  else
3221	    {
3222	      *op0 = cmp_operands[0];
3223	      *op1 = force_reg (GET_MODE (*op0), cmp_operands[1]);
3224	    }
3225	}
3226      else
3227	{
3228	  /* The comparison needs a separate scc instruction.  Store the
3229	     result of the scc in *OP0 and compare it against zero.  */
3230	  bool invert = false;
3231	  *op0 = gen_reg_rtx (GET_MODE (cmp_operands[0]));
3232	  *op1 = const0_rtx;
3233	  mips_emit_int_relational (*code, &invert, *op0,
3234				    cmp_operands[0], cmp_operands[1]);
3235	  *code = (invert ? EQ : NE);
3236	}
3237    }
3238  else
3239    {
3240      enum rtx_code cmp_code;
3241
3242      /* Floating-point tests use a separate c.cond.fmt comparison to
3243	 set a condition code register.  The branch or conditional move
3244	 will then compare that register against zero.
3245
3246	 Set CMP_CODE to the code of the comparison instruction and
3247	 *CODE to the code that the branch or move should use.  */
3248      cmp_code = *code;
3249      *code = mips_reverse_fp_cond_p (&cmp_code) ? EQ : NE;
3250      *op0 = (ISA_HAS_8CC
3251	      ? gen_reg_rtx (CCmode)
3252	      : gen_rtx_REG (CCmode, FPSW_REGNUM));
3253      *op1 = const0_rtx;
3254      mips_emit_binary (cmp_code, *op0, cmp_operands[0], cmp_operands[1]);
3255    }
3256}
3257
3258/* Try comparing cmp_operands[0] and cmp_operands[1] using rtl code CODE.
3259   Store the result in TARGET and return true if successful.
3260
3261   On 64-bit targets, TARGET may be wider than cmp_operands[0].  */
3262
3263bool
3264mips_emit_scc (enum rtx_code code, rtx target)
3265{
3266  if (GET_MODE_CLASS (GET_MODE (cmp_operands[0])) != MODE_INT)
3267    return false;
3268
3269  target = gen_lowpart (GET_MODE (cmp_operands[0]), target);
3270  if (code == EQ || code == NE)
3271    {
3272      rtx zie = mips_zero_if_equal (cmp_operands[0], cmp_operands[1]);
3273      mips_emit_binary (code, target, zie, const0_rtx);
3274    }
3275  else
3276    mips_emit_int_relational (code, 0, target,
3277			      cmp_operands[0], cmp_operands[1]);
3278  return true;
3279}
3280
3281/* Emit the common code for doing conditional branches.
3282   operand[0] is the label to jump to.
3283   The comparison operands are saved away by cmp{si,di,sf,df}.  */
3284
3285void
3286gen_conditional_branch (rtx *operands, enum rtx_code code)
3287{
3288  rtx op0, op1, condition;
3289
3290  mips_emit_compare (&code, &op0, &op1, TARGET_MIPS16);
3291  condition = gen_rtx_fmt_ee (code, VOIDmode, op0, op1);
3292  emit_jump_insn (gen_condjump (condition, operands[0]));
3293}
3294
3295/* Implement:
3296
3297   (set temp (COND:CCV2 CMP_OP0 CMP_OP1))
3298   (set DEST (unspec [TRUE_SRC FALSE_SRC temp] UNSPEC_MOVE_TF_PS))  */
3299
3300void
3301mips_expand_vcondv2sf (rtx dest, rtx true_src, rtx false_src,
3302		       enum rtx_code cond, rtx cmp_op0, rtx cmp_op1)
3303{
3304  rtx cmp_result;
3305  bool reversed_p;
3306
3307  reversed_p = mips_reverse_fp_cond_p (&cond);
3308  cmp_result = gen_reg_rtx (CCV2mode);
3309  emit_insn (gen_scc_ps (cmp_result,
3310			 gen_rtx_fmt_ee (cond, VOIDmode, cmp_op0, cmp_op1)));
3311  if (reversed_p)
3312    emit_insn (gen_mips_cond_move_tf_ps (dest, false_src, true_src,
3313					 cmp_result));
3314  else
3315    emit_insn (gen_mips_cond_move_tf_ps (dest, true_src, false_src,
3316					 cmp_result));
3317}
3318
3319/* Emit the common code for conditional moves.  OPERANDS is the array
3320   of operands passed to the conditional move define_expand.  */
3321
3322void
3323gen_conditional_move (rtx *operands)
3324{
3325  enum rtx_code code;
3326  rtx op0, op1;
3327
3328  code = GET_CODE (operands[1]);
3329  mips_emit_compare (&code, &op0, &op1, true);
3330  emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3331			  gen_rtx_IF_THEN_ELSE (GET_MODE (operands[0]),
3332						gen_rtx_fmt_ee (code,
3333								GET_MODE (op0),
3334								op0, op1),
3335						operands[2], operands[3])));
3336}
3337
3338/* Emit a conditional trap.  OPERANDS is the array of operands passed to
3339   the conditional_trap expander.  */
3340
3341void
3342mips_gen_conditional_trap (rtx *operands)
3343{
3344  rtx op0, op1;
3345  enum rtx_code cmp_code = GET_CODE (operands[0]);
3346  enum machine_mode mode = GET_MODE (cmp_operands[0]);
3347
3348  /* MIPS conditional trap machine instructions don't have GT or LE
3349     flavors, so we must invert the comparison and convert to LT and
3350     GE, respectively.  */
3351  switch (cmp_code)
3352    {
3353    case GT: cmp_code = LT; break;
3354    case LE: cmp_code = GE; break;
3355    case GTU: cmp_code = LTU; break;
3356    case LEU: cmp_code = GEU; break;
3357    default: break;
3358    }
3359  if (cmp_code == GET_CODE (operands[0]))
3360    {
3361      op0 = cmp_operands[0];
3362      op1 = cmp_operands[1];
3363    }
3364  else
3365    {
3366      op0 = cmp_operands[1];
3367      op1 = cmp_operands[0];
3368    }
3369  op0 = force_reg (mode, op0);
3370  if (!arith_operand (op1, mode))
3371    op1 = force_reg (mode, op1);
3372
3373  emit_insn (gen_rtx_TRAP_IF (VOIDmode,
3374			      gen_rtx_fmt_ee (cmp_code, mode, op0, op1),
3375			      operands[1]));
3376}
3377
3378/* Load function address ADDR into register DEST.  SIBCALL_P is true
3379   if the address is needed for a sibling call.  */
3380
3381static void
3382mips_load_call_address (rtx dest, rtx addr, int sibcall_p)
3383{
3384  /* If we're generating PIC, and this call is to a global function,
3385     try to allow its address to be resolved lazily.  This isn't
3386     possible for NewABI sibcalls since the value of $gp on entry
3387     to the stub would be our caller's gp, not ours.  */
3388  if (TARGET_EXPLICIT_RELOCS
3389      && !(sibcall_p && TARGET_NEWABI)
3390      && global_got_operand (addr, VOIDmode))
3391    {
3392      rtx high, lo_sum_symbol;
3393
3394      high = mips_unspec_offset_high (dest, pic_offset_table_rtx,
3395				      addr, SYMBOL_GOTOFF_CALL);
3396      lo_sum_symbol = mips_unspec_address (addr, SYMBOL_GOTOFF_CALL);
3397      if (Pmode == SImode)
3398	emit_insn (gen_load_callsi (dest, high, lo_sum_symbol));
3399      else
3400	emit_insn (gen_load_calldi (dest, high, lo_sum_symbol));
3401    }
3402  else
3403    emit_move_insn (dest, addr);
3404}
3405
3406
3407/* Expand a call or call_value instruction.  RESULT is where the
3408   result will go (null for calls), ADDR is the address of the
3409   function, ARGS_SIZE is the size of the arguments and AUX is
3410   the value passed to us by mips_function_arg.  SIBCALL_P is true
3411   if we are expanding a sibling call, false if we're expanding
3412   a normal call.  */
3413
3414void
3415mips_expand_call (rtx result, rtx addr, rtx args_size, rtx aux, int sibcall_p)
3416{
3417  rtx orig_addr, pattern, insn;
3418
3419  orig_addr = addr;
3420  if (!call_insn_operand (addr, VOIDmode))
3421    {
3422      addr = gen_reg_rtx (Pmode);
3423      mips_load_call_address (addr, orig_addr, sibcall_p);
3424    }
3425
3426  if (TARGET_MIPS16
3427      && mips16_hard_float
3428      && build_mips16_call_stub (result, addr, args_size,
3429				 aux == 0 ? 0 : (int) GET_MODE (aux)))
3430    return;
3431
3432  if (result == 0)
3433    pattern = (sibcall_p
3434	       ? gen_sibcall_internal (addr, args_size)
3435	       : gen_call_internal (addr, args_size));
3436  else if (GET_CODE (result) == PARALLEL && XVECLEN (result, 0) == 2)
3437    {
3438      rtx reg1, reg2;
3439
3440      reg1 = XEXP (XVECEXP (result, 0, 0), 0);
3441      reg2 = XEXP (XVECEXP (result, 0, 1), 0);
3442      pattern =
3443	(sibcall_p
3444	 ? gen_sibcall_value_multiple_internal (reg1, addr, args_size, reg2)
3445	 : gen_call_value_multiple_internal (reg1, addr, args_size, reg2));
3446    }
3447  else
3448    pattern = (sibcall_p
3449	       ? gen_sibcall_value_internal (result, addr, args_size)
3450	       : gen_call_value_internal (result, addr, args_size));
3451
3452  insn = emit_call_insn (pattern);
3453
3454  /* Lazy-binding stubs require $gp to be valid on entry.  */
3455  if (global_got_operand (orig_addr, VOIDmode))
3456    use_reg (&CALL_INSN_FUNCTION_USAGE (insn), pic_offset_table_rtx);
3457}
3458
3459
3460/* We can handle any sibcall when TARGET_SIBCALLS is true.  */
3461
3462static bool
3463mips_function_ok_for_sibcall (tree decl ATTRIBUTE_UNUSED,
3464			      tree exp ATTRIBUTE_UNUSED)
3465{
3466  return TARGET_SIBCALLS;
3467}
3468
3469/* Emit code to move general operand SRC into condition-code
3470   register DEST.  SCRATCH is a scratch TFmode float register.
3471   The sequence is:
3472
3473	FP1 = SRC
3474	FP2 = 0.0f
3475	DEST = FP2 < FP1
3476
3477   where FP1 and FP2 are single-precision float registers
3478   taken from SCRATCH.  */
3479
3480void
3481mips_emit_fcc_reload (rtx dest, rtx src, rtx scratch)
3482{
3483  rtx fp1, fp2;
3484
3485  /* Change the source to SFmode.  */
3486  if (MEM_P (src))
3487    src = adjust_address (src, SFmode, 0);
3488  else if (REG_P (src) || GET_CODE (src) == SUBREG)
3489    src = gen_rtx_REG (SFmode, true_regnum (src));
3490
3491  fp1 = gen_rtx_REG (SFmode, REGNO (scratch));
3492  fp2 = gen_rtx_REG (SFmode, REGNO (scratch) + FP_INC);
3493
3494  emit_move_insn (copy_rtx (fp1), src);
3495  emit_move_insn (copy_rtx (fp2), CONST0_RTX (SFmode));
3496  emit_insn (gen_slt_sf (dest, fp2, fp1));
3497}
3498
3499/* Emit code to change the current function's return address to
3500   ADDRESS.  SCRATCH is available as a scratch register, if needed.
3501   ADDRESS and SCRATCH are both word-mode GPRs.  */
3502
3503void
3504mips_set_return_address (rtx address, rtx scratch)
3505{
3506  rtx slot_address;
3507
3508  compute_frame_size (get_frame_size ());
3509  gcc_assert ((cfun->machine->frame.mask >> 31) & 1);
3510  slot_address = mips_add_offset (scratch, stack_pointer_rtx,
3511				  cfun->machine->frame.gp_sp_offset);
3512
3513  emit_move_insn (gen_rtx_MEM (GET_MODE (address), slot_address), address);
3514}
3515
3516/* Emit straight-line code to move LENGTH bytes from SRC to DEST.
3517   Assume that the areas do not overlap.  */
3518
3519static void
3520mips_block_move_straight (rtx dest, rtx src, HOST_WIDE_INT length)
3521{
3522  HOST_WIDE_INT offset, delta;
3523  unsigned HOST_WIDE_INT bits;
3524  int i;
3525  enum machine_mode mode;
3526  rtx *regs;
3527
3528  /* Work out how many bits to move at a time.  If both operands have
3529     half-word alignment, it is usually better to move in half words.
3530     For instance, lh/lh/sh/sh is usually better than lwl/lwr/swl/swr
3531     and lw/lw/sw/sw is usually better than ldl/ldr/sdl/sdr.
3532     Otherwise move word-sized chunks.  */
3533  if (MEM_ALIGN (src) == BITS_PER_WORD / 2
3534      && MEM_ALIGN (dest) == BITS_PER_WORD / 2)
3535    bits = BITS_PER_WORD / 2;
3536  else
3537    bits = BITS_PER_WORD;
3538
3539  mode = mode_for_size (bits, MODE_INT, 0);
3540  delta = bits / BITS_PER_UNIT;
3541
3542  /* Allocate a buffer for the temporary registers.  */
3543  regs = alloca (sizeof (rtx) * length / delta);
3544
3545  /* Load as many BITS-sized chunks as possible.  Use a normal load if
3546     the source has enough alignment, otherwise use left/right pairs.  */
3547  for (offset = 0, i = 0; offset + delta <= length; offset += delta, i++)
3548    {
3549      regs[i] = gen_reg_rtx (mode);
3550      if (MEM_ALIGN (src) >= bits)
3551	emit_move_insn (regs[i], adjust_address (src, mode, offset));
3552      else
3553	{
3554	  rtx part = adjust_address (src, BLKmode, offset);
3555	  if (!mips_expand_unaligned_load (regs[i], part, bits, 0))
3556	    gcc_unreachable ();
3557	}
3558    }
3559
3560  /* Copy the chunks to the destination.  */
3561  for (offset = 0, i = 0; offset + delta <= length; offset += delta, i++)
3562    if (MEM_ALIGN (dest) >= bits)
3563      emit_move_insn (adjust_address (dest, mode, offset), regs[i]);
3564    else
3565      {
3566	rtx part = adjust_address (dest, BLKmode, offset);
3567	if (!mips_expand_unaligned_store (part, regs[i], bits, 0))
3568	  gcc_unreachable ();
3569      }
3570
3571  /* Mop up any left-over bytes.  */
3572  if (offset < length)
3573    {
3574      src = adjust_address (src, BLKmode, offset);
3575      dest = adjust_address (dest, BLKmode, offset);
3576      move_by_pieces (dest, src, length - offset,
3577		      MIN (MEM_ALIGN (src), MEM_ALIGN (dest)), 0);
3578    }
3579}
3580
3581#define MAX_MOVE_REGS 4
3582#define MAX_MOVE_BYTES (MAX_MOVE_REGS * UNITS_PER_WORD)
3583
3584
3585/* Helper function for doing a loop-based block operation on memory
3586   reference MEM.  Each iteration of the loop will operate on LENGTH
3587   bytes of MEM.
3588
3589   Create a new base register for use within the loop and point it to
3590   the start of MEM.  Create a new memory reference that uses this
3591   register.  Store them in *LOOP_REG and *LOOP_MEM respectively.  */
3592
3593static void
3594mips_adjust_block_mem (rtx mem, HOST_WIDE_INT length,
3595		       rtx *loop_reg, rtx *loop_mem)
3596{
3597  *loop_reg = copy_addr_to_reg (XEXP (mem, 0));
3598
3599  /* Although the new mem does not refer to a known location,
3600     it does keep up to LENGTH bytes of alignment.  */
3601  *loop_mem = change_address (mem, BLKmode, *loop_reg);
3602  set_mem_align (*loop_mem, MIN (MEM_ALIGN (mem), length * BITS_PER_UNIT));
3603}
3604
3605
3606/* Move LENGTH bytes from SRC to DEST using a loop that moves MAX_MOVE_BYTES
3607   per iteration.  LENGTH must be at least MAX_MOVE_BYTES.  Assume that the
3608   memory regions do not overlap.  */
3609
3610static void
3611mips_block_move_loop (rtx dest, rtx src, HOST_WIDE_INT length)
3612{
3613  rtx label, src_reg, dest_reg, final_src;
3614  HOST_WIDE_INT leftover;
3615
3616  leftover = length % MAX_MOVE_BYTES;
3617  length -= leftover;
3618
3619  /* Create registers and memory references for use within the loop.  */
3620  mips_adjust_block_mem (src, MAX_MOVE_BYTES, &src_reg, &src);
3621  mips_adjust_block_mem (dest, MAX_MOVE_BYTES, &dest_reg, &dest);
3622
3623  /* Calculate the value that SRC_REG should have after the last iteration
3624     of the loop.  */
3625  final_src = expand_simple_binop (Pmode, PLUS, src_reg, GEN_INT (length),
3626				   0, 0, OPTAB_WIDEN);
3627
3628  /* Emit the start of the loop.  */
3629  label = gen_label_rtx ();
3630  emit_label (label);
3631
3632  /* Emit the loop body.  */
3633  mips_block_move_straight (dest, src, MAX_MOVE_BYTES);
3634
3635  /* Move on to the next block.  */
3636  emit_move_insn (src_reg, plus_constant (src_reg, MAX_MOVE_BYTES));
3637  emit_move_insn (dest_reg, plus_constant (dest_reg, MAX_MOVE_BYTES));
3638
3639  /* Emit the loop condition.  */
3640  if (Pmode == DImode)
3641    emit_insn (gen_cmpdi (src_reg, final_src));
3642  else
3643    emit_insn (gen_cmpsi (src_reg, final_src));
3644  emit_jump_insn (gen_bne (label));
3645
3646  /* Mop up any left-over bytes.  */
3647  if (leftover)
3648    mips_block_move_straight (dest, src, leftover);
3649}
3650
3651/* Expand a movmemsi instruction.  */
3652
3653bool
3654mips_expand_block_move (rtx dest, rtx src, rtx length)
3655{
3656  if (GET_CODE (length) == CONST_INT)
3657    {
3658      if (INTVAL (length) <= 2 * MAX_MOVE_BYTES)
3659	{
3660	  mips_block_move_straight (dest, src, INTVAL (length));
3661	  return true;
3662	}
3663      else if (optimize)
3664	{
3665	  mips_block_move_loop (dest, src, INTVAL (length));
3666	  return true;
3667	}
3668    }
3669  return false;
3670}
3671
3672/* Argument support functions.  */
3673
3674/* Initialize CUMULATIVE_ARGS for a function.  */
3675
3676void
3677init_cumulative_args (CUMULATIVE_ARGS *cum, tree fntype,
3678		      rtx libname ATTRIBUTE_UNUSED)
3679{
3680  static CUMULATIVE_ARGS zero_cum;
3681  tree param, next_param;
3682
3683  *cum = zero_cum;
3684  cum->prototype = (fntype && TYPE_ARG_TYPES (fntype));
3685
3686  /* Determine if this function has variable arguments.  This is
3687     indicated by the last argument being 'void_type_mode' if there
3688     are no variable arguments.  The standard MIPS calling sequence
3689     passes all arguments in the general purpose registers in this case.  */
3690
3691  for (param = fntype ? TYPE_ARG_TYPES (fntype) : 0;
3692       param != 0; param = next_param)
3693    {
3694      next_param = TREE_CHAIN (param);
3695      if (next_param == 0 && TREE_VALUE (param) != void_type_node)
3696	cum->gp_reg_found = 1;
3697    }
3698}
3699
3700
3701/* Fill INFO with information about a single argument.  CUM is the
3702   cumulative state for earlier arguments.  MODE is the mode of this
3703   argument and TYPE is its type (if known).  NAMED is true if this
3704   is a named (fixed) argument rather than a variable one.  */
3705
3706static void
3707mips_arg_info (const CUMULATIVE_ARGS *cum, enum machine_mode mode,
3708	       tree type, int named, struct mips_arg_info *info)
3709{
3710  bool doubleword_aligned_p;
3711  unsigned int num_bytes, num_words, max_regs;
3712
3713  /* Work out the size of the argument.  */
3714  num_bytes = type ? int_size_in_bytes (type) : GET_MODE_SIZE (mode);
3715  num_words = (num_bytes + UNITS_PER_WORD - 1) / UNITS_PER_WORD;
3716
3717  /* Decide whether it should go in a floating-point register, assuming
3718     one is free.  Later code checks for availability.
3719
3720     The checks against UNITS_PER_FPVALUE handle the soft-float and
3721     single-float cases.  */
3722  switch (mips_abi)
3723    {
3724    case ABI_EABI:
3725      /* The EABI conventions have traditionally been defined in terms
3726	 of TYPE_MODE, regardless of the actual type.  */
3727      info->fpr_p = ((GET_MODE_CLASS (mode) == MODE_FLOAT
3728		      || GET_MODE_CLASS (mode) == MODE_VECTOR_FLOAT)
3729		     && GET_MODE_SIZE (mode) <= UNITS_PER_FPVALUE);
3730      break;
3731
3732    case ABI_32:
3733    case ABI_O64:
3734      /* Only leading floating-point scalars are passed in
3735	 floating-point registers.  We also handle vector floats the same
3736	 say, which is OK because they are not covered by the standard ABI.  */
3737      info->fpr_p = (!cum->gp_reg_found
3738		     && cum->arg_number < 2
3739		     && (type == 0 || SCALAR_FLOAT_TYPE_P (type)
3740			 || VECTOR_FLOAT_TYPE_P (type))
3741		     && (GET_MODE_CLASS (mode) == MODE_FLOAT
3742			 || GET_MODE_CLASS (mode) == MODE_VECTOR_FLOAT)
3743		     && GET_MODE_SIZE (mode) <= UNITS_PER_FPVALUE);
3744      break;
3745
3746    case ABI_N32:
3747    case ABI_64:
3748      /* Scalar and complex floating-point types are passed in
3749	 floating-point registers.  */
3750      info->fpr_p = (named
3751		     && (type == 0 || FLOAT_TYPE_P (type))
3752		     && (GET_MODE_CLASS (mode) == MODE_FLOAT
3753			 || GET_MODE_CLASS (mode) == MODE_COMPLEX_FLOAT
3754			 || GET_MODE_CLASS (mode) == MODE_VECTOR_FLOAT)
3755		     && GET_MODE_UNIT_SIZE (mode) <= UNITS_PER_FPVALUE);
3756
3757      /* ??? According to the ABI documentation, the real and imaginary
3758	 parts of complex floats should be passed in individual registers.
3759	 The real and imaginary parts of stack arguments are supposed
3760	 to be contiguous and there should be an extra word of padding
3761	 at the end.
3762
3763	 This has two problems.  First, it makes it impossible to use a
3764	 single "void *" va_list type, since register and stack arguments
3765	 are passed differently.  (At the time of writing, MIPSpro cannot
3766	 handle complex float varargs correctly.)  Second, it's unclear
3767	 what should happen when there is only one register free.
3768
3769	 For now, we assume that named complex floats should go into FPRs
3770	 if there are two FPRs free, otherwise they should be passed in the
3771	 same way as a struct containing two floats.  */
3772      if (info->fpr_p
3773	  && GET_MODE_CLASS (mode) == MODE_COMPLEX_FLOAT
3774	  && GET_MODE_UNIT_SIZE (mode) < UNITS_PER_FPVALUE)
3775	{
3776	  if (cum->num_gprs >= MAX_ARGS_IN_REGISTERS - 1)
3777	    info->fpr_p = false;
3778	  else
3779	    num_words = 2;
3780	}
3781      break;
3782
3783    default:
3784      gcc_unreachable ();
3785    }
3786
3787  /* See whether the argument has doubleword alignment.  */
3788  doubleword_aligned_p = FUNCTION_ARG_BOUNDARY (mode, type) > BITS_PER_WORD;
3789
3790  /* Set REG_OFFSET to the register count we're interested in.
3791     The EABI allocates the floating-point registers separately,
3792     but the other ABIs allocate them like integer registers.  */
3793  info->reg_offset = (mips_abi == ABI_EABI && info->fpr_p
3794		      ? cum->num_fprs
3795		      : cum->num_gprs);
3796
3797  /* Advance to an even register if the argument is doubleword-aligned.  */
3798  if (doubleword_aligned_p)
3799    info->reg_offset += info->reg_offset & 1;
3800
3801  /* Work out the offset of a stack argument.  */
3802  info->stack_offset = cum->stack_words;
3803  if (doubleword_aligned_p)
3804    info->stack_offset += info->stack_offset & 1;
3805
3806  max_regs = MAX_ARGS_IN_REGISTERS - info->reg_offset;
3807
3808  /* Partition the argument between registers and stack.  */
3809  info->reg_words = MIN (num_words, max_regs);
3810  info->stack_words = num_words - info->reg_words;
3811}
3812
3813
3814/* Implement FUNCTION_ARG_ADVANCE.  */
3815
3816void
3817function_arg_advance (CUMULATIVE_ARGS *cum, enum machine_mode mode,
3818		      tree type, int named)
3819{
3820  struct mips_arg_info info;
3821
3822  mips_arg_info (cum, mode, type, named, &info);
3823
3824  if (!info.fpr_p)
3825    cum->gp_reg_found = true;
3826
3827  /* See the comment above the cumulative args structure in mips.h
3828     for an explanation of what this code does.  It assumes the O32
3829     ABI, which passes at most 2 arguments in float registers.  */
3830  if (cum->arg_number < 2 && info.fpr_p)
3831    cum->fp_code += (mode == SFmode ? 1 : 2) << ((cum->arg_number - 1) * 2);
3832
3833  if (mips_abi != ABI_EABI || !info.fpr_p)
3834    cum->num_gprs = info.reg_offset + info.reg_words;
3835  else if (info.reg_words > 0)
3836    cum->num_fprs += FP_INC;
3837
3838  if (info.stack_words > 0)
3839    cum->stack_words = info.stack_offset + info.stack_words;
3840
3841  cum->arg_number++;
3842}
3843
3844/* Implement FUNCTION_ARG.  */
3845
3846struct rtx_def *
3847function_arg (const CUMULATIVE_ARGS *cum, enum machine_mode mode,
3848	      tree type, int named)
3849{
3850  struct mips_arg_info info;
3851
3852  /* We will be called with a mode of VOIDmode after the last argument
3853     has been seen.  Whatever we return will be passed to the call
3854     insn.  If we need a mips16 fp_code, return a REG with the code
3855     stored as the mode.  */
3856  if (mode == VOIDmode)
3857    {
3858      if (TARGET_MIPS16 && cum->fp_code != 0)
3859	return gen_rtx_REG ((enum machine_mode) cum->fp_code, 0);
3860
3861      else
3862	return 0;
3863    }
3864
3865  mips_arg_info (cum, mode, type, named, &info);
3866
3867  /* Return straight away if the whole argument is passed on the stack.  */
3868  if (info.reg_offset == MAX_ARGS_IN_REGISTERS)
3869    return 0;
3870
3871  if (type != 0
3872      && TREE_CODE (type) == RECORD_TYPE
3873      && TARGET_NEWABI
3874      && TYPE_SIZE_UNIT (type)
3875      && host_integerp (TYPE_SIZE_UNIT (type), 1)
3876      && named)
3877    {
3878      /* The Irix 6 n32/n64 ABIs say that if any 64 bit chunk of the
3879	 structure contains a double in its entirety, then that 64 bit
3880	 chunk is passed in a floating point register.  */
3881      tree field;
3882
3883      /* First check to see if there is any such field.  */
3884      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
3885	if (TREE_CODE (field) == FIELD_DECL
3886	    && TREE_CODE (TREE_TYPE (field)) == REAL_TYPE
3887	    && TYPE_PRECISION (TREE_TYPE (field)) == BITS_PER_WORD
3888	    && host_integerp (bit_position (field), 0)
3889	    && int_bit_position (field) % BITS_PER_WORD == 0)
3890	  break;
3891
3892      if (field != 0)
3893	{
3894	  /* Now handle the special case by returning a PARALLEL
3895	     indicating where each 64 bit chunk goes.  INFO.REG_WORDS
3896	     chunks are passed in registers.  */
3897	  unsigned int i;
3898	  HOST_WIDE_INT bitpos;
3899	  rtx ret;
3900
3901	  /* assign_parms checks the mode of ENTRY_PARM, so we must
3902	     use the actual mode here.  */
3903	  ret = gen_rtx_PARALLEL (mode, rtvec_alloc (info.reg_words));
3904
3905	  bitpos = 0;
3906	  field = TYPE_FIELDS (type);
3907	  for (i = 0; i < info.reg_words; i++)
3908	    {
3909	      rtx reg;
3910
3911	      for (; field; field = TREE_CHAIN (field))
3912		if (TREE_CODE (field) == FIELD_DECL
3913		    && int_bit_position (field) >= bitpos)
3914		  break;
3915
3916	      if (field
3917		  && int_bit_position (field) == bitpos
3918		  && TREE_CODE (TREE_TYPE (field)) == REAL_TYPE
3919		  && !TARGET_SOFT_FLOAT
3920		  && TYPE_PRECISION (TREE_TYPE (field)) == BITS_PER_WORD)
3921		reg = gen_rtx_REG (DFmode, FP_ARG_FIRST + info.reg_offset + i);
3922	      else
3923		reg = gen_rtx_REG (DImode, GP_ARG_FIRST + info.reg_offset + i);
3924
3925	      XVECEXP (ret, 0, i)
3926		= gen_rtx_EXPR_LIST (VOIDmode, reg,
3927				     GEN_INT (bitpos / BITS_PER_UNIT));
3928
3929	      bitpos += BITS_PER_WORD;
3930	    }
3931	  return ret;
3932	}
3933    }
3934
3935  /* Handle the n32/n64 conventions for passing complex floating-point
3936     arguments in FPR pairs.  The real part goes in the lower register
3937     and the imaginary part goes in the upper register.  */
3938  if (TARGET_NEWABI
3939      && info.fpr_p
3940      && GET_MODE_CLASS (mode) == MODE_COMPLEX_FLOAT)
3941    {
3942      rtx real, imag;
3943      enum machine_mode inner;
3944      int reg;
3945
3946      inner = GET_MODE_INNER (mode);
3947      reg = FP_ARG_FIRST + info.reg_offset;
3948      if (info.reg_words * UNITS_PER_WORD == GET_MODE_SIZE (inner))
3949	{
3950	  /* Real part in registers, imaginary part on stack.  */
3951	  gcc_assert (info.stack_words == info.reg_words);
3952	  return gen_rtx_REG (inner, reg);
3953	}
3954      else
3955	{
3956	  gcc_assert (info.stack_words == 0);
3957	  real = gen_rtx_EXPR_LIST (VOIDmode,
3958				    gen_rtx_REG (inner, reg),
3959				    const0_rtx);
3960	  imag = gen_rtx_EXPR_LIST (VOIDmode,
3961				    gen_rtx_REG (inner,
3962						 reg + info.reg_words / 2),
3963				    GEN_INT (GET_MODE_SIZE (inner)));
3964	  return gen_rtx_PARALLEL (mode, gen_rtvec (2, real, imag));
3965	}
3966    }
3967
3968  if (!info.fpr_p)
3969    return gen_rtx_REG (mode, GP_ARG_FIRST + info.reg_offset);
3970  else if (info.reg_offset == 1)
3971    /* This code handles the special o32 case in which the second word
3972       of the argument structure is passed in floating-point registers.  */
3973    return gen_rtx_REG (mode, FP_ARG_FIRST + FP_INC);
3974  else
3975    return gen_rtx_REG (mode, FP_ARG_FIRST + info.reg_offset);
3976}
3977
3978
3979/* Implement TARGET_ARG_PARTIAL_BYTES.  */
3980
3981static int
3982mips_arg_partial_bytes (CUMULATIVE_ARGS *cum,
3983			enum machine_mode mode, tree type, bool named)
3984{
3985  struct mips_arg_info info;
3986
3987  mips_arg_info (cum, mode, type, named, &info);
3988  return info.stack_words > 0 ? info.reg_words * UNITS_PER_WORD : 0;
3989}
3990
3991
3992/* Implement FUNCTION_ARG_BOUNDARY.  Every parameter gets at least
3993   PARM_BOUNDARY bits of alignment, but will be given anything up
3994   to STACK_BOUNDARY bits if the type requires it.  */
3995
3996int
3997function_arg_boundary (enum machine_mode mode, tree type)
3998{
3999  unsigned int alignment;
4000
4001  alignment = type ? TYPE_ALIGN (type) : GET_MODE_ALIGNMENT (mode);
4002  if (alignment < PARM_BOUNDARY)
4003    alignment = PARM_BOUNDARY;
4004  if (alignment > STACK_BOUNDARY)
4005    alignment = STACK_BOUNDARY;
4006  return alignment;
4007}
4008
4009/* Return true if FUNCTION_ARG_PADDING (MODE, TYPE) should return
4010   upward rather than downward.  In other words, return true if the
4011   first byte of the stack slot has useful data, false if the last
4012   byte does.  */
4013
4014bool
4015mips_pad_arg_upward (enum machine_mode mode, tree type)
4016{
4017  /* On little-endian targets, the first byte of every stack argument
4018     is passed in the first byte of the stack slot.  */
4019  if (!BYTES_BIG_ENDIAN)
4020    return true;
4021
4022  /* Otherwise, integral types are padded downward: the last byte of a
4023     stack argument is passed in the last byte of the stack slot.  */
4024  if (type != 0
4025      ? INTEGRAL_TYPE_P (type) || POINTER_TYPE_P (type)
4026      : GET_MODE_CLASS (mode) == MODE_INT)
4027    return false;
4028
4029  /* Big-endian o64 pads floating-point arguments downward.  */
4030  if (mips_abi == ABI_O64)
4031    if (type != 0 ? FLOAT_TYPE_P (type) : GET_MODE_CLASS (mode) == MODE_FLOAT)
4032      return false;
4033
4034  /* Other types are padded upward for o32, o64, n32 and n64.  */
4035  if (mips_abi != ABI_EABI)
4036    return true;
4037
4038  /* Arguments smaller than a stack slot are padded downward.  */
4039  if (mode != BLKmode)
4040    return (GET_MODE_BITSIZE (mode) >= PARM_BOUNDARY);
4041  else
4042    return (int_size_in_bytes (type) >= (PARM_BOUNDARY / BITS_PER_UNIT));
4043}
4044
4045
4046/* Likewise BLOCK_REG_PADDING (MODE, TYPE, ...).  Return !BYTES_BIG_ENDIAN
4047   if the least significant byte of the register has useful data.  Return
4048   the opposite if the most significant byte does.  */
4049
4050bool
4051mips_pad_reg_upward (enum machine_mode mode, tree type)
4052{
4053  /* No shifting is required for floating-point arguments.  */
4054  if (type != 0 ? FLOAT_TYPE_P (type) : GET_MODE_CLASS (mode) == MODE_FLOAT)
4055    return !BYTES_BIG_ENDIAN;
4056
4057  /* Otherwise, apply the same padding to register arguments as we do
4058     to stack arguments.  */
4059  return mips_pad_arg_upward (mode, type);
4060}
4061
4062static void
4063mips_setup_incoming_varargs (CUMULATIVE_ARGS *cum, enum machine_mode mode,
4064			     tree type, int *pretend_size ATTRIBUTE_UNUSED,
4065			     int no_rtl)
4066{
4067  CUMULATIVE_ARGS local_cum;
4068  int gp_saved, fp_saved;
4069
4070  /* The caller has advanced CUM up to, but not beyond, the last named
4071     argument.  Advance a local copy of CUM past the last "real" named
4072     argument, to find out how many registers are left over.  */
4073
4074  local_cum = *cum;
4075  FUNCTION_ARG_ADVANCE (local_cum, mode, type, 1);
4076
4077  /* Found out how many registers we need to save.  */
4078  gp_saved = MAX_ARGS_IN_REGISTERS - local_cum.num_gprs;
4079  fp_saved = (EABI_FLOAT_VARARGS_P
4080	      ? MAX_ARGS_IN_REGISTERS - local_cum.num_fprs
4081	      : 0);
4082
4083  if (!no_rtl)
4084    {
4085      if (gp_saved > 0)
4086	{
4087	  rtx ptr, mem;
4088
4089	  ptr = plus_constant (virtual_incoming_args_rtx,
4090			       REG_PARM_STACK_SPACE (cfun->decl)
4091			       - gp_saved * UNITS_PER_WORD);
4092	  mem = gen_rtx_MEM (BLKmode, ptr);
4093	  set_mem_alias_set (mem, get_varargs_alias_set ());
4094
4095	  move_block_from_reg (local_cum.num_gprs + GP_ARG_FIRST,
4096			       mem, gp_saved);
4097	}
4098      if (fp_saved > 0)
4099	{
4100	  /* We can't use move_block_from_reg, because it will use
4101	     the wrong mode.  */
4102	  enum machine_mode mode;
4103	  int off, i;
4104
4105	  /* Set OFF to the offset from virtual_incoming_args_rtx of
4106	     the first float register.  The FP save area lies below
4107	     the integer one, and is aligned to UNITS_PER_FPVALUE bytes.  */
4108	  off = -gp_saved * UNITS_PER_WORD;
4109	  off &= ~(UNITS_PER_FPVALUE - 1);
4110	  off -= fp_saved * UNITS_PER_FPREG;
4111
4112	  mode = TARGET_SINGLE_FLOAT ? SFmode : DFmode;
4113
4114	  for (i = local_cum.num_fprs; i < MAX_ARGS_IN_REGISTERS; i += FP_INC)
4115	    {
4116	      rtx ptr, mem;
4117
4118	      ptr = plus_constant (virtual_incoming_args_rtx, off);
4119	      mem = gen_rtx_MEM (mode, ptr);
4120	      set_mem_alias_set (mem, get_varargs_alias_set ());
4121	      emit_move_insn (mem, gen_rtx_REG (mode, FP_ARG_FIRST + i));
4122	      off += UNITS_PER_HWFPVALUE;
4123	    }
4124	}
4125    }
4126  if (REG_PARM_STACK_SPACE (cfun->decl) == 0)
4127    cfun->machine->varargs_size = (gp_saved * UNITS_PER_WORD
4128				   + fp_saved * UNITS_PER_FPREG);
4129}
4130
4131/* Create the va_list data type.
4132   We keep 3 pointers, and two offsets.
4133   Two pointers are to the overflow area, which starts at the CFA.
4134     One of these is constant, for addressing into the GPR save area below it.
4135     The other is advanced up the stack through the overflow region.
4136   The third pointer is to the GPR save area.  Since the FPR save area
4137     is just below it, we can address FPR slots off this pointer.
4138   We also keep two one-byte offsets, which are to be subtracted from the
4139     constant pointers to yield addresses in the GPR and FPR save areas.
4140     These are downcounted as float or non-float arguments are used,
4141     and when they get to zero, the argument must be obtained from the
4142     overflow region.
4143   If !EABI_FLOAT_VARARGS_P, then no FPR save area exists, and a single
4144     pointer is enough.  It's started at the GPR save area, and is
4145     advanced, period.
4146   Note that the GPR save area is not constant size, due to optimization
4147     in the prologue.  Hence, we can't use a design with two pointers
4148     and two offsets, although we could have designed this with two pointers
4149     and three offsets.  */
4150
4151static tree
4152mips_build_builtin_va_list (void)
4153{
4154  if (EABI_FLOAT_VARARGS_P)
4155    {
4156      tree f_ovfl, f_gtop, f_ftop, f_goff, f_foff, f_res, record;
4157      tree array, index;
4158
4159      record = (*lang_hooks.types.make_type) (RECORD_TYPE);
4160
4161      f_ovfl = build_decl (FIELD_DECL, get_identifier ("__overflow_argptr"),
4162			  ptr_type_node);
4163      f_gtop = build_decl (FIELD_DECL, get_identifier ("__gpr_top"),
4164			  ptr_type_node);
4165      f_ftop = build_decl (FIELD_DECL, get_identifier ("__fpr_top"),
4166			  ptr_type_node);
4167      f_goff = build_decl (FIELD_DECL, get_identifier ("__gpr_offset"),
4168			  unsigned_char_type_node);
4169      f_foff = build_decl (FIELD_DECL, get_identifier ("__fpr_offset"),
4170			  unsigned_char_type_node);
4171      /* Explicitly pad to the size of a pointer, so that -Wpadded won't
4172	 warn on every user file.  */
4173      index = build_int_cst (NULL_TREE, GET_MODE_SIZE (ptr_mode) - 2 - 1);
4174      array = build_array_type (unsigned_char_type_node,
4175			        build_index_type (index));
4176      f_res = build_decl (FIELD_DECL, get_identifier ("__reserved"), array);
4177
4178      DECL_FIELD_CONTEXT (f_ovfl) = record;
4179      DECL_FIELD_CONTEXT (f_gtop) = record;
4180      DECL_FIELD_CONTEXT (f_ftop) = record;
4181      DECL_FIELD_CONTEXT (f_goff) = record;
4182      DECL_FIELD_CONTEXT (f_foff) = record;
4183      DECL_FIELD_CONTEXT (f_res) = record;
4184
4185      TYPE_FIELDS (record) = f_ovfl;
4186      TREE_CHAIN (f_ovfl) = f_gtop;
4187      TREE_CHAIN (f_gtop) = f_ftop;
4188      TREE_CHAIN (f_ftop) = f_goff;
4189      TREE_CHAIN (f_goff) = f_foff;
4190      TREE_CHAIN (f_foff) = f_res;
4191
4192      layout_type (record);
4193      return record;
4194    }
4195  else if (TARGET_IRIX && TARGET_IRIX6)
4196    /* On IRIX 6, this type is 'char *'.  */
4197    return build_pointer_type (char_type_node);
4198  else
4199    /* Otherwise, we use 'void *'.  */
4200    return ptr_type_node;
4201}
4202
4203/* Implement va_start.  */
4204
4205void
4206mips_va_start (tree valist, rtx nextarg)
4207{
4208  if (EABI_FLOAT_VARARGS_P)
4209    {
4210      const CUMULATIVE_ARGS *cum;
4211      tree f_ovfl, f_gtop, f_ftop, f_goff, f_foff;
4212      tree ovfl, gtop, ftop, goff, foff;
4213      tree t;
4214      int gpr_save_area_size;
4215      int fpr_save_area_size;
4216      int fpr_offset;
4217
4218      cum = &current_function_args_info;
4219      gpr_save_area_size
4220	= (MAX_ARGS_IN_REGISTERS - cum->num_gprs) * UNITS_PER_WORD;
4221      fpr_save_area_size
4222	= (MAX_ARGS_IN_REGISTERS - cum->num_fprs) * UNITS_PER_FPREG;
4223
4224      f_ovfl = TYPE_FIELDS (va_list_type_node);
4225      f_gtop = TREE_CHAIN (f_ovfl);
4226      f_ftop = TREE_CHAIN (f_gtop);
4227      f_goff = TREE_CHAIN (f_ftop);
4228      f_foff = TREE_CHAIN (f_goff);
4229
4230      ovfl = build3 (COMPONENT_REF, TREE_TYPE (f_ovfl), valist, f_ovfl,
4231		     NULL_TREE);
4232      gtop = build3 (COMPONENT_REF, TREE_TYPE (f_gtop), valist, f_gtop,
4233		     NULL_TREE);
4234      ftop = build3 (COMPONENT_REF, TREE_TYPE (f_ftop), valist, f_ftop,
4235		     NULL_TREE);
4236      goff = build3 (COMPONENT_REF, TREE_TYPE (f_goff), valist, f_goff,
4237		     NULL_TREE);
4238      foff = build3 (COMPONENT_REF, TREE_TYPE (f_foff), valist, f_foff,
4239		     NULL_TREE);
4240
4241      /* Emit code to initialize OVFL, which points to the next varargs
4242	 stack argument.  CUM->STACK_WORDS gives the number of stack
4243	 words used by named arguments.  */
4244      t = make_tree (TREE_TYPE (ovfl), virtual_incoming_args_rtx);
4245      if (cum->stack_words > 0)
4246	t = build2 (PLUS_EXPR, TREE_TYPE (ovfl), t,
4247		    build_int_cst (NULL_TREE,
4248				   cum->stack_words * UNITS_PER_WORD));
4249      t = build2 (MODIFY_EXPR, TREE_TYPE (ovfl), ovfl, t);
4250      expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
4251
4252      /* Emit code to initialize GTOP, the top of the GPR save area.  */
4253      t = make_tree (TREE_TYPE (gtop), virtual_incoming_args_rtx);
4254      t = build2 (MODIFY_EXPR, TREE_TYPE (gtop), gtop, t);
4255      expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
4256
4257      /* Emit code to initialize FTOP, the top of the FPR save area.
4258	 This address is gpr_save_area_bytes below GTOP, rounded
4259	 down to the next fp-aligned boundary.  */
4260      t = make_tree (TREE_TYPE (ftop), virtual_incoming_args_rtx);
4261      fpr_offset = gpr_save_area_size + UNITS_PER_FPVALUE - 1;
4262      fpr_offset &= ~(UNITS_PER_FPVALUE - 1);
4263      if (fpr_offset)
4264	t = build2 (PLUS_EXPR, TREE_TYPE (ftop), t,
4265		    build_int_cst (NULL_TREE, -fpr_offset));
4266      t = build2 (MODIFY_EXPR, TREE_TYPE (ftop), ftop, t);
4267      expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
4268
4269      /* Emit code to initialize GOFF, the offset from GTOP of the
4270	 next GPR argument.  */
4271      t = build2 (MODIFY_EXPR, TREE_TYPE (goff), goff,
4272		  build_int_cst (NULL_TREE, gpr_save_area_size));
4273      expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
4274
4275      /* Likewise emit code to initialize FOFF, the offset from FTOP
4276	 of the next FPR argument.  */
4277      t = build2 (MODIFY_EXPR, TREE_TYPE (foff), foff,
4278		  build_int_cst (NULL_TREE, fpr_save_area_size));
4279      expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
4280    }
4281  else
4282    {
4283      nextarg = plus_constant (nextarg, -cfun->machine->varargs_size);
4284      std_expand_builtin_va_start (valist, nextarg);
4285    }
4286}
4287
4288/* Implement va_arg.  */
4289
4290static tree
4291mips_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p, tree *post_p)
4292{
4293  HOST_WIDE_INT size, rsize;
4294  tree addr;
4295  bool indirect;
4296
4297  indirect = pass_by_reference (NULL, TYPE_MODE (type), type, 0);
4298
4299  if (indirect)
4300    type = build_pointer_type (type);
4301
4302  size = int_size_in_bytes (type);
4303  rsize = (size + UNITS_PER_WORD - 1) & -UNITS_PER_WORD;
4304
4305  if (mips_abi != ABI_EABI || !EABI_FLOAT_VARARGS_P)
4306    addr = std_gimplify_va_arg_expr (valist, type, pre_p, post_p);
4307  else
4308    {
4309      /* Not a simple merged stack.	 */
4310
4311      tree f_ovfl, f_gtop, f_ftop, f_goff, f_foff;
4312      tree ovfl, top, off, align;
4313      HOST_WIDE_INT osize;
4314      tree t, u;
4315
4316      f_ovfl = TYPE_FIELDS (va_list_type_node);
4317      f_gtop = TREE_CHAIN (f_ovfl);
4318      f_ftop = TREE_CHAIN (f_gtop);
4319      f_goff = TREE_CHAIN (f_ftop);
4320      f_foff = TREE_CHAIN (f_goff);
4321
4322      /* We maintain separate pointers and offsets for floating-point
4323	 and integer arguments, but we need similar code in both cases.
4324	 Let:
4325
4326	 TOP be the top of the register save area;
4327	 OFF be the offset from TOP of the next register;
4328	 ADDR_RTX be the address of the argument;
4329	 RSIZE be the number of bytes used to store the argument
4330	 when it's in the register save area;
4331	 OSIZE be the number of bytes used to store it when it's
4332	 in the stack overflow area; and
4333	 PADDING be (BYTES_BIG_ENDIAN ? OSIZE - RSIZE : 0)
4334
4335	 The code we want is:
4336
4337	 1: off &= -rsize;	  // round down
4338	 2: if (off != 0)
4339	 3:   {
4340	 4:	 addr_rtx = top - off;
4341	 5:	 off -= rsize;
4342	 6:   }
4343	 7: else
4344	 8:   {
4345	 9:	 ovfl += ((intptr_t) ovfl + osize - 1) & -osize;
4346	 10:	 addr_rtx = ovfl + PADDING;
4347	 11:	 ovfl += osize;
4348	 14:   }
4349
4350	 [1] and [9] can sometimes be optimized away.  */
4351
4352      ovfl = build3 (COMPONENT_REF, TREE_TYPE (f_ovfl), valist, f_ovfl,
4353		     NULL_TREE);
4354
4355      if (GET_MODE_CLASS (TYPE_MODE (type)) == MODE_FLOAT
4356	  && GET_MODE_SIZE (TYPE_MODE (type)) <= UNITS_PER_FPVALUE)
4357	{
4358	  top = build3 (COMPONENT_REF, TREE_TYPE (f_ftop), valist, f_ftop,
4359		        NULL_TREE);
4360	  off = build3 (COMPONENT_REF, TREE_TYPE (f_foff), valist, f_foff,
4361		        NULL_TREE);
4362
4363	  /* When floating-point registers are saved to the stack,
4364	     each one will take up UNITS_PER_HWFPVALUE bytes, regardless
4365	     of the float's precision.  */
4366	  rsize = UNITS_PER_HWFPVALUE;
4367
4368	  /* Overflow arguments are padded to UNITS_PER_WORD bytes
4369	     (= PARM_BOUNDARY bits).  This can be different from RSIZE
4370	     in two cases:
4371
4372	     (1) On 32-bit targets when TYPE is a structure such as:
4373
4374	     struct s { float f; };
4375
4376	     Such structures are passed in paired FPRs, so RSIZE
4377	     will be 8 bytes.  However, the structure only takes
4378	     up 4 bytes of memory, so OSIZE will only be 4.
4379
4380	     (2) In combinations such as -mgp64 -msingle-float
4381	     -fshort-double.  Doubles passed in registers
4382	     will then take up 4 (UNITS_PER_HWFPVALUE) bytes,
4383	     but those passed on the stack take up
4384	     UNITS_PER_WORD bytes.  */
4385	  osize = MAX (GET_MODE_SIZE (TYPE_MODE (type)), UNITS_PER_WORD);
4386	}
4387      else
4388	{
4389	  top = build3 (COMPONENT_REF, TREE_TYPE (f_gtop), valist, f_gtop,
4390		        NULL_TREE);
4391	  off = build3 (COMPONENT_REF, TREE_TYPE (f_goff), valist, f_goff,
4392		        NULL_TREE);
4393	  if (rsize > UNITS_PER_WORD)
4394	    {
4395	      /* [1] Emit code for: off &= -rsize.	*/
4396	      t = build2 (BIT_AND_EXPR, TREE_TYPE (off), off,
4397			  build_int_cst (NULL_TREE, -rsize));
4398	      t = build2 (MODIFY_EXPR, TREE_TYPE (off), off, t);
4399	      gimplify_and_add (t, pre_p);
4400	    }
4401	  osize = rsize;
4402	}
4403
4404      /* [2] Emit code to branch if off == 0.  */
4405      t = build2 (NE_EXPR, boolean_type_node, off,
4406		  build_int_cst (TREE_TYPE (off), 0));
4407      addr = build3 (COND_EXPR, ptr_type_node, t, NULL_TREE, NULL_TREE);
4408
4409      /* [5] Emit code for: off -= rsize.  We do this as a form of
4410	 post-increment not available to C.  Also widen for the
4411	 coming pointer arithmetic.  */
4412      t = fold_convert (TREE_TYPE (off), build_int_cst (NULL_TREE, rsize));
4413      t = build2 (POSTDECREMENT_EXPR, TREE_TYPE (off), off, t);
4414      t = fold_convert (sizetype, t);
4415      t = fold_convert (TREE_TYPE (top), t);
4416
4417      /* [4] Emit code for: addr_rtx = top - off.  On big endian machines,
4418	 the argument has RSIZE - SIZE bytes of leading padding.  */
4419      t = build2 (MINUS_EXPR, TREE_TYPE (top), top, t);
4420      if (BYTES_BIG_ENDIAN && rsize > size)
4421	{
4422	  u = fold_convert (TREE_TYPE (t), build_int_cst (NULL_TREE,
4423							  rsize - size));
4424	  t = build2 (PLUS_EXPR, TREE_TYPE (t), t, u);
4425	}
4426      COND_EXPR_THEN (addr) = t;
4427
4428      if (osize > UNITS_PER_WORD)
4429	{
4430	  /* [9] Emit: ovfl += ((intptr_t) ovfl + osize - 1) & -osize.  */
4431	  u = fold_convert (TREE_TYPE (ovfl),
4432			    build_int_cst (NULL_TREE, osize - 1));
4433	  t = build2 (PLUS_EXPR, TREE_TYPE (ovfl), ovfl, u);
4434	  u = fold_convert (TREE_TYPE (ovfl),
4435			    build_int_cst (NULL_TREE, -osize));
4436	  t = build2 (BIT_AND_EXPR, TREE_TYPE (ovfl), t, u);
4437	  align = build2 (MODIFY_EXPR, TREE_TYPE (ovfl), ovfl, t);
4438	}
4439      else
4440	align = NULL;
4441
4442      /* [10, 11].	Emit code to store ovfl in addr_rtx, then
4443	 post-increment ovfl by osize.  On big-endian machines,
4444	 the argument has OSIZE - SIZE bytes of leading padding.  */
4445      u = fold_convert (TREE_TYPE (ovfl),
4446			build_int_cst (NULL_TREE, osize));
4447      t = build2 (POSTINCREMENT_EXPR, TREE_TYPE (ovfl), ovfl, u);
4448      if (BYTES_BIG_ENDIAN && osize > size)
4449	{
4450	  u = fold_convert (TREE_TYPE (t),
4451			    build_int_cst (NULL_TREE, osize - size));
4452	  t = build2 (PLUS_EXPR, TREE_TYPE (t), t, u);
4453	}
4454
4455      /* String [9] and [10,11] together.  */
4456      if (align)
4457	t = build2 (COMPOUND_EXPR, TREE_TYPE (t), align, t);
4458      COND_EXPR_ELSE (addr) = t;
4459
4460      addr = fold_convert (build_pointer_type (type), addr);
4461      addr = build_va_arg_indirect_ref (addr);
4462    }
4463
4464  if (indirect)
4465    addr = build_va_arg_indirect_ref (addr);
4466
4467  return addr;
4468}
4469
4470/* Return true if it is possible to use left/right accesses for a
4471   bitfield of WIDTH bits starting BITPOS bits into *OP.  When
4472   returning true, update *OP, *LEFT and *RIGHT as follows:
4473
4474   *OP is a BLKmode reference to the whole field.
4475
4476   *LEFT is a QImode reference to the first byte if big endian or
4477   the last byte if little endian.  This address can be used in the
4478   left-side instructions (lwl, swl, ldl, sdl).
4479
4480   *RIGHT is a QImode reference to the opposite end of the field and
4481   can be used in the patterning right-side instruction.  */
4482
4483static bool
4484mips_get_unaligned_mem (rtx *op, unsigned int width, int bitpos,
4485			rtx *left, rtx *right)
4486{
4487  rtx first, last;
4488
4489  /* Check that the operand really is a MEM.  Not all the extv and
4490     extzv predicates are checked.  */
4491  if (!MEM_P (*op))
4492    return false;
4493
4494  /* Check that the size is valid.  */
4495  if (width != 32 && (!TARGET_64BIT || width != 64))
4496    return false;
4497
4498  /* We can only access byte-aligned values.  Since we are always passed
4499     a reference to the first byte of the field, it is not necessary to
4500     do anything with BITPOS after this check.  */
4501  if (bitpos % BITS_PER_UNIT != 0)
4502    return false;
4503
4504  /* Reject aligned bitfields: we want to use a normal load or store
4505     instead of a left/right pair.  */
4506  if (MEM_ALIGN (*op) >= width)
4507    return false;
4508
4509  /* Adjust *OP to refer to the whole field.  This also has the effect
4510     of legitimizing *OP's address for BLKmode, possibly simplifying it.  */
4511  *op = adjust_address (*op, BLKmode, 0);
4512  set_mem_size (*op, GEN_INT (width / BITS_PER_UNIT));
4513
4514  /* Get references to both ends of the field.  We deliberately don't
4515     use the original QImode *OP for FIRST since the new BLKmode one
4516     might have a simpler address.  */
4517  first = adjust_address (*op, QImode, 0);
4518  last = adjust_address (*op, QImode, width / BITS_PER_UNIT - 1);
4519
4520  /* Allocate to LEFT and RIGHT according to endianness.  LEFT should
4521     be the upper word and RIGHT the lower word.  */
4522  if (TARGET_BIG_ENDIAN)
4523    *left = first, *right = last;
4524  else
4525    *left = last, *right = first;
4526
4527  return true;
4528}
4529
4530
4531/* Try to emit the equivalent of (set DEST (zero_extract SRC WIDTH BITPOS)).
4532   Return true on success.  We only handle cases where zero_extract is
4533   equivalent to sign_extract.  */
4534
4535bool
4536mips_expand_unaligned_load (rtx dest, rtx src, unsigned int width, int bitpos)
4537{
4538  rtx left, right, temp;
4539
4540  /* If TARGET_64BIT, the destination of a 32-bit load will be a
4541     paradoxical word_mode subreg.  This is the only case in which
4542     we allow the destination to be larger than the source.  */
4543  if (GET_CODE (dest) == SUBREG
4544      && GET_MODE (dest) == DImode
4545      && SUBREG_BYTE (dest) == 0
4546      && GET_MODE (SUBREG_REG (dest)) == SImode)
4547    dest = SUBREG_REG (dest);
4548
4549  /* After the above adjustment, the destination must be the same
4550     width as the source.  */
4551  if (GET_MODE_BITSIZE (GET_MODE (dest)) != width)
4552    return false;
4553
4554  if (!mips_get_unaligned_mem (&src, width, bitpos, &left, &right))
4555    return false;
4556
4557  temp = gen_reg_rtx (GET_MODE (dest));
4558  if (GET_MODE (dest) == DImode)
4559    {
4560      emit_insn (gen_mov_ldl (temp, src, left));
4561      emit_insn (gen_mov_ldr (dest, copy_rtx (src), right, temp));
4562    }
4563  else
4564    {
4565      emit_insn (gen_mov_lwl (temp, src, left));
4566      emit_insn (gen_mov_lwr (dest, copy_rtx (src), right, temp));
4567    }
4568  return true;
4569}
4570
4571
4572/* Try to expand (set (zero_extract DEST WIDTH BITPOS) SRC).  Return
4573   true on success.  */
4574
4575bool
4576mips_expand_unaligned_store (rtx dest, rtx src, unsigned int width, int bitpos)
4577{
4578  rtx left, right;
4579  enum machine_mode mode;
4580
4581  if (!mips_get_unaligned_mem (&dest, width, bitpos, &left, &right))
4582    return false;
4583
4584  mode = mode_for_size (width, MODE_INT, 0);
4585  src = gen_lowpart (mode, src);
4586
4587  if (mode == DImode)
4588    {
4589      emit_insn (gen_mov_sdl (dest, src, left));
4590      emit_insn (gen_mov_sdr (copy_rtx (dest), copy_rtx (src), right));
4591    }
4592  else
4593    {
4594      emit_insn (gen_mov_swl (dest, src, left));
4595      emit_insn (gen_mov_swr (copy_rtx (dest), copy_rtx (src), right));
4596    }
4597  return true;
4598}
4599
4600/* Return true if X is a MEM with the same size as MODE.  */
4601
4602bool
4603mips_mem_fits_mode_p (enum machine_mode mode, rtx x)
4604{
4605  rtx size;
4606
4607  if (!MEM_P (x))
4608    return false;
4609
4610  size = MEM_SIZE (x);
4611  return size && INTVAL (size) == GET_MODE_SIZE (mode);
4612}
4613
4614/* Return true if (zero_extract OP SIZE POSITION) can be used as the
4615   source of an "ext" instruction or the destination of an "ins"
4616   instruction.  OP must be a register operand and the following
4617   conditions must hold:
4618
4619     0 <= POSITION < GET_MODE_BITSIZE (GET_MODE (op))
4620     0 < SIZE <= GET_MODE_BITSIZE (GET_MODE (op))
4621     0 < POSITION + SIZE <= GET_MODE_BITSIZE (GET_MODE (op))
4622
4623   Also reject lengths equal to a word as they are better handled
4624   by the move patterns.  */
4625
4626bool
4627mips_use_ins_ext_p (rtx op, rtx size, rtx position)
4628{
4629  HOST_WIDE_INT len, pos;
4630
4631  if (!ISA_HAS_EXT_INS
4632      || !register_operand (op, VOIDmode)
4633      || GET_MODE_BITSIZE (GET_MODE (op)) > BITS_PER_WORD)
4634    return false;
4635
4636  len = INTVAL (size);
4637  pos = INTVAL (position);
4638
4639  if (len <= 0 || len >= GET_MODE_BITSIZE (GET_MODE (op))
4640      || pos < 0 || pos + len > GET_MODE_BITSIZE (GET_MODE (op)))
4641    return false;
4642
4643  return true;
4644}
4645
4646/* Set up globals to generate code for the ISA or processor
4647   described by INFO.  */
4648
4649static void
4650mips_set_architecture (const struct mips_cpu_info *info)
4651{
4652  if (info != 0)
4653    {
4654      mips_arch_info = info;
4655      mips_arch = info->cpu;
4656      mips_isa = info->isa;
4657    }
4658}
4659
4660
4661/* Likewise for tuning.  */
4662
4663static void
4664mips_set_tune (const struct mips_cpu_info *info)
4665{
4666  if (info != 0)
4667    {
4668      mips_tune_info = info;
4669      mips_tune = info->cpu;
4670    }
4671}
4672
4673/* Implement TARGET_HANDLE_OPTION.  */
4674
4675static bool
4676mips_handle_option (size_t code, const char *arg, int value ATTRIBUTE_UNUSED)
4677{
4678  switch (code)
4679    {
4680    case OPT_mabi_:
4681      if (strcmp (arg, "32") == 0)
4682	mips_abi = ABI_32;
4683      else if (strcmp (arg, "o64") == 0)
4684	mips_abi = ABI_O64;
4685      else if (strcmp (arg, "n32") == 0)
4686	mips_abi = ABI_N32;
4687      else if (strcmp (arg, "64") == 0)
4688	mips_abi = ABI_64;
4689      else if (strcmp (arg, "eabi") == 0)
4690	mips_abi = ABI_EABI;
4691      else
4692	return false;
4693      return true;
4694
4695    case OPT_march_:
4696    case OPT_mtune_:
4697      return mips_parse_cpu (arg) != 0;
4698
4699    case OPT_mips:
4700      mips_isa_info = mips_parse_cpu (ACONCAT (("mips", arg, NULL)));
4701      return mips_isa_info != 0;
4702
4703    case OPT_mno_flush_func:
4704      mips_cache_flush_func = NULL;
4705      return true;
4706
4707    default:
4708      return true;
4709    }
4710}
4711
4712/* Set up the threshold for data to go into the small data area, instead
4713   of the normal data area, and detect any conflicts in the switches.  */
4714
4715void
4716override_options (void)
4717{
4718  int i, start, regno;
4719  enum machine_mode mode;
4720
4721  mips_section_threshold = g_switch_set ? g_switch_value : MIPS_DEFAULT_GVALUE;
4722
4723  /* The following code determines the architecture and register size.
4724     Similar code was added to GAS 2.14 (see tc-mips.c:md_after_parse_args()).
4725     The GAS and GCC code should be kept in sync as much as possible.  */
4726
4727  if (mips_arch_string != 0)
4728    mips_set_architecture (mips_parse_cpu (mips_arch_string));
4729
4730  if (mips_isa_info != 0)
4731    {
4732      if (mips_arch_info == 0)
4733	mips_set_architecture (mips_isa_info);
4734      else if (mips_arch_info->isa != mips_isa_info->isa)
4735	error ("-%s conflicts with the other architecture options, "
4736	       "which specify a %s processor",
4737	       mips_isa_info->name,
4738	       mips_cpu_info_from_isa (mips_arch_info->isa)->name);
4739    }
4740
4741  if (mips_arch_info == 0)
4742    {
4743#ifdef MIPS_CPU_STRING_DEFAULT
4744      mips_set_architecture (mips_parse_cpu (MIPS_CPU_STRING_DEFAULT));
4745#else
4746      mips_set_architecture (mips_cpu_info_from_isa (MIPS_ISA_DEFAULT));
4747#endif
4748    }
4749
4750  if (ABI_NEEDS_64BIT_REGS && !ISA_HAS_64BIT_REGS)
4751    error ("-march=%s is not compatible with the selected ABI",
4752	   mips_arch_info->name);
4753
4754  /* Optimize for mips_arch, unless -mtune selects a different processor.  */
4755  if (mips_tune_string != 0)
4756    mips_set_tune (mips_parse_cpu (mips_tune_string));
4757
4758  if (mips_tune_info == 0)
4759    mips_set_tune (mips_arch_info);
4760
4761  /* Set cost structure for the processor.  */
4762  mips_cost = &mips_rtx_cost_data[mips_tune];
4763
4764  if ((target_flags_explicit & MASK_64BIT) != 0)
4765    {
4766      /* The user specified the size of the integer registers.  Make sure
4767	 it agrees with the ABI and ISA.  */
4768      if (TARGET_64BIT && !ISA_HAS_64BIT_REGS)
4769	error ("-mgp64 used with a 32-bit processor");
4770      else if (!TARGET_64BIT && ABI_NEEDS_64BIT_REGS)
4771	error ("-mgp32 used with a 64-bit ABI");
4772      else if (TARGET_64BIT && ABI_NEEDS_32BIT_REGS)
4773	error ("-mgp64 used with a 32-bit ABI");
4774    }
4775  else
4776    {
4777      /* Infer the integer register size from the ABI and processor.
4778	 Restrict ourselves to 32-bit registers if that's all the
4779	 processor has, or if the ABI cannot handle 64-bit registers.  */
4780      if (ABI_NEEDS_32BIT_REGS || !ISA_HAS_64BIT_REGS)
4781	target_flags &= ~MASK_64BIT;
4782      else
4783	target_flags |= MASK_64BIT;
4784    }
4785
4786  if ((target_flags_explicit & MASK_FLOAT64) != 0)
4787    {
4788      /* Really, -mfp32 and -mfp64 are ornamental options.  There's
4789	 only one right answer here.  */
4790      if (TARGET_64BIT && TARGET_DOUBLE_FLOAT && !TARGET_FLOAT64)
4791	error ("unsupported combination: %s", "-mgp64 -mfp32 -mdouble-float");
4792      else if (!TARGET_64BIT && TARGET_FLOAT64)
4793	error ("unsupported combination: %s", "-mgp32 -mfp64");
4794      else if (TARGET_SINGLE_FLOAT && TARGET_FLOAT64)
4795	error ("unsupported combination: %s", "-mfp64 -msingle-float");
4796    }
4797  else
4798    {
4799      /* -msingle-float selects 32-bit float registers.  Otherwise the
4800	 float registers should be the same size as the integer ones.  */
4801      if (TARGET_64BIT && TARGET_DOUBLE_FLOAT)
4802	target_flags |= MASK_FLOAT64;
4803      else
4804	target_flags &= ~MASK_FLOAT64;
4805    }
4806
4807  /* End of code shared with GAS.  */
4808
4809  if ((target_flags_explicit & MASK_LONG64) == 0)
4810    {
4811      if ((mips_abi == ABI_EABI && TARGET_64BIT) || mips_abi == ABI_64)
4812	target_flags |= MASK_LONG64;
4813      else
4814	target_flags &= ~MASK_LONG64;
4815    }
4816
4817  if (MIPS_MARCH_CONTROLS_SOFT_FLOAT
4818      && (target_flags_explicit & MASK_SOFT_FLOAT) == 0)
4819    {
4820      /* For some configurations, it is useful to have -march control
4821	 the default setting of MASK_SOFT_FLOAT.  */
4822      switch ((int) mips_arch)
4823	{
4824	case PROCESSOR_R4100:
4825	case PROCESSOR_R4111:
4826	case PROCESSOR_R4120:
4827	case PROCESSOR_R4130:
4828	  target_flags |= MASK_SOFT_FLOAT;
4829	  break;
4830
4831	default:
4832	  target_flags &= ~MASK_SOFT_FLOAT;
4833	  break;
4834	}
4835    }
4836
4837  if (!TARGET_OLDABI)
4838    flag_pcc_struct_return = 0;
4839
4840  if ((target_flags_explicit & MASK_BRANCHLIKELY) == 0)
4841    {
4842      /* If neither -mbranch-likely nor -mno-branch-likely was given
4843	 on the command line, set MASK_BRANCHLIKELY based on the target
4844	 architecture.
4845
4846	 By default, we enable use of Branch Likely instructions on
4847	 all architectures which support them with the following
4848	 exceptions: when creating MIPS32 or MIPS64 code, and when
4849	 tuning for architectures where their use tends to hurt
4850	 performance.
4851
4852	 The MIPS32 and MIPS64 architecture specifications say "Software
4853	 is strongly encouraged to avoid use of Branch Likely
4854	 instructions, as they will be removed from a future revision
4855	 of the [MIPS32 and MIPS64] architecture."  Therefore, we do not
4856	 issue those instructions unless instructed to do so by
4857	 -mbranch-likely.  */
4858      if (ISA_HAS_BRANCHLIKELY
4859	  && !(ISA_MIPS32 || ISA_MIPS32R2 || ISA_MIPS64 || ISA_MIPS64R2)
4860	  && !(TUNE_MIPS5500 || TUNE_SB1))
4861	target_flags |= MASK_BRANCHLIKELY;
4862      else
4863	target_flags &= ~MASK_BRANCHLIKELY;
4864    }
4865  if (TARGET_BRANCHLIKELY && !ISA_HAS_BRANCHLIKELY)
4866    warning (0, "generation of Branch Likely instructions enabled, but not supported by architecture");
4867
4868  /* The effect of -mabicalls isn't defined for the EABI.  */
4869  if (mips_abi == ABI_EABI && TARGET_ABICALLS)
4870    {
4871      error ("unsupported combination: %s", "-mabicalls -mabi=eabi");
4872      target_flags &= ~MASK_ABICALLS;
4873    }
4874
4875  if (TARGET_ABICALLS)
4876    {
4877      /* We need to set flag_pic for executables as well as DSOs
4878	 because we may reference symbols that are not defined in
4879	 the final executable.  (MIPS does not use things like
4880	 copy relocs, for example.)
4881
4882	 Also, there is a body of code that uses __PIC__ to distinguish
4883	 between -mabicalls and -mno-abicalls code.  */
4884      flag_pic = 1;
4885      if (mips_section_threshold > 0)
4886	warning (0, "%<-G%> is incompatible with %<-mabicalls%>");
4887    }
4888
4889  /* mips_split_addresses is a half-way house between explicit
4890     relocations and the traditional assembler macros.  It can
4891     split absolute 32-bit symbolic constants into a high/lo_sum
4892     pair but uses macros for other sorts of access.
4893
4894     Like explicit relocation support for REL targets, it relies
4895     on GNU extensions in the assembler and the linker.
4896
4897     Although this code should work for -O0, it has traditionally
4898     been treated as an optimization.  */
4899  if (!TARGET_MIPS16 && TARGET_SPLIT_ADDRESSES
4900      && optimize && !flag_pic
4901      && !ABI_HAS_64BIT_SYMBOLS)
4902    mips_split_addresses = 1;
4903  else
4904    mips_split_addresses = 0;
4905
4906  /* -mvr4130-align is a "speed over size" optimization: it usually produces
4907     faster code, but at the expense of more nops.  Enable it at -O3 and
4908     above.  */
4909  if (optimize > 2 && (target_flags_explicit & MASK_VR4130_ALIGN) == 0)
4910    target_flags |= MASK_VR4130_ALIGN;
4911
4912  /* When compiling for the mips16, we cannot use floating point.  We
4913     record the original hard float value in mips16_hard_float.  */
4914  if (TARGET_MIPS16)
4915    {
4916      if (TARGET_SOFT_FLOAT)
4917	mips16_hard_float = 0;
4918      else
4919	mips16_hard_float = 1;
4920      target_flags |= MASK_SOFT_FLOAT;
4921
4922      /* Don't run the scheduler before reload, since it tends to
4923         increase register pressure.  */
4924      flag_schedule_insns = 0;
4925
4926      /* Don't do hot/cold partitioning.  The constant layout code expects
4927	 the whole function to be in a single section.  */
4928      flag_reorder_blocks_and_partition = 0;
4929
4930      /* Silently disable -mexplicit-relocs since it doesn't apply
4931	 to mips16 code.  Even so, it would overly pedantic to warn
4932	 about "-mips16 -mexplicit-relocs", especially given that
4933	 we use a %gprel() operator.  */
4934      target_flags &= ~MASK_EXPLICIT_RELOCS;
4935    }
4936
4937  /* When using explicit relocs, we call dbr_schedule from within
4938     mips_reorg.  */
4939  if (TARGET_EXPLICIT_RELOCS)
4940    {
4941      mips_flag_delayed_branch = flag_delayed_branch;
4942      flag_delayed_branch = 0;
4943    }
4944
4945#ifdef MIPS_TFMODE_FORMAT
4946  REAL_MODE_FORMAT (TFmode) = &MIPS_TFMODE_FORMAT;
4947#endif
4948
4949  /* Make sure that the user didn't turn off paired single support when
4950     MIPS-3D support is requested.  */
4951  if (TARGET_MIPS3D && (target_flags_explicit & MASK_PAIRED_SINGLE_FLOAT)
4952      && !TARGET_PAIRED_SINGLE_FLOAT)
4953    error ("-mips3d requires -mpaired-single");
4954
4955  /* If TARGET_MIPS3D, enable MASK_PAIRED_SINGLE_FLOAT.  */
4956  if (TARGET_MIPS3D)
4957    target_flags |= MASK_PAIRED_SINGLE_FLOAT;
4958
4959  /* Make sure that when TARGET_PAIRED_SINGLE_FLOAT is true, TARGET_FLOAT64
4960     and TARGET_HARD_FLOAT are both true.  */
4961  if (TARGET_PAIRED_SINGLE_FLOAT && !(TARGET_FLOAT64 && TARGET_HARD_FLOAT))
4962    error ("-mips3d/-mpaired-single must be used with -mfp64 -mhard-float");
4963
4964  /* Make sure that the ISA supports TARGET_PAIRED_SINGLE_FLOAT when it is
4965     enabled.  */
4966  if (TARGET_PAIRED_SINGLE_FLOAT && !ISA_MIPS64)
4967    error ("-mips3d/-mpaired-single must be used with -mips64");
4968
4969  if (TARGET_MIPS16 && TARGET_DSP)
4970    error ("-mips16 and -mdsp cannot be used together");
4971
4972  mips_print_operand_punct['?'] = 1;
4973  mips_print_operand_punct['#'] = 1;
4974  mips_print_operand_punct['/'] = 1;
4975  mips_print_operand_punct['&'] = 1;
4976  mips_print_operand_punct['!'] = 1;
4977  mips_print_operand_punct['*'] = 1;
4978  mips_print_operand_punct['@'] = 1;
4979  mips_print_operand_punct['.'] = 1;
4980  mips_print_operand_punct['('] = 1;
4981  mips_print_operand_punct[')'] = 1;
4982  mips_print_operand_punct['['] = 1;
4983  mips_print_operand_punct[']'] = 1;
4984  mips_print_operand_punct['<'] = 1;
4985  mips_print_operand_punct['>'] = 1;
4986  mips_print_operand_punct['{'] = 1;
4987  mips_print_operand_punct['}'] = 1;
4988  mips_print_operand_punct['^'] = 1;
4989  mips_print_operand_punct['$'] = 1;
4990  mips_print_operand_punct['+'] = 1;
4991  mips_print_operand_punct['~'] = 1;
4992
4993  /* Set up array to map GCC register number to debug register number.
4994     Ignore the special purpose register numbers.  */
4995
4996  for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
4997    mips_dbx_regno[i] = -1;
4998
4999  start = GP_DBX_FIRST - GP_REG_FIRST;
5000  for (i = GP_REG_FIRST; i <= GP_REG_LAST; i++)
5001    mips_dbx_regno[i] = i + start;
5002
5003  start = FP_DBX_FIRST - FP_REG_FIRST;
5004  for (i = FP_REG_FIRST; i <= FP_REG_LAST; i++)
5005    mips_dbx_regno[i] = i + start;
5006
5007  mips_dbx_regno[HI_REGNUM] = MD_DBX_FIRST + 0;
5008  mips_dbx_regno[LO_REGNUM] = MD_DBX_FIRST + 1;
5009
5010  /* Set up array giving whether a given register can hold a given mode.  */
5011
5012  for (mode = VOIDmode;
5013       mode != MAX_MACHINE_MODE;
5014       mode = (enum machine_mode) ((int)mode + 1))
5015    {
5016      register int size		     = GET_MODE_SIZE (mode);
5017      register enum mode_class class = GET_MODE_CLASS (mode);
5018
5019      for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
5020	{
5021	  register int temp;
5022
5023	  if (mode == CCV2mode)
5024	    temp = (ISA_HAS_8CC
5025		    && ST_REG_P (regno)
5026		    && (regno - ST_REG_FIRST) % 2 == 0);
5027
5028	  else if (mode == CCV4mode)
5029	    temp = (ISA_HAS_8CC
5030		    && ST_REG_P (regno)
5031		    && (regno - ST_REG_FIRST) % 4 == 0);
5032
5033	  else if (mode == CCmode)
5034	    {
5035	      if (! ISA_HAS_8CC)
5036		temp = (regno == FPSW_REGNUM);
5037	      else
5038		temp = (ST_REG_P (regno) || GP_REG_P (regno)
5039			|| FP_REG_P (regno));
5040	    }
5041
5042	  else if (GP_REG_P (regno))
5043	    temp = ((regno & 1) == 0 || size <= UNITS_PER_WORD);
5044
5045	  else if (FP_REG_P (regno))
5046	    temp = ((regno % FP_INC) == 0)
5047		    && (((class == MODE_FLOAT || class == MODE_COMPLEX_FLOAT
5048			  || class == MODE_VECTOR_FLOAT)
5049			 && size <= UNITS_PER_FPVALUE)
5050			/* Allow integer modes that fit into a single
5051			   register.  We need to put integers into FPRs
5052			   when using instructions like cvt and trunc.
5053			   We can't allow sizes smaller than a word,
5054			   the FPU has no appropriate load/store
5055			   instructions for those.  */
5056			|| (class == MODE_INT
5057			    && size >= MIN_UNITS_PER_WORD
5058			    && size <= UNITS_PER_FPREG)
5059			/* Allow TFmode for CCmode reloads.  */
5060			|| (ISA_HAS_8CC && mode == TFmode));
5061
5062          else if (ACC_REG_P (regno))
5063	    temp = (INTEGRAL_MODE_P (mode)
5064		    && (size <= UNITS_PER_WORD
5065			|| (ACC_HI_REG_P (regno)
5066			    && size == 2 * UNITS_PER_WORD)));
5067
5068	  else if (ALL_COP_REG_P (regno))
5069	    temp = (class == MODE_INT && size <= UNITS_PER_WORD);
5070	  else
5071	    temp = 0;
5072
5073	  mips_hard_regno_mode_ok[(int)mode][regno] = temp;
5074	}
5075    }
5076
5077  /* Save GPR registers in word_mode sized hunks.  word_mode hasn't been
5078     initialized yet, so we can't use that here.  */
5079  gpr_mode = TARGET_64BIT ? DImode : SImode;
5080
5081  /* Provide default values for align_* for 64-bit targets.  */
5082  if (TARGET_64BIT && !TARGET_MIPS16)
5083    {
5084      if (align_loops == 0)
5085	align_loops = 8;
5086      if (align_jumps == 0)
5087	align_jumps = 8;
5088      if (align_functions == 0)
5089	align_functions = 8;
5090    }
5091
5092  /* Function to allocate machine-dependent function status.  */
5093  init_machine_status = &mips_init_machine_status;
5094
5095  if (ABI_HAS_64BIT_SYMBOLS)
5096    {
5097      if (TARGET_EXPLICIT_RELOCS)
5098	{
5099	  mips_split_p[SYMBOL_64_HIGH] = true;
5100	  mips_hi_relocs[SYMBOL_64_HIGH] = "%highest(";
5101	  mips_lo_relocs[SYMBOL_64_HIGH] = "%higher(";
5102
5103	  mips_split_p[SYMBOL_64_MID] = true;
5104	  mips_hi_relocs[SYMBOL_64_MID] = "%higher(";
5105	  mips_lo_relocs[SYMBOL_64_MID] = "%hi(";
5106
5107	  mips_split_p[SYMBOL_64_LOW] = true;
5108	  mips_hi_relocs[SYMBOL_64_LOW] = "%hi(";
5109	  mips_lo_relocs[SYMBOL_64_LOW] = "%lo(";
5110
5111	  mips_split_p[SYMBOL_GENERAL] = true;
5112	  mips_lo_relocs[SYMBOL_GENERAL] = "%lo(";
5113	}
5114    }
5115  else
5116    {
5117      if (TARGET_EXPLICIT_RELOCS || mips_split_addresses)
5118	{
5119	  mips_split_p[SYMBOL_GENERAL] = true;
5120	  mips_hi_relocs[SYMBOL_GENERAL] = "%hi(";
5121	  mips_lo_relocs[SYMBOL_GENERAL] = "%lo(";
5122	}
5123    }
5124
5125  if (TARGET_MIPS16)
5126    {
5127      /* The high part is provided by a pseudo copy of $gp.  */
5128      mips_split_p[SYMBOL_SMALL_DATA] = true;
5129      mips_lo_relocs[SYMBOL_SMALL_DATA] = "%gprel(";
5130    }
5131
5132  if (TARGET_EXPLICIT_RELOCS)
5133    {
5134      /* Small data constants are kept whole until after reload,
5135	 then lowered by mips_rewrite_small_data.  */
5136      mips_lo_relocs[SYMBOL_SMALL_DATA] = "%gp_rel(";
5137
5138      mips_split_p[SYMBOL_GOT_LOCAL] = true;
5139      if (TARGET_NEWABI)
5140	{
5141	  mips_lo_relocs[SYMBOL_GOTOFF_PAGE] = "%got_page(";
5142	  mips_lo_relocs[SYMBOL_GOT_LOCAL] = "%got_ofst(";
5143	}
5144      else
5145	{
5146	  mips_lo_relocs[SYMBOL_GOTOFF_PAGE] = "%got(";
5147	  mips_lo_relocs[SYMBOL_GOT_LOCAL] = "%lo(";
5148	}
5149
5150      if (TARGET_XGOT)
5151	{
5152	  /* The HIGH and LO_SUM are matched by special .md patterns.  */
5153	  mips_split_p[SYMBOL_GOT_GLOBAL] = true;
5154
5155	  mips_split_p[SYMBOL_GOTOFF_GLOBAL] = true;
5156	  mips_hi_relocs[SYMBOL_GOTOFF_GLOBAL] = "%got_hi(";
5157	  mips_lo_relocs[SYMBOL_GOTOFF_GLOBAL] = "%got_lo(";
5158
5159	  mips_split_p[SYMBOL_GOTOFF_CALL] = true;
5160	  mips_hi_relocs[SYMBOL_GOTOFF_CALL] = "%call_hi(";
5161	  mips_lo_relocs[SYMBOL_GOTOFF_CALL] = "%call_lo(";
5162	}
5163      else
5164	{
5165	  if (TARGET_NEWABI)
5166	    mips_lo_relocs[SYMBOL_GOTOFF_GLOBAL] = "%got_disp(";
5167	  else
5168	    mips_lo_relocs[SYMBOL_GOTOFF_GLOBAL] = "%got(";
5169	  mips_lo_relocs[SYMBOL_GOTOFF_CALL] = "%call16(";
5170	}
5171    }
5172
5173  if (TARGET_NEWABI)
5174    {
5175      mips_split_p[SYMBOL_GOTOFF_LOADGP] = true;
5176      mips_hi_relocs[SYMBOL_GOTOFF_LOADGP] = "%hi(%neg(%gp_rel(";
5177      mips_lo_relocs[SYMBOL_GOTOFF_LOADGP] = "%lo(%neg(%gp_rel(";
5178    }
5179
5180  /* Thread-local relocation operators.  */
5181  mips_lo_relocs[SYMBOL_TLSGD] = "%tlsgd(";
5182  mips_lo_relocs[SYMBOL_TLSLDM] = "%tlsldm(";
5183  mips_split_p[SYMBOL_DTPREL] = 1;
5184  mips_hi_relocs[SYMBOL_DTPREL] = "%dtprel_hi(";
5185  mips_lo_relocs[SYMBOL_DTPREL] = "%dtprel_lo(";
5186  mips_lo_relocs[SYMBOL_GOTTPREL] = "%gottprel(";
5187  mips_split_p[SYMBOL_TPREL] = 1;
5188  mips_hi_relocs[SYMBOL_TPREL] = "%tprel_hi(";
5189  mips_lo_relocs[SYMBOL_TPREL] = "%tprel_lo(";
5190
5191  /* We don't have a thread pointer access instruction on MIPS16, or
5192     appropriate TLS relocations.  */
5193  if (TARGET_MIPS16)
5194    targetm.have_tls = false;
5195
5196  /* Default to working around R4000 errata only if the processor
5197     was selected explicitly.  */
5198  if ((target_flags_explicit & MASK_FIX_R4000) == 0
5199      && mips_matching_cpu_name_p (mips_arch_info->name, "r4000"))
5200    target_flags |= MASK_FIX_R4000;
5201
5202  /* Default to working around R4400 errata only if the processor
5203     was selected explicitly.  */
5204  if ((target_flags_explicit & MASK_FIX_R4400) == 0
5205      && mips_matching_cpu_name_p (mips_arch_info->name, "r4400"))
5206    target_flags |= MASK_FIX_R4400;
5207}
5208
5209/* Implement CONDITIONAL_REGISTER_USAGE.  */
5210
5211void
5212mips_conditional_register_usage (void)
5213{
5214  if (!TARGET_DSP)
5215    {
5216      int regno;
5217
5218      for (regno = DSP_ACC_REG_FIRST; regno <= DSP_ACC_REG_LAST; regno++)
5219	fixed_regs[regno] = call_used_regs[regno] = 1;
5220    }
5221  if (!TARGET_HARD_FLOAT)
5222    {
5223      int regno;
5224
5225      for (regno = FP_REG_FIRST; regno <= FP_REG_LAST; regno++)
5226	fixed_regs[regno] = call_used_regs[regno] = 1;
5227      for (regno = ST_REG_FIRST; regno <= ST_REG_LAST; regno++)
5228	fixed_regs[regno] = call_used_regs[regno] = 1;
5229    }
5230  else if (! ISA_HAS_8CC)
5231    {
5232      int regno;
5233
5234      /* We only have a single condition code register.  We
5235	 implement this by hiding all the condition code registers,
5236	 and generating RTL that refers directly to ST_REG_FIRST.  */
5237      for (regno = ST_REG_FIRST; regno <= ST_REG_LAST; regno++)
5238	fixed_regs[regno] = call_used_regs[regno] = 1;
5239    }
5240  /* In mips16 mode, we permit the $t temporary registers to be used
5241     for reload.  We prohibit the unused $s registers, since they
5242     are caller saved, and saving them via a mips16 register would
5243     probably waste more time than just reloading the value.  */
5244  if (TARGET_MIPS16)
5245    {
5246      fixed_regs[18] = call_used_regs[18] = 1;
5247      fixed_regs[19] = call_used_regs[19] = 1;
5248      fixed_regs[20] = call_used_regs[20] = 1;
5249      fixed_regs[21] = call_used_regs[21] = 1;
5250      fixed_regs[22] = call_used_regs[22] = 1;
5251      fixed_regs[23] = call_used_regs[23] = 1;
5252      fixed_regs[26] = call_used_regs[26] = 1;
5253      fixed_regs[27] = call_used_regs[27] = 1;
5254      fixed_regs[30] = call_used_regs[30] = 1;
5255    }
5256  /* fp20-23 are now caller saved.  */
5257  if (mips_abi == ABI_64)
5258    {
5259      int regno;
5260      for (regno = FP_REG_FIRST + 20; regno < FP_REG_FIRST + 24; regno++)
5261	call_really_used_regs[regno] = call_used_regs[regno] = 1;
5262    }
5263  /* Odd registers from fp21 to fp31 are now caller saved.  */
5264  if (mips_abi == ABI_N32)
5265    {
5266      int regno;
5267      for (regno = FP_REG_FIRST + 21; regno <= FP_REG_FIRST + 31; regno+=2)
5268	call_really_used_regs[regno] = call_used_regs[regno] = 1;
5269    }
5270}
5271
5272/* Allocate a chunk of memory for per-function machine-dependent data.  */
5273static struct machine_function *
5274mips_init_machine_status (void)
5275{
5276  return ((struct machine_function *)
5277	  ggc_alloc_cleared (sizeof (struct machine_function)));
5278}
5279
5280/* On the mips16, we want to allocate $24 (T_REG) before other
5281   registers for instructions for which it is possible.  This helps
5282   avoid shuffling registers around in order to set up for an xor,
5283   encouraging the compiler to use a cmp instead.  */
5284
5285void
5286mips_order_regs_for_local_alloc (void)
5287{
5288  register int i;
5289
5290  for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
5291    reg_alloc_order[i] = i;
5292
5293  if (TARGET_MIPS16)
5294    {
5295      /* It really doesn't matter where we put register 0, since it is
5296         a fixed register anyhow.  */
5297      reg_alloc_order[0] = 24;
5298      reg_alloc_order[24] = 0;
5299    }
5300}
5301
5302
5303/* The MIPS debug format wants all automatic variables and arguments
5304   to be in terms of the virtual frame pointer (stack pointer before
5305   any adjustment in the function), while the MIPS 3.0 linker wants
5306   the frame pointer to be the stack pointer after the initial
5307   adjustment.  So, we do the adjustment here.  The arg pointer (which
5308   is eliminated) points to the virtual frame pointer, while the frame
5309   pointer (which may be eliminated) points to the stack pointer after
5310   the initial adjustments.  */
5311
5312HOST_WIDE_INT
5313mips_debugger_offset (rtx addr, HOST_WIDE_INT offset)
5314{
5315  rtx offset2 = const0_rtx;
5316  rtx reg = eliminate_constant_term (addr, &offset2);
5317
5318  if (offset == 0)
5319    offset = INTVAL (offset2);
5320
5321  if (reg == stack_pointer_rtx || reg == frame_pointer_rtx
5322      || reg == hard_frame_pointer_rtx)
5323    {
5324      HOST_WIDE_INT frame_size = (!cfun->machine->frame.initialized)
5325				  ? compute_frame_size (get_frame_size ())
5326				  : cfun->machine->frame.total_size;
5327
5328      /* MIPS16 frame is smaller */
5329      if (frame_pointer_needed && TARGET_MIPS16)
5330	frame_size -= cfun->machine->frame.args_size;
5331
5332      offset = offset - frame_size;
5333    }
5334
5335  /* sdbout_parms does not want this to crash for unrecognized cases.  */
5336#if 0
5337  else if (reg != arg_pointer_rtx)
5338    fatal_insn ("mips_debugger_offset called with non stack/frame/arg pointer",
5339		addr);
5340#endif
5341
5342  return offset;
5343}
5344
5345/* Implement the PRINT_OPERAND macro.  The MIPS-specific operand codes are:
5346
5347   'X'  OP is CONST_INT, prints 32 bits in hexadecimal format = "0x%08x",
5348   'x'  OP is CONST_INT, prints 16 bits in hexadecimal format = "0x%04x",
5349   'h'  OP is HIGH, prints %hi(X),
5350   'd'  output integer constant in decimal,
5351   'z'	if the operand is 0, use $0 instead of normal operand.
5352   'D'  print second part of double-word register or memory operand.
5353   'L'  print low-order register of double-word register operand.
5354   'M'  print high-order register of double-word register operand.
5355   'C'  print part of opcode for a branch condition.
5356   'F'  print part of opcode for a floating-point branch condition.
5357   'N'  print part of opcode for a branch condition, inverted.
5358   'W'  print part of opcode for a floating-point branch condition, inverted.
5359   'T'  print 'f' for (eq:CC ...), 't' for (ne:CC ...),
5360	      'z' for (eq:?I ...), 'n' for (ne:?I ...).
5361   't'  like 'T', but with the EQ/NE cases reversed
5362   'Y'  for a CONST_INT X, print mips_fp_conditions[X]
5363   'Z'  print the operand and a comma for ISA_HAS_8CC, otherwise print nothing
5364   'R'  print the reloc associated with LO_SUM
5365   'q'  print DSP accumulator registers
5366
5367   The punctuation characters are:
5368
5369   '('	Turn on .set noreorder
5370   ')'	Turn on .set reorder
5371   '['	Turn on .set noat
5372   ']'	Turn on .set at
5373   '<'	Turn on .set nomacro
5374   '>'	Turn on .set macro
5375   '{'	Turn on .set volatile (not GAS)
5376   '}'	Turn on .set novolatile (not GAS)
5377   '&'	Turn on .set noreorder if filling delay slots
5378   '*'	Turn on both .set noreorder and .set nomacro if filling delay slots
5379   '!'	Turn on .set nomacro if filling delay slots
5380   '#'	Print nop if in a .set noreorder section.
5381   '/'	Like '#', but does nothing within a delayed branch sequence
5382   '?'	Print 'l' if we are to use a branch likely instead of normal branch.
5383   '@'	Print the name of the assembler temporary register (at or $1).
5384   '.'	Print the name of the register with a hard-wired zero (zero or $0).
5385   '^'	Print the name of the pic call-through register (t9 or $25).
5386   '$'	Print the name of the stack pointer register (sp or $29).
5387   '+'	Print the name of the gp register (usually gp or $28).
5388   '~'	Output a branch alignment to LABEL_ALIGN(NULL).  */
5389
5390void
5391print_operand (FILE *file, rtx op, int letter)
5392{
5393  register enum rtx_code code;
5394
5395  if (PRINT_OPERAND_PUNCT_VALID_P (letter))
5396    {
5397      switch (letter)
5398	{
5399	case '?':
5400	  if (mips_branch_likely)
5401	    putc ('l', file);
5402	  break;
5403
5404	case '@':
5405	  fputs (reg_names [GP_REG_FIRST + 1], file);
5406	  break;
5407
5408	case '^':
5409	  fputs (reg_names [PIC_FUNCTION_ADDR_REGNUM], file);
5410	  break;
5411
5412	case '.':
5413	  fputs (reg_names [GP_REG_FIRST + 0], file);
5414	  break;
5415
5416	case '$':
5417	  fputs (reg_names[STACK_POINTER_REGNUM], file);
5418	  break;
5419
5420	case '+':
5421	  fputs (reg_names[PIC_OFFSET_TABLE_REGNUM], file);
5422	  break;
5423
5424	case '&':
5425	  if (final_sequence != 0 && set_noreorder++ == 0)
5426	    fputs (".set\tnoreorder\n\t", file);
5427	  break;
5428
5429	case '*':
5430	  if (final_sequence != 0)
5431	    {
5432	      if (set_noreorder++ == 0)
5433		fputs (".set\tnoreorder\n\t", file);
5434
5435	      if (set_nomacro++ == 0)
5436		fputs (".set\tnomacro\n\t", file);
5437	    }
5438	  break;
5439
5440	case '!':
5441	  if (final_sequence != 0 && set_nomacro++ == 0)
5442	    fputs ("\n\t.set\tnomacro", file);
5443	  break;
5444
5445	case '#':
5446	  if (set_noreorder != 0)
5447	    fputs ("\n\tnop", file);
5448	  break;
5449
5450	case '/':
5451	  /* Print an extra newline so that the delayed insn is separated
5452	     from the following ones.  This looks neater and is consistent
5453	     with non-nop delayed sequences.  */
5454	  if (set_noreorder != 0 && final_sequence == 0)
5455	    fputs ("\n\tnop\n", file);
5456	  break;
5457
5458	case '(':
5459	  if (set_noreorder++ == 0)
5460	    fputs (".set\tnoreorder\n\t", file);
5461	  break;
5462
5463	case ')':
5464	  if (set_noreorder == 0)
5465	    error ("internal error: %%) found without a %%( in assembler pattern");
5466
5467	  else if (--set_noreorder == 0)
5468	    fputs ("\n\t.set\treorder", file);
5469
5470	  break;
5471
5472	case '[':
5473	  if (set_noat++ == 0)
5474	    fputs (".set\tnoat\n\t", file);
5475	  break;
5476
5477	case ']':
5478	  if (set_noat == 0)
5479	    error ("internal error: %%] found without a %%[ in assembler pattern");
5480	  else if (--set_noat == 0)
5481	    fputs ("\n\t.set\tat", file);
5482
5483	  break;
5484
5485	case '<':
5486	  if (set_nomacro++ == 0)
5487	    fputs (".set\tnomacro\n\t", file);
5488	  break;
5489
5490	case '>':
5491	  if (set_nomacro == 0)
5492	    error ("internal error: %%> found without a %%< in assembler pattern");
5493	  else if (--set_nomacro == 0)
5494	    fputs ("\n\t.set\tmacro", file);
5495
5496	  break;
5497
5498	case '{':
5499	  if (set_volatile++ == 0)
5500	    fputs ("#.set\tvolatile\n\t", file);
5501	  break;
5502
5503	case '}':
5504	  if (set_volatile == 0)
5505	    error ("internal error: %%} found without a %%{ in assembler pattern");
5506	  else if (--set_volatile == 0)
5507	    fputs ("\n\t#.set\tnovolatile", file);
5508
5509	  break;
5510
5511	case '~':
5512	  {
5513	    if (align_labels_log > 0)
5514	      ASM_OUTPUT_ALIGN (file, align_labels_log);
5515	  }
5516	  break;
5517
5518	default:
5519	  error ("PRINT_OPERAND: unknown punctuation '%c'", letter);
5520	  break;
5521	}
5522
5523      return;
5524    }
5525
5526  if (! op)
5527    {
5528      error ("PRINT_OPERAND null pointer");
5529      return;
5530    }
5531
5532  code = GET_CODE (op);
5533
5534  if (letter == 'C')
5535    switch (code)
5536      {
5537      case EQ:	fputs ("eq",  file); break;
5538      case NE:	fputs ("ne",  file); break;
5539      case GT:	fputs ("gt",  file); break;
5540      case GE:	fputs ("ge",  file); break;
5541      case LT:	fputs ("lt",  file); break;
5542      case LE:	fputs ("le",  file); break;
5543      case GTU: fputs ("gtu", file); break;
5544      case GEU: fputs ("geu", file); break;
5545      case LTU: fputs ("ltu", file); break;
5546      case LEU: fputs ("leu", file); break;
5547      default:
5548	fatal_insn ("PRINT_OPERAND, invalid insn for %%C", op);
5549      }
5550
5551  else if (letter == 'N')
5552    switch (code)
5553      {
5554      case EQ:	fputs ("ne",  file); break;
5555      case NE:	fputs ("eq",  file); break;
5556      case GT:	fputs ("le",  file); break;
5557      case GE:	fputs ("lt",  file); break;
5558      case LT:	fputs ("ge",  file); break;
5559      case LE:	fputs ("gt",  file); break;
5560      case GTU: fputs ("leu", file); break;
5561      case GEU: fputs ("ltu", file); break;
5562      case LTU: fputs ("geu", file); break;
5563      case LEU: fputs ("gtu", file); break;
5564      default:
5565	fatal_insn ("PRINT_OPERAND, invalid insn for %%N", op);
5566      }
5567
5568  else if (letter == 'F')
5569    switch (code)
5570      {
5571      case EQ: fputs ("c1f", file); break;
5572      case NE: fputs ("c1t", file); break;
5573      default:
5574	fatal_insn ("PRINT_OPERAND, invalid insn for %%F", op);
5575      }
5576
5577  else if (letter == 'W')
5578    switch (code)
5579      {
5580      case EQ: fputs ("c1t", file); break;
5581      case NE: fputs ("c1f", file); break;
5582      default:
5583	fatal_insn ("PRINT_OPERAND, invalid insn for %%W", op);
5584      }
5585
5586  else if (letter == 'h')
5587    {
5588      if (GET_CODE (op) == HIGH)
5589	op = XEXP (op, 0);
5590
5591      print_operand_reloc (file, op, mips_hi_relocs);
5592    }
5593
5594  else if (letter == 'R')
5595    print_operand_reloc (file, op, mips_lo_relocs);
5596
5597  else if (letter == 'Y')
5598    {
5599      if (GET_CODE (op) == CONST_INT
5600	  && ((unsigned HOST_WIDE_INT) INTVAL (op)
5601	      < ARRAY_SIZE (mips_fp_conditions)))
5602	fputs (mips_fp_conditions[INTVAL (op)], file);
5603      else
5604	output_operand_lossage ("invalid %%Y value");
5605    }
5606
5607  else if (letter == 'Z')
5608    {
5609      if (ISA_HAS_8CC)
5610	{
5611	  print_operand (file, op, 0);
5612	  fputc (',', file);
5613	}
5614    }
5615
5616  else if (letter == 'q')
5617    {
5618      int regnum;
5619
5620      if (code != REG)
5621	fatal_insn ("PRINT_OPERAND, invalid insn for %%q", op);
5622
5623      regnum = REGNO (op);
5624      if (MD_REG_P (regnum))
5625	fprintf (file, "$ac0");
5626      else if (DSP_ACC_REG_P (regnum))
5627	fprintf (file, "$ac%c", reg_names[regnum][3]);
5628      else
5629	fatal_insn ("PRINT_OPERAND, invalid insn for %%q", op);
5630    }
5631
5632  else if (code == REG || code == SUBREG)
5633    {
5634      register int regnum;
5635
5636      if (code == REG)
5637	regnum = REGNO (op);
5638      else
5639	regnum = true_regnum (op);
5640
5641      if ((letter == 'M' && ! WORDS_BIG_ENDIAN)
5642	  || (letter == 'L' && WORDS_BIG_ENDIAN)
5643	  || letter == 'D')
5644	regnum++;
5645
5646      fprintf (file, "%s", reg_names[regnum]);
5647    }
5648
5649  else if (code == MEM)
5650    {
5651      if (letter == 'D')
5652	output_address (plus_constant (XEXP (op, 0), 4));
5653      else
5654	output_address (XEXP (op, 0));
5655    }
5656
5657  else if (letter == 'x' && GET_CODE (op) == CONST_INT)
5658    fprintf (file, HOST_WIDE_INT_PRINT_HEX, 0xffff & INTVAL(op));
5659
5660  else if (letter == 'X' && GET_CODE(op) == CONST_INT)
5661    fprintf (file, HOST_WIDE_INT_PRINT_HEX, INTVAL (op));
5662
5663  else if (letter == 'd' && GET_CODE(op) == CONST_INT)
5664    fprintf (file, HOST_WIDE_INT_PRINT_DEC, (INTVAL(op)));
5665
5666  else if (letter == 'z' && op == CONST0_RTX (GET_MODE (op)))
5667    fputs (reg_names[GP_REG_FIRST], file);
5668
5669  else if (letter == 'd' || letter == 'x' || letter == 'X')
5670    output_operand_lossage ("invalid use of %%d, %%x, or %%X");
5671
5672  else if (letter == 'T' || letter == 't')
5673    {
5674      int truth = (code == NE) == (letter == 'T');
5675      fputc ("zfnt"[truth * 2 + (GET_MODE (op) == CCmode)], file);
5676    }
5677
5678  else if (CONST_GP_P (op))
5679    fputs (reg_names[GLOBAL_POINTER_REGNUM], file);
5680
5681  else
5682    output_addr_const (file, op);
5683}
5684
5685
5686/* Print symbolic operand OP, which is part of a HIGH or LO_SUM.
5687   RELOCS is the array of relocations to use.  */
5688
5689static void
5690print_operand_reloc (FILE *file, rtx op, const char **relocs)
5691{
5692  enum mips_symbol_type symbol_type;
5693  const char *p;
5694  rtx base;
5695  HOST_WIDE_INT offset;
5696
5697  symbol_type = mips_classify_symbolic_expression (op);
5698  if (relocs[symbol_type] == 0)
5699    fatal_insn ("PRINT_OPERAND, invalid operand for relocation", op);
5700
5701  /* If OP uses an UNSPEC address, we want to print the inner symbol.  */
5702  mips_split_const (op, &base, &offset);
5703  if (UNSPEC_ADDRESS_P (base))
5704    op = plus_constant (UNSPEC_ADDRESS (base), offset);
5705
5706  fputs (relocs[symbol_type], file);
5707  output_addr_const (file, op);
5708  for (p = relocs[symbol_type]; *p != 0; p++)
5709    if (*p == '(')
5710      fputc (')', file);
5711}
5712
5713/* Output address operand X to FILE.  */
5714
5715void
5716print_operand_address (FILE *file, rtx x)
5717{
5718  struct mips_address_info addr;
5719
5720  if (mips_classify_address (&addr, x, word_mode, true))
5721    switch (addr.type)
5722      {
5723      case ADDRESS_REG:
5724	print_operand (file, addr.offset, 0);
5725	fprintf (file, "(%s)", reg_names[REGNO (addr.reg)]);
5726	return;
5727
5728      case ADDRESS_LO_SUM:
5729	print_operand (file, addr.offset, 'R');
5730	fprintf (file, "(%s)", reg_names[REGNO (addr.reg)]);
5731	return;
5732
5733      case ADDRESS_CONST_INT:
5734	output_addr_const (file, x);
5735	fprintf (file, "(%s)", reg_names[0]);
5736	return;
5737
5738      case ADDRESS_SYMBOLIC:
5739	output_addr_const (file, x);
5740	return;
5741      }
5742  gcc_unreachable ();
5743}
5744
5745/* When using assembler macros, keep track of all of small-data externs
5746   so that mips_file_end can emit the appropriate declarations for them.
5747
5748   In most cases it would be safe (though pointless) to emit .externs
5749   for other symbols too.  One exception is when an object is within
5750   the -G limit but declared by the user to be in a section other
5751   than .sbss or .sdata.  */
5752
5753int
5754mips_output_external (FILE *file ATTRIBUTE_UNUSED, tree decl, const char *name)
5755{
5756  register struct extern_list *p;
5757
5758  if (!TARGET_EXPLICIT_RELOCS && mips_in_small_data_p (decl))
5759    {
5760      p = (struct extern_list *) ggc_alloc (sizeof (struct extern_list));
5761      p->next = extern_head;
5762      p->name = name;
5763      p->size = int_size_in_bytes (TREE_TYPE (decl));
5764      extern_head = p;
5765    }
5766
5767  if (TARGET_IRIX && mips_abi == ABI_32 && TREE_CODE (decl) == FUNCTION_DECL)
5768    {
5769      p = (struct extern_list *) ggc_alloc (sizeof (struct extern_list));
5770      p->next = extern_head;
5771      p->name = name;
5772      p->size = -1;
5773      extern_head = p;
5774    }
5775
5776  return 0;
5777}
5778
5779#if TARGET_IRIX
5780static void
5781irix_output_external_libcall (rtx fun)
5782{
5783  register struct extern_list *p;
5784
5785  if (mips_abi == ABI_32)
5786    {
5787      p = (struct extern_list *) ggc_alloc (sizeof (struct extern_list));
5788      p->next = extern_head;
5789      p->name = XSTR (fun, 0);
5790      p->size = -1;
5791      extern_head = p;
5792    }
5793}
5794#endif
5795
5796/* Emit a new filename to a stream.  If we are smuggling stabs, try to
5797   put out a MIPS ECOFF file and a stab.  */
5798
5799void
5800mips_output_filename (FILE *stream, const char *name)
5801{
5802
5803  /* If we are emitting DWARF-2, let dwarf2out handle the ".file"
5804     directives.  */
5805  if (write_symbols == DWARF2_DEBUG)
5806    return;
5807  else if (mips_output_filename_first_time)
5808    {
5809      mips_output_filename_first_time = 0;
5810      num_source_filenames += 1;
5811      current_function_file = name;
5812      fprintf (stream, "\t.file\t%d ", num_source_filenames);
5813      output_quoted_string (stream, name);
5814      putc ('\n', stream);
5815    }
5816
5817  /* If we are emitting stabs, let dbxout.c handle this (except for
5818     the mips_output_filename_first_time case).  */
5819  else if (write_symbols == DBX_DEBUG)
5820    return;
5821
5822  else if (name != current_function_file
5823	   && strcmp (name, current_function_file) != 0)
5824    {
5825      num_source_filenames += 1;
5826      current_function_file = name;
5827      fprintf (stream, "\t.file\t%d ", num_source_filenames);
5828      output_quoted_string (stream, name);
5829      putc ('\n', stream);
5830    }
5831}
5832
5833/* Output an ASCII string, in a space-saving way.  PREFIX is the string
5834   that should be written before the opening quote, such as "\t.ascii\t"
5835   for real string data or "\t# " for a comment.  */
5836
5837void
5838mips_output_ascii (FILE *stream, const char *string_param, size_t len,
5839		   const char *prefix)
5840{
5841  size_t i;
5842  int cur_pos = 17;
5843  register const unsigned char *string =
5844    (const unsigned char *)string_param;
5845
5846  fprintf (stream, "%s\"", prefix);
5847  for (i = 0; i < len; i++)
5848    {
5849      register int c = string[i];
5850
5851      if (ISPRINT (c))
5852	{
5853	  if (c == '\\' || c == '\"')
5854	    {
5855	      putc ('\\', stream);
5856	      cur_pos++;
5857	    }
5858	  putc (c, stream);
5859	  cur_pos++;
5860	}
5861      else
5862	{
5863	  fprintf (stream, "\\%03o", c);
5864	  cur_pos += 4;
5865	}
5866
5867      if (cur_pos > 72 && i+1 < len)
5868	{
5869	  cur_pos = 17;
5870	  fprintf (stream, "\"\n%s\"", prefix);
5871	}
5872    }
5873  fprintf (stream, "\"\n");
5874}
5875
5876/* Implement TARGET_ASM_FILE_START.  */
5877
5878static void
5879mips_file_start (void)
5880{
5881  default_file_start ();
5882
5883  if (!TARGET_IRIX)
5884    {
5885      /* Generate a special section to describe the ABI switches used to
5886	 produce the resultant binary.  This used to be done by the assembler
5887	 setting bits in the ELF header's flags field, but we have run out of
5888	 bits.  GDB needs this information in order to be able to correctly
5889	 debug these binaries.  See the function mips_gdbarch_init() in
5890	 gdb/mips-tdep.c.  This is unnecessary for the IRIX 5/6 ABIs and
5891	 causes unnecessary IRIX 6 ld warnings.  */
5892      const char * abi_string = NULL;
5893
5894      switch (mips_abi)
5895	{
5896	case ABI_32:   abi_string = "abi32"; break;
5897	case ABI_N32:  abi_string = "abiN32"; break;
5898	case ABI_64:   abi_string = "abi64"; break;
5899	case ABI_O64:  abi_string = "abiO64"; break;
5900	case ABI_EABI: abi_string = TARGET_64BIT ? "eabi64" : "eabi32"; break;
5901	default:
5902	  gcc_unreachable ();
5903	}
5904      /* Note - we use fprintf directly rather than calling switch_to_section
5905	 because in this way we can avoid creating an allocated section.  We
5906	 do not want this section to take up any space in the running
5907	 executable.  */
5908      fprintf (asm_out_file, "\t.section .mdebug.%s\n", abi_string);
5909
5910      /* There is no ELF header flag to distinguish long32 forms of the
5911	 EABI from long64 forms.  Emit a special section to help tools
5912	 such as GDB.  Do the same for o64, which is sometimes used with
5913	 -mlong64.  */
5914      if (mips_abi == ABI_EABI || mips_abi == ABI_O64)
5915	fprintf (asm_out_file, "\t.section .gcc_compiled_long%d\n",
5916		 TARGET_LONG64 ? 64 : 32);
5917
5918      /* Restore the default section.  */
5919      fprintf (asm_out_file, "\t.previous\n");
5920    }
5921
5922  /* Generate the pseudo ops that System V.4 wants.  */
5923  if (TARGET_ABICALLS)
5924    fprintf (asm_out_file, "\t.abicalls\n");
5925
5926  if (TARGET_MIPS16)
5927    fprintf (asm_out_file, "\t.set\tmips16\n");
5928
5929  if (flag_verbose_asm)
5930    fprintf (asm_out_file, "\n%s -G value = %d, Arch = %s, ISA = %d\n",
5931	     ASM_COMMENT_START,
5932	     mips_section_threshold, mips_arch_info->name, mips_isa);
5933}
5934
5935#ifdef BSS_SECTION_ASM_OP
5936/* Implement ASM_OUTPUT_ALIGNED_BSS.  This differs from the default only
5937   in the use of sbss.  */
5938
5939void
5940mips_output_aligned_bss (FILE *stream, tree decl, const char *name,
5941			 unsigned HOST_WIDE_INT size, int align)
5942{
5943  extern tree last_assemble_variable_decl;
5944
5945  if (mips_in_small_data_p (decl))
5946    switch_to_section (get_named_section (NULL, ".sbss", 0));
5947  else
5948    switch_to_section (bss_section);
5949  ASM_OUTPUT_ALIGN (stream, floor_log2 (align / BITS_PER_UNIT));
5950  last_assemble_variable_decl = decl;
5951  ASM_DECLARE_OBJECT_NAME (stream, name, decl);
5952  ASM_OUTPUT_SKIP (stream, size != 0 ? size : 1);
5953}
5954#endif
5955
5956/* Implement TARGET_ASM_FILE_END.  When using assembler macros, emit
5957   .externs for any small-data variables that turned out to be external.  */
5958
5959static void
5960mips_file_end (void)
5961{
5962  tree name_tree;
5963  struct extern_list *p;
5964
5965  if (extern_head)
5966    {
5967      fputs ("\n", asm_out_file);
5968
5969      for (p = extern_head; p != 0; p = p->next)
5970	{
5971	  name_tree = get_identifier (p->name);
5972
5973	  /* Positively ensure only one .extern for any given symbol.  */
5974	  if (!TREE_ASM_WRITTEN (name_tree)
5975	      && TREE_SYMBOL_REFERENCED (name_tree))
5976	    {
5977	      TREE_ASM_WRITTEN (name_tree) = 1;
5978	      /* In IRIX 5 or IRIX 6 for the O32 ABI, we must output a
5979		 `.global name .text' directive for every used but
5980		 undefined function.  If we don't, the linker may perform
5981		 an optimization (skipping over the insns that set $gp)
5982		 when it is unsafe.  */
5983	      if (TARGET_IRIX && mips_abi == ABI_32 && p->size == -1)
5984		{
5985		  fputs ("\t.globl ", asm_out_file);
5986		  assemble_name (asm_out_file, p->name);
5987		  fputs (" .text\n", asm_out_file);
5988		}
5989	      else
5990		{
5991		  fputs ("\t.extern\t", asm_out_file);
5992		  assemble_name (asm_out_file, p->name);
5993		  fprintf (asm_out_file, ", %d\n", p->size);
5994		}
5995	    }
5996	}
5997    }
5998}
5999
6000/* Implement ASM_OUTPUT_ALIGNED_DECL_COMMON.  This is usually the same as the
6001   elfos.h version, but we also need to handle -muninit-const-in-rodata.  */
6002
6003void
6004mips_output_aligned_decl_common (FILE *stream, tree decl, const char *name,
6005				 unsigned HOST_WIDE_INT size,
6006				 unsigned int align)
6007{
6008  /* If the target wants uninitialized const declarations in
6009     .rdata then don't put them in .comm.  */
6010  if (TARGET_EMBEDDED_DATA && TARGET_UNINIT_CONST_IN_RODATA
6011      && TREE_CODE (decl) == VAR_DECL && TREE_READONLY (decl)
6012      && (DECL_INITIAL (decl) == 0 || DECL_INITIAL (decl) == error_mark_node))
6013    {
6014      if (TREE_PUBLIC (decl) && DECL_NAME (decl))
6015	targetm.asm_out.globalize_label (stream, name);
6016
6017      switch_to_section (readonly_data_section);
6018      ASM_OUTPUT_ALIGN (stream, floor_log2 (align / BITS_PER_UNIT));
6019      mips_declare_object (stream, name, "",
6020			   ":\n\t.space\t" HOST_WIDE_INT_PRINT_UNSIGNED "\n",
6021			   size);
6022    }
6023  else
6024    mips_declare_common_object (stream, name, "\n\t.comm\t",
6025				size, align, true);
6026}
6027
6028/* Declare a common object of SIZE bytes using asm directive INIT_STRING.
6029   NAME is the name of the object and ALIGN is the required alignment
6030   in bytes.  TAKES_ALIGNMENT_P is true if the directive takes a third
6031   alignment argument.  */
6032
6033void
6034mips_declare_common_object (FILE *stream, const char *name,
6035			    const char *init_string,
6036			    unsigned HOST_WIDE_INT size,
6037			    unsigned int align, bool takes_alignment_p)
6038{
6039  if (!takes_alignment_p)
6040    {
6041      size += (align / BITS_PER_UNIT) - 1;
6042      size -= size % (align / BITS_PER_UNIT);
6043      mips_declare_object (stream, name, init_string,
6044			   "," HOST_WIDE_INT_PRINT_UNSIGNED "\n", size);
6045    }
6046  else
6047    mips_declare_object (stream, name, init_string,
6048			 "," HOST_WIDE_INT_PRINT_UNSIGNED ",%u\n",
6049			 size, align / BITS_PER_UNIT);
6050}
6051
6052/* Emit either a label, .comm, or .lcomm directive.  When using assembler
6053   macros, mark the symbol as written so that mips_file_end won't emit an
6054   .extern for it.  STREAM is the output file, NAME is the name of the
6055   symbol, INIT_STRING is the string that should be written before the
6056   symbol and FINAL_STRING is the string that should be written after it.
6057   FINAL_STRING is a printf() format that consumes the remaining arguments.  */
6058
6059void
6060mips_declare_object (FILE *stream, const char *name, const char *init_string,
6061		     const char *final_string, ...)
6062{
6063  va_list ap;
6064
6065  fputs (init_string, stream);
6066  assemble_name (stream, name);
6067  va_start (ap, final_string);
6068  vfprintf (stream, final_string, ap);
6069  va_end (ap);
6070
6071  if (!TARGET_EXPLICIT_RELOCS)
6072    {
6073      tree name_tree = get_identifier (name);
6074      TREE_ASM_WRITTEN (name_tree) = 1;
6075    }
6076}
6077
6078#ifdef ASM_OUTPUT_SIZE_DIRECTIVE
6079extern int size_directive_output;
6080
6081/* Implement ASM_DECLARE_OBJECT_NAME.  This is like most of the standard ELF
6082   definitions except that it uses mips_declare_object() to emit the label.  */
6083
6084void
6085mips_declare_object_name (FILE *stream, const char *name,
6086			  tree decl ATTRIBUTE_UNUSED)
6087{
6088#ifdef ASM_OUTPUT_TYPE_DIRECTIVE
6089  ASM_OUTPUT_TYPE_DIRECTIVE (stream, name, "object");
6090#endif
6091
6092  size_directive_output = 0;
6093  if (!flag_inhibit_size_directive && DECL_SIZE (decl))
6094    {
6095      HOST_WIDE_INT size;
6096
6097      size_directive_output = 1;
6098      size = int_size_in_bytes (TREE_TYPE (decl));
6099      ASM_OUTPUT_SIZE_DIRECTIVE (stream, name, size);
6100    }
6101
6102  mips_declare_object (stream, name, "", ":\n");
6103}
6104
6105/* Implement ASM_FINISH_DECLARE_OBJECT.  This is generic ELF stuff.  */
6106
6107void
6108mips_finish_declare_object (FILE *stream, tree decl, int top_level, int at_end)
6109{
6110  const char *name;
6111
6112  name = XSTR (XEXP (DECL_RTL (decl), 0), 0);
6113  if (!flag_inhibit_size_directive
6114      && DECL_SIZE (decl) != 0
6115      && !at_end && top_level
6116      && DECL_INITIAL (decl) == error_mark_node
6117      && !size_directive_output)
6118    {
6119      HOST_WIDE_INT size;
6120
6121      size_directive_output = 1;
6122      size = int_size_in_bytes (TREE_TYPE (decl));
6123      ASM_OUTPUT_SIZE_DIRECTIVE (stream, name, size);
6124    }
6125}
6126#endif
6127
6128/* Return true if X is a small data address that can be rewritten
6129   as a LO_SUM.  */
6130
6131static bool
6132mips_rewrite_small_data_p (rtx x)
6133{
6134  enum mips_symbol_type symbol_type;
6135
6136  return (TARGET_EXPLICIT_RELOCS
6137	  && mips_symbolic_constant_p (x, &symbol_type)
6138	  && symbol_type == SYMBOL_SMALL_DATA);
6139}
6140
6141
6142/* A for_each_rtx callback for mips_small_data_pattern_p.  */
6143
6144static int
6145mips_small_data_pattern_1 (rtx *loc, void *data ATTRIBUTE_UNUSED)
6146{
6147  if (GET_CODE (*loc) == LO_SUM)
6148    return -1;
6149
6150  return mips_rewrite_small_data_p (*loc);
6151}
6152
6153/* Return true if OP refers to small data symbols directly, not through
6154   a LO_SUM.  */
6155
6156bool
6157mips_small_data_pattern_p (rtx op)
6158{
6159  return for_each_rtx (&op, mips_small_data_pattern_1, 0);
6160}
6161
6162/* A for_each_rtx callback, used by mips_rewrite_small_data.  */
6163
6164static int
6165mips_rewrite_small_data_1 (rtx *loc, void *data ATTRIBUTE_UNUSED)
6166{
6167  if (mips_rewrite_small_data_p (*loc))
6168    *loc = gen_rtx_LO_SUM (Pmode, pic_offset_table_rtx, *loc);
6169
6170  if (GET_CODE (*loc) == LO_SUM)
6171    return -1;
6172
6173  return 0;
6174}
6175
6176/* If possible, rewrite OP so that it refers to small data using
6177   explicit relocations.  */
6178
6179rtx
6180mips_rewrite_small_data (rtx op)
6181{
6182  op = copy_insn (op);
6183  for_each_rtx (&op, mips_rewrite_small_data_1, 0);
6184  return op;
6185}
6186
6187/* Return true if the current function has an insn that implicitly
6188   refers to $gp.  */
6189
6190static bool
6191mips_function_has_gp_insn (void)
6192{
6193  /* Don't bother rechecking if we found one last time.  */
6194  if (!cfun->machine->has_gp_insn_p)
6195    {
6196      rtx insn;
6197
6198      push_topmost_sequence ();
6199      for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
6200	if (INSN_P (insn)
6201	    && GET_CODE (PATTERN (insn)) != USE
6202	    && GET_CODE (PATTERN (insn)) != CLOBBER
6203	    && (get_attr_got (insn) != GOT_UNSET
6204		|| small_data_pattern (PATTERN (insn), VOIDmode)))
6205	  break;
6206      pop_topmost_sequence ();
6207
6208      cfun->machine->has_gp_insn_p = (insn != 0);
6209    }
6210  return cfun->machine->has_gp_insn_p;
6211}
6212
6213
6214/* Return the register that should be used as the global pointer
6215   within this function.  Return 0 if the function doesn't need
6216   a global pointer.  */
6217
6218static unsigned int
6219mips_global_pointer (void)
6220{
6221  unsigned int regno;
6222
6223  /* $gp is always available in non-abicalls code.  */
6224  if (!TARGET_ABICALLS)
6225    return GLOBAL_POINTER_REGNUM;
6226
6227  /* We must always provide $gp when it is used implicitly.  */
6228  if (!TARGET_EXPLICIT_RELOCS)
6229    return GLOBAL_POINTER_REGNUM;
6230
6231  /* FUNCTION_PROFILER includes a jal macro, so we need to give it
6232     a valid gp.  */
6233  if (current_function_profile)
6234    return GLOBAL_POINTER_REGNUM;
6235
6236  /* If the function has a nonlocal goto, $gp must hold the correct
6237     global pointer for the target function.  */
6238  if (current_function_has_nonlocal_goto)
6239    return GLOBAL_POINTER_REGNUM;
6240
6241  /* If the gp is never referenced, there's no need to initialize it.
6242     Note that reload can sometimes introduce constant pool references
6243     into a function that otherwise didn't need them.  For example,
6244     suppose we have an instruction like:
6245
6246	  (set (reg:DF R1) (float:DF (reg:SI R2)))
6247
6248     If R2 turns out to be constant such as 1, the instruction may have a
6249     REG_EQUAL note saying that R1 == 1.0.  Reload then has the option of
6250     using this constant if R2 doesn't get allocated to a register.
6251
6252     In cases like these, reload will have added the constant to the pool
6253     but no instruction will yet refer to it.  */
6254  if (!regs_ever_live[GLOBAL_POINTER_REGNUM]
6255      && !current_function_uses_const_pool
6256      && !mips_function_has_gp_insn ())
6257    return 0;
6258
6259  /* We need a global pointer, but perhaps we can use a call-clobbered
6260     register instead of $gp.  */
6261  if (TARGET_NEWABI && current_function_is_leaf)
6262    for (regno = GP_REG_FIRST; regno <= GP_REG_LAST; regno++)
6263      if (!regs_ever_live[regno]
6264	  && call_used_regs[regno]
6265	  && !fixed_regs[regno]
6266	  && regno != PIC_FUNCTION_ADDR_REGNUM)
6267	return regno;
6268
6269  return GLOBAL_POINTER_REGNUM;
6270}
6271
6272
6273/* Return true if the current function must save REGNO.  */
6274
6275static bool
6276mips_save_reg_p (unsigned int regno)
6277{
6278  /* We only need to save $gp for NewABI PIC.  */
6279  if (regno == GLOBAL_POINTER_REGNUM)
6280    return (TARGET_ABICALLS && TARGET_NEWABI
6281	    && cfun->machine->global_pointer == regno);
6282
6283  /* Check call-saved registers.  */
6284  if (regs_ever_live[regno] && !call_used_regs[regno])
6285    return true;
6286
6287  /* We need to save the old frame pointer before setting up a new one.  */
6288  if (regno == HARD_FRAME_POINTER_REGNUM && frame_pointer_needed)
6289    return true;
6290
6291  /* We need to save the incoming return address if it is ever clobbered
6292     within the function.  */
6293  if (regno == GP_REG_FIRST + 31 && regs_ever_live[regno])
6294    return true;
6295
6296  if (TARGET_MIPS16)
6297    {
6298      tree return_type;
6299
6300      return_type = DECL_RESULT (current_function_decl);
6301
6302      /* $18 is a special case in mips16 code.  It may be used to call
6303	 a function which returns a floating point value, but it is
6304	 marked in call_used_regs.  */
6305      if (regno == GP_REG_FIRST + 18 && regs_ever_live[regno])
6306	return true;
6307
6308      /* $31 is also a special case.  It will be used to copy a return
6309	 value into the floating point registers if the return value is
6310	 floating point.  */
6311      if (regno == GP_REG_FIRST + 31
6312	  && mips16_hard_float
6313	  && !aggregate_value_p (return_type, current_function_decl)
6314	  && GET_MODE_CLASS (DECL_MODE (return_type)) == MODE_FLOAT
6315	  && GET_MODE_SIZE (DECL_MODE (return_type)) <= UNITS_PER_FPVALUE)
6316	return true;
6317    }
6318
6319  return false;
6320}
6321
6322
6323/* Return the bytes needed to compute the frame pointer from the current
6324   stack pointer.  SIZE is the size (in bytes) of the local variables.
6325
6326   MIPS stack frames look like:
6327
6328             Before call		        After call
6329        +-----------------------+	+-----------------------+
6330   high |			|       |      			|
6331   mem. |		        |	|			|
6332        |  caller's temps.    	|       |  caller's temps.    	|
6333	|       		|       |       	        |
6334        +-----------------------+	+-----------------------+
6335 	|       		|	|		        |
6336        |  arguments on stack.  |	|  arguments on stack.  |
6337	|       		|	|			|
6338        +-----------------------+	+-----------------------+
6339 	|  4 words to save     	|	|  4 words to save	|
6340	|  arguments passed	|	|  arguments passed	|
6341	|  in registers, even	|	|  in registers, even	|
6342    SP->|  if not passed.       |  VFP->|  if not passed.	|
6343	+-----------------------+       +-----------------------+
6344					|		        |
6345                                        |  fp register save     |
6346					|			|
6347					+-----------------------+
6348					|		        |
6349                                        |  gp register save     |
6350                                        |       		|
6351					+-----------------------+
6352					|			|
6353					|  local variables	|
6354					|			|
6355					+-----------------------+
6356					|			|
6357                                        |  alloca allocations   |
6358        				|			|
6359					+-----------------------+
6360					|			|
6361					|  GP save for V.4 abi	|
6362					|			|
6363					+-----------------------+
6364					|			|
6365                                        |  arguments on stack   |
6366        				|		        |
6367					+-----------------------+
6368                                        |  4 words to save      |
6369					|  arguments passed     |
6370                                        |  in registers, even   |
6371   low                              SP->|  if not passed.       |
6372   memory        			+-----------------------+
6373
6374*/
6375
6376HOST_WIDE_INT
6377compute_frame_size (HOST_WIDE_INT size)
6378{
6379  unsigned int regno;
6380  HOST_WIDE_INT total_size;	/* # bytes that the entire frame takes up */
6381  HOST_WIDE_INT var_size;	/* # bytes that variables take up */
6382  HOST_WIDE_INT args_size;	/* # bytes that outgoing arguments take up */
6383  HOST_WIDE_INT cprestore_size; /* # bytes that the cprestore slot takes up */
6384  HOST_WIDE_INT gp_reg_rounded;	/* # bytes needed to store gp after rounding */
6385  HOST_WIDE_INT gp_reg_size;	/* # bytes needed to store gp regs */
6386  HOST_WIDE_INT fp_reg_size;	/* # bytes needed to store fp regs */
6387  unsigned int mask;		/* mask of saved gp registers */
6388  unsigned int fmask;		/* mask of saved fp registers */
6389
6390  cfun->machine->global_pointer = mips_global_pointer ();
6391
6392  gp_reg_size = 0;
6393  fp_reg_size = 0;
6394  mask = 0;
6395  fmask	= 0;
6396  var_size = MIPS_STACK_ALIGN (size);
6397  args_size = current_function_outgoing_args_size;
6398  cprestore_size = MIPS_STACK_ALIGN (STARTING_FRAME_OFFSET) - args_size;
6399
6400  /* The space set aside by STARTING_FRAME_OFFSET isn't needed in leaf
6401     functions.  If the function has local variables, we're committed
6402     to allocating it anyway.  Otherwise reclaim it here.  */
6403  if (var_size == 0 && current_function_is_leaf)
6404    cprestore_size = args_size = 0;
6405
6406  /* The MIPS 3.0 linker does not like functions that dynamically
6407     allocate the stack and have 0 for STACK_DYNAMIC_OFFSET, since it
6408     looks like we are trying to create a second frame pointer to the
6409     function, so allocate some stack space to make it happy.  */
6410
6411  if (args_size == 0 && current_function_calls_alloca)
6412    args_size = 4 * UNITS_PER_WORD;
6413
6414  total_size = var_size + args_size + cprestore_size;
6415
6416  /* Calculate space needed for gp registers.  */
6417  for (regno = GP_REG_FIRST; regno <= GP_REG_LAST; regno++)
6418    if (mips_save_reg_p (regno))
6419      {
6420	gp_reg_size += GET_MODE_SIZE (gpr_mode);
6421	mask |= 1 << (regno - GP_REG_FIRST);
6422      }
6423
6424  /* We need to restore these for the handler.  */
6425  if (current_function_calls_eh_return)
6426    {
6427      unsigned int i;
6428      for (i = 0; ; ++i)
6429	{
6430	  regno = EH_RETURN_DATA_REGNO (i);
6431	  if (regno == INVALID_REGNUM)
6432	    break;
6433	  gp_reg_size += GET_MODE_SIZE (gpr_mode);
6434	  mask |= 1 << (regno - GP_REG_FIRST);
6435	}
6436    }
6437
6438  /* This loop must iterate over the same space as its companion in
6439     save_restore_insns.  */
6440  for (regno = (FP_REG_LAST - FP_INC + 1);
6441       regno >= FP_REG_FIRST;
6442       regno -= FP_INC)
6443    {
6444      if (mips_save_reg_p (regno))
6445	{
6446	  fp_reg_size += FP_INC * UNITS_PER_FPREG;
6447	  fmask |= ((1 << FP_INC) - 1) << (regno - FP_REG_FIRST);
6448	}
6449    }
6450
6451  gp_reg_rounded = MIPS_STACK_ALIGN (gp_reg_size);
6452  total_size += gp_reg_rounded + MIPS_STACK_ALIGN (fp_reg_size);
6453
6454  /* Add in the space required for saving incoming register arguments.  */
6455  total_size += current_function_pretend_args_size;
6456  total_size += MIPS_STACK_ALIGN (cfun->machine->varargs_size);
6457
6458  /* Save other computed information.  */
6459  cfun->machine->frame.total_size = total_size;
6460  cfun->machine->frame.var_size = var_size;
6461  cfun->machine->frame.args_size = args_size;
6462  cfun->machine->frame.cprestore_size = cprestore_size;
6463  cfun->machine->frame.gp_reg_size = gp_reg_size;
6464  cfun->machine->frame.fp_reg_size = fp_reg_size;
6465  cfun->machine->frame.mask = mask;
6466  cfun->machine->frame.fmask = fmask;
6467  cfun->machine->frame.initialized = reload_completed;
6468  cfun->machine->frame.num_gp = gp_reg_size / UNITS_PER_WORD;
6469  cfun->machine->frame.num_fp = fp_reg_size / (FP_INC * UNITS_PER_FPREG);
6470
6471  if (mask)
6472    {
6473      HOST_WIDE_INT offset;
6474
6475      offset = (args_size + cprestore_size + var_size
6476		+ gp_reg_size - GET_MODE_SIZE (gpr_mode));
6477      cfun->machine->frame.gp_sp_offset = offset;
6478      cfun->machine->frame.gp_save_offset = offset - total_size;
6479    }
6480  else
6481    {
6482      cfun->machine->frame.gp_sp_offset = 0;
6483      cfun->machine->frame.gp_save_offset = 0;
6484    }
6485
6486  if (fmask)
6487    {
6488      HOST_WIDE_INT offset;
6489
6490      offset = (args_size + cprestore_size + var_size
6491		+ gp_reg_rounded + fp_reg_size
6492		- FP_INC * UNITS_PER_FPREG);
6493      cfun->machine->frame.fp_sp_offset = offset;
6494      cfun->machine->frame.fp_save_offset = offset - total_size;
6495    }
6496  else
6497    {
6498      cfun->machine->frame.fp_sp_offset = 0;
6499      cfun->machine->frame.fp_save_offset = 0;
6500    }
6501
6502  /* Ok, we're done.  */
6503  return total_size;
6504}
6505
6506/* Implement INITIAL_ELIMINATION_OFFSET.  FROM is either the frame
6507   pointer or argument pointer.  TO is either the stack pointer or
6508   hard frame pointer.  */
6509
6510HOST_WIDE_INT
6511mips_initial_elimination_offset (int from, int to)
6512{
6513  HOST_WIDE_INT offset;
6514
6515  compute_frame_size (get_frame_size ());
6516
6517  /* Set OFFSET to the offset from the stack pointer.  */
6518  switch (from)
6519    {
6520    case FRAME_POINTER_REGNUM:
6521      offset = 0;
6522      break;
6523
6524    case ARG_POINTER_REGNUM:
6525      offset = (cfun->machine->frame.total_size
6526		- current_function_pretend_args_size);
6527      break;
6528
6529    default:
6530      gcc_unreachable ();
6531    }
6532
6533  if (TARGET_MIPS16 && to == HARD_FRAME_POINTER_REGNUM)
6534    offset -= cfun->machine->frame.args_size;
6535
6536  return offset;
6537}
6538
6539/* Implement RETURN_ADDR_RTX.  Note, we do not support moving
6540   back to a previous frame.  */
6541rtx
6542mips_return_addr (int count, rtx frame ATTRIBUTE_UNUSED)
6543{
6544  if (count != 0)
6545    return const0_rtx;
6546
6547  return get_hard_reg_initial_val (Pmode, GP_REG_FIRST + 31);
6548}
6549
6550/* Use FN to save or restore register REGNO.  MODE is the register's
6551   mode and OFFSET is the offset of its save slot from the current
6552   stack pointer.  */
6553
6554static void
6555mips_save_restore_reg (enum machine_mode mode, int regno,
6556		       HOST_WIDE_INT offset, mips_save_restore_fn fn)
6557{
6558  rtx mem;
6559
6560  mem = gen_frame_mem (mode, plus_constant (stack_pointer_rtx, offset));
6561
6562  fn (gen_rtx_REG (mode, regno), mem);
6563}
6564
6565
6566/* Call FN for each register that is saved by the current function.
6567   SP_OFFSET is the offset of the current stack pointer from the start
6568   of the frame.  */
6569
6570static void
6571mips_for_each_saved_reg (HOST_WIDE_INT sp_offset, mips_save_restore_fn fn)
6572{
6573#define BITSET_P(VALUE, BIT) (((VALUE) & (1L << (BIT))) != 0)
6574
6575  enum machine_mode fpr_mode;
6576  HOST_WIDE_INT offset;
6577  int regno;
6578
6579  /* Save registers starting from high to low.  The debuggers prefer at least
6580     the return register be stored at func+4, and also it allows us not to
6581     need a nop in the epilog if at least one register is reloaded in
6582     addition to return address.  */
6583  offset = cfun->machine->frame.gp_sp_offset - sp_offset;
6584  for (regno = GP_REG_LAST; regno >= GP_REG_FIRST; regno--)
6585    if (BITSET_P (cfun->machine->frame.mask, regno - GP_REG_FIRST))
6586      {
6587	mips_save_restore_reg (gpr_mode, regno, offset, fn);
6588	offset -= GET_MODE_SIZE (gpr_mode);
6589      }
6590
6591  /* This loop must iterate over the same space as its companion in
6592     compute_frame_size.  */
6593  offset = cfun->machine->frame.fp_sp_offset - sp_offset;
6594  fpr_mode = (TARGET_SINGLE_FLOAT ? SFmode : DFmode);
6595  for (regno = (FP_REG_LAST - FP_INC + 1);
6596       regno >= FP_REG_FIRST;
6597       regno -= FP_INC)
6598    if (BITSET_P (cfun->machine->frame.fmask, regno - FP_REG_FIRST))
6599      {
6600	mips_save_restore_reg (fpr_mode, regno, offset, fn);
6601	offset -= GET_MODE_SIZE (fpr_mode);
6602      }
6603#undef BITSET_P
6604}
6605
6606/* If we're generating n32 or n64 abicalls, and the current function
6607   does not use $28 as its global pointer, emit a cplocal directive.
6608   Use pic_offset_table_rtx as the argument to the directive.  */
6609
6610static void
6611mips_output_cplocal (void)
6612{
6613  if (!TARGET_EXPLICIT_RELOCS
6614      && cfun->machine->global_pointer > 0
6615      && cfun->machine->global_pointer != GLOBAL_POINTER_REGNUM)
6616    output_asm_insn (".cplocal %+", 0);
6617}
6618
6619/* Return the style of GP load sequence that is being used for the
6620   current function.  */
6621
6622enum mips_loadgp_style
6623mips_current_loadgp_style (void)
6624{
6625  if (!TARGET_ABICALLS || cfun->machine->global_pointer == 0)
6626    return LOADGP_NONE;
6627
6628  if (TARGET_ABSOLUTE_ABICALLS)
6629    return LOADGP_ABSOLUTE;
6630
6631  return TARGET_NEWABI ? LOADGP_NEWABI : LOADGP_OLDABI;
6632}
6633
6634/* The __gnu_local_gp symbol.  */
6635
6636static GTY(()) rtx mips_gnu_local_gp;
6637
6638/* If we're generating n32 or n64 abicalls, emit instructions
6639   to set up the global pointer.  */
6640
6641static void
6642mips_emit_loadgp (void)
6643{
6644  rtx addr, offset, incoming_address;
6645
6646  switch (mips_current_loadgp_style ())
6647    {
6648    case LOADGP_ABSOLUTE:
6649      if (mips_gnu_local_gp == NULL)
6650	{
6651	  mips_gnu_local_gp = gen_rtx_SYMBOL_REF (Pmode, "__gnu_local_gp");
6652	  SYMBOL_REF_FLAGS (mips_gnu_local_gp) |= SYMBOL_FLAG_LOCAL;
6653	}
6654      emit_insn (gen_loadgp_noshared (mips_gnu_local_gp));
6655      break;
6656
6657    case LOADGP_NEWABI:
6658      addr = XEXP (DECL_RTL (current_function_decl), 0);
6659      offset = mips_unspec_address (addr, SYMBOL_GOTOFF_LOADGP);
6660      incoming_address = gen_rtx_REG (Pmode, PIC_FUNCTION_ADDR_REGNUM);
6661      emit_insn (gen_loadgp (offset, incoming_address));
6662      if (!TARGET_EXPLICIT_RELOCS)
6663	emit_insn (gen_loadgp_blockage ());
6664      break;
6665
6666    default:
6667      break;
6668    }
6669}
6670
6671/* Set up the stack and frame (if desired) for the function.  */
6672
6673static void
6674mips_output_function_prologue (FILE *file, HOST_WIDE_INT size ATTRIBUTE_UNUSED)
6675{
6676  const char *fnname;
6677  HOST_WIDE_INT tsize = cfun->machine->frame.total_size;
6678
6679#ifdef SDB_DEBUGGING_INFO
6680  if (debug_info_level != DINFO_LEVEL_TERSE && write_symbols == SDB_DEBUG)
6681    SDB_OUTPUT_SOURCE_LINE (file, DECL_SOURCE_LINE (current_function_decl));
6682#endif
6683
6684  /* In mips16 mode, we may need to generate a 32 bit to handle
6685     floating point arguments.  The linker will arrange for any 32 bit
6686     functions to call this stub, which will then jump to the 16 bit
6687     function proper.  */
6688  if (TARGET_MIPS16 && !TARGET_SOFT_FLOAT
6689      && current_function_args_info.fp_code != 0)
6690    build_mips16_function_stub (file);
6691
6692  if (!FUNCTION_NAME_ALREADY_DECLARED)
6693    {
6694      /* Get the function name the same way that toplev.c does before calling
6695	 assemble_start_function.  This is needed so that the name used here
6696	 exactly matches the name used in ASM_DECLARE_FUNCTION_NAME.  */
6697      fnname = XSTR (XEXP (DECL_RTL (current_function_decl), 0), 0);
6698
6699      if (!flag_inhibit_size_directive)
6700	{
6701	  fputs ("\t.ent\t", file);
6702	  assemble_name (file, fnname);
6703	  fputs ("\n", file);
6704	}
6705
6706      assemble_name (file, fnname);
6707      fputs (":\n", file);
6708    }
6709
6710  /* Stop mips_file_end from treating this function as external.  */
6711  if (TARGET_IRIX && mips_abi == ABI_32)
6712    TREE_ASM_WRITTEN (DECL_NAME (cfun->decl)) = 1;
6713
6714  if (!flag_inhibit_size_directive)
6715    {
6716      /* .frame FRAMEREG, FRAMESIZE, RETREG */
6717      fprintf (file,
6718	       "\t.frame\t%s," HOST_WIDE_INT_PRINT_DEC ",%s\t\t"
6719	       "# vars= " HOST_WIDE_INT_PRINT_DEC ", regs= %d/%d"
6720	       ", args= " HOST_WIDE_INT_PRINT_DEC
6721	       ", gp= " HOST_WIDE_INT_PRINT_DEC "\n",
6722	       (reg_names[(frame_pointer_needed)
6723			  ? HARD_FRAME_POINTER_REGNUM : STACK_POINTER_REGNUM]),
6724	       ((frame_pointer_needed && TARGET_MIPS16)
6725		? tsize - cfun->machine->frame.args_size
6726		: tsize),
6727	       reg_names[GP_REG_FIRST + 31],
6728	       cfun->machine->frame.var_size,
6729	       cfun->machine->frame.num_gp,
6730	       cfun->machine->frame.num_fp,
6731	       cfun->machine->frame.args_size,
6732	       cfun->machine->frame.cprestore_size);
6733
6734      /* .mask MASK, GPOFFSET; .fmask FPOFFSET */
6735      fprintf (file, "\t.mask\t0x%08x," HOST_WIDE_INT_PRINT_DEC "\n",
6736	       cfun->machine->frame.mask,
6737	       cfun->machine->frame.gp_save_offset);
6738      fprintf (file, "\t.fmask\t0x%08x," HOST_WIDE_INT_PRINT_DEC "\n",
6739	       cfun->machine->frame.fmask,
6740	       cfun->machine->frame.fp_save_offset);
6741
6742      /* Require:
6743	 OLD_SP == *FRAMEREG + FRAMESIZE => can find old_sp from nominated FP reg.
6744	 HIGHEST_GP_SAVED == *FRAMEREG + FRAMESIZE + GPOFFSET => can find saved regs.  */
6745    }
6746
6747  if (mips_current_loadgp_style () == LOADGP_OLDABI)
6748    {
6749      /* Handle the initialization of $gp for SVR4 PIC.  */
6750      if (!cfun->machine->all_noreorder_p)
6751	output_asm_insn ("%(.cpload\t%^%)", 0);
6752      else
6753	output_asm_insn ("%(.cpload\t%^\n\t%<", 0);
6754    }
6755  else if (cfun->machine->all_noreorder_p)
6756    output_asm_insn ("%(%<", 0);
6757
6758  /* Tell the assembler which register we're using as the global
6759     pointer.  This is needed for thunks, since they can use either
6760     explicit relocs or assembler macros.  */
6761  mips_output_cplocal ();
6762}
6763
6764/* Make the last instruction frame related and note that it performs
6765   the operation described by FRAME_PATTERN.  */
6766
6767static void
6768mips_set_frame_expr (rtx frame_pattern)
6769{
6770  rtx insn;
6771
6772  insn = get_last_insn ();
6773  RTX_FRAME_RELATED_P (insn) = 1;
6774  REG_NOTES (insn) = alloc_EXPR_LIST (REG_FRAME_RELATED_EXPR,
6775				      frame_pattern,
6776				      REG_NOTES (insn));
6777}
6778
6779
6780/* Return a frame-related rtx that stores REG at MEM.
6781   REG must be a single register.  */
6782
6783static rtx
6784mips_frame_set (rtx mem, rtx reg)
6785{
6786  rtx set;
6787
6788  /* If we're saving the return address register and the dwarf return
6789     address column differs from the hard register number, adjust the
6790     note reg to refer to the former.  */
6791  if (REGNO (reg) == GP_REG_FIRST + 31
6792      && DWARF_FRAME_RETURN_COLUMN != GP_REG_FIRST + 31)
6793    reg = gen_rtx_REG (GET_MODE (reg), DWARF_FRAME_RETURN_COLUMN);
6794
6795  set = gen_rtx_SET (VOIDmode, mem, reg);
6796  RTX_FRAME_RELATED_P (set) = 1;
6797
6798  return set;
6799}
6800
6801
6802/* Save register REG to MEM.  Make the instruction frame-related.  */
6803
6804static void
6805mips_save_reg (rtx reg, rtx mem)
6806{
6807  if (GET_MODE (reg) == DFmode && !TARGET_FLOAT64)
6808    {
6809      rtx x1, x2;
6810
6811      if (mips_split_64bit_move_p (mem, reg))
6812	mips_split_64bit_move (mem, reg);
6813      else
6814	emit_move_insn (mem, reg);
6815
6816      x1 = mips_frame_set (mips_subword (mem, 0), mips_subword (reg, 0));
6817      x2 = mips_frame_set (mips_subword (mem, 1), mips_subword (reg, 1));
6818      mips_set_frame_expr (gen_rtx_PARALLEL (VOIDmode, gen_rtvec (2, x1, x2)));
6819    }
6820  else
6821    {
6822      if (TARGET_MIPS16
6823	  && REGNO (reg) != GP_REG_FIRST + 31
6824	  && !M16_REG_P (REGNO (reg)))
6825	{
6826	  /* Save a non-mips16 register by moving it through a temporary.
6827	     We don't need to do this for $31 since there's a special
6828	     instruction for it.  */
6829	  emit_move_insn (MIPS_PROLOGUE_TEMP (GET_MODE (reg)), reg);
6830	  emit_move_insn (mem, MIPS_PROLOGUE_TEMP (GET_MODE (reg)));
6831	}
6832      else
6833	emit_move_insn (mem, reg);
6834
6835      mips_set_frame_expr (mips_frame_set (mem, reg));
6836    }
6837}
6838
6839
6840/* Expand the prologue into a bunch of separate insns.  */
6841
6842void
6843mips_expand_prologue (void)
6844{
6845  HOST_WIDE_INT size;
6846
6847  if (cfun->machine->global_pointer > 0)
6848    REGNO (pic_offset_table_rtx) = cfun->machine->global_pointer;
6849
6850  size = compute_frame_size (get_frame_size ());
6851
6852  /* Save the registers.  Allocate up to MIPS_MAX_FIRST_STACK_STEP
6853     bytes beforehand; this is enough to cover the register save area
6854     without going out of range.  */
6855  if ((cfun->machine->frame.mask | cfun->machine->frame.fmask) != 0)
6856    {
6857      HOST_WIDE_INT step1;
6858
6859      step1 = MIN (size, MIPS_MAX_FIRST_STACK_STEP);
6860      RTX_FRAME_RELATED_P (emit_insn (gen_add3_insn (stack_pointer_rtx,
6861						     stack_pointer_rtx,
6862						     GEN_INT (-step1)))) = 1;
6863      size -= step1;
6864      mips_for_each_saved_reg (size, mips_save_reg);
6865    }
6866
6867  /* Allocate the rest of the frame.  */
6868  if (size > 0)
6869    {
6870      if (SMALL_OPERAND (-size))
6871	RTX_FRAME_RELATED_P (emit_insn (gen_add3_insn (stack_pointer_rtx,
6872						       stack_pointer_rtx,
6873						       GEN_INT (-size)))) = 1;
6874      else
6875	{
6876	  emit_move_insn (MIPS_PROLOGUE_TEMP (Pmode), GEN_INT (size));
6877	  if (TARGET_MIPS16)
6878	    {
6879	      /* There are no instructions to add or subtract registers
6880		 from the stack pointer, so use the frame pointer as a
6881		 temporary.  We should always be using a frame pointer
6882		 in this case anyway.  */
6883	      gcc_assert (frame_pointer_needed);
6884	      emit_move_insn (hard_frame_pointer_rtx, stack_pointer_rtx);
6885	      emit_insn (gen_sub3_insn (hard_frame_pointer_rtx,
6886					hard_frame_pointer_rtx,
6887					MIPS_PROLOGUE_TEMP (Pmode)));
6888	      emit_move_insn (stack_pointer_rtx, hard_frame_pointer_rtx);
6889	    }
6890	  else
6891	    emit_insn (gen_sub3_insn (stack_pointer_rtx,
6892				      stack_pointer_rtx,
6893				      MIPS_PROLOGUE_TEMP (Pmode)));
6894
6895	  /* Describe the combined effect of the previous instructions.  */
6896	  mips_set_frame_expr
6897	    (gen_rtx_SET (VOIDmode, stack_pointer_rtx,
6898			  plus_constant (stack_pointer_rtx, -size)));
6899	}
6900    }
6901
6902  /* Set up the frame pointer, if we're using one.  In mips16 code,
6903     we point the frame pointer ahead of the outgoing argument area.
6904     This should allow more variables & incoming arguments to be
6905     accessed with unextended instructions.  */
6906  if (frame_pointer_needed)
6907    {
6908      if (TARGET_MIPS16 && cfun->machine->frame.args_size != 0)
6909	{
6910	  rtx offset = GEN_INT (cfun->machine->frame.args_size);
6911	  if (SMALL_OPERAND (cfun->machine->frame.args_size))
6912	    RTX_FRAME_RELATED_P
6913	      (emit_insn (gen_add3_insn (hard_frame_pointer_rtx,
6914					 stack_pointer_rtx,
6915					 offset))) = 1;
6916	  else
6917	    {
6918	      emit_move_insn (MIPS_PROLOGUE_TEMP (Pmode), offset);
6919	      emit_move_insn (hard_frame_pointer_rtx, stack_pointer_rtx);
6920	      emit_insn (gen_add3_insn (hard_frame_pointer_rtx,
6921					hard_frame_pointer_rtx,
6922					MIPS_PROLOGUE_TEMP (Pmode)));
6923	      mips_set_frame_expr
6924		(gen_rtx_SET (VOIDmode, hard_frame_pointer_rtx,
6925			      plus_constant (stack_pointer_rtx,
6926					     cfun->machine->frame.args_size)));
6927	    }
6928	}
6929      else
6930	RTX_FRAME_RELATED_P (emit_move_insn (hard_frame_pointer_rtx,
6931					     stack_pointer_rtx)) = 1;
6932    }
6933
6934  mips_emit_loadgp ();
6935
6936  /* If generating o32/o64 abicalls, save $gp on the stack.  */
6937  if (TARGET_ABICALLS && !TARGET_NEWABI && !current_function_is_leaf)
6938    emit_insn (gen_cprestore (GEN_INT (current_function_outgoing_args_size)));
6939
6940  /* If we are profiling, make sure no instructions are scheduled before
6941     the call to mcount.  */
6942
6943  if (current_function_profile)
6944    emit_insn (gen_blockage ());
6945}
6946
6947/* Do any necessary cleanup after a function to restore stack, frame,
6948   and regs.  */
6949
6950#define RA_MASK BITMASK_HIGH	/* 1 << 31 */
6951
6952static void
6953mips_output_function_epilogue (FILE *file ATTRIBUTE_UNUSED,
6954			       HOST_WIDE_INT size ATTRIBUTE_UNUSED)
6955{
6956  /* Reinstate the normal $gp.  */
6957  REGNO (pic_offset_table_rtx) = GLOBAL_POINTER_REGNUM;
6958  mips_output_cplocal ();
6959
6960  if (cfun->machine->all_noreorder_p)
6961    {
6962      /* Avoid using %>%) since it adds excess whitespace.  */
6963      output_asm_insn (".set\tmacro", 0);
6964      output_asm_insn (".set\treorder", 0);
6965      set_noreorder = set_nomacro = 0;
6966    }
6967
6968  if (!FUNCTION_NAME_ALREADY_DECLARED && !flag_inhibit_size_directive)
6969    {
6970      const char *fnname;
6971
6972      /* Get the function name the same way that toplev.c does before calling
6973	 assemble_start_function.  This is needed so that the name used here
6974	 exactly matches the name used in ASM_DECLARE_FUNCTION_NAME.  */
6975      fnname = XSTR (XEXP (DECL_RTL (current_function_decl), 0), 0);
6976      fputs ("\t.end\t", file);
6977      assemble_name (file, fnname);
6978      fputs ("\n", file);
6979    }
6980}
6981
6982/* Emit instructions to restore register REG from slot MEM.  */
6983
6984static void
6985mips_restore_reg (rtx reg, rtx mem)
6986{
6987  /* There's no mips16 instruction to load $31 directly.  Load into
6988     $7 instead and adjust the return insn appropriately.  */
6989  if (TARGET_MIPS16 && REGNO (reg) == GP_REG_FIRST + 31)
6990    reg = gen_rtx_REG (GET_MODE (reg), 7);
6991
6992  if (TARGET_MIPS16 && !M16_REG_P (REGNO (reg)))
6993    {
6994      /* Can't restore directly; move through a temporary.  */
6995      emit_move_insn (MIPS_EPILOGUE_TEMP (GET_MODE (reg)), mem);
6996      emit_move_insn (reg, MIPS_EPILOGUE_TEMP (GET_MODE (reg)));
6997    }
6998  else
6999    emit_move_insn (reg, mem);
7000}
7001
7002
7003/* Expand the epilogue into a bunch of separate insns.  SIBCALL_P is true
7004   if this epilogue precedes a sibling call, false if it is for a normal
7005   "epilogue" pattern.  */
7006
7007void
7008mips_expand_epilogue (int sibcall_p)
7009{
7010  HOST_WIDE_INT step1, step2;
7011  rtx base, target;
7012
7013  if (!sibcall_p && mips_can_use_return_insn ())
7014    {
7015      emit_jump_insn (gen_return ());
7016      return;
7017    }
7018
7019  /* Split the frame into two.  STEP1 is the amount of stack we should
7020     deallocate before restoring the registers.  STEP2 is the amount we
7021     should deallocate afterwards.
7022
7023     Start off by assuming that no registers need to be restored.  */
7024  step1 = cfun->machine->frame.total_size;
7025  step2 = 0;
7026
7027  /* Work out which register holds the frame address.  Account for the
7028     frame pointer offset used by mips16 code.  */
7029  if (!frame_pointer_needed)
7030    base = stack_pointer_rtx;
7031  else
7032    {
7033      base = hard_frame_pointer_rtx;
7034      if (TARGET_MIPS16)
7035	step1 -= cfun->machine->frame.args_size;
7036    }
7037
7038  /* If we need to restore registers, deallocate as much stack as
7039     possible in the second step without going out of range.  */
7040  if ((cfun->machine->frame.mask | cfun->machine->frame.fmask) != 0)
7041    {
7042      step2 = MIN (step1, MIPS_MAX_FIRST_STACK_STEP);
7043      step1 -= step2;
7044    }
7045
7046  /* Set TARGET to BASE + STEP1.  */
7047  target = base;
7048  if (step1 > 0)
7049    {
7050      rtx adjust;
7051
7052      /* Get an rtx for STEP1 that we can add to BASE.  */
7053      adjust = GEN_INT (step1);
7054      if (!SMALL_OPERAND (step1))
7055	{
7056	  emit_move_insn (MIPS_EPILOGUE_TEMP (Pmode), adjust);
7057	  adjust = MIPS_EPILOGUE_TEMP (Pmode);
7058	}
7059
7060      /* Normal mode code can copy the result straight into $sp.  */
7061      if (!TARGET_MIPS16)
7062	target = stack_pointer_rtx;
7063
7064      emit_insn (gen_add3_insn (target, base, adjust));
7065    }
7066
7067  /* Copy TARGET into the stack pointer.  */
7068  if (target != stack_pointer_rtx)
7069    emit_move_insn (stack_pointer_rtx, target);
7070
7071  /* If we're using addressing macros for n32/n64 abicalls, $gp is
7072     implicitly used by all SYMBOL_REFs.  We must emit a blockage
7073     insn before restoring it.  */
7074  if (TARGET_ABICALLS && TARGET_NEWABI && !TARGET_EXPLICIT_RELOCS)
7075    emit_insn (gen_blockage ());
7076
7077  /* Restore the registers.  */
7078  mips_for_each_saved_reg (cfun->machine->frame.total_size - step2,
7079			   mips_restore_reg);
7080
7081  /* Deallocate the final bit of the frame.  */
7082  if (step2 > 0)
7083    emit_insn (gen_add3_insn (stack_pointer_rtx,
7084			      stack_pointer_rtx,
7085			      GEN_INT (step2)));
7086
7087  /* Add in the __builtin_eh_return stack adjustment.  We need to
7088     use a temporary in mips16 code.  */
7089  if (current_function_calls_eh_return)
7090    {
7091      if (TARGET_MIPS16)
7092	{
7093	  emit_move_insn (MIPS_EPILOGUE_TEMP (Pmode), stack_pointer_rtx);
7094	  emit_insn (gen_add3_insn (MIPS_EPILOGUE_TEMP (Pmode),
7095				    MIPS_EPILOGUE_TEMP (Pmode),
7096				    EH_RETURN_STACKADJ_RTX));
7097	  emit_move_insn (stack_pointer_rtx, MIPS_EPILOGUE_TEMP (Pmode));
7098	}
7099      else
7100	emit_insn (gen_add3_insn (stack_pointer_rtx,
7101				  stack_pointer_rtx,
7102				  EH_RETURN_STACKADJ_RTX));
7103    }
7104
7105  if (!sibcall_p)
7106    {
7107      /* The mips16 loads the return address into $7, not $31.  */
7108      if (TARGET_MIPS16 && (cfun->machine->frame.mask & RA_MASK) != 0)
7109	emit_jump_insn (gen_return_internal (gen_rtx_REG (Pmode,
7110							  GP_REG_FIRST + 7)));
7111      else
7112	emit_jump_insn (gen_return_internal (gen_rtx_REG (Pmode,
7113							  GP_REG_FIRST + 31)));
7114    }
7115}
7116
7117/* Return nonzero if this function is known to have a null epilogue.
7118   This allows the optimizer to omit jumps to jumps if no stack
7119   was created.  */
7120
7121int
7122mips_can_use_return_insn (void)
7123{
7124  tree return_type;
7125
7126  if (! reload_completed)
7127    return 0;
7128
7129  if (regs_ever_live[31] || current_function_profile)
7130    return 0;
7131
7132  return_type = DECL_RESULT (current_function_decl);
7133
7134  /* In mips16 mode, a function which returns a floating point value
7135     needs to arrange to copy the return value into the floating point
7136     registers.  */
7137  if (TARGET_MIPS16
7138      && mips16_hard_float
7139      && ! aggregate_value_p (return_type, current_function_decl)
7140      && GET_MODE_CLASS (DECL_MODE (return_type)) == MODE_FLOAT
7141      && GET_MODE_SIZE (DECL_MODE (return_type)) <= UNITS_PER_FPVALUE)
7142    return 0;
7143
7144  if (cfun->machine->frame.initialized)
7145    return cfun->machine->frame.total_size == 0;
7146
7147  return compute_frame_size (get_frame_size ()) == 0;
7148}
7149
7150/* Implement TARGET_ASM_OUTPUT_MI_THUNK.  Generate rtl rather than asm text
7151   in order to avoid duplicating too much logic from elsewhere.  */
7152
7153static void
7154mips_output_mi_thunk (FILE *file, tree thunk_fndecl ATTRIBUTE_UNUSED,
7155		      HOST_WIDE_INT delta, HOST_WIDE_INT vcall_offset,
7156		      tree function)
7157{
7158  rtx this, temp1, temp2, insn, fnaddr;
7159
7160  /* Pretend to be a post-reload pass while generating rtl.  */
7161  no_new_pseudos = 1;
7162  reload_completed = 1;
7163  reset_block_changes ();
7164
7165  /* Pick a global pointer for -mabicalls.  Use $15 rather than $28
7166     for TARGET_NEWABI since the latter is a call-saved register.  */
7167  if (TARGET_ABICALLS)
7168    cfun->machine->global_pointer
7169      = REGNO (pic_offset_table_rtx)
7170      = TARGET_NEWABI ? 15 : GLOBAL_POINTER_REGNUM;
7171
7172  /* Set up the global pointer for n32 or n64 abicalls.  */
7173  mips_emit_loadgp ();
7174
7175  /* We need two temporary registers in some cases.  */
7176  temp1 = gen_rtx_REG (Pmode, 2);
7177  temp2 = gen_rtx_REG (Pmode, 3);
7178
7179  /* Find out which register contains the "this" pointer.  */
7180  if (aggregate_value_p (TREE_TYPE (TREE_TYPE (function)), function))
7181    this = gen_rtx_REG (Pmode, GP_ARG_FIRST + 1);
7182  else
7183    this = gen_rtx_REG (Pmode, GP_ARG_FIRST);
7184
7185  /* Add DELTA to THIS.  */
7186  if (delta != 0)
7187    {
7188      rtx offset = GEN_INT (delta);
7189      if (!SMALL_OPERAND (delta))
7190	{
7191	  emit_move_insn (temp1, offset);
7192	  offset = temp1;
7193	}
7194      emit_insn (gen_add3_insn (this, this, offset));
7195    }
7196
7197  /* If needed, add *(*THIS + VCALL_OFFSET) to THIS.  */
7198  if (vcall_offset != 0)
7199    {
7200      rtx addr;
7201
7202      /* Set TEMP1 to *THIS.  */
7203      emit_move_insn (temp1, gen_rtx_MEM (Pmode, this));
7204
7205      /* Set ADDR to a legitimate address for *THIS + VCALL_OFFSET.  */
7206      addr = mips_add_offset (temp2, temp1, vcall_offset);
7207
7208      /* Load the offset and add it to THIS.  */
7209      emit_move_insn (temp1, gen_rtx_MEM (Pmode, addr));
7210      emit_insn (gen_add3_insn (this, this, temp1));
7211    }
7212
7213  /* Jump to the target function.  Use a sibcall if direct jumps are
7214     allowed, otherwise load the address into a register first.  */
7215  fnaddr = XEXP (DECL_RTL (function), 0);
7216  if (TARGET_MIPS16 || TARGET_ABICALLS || TARGET_LONG_CALLS)
7217    {
7218      /* This is messy.  gas treats "la $25,foo" as part of a call
7219	 sequence and may allow a global "foo" to be lazily bound.
7220	 The general move patterns therefore reject this combination.
7221
7222	 In this context, lazy binding would actually be OK for o32 and o64,
7223	 but it's still wrong for n32 and n64; see mips_load_call_address.
7224	 We must therefore load the address via a temporary register if
7225	 mips_dangerous_for_la25_p.
7226
7227	 If we jump to the temporary register rather than $25, the assembler
7228	 can use the move insn to fill the jump's delay slot.  */
7229      if (TARGET_ABICALLS && !mips_dangerous_for_la25_p (fnaddr))
7230	temp1 = gen_rtx_REG (Pmode, PIC_FUNCTION_ADDR_REGNUM);
7231      mips_load_call_address (temp1, fnaddr, true);
7232
7233      if (TARGET_ABICALLS && REGNO (temp1) != PIC_FUNCTION_ADDR_REGNUM)
7234	emit_move_insn (gen_rtx_REG (Pmode, PIC_FUNCTION_ADDR_REGNUM), temp1);
7235      emit_jump_insn (gen_indirect_jump (temp1));
7236    }
7237  else
7238    {
7239      insn = emit_call_insn (gen_sibcall_internal (fnaddr, const0_rtx));
7240      SIBLING_CALL_P (insn) = 1;
7241    }
7242
7243  /* Run just enough of rest_of_compilation.  This sequence was
7244     "borrowed" from alpha.c.  */
7245  insn = get_insns ();
7246  insn_locators_initialize ();
7247  split_all_insns_noflow ();
7248  if (TARGET_MIPS16)
7249    mips16_lay_out_constants ();
7250  shorten_branches (insn);
7251  final_start_function (insn, file, 1);
7252  final (insn, file, 1);
7253  final_end_function ();
7254
7255  /* Clean up the vars set above.  Note that final_end_function resets
7256     the global pointer for us.  */
7257  reload_completed = 0;
7258  no_new_pseudos = 0;
7259}
7260
7261/* Returns nonzero if X contains a SYMBOL_REF.  */
7262
7263static int
7264symbolic_expression_p (rtx x)
7265{
7266  if (GET_CODE (x) == SYMBOL_REF)
7267    return 1;
7268
7269  if (GET_CODE (x) == CONST)
7270    return symbolic_expression_p (XEXP (x, 0));
7271
7272  if (UNARY_P (x))
7273    return symbolic_expression_p (XEXP (x, 0));
7274
7275  if (ARITHMETIC_P (x))
7276    return (symbolic_expression_p (XEXP (x, 0))
7277	    || symbolic_expression_p (XEXP (x, 1)));
7278
7279  return 0;
7280}
7281
7282/* Choose the section to use for the constant rtx expression X that has
7283   mode MODE.  */
7284
7285static section *
7286mips_select_rtx_section (enum machine_mode mode, rtx x,
7287			 unsigned HOST_WIDE_INT align)
7288{
7289  if (TARGET_MIPS16)
7290    {
7291      /* In mips16 mode, the constant table always goes in the same section
7292         as the function, so that constants can be loaded using PC relative
7293         addressing.  */
7294      return function_section (current_function_decl);
7295    }
7296  else if (TARGET_EMBEDDED_DATA)
7297    {
7298      /* For embedded applications, always put constants in read-only data,
7299	 in order to reduce RAM usage.  */
7300      return mergeable_constant_section (mode, align, 0);
7301    }
7302  else
7303    {
7304      /* For hosted applications, always put constants in small data if
7305	 possible, as this gives the best performance.  */
7306      /* ??? Consider using mergeable small data sections.  */
7307
7308      if (GET_MODE_SIZE (mode) <= (unsigned) mips_section_threshold
7309	  && mips_section_threshold > 0)
7310	return get_named_section (NULL, ".sdata", 0);
7311      else if (flag_pic && symbolic_expression_p (x))
7312	return get_named_section (NULL, ".data.rel.ro", 3);
7313      else
7314	return mergeable_constant_section (mode, align, 0);
7315    }
7316}
7317
7318/* Implement TARGET_ASM_FUNCTION_RODATA_SECTION.
7319
7320   The complication here is that, with the combination TARGET_ABICALLS
7321   && !TARGET_GPWORD, jump tables will use absolute addresses, and should
7322   therefore not be included in the read-only part of a DSO.  Handle such
7323   cases by selecting a normal data section instead of a read-only one.
7324   The logic apes that in default_function_rodata_section.  */
7325
7326static section *
7327mips_function_rodata_section (tree decl)
7328{
7329  if (!TARGET_ABICALLS || TARGET_GPWORD)
7330    return default_function_rodata_section (decl);
7331
7332  if (decl && DECL_SECTION_NAME (decl))
7333    {
7334      const char *name = TREE_STRING_POINTER (DECL_SECTION_NAME (decl));
7335      if (DECL_ONE_ONLY (decl) && strncmp (name, ".gnu.linkonce.t.", 16) == 0)
7336	{
7337	  char *rname = ASTRDUP (name);
7338	  rname[14] = 'd';
7339	  return get_section (rname, SECTION_LINKONCE | SECTION_WRITE, decl);
7340	}
7341      else if (flag_function_sections && flag_data_sections
7342	       && strncmp (name, ".text.", 6) == 0)
7343	{
7344	  char *rname = ASTRDUP (name);
7345	  memcpy (rname + 1, "data", 4);
7346	  return get_section (rname, SECTION_WRITE, decl);
7347	}
7348    }
7349  return data_section;
7350}
7351
7352/* Implement TARGET_IN_SMALL_DATA_P.  This function controls whether
7353   locally-defined objects go in a small data section.  It also controls
7354   the setting of the SYMBOL_REF_SMALL_P flag, which in turn helps
7355   mips_classify_symbol decide when to use %gp_rel(...)($gp) accesses.  */
7356
7357static bool
7358mips_in_small_data_p (tree decl)
7359{
7360  HOST_WIDE_INT size;
7361
7362  if (TREE_CODE (decl) == STRING_CST || TREE_CODE (decl) == FUNCTION_DECL)
7363    return false;
7364
7365  /* We don't yet generate small-data references for -mabicalls.  See related
7366     -G handling in override_options.  */
7367  if (TARGET_ABICALLS)
7368    return false;
7369
7370  if (TREE_CODE (decl) == VAR_DECL && DECL_SECTION_NAME (decl) != 0)
7371    {
7372      const char *name;
7373
7374      /* Reject anything that isn't in a known small-data section.  */
7375      name = TREE_STRING_POINTER (DECL_SECTION_NAME (decl));
7376      if (strcmp (name, ".sdata") != 0 && strcmp (name, ".sbss") != 0)
7377	return false;
7378
7379      /* If a symbol is defined externally, the assembler will use the
7380	 usual -G rules when deciding how to implement macros.  */
7381      if (TARGET_EXPLICIT_RELOCS || !DECL_EXTERNAL (decl))
7382	return true;
7383    }
7384  else if (TARGET_EMBEDDED_DATA)
7385    {
7386      /* Don't put constants into the small data section: we want them
7387	 to be in ROM rather than RAM.  */
7388      if (TREE_CODE (decl) != VAR_DECL)
7389	return false;
7390
7391      if (TREE_READONLY (decl)
7392	  && !TREE_SIDE_EFFECTS (decl)
7393	  && (!DECL_INITIAL (decl) || TREE_CONSTANT (DECL_INITIAL (decl))))
7394	return false;
7395    }
7396
7397  size = int_size_in_bytes (TREE_TYPE (decl));
7398  return (size > 0 && size <= mips_section_threshold);
7399}
7400
7401/* Implement TARGET_USE_ANCHORS_FOR_SYMBOL_P.  We don't want to use
7402   anchors for small data: the GP register acts as an anchor in that
7403   case.  We also don't want to use them for PC-relative accesses,
7404   where the PC acts as an anchor.  */
7405
7406static bool
7407mips_use_anchors_for_symbol_p (rtx symbol)
7408{
7409  switch (mips_classify_symbol (symbol))
7410    {
7411    case SYMBOL_CONSTANT_POOL:
7412    case SYMBOL_SMALL_DATA:
7413      return false;
7414
7415    default:
7416      return true;
7417    }
7418}
7419
7420/* See whether VALTYPE is a record whose fields should be returned in
7421   floating-point registers.  If so, return the number of fields and
7422   list them in FIELDS (which should have two elements).  Return 0
7423   otherwise.
7424
7425   For n32 & n64, a structure with one or two fields is returned in
7426   floating-point registers as long as every field has a floating-point
7427   type.  */
7428
7429static int
7430mips_fpr_return_fields (tree valtype, tree *fields)
7431{
7432  tree field;
7433  int i;
7434
7435  if (!TARGET_NEWABI)
7436    return 0;
7437
7438  if (TREE_CODE (valtype) != RECORD_TYPE)
7439    return 0;
7440
7441  i = 0;
7442  for (field = TYPE_FIELDS (valtype); field != 0; field = TREE_CHAIN (field))
7443    {
7444      if (TREE_CODE (field) != FIELD_DECL)
7445	continue;
7446
7447      if (TREE_CODE (TREE_TYPE (field)) != REAL_TYPE)
7448	return 0;
7449
7450      if (i == 2)
7451	return 0;
7452
7453      fields[i++] = field;
7454    }
7455  return i;
7456}
7457
7458
7459/* Implement TARGET_RETURN_IN_MSB.  For n32 & n64, we should return
7460   a value in the most significant part of $2/$3 if:
7461
7462      - the target is big-endian;
7463
7464      - the value has a structure or union type (we generalize this to
7465	cover aggregates from other languages too); and
7466
7467      - the structure is not returned in floating-point registers.  */
7468
7469static bool
7470mips_return_in_msb (tree valtype)
7471{
7472  tree fields[2];
7473
7474  return (TARGET_NEWABI
7475	  && TARGET_BIG_ENDIAN
7476	  && AGGREGATE_TYPE_P (valtype)
7477	  && mips_fpr_return_fields (valtype, fields) == 0);
7478}
7479
7480
7481/* Return a composite value in a pair of floating-point registers.
7482   MODE1 and OFFSET1 are the mode and byte offset for the first value,
7483   likewise MODE2 and OFFSET2 for the second.  MODE is the mode of the
7484   complete value.
7485
7486   For n32 & n64, $f0 always holds the first value and $f2 the second.
7487   Otherwise the values are packed together as closely as possible.  */
7488
7489static rtx
7490mips_return_fpr_pair (enum machine_mode mode,
7491		      enum machine_mode mode1, HOST_WIDE_INT offset1,
7492		      enum machine_mode mode2, HOST_WIDE_INT offset2)
7493{
7494  int inc;
7495
7496  inc = (TARGET_NEWABI ? 2 : FP_INC);
7497  return gen_rtx_PARALLEL
7498    (mode,
7499     gen_rtvec (2,
7500		gen_rtx_EXPR_LIST (VOIDmode,
7501				   gen_rtx_REG (mode1, FP_RETURN),
7502				   GEN_INT (offset1)),
7503		gen_rtx_EXPR_LIST (VOIDmode,
7504				   gen_rtx_REG (mode2, FP_RETURN + inc),
7505				   GEN_INT (offset2))));
7506
7507}
7508
7509
7510/* Implement FUNCTION_VALUE and LIBCALL_VALUE.  For normal calls,
7511   VALTYPE is the return type and MODE is VOIDmode.  For libcalls,
7512   VALTYPE is null and MODE is the mode of the return value.  */
7513
7514rtx
7515mips_function_value (tree valtype, tree func ATTRIBUTE_UNUSED,
7516		     enum machine_mode mode)
7517{
7518  if (valtype)
7519    {
7520      tree fields[2];
7521      int unsignedp;
7522
7523      mode = TYPE_MODE (valtype);
7524      unsignedp = TYPE_UNSIGNED (valtype);
7525
7526      /* Since we define TARGET_PROMOTE_FUNCTION_RETURN that returns
7527	 true, we must promote the mode just as PROMOTE_MODE does.  */
7528      mode = promote_mode (valtype, mode, &unsignedp, 1);
7529
7530      /* Handle structures whose fields are returned in $f0/$f2.  */
7531      switch (mips_fpr_return_fields (valtype, fields))
7532	{
7533	case 1:
7534	  return gen_rtx_REG (mode, FP_RETURN);
7535
7536	case 2:
7537	  return mips_return_fpr_pair (mode,
7538				       TYPE_MODE (TREE_TYPE (fields[0])),
7539				       int_byte_position (fields[0]),
7540				       TYPE_MODE (TREE_TYPE (fields[1])),
7541				       int_byte_position (fields[1]));
7542	}
7543
7544      /* If a value is passed in the most significant part of a register, see
7545	 whether we have to round the mode up to a whole number of words.  */
7546      if (mips_return_in_msb (valtype))
7547	{
7548	  HOST_WIDE_INT size = int_size_in_bytes (valtype);
7549	  if (size % UNITS_PER_WORD != 0)
7550	    {
7551	      size += UNITS_PER_WORD - size % UNITS_PER_WORD;
7552	      mode = mode_for_size (size * BITS_PER_UNIT, MODE_INT, 0);
7553	    }
7554	}
7555
7556      /* For EABI, the class of return register depends entirely on MODE.
7557	 For example, "struct { some_type x; }" and "union { some_type x; }"
7558	 are returned in the same way as a bare "some_type" would be.
7559	 Other ABIs only use FPRs for scalar, complex or vector types.  */
7560      if (mips_abi != ABI_EABI && !FLOAT_TYPE_P (valtype))
7561	return gen_rtx_REG (mode, GP_RETURN);
7562    }
7563
7564  if ((GET_MODE_CLASS (mode) == MODE_FLOAT
7565       || GET_MODE_CLASS (mode) == MODE_VECTOR_FLOAT)
7566      && GET_MODE_SIZE (mode) <= UNITS_PER_HWFPVALUE)
7567    return gen_rtx_REG (mode, FP_RETURN);
7568
7569  /* Handle long doubles for n32 & n64.  */
7570  if (mode == TFmode)
7571    return mips_return_fpr_pair (mode,
7572				 DImode, 0,
7573				 DImode, GET_MODE_SIZE (mode) / 2);
7574
7575  if (GET_MODE_CLASS (mode) == MODE_COMPLEX_FLOAT
7576      && GET_MODE_SIZE (mode) <= UNITS_PER_HWFPVALUE * 2)
7577    return mips_return_fpr_pair (mode,
7578				 GET_MODE_INNER (mode), 0,
7579				 GET_MODE_INNER (mode),
7580				 GET_MODE_SIZE (mode) / 2);
7581
7582  return gen_rtx_REG (mode, GP_RETURN);
7583}
7584
7585/* Return nonzero when an argument must be passed by reference.  */
7586
7587static bool
7588mips_pass_by_reference (CUMULATIVE_ARGS *cum ATTRIBUTE_UNUSED,
7589			enum machine_mode mode, tree type,
7590			bool named ATTRIBUTE_UNUSED)
7591{
7592  if (mips_abi == ABI_EABI)
7593    {
7594      int size;
7595
7596      /* ??? How should SCmode be handled?  */
7597      if (mode == DImode || mode == DFmode)
7598	return 0;
7599
7600      size = type ? int_size_in_bytes (type) : GET_MODE_SIZE (mode);
7601      return size == -1 || size > UNITS_PER_WORD;
7602    }
7603  else
7604    {
7605      /* If we have a variable-sized parameter, we have no choice.  */
7606      return targetm.calls.must_pass_in_stack (mode, type);
7607    }
7608}
7609
7610static bool
7611mips_callee_copies (CUMULATIVE_ARGS *cum ATTRIBUTE_UNUSED,
7612		    enum machine_mode mode ATTRIBUTE_UNUSED,
7613		    tree type ATTRIBUTE_UNUSED, bool named)
7614{
7615  return mips_abi == ABI_EABI && named;
7616}
7617
7618/* Return true if registers of class CLASS cannot change from mode FROM
7619   to mode TO.  */
7620
7621bool
7622mips_cannot_change_mode_class (enum machine_mode from,
7623			       enum machine_mode to, enum reg_class class)
7624{
7625  if (MIN (GET_MODE_SIZE (from), GET_MODE_SIZE (to)) <= UNITS_PER_WORD
7626      && MAX (GET_MODE_SIZE (from), GET_MODE_SIZE (to)) > UNITS_PER_WORD)
7627    {
7628      if (TARGET_BIG_ENDIAN)
7629	{
7630	  /* When a multi-word value is stored in paired floating-point
7631	     registers, the first register always holds the low word.
7632	     We therefore can't allow FPRs to change between single-word
7633	     and multi-word modes.  */
7634	  if (FP_INC > 1 && reg_classes_intersect_p (FP_REGS, class))
7635	    return true;
7636	}
7637      else
7638	{
7639	  /* LO_REGNO == HI_REGNO + 1, so if a multi-word value is stored
7640	     in LO and HI, the high word always comes first.  We therefore
7641	     can't allow values stored in HI to change between single-word
7642	     and multi-word modes.
7643	     This rule applies to both the original HI/LO pair and the new
7644	     DSP accumulators.  */
7645	  if (reg_classes_intersect_p (ACC_REGS, class))
7646	    return true;
7647	}
7648    }
7649  /* Loading a 32-bit value into a 64-bit floating-point register
7650     will not sign-extend the value, despite what LOAD_EXTEND_OP says.
7651     We can't allow 64-bit float registers to change from SImode to
7652     to a wider mode.  */
7653  if (TARGET_FLOAT64
7654      && from == SImode
7655      && GET_MODE_SIZE (to) >= UNITS_PER_WORD
7656      && reg_classes_intersect_p (FP_REGS, class))
7657    return true;
7658  return false;
7659}
7660
7661/* Return true if X should not be moved directly into register $25.
7662   We need this because many versions of GAS will treat "la $25,foo" as
7663   part of a call sequence and so allow a global "foo" to be lazily bound.  */
7664
7665bool
7666mips_dangerous_for_la25_p (rtx x)
7667{
7668  HOST_WIDE_INT offset;
7669
7670  if (TARGET_EXPLICIT_RELOCS)
7671    return false;
7672
7673  mips_split_const (x, &x, &offset);
7674  return global_got_operand (x, VOIDmode);
7675}
7676
7677/* Implement PREFERRED_RELOAD_CLASS.  */
7678
7679enum reg_class
7680mips_preferred_reload_class (rtx x, enum reg_class class)
7681{
7682  if (mips_dangerous_for_la25_p (x) && reg_class_subset_p (LEA_REGS, class))
7683    return LEA_REGS;
7684
7685  if (TARGET_HARD_FLOAT
7686      && FLOAT_MODE_P (GET_MODE (x))
7687      && reg_class_subset_p (FP_REGS, class))
7688    return FP_REGS;
7689
7690  if (reg_class_subset_p (GR_REGS, class))
7691    class = GR_REGS;
7692
7693  if (TARGET_MIPS16 && reg_class_subset_p (M16_REGS, class))
7694    class = M16_REGS;
7695
7696  return class;
7697}
7698
7699/* This function returns the register class required for a secondary
7700   register when copying between one of the registers in CLASS, and X,
7701   using MODE.  If IN_P is nonzero, the copy is going from X to the
7702   register, otherwise the register is the source.  A return value of
7703   NO_REGS means that no secondary register is required.  */
7704
7705enum reg_class
7706mips_secondary_reload_class (enum reg_class class,
7707			     enum machine_mode mode, rtx x, int in_p)
7708{
7709  enum reg_class gr_regs = TARGET_MIPS16 ? M16_REGS : GR_REGS;
7710  int regno = -1;
7711  int gp_reg_p;
7712
7713  if (REG_P (x)|| GET_CODE (x) == SUBREG)
7714    regno = true_regnum (x);
7715
7716  gp_reg_p = TARGET_MIPS16 ? M16_REG_P (regno) : GP_REG_P (regno);
7717
7718  if (mips_dangerous_for_la25_p (x))
7719    {
7720      gr_regs = LEA_REGS;
7721      if (TEST_HARD_REG_BIT (reg_class_contents[(int) class], 25))
7722	return gr_regs;
7723    }
7724
7725  /* Copying from HI or LO to anywhere other than a general register
7726     requires a general register.
7727     This rule applies to both the original HI/LO pair and the new
7728     DSP accumulators.  */
7729  if (reg_class_subset_p (class, ACC_REGS))
7730    {
7731      if (TARGET_MIPS16 && in_p)
7732	{
7733	  /* We can't really copy to HI or LO at all in mips16 mode.  */
7734	  return M16_REGS;
7735	}
7736      return gp_reg_p ? NO_REGS : gr_regs;
7737    }
7738  if (ACC_REG_P (regno))
7739    {
7740      if (TARGET_MIPS16 && ! in_p)
7741	{
7742	  /* We can't really copy to HI or LO at all in mips16 mode.  */
7743	  return M16_REGS;
7744	}
7745      return class == gr_regs ? NO_REGS : gr_regs;
7746    }
7747
7748  /* We can only copy a value to a condition code register from a
7749     floating point register, and even then we require a scratch
7750     floating point register.  We can only copy a value out of a
7751     condition code register into a general register.  */
7752  if (class == ST_REGS)
7753    {
7754      if (in_p)
7755	return FP_REGS;
7756      return gp_reg_p ? NO_REGS : gr_regs;
7757    }
7758  if (ST_REG_P (regno))
7759    {
7760      if (! in_p)
7761	return FP_REGS;
7762      return class == gr_regs ? NO_REGS : gr_regs;
7763    }
7764
7765  if (class == FP_REGS)
7766    {
7767      if (MEM_P (x))
7768	{
7769	  /* In this case we can use lwc1, swc1, ldc1 or sdc1.  */
7770	  return NO_REGS;
7771	}
7772      else if (CONSTANT_P (x) && GET_MODE_CLASS (mode) == MODE_FLOAT)
7773	{
7774	  /* We can use the l.s and l.d macros to load floating-point
7775	     constants.  ??? For l.s, we could probably get better
7776	     code by returning GR_REGS here.  */
7777	  return NO_REGS;
7778	}
7779      else if (gp_reg_p || x == CONST0_RTX (mode))
7780	{
7781	  /* In this case we can use mtc1, mfc1, dmtc1 or dmfc1.  */
7782	  return NO_REGS;
7783	}
7784      else if (FP_REG_P (regno))
7785	{
7786	  /* In this case we can use mov.s or mov.d.  */
7787	  return NO_REGS;
7788	}
7789      else
7790	{
7791	  /* Otherwise, we need to reload through an integer register.  */
7792	  return gr_regs;
7793	}
7794    }
7795
7796  /* In mips16 mode, going between memory and anything but M16_REGS
7797     requires an M16_REG.  */
7798  if (TARGET_MIPS16)
7799    {
7800      if (class != M16_REGS && class != M16_NA_REGS)
7801	{
7802	  if (gp_reg_p)
7803	    return NO_REGS;
7804	  return M16_REGS;
7805	}
7806      if (! gp_reg_p)
7807	{
7808	  if (class == M16_REGS || class == M16_NA_REGS)
7809	    return NO_REGS;
7810	  return M16_REGS;
7811	}
7812    }
7813
7814  return NO_REGS;
7815}
7816
7817/* Implement CLASS_MAX_NREGS.
7818
7819   Usually all registers are word-sized.  The only supported exception
7820   is -mgp64 -msingle-float, which has 64-bit words but 32-bit float
7821   registers.  A word-based calculation is correct even in that case,
7822   since -msingle-float disallows multi-FPR values.
7823
7824   The FP status registers are an exception to this rule.  They are always
7825   4 bytes wide as they only hold condition code modes, and CCmode is always
7826   considered to be 4 bytes wide.  */
7827
7828int
7829mips_class_max_nregs (enum reg_class class ATTRIBUTE_UNUSED,
7830		      enum machine_mode mode)
7831{
7832  if (class == ST_REGS)
7833    return (GET_MODE_SIZE (mode) + 3) / 4;
7834  else
7835    return (GET_MODE_SIZE (mode) + UNITS_PER_WORD - 1) / UNITS_PER_WORD;
7836}
7837
7838static bool
7839mips_valid_pointer_mode (enum machine_mode mode)
7840{
7841  return (mode == SImode || (TARGET_64BIT && mode == DImode));
7842}
7843
7844/* Target hook for vector_mode_supported_p.  */
7845
7846static bool
7847mips_vector_mode_supported_p (enum machine_mode mode)
7848{
7849  switch (mode)
7850    {
7851    case V2SFmode:
7852      return TARGET_PAIRED_SINGLE_FLOAT;
7853
7854    case V2HImode:
7855    case V4QImode:
7856      return TARGET_DSP;
7857
7858    default:
7859      return false;
7860    }
7861}
7862
7863/* If we can access small data directly (using gp-relative relocation
7864   operators) return the small data pointer, otherwise return null.
7865
7866   For each mips16 function which refers to GP relative symbols, we
7867   use a pseudo register, initialized at the start of the function, to
7868   hold the $gp value.  */
7869
7870static rtx
7871mips16_gp_pseudo_reg (void)
7872{
7873  if (cfun->machine->mips16_gp_pseudo_rtx == NULL_RTX)
7874    {
7875      rtx unspec;
7876      rtx insn, scan;
7877
7878      cfun->machine->mips16_gp_pseudo_rtx = gen_reg_rtx (Pmode);
7879
7880      /* We want to initialize this to a value which gcc will believe
7881         is constant.  */
7882      start_sequence ();
7883      unspec = gen_rtx_UNSPEC (VOIDmode, gen_rtvec (1, const0_rtx), UNSPEC_GP);
7884      emit_move_insn (cfun->machine->mips16_gp_pseudo_rtx,
7885		      gen_rtx_CONST (Pmode, unspec));
7886      insn = get_insns ();
7887      end_sequence ();
7888
7889      push_topmost_sequence ();
7890      /* We need to emit the initialization after the FUNCTION_BEG
7891         note, so that it will be integrated.  */
7892      for (scan = get_insns (); scan != NULL_RTX; scan = NEXT_INSN (scan))
7893	if (NOTE_P (scan)
7894	    && NOTE_LINE_NUMBER (scan) == NOTE_INSN_FUNCTION_BEG)
7895	  break;
7896      if (scan == NULL_RTX)
7897	scan = get_insns ();
7898      insn = emit_insn_after (insn, scan);
7899      pop_topmost_sequence ();
7900    }
7901
7902  return cfun->machine->mips16_gp_pseudo_rtx;
7903}
7904
7905/* Write out code to move floating point arguments in or out of
7906   general registers.  Output the instructions to FILE.  FP_CODE is
7907   the code describing which arguments are present (see the comment at
7908   the definition of CUMULATIVE_ARGS in mips.h).  FROM_FP_P is nonzero if
7909   we are copying from the floating point registers.  */
7910
7911static void
7912mips16_fp_args (FILE *file, int fp_code, int from_fp_p)
7913{
7914  const char *s;
7915  int gparg, fparg;
7916  unsigned int f;
7917
7918  /* This code only works for the original 32 bit ABI and the O64 ABI.  */
7919  gcc_assert (TARGET_OLDABI);
7920
7921  if (from_fp_p)
7922    s = "mfc1";
7923  else
7924    s = "mtc1";
7925  gparg = GP_ARG_FIRST;
7926  fparg = FP_ARG_FIRST;
7927  for (f = (unsigned int) fp_code; f != 0; f >>= 2)
7928    {
7929      if ((f & 3) == 1)
7930	{
7931	  if ((fparg & 1) != 0)
7932	    ++fparg;
7933	  fprintf (file, "\t%s\t%s,%s\n", s,
7934		   reg_names[gparg], reg_names[fparg]);
7935	}
7936      else if ((f & 3) == 2)
7937	{
7938	  if (TARGET_64BIT)
7939	    fprintf (file, "\td%s\t%s,%s\n", s,
7940		     reg_names[gparg], reg_names[fparg]);
7941	  else
7942	    {
7943	      if ((fparg & 1) != 0)
7944		++fparg;
7945	      if (TARGET_BIG_ENDIAN)
7946		fprintf (file, "\t%s\t%s,%s\n\t%s\t%s,%s\n", s,
7947			 reg_names[gparg], reg_names[fparg + 1], s,
7948			 reg_names[gparg + 1], reg_names[fparg]);
7949	      else
7950		fprintf (file, "\t%s\t%s,%s\n\t%s\t%s,%s\n", s,
7951			 reg_names[gparg], reg_names[fparg], s,
7952			 reg_names[gparg + 1], reg_names[fparg + 1]);
7953	      ++gparg;
7954	      ++fparg;
7955	    }
7956	}
7957      else
7958	gcc_unreachable ();
7959
7960      ++gparg;
7961      ++fparg;
7962    }
7963}
7964
7965/* Build a mips16 function stub.  This is used for functions which
7966   take arguments in the floating point registers.  It is 32 bit code
7967   that moves the floating point args into the general registers, and
7968   then jumps to the 16 bit code.  */
7969
7970static void
7971build_mips16_function_stub (FILE *file)
7972{
7973  const char *fnname;
7974  char *secname, *stubname;
7975  tree stubid, stubdecl;
7976  int need_comma;
7977  unsigned int f;
7978
7979  fnname = XSTR (XEXP (DECL_RTL (current_function_decl), 0), 0);
7980  secname = (char *) alloca (strlen (fnname) + 20);
7981  sprintf (secname, ".mips16.fn.%s", fnname);
7982  stubname = (char *) alloca (strlen (fnname) + 20);
7983  sprintf (stubname, "__fn_stub_%s", fnname);
7984  stubid = get_identifier (stubname);
7985  stubdecl = build_decl (FUNCTION_DECL, stubid,
7986			 build_function_type (void_type_node, NULL_TREE));
7987  DECL_SECTION_NAME (stubdecl) = build_string (strlen (secname), secname);
7988
7989  fprintf (file, "\t# Stub function for %s (", current_function_name ());
7990  need_comma = 0;
7991  for (f = (unsigned int) current_function_args_info.fp_code; f != 0; f >>= 2)
7992    {
7993      fprintf (file, "%s%s",
7994	       need_comma ? ", " : "",
7995	       (f & 3) == 1 ? "float" : "double");
7996      need_comma = 1;
7997    }
7998  fprintf (file, ")\n");
7999
8000  fprintf (file, "\t.set\tnomips16\n");
8001  switch_to_section (function_section (stubdecl));
8002  ASM_OUTPUT_ALIGN (file, floor_log2 (FUNCTION_BOUNDARY / BITS_PER_UNIT));
8003
8004  /* ??? If FUNCTION_NAME_ALREADY_DECLARED is defined, then we are
8005     within a .ent, and we cannot emit another .ent.  */
8006  if (!FUNCTION_NAME_ALREADY_DECLARED)
8007    {
8008      fputs ("\t.ent\t", file);
8009      assemble_name (file, stubname);
8010      fputs ("\n", file);
8011    }
8012
8013  assemble_name (file, stubname);
8014  fputs (":\n", file);
8015
8016  /* We don't want the assembler to insert any nops here.  */
8017  fprintf (file, "\t.set\tnoreorder\n");
8018
8019  mips16_fp_args (file, current_function_args_info.fp_code, 1);
8020
8021  fprintf (asm_out_file, "\t.set\tnoat\n");
8022  fprintf (asm_out_file, "\tla\t%s,", reg_names[GP_REG_FIRST + 1]);
8023  assemble_name (file, fnname);
8024  fprintf (file, "\n");
8025  fprintf (asm_out_file, "\tjr\t%s\n", reg_names[GP_REG_FIRST + 1]);
8026  fprintf (asm_out_file, "\t.set\tat\n");
8027
8028  /* Unfortunately, we can't fill the jump delay slot.  We can't fill
8029     with one of the mfc1 instructions, because the result is not
8030     available for one instruction, so if the very first instruction
8031     in the function refers to the register, it will see the wrong
8032     value.  */
8033  fprintf (file, "\tnop\n");
8034
8035  fprintf (file, "\t.set\treorder\n");
8036
8037  if (!FUNCTION_NAME_ALREADY_DECLARED)
8038    {
8039      fputs ("\t.end\t", file);
8040      assemble_name (file, stubname);
8041      fputs ("\n", file);
8042    }
8043
8044  fprintf (file, "\t.set\tmips16\n");
8045
8046  switch_to_section (function_section (current_function_decl));
8047}
8048
8049/* We keep a list of functions for which we have already built stubs
8050   in build_mips16_call_stub.  */
8051
8052struct mips16_stub
8053{
8054  struct mips16_stub *next;
8055  char *name;
8056  int fpret;
8057};
8058
8059static struct mips16_stub *mips16_stubs;
8060
8061/* Build a call stub for a mips16 call.  A stub is needed if we are
8062   passing any floating point values which should go into the floating
8063   point registers.  If we are, and the call turns out to be to a 32
8064   bit function, the stub will be used to move the values into the
8065   floating point registers before calling the 32 bit function.  The
8066   linker will magically adjust the function call to either the 16 bit
8067   function or the 32 bit stub, depending upon where the function call
8068   is actually defined.
8069
8070   Similarly, we need a stub if the return value might come back in a
8071   floating point register.
8072
8073   RETVAL is the location of the return value, or null if this is
8074   a call rather than a call_value.  FN is the address of the
8075   function and ARG_SIZE is the size of the arguments.  FP_CODE
8076   is the code built by function_arg.  This function returns a nonzero
8077   value if it builds the call instruction itself.  */
8078
8079int
8080build_mips16_call_stub (rtx retval, rtx fn, rtx arg_size, int fp_code)
8081{
8082  int fpret;
8083  const char *fnname;
8084  char *secname, *stubname;
8085  struct mips16_stub *l;
8086  tree stubid, stubdecl;
8087  int need_comma;
8088  unsigned int f;
8089
8090  /* We don't need to do anything if we aren't in mips16 mode, or if
8091     we were invoked with the -msoft-float option.  */
8092  if (! TARGET_MIPS16 || ! mips16_hard_float)
8093    return 0;
8094
8095  /* Figure out whether the value might come back in a floating point
8096     register.  */
8097  fpret = (retval != 0
8098	   && GET_MODE_CLASS (GET_MODE (retval)) == MODE_FLOAT
8099	   && GET_MODE_SIZE (GET_MODE (retval)) <= UNITS_PER_FPVALUE);
8100
8101  /* We don't need to do anything if there were no floating point
8102     arguments and the value will not be returned in a floating point
8103     register.  */
8104  if (fp_code == 0 && ! fpret)
8105    return 0;
8106
8107  /* We don't need to do anything if this is a call to a special
8108     mips16 support function.  */
8109  if (GET_CODE (fn) == SYMBOL_REF
8110      && strncmp (XSTR (fn, 0), "__mips16_", 9) == 0)
8111    return 0;
8112
8113  /* This code will only work for o32 and o64 abis.  The other ABI's
8114     require more sophisticated support.  */
8115  gcc_assert (TARGET_OLDABI);
8116
8117  /* We can only handle SFmode and DFmode floating point return
8118     values.  */
8119  if (fpret)
8120    gcc_assert (GET_MODE (retval) == SFmode || GET_MODE (retval) == DFmode);
8121
8122  /* If we're calling via a function pointer, then we must always call
8123     via a stub.  There are magic stubs provided in libgcc.a for each
8124     of the required cases.  Each of them expects the function address
8125     to arrive in register $2.  */
8126
8127  if (GET_CODE (fn) != SYMBOL_REF)
8128    {
8129      char buf[30];
8130      tree id;
8131      rtx stub_fn, insn;
8132
8133      /* ??? If this code is modified to support other ABI's, we need
8134         to handle PARALLEL return values here.  */
8135
8136      sprintf (buf, "__mips16_call_stub_%s%d",
8137	       (fpret
8138		? (GET_MODE (retval) == SFmode ? "sf_" : "df_")
8139		: ""),
8140	       fp_code);
8141      id = get_identifier (buf);
8142      stub_fn = gen_rtx_SYMBOL_REF (Pmode, IDENTIFIER_POINTER (id));
8143
8144      emit_move_insn (gen_rtx_REG (Pmode, 2), fn);
8145
8146      if (retval == NULL_RTX)
8147	insn = gen_call_internal (stub_fn, arg_size);
8148      else
8149	insn = gen_call_value_internal (retval, stub_fn, arg_size);
8150      insn = emit_call_insn (insn);
8151
8152      /* Put the register usage information on the CALL.  */
8153      CALL_INSN_FUNCTION_USAGE (insn) =
8154	gen_rtx_EXPR_LIST (VOIDmode,
8155			   gen_rtx_USE (VOIDmode, gen_rtx_REG (Pmode, 2)),
8156			   CALL_INSN_FUNCTION_USAGE (insn));
8157
8158      /* If we are handling a floating point return value, we need to
8159         save $18 in the function prologue.  Putting a note on the
8160         call will mean that regs_ever_live[$18] will be true if the
8161         call is not eliminated, and we can check that in the prologue
8162         code.  */
8163      if (fpret)
8164	CALL_INSN_FUNCTION_USAGE (insn) =
8165	  gen_rtx_EXPR_LIST (VOIDmode,
8166			     gen_rtx_USE (VOIDmode,
8167					  gen_rtx_REG (word_mode, 18)),
8168			     CALL_INSN_FUNCTION_USAGE (insn));
8169
8170      /* Return 1 to tell the caller that we've generated the call
8171         insn.  */
8172      return 1;
8173    }
8174
8175  /* We know the function we are going to call.  If we have already
8176     built a stub, we don't need to do anything further.  */
8177
8178  fnname = XSTR (fn, 0);
8179  for (l = mips16_stubs; l != NULL; l = l->next)
8180    if (strcmp (l->name, fnname) == 0)
8181      break;
8182
8183  if (l == NULL)
8184    {
8185      /* Build a special purpose stub.  When the linker sees a
8186	 function call in mips16 code, it will check where the target
8187	 is defined.  If the target is a 32 bit call, the linker will
8188	 search for the section defined here.  It can tell which
8189	 symbol this section is associated with by looking at the
8190	 relocation information (the name is unreliable, since this
8191	 might be a static function).  If such a section is found, the
8192	 linker will redirect the call to the start of the magic
8193	 section.
8194
8195	 If the function does not return a floating point value, the
8196	 special stub section is named
8197	     .mips16.call.FNNAME
8198
8199	 If the function does return a floating point value, the stub
8200	 section is named
8201	     .mips16.call.fp.FNNAME
8202	 */
8203
8204      secname = (char *) alloca (strlen (fnname) + 40);
8205      sprintf (secname, ".mips16.call.%s%s",
8206	       fpret ? "fp." : "",
8207	       fnname);
8208      stubname = (char *) alloca (strlen (fnname) + 20);
8209      sprintf (stubname, "__call_stub_%s%s",
8210	       fpret ? "fp_" : "",
8211	       fnname);
8212      stubid = get_identifier (stubname);
8213      stubdecl = build_decl (FUNCTION_DECL, stubid,
8214			     build_function_type (void_type_node, NULL_TREE));
8215      DECL_SECTION_NAME (stubdecl) = build_string (strlen (secname), secname);
8216
8217      fprintf (asm_out_file, "\t# Stub function to call %s%s (",
8218	       (fpret
8219		? (GET_MODE (retval) == SFmode ? "float " : "double ")
8220		: ""),
8221	       fnname);
8222      need_comma = 0;
8223      for (f = (unsigned int) fp_code; f != 0; f >>= 2)
8224	{
8225	  fprintf (asm_out_file, "%s%s",
8226		   need_comma ? ", " : "",
8227		   (f & 3) == 1 ? "float" : "double");
8228	  need_comma = 1;
8229	}
8230      fprintf (asm_out_file, ")\n");
8231
8232      fprintf (asm_out_file, "\t.set\tnomips16\n");
8233      assemble_start_function (stubdecl, stubname);
8234
8235      if (!FUNCTION_NAME_ALREADY_DECLARED)
8236	{
8237	  fputs ("\t.ent\t", asm_out_file);
8238	  assemble_name (asm_out_file, stubname);
8239	  fputs ("\n", asm_out_file);
8240
8241	  assemble_name (asm_out_file, stubname);
8242	  fputs (":\n", asm_out_file);
8243	}
8244
8245      /* We build the stub code by hand.  That's the only way we can
8246	 do it, since we can't generate 32 bit code during a 16 bit
8247	 compilation.  */
8248
8249      /* We don't want the assembler to insert any nops here.  */
8250      fprintf (asm_out_file, "\t.set\tnoreorder\n");
8251
8252      mips16_fp_args (asm_out_file, fp_code, 0);
8253
8254      if (! fpret)
8255	{
8256	  fprintf (asm_out_file, "\t.set\tnoat\n");
8257	  fprintf (asm_out_file, "\tla\t%s,%s\n", reg_names[GP_REG_FIRST + 1],
8258		   fnname);
8259	  fprintf (asm_out_file, "\tjr\t%s\n", reg_names[GP_REG_FIRST + 1]);
8260	  fprintf (asm_out_file, "\t.set\tat\n");
8261	  /* Unfortunately, we can't fill the jump delay slot.  We
8262	     can't fill with one of the mtc1 instructions, because the
8263	     result is not available for one instruction, so if the
8264	     very first instruction in the function refers to the
8265	     register, it will see the wrong value.  */
8266	  fprintf (asm_out_file, "\tnop\n");
8267	}
8268      else
8269	{
8270	  fprintf (asm_out_file, "\tmove\t%s,%s\n",
8271		   reg_names[GP_REG_FIRST + 18], reg_names[GP_REG_FIRST + 31]);
8272	  fprintf (asm_out_file, "\tjal\t%s\n", fnname);
8273	  /* As above, we can't fill the delay slot.  */
8274	  fprintf (asm_out_file, "\tnop\n");
8275	  if (GET_MODE (retval) == SFmode)
8276	    fprintf (asm_out_file, "\tmfc1\t%s,%s\n",
8277		     reg_names[GP_REG_FIRST + 2], reg_names[FP_REG_FIRST + 0]);
8278	  else
8279	    {
8280	      if (TARGET_BIG_ENDIAN)
8281		{
8282		  fprintf (asm_out_file, "\tmfc1\t%s,%s\n",
8283			   reg_names[GP_REG_FIRST + 2],
8284			   reg_names[FP_REG_FIRST + 1]);
8285		  fprintf (asm_out_file, "\tmfc1\t%s,%s\n",
8286			   reg_names[GP_REG_FIRST + 3],
8287			   reg_names[FP_REG_FIRST + 0]);
8288		}
8289	      else
8290		{
8291		  fprintf (asm_out_file, "\tmfc1\t%s,%s\n",
8292			   reg_names[GP_REG_FIRST + 2],
8293			   reg_names[FP_REG_FIRST + 0]);
8294		  fprintf (asm_out_file, "\tmfc1\t%s,%s\n",
8295			   reg_names[GP_REG_FIRST + 3],
8296			   reg_names[FP_REG_FIRST + 1]);
8297		}
8298	    }
8299	  fprintf (asm_out_file, "\tj\t%s\n", reg_names[GP_REG_FIRST + 18]);
8300	  /* As above, we can't fill the delay slot.  */
8301	  fprintf (asm_out_file, "\tnop\n");
8302	}
8303
8304      fprintf (asm_out_file, "\t.set\treorder\n");
8305
8306#ifdef ASM_DECLARE_FUNCTION_SIZE
8307      ASM_DECLARE_FUNCTION_SIZE (asm_out_file, stubname, stubdecl);
8308#endif
8309
8310      if (!FUNCTION_NAME_ALREADY_DECLARED)
8311	{
8312	  fputs ("\t.end\t", asm_out_file);
8313	  assemble_name (asm_out_file, stubname);
8314	  fputs ("\n", asm_out_file);
8315	}
8316
8317      fprintf (asm_out_file, "\t.set\tmips16\n");
8318
8319      /* Record this stub.  */
8320      l = (struct mips16_stub *) xmalloc (sizeof *l);
8321      l->name = xstrdup (fnname);
8322      l->fpret = fpret;
8323      l->next = mips16_stubs;
8324      mips16_stubs = l;
8325    }
8326
8327  /* If we expect a floating point return value, but we've built a
8328     stub which does not expect one, then we're in trouble.  We can't
8329     use the existing stub, because it won't handle the floating point
8330     value.  We can't build a new stub, because the linker won't know
8331     which stub to use for the various calls in this object file.
8332     Fortunately, this case is illegal, since it means that a function
8333     was declared in two different ways in a single compilation.  */
8334  if (fpret && ! l->fpret)
8335    error ("cannot handle inconsistent calls to %qs", fnname);
8336
8337  /* If we are calling a stub which handles a floating point return
8338     value, we need to arrange to save $18 in the prologue.  We do
8339     this by marking the function call as using the register.  The
8340     prologue will later see that it is used, and emit code to save
8341     it.  */
8342
8343  if (l->fpret)
8344    {
8345      rtx insn;
8346
8347      if (retval == NULL_RTX)
8348	insn = gen_call_internal (fn, arg_size);
8349      else
8350	insn = gen_call_value_internal (retval, fn, arg_size);
8351      insn = emit_call_insn (insn);
8352
8353      CALL_INSN_FUNCTION_USAGE (insn) =
8354	gen_rtx_EXPR_LIST (VOIDmode,
8355			   gen_rtx_USE (VOIDmode, gen_rtx_REG (word_mode, 18)),
8356			   CALL_INSN_FUNCTION_USAGE (insn));
8357
8358      /* Return 1 to tell the caller that we've generated the call
8359         insn.  */
8360      return 1;
8361    }
8362
8363  /* Return 0 to let the caller generate the call insn.  */
8364  return 0;
8365}
8366
8367/* An entry in the mips16 constant pool.  VALUE is the pool constant,
8368   MODE is its mode, and LABEL is the CODE_LABEL associated with it.  */
8369
8370struct mips16_constant {
8371  struct mips16_constant *next;
8372  rtx value;
8373  rtx label;
8374  enum machine_mode mode;
8375};
8376
8377/* Information about an incomplete mips16 constant pool.  FIRST is the
8378   first constant, HIGHEST_ADDRESS is the highest address that the first
8379   byte of the pool can have, and INSN_ADDRESS is the current instruction
8380   address.  */
8381
8382struct mips16_constant_pool {
8383  struct mips16_constant *first;
8384  int highest_address;
8385  int insn_address;
8386};
8387
8388/* Add constant VALUE to POOL and return its label.  MODE is the
8389   value's mode (used for CONST_INTs, etc.).  */
8390
8391static rtx
8392add_constant (struct mips16_constant_pool *pool,
8393	      rtx value, enum machine_mode mode)
8394{
8395  struct mips16_constant **p, *c;
8396  bool first_of_size_p;
8397
8398  /* See whether the constant is already in the pool.  If so, return the
8399     existing label, otherwise leave P pointing to the place where the
8400     constant should be added.
8401
8402     Keep the pool sorted in increasing order of mode size so that we can
8403     reduce the number of alignments needed.  */
8404  first_of_size_p = true;
8405  for (p = &pool->first; *p != 0; p = &(*p)->next)
8406    {
8407      if (mode == (*p)->mode && rtx_equal_p (value, (*p)->value))
8408	return (*p)->label;
8409      if (GET_MODE_SIZE (mode) < GET_MODE_SIZE ((*p)->mode))
8410	break;
8411      if (GET_MODE_SIZE (mode) == GET_MODE_SIZE ((*p)->mode))
8412	first_of_size_p = false;
8413    }
8414
8415  /* In the worst case, the constant needed by the earliest instruction
8416     will end up at the end of the pool.  The entire pool must then be
8417     accessible from that instruction.
8418
8419     When adding the first constant, set the pool's highest address to
8420     the address of the first out-of-range byte.  Adjust this address
8421     downwards each time a new constant is added.  */
8422  if (pool->first == 0)
8423    /* For pc-relative lw, addiu and daddiu instructions, the base PC value
8424       is the address of the instruction with the lowest two bits clear.
8425       The base PC value for ld has the lowest three bits clear.  Assume
8426       the worst case here.  */
8427    pool->highest_address = pool->insn_address - (UNITS_PER_WORD - 2) + 0x8000;
8428  pool->highest_address -= GET_MODE_SIZE (mode);
8429  if (first_of_size_p)
8430    /* Take into account the worst possible padding due to alignment.  */
8431    pool->highest_address -= GET_MODE_SIZE (mode) - 1;
8432
8433  /* Create a new entry.  */
8434  c = (struct mips16_constant *) xmalloc (sizeof *c);
8435  c->value = value;
8436  c->mode = mode;
8437  c->label = gen_label_rtx ();
8438  c->next = *p;
8439  *p = c;
8440
8441  return c->label;
8442}
8443
8444/* Output constant VALUE after instruction INSN and return the last
8445   instruction emitted.  MODE is the mode of the constant.  */
8446
8447static rtx
8448dump_constants_1 (enum machine_mode mode, rtx value, rtx insn)
8449{
8450  switch (GET_MODE_CLASS (mode))
8451    {
8452    case MODE_INT:
8453      {
8454	rtx size = GEN_INT (GET_MODE_SIZE (mode));
8455	return emit_insn_after (gen_consttable_int (value, size), insn);
8456      }
8457
8458    case MODE_FLOAT:
8459      return emit_insn_after (gen_consttable_float (value), insn);
8460
8461    case MODE_VECTOR_FLOAT:
8462    case MODE_VECTOR_INT:
8463      {
8464	int i;
8465	for (i = 0; i < CONST_VECTOR_NUNITS (value); i++)
8466	  insn = dump_constants_1 (GET_MODE_INNER (mode),
8467				   CONST_VECTOR_ELT (value, i), insn);
8468	return insn;
8469      }
8470
8471    default:
8472      gcc_unreachable ();
8473    }
8474}
8475
8476
8477/* Dump out the constants in CONSTANTS after INSN.  */
8478
8479static void
8480dump_constants (struct mips16_constant *constants, rtx insn)
8481{
8482  struct mips16_constant *c, *next;
8483  int align;
8484
8485  align = 0;
8486  for (c = constants; c != NULL; c = next)
8487    {
8488      /* If necessary, increase the alignment of PC.  */
8489      if (align < GET_MODE_SIZE (c->mode))
8490	{
8491	  int align_log = floor_log2 (GET_MODE_SIZE (c->mode));
8492	  insn = emit_insn_after (gen_align (GEN_INT (align_log)), insn);
8493	}
8494      align = GET_MODE_SIZE (c->mode);
8495
8496      insn = emit_label_after (c->label, insn);
8497      insn = dump_constants_1 (c->mode, c->value, insn);
8498
8499      next = c->next;
8500      free (c);
8501    }
8502
8503  emit_barrier_after (insn);
8504}
8505
8506/* Return the length of instruction INSN.  */
8507
8508static int
8509mips16_insn_length (rtx insn)
8510{
8511  if (JUMP_P (insn))
8512    {
8513      rtx body = PATTERN (insn);
8514      if (GET_CODE (body) == ADDR_VEC)
8515	return GET_MODE_SIZE (GET_MODE (body)) * XVECLEN (body, 0);
8516      if (GET_CODE (body) == ADDR_DIFF_VEC)
8517	return GET_MODE_SIZE (GET_MODE (body)) * XVECLEN (body, 1);
8518    }
8519  return get_attr_length (insn);
8520}
8521
8522/* Rewrite *X so that constant pool references refer to the constant's
8523   label instead.  DATA points to the constant pool structure.  */
8524
8525static int
8526mips16_rewrite_pool_refs (rtx *x, void *data)
8527{
8528  struct mips16_constant_pool *pool = data;
8529  if (GET_CODE (*x) == SYMBOL_REF && CONSTANT_POOL_ADDRESS_P (*x))
8530    *x = gen_rtx_LABEL_REF (Pmode, add_constant (pool,
8531						 get_pool_constant (*x),
8532						 get_pool_mode (*x)));
8533  return 0;
8534}
8535
8536/* Build MIPS16 constant pools.  */
8537
8538static void
8539mips16_lay_out_constants (void)
8540{
8541  struct mips16_constant_pool pool;
8542  rtx insn, barrier;
8543
8544  barrier = 0;
8545  memset (&pool, 0, sizeof (pool));
8546  for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
8547    {
8548      /* Rewrite constant pool references in INSN.  */
8549      if (INSN_P (insn))
8550	for_each_rtx (&PATTERN (insn), mips16_rewrite_pool_refs, &pool);
8551
8552      pool.insn_address += mips16_insn_length (insn);
8553
8554      if (pool.first != NULL)
8555	{
8556	  /* If there are no natural barriers between the first user of
8557	     the pool and the highest acceptable address, we'll need to
8558	     create a new instruction to jump around the constant pool.
8559	     In the worst case, this instruction will be 4 bytes long.
8560
8561	     If it's too late to do this transformation after INSN,
8562	     do it immediately before INSN.  */
8563	  if (barrier == 0 && pool.insn_address + 4 > pool.highest_address)
8564	    {
8565	      rtx label, jump;
8566
8567	      label = gen_label_rtx ();
8568
8569	      jump = emit_jump_insn_before (gen_jump (label), insn);
8570	      JUMP_LABEL (jump) = label;
8571	      LABEL_NUSES (label) = 1;
8572	      barrier = emit_barrier_after (jump);
8573
8574	      emit_label_after (label, barrier);
8575	      pool.insn_address += 4;
8576	    }
8577
8578	  /* See whether the constant pool is now out of range of the first
8579	     user.  If so, output the constants after the previous barrier.
8580	     Note that any instructions between BARRIER and INSN (inclusive)
8581	     will use negative offsets to refer to the pool.  */
8582	  if (pool.insn_address > pool.highest_address)
8583	    {
8584	      dump_constants (pool.first, barrier);
8585	      pool.first = NULL;
8586	      barrier = 0;
8587	    }
8588	  else if (BARRIER_P (insn))
8589	    barrier = insn;
8590	}
8591    }
8592  dump_constants (pool.first, get_last_insn ());
8593}
8594
8595/* A temporary variable used by for_each_rtx callbacks, etc.  */
8596static rtx mips_sim_insn;
8597
8598/* A structure representing the state of the processor pipeline.
8599   Used by the mips_sim_* family of functions.  */
8600struct mips_sim {
8601  /* The maximum number of instructions that can be issued in a cycle.
8602     (Caches mips_issue_rate.)  */
8603  unsigned int issue_rate;
8604
8605  /* The current simulation time.  */
8606  unsigned int time;
8607
8608  /* How many more instructions can be issued in the current cycle.  */
8609  unsigned int insns_left;
8610
8611  /* LAST_SET[X].INSN is the last instruction to set register X.
8612     LAST_SET[X].TIME is the time at which that instruction was issued.
8613     INSN is null if no instruction has yet set register X.  */
8614  struct {
8615    rtx insn;
8616    unsigned int time;
8617  } last_set[FIRST_PSEUDO_REGISTER];
8618
8619  /* The pipeline's current DFA state.  */
8620  state_t dfa_state;
8621};
8622
8623/* Reset STATE to the initial simulation state.  */
8624
8625static void
8626mips_sim_reset (struct mips_sim *state)
8627{
8628  state->time = 0;
8629  state->insns_left = state->issue_rate;
8630  memset (&state->last_set, 0, sizeof (state->last_set));
8631  state_reset (state->dfa_state);
8632}
8633
8634/* Initialize STATE before its first use.  DFA_STATE points to an
8635   allocated but uninitialized DFA state.  */
8636
8637static void
8638mips_sim_init (struct mips_sim *state, state_t dfa_state)
8639{
8640  state->issue_rate = mips_issue_rate ();
8641  state->dfa_state = dfa_state;
8642  mips_sim_reset (state);
8643}
8644
8645/* Advance STATE by one clock cycle.  */
8646
8647static void
8648mips_sim_next_cycle (struct mips_sim *state)
8649{
8650  state->time++;
8651  state->insns_left = state->issue_rate;
8652  state_transition (state->dfa_state, 0);
8653}
8654
8655/* Advance simulation state STATE until instruction INSN can read
8656   register REG.  */
8657
8658static void
8659mips_sim_wait_reg (struct mips_sim *state, rtx insn, rtx reg)
8660{
8661  unsigned int i;
8662
8663  for (i = 0; i < HARD_REGNO_NREGS (REGNO (reg), GET_MODE (reg)); i++)
8664    if (state->last_set[REGNO (reg) + i].insn != 0)
8665      {
8666	unsigned int t;
8667
8668	t = state->last_set[REGNO (reg) + i].time;
8669	t += insn_latency (state->last_set[REGNO (reg) + i].insn, insn);
8670	while (state->time < t)
8671	  mips_sim_next_cycle (state);
8672    }
8673}
8674
8675/* A for_each_rtx callback.  If *X is a register, advance simulation state
8676   DATA until mips_sim_insn can read the register's value.  */
8677
8678static int
8679mips_sim_wait_regs_2 (rtx *x, void *data)
8680{
8681  if (REG_P (*x))
8682    mips_sim_wait_reg (data, mips_sim_insn, *x);
8683  return 0;
8684}
8685
8686/* Call mips_sim_wait_regs_2 (R, DATA) for each register R mentioned in *X.  */
8687
8688static void
8689mips_sim_wait_regs_1 (rtx *x, void *data)
8690{
8691  for_each_rtx (x, mips_sim_wait_regs_2, data);
8692}
8693
8694/* Advance simulation state STATE until all of INSN's register
8695   dependencies are satisfied.  */
8696
8697static void
8698mips_sim_wait_regs (struct mips_sim *state, rtx insn)
8699{
8700  mips_sim_insn = insn;
8701  note_uses (&PATTERN (insn), mips_sim_wait_regs_1, state);
8702}
8703
8704/* Advance simulation state STATE until the units required by
8705   instruction INSN are available.  */
8706
8707static void
8708mips_sim_wait_units (struct mips_sim *state, rtx insn)
8709{
8710  state_t tmp_state;
8711
8712  tmp_state = alloca (state_size ());
8713  while (state->insns_left == 0
8714	 || (memcpy (tmp_state, state->dfa_state, state_size ()),
8715	     state_transition (tmp_state, insn) >= 0))
8716    mips_sim_next_cycle (state);
8717}
8718
8719/* Advance simulation state STATE until INSN is ready to issue.  */
8720
8721static void
8722mips_sim_wait_insn (struct mips_sim *state, rtx insn)
8723{
8724  mips_sim_wait_regs (state, insn);
8725  mips_sim_wait_units (state, insn);
8726}
8727
8728/* mips_sim_insn has just set X.  Update the LAST_SET array
8729   in simulation state DATA.  */
8730
8731static void
8732mips_sim_record_set (rtx x, rtx pat ATTRIBUTE_UNUSED, void *data)
8733{
8734  struct mips_sim *state;
8735  unsigned int i;
8736
8737  state = data;
8738  if (REG_P (x))
8739    for (i = 0; i < HARD_REGNO_NREGS (REGNO (x), GET_MODE (x)); i++)
8740      {
8741	state->last_set[REGNO (x) + i].insn = mips_sim_insn;
8742	state->last_set[REGNO (x) + i].time = state->time;
8743      }
8744}
8745
8746/* Issue instruction INSN in scheduler state STATE.  Assume that INSN
8747   can issue immediately (i.e., that mips_sim_wait_insn has already
8748   been called).  */
8749
8750static void
8751mips_sim_issue_insn (struct mips_sim *state, rtx insn)
8752{
8753  state_transition (state->dfa_state, insn);
8754  state->insns_left--;
8755
8756  mips_sim_insn = insn;
8757  note_stores (PATTERN (insn), mips_sim_record_set, state);
8758}
8759
8760/* Simulate issuing a NOP in state STATE.  */
8761
8762static void
8763mips_sim_issue_nop (struct mips_sim *state)
8764{
8765  if (state->insns_left == 0)
8766    mips_sim_next_cycle (state);
8767  state->insns_left--;
8768}
8769
8770/* Update simulation state STATE so that it's ready to accept the instruction
8771   after INSN.  INSN should be part of the main rtl chain, not a member of a
8772   SEQUENCE.  */
8773
8774static void
8775mips_sim_finish_insn (struct mips_sim *state, rtx insn)
8776{
8777  /* If INSN is a jump with an implicit delay slot, simulate a nop.  */
8778  if (JUMP_P (insn))
8779    mips_sim_issue_nop (state);
8780
8781  switch (GET_CODE (SEQ_BEGIN (insn)))
8782    {
8783    case CODE_LABEL:
8784    case CALL_INSN:
8785      /* We can't predict the processor state after a call or label.  */
8786      mips_sim_reset (state);
8787      break;
8788
8789    case JUMP_INSN:
8790      /* The delay slots of branch likely instructions are only executed
8791	 when the branch is taken.  Therefore, if the caller has simulated
8792	 the delay slot instruction, STATE does not really reflect the state
8793	 of the pipeline for the instruction after the delay slot.  Also,
8794	 branch likely instructions tend to incur a penalty when not taken,
8795	 so there will probably be an extra delay between the branch and
8796	 the instruction after the delay slot.  */
8797      if (INSN_ANNULLED_BRANCH_P (SEQ_BEGIN (insn)))
8798	mips_sim_reset (state);
8799      break;
8800
8801    default:
8802      break;
8803    }
8804}
8805
8806/* The VR4130 pipeline issues aligned pairs of instructions together,
8807   but it stalls the second instruction if it depends on the first.
8808   In order to cut down the amount of logic required, this dependence
8809   check is not based on a full instruction decode.  Instead, any non-SPECIAL
8810   instruction is assumed to modify the register specified by bits 20-16
8811   (which is usually the "rt" field).
8812
8813   In beq, beql, bne and bnel instructions, the rt field is actually an
8814   input, so we can end up with a false dependence between the branch
8815   and its delay slot.  If this situation occurs in instruction INSN,
8816   try to avoid it by swapping rs and rt.  */
8817
8818static void
8819vr4130_avoid_branch_rt_conflict (rtx insn)
8820{
8821  rtx first, second;
8822
8823  first = SEQ_BEGIN (insn);
8824  second = SEQ_END (insn);
8825  if (JUMP_P (first)
8826      && NONJUMP_INSN_P (second)
8827      && GET_CODE (PATTERN (first)) == SET
8828      && GET_CODE (SET_DEST (PATTERN (first))) == PC
8829      && GET_CODE (SET_SRC (PATTERN (first))) == IF_THEN_ELSE)
8830    {
8831      /* Check for the right kind of condition.  */
8832      rtx cond = XEXP (SET_SRC (PATTERN (first)), 0);
8833      if ((GET_CODE (cond) == EQ || GET_CODE (cond) == NE)
8834	  && REG_P (XEXP (cond, 0))
8835	  && REG_P (XEXP (cond, 1))
8836	  && reg_referenced_p (XEXP (cond, 1), PATTERN (second))
8837	  && !reg_referenced_p (XEXP (cond, 0), PATTERN (second)))
8838	{
8839	  /* SECOND mentions the rt register but not the rs register.  */
8840	  rtx tmp = XEXP (cond, 0);
8841	  XEXP (cond, 0) = XEXP (cond, 1);
8842	  XEXP (cond, 1) = tmp;
8843	}
8844    }
8845}
8846
8847/* Implement -mvr4130-align.  Go through each basic block and simulate the
8848   processor pipeline.  If we find that a pair of instructions could execute
8849   in parallel, and the first of those instruction is not 8-byte aligned,
8850   insert a nop to make it aligned.  */
8851
8852static void
8853vr4130_align_insns (void)
8854{
8855  struct mips_sim state;
8856  rtx insn, subinsn, last, last2, next;
8857  bool aligned_p;
8858
8859  dfa_start ();
8860
8861  /* LAST is the last instruction before INSN to have a nonzero length.
8862     LAST2 is the last such instruction before LAST.  */
8863  last = 0;
8864  last2 = 0;
8865
8866  /* ALIGNED_P is true if INSN is known to be at an aligned address.  */
8867  aligned_p = true;
8868
8869  mips_sim_init (&state, alloca (state_size ()));
8870  for (insn = get_insns (); insn != 0; insn = next)
8871    {
8872      unsigned int length;
8873
8874      next = NEXT_INSN (insn);
8875
8876      /* See the comment above vr4130_avoid_branch_rt_conflict for details.
8877	 This isn't really related to the alignment pass, but we do it on
8878	 the fly to avoid a separate instruction walk.  */
8879      vr4130_avoid_branch_rt_conflict (insn);
8880
8881      if (USEFUL_INSN_P (insn))
8882	FOR_EACH_SUBINSN (subinsn, insn)
8883	  {
8884	    mips_sim_wait_insn (&state, subinsn);
8885
8886	    /* If we want this instruction to issue in parallel with the
8887	       previous one, make sure that the previous instruction is
8888	       aligned.  There are several reasons why this isn't worthwhile
8889	       when the second instruction is a call:
8890
8891	          - Calls are less likely to be performance critical,
8892		  - There's a good chance that the delay slot can execute
8893		    in parallel with the call.
8894	          - The return address would then be unaligned.
8895
8896	       In general, if we're going to insert a nop between instructions
8897	       X and Y, it's better to insert it immediately after X.  That
8898	       way, if the nop makes Y aligned, it will also align any labels
8899	       between X and Y.  */
8900	    if (state.insns_left != state.issue_rate
8901		&& !CALL_P (subinsn))
8902	      {
8903		if (subinsn == SEQ_BEGIN (insn) && aligned_p)
8904		  {
8905		    /* SUBINSN is the first instruction in INSN and INSN is
8906		       aligned.  We want to align the previous instruction
8907		       instead, so insert a nop between LAST2 and LAST.
8908
8909		       Note that LAST could be either a single instruction
8910		       or a branch with a delay slot.  In the latter case,
8911		       LAST, like INSN, is already aligned, but the delay
8912		       slot must have some extra delay that stops it from
8913		       issuing at the same time as the branch.  We therefore
8914		       insert a nop before the branch in order to align its
8915		       delay slot.  */
8916		    emit_insn_after (gen_nop (), last2);
8917		    aligned_p = false;
8918		  }
8919		else if (subinsn != SEQ_BEGIN (insn) && !aligned_p)
8920		  {
8921		    /* SUBINSN is the delay slot of INSN, but INSN is
8922		       currently unaligned.  Insert a nop between
8923		       LAST and INSN to align it.  */
8924		    emit_insn_after (gen_nop (), last);
8925		    aligned_p = true;
8926		  }
8927	      }
8928	    mips_sim_issue_insn (&state, subinsn);
8929	  }
8930      mips_sim_finish_insn (&state, insn);
8931
8932      /* Update LAST, LAST2 and ALIGNED_P for the next instruction.  */
8933      length = get_attr_length (insn);
8934      if (length > 0)
8935	{
8936	  /* If the instruction is an asm statement or multi-instruction
8937	     mips.md patern, the length is only an estimate.  Insert an
8938	     8 byte alignment after it so that the following instructions
8939	     can be handled correctly.  */
8940	  if (NONJUMP_INSN_P (SEQ_BEGIN (insn))
8941	      && (recog_memoized (insn) < 0 || length >= 8))
8942	    {
8943	      next = emit_insn_after (gen_align (GEN_INT (3)), insn);
8944	      next = NEXT_INSN (next);
8945	      mips_sim_next_cycle (&state);
8946	      aligned_p = true;
8947	    }
8948	  else if (length & 4)
8949	    aligned_p = !aligned_p;
8950	  last2 = last;
8951	  last = insn;
8952	}
8953
8954      /* See whether INSN is an aligned label.  */
8955      if (LABEL_P (insn) && label_to_alignment (insn) >= 3)
8956	aligned_p = true;
8957    }
8958  dfa_finish ();
8959}
8960
8961/* Subroutine of mips_reorg.  If there is a hazard between INSN
8962   and a previous instruction, avoid it by inserting nops after
8963   instruction AFTER.
8964
8965   *DELAYED_REG and *HILO_DELAY describe the hazards that apply at
8966   this point.  If *DELAYED_REG is non-null, INSN must wait a cycle
8967   before using the value of that register.  *HILO_DELAY counts the
8968   number of instructions since the last hilo hazard (that is,
8969   the number of instructions since the last mflo or mfhi).
8970
8971   After inserting nops for INSN, update *DELAYED_REG and *HILO_DELAY
8972   for the next instruction.
8973
8974   LO_REG is an rtx for the LO register, used in dependence checking.  */
8975
8976static void
8977mips_avoid_hazard (rtx after, rtx insn, int *hilo_delay,
8978		   rtx *delayed_reg, rtx lo_reg)
8979{
8980  rtx pattern, set;
8981  int nops, ninsns;
8982
8983  if (!INSN_P (insn))
8984    return;
8985
8986  pattern = PATTERN (insn);
8987
8988  /* Do not put the whole function in .set noreorder if it contains
8989     an asm statement.  We don't know whether there will be hazards
8990     between the asm statement and the gcc-generated code.  */
8991  if (GET_CODE (pattern) == ASM_INPUT || asm_noperands (pattern) >= 0)
8992    cfun->machine->all_noreorder_p = false;
8993
8994  /* Ignore zero-length instructions (barriers and the like).  */
8995  ninsns = get_attr_length (insn) / 4;
8996  if (ninsns == 0)
8997    return;
8998
8999  /* Work out how many nops are needed.  Note that we only care about
9000     registers that are explicitly mentioned in the instruction's pattern.
9001     It doesn't matter that calls use the argument registers or that they
9002     clobber hi and lo.  */
9003  if (*hilo_delay < 2 && reg_set_p (lo_reg, pattern))
9004    nops = 2 - *hilo_delay;
9005  else if (*delayed_reg != 0 && reg_referenced_p (*delayed_reg, pattern))
9006    nops = 1;
9007  else
9008    nops = 0;
9009
9010  /* Insert the nops between this instruction and the previous one.
9011     Each new nop takes us further from the last hilo hazard.  */
9012  *hilo_delay += nops;
9013  while (nops-- > 0)
9014    emit_insn_after (gen_hazard_nop (), after);
9015
9016  /* Set up the state for the next instruction.  */
9017  *hilo_delay += ninsns;
9018  *delayed_reg = 0;
9019  if (INSN_CODE (insn) >= 0)
9020    switch (get_attr_hazard (insn))
9021      {
9022      case HAZARD_NONE:
9023	break;
9024
9025      case HAZARD_HILO:
9026	*hilo_delay = 0;
9027	break;
9028
9029      case HAZARD_DELAY:
9030	set = single_set (insn);
9031	gcc_assert (set != 0);
9032	*delayed_reg = SET_DEST (set);
9033	break;
9034      }
9035}
9036
9037
9038/* Go through the instruction stream and insert nops where necessary.
9039   See if the whole function can then be put into .set noreorder &
9040   .set nomacro.  */
9041
9042static void
9043mips_avoid_hazards (void)
9044{
9045  rtx insn, last_insn, lo_reg, delayed_reg;
9046  int hilo_delay, i;
9047
9048  /* Force all instructions to be split into their final form.  */
9049  split_all_insns_noflow ();
9050
9051  /* Recalculate instruction lengths without taking nops into account.  */
9052  cfun->machine->ignore_hazard_length_p = true;
9053  shorten_branches (get_insns ());
9054
9055  cfun->machine->all_noreorder_p = true;
9056
9057  /* Profiled functions can't be all noreorder because the profiler
9058     support uses assembler macros.  */
9059  if (current_function_profile)
9060    cfun->machine->all_noreorder_p = false;
9061
9062  /* Code compiled with -mfix-vr4120 can't be all noreorder because
9063     we rely on the assembler to work around some errata.  */
9064  if (TARGET_FIX_VR4120)
9065    cfun->machine->all_noreorder_p = false;
9066
9067  /* The same is true for -mfix-vr4130 if we might generate mflo or
9068     mfhi instructions.  Note that we avoid using mflo and mfhi if
9069     the VR4130 macc and dmacc instructions are available instead;
9070     see the *mfhilo_{si,di}_macc patterns.  */
9071  if (TARGET_FIX_VR4130 && !ISA_HAS_MACCHI)
9072    cfun->machine->all_noreorder_p = false;
9073
9074  last_insn = 0;
9075  hilo_delay = 2;
9076  delayed_reg = 0;
9077  lo_reg = gen_rtx_REG (SImode, LO_REGNUM);
9078
9079  for (insn = get_insns (); insn != 0; insn = NEXT_INSN (insn))
9080    if (INSN_P (insn))
9081      {
9082	if (GET_CODE (PATTERN (insn)) == SEQUENCE)
9083	  for (i = 0; i < XVECLEN (PATTERN (insn), 0); i++)
9084	    mips_avoid_hazard (last_insn, XVECEXP (PATTERN (insn), 0, i),
9085			       &hilo_delay, &delayed_reg, lo_reg);
9086	else
9087	  mips_avoid_hazard (last_insn, insn, &hilo_delay,
9088			     &delayed_reg, lo_reg);
9089
9090	last_insn = insn;
9091      }
9092}
9093
9094
9095/* Implement TARGET_MACHINE_DEPENDENT_REORG.  */
9096
9097static void
9098mips_reorg (void)
9099{
9100  if (TARGET_MIPS16)
9101    mips16_lay_out_constants ();
9102  else if (TARGET_EXPLICIT_RELOCS)
9103    {
9104      if (mips_flag_delayed_branch)
9105	dbr_schedule (get_insns ());
9106      mips_avoid_hazards ();
9107      if (TUNE_MIPS4130 && TARGET_VR4130_ALIGN)
9108	vr4130_align_insns ();
9109    }
9110}
9111
9112/* This function does three things:
9113
9114   - Register the special divsi3 and modsi3 functions if -mfix-vr4120.
9115   - Register the mips16 hardware floating point stubs.
9116   - Register the gofast functions if selected using --enable-gofast.  */
9117
9118#include "config/gofast.h"
9119
9120static void
9121mips_init_libfuncs (void)
9122{
9123  if (TARGET_FIX_VR4120)
9124    {
9125      set_optab_libfunc (sdiv_optab, SImode, "__vr4120_divsi3");
9126      set_optab_libfunc (smod_optab, SImode, "__vr4120_modsi3");
9127    }
9128
9129  if (TARGET_MIPS16 && mips16_hard_float)
9130    {
9131      set_optab_libfunc (add_optab, SFmode, "__mips16_addsf3");
9132      set_optab_libfunc (sub_optab, SFmode, "__mips16_subsf3");
9133      set_optab_libfunc (smul_optab, SFmode, "__mips16_mulsf3");
9134      set_optab_libfunc (sdiv_optab, SFmode, "__mips16_divsf3");
9135
9136      set_optab_libfunc (eq_optab, SFmode, "__mips16_eqsf2");
9137      set_optab_libfunc (ne_optab, SFmode, "__mips16_nesf2");
9138      set_optab_libfunc (gt_optab, SFmode, "__mips16_gtsf2");
9139      set_optab_libfunc (ge_optab, SFmode, "__mips16_gesf2");
9140      set_optab_libfunc (lt_optab, SFmode, "__mips16_ltsf2");
9141      set_optab_libfunc (le_optab, SFmode, "__mips16_lesf2");
9142
9143      set_conv_libfunc (sfix_optab, SImode, SFmode, "__mips16_fix_truncsfsi");
9144      set_conv_libfunc (sfloat_optab, SFmode, SImode, "__mips16_floatsisf");
9145
9146      if (TARGET_DOUBLE_FLOAT)
9147	{
9148	  set_optab_libfunc (add_optab, DFmode, "__mips16_adddf3");
9149	  set_optab_libfunc (sub_optab, DFmode, "__mips16_subdf3");
9150	  set_optab_libfunc (smul_optab, DFmode, "__mips16_muldf3");
9151	  set_optab_libfunc (sdiv_optab, DFmode, "__mips16_divdf3");
9152
9153	  set_optab_libfunc (eq_optab, DFmode, "__mips16_eqdf2");
9154	  set_optab_libfunc (ne_optab, DFmode, "__mips16_nedf2");
9155	  set_optab_libfunc (gt_optab, DFmode, "__mips16_gtdf2");
9156	  set_optab_libfunc (ge_optab, DFmode, "__mips16_gedf2");
9157	  set_optab_libfunc (lt_optab, DFmode, "__mips16_ltdf2");
9158	  set_optab_libfunc (le_optab, DFmode, "__mips16_ledf2");
9159
9160	  set_conv_libfunc (sext_optab, DFmode, SFmode, "__mips16_extendsfdf2");
9161	  set_conv_libfunc (trunc_optab, SFmode, DFmode, "__mips16_truncdfsf2");
9162
9163	  set_conv_libfunc (sfix_optab, SImode, DFmode, "__mips16_fix_truncdfsi");
9164	  set_conv_libfunc (sfloat_optab, DFmode, SImode, "__mips16_floatsidf");
9165	}
9166    }
9167  else
9168    gofast_maybe_init_libfuncs ();
9169}
9170
9171/* Return a number assessing the cost of moving a register in class
9172   FROM to class TO.  The classes are expressed using the enumeration
9173   values such as `GENERAL_REGS'.  A value of 2 is the default; other
9174   values are interpreted relative to that.
9175
9176   It is not required that the cost always equal 2 when FROM is the
9177   same as TO; on some machines it is expensive to move between
9178   registers if they are not general registers.
9179
9180   If reload sees an insn consisting of a single `set' between two
9181   hard registers, and if `REGISTER_MOVE_COST' applied to their
9182   classes returns a value of 2, reload does not check to ensure that
9183   the constraints of the insn are met.  Setting a cost of other than
9184   2 will allow reload to verify that the constraints are met.  You
9185   should do this if the `movM' pattern's constraints do not allow
9186   such copying.
9187
9188   ??? We make the cost of moving from HI/LO into general
9189   registers the same as for one of moving general registers to
9190   HI/LO for TARGET_MIPS16 in order to prevent allocating a
9191   pseudo to HI/LO.  This might hurt optimizations though, it
9192   isn't clear if it is wise.  And it might not work in all cases.  We
9193   could solve the DImode LO reg problem by using a multiply, just
9194   like reload_{in,out}si.  We could solve the SImode/HImode HI reg
9195   problem by using divide instructions.  divu puts the remainder in
9196   the HI reg, so doing a divide by -1 will move the value in the HI
9197   reg for all values except -1.  We could handle that case by using a
9198   signed divide, e.g.  -1 / 2 (or maybe 1 / -2?).  We'd have to emit
9199   a compare/branch to test the input value to see which instruction
9200   we need to use.  This gets pretty messy, but it is feasible.  */
9201
9202int
9203mips_register_move_cost (enum machine_mode mode ATTRIBUTE_UNUSED,
9204			 enum reg_class to, enum reg_class from)
9205{
9206  if (from == M16_REGS && GR_REG_CLASS_P (to))
9207    return 2;
9208  else if (from == M16_NA_REGS && GR_REG_CLASS_P (to))
9209    return 2;
9210  else if (GR_REG_CLASS_P (from))
9211    {
9212      if (to == M16_REGS)
9213	return 2;
9214      else if (to == M16_NA_REGS)
9215	return 2;
9216      else if (GR_REG_CLASS_P (to))
9217	{
9218	  if (TARGET_MIPS16)
9219	    return 4;
9220	  else
9221	    return 2;
9222	}
9223      else if (to == FP_REGS)
9224	return 4;
9225      else if (reg_class_subset_p (to, ACC_REGS))
9226	{
9227	  if (TARGET_MIPS16)
9228	    return 12;
9229	  else
9230	    return 6;
9231	}
9232      else if (COP_REG_CLASS_P (to))
9233	{
9234	  return 5;
9235	}
9236    }
9237  else if (from == FP_REGS)
9238    {
9239      if (GR_REG_CLASS_P (to))
9240	return 4;
9241      else if (to == FP_REGS)
9242	return 2;
9243      else if (to == ST_REGS)
9244	return 8;
9245    }
9246  else if (reg_class_subset_p (from, ACC_REGS))
9247    {
9248      if (GR_REG_CLASS_P (to))
9249	{
9250	  if (TARGET_MIPS16)
9251	    return 12;
9252	  else
9253	    return 6;
9254	}
9255    }
9256  else if (from == ST_REGS && GR_REG_CLASS_P (to))
9257    return 4;
9258  else if (COP_REG_CLASS_P (from))
9259    {
9260      return 5;
9261    }
9262
9263  /* Fall through.
9264     ??? What cases are these? Shouldn't we return 2 here?  */
9265
9266  return 12;
9267}
9268
9269/* Return the length of INSN.  LENGTH is the initial length computed by
9270   attributes in the machine-description file.  */
9271
9272int
9273mips_adjust_insn_length (rtx insn, int length)
9274{
9275  /* A unconditional jump has an unfilled delay slot if it is not part
9276     of a sequence.  A conditional jump normally has a delay slot, but
9277     does not on MIPS16.  */
9278  if (CALL_P (insn) || (TARGET_MIPS16 ? simplejump_p (insn) : JUMP_P (insn)))
9279    length += 4;
9280
9281  /* See how many nops might be needed to avoid hardware hazards.  */
9282  if (!cfun->machine->ignore_hazard_length_p && INSN_CODE (insn) >= 0)
9283    switch (get_attr_hazard (insn))
9284      {
9285      case HAZARD_NONE:
9286	break;
9287
9288      case HAZARD_DELAY:
9289	length += 4;
9290	break;
9291
9292      case HAZARD_HILO:
9293	length += 8;
9294	break;
9295      }
9296
9297  /* All MIPS16 instructions are a measly two bytes.  */
9298  if (TARGET_MIPS16)
9299    length /= 2;
9300
9301  return length;
9302}
9303
9304
9305/* Return an asm sequence to start a noat block and load the address
9306   of a label into $1.  */
9307
9308const char *
9309mips_output_load_label (void)
9310{
9311  if (TARGET_EXPLICIT_RELOCS)
9312    switch (mips_abi)
9313      {
9314      case ABI_N32:
9315	return "%[lw\t%@,%%got_page(%0)(%+)\n\taddiu\t%@,%@,%%got_ofst(%0)";
9316
9317      case ABI_64:
9318	return "%[ld\t%@,%%got_page(%0)(%+)\n\tdaddiu\t%@,%@,%%got_ofst(%0)";
9319
9320      default:
9321	if (ISA_HAS_LOAD_DELAY)
9322	  return "%[lw\t%@,%%got(%0)(%+)%#\n\taddiu\t%@,%@,%%lo(%0)";
9323	return "%[lw\t%@,%%got(%0)(%+)\n\taddiu\t%@,%@,%%lo(%0)";
9324      }
9325  else
9326    {
9327      if (Pmode == DImode)
9328	return "%[dla\t%@,%0";
9329      else
9330	return "%[la\t%@,%0";
9331    }
9332}
9333
9334/* Return the assembly code for INSN, which has the operands given by
9335   OPERANDS, and which branches to OPERANDS[1] if some condition is true.
9336   BRANCH_IF_TRUE is the asm template that should be used if OPERANDS[1]
9337   is in range of a direct branch.  BRANCH_IF_FALSE is an inverted
9338   version of BRANCH_IF_TRUE.  */
9339
9340const char *
9341mips_output_conditional_branch (rtx insn, rtx *operands,
9342				const char *branch_if_true,
9343				const char *branch_if_false)
9344{
9345  unsigned int length;
9346  rtx taken, not_taken;
9347
9348  length = get_attr_length (insn);
9349  if (length <= 8)
9350    {
9351      /* Just a simple conditional branch.  */
9352      mips_branch_likely = (final_sequence && INSN_ANNULLED_BRANCH_P (insn));
9353      return branch_if_true;
9354    }
9355
9356  /* Generate a reversed branch around a direct jump.  This fallback does
9357     not use branch-likely instructions.  */
9358  mips_branch_likely = false;
9359  not_taken = gen_label_rtx ();
9360  taken = operands[1];
9361
9362  /* Generate the reversed branch to NOT_TAKEN.  */
9363  operands[1] = not_taken;
9364  output_asm_insn (branch_if_false, operands);
9365
9366  /* If INSN has a delay slot, we must provide delay slots for both the
9367     branch to NOT_TAKEN and the conditional jump.  We must also ensure
9368     that INSN's delay slot is executed in the appropriate cases.  */
9369  if (final_sequence)
9370    {
9371      /* This first delay slot will always be executed, so use INSN's
9372	 delay slot if is not annulled.  */
9373      if (!INSN_ANNULLED_BRANCH_P (insn))
9374	{
9375	  final_scan_insn (XVECEXP (final_sequence, 0, 1),
9376			   asm_out_file, optimize, 1, NULL);
9377	  INSN_DELETED_P (XVECEXP (final_sequence, 0, 1)) = 1;
9378	}
9379      else
9380	output_asm_insn ("nop", 0);
9381      fprintf (asm_out_file, "\n");
9382    }
9383
9384  /* Output the unconditional branch to TAKEN.  */
9385  if (length <= 16)
9386    output_asm_insn ("j\t%0%/", &taken);
9387  else
9388    {
9389      output_asm_insn (mips_output_load_label (), &taken);
9390      output_asm_insn ("jr\t%@%]%/", 0);
9391    }
9392
9393  /* Now deal with its delay slot; see above.  */
9394  if (final_sequence)
9395    {
9396      /* This delay slot will only be executed if the branch is taken.
9397	 Use INSN's delay slot if is annulled.  */
9398      if (INSN_ANNULLED_BRANCH_P (insn))
9399	{
9400	  final_scan_insn (XVECEXP (final_sequence, 0, 1),
9401			   asm_out_file, optimize, 1, NULL);
9402	  INSN_DELETED_P (XVECEXP (final_sequence, 0, 1)) = 1;
9403	}
9404      else
9405	output_asm_insn ("nop", 0);
9406      fprintf (asm_out_file, "\n");
9407    }
9408
9409  /* Output NOT_TAKEN.  */
9410  (*targetm.asm_out.internal_label) (asm_out_file, "L",
9411				     CODE_LABEL_NUMBER (not_taken));
9412  return "";
9413}
9414
9415/* Return the assembly code for INSN, which branches to OPERANDS[1]
9416   if some ordered condition is true.  The condition is given by
9417   OPERANDS[0] if !INVERTED_P, otherwise it is the inverse of
9418   OPERANDS[0].  OPERANDS[2] is the comparison's first operand;
9419   its second is always zero.  */
9420
9421const char *
9422mips_output_order_conditional_branch (rtx insn, rtx *operands, bool inverted_p)
9423{
9424  const char *branch[2];
9425
9426  /* Make BRANCH[1] branch to OPERANDS[1] when the condition is true.
9427     Make BRANCH[0] branch on the inverse condition.  */
9428  switch (GET_CODE (operands[0]))
9429    {
9430      /* These cases are equivalent to comparisons against zero.  */
9431    case LEU:
9432      inverted_p = !inverted_p;
9433      /* Fall through.  */
9434    case GTU:
9435      branch[!inverted_p] = MIPS_BRANCH ("bne", "%2,%.,%1");
9436      branch[inverted_p] = MIPS_BRANCH ("beq", "%2,%.,%1");
9437      break;
9438
9439      /* These cases are always true or always false.  */
9440    case LTU:
9441      inverted_p = !inverted_p;
9442      /* Fall through.  */
9443    case GEU:
9444      branch[!inverted_p] = MIPS_BRANCH ("beq", "%.,%.,%1");
9445      branch[inverted_p] = MIPS_BRANCH ("bne", "%.,%.,%1");
9446      break;
9447
9448    default:
9449      branch[!inverted_p] = MIPS_BRANCH ("b%C0z", "%2,%1");
9450      branch[inverted_p] = MIPS_BRANCH ("b%N0z", "%2,%1");
9451      break;
9452    }
9453  return mips_output_conditional_branch (insn, operands, branch[1], branch[0]);
9454}
9455
9456/* Used to output div or ddiv instruction DIVISION, which has the operands
9457   given by OPERANDS.  Add in a divide-by-zero check if needed.
9458
9459   When working around R4000 and R4400 errata, we need to make sure that
9460   the division is not immediately followed by a shift[1][2].  We also
9461   need to stop the division from being put into a branch delay slot[3].
9462   The easiest way to avoid both problems is to add a nop after the
9463   division.  When a divide-by-zero check is needed, this nop can be
9464   used to fill the branch delay slot.
9465
9466   [1] If a double-word or a variable shift executes immediately
9467       after starting an integer division, the shift may give an
9468       incorrect result.  See quotations of errata #16 and #28 from
9469       "MIPS R4000PC/SC Errata, Processor Revision 2.2 and 3.0"
9470       in mips.md for details.
9471
9472   [2] A similar bug to [1] exists for all revisions of the
9473       R4000 and the R4400 when run in an MC configuration.
9474       From "MIPS R4000MC Errata, Processor Revision 2.2 and 3.0":
9475
9476       "19. In this following sequence:
9477
9478		    ddiv		(or ddivu or div or divu)
9479		    dsll32		(or dsrl32, dsra32)
9480
9481	    if an MPT stall occurs, while the divide is slipping the cpu
9482	    pipeline, then the following double shift would end up with an
9483	    incorrect result.
9484
9485	    Workaround: The compiler needs to avoid generating any
9486	    sequence with divide followed by extended double shift."
9487
9488       This erratum is also present in "MIPS R4400MC Errata, Processor
9489       Revision 1.0" and "MIPS R4400MC Errata, Processor Revision 2.0
9490       & 3.0" as errata #10 and #4, respectively.
9491
9492   [3] From "MIPS R4000PC/SC Errata, Processor Revision 2.2 and 3.0"
9493       (also valid for MIPS R4000MC processors):
9494
9495       "52. R4000SC: This bug does not apply for the R4000PC.
9496
9497	    There are two flavors of this bug:
9498
9499	    1) If the instruction just after divide takes an RF exception
9500	       (tlb-refill, tlb-invalid) and gets an instruction cache
9501	       miss (both primary and secondary) and the line which is
9502	       currently in secondary cache at this index had the first
9503	       data word, where the bits 5..2 are set, then R4000 would
9504	       get a wrong result for the div.
9505
9506	    ##1
9507		    nop
9508		    div	r8, r9
9509		    -------------------		# end-of page. -tlb-refill
9510		    nop
9511	    ##2
9512		    nop
9513		    div	r8, r9
9514		    -------------------		# end-of page. -tlb-invalid
9515		    nop
9516
9517	    2) If the divide is in the taken branch delay slot, where the
9518	       target takes RF exception and gets an I-cache miss for the
9519	       exception vector or where I-cache miss occurs for the
9520	       target address, under the above mentioned scenarios, the
9521	       div would get wrong results.
9522
9523	    ##1
9524		    j	r2		# to next page mapped or unmapped
9525		    div	r8,r9		# this bug would be there as long
9526					# as there is an ICache miss and
9527		    nop			# the "data pattern" is present
9528
9529	    ##2
9530		    beq	r0, r0, NextPage	# to Next page
9531		    div	r8,r9
9532		    nop
9533
9534	    This bug is present for div, divu, ddiv, and ddivu
9535	    instructions.
9536
9537	    Workaround: For item 1), OS could make sure that the next page
9538	    after the divide instruction is also mapped.  For item 2), the
9539	    compiler could make sure that the divide instruction is not in
9540	    the branch delay slot."
9541
9542       These processors have PRId values of 0x00004220 and 0x00004300 for
9543       the R4000 and 0x00004400, 0x00004500 and 0x00004600 for the R4400.  */
9544
9545const char *
9546mips_output_division (const char *division, rtx *operands)
9547{
9548  const char *s;
9549
9550  s = division;
9551  if (TARGET_FIX_R4000 || TARGET_FIX_R4400)
9552    {
9553      output_asm_insn (s, operands);
9554      s = "nop";
9555    }
9556  if (TARGET_CHECK_ZERO_DIV)
9557    {
9558      if (TARGET_MIPS16)
9559	{
9560	  output_asm_insn (s, operands);
9561	  s = "bnez\t%2,1f\n\tbreak\t7\n1:";
9562	}
9563      else if (GENERATE_DIVIDE_TRAPS)
9564        {
9565	  output_asm_insn (s, operands);
9566	  s = "teq\t%2,%.,7";
9567        }
9568      else
9569	{
9570	  output_asm_insn ("%(bne\t%2,%.,1f", operands);
9571	  output_asm_insn (s, operands);
9572	  s = "break\t7%)\n1:";
9573	}
9574    }
9575  return s;
9576}
9577
9578/* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
9579   with a final "000" replaced by "k".  Ignore case.
9580
9581   Note: this function is shared between GCC and GAS.  */
9582
9583static bool
9584mips_strict_matching_cpu_name_p (const char *canonical, const char *given)
9585{
9586  while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
9587    given++, canonical++;
9588
9589  return ((*given == 0 && *canonical == 0)
9590	  || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
9591}
9592
9593
9594/* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
9595   CPU name.  We've traditionally allowed a lot of variation here.
9596
9597   Note: this function is shared between GCC and GAS.  */
9598
9599static bool
9600mips_matching_cpu_name_p (const char *canonical, const char *given)
9601{
9602  /* First see if the name matches exactly, or with a final "000"
9603     turned into "k".  */
9604  if (mips_strict_matching_cpu_name_p (canonical, given))
9605    return true;
9606
9607  /* If not, try comparing based on numerical designation alone.
9608     See if GIVEN is an unadorned number, or 'r' followed by a number.  */
9609  if (TOLOWER (*given) == 'r')
9610    given++;
9611  if (!ISDIGIT (*given))
9612    return false;
9613
9614  /* Skip over some well-known prefixes in the canonical name,
9615     hoping to find a number there too.  */
9616  if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
9617    canonical += 2;
9618  else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
9619    canonical += 2;
9620  else if (TOLOWER (canonical[0]) == 'r')
9621    canonical += 1;
9622
9623  return mips_strict_matching_cpu_name_p (canonical, given);
9624}
9625
9626
9627/* Return the mips_cpu_info entry for the processor or ISA given
9628   by CPU_STRING.  Return null if the string isn't recognized.
9629
9630   A similar function exists in GAS.  */
9631
9632static const struct mips_cpu_info *
9633mips_parse_cpu (const char *cpu_string)
9634{
9635  const struct mips_cpu_info *p;
9636  const char *s;
9637
9638  /* In the past, we allowed upper-case CPU names, but it doesn't
9639     work well with the multilib machinery.  */
9640  for (s = cpu_string; *s != 0; s++)
9641    if (ISUPPER (*s))
9642      {
9643	warning (0, "the cpu name must be lower case");
9644	break;
9645      }
9646
9647  /* 'from-abi' selects the most compatible architecture for the given
9648     ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs.  For the
9649     EABIs, we have to decide whether we're using the 32-bit or 64-bit
9650     version.  Look first at the -mgp options, if given, otherwise base
9651     the choice on MASK_64BIT in TARGET_DEFAULT.  */
9652  if (strcasecmp (cpu_string, "from-abi") == 0)
9653    return mips_cpu_info_from_isa (ABI_NEEDS_32BIT_REGS ? 1
9654				   : ABI_NEEDS_64BIT_REGS ? 3
9655				   : (TARGET_64BIT ? 3 : 1));
9656
9657  /* 'default' has traditionally been a no-op.  Probably not very useful.  */
9658  if (strcasecmp (cpu_string, "default") == 0)
9659    return 0;
9660
9661  for (p = mips_cpu_info_table; p->name != 0; p++)
9662    if (mips_matching_cpu_name_p (p->name, cpu_string))
9663      return p;
9664
9665  return 0;
9666}
9667
9668
9669/* Return the processor associated with the given ISA level, or null
9670   if the ISA isn't valid.  */
9671
9672static const struct mips_cpu_info *
9673mips_cpu_info_from_isa (int isa)
9674{
9675  const struct mips_cpu_info *p;
9676
9677  for (p = mips_cpu_info_table; p->name != 0; p++)
9678    if (p->isa == isa)
9679      return p;
9680
9681  return 0;
9682}
9683
9684/* Implement HARD_REGNO_NREGS.  The size of FP registers is controlled
9685   by UNITS_PER_FPREG.  The size of FP status registers is always 4, because
9686   they only hold condition code modes, and CCmode is always considered to
9687   be 4 bytes wide.  All other registers are word sized.  */
9688
9689unsigned int
9690mips_hard_regno_nregs (int regno, enum machine_mode mode)
9691{
9692  if (ST_REG_P (regno))
9693    return ((GET_MODE_SIZE (mode) + 3) / 4);
9694  else if (! FP_REG_P (regno))
9695    return ((GET_MODE_SIZE (mode) + UNITS_PER_WORD - 1) / UNITS_PER_WORD);
9696  else
9697    return ((GET_MODE_SIZE (mode) + UNITS_PER_FPREG - 1) / UNITS_PER_FPREG);
9698}
9699
9700/* Implement TARGET_RETURN_IN_MEMORY.  Under the old (i.e., 32 and O64 ABIs)
9701   all BLKmode objects are returned in memory.  Under the new (N32 and
9702   64-bit MIPS ABIs) small structures are returned in a register.
9703   Objects with varying size must still be returned in memory, of
9704   course.  */
9705
9706static bool
9707mips_return_in_memory (tree type, tree fndecl ATTRIBUTE_UNUSED)
9708{
9709  if (TARGET_OLDABI)
9710    return (TYPE_MODE (type) == BLKmode);
9711  else
9712    return ((int_size_in_bytes (type) > (2 * UNITS_PER_WORD))
9713	    || (int_size_in_bytes (type) == -1));
9714}
9715
9716static bool
9717mips_strict_argument_naming (CUMULATIVE_ARGS *ca ATTRIBUTE_UNUSED)
9718{
9719  return !TARGET_OLDABI;
9720}
9721
9722/* Return true if INSN is a multiply-add or multiply-subtract
9723   instruction and PREV assigns to the accumulator operand.  */
9724
9725bool
9726mips_linked_madd_p (rtx prev, rtx insn)
9727{
9728  rtx x;
9729
9730  x = single_set (insn);
9731  if (x == 0)
9732    return false;
9733
9734  x = SET_SRC (x);
9735
9736  if (GET_CODE (x) == PLUS
9737      && GET_CODE (XEXP (x, 0)) == MULT
9738      && reg_set_p (XEXP (x, 1), prev))
9739    return true;
9740
9741  if (GET_CODE (x) == MINUS
9742      && GET_CODE (XEXP (x, 1)) == MULT
9743      && reg_set_p (XEXP (x, 0), prev))
9744    return true;
9745
9746  return false;
9747}
9748
9749/* Used by TUNE_MACC_CHAINS to record the last scheduled instruction
9750   that may clobber hi or lo.  */
9751
9752static rtx mips_macc_chains_last_hilo;
9753
9754/* A TUNE_MACC_CHAINS helper function.  Record that instruction INSN has
9755   been scheduled, updating mips_macc_chains_last_hilo appropriately.  */
9756
9757static void
9758mips_macc_chains_record (rtx insn)
9759{
9760  if (get_attr_may_clobber_hilo (insn))
9761    mips_macc_chains_last_hilo = insn;
9762}
9763
9764/* A TUNE_MACC_CHAINS helper function.  Search ready queue READY, which
9765   has NREADY elements, looking for a multiply-add or multiply-subtract
9766   instruction that is cumulative with mips_macc_chains_last_hilo.
9767   If there is one, promote it ahead of anything else that might
9768   clobber hi or lo.  */
9769
9770static void
9771mips_macc_chains_reorder (rtx *ready, int nready)
9772{
9773  int i, j;
9774
9775  if (mips_macc_chains_last_hilo != 0)
9776    for (i = nready - 1; i >= 0; i--)
9777      if (mips_linked_madd_p (mips_macc_chains_last_hilo, ready[i]))
9778	{
9779	  for (j = nready - 1; j > i; j--)
9780	    if (recog_memoized (ready[j]) >= 0
9781		&& get_attr_may_clobber_hilo (ready[j]))
9782	      {
9783		mips_promote_ready (ready, i, j);
9784		break;
9785	      }
9786	  break;
9787	}
9788}
9789
9790/* The last instruction to be scheduled.  */
9791
9792static rtx vr4130_last_insn;
9793
9794/* A note_stores callback used by vr4130_true_reg_dependence_p.  DATA
9795   points to an rtx that is initially an instruction.  Nullify the rtx
9796   if the instruction uses the value of register X.  */
9797
9798static void
9799vr4130_true_reg_dependence_p_1 (rtx x, rtx pat ATTRIBUTE_UNUSED, void *data)
9800{
9801  rtx *insn_ptr = data;
9802  if (REG_P (x)
9803      && *insn_ptr != 0
9804      && reg_referenced_p (x, PATTERN (*insn_ptr)))
9805    *insn_ptr = 0;
9806}
9807
9808/* Return true if there is true register dependence between vr4130_last_insn
9809   and INSN.  */
9810
9811static bool
9812vr4130_true_reg_dependence_p (rtx insn)
9813{
9814  note_stores (PATTERN (vr4130_last_insn),
9815	       vr4130_true_reg_dependence_p_1, &insn);
9816  return insn == 0;
9817}
9818
9819/* A TUNE_MIPS4130 helper function.  Given that INSN1 is at the head of
9820   the ready queue and that INSN2 is the instruction after it, return
9821   true if it is worth promoting INSN2 ahead of INSN1.  Look for cases
9822   in which INSN1 and INSN2 can probably issue in parallel, but for
9823   which (INSN2, INSN1) should be less sensitive to instruction
9824   alignment than (INSN1, INSN2).  See 4130.md for more details.  */
9825
9826static bool
9827vr4130_swap_insns_p (rtx insn1, rtx insn2)
9828{
9829  rtx dep;
9830
9831  /* Check for the following case:
9832
9833     1) there is some other instruction X with an anti dependence on INSN1;
9834     2) X has a higher priority than INSN2; and
9835     3) X is an arithmetic instruction (and thus has no unit restrictions).
9836
9837     If INSN1 is the last instruction blocking X, it would better to
9838     choose (INSN1, X) over (INSN2, INSN1).  */
9839  for (dep = INSN_DEPEND (insn1); dep != 0; dep = XEXP (dep, 1))
9840    if (REG_NOTE_KIND (dep) == REG_DEP_ANTI
9841	&& INSN_PRIORITY (XEXP (dep, 0)) > INSN_PRIORITY (insn2)
9842	&& recog_memoized (XEXP (dep, 0)) >= 0
9843	&& get_attr_vr4130_class (XEXP (dep, 0)) == VR4130_CLASS_ALU)
9844      return false;
9845
9846  if (vr4130_last_insn != 0
9847      && recog_memoized (insn1) >= 0
9848      && recog_memoized (insn2) >= 0)
9849    {
9850      /* See whether INSN1 and INSN2 use different execution units,
9851	 or if they are both ALU-type instructions.  If so, they can
9852	 probably execute in parallel.  */
9853      enum attr_vr4130_class class1 = get_attr_vr4130_class (insn1);
9854      enum attr_vr4130_class class2 = get_attr_vr4130_class (insn2);
9855      if (class1 != class2 || class1 == VR4130_CLASS_ALU)
9856	{
9857	  /* If only one of the instructions has a dependence on
9858	     vr4130_last_insn, prefer to schedule the other one first.  */
9859	  bool dep1 = vr4130_true_reg_dependence_p (insn1);
9860	  bool dep2 = vr4130_true_reg_dependence_p (insn2);
9861	  if (dep1 != dep2)
9862	    return dep1;
9863
9864	  /* Prefer to schedule INSN2 ahead of INSN1 if vr4130_last_insn
9865	     is not an ALU-type instruction and if INSN1 uses the same
9866	     execution unit.  (Note that if this condition holds, we already
9867	     know that INSN2 uses a different execution unit.)  */
9868	  if (class1 != VR4130_CLASS_ALU
9869	      && recog_memoized (vr4130_last_insn) >= 0
9870	      && class1 == get_attr_vr4130_class (vr4130_last_insn))
9871	    return true;
9872	}
9873    }
9874  return false;
9875}
9876
9877/* A TUNE_MIPS4130 helper function.  (READY, NREADY) describes a ready
9878   queue with at least two instructions.  Swap the first two if
9879   vr4130_swap_insns_p says that it could be worthwhile.  */
9880
9881static void
9882vr4130_reorder (rtx *ready, int nready)
9883{
9884  if (vr4130_swap_insns_p (ready[nready - 1], ready[nready - 2]))
9885    mips_promote_ready (ready, nready - 2, nready - 1);
9886}
9887
9888/* Remove the instruction at index LOWER from ready queue READY and
9889   reinsert it in front of the instruction at index HIGHER.  LOWER must
9890   be <= HIGHER.  */
9891
9892static void
9893mips_promote_ready (rtx *ready, int lower, int higher)
9894{
9895  rtx new_head;
9896  int i;
9897
9898  new_head = ready[lower];
9899  for (i = lower; i < higher; i++)
9900    ready[i] = ready[i + 1];
9901  ready[i] = new_head;
9902}
9903
9904/* Implement TARGET_SCHED_REORDER.  */
9905
9906static int
9907mips_sched_reorder (FILE *file ATTRIBUTE_UNUSED, int verbose ATTRIBUTE_UNUSED,
9908		    rtx *ready, int *nreadyp, int cycle)
9909{
9910  if (!reload_completed && TUNE_MACC_CHAINS)
9911    {
9912      if (cycle == 0)
9913	mips_macc_chains_last_hilo = 0;
9914      if (*nreadyp > 0)
9915	mips_macc_chains_reorder (ready, *nreadyp);
9916    }
9917  if (reload_completed && TUNE_MIPS4130 && !TARGET_VR4130_ALIGN)
9918    {
9919      if (cycle == 0)
9920	vr4130_last_insn = 0;
9921      if (*nreadyp > 1)
9922	vr4130_reorder (ready, *nreadyp);
9923    }
9924  return mips_issue_rate ();
9925}
9926
9927/* Implement TARGET_SCHED_VARIABLE_ISSUE.  */
9928
9929static int
9930mips_variable_issue (FILE *file ATTRIBUTE_UNUSED, int verbose ATTRIBUTE_UNUSED,
9931		     rtx insn, int more)
9932{
9933  switch (GET_CODE (PATTERN (insn)))
9934    {
9935    case USE:
9936    case CLOBBER:
9937      /* Don't count USEs and CLOBBERs against the issue rate.  */
9938      break;
9939
9940    default:
9941      more--;
9942      if (!reload_completed && TUNE_MACC_CHAINS)
9943	mips_macc_chains_record (insn);
9944      vr4130_last_insn = insn;
9945      break;
9946    }
9947  return more;
9948}
9949
9950/* Implement TARGET_SCHED_ADJUST_COST.  We assume that anti and output
9951   dependencies have no cost.  */
9952
9953static int
9954mips_adjust_cost (rtx insn ATTRIBUTE_UNUSED, rtx link,
9955		  rtx dep ATTRIBUTE_UNUSED, int cost)
9956{
9957  if (REG_NOTE_KIND (link) != 0)
9958    return 0;
9959  return cost;
9960}
9961
9962/* Return the number of instructions that can be issued per cycle.  */
9963
9964static int
9965mips_issue_rate (void)
9966{
9967  switch (mips_tune)
9968    {
9969    case PROCESSOR_R4130:
9970    case PROCESSOR_R5400:
9971    case PROCESSOR_R5500:
9972    case PROCESSOR_R7000:
9973    case PROCESSOR_R9000:
9974    case PROCESSOR_OCTEON:
9975      return 2;
9976
9977    case PROCESSOR_SB1:
9978    case PROCESSOR_SB1A:
9979      /* This is actually 4, but we get better performance if we claim 3.
9980	 This is partly because of unwanted speculative code motion with the
9981	 larger number, and partly because in most common cases we can't
9982	 reach the theoretical max of 4.  */
9983      return 3;
9984
9985    default:
9986      return 1;
9987    }
9988}
9989
9990/* Implements TARGET_SCHED_FIRST_CYCLE_MULTIPASS_DFA_LOOKAHEAD.  This should
9991   be as wide as the scheduling freedom in the DFA.  */
9992
9993static int
9994mips_multipass_dfa_lookahead (void)
9995{
9996  /* Can schedule up to 4 of the 6 function units in any one cycle.  */
9997  if (TUNE_SB1)
9998    return 4;
9999
10000  return 0;
10001}
10002
10003/* Implements a store data bypass check.  We need this because the cprestore
10004   pattern is type store, but defined using an UNSPEC.  This UNSPEC causes the
10005   default routine to abort.  We just return false for that case.  */
10006/* ??? Should try to give a better result here than assuming false.  */
10007
10008int
10009mips_store_data_bypass_p (rtx out_insn, rtx in_insn)
10010{
10011  if (GET_CODE (PATTERN (in_insn)) == UNSPEC_VOLATILE)
10012    return false;
10013
10014  return ! store_data_bypass_p (out_insn, in_insn);
10015}
10016
10017/* Given that we have an rtx of the form (prefetch ... WRITE LOCALITY),
10018   return the first operand of the associated "pref" or "prefx" insn.  */
10019
10020rtx
10021mips_prefetch_cookie (rtx write, rtx locality)
10022{
10023  /* store_streamed / load_streamed.  */
10024  if (INTVAL (locality) <= 0)
10025    return GEN_INT (INTVAL (write) + 4);
10026
10027  /* store / load.  */
10028  if (INTVAL (locality) <= 2)
10029    return write;
10030
10031  /* store_retained / load_retained.  */
10032  return GEN_INT (INTVAL (write) + 6);
10033}
10034
10035/* MIPS builtin function support. */
10036
10037struct builtin_description
10038{
10039  /* The code of the main .md file instruction.  See mips_builtin_type
10040     for more information.  */
10041  enum insn_code icode;
10042
10043  /* The floating-point comparison code to use with ICODE, if any.  */
10044  enum mips_fp_condition cond;
10045
10046  /* The name of the builtin function.  */
10047  const char *name;
10048
10049  /* Specifies how the function should be expanded.  */
10050  enum mips_builtin_type builtin_type;
10051
10052  /* The function's prototype.  */
10053  enum mips_function_type function_type;
10054
10055  /* The target flags required for this function.  */
10056  int target_flags;
10057};
10058
10059/* Define a MIPS_BUILTIN_DIRECT function for instruction CODE_FOR_mips_<INSN>.
10060   FUNCTION_TYPE and TARGET_FLAGS are builtin_description fields.  */
10061#define DIRECT_BUILTIN(INSN, FUNCTION_TYPE, TARGET_FLAGS)		\
10062  { CODE_FOR_mips_ ## INSN, 0, "__builtin_mips_" #INSN,			\
10063    MIPS_BUILTIN_DIRECT, FUNCTION_TYPE, TARGET_FLAGS }
10064
10065/* Define __builtin_mips_<INSN>_<COND>_{s,d}, both of which require
10066   TARGET_FLAGS.  */
10067#define CMP_SCALAR_BUILTINS(INSN, COND, TARGET_FLAGS)			\
10068  { CODE_FOR_mips_ ## INSN ## _cond_s, MIPS_FP_COND_ ## COND,		\
10069    "__builtin_mips_" #INSN "_" #COND "_s",				\
10070    MIPS_BUILTIN_CMP_SINGLE, MIPS_INT_FTYPE_SF_SF, TARGET_FLAGS },	\
10071  { CODE_FOR_mips_ ## INSN ## _cond_d, MIPS_FP_COND_ ## COND,		\
10072    "__builtin_mips_" #INSN "_" #COND "_d",				\
10073    MIPS_BUILTIN_CMP_SINGLE, MIPS_INT_FTYPE_DF_DF, TARGET_FLAGS }
10074
10075/* Define __builtin_mips_{any,all,upper,lower}_<INSN>_<COND>_ps.
10076   The lower and upper forms require TARGET_FLAGS while the any and all
10077   forms require MASK_MIPS3D.  */
10078#define CMP_PS_BUILTINS(INSN, COND, TARGET_FLAGS)			\
10079  { CODE_FOR_mips_ ## INSN ## _cond_ps, MIPS_FP_COND_ ## COND,		\
10080    "__builtin_mips_any_" #INSN "_" #COND "_ps",			\
10081    MIPS_BUILTIN_CMP_ANY, MIPS_INT_FTYPE_V2SF_V2SF, MASK_MIPS3D },	\
10082  { CODE_FOR_mips_ ## INSN ## _cond_ps, MIPS_FP_COND_ ## COND,		\
10083    "__builtin_mips_all_" #INSN "_" #COND "_ps",			\
10084    MIPS_BUILTIN_CMP_ALL, MIPS_INT_FTYPE_V2SF_V2SF, MASK_MIPS3D },	\
10085  { CODE_FOR_mips_ ## INSN ## _cond_ps, MIPS_FP_COND_ ## COND,		\
10086    "__builtin_mips_lower_" #INSN "_" #COND "_ps",			\
10087    MIPS_BUILTIN_CMP_LOWER, MIPS_INT_FTYPE_V2SF_V2SF, TARGET_FLAGS },	\
10088  { CODE_FOR_mips_ ## INSN ## _cond_ps, MIPS_FP_COND_ ## COND,		\
10089    "__builtin_mips_upper_" #INSN "_" #COND "_ps",			\
10090    MIPS_BUILTIN_CMP_UPPER, MIPS_INT_FTYPE_V2SF_V2SF, TARGET_FLAGS }
10091
10092/* Define __builtin_mips_{any,all}_<INSN>_<COND>_4s.  The functions
10093   require MASK_MIPS3D.  */
10094#define CMP_4S_BUILTINS(INSN, COND)					\
10095  { CODE_FOR_mips_ ## INSN ## _cond_4s, MIPS_FP_COND_ ## COND,		\
10096    "__builtin_mips_any_" #INSN "_" #COND "_4s",			\
10097    MIPS_BUILTIN_CMP_ANY, MIPS_INT_FTYPE_V2SF_V2SF_V2SF_V2SF,		\
10098    MASK_MIPS3D },							\
10099  { CODE_FOR_mips_ ## INSN ## _cond_4s, MIPS_FP_COND_ ## COND,		\
10100    "__builtin_mips_all_" #INSN "_" #COND "_4s",			\
10101    MIPS_BUILTIN_CMP_ALL, MIPS_INT_FTYPE_V2SF_V2SF_V2SF_V2SF,		\
10102    MASK_MIPS3D }
10103
10104/* Define __builtin_mips_mov{t,f}_<INSN>_<COND>_ps.  The comparison
10105   instruction requires TARGET_FLAGS.  */
10106#define MOVTF_BUILTINS(INSN, COND, TARGET_FLAGS)			\
10107  { CODE_FOR_mips_ ## INSN ## _cond_ps, MIPS_FP_COND_ ## COND,		\
10108    "__builtin_mips_movt_" #INSN "_" #COND "_ps",			\
10109    MIPS_BUILTIN_MOVT, MIPS_V2SF_FTYPE_V2SF_V2SF_V2SF_V2SF,		\
10110    TARGET_FLAGS },							\
10111  { CODE_FOR_mips_ ## INSN ## _cond_ps, MIPS_FP_COND_ ## COND,		\
10112    "__builtin_mips_movf_" #INSN "_" #COND "_ps",			\
10113    MIPS_BUILTIN_MOVF, MIPS_V2SF_FTYPE_V2SF_V2SF_V2SF_V2SF,		\
10114    TARGET_FLAGS }
10115
10116/* Define all the builtins related to c.cond.fmt condition COND.  */
10117#define CMP_BUILTINS(COND)						\
10118  MOVTF_BUILTINS (c, COND, MASK_PAIRED_SINGLE_FLOAT),			\
10119  MOVTF_BUILTINS (cabs, COND, MASK_MIPS3D),				\
10120  CMP_SCALAR_BUILTINS (cabs, COND, MASK_MIPS3D),			\
10121  CMP_PS_BUILTINS (c, COND, MASK_PAIRED_SINGLE_FLOAT),			\
10122  CMP_PS_BUILTINS (cabs, COND, MASK_MIPS3D),				\
10123  CMP_4S_BUILTINS (c, COND),						\
10124  CMP_4S_BUILTINS (cabs, COND)
10125
10126static const struct builtin_description mips_bdesc[] =
10127{
10128  DIRECT_BUILTIN (pll_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_PAIRED_SINGLE_FLOAT),
10129  DIRECT_BUILTIN (pul_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_PAIRED_SINGLE_FLOAT),
10130  DIRECT_BUILTIN (plu_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_PAIRED_SINGLE_FLOAT),
10131  DIRECT_BUILTIN (puu_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_PAIRED_SINGLE_FLOAT),
10132  DIRECT_BUILTIN (cvt_ps_s, MIPS_V2SF_FTYPE_SF_SF, MASK_PAIRED_SINGLE_FLOAT),
10133  DIRECT_BUILTIN (cvt_s_pl, MIPS_SF_FTYPE_V2SF, MASK_PAIRED_SINGLE_FLOAT),
10134  DIRECT_BUILTIN (cvt_s_pu, MIPS_SF_FTYPE_V2SF, MASK_PAIRED_SINGLE_FLOAT),
10135  DIRECT_BUILTIN (abs_ps, MIPS_V2SF_FTYPE_V2SF, MASK_PAIRED_SINGLE_FLOAT),
10136
10137  DIRECT_BUILTIN (alnv_ps, MIPS_V2SF_FTYPE_V2SF_V2SF_INT,
10138		  MASK_PAIRED_SINGLE_FLOAT),
10139  DIRECT_BUILTIN (addr_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_MIPS3D),
10140  DIRECT_BUILTIN (mulr_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_MIPS3D),
10141  DIRECT_BUILTIN (cvt_pw_ps, MIPS_V2SF_FTYPE_V2SF, MASK_MIPS3D),
10142  DIRECT_BUILTIN (cvt_ps_pw, MIPS_V2SF_FTYPE_V2SF, MASK_MIPS3D),
10143
10144  DIRECT_BUILTIN (recip1_s, MIPS_SF_FTYPE_SF, MASK_MIPS3D),
10145  DIRECT_BUILTIN (recip1_d, MIPS_DF_FTYPE_DF, MASK_MIPS3D),
10146  DIRECT_BUILTIN (recip1_ps, MIPS_V2SF_FTYPE_V2SF, MASK_MIPS3D),
10147  DIRECT_BUILTIN (recip2_s, MIPS_SF_FTYPE_SF_SF, MASK_MIPS3D),
10148  DIRECT_BUILTIN (recip2_d, MIPS_DF_FTYPE_DF_DF, MASK_MIPS3D),
10149  DIRECT_BUILTIN (recip2_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_MIPS3D),
10150
10151  DIRECT_BUILTIN (rsqrt1_s, MIPS_SF_FTYPE_SF, MASK_MIPS3D),
10152  DIRECT_BUILTIN (rsqrt1_d, MIPS_DF_FTYPE_DF, MASK_MIPS3D),
10153  DIRECT_BUILTIN (rsqrt1_ps, MIPS_V2SF_FTYPE_V2SF, MASK_MIPS3D),
10154  DIRECT_BUILTIN (rsqrt2_s, MIPS_SF_FTYPE_SF_SF, MASK_MIPS3D),
10155  DIRECT_BUILTIN (rsqrt2_d, MIPS_DF_FTYPE_DF_DF, MASK_MIPS3D),
10156  DIRECT_BUILTIN (rsqrt2_ps, MIPS_V2SF_FTYPE_V2SF_V2SF, MASK_MIPS3D),
10157
10158  MIPS_FP_CONDITIONS (CMP_BUILTINS)
10159};
10160
10161/* Builtin functions for the SB-1 processor.  */
10162
10163#define CODE_FOR_mips_sqrt_ps CODE_FOR_sqrtv2sf2
10164
10165static const struct builtin_description sb1_bdesc[] =
10166{
10167  DIRECT_BUILTIN (sqrt_ps, MIPS_V2SF_FTYPE_V2SF, MASK_PAIRED_SINGLE_FLOAT)
10168};
10169
10170/* Builtin functions for DSP ASE.  */
10171
10172#define CODE_FOR_mips_addq_ph CODE_FOR_addv2hi3
10173#define CODE_FOR_mips_addu_qb CODE_FOR_addv4qi3
10174#define CODE_FOR_mips_subq_ph CODE_FOR_subv2hi3
10175#define CODE_FOR_mips_subu_qb CODE_FOR_subv4qi3
10176
10177/* Define a MIPS_BUILTIN_DIRECT_NO_TARGET function for instruction
10178   CODE_FOR_mips_<INSN>.  FUNCTION_TYPE and TARGET_FLAGS are
10179   builtin_description fields.  */
10180#define DIRECT_NO_TARGET_BUILTIN(INSN, FUNCTION_TYPE, TARGET_FLAGS)	\
10181  { CODE_FOR_mips_ ## INSN, 0, "__builtin_mips_" #INSN,			\
10182    MIPS_BUILTIN_DIRECT_NO_TARGET, FUNCTION_TYPE, TARGET_FLAGS }
10183
10184/* Define __builtin_mips_bposge<VALUE>.  <VALUE> is 32 for the MIPS32 DSP
10185   branch instruction.  TARGET_FLAGS is a builtin_description field.  */
10186#define BPOSGE_BUILTIN(VALUE, TARGET_FLAGS)				\
10187  { CODE_FOR_mips_bposge, 0, "__builtin_mips_bposge" #VALUE,		\
10188    MIPS_BUILTIN_BPOSGE ## VALUE, MIPS_SI_FTYPE_VOID, TARGET_FLAGS }
10189
10190static const struct builtin_description dsp_bdesc[] =
10191{
10192  DIRECT_BUILTIN (addq_ph, MIPS_V2HI_FTYPE_V2HI_V2HI, MASK_DSP),
10193  DIRECT_BUILTIN (addq_s_ph, MIPS_V2HI_FTYPE_V2HI_V2HI, MASK_DSP),
10194  DIRECT_BUILTIN (addq_s_w, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10195  DIRECT_BUILTIN (addu_qb, MIPS_V4QI_FTYPE_V4QI_V4QI, MASK_DSP),
10196  DIRECT_BUILTIN (addu_s_qb, MIPS_V4QI_FTYPE_V4QI_V4QI, MASK_DSP),
10197  DIRECT_BUILTIN (subq_ph, MIPS_V2HI_FTYPE_V2HI_V2HI, MASK_DSP),
10198  DIRECT_BUILTIN (subq_s_ph, MIPS_V2HI_FTYPE_V2HI_V2HI, MASK_DSP),
10199  DIRECT_BUILTIN (subq_s_w, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10200  DIRECT_BUILTIN (subu_qb, MIPS_V4QI_FTYPE_V4QI_V4QI, MASK_DSP),
10201  DIRECT_BUILTIN (subu_s_qb, MIPS_V4QI_FTYPE_V4QI_V4QI, MASK_DSP),
10202  DIRECT_BUILTIN (addsc, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10203  DIRECT_BUILTIN (addwc, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10204  DIRECT_BUILTIN (modsub, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10205  DIRECT_BUILTIN (raddu_w_qb, MIPS_SI_FTYPE_V4QI, MASK_DSP),
10206  DIRECT_BUILTIN (absq_s_ph, MIPS_V2HI_FTYPE_V2HI, MASK_DSP),
10207  DIRECT_BUILTIN (absq_s_w, MIPS_SI_FTYPE_SI, MASK_DSP),
10208  DIRECT_BUILTIN (precrq_qb_ph, MIPS_V4QI_FTYPE_V2HI_V2HI, MASK_DSP),
10209  DIRECT_BUILTIN (precrq_ph_w, MIPS_V2HI_FTYPE_SI_SI, MASK_DSP),
10210  DIRECT_BUILTIN (precrq_rs_ph_w, MIPS_V2HI_FTYPE_SI_SI, MASK_DSP),
10211  DIRECT_BUILTIN (precrqu_s_qb_ph, MIPS_V4QI_FTYPE_V2HI_V2HI, MASK_DSP),
10212  DIRECT_BUILTIN (preceq_w_phl, MIPS_SI_FTYPE_V2HI, MASK_DSP),
10213  DIRECT_BUILTIN (preceq_w_phr, MIPS_SI_FTYPE_V2HI, MASK_DSP),
10214  DIRECT_BUILTIN (precequ_ph_qbl, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10215  DIRECT_BUILTIN (precequ_ph_qbr, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10216  DIRECT_BUILTIN (precequ_ph_qbla, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10217  DIRECT_BUILTIN (precequ_ph_qbra, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10218  DIRECT_BUILTIN (preceu_ph_qbl, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10219  DIRECT_BUILTIN (preceu_ph_qbr, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10220  DIRECT_BUILTIN (preceu_ph_qbla, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10221  DIRECT_BUILTIN (preceu_ph_qbra, MIPS_V2HI_FTYPE_V4QI, MASK_DSP),
10222  DIRECT_BUILTIN (shll_qb, MIPS_V4QI_FTYPE_V4QI_SI, MASK_DSP),
10223  DIRECT_BUILTIN (shll_ph, MIPS_V2HI_FTYPE_V2HI_SI, MASK_DSP),
10224  DIRECT_BUILTIN (shll_s_ph, MIPS_V2HI_FTYPE_V2HI_SI, MASK_DSP),
10225  DIRECT_BUILTIN (shll_s_w, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10226  DIRECT_BUILTIN (shrl_qb, MIPS_V4QI_FTYPE_V4QI_SI, MASK_DSP),
10227  DIRECT_BUILTIN (shra_ph, MIPS_V2HI_FTYPE_V2HI_SI, MASK_DSP),
10228  DIRECT_BUILTIN (shra_r_ph, MIPS_V2HI_FTYPE_V2HI_SI, MASK_DSP),
10229  DIRECT_BUILTIN (shra_r_w, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10230  DIRECT_BUILTIN (muleu_s_ph_qbl, MIPS_V2HI_FTYPE_V4QI_V2HI, MASK_DSP),
10231  DIRECT_BUILTIN (muleu_s_ph_qbr, MIPS_V2HI_FTYPE_V4QI_V2HI, MASK_DSP),
10232  DIRECT_BUILTIN (mulq_rs_ph, MIPS_V2HI_FTYPE_V2HI_V2HI, MASK_DSP),
10233  DIRECT_BUILTIN (muleq_s_w_phl, MIPS_SI_FTYPE_V2HI_V2HI, MASK_DSP),
10234  DIRECT_BUILTIN (muleq_s_w_phr, MIPS_SI_FTYPE_V2HI_V2HI, MASK_DSP),
10235  DIRECT_BUILTIN (dpau_h_qbl, MIPS_DI_FTYPE_DI_V4QI_V4QI, MASK_DSP),
10236  DIRECT_BUILTIN (dpau_h_qbr, MIPS_DI_FTYPE_DI_V4QI_V4QI, MASK_DSP),
10237  DIRECT_BUILTIN (dpsu_h_qbl, MIPS_DI_FTYPE_DI_V4QI_V4QI, MASK_DSP),
10238  DIRECT_BUILTIN (dpsu_h_qbr, MIPS_DI_FTYPE_DI_V4QI_V4QI, MASK_DSP),
10239  DIRECT_BUILTIN (dpaq_s_w_ph, MIPS_DI_FTYPE_DI_V2HI_V2HI, MASK_DSP),
10240  DIRECT_BUILTIN (dpsq_s_w_ph, MIPS_DI_FTYPE_DI_V2HI_V2HI, MASK_DSP),
10241  DIRECT_BUILTIN (mulsaq_s_w_ph, MIPS_DI_FTYPE_DI_V2HI_V2HI, MASK_DSP),
10242  DIRECT_BUILTIN (dpaq_sa_l_w, MIPS_DI_FTYPE_DI_SI_SI, MASK_DSP),
10243  DIRECT_BUILTIN (dpsq_sa_l_w, MIPS_DI_FTYPE_DI_SI_SI, MASK_DSP),
10244  DIRECT_BUILTIN (maq_s_w_phl, MIPS_DI_FTYPE_DI_V2HI_V2HI, MASK_DSP),
10245  DIRECT_BUILTIN (maq_s_w_phr, MIPS_DI_FTYPE_DI_V2HI_V2HI, MASK_DSP),
10246  DIRECT_BUILTIN (maq_sa_w_phl, MIPS_DI_FTYPE_DI_V2HI_V2HI, MASK_DSP),
10247  DIRECT_BUILTIN (maq_sa_w_phr, MIPS_DI_FTYPE_DI_V2HI_V2HI, MASK_DSP),
10248  DIRECT_BUILTIN (bitrev, MIPS_SI_FTYPE_SI, MASK_DSP),
10249  DIRECT_BUILTIN (insv, MIPS_SI_FTYPE_SI_SI, MASK_DSP),
10250  DIRECT_BUILTIN (repl_qb, MIPS_V4QI_FTYPE_SI, MASK_DSP),
10251  DIRECT_BUILTIN (repl_ph, MIPS_V2HI_FTYPE_SI, MASK_DSP),
10252  DIRECT_NO_TARGET_BUILTIN (cmpu_eq_qb, MIPS_VOID_FTYPE_V4QI_V4QI, MASK_DSP),
10253  DIRECT_NO_TARGET_BUILTIN (cmpu_lt_qb, MIPS_VOID_FTYPE_V4QI_V4QI, MASK_DSP),
10254  DIRECT_NO_TARGET_BUILTIN (cmpu_le_qb, MIPS_VOID_FTYPE_V4QI_V4QI, MASK_DSP),
10255  DIRECT_BUILTIN (cmpgu_eq_qb, MIPS_SI_FTYPE_V4QI_V4QI, MASK_DSP),
10256  DIRECT_BUILTIN (cmpgu_lt_qb, MIPS_SI_FTYPE_V4QI_V4QI, MASK_DSP),
10257  DIRECT_BUILTIN (cmpgu_le_qb, MIPS_SI_FTYPE_V4QI_V4QI, MASK_DSP),
10258  DIRECT_NO_TARGET_BUILTIN (cmp_eq_ph, MIPS_VOID_FTYPE_V2HI_V2HI, MASK_DSP),
10259  DIRECT_NO_TARGET_BUILTIN (cmp_lt_ph, MIPS_VOID_FTYPE_V2HI_V2HI, MASK_DSP),
10260  DIRECT_NO_TARGET_BUILTIN (cmp_le_ph, MIPS_VOID_FTYPE_V2HI_V2HI, MASK_DSP),
10261  DIRECT_BUILTIN (pick_qb, MIPS_V4QI_FTYPE_V4QI_V4QI, MASK_DSP),
10262  DIRECT_BUILTIN (pick_ph, MIPS_V2HI_FTYPE_V2HI_V2HI, MASK_DSP),
10263  DIRECT_BUILTIN (packrl_ph, MIPS_V2HI_FTYPE_V2HI_V2HI, MASK_DSP),
10264  DIRECT_BUILTIN (extr_w, MIPS_SI_FTYPE_DI_SI, MASK_DSP),
10265  DIRECT_BUILTIN (extr_r_w, MIPS_SI_FTYPE_DI_SI, MASK_DSP),
10266  DIRECT_BUILTIN (extr_rs_w, MIPS_SI_FTYPE_DI_SI, MASK_DSP),
10267  DIRECT_BUILTIN (extr_s_h, MIPS_SI_FTYPE_DI_SI, MASK_DSP),
10268  DIRECT_BUILTIN (extp, MIPS_SI_FTYPE_DI_SI, MASK_DSP),
10269  DIRECT_BUILTIN (extpdp, MIPS_SI_FTYPE_DI_SI, MASK_DSP),
10270  DIRECT_BUILTIN (shilo, MIPS_DI_FTYPE_DI_SI, MASK_DSP),
10271  DIRECT_BUILTIN (mthlip, MIPS_DI_FTYPE_DI_SI, MASK_DSP),
10272  DIRECT_NO_TARGET_BUILTIN (wrdsp, MIPS_VOID_FTYPE_SI_SI, MASK_DSP),
10273  DIRECT_BUILTIN (rddsp, MIPS_SI_FTYPE_SI, MASK_DSP),
10274  DIRECT_BUILTIN (lbux, MIPS_SI_FTYPE_PTR_SI, MASK_DSP),
10275  DIRECT_BUILTIN (lhx, MIPS_SI_FTYPE_PTR_SI, MASK_DSP),
10276  DIRECT_BUILTIN (lwx, MIPS_SI_FTYPE_PTR_SI, MASK_DSP),
10277  BPOSGE_BUILTIN (32, MASK_DSP)
10278};
10279
10280/* This helps provide a mapping from builtin function codes to bdesc
10281   arrays.  */
10282
10283struct bdesc_map
10284{
10285  /* The builtin function table that this entry describes.  */
10286  const struct builtin_description *bdesc;
10287
10288  /* The number of entries in the builtin function table.  */
10289  unsigned int size;
10290
10291  /* The target processor that supports these builtin functions.
10292     PROCESSOR_MAX means we enable them for all processors.  */
10293  enum processor_type proc;
10294};
10295
10296static const struct bdesc_map bdesc_arrays[] =
10297{
10298  { mips_bdesc, ARRAY_SIZE (mips_bdesc), PROCESSOR_MAX },
10299  { sb1_bdesc, ARRAY_SIZE (sb1_bdesc), PROCESSOR_SB1 },
10300  { dsp_bdesc, ARRAY_SIZE (dsp_bdesc), PROCESSOR_MAX }
10301};
10302
10303/* Take the head of argument list *ARGLIST and convert it into a form
10304   suitable for input operand OP of instruction ICODE.  Return the value
10305   and point *ARGLIST at the next element of the list.  */
10306
10307static rtx
10308mips_prepare_builtin_arg (enum insn_code icode,
10309			  unsigned int op, tree *arglist)
10310{
10311  rtx value;
10312  enum machine_mode mode;
10313
10314  value = expand_normal (TREE_VALUE (*arglist));
10315  mode = insn_data[icode].operand[op].mode;
10316  if (!insn_data[icode].operand[op].predicate (value, mode))
10317    {
10318      value = copy_to_mode_reg (mode, value);
10319      /* Check the predicate again.  */
10320      if (!insn_data[icode].operand[op].predicate (value, mode))
10321	{
10322	  error ("invalid argument to builtin function");
10323	  return const0_rtx;
10324	}
10325    }
10326
10327  *arglist = TREE_CHAIN (*arglist);
10328  return value;
10329}
10330
10331/* Return an rtx suitable for output operand OP of instruction ICODE.
10332   If TARGET is non-null, try to use it where possible.  */
10333
10334static rtx
10335mips_prepare_builtin_target (enum insn_code icode, unsigned int op, rtx target)
10336{
10337  enum machine_mode mode;
10338
10339  mode = insn_data[icode].operand[op].mode;
10340  if (target == 0 || !insn_data[icode].operand[op].predicate (target, mode))
10341    target = gen_reg_rtx (mode);
10342
10343  return target;
10344}
10345
10346/* Expand builtin functions.  This is called from TARGET_EXPAND_BUILTIN.  */
10347
10348rtx
10349mips_expand_builtin (tree exp, rtx target, rtx subtarget ATTRIBUTE_UNUSED,
10350		     enum machine_mode mode ATTRIBUTE_UNUSED,
10351		     int ignore ATTRIBUTE_UNUSED)
10352{
10353  enum insn_code icode;
10354  enum mips_builtin_type type;
10355  tree fndecl, arglist;
10356  unsigned int fcode;
10357  const struct builtin_description *bdesc;
10358  const struct bdesc_map *m;
10359
10360  fndecl = TREE_OPERAND (TREE_OPERAND (exp, 0), 0);
10361  arglist = TREE_OPERAND (exp, 1);
10362  fcode = DECL_FUNCTION_CODE (fndecl);
10363
10364  bdesc = NULL;
10365  for (m = bdesc_arrays; m < &bdesc_arrays[ARRAY_SIZE (bdesc_arrays)]; m++)
10366    {
10367      if (fcode < m->size)
10368	{
10369	  bdesc = m->bdesc;
10370	  icode = bdesc[fcode].icode;
10371	  type = bdesc[fcode].builtin_type;
10372	  break;
10373	}
10374      fcode -= m->size;
10375    }
10376  if (bdesc == NULL)
10377    return 0;
10378
10379  switch (type)
10380    {
10381    case MIPS_BUILTIN_DIRECT:
10382      return mips_expand_builtin_direct (icode, target, arglist, true);
10383
10384    case MIPS_BUILTIN_DIRECT_NO_TARGET:
10385      return mips_expand_builtin_direct (icode, target, arglist, false);
10386
10387    case MIPS_BUILTIN_MOVT:
10388    case MIPS_BUILTIN_MOVF:
10389      return mips_expand_builtin_movtf (type, icode, bdesc[fcode].cond,
10390					target, arglist);
10391
10392    case MIPS_BUILTIN_CMP_ANY:
10393    case MIPS_BUILTIN_CMP_ALL:
10394    case MIPS_BUILTIN_CMP_UPPER:
10395    case MIPS_BUILTIN_CMP_LOWER:
10396    case MIPS_BUILTIN_CMP_SINGLE:
10397      return mips_expand_builtin_compare (type, icode, bdesc[fcode].cond,
10398					  target, arglist);
10399
10400    case MIPS_BUILTIN_BPOSGE32:
10401      return mips_expand_builtin_bposge (type, target);
10402
10403    default:
10404      return 0;
10405    }
10406}
10407
10408/* Init builtin functions.  This is called from TARGET_INIT_BUILTIN.  */
10409
10410void
10411mips_init_builtins (void)
10412{
10413  const struct builtin_description *d;
10414  const struct bdesc_map *m;
10415  tree types[(int) MIPS_MAX_FTYPE_MAX];
10416  tree V2SF_type_node;
10417  tree V2HI_type_node;
10418  tree V4QI_type_node;
10419  unsigned int offset;
10420
10421  /* We have only builtins for -mpaired-single, -mips3d and -mdsp.  */
10422  if (!TARGET_PAIRED_SINGLE_FLOAT && !TARGET_DSP)
10423    return;
10424
10425  if (TARGET_PAIRED_SINGLE_FLOAT)
10426    {
10427      V2SF_type_node = build_vector_type_for_mode (float_type_node, V2SFmode);
10428
10429      types[MIPS_V2SF_FTYPE_V2SF]
10430	= build_function_type_list (V2SF_type_node, V2SF_type_node, NULL_TREE);
10431
10432      types[MIPS_V2SF_FTYPE_V2SF_V2SF]
10433	= build_function_type_list (V2SF_type_node,
10434				    V2SF_type_node, V2SF_type_node, NULL_TREE);
10435
10436      types[MIPS_V2SF_FTYPE_V2SF_V2SF_INT]
10437	= build_function_type_list (V2SF_type_node,
10438				    V2SF_type_node, V2SF_type_node,
10439				    integer_type_node, NULL_TREE);
10440
10441      types[MIPS_V2SF_FTYPE_V2SF_V2SF_V2SF_V2SF]
10442	= build_function_type_list (V2SF_type_node,
10443				    V2SF_type_node, V2SF_type_node,
10444				    V2SF_type_node, V2SF_type_node, NULL_TREE);
10445
10446      types[MIPS_V2SF_FTYPE_SF_SF]
10447	= build_function_type_list (V2SF_type_node,
10448				    float_type_node, float_type_node, NULL_TREE);
10449
10450      types[MIPS_INT_FTYPE_V2SF_V2SF]
10451	= build_function_type_list (integer_type_node,
10452				    V2SF_type_node, V2SF_type_node, NULL_TREE);
10453
10454      types[MIPS_INT_FTYPE_V2SF_V2SF_V2SF_V2SF]
10455	= build_function_type_list (integer_type_node,
10456				    V2SF_type_node, V2SF_type_node,
10457				    V2SF_type_node, V2SF_type_node, NULL_TREE);
10458
10459      types[MIPS_INT_FTYPE_SF_SF]
10460	= build_function_type_list (integer_type_node,
10461				    float_type_node, float_type_node, NULL_TREE);
10462
10463      types[MIPS_INT_FTYPE_DF_DF]
10464	= build_function_type_list (integer_type_node,
10465				    double_type_node, double_type_node, NULL_TREE);
10466
10467      types[MIPS_SF_FTYPE_V2SF]
10468	= build_function_type_list (float_type_node, V2SF_type_node, NULL_TREE);
10469
10470      types[MIPS_SF_FTYPE_SF]
10471	= build_function_type_list (float_type_node,
10472				    float_type_node, NULL_TREE);
10473
10474      types[MIPS_SF_FTYPE_SF_SF]
10475	= build_function_type_list (float_type_node,
10476				    float_type_node, float_type_node, NULL_TREE);
10477
10478      types[MIPS_DF_FTYPE_DF]
10479	= build_function_type_list (double_type_node,
10480				    double_type_node, NULL_TREE);
10481
10482      types[MIPS_DF_FTYPE_DF_DF]
10483	= build_function_type_list (double_type_node,
10484				    double_type_node, double_type_node, NULL_TREE);
10485    }
10486
10487  if (TARGET_DSP)
10488    {
10489      V2HI_type_node = build_vector_type_for_mode (intHI_type_node, V2HImode);
10490      V4QI_type_node = build_vector_type_for_mode (intQI_type_node, V4QImode);
10491
10492      types[MIPS_V2HI_FTYPE_V2HI_V2HI]
10493	= build_function_type_list (V2HI_type_node,
10494				    V2HI_type_node, V2HI_type_node,
10495				    NULL_TREE);
10496
10497      types[MIPS_SI_FTYPE_SI_SI]
10498	= build_function_type_list (intSI_type_node,
10499				    intSI_type_node, intSI_type_node,
10500				    NULL_TREE);
10501
10502      types[MIPS_V4QI_FTYPE_V4QI_V4QI]
10503	= build_function_type_list (V4QI_type_node,
10504				    V4QI_type_node, V4QI_type_node,
10505				    NULL_TREE);
10506
10507      types[MIPS_SI_FTYPE_V4QI]
10508	= build_function_type_list (intSI_type_node,
10509				    V4QI_type_node,
10510				    NULL_TREE);
10511
10512      types[MIPS_V2HI_FTYPE_V2HI]
10513	= build_function_type_list (V2HI_type_node,
10514				    V2HI_type_node,
10515				    NULL_TREE);
10516
10517      types[MIPS_SI_FTYPE_SI]
10518	= build_function_type_list (intSI_type_node,
10519				    intSI_type_node,
10520				    NULL_TREE);
10521
10522      types[MIPS_V4QI_FTYPE_V2HI_V2HI]
10523	= build_function_type_list (V4QI_type_node,
10524				    V2HI_type_node, V2HI_type_node,
10525				    NULL_TREE);
10526
10527      types[MIPS_V2HI_FTYPE_SI_SI]
10528	= build_function_type_list (V2HI_type_node,
10529				    intSI_type_node, intSI_type_node,
10530				    NULL_TREE);
10531
10532      types[MIPS_SI_FTYPE_V2HI]
10533	= build_function_type_list (intSI_type_node,
10534				    V2HI_type_node,
10535				    NULL_TREE);
10536
10537      types[MIPS_V2HI_FTYPE_V4QI]
10538	= build_function_type_list (V2HI_type_node,
10539				    V4QI_type_node,
10540				    NULL_TREE);
10541
10542      types[MIPS_V4QI_FTYPE_V4QI_SI]
10543	= build_function_type_list (V4QI_type_node,
10544				    V4QI_type_node, intSI_type_node,
10545				    NULL_TREE);
10546
10547      types[MIPS_V2HI_FTYPE_V2HI_SI]
10548	= build_function_type_list (V2HI_type_node,
10549				    V2HI_type_node, intSI_type_node,
10550				    NULL_TREE);
10551
10552      types[MIPS_V2HI_FTYPE_V4QI_V2HI]
10553	= build_function_type_list (V2HI_type_node,
10554				    V4QI_type_node, V2HI_type_node,
10555				    NULL_TREE);
10556
10557      types[MIPS_SI_FTYPE_V2HI_V2HI]
10558	= build_function_type_list (intSI_type_node,
10559				    V2HI_type_node, V2HI_type_node,
10560				    NULL_TREE);
10561
10562      types[MIPS_DI_FTYPE_DI_V4QI_V4QI]
10563	= build_function_type_list (intDI_type_node,
10564				    intDI_type_node, V4QI_type_node, V4QI_type_node,
10565				    NULL_TREE);
10566
10567      types[MIPS_DI_FTYPE_DI_V2HI_V2HI]
10568	= build_function_type_list (intDI_type_node,
10569				    intDI_type_node, V2HI_type_node, V2HI_type_node,
10570				    NULL_TREE);
10571
10572      types[MIPS_DI_FTYPE_DI_SI_SI]
10573	= build_function_type_list (intDI_type_node,
10574				    intDI_type_node, intSI_type_node, intSI_type_node,
10575				    NULL_TREE);
10576
10577      types[MIPS_V4QI_FTYPE_SI]
10578	= build_function_type_list (V4QI_type_node,
10579				    intSI_type_node,
10580				    NULL_TREE);
10581
10582      types[MIPS_V2HI_FTYPE_SI]
10583	= build_function_type_list (V2HI_type_node,
10584				    intSI_type_node,
10585				    NULL_TREE);
10586
10587      types[MIPS_VOID_FTYPE_V4QI_V4QI]
10588	= build_function_type_list (void_type_node,
10589				    V4QI_type_node, V4QI_type_node,
10590				    NULL_TREE);
10591
10592      types[MIPS_SI_FTYPE_V4QI_V4QI]
10593	= build_function_type_list (intSI_type_node,
10594				    V4QI_type_node, V4QI_type_node,
10595				    NULL_TREE);
10596
10597      types[MIPS_VOID_FTYPE_V2HI_V2HI]
10598	= build_function_type_list (void_type_node,
10599				    V2HI_type_node, V2HI_type_node,
10600				    NULL_TREE);
10601
10602      types[MIPS_SI_FTYPE_DI_SI]
10603	= build_function_type_list (intSI_type_node,
10604				    intDI_type_node, intSI_type_node,
10605				    NULL_TREE);
10606
10607      types[MIPS_DI_FTYPE_DI_SI]
10608	= build_function_type_list (intDI_type_node,
10609				    intDI_type_node, intSI_type_node,
10610				    NULL_TREE);
10611
10612      types[MIPS_VOID_FTYPE_SI_SI]
10613	= build_function_type_list (void_type_node,
10614				    intSI_type_node, intSI_type_node,
10615				    NULL_TREE);
10616
10617      types[MIPS_SI_FTYPE_PTR_SI]
10618	= build_function_type_list (intSI_type_node,
10619				    ptr_type_node, intSI_type_node,
10620				    NULL_TREE);
10621
10622      types[MIPS_SI_FTYPE_VOID]
10623	= build_function_type (intSI_type_node, void_list_node);
10624    }
10625
10626  /* Iterate through all of the bdesc arrays, initializing all of the
10627     builtin functions.  */
10628
10629  offset = 0;
10630  for (m = bdesc_arrays; m < &bdesc_arrays[ARRAY_SIZE (bdesc_arrays)]; m++)
10631    {
10632      if (m->proc == PROCESSOR_MAX || (m->proc == mips_arch))
10633	for (d = m->bdesc; d < &m->bdesc[m->size]; d++)
10634	  if ((d->target_flags & target_flags) == d->target_flags)
10635	    lang_hooks.builtin_function (d->name, types[d->function_type],
10636					 d - m->bdesc + offset,
10637					 BUILT_IN_MD, NULL, NULL);
10638      offset += m->size;
10639    }
10640}
10641
10642/* Expand a MIPS_BUILTIN_DIRECT function.  ICODE is the code of the
10643   .md pattern and ARGLIST is the list of function arguments.  TARGET,
10644   if nonnull, suggests a good place to put the result.
10645   HAS_TARGET indicates the function must return something.  */
10646
10647static rtx
10648mips_expand_builtin_direct (enum insn_code icode, rtx target, tree arglist,
10649			    bool has_target)
10650{
10651  rtx ops[MAX_RECOG_OPERANDS];
10652  int i = 0;
10653
10654  if (has_target)
10655    {
10656      /* We save target to ops[0].  */
10657      ops[0] = mips_prepare_builtin_target (icode, 0, target);
10658      i = 1;
10659    }
10660
10661  /* We need to test if arglist is not zero.  Some instructions have extra
10662     clobber registers.  */
10663  for (; i < insn_data[icode].n_operands && arglist != 0; i++)
10664    ops[i] = mips_prepare_builtin_arg (icode, i, &arglist);
10665
10666  switch (i)
10667    {
10668    case 2:
10669      emit_insn (GEN_FCN (icode) (ops[0], ops[1]));
10670      break;
10671
10672    case 3:
10673      emit_insn (GEN_FCN (icode) (ops[0], ops[1], ops[2]));
10674      break;
10675
10676    case 4:
10677      emit_insn (GEN_FCN (icode) (ops[0], ops[1], ops[2], ops[3]));
10678      break;
10679
10680    default:
10681      gcc_unreachable ();
10682    }
10683  return target;
10684}
10685
10686/* Expand a __builtin_mips_movt_*_ps() or __builtin_mips_movf_*_ps()
10687   function (TYPE says which).  ARGLIST is the list of arguments to the
10688   function, ICODE is the instruction that should be used to compare
10689   the first two arguments, and COND is the condition it should test.
10690   TARGET, if nonnull, suggests a good place to put the result.  */
10691
10692static rtx
10693mips_expand_builtin_movtf (enum mips_builtin_type type,
10694			   enum insn_code icode, enum mips_fp_condition cond,
10695			   rtx target, tree arglist)
10696{
10697  rtx cmp_result, op0, op1;
10698
10699  cmp_result = mips_prepare_builtin_target (icode, 0, 0);
10700  op0 = mips_prepare_builtin_arg (icode, 1, &arglist);
10701  op1 = mips_prepare_builtin_arg (icode, 2, &arglist);
10702  emit_insn (GEN_FCN (icode) (cmp_result, op0, op1, GEN_INT (cond)));
10703
10704  icode = CODE_FOR_mips_cond_move_tf_ps;
10705  target = mips_prepare_builtin_target (icode, 0, target);
10706  if (type == MIPS_BUILTIN_MOVT)
10707    {
10708      op1 = mips_prepare_builtin_arg (icode, 2, &arglist);
10709      op0 = mips_prepare_builtin_arg (icode, 1, &arglist);
10710    }
10711  else
10712    {
10713      op0 = mips_prepare_builtin_arg (icode, 1, &arglist);
10714      op1 = mips_prepare_builtin_arg (icode, 2, &arglist);
10715    }
10716  emit_insn (gen_mips_cond_move_tf_ps (target, op0, op1, cmp_result));
10717  return target;
10718}
10719
10720/* Move VALUE_IF_TRUE into TARGET if CONDITION is true; move VALUE_IF_FALSE
10721   into TARGET otherwise.  Return TARGET.  */
10722
10723static rtx
10724mips_builtin_branch_and_move (rtx condition, rtx target,
10725			      rtx value_if_true, rtx value_if_false)
10726{
10727  rtx true_label, done_label;
10728
10729  true_label = gen_label_rtx ();
10730  done_label = gen_label_rtx ();
10731
10732  /* First assume that CONDITION is false.  */
10733  emit_move_insn (target, value_if_false);
10734
10735  /* Branch to TRUE_LABEL if CONDITION is true and DONE_LABEL otherwise.  */
10736  emit_jump_insn (gen_condjump (condition, true_label));
10737  emit_jump_insn (gen_jump (done_label));
10738  emit_barrier ();
10739
10740  /* Fix TARGET if CONDITION is true.  */
10741  emit_label (true_label);
10742  emit_move_insn (target, value_if_true);
10743
10744  emit_label (done_label);
10745  return target;
10746}
10747
10748/* Expand a comparison builtin of type BUILTIN_TYPE.  ICODE is the code
10749   of the comparison instruction and COND is the condition it should test.
10750   ARGLIST is the list of function arguments and TARGET, if nonnull,
10751   suggests a good place to put the boolean result.  */
10752
10753static rtx
10754mips_expand_builtin_compare (enum mips_builtin_type builtin_type,
10755			     enum insn_code icode, enum mips_fp_condition cond,
10756			     rtx target, tree arglist)
10757{
10758  rtx offset, condition, cmp_result, ops[MAX_RECOG_OPERANDS];
10759  int i;
10760
10761  if (target == 0 || GET_MODE (target) != SImode)
10762    target = gen_reg_rtx (SImode);
10763
10764  /* Prepare the operands to the comparison.  */
10765  cmp_result = mips_prepare_builtin_target (icode, 0, 0);
10766  for (i = 1; i < insn_data[icode].n_operands - 1; i++)
10767    ops[i] = mips_prepare_builtin_arg (icode, i, &arglist);
10768
10769  switch (insn_data[icode].n_operands)
10770    {
10771    case 4:
10772      emit_insn (GEN_FCN (icode) (cmp_result, ops[1], ops[2], GEN_INT (cond)));
10773      break;
10774
10775    case 6:
10776      emit_insn (GEN_FCN (icode) (cmp_result, ops[1], ops[2],
10777				  ops[3], ops[4], GEN_INT (cond)));
10778      break;
10779
10780    default:
10781      gcc_unreachable ();
10782    }
10783
10784  /* If the comparison sets more than one register, we define the result
10785     to be 0 if all registers are false and -1 if all registers are true.
10786     The value of the complete result is indeterminate otherwise.  */
10787  switch (builtin_type)
10788    {
10789    case MIPS_BUILTIN_CMP_ALL:
10790      condition = gen_rtx_NE (VOIDmode, cmp_result, constm1_rtx);
10791      return mips_builtin_branch_and_move (condition, target,
10792					   const0_rtx, const1_rtx);
10793
10794    case MIPS_BUILTIN_CMP_UPPER:
10795    case MIPS_BUILTIN_CMP_LOWER:
10796      offset = GEN_INT (builtin_type == MIPS_BUILTIN_CMP_UPPER);
10797      condition = gen_single_cc (cmp_result, offset);
10798      return mips_builtin_branch_and_move (condition, target,
10799					   const1_rtx, const0_rtx);
10800
10801    default:
10802      condition = gen_rtx_NE (VOIDmode, cmp_result, const0_rtx);
10803      return mips_builtin_branch_and_move (condition, target,
10804					   const1_rtx, const0_rtx);
10805    }
10806}
10807
10808/* Expand a bposge builtin of type BUILTIN_TYPE.  TARGET, if nonnull,
10809   suggests a good place to put the boolean result.  */
10810
10811static rtx
10812mips_expand_builtin_bposge (enum mips_builtin_type builtin_type, rtx target)
10813{
10814  rtx condition, cmp_result;
10815  int cmp_value;
10816
10817  if (target == 0 || GET_MODE (target) != SImode)
10818    target = gen_reg_rtx (SImode);
10819
10820  cmp_result = gen_rtx_REG (CCDSPmode, CCDSP_PO_REGNUM);
10821
10822  if (builtin_type == MIPS_BUILTIN_BPOSGE32)
10823    cmp_value = 32;
10824  else
10825    gcc_assert (0);
10826
10827  condition = gen_rtx_GE (VOIDmode, cmp_result, GEN_INT (cmp_value));
10828  return mips_builtin_branch_and_move (condition, target,
10829				       const1_rtx, const0_rtx);
10830}
10831
10832/* Set SYMBOL_REF_FLAGS for the SYMBOL_REF inside RTL, which belongs to DECL.
10833   FIRST is true if this is the first time handling this decl.  */
10834
10835static void
10836mips_encode_section_info (tree decl, rtx rtl, int first)
10837{
10838  default_encode_section_info (decl, rtl, first);
10839
10840  if (TREE_CODE (decl) == FUNCTION_DECL
10841      && lookup_attribute ("long_call", TYPE_ATTRIBUTES (TREE_TYPE (decl))))
10842    {
10843      rtx symbol = XEXP (rtl, 0);
10844      SYMBOL_REF_FLAGS (symbol) |= SYMBOL_FLAG_LONG_CALL;
10845    }
10846}
10847
10848/* Implement TARGET_EXTRA_LIVE_ON_ENTRY.  PIC_FUNCTION_ADDR_REGNUM is live
10849   on entry to a function when generating -mshared abicalls code.  */
10850
10851static void
10852mips_extra_live_on_entry (bitmap regs)
10853{
10854  if (TARGET_ABICALLS && !TARGET_ABSOLUTE_ABICALLS)
10855    bitmap_set_bit (regs, PIC_FUNCTION_ADDR_REGNUM);
10856}
10857
10858/* SImode values are represented as sign-extended to DImode.  */
10859
10860int
10861mips_mode_rep_extended (enum machine_mode mode, enum machine_mode mode_rep)
10862{
10863  if (TARGET_64BIT && mode == SImode && mode_rep == DImode)
10864    return SIGN_EXTEND;
10865
10866  return UNKNOWN;
10867}
10868
10869#include "gt-mips.h"
10870