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