X-Git-Url: https://oss.titaniummirror.com/gitweb?a=blobdiff_plain;f=gcc%2Fconfig%2Fm32r%2Fm32r.md;fp=gcc%2Fconfig%2Fm32r%2Fm32r.md;h=d117e1e692821db392147bddac235655902ba254;hb=6fed43773c9b0ce596dca5686f37ac3fc0fa11c0;hp=a8e28db0ba987a9128ad5faff6f190b237e7fc07;hpb=27b11d56b743098deb193d510b337ba22dc52e5c;p=msp430-gcc.git diff --git a/gcc/config/m32r/m32r.md b/gcc/config/m32r/m32r.md index a8e28db0..d117e1e6 100644 --- a/gcc/config/m32r/m32r.md +++ b/gcc/config/m32r/m32r.md @@ -1,31 +1,39 @@ -;; Machine description of the Mitsubishi M32R cpu for GNU C compiler -;; Copyright (C) 1996, 1997, 1998, 1999, 2001 Free Software Foundation, Inc. +;; Machine description of the Renesas M32R cpu for GNU C compiler +;; Copyright (C) 1996, 1997, 1998, 1999, 2001, 2003, 2004, 2005, +; 2007, 2008 Free Software Foundation, Inc. -;; This file is part of GNU CC. +;; This file is part of GCC. -;; GNU CC 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 2, or (at your option) -;; any later version. +;; 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. -;; GNU CC 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. +;; 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 GNU CC; see the file COPYING. If not, write to -;; the Free Software Foundation, 59 Temple Place - Suite 330, -;; Boston, MA 02111-1307, USA. +;; along with GCC; see the file COPYING3. If not see +;; . ;; See file "rtl.def" for documentation on define_insn, match_*, et. al. - -;; unspec usage -;; 0 - blockage -;; 1 - flush_icache -;; 2 - load_sda_base -;; 3 - setting carry in addx/subx instructions. +;; UNSPEC_VOLATILE usage +(define_constants + [(UNSPECV_BLOCKAGE 0) + (UNSPECV_FLUSH_ICACHE 1)]) + +;; UNSPEC usage +(define_constants + [(UNSPEC_LOAD_SDA_BASE 2) + (UNSPEC_SET_CBIT 3) + (UNSPEC_PIC_LOAD_ADDR 4) + (UNSPEC_GET_PC 5) + (UNSPEC_GOTOFF 6) + ]) + ;; Insn type. Used to default other attribute values. (define_attr "type" "int2,int4,load2,load4,load8,store2,store4,store8,shift2,shift4,mul2,div4,uncond_branch,branch,call,multi,misc" @@ -53,222 +61,146 @@ [(set_attr "length" "4") (set_attr "type" "multi")]) - -;; Whether an instruction is 16-bit or 32-bit +;; Whether an instruction is short (16-bit) or long (32-bit). (define_attr "insn_size" "short,long" (if_then_else (eq_attr "type" "int2,load2,store2,shift2,mul2") (const_string "short") (const_string "long"))) -(define_attr "debug" "no,yes" - (const (symbol_ref "(TARGET_DEBUG != 0)"))) - -(define_attr "opt_size" "no,yes" - (const (symbol_ref "(optimize_size != 0)"))) - -(define_attr "m32r" "no,yes" - (const (symbol_ref "(TARGET_M32R != 0)"))) - -(define_attr "m32rx" "no,yes" - (const (symbol_ref "(TARGET_M32RX != 0)"))) - -(define_attr "m32rx_pipeline" "either,s,o,long,m32r" - (cond [(eq_attr "m32rx" "no") - (const_string "m32r") - +;; The target CPU we're compiling for. +(define_attr "cpu" "m32r,m32r2,m32rx" + (cond [(ne (symbol_ref "TARGET_M32RX") (const_int 0)) + (const_string "m32rx") + (ne (symbol_ref "TARGET_M32R2") (const_int 0)) + (const_string "m32r2")] + (const_string "m32r"))) + +;; Defines the pipeline where an instruction can be executed on. +;; For the M32R, a short instruction can execute one of the two pipes. +;; For the M32Rx, the restrictions are modelled in the second +;; condition of this attribute definition. +(define_attr "m32r_pipeline" "either,s,o,long" + (cond [(and (eq_attr "cpu" "m32r") + (eq_attr "insn_size" "short")) + (const_string "either") (eq_attr "insn_size" "!short") - (const_string "long")] - - (cond [(eq_attr "type" "int2") - (const_string "either") - - (eq_attr "type" "load2,store2,shift2,uncond_branch,branch,call") - (const_string "o") - - (eq_attr "type" "mul2") - (const_string "s")] - - (const_string "long")))) + (const_string "long")] + (cond [(eq_attr "type" "int2") + (const_string "either") + (eq_attr "type" "load2,store2,shift2,uncond_branch,branch,call") + (const_string "o") + (eq_attr "type" "mul2") + (const_string "s")] + (const_string "long")))) ;; :::::::::::::::::::: ;; :: -;; :: Function Units +;; :: Pipeline description ;; :: ;; :::::::::::::::::::: -;; On most RISC machines, there are instructions whose results are not -;; available for a specific number of cycles. Common cases are instructions -;; that load data from memory. On many machines, a pipeline stall will result -;; if the data is referenced too soon after the load instruction. - -;; In addition, many newer microprocessors have multiple function units, -;; usually one for integer and one for floating point, and often will incur -;; pipeline stalls when a result that is needed is not yet ready. - -;; The descriptions in this section allow the specification of how much time -;; must elapse between the execution of an instruction and the time when its -;; result is used. It also allows specification of when the execution of an -;; instruction will delay execution of similar instructions due to function -;; unit conflicts. - -;; For the purposes of the specifications in this section, a machine is divided -;; into "function units", each of which execute a specific class of -;; instructions in first-in-first-out order. Function units that accept one -;; instruction each cycle and allow a result to be used in the succeeding -;; instruction (usually via forwarding) need not be specified. Classic RISC -;; microprocessors will normally have a single function unit, which we can call -;; `memory'. The newer "superscalar" processors will often have function units -;; for floating point operations, usually at least a floating point adder and -;; multiplier. - -;; Each usage of a function units by a class of insns is specified with a -;; `define_function_unit' expression, which looks like this: - -;; (define_function_unit NAME MULTIPLICITY SIMULTANEITY TEST READY-DELAY -;; ISSUE-DELAY [CONFLICT-LIST]) - -;; NAME is a string giving the name of the function unit. - -;; MULTIPLICITY is an integer specifying the number of identical units in the -;; processor. If more than one unit is specified, they will be scheduled -;; independently. Only truly independent units should be counted; a pipelined -;; unit should be specified as a single unit. (The only common example of a -;; machine that has multiple function units for a single instruction class that -;; are truly independent and not pipelined are the two multiply and two -;; increment units of the CDC 6600.) - -;; SIMULTANEITY specifies the maximum number of insns that can be executing in -;; each instance of the function unit simultaneously or zero if the unit is -;; pipelined and has no limit. - -;; All `define_function_unit' definitions referring to function unit NAME must -;; have the same name and values for MULTIPLICITY and SIMULTANEITY. - -;; TEST is an attribute test that selects the insns we are describing in this -;; definition. Note that an insn may use more than one function unit and a -;; function unit may be specified in more than one `define_function_unit'. - -;; READY-DELAY is an integer that specifies the number of cycles after which -;; the result of the instruction can be used without introducing any stalls. - -;; ISSUE-DELAY is an integer that specifies the number of cycles after the -;; instruction matching the TEST expression begins using this unit until a -;; subsequent instruction can begin. A cost of N indicates an N-1 cycle delay. -;; A subsequent instruction may also be delayed if an earlier instruction has a -;; longer READY-DELAY value. This blocking effect is computed using the -;; SIMULTANEITY, READY-DELAY, ISSUE-DELAY, and CONFLICT-LIST terms. For a -;; normal non-pipelined function unit, SIMULTANEITY is one, the unit is taken -;; to block for the READY-DELAY cycles of the executing insn, and smaller -;; values of ISSUE-DELAY are ignored. - -;; CONFLICT-LIST is an optional list giving detailed conflict costs for this -;; unit. If specified, it is a list of condition test expressions to be -;; applied to insns chosen to execute in NAME following the particular insn -;; matching TEST that is already executing in NAME. For each insn in the list, -;; ISSUE-DELAY specifies the conflict cost; for insns not in the list, the cost -;; is zero. If not specified, CONFLICT-LIST defaults to all instructions that -;; use the function unit. - -;; Typical uses of this vector are where a floating point function unit can -;; pipeline either single- or double-precision operations, but not both, or -;; where a memory unit can pipeline loads, but not stores, etc. - -;; As an example, consider a classic RISC machine where the result of a load -;; instruction is not available for two cycles (a single "delay" instruction is -;; required) and where only one load instruction can be executed -;; simultaneously. This would be specified as: - -;; (define_function_unit "memory" 1 1 (eq_attr "type" "load") 2 0) - -;; For the case of a floating point function unit that can pipeline -;; either single or double precision, but not both, the following could be -;; specified: +;; This model is based on Chapter 2, Appendix 3 and Appendix 4 of the +;; "M32R-FPU Software Manual", Revision 1.01, plus additional information +;; obtained by our best friend and mine, Google. ;; -;; (define_function_unit "fp" 1 0 -;; (eq_attr "type" "sp_fp") 4 4 -;; [(eq_attr "type" "dp_fp")]) +;; The pipeline is modelled as a fetch unit, and a core with a memory unit, +;; two execution units, where "fetch" models IF and D, "memory" for MEM1 +;; and MEM2, and "EXEC" for E, E1, E2, EM, and EA. Writeback and +;; bypasses are not modelled. +(define_automaton "m32r") + +;; We pretend there are two short (16 bits) instruction fetchers. The +;; "s" short fetcher cannot be reserved until the "o" short fetcher is +;; reserved. Some instructions reserve both the left and right fetchers. +;; These fetch units are a hack to get GCC to better pack the instructions +;; for the M32Rx processor, which has two execution pipes. ;; -;; (define_function_unit "fp" 1 0 -;; (eq_attr "type" "dp_fp") 4 4 -;; [(eq_attr "type" "sp_fp")]) - -;; Note: The scheduler attempts to avoid function unit conflicts and uses all -;; the specifications in the `define_function_unit' expression. It has -;; recently come to our attention that these specifications may not allow -;; modeling of some of the newer "superscalar" processors that have insns using -;; multiple pipelined units. These insns will cause a potential conflict for -;; the second unit used during their execution and there is no way of -;; representing that conflict. We welcome any examples of how function unit -;; conflicts work in such processors and suggestions for their representation. - -;; Function units of the M32R -;; Units that take one cycle do not need to be specified. - -;; (define_function_unit {name} {multiplicity} {simulataneity} {test} -;; {ready-delay} {issue-delay} [{conflict-list}]) - -;; Hack to get GCC to better pack the instructions. -;; We pretend there is a separate long function unit that conflicts with -;; both the left and right 16 bit insn slots. - -(define_function_unit "short" 2 2 - (and (eq_attr "m32r" "yes") +;; In reality there is only one decoder, which can decode either two 16-bit +;; instructions, or a single 32-bit instruction. +;; +;; Note, "fetch" models both the IF and the D pipeline stages. +;; +;; The m32rx core has two execution pipes. We name them o_E and s_E. +;; In addition, there's a memory unit. + +(define_cpu_unit "o_IF,s_IF,o_E,s_E,memory" "m32r") + +;; Prevent the s pipe from being reserved before the o pipe. +(absence_set "s_IF" "o_IF") +(absence_set "s_E" "o_E") + +;; On the M32Rx, long instructions execute on both pipes, so reserve +;; both fetch slots and both pipes. +(define_reservation "long_IF" "o_IF+s_IF") +(define_reservation "long_E" "o_E+s_E") + +;; :::::::::::::::::::: + +;; Simple instructions do 4 stages: IF D E WB. WB is not modelled. +;; Hence, ready latency is 1. +(define_insn_reservation "short_left" 1 + (and (eq_attr "m32r_pipeline" "o") (and (eq_attr "insn_size" "short") (eq_attr "type" "!load2"))) - 1 0 - [(eq_attr "insn_size" "long")]) + "o_IF,o_E") -(define_function_unit "short" 2 2 ;; load delay of 1 clock for mem execution + 1 clock for WB - (and (eq_attr "m32r" "yes") - (eq_attr "type" "load2")) - 3 0 - [(eq_attr "insn_size" "long")]) +(define_insn_reservation "short_right" 1 + (and (eq_attr "m32r_pipeline" "s") + (and (eq_attr "insn_size" "short") + (eq_attr "type" "!load2"))) + "s_IF,s_E") -(define_function_unit "long" 1 1 - (and (eq_attr "m32r" "yes") +(define_insn_reservation "short_either" 1 + (and (eq_attr "m32r_pipeline" "either") + (and (eq_attr "insn_size" "short") + (eq_attr "type" "!load2"))) + "o_IF|s_IF,o_E|s_E") + +(define_insn_reservation "long_m32r" 1 + (and (eq_attr "cpu" "m32r") (and (eq_attr "insn_size" "long") (eq_attr "type" "!load4,load8"))) - 1 0 - [(eq_attr "insn_size" "short")]) + "long_IF,long_E") -(define_function_unit "long" 1 1 ;; load delay of 1 clock for mem execution + 1 clock for WB - (and (eq_attr "m32r" "yes") - (and (eq_attr "insn_size" "long") - (eq_attr "type" "load4,load8"))) - 3 0 - [(eq_attr "insn_size" "short")]) - -(define_function_unit "left" 1 1 - (and (eq_attr "m32rx_pipeline" "o,either") - (eq_attr "type" "!load2")) - 1 0 - [(eq_attr "insn_size" "long")]) - -(define_function_unit "left" 1 1 ;; load delay of 1 clock for mem execution + 1 clock for WB - (and (eq_attr "m32rx_pipeline" "o,either") - (eq_attr "type" "load2")) - 3 0 - [(eq_attr "insn_size" "long")]) - -(define_function_unit "right" 1 1 - (eq_attr "m32rx_pipeline" "s,either") - 1 0 - [(eq_attr "insn_size" "long")]) - -(define_function_unit "long" 1 1 - (and (eq_attr "m32rx" "yes") +(define_insn_reservation "long_m32rx" 2 + (and (eq_attr "m32r_pipeline" "long") (and (eq_attr "insn_size" "long") (eq_attr "type" "!load4,load8"))) - 2 0 - [(eq_attr "insn_size" "short")]) + "long_IF,long_E") + +;; Load/store instructions do 6 stages: IF D E MEM1 MEM2 WB. +;; MEM1 may require more than one cycle depending on locality. We +;; optimistically assume all memory is nearby, i.e. MEM1 takes only +;; one cycle. Hence, ready latency is 3. -(define_function_unit "long" 1 1 ;; load delay of 1 clock for mem execution + 1 clock for WB - (and (eq_attr "m32rx" "yes") +;; The M32Rx can do short load/store only on the left pipe. +(define_insn_reservation "short_load_left" 3 + (and (eq_attr "m32r_pipeline" "o") + (and (eq_attr "insn_size" "short") + (eq_attr "type" "load2"))) + "o_IF,o_E,memory*2") + +(define_insn_reservation "short_load" 3 + (and (eq_attr "m32r_pipeline" "either") + (and (eq_attr "insn_size" "short") + (eq_attr "type" "load2"))) + "s_IF|o_IF,s_E|o_E,memory*2") + +(define_insn_reservation "long_load" 3 + (and (eq_attr "cpu" "m32r") (and (eq_attr "insn_size" "long") (eq_attr "type" "load4,load8"))) - 3 0 - [(eq_attr "insn_size" "short")]) + "long_IF,long_E,memory*2") + +(define_insn_reservation "long_load_m32rx" 3 + (and (eq_attr "m32r_pipeline" "long") + (eq_attr "type" "load4,load8")) + "long_IF,long_E,memory*2") + +(include "predicates.md") +(include "constraints.md") + ;; Expand prologue as RTL (define_expand "prologue" [(const_int 1)] @@ -279,6 +211,16 @@ DONE; }") +;; Expand epilogue as RTL +(define_expand "epilogue" + [(return)] + "" + " +{ + m32r_expand_epilogue (); + emit_jump_insn (gen_return_normal ()); + DONE; +}") ;; Move instructions. ;; @@ -293,6 +235,18 @@ "" " { + /* Fixup PIC cases. */ + if (flag_pic) + { + if (symbolic_operand (operands[1], QImode)) + { + if (reload_in_progress || reload_completed) + operands[1] = m32r_legitimize_pic_address (operands[1], operands[0]); + else + operands[1] = m32r_legitimize_pic_address (operands[1], NULL_RTX); + } + } + /* Everything except mem = const or mem = mem can be done easily. Objects in the small data area are handled too. */ @@ -321,6 +275,18 @@ "" " { + /* Fixup PIC cases. */ + if (flag_pic) + { + if (symbolic_operand (operands[1], HImode)) + { + if (reload_in_progress || reload_completed) + operands[1] = m32r_legitimize_pic_address (operands[1], operands[0]); + else + operands[1] = m32r_legitimize_pic_address (operands[1], NULL_RTX); + } + } + /* Everything except mem = const or mem = mem can be done easily. */ if (GET_CODE (operands[0]) == MEM) @@ -361,6 +327,18 @@ "" " { + /* Fixup PIC cases. */ + if (flag_pic) + { + if (symbolic_operand (operands[1], SImode)) + { + if (reload_in_progress || reload_completed) + operands[1] = m32r_legitimize_pic_address (operands[1], operands[0]); + else + operands[1] = m32r_legitimize_pic_address (operands[1], NULL_RTX); + } + } + /* Everything except mem = const or mem = mem can be done easily. */ if (GET_CODE (operands[0]) == MEM) @@ -410,14 +388,13 @@ return \"ld %0,%1\"; case CONST_INT: - value = INTVAL (operands[1]); - if (INT16_P (value)) + if (satisfies_constraint_J (operands[1])) return \"ldi %0,%#%1\\t; %X1\"; - if (UINT24_P (value)) + if (satisfies_constraint_M (operands[1])) return \"ld24 %0,%#%1\\t; %X1\"; - if (UPPER16_P (value)) + if (satisfies_constraint_L (operands[1])) return \"seth %0,%#%T1\\t; %X1\"; return \"#\"; @@ -442,7 +419,7 @@ return \"st %1,%0\"; } - abort (); + gcc_unreachable (); }" [(set_attr "type" "int2,int2,int4,int4,int4,multi,load2,load2,load4,store2,store2,store4") (set_attr "length" "2,2,4,4,4,8,2,2,4,2,2,4")]) @@ -466,7 +443,7 @@ use 2 byte instructions wherever possible. We can assume the constant isn't loadable with any of ldi, ld24, or seth. */ - /* See if we can load a 24 bit unsigned value and invert it. */ + /* See if we can load a 24-bit unsigned value and invert it. */ if (UINT24_P (~ val)) { emit_insn (gen_movsi (operands[0], GEN_INT (~ val))); @@ -474,7 +451,7 @@ DONE; } - /* See if we can load a 24 bit unsigned value and shift it into place. + /* See if we can load a 24-bit unsigned value and shift it into place. 0x01fffffe is just beyond ld24's range. */ for (shift = 1, tmp = 0x01fffffe; shift < 8; @@ -496,7 +473,7 @@ (define_split [(set (match_operand:SI 0 "register_operand" "") - (match_operand:SI 1 "seth_add3_operand" "i"))] + (match_operand:SI 1 "seth_add3_operand" ""))] "TARGET_ADDR32" [(set (match_dup 0) (high:SI (match_dup 1))) @@ -510,7 +487,7 @@ ;; the small data area are indexed off that. This is done for each reference ;; but cse will clean things up for us. We let the compiler choose the ;; register to use so we needn't allocate (and maybe even fix) a special -;; register to use. Since the load and store insns have a 16 bit offset the +;; register to use. Since the load and store insns have a 16-bit offset the ;; total size of the data area can be 64K. However, if the data area lives ;; above 16M (24 bits), _SDA_BASE_ will have to be loaded with seth/add3 which ;; would then yield 3 instructions to reference an object [though there would @@ -524,7 +501,7 @@ (define_expand "movsi_sda" [(set (match_dup 2) - (unspec [(const_int 0)] 2)) + (unspec:SI [(const_int 0)] UNSPEC_LOAD_SDA_BASE)) (set (match_operand:SI 0 "register_operand" "") (lo_sum:SI (match_dup 2) (match_operand:SI 1 "small_data_operand" "")))] @@ -537,15 +514,23 @@ operands[2] = gen_reg_rtx (SImode); }") +(define_insn "*load_sda_base_32" + [(set (match_operand:SI 0 "register_operand" "=r") + (unspec:SI [(const_int 0)] UNSPEC_LOAD_SDA_BASE))] + "TARGET_ADDR32" + "seth %0,%#shigh(_SDA_BASE_)\;add3 %0,%0,%#low(_SDA_BASE_)" + [(set_attr "type" "multi") + (set_attr "length" "8")]) + (define_insn "*load_sda_base" [(set (match_operand:SI 0 "register_operand" "=r") - (unspec [(const_int 0)] 2))] + (unspec:SI [(const_int 0)] UNSPEC_LOAD_SDA_BASE))] "" "ld24 %0,#_SDA_BASE_" [(set_attr "type" "int4") (set_attr "length" "4")]) -;; 32 bit address support. +;; 32-bit address support. (define_expand "movsi_addr32" [(set (match_dup 2) @@ -586,6 +571,18 @@ "" " { + /* Fixup PIC cases. */ + if (flag_pic) + { + if (symbolic_operand (operands[1], DImode)) + { + if (reload_in_progress || reload_completed) + operands[1] = m32r_legitimize_pic_address (operands[1], operands[0]); + else + operands[1] = m32r_legitimize_pic_address (operands[1], NULL_RTX); + } + } + /* Everything except mem = const or mem = mem can be done easily. */ if (GET_CODE (operands[0]) == MEM) @@ -615,6 +612,18 @@ "" " { + /* Fixup PIC cases. */ + if (flag_pic) + { + if (symbolic_operand (operands[1], SFmode)) + { + if (reload_in_progress || reload_completed) + operands[1] = m32r_legitimize_pic_address (operands[1], operands[0]); + else + operands[1] = m32r_legitimize_pic_address (operands[1], NULL_RTX); + } + } + /* Everything except mem = const or mem = mem can be done easily. */ if (GET_CODE (operands[0]) == MEM) @@ -655,6 +664,18 @@ "" " { + /* Fixup PIC cases. */ + if (flag_pic) + { + if (symbolic_operand (operands[1], DFmode)) + { + if (reload_in_progress || reload_completed) + operands[1] = m32r_legitimize_pic_address (operands[1], operands[0]); + else + operands[1] = m32r_legitimize_pic_address (operands[1], NULL_RTX); + } + } + /* Everything except mem = const or mem = mem can be done easily. */ if (GET_CODE (operands[0]) == MEM) @@ -732,7 +753,7 @@ " { rtx op0 = gen_lowpart (SImode, operands[0]); - rtx shift = gen_rtx (CONST_INT, VOIDmode, 24); + rtx shift = GEN_INT (24); operands[2] = gen_ashlsi3 (op0, op0, shift); operands[3] = gen_ashrsi3 (op0, op0, shift); @@ -757,11 +778,10 @@ (match_dup 3)] " { - rtx op0 = gen_lowpart (SImode, operands[0]); - rtx shift = gen_rtx (CONST_INT, VOIDmode, 24); + rtx shift = GEN_INT (24); - operands[2] = gen_ashlsi3 (op0, op0, shift); - operands[3] = gen_ashrsi3 (op0, op0, shift); + operands[2] = gen_ashlsi3 (operands[0], operands[0], shift); + operands[3] = gen_ashrsi3 (operands[0], operands[0], shift); }") (define_insn "extendhisi2" @@ -783,11 +803,10 @@ (match_dup 3)] " { - rtx op0 = gen_lowpart (SImode, operands[0]); - rtx shift = gen_rtx (CONST_INT, VOIDmode, 16); + rtx shift = GEN_INT (16); - operands[2] = gen_ashlsi3 (op0, op0, shift); - operands[3] = gen_ashrsi3 (op0, op0, shift); + operands[2] = gen_ashlsi3 (operands[0], operands[0], shift); + operands[3] = gen_ashrsi3 (operands[0], operands[0], shift); }") ;; Arithmetic instructions. @@ -814,7 +833,7 @@ ; (match_operand:SI 2 "int8_operand" "")))] ; "reload_completed ; && REGNO (operands[0]) != REGNO (operands[1]) -; && INT8_P (INTVAL (operands[2])) +; && satisfies_constraint_I (operands[2]) ; && INTVAL (operands[2]) != 0" ; [(set (match_dup 0) (match_dup 1)) ; (set (match_dup 0) (plus:SI (match_dup 0) (match_dup 2)))] @@ -824,7 +843,7 @@ [(set (match_operand:DI 0 "register_operand" "=r") (plus:DI (match_operand:DI 1 "register_operand" "%0") (match_operand:DI 2 "register_operand" "r"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -835,23 +854,23 @@ [(set (match_operand:DI 0 "register_operand" "") (plus:DI (match_operand:DI 1 "register_operand" "") (match_operand:DI 2 "register_operand" ""))) - (clobber (match_operand 3 "" ""))] + (clobber (reg:CC 17))] "reload_completed" - [(parallel [(set (match_dup 3) + [(parallel [(set (reg:CC 17) (const_int 0)) (use (match_dup 4))]) (parallel [(set (match_dup 4) (plus:SI (match_dup 4) (plus:SI (match_dup 5) - (match_dup 3)))) - (set (match_dup 3) - (unspec [(const_int 0)] 3))]) + (ne:SI (reg:CC 17) (const_int 0))))) + (set (reg:CC 17) + (unspec:CC [(const_int 0)] UNSPEC_SET_CBIT))]) (parallel [(set (match_dup 6) (plus:SI (match_dup 6) (plus:SI (match_dup 7) - (match_dup 3)))) - (set (match_dup 3) - (unspec [(const_int 0)] 3))])] + (ne:SI (reg:CC 17) (const_int 0))))) + (set (reg:CC 17) + (unspec:CC [(const_int 0)] UNSPEC_SET_CBIT))])] " { operands[4] = operand_subword (operands[0], (WORDS_BIG_ENDIAN != 0), 0, DImode); @@ -861,7 +880,7 @@ }") (define_insn "*clear_c" - [(set (reg:SI 17) + [(set (reg:CC 17) (const_int 0)) (use (match_operand:SI 0 "register_operand" "r"))] "" @@ -873,9 +892,9 @@ [(set (match_operand:SI 0 "register_operand" "=r") (plus:SI (match_operand:SI 1 "register_operand" "%0") (plus:SI (match_operand:SI 2 "register_operand" "r") - (reg:SI 17)))) - (set (reg:SI 17) - (unspec [(const_int 0)] 3))] + (ne:SI (reg:CC 17) (const_int 0))))) + (set (reg:CC 17) + (unspec:CC [(const_int 0)] UNSPEC_SET_CBIT))] "" "addx %0,%2" [(set_attr "type" "int2") @@ -894,7 +913,7 @@ [(set (match_operand:DI 0 "register_operand" "=r") (minus:DI (match_operand:DI 1 "register_operand" "0") (match_operand:DI 2 "register_operand" "r"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -905,23 +924,23 @@ [(set (match_operand:DI 0 "register_operand" "") (minus:DI (match_operand:DI 1 "register_operand" "") (match_operand:DI 2 "register_operand" ""))) - (clobber (match_operand 3 "" ""))] + (clobber (reg:CC 17))] "reload_completed" - [(parallel [(set (match_dup 3) + [(parallel [(set (reg:CC 17) (const_int 0)) (use (match_dup 4))]) (parallel [(set (match_dup 4) (minus:SI (match_dup 4) (minus:SI (match_dup 5) - (match_dup 3)))) - (set (match_dup 3) - (unspec [(const_int 0)] 3))]) + (ne:SI (reg:CC 17) (const_int 0))))) + (set (reg:CC 17) + (unspec:CC [(const_int 0)] UNSPEC_SET_CBIT))]) (parallel [(set (match_dup 6) (minus:SI (match_dup 6) (minus:SI (match_dup 7) - (match_dup 3)))) - (set (match_dup 3) - (unspec [(const_int 0)] 3))])] + (ne:SI (reg:CC 17) (const_int 0))))) + (set (reg:CC 17) + (unspec:CC [(const_int 0)] UNSPEC_SET_CBIT))])] " { operands[4] = operand_subword (operands[0], (WORDS_BIG_ENDIAN != 0), 0, DImode); @@ -934,9 +953,9 @@ [(set (match_operand:SI 0 "register_operand" "=r") (minus:SI (match_operand:SI 1 "register_operand" "%0") (minus:SI (match_operand:SI 2 "register_operand" "r") - (reg:SI 17)))) - (set (reg:SI 17) - (unspec [(const_int 0)] 3))] + (ne:SI (reg:CC 17) (const_int 0))))) + (set (reg:CC 17) + (unspec:CC [(const_int 0)] UNSPEC_SET_CBIT))] "" "subx %0,%2" [(set_attr "type" "int2") @@ -1014,8 +1033,7 @@ short instructions, which might eliminate a NOP being inserted. */ if (optimize_size && m32r_not_same_reg (operands[0], operands[1]) - && GET_CODE (operands[2]) == CONST_INT - && INT8_P (INTVAL (operands[2]))) + && satisfies_constraint_I (operands[2])) return \"#\"; else if (GET_CODE (operands[2]) == CONST_INT) @@ -1046,8 +1064,7 @@ short instructions, which might eliminate a NOP being inserted. */ if (optimize_size && m32r_not_same_reg (operands[0], operands[1]) - && GET_CODE (operands[2]) == CONST_INT - && INT8_P (INTVAL (operands[2]))) + && satisfies_constraint_I (operands[2])) return \"#\"; else if (GET_CODE (operands[2]) == CONST_INT) @@ -1078,8 +1095,7 @@ short instructions, which might eliminate a NOP being inserted. */ if (optimize_size && m32r_not_same_reg (operands[0], operands[1]) - && GET_CODE (operands[2]) == CONST_INT - && INT8_P (INTVAL (operands[2]))) + && satisfies_constraint_I (operands[2])) return \"#\"; else if (GET_CODE (operands[2]) == CONST_INT) @@ -1156,7 +1172,7 @@ ;; Compare instructions. ;; This controls RTL generation and register allocation. -;; We generate RTL for comparisons and branches by having the cmpxx +;; We generate RTL for comparisons and branches by having the cmpxx ;; patterns store away the operands. Then the bcc patterns ;; emit RTL for both the compare and the branch. ;; @@ -1165,7 +1181,7 @@ ;; preferred. (define_expand "cmpsi" - [(set (reg:SI 17) + [(set (reg:CC 17) (compare:CC (match_operand:SI 0 "register_operand" "") (match_operand:SI 1 "reg_or_cmp_int16_operand" "")))] "" @@ -1177,10 +1193,10 @@ }") (define_insn "cmp_eqsi_zero_insn" - [(set (reg:SI 17) - (eq:SI (match_operand:SI 0 "register_operand" "r,r") + [(set (reg:CC 17) + (eq:CC (match_operand:SI 0 "register_operand" "r,r") (match_operand:SI 1 "reg_or_zero_operand" "r,P")))] - "TARGET_M32RX" + "TARGET_M32RX || TARGET_M32R2" "@ cmpeq %0, %1 cmpz %0" @@ -1192,8 +1208,8 @@ ;; is quite inefficient. However, it is rarely used. (define_insn "cmp_eqsi_insn" - [(set (reg:SI 17) - (eq:SI (match_operand:SI 0 "register_operand" "r,r") + [(set (reg:CC 17) + (eq:CC (match_operand:SI 0 "register_operand" "r,r") (match_operand:SI 1 "reg_or_cmp_int16_operand" "r,P"))) (clobber (match_scratch:SI 2 "=&r,&r"))] "" @@ -1217,8 +1233,8 @@ (set_attr "length" "8,8")]) (define_insn "cmp_ltsi_insn" - [(set (reg:SI 17) - (lt:SI (match_operand:SI 0 "register_operand" "r,r") + [(set (reg:CC 17) + (lt:CC (match_operand:SI 0 "register_operand" "r,r") (match_operand:SI 1 "reg_or_int16_operand" "r,J")))] "" "@ @@ -1228,8 +1244,8 @@ (set_attr "length" "2,4")]) (define_insn "cmp_ltusi_insn" - [(set (reg:SI 17) - (ltu:SI (match_operand:SI 0 "register_operand" "r,r") + [(set (reg:CC 17) + (ltu:CC (match_operand:SI 0 "register_operand" "r,r") (match_operand:SI 1 "reg_or_int16_operand" "r,J")))] "" "@ @@ -1237,23 +1253,6 @@ cmpui %0,%#%1" [(set_attr "type" "int2,int4") (set_attr "length" "2,4")]) - - -;; reg == small constant comparisons are best handled by putting the result -;; of the comparison in a tmp reg and then using beqz/bnez. -;; ??? The result register doesn't contain 0/STORE_FLAG_VALUE, -;; it contains 0/non-zero. - -(define_insn "cmp_ne_small_const_insn" - [(set (match_operand:SI 0 "register_operand" "=r,r") - (ne:SI (match_operand:SI 1 "register_operand" "0,r") - (match_operand:SI 2 "cmp_int16_operand" "N,P")))] - "" - "@ - addi %0,%#%N2 - add3 %0,%1,%#%N2" - [(set_attr "type" "int2,int4") - (set_attr "length" "2,4")]) ;; These control RTL generation for conditional jump insns. @@ -1385,15 +1384,16 @@ return instruction; }" [(set_attr "type" "branch") - ; We use 400/800 instead of 512,1024 to account for inaccurate insn + ; cf PR gcc/28508 + ; We use 300/600 instead of 512,1024 to account for inaccurate insn ; lengths and insn alignments that are complex to track. ; It's not important that we be hyper-precise here. It may be more ; important blah blah blah when the chip supports parallel execution ; blah blah blah but until then blah blah blah this is simple and ; suffices. (set (attr "length") (if_then_else (ltu (plus (minus (match_dup 0) (pc)) - (const_int 400)) - (const_int 800)) + (const_int 300)) + (const_int 600)) (const_int 2) (const_int 4)))]) @@ -1414,15 +1414,16 @@ return instruction; }" [(set_attr "type" "branch") - ; We use 400/800 instead of 512,1024 to account for inaccurate insn + ; cf PR gcc/28508 + ; We use 300/600 instead of 512,1024 to account for inaccurate insn ; lengths and insn alignments that are complex to track. ; It's not important that we be hyper-precise here. It may be more ; important blah blah blah when the chip supports parallel execution ; blah blah blah but until then blah blah blah this is simple and ; suffices. (set (attr "length") (if_then_else (ltu (plus (minus (match_dup 0) (pc)) - (const_int 400)) - (const_int 800)) + (const_int 300)) + (const_int 600)) (const_int 2) (const_int 4)))]) @@ -1522,7 +1523,7 @@ case LT : br = \"lt\"; invbr = \"ge\"; break; case GE : br = \"ge\"; invbr = \"lt\"; break; - default: abort(); + default: gcc_unreachable (); } /* Is branch target reachable with bxxz? */ @@ -1569,7 +1570,7 @@ case LT : br = \"lt\"; invbr = \"ge\"; break; case GE : br = \"ge\"; invbr = \"lt\"; break; - default: abort(); + default: gcc_unreachable (); } /* Is branch target reachable with bxxz? */ @@ -1612,7 +1613,7 @@ if (! register_operand (op1, mode)) op1 = force_reg (mode, op1); - if (TARGET_M32RX) + if (TARGET_M32RX || TARGET_M32R2) { if (! reg_or_zero_operand (op2, mode)) op2 = force_reg (mode, op2); @@ -1637,8 +1638,8 @@ [(set (match_operand:SI 0 "register_operand" "=r") (eq:SI (match_operand:SI 1 "register_operand" "%r") (match_operand:SI 2 "reg_or_zero_operand" "rP"))) - (clobber (reg:SI 17))] - "TARGET_M32RX" + (clobber (reg:CC 17))] + "TARGET_M32RX || TARGET_M32R2" "#" [(set_attr "type" "multi") (set_attr "length" "6")]) @@ -1647,20 +1648,20 @@ [(set (match_operand:SI 0 "register_operand" "") (eq:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_zero_operand" ""))) - (clobber (reg:SI 17))] - "TARGET_M32RX" - [(set (reg:SI 17) - (eq:SI (match_dup 1) + (clobber (reg:CC 17))] + "TARGET_M32RX || TARGET_M32R2" + [(set (reg:CC 17) + (eq:CC (match_dup 1) (match_dup 2))) (set (match_dup 0) - (reg:SI 17))] + (ne:SI (reg:CC 17) (const_int 0)))] "") (define_insn "seq_zero_insn" [(set (match_operand:SI 0 "register_operand" "=r") (eq:SI (match_operand:SI 1 "register_operand" "r") (const_int 0))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "TARGET_M32R" "#" [(set_attr "type" "multi") @@ -1670,7 +1671,7 @@ [(set (match_operand:SI 0 "register_operand" "") (eq:SI (match_operand:SI 1 "register_operand" "") (const_int 0))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "TARGET_M32R" [(match_dup 3)] " @@ -1679,9 +1680,9 @@ rtx op1 = operands[1]; start_sequence (); - emit_insn (gen_cmp_ltusi_insn (op1, GEN_INT (1))); + emit_insn (gen_cmp_ltusi_insn (op1, const1_rtx)); emit_insn (gen_movcc_insn (op0)); - operands[3] = gen_sequence (); + operands[3] = get_insns (); end_sequence (); }") @@ -1689,7 +1690,7 @@ [(set (match_operand:SI 0 "register_operand" "=r,r,??r,r") (eq:SI (match_operand:SI 1 "register_operand" "r,r,r,r") (match_operand:SI 2 "reg_or_eq_int16_operand" "r,r,r,PK"))) - (clobber (reg:SI 17)) + (clobber (reg:CC 17)) (clobber (match_scratch:SI 3 "=1,2,&r,r"))] "TARGET_M32R" "#" @@ -1700,7 +1701,7 @@ [(set (match_operand:SI 0 "register_operand" "") (eq:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_eq_int16_operand" ""))) - (clobber (reg:SI 17)) + (clobber (reg:CC 17)) (clobber (match_scratch:SI 3 ""))] "TARGET_M32R && reload_completed" [(match_dup 4)] @@ -1727,15 +1728,14 @@ op1 = op3; } - if (GET_CODE (op2) == CONST_INT && (value = INTVAL (op2)) != 0 - && CMP_INT16_P (value)) + if (satisfies_constraint_P (op2) && (value = INTVAL (op2)) != 0) emit_insn (gen_addsi3 (op3, op1, GEN_INT (-value))); else emit_insn (gen_xorsi3 (op3, op1, op2)); - emit_insn (gen_cmp_ltusi_insn (op3, GEN_INT (1))); + emit_insn (gen_cmp_ltusi_insn (op3, const1_rtx)); emit_insn (gen_movcc_insn (op0)); - operands[4] = gen_sequence (); + operands[4] = get_insns (); end_sequence (); }") @@ -1752,8 +1752,8 @@ if (mode != SImode) FAIL; - if (GET_CODE (op2) != CONST_INT - || (INTVAL (op2) != 0 && UINT16_P (INTVAL (op2)))) + if (GET_CODE (op2) != CONST_INT + || (INTVAL (op2) != 0 && satisfies_constraint_K (op2))) { rtx reg; @@ -1778,7 +1778,7 @@ [(set (match_operand:SI 0 "register_operand" "=r") (ne:SI (match_operand:SI 1 "register_operand" "r") (const_int 0))) - (clobber (reg:SI 17)) + (clobber (reg:CC 17)) (clobber (match_scratch:SI 2 "=&r"))] "" "#" @@ -1789,18 +1789,18 @@ [(set (match_operand:SI 0 "register_operand" "") (ne:SI (match_operand:SI 1 "register_operand" "") (const_int 0))) - (clobber (reg:SI 17)) + (clobber (reg:CC 17)) (clobber (match_scratch:SI 2 ""))] "reload_completed" [(set (match_dup 2) (const_int 0)) - (set (reg:SI 17) - (ltu:SI (match_dup 2) + (set (reg:CC 17) + (ltu:CC (match_dup 2) (match_dup 1))) (set (match_dup 0) - (reg:SI 17))] + (ne:SI (reg:CC 17) (const_int 0)))] "") - + (define_expand "slt" [(match_operand:SI 0 "register_operand" "")] "" @@ -1828,7 +1828,7 @@ [(set (match_operand:SI 0 "register_operand" "=r,r") (lt:SI (match_operand:SI 1 "register_operand" "r,r") (match_operand:SI 2 "reg_or_int16_operand" "r,J"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -1838,13 +1838,13 @@ [(set (match_operand:SI 0 "register_operand" "") (lt:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_int16_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" - [(set (reg:SI 17) - (lt:SI (match_dup 1) + [(set (reg:CC 17) + (lt:CC (match_dup 1) (match_dup 2))) (set (match_dup 0) - (reg:SI 17))] + (ne:SI (reg:CC 17) (const_int 0)))] "") (define_expand "sle" @@ -1868,7 +1868,7 @@ HOST_WIDE_INT value = INTVAL (op2); if (value >= 2147483647) { - emit_move_insn (op0, GEN_INT (1)); + emit_move_insn (op0, const1_rtx); DONE; } @@ -1891,7 +1891,7 @@ [(set (match_operand:SI 0 "register_operand" "=r") (le:SI (match_operand:SI 1 "register_operand" "r") (match_operand:SI 2 "register_operand" "r"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -1901,13 +1901,13 @@ [(set (match_operand:SI 0 "register_operand" "") (le:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "register_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "!optimize_size" - [(set (reg:SI 17) - (lt:SI (match_dup 2) + [(set (reg:CC 17) + (lt:CC (match_dup 2) (match_dup 1))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (xor:SI (match_dup 0) (const_int 1)))] @@ -1919,13 +1919,13 @@ [(set (match_operand:SI 0 "register_operand" "") (le:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "register_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "optimize_size" - [(set (reg:SI 17) - (lt:SI (match_dup 2) + [(set (reg:CC 17) + (lt:CC (match_dup 2) (match_dup 1))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (plus:SI (match_dup 0) (const_int -1))) @@ -1983,7 +1983,7 @@ [(set (match_operand:SI 0 "register_operand" "=r,r") (ge:SI (match_operand:SI 1 "register_operand" "r,r") (match_operand:SI 2 "reg_or_int16_operand" "r,J"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -1993,13 +1993,13 @@ [(set (match_operand:SI 0 "register_operand" "") (ge:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_int16_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "!optimize_size" - [(set (reg:SI 17) - (lt:SI (match_dup 1) + [(set (reg:CC 17) + (lt:CC (match_dup 1) (match_dup 2))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (xor:SI (match_dup 0) (const_int 1)))] @@ -2011,13 +2011,13 @@ [(set (match_operand:SI 0 "register_operand" "") (ge:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_int16_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "optimize_size" - [(set (reg:SI 17) - (lt:SI (match_dup 1) + [(set (reg:CC 17) + (lt:CC (match_dup 1) (match_dup 2))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (plus:SI (match_dup 0) (const_int -1))) @@ -2052,7 +2052,7 @@ [(set (match_operand:SI 0 "register_operand" "=r,r") (ltu:SI (match_operand:SI 1 "register_operand" "r,r") (match_operand:SI 2 "reg_or_int16_operand" "r,J"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -2062,13 +2062,13 @@ [(set (match_operand:SI 0 "register_operand" "") (ltu:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_int16_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" - [(set (reg:SI 17) - (ltu:SI (match_dup 1) + [(set (reg:CC 17) + (ltu:CC (match_dup 1) (match_dup 2))) (set (match_dup 0) - (reg:SI 17))] + (ne:SI (reg:CC 17) (const_int 0)))] "") (define_expand "sleu" @@ -2089,7 +2089,7 @@ HOST_WIDE_INT value = INTVAL (op2); if (value >= 2147483647) { - emit_move_insn (op0, GEN_INT (1)); + emit_move_insn (op0, const1_rtx); DONE; } @@ -2112,7 +2112,7 @@ [(set (match_operand:SI 0 "register_operand" "=r") (leu:SI (match_operand:SI 1 "register_operand" "r") (match_operand:SI 2 "register_operand" "r"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -2122,13 +2122,13 @@ [(set (match_operand:SI 0 "register_operand" "") (leu:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "register_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "!optimize_size" - [(set (reg:SI 17) - (ltu:SI (match_dup 2) + [(set (reg:CC 17) + (ltu:CC (match_dup 2) (match_dup 1))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (xor:SI (match_dup 0) (const_int 1)))] @@ -2140,13 +2140,13 @@ [(set (match_operand:SI 0 "register_operand" "") (leu:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "register_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "optimize_size" - [(set (reg:SI 17) - (ltu:SI (match_dup 2) + [(set (reg:CC 17) + (ltu:CC (match_dup 2) (match_dup 1))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (plus:SI (match_dup 0) (const_int -1))) @@ -2204,7 +2204,7 @@ [(set (match_operand:SI 0 "register_operand" "=r,r") (geu:SI (match_operand:SI 1 "register_operand" "r,r") (match_operand:SI 2 "reg_or_int16_operand" "r,J"))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "" "#" [(set_attr "type" "multi") @@ -2214,13 +2214,13 @@ [(set (match_operand:SI 0 "register_operand" "") (geu:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_int16_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "!optimize_size" - [(set (reg:SI 17) - (ltu:SI (match_dup 1) + [(set (reg:CC 17) + (ltu:CC (match_dup 1) (match_dup 2))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (xor:SI (match_dup 0) (const_int 1)))] @@ -2232,13 +2232,13 @@ [(set (match_operand:SI 0 "register_operand" "") (geu:SI (match_operand:SI 1 "register_operand" "") (match_operand:SI 2 "reg_or_int16_operand" ""))) - (clobber (reg:SI 17))] + (clobber (reg:CC 17))] "optimize_size" - [(set (reg:SI 17) - (ltu:SI (match_dup 1) + [(set (reg:CC 17) + (ltu:CC (match_dup 1) (match_dup 2))) (set (match_dup 0) - (reg:SI 17)) + (ne:SI (reg:CC 17) (const_int 0))) (set (match_dup 0) (plus:SI (match_dup 0) (const_int -1))) @@ -2248,7 +2248,7 @@ (define_insn "movcc_insn" [(set (match_operand:SI 0 "register_operand" "=r") - (reg:SI 17))] + (ne:SI (reg:CC 17) (const_int 0)))] "" "mvfc %0, cbr" [(set_attr "type" "misc") @@ -2275,14 +2275,68 @@ [(set_attr "type" "uncond_branch") (set_attr "length" "2")]) -(define_insn "return" - [(return)] - "direct_return ()" +(define_insn "return_lr" + [(parallel [(return) (use (reg:SI 14))])] + "" "jmp lr" [(set_attr "type" "uncond_branch") (set_attr "length" "2")]) - -(define_insn "tablejump" + +(define_insn "return_rte" + [(return)] + "" + "rte" + [(set_attr "type" "uncond_branch") + (set_attr "length" "2")]) + +(define_expand "return" + [(return)] + "direct_return ()" + " +{ + emit_jump_insn (gen_return_lr ()); + DONE; +}") + +(define_expand "return_normal" + [(return)] + "!direct_return ()" + " +{ + enum m32r_function_type fn_type; + + fn_type = m32r_compute_function_type (current_function_decl); + if (M32R_INTERRUPT_P (fn_type)) + { + emit_jump_insn (gen_return_rte ()); + DONE; + } + + emit_jump_insn (gen_return_lr ()); + DONE; +}") + +(define_expand "tablejump" + [(parallel [(set (pc) (match_operand 0 "register_operand" "r")) + (use (label_ref (match_operand 1 "" "")))])] + "" + " +{ + /* In pic mode, our address differences are against the base of the + table. Add that base value back in; CSE ought to be able to combine + the two address loads. */ + if (flag_pic) + { + rtx tmp, tmp2; + + tmp = gen_rtx_LABEL_REF (Pmode, operands[1]); + tmp2 = operands[0]; + tmp = gen_rtx_PLUS (Pmode, tmp2, tmp); + operands[0] = memory_address (Pmode, tmp); + } +}") + +(define_insn "*tablejump_insn" [(set (pc) (match_operand:SI 0 "address_operand" "p")) (use (label_ref (match_operand 1 "" "")))] "" @@ -2297,7 +2351,11 @@ (match_operand 1 "" "")) (clobber (reg:SI 14))])] "" - "") + " +{ + if (flag_pic) + crtl->uses_pic_offset_table = 1; +}") (define_insn "*call_via_reg" [(call (mem:SI (match_operand:SI 0 "register_operand" "r")) @@ -2348,7 +2406,11 @@ (match_operand 2 "" ""))) (clobber (reg:SI 14))])] "" - "") + " +{ + if (flag_pic) + crtl->uses_pic_offset_table = 1; +}") (define_insn "*call_value_via_reg" [(set (match_operand 0 "register_operand" "=r") @@ -2370,6 +2432,9 @@ { int call26_p = call26_operand (operands[1], FUNCTION_MODE); + if (flag_pic) + crtl->uses_pic_offset_table = 1; + if (! call26_p) { /* We may not be able to reach with a `bl' insn so punt and leave it to @@ -2404,18 +2469,21 @@ ;; all of memory. This blocks insns from being moved across this point. (define_insn "blockage" - [(unspec_volatile [(const_int 0)] 0)] + [(unspec_volatile [(const_int 0)] UNSPECV_BLOCKAGE)] "" "") ;; Special pattern to flush the icache. (define_insn "flush_icache" - [(unspec_volatile [(match_operand 0 "memory_operand" "m")] 0)] + [(unspec_volatile [(match_operand 0 "memory_operand" "m")] + UNSPECV_FLUSH_ICACHE) + (match_operand 1 "" "") + (clobber (reg:SI 17))] "" - "* return \"nop ; flush-icache\";" - [(set_attr "type" "int2") - (set_attr "length" "2")]) + "* return \"trap %#%1 ; flush-icache\";" + [(set_attr "type" "int4") + (set_attr "length" "4")]) ;; Speed up fabs and provide correct sign handling for -0 @@ -2477,7 +2545,7 @@ if (! zero_and_one (operands [2], operands [3])) FAIL; - /* Generate the comparision that will set the carry flag. */ + /* Generate the comparison that will set the carry flag. */ operands[1] = gen_compare (GET_CODE (operands[1]), m32r_compare_op0, m32r_compare_op1, TRUE); @@ -2501,71 +2569,13 @@ ) -;; Split up troublesome insns for better scheduling. -;; FIXME: Peepholes go at the end. - -;; ??? Setting the type attribute may not be useful, but for completeness -;; we do it. - -(define_peephole - [(set (mem:SI (plus:SI (match_operand:SI 0 "register_operand" "r") - (const_int 4))) - (match_operand:SI 1 "register_operand" "r"))] - "0 && dead_or_set_p (insn, operands[0])" - "st %1,@+%0" - [(set_attr "type" "store2") - (set_attr "length" "2")]) - -;; This case is triggered by compiling this code: -;; -;; extern void sub(int *); -;; void main (void) -;; { -;; int i=2,j=3,k; -;; while (i < j) sub(&k); -;; i = j / k; -;; sub(&i); -;; i = j - k; -;; sub(&i); -;; } -;; -;; Without the peephole the following assembler is generated for the -;; divide and subtract expressions: -;; -;; div r5,r4 -;; mv r4,r5 -;; st r4,@(4,sp) -;; bl sub -;; -;; Simialr code is produced for the subtract expression. With this -;; peephole the redundant move is eliminated. -;; -;; This optimisation onbly works if PRESERVE_DEATH_INFO_REGNO_P is -;; defined in m32r.h - -(define_peephole - [(set (match_operand:SI 0 "register_operand" "r") - (match_operand:SI 1 "register_operand" "r") - ) - (set (mem:SI (plus: SI (match_operand:SI 2 "register_operand" "r") - (match_operand:SI 3 "immediate_operand" "J"))) - (match_dup 0) - ) - ] - "0 && dead_or_set_p (insn, operands [0])" - "st %1,@(%3,%2)" - [(set_attr "type" "store4") - (set_attr "length" "4") - ] -) - ;; Block moves, see m32r.c for more details. ;; Argument 0 is the destination ;; Argument 1 is the source ;; Argument 2 is the length ;; Argument 3 is the alignment -(define_expand "movstrsi" +(define_expand "movmemsi" [(parallel [(set (match_operand:BLK 0 "general_operand" "") (match_operand:BLK 1 "general_operand" "")) (use (match_operand:SI 2 "immediate_operand" "")) @@ -2573,24 +2583,74 @@ "" " { - if (operands[0]) /* avoid unused code messages */ + if (operands[0]) /* Avoid unused code messages. */ { - m32r_expand_block_move (operands); - DONE; + if (m32r_expand_block_move (operands)) + DONE; + else + FAIL; } }") ;; Insn generated by block moves -(define_insn "movstrsi_internal" - [(set (mem:BLK (match_operand:SI 0 "register_operand" "+r")) ;; destination - (mem:BLK (match_operand:SI 1 "register_operand" "+r"))) ;; source +(define_insn "movmemsi_internal" + [(set (mem:BLK (match_operand:SI 0 "register_operand" "r")) ;; destination + (mem:BLK (match_operand:SI 1 "register_operand" "r"))) ;; source (use (match_operand:SI 2 "m32r_block_immediate_operand" "J"));; # bytes to move - (set (match_dup 0) (plus:SI (match_dup 0) (minus:SI (match_dup 2) (const_int 4)))) - (set (match_dup 1) (plus:SI (match_dup 1) (match_dup 2))) - (clobber (match_scratch:SI 3 "=&r")) ;; temp 1 - (clobber (match_scratch:SI 4 "=&r"))] ;; temp 2 + (set (match_operand:SI 3 "register_operand" "=0") + (plus:SI (minus (match_dup 2) (const_int 4)) + (match_dup 0))) + (set (match_operand:SI 4 "register_operand" "=1") + (plus:SI (match_dup 1) + (match_dup 2))) + (clobber (match_scratch:SI 5 "=&r")) ;; temp1 + (clobber (match_scratch:SI 6 "=&r"))] ;; temp2 "" "* m32r_output_block_move (insn, operands); return \"\"; " [(set_attr "type" "store8") (set_attr "length" "72")]) ;; Maximum + +;; PIC + +/* When generating pic, we need to load the symbol offset into a register. + So that the optimizer does not confuse this with a normal symbol load + we use an unspec. The offset will be loaded from a constant pool entry, + since that is the only type of relocation we can use. */ + +(define_insn "pic_load_addr" + [(set (match_operand:SI 0 "register_operand" "=r") + (unspec:SI [(match_operand 1 "" "")] UNSPEC_PIC_LOAD_ADDR))] + "flag_pic" + "ld24 %0,%#%1" + [(set_attr "type" "int4")]) + +(define_insn "gotoff_load_addr" + [(set (match_operand:SI 0 "register_operand" "=r") + (unspec:SI [(match_operand 1 "" "")] UNSPEC_GOTOFF))] + "flag_pic" + "seth %0, %#shigh(%1@GOTOFF)\;add3 %0, %0, low(%1@GOTOFF)" + [(set_attr "type" "int4") + (set_attr "length" "8")]) + +;; Load program counter insns. + +(define_insn "get_pc" + [(clobber (reg:SI 14)) + (set (match_operand 0 "register_operand" "=r,r") + (unspec [(match_operand 1 "" "")] UNSPEC_GET_PC)) + (use (match_operand:SI 2 "immediate_operand" "W,i"))] + "flag_pic" + "@ + bl.s .+4\;seth %0,%#shigh(%1)\;add3 %0,%0,%#low(%1+4)\;add %0,lr + bl.s .+4\;ld24 %0,%#%1\;add %0,lr" + [(set_attr "length" "12,8")]) + +(define_expand "builtin_setjmp_receiver" + [(label_ref (match_operand 0 "" ""))] + "flag_pic" + " +{ + m32r_load_pic_register (); + DONE; +}")