home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Education Sampler 1992 [NeXTSTEP]
/
Education_1992_Sampler.iso
/
NeXT
/
GnuSource
/
cc-61.0.1
/
cc
/
config
/
m88k.md
< prev
next >
Wrap
Text File
|
1991-06-10
|
86KB
|
2,962 lines
;;- Machine description for the Motorola 88000 for GNU C compiler
;; Copyright (C) 1988, 1990 Free Software Foundation, Inc.
;; Contributed by Michael Tiemann (tiemann@mcc.com)
;; Additional changes by Michael Meissner (meissner@osf.org)
;; Currently supported by Tom Wood (wood@dg-rtp.dg.com)
;; This file is part of GNU CC.
;; 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.
;; 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.
;; 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, 675 Mass Ave, Cambridge, MA 02139, USA.
;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
;; SCCS rev field. This is a NOP, just to get the SCCS id into the
;; program image.
(define_expand "m88k_sccs_id"
[(match_operand:SI 0 "" "")]
""
"{ static char sccs_id[] = \"@(#)m88k.md 1.93.5.4 5/29/91 07:30:05\";
FAIL; }")
;; Attribute specifications
; Type of each instruction. Default is arithmetic.
; I'd like to write the list as this, but genattrtab won't accept it.
;
; "branch,jump,call, ; flow-control instructions
; load,store,loada, ; data unit instructions
; spadd,dpadd,spdiv,dpdiv,idiv, ; FPU add instructions
; spmul,dpmul,imul, ; FPU multiply instructions
; arith, ; integer unit instructions
; marith,mstore,mfp,wierd" ; multi-word instructions
; Classification of each insn. Some insns of TYPE_BRANCH are multi-word.
(define_attr "type"
"branch,jump,call,load,store,loada,spadd,dpadd,spdiv,dpdiv,idiv,spmul,dpmul,imul,arith,marith,mstore,mfp,wierd"
(const_string "arith"))
; Convenience attributes.
(define_attr "fpu" "yes,no"
(if_then_else
(eq_attr "type" "spmul,dpmul,imul,spadd,dpadd,spdiv,dpdiv,idiv,mfp")
(const_string "yes") (const_string "no")))
; Length in # of instructions of each insn. The values are not exact, but
; are safe.
(define_attr "length" ""
(cond [(eq_attr "type" "marith,mstore,mfp")
(const_int 2)]
(const_int 1)))
; Describe a user's asm statement.
(define_asm_attributes
[(set_attr "type" "wierd")])
; Define the delay slot requirements for branches and calls.
; The m88100 annuls instructions if a conditional branch is taken.
; For insns of TYPE_BRANCH that are multi-word instructions, the
; delay slot applies to the first instruction.
; @@ For the moment, reorg.c requires that the delay slot of a branch not
; be a call or branch.
(define_delay (eq_attr "type" "branch,jump")
[(and
(and
(eq_attr "type" "!branch,jump,call,marith,mstore,mfp,wierd") ; required.
(eq_attr "type" "!load")) ; issue as-soon-as-possible.
(eq_attr "fpu" "no")) ; issue as-soon-as-possible.
(eq_attr "type" "!call,branch,jump") (nil)]) ; @@ was (const_int 1)
; output_call supports an unconditional branch in the delay slot of
; a call. (@@ Support for this case is expected in reorg.c soon.)
(define_delay (eq_attr "type" "call")
[(eq_attr "type" "!branch,call,marith,mstore,mfp,wierd") ; required.
(nil) (nil)])
; An abstract block diagram of the function units for the m88100.
;
; *
; |
; +---v----+
; | decode |
; +-vv-v-v-+ fpu
; ,----------'| | `----------------------.
; | | | | ,-----.
; load | store | | arith | | |
; | | | +-v-v-+ | dp source
; | | | | fp1 |---'
; store | | | div +-v-v-+
; ,------. | | | ,-----. ,-----------' `-----------.
; | | | | | | | | |
; | +--v---v--+ ,---' | | +-v-v---+ +---v---+
; | | stage 2 | | | `---| add 2 | | mul 2 |
; | +---------+ | +--v--+ +-------+ imul +-------+
; | | stage 1 | | | alu | | add 3 | ,--------| mul 3 |
; | +---------+ | +--v--+ +-------+ | +-------+
; | | stage 0 | | | | add 4 | | | mul 4 |
; | +--v---v--+ | | +---v---+ | +-------+
; | | | | | | | | mul 5 |
; | * | | | | | +---v---+
; | | | | | +----v----+ |
; | load | | | fp add `------>| fp last |<------' fp mul
; | | | | +---v-v--^+
; | | | | | | |
; | | | | | `--' dp dest
; | | +--v-----v--+ |
; | `--->| writeback |<--------------------'
; | +--v-----v--+
; | | |
; `------------------' *
;
; The decode unit need not be specified.
; Consideration of writeback contention is critical to superb scheduling.
;
; (define_function_unit NAME MULTIPLICITY SIMULTANEITY
; TEST READY-DELAY BUSY-DELAY [CONFLICT-LIST])
;(define_function_unit "decode" 1 1 (const_int 1) 0 1)
; Describing the alu is currently not useful.
;(define_function_unit "alu" 1 0 (eq_attr "type"
; "!store,mstore,marith,mfp,wierd") 1 0)
;(define_function_unit "alu" 1 0 (eq_attr "type" "marith,wierd") 2 0)
(define_function_unit "memory" 1 3 (eq_attr "type" "load") 3 2)
(define_function_unit "fp1" 1 1 (eq_attr "fpu" "yes") 1 2)
(define_function_unit "fpmul" 1 4 (eq_attr "type" "spmul") 4 2)
(define_function_unit "fpmul" 1 4 (eq_attr "type" "dpmul,mfp") 7 2)
(define_function_unit "fpmul" 1 4 (eq_attr "type" "imul") 2 2)
(define_function_unit "fpadd" 1 3 (eq_attr "type" "spadd") 3 2)
(define_function_unit "fpadd" 1 3 (eq_attr "type" "dpadd") 4 2)
(define_function_unit "fpadd" 1 3 (eq_attr "type" "spdiv") 28 2)
(define_function_unit "fpadd" 1 3 (eq_attr "type" "dpdiv") 58 2)
(define_function_unit "fpadd" 1 3 (eq_attr "type" "idiv") 36 2)
(define_function_unit "fplast" 1 1 (eq_attr "fpu" "yes") 1 2)
; Describing writeback contention is currently not useful.
;(define_function_unit "writeback" 1 1
; (eq_attr "type" "!store,mstore,branch,jump,call") 0 1)
; Describing stores is currently not useful. The suggestion here is that the
; function unit ordering has already been established (writeback is last) and
; that store insns use the units in an unusal order.
;(define_function_unit "writeback" 1 1 (eq_attr "type" "store,mstore") 0 1)
;(define_function_unit "memory" 1 3 (eq_attr "type" "store,mstore") 1 2)
;; This rich set of complex patterns are mostly due to Torbjorn Granlund
;; (tege@sics.se). They've changed since then, so don't complain to him
;; if they don't work right.
;; Regarding shifts, gen_lshlsi3 generates ASHIFT. LSHIFT opcodes are
;; not produced and should not normally occur. Also, the gen functions
;; produce the necessary insns to support TARGET_*_LARGE_SHIFT, so nothing
;; special needs to be done here.
;; (a << int1) >> int2 optimizations into a single extract.
;; These patterns need to occur before the normal shift patterns
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ashiftrt:SI (ashift:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "int5_operand" ""))
(match_operand:SI 3 "int5_operand" "")))]
"INTVAL (operands [2]) <= INTVAL (operands [3])"
"ext %0,%1,%w3<(%3-%2)>")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(lshiftrt:SI (ashift:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "int5_operand" ""))
(match_operand:SI 3 "int5_operand" "")))]
"INTVAL (operands [2]) <= INTVAL (operands [3])"
"extu %0,%1,%w3<(%3-%2)>")
;; Optimize possible cases of the set instruction.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ashift:SI (const_int -1)
(match_operand:SI 1 "register_operand" "r")))]
""
"set %0,%#r0,%1")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ior:SI (ashift:SI (const_int -1)
(match_operand:SI 1 "register_operand" "r"))
(match_operand:SI 2 "register_operand" "r")))]
""
"set %0,%2,%1")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ior:SI (match_operand:SI 1 "register_operand" "r")
(ashift:SI (const_int -1)
(match_operand:SI 2 "register_operand" "r"))))]
""
"set %0,%1,%2")
;; Optimize possible cases of the mak instruction.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(and:SI (ashift:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "int5_operand" ""))
(match_operand:SI 3 "immediate_operand" "n")))]
"mak_mask_p (INTVAL (operands[3]) >> INTVAL (operands[2]))"
"*
{
operands[4] = gen_rtx (CONST_INT, SImode,
exact_log2 (1 + (INTVAL (operands[3])
>> INTVAL(operands[2]))));
return \"mak %0,%1,%4<%2>\";
}")
;; Optimize possible cases of output_and.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ashift:SI (zero_extract:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "int5_operand" "")
(match_operand:SI 3 "int5_operand" ""))
(match_operand:SI 4 "int5_operand" "")))]
"INTVAL (operands[2]) + INTVAL (operands[3]) + INTVAL (operands[4]) == 32"
"*
{
operands[2]
= gen_rtx (CONST_INT, SImode,
((1 << INTVAL (operands[2])) - 1) << INTVAL (operands[4]));
return output_and (operands);
}"
[(set_attr "type" "marith")]) ; length is 1 or 2.
;; Recognize bcnd instructions for integer values. This is distinguished
;; from a conditional branch instruction (below) with SImode instead of
;; CCmode.
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "relop_no_unsigned"
[(match_operand:SI 1 "register_operand" "r")
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bcnd%. %R3%B0,%1,%P2%P3"
[(set_attr "type" "branch")])
;; Recognize tests for sign and zero.
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "equality_op"
[(match_operand:SI 1 "register_operand" "r")
(const_int -2147483648)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bcnd%. %R3%E0,%1,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "equality_op"
[(zero_extract:SI
(match_operand:SI 1 "register_operand" "r")
(const_int 31)
(const_int 1))
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bcnd%. %R3%D0,%1,%P2%P3"
[(set_attr "type" "branch")])
;; Recognize bcnd instructions for double integer values
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "relop_no_unsigned"
[(sign_extend:DI
(match_operand:SI 1 "register_operand" "r"))
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bcnd%. %R3%B0,%1,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "equality_op"
[(zero_extend:DI
(match_operand:SI 1 "register_operand" "r"))
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bcnd%. %R3%B0,%1,%P2%P3"
[(set_attr "type" "branch")])
; @@ I doubt this is interesting until cmpdi is provided. Anyway, it needs
; to be reworked.
;
;(define_insn ""
; [(set (pc)
; (if_then_else
; (match_operator 0 "relop_no_unsigned"
; [(match_operand:DI 1 "register_operand" "r")
; (const_int 0)])
; (match_operand 2 "pc_or_label_ref" "")
; (match_operand 3 "pc_or_label_ref" "")))]
; ""
; "*
;{
; switch (GET_CODE (operands[0]))
; {
; case EQ:
; case NE:
; /* I'm not sure if it's safe to use .n here. */
; return \"or %!,%1,%d1\;bcnd %R3%B0,%!,%P2%P3\";
; case GE:
; case LT:
; return \"bcnd%. %R3%B0,%1,%P2%P3\";
; case GT:
; {
; rtx op2 = operands[2];
; operands[2] = operands[3];
; operands[3] = op2;
; }
; case LE:
; if (GET_CODE (operands[3]) == LABEL_REF)
; {
; int label_num;
; operands[2] = gen_label_rtx ();
; label_num = XINT (operands[2], 3);
; output_asm_insn
; (\"bcnd%. %#lt0,%1,%2\;or %!,%1,%d1\;bcnd %#ne0,%!,%3\", operands);
; output_label (label_num);
; return \"\";
; }
; else
; return \"bcnd%. %#lt0,%1,%2\;or %!,%1,%d1\;bcnd %#eq0,%!,%2\";
; }
;}")
;; Recognize bcnd instructions for single precision float values
;; Exclude relational operations as they must signal NaNs.
;; @@ These bcnd insns for float and double values don't seem to be recognized.
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "equality_op"
[(float_extend:DF
(match_operand:SF 1 "register_operand" "r"))
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bcnd%. %R3%D0,%1,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "equality_op"
[(match_operand:SF 1 "register_operand" "r")
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bcnd%. %R3%D0,%1,%P2%P3"
[(set_attr "type" "branch")])
;; Recognize bcnd instructions for double precision float values
;; Exclude relational operations as they must signal NaNs.
(define_insn ""
[(set (pc)
(if_then_else
(match_operator 0 "equality_op"
[(match_operand:DF 1 "register_operand" "r")
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"*
{
int label_num;
if (GET_CODE (operands[0]) == NE)
{
rtx op2 = operands[2];
operands[2] = operands[3];
operands[3] = op2;
}
if (GET_CODE (operands[3]) == LABEL_REF)
return \"bcnd%. 0x5,%1,%3\;bcnd %#ne0,%d1,%3\";
operands[3] = gen_label_rtx ();
label_num = XINT (operands[3], 3);
output_asm_insn (\"bcnd%. 0x5,%1,%3\;bcnd %#eq0,%d1,%2\", operands);
output_label (label_num);
return \"\";
}"
[(set_attr "type" "branch")])
;; Recognize bb0 and bb1 instructions. These use two unusual template
;; patterns, %Lx and %Px. %Lx outputs a 1 if operand `x' is a LABEL_REF
;; otherwise it outputs a 0. It then may print ".n" if the delay slot
;; is used. %Px does noting if `x' is PC and outputs the operand if `x'
;; is a LABEL_REF.
(define_insn ""
[(set (pc)
(if_then_else
(ne (sign_extract:SI (match_operand:SI 0 "register_operand" "r")
(const_int 1)
(match_operand:SI 1 "int5_operand" ""))
(const_int 0))
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bb%L2 (31-%1),%0,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(eq (sign_extract:SI (match_operand:SI 0 "register_operand" "r")
(const_int 1)
(match_operand:SI 1 "int5_operand" ""))
(const_int 0))
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bb%L3 (31-%1),%0,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(ne (zero_extract:SI (match_operand:SI 0 "register_operand" "r")
(const_int 1)
(match_operand:SI 1 "int5_operand" ""))
(const_int 0))
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bb%L2 (31-%1),%0,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(eq (zero_extract:SI (match_operand:SI 0 "register_operand" "r")
(const_int 1)
(match_operand:SI 1 "int5_operand" ""))
(const_int 0))
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bb%L3 (31-%1),%0,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(eq (and:SI (match_operand:SI 0 "reg_or_bbx_mask_operand" "%r")
(match_operand:SI 1 "reg_or_bbx_mask_operand" "n"))
(const_int 0))
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
"(GET_CODE (operands[0]) == CONST_INT)
!= (GET_CODE (operands[1]) == CONST_INT)"
"bb%L3 %p1,%0,%P2%P3"
[(set_attr "type" "branch")])
(define_insn ""
[(set (pc)
(if_then_else
(ne (and:SI (match_operand:SI 0 "reg_or_bbx_mask_operand" "%r")
(match_operand:SI 1 "reg_or_bbx_mask_operand" "n"))
(const_int 0))
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
"(GET_CODE (operands[0]) == CONST_INT)
!= (GET_CODE (operands[1]) == CONST_INT)"
"bb%L2 %p1,%0,%P2%P3"
[(set_attr "type" "branch")])
;; The comparison operations store the comparison into a register and
;; record that register. The following Bxx or Sxx insn uses that
;; register as an input. To facilitate use of bcnd instead of cmp/bb1,
;; cmpsi records it's operands and produces no code when any operand
;; is constant. In this case, the Bxx insns use gen_bcnd and the
;; Sxx insns use gen_test to ensure a cmp has been emitted.
;;
;; This could also be done for SFmode and DFmode having only beq and bne
;; use gen_bcnd. The others must signal NaNs. It seems though that zero
;; has already been copied into a register.
;;
;; cmpsi/beq and cmpsi/bne can always be done with bcnd if any operand
;; is a constant. (This idea is due to Torbjorn Granlund.) Others can
;; use bcnd only if an operand is zero.
;;
;; It is necessary to distinguish a register holding condition codes.
;; This is done by context.
(define_expand "test"
[(set (match_dup 2)
(compare:CC (match_operand 0 "" "")
(match_operand 1 "" "")))]
""
"
{
if (m88k_compare_reg)
abort ();
if (GET_CODE (operands[0]) == CONST_INT
&& ! SMALL_INT (operands[0]))
operands[0] = force_reg (SImode, operands[0]);
if (GET_CODE (operands[1]) == CONST_INT
&& ! SMALL_INT (operands[1]))
operands[1] = force_reg (SImode, operands[1]);
operands[2] = m88k_compare_reg = gen_reg_rtx (CCmode);
}")
; @@ The docs say don't do this. It's probably a nop since the insn looks
; identical to cmpsi against zero. Is there an advantage to providing
; this, perhaps with a different form?
;(define_expand "tstsi"
; [(set (match_dup 1)
; (compare:CC (match_operand:SI 0 "register_operand" "")
; (const_int 0)))]
; ""
; "
;{
; m88k_compare_reg = 0;
; m88k_compare_op0 = operands[0];
; m88k_compare_op1 = const0_rtx;
; DONE;
;}")
;; (NeXT) Changed arith32_operand to reg_or_0_operand to match
;; the actual compare insn.
(define_expand "cmpsi"
[(set (match_dup 2)
(compare:CC (match_operand:SI 0 "reg_or_0_operand" "")
(match_operand:SI 1 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[0]) == CONST_INT
|| GET_CODE (operands[1]) == CONST_INT)
{
m88k_compare_reg = 0;
m88k_compare_op0 = operands[0];
m88k_compare_op1 = operands[1];
DONE;
}
operands[2] = m88k_compare_reg = gen_reg_rtx (CCmode);
}")
(define_expand "cmpsf"
[(set (match_dup 2)
(compare:CC (match_operand:SF 0 "register_operand" "")
(match_operand:SF 1 "register_operand" "")))]
""
"operands[2] = m88k_compare_reg = gen_reg_rtx (CCmode);")
(define_expand "cmpdf"
[(set (match_dup 2)
(compare:CC (match_operand:DF 0 "register_operand" "")
(match_operand:DF 1 "register_operand" "")))]
""
"operands[2] = m88k_compare_reg = gen_reg_rtx (CCmode);")
; @@ Get back to this later on.
;
;(define_insn "cmpdi"
; [(set (cc0)
; (compare:CC (match_operand:DI 0 "register_operand" "r")
; (match_operand:DI 1 "register_operand" "r")))]
; ""
; "*
;{
; if ((cc_status.mdep & MDEP_LS_CHANGE) != 0)
; abort (); /* output_move_double MDEP_LS_CHANGE bits were set. */
;
; cc_status.mdep &= ~ MDEP_LS_MASK;
;
; operands[2] = gen_label_rtx ();
; /* Remember, %! is the condition code register and %@ is the
; literal synthesis register. */
;
; output_asm_insn (\"cmp %!,%0,%1\;bb0 %#eq,%!,%l2\;cmp %!,%d0,%d1\",
; operands);
;
; output_asm_insn (\"extu %@,%!,4<8>\;clr %!,%!,4<4>\", operands);
; output_asm_insn (\"mak %@,%@,4<4>\;or %!,%!,%@\", operands);
; output_label (XINT (operands[2], 3));
; return \"\";
;}"
;; The actual compare instructions.
;; (NeXT) The second alternative is completely bugus!!!
;; It gets the wrong answer for tests of equality.
;; Besides, we shouldn't have to clutter up the md with this.
;; The compiler should be able to reverse the comparison.
;;
;; (define_insn ""
;; [(set (match_operand:CC 0 "register_operand" "=r,r")
;; (compare:CC (match_operand:SI 1 "reg_or_0_operand" "rO,I")
;; (match_operand:SI 2 "arith_operand" "rI,r")))]
;; ""
;; "@
;; cmp %0,%r1,%2
;; cmp %0,%2,%1\;xor.c %0,%#r0,%0"
;; [(set_attr "type" "arith,marith")])
(define_insn ""
[(set (match_operand:CC 0 "register_operand" "=r")
(compare:CC (match_operand:SI 1 "reg_or_0_operand" "rO")
(match_operand:SI 2 "arith_operand" "rI")))]
""
"cmp %0,%r1,%2"
[(set_attr "type" "arith")])
(define_insn ""
[(set (match_operand:CC 0 "register_operand" "=r,r")
(compare:CC (match_operand:SF 1 "register_operand" "r,r")
(match_operand:SF 2 "real_or_0_operand" "r,G")))]
""
"@
fcmp.sss %0,%1,%2
fcmp.sss %0,%1,%#r0"
[(set_attr "type" "spadd")])
(define_insn ""
[(set (match_operand:CC 0 "register_operand" "=r")
(compare:CC (match_operand:DF 1 "register_operand" "r")
(float_extend:DF
(match_operand:SF 2 "register_operand" "r"))))]
""
"fcmp.sds %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn ""
[(set (match_operand:CC 0 "register_operand" "=r")
(compare:CC (float_extend:DF
(match_operand:SF 1 "register_operand" "r"))
(match_operand:DF 2 "register_operand" "r")))]
""
"fcmp.ssd %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn ""
[(set (match_operand:CC 0 "register_operand" "=r,r")
(compare:CC (match_operand:DF 1 "register_operand" "r,r")
(match_operand:DF 2 "real_or_0_operand" "r,G")))]
""
"@
fcmp.sdd %0,%1,%2
fcmp.sds %0,%1,%#r0"
[(set_attr "type" "dpadd")])
;; Store condition code insns. The compare insns set a register
;; rather than cc0 and record that register for use here. See above
;; for the special treatment of cmpsi with a constant operand.
(define_expand "seq"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (EQ, SImode);")
(define_expand "sne"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (NE, SImode);")
(define_expand "sgt"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (GT, SImode);")
(define_expand "sgtu"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (GTU, SImode);")
(define_expand "slt"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (LT, SImode);")
(define_expand "sltu"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (LTU, SImode);")
(define_expand "sge"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (GE, SImode);")
(define_expand "sgeu"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (GEU, SImode);")
(define_expand "sle"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (LE, SImode);")
(define_expand "sleu"
[(set (match_operand:SI 0 "register_operand" "")
(match_dup 1))]
""
"operands[1] = emit_test (LEU, SImode);")
;; The actual set condition code instruction.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(match_operator:SI 1 "relop"
[(match_operand:CC 2 "register_operand" "r")
(const_int 0)]))]
""
"extu %0,%2,1<%C1>")
;; Special cases to support TARGET_HANDLE_LARGE_SHIFT.
(define_expand "extendsleu"
[(set (match_operand:SI 0 "register_operand" "")
(neg:SI (match_dup 1)))]
""
"operands[1] = emit_test (LEU, SImode);")
(define_expand "extendsgtu"
[(set (match_operand:SI 0 "register_operand" "")
(neg:SI (match_dup 1)))]
""
"operands[1] = emit_test (GTU, SImode);")
;; The actual sign-extend set condition code instruction.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(neg:SI
(match_operator:SI 1 "relop"
[(match_operand:CC 2 "register_operand" "r")
(const_int 0)])))]
""
"ext %0,%2,1<%C1>")
;; Conditional branch insns. The compare insns set a register
;; rather than cc0 and record that register for use here. See above
;; for the special case of cmpsi with a constant operand.
(define_expand "bcnd"
[(set (pc)
(if_then_else (match_operand 0 "" "")
(label_ref (match_operand 1 "" ""))
(pc)))]
""
"if (m88k_compare_reg) abort ();")
(define_expand "bxx"
[(set (pc)
(if_then_else (match_operand 0 "" "")
(label_ref (match_operand 1 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0) abort ();")
(define_expand "beq"
[(set (pc)
(if_then_else (eq (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_bcnd (EQ, operands[0]);
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "bne"
[(set (pc)
(if_then_else (ne (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_bcnd (NE, operands[0]);
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "bgt"
[(set (pc)
(if_then_else (gt (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_bcnd (GT, operands[0]);
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "bgtu"
[(set (pc)
(if_then_else (gtu (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_jump_insn (gen_bxx (emit_test (GTU, VOIDmode), operands[0]));
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "blt"
[(set (pc)
(if_then_else (lt (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_bcnd (LT, operands[0]);
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "bltu"
[(set (pc)
(if_then_else (ltu (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_jump_insn (gen_bxx (emit_test (LTU, VOIDmode), operands[0]));
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "bge"
[(set (pc)
(if_then_else (ge (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_bcnd (GE, operands[0]);
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "bgeu"
[(set (pc)
(if_then_else (geu (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_jump_insn (gen_bxx (emit_test (GEU, VOIDmode), operands[0]));
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "ble"
[(set (pc)
(if_then_else (le (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_bcnd (LE, operands[0]);
DONE;
}
operands[1] = m88k_compare_reg;")
(define_expand "bleu"
[(set (pc)
(if_then_else (leu (match_dup 1) (const_int 0))
(label_ref (match_operand 0 "" ""))
(pc)))]
""
"if (m88k_compare_reg == 0)
{
emit_jump_insn (gen_bxx (emit_test (LEU, VOIDmode), operands[0]));
DONE;
}
operands[1] = m88k_compare_reg;")
;; The actual conditional branch instruction (both directions). This
;; uses two unusual template patterns, %Rx and %Px. %Rx is a prefix code
;; for the immediately following condition and reverses the condition iff
;; operand `x' is a LABEL_REF. %Px does nothing if `x' is PC and outputs
;; the operand if `x' is a LABEL_REF.
(define_insn ""
[(set (pc) (if_then_else
(match_operator 0 "relop"
[(match_operand:CC 1 "register_operand" "r")
(const_int 0)])
(match_operand 2 "pc_or_label_ref" "")
(match_operand 3 "pc_or_label_ref" "")))]
""
"bb1%. %R3%C0,%1,%P2%P3"
[(set_attr "type" "branch")])
;; SImode move instructions
(define_expand "movsi"
[(set (match_operand:SI 0 "general_operand" "")
(match_operand:SI 1 "general_operand" ""))]
""
"
{
rtx temp = emit_move_sequence (operands, SImode);
if (temp)
return temp;
}")
(define_insn ""
[(set (match_operand:SI 0 "nonimmediate_operand" "=r,r,m,r,r")
(match_operand:SI 1 "move_operand" "rI,m,rO,J,M"))]
"(register_operand (operands[0], SImode)
|| register_operand (operands[1], SImode)
|| operands[1] == const0_rtx)"
"@
or %0,%#r0,%1
ld %0,%1
st %r1,%0
subu %0,%#r0,%n1
set %0,%#r0,%s1"
[(set_attr "type" "arith,load,store,arith,arith")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r,r,r,r")
(match_operand:SI 1 "arith32_operand" "rI,J,L,M,n"))]
""
"@
or %0,%#r0,%1
subu %0,%#r0,%n1
or.u %0,%#r0,%X1
set %0,%#r0,%s1
or.u %0,%#r0,%X1\;or %0,%0,%x1"
[(set_attr "type" "arith,arith,arith,arith,marith")])
;; @@ Why the constraint "in"? Doesn't `i' include `n'?
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(lo_sum:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "immediate_operand" "in")))]
""
"or %0,%1,%#lo16(%g2)")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(high:SI (match_operand 1 "" "")))]
""
"or.u %0,%#r0,%#hi16(%g1)")
;; HImode move instructions
(define_expand "movhi"
[(set (match_operand:HI 0 "general_operand" "")
(match_operand:HI 1 "general_operand" ""))]
""
"
{
rtx temp = emit_move_sequence (operands, HImode);
if (temp)
return temp;
}")
(define_insn ""
[(set (match_operand:HI 0 "nonimmediate_operand" "=r,r,m,r")
(match_operand:HI 1 "move_operand" "rP,m,rO,N"))]
"(register_operand (operands[0], HImode)
|| register_operand (operands[1], HImode)
|| operands[1] == const0_rtx)"
"@
or %0,%#r0,%h1
ld.hu %0,%1
st.h %r1,%0
subu %0,%#r0,%H1"
[(set_attr "type" "arith,load,store,arith")])
(define_insn ""
[(set (match_operand:HI 0 "register_operand" "=r")
(subreg:HI (lo_sum:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "immediate_operand" "in")) 0))]
"!flag_pic"
"or %0,%1,%#lo16(%2)")
;; QImode move instructions
(define_expand "movqi"
[(set (match_operand:QI 0 "general_operand" "")
(match_operand:QI 1 "general_operand" ""))]
""
"
{
rtx temp = emit_move_sequence (operands, QImode);
if (temp)
return temp;
}")
(define_insn ""
[(set (match_operand:QI 0 "nonimmediate_operand" "=r,r,m,r")
(match_operand:QI 1 "move_operand" "rP,m,rO,N"))]
"(register_operand (operands[0], QImode)
|| register_operand (operands[1], QImode)
|| operands[1] == const0_rtx)"
"@
or %0,%#r0,%q1
ld.bu %0,%1
st.b %r1,%0
subu %r0,%#r0,%Q1"
[(set_attr "type" "arith,load,store,arith")])
(define_insn ""
[(set (match_operand:QI 0 "register_operand" "=r")
(subreg:QI (lo_sum:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "immediate_operand" "in")) 0))]
"!flag_pic"
"or %0,%1,%#lo16(%2)")
;; DImode move instructions
(define_expand "movdi"
[(set (match_operand:DI 0 "general_operand" "")
(match_operand:DI 1 "general_operand" ""))]
""
"
{
rtx temp = emit_move_sequence (operands, DImode);
if (temp)
return temp;
}")
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(const_int 0))]
""
"or %0,%#r0,0\;or %d0,%#r0,0"
[(set_attr "type" "marith")])
(define_insn ""
[(set (match_operand:DI 0 "nonimmediate_operand" "=r,r,m")
(match_operand:DI 1 "nonimmediate_operand" "r,m,r"))]
""
"@
or %0,%#r0,%1\;or %d0,%#r0,%d1
ld.d %0,%1
st.d %1,%0"
[(set_attr "type" "marith,load,store")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(subreg:DI (lo_sum:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "immediate_operand" "in")) 0))]
"!flag_pic"
"or %0,%1,%#lo16(%2)")
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(match_operand:DI 1 "immediate_operand" "n"))]
""
"* return output_load_const_dimode (operands);"
[(set_attr "type" "marith")
(set_attr "length" "4")]) ; length is 2, 3 or 4.
;; DFmode move instructions
(define_expand "movdf"
[(set (match_operand:DF 0 "general_operand" "")
(match_operand:DF 1 "general_operand" ""))]
""
"
{
rtx temp = emit_move_sequence (operands, DFmode);
if (temp)
return temp;
}")
;; @@ This pattern is incomplete and doesn't appear necessary.
;;
;; This pattern forces (set (reg:DF ...) (const_double ...))
;; to be reloaded by putting the constant into memory.
;; It must come before the more general movdf pattern.
;(define_insn ""
; [(set (match_operand:DF 0 "general_operand" "=r,o")
; (match_operand:DF 1 "" "G,G"))]
; "GET_CODE (operands[1]) == CONST_DOUBLE"
; "*
;{
; switch (which_alternative)
; {
; case 0:
; return \"or %0,%#r0,0\;or %d0,%#r0,0\";
; case 1:
; operands[1] = adj_offsettable_operand (operands[0], 4);
; return \"st %#r0,%0\;st %#r0,%1\";
; }
;}")
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(const_int 0))]
""
"or %0,%#r0,0\;or %d0,%#r0,0"
[(set_attr "type" "marith")])
(define_insn ""
[(set (match_operand:DF 0 "nonimmediate_operand" "=r,r,m")
(match_operand:DF 1 "nonimmediate_operand" "r,m,r"))]
""
"@
or %0,%#r0,%1\;or %d0,%#r0,%d1
ld.d %0,%1
st.d %1,%0"
[(set_attr "type" "marith,load,store")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(subreg:DF (lo_sum:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "immediate_operand" "in")) 0))]
"!flag_pic"
"or %0,%1,%#lo16(%2)")
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(match_operand:DF 1 "immediate_operand" "F"))]
""
"* return output_load_const_double (operands);"
[(set_attr "type" "marith")
(set_attr "length" "4")]) ; length is 2, 3, or 4.
;; SFmode move instructions
(define_expand "movsf"
[(set (match_operand:SF 0 "general_operand" "")
(match_operand:SF 1 "general_operand" ""))]
""
"
{
rtx temp = emit_move_sequence (operands, SFmode);
if (temp)
return temp;
}")
;; @@ What happens to fconst0_rtx?
(define_insn ""
[(set (match_operand:SF 0 "register_operand" "=r")
(const_int 0))]
""
"or %0,%#r0,0")
(define_insn ""
[(set (match_operand:SF 0 "nonimmediate_operand" "=r,r,m")
(match_operand:SF 1 "nonimmediate_operand" "r,m,r"))]
""
"@
or %0,%#r0,%1
ld %0,%1
st %r1,%0"
[(set_attr "type" "arith,load,store")])
(define_insn ""
[(set (match_operand:SF 0 "register_operand" "=r")
(subreg:SF (lo_sum:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "immediate_operand" "in")) 0))]
"!flag_pic"
"or %0,%1,%#lo16(%2)")
(define_insn ""
[(set (match_operand:SF 0 "register_operand" "=r")
(match_operand:SF 1 "immediate_operand" "F"))]
"operands[1] != const0_rtx"
"* return output_load_const_float (operands);"
[(set_attr "type" "marith")]) ; length is 1 or 2.
;; String/block move insn. See out-m88k.c for details.
(define_expand "movstrsi"
[(parallel [(set (mem:BLK (match_operand:BLK 0 "general_operand" ""))
(mem:BLK (match_operand:BLK 1 "general_operand" "")))
(use (match_operand:SI 2 "arith32_operand" ""))
(use (match_operand:SI 3 "immediate_operand" ""))])]
""
"
{
rtx dest_mem = operands[0];
rtx src_mem = operands[1];
operands[0] = copy_to_mode_reg (SImode, XEXP (operands[0], 0));
operands[1] = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
expand_block_move (dest_mem, src_mem, operands);
DONE;
}")
;; Call a non-looping block move library function (e.g. __movstrSI96x64).
;; operand 0 is the function name
;; operand 1 is the destination pointer
;; operand 2 is the source pointer
;; operand 3 is the offset for the source and destination pointers
;; operand 4 is the first value to be loaded
;; operand 5 is the register to hold the value (r4 or r5)
;; Upon completion, r2 and r3 are unchanged
(define_expand "call_block_move"
[(set (reg:SI 3) (minus:SI (match_operand:SI 2 "register_operand" "r")
(match_operand:SI 3 "immediate_operand" "i")))
(use (reg:SI 3))
(set (match_operand 5 "register_operand" "r")
(match_operand 4 "memory_operand" "m"))
(use (reg:SI 4))
(use (reg:SI 5))
(set (reg:SI 2) (minus:SI (match_operand:SI 1 "register_operand" "r")
(match_dup 3)))
(use (reg:SI 2))
(parallel [(call (mem:SI (match_operand 0 "" ""))
(const_int 0))
(use (reg:SI 1))])
(clobber (reg:SI 4))
(clobber (reg:SI 5))]
""
"")
;; Call a looping block move library function (e.g. __movstrSI64n68).
;; operands 0-5 as in the non-looping interface
;; operand 6 is the loop count
(define_expand "call_block_move_loop"
[(set (reg:SI 3) (minus:SI (match_operand:SI 2 "register_operand" "r")
(match_operand:SI 3 "immediate_operand" "i")))
(use (reg:SI 3))
(set (match_operand:SI 5 "register_operand" "r")
(match_operand:SI 4 "memory_operand" "m"))
(use (reg:SI 4))
(use (reg:SI 5))
(set (reg:SI 2) (minus:SI (match_operand:SI 1 "register_operand" "r")
(match_dup 3)))
(use (reg:SI 2))
(set (reg:SI 6) (match_operand:SI 6 "immediate_operand" "i"))
(use (reg:SI 6))
(parallel [(call (mem:SI (match_operand 0 "" ""))
(const_int 0))
(use (reg:SI 1))])
(clobber (reg:SI 4))
(clobber (reg:SI 5))
(clobber (reg:SI 6))]
""
"")
;;- zero extension instructions
;; Note that the one starting from HImode comes before those for QImode
;; so that a constant operand will match HImode, not QImode.
(define_expand "zero_extendhisi2"
[(set (match_operand:SI 0 "register_operand" "")
(zero_extend:SI
(match_operand:HI 1 "general_operand" "")))]
""
"
{
if (GET_CODE (operands[1]) == MEM
&& symbolic_address_p (XEXP (operands[1], 0)))
operands[1]
= legitimize_address (flag_pic, operands[1], gen_reg_rtx (Pmode));
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r,r")
(zero_extend:SI
(match_operand:HI 1 "move_operand" "!r,n,m")))]
""
"@
mask %0,%1,0xffff
or %0,%#r0,%h1
ld.hu %0,%1"
[(set_attr "type" "arith,arith,load")])
(define_expand "zero_extendqihi2"
[(set (match_operand:HI 0 "register_operand" "")
(zero_extend:HI
(match_operand:QI 1 "general_operand" "")))]
""
"
{
if (GET_CODE (operands[1]) == MEM
&& symbolic_address_p (XEXP (operands[1], 0)))
operands[1]
= legitimize_address (flag_pic, operands[1], gen_reg_rtx (Pmode));
}")
(define_insn ""
[(set (match_operand:HI 0 "register_operand" "=r,r,r")
(zero_extend:HI
(match_operand:QI 1 "move_operand" "r,n,m")))]
""
"@
mask %0,%1,0xff
or %0,%#r0,%q1
ld.bu %0,%1"
[(set_attr "type" "arith,arith,load")])
(define_expand "zero_extendqisi2"
[(set (match_operand:SI 0 "register_operand" "")
(zero_extend:SI
(match_operand:QI 1 "general_operand" "")))]
""
"
{
if (GET_CODE (operands[1]) == MEM
&& symbolic_address_p (XEXP (operands[1], 0)))
{
operands[1]
= legitimize_address (flag_pic, operands[1], gen_reg_rtx (Pmode));
emit_insn (gen_rtx (SET, VOIDmode, operands[0],
gen_rtx (ZERO_EXTEND, SImode, operands[1])));
DONE;
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r,r")
(zero_extend:SI
(match_operand:QI 1 "move_operand" "r,n,m")))]
""
"@
mask %0,%1,0xff
or %0,%#r0,%q1
ld.bu %0,%1"
[(set_attr "type" "arith,arith,load")])
;;- sign extension instructions
;; Note that the one starting from HImode comes before those for QImode
;; so that a constant operand will match HImode, not QImode.
(define_expand "extendsidi2"
[(set (subreg:SI (match_operand:DI 0 "register_operand" "=r") 1)
(match_operand:SI 1 "general_operand" "g"))
(set (subreg:SI (match_dup 0) 0)
(ashiftrt:SI (subreg:SI (match_dup 0) 1)
(const_int 31)))]
""
"")
(define_expand "extendhisi2"
[(set (match_operand:SI 0 "register_operand" "")
(sign_extend:SI
(match_operand:HI 1 "general_operand" "")))]
""
"
{
if (GET_CODE (operands[1]) == MEM
&& symbolic_address_p (XEXP (operands[1], 0)))
operands[1]
= legitimize_address (flag_pic, operands[1], gen_reg_rtx (Pmode));
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r,r,r")
(sign_extend:SI
(match_operand:HI 1 "move_operand" "!r,P,N,m")))]
""
"@
ext %0,%1,16<0>
or %0,%#r0,%h1
subu %0,%#r0,%H1
ld.h %0,%1"
[(set_attr "type" "arith,arith,arith,load")])
(define_expand "extendqihi2"
[(set (match_operand:HI 0 "register_operand" "")
(sign_extend:HI
(match_operand:QI 1 "general_operand" "")))]
""
"
{
if (GET_CODE (operands[1]) == MEM
&& symbolic_address_p (XEXP (operands[1], 0)))
operands[1]
= legitimize_address (flag_pic, operands[1], gen_reg_rtx (Pmode));
}")
(define_insn ""
[(set (match_operand:HI 0 "register_operand" "=r,r,r,r")
(sign_extend:HI
(match_operand:QI 1 "move_operand" "!r,P,N,m")))]
""
"@
ext %0,%1,8<0>
or %0,%#r0,%q1
subu %0,%#r0,%Q1
ld.b %0,%1"
[(set_attr "type" "arith,arith,arith,load")])
(define_expand "extendqisi2"
[(set (match_operand:SI 0 "register_operand" "")
(sign_extend:SI
(match_operand:QI 1 "general_operand" "")))]
""
"
{
if (GET_CODE (operands[1]) == MEM
&& symbolic_address_p (XEXP (operands[1], 0)))
operands[1]
= legitimize_address (flag_pic, operands[1], gen_reg_rtx (Pmode));
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r,r,r")
(sign_extend:SI
(match_operand:QI 1 "move_operand" "!r,P,N,m")))]
""
"@
ext %0,%1,8<0>
or %0,%#r0,%q1
subu %0,%#r0,%Q1
ld.b %0,%1"
[(set_attr "type" "arith,arith,arith,load")])
;; Conversions between float and double.
(define_insn "extendsfdf2"
[(set (match_operand:DF 0 "register_operand" "=r")
(float_extend:DF (match_operand:SF 1 "register_operand" "r")))]
""
"fadd.dss %0,%#r0,%1"
[(set_attr "type" "spadd")])
(define_insn "truncdfsf2"
[(set (match_operand:SF 0 "register_operand" "=r")
(float_truncate:SF (match_operand:DF 1 "register_operand" "r")))]
""
"fadd.ssd %0,%#r0,%1"
[(set_attr "type" "dpadd")])
;; Conversions between floating point and integer
(define_insn "floatsidf2"
[(set (match_operand:DF 0 "register_operand" "=r")
(float:DF (match_operand:SI 1 "register_operand" "r")))]
""
"flt.ds %0,%1"
[(set_attr "type" "spadd")])
(define_insn "floatsisf2"
[(set (match_operand:SF 0 "register_operand" "=r")
(float:SF (match_operand:SI 1 "register_operand" "r")))]
""
"flt.ss %0,%1"
[(set_attr "type" "spadd")])
(define_insn "fix_truncdfsi2"
[(set (match_operand:SI 0 "register_operand" "=r")
(fix:SI (match_operand:DF 1 "register_operand" "r")))]
""
"trnc.sd %0,%1"
[(set_attr "type" "dpadd")])
(define_insn "fix_truncsfsi2"
[(set (match_operand:SI 0 "register_operand" "=r")
(fix:SI (match_operand:SF 1 "register_operand" "r")))]
""
"trnc.ss %0,%1"
[(set_attr "type" "spadd")])
;;- arithmetic instructions
;;- add instructions
(define_insn "addsi3"
[(set (match_operand:SI 0 "register_operand" "=r,r")
(plus:SI (match_operand:SI 1 "add_operand" "%r,r")
(match_operand:SI 2 "add_operand" "rI,J")))]
""
"@
addu %0,%1,%2
subu %0,%1,%n2")
;; In unusual contexts, an add of a large value is generated (case statements
;; for example). In these contexts, it is sufficient to accept only those
;; cases where the two registers are different.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,&r")
(plus:SI (match_operand:SI 1 "arith32_operand" "%r,r")
(match_operand:SI 2 "arith32_operand" "r,!n")))]
""
"*
{
rtx xoperands[10];
if (which_alternative == 0)
return \"addu %0,%1,%2\";
xoperands[0] = operands[0];
xoperands[1] = operands[2];
output_asm_insn (output_load_const_int (SImode, xoperands),
xoperands);
return \"addu %0,%1,%0\";
}"
[(set_attr "type" "arith,marith")
(set_attr "length" "1,3")]) ; may be 2 or 3.
;; patterns for mixed mode floating point.
;; Do not define patterns that utilize mixed mode arithmetic that result
;; in narrowing the precision, because it loses accuracy, since the standard
;; requires double rounding, whereas the 88000 instruction only rounds once.
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(plus:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fadd.dss %0,%1,%2"
[(set_attr "type" "spadd")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(plus:DF (match_operand:DF 1 "register_operand" "r")
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fadd.dds %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(plus:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(match_operand:DF 2 "register_operand" "r")))]
""
"fadd.dsd %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn "adddf3"
[(set (match_operand:DF 0 "register_operand" "=r")
(plus:DF (match_operand:DF 1 "register_operand" "%r")
(match_operand:DF 2 "register_operand" "r")))]
""
"fadd.ddd %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn "addsf3"
[(set (match_operand:SF 0 "register_operand" "=r")
(plus:SF (match_operand:SF 1 "register_operand" "%r")
(match_operand:SF 2 "register_operand" "r")))]
""
"fadd.sss %0,%1,%2"
[(set_attr "type" "spadd")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(plus:DI (match_operand:DI 1 "register_operand" "r")
(zero_extend:DI
(match_operand:SI 2 "register_operand" "r"))))]
""
"addu.co %d0,%d1,%2\;addu.ci %0,%1,%#r0"
[(set_attr "type" "marith")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(plus:DI (zero_extend:DI
(match_operand:SI 1 "register_operand" "r"))
(match_operand:DI 2 "register_operand" "r")))]
""
"addu.co %d0,%1,%d2\;addu.ci %0,%#r0,%2"
[(set_attr "type" "marith")])
(define_insn "adddi3"
[(set (match_operand:DI 0 "register_operand" "=r")
(plus:DI (match_operand:DI 1 "register_operand" "%r")
(match_operand:DI 2 "register_operand" "r")))]
""
"addu.co %d0,%d1,%d2\;addu.ci %0,%1,%2"
[(set_attr "type" "marith")])
;;- subtract instructions
(define_insn "subsi3"
[(set (match_operand:SI 0 "register_operand" "=r")
(minus:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "arith32_operand" "rI")))]
""
"subu %0,%1,%2")
;; patterns for mixed mode floating point
;; Do not define patterns that utilize mixed mode arithmetic that result
;; in narrowing the precision, because it loses accuracy, since the standard
;; requires double rounding, whereas the 88000 instruction only rounds once.
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(minus:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fsub.dss %0,%1,%2"
[(set_attr "type" "spadd")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(minus:DF (match_operand:DF 1 "register_operand" "r")
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fsub.dds %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(minus:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(match_operand:DF 2 "register_operand" "r")))]
""
"fsub.dsd %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn "subdf3"
[(set (match_operand:DF 0 "register_operand" "=r")
(minus:DF (match_operand:DF 1 "register_operand" "r")
(match_operand:DF 2 "register_operand" "r")))]
""
"fsub.ddd %0,%1,%2"
[(set_attr "type" "dpadd")])
(define_insn "subsf3"
[(set (match_operand:SF 0 "register_operand" "=r")
(minus:SF (match_operand:SF 1 "register_operand" "r")
(match_operand:SF 2 "register_operand" "r")))]
""
"fsub.sss %0,%1,%2"
[(set_attr "type" "spadd")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(minus:DI (match_operand:DI 1 "register_operand" "r")
(zero_extend:DI
(match_operand:SI 2 "register_operand" "r"))))]
""
"subu.co %d0,%d1,%2\;subu.ci %0,%1,%#r0"
[(set_attr "type" "marith")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(minus:DI (zero_extend:DI
(match_operand:SI 1 "register_operand" "r"))
(match_operand:DI 2 "register_operand" "r")))]
""
"subu.co %d0,%1,%d2\;subu.ci %0,%#r0,%2"
[(set_attr "type" "marith")])
(define_insn "subdi3"
[(set (match_operand:DI 0 "register_operand" "=r")
(minus:DI (match_operand:DI 1 "register_operand" "r")
(match_operand:DI 2 "register_operand" "r")))]
""
"subu.co %d0,%d1,%d2\;subu.ci %0,%1,%2"
[(set_attr "type" "marith")])
;;- multiply instructions
;;
;; There is an unfounded silicon eratta for E.1 requiring that an
;; immediate constant value in div/divu/mul instructions be less than
;; 0x800. This is no longer provided for.
(define_insn "mulsi3"
[(set (match_operand:SI 0 "register_operand" "=r")
(mult:SI (match_operand:SI 1 "arith32_operand" "%r")
(match_operand:SI 2 "arith32_operand" "rI")))]
""
"mul %0,%1,%2"
[(set_attr "type" "imul")])
;; patterns for mixed mode floating point
;; Do not define patterns that utilize mixed mode arithmetic that result
;; in narrowing the precision, because it loses accuracy, since the standard
;; requires double rounding, whereas the 88000 instruction only rounds once.
(define_expand "muldf3"
[(set (match_operand:DF 0 "register_operand" "=r")
(mult:DF (match_operand:DF 1 "register_operand" "%r")
(match_operand:DF 2 "general_operand" "r")))]
""
"
{
rtx temp;
/* If constant can be represented in SFmode without loss of accuracy
(for now we just do this for powers of two), use fmul.dsd. */
if (real_power_of_2_operand (operands[2])
&& (temp = simplify_unary_operation (FLOAT_TRUNCATE, SFmode,
operands[2], DFmode)) != 0)
{
operands[2] = operands[1];
operands[1] = gen_rtx (FLOAT_EXTEND, DFmode, force_reg (SFmode, temp));
}
else if (! register_operand (operands[2], DFmode))
operands[2] = force_reg (DFmode, operands[2]);
}")
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(mult:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fmul.dss %0,%1,%2"
[(set_attr "type" "spmul")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(mult:DF (match_operand:DF 1 "register_operand" "r")
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fmul.dds %0,%1,%2"
[(set_attr "type" "spmul")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(mult:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(match_operand:DF 2 "register_operand" "r")))]
""
"fmul.dsd %0,%1,%2"
[(set_attr "type" "spmul")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(mult:DF (match_operand:DF 1 "register_operand" "%r")
(match_operand:DF 2 "register_operand" "r")))]
""
"fmul.ddd %0,%1,%2"
[(set_attr "type" "dpmul")])
(define_insn "mulsf3"
[(set (match_operand:SF 0 "register_operand" "=r")
(mult:SF (match_operand:SF 1 "register_operand" "%r")
(match_operand:SF 2 "register_operand" "r")))]
""
"fmul.sss %0,%1,%2"
[(set_attr "type" "spmul")])
;;- divide instructions
;;
;; The 88k div and divu instructions don't reliably trap on
;; divide-by-zero. A trap to vector 503 asserts divide-by-zero. The
;; general scheme for doing divide is to do a 4-way split based on the
;; sign of the two operand and do the appropriate negates.
;;
;; The conditional trap instruction is not used as this serializes the
;; processor. Instead a conditional branch and an unconditional trap
;; are used, but after the divu. Since the divu takes up to 38 cycles,
;; the conditional branch is essentially free.
;;
;; Two target options control how divide is done. One options selects
;; whether to do the branch and negate scheme instead of using the div
;; instruction; the other option selects whether to explicitly check
;; for divide-by-zero or take your chances. If the div instruction is
;; used, the O/S must complete the operation if the operands are
;; negative. The O/S will signal an overflow condition if the most
;; negative number (-214783648) is divided by negative 1.
;;
;; There is an unfounded silicon eratta for E.1 requiring that an
;; immediate constant value in div/divu/mul instructions be less than
;; 0x800. This is no longer provided for.
;; Division by 0 trap
(define_insn "trap_divide_by_zero"
[(set (pc) (const_int 503))]
""
"tb0 0,%#r0,503"
[(set_attr "type" "wierd")])
;; Conditional division by 0 trap.
(define_expand "tcnd_divide_by_zero"
[(set (pc)
(if_then_else (eq (match_operand:SI 0 "register_operand" "")
(const_int 0))
(const_int 503)
(match_operand 1 "" "")))]
""
"
{
emit_insn (gen_cmpsi (operands[0], const0_rtx));
emit_jump_insn (gen_bne (operands[1]));
emit_insn (gen_trap_divide_by_zero ());
emit_barrier ();
DONE;
}")
(define_expand "divsi3"
[(set (match_operand:SI 0 "register_operand" "")
(div:SI (match_operand:SI 1 "arith32_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
rtx op1 = operands[1];
rtx op2 = operands[2];
rtx join_label;
/* @@ This needs to be reworked. Torbjorn Granlund has suggested making
it a runtime (perhaps quite special). */
if (GET_CODE (op1) == CONST_INT)
op1 = force_reg (SImode, op1);
else if (GET_CODE (op2) == CONST_INT
&& ! SMALL_INT (operands[2]))
op2 = force_reg (SImode, op2);
if (op2 == const0_rtx)
{
emit_insn (gen_trap_divide_by_zero ());
emit_barrier ();
emit_insn (gen_dummy (operands[0]));
DONE;
}
if (TARGET_USE_DIV)
{
emit_move_insn (operands[0], gen_rtx (DIV, SImode, op1, op2));
if (TARGET_CHECK_ZERO_DIV && GET_CODE (op2) != CONST_INT)
{
rtx label = gen_label_rtx ();
emit_insn (gen_tcnd_divide_by_zero (op2, label));
emit_label (label);
emit_insn (gen_dummy (op2));
}
DONE;
}
join_label = gen_label_rtx ();
if (GET_CODE (op1) == CONST_INT)
{
int neg = FALSE;
rtx neg_op2 = gen_reg_rtx (SImode);
rtx label1 = gen_label_rtx ();
if (INTVAL (op1) < 0)
{
neg = TRUE;
op1 = gen_rtx (CONST_INT, VOIDmode, -INTVAL (op1));
}
op1 = force_reg (SImode, op1);
emit_insn (gen_negsi2 (neg_op2, op2));
emit_insn (gen_cmpsi (op2, const0_rtx));
emit_jump_insn (gen_bgt (label1));
/* constant / 0-or-negative */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, op1, neg_op2));
if (!neg)
emit_insn (gen_negsi2 (operands[0], operands[0]));
if (TARGET_CHECK_ZERO_DIV)
emit_insn (gen_tcnd_divide_by_zero (op2, join_label));
else
{
emit_jump_insn (gen_jump (join_label));
emit_barrier ();
}
emit_label (label1); /* constant / positive */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, op1, op2));
if (neg)
emit_insn (gen_negsi2 (operands[0], operands[0]));
}
else if (GET_CODE (op2) == CONST_INT)
{
int neg = FALSE;
rtx neg_op1 = gen_reg_rtx (SImode);
rtx label1 = gen_label_rtx ();
if (INTVAL (op2) < 0)
{
neg = TRUE;
op2 = gen_rtx (CONST_INT, VOIDmode, -INTVAL (op2));
}
else if (! SMALL_INT (operands[2]))
op2 = force_reg (SImode, op2);
emit_insn (gen_negsi2 (neg_op1, op1));
emit_insn (gen_cmpsi (op1, const0_rtx));
emit_jump_insn (gen_bge (label1));
/* 0-or-negative / constant */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, neg_op1, op2));
if (!neg)
emit_insn (gen_negsi2 (operands[0], operands[0]));
emit_jump_insn (gen_jump (join_label));
emit_barrier ();
emit_label (label1); /* positive / constant */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, op1, op2));
if (neg)
emit_insn (gen_negsi2 (operands[0], operands[0]));
}
else
{
rtx neg_op1 = gen_reg_rtx (SImode);
rtx neg_op2 = gen_reg_rtx (SImode);
rtx label1 = gen_label_rtx ();
rtx label2 = gen_label_rtx ();
rtx label3 = gen_label_rtx ();
rtx label4;
emit_insn (gen_negsi2 (neg_op2, op2));
emit_insn (gen_cmpsi (op2, const0_rtx));
emit_jump_insn (gen_bgt (label1));
emit_insn (gen_negsi2 (neg_op1, op1));
emit_insn (gen_cmpsi (op1, const0_rtx));
emit_jump_insn (gen_bge (label2));
/* negative / negative-or-0 */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, neg_op1, neg_op2));
if (TARGET_CHECK_ZERO_DIV)
{
label4 = gen_label_rtx ();
emit_insn (gen_cmpsi (op2, const0_rtx));
emit_jump_insn (gen_bne (join_label));
emit_label (label4);
emit_insn (gen_trap_divide_by_zero ());
emit_barrier ();
}
else
{
emit_jump_insn (gen_jump (join_label));
emit_barrier ();
}
emit_label (label2); /* pos.-or-0 / neg.-or-0 */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, op1, neg_op2));
if (TARGET_CHECK_ZERO_DIV)
{
emit_insn (gen_cmpsi (op2, const0_rtx));
emit_jump_insn (gen_beq (label4));
}
emit_insn (gen_negsi2 (operands[0], operands[0]));
emit_jump_insn (gen_jump (join_label));
emit_barrier ();
emit_label (label1);
emit_insn (gen_negsi2 (neg_op1, op1));
emit_insn (gen_cmpsi (op1, const0_rtx));
emit_jump_insn (gen_bge (label3));
/* negative / positive */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, neg_op1, op2));
emit_insn (gen_negsi2 (operands[0], operands[0]));
emit_jump_insn (gen_jump (join_label));
emit_barrier ();
emit_label (label3); /* positive-or-0 / positive */
emit_move_insn (operands[0], gen_rtx (UDIV, SImode, op1, op2));
}
emit_label (join_label);
emit_insn (gen_dummy (operands[0]));
DONE;
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(div:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "arith_operand" "rI")))]
""
"div %0,%1,%2"
[(set_attr "type" "idiv")])
(define_expand "udivsi3"
[(set (match_operand:SI 0 "register_operand" "")
(udiv:SI (match_operand:SI 1 "register_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
rtx op2 = operands[2];
if (op2 == const0_rtx)
{
emit_insn (gen_trap_divide_by_zero ());
emit_barrier ();
emit_insn (gen_dummy (operands[0]));
DONE;
}
else if (GET_CODE (op2) != CONST_INT && TARGET_CHECK_ZERO_DIV)
{
rtx label = gen_label_rtx ();
emit_insn (gen_rtx (SET, VOIDmode, operands[0],
gen_rtx (UDIV, SImode, operands[1], op2)));
emit_insn (gen_tcnd_divide_by_zero (op2, label));
emit_label (label);
emit_insn (gen_dummy (operands[0]));
DONE;
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(udiv:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "arith32_operand" "rI")))]
"operands[2] != const0_rtx"
"divu %0,%1,%2"
[(set_attr "type" "idiv")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(udiv:SI (match_operand:SI 1 "register_operand" "r")
(const_int 0)))]
""
"tb0 0,%#r0,503"
[(set_attr "type" "wierd")])
;; patterns for mixed mode floating point.
;; Do not define patterns that utilize mixed mode arithmetic that result
;; in narrowing the precision, because it loses accuracy, since the standard
;; requires double rounding, whereas the 88000 instruction only rounds once.
(define_expand "divdf3"
[(set (match_operand:DF 0 "register_operand" "=r")
(div:DF (match_operand:DF 1 "register_operand" "r")
(match_operand:DF 2 "general_operand" "r")))]
""
"
{
if (real_power_of_2_operand (operands[2]))
{
union real_extract u;
bcopy (&CONST_DOUBLE_LOW (operands[2]), &u, sizeof u);
emit_insn (gen_muldf3 (operands[0], operands[1],
CONST_DOUBLE_FROM_REAL_VALUE (1.0/u.d, DFmode)));
DONE;
}
else if (! register_operand (operands[2], DFmode))
operands[2] = force_reg (DFmode, operands[2]);
}")
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(div:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fdiv.dss %0,%1,%2"
[(set_attr "type" "dpdiv")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(div:DF (match_operand:DF 1 "register_operand" "r")
(float_extend:DF (match_operand:SF 2 "register_operand" "r"))))]
""
"fdiv.dds %0,%1,%2"
[(set_attr "type" "dpdiv")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(div:DF (float_extend:DF (match_operand:SF 1 "register_operand" "r"))
(match_operand:DF 2 "register_operand" "r")))]
""
"fdiv.dsd %0,%1,%2"
[(set_attr "type" "dpdiv")])
(define_insn "divsf3"
[(set (match_operand:SF 0 "register_operand" "=r")
(div:SF (match_operand:SF 1 "register_operand" "r")
(match_operand:SF 2 "register_operand" "r")))]
""
"fdiv.sss %0,%1,%2"
[(set_attr "type" "spdiv")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "=r")
(div:DF (match_operand:DF 1 "register_operand" "r")
(match_operand:DF 2 "register_operand" "r")))]
""
"fdiv.ddd %0,%1,%2"
[(set_attr "type" "dpdiv")])
;; - remainder instructions, don't define, since the hardware doesn't have any
;; direct support, and GNU can synthesis them out of div/mul just fine.
;;- load effective address, must come after add, so that we favor using
;; addu reg,reg,reg instead of: lda reg,reg,reg (addu doesn't require
;; the data unit), and also future 88k chips might not support unscaled
;; lda instructions.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(match_operand:HI 1 "address_operand" "p"))]
""
"lda.h %0,%a1"
[(set_attr "type" "loada")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(match_operand:SI 1 "address_operand" "p"))]
""
"lda %0,%a1"
[(set_attr "type" "loada")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(match_operand:DI 1 "address_operand" "p"))]
""
"lda.d %0,%a1"
[(set_attr "type" "loada")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(match_operand:SF 1 "address_operand" "p"))]
""
"lda %0,%a1"
[(set_attr "type" "loada")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(match_operand:DF 1 "address_operand" "p"))]
""
"lda.d %0,%a1"
[(set_attr "type" "loada")])
;;- and instructions (with complement also)
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(and:SI (not:SI (match_operand:SI 1 "register_operand" "r"))
(match_operand:SI 2 "register_operand" "r")))]
""
"and.c %0,%2,%1")
;; If the operation is being performed on a 32-bit constant such that
;; it cannot be done in one insn, do it in two. We may lose a bit on
;; CSE in pathological cases, but it seems better doing it this way.
(define_expand "andsi3"
[(set (match_operand:SI 0 "register_operand" "")
(and:SI (match_operand:SI 1 "arith32_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[2]) == CONST_INT)
{
int value = INTVAL (operands[2]);
if (! (SMALL_INTVAL (value)
|| (value & 0xffff0000) == 0xffff0000
|| (value & 0xffff) == 0xffff
|| (value & 0xffff) == 0
|| integer_ok_for_set (~value)))
{
emit_insn (gen_andsi3 (operands[0], operands[1],
gen_rtx (CONST_INT, VOIDmode,
value | 0xffff)));
operands[1] = operands[0];
operands[2] = gen_rtx (CONST_INT, VOIDmode, value | 0xffff0000);
}
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r")
(and:SI (match_operand:SI 1 "arith32_operand" "%r,r")
(match_operand:SI 2 "arith32_operand" "rIJL,rn")))]
""
"* return output_and (operands);"
[(set_attr "type" "arith,marith")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(and:DI (not:DI (match_operand:DI 1 "register_operand" "r"))
(match_operand:DI 2 "register_operand" "r")))]
""
"and.c %d0,%d2,%d1\;and.c %0,%2,%1"
[(set_attr "type" "marith")])
(define_insn "anddi3"
[(set (match_operand:DI 0 "register_operand" "=r")
(and:DI (match_operand:DI 1 "arith64_operand" "%r")
(match_operand:DI 2 "arith64_operand" "rn")))]
""
"*
{
rtx xoperands[10];
xoperands[0] = operand_subword (operands[0], 1, 0, DImode);
xoperands[1] = operand_subword (operands[1], 1, 0, DImode);
xoperands[2] = operand_subword (operands[2], 1, 0, DImode);
output_asm_insn (output_and (xoperands), xoperands);
operands[0] = operand_subword (operands[0], 0, 0, DImode);
operands[1] = operand_subword (operands[1], 0, 0, DImode);
operands[2] = operand_subword (operands[2], 0, 0, DImode);
return output_and (operands);
}"
[(set_attr "type" "marith")
(set_attr "length" "4")]) ; length is 2, 3, or 4.
;;- Bit set (inclusive or) instructions (with complement also)
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ior:SI (not:SI (match_operand:SI 1 "register_operand" "r"))
(match_operand:SI 2 "register_operand" "r")))]
""
"or.c %0,%2,%1")
(define_expand "iorsi3"
[(set (match_operand:SI 0 "register_operand" "")
(ior:SI (match_operand:SI 1 "arith32_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[2]) == CONST_INT)
{
int value = INTVAL (operands[2]);
if (! (SMALL_INTVAL (value)
|| (value & 0xffff) == 0
|| integer_ok_for_set (value)))
{
emit_insn (gen_iorsi3 (operands[0], operands[1],
gen_rtx (CONST_INT, VOIDmode,
value & 0xffff0000)));
operands[1] = operands[0];
operands[2] = gen_rtx (CONST_INT, VOIDmode, value & 0xffff);
}
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r,r,r")
(ior:SI (match_operand:SI 1 "arith32_operand" "%r,r,r,r")
(match_operand:SI 2 "arith32_operand" "rI,L,M,n")))]
""
"@
or %0,%1,%2
or.u %0,%1,%X2
set %0,%1,%s2
or.u %0,%1,%X2\;or %0,%0,%x2"
[(set_attr "type" "arith,arith,arith,marith")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(ior:DI (not:DI (match_operand:DI 1 "register_operand" "r"))
(match_operand:DI 2 "register_operand" "r")))]
""
"or.c %d0,%d2,%d1\;or.c %0,%2,%1"
[(set_attr "type" "marith")])
(define_insn "iordi3"
[(set (match_operand:DI 0 "register_operand" "=r")
(ior:DI (match_operand:DI 1 "arith64_operand" "%r")
(match_operand:DI 2 "arith64_operand" "rn")))]
""
"*
{
rtx xoperands[10];
xoperands[0] = operand_subword (operands[0], 1, 0, DImode);
xoperands[1] = operand_subword (operands[1], 1, 0, DImode);
xoperands[2] = operand_subword (operands[2], 1, 0, DImode);
output_asm_insn (output_ior (xoperands), xoperands);
operands[0] = operand_subword (operands[0], 0, 0, DImode);
operands[1] = operand_subword (operands[1], 0, 0, DImode);
operands[2] = operand_subword (operands[2], 0, 0, DImode);
return output_ior (operands);
}"
[(set_attr "type" "marith")
(set_attr "length" "4")]) ; length is 2, 3, or 4.
;;- xor instructions (with complement also)
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(not:SI (xor:SI (match_operand:SI 1 "register_operand" "%r")
(match_operand:SI 2 "register_operand" "r"))))]
""
"xor.c %0,%1,%2")
(define_expand "xorsi3"
[(set (match_operand:SI 0 "register_operand" "")
(xor:SI (match_operand:SI 1 "arith32_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[2]) == CONST_INT)
{
int value = INTVAL (operands[2]);
if (! (SMALL_INTVAL (value)
|| (value & 0xffff) == 0))
{
emit_insn (gen_xorsi3 (operands[0], operands[1],
gen_rtx (CONST_INT, VOIDmode,
value & 0xffff0000)));
operands[1] = operands[0];
operands[2] = gen_rtx (CONST_INT, VOIDmode, value & 0xffff);
}
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r,r")
(xor:SI (match_operand:SI 1 "arith32_operand" "%r,r,r")
(match_operand:SI 2 "arith32_operand" "rI,L,n")))]
""
"@
xor %0,%1,%2
xor.u %0,%1,%X2
xor.u %0,%1,%X2\;xor %0,%0,%x2"
[(set_attr "type" "arith,arith,marith")])
(define_insn ""
[(set (match_operand:DI 0 "register_operand" "=r")
(not:DI (xor:DI (match_operand:DI 1 "register_operand" "r")
(match_operand:DI 2 "register_operand" "r"))))]
""
"xor.c %d0,%d1,%d2\;xor.c %0,%1,%2"
[(set_attr "type" "marith")])
(define_insn "xordi3"
[(set (match_operand:DI 0 "register_operand" "=r")
(xor:DI (match_operand:DI 1 "arith64_operand" "%r")
(match_operand:DI 2 "arith64_operand" "rn")))]
""
"*
{
rtx xoperands[10];
xoperands[0] = operand_subword (operands[0], 1, 0, DImode);
xoperands[1] = operand_subword (operands[1], 1, 0, DImode);
xoperands[2] = operand_subword (operands[2], 1, 0, DImode);
output_asm_insn (output_xor (xoperands), xoperands);
operands[0] = operand_subword (operands[0], 0, 0, DImode);
operands[1] = operand_subword (operands[1], 0, 0, DImode);
operands[2] = operand_subword (operands[2], 0, 0, DImode);
return output_xor (operands);
}"
[(set_attr "type" "marith")
(set_attr "length" "4")]) ; length is 2, 3, or 4.
;;- ones complement instructions
(define_insn "one_cmplsi2"
[(set (match_operand:SI 0 "register_operand" "=r")
(not:SI (match_operand:SI 1 "register_operand" "r")))]
""
"xor.c %0,%1,%#r0")
(define_insn "one_cmpldi2"
[(set (match_operand:DI 0 "register_operand" "=r")
(not:DI (match_operand:DI 1 "register_operand" "r")))]
""
"xor.c %d0,%d1,%#r0\;xor.c %0,%1,%#r0"
[(set_attr "type" "marith")])
;; Optimized special cases of shifting.
;; Must precede the general case.
;; @@ What about HImode shifted by 8?
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ashiftrt:SI (match_operand:SI 1 "memory_operand" "m")
(const_int 24)))]
"! SCALED_ADDRESS_P (XEXP (operands[1], 0))"
"ld.b %0,%1"
[(set_attr "type" "load")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(lshiftrt:SI (match_operand:SI 1 "memory_operand" "m")
(const_int 24)))]
"! SCALED_ADDRESS_P (XEXP (operands[1], 0))"
"ld.bu %0,%1"
[(set_attr "type" "load")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(ashiftrt:SI (match_operand:SI 1 "memory_operand" "m")
(const_int 16)))]
"! SCALED_ADDRESS_P (XEXP (operands[1], 0))"
"ld.h %0,%1"
[(set_attr "type" "load")])
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(lshiftrt:SI (match_operand:SI 1 "memory_operand" "m")
(const_int 16)))]
"! SCALED_ADDRESS_P (XEXP (operands[1], 0))"
"ld.hu %0,%1"
[(set_attr "type" "load")])
;;- arithmetic shift instructions.
;; @@ Do the optimized patterns with -1 get used? Perhaps operand 1 should
;; be arith32_operand?
;; Use tbnd to support TARGET_TRAP_LARGE_SHIFT.
(define_insn "tbnd"
[(set (pc)
(if_then_else (gtu (match_operand:SI 0 "register_operand" "r")
(match_operand:SI 0 "arith_operand" "rI"))
(const_int 7)
(pc)))]
""
"tbnd %r0,%1"
[(set_attr "type" "wierd")])
;; Just in case the optimizer decides to fold away the test.
(define_insn ""
[(set (pc) (const_int 7))]
""
"tbnd %#r31,0"
[(set_attr "type" "wierd")])
(define_expand "ashlsi3"
[(set (match_operand:SI 0 "register_operand" "")
(ashift:SI (match_operand:SI 1 "register_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[2]) == CONST_INT)
{
if ((unsigned) INTVAL (operands[2]) > 31)
{
if (TARGET_TRAP_LARGE_SHIFT)
emit_insn (gen_tbnd (force_reg (SImode, operands[2]),
gen_rtx (CONST_INT, VOIDmode, 31)));
else
emit_move_insn (operands[0], const0_rtx);
DONE;
}
}
else if (TARGET_TRAP_LARGE_SHIFT)
emit_insn (gen_tbnd (operands[2], gen_rtx (CONST_INT, VOIDmode, 31)));
else if (TARGET_HANDLE_LARGE_SHIFT)
{
rtx reg = gen_reg_rtx (SImode);
emit_insn (gen_cmpsi (operands[2], gen_rtx (CONST_INT, VOIDmode, 31)));
emit_insn (gen_extendsleu (reg));
emit_insn (gen_andsi3 (reg, operands[1], reg));
operands[1] = reg;
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r")
(ashift:SI (match_operand:SI 1 "register_operand" "r,r")
(match_operand:SI 2 "arith5_operand" "r,n")))]
""
"@
mak %0,%1,%2
mak %0,%1,0<%2>")
(define_expand "ashrsi3"
[(set (match_operand:SI 0 "register_operand" "")
(ashiftrt:SI (match_operand:SI 1 "register_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[2]) == CONST_INT)
{
if ((unsigned) INTVAL (operands[2]) > 31)
{
if (TARGET_TRAP_LARGE_SHIFT)
{
emit_insn (gen_tbnd (force_reg (SImode, operands[2]),
gen_rtx (CONST_INT, VOIDmode, 31)));
DONE;
}
else
operands[2] = gen_rtx (CONST_INT, VOIDmode, 31);
}
}
else if (TARGET_TRAP_LARGE_SHIFT)
emit_insn (gen_tbnd (operands[2], gen_rtx (CONST_INT, VOIDmode, 31)));
else if (TARGET_HANDLE_LARGE_SHIFT)
{
rtx reg = gen_reg_rtx (SImode);
emit_insn (gen_cmpsi (operands[2], gen_rtx (CONST_INT, VOIDmode, 31)));
emit_insn (gen_extendsgtu (reg));
emit_insn (gen_iorsi3 (reg, operands[2], reg));
operands[2] = reg;
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r")
(ashiftrt:SI (match_operand:SI 1 "register_operand" "r,r")
(match_operand:SI 2 "arith5_operand" "r,n")))]
""
"@
ext %0,%1,%2
ext %0,%1,0<%2>")
;;- logical shift instructions. Logical shift left becomes arithmetic
;; shift left. LSHIFT is not normally produced, but is supported.
(define_expand "lshlsi3"
[(set (match_operand:SI 0 "register_operand" "")
(lshift:SI (match_operand:SI 1 "register_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
emit_insn (gen_ashlsi3 (operands[0], operands[1], operands[2]));
DONE;
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r")
(lshift:SI (match_operand:SI 1 "register_operand" "r,r")
(match_operand:SI 2 "arith5_operand" "r,n")))]
""
"@
mak %0,%1,%2
mak %0,%1,0<%2>")
(define_expand "lshrsi3"
[(set (match_operand:SI 0 "register_operand" "")
(lshiftrt:SI (match_operand:SI 1 "register_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[2]) == CONST_INT)
{
if ((unsigned) INTVAL (operands[2]) > 31)
{
if (TARGET_TRAP_LARGE_SHIFT)
emit_insn (gen_tbnd (force_reg (SImode, operands[2]),
gen_rtx (CONST_INT, VOIDmode, 31)));
else
emit_move_insn (operands[0], const0_rtx);
DONE;
}
}
else if (TARGET_TRAP_LARGE_SHIFT)
emit_insn (gen_tbnd (operands[2], gen_rtx (CONST_INT, VOIDmode, 31)));
else if (TARGET_HANDLE_LARGE_SHIFT)
{
rtx reg = gen_reg_rtx (SImode);
emit_insn (gen_cmpsi (operands[2], gen_rtx (CONST_INT, VOIDmode, 31)));
emit_insn (gen_extendsleu (reg));
emit_insn (gen_andsi3 (reg, operands[1], reg));
operands[1] = reg;
}
}")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r,r")
(lshiftrt:SI (match_operand:SI 1 "register_operand" "r,r")
(match_operand:SI 2 "arith5_operand" "r,n")))]
""
"@
extu %0,%1,%2
extu %0,%1,0<%2>")
;;- rotate instructions
(define_expand "rotlsi3"
[(set (match_operand:SI 0 "register_operand" "")
(rotatert:SI (match_operand:SI 1 "register_operand" "")
(match_operand:SI 2 "arith32_operand" "")))]
""
"
{
if (GET_CODE (operands[2]) == CONST_INT
&& (unsigned) INTVAL (operands[2]) >= 32)
operands[2] = gen_rtx (CONST_INT, VOIDmode,
(32 - INTVAL (operands[2])) % 32);
else
{
rtx op = gen_reg_rtx (SImode);
emit_insn (gen_negsi2 (op, operands[2]));
operands[2] = op;
}
}")
(define_insn "rotrsi3"
[(set (match_operand:SI 0 "register_operand" "=r")
(rotatert:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "arith_operand" "rI")))]
""
"rot %0,%1,%2")
;; Bit field instructions.
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(sign_extract:SI (match_operand:SI 1 "register_operand" "r")
(const_int 32)
(const_int 0)))]
""
"or %0,%#r0,%1")
(define_insn "extv"
[(set (match_operand:SI 0 "register_operand" "=r")
(sign_extract:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "int5_operand" "")
(match_operand:SI 3 "int5_operand" "")))]
""
"ext %0,%1,%2<(32-%2-%3)>")
(define_insn ""
[(set (match_operand:SI 0 "register_operand" "=r")
(zero_extract:SI (match_operand:SI 1 "register_operand" "r")
(const_int 32)
(const_int 0)))]
""
"or %0,%#r0,%1")
(define_insn "extzv"
[(set (match_operand:SI 0 "register_operand" "=r")
(zero_extract:SI (match_operand:SI 1 "register_operand" "r")
(match_operand:SI 2 "int5_operand" "")
(match_operand:SI 3 "int5_operand" "")))]
""
"extu %0,%1,%2<(32-%2-%3)>")
(define_insn ""
[(set (zero_extract:SI (match_operand:SI 0 "register_operand" "r")
(match_operand:SI 1 "int5_operand" "")
(match_operand:SI 2 "int5_operand" ""))
(const_int 0))]
""
"clr %0,%0,%1<(32-%1-%2)>")
(define_insn ""
[(set (zero_extract:SI (match_operand:SI 0 "register_operand" "r")
(match_operand:SI 1 "int5_operand" "")
(match_operand:SI 2 "int5_operand" ""))
(const_int -1))]
""
"set %0,%0,%1<(32-%1-%2)>")
(define_insn ""
[(set (zero_extract:SI (match_operand:SI 0 "register_operand" "=r")
(match_operand:SI 1 "int5_operand" "")
(match_operand:SI 2 "int5_operand" ""))
(match_operand:SI 3 "int32_operand" "n"))]
""
"*
{
int value = INTVAL (operands[3]);
if (INTVAL (operands[1]) < 32)
value &= (1 << INTVAL (operands[1])) - 1;
operands[2] = gen_rtx (CONST_INT, VOIDmode,
32 - (INTVAL(operands[1]) + INTVAL(operands[2])));
value <<= INTVAL (operands[2]);
operands[3] = gen_rtx (CONST_INT, VOIDmode, value);
if (SMALL_INTVAL (value))
return \"clr %0,%0,%1<%2>\;or %0,%0,%3\";
else if ((value & 0x0000ffff) == 0)
return \"clr %0,%0,%1<%2>\;or.u %0,%0,%X3\";
else
return \"clr %0,%0,%1<%2>\;or.u %0,%0,%X3\;or %0,%0,%x3\";
}"
[(set_attr "type" "marith")
(set_attr "length" "3")]) ; may be 2 or 3.
;; negate insns
(define_insn "negsi2"
[(set (match_operand:SI 0 "register_operand" "=r")
(neg:SI (match_operand:SI 1 "arith_operand" "rI")))]
""
"subu %0,%#r0,%1")
(define_insn ""
[(set (match_operand:SF 0 "register_operand" "=r")
(float_truncate:SF (neg:DF (match_operand:DF 1 "register_operand" "r"))))]
""
"fsub.ssd %0,%#r0,%1"
[(set_attr "type" "dpadd")])
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "+r")
(neg:DF (match_dup 0)))]
""
"xor.u %0,%0,0x8000")
(define_insn "negdf2"
[(set (match_operand:DF 0 "register_operand" "=&r")
(neg:DF (match_operand:DF 1 "register_operand" "r")))]
""
"xor.u %0,%1,0x8000\;or %d0,%#r0,%d1"
[(set_attr "type" "marith")])
(define_insn "negsf2"
[(set (match_operand:SF 0 "register_operand" "=r")
(neg:SF (match_operand:SF 1 "register_operand" "r")))]
""
"xor.u %0,%1,0x8000")
;; absolute value insns
(define_expand "abssi2"
[(set (match_operand:SI 0 "register_operand" "")
(abs:SI (match_operand:SI 1 "register_operand" "")))]
""
"
{
rtx reg_mask = gen_reg_rtx (SImode);
rtx op1 = force_reg (SImode, operands[1]);
emit_insn (gen_ashrsi3 (reg_mask, op1,
gen_rtx (CONST_INT, VOIDmode, 31)));
emit_insn (gen_xorsi3 (operands[0], op1, reg_mask));
emit_insn (gen_subsi3 (operands[0], operands[0], reg_mask));
DONE;
}")
(define_insn ""
[(set (match_operand:DF 0 "register_operand" "+r")
(abs:DF (match_dup 0)))]
""
"and.u %0,%0,0x7fff")
(define_insn "absdf2"
[(set (match_operand:DF 0 "register_operand" "=&r")
(abs:DF (match_operand:DF 1 "register_operand" "r")))]
""
"and.u %0,%1,0x7fff\;or %d0,%#r0,%d1"
[(set_attr "type" "marith")])
(define_insn "abssf2"
[(set (match_operand:SF 0 "register_operand" "=r")
(abs:SF (match_operand:SF 1 "register_operand" "r")))]
""
"and.u %0,%1,0x7fff")
;; Subroutines of "casesi".
;; Operand 0 is index
;; operand 1 is the minimum bound
;; operand 2 is the maximum bound - minimum bound + 1
;; operand 3 is CODE_LABEL for the table;
;; operand 4 is the CODE_LABEL to go to if index out of range.
;; (disabled on NeXT)
(define_expand "casesi"
;; We don't use these for generating the RTL, but we must describe
;; the operands here.
[(match_operand:SI 0 "general_operand" "")
(match_operand:SI 1 "immediate_operand" "")
(match_operand:SI 2 "immediate_operand" "")
(match_operand 3 "" "")
(match_operand 4 "" "")]
"0"
"
{
register rtx index_diff = gen_reg_rtx (SImode);
register rtx low = gen_rtx (CONST_INT, VOIDmode, -INTVAL (operands[1]));
/* Compute the index difference and handle the default case. */
emit_insn (gen_addsi3 (index_diff,
force_reg (SImode, operands[0]),
ADD_INT (low) ? low : force_reg (SImode, low)));
emit_insn (gen_cmpsi (index_diff, operands[2]));
emit_jump_insn (gen_bgtu (operands[4]));
/* Call the jump that will branch to the appropriate case. */
emit_jump_insn (gen_casesi_enter (gen_rtx (LABEL_REF, VOIDmode, operands[3]),
index_diff,
operands[3]));
emit_barrier ();
DONE;
}")
;; The bsr.n instruction is directed to the END of the table. See
;; ASM_OUTPUT_CASE_END.
(define_insn "casesi_enter"
[(set (pc) (match_operand 0 "" ""))
(use (match_operand:SI 1 "register_operand" "r"))
;; The USE here is so that at least one jump-insn will refer to the label,
;; to keep it alive in jump_optimize.
(use (label_ref (match_operand 2 "" "")))
(clobber (reg:SI 1))]
""
"bsr.n %0e\;lda %#r1,%#r1[%1]"
[(set_attr "type" "wierd")
(set_attr "length" "3")]) ; Including the "jmp r1".
;;- jump to subroutine
(define_expand "call"
[(parallel [(call (match_operand:SI 0 "" "")
(match_operand 1 "" ""))
(use (reg:SI 1))])]
""
"
{
if (GET_CODE (operands[0]) == MEM
&& ! call_address_operand (XEXP (operands[0], 0), SImode))
operands[0] = gen_rtx (MEM, GET_MODE (operands[0]),
force_reg (Pmode, XEXP (operands[0], 0)));
}")
(define_insn ""
[(parallel [(call (mem:SI (match_operand:SI 0 "call_address_operand" "rQ"))
(match_operand 1 "" ""))
(use (reg:SI 1))])]
""
"* return output_call (operands, operands[0]);"
[(set_attr "type" "call")])
(define_expand "call_value"
[(parallel [(set (match_operand 0 "register_operand" "")
(call (match_operand:SI 1 "" "")
(match_operand 2 "" "")))
(use (reg:SI 1))])]
""
"
{
if (GET_CODE (operands[1]) == MEM
&& ! call_address_operand (XEXP (operands[1], 0), SImode))
operands[1] = gen_rtx (MEM, GET_MODE (operands[1]),
force_reg (Pmode, XEXP (operands[1], 0)));
}")
(define_insn ""
[(parallel [(set (match_operand 0 "register_operand" "=r")
(call (mem:SI
(match_operand:SI 1 "call_address_operand" "rQ"))
(match_operand 2 "" "")))
(use (reg:SI 1))])]
""
"* return output_call (operands, operands[1]);"
[(set_attr "type" "call")])
;; Nop instruction and others
(define_insn "nop"
[(const_int 0)]
""
"ff0 %#r0,%#r0")
(define_insn "return"
[(return)]
"null_epilogue ()"
"jmp%. %#r1"
[(set_attr "type" "branch")])
;; jump to variable address (for NeXT).
(define_insn "tablejump"
[(set (pc) (match_operand:SI 0 "register_operand" "r"))
(use (label_ref (match_operand 1 "" "")))]
""
"jmp%. %0"
[(set_attr "type" "branch")])
(define_insn "indirect_jump"
[(set (pc) (match_operand:SI 0 "register_operand" "r"))]
""
"jmp%. %0"
[(set_attr "type" "branch")])
(define_insn "jump"
[(set (pc)
(label_ref (match_operand 0 "" "")))]
""
"br%. %l0"
[(set_attr "type" "jump")])
;; Special insn to serve as the last insn of a define_expand. This insn
;; will generate no code.
(define_expand "dummy"
[(set (match_operand 0 "" "") (match_dup 0))]
""
"")
;;- Local variables:
;;- mode:emacs-lisp
;;- comment-start: ";;- "
;;- eval: (set-syntax-table (copy-sequence (syntax-table)))
;;- eval: (modify-syntax-entry ?[ "(]")
;;- eval: (modify-syntax-entry ?] ")[")
;;- eval: (modify-syntax-entry ?{ "(}")
;;- eval: (modify-syntax-entry ?} "){")
;;- End: