/* Subroutines used for MIPS code generation.
Copyright (C) 1989-2014 Free Software Foundation, Inc.
Contributed by A. Lichnewsky, lich@inria.inria.fr.
Changes by Michael Meissner, meissner@osf.org.
64-bit r4000 support by Ian Lance Taylor, ian@cygnus.com, and
Brendan Eich, brendan@microunity.com.
This file is part of GCC.
GCC is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 3, or (at your option)
any later version.
GCC is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with GCC; see the file COPYING3. If not see
<http://www.gnu.org/licenses/>. */
#include "config.h"
#include "system.h"
#include "coretypes.h"
#include "tm.h"
#include "rtl.h"
#include "regs.h"
#include "hard-reg-set.h"
#include "insn-config.h"
#include "conditions.h"
#include "insn-attr.h"
#include "recog.h"
#include "output.h"
#include "tree.h"
#include "varasm.h"
#include "stringpool.h"
#include "stor-layout.h"
#include "calls.h"
#include "function.h"
#include "expr.h"
#include "optabs.h"
#include "libfuncs.h"
#include "flags.h"
#include "reload.h"
#include "tm_p.h"
#include "ggc.h"
#include "gstab.h"
#include "hash-table.h"
#include "debug.h"
#include "target.h"
#include "target-def.h"
#include "common/common-target.h"
#include "langhooks.h"
#include "sched-int.h"
#include "pointer-set.h"
#include "vec.h"
#include "basic-block.h"
#include "tree-ssa-alias.h"
#include "internal-fn.h"
#include "gimple-fold.h"
#include "tree-eh.h"
#include "gimple-expr.h"
#include "is-a.h"
#include "gimple.h"
#include "gimplify.h"
#include "bitmap.h"
#include "diagnostic.h"
#include "target-globals.h"
#include "opts.h"
#include "tree-pass.h"
#include "context.h"
/* Definitions used in ready queue reordering for first scheduling pass. */
static int *level = NULL;
static int *consumer_luid = NULL;
#define LEVEL(INSN) \
level[INSN_UID ((INSN))]
#define CONSUMER_LUID(INSN) \
consumer_luid[INSN_UID ((INSN))]
/* True if X is an UNSPEC wrapper around a SYMBOL_REF or LABEL_REF. */
#define UNSPEC_ADDRESS_P(X) \
(GET_CODE (X) == UNSPEC \
&& XINT (X, 1) >= UNSPEC_ADDRESS_FIRST \
&& XINT (X, 1) < UNSPEC_ADDRESS_FIRST + NUM_SYMBOL_TYPES)
/* Extract the symbol or label from UNSPEC wrapper X. */
#define UNSPEC_ADDRESS(X) \
XVECEXP (X, 0, 0)
/* Extract the symbol type from UNSPEC wrapper X. */
#define UNSPEC_ADDRESS_TYPE(X) \
((enum mips_symbol_type) (XINT (X, 1) - UNSPEC_ADDRESS_FIRST))
/* The maximum distance between the top of the stack frame and the
value $sp has when we save and restore registers.
The value for normal-mode code must be a SMALL_OPERAND and must
preserve the maximum stack alignment. We therefore use a value
of 0x7ff0 in this case.
microMIPS LWM and SWM support 12-bit offsets (from -0x800 to 0x7ff),
so we use a maximum of 0x7f0 for TARGET_MICROMIPS.
MIPS16e SAVE and RESTORE instructions can adjust the stack pointer by
up to 0x7f8 bytes and can usually save or restore all the registers
that we need to save or restore. (Note that we can only use these
instructions for o32, for which the stack alignment is 8 bytes.)
We use a maximum gap of 0x100 or 0x400 for MIPS16 code when SAVE and
RESTORE are not available. We can then use unextended instructions
to save and restore registers, and to allocate and deallocate the top
part of the frame. */
#define MIPS_MAX_FIRST_STACK_STEP \
(!TARGET_COMPRESSION ? 0x7ff0 \
: TARGET_MICROMIPS || GENERATE_MIPS16E_SAVE_RESTORE ? 0x7f8 \
: TARGET_64BIT ? 0x100 : 0x400)
/* True if INSN is a mips.md pattern or asm statement. */
/* ??? This test exists through the compiler, perhaps it should be
moved to rtl.h. */
#define USEFUL_INSN_P(INSN) \
(NONDEBUG_INSN_P (INSN) \
&& GET_CODE (PATTERN (INSN)) != USE \
&& GET_CODE (PATTERN (INSN)) != CLOBBER)
/* If INSN is a delayed branch sequence, return the first instruction
in the sequence, otherwise return INSN itself. */
#define SEQ_BEGIN(INSN) \
(INSN_P (INSN) && GET_CODE (PATTERN (INSN)) == SEQUENCE \
? XVECEXP (PATTERN (INSN), 0, 0) \
: (INSN))
/* Likewise for the last instruction in a delayed branch sequence. */
#define SEQ_END(INSN) \
(INSN_P (INSN) && GET_CODE (PATTERN (INSN)) == SEQUENCE \
? XVECEXP (PATTERN (INSN), 0, XVECLEN (PATTERN (INSN), 0) - 1) \
: (INSN))
/* Execute the following loop body with SUBINSN set to each instruction
between SEQ_BEGIN (INSN) and SEQ_END (INSN) inclusive. */
#define FOR_EACH_SUBINSN(SUBINSN, INSN) \
for ((SUBINSN) = SEQ_BEGIN (INSN); \
(SUBINSN) != NEXT_INSN (SEQ_END (INSN)); \
(SUBINSN) = NEXT_INSN (SUBINSN))
/* True if bit BIT is set in VALUE. */
#define BITSET_P(VALUE, BIT) (((VALUE) & (1 << (BIT))) != 0)
/* Return the opcode for a ptr_mode load of the form:
l[wd] DEST, OFFSET(BASE). */
#define MIPS_LOAD_PTR(DEST, OFFSET, BASE) \
(((ptr_mode == DImode ? 0x37 : 0x23) << 26) \
| ((BASE) << 21) \
| ((DEST) << 16) \
| (OFFSET))
/* Return the opcode to move register SRC into register DEST. */
#define MIPS_MOVE(DEST, SRC) \
((TARGET_64BIT ? 0x2d : 0x21) \
| ((DEST) << 11) \
| ((SRC) << 21))
/* Return the opcode for:
lui DEST, VALUE. */
#define MIPS_LUI(DEST, VALUE) \
((0xf << 26) | ((DEST) << 16) | (VALUE))
/* Return the opcode to jump to register DEST. When the JR opcode is not
available use JALR $0, DEST. */
#define MIPS_JR(DEST) \
(TARGET_CB_ALWAYS ? ((0x1b << 27) | ((DEST) << 16)) \
: (((DEST) << 21) | (ISA_HAS_JR ? 0x8 : 0x9)))
/* Return the opcode for:
bal . + (1 + OFFSET) * 4. */
#define MIPS_BAL(OFFSET) \
((0x1 << 26) | (0x11 << 16) | (OFFSET))
/* Return the usual opcode for a nop. */
#define MIPS_NOP 0
/* Classifies an address.
ADDRESS_REG
A natural register + offset address. The register satisfies
mips_valid_base_register_p and the offset is a const_arith_operand.
ADDRESS_LO_SUM
A LO_SUM rtx. The first operand is a valid base register and
the second operand is a symbolic address.
ADDRESS_CONST_INT
A signed 16-bit constant address.
ADDRESS_SYMBOLIC:
A constant symbolic address. */
enum mips_address_type {
ADDRESS_REG,
ADDRESS_LO_SUM,
ADDRESS_CONST_INT,
ADDRESS_SYMBOLIC
};
/* Macros to create an enumeration identifier for a function prototype. */
#define MIPS_FTYPE_NAME1(A, B) MIPS_##A##_FTYPE_##B
#define MIPS_FTYPE_NAME2(A, B, C) MIPS_##A##_FTYPE_##B##_##C
#define MIPS_FTYPE_NAME3(A, B, C, D) MIPS_##A##_FTYPE_##B##_##C##_##D
#define MIPS_FTYPE_NAME4(A, B, C, D, E) MIPS_##A##_FTYPE_##B##_##C##_##D##_##E
/* Classifies the prototype of a built-in function. */
enum mips_function_type {
#define DEF_MIPS_FTYPE(NARGS, LIST) MIPS_FTYPE_NAME##NARGS LIST,
#include "config/mips/mips-ftypes.def"
#undef DEF_MIPS_FTYPE
MIPS_MAX_FTYPE_MAX
};
/* Specifies how a built-in function should be converted into rtl. */
enum mips_builtin_type {
/* The function corresponds directly to an .md pattern. The return
value is mapped to operand 0 and the arguments are mapped to
operands 1 and above. */
MIPS_BUILTIN_DIRECT,
/* The function corresponds directly to an .md pattern. There is no return
value and the arguments are mapped to operands 0 and above. */
MIPS_BUILTIN_DIRECT_NO_TARGET,
/* The function corresponds to a comparison instruction followed by
a mips_cond_move_tf_ps pattern. The first two arguments are the
values to compare and the second two arguments are the vector
operands for the movt.ps or movf.ps instruction (in assembly order). */
MIPS_BUILTIN_MOVF,
MIPS_BUILTIN_MOVT,
/* The function corresponds to a V2SF comparison instruction. Operand 0
of this instruction is the result of the comparison, which has mode
CCV2 or CCV4. The function arguments are mapped to operands 1 and
above. The function's return value is an SImode boolean that is
true under the following conditions:
MIPS_BUILTIN_CMP_ANY: one of the registers is true
MIPS_BUILTIN_CMP_ALL: all of the registers are true
MIPS_BUILTIN_CMP_LOWER: the first register is true
MIPS_BUILTIN_CMP_UPPER: the second register is true. */
MIPS_BUILTIN_CMP_ANY,
MIPS_BUILTIN_CMP_ALL,
MIPS_BUILTIN_CMP_UPPER,
MIPS_BUILTIN_CMP_LOWER,
/* As above, but the instruction only sets a single $fcc register. */
MIPS_BUILTIN_CMP_SINGLE,
/* For generating bposge32 branch instructions in MIPS32 DSP ASE. */
MIPS_BUILTIN_BPOSGE32
};
/* Invoke MACRO (COND) for each C.cond.fmt condition. */
#define MIPS_FP_CONDITIONS(MACRO) \
MACRO (f), \
MACRO (un), \
MACRO (eq), \
MACRO (ueq), \
MACRO (olt), \
MACRO (ult), \
MACRO (ole), \
MACRO (ule), \
MACRO (sf), \
MACRO (ngle), \
MACRO (seq), \
MACRO (ngl), \
MACRO (lt), \
MACRO (nge), \
MACRO (le), \
MACRO (ngt)
/* Enumerates the codes above as MIPS_FP_COND_<X>. */
#define DECLARE_MIPS_COND(X) MIPS_FP_COND_ ## X
enum mips_fp_condition {
MIPS_FP_CONDITIONS (DECLARE_MIPS_COND)
};
#undef DECLARE_MIPS_COND
/* Index X provides the string representation of MIPS_FP_COND_<X>. */
#define STRINGIFY(X) #X
static const char *const mips_fp_conditions[] = {
MIPS_FP_CONDITIONS (STRINGIFY)
};
#undef STRINGIFY
/* A class used to control a comdat-style stub that we output in each
translation unit that needs it. */
class mips_one_only_stub {
public:
virtual ~mips_one_only_stub () {}
/* Return the name of the stub. */
virtual const char *get_name () = 0;
/* Output the body of the function to asm_out_file. */
virtual void output_body () = 0;
};
/* Tuning information that is automatically derived from other sources
(such as the scheduler). */
static struct {
/* The architecture and tuning settings that this structure describes. */
enum processor arch;
enum processor tune;
/* True if this structure describes MIPS16 settings. */
bool mips16_p;
/* True if the structure has been initialized. */
bool initialized_p;
/* True if "MULT $0, $0" is preferable to "MTLO $0; MTHI $0"
when optimizing for speed. */
bool fast_mult_zero_zero_p;
} mips_tuning_info;
/* Information about a function's frame layout. */
struct GTY(()) mips_frame_info {
/* The size of the frame in bytes. */
HOST_WIDE_INT total_size;
/* The number of bytes allocated to variables. */
HOST_WIDE_INT var_size;
/* The number of bytes allocated to outgoing function arguments. */
HOST_WIDE_INT args_size;
/* The number of bytes allocated to the .cprestore slot, or 0 if there
is no such slot. */
HOST_WIDE_INT cprestore_size;
/* Bit X is set if the function saves or restores GPR X. */
unsigned int mask;
/* Likewise FPR X. */
unsigned int fmask;
/* Likewise doubleword accumulator X ($acX). */
unsigned int acc_mask;
/* The number of GPRs, FPRs, doubleword accumulators and COP0
registers saved. */
unsigned int num_gp;
unsigned int num_fp;
unsigned int num_acc;
unsigned int num_cop0_regs;
/* The offset of the topmost GPR, FPR, accumulator and COP0-register
save slots from the top of the frame, or zero if no such slots are
needed. */
HOST_WIDE_INT gp_save_offset;
HOST_WIDE_INT fp_save_offset;
HOST_WIDE_INT acc_save_offset;
HOST_WIDE_INT cop0_save_offset;
/* Likewise, but giving offsets from the bottom of the frame. */
HOST_WIDE_INT gp_sp_offset;
HOST_WIDE_INT fp_sp_offset;
HOST_WIDE_INT acc_sp_offset;
HOST_WIDE_INT cop0_sp_offset;
/* Similar, but the value passed to _mcount. */
HOST_WIDE_INT ra_fp_offset;
/* The offset of arg_pointer_rtx from the bottom of the frame. */
HOST_WIDE_INT arg_pointer_offset;
/* The offset of hard_frame_pointer_rtx from the bottom of the frame. */
HOST_WIDE_INT hard_frame_pointer_offset;
};
struct GTY(()) machine_function {
/* The next floating-point condition-code register to allocate
for ISA_HAS_8CC targets, relative to ST_REG_FIRST. */
unsigned int next_fcc;
/* The register returned by mips16_gp_pseudo_reg; see there for details. */
rtx mips16_gp_pseudo_rtx;
/* The number of extra stack bytes taken up by register varargs.
This area is allocated by the callee at the very top of the frame. */
int varargs_size;
/* The current frame information, calculated by mips_compute_frame_info. */
struct mips_frame_info frame;
/* The register to use as the function's global pointer, or INVALID_REGNUM
if the function doesn't need one. */
unsigned int global_pointer;
/* How many instructions it takes to load a label into $AT, or 0 if
this property hasn't yet been calculated. */
unsigned int load_label_num_insns;
/* True if mips_adjust_insn_length should ignore an instruction's
hazard attribute. */
bool ignore_hazard_length_p;
/* True if the whole function is suitable for .set noreorder and
.set nomacro. */
bool all_noreorder_p;
/* True if the function has "inflexible" and "flexible" references
to the global pointer. See mips_cfun_has_inflexible_gp_ref_p
and mips_cfun_has_flexible_gp_ref_p for details. */
bool has_inflexible_gp_insn_p;
bool has_flexible_gp_insn_p;
/* True if the function's prologue must load the global pointer
value into pic_offset_table_rtx and store the same value in
the function's cprestore slot (if any). Even if this value
is currently false, we may decide to set it to true later;
see mips_must_initialize_gp_p () for details. */
bool must_initialize_gp_p;
/* True if the current function must restore $gp after any potential
clobber. This value is only meaningful during the first post-epilogue
split_insns pass; see mips_must_initialize_gp_p () for details. */
bool must_restore_gp_when_clobbered_p;
/* True if this is an interrupt handler. */
bool interrupt_handler_p;
/* True if this is an interrupt handler that uses shadow registers. */
bool use_shadow_register_set_p;
/* True if this is an interrupt handler that should keep interrupts
masked. */
bool keep_interrupts_masked_p;
/* True if this is an interrupt handler that should use DERET
instead of ERET. */
bool use_debug_exception_return_p;
};
/* Information about a single argument. */
struct mips_arg_info {
/* True if the argument is passed in a floating-point register, or
would have been if we hadn't run out of registers. */
bool fpr_p;
/* The number of words passed in registers, rounded up. */
unsigned int reg_words;
/* For EABI, the offset of the first register from GP_ARG_FIRST or
FP_ARG_FIRST. For other ABIs, the offset of the first register from
the start of the ABI's argument structure (see the CUMULATIVE_ARGS
comment for details).
The value is MAX_ARGS_IN_REGISTERS if the argument is passed entirely
on the stack. */
unsigned int reg_offset;
/* The number of words that must be passed on the stack, rounded up. */
unsigned int stack_words;
/* The offset from the start of the stack overflow area of the argument's
first stack word. Only meaningful when STACK_WORDS is nonzero. */
unsigned int stack_offset;
};
/* Information about an address described by mips_address_type.
ADDRESS_CONST_INT
No fields are used.
ADDRESS_REG
REG is the base register and OFFSET is the constant offset.
ADDRESS_LO_SUM
REG and OFFSET are the operands to the LO_SUM and SYMBOL_TYPE
is the type of symbol it references.
ADDRESS_SYMBOLIC
SYMBOL_TYPE is the type of symbol that the address references. */
struct mips_address_info {
enum mips_address_type type;
rtx reg;
rtx offset;
enum mips_symbol_type symbol_type;
};
/* One stage in a constant building sequence. These sequences have
the form:
A = VALUE[0]
A = A CODE[1] VALUE[1]
A = A CODE[2] VALUE[2]
...
where A is an accumulator, each CODE[i] is a binary rtl operation
and each VALUE[i] is a constant integer. CODE[0] is undefined. */
struct mips_integer_op {
enum rtx_code code;
unsigned HOST_WIDE_INT value;
};
/* The largest number of operations needed to load an integer constant.
The worst accepted case for 64-bit constants is LUI,ORI,SLL,ORI,SLL,ORI.
When the lowest bit is clear, we can try, but reject a sequence with
an extra SLL at the end. */
#define MIPS_MAX_INTEGER_OPS 7
/* Information about a MIPS16e SAVE or RESTORE instruction. */
struct mips16e_save_restore_info {
/* The number of argument registers saved by a SAVE instruction.
0 for RESTORE instructions. */
unsigned int nargs;
/* Bit X is set if the instruction saves or restores GPR X. */
unsigned int mask;
/* The total number of bytes to allocate. */
HOST_WIDE_INT size;
};
/* Costs of various operations on the different architectures. */
struct mips_rtx_cost_data
{
unsigned short fp_add;
unsigned short fp_mult_sf;
unsigned short fp_mult_df;
unsigned short fp_div_sf;
unsigned short fp_div_df;
unsigned short int_mult_si;
unsigned short int_mult_di;
unsigned short int_div_si;
unsigned short int_div_di;
unsigned short branch_cost;
unsigned short memory_latency;
};
/* Global variables for machine-dependent things. */
/* The -G setting, or the configuration's default small-data limit if
no -G option is given. */
static unsigned int mips_small_data_threshold;
/* The number of file directives written by mips_output_filename. */
int num_source_filenames;
/* The name that appeared in the last .file directive written by
mips_output_filename, or "" if mips_output_filename hasn't
written anything yet. */
const char *current_function_file = "";
/* Arrays that map GCC register numbers to debugger register numbers. */
int mips_dbx_regno[FIRST_PSEUDO_REGISTER];
int mips_dwarf_regno[FIRST_PSEUDO_REGISTER];
/* Information about the current function's epilogue, used only while
expanding it. */
static struct {
/* A list of queued REG_CFA_RESTORE notes. */
rtx cfa_restores;
/* The CFA is currently defined as CFA_REG + CFA_OFFSET. */
rtx cfa_reg;
HOST_WIDE_INT cfa_offset;
/* The offset of the CFA from the stack pointer while restoring
registers. */
HOST_WIDE_INT cfa_restore_sp_offset;
} mips_epilogue;
/* The nesting depth of the PRINT_OPERAND '%(', '%<' and '%[' constructs. */
struct mips_asm_switch mips_noreorder = { "reorder", 0 };
struct mips_asm_switch mips_nomacro = { "macro", 0 };
struct mips_asm_switch mips_noat = { "at", 0 };
/* True if we're writing out a branch-likely instruction rather than a
normal branch. */
static bool mips_branch_likely;
/* The current instruction-set architecture. */
enum processor mips_arch;
const struct mips_cpu_info *mips_arch_info;
/* The processor that we should tune the code for. */
enum processor mips_tune;
const struct mips_cpu_info *mips_tune_info;
/* The ISA level associated with mips_arch. */
int mips_isa;
/* The ISA revision level. This is 0 for MIPS I to V and N for
MIPS{32,64}rN. */
int mips_isa_rev;
/* The architecture selected by -mipsN, or null if -mipsN wasn't used. */
static const struct mips_cpu_info *mips_isa_option_info;
/* Which cost information to use. */
static const struct mips_rtx_cost_data *mips_cost;
/* The ambient target flags, excluding MASK_MIPS16. */
static int mips_base_target_flags;
/* The default compression mode. */
unsigned int mips_base_compression_flags;
/* The ambient values of other global variables. */
static int mips_base_schedule_insns; /* flag_schedule_insns */
static int mips_base_reorder_blocks_and_partition; /* flag_reorder... */
static int mips_base_move_loop_invariants; /* flag_move_loop_invariants */
static int mips_base_align_loops; /* align_loops */
static int mips_base_align_jumps; /* align_jumps */
static int mips_base_align_functions; /* align_functions */
/* Index [M][R] is true if register R is allowed to hold a value of mode M. */
bool mips_hard_regno_mode_ok[(int) MAX_MACHINE_MODE][FIRST_PSEUDO_REGISTER];
/* Index C is true if character C is a valid PRINT_OPERAND punctation
character. */
static bool mips_print_operand_punct[256];
static GTY (()) int mips_output_filename_first_time = 1;
/* mips_split_p[X] is true if symbols of type X can be split by
mips_split_symbol. */
bool mips_split_p[NUM_SYMBOL_TYPES];
/* mips_split_hi_p[X] is true if the high parts of symbols of type X
can be split by mips_split_symbol. */
bool mips_split_hi_p[NUM_SYMBOL_TYPES];
/* mips_use_pcrel_pool_p[X] is true if symbols of type X should be
forced into a PC-relative constant pool. */
bool mips_use_pcrel_pool_p[NUM_SYMBOL_TYPES];
/* mips_lo_relocs[X] is the relocation to use when a symbol of type X
appears in a LO_SUM. It can be null if such LO_SUMs aren't valid or
if they are matched by a special .md file pattern. */
const char *mips_lo_relocs[NUM_SYMBOL_TYPES];
/* Likewise for HIGHs. */
const char *mips_hi_relocs[NUM_SYMBOL_TYPES];
/* Target state for MIPS16. */
struct target_globals *mips16_globals;
/* Cached value of can_issue_more. This is cached in mips_variable_issue hook
and returned from mips_sched_reorder2. */
static int cached_can_issue_more;
/* The stubs for various MIPS16 support functions, if used. */
static mips_one_only_stub *mips16_rdhwr_stub;
static mips_one_only_stub *mips16_get_fcsr_stub;
static mips_one_only_stub *mips16_set_fcsr_stub;
/* Index R is the smallest register class that contains register R. */
const enum reg_class mips_regno_to_class[FIRST_PSEUDO_REGISTER] = {
LEA_REGS, LEA_REGS, M16_STORE_REGS, V1_REG,
M16_STORE_REGS, M16_STORE_REGS, M16_STORE_REGS, M16_STORE_REGS,
LEA_REGS, LEA_REGS, LEA_REGS, LEA_REGS,
LEA_REGS, LEA_REGS, LEA_REGS, LEA_REGS,
M16_REGS, M16_STORE_REGS, LEA_REGS, LEA_REGS,
LEA_REGS, LEA_REGS, LEA_REGS, LEA_REGS,
T_REG, PIC_FN_ADDR_REG, LEA_REGS, LEA_REGS,
LEA_REGS, M16_SP_REGS, LEA_REGS, LEA_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
FP_REGS, FP_REGS, FP_REGS, FP_REGS,
MD0_REG, MD1_REG, NO_REGS, ST_REGS,
ST_REGS, ST_REGS, ST_REGS, ST_REGS,
ST_REGS, ST_REGS, ST_REGS, NO_REGS,
NO_REGS, FRAME_REGS, FRAME_REGS, NO_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP0_REGS, COP0_REGS, COP0_REGS, COP0_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP2_REGS, COP2_REGS, COP2_REGS, COP2_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
COP3_REGS, COP3_REGS, COP3_REGS, COP3_REGS,
DSP_ACC_REGS, DSP_ACC_REGS, DSP_ACC_REGS, DSP_ACC_REGS,
DSP_ACC_REGS, DSP_ACC_REGS, ALL_REGS, ALL_REGS,
ALL_REGS, ALL_REGS, ALL_REGS, ALL_REGS
};
/* The value of TARGET_ATTRIBUTE_TABLE. */
static const struct attribute_spec mips_attribute_table[] = {
/* { name, min_len, max_len, decl_req, type_req, fn_type_req, handler,
om_diagnostic } */
{ "long_call", 0, 0, false, true, true, NULL, false },
{ "far", 0, 0, false, true, true, NULL, false },
{ "near", 0, 0, false, true, true, NULL, false },
/* We would really like to treat "mips16" and "nomips16" as type
attributes, but GCC doesn't provide the hooks we need to support
the right conversion rules. As declaration attributes, they affect
code generation but don't carry other semantics. */
{ "mips16", 0, 0, true, false, false, NULL, false },
{ "nomips16", 0, 0, true, false, false, NULL, false },
{ "micromips", 0, 0, true, false, false, NULL, false },
{ "nomicromips", 0, 0, true, false, false, NULL, false },
{ "nocompression", 0, 0, true, false, false, NULL, false },
/* Allow functions to be specified as interrupt handlers */
{ "interrupt", 0, 0, false, true, true, NULL, false },
{ "use_shadow_register_set", 0, 0, false, true, true, NULL, false },
{ "keep_interrupts_masked", 0, 0, false, true, true, NULL, false },
{ "use_debug_exception_return", 0, 0, false, true, true, NULL, false },
{ NULL, 0, 0, false, false, false, NULL, false }
};
/* A table describing all the processors GCC knows about; see
mips-cpus.def for details. */
static const struct mips_cpu_info mips_cpu_info_table[] = {
#define MIPS_CPU(NAME, CPU, ISA, FLAGS) \
{ NAME, CPU, ISA, FLAGS },
#include "mips-cpus.def"
#undef MIPS_CPU
};
/* Default costs. If these are used for a processor we should look
up the actual costs. */
#define DEFAULT_COSTS COSTS_N_INSNS (6), /* fp_add */ \
COSTS_N_INSNS (7), /* fp_mult_sf */ \
COSTS_N_INSNS (8), /* fp_mult_df */ \
COSTS_N_INSNS (23), /* fp_div_sf */ \
COSTS_N_INSNS (36), /* fp_div_df */ \
COSTS_N_INSNS (10), /* int_mult_si */ \
COSTS_N_INSNS (10), /* int_mult_di */ \
COSTS_N_INSNS (69), /* int_div_si */ \
COSTS_N_INSNS (69), /* int_div_di */ \
2, /* branch_cost */ \
4 /* memory_latency */
/* Floating-point costs for processors without an FPU. Just assume that
all floating-point libcalls are very expensive. */
#define SOFT_FP_COSTS COSTS_N_INSNS (256), /* fp_add */ \
COSTS_N_INSNS (256), /* fp_mult_sf */ \
COSTS_N_INSNS (256), /* fp_mult_df */ \
COSTS_N_INSNS (256), /* fp_div_sf */ \
COSTS_N_INSNS (256) /* fp_div_df */
/* Costs to use when optimizing for size. */
static const struct mips_rtx_cost_data mips_rtx_cost_optimize_size = {
COSTS_N_INSNS (1), /* fp_add */
COSTS_N_INSNS (1), /* fp_mult_sf */
COSTS_N_INSNS (1), /* fp_mult_df */
COSTS_N_INSNS (1), /* fp_div_sf */
COSTS_N_INSNS (1), /* fp_div_df */
COSTS_N_INSNS (1), /* int_mult_si */
COSTS_N_INSNS (1), /* int_mult_di */
COSTS_N_INSNS (1), /* int_div_si */
COSTS_N_INSNS (1), /* int_div_di */
2, /* branch_cost */
4 /* memory_latency */
};
/* Costs to use when optimizing for speed, indexed by processor. */
static const struct mips_rtx_cost_data
mips_rtx_cost_data[NUM_PROCESSOR_VALUES] = {
{ /* R3000 */
COSTS_N_INSNS (2), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (12), /* fp_div_sf */
COSTS_N_INSNS (19), /* fp_div_df */
COSTS_N_INSNS (12), /* int_mult_si */
COSTS_N_INSNS (12), /* int_mult_di */
COSTS_N_INSNS (35), /* int_div_si */
COSTS_N_INSNS (35), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 4KC */
SOFT_FP_COSTS,
COSTS_N_INSNS (6), /* int_mult_si */
COSTS_N_INSNS (6), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (36), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 4KP */
SOFT_FP_COSTS,
COSTS_N_INSNS (36), /* int_mult_si */
COSTS_N_INSNS (36), /* int_mult_di */
COSTS_N_INSNS (37), /* int_div_si */
COSTS_N_INSNS (37), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 5KC */
SOFT_FP_COSTS,
COSTS_N_INSNS (4), /* int_mult_si */
COSTS_N_INSNS (11), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (68), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 5KF */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (4), /* int_mult_si */
COSTS_N_INSNS (11), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (68), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 20KC */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (4), /* int_mult_si */
COSTS_N_INSNS (7), /* int_mult_di */
COSTS_N_INSNS (42), /* int_div_si */
COSTS_N_INSNS (72), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 24KC */
SOFT_FP_COSTS,
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 24KF2_1 */
COSTS_N_INSNS (8), /* fp_add */
COSTS_N_INSNS (8), /* fp_mult_sf */
COSTS_N_INSNS (10), /* fp_mult_df */
COSTS_N_INSNS (34), /* fp_div_sf */
COSTS_N_INSNS (64), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 24KF1_1 */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 74KC */
SOFT_FP_COSTS,
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 74KF2_1 */
COSTS_N_INSNS (8), /* fp_add */
COSTS_N_INSNS (8), /* fp_mult_sf */
COSTS_N_INSNS (10), /* fp_mult_df */
COSTS_N_INSNS (34), /* fp_div_sf */
COSTS_N_INSNS (64), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 74KF1_1 */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* 74KF3_2 */
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (6), /* fp_mult_sf */
COSTS_N_INSNS (7), /* fp_mult_df */
COSTS_N_INSNS (25), /* fp_div_sf */
COSTS_N_INSNS (48), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* Loongson-2E */
DEFAULT_COSTS
},
{ /* Loongson-2F */
DEFAULT_COSTS
},
{ /* Loongson-3A */
DEFAULT_COSTS
},
{ /* M4k */
DEFAULT_COSTS
},
/* Octeon */
{
SOFT_FP_COSTS,
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (72), /* int_div_si */
COSTS_N_INSNS (72), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
/* Octeon II */
{
SOFT_FP_COSTS,
COSTS_N_INSNS (6), /* int_mult_si */
COSTS_N_INSNS (6), /* int_mult_di */
COSTS_N_INSNS (18), /* int_div_si */
COSTS_N_INSNS (35), /* int_div_di */
4, /* branch_cost */
4 /* memory_latency */
},
/* Octeon III */
{
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (6), /* fp_mult_sf */
COSTS_N_INSNS (7), /* fp_mult_df */
COSTS_N_INSNS (25), /* fp_div_sf */
COSTS_N_INSNS (48), /* fp_div_df */
COSTS_N_INSNS (6), /* int_mult_si */
COSTS_N_INSNS (6), /* int_mult_di */
COSTS_N_INSNS (18), /* int_div_si */
COSTS_N_INSNS (35), /* int_div_di */
4, /* branch_cost */
4 /* memory_latency */
},
{ /* R3900 */
COSTS_N_INSNS (2), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (12), /* fp_div_sf */
COSTS_N_INSNS (19), /* fp_div_df */
COSTS_N_INSNS (2), /* int_mult_si */
COSTS_N_INSNS (2), /* int_mult_di */
COSTS_N_INSNS (35), /* int_div_si */
COSTS_N_INSNS (35), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R6000 */
COSTS_N_INSNS (3), /* fp_add */
COSTS_N_INSNS (5), /* fp_mult_sf */
COSTS_N_INSNS (6), /* fp_mult_df */
COSTS_N_INSNS (15), /* fp_div_sf */
COSTS_N_INSNS (16), /* fp_div_df */
COSTS_N_INSNS (17), /* int_mult_si */
COSTS_N_INSNS (17), /* int_mult_di */
COSTS_N_INSNS (38), /* int_div_si */
COSTS_N_INSNS (38), /* int_div_di */
2, /* branch_cost */
6 /* memory_latency */
},
{ /* R4000 */
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (7), /* fp_mult_sf */
COSTS_N_INSNS (8), /* fp_mult_df */
COSTS_N_INSNS (23), /* fp_div_sf */
COSTS_N_INSNS (36), /* fp_div_df */
COSTS_N_INSNS (10), /* int_mult_si */
COSTS_N_INSNS (10), /* int_mult_di */
COSTS_N_INSNS (69), /* int_div_si */
COSTS_N_INSNS (69), /* int_div_di */
2, /* branch_cost */
6 /* memory_latency */
},
{ /* R4100 */
DEFAULT_COSTS
},
{ /* R4111 */
DEFAULT_COSTS
},
{ /* R4120 */
DEFAULT_COSTS
},
{ /* R4130 */
/* The only costs that appear to be updated here are
integer multiplication. */
SOFT_FP_COSTS,
COSTS_N_INSNS (4), /* int_mult_si */
COSTS_N_INSNS (6), /* int_mult_di */
COSTS_N_INSNS (69), /* int_div_si */
COSTS_N_INSNS (69), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R4300 */
DEFAULT_COSTS
},
{ /* R4600 */
DEFAULT_COSTS
},
{ /* R4650 */
DEFAULT_COSTS
},
{ /* R4700 */
DEFAULT_COSTS
},
{ /* R5000 */
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (23), /* fp_div_sf */
COSTS_N_INSNS (36), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (36), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R5400 */
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (5), /* fp_mult_sf */
COSTS_N_INSNS (6), /* fp_mult_df */
COSTS_N_INSNS (30), /* fp_div_sf */
COSTS_N_INSNS (59), /* fp_div_df */
COSTS_N_INSNS (3), /* int_mult_si */
COSTS_N_INSNS (4), /* int_mult_di */
COSTS_N_INSNS (42), /* int_div_si */
COSTS_N_INSNS (74), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R5500 */
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (5), /* fp_mult_sf */
COSTS_N_INSNS (6), /* fp_mult_df */
COSTS_N_INSNS (30), /* fp_div_sf */
COSTS_N_INSNS (59), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (9), /* int_mult_di */
COSTS_N_INSNS (42), /* int_div_si */
COSTS_N_INSNS (74), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R5900 */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (256), /* fp_mult_df */
COSTS_N_INSNS (8), /* fp_div_sf */
COSTS_N_INSNS (256), /* fp_div_df */
COSTS_N_INSNS (4), /* int_mult_si */
COSTS_N_INSNS (256), /* int_mult_di */
COSTS_N_INSNS (37), /* int_div_si */
COSTS_N_INSNS (256), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R7000 */
/* The only costs that are changed here are
integer multiplication. */
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (7), /* fp_mult_sf */
COSTS_N_INSNS (8), /* fp_mult_df */
COSTS_N_INSNS (23), /* fp_div_sf */
COSTS_N_INSNS (36), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (9), /* int_mult_di */
COSTS_N_INSNS (69), /* int_div_si */
COSTS_N_INSNS (69), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R8000 */
DEFAULT_COSTS
},
{ /* R9000 */
/* The only costs that are changed here are
integer multiplication. */
COSTS_N_INSNS (6), /* fp_add */
COSTS_N_INSNS (7), /* fp_mult_sf */
COSTS_N_INSNS (8), /* fp_mult_df */
COSTS_N_INSNS (23), /* fp_div_sf */
COSTS_N_INSNS (36), /* fp_div_df */
COSTS_N_INSNS (3), /* int_mult_si */
COSTS_N_INSNS (8), /* int_mult_di */
COSTS_N_INSNS (69), /* int_div_si */
COSTS_N_INSNS (69), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* R1x000 */
COSTS_N_INSNS (2), /* fp_add */
COSTS_N_INSNS (2), /* fp_mult_sf */
COSTS_N_INSNS (2), /* fp_mult_df */
COSTS_N_INSNS (12), /* fp_div_sf */
COSTS_N_INSNS (19), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (9), /* int_mult_di */
COSTS_N_INSNS (34), /* int_div_si */
COSTS_N_INSNS (66), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* SB1 */
/* These costs are the same as the SB-1A below. */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (4), /* fp_mult_df */
COSTS_N_INSNS (24), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (3), /* int_mult_si */
COSTS_N_INSNS (4), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (68), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* SB1-A */
/* These costs are the same as the SB-1 above. */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (4), /* fp_mult_df */
COSTS_N_INSNS (24), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (3), /* int_mult_si */
COSTS_N_INSNS (4), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (68), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* SR71000 */
DEFAULT_COSTS
},
{ /* XLR */
SOFT_FP_COSTS,
COSTS_N_INSNS (8), /* int_mult_si */
COSTS_N_INSNS (8), /* int_mult_di */
COSTS_N_INSNS (72), /* int_div_si */
COSTS_N_INSNS (72), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* XLP */
/* These costs are the same as 5KF above. */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (4), /* int_mult_si */
COSTS_N_INSNS (11), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (68), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* P5600 */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (5), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (17), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (8), /* int_div_si */
COSTS_N_INSNS (8), /* int_div_di */
2, /* branch_cost */
4 /* memory_latency */
},
{ /* W32 */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* W64 */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (4), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (17), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (41), /* int_div_si */
COSTS_N_INSNS (41), /* int_div_di */
1, /* branch_cost */
4 /* memory_latency */
},
{ /* I6400 */
COSTS_N_INSNS (4), /* fp_add */
COSTS_N_INSNS (5), /* fp_mult_sf */
COSTS_N_INSNS (5), /* fp_mult_df */
COSTS_N_INSNS (32), /* fp_div_sf */
COSTS_N_INSNS (32), /* fp_div_df */
COSTS_N_INSNS (5), /* int_mult_si */
COSTS_N_INSNS (5), /* int_mult_di */
COSTS_N_INSNS (36), /* int_div_si */
COSTS_N_INSNS (36), /* int_div_di */
2, /* branch_cost */
4 /* memory_latency */
}
};
static rtx mips_find_pic_call_symbol (rtx, rtx, bool);
static int mips_register_move_cost (machine_mode, reg_class_t,
reg_class_t);
static unsigned int mips_function_arg_boundary (machine_mode, const_tree);
static machine_mode mips_get_reg_raw_mode (int regno);
/* This hash table keeps track of implicit "mips16" and "nomips16" attributes
for -mflip_mips16. It maps decl names onto a boolean mode setting. */
struct GTY (()) mflip_mips16_entry {
const char *name;
bool mips16_p;
};
static GTY ((param_is (struct mflip_mips16_entry))) htab_t mflip_mips16_htab;
/* Hash table callbacks for mflip_mips16_htab. */
static hashval_t
mflip_mips16_htab_hash (const void *entry)
{
return htab_hash_string (((const struct mflip_mips16_entry *) entry)->name);
}
static int
mflip_mips16_htab_eq (const void *entry, const void *name)
{
return strcmp (((const struct mflip_mips16_entry *) entry)->name,
(const char *) name) == 0;
}
/* True if -mflip-mips16 should next add an attribute for the default MIPS16
mode, false if it should next add an attribute for the opposite mode. */
static GTY(()) bool mips16_flipper;
/* DECL is a function that needs a default "mips16" or "nomips16" attribute
for -mflip-mips16. Return true if it should use "mips16" and false if
it should use "nomips16". */
static bool
mflip_mips16_use_mips16_p (tree decl)
{
struct mflip_mips16_entry *entry;
const char *name;
hashval_t hash;
void **slot;
bool base_is_mips16 = (mips_base_compression_flags & MASK_MIPS16) != 0;
/* Use the opposite of the command-line setting for anonymous decls. */
if (!DECL_NAME (decl))
return !base_is_mips16;
if (!mflip_mips16_htab)
mflip_mips16_htab = htab_create_ggc (37, mflip_mips16_htab_hash,
mflip_mips16_htab_eq, NULL);
name = IDENTIFIER_POINTER (DECL_NAME (decl));
hash = htab_hash_string (name);
slot = htab_find_slot_with_hash (mflip_mips16_htab, name, hash, INSERT);
entry = (struct mflip_mips16_entry *) *slot;
if (!entry)
{
mips16_flipper = !mips16_flipper;
entry = ggc_alloc_mflip_mips16_entry ();
entry->name = name;
entry->mips16_p = mips16_flipper ? !base_is_mips16 : base_is_mips16;
*slot = entry;
}
return entry->mips16_p;
}
/* Predicates to test for presence of "near" and "far"/"long_call"
attributes on the given TYPE. */
static bool
mips_near_type_p (const_tree type)
{
return lookup_attribute ("near", TYPE_ATTRIBUTES (type)) != NULL;
}
static bool
mips_far_type_p (const_tree type)
{
return (lookup_attribute ("long_call", TYPE_ATTRIBUTES (type)) != NULL
|| lookup_attribute ("far", TYPE_ATTRIBUTES (type)) != NULL);
}
/* Check if the interrupt attribute is set for a function. */
static bool
mips_interrupt_type_p (tree type)
{
return lookup_attribute ("interrupt", TYPE_ATTRIBUTES (type)) != NULL;
}
/* Check if the attribute to use shadow register set is set for a function. */
static bool
mips_use_shadow_register_set_p (tree type)
{
return lookup_attribute ("use_shadow_register_set",
TYPE_ATTRIBUTES (type)) != NULL;
}
/* Check if the attribute to keep interrupts masked is set for a function. */
static bool
mips_keep_interrupts_masked_p (tree type)
{
return lookup_attribute ("keep_interrupts_masked",
TYPE_ATTRIBUTES (type)) != NULL;
}
/* Check if the attribute to use debug exception return is set for
a function. */
static bool
mips_use_debug_exception_return_p (tree type)
{
return lookup_attribute ("use_debug_exception_return",
TYPE_ATTRIBUTES (type)) != NULL;
}
/* Return the set of compression modes that are explicitly required
by the attributes in ATTRIBUTES. */
static unsigned int
mips_get_compress_on_flags (tree attributes)
{
unsigned int flags = 0;
if (lookup_attribute ("mips16", attributes) != NULL)
flags |= MASK_MIPS16;
if (lookup_attribute ("micromips", attributes) != NULL)
flags |= MASK_MICROMIPS;
return flags;
}
/* Return the set of compression modes that are explicitly forbidden
by the attributes in ATTRIBUTES. */
static unsigned int
mips_get_compress_off_flags (tree attributes)
{
unsigned int flags = 0;
if (lookup_attribute ("nocompression", attributes) != NULL)
flags |= MASK_MIPS16 | MASK_MICROMIPS;
if (lookup_attribute ("nomips16", attributes) != NULL)
flags |= MASK_MIPS16;
if (lookup_attribute ("nomicromips", attributes) != NULL)
flags |= MASK_MICROMIPS;
return flags;
}
/* Return the compression mode that should be used for function DECL.
Return the ambient setting if DECL is null. */
static unsigned int
mips_get_compress_mode (tree decl)
{
unsigned int flags, force_on;
flags = mips_base_compression_flags;
if (decl)
{
/* Nested functions must use the same frame pointer as their
parent and must therefore use the same ISA mode. */
tree parent = decl_function_context (decl);
if (parent)
decl = parent;
force_on = mips_get_compress_on_flags (DECL_ATTRIBUTES (decl));
if (force_on)
return force_on;
flags &= ~mips_get_compress_off_flags (DECL_ATTRIBUTES (decl));
}
return flags;
}
/* Return the attribute name associated with MASK_MIPS16 and MASK_MICROMIPS
flags FLAGS. */
static const char *
mips_get_compress_on_name (unsigned int flags)
{
if (flags == MASK_MIPS16)
return "mips16";
return "micromips";
}
/* Return the attribute name that forbids MASK_MIPS16 and MASK_MICROMIPS
flags FLAGS. */
static const char *
mips_get_compress_off_name (unsigned int flags)
{
if (flags == MASK_MIPS16)
return "nomips16";
if (flags == MASK_MICROMIPS)
return "nomicromips";
return "nocompression";
}
/* Implement TARGET_COMP_TYPE_ATTRIBUTES. */
static int
mips_comp_type_attributes (const_tree type1, const_tree type2)
{
/* Disallow mixed near/far attributes. */
if (mips_far_type_p (type1) && mips_near_type_p (type2))
return 0;
if (mips_near_type_p (type1) && mips_far_type_p (type2))
return 0;
return 1;
}
/* Implement TARGET_INSERT_ATTRIBUTES. */
static void
mips_insert_attributes (tree decl, tree *attributes)
{
const char *name;
unsigned int compression_flags, nocompression_flags;
/* Check for "mips16" and "nomips16" attributes. */
compression_flags = mips_get_compress_on_flags (*attributes);
nocompression_flags = mips_get_compress_off_flags (*attributes);
if (TREE_CODE (decl) != FUNCTION_DECL)
{
if (nocompression_flags)
error ("%qs attribute only applies to functions",
mips_get_compress_off_name (nocompression_flags));
if (compression_flags)
error ("%qs attribute only applies to functions",
mips_get_compress_on_name (nocompression_flags));
}
else
{
compression_flags |= mips_get_compress_on_flags (DECL_ATTRIBUTES (decl));
nocompression_flags |=
mips_get_compress_off_flags (DECL_ATTRIBUTES (decl));
if (compression_flags && nocompression_flags)
error ("%qE cannot have both %qs and %qs attributes",
DECL_NAME (decl), mips_get_compress_on_name (compression_flags),
mips_get_compress_off_name (nocompression_flags));
if (compression_flags & MASK_MIPS16
&& compression_flags & MASK_MICROMIPS)
error ("%qE cannot have both %qs and %qs attributes",
DECL_NAME (decl), "mips16", "micromips");
if (TARGET_FLIP_MIPS16
&& !DECL_ARTIFICIAL (decl)
&& compression_flags == 0
&& nocompression_flags == 0)
{
/* Implement -mflip-mips16. If DECL has neither a "nomips16" nor a
"mips16" attribute, arbitrarily pick one. We must pick the same
setting for duplicate declarations of a function. */
name = mflip_mips16_use_mips16_p (decl) ? "mips16" : "nomips16";
*attributes = tree_cons (get_identifier (name), NULL, *attributes);
name = "nomicromips";
*attributes = tree_cons (get_identifier (name), NULL, *attributes);
}
}
}
/* Implement TARGET_MERGE_DECL_ATTRIBUTES. */
static tree
mips_merge_decl_attributes (tree olddecl, tree newdecl)
{
unsigned int diff;
diff = (mips_get_compress_on_flags (DECL_ATTRIBUTES (olddecl))
^ mips_get_compress_on_flags (DECL_ATTRIBUTES (newdecl)));
if (diff)
error ("%qE redeclared with conflicting %qs attributes",
DECL_NAME (newdecl), mips_get_compress_on_name (diff));
diff = (mips_get_compress_off_flags (DECL_ATTRIBUTES (olddecl))
^ mips_get_compress_off_flags (DECL_ATTRIBUTES (newdecl)));
if (diff)
error ("%qE redeclared with conflicting %qs attributes",
DECL_NAME (newdecl), mips_get_compress_off_name (diff));
return merge_attributes (DECL_ATTRIBUTES (olddecl),
DECL_ATTRIBUTES (newdecl));
}
/* Implement TARGET_CAN_INLINE_P. */
static bool
mips_can_inline_p (tree caller, tree callee)
{
if (mips_get_compress_mode (callee) != mips_get_compress_mode (caller))
return false;
return default_target_can_inline_p (caller, callee);
}
/* If X is a PLUS of a CONST_INT, return the two terms in *BASE_PTR
and *OFFSET_PTR. Return X in *BASE_PTR and 0 in *OFFSET_PTR otherwise. */
static void
mips_split_plus (rtx x, rtx *base_ptr, HOST_WIDE_INT *offset_ptr)
{
if (GET_CODE (x) == PLUS && CONST_INT_P (XEXP (x, 1)))
{
*base_ptr = XEXP (x, 0);
*offset_ptr = INTVAL (XEXP (x, 1));
}
else
{
*base_ptr = x;
*offset_ptr = 0;
}
}
static unsigned int mips_build_integer (struct mips_integer_op *,
unsigned HOST_WIDE_INT);
/* A subroutine of mips_build_integer, with the same interface.
Assume that the final action in the sequence should be a left shift. */
static unsigned int
mips_build_shift (struct mips_integer_op *codes, HOST_WIDE_INT value)
{
unsigned int i, shift;
/* Shift VALUE right until its lowest bit is set. Shift arithmetically
since signed numbers are easier to load than unsigned ones. */
shift = 0;
while ((value & 1) == 0)
value /= 2, shift++;
i = mips_build_integer (codes, value);
codes[i].code = ASHIFT;
codes[i].value = shift;
return i + 1;
}
/* As for mips_build_shift, but assume that the final action will be
an IOR or PLUS operation. */
static unsigned int
mips_build_lower (struct mips_integer_op *codes, unsigned HOST_WIDE_INT value)
{
unsigned HOST_WIDE_INT high;
unsigned int i;
high = value & ~(unsigned HOST_WIDE_INT) 0xffff;
if (!LUI_OPERAND (high) && (value & 0x18000) == 0x18000)
{
/* The constant is too complex to load with a simple LUI/ORI pair,
so we want to give the recursive call as many trailing zeros as
possible. In this case, we know bit 16 is set and that the
low 16 bits form a negative number. If we subtract that number
from VALUE, we will clear at least the lowest 17 bits, maybe more. */
i = mips_build_integer (codes, CONST_HIGH_PART (value));
codes[i].code = PLUS;
codes[i].value = CONST_LOW_PART (value);
}
else
{
/* Either this is a simple LUI/ORI pair, or clearing the lowest 16
bits gives a value with at least 17 trailing zeros. */
i = mips_build_integer (codes, high);
codes[i].code = IOR;
codes[i].value = value & 0xffff;
}
return i + 1;
}
/* Fill CODES with a sequence of rtl operations to load VALUE.
Return the number of operations needed. */
static unsigned int
mips_build_integer (struct mips_integer_op *codes,
unsigned HOST_WIDE_INT value)
{
if (SMALL_OPERAND (value)
|| SMALL_OPERAND_UNSIGNED (value)
|| LUI_OPERAND (value))
{
/* The value can be loaded with a single instruction. */
codes[0].code = UNKNOWN;
codes[0].value = value;
return 1;
}
else if ((value & 1) != 0 || LUI_OPERAND (CONST_HIGH_PART (value)))
{
/* Either the constant is a simple LUI/ORI combination or its
lowest bit is set. We don't want to shift in this case. */
return mips_build_lower (codes, value);
}
else if ((value & 0xffff) == 0)
{
/* The constant will need at least three actions. The lowest
16 bits are clear, so the final action will be a shift. */
return mips_build_shift (codes, value);
}
else
{
/* The final action could be a shift, add or inclusive OR.
Rather than use a complex condition to select the best
approach, try both mips_build_shift and mips_build_lower
and pick the one that gives the shortest sequence.
Note that this case is only used once per constant. */
struct mips_integer_op alt_codes[MIPS_MAX_INTEGER_OPS];
unsigned int cost, alt_cost;
cost = mips_build_shift (codes, value);
alt_cost = mips_build_lower (alt_codes, value);
if (alt_cost < cost)
{
memcpy (codes, alt_codes, alt_cost * sizeof (codes[0]));
cost = alt_cost;
}
return cost;
}
}
/* Implement TARGET_LEGITIMATE_CONSTANT_P. */
static bool
mips_legitimate_constant_p (machine_mode mode ATTRIBUTE_UNUSED, rtx x)
{
return mips_const_insns (x) > 0;
}
/* Return a SYMBOL_REF for a MIPS16 function called NAME. */
static rtx
mips16_stub_function (const char *name)
{
rtx x;
x = gen_rtx_SYMBOL_REF (Pmode, ggc_strdup (name));
SYMBOL_REF_FLAGS (x) |= (SYMBOL_FLAG_EXTERNAL | SYMBOL_FLAG_FUNCTION);
return x;
}
/* Return a legitimate call address for STUB, given that STUB is a MIPS16
support function. */
static rtx
mips16_stub_call_address (mips_one_only_stub *stub)
{
rtx fn = mips16_stub_function (stub->get_name ());
SYMBOL_REF_FLAGS (fn) |= SYMBOL_FLAG_LOCAL;
if (!call_insn_operand (fn, VOIDmode))
fn = force_reg (Pmode, fn);
return fn;
}
/* A stub for moving the thread pointer into TLS_GET_TP_REGNUM. */
class mips16_rdhwr_one_only_stub : public mips_one_only_stub
{
virtual const char *get_name ();
virtual void output_body ();
};
const char *
mips16_rdhwr_one_only_stub::get_name ()
{
return "__mips16_rdhwr";
}
void
mips16_rdhwr_one_only_stub::output_body ()
{
fprintf (asm_out_file,
"\t.set\tpush\n"
"\t.set\tmips32r2\n"
"\t.set\tnoreorder\n"
"\trdhwr\t$3,$29\n"
"\t.set\tpop\n"
"\tj\t$31\n");
}
/* A stub for moving the FCSR into GET_FCSR_REGNUM. */
class mips16_get_fcsr_one_only_stub : public mips_one_only_stub
{
virtual const char *get_name ();
virtual void output_body ();
};
const char *
mips16_get_fcsr_one_only_stub::get_name ()
{
return "__mips16_get_fcsr";
}
void
mips16_get_fcsr_one_only_stub::output_body ()
{
fprintf (asm_out_file,
"\tcfc1\t%s,$31\n"
"\tj\t$31\n", reg_names[GET_FCSR_REGNUM]);
}
/* A stub for moving SET_FCSR_REGNUM into the FCSR. */
class mips16_set_fcsr_one_only_stub : public mips_one_only_stub
{
virtual const char *get_name ();
virtual void output_body ();
};
const char *
mips16_set_fcsr_one_only_stub::get_name ()
{
return "__mips16_set_fcsr";
}
void
mips16_set_fcsr_one_only_stub::output_body ()
{
fprintf (asm_out_file,
"\tctc1\t%s,$31\n"
"\tj\t$31\n", reg_names[SET_FCSR_REGNUM]);
}
/* Return true if symbols of type TYPE require a GOT access. */
static bool
mips_got_symbol_type_p (enum mips_symbol_type type)
{
switch (type)
{
case SYMBOL_GOT_PAGE_OFST:
case SYMBOL_GOT_DISP:
return true;
default:
return false;
}
}
/* Return true if X is a thread-local symbol. */
static bool
mips_tls_symbol_p (rtx x)
{
return GET_CODE (x) == SYMBOL_REF && SYMBOL_REF_TLS_MODEL (x) != 0;
}
/* Return true if SYMBOL_REF X is associated with a global symbol
(in the STB_GLOBAL sense). */
static bool
mips_global_symbol_p (const_rtx x)
{
const_tree decl = SYMBOL_REF_DECL (x);
if (!decl)
return !SYMBOL_REF_LOCAL_P (x) || SYMBOL_REF_EXTERNAL_P (x);
/* Weakref symbols are not TREE_PUBLIC, but their targets are global
or weak symbols. Relocations in the object file will be against
the target symbol, so it's that symbol's binding that matters here. */
return DECL_P (decl) && (TREE_PUBLIC (decl) || DECL_WEAK (decl));
}
/* Return true if function X is a libgcc MIPS16 stub function. */
static bool
mips16_stub_function_p (const_rtx x)
{
return (GET_CODE (x) == SYMBOL_REF
&& strncmp (XSTR (x,
|