1;; Mitsubishi D30V Machine description template
2;; Copyright (C) 1997, 1998, 1999, 2000 Free Software Foundation, Inc.
3;; Contributed by Cygnus Solutions.
4;;
5;; This file is part of GCC.
6;;
7;; GCC is free software; you can redistribute it and/or modify
8;; it under the terms of the GNU General Public License as published by
9;; the Free Software Foundation; either version 2, or (at your option)
10;; any later version.
11;;
12;; GCC is distributed in the hope that it will be useful,
13;; but WITHOUT ANY WARRANTY; without even the implied warranty of
14;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15;; GNU General Public License for more details.
16;;
17;; You should have received a copy of the GNU General Public License
18;; along with GCC; see the file COPYING.  If not, write to
19;; the Free Software Foundation, 59 Temple Place - Suite 330,
20;; Boston, MA 02111-1307, USA.
21
22;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
23
24
25;; ::::::::::::::::::::
26;; ::
27;; :: Constraints
28;; ::
29;; ::::::::::::::::::::
30
31;; Standard Constraints
32;;
33;; `m' A memory operand is allowed, with any kind of address that the
34;;     machine supports in general.
35;;
36;; `o' A memory operand is allowed, but only if the address is
37;;     "offsettable".  This means that adding a small integer (actually, the
38;;     width in bytes of the operand, as determined by its machine mode) may be
39;;     added to the address and the result is also a valid memory address.
40;;
41;; `V' A memory operand that is not offsettable.  In other words,
42;;     anything that would fit the `m' constraint but not the `o' constraint.
43;;
44;; `<' A memory operand with autodecrement addressing (either
45;;     predecrement or postdecrement) is allowed.
46;;
47;; `>' A memory operand with autoincrement addressing (either
48;;     preincrement or postincrement) is allowed.
49;;
50;; `r' A register operand is allowed provided that it is in a general
51;;     register.
52;;
53;; `d', `a', `f', ...
54;;     Other letters can be defined in machine-dependent fashion to stand for
55;;     particular classes of registers.  `d', `a' and `f' are defined on the
56;;     68000/68020 to stand for data, address and floating point registers.
57;;
58;; `i' An immediate integer operand (one with constant value) is allowed.
59;;     This includes symbolic constants whose values will be known only at
60;;     assembly time.
61;;
62;; `n' An immediate integer operand with a known numeric value is allowed.
63;;     Many systems cannot support assembly-time constants for operands less
64;;     than a word wide.  Constraints for these operands should use `n' rather
65;;     than `i'.
66;;
67;; 'I' First machine-dependent integer constant.
68;; 'J' Second machine-dependent integer constant.
69;; 'K' Third machine-dependent integer constant.
70;; 'L' Fourth machine-dependent integer constant.
71;; 'M' Fifth machine-dependent integer constant.
72;; 'N' Sixth machine-dependent integer constant.
73;; 'O' Seventh machine-dependent integer constant.
74;; 'P' Eighth machine-dependent integer constant.
75;;
76;;     Other letters in the range `I' through `P' may be defined in a
77;;     machine-dependent fashion to permit immediate integer operands with
78;;     explicit integer values in specified ranges.  For example, on the 68000,
79;;     `I' is defined to stand for the range of values 1 to 8.  This is the
80;;     range permitted as a shift count in the shift instructions.
81;;
82;; `E' An immediate floating operand (expression code `const_double') is
83;;     allowed, but only if the target floating point format is the same as
84;;     that of the host machine (on which the compiler is running).
85;;
86;; `F' An immediate floating operand (expression code `const_double') is
87;;     allowed.
88;;
89;; 'G' First machine-dependent const_double.
90;; 'H' Second machine-dependent const_double.
91;;
92;; `s' An immediate integer operand whose value is not an explicit
93;;     integer is allowed.
94;;
95;;     This might appear strange; if an insn allows a constant operand with a
96;;     value not known at compile time, it certainly must allow any known
97;;     value.  So why use `s' instead of `i'?  Sometimes it allows better code
98;;     to be generated.
99;;
100;;     For example, on the 68000 in a fullword instruction it is possible to
101;;     use an immediate operand; but if the immediate value is between -128 and
102;;     127, better code results from loading the value into a register and
103;;     using the register.  This is because the load into the register can be
104;;     done with a `moveq' instruction.  We arrange for this to happen by
105;;     defining the letter `K' to mean "any integer outside the range -128 to
106;;     127", and then specifying `Ks' in the operand constraints.
107;;
108;; `g' Any register, memory or immediate integer operand is allowed,
109;;     except for registers that are not general registers.
110;;
111;; `X' Any operand whatsoever is allowed, even if it does not satisfy
112;;     `general_operand'.  This is normally used in the constraint of a
113;;     `match_scratch' when certain alternatives will not actually require a
114;;     scratch register.
115;;
116;; `0' Match operand 0.
117;; `1' Match operand 1.
118;; `2' Match operand 2.
119;; `3' Match operand 3.
120;; `4' Match operand 4.
121;; `5' Match operand 5.
122;; `6' Match operand 6.
123;; `7' Match operand 7.
124;; `8' Match operand 8.
125;; `9' Match operand 9.
126;;
127;;     An operand that matches the specified operand number is allowed.  If a
128;;     digit is used together with letters within the same alternative, the
129;;     digit should come last.
130;;
131;;     This is called a "matching constraint" and what it really means is that
132;;     the assembler has only a single operand that fills two roles considered
133;;     separate in the RTL insn.  For example, an add insn has two input
134;;     operands and one output operand in the RTL, but on most CISC machines an
135;;     add instruction really has only two operands, one of them an
136;;     input-output operand:
137;;
138;;          addl #35,r12
139;;
140;;     Matching constraints are used in these circumstances.  More precisely,
141;;     the two operands that match must include one input-only operand and one
142;;     output-only operand.  Moreover, the digit must be a smaller number than
143;;     the number of the operand that uses it in the constraint.
144;;
145;;     For operands to match in a particular case usually means that they are
146;;     identical-looking RTL expressions.  But in a few special cases specific
147;;     kinds of dissimilarity are allowed.  For example, `*x' as an input
148;;     operand will match `*x++' as an output operand.  For proper results in
149;;     such cases, the output template should always use the output-operand's
150;;     number when printing the operand.
151;;
152;; `p' An operand that is a valid memory address is allowed.  This is for
153;;     "load address" and "push address" instructions.
154;;
155;;     `p' in the constraint must be accompanied by `address_operand' as the
156;;     predicate in the `match_operand'.  This predicate interprets the mode
157;;     specified in the `match_operand' as the mode of the memory reference for
158;;     which the address would be valid.
159;;
160;; `Q` First non constant, non register machine-dependent insns
161;; `R` Second non constant, non register machine-dependent insns
162;; `S` Third non constant, non register machine-dependent insns
163;; `T` Fourth non constant, non register machine-dependent insns
164;; `U` Fifth non constant, non register machine-dependent insns
165;;
166;;     Letters in the range `Q' through `U' may be defined in a
167;;     machine-dependent fashion to stand for arbitrary operand types.  The
168;;     machine description macro `EXTRA_CONSTRAINT' is passed the operand as
169;;     its first argument and the constraint letter as its second operand.
170;;
171;;     A typical use for this would be to distinguish certain types of memory
172;;     references that affect other insn operands.
173;;
174;;     Do not define these constraint letters to accept register references
175;;     (`reg'); the reload pass does not expect this and would not handle it
176;;     properly.
177
178;; Multiple Alternative Constraints
179;; `?' Disparage slightly the alternative that the `?' appears in, as a
180;;     choice when no alternative applies exactly.  The compiler regards this
181;;     alternative as one unit more costly for each `?' that appears in it.
182;;
183;; `!' Disparage severely the alternative that the `!' appears in.  This
184;;     alternative can still be used if it fits without reloading, but if
185;;     reloading is needed, some other alternative will be used.
186
187;; Constraint modifiers
188;; `=' Means that this operand is write-only for this instruction: the
189;;     previous value is discarded and replaced by output data.
190;;
191;; `+' Means that this operand is both read and written by the
192;;     instruction.
193;;
194;;     When the compiler fixes up the operands to satisfy the constraints, it
195;;     needs to know which operands are inputs to the instruction and which are
196;;     outputs from it.  `=' identifies an output; `+' identifies an operand
197;;     that is both input and output; all other operands are assumed to be
198;;     input only.
199;;
200;; `&' Means (in a particular alternative) that this operand is written
201;;     before the instruction is finished using the input operands.  Therefore,
202;;     this operand may not lie in a register that is used as an input operand
203;;     or as part of any memory address.
204;;
205;;     `&' applies only to the alternative in which it is written.  In
206;;     constraints with multiple alternatives, sometimes one alternative
207;;     requires `&' while others do not.
208;;
209;;     `&' does not obviate the need to write `='.
210;;
211;; `%' Declares the instruction to be commutative for this operand and the
212;;     following operand.  This means that the compiler may interchange the two
213;;     operands if that is the cheapest way to make all operands fit the
214;;     constraints.  This is often used in patterns for addition instructions
215;;     that really have only two operands: the result must go in one of the
216;;     arguments.
217;;
218;; `#' Says that all following characters, up to the next comma, are to be
219;;     ignored as a constraint.  They are significant only for choosing
220;;     register preferences.
221;;
222;; `*' Says that the following character should be ignored when choosing
223;;     register preferences.  `*' has no effect on the meaning of the
224;;     constraint as a constraint, and no effect on reloading.
225
226;; ::::::::::::::::::::
227;; ::
228;; :: D30V register classes
229;; ::
230;; ::::::::::::::::::::
231
232;; `a'	Accumulator registers (a0, a1)
233;; `b'	Flag registers for speculative execution (f0, f1)
234;; `c'	CR registers
235;; `d'	GPR registers
236;; `e'	Even GPR registers
237;; `f'	Any flag registers (f0, f1, ..., c)
238;; `l'	CR7, the repeat count
239;; `x'	F0
240;; `y'	F1
241;; `z'	Flag registers other than F0 and F1.
242
243;; ::::::::::::::::::::
244;; ::
245;; :: D30V special constraints
246;; ::
247;; ::::::::::::::::::::
248
249;; `G'	Const double with 0 in both low & high part.
250;; `H'	Unused.
251;; `I'	Signed 6 bit integer constant (>= -32 && <= 31).
252;; `J'	Unsigned 5 bit integer constant (>= 0 && <= 31).
253;; `K'	Integer constant with 1 bit set (for bset).
254;; `L'	Integer constant with 1 bit clear (for bclr).
255;; `M'	Integer constant 32.
256;; `N'	Integer constant 1.
257;; `O'	Integer constant 0.
258;; `P'	Integer constant >= 32 && <= 63.
259;; `Q'	Short memory operand (can be done in small insn).
260;; `R'	Memory operand using a single register for address.
261;; `S'	Memory operand to constant address.
262;; `T'	Unused.
263;; `U'	Unused.
264
265;; ::::::::::::::::::::
266;; ::
267;; :: Standard operand flags
268;; ::
269;; ::::::::::::::::::::
270
271;; `='  Output a number unique to each instruction in the compilation.
272;; `a'  Substitute an operand as if it were a memory reference.
273;; `c'  Omit the syntax that indicates an immediate operand.
274;; `l'  Substitute a LABEL_REF into a jump instruction.
275;; `n'  Like %cDIGIT, except negate the value before printing.
276
277;; ::::::::::::::::::::
278;; ::
279;; :: D30V print_operand flags
280;; ::
281;; ::::::::::::::::::::
282
283;; `.'	Print r0
284;; `f'  Print a SF constant as an int.
285;; `s'  Subtract 32 and negate.
286;; `A'  Print accumulator number without an `a' in front of it.
287;; `B'  Print bit offset for BSET, etc. instructions.
288;; `E'  Print u if this is zero extend, nothing if this is sign extend.
289;; `F'  Emit /{f,t,x}{f,t,x} for executing a false condition.
290;; `L'  Print the lower half of a 64 bit item.
291;; `M'  Print a memory reference for ld/st instructions.
292;; `R'  Return appropriate cmp instruction for relational test.
293;; `S'  Subtract 32.
294;; `T'  Emit /{f,t,x}{f,t,x} for executing a true condition.
295;; `U'  Print the upper half of a 64 bit item.
296
297
298;; ::::::::::::::::::::
299;; ::
300;; :: Attributes
301;; ::
302;; ::::::::::::::::::::
303
304;; The `define_attr' expression is used to define each attribute required by
305;; the target machine.  It looks like:
306;;
307;; (define_attr NAME LIST-OF-VALUES DEFAULT)
308
309;; NAME is a string specifying the name of the attribute being defined.
310
311;; LIST-OF-VALUES is either a string that specifies a comma-separated list of
312;; values that can be assigned to the attribute, or a null string to indicate
313;; that the attribute takes numeric values.
314
315;; DEFAULT is an attribute expression that gives the value of this attribute
316;; for insns that match patterns whose definition does not include an explicit
317;; value for this attribute.
318
319;; For each defined attribute, a number of definitions are written to the
320;; `insn-attr.h' file.  For cases where an explicit set of values is specified
321;; for an attribute, the following are defined:
322
323;; * A `#define' is written for the symbol `HAVE_ATTR_NAME'.
324;;
325;; * An enumeral class is defined for `attr_NAME' with elements of the
326;;   form `UPPER-NAME_UPPER-VALUE' where the attribute name and value are first
327;;   converted to upper case.
328;;
329;; * A function `get_attr_NAME' is defined that is passed an insn and
330;;   returns the attribute value for that insn.
331
332;; For example, if the following is present in the `md' file:
333;;
334;; (define_attr "type" "branch,fp,load,store,arith" ...)
335;;
336;; the following lines will be written to the file `insn-attr.h'.
337;;
338;; #define HAVE_ATTR_type
339;; enum attr_type {TYPE_BRANCH, TYPE_FP, TYPE_LOAD, TYPE_STORE, TYPE_ARITH};
340;; extern enum attr_type get_attr_type ();
341
342;; If the attribute takes numeric values, no `enum' type will be defined and
343;; the function to obtain the attribute's value will return `int'.
344
345;; Note, we lie a little bit here to make it simpler to optimize.  We pretend there
346;; is a separate long functional unit for long instructions that uses both the IU & MU.
347
348(define_attr "type" "iu,mu,br,br2,either,scarry,lcarry,scmp,lcmp,sload,lload,mul,long,multi,unknown"
349  (const_string "unknown"))
350
351;; Length in word units
352(define_attr "length" ""
353  (cond [(eq_attr "type" "iu,mu,either,scmp,sload,mul,scarry,")
354		(const_int 4)
355	 (eq_attr "type" "long,lcmp,lload,lcarry")
356		(const_int 8)
357	 (eq_attr "type" "multi,unknown")
358		(const_int 64)	;; set higher to give a fudge factor
359	 (eq_attr "type" "br")
360		(if_then_else (and (ge (minus (pc) (match_dup 0))
361				       (const_int -1048576))
362				   (lt (minus (pc) (match_dup 0))
363				       (const_int 1048575)))
364		  (const_int 4)
365		  (const_int 8))
366	 (eq_attr "type" "br2")
367		(if_then_else (and (ge (minus (pc) (match_dup 0))
368				       (const_int -16384))
369				   (lt (minus (pc) (match_dup 0))
370				       (const_int 16383)))
371		  (const_int 4)
372		  (const_int 8))
373	]
374	(const_int 8)))
375
376(define_attr "predicable" "no,yes"
377  (const_string "yes"))
378
379;; ::::::::::::::::::::
380;; ::
381;; :: Function Units
382;; ::
383;; ::::::::::::::::::::
384
385;; On most RISC machines, there are instructions whose results are not
386;; available for a specific number of cycles.  Common cases are instructions
387;; that load data from memory.  On many machines, a pipeline stall will result
388;; if the data is referenced too soon after the load instruction.
389
390;; In addition, many newer microprocessors have multiple function units,
391;; usually one for integer and one for floating point, and often will incur
392;; pipeline stalls when a result that is needed is not yet ready.
393
394;; The descriptions in this section allow the specification of how much time
395;; must elapse between the execution of an instruction and the time when its
396;; result is used.  It also allows specification of when the execution of an
397;; instruction will delay execution of similar instructions due to function
398;; unit conflicts.
399
400;; For the purposes of the specifications in this section, a machine is divided
401;; into "function units", each of which execute a specific class of
402;; instructions in first-in-first-out order.  Function units that accept one
403;; instruction each cycle and allow a result to be used in the succeeding
404;; instruction (usually via forwarding) need not be specified.  Classic RISC
405;; microprocessors will normally have a single function unit, which we can call
406;; `memory'.  The newer "superscalar" processors will often have function units
407;; for floating point operations, usually at least a floating point adder and
408;; multiplier.
409
410;; Each usage of a function units by a class of insns is specified with a
411;; `define_function_unit' expression, which looks like this:
412
413;; (define_function_unit NAME MULTIPLICITY SIMULTANEITY TEST READY-DELAY
414;;   ISSUE-DELAY [CONFLICT-LIST])
415
416;; NAME is a string giving the name of the function unit.
417
418;; MULTIPLICITY is an integer specifying the number of identical units in the
419;; processor.  If more than one unit is specified, they will be scheduled
420;; independently.  Only truly independent units should be counted; a pipelined
421;; unit should be specified as a single unit.  (The only common example of a
422;; machine that has multiple function units for a single instruction class that
423;; are truly independent and not pipelined are the two multiply and two
424;; increment units of the CDC 6600.)
425
426;; SIMULTANEITY specifies the maximum number of insns that can be executing in
427;; each instance of the function unit simultaneously or zero if the unit is
428;; pipelined and has no limit.
429
430;; All `define_function_unit' definitions referring to function unit NAME must
431;; have the same name and values for MULTIPLICITY and SIMULTANEITY.
432
433;; TEST is an attribute test that selects the insns we are describing in this
434;; definition.  Note that an insn may use more than one function unit and a
435;; function unit may be specified in more than one `define_function_unit'.
436
437;; READY-DELAY is an integer that specifies the number of cycles after which
438;; the result of the instruction can be used without introducing any stalls.
439
440;; ISSUE-DELAY is an integer that specifies the number of cycles after the
441;; instruction matching the TEST expression begins using this unit until a
442;; subsequent instruction can begin.  A cost of N indicates an N-1 cycle delay.
443;; A subsequent instruction may also be delayed if an earlier instruction has a
444;; longer READY-DELAY value.  This blocking effect is computed using the
445;; SIMULTANEITY, READY-DELAY, ISSUE-DELAY, and CONFLICT-LIST terms.  For a
446;; normal non-pipelined function unit, SIMULTANEITY is one, the unit is taken
447;; to block for the READY-DELAY cycles of the executing insn, and smaller
448;; values of ISSUE-DELAY are ignored.
449
450;; CONFLICT-LIST is an optional list giving detailed conflict costs for this
451;; unit.  If specified, it is a list of condition test expressions to be
452;; applied to insns chosen to execute in NAME following the particular insn
453;; matching TEST that is already executing in NAME.  For each insn in the list,
454;; ISSUE-DELAY specifies the conflict cost; for insns not in the list, the cost
455;; is zero.  If not specified, CONFLICT-LIST defaults to all instructions that
456;; use the function unit.
457
458;; Typical uses of this vector are where a floating point function unit can
459;; pipeline either single- or double-precision operations, but not both, or
460;; where a memory unit can pipeline loads, but not stores, etc.
461
462;; As an example, consider a classic RISC machine where the result of a load
463;; instruction is not available for two cycles (a single "delay" instruction is
464;; required) and where only one load instruction can be executed
465;; simultaneously.  This would be specified as:
466
467;; (define_function_unit "memory" 1 1 (eq_attr "type" "load") 2 0)
468
469;; For the case of a floating point function unit that can pipeline
470;; either single or double precision, but not both, the following could be
471;; specified:
472;;
473;; (define_function_unit "fp" 1 0
474;;   (eq_attr "type" "sp_fp") 4 4
475;;   [(eq_attr "type" "dp_fp")])
476;;
477;; (define_function_unit "fp" 1 0
478;;   (eq_attr "type" "dp_fp") 4 4
479;;   [(eq_attr "type" "sp_fp")])
480
481;; Note: The scheduler attempts to avoid function unit conflicts and uses all
482;; the specifications in the `define_function_unit' expression.  It has
483;; recently come to our attention that these specifications may not allow
484;; modeling of some of the newer "superscalar" processors that have insns using
485;; multiple pipelined units.  These insns will cause a potential conflict for
486;; the second unit used during their execution and there is no way of
487;; representing that conflict.  We welcome any examples of how function unit
488;; conflicts work in such processors and suggestions for their representation.
489
490(define_function_unit "iu" 1 0
491  (eq_attr "type" "iu,either")
492  1 1
493  [(eq_attr "type" "long,lcmp,lload,multi,unknown")])
494
495(define_function_unit "iu" 1 0
496  (eq_attr "type" "scmp,mul,scarry")
497  2 1
498  [(eq_attr "type" "long,lcmp,lload,multi,unknown")])
499
500(define_function_unit "mu" 1 0
501  (eq_attr "type" "mu,br,br2,either")
502  1 1
503  [(eq_attr "type" "long,lcmp,lload,multi,unknown")])
504
505(define_function_unit "mu" 1 0
506  (eq_attr "type" "scarry,scmp,sload")
507  2 1
508  [(eq_attr "type" "long,lcmp,lload,multi,unknown")])
509
510(define_function_unit "long" 1 0
511  (eq_attr "type" "long,multi,unknown")
512  1 1
513  [(eq_attr "type" "iu,mu,scarry,scmp,sload,mul,br,br2,either")])
514
515(define_function_unit "long" 1 0
516  (eq_attr "type" "lcmp,lload,lcarry")
517  2 1
518  [(eq_attr "type" "iu,mu,scarry,scmp,sload,mul,br,br2,either")])
519
520
521;; ::::::::::::::::::::
522;; ::
523;; :: Delay Slots
524;; ::
525;; ::::::::::::::::::::
526
527;; The insn attribute mechanism can be used to specify the requirements for
528;; delay slots, if any, on a target machine.  An instruction is said to require
529;; a "delay slot" if some instructions that are physically after the
530;; instruction are executed as if they were located before it.  Classic
531;; examples are branch and call instructions, which often execute the following
532;; instruction before the branch or call is performed.
533
534;; On some machines, conditional branch instructions can optionally "annul"
535;; instructions in the delay slot.  This means that the instruction will not be
536;; executed for certain branch outcomes.  Both instructions that annul if the
537;; branch is true and instructions that annul if the branch is false are
538;; supported.
539
540;; Delay slot scheduling differs from instruction scheduling in that
541;; determining whether an instruction needs a delay slot is dependent only
542;; on the type of instruction being generated, not on data flow between the
543;; instructions.  See the next section for a discussion of data-dependent
544;; instruction scheduling.
545
546;; The requirement of an insn needing one or more delay slots is indicated via
547;; the `define_delay' expression.  It has the following form:
548;;
549;; (define_delay TEST
550;;   [DELAY-1 ANNUL-TRUE-1 ANNUL-FALSE-1
551;;    DELAY-2 ANNUL-TRUE-2 ANNUL-FALSE-2
552;;    ...])
553
554;; TEST is an attribute test that indicates whether this `define_delay' applies
555;; to a particular insn.  If so, the number of required delay slots is
556;; determined by the length of the vector specified as the second argument.  An
557;; insn placed in delay slot N must satisfy attribute test DELAY-N.
558;; ANNUL-TRUE-N is an attribute test that specifies which insns may be annulled
559;; if the branch is true.  Similarly, ANNUL-FALSE-N specifies which insns in
560;; the delay slot may be annulled if the branch is false.  If annulling is not
561;; supported for that delay slot, `(nil)' should be coded.
562
563;; For example, in the common case where branch and call insns require a single
564;; delay slot, which may contain any insn other than a branch or call, the
565;; following would be placed in the `md' file:
566
567;; (define_delay (eq_attr "type" "branch,call")
568;;		 [(eq_attr "type" "!branch,call") (nil) (nil)])
569
570;; Multiple `define_delay' expressions may be specified.  In this case, each
571;; such expression specifies different delay slot requirements and there must
572;; be no insn for which tests in two `define_delay' expressions are both true.
573
574;; For example, if we have a machine that requires one delay slot for branches
575;; but two for calls, no delay slot can contain a branch or call insn, and any
576;; valid insn in the delay slot for the branch can be annulled if the branch is
577;; true, we might represent this as follows:
578
579;; (define_delay (eq_attr "type" "branch")
580;;   [(eq_attr "type" "!branch,call")
581;;    (eq_attr "type" "!branch,call")
582;;    (nil)])
583;;
584;; (define_delay (eq_attr "type" "call")
585;;   [(eq_attr "type" "!branch,call") (nil) (nil)
586;;    (eq_attr "type" "!branch,call") (nil) (nil)])
587
588
589;; ::::::::::::::::::::
590;; ::
591;; :: Moves
592;; ::
593;; ::::::::::::::::::::
594
595;; Wrap moves in define_expand to prevent memory->memory moves from being
596;; generated at the RTL level, which generates better code for most machines
597;; which can't do mem->mem moves.
598
599;; If operand 0 is a `subreg' with mode M of a register whose own mode is wider
600;; than M, the effect of this instruction is to store the specified value in
601;; the part of the register that corresponds to mode M.  The effect on the rest
602;; of the register is undefined.
603
604;; This class of patterns is special in several ways.  First of all, each of
605;; these names *must* be defined, because there is no other way to copy a datum
606;; from one place to another.
607
608;; Second, these patterns are not used solely in the RTL generation pass.  Even
609;; the reload pass can generate move insns to copy values from stack slots into
610;; temporary registers.  When it does so, one of the operands is a hard
611;; register and the other is an operand that can need to be reloaded into a
612;; register.
613
614;; Therefore, when given such a pair of operands, the pattern must
615;; generate RTL which needs no reloading and needs no temporary
616;; registers--no registers other than the operands.  For example, if
617;; you support the pattern with a `define_expand', then in such a
618;; case the `define_expand' mustn't call `force_reg' or any other such
619;; function which might generate new pseudo registers.
620
621;; This requirement exists even for subword modes on a RISC machine
622;; where fetching those modes from memory normally requires several
623;; insns and some temporary registers.  Look in `spur.md' to see how
624;; the requirement can be satisfied.
625
626;; During reload a memory reference with an invalid address may be passed as an
627;; operand.  Such an address will be replaced with a valid address later in the
628;; reload pass.  In this case, nothing may be done with the address except to
629;; use it as it stands.  If it is copied, it will not be replaced with a valid
630;; address.  No attempt should be made to make such an address into a valid
631;; address and no routine (such as `change_address') that will do so may be
632;; called.  Note that `general_operand' will fail when applied to such an
633;; address.
634;;
635;; The global variable `reload_in_progress' (which must be explicitly declared
636;; if required) can be used to determine whether such special handling is
637;; required.
638;;
639;; The variety of operands that have reloads depends on the rest of
640;; the machine description, but typically on a RISC machine these can
641;; only be pseudo registers that did not get hard registers, while on
642;; other machines explicit memory references will get optional
643;; reloads.
644;;
645;; If a scratch register is required to move an object to or from memory, it
646;; can be allocated using `gen_reg_rtx' prior to reload.  But this is
647;; impossible during and after reload.  If there are cases needing scratch
648;; registers after reload, you must define `SECONDARY_INPUT_RELOAD_CLASS' and
649;; perhaps also `SECONDARY_OUTPUT_RELOAD_CLASS' to detect them, and provide
650;; patterns `reload_inM' or `reload_outM' to handle them.  *Note Register
651;; Classes::.
652
653;; The constraints on a `moveM' must permit moving any hard register to any
654;; other hard register provided that `HARD_REGNO_MODE_OK' permits mode M in
655;; both registers and `REGISTER_MOVE_COST' applied to their classes returns a
656;; value of 2.
657
658;; It is obligatory to support floating point `moveM' instructions
659;; into and out of any registers that can hold fixed point values,
660;; because unions and structures (which have modes `SImode' or
661;; `DImode') can be in those registers and they may have floating
662;; point members.
663
664;; There may also be a need to support fixed point `moveM' instructions in and
665;; out of floating point registers.  Unfortunately, I have forgotten why this
666;; was so, and I don't know whether it is still true.  If `HARD_REGNO_MODE_OK'
667;; rejects fixed point values in floating point registers, then the constraints
668;; of the fixed point `moveM' instructions must be designed to avoid ever
669;; trying to reload into a floating point register.
670
671(define_expand "movqi"
672  [(set (match_operand:QI 0 "general_operand" "")
673	(match_operand:QI 1 "general_operand" ""))]
674  ""
675  "
676{
677  if (!reload_in_progress && !reload_completed
678      && !register_operand (operands[0], QImode)
679      && !reg_or_0_operand (operands[1], QImode))
680    operands[1] = copy_to_mode_reg (QImode, operands[1]);
681}")
682
683(define_insn "*movqi_internal"
684  [(set (match_operand:QI 0 "move_output_operand" "=d,d,d,d,Q,m,Q,m,d,c")
685	(match_operand:QI 1 "move_input_operand" "dI,i,Q,m,d,d,O,O,c,d"))]
686  "register_operand (operands[0], QImode) || reg_or_0_operand (operands[1], QImode)"
687  "@
688    or%: %0,%.,%1
689    or%: %0,%.,%1
690    ldb%: %0,%M1
691    ldb%: %0,%M1
692    stb%: %1,%M0
693    stb%: %1,%M0
694    stb%: %.,%M0
695    stb%: %.,%M0
696    mvfsys%: %0,%1
697    mvtsys%: %0,%1"
698  [(set_attr "length" "4,8,4,8,4,8,4,8,4,4")
699   (set_attr "type" "either,long,sload,lload,mu,long,mu,long,mu,mu")])
700
701(define_expand "movhi"
702  [(set (match_operand:HI 0 "general_operand" "")
703	(match_operand:HI 1 "general_operand" ""))]
704  ""
705  "
706{
707  if (!reload_in_progress && !reload_completed
708      && !register_operand (operands[0], HImode)
709      && !reg_or_0_operand (operands[1], HImode))
710    operands[1] = copy_to_mode_reg (HImode, operands[1]);
711}")
712
713(define_insn "*movhi_internal"
714  [(set (match_operand:HI 0 "move_output_operand" "=d,d,d,d,Q,m,Q,m,d,c")
715	(match_operand:HI 1 "move_input_operand" "dI,i,Q,m,d,d,O,O,c,d"))]
716  "register_operand (operands[0], HImode) || reg_or_0_operand (operands[1], HImode)"
717  "@
718    or%: %0,%.,%1
719    or%: %0,%.,%1
720    ldh%: %0,%M1
721    ldh%: %0,%M1
722    sth%: %1,%M0
723    sth%: %1,%M0
724    sth%: %.,%M0
725    sth%: %.,%M0
726    mvfsys%: %0,%1
727    mvtsys%: %0,%1"
728  [(set_attr "length" "4,8,4,8,4,8,4,8,4,4")
729   (set_attr "type" "either,long,sload,lload,mu,long,mu,long,mu,mu")])
730
731(define_expand "movsi"
732  [(set (match_operand:SI 0 "general_operand" "")
733	(match_operand:SI 1 "general_operand" ""))]
734  ""
735  "
736{
737  if (!reload_in_progress && !reload_completed
738      && !register_operand (operands[0], SImode)
739      && !reg_or_0_operand (operands[1], SImode))
740    operands[1] = copy_to_mode_reg (SImode, operands[1]);
741
742  /* Convert addressing modes into the appropriate add/sub with the clobbers
743     needed.  This is generated by builtin_setjmp in the exception handling. */
744  if (GET_CODE (operands[1]) == PLUS)
745    {
746      emit_insn (gen_addsi3 (operands[0], XEXP (operands[1], 0),
747			     XEXP (operands[1], 1)));
748      DONE;
749    }
750
751  else if (GET_CODE (operands[1]) == MINUS)
752    {
753      emit_insn (gen_subsi3 (operands[0], XEXP (operands[1], 0),
754			     XEXP (operands[1], 1)));
755      DONE;
756    }
757}")
758
759(define_insn "*movsi_internal"
760  [(set (match_operand:SI 0 "move_output_operand" "=d,d,d,d,d,Q,m,Q,m,d,c")
761	(match_operand:SI 1 "move_input_operand" "dI,F,i,Q,m,d,d,O,O,c,d"))]
762  "register_operand (operands[0], SImode) || reg_or_0_operand (operands[1], SImode)"
763  "@
764    or%: %0,%.,%1
765    or%: %0,%.,%L1
766    or%: %0,%.,%1
767    ldw%: %0,%M1
768    ldw%: %0,%M1
769    stw%: %1,%M0
770    stw%: %1,%M0
771    stw%: %.,%M0
772    stw%: %.,%M0
773    mvfsys%: %0,%1
774    mvtsys%: %0,%1"
775  [(set_attr "length" "4,8,8,4,8,4,8,4,8,4,4")
776   (set_attr "type" "either,long,long,sload,lload,mu,long,mu,long,mu,mu")])
777
778(define_expand "movdi"
779  [(set (match_operand:DI 0 "general_operand" "")
780	(match_operand:DI 1 "general_operand" ""))]
781  ""
782  "
783{
784  if (!reload_in_progress && !reload_completed
785      && !register_operand (operands[0], DImode)
786      && !register_operand (operands[1], DImode))
787    operands[1] = copy_to_mode_reg (DImode, operands[1]);
788}")
789
790(define_insn "*movdi_internal"
791  [(set (match_operand:DI 0 "move_output_operand" "=e,e,e,e,Q,m,e,a,a")
792	(match_operand:DI 1 "move_input_operand" "eI,iF,Q,m,e,e,a,e,O"))]
793  "register_operand (operands[0], DImode) || register_operand (operands[1], DImode)"
794  "* return d30v_move_2words (operands, insn);"
795  [(set_attr "length" "8,16,4,8,4,8,8,4,4")
796   (set_attr "type" "multi,multi,sload,lload,mu,long,multi,iu,iu")])
797
798(define_split
799  [(set (match_operand:DI 0 "gpr_operand" "")
800	(match_operand:DI 1 "gpr_or_dbl_const_operand" ""))]
801  "reload_completed"
802  [(set (match_dup 2) (match_dup 3))
803   (set (match_dup 4) (match_dup 5))]
804  "
805{
806  d30v_split_double (operands[0], &operands[2], &operands[4]);
807  d30v_split_double (operands[1], &operands[3], &operands[5]);
808}")
809
810(define_expand "movsf"
811  [(set (match_operand:SF 0 "general_operand" "")
812	(match_operand:SF 1 "general_operand" ""))]
813  ""
814  "
815{
816  if (!reload_in_progress && !reload_completed
817      && !register_operand (operands[0], SFmode)
818      && !reg_or_0_operand (operands[1], SFmode))
819    operands[1] = copy_to_mode_reg (SFmode, operands[1]);
820}")
821
822(define_insn "*movsf_internal"
823  [(set (match_operand:SF 0 "move_output_operand" "=d,d,d,d,d,Q,m,Q,m")
824	(match_operand:SF 1 "move_input_operand" "d,G,F,Q,m,d,d,G,G"))]
825  "register_operand (operands[0], SFmode) || reg_or_0_operand (operands[1], SFmode)"
826  "@
827    or%: %0,%.,%1
828    or%: %0,%.,0
829    or%: %0,%.,%f1
830    ldw%: %0,%M1
831    ldw%: %0,%M1
832    stw%: %1,%M0
833    stw%: %1,%M0
834    stw%: %.,%M0
835    stw%: %.,%M0"
836  [(set_attr "length" "4,4,8,4,8,4,8,4,8")
837   (set_attr "type" "either,either,long,sload,lload,mu,long,mu,long")])
838
839(define_expand "movdf"
840  [(set (match_operand:DF 0 "general_operand" "")
841	(match_operand:DF 1 "general_operand" ""))]
842  ""
843  "
844{
845  if (!reload_in_progress && !reload_completed
846      && !register_operand (operands[0], DFmode)
847      && !register_operand (operands[1], DFmode))
848    operands[1] = copy_to_mode_reg (DFmode, operands[1]);
849}")
850
851(define_insn "*movdf_internal"
852  [(set (match_operand:DF 0 "move_output_operand" "=e,e,e,e,Q,m,!*e,!*a")
853	(match_operand:DF 1 "move_input_operand" "eG,F,Q,m,e,e,!*a,!*e"))]
854  "register_operand (operands[0], DFmode) || register_operand (operands[1], DFmode)"
855  "* return d30v_move_2words (operands, insn);"
856  [(set_attr "length" "8,16,4,8,4,8,8,4")
857   (set_attr "type" "multi,multi,sload,lload,mu,long,multi,iu")])
858
859(define_split
860  [(set (match_operand:DF 0 "gpr_operand" "")
861	(match_operand:DF 1 "gpr_or_dbl_const_operand" ""))]
862  "reload_completed"
863  [(set (match_dup 2) (match_dup 3))
864   (set (match_dup 4) (match_dup 5))]
865  "
866{
867  d30v_split_double (operands[0], &operands[2], &operands[4]);
868  d30v_split_double (operands[1], &operands[3], &operands[5]);
869}")
870
871(define_expand "movcc"
872  [(set (match_operand:CC 0 "general_operand" "")
873	(match_operand:CC 1 "general_operand" ""))]
874  ""
875  "
876{
877  if (!reload_in_progress && !reload_completed
878      && GET_CODE (operands[0]) == MEM
879      && GET_CODE (operands[1]) == MEM)
880    operands[1] = copy_to_mode_reg (CCmode, operands[1]);
881}")
882
883(define_insn "*movcc_internal"
884  [(set (match_operand:CC 0 "move_output_operand" "=f,f,f,d,?d,f,d,*d,*d,*Q,*m")
885	(match_operand:CC 1 "move_input_operand" "f,O,N,b,f,d,dON,*Q,*m,*d,*d"))]
886  "!memory_operand (operands[0], CCmode) || !memory_operand (operands[1], CCmode)"
887  "@
888    orfg%: %0,%1,%1
889    andfg%: %0,%0,0
890    orfg%: %0,%0,1
891    #
892    mvfsys%: %0,%1
893    cmpne%: %0,%1,0
894    or%: %0,%.,%1
895    ldb%: %0,%M1
896    ldb%: %0,%M1
897    stb%: %1,%M0
898    stb%: %1,%M0"
899  [(set_attr "length" "4,4,4,8,4,4,4,4,8,4,8")
900   (set_attr "type" "either,either,either,multi,mu,mu,either,sload,lload,mu,long")])
901
902(define_split
903  [(set (match_operand:CC 0 "gpr_operand" "")
904	(match_operand:CC 1 "br_flag_operand" ""))]
905  "reload_completed"
906  [(set (match_dup 2)
907	(const_int 0))
908   (set (match_dup 2)
909	(if_then_else:SI (ne:CC (match_dup 1)
910				(const_int 0))
911			 (const_int 1)
912			 (match_dup 2)))]
913  "
914{
915  operands[2] = gen_lowpart (SImode, operands[0]);
916}")
917
918
919;; ::::::::::::::::::::
920;; ::
921;; :: Conversions
922;; ::
923;; ::::::::::::::::::::
924
925;; Signed conversions from a smaller integer to a larger integer
926(define_insn "extendqihi2"
927  [(set (match_operand:HI 0 "gpr_operand" "=d,d,d")
928	(sign_extend:HI (match_operand:QI 1 "gpr_or_memory_operand" "d,Q,m")))]
929  ""
930  "@
931    #
932    ldb%: %0,%M1
933    ldb%: %0,%M1"
934  [(set_attr "type" "multi,sload,lload")
935   (set_attr "length" "16,4,8")])
936
937(define_split
938  [(set (match_operand:HI 0 "gpr_operand" "")
939	(sign_extend:HI (match_operand:QI 1 "gpr_operand" "")))]
940  "reload_completed"
941  [(match_dup 2)
942   (match_dup 3)]
943  "
944{
945  rtx op0   = gen_lowpart (SImode, operands[0]);
946  rtx op1   = gen_lowpart (SImode, operands[1]);
947  rtx shift = gen_rtx (CONST_INT, VOIDmode, 24);
948
949  operands[2] = gen_ashlsi3 (op0, op1, shift);
950  operands[3] = gen_ashrsi3 (op0, op0, shift);
951}")
952
953(define_insn "extendqisi2"
954  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d")
955	(sign_extend:SI (match_operand:QI 1 "gpr_or_memory_operand" "d,Q,m")))]
956  ""
957  "@
958    #
959    ldb%: %0,%M1
960    ldb%: %0,%M1"
961  [(set_attr "type" "multi,sload,lload")
962   (set_attr "length" "16,4,8")])
963
964(define_split
965  [(set (match_operand:SI 0 "gpr_operand" "")
966	(sign_extend:SI (match_operand:QI 1 "gpr_operand" "")))]
967  "reload_completed"
968  [(match_dup 2)
969   (match_dup 3)]
970  "
971{
972  rtx op0   = gen_lowpart (SImode, operands[0]);
973  rtx op1   = gen_lowpart (SImode, operands[1]);
974  rtx shift = gen_rtx (CONST_INT, VOIDmode, 24);
975
976  operands[2] = gen_ashlsi3 (op0, op1, shift);
977  operands[3] = gen_ashrsi3 (op0, op0, shift);
978}")
979
980(define_insn "extendhisi2"
981  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d")
982	(sign_extend:SI (match_operand:HI 1 "gpr_or_memory_operand" "d,Q,m")))]
983  ""
984  "@
985    #
986    ldh%: %0,%M1
987    ldh%: %0,%M1"
988  [(set_attr "type" "multi,sload,lload")
989   (set_attr "length" "16,4,8")])
990
991(define_split
992  [(set (match_operand:SI 0 "gpr_operand" "")
993	(sign_extend:SI (match_operand:HI 1 "gpr_operand" "")))]
994  "reload_completed"
995  [(match_dup 2)
996   (match_dup 3)]
997  "
998{
999  rtx op0   = gen_lowpart (SImode, operands[0]);
1000  rtx op1   = gen_lowpart (SImode, operands[1]);
1001  rtx shift = gen_rtx (CONST_INT, VOIDmode, 16);
1002
1003  operands[2] = gen_ashlsi3 (op0, op1, shift);
1004  operands[3] = gen_ashrsi3 (op0, op0, shift);
1005}")
1006
1007(define_insn "extendqidi2"
1008  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1009	(sign_extend:DI (match_operand:QI 1 "gpr_or_memory_operand" "d,Q,m")))]
1010  ""
1011  "#"
1012  [(set_attr "length" "12,8,12")
1013   (set_attr "type" "multi")])
1014
1015(define_split
1016  [(set (match_operand:DI 0 "gpr_operand" "")
1017	(sign_extend:DI (match_operand:QI 1 "gpr_or_memory_operand" "")))]
1018  "reload_completed"
1019  [(set (match_dup 2) (sign_extend:SI (match_dup 1)))
1020   (set (match_dup 3) (ashiftrt:SI (match_dup 2) (const_int 31)))]
1021  "
1022{
1023  d30v_split_double (operands[0], &operands[3], &operands[2]);
1024}")
1025
1026(define_insn "extendhidi2"
1027  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1028	(sign_extend:DI (match_operand:HI 1 "gpr_or_memory_operand" "d,Q,m")))]
1029  ""
1030  "#"
1031  [(set_attr "length" "12,8,12")
1032   (set_attr "type" "multi")])
1033
1034(define_split
1035  [(set (match_operand:DI 0 "gpr_operand" "")
1036	(sign_extend:DI (match_operand:HI 1 "gpr_or_memory_operand" "")))]
1037  "reload_completed"
1038  [(set (match_dup 2) (sign_extend:SI (match_dup 1)))
1039   (set (match_dup 3) (ashiftrt:SI (match_dup 2) (const_int 31)))]
1040  "
1041{
1042  d30v_split_double (operands[0], &operands[3], &operands[2]);
1043}")
1044
1045(define_insn "extendsidi2"
1046  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1047	(sign_extend:DI (match_operand:SI 1 "gpr_or_memory_operand" "d,Q,m")))]
1048  ""
1049  "#"
1050  [(set_attr "length" "8,8,12")
1051   (set_attr "type" "multi")])
1052
1053(define_split
1054  [(set (match_operand:DI 0 "gpr_operand" "")
1055	(sign_extend:DI (match_operand:SI 1 "gpr_or_memory_operand" "")))]
1056  "reload_completed"
1057  [(set (match_dup 2) (match_dup 1))
1058   (set (match_dup 3) (ashiftrt:SI (match_dup 2) (const_int 31)))]
1059  "
1060{
1061  d30v_split_double (operands[0], &operands[3], &operands[2]);
1062}")
1063
1064;; Unsigned conversions from a smaller integer to a larger integer
1065
1066(define_insn "zero_extendqihi2"
1067  [(set (match_operand:HI 0 "gpr_operand" "=d,d,d")
1068	(zero_extend:HI (match_operand:QI 1 "gpr_or_memory_operand" "d,Q,m")))]
1069  ""
1070  "@
1071    and%: %0,%1,0xff
1072    ldbu%: %0,%M1
1073    ldbu%: %0,%M1"
1074  [(set_attr "length" "8,4,8")
1075   (set_attr "type" "long,sload,lload")])
1076
1077(define_insn "zero_extendqisi2"
1078  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d")
1079	(zero_extend:SI (match_operand:QI 1 "gpr_or_memory_operand" "d,Q,m")))]
1080  ""
1081  "@
1082    and%: %0,%1,0xff
1083    ldbu%: %0,%M1
1084    ldbu%: %0,%M1"
1085  [(set_attr "length" "8,4,8")
1086   (set_attr "type" "long,sload,lload")])
1087
1088(define_insn "zero_extendhisi2"
1089  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d")
1090	(zero_extend:SI (match_operand:HI 1 "gpr_or_memory_operand" "d,Q,m")))]
1091  ""
1092  "@
1093    and%: %0,%1,0xffff
1094    ldhu%: %0,%M1
1095    ldhu%: %0,%M1"
1096  [(set_attr "length" "8,4,8")
1097   (set_attr "type" "long,sload,lload")])
1098
1099(define_insn "zero_extendqidi2"
1100  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1101	(zero_extend:DI (match_operand:QI 1 "gpr_or_memory_operand" "d,Q,m")))]
1102  ""
1103  "#"
1104  [(set_attr "length" "12,8,12")
1105   (set_attr "type" "multi")])
1106
1107(define_split
1108  [(set (match_operand:DI 0 "gpr_operand" "")
1109	(zero_extend:DI (match_operand:QI 1 "gpr_or_memory_operand" "")))]
1110  "reload_completed"
1111  [(set (match_dup 2) (zero_extend:SI (match_dup 1)))
1112   (set (match_dup 3) (const_int 0))]
1113  "
1114{
1115  d30v_split_double (operands[0], &operands[3], &operands[2]);
1116}")
1117
1118(define_insn "zero_extendhidi2"
1119  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1120	(zero_extend:DI (match_operand:HI 1 "gpr_or_memory_operand" "d,Q,m")))]
1121  ""
1122  "#"
1123  [(set_attr "length" "8,8,12")
1124   (set_attr "type" "multi")])
1125
1126(define_split
1127  [(set (match_operand:DI 0 "gpr_operand" "")
1128	(zero_extend:DI (match_operand:HI 1 "gpr_or_memory_operand" "")))]
1129  "reload_completed"
1130  [(set (match_dup 2) (zero_extend:SI (match_dup 1)))
1131   (set (match_dup 3) (const_int 0))]
1132  "
1133{
1134  d30v_split_double (operands[0], &operands[3], &operands[2]);
1135}")
1136
1137(define_insn "zero_extendsidi2"
1138  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1139	(zero_extend:DI (match_operand:SI 1 "gpr_or_memory_operand" "d,Q,m")))]
1140  ""
1141  "#"
1142  [(set_attr "length" "8,8,12")
1143   (set_attr "type" "multi")])
1144
1145(define_split
1146  [(set (match_operand:DI 0 "gpr_operand" "")
1147	(zero_extend:DI (match_operand:SI 1 "gpr_or_memory_operand" "")))]
1148  "reload_completed"
1149  [(set (match_dup 2) (match_dup 1))
1150   (set (match_dup 3) (const_int 0))]
1151  "
1152{
1153  d30v_split_double (operands[0], &operands[3], &operands[2]);
1154}")
1155
1156
1157;; ::::::::::::::::::::
1158;; ::
1159;; :: 32 bit Integer arithmetic
1160;; ::
1161;; ::::::::::::::::::::
1162
1163;; Addition
1164(define_expand "addsi3"
1165  [(parallel [(set (match_operand:SI 0 "gpr_operand" "")
1166		   (plus:SI (match_operand:SI 1 "gpr_operand" "")
1167			    (match_operand:SI 2 "gpr_or_constant_operand" "")))
1168	      (clobber (match_dup 3))
1169	      (clobber (match_dup 4))
1170	      (clobber (match_dup 5))])]
1171  ""
1172  "
1173{
1174  operands[3] = gen_rtx (REG, CCmode, FLAG_CARRY);
1175  operands[4] = gen_rtx (REG, CCmode, FLAG_OVERFLOW);
1176  operands[5] = gen_rtx (REG, CCmode, FLAG_ACC_OVER);
1177}")
1178
1179(define_insn "*addsi3_internal"
1180  [(set (match_operand:SI 0 "gpr_operand" "=d,d")
1181	(plus:SI (match_operand:SI 1 "gpr_operand" "%d,d")
1182		 (match_operand:SI 2 "gpr_or_constant_operand" "dI,i")))
1183   (clobber (match_operand:CC 3 "flag_operand" "=f,f"))
1184   (clobber (match_operand:CC 4 "flag_operand" "=f,f"))
1185   (clobber (match_operand:CC 5 "flag_operand" "=f,f"))]
1186  ""
1187  "add%: %0,%1,%2"
1188  [(set_attr "length" "4,8")
1189   (set_attr "type" "either,long")])
1190
1191;; Subtraction
1192(define_expand "subsi3"
1193  [(parallel [(set (match_operand:SI 0 "gpr_operand" "")
1194		   (minus:SI (match_operand:SI 1 "reg_or_0_operand" "")
1195			     (match_operand:SI 2 "gpr_or_constant_operand" "")))
1196	      (clobber (match_dup 3))
1197	      (clobber (match_dup 4))
1198	      (clobber (match_dup 5))])]
1199  ""
1200  "
1201{
1202  operands[3] = gen_rtx (REG, CCmode, FLAG_CARRY);
1203  operands[4] = gen_rtx (REG, CCmode, FLAG_OVERFLOW);
1204  operands[5] = gen_rtx (REG, CCmode, FLAG_ACC_OVER);
1205}")
1206
1207(define_insn "*subsi3_internal"
1208  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d,d")
1209	(minus:SI (match_operand:SI 1 "reg_or_0_operand" "d,d,O,O")
1210		  (match_operand:SI 2 "gpr_or_constant_operand" "dI,i,dI,i")))
1211   (clobber (match_operand:CC 3 "flag_operand" "=f,f,f,f"))
1212   (clobber (match_operand:CC 4 "flag_operand" "=f,f,f,f"))
1213   (clobber (match_operand:CC 5 "flag_operand" "=f,f,f,f"))]
1214  ""
1215  "@
1216    sub%: %0,%1,%2
1217    sub%: %0,%1,%2
1218    sub%: %0,%.,%2
1219    sub%: %0,%.,%2"
1220  [(set_attr "length" "4,8,4,8")
1221   (set_attr "type" "either,long,either,long")])
1222
1223;; Multiplication (same size)
1224(define_insn "mulsi3"
1225  [(set (match_operand:SI 0 "gpr_operand" "=d")
1226	(mult:SI (match_operand:SI 1 "gpr_operand" "%d")
1227		 (match_operand:SI 2 "gpr_or_signed6_operand" "dI")))]
1228  ""
1229  "mul%: %0,%1,%2"
1230  [(set_attr "length" "4")
1231   (set_attr "type" "mul")])
1232
1233;; Signed multiplication producing 64 bit results from 32 bit inputs
1234(define_insn "mulsidi3"
1235  [(set (match_operand:DI 0 "accum_operand" "=a")
1236	(mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "d"))
1237		 (sign_extend:DI (match_operand:SI 2 "gpr_operand" "d"))))]
1238  ""
1239  "mulx%: %0,%1,%2"
1240  [(set_attr "length" "4")
1241   (set_attr "type" "mul")])
1242
1243(define_insn "*mulsidi3_const"
1244  [(set (match_operand:DI 0 "accum_operand" "=a")
1245	(mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "%d"))
1246		 (match_operand:DI 2 "signed6_operand" "I")))]
1247  ""
1248  "mulx%: %0,%1,%2"
1249  [(set_attr "length" "4")
1250   (set_attr "type" "mul")])
1251
1252;; Signed multiplication producing just the upper 32 bits from a 32x32->64
1253;; bit multiply.  We specifically allow any integer constant here so
1254;; allow division by constants to be done by multiplying by a large constant.
1255
1256(define_expand "smulsi3_highpart"
1257  [(set (match_dup 3)
1258	(mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" ""))
1259		 (match_operand:SI 2 "gpr_or_constant_operand" "")))
1260   (set (match_operand:SI 0 "gpr_operand" "")
1261	(truncate:SI (lshiftrt:DI (match_dup 3)
1262				  (const_int 32))))]
1263  ""
1264  "
1265{
1266  operands[3] = gen_reg_rtx (DImode);
1267
1268  if (GET_CODE (operands[2]) == CONST_INT &&
1269      !IN_RANGE_P (INTVAL (operands[2]), -32, 31))
1270    operands[2] = force_reg (SImode, operands[2]);
1271
1272  if (GET_CODE (operands[2]) == REG || GET_CODE (operands[2]) == SUBREG)
1273    operands[2] = gen_rtx (SIGN_EXTEND, DImode, operands[2]);
1274}")
1275
1276(define_insn "*di_highpart"
1277  [(set (match_operand:SI 0 "gpr_operand" "=d,d")
1278	(truncate:SI (lshiftrt:DI (match_operand:DI 1 "gpr_or_accum_operand" "e,a")
1279		      (const_int 32))))]
1280  ""
1281  "@
1282    or%: %0,%.,%U1
1283    mvfacc%: %0,%1,32"
1284  [(set_attr "length" "4")
1285   (set_attr "type" "either,iu")])
1286
1287;; Negation
1288(define_expand "negsi2"
1289  [(parallel [(set (match_operand:SI 0 "gpr_operand" "")
1290		   (neg:SI (match_operand:SI 1 "gpr_operand" "")))
1291	      (clobber (match_dup 2))
1292	      (clobber (match_dup 3))
1293	      (clobber (match_dup 4))])]
1294  ""
1295  "
1296{
1297  operands[2] = gen_rtx (REG, CCmode, FLAG_CARRY);
1298  operands[3] = gen_rtx (REG, CCmode, FLAG_OVERFLOW);
1299  operands[4] = gen_rtx (REG, CCmode, FLAG_ACC_OVER);
1300}")
1301
1302(define_insn "*negsi2_internal"
1303  [(set (match_operand:SI 0 "gpr_operand" "=d")
1304	(neg:SI (match_operand:SI 1 "gpr_operand" "d")))
1305   (clobber (match_operand:CC 2 "flag_operand" "=f"))
1306   (clobber (match_operand:CC 3 "flag_operand" "=f"))
1307   (clobber (match_operand:CC 4 "flag_operand" "=f"))]
1308  ""
1309  "sub%: %0,%.,%1"
1310  [(set_attr "length" "4")
1311   (set_attr "type" "either")])
1312
1313;; Absolute value
1314(define_insn "abssi2"
1315  [(set (match_operand:SI 0 "gpr_operand" "=d")
1316	(abs:SI (match_operand:SI 1 "gpr_operand" "d")))]
1317  ""
1318  "abs%: %0,%1"
1319  [(set_attr "length" "4")
1320   (set_attr "type" "either")])
1321
1322
1323;; ::::::::::::::::::::
1324;; ::
1325;; :: 64 bit Integer arithmetic
1326;; ::
1327;; ::::::::::::::::::::
1328
1329;; Addition
1330(define_expand "adddi3"
1331  [(parallel [(set (match_operand:DI 0 "gpr_operand" "")
1332		   (plus:DI (match_operand:DI 1 "gpr_operand" "")
1333			    (match_operand:DI 2 "gpr_or_constant_operand" "")))
1334	      (clobber (match_dup 3))
1335	      (clobber (match_dup 4))
1336	      (clobber (match_dup 5))])]
1337  ""
1338  "
1339{
1340  operands[3] = gen_rtx (REG, CCmode, FLAG_CARRY);
1341  operands[4] = gen_rtx (REG, CCmode, FLAG_OVERFLOW);
1342  operands[5] = gen_rtx (REG, CCmode, FLAG_ACC_OVER);
1343}")
1344
1345(define_insn "*adddi3_internal"
1346  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e,e")
1347	(plus:DI (match_operand:DI 1 "gpr_operand" "%e,e,e,e")
1348		 (match_operand:DI 2 "gpr_or_constant_operand" "I,i,e,F")))
1349   (clobber (match_operand:CC 3 "flag_operand" "=f,f,f,f"))
1350   (clobber (match_operand:CC 4 "flag_operand" "=f,f,f,f"))
1351   (clobber (match_operand:CC 5 "flag_operand" "=f,f,f,f"))]
1352  ""
1353  "#"
1354  [(set_attr "length" "8,12,8,16")
1355   (set_attr "type" "multi")])
1356
1357(define_insn "addsi3_set_carry"
1358  [(set (match_operand:SI 0 "gpr_operand" "=d,d")
1359	(plus:SI (match_operand:SI 1 "gpr_operand" "%d,d")
1360		 (match_operand:SI 2 "gpr_or_constant_operand" "dI,i")))
1361   (set (match_operand:CC 3 "carry_operand" "=f,f")
1362	(unspec:CC [(match_dup 1)
1363		 (match_dup 2)] 1))
1364   (clobber (match_operand:CC 4 "flag_operand" "=f,f"))
1365   (clobber (match_operand:CC 5 "flag_operand" "=f,f"))]
1366  ""
1367  "add%: %0,%1,%2"
1368  [(set_attr "length" "4,8")
1369   (set_attr "type" "scarry,lcarry")])
1370
1371(define_insn "addsi3_use_carry"
1372  [(set (match_operand:SI 0 "gpr_operand" "=d,d")
1373	(unspec:SI [(match_operand:SI 1 "gpr_operand" "%d,d")
1374		 (match_operand:SI 2 "gpr_or_constant_operand" "dI,i")
1375		 (match_operand:CC 3 "carry_operand" "+f,f")] 2))
1376   (clobber (match_operand:CC 4 "flag_operand" "=f,f"))
1377   (clobber (match_operand:CC 5 "flag_operand" "=f,f"))]
1378  ""
1379  "addc%: %0,%1,%2"
1380  [(set_attr "length" "4,8")
1381   (set_attr "type" "scarry,lcarry")])
1382
1383(define_split
1384  [(set (match_operand:DI 0 "gpr_operand" "")
1385	(plus:DI (match_operand:DI 1 "gpr_operand" "")
1386		 (match_operand:DI 2 "gpr_or_constant_operand" "")))
1387   (clobber (match_operand:CC 3 "flag_operand" ""))
1388   (clobber (match_operand:CC 4 "flag_operand" ""))
1389   (clobber (match_operand:CC 5 "flag_operand" ""))]
1390  "reload_completed"
1391  [(match_dup 6)
1392   (match_dup 7)]
1393  "
1394{
1395  rtx high[3];
1396  rtx low[3];
1397
1398  d30v_split_double (operands[0], &high[0], &low[0]);
1399  d30v_split_double (operands[1], &high[1], &low[1]);
1400  d30v_split_double (operands[2], &high[2], &low[2]);
1401
1402  operands[6] = gen_addsi3_set_carry (low[0], low[1], low[2], operands[3],
1403				      operands[4], operands[5]);
1404
1405  operands[7] = gen_addsi3_use_carry (high[0], high[1], high[2], operands[3],
1406				      operands[4], operands[5]);
1407}")
1408
1409;; Subtraction
1410(define_expand "subdi3"
1411  [(parallel [(set (match_operand:DI 0 "gpr_operand" "")
1412		   (minus:DI (match_operand:DI 1 "gpr_operand" "")
1413			     (match_operand:DI 2 "gpr_or_constant_operand" "")))
1414	      (clobber (match_dup 3))
1415	      (clobber (match_dup 4))
1416	      (clobber (match_dup 5))])]
1417  ""
1418  "
1419{
1420  operands[3] = gen_rtx (REG, CCmode, FLAG_CARRY);
1421  operands[4] = gen_rtx (REG, CCmode, FLAG_OVERFLOW);
1422  operands[5] = gen_rtx (REG, CCmode, FLAG_ACC_OVER);
1423}")
1424
1425(define_insn "*subdi3_internal"
1426  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e,e")
1427	(minus:DI (match_operand:DI 1 "gpr_operand" "e,e,e,e")
1428		  (match_operand:DI 2 "gpr_or_constant_operand" "I,i,e,F")))
1429   (clobber (match_operand:CC 3 "flag_operand" "=f,f,f,f"))
1430   (clobber (match_operand:CC 4 "flag_operand" "=f,f,f,f"))
1431   (clobber (match_operand:CC 5 "flag_operand" "=f,f,f,f"))]
1432  ""
1433  "#"
1434  [(set_attr "length" "8,12,8,16")
1435   (set_attr "type" "multi")])
1436
1437(define_insn "subsi3_set_carry"
1438  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d,d")
1439	(minus:SI (match_operand:SI 1 "reg_or_0_operand" "d,d,O,O")
1440		  (match_operand:SI 2 "gpr_or_constant_operand" "dI,i,dI,i")))
1441   (set (match_operand:CC 3 "carry_operand" "=f,f,f,f")
1442	(unspec:CC [(match_dup 1)
1443		    (match_dup 2)] 3))
1444   (clobber (match_operand:CC 4 "flag_operand" "=f,f,f,f"))
1445   (clobber (match_operand:CC 5 "flag_operand" "=f,f,f,f"))]
1446  ""
1447  "@
1448    sub%: %0,%1,%2
1449    sub%: %0,%1,%2
1450    sub%: %0,%.,%2
1451    sub%: %0,%.,%2"
1452  [(set_attr "length" "4,8,4,8")
1453   (set_attr "type" "scarry,lcarry,scarry,lcarry")])
1454
1455(define_insn "subsi3_use_carry"
1456  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d,d")
1457	(unspec:SI [(match_operand:SI 1 "reg_or_0_operand" "d,d,O,O")
1458		    (match_operand:SI 2 "gpr_operand" "dI,i,dI,i")
1459		    (match_operand:CC 3 "carry_operand" "+f,f,f,f")] 4))
1460   (clobber (match_operand:CC 4 "flag_operand" "=f,f,f,f"))
1461   (clobber (match_operand:CC 5 "flag_operand" "=f,f,f,f"))]
1462  ""
1463  "@
1464    subb%: %0,%1,%2
1465    subb%: %0,%1,%2
1466    subb%: %0,%.,%2
1467    subb%: %0,%.,%2"
1468  [(set_attr "length" "4,8,4,8")
1469   (set_attr "type" "scarry,lcarry,scarry,lcarry")])
1470
1471(define_split
1472  [(set (match_operand:DI 0 "gpr_operand" "")
1473	(minus:DI (match_operand:DI 1 "gpr_operand" "")
1474		  (match_operand:DI 2 "gpr_or_constant_operand" "")))
1475   (clobber (match_operand:CC 3 "flag_operand" ""))
1476   (clobber (match_operand:CC 4 "flag_operand" ""))
1477   (clobber (match_operand:CC 5 "flag_operand" ""))]
1478  "reload_completed"
1479  [(match_dup 6)
1480   (match_dup 7)]
1481  "
1482{
1483  rtx high[3];
1484  rtx low[3];
1485
1486  d30v_split_double (operands[0], &high[0], &low[0]);
1487  d30v_split_double (operands[1], &high[1], &low[1]);
1488  d30v_split_double (operands[2], &high[2], &low[2]);
1489
1490  operands[6] = gen_subsi3_set_carry (low[0], low[1], low[2], operands[3],
1491				      operands[4], operands[5]);
1492
1493  operands[7] = gen_subsi3_use_carry (high[0], high[1], high[2], operands[3],
1494				      operands[4], operands[5]);
1495}")
1496
1497;; Negation
1498(define_expand "negdi2"
1499  [(parallel [(set (match_operand:DI 0 "gpr_operand" "")
1500		   (neg:DI (match_operand:DI 1 "gpr_operand" "")))
1501	      (clobber (match_dup 2))
1502	      (clobber (match_dup 3))
1503	      (clobber (match_dup 4))])]
1504  ""
1505  "
1506{
1507  operands[2] = gen_rtx (REG, CCmode, FLAG_CARRY);
1508  operands[3] = gen_rtx (REG, CCmode, FLAG_OVERFLOW);
1509  operands[4] = gen_rtx (REG, CCmode, FLAG_ACC_OVER);
1510}")
1511
1512(define_insn "*negdi2_internal"
1513  [(set (match_operand:DI 0 "gpr_operand" "=e")
1514	(neg:DI (match_operand:DI 1 "gpr_operand" "e")))
1515   (clobber (match_operand:CC 2 "flag_operand" "=f"))
1516   (clobber (match_operand:CC 3 "flag_operand" "=f"))
1517   (clobber (match_operand:CC 4 "flag_operand" "=f"))]
1518  ""
1519  "#"
1520  [(set_attr "length" "8")
1521   (set_attr "type" "multi")])
1522
1523(define_split
1524  [(set (match_operand:DI 0 "gpr_operand" "=e")
1525	(neg:DI (match_operand:DI 1 "gpr_operand" "e")))
1526   (clobber (match_operand:CC 2 "flag_operand" "=f"))
1527   (clobber (match_operand:CC 3 "flag_operand" "=f"))
1528   (clobber (match_operand:CC 4 "flag_operand" "=f"))]
1529  "reload_completed"
1530  [(match_dup 5)
1531   (match_dup 6)]
1532  "
1533{
1534  rtx high[2];
1535  rtx low[2];
1536  rtx r0 = const0_rtx;
1537
1538  d30v_split_double (operands[0], &high[0], &low[0]);
1539  d30v_split_double (operands[1], &high[1], &low[1]);
1540
1541  operands[5] = gen_subsi3_set_carry (low[0], r0, low[1], operands[2],
1542				      operands[3], operands[4]);
1543
1544  operands[6] = gen_subsi3_use_carry (high[0], r0, high[1], operands[2],
1545				      operands[3], operands[4]);
1546}")
1547
1548
1549;; ::::::::::::::::::::
1550;; ::
1551;; :: 32 bit Integer Shifts and Rotates
1552;; ::
1553;; ::::::::::::::::::::
1554
1555;; Arithmetic Shift Left (negate the shift value and use shift right)
1556(define_expand "ashlsi3"
1557  [(set (match_operand:SI 0 "gpr_operand" "")
1558	(ashift:SI (match_operand:SI 1 "gpr_operand" "")
1559		   (match_operand:SI 2 "gpr_or_unsigned5_operand" "")))]
1560  ""
1561  "
1562{
1563  if (GET_CODE (operands[2]) != CONST_INT)
1564    operands[2] = gen_rtx (NEG, SImode, negate_rtx (SImode, operands[2]));
1565}")
1566
1567(define_insn "*ashlsi3_constant"
1568  [(set (match_operand:SI 0 "gpr_operand" "=d")
1569	(ashift:SI (match_operand:SI 1 "gpr_operand" "d")
1570		   (match_operand:SI 2 "unsigned5_operand" "J")))]
1571  ""
1572  "sra%: %0,%1,%n2"
1573  [(set_attr "length" "4")
1574   (set_attr "type" "either")])
1575
1576(define_insn "*ashlsi3_register"
1577  [(set (match_operand:SI 0 "gpr_operand" "=d")
1578	(ashift:SI (match_operand:SI 1 "gpr_operand" "d")
1579		   (neg:SI (match_operand:SI 2 "gpr_operand" "d"))))]
1580  ""
1581  "sra%: %0,%1,%2"
1582  [(set_attr "length" "4")
1583   (set_attr "type" "either")])
1584
1585;; Arithmetic Shift Right
1586(define_insn "ashrsi3"
1587  [(set (match_operand:SI 0 "gpr_operand" "=d")
1588	(ashiftrt:SI (match_operand:SI 1 "gpr_operand" "d")
1589		     (match_operand:SI 2 "gpr_or_unsigned5_operand" "dJ")))]
1590  ""
1591  "sra%: %0,%1,%2"
1592  [(set_attr "length" "4")])
1593
1594;; Logical Shift Right
1595(define_insn "lshrsi3"
1596  [(set (match_operand:SI 0 "gpr_operand" "=d")
1597	(lshiftrt:SI (match_operand:SI 1 "gpr_operand" "d")
1598		     (match_operand:SI 2 "gpr_or_unsigned5_operand" "dJ")))]
1599  ""
1600  "srl%: %0,%1,%2"
1601  [(set_attr "length" "4")
1602   (set_attr "type" "either")])
1603
1604;; Rotate Left (negate the shift value and use rotate right)
1605(define_expand "rotlsi3"
1606  [(set (match_operand:SI 0 "gpr_operand" "")
1607	(rotate:SI (match_operand:SI 1 "gpr_operand" "")
1608		   (match_operand:SI 2 "gpr_or_unsigned5_operand" "")))]
1609  ""
1610  "
1611{
1612  if (GET_CODE (operands[2]) != CONST_INT)
1613    operands[2] = gen_rtx (NEG, SImode, negate_rtx (SImode, operands[2]));
1614}")
1615
1616(define_insn "*rotlsi3_constant"
1617  [(set (match_operand:SI 0 "gpr_operand" "=d")
1618	(rotate:SI (match_operand:SI 1 "gpr_operand" "d")
1619		   (match_operand:SI 2 "unsigned5_operand" "J")))]
1620  ""
1621  "rot%: %0,%1,%n2"
1622  [(set_attr "length" "4")
1623   (set_attr "type" "either")])
1624
1625(define_insn "*rotlsi3_register"
1626  [(set (match_operand:SI 0 "gpr_operand" "=d")
1627	(rotate:SI (match_operand:SI 1 "gpr_operand" "d")
1628		   (neg:SI (match_operand:SI 2 "gpr_operand" "d"))))]
1629  ""
1630  "rot%: %0,%1,%2"
1631  [(set_attr "length" "4")
1632   (set_attr "type" "either")])
1633
1634;; Rotate Right
1635(define_insn "rotrsi3"
1636  [(set (match_operand:SI 0 "gpr_operand" "=d")
1637	(rotatert:SI (match_operand:SI 1 "gpr_operand" "d")
1638		     (match_operand:SI 2 "gpr_or_unsigned5_operand" "dJ")))]
1639  ""
1640  "rot%: %0,%1,%2"
1641  [(set_attr "length" "4")
1642   (set_attr "type" "either")])
1643
1644
1645;; ::::::::::::::::::::
1646;; ::
1647;; :: 64 bit Integer Shifts and Rotates
1648;; ::
1649;; ::::::::::::::::::::
1650
1651;; Arithmetic Shift Left
1652(define_expand "ashldi3"
1653  [(parallel [(set (match_operand:DI 0 "gpr_operand" "")
1654		   (ashift:DI (match_operand:DI 1 "gpr_operand" "")
1655			      (match_operand:SI 2 "gpr_or_unsigned6_operand" "")))
1656	      (clobber (match_scratch:CC 3 ""))])]
1657  ""
1658  "
1659{
1660  if (GET_CODE (operands[2]) == CONST_INT)
1661    {
1662      if (IN_RANGE_P (INTVAL (operands[2]), 0, 63))
1663	{
1664	  emit_insn (gen_ashldi3_constant (operands[0], operands[1], operands[2]));
1665	  DONE;
1666	}
1667      else
1668	operands[2] = copy_to_mode_reg (SImode, operands[2]);
1669    }
1670
1671  operands[2] = gen_rtx (NEG, SImode, negate_rtx (SImode, operands[2]));
1672}")
1673
1674(define_insn "ashldi3_constant"
1675  [(set (match_operand:DI 0 "gpr_operand" "=e,e")
1676	(ashift:DI (match_operand:DI 1 "gpr_operand" "0,e")
1677		   (match_operand:SI 2 "unsigned6_operand" "J,P")))]
1678  ""
1679  "@
1680    src%: %U0,%L0,%n2\;sra%: %L0,%L0,%n2
1681    sra%: %U0,%L1,%s2\;or%: %L0,%.,0"
1682  [(set_attr "length" "8")
1683   (set_attr "type" "multi")])
1684
1685(define_insn "*ashldi3_register"
1686  [(set (match_operand:DI 0 "gpr_operand" "=e")
1687	(ashift:DI (match_operand:DI 1 "gpr_operand" "0")
1688		   (neg:SI (match_operand:SI 2 "gpr_operand" "d"))))
1689   (clobber (match_scratch:CC 3 "=b"))]
1690  ""
1691  "cmpge %3,%2,-31\;src%T3 %U0,%L0,%2\;sra%T3 %L0,%L0,%2\;sub%F3 %U0,%2,-32\;sra%F3 %U0,%L0,%U0\;or%F3 %L0,%.,0"
1692  [(set_attr "length" "32")
1693   (set_attr "type" "multi")
1694   ;; Not strictly true, since we ought to be able to combine conditions,
1695   (set_attr "predicable" "no")])
1696
1697;; Arithmetic Shift Right
1698(define_insn "ashrdi3"
1699  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1700	(ashiftrt:DI (match_operand:DI 1 "gpr_operand" "0,e,0")
1701		     (match_operand:SI 2 "gpr_or_unsigned6_operand" "J,P,d")))
1702   (clobber (match_scratch:CC 3 "=X,X,b"))]
1703  ""
1704  "@
1705    src %L0,%U0,%2\;sra %U0,%U0,%2
1706    sra %L0,%U1,%S2\;sra %U0,%L0,31
1707    cmple %3,%2,31\;src%T3 %L0,%U0,%2\;sra%T3 %U0,%U0,%2\;add%F3 %L0,%2,-32\;sra%F3 %L0,%U0,%L0\;sra%F3 %U0,%U0,31"
1708  [(set_attr "length" "8,8,28")
1709   (set_attr "type" "multi")
1710   ;; Not strictly true, since we ought to be able to combine conditions,
1711   (set_attr "predicable" "no")])
1712
1713;; Logical Shift Right
1714
1715(define_insn "lshrdi3"
1716  [(set (match_operand:DI 0 "gpr_operand" "=e,e,e")
1717	(lshiftrt:DI (match_operand:DI 1 "gpr_operand" "0,e,0")
1718		     (match_operand:SI 2 "gpr_or_unsigned6_operand" "J,P,d")))
1719   (clobber (match_scratch:CC 3 "=X,X,b"))]
1720  ""
1721  "@
1722    src %L0,%U0,%2\;srl %U0,%U0,%2
1723    srl %L0,%U1,%S2\;or %U0,%.,0
1724    cmple %3,%2,31\;src%T3 %L0,%U0,%2\;srl%T3 %U0,%U0,%2\;add%F3 %L0,%2,-32\;srl%F3 %L0,%U0,%L0\;or%F3 %U0,%.,0"
1725  [(set_attr "length" "8,8,28")
1726   (set_attr "type" "multi")
1727   ;; Not strictly true, since we ought to be able to combine conditions,
1728   (set_attr "predicable" "no")])
1729
1730
1731;; ::::::::::::::::::::
1732;; ::
1733;; :: 32 Bit Integer Logical operations
1734;; ::
1735;; ::::::::::::::::::::
1736
1737;; Logical AND, 32 bit integers
1738
1739(define_insn "andsi3"
1740  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d,d")
1741	(and:SI (match_operand:SI 1 "gpr_operand" "%d,d,d,d")
1742		(match_operand:SI 2 "gpr_or_constant_operand" "L,I,i,d")))]
1743  ""
1744  "@
1745    bclr%: %0,%1,%B2
1746    and%: %0,%1,%2
1747    and%: %0,%1,%2
1748    and%: %0,%1,%2"
1749  [(set_attr "length" "4,4,8,4")
1750   (set_attr "type" "either,either,long,either")])
1751
1752;; Inclusive OR, 32 bit integers
1753
1754(define_insn "iorsi3"
1755  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d,d")
1756	(ior:SI (match_operand:SI 1 "gpr_operand" "%d,d,d,d")
1757		(match_operand:SI 2 "gpr_or_constant_operand" "K,I,i,d")))]
1758  ""
1759  "@
1760    bset%: %0,%1,%B2
1761    or%: %0,%1,%2
1762    or%: %0,%1,%2
1763    or%: %0,%1,%2"
1764  [(set_attr "length" "4,4,8,4")
1765   (set_attr "type" "either,either,long,either")])
1766
1767;; Exclusive OR, 32 bit integers
1768
1769(define_insn "*xorsi3_constant"
1770  [(set (match_operand:SI 0 "gpr_operand" "=d,d,d,d")
1771	(xor:SI (match_operand:SI 1 "gpr_operand" "%d,d,d,d")
1772		(match_operand:SI 2 "gpr_or_constant_operand" "K,I,i,d")))]
1773  ""
1774  "@
1775    bnot%: %0,%1,%B2
1776    xor%: %0,%1,%2
1777    xor%: %0,%1,%2
1778    xor%: %0,%1,%2"
1779  [(set_attr "length" "4,4,8,4")
1780   (set_attr "type" "either,either,long,either")])
1781
1782;; One's complement, 32 bit integers
1783(define_insn "one_cmplsi2"
1784  [(set (match_operand:SI 0 "gpr_operand" "=d")
1785	(not:SI (match_operand:SI 1 "gpr_operand" "d")))]
1786  ""
1787  "not%: %0,%1"
1788  [(set_attr "length" "4")
1789   (set_attr "type" "either")])
1790
1791
1792;; ::::::::::::::::::::
1793;; ::
1794;; :: 64 Bit Integer Logical operations
1795;; ::
1796;; ::::::::::::::::::::
1797
1798;; Logical AND, 64 bit integers
1799(define_insn "anddi3"
1800  [(set (match_operand:DI 0 "gpr_operand" "=e,e,&e,e,e,e")
1801	(and:DI (match_operand:DI 1 "gpr_operand" "%e,0,e,e,e,e")
1802		(match_operand:DI 2 "gpr_or_dbl_const_operand" "0,e,e,I,i,F")))]
1803  ""
1804  "#"
1805  [(set_attr "length" "8,8,8,8,12,16")
1806   (set_attr "type" "multi")])
1807
1808(define_split
1809  [(set (match_operand:DI 0 "gpr_operand" "")
1810	(and:DI (match_operand:DI 1 "gpr_operand" "")
1811		(match_operand:DI 2 "gpr_or_dbl_const_operand" "")))]
1812  "reload_completed"
1813  [(set (match_dup 3) (and:SI (match_dup 4) (match_dup 5)))
1814   (set (match_dup 6) (and:SI (match_dup 7) (match_dup 8)))]
1815  "
1816{
1817  d30v_split_double (operands[0], &operands[3], &operands[6]);
1818  d30v_split_double (operands[1], &operands[4], &operands[7]);
1819  d30v_split_double (operands[2], &operands[5], &operands[8]);
1820}")
1821
1822;; Includive OR, 64 bit integers
1823(define_insn "iordi3"
1824  [(set (match_operand:DI 0 "gpr_operand" "=e,e,&e,e,e,e")
1825	(ior:DI (match_operand:DI 1 "gpr_operand" "%e,0,e,e,e,e")
1826		(match_operand:DI 2 "gpr_or_dbl_const_operand" "0,e,e,I,i,F")))]
1827  ""
1828  "#"
1829  [(set_attr "length" "8,8,8,8,12,16")
1830   (set_attr "type" "multi")])
1831
1832(define_split
1833  [(set (match_operand:DI 0 "gpr_operand" "")
1834	(ior:DI (match_operand:DI 1 "gpr_operand" "")
1835		(match_operand:DI 2 "gpr_or_dbl_const_operand" "")))]
1836  "reload_completed"
1837  [(set (match_dup 3) (ior:SI (match_dup 4) (match_dup 5)))
1838   (set (match_dup 6) (ior:SI (match_dup 7) (match_dup 8)))]
1839  "
1840{
1841  d30v_split_double (operands[0], &operands[3], &operands[6]);
1842  d30v_split_double (operands[1], &operands[4], &operands[7]);
1843  d30v_split_double (operands[2], &operands[5], &operands[8]);
1844}")
1845
1846;; Excludive OR, 64 bit integers
1847(define_insn "xordi3"
1848  [(set (match_operand:DI 0 "gpr_operand" "=e,e,&e,e,e,e")
1849	(xor:DI (match_operand:DI 1 "gpr_operand" "%e,0,e,e,e,e")
1850		(match_operand:DI 2 "gpr_or_dbl_const_operand" "0,e,e,I,i,F")))]
1851  ""
1852  "#"
1853  [(set_attr "length" "8,8,8,8,12,16")
1854   (set_attr "type" "multi")])
1855
1856(define_split
1857  [(set (match_operand:DI 0 "gpr_operand" "")
1858	(xor:DI (match_operand:DI 1 "gpr_operand" "")
1859		(match_operand:DI 2 "gpr_or_dbl_const_operand" "")))]
1860  "reload_completed"
1861  [(set (match_dup 3) (xor:SI (match_dup 4) (match_dup 5)))
1862   (set (match_dup 6) (xor:SI (match_dup 7) (match_dup 8)))]
1863  "
1864{
1865  d30v_split_double (operands[0], &operands[3], &operands[6]);
1866  d30v_split_double (operands[1], &operands[4], &operands[7]);
1867  d30v_split_double (operands[2], &operands[5], &operands[8]);
1868}")
1869
1870;; One's complement, 64 bit integers
1871(define_insn "one_cmpldi2"
1872  [(set (match_operand:DI 0 "gpr_operand" "=e,&e")
1873	(not:DI (match_operand:DI 1 "gpr_operand" "0,e")))]
1874  ""
1875  "#"
1876  [(set_attr "length" "8")
1877   (set_attr "type" "multi")])
1878
1879(define_split
1880  [(set (match_operand:DI 0 "gpr_operand" "")
1881	(not:DI (match_operand:DI 1 "gpr_operand" "")))]
1882  "reload_completed"
1883  [(set (match_dup 3) (not:SI (match_dup 4)))
1884   (set (match_dup 5) (not:SI (match_dup 6)))]
1885  "
1886{
1887  d30v_split_double (operands[0], &operands[3], &operands[5]);
1888  d30v_split_double (operands[1], &operands[4], &operands[6]);
1889}")
1890
1891
1892;; ::::::::::::::::::::
1893;; ::
1894;; :: Multiply and accumulate instructions
1895;; ::
1896;; ::::::::::::::::::::
1897
1898(define_insn "*mac_reg"
1899  [(set (match_operand:DI 0 "accum_operand" "+a")
1900	(plus:DI (match_dup 0)
1901		 (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "%d"))
1902			  (sign_extend:DI (match_operand:SI 2 "gpr_operand" "d")))))]
1903  ""
1904  "mac%A0%: %.,%1,%2"
1905  [(set_attr "length" "4")
1906   (set_attr "type" "mul")])
1907
1908(define_insn "*mac_const"
1909  [(set (match_operand:DI 0 "accum_operand" "+a")
1910	(plus:DI (match_dup 0)
1911		 (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "%d"))
1912			  (match_operand:DI 2 "signed6_operand" "I"))))]
1913  ""
1914  "mac%A0%: %.,%1,%2"
1915  [(set_attr "length" "4")
1916   (set_attr "type" "mul")])
1917
1918(define_insn "*macs_reg"
1919  [(set (match_operand:DI 0 "accum_operand" "+a")
1920	(plus:DI (match_dup 0)
1921		 (ashift:DI (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "%d"))
1922				     (sign_extend:DI (match_operand:SI 2 "gpr_operand" "d")))
1923			    (const_int 1))))]
1924  ""
1925  "macs%A0%: %.,%1,%2"
1926  [(set_attr "length" "4")
1927   (set_attr "type" "mul")])
1928
1929(define_insn "*macs_const"
1930  [(set (match_operand:DI 0 "accum_operand" "+a")
1931	(plus:DI (match_dup 0)
1932		 (ashift:DI (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "%d"))
1933				     (match_operand:DI 2 "signed6_operand" "I"))
1934			    (const_int 1))))]
1935  ""
1936  "macs%A0%: %.,%1,%2"
1937  [(set_attr "length" "4")
1938   (set_attr "type" "mul")])
1939
1940(define_insn "*msub_reg"
1941  [(set (match_operand:DI 0 "accum_operand" "+a")
1942	(minus:DI (match_dup 0)
1943		  (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "d"))
1944			   (sign_extend:DI (match_operand:SI 2 "gpr_operand" "d")))))]
1945  ""
1946  "msub%A0%: %.,%1,%2"
1947  [(set_attr "length" "4")
1948   (set_attr "type" "mul")])
1949
1950(define_insn "*msub_const"
1951  [(set (match_operand:DI 0 "accum_operand" "+a")
1952	(minus:DI (match_dup 0)
1953		  (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "d"))
1954			   (match_operand:DI 2 "signed6_operand" "I"))))]
1955  ""
1956  "msub%A0%: %.,%1,%2"
1957  [(set_attr "length" "4")
1958   (set_attr "type" "mul")])
1959
1960(define_insn "*msubs_reg"
1961  [(set (match_operand:DI 0 "accum_operand" "+a")
1962	(minus:DI (match_dup 0)
1963		  (ashift:DI (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "d"))
1964				      (sign_extend:DI (match_operand:SI 2 "gpr_operand" "d")))
1965			     (const_int 1))))]
1966  ""
1967  "msubs%A0%: %.,%1,%2"
1968  [(set_attr "length" "4")
1969   (set_attr "type" "mul")])
1970
1971(define_insn "*msubs_const"
1972  [(set (match_operand:DI 0 "accum_operand" "+a")
1973	(minus:DI (match_dup 0)
1974		  (ashift:DI (mult:DI (sign_extend:DI (match_operand:SI 1 "gpr_operand" "d"))
1975				      (match_operand:DI 2 "signed6_operand" "I"))
1976			     (const_int 1))))]
1977  ""
1978  "msubs%A0%: %.,%1,%2"
1979  [(set_attr "length" "4")
1980   (set_attr "type" "mul")])
1981
1982
1983;; ::::::::::::::::::::
1984;; ::
1985;; :: Comparisons
1986;; ::
1987;; ::::::::::::::::::::
1988
1989;; Note, we store the operands in the comparison insns, and use them later
1990;; when generating the branch or scc operation.
1991
1992;; First the routines called by the machine independent part of the compiler
1993(define_expand "cmpsi"
1994  [(set (cc0)
1995        (compare (match_operand:SI 0 "gpr_operand" "")
1996  		 (match_operand:SI 1 "gpr_or_constant_operand" "")))]
1997  ""
1998  "
1999{
2000  d30v_compare_op0 = operands[0];
2001  d30v_compare_op1 = operands[1];
2002  DONE;
2003}")
2004
2005(define_expand "cmpdi"
2006  [(set (cc0)
2007        (compare (match_operand:DI 0 "gpr_operand" "")
2008  		 (match_operand:DI 1 "nonmemory_operand" "")))]
2009  ""
2010  "
2011{
2012  d30v_compare_op0 = operands[0];
2013  d30v_compare_op1 = operands[1];
2014  DONE;
2015}")
2016
2017;; Now, the actual comparisons, generated by the branch and/or scc operations
2018
2019;; 32 bit integer tests
2020(define_insn "*srelational"
2021  [(set (match_operand:CC 0 "flag_operand" "=f,f")
2022	(match_operator:CC 1 "srelational_si_operator"
2023			   [(match_operand:SI 2 "gpr_operand" "d,d")
2024			    (match_operand:SI 3 "gpr_or_constant_operand" "dI,i")]))]
2025  ""
2026  "%R1%: %0,%2,%3"
2027  [(set_attr "length" "4,8")
2028   (set_attr "type" "scmp,lcmp")])
2029
2030(define_insn "*urelational"
2031  [(set (match_operand:CC 0 "flag_operand" "=f,f")
2032	(match_operator:CC 1 "urelational_si_operator"
2033			   [(match_operand:SI 2 "gpr_operand" "d,d")
2034			    (match_operand:SI 3 "gpr_or_constant_operand" "dJP,i")]))]
2035  ""
2036  "%R1%: %0,%2,%3"
2037  [(set_attr "length" "4,8")
2038   (set_attr "type" "scmp,lcmp")])
2039
2040;; 64 bit integer tests
2041(define_insn "*eqdi_internal"
2042  [(set (match_operand:CC 0 "br_flag_operand" "=b,b,b")
2043	(eq:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2044	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "eI,i,F")))]
2045  ""
2046  "#"
2047  [(set_attr "length" "8,12,16")
2048   (set_attr "type" "multi")])
2049
2050(define_split
2051  [(set (match_operand:CC 0 "br_flag_operand" "")
2052	(eq:CC (match_operand:DI 1 "gpr_operand" "")
2053	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "")))]
2054  "reload_completed"
2055  [(set (match_dup 0)
2056	(eq:CC (match_dup 3)
2057	       (match_dup 4)))
2058   (cond_exec
2059    (eq:CC (match_dup 0)
2060	   (const_int 0))
2061    (set (match_dup 0)
2062	 (eq:CC (match_dup 5)
2063		(match_dup 6))))]
2064  "
2065{
2066  d30v_split_double (operands[1], &operands[3], &operands[5]);
2067  d30v_split_double (operands[2], &operands[4], &operands[6]);
2068}")
2069
2070(define_insn "*nedi_internal"
2071  [(set (match_operand:CC 0 "br_flag_operand" "=b,b,b")
2072	(ne:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2073	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "eI,i,F")))]
2074  ""
2075  "#"
2076  [(set_attr "length" "8,12,16")
2077   (set_attr "type" "multi")])
2078
2079(define_split
2080  [(set (match_operand:CC 0 "br_flag_operand" "")
2081	(ne:CC (match_operand:DI 1 "gpr_operand" "")
2082	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "")))]
2083  "reload_completed"
2084  [(set (match_dup 0)
2085	(ne:CC (match_dup 3)
2086	       (match_dup 4)))
2087   (cond_exec
2088    (ne:CC (match_dup 0)
2089	   (const_int 0))
2090    (set (match_dup 0)
2091	 (ne:CC (match_dup 5)
2092		(match_dup 6))))]
2093  "
2094{
2095  d30v_split_double (operands[1], &operands[3], &operands[5]);
2096  d30v_split_double (operands[2], &operands[4], &operands[6]);
2097}")
2098
2099(define_insn "*ltdi_zero"
2100  [(set (match_operand:CC 0 "flag_operand" "=f")
2101	(lt:CC (match_operand:DI 1 "gpr_operand" "e")
2102	       (const_int 0)))]
2103  ""
2104  "cmplt%: %0,%U1,0"
2105  [(set_attr "length" "4")
2106   (set_attr "type" "scmp")])
2107
2108(define_insn "*ltdi_internal"
2109  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2110	(lt:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2111	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2112   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2113  ""
2114  "#"
2115  [(set_attr "length" "12,16,24")
2116   (set_attr "type" "multi")])
2117
2118(define_insn "*ledi_internal"
2119  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2120	(le:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2121	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2122   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2123  ""
2124  "#"
2125  [(set_attr "length" "12,16,24")
2126   (set_attr "type" "multi")])
2127
2128(define_insn "*gtdi_internal"
2129  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2130	(gt:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2131	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2132   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2133  ""
2134  "#"
2135  [(set_attr "length" "12,16,24")
2136   (set_attr "type" "multi")])
2137
2138(define_insn "*gedi_zero"
2139  [(set (match_operand:CC 0 "flag_operand" "=f")
2140	(ge:CC (match_operand:DI 1 "gpr_operand" "e")
2141	       (const_int 0)))]
2142  ""
2143  "cmpge%: %0,%U1,0"
2144  [(set_attr "length" "4")
2145   (set_attr "type" "scmp")])
2146
2147(define_insn "*gedi_internal"
2148  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2149	(ge:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2150	       (match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2151   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2152  ""
2153  "#"
2154  [(set_attr "length" "12,16,24")
2155   (set_attr "type" "multi")])
2156
2157(define_insn "*ltudi_internal"
2158  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2159	(ltu:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2160		(match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2161   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2162  ""
2163  "#"
2164  [(set_attr "length" "12,16,24")
2165   (set_attr "type" "multi")])
2166
2167(define_insn "*leudi_internal"
2168  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2169	(leu:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2170		(match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2171   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2172  ""
2173  "#"
2174  [(set_attr "length" "12,16,24")
2175   (set_attr "type" "multi")])
2176
2177(define_insn "*gtudi_internal"
2178  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2179	(gtu:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2180		(match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2181   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2182  ""
2183  "#"
2184  [(set_attr "length" "12,16,24")
2185   (set_attr "type" "multi")])
2186
2187(define_insn "*geudi_internal"
2188  [(set (match_operand:CC 0 "flag_operand" "=&f,&f,&f")
2189	(geu:CC (match_operand:DI 1 "gpr_operand" "e,e,e")
2190		(match_operand:DI 2 "gpr_or_dbl_const_operand" "eJP,i,F")))
2191   (clobber (match_operand:CC 3 "br_flag_operand" "=&b,&b,&b"))]
2192  ""
2193  "#"
2194  [(set_attr "length" "12,16,24")
2195   (set_attr "type" "multi")])
2196
2197(define_split
2198  [(set (match_operand:CC 0 "flag_operand" "")
2199	(match_operator:CC 1 "relational_di_operator"
2200			   [(match_operand:DI 2 "gpr_operand" "")
2201			    (match_operand:DI 3 "gpr_or_dbl_const_operand" "")]))
2202   (clobber (match_operand:CC 4 "br_flag_operand" ""))]
2203  "reload_completed"
2204  [(match_dup 5)
2205   (match_dup 6)
2206   (match_dup 7)]
2207  "
2208{
2209  enum rtx_code cond = GET_CODE (operands[1]);
2210  enum rtx_code ucond = unsigned_condition (cond);
2211  rtx tmpflag = operands[4];
2212  rtx outflag = operands[0];
2213  rtx high[2];
2214  rtx low[2];
2215
2216  d30v_split_double (operands[2], &high[0], &low[0]);
2217  d30v_split_double (operands[3], &high[1], &low[1]);
2218
2219  operands[5] = gen_rtx_SET (VOIDmode,
2220			     tmpflag,
2221			     gen_rtx_EQ (CCmode, high[0], high[1]));
2222
2223  operands[6] = gen_rtx_COND_EXEC (VOIDmode,
2224				   gen_rtx_NE (CCmode, tmpflag, const0_rtx),
2225				   gen_rtx_SET (VOIDmode, outflag,
2226						gen_rtx_fmt_ee (cond, CCmode,
2227								high[0],
2228								high[1])));
2229
2230  operands[7] = gen_rtx_COND_EXEC (VOIDmode,
2231				   gen_rtx_EQ (CCmode, tmpflag, const0_rtx),
2232				   gen_rtx_SET (VOIDmode, outflag,
2233						gen_rtx_fmt_ee (ucond, CCmode,
2234								low[0],
2235								low[1])));
2236}")
2237
2238
2239;; ::::::::::::::::::::
2240;; ::
2241;; :: Branches
2242;; ::
2243;; ::::::::::::::::::::
2244
2245;; Define_expands called by the machine independent part of the compiler
2246;; to allocate a new comparison register
2247
2248(define_expand "beq"
2249  [(match_dup 2)
2250   (set (pc)
2251	(if_then_else (ne:CC (match_dup 1)
2252			     (const_int 0))
2253		      (label_ref (match_operand 0 "" ""))
2254		      (pc)))]
2255  ""
2256  "
2257{
2258  operands[1] = gen_reg_rtx (CCmode);
2259  operands[2] = d30v_emit_comparison (EQ, operands[1],
2260				      d30v_compare_op0,
2261				      d30v_compare_op1);
2262}")
2263
2264(define_expand "bne"
2265  [(match_dup 2)
2266   (set (pc)
2267	(if_then_else (ne:CC (match_dup 1)
2268			     (const_int 0))
2269		      (label_ref (match_operand 0 "" ""))
2270		      (pc)))]
2271  ""
2272  "
2273{
2274  operands[1] = gen_reg_rtx (CCmode);
2275  operands[2] = d30v_emit_comparison (NE, operands[1],
2276				      d30v_compare_op0,
2277				      d30v_compare_op1);
2278}")
2279
2280(define_expand "bgt"
2281  [(match_dup 2)
2282   (set (pc)
2283	(if_then_else (ne:CC (match_dup 1)
2284			     (const_int 0))
2285		      (label_ref (match_operand 0 "" ""))
2286		      (pc)))]
2287  ""
2288  "
2289{
2290  operands[1] = gen_reg_rtx (CCmode);
2291  operands[2] = d30v_emit_comparison (GT, operands[1],
2292				      d30v_compare_op0,
2293				      d30v_compare_op1);
2294}")
2295
2296(define_expand "bge"
2297  [(match_dup 2)
2298   (set (pc)
2299	(if_then_else (ne:CC (match_dup 1)
2300			     (const_int 0))
2301		      (label_ref (match_operand 0 "" ""))
2302		      (pc)))]
2303  ""
2304  "
2305{
2306  operands[1] = gen_reg_rtx (CCmode);
2307  operands[2] = d30v_emit_comparison (GE, operands[1],
2308				      d30v_compare_op0,
2309				      d30v_compare_op1);
2310}")
2311
2312(define_expand "blt"
2313  [(match_dup 2)
2314   (set (pc)
2315	(if_then_else (ne:CC (match_dup 1)
2316			     (const_int 0))
2317		      (label_ref (match_operand 0 "" ""))
2318		      (pc)))]
2319  ""
2320  "
2321{
2322  operands[1] = gen_reg_rtx (CCmode);
2323  operands[2] = d30v_emit_comparison (LT, operands[1],
2324				      d30v_compare_op0,
2325				      d30v_compare_op1);
2326}")
2327
2328(define_expand "ble"
2329  [(match_dup 2)
2330   (set (pc)
2331	(if_then_else (ne:CC (match_dup 1)
2332			     (const_int 0))
2333		      (label_ref (match_operand 0 "" ""))
2334		      (pc)))]
2335  ""
2336  "
2337{
2338  operands[1] = gen_reg_rtx (CCmode);
2339  operands[2] = d30v_emit_comparison (LE, operands[1],
2340				      d30v_compare_op0,
2341				      d30v_compare_op1);
2342}")
2343
2344(define_expand "bgtu"
2345  [(match_dup 2)
2346   (set (pc)
2347	(if_then_else (ne:CC (match_dup 1)
2348			     (const_int 0))
2349		      (label_ref (match_operand 0 "" ""))
2350		      (pc)))]
2351  ""
2352  "
2353{
2354  operands[1] = gen_reg_rtx (CCmode);
2355  operands[2] = d30v_emit_comparison (GTU, operands[1],
2356				      d30v_compare_op0,
2357				      d30v_compare_op1);
2358}")
2359
2360(define_expand "bgeu"
2361  [(match_dup 2)
2362   (set (pc)
2363	(if_then_else (ne:CC (match_dup 1)
2364			     (const_int 0))
2365		      (label_ref (match_operand 0 "" ""))
2366		      (pc)))]
2367  ""
2368  "
2369{
2370  operands[1] = gen_reg_rtx (CCmode);
2371  operands[2] = d30v_emit_comparison (GEU, operands[1],
2372				      d30v_compare_op0,
2373				      d30v_compare_op1);
2374}")
2375
2376(define_expand "bltu"
2377  [(match_dup 2)
2378   (set (pc)
2379	(if_then_else (ne:CC (match_dup 1)
2380			     (const_int 0))
2381		      (label_ref (match_operand 0 "" ""))
2382		      (pc)))]
2383  ""
2384  "
2385{
2386  operands[1] = gen_reg_rtx (CCmode);
2387  operands[2] = d30v_emit_comparison (LTU, operands[1],
2388				      d30v_compare_op0,
2389				      d30v_compare_op1);
2390}")
2391
2392(define_expand "bleu"
2393  [(match_dup 2)
2394   (set (pc)
2395	(if_then_else (ne:CC (match_dup 1)
2396			     (const_int 0))
2397		      (label_ref (match_operand 0 "" ""))
2398		      (pc)))]
2399  ""
2400  "
2401{
2402  operands[1] = gen_reg_rtx (CCmode);
2403  operands[2] = d30v_emit_comparison (LEU, operands[1],
2404				      d30v_compare_op0,
2405				      d30v_compare_op1);
2406}")
2407
2408;; Actual branches.  We must allow for the (label_ref) and the (pc) to be
2409;; swapped.  If they are swapped, it reverses the sense of the branch.
2410;; Also handle changing the ne to eq.
2411;; In order for the length calculations to be correct, the label must be
2412;; operand 0.
2413
2414;; We used to handle branches against 0 to be folded directly into
2415;; bratnz/bratzr instruction, but this dimisses the possibility of doing
2416;; conditional execution.  Instead handle these via peepholes.
2417
2418;; Branches based off of the flag bits
2419(define_insn "*bra_true"
2420  [(set (pc)
2421	(if_then_else (match_operator:CC 1 "condexec_branch_operator"
2422					 [(match_operand:CC 2 "br_flag_or_constant_operand" "b,I,N")
2423					  (const_int 0)])
2424		      (label_ref (match_operand 0 "" ""))
2425		      (pc)))]
2426  ""
2427  "*
2428{
2429  if (GET_CODE (operands[2]) == REG || GET_CODE (operands[2]) == SUBREG)
2430    return \"bra%F1 %l0\";
2431
2432  if (GET_CODE (operands[2]) != CONST_INT)
2433    fatal_insn (\"bad jump\", insn);
2434
2435  if ((GET_CODE (operands[1]) == EQ && INTVAL (operands[2]) == 0)
2436      || (GET_CODE (operands[1]) == NE && INTVAL (operands[2]) != 0))
2437    return \"bra %l0\";
2438
2439  return \"; jump to %l0 optimized away\";
2440}"
2441  [(set_attr "type" "br")
2442   (set_attr "predicable" "no")])
2443
2444(define_insn "*bra_false"
2445  [(set (pc)
2446	(if_then_else (match_operator:CC 1 "condexec_branch_operator"
2447					 [(match_operand:CC 2 "br_flag_or_constant_operand" "b,I,N")
2448					  (const_int 0)])
2449		      (pc)
2450		      (label_ref (match_operand 0 "" ""))))]
2451  ""
2452  "*
2453{
2454  if (GET_CODE (operands[2]) == REG || GET_CODE (operands[2]) == SUBREG)
2455    return \"bra%T1 %l0\";
2456
2457  if (GET_CODE (operands[2]) != CONST_INT)
2458    fatal_insn (\"bad jump\", insn);
2459
2460  if ((GET_CODE (operands[1]) == EQ && INTVAL (operands[2]) != 0)
2461      || (GET_CODE (operands[1]) == NE && INTVAL (operands[2]) == 0))
2462    return \"bra %l0\";
2463
2464  return \"; jump to %l0 optimized away\";
2465}"
2466  [(set_attr "type" "br")
2467   (set_attr "predicable" "no")])
2468
2469;; Peephole to turn set flag, cond. jumps into branch if register ==/!= 0.
2470
2471(define_peephole2
2472  [(set (match_operand:CC 0 "br_flag_operand" "=b")
2473	(match_operator:CC 1 "branch_zero_operator"
2474			   [(match_operand:SI 2 "gpr_operand" "d")
2475			    (const_int 0)]))
2476   (set (pc)
2477	(if_then_else (match_operator:CC 3 "condexec_test_operator"
2478					 [(match_dup 0)
2479					  (const_int 0)])
2480		      (match_operand 4 "" "")
2481		      (match_operand 5 "" "")))]
2482  "peep2_reg_dead_p (2, operands[0])
2483   && GET_CODE (operands[4]) != RETURN
2484   && GET_CODE (operands[5]) != RETURN"
2485  [(set (pc)
2486	(if_then_else (match_dup 6)
2487		      (match_dup 4)
2488		      (match_dup 5)))]
2489  "
2490{
2491  int true_false = 1;
2492  if (GET_CODE (operands[1]) == EQ)
2493    true_false = !true_false;
2494  if (GET_CODE (operands[3]) == EQ)
2495    true_false = !true_false;
2496  operands[6] = gen_rtx_fmt_ee ((true_false ? NE : EQ), CCmode,
2497				operands[2], const0_rtx);
2498}")
2499
2500(define_insn "*bra_reg_true"
2501  [(set (pc) (if_then_else (match_operator:CC 1 "branch_zero_operator"
2502			     [(match_operand:SI 2 "gpr_operand" "d")
2503			      (const_int 0)])
2504			   (label_ref (match_operand 0 "" ""))
2505			   (pc)))]
2506  "reload_completed"
2507  "*
2508{
2509  return GET_CODE (operands[1]) == NE ? \"bratnz %2,%l0\" : \"bratzr %2,%l0\";
2510}"
2511  [(set_attr "type" "br2")
2512   (set_attr "predicable" "no")])
2513
2514(define_insn "*bra_reg_false"
2515  [(set (pc) (if_then_else (match_operator:CC 1 "branch_zero_operator"
2516			     [(match_operand:SI 2 "gpr_operand" "d")
2517			      (const_int 0)])
2518			   (pc)
2519			   (label_ref (match_operand 0 "" ""))))]
2520  "reload_completed"
2521  "*
2522{
2523  return GET_CODE (operands[1]) == EQ ? \"bratnz %2,%l0\" : \"bratzr %2,%l0\";
2524}"
2525  [(set_attr "type" "br2")
2526   (set_attr "predicable" "no")])
2527
2528;; ::::::::::::::::::::
2529;; ::
2530;; :: Set flag operations
2531;; ::
2532;; ::::::::::::::::::::
2533
2534;; Define_expands called by the machine independent part of the compiler
2535;; to allocate a new comparison register
2536
2537;; ??? These patterns should all probably use (ne:SI ... (const_int 0)) instead
2538;; of (eq:SI ... (const_int 1)), because the former is the canonical form.
2539;; The non-canonical form was used here because I was just trying to get the
2540;; port working again after it broke, and the non-canonical form was the
2541;; safer faster way to fix this.
2542
2543
2544(define_expand "seq"
2545  [(match_dup 2)
2546   (set (match_operand:SI 0 "gpr_operand" "")
2547	(ne:SI (match_dup 1) (const_int 0)))]
2548  ""
2549  "
2550{
2551  operands[1] = gen_reg_rtx (CCmode);
2552  operands[2] = d30v_emit_comparison (EQ, operands[1],
2553				      d30v_compare_op0,
2554				      d30v_compare_op1);
2555}")
2556
2557(define_expand "sne"
2558  [(match_dup 2)
2559   (set (match_operand:SI 0 "gpr_operand" "")
2560	(ne:SI (match_dup 1) (const_int 0)))]
2561  ""
2562  "
2563{
2564  operands[1] = gen_reg_rtx (CCmode);
2565  operands[2] = d30v_emit_comparison (NE, operands[1],
2566				      d30v_compare_op0,
2567				      d30v_compare_op1);
2568}")
2569
2570(define_expand "sgt"
2571  [(match_dup 2)
2572   (set (match_operand:SI 0 "gpr_operand" "")
2573	(ne:SI (match_dup 1) (const_int 0)))]
2574  ""
2575  "
2576{
2577  operands[1] = gen_reg_rtx (CCmode);
2578  operands[2] = d30v_emit_comparison (GT, operands[1],
2579				      d30v_compare_op0,
2580				      d30v_compare_op1);
2581}")
2582
2583(define_expand "sge"
2584  [(match_dup 2)
2585   (set (match_operand:SI 0 "gpr_operand" "")
2586	(ne:SI (match_dup 1) (const_int 0)))]
2587  ""
2588  "
2589{
2590  operands[1] = gen_reg_rtx (CCmode);
2591  operands[2] = d30v_emit_comparison (GE, operands[1],
2592				      d30v_compare_op0,
2593				      d30v_compare_op1);
2594}")
2595
2596(define_expand "slt"
2597  [(match_dup 2)
2598   (set (match_operand:SI 0 "gpr_operand" "")
2599	(ne:SI (match_dup 1) (const_int 0)))]
2600  ""
2601  "
2602{
2603  operands[1] = gen_reg_rtx (CCmode);
2604  operands[2] = d30v_emit_comparison (LT, operands[1],
2605				      d30v_compare_op0,
2606				      d30v_compare_op1);
2607}")
2608
2609(define_expand "sle"
2610  [(match_dup 2)
2611   (set (match_operand:SI 0 "gpr_operand" "")
2612	(ne:SI (match_dup 1) (const_int 0)))]
2613  ""
2614  "
2615{
2616  operands[1] = gen_reg_rtx (CCmode);
2617  operands[2] = d30v_emit_comparison (LE, operands[1],
2618				      d30v_compare_op0,
2619				      d30v_compare_op1);
2620}")
2621
2622(define_expand "sgtu"
2623  [(match_dup 2)
2624   (set (match_operand:SI 0 "gpr_operand" "")
2625	(ne:SI (match_dup 1) (const_int 0)))]
2626  ""
2627  "
2628{
2629  operands[1] = gen_reg_rtx (CCmode);
2630  operands[2] = d30v_emit_comparison (GTU, operands[1],
2631				      d30v_compare_op0,
2632				      d30v_compare_op1);
2633}")
2634
2635(define_expand "sgeu"
2636  [(match_dup 2)
2637   (set (match_operand:SI 0 "gpr_operand" "")
2638	(ne:SI (match_dup 1) (const_int 0)))]
2639  ""
2640  "
2641{
2642  operands[1] = gen_reg_rtx (CCmode);
2643  operands[2] = d30v_emit_comparison (GEU, operands[1],
2644				      d30v_compare_op0,
2645				      d30v_compare_op1);
2646}")
2647
2648(define_expand "sltu"
2649  [(match_dup 2)
2650   (set (match_operand:SI 0 "gpr_operand" "")
2651	(ne:SI (match_dup 1) (const_int 0)))]
2652  ""
2653  "
2654{
2655  operands[1] = gen_reg_rtx (CCmode);
2656  operands[2] = d30v_emit_comparison (LTU, operands[1],
2657				      d30v_compare_op0,
2658				      d30v_compare_op1);
2659}")
2660
2661(define_expand "sleu"
2662  [(match_dup 2)
2663   (set (match_operand:SI 0 "gpr_operand" "")
2664	(ne:SI (match_dup 1) (const_int 0)))]
2665  ""
2666  "
2667{
2668  operands[1] = gen_reg_rtx (CCmode);
2669  operands[2] = d30v_emit_comparison (LEU, operands[1],
2670				      d30v_compare_op0,
2671				      d30v_compare_op1);
2672}")
2673
2674;; Set flag operations.  We prefer to use conditional execution instead of
2675;; mvfsys, since it is faster, but allow the use of mvfsys to offload some
2676;; register pressure.
2677(define_insn "*setcc_internal"
2678  [(set (match_operand:SI 0 "gpr_operand" "=d,?d,?*d")
2679	(ne:SI (match_operand:CC 1 "flag_operand" "b,z,*d")
2680	       (const_int 0)))]
2681  ""
2682  "@
2683    #
2684    mvfsys%: %0,%1
2685    or%: %0,%.,%1"
2686  [(set_attr "length" "8,4,4")
2687   (set_attr "type" "multi,either,either")])
2688
2689(define_split
2690  [(set (match_operand:SI 0 "gpr_operand" "")
2691	(ne:SI (match_operand:CC 1 "br_flag_operand" "")
2692	       (const_int 0)))]
2693  "reload_completed"
2694  [(set (match_dup 0)
2695	(const_int 0))
2696   (set (match_dup 0)
2697	(if_then_else:SI (ne:CC (match_dup 1)
2698				(const_int 0))
2699			 (const_int 1)
2700			 (match_dup 0)))]
2701  "")
2702
2703
2704;; ::::::::::::::::::::
2705;; ::
2706;; :: Operations on flags
2707;; ::
2708;; ::::::::::::::::::::
2709
2710(define_insn "andcc3"
2711  [(set (match_operand:CC 0 "flag_operand" "=f")
2712	(and:CC (match_operand:CC 1 "flag_operand" "f")
2713		(match_operand:CC 2 "flag_operand" "f")))]
2714  ""
2715  "andfg%: %0,%1,%2"
2716  [(set_attr "length" "4")
2717   (set_attr "type" "either")])
2718
2719(define_insn "iorcc3"
2720  [(set (match_operand:CC 0 "flag_operand" "=f")
2721	(ior:CC (match_operand:CC 1 "flag_operand" "f")
2722		(match_operand:CC 2 "flag_operand" "f")))]
2723  ""
2724  "orfg%: %0,%1,%2"
2725  [(set_attr "length" "4")
2726   (set_attr "type" "either")])
2727
2728(define_insn "xorcc3"
2729  [(set (match_operand:CC 0 "flag_operand" "=f")
2730	(xor:CC (match_operand:CC 1 "flag_operand" "f")
2731		(match_operand:CC 2 "flag_operand" "f")))]
2732  ""
2733  "xorfg%: %0,%1,%2"
2734  [(set_attr "length" "4")
2735   (set_attr "type" "either")])
2736
2737;; This is the canonical form produced by combine.
2738
2739(define_insn "incscc"
2740  [(set (match_operand:SI 0 "gpr_operand" "=d")
2741        (plus:SI (eq:SI (match_operand:CC 1 "br_flag_operand" "b")
2742			(const_int 1))
2743		 (match_operand:SI 2 "gpr_operand" "0")))]
2744  ""
2745  "add%T1 %0,%2,1"
2746  [(set_attr "length" "4")
2747   (set_attr "type" "either")
2748   ;; Not strictly true -- we could combine conditions.
2749   (set_attr "predicable" "no")])
2750
2751(define_insn "decscc"
2752  [(set (match_operand:SI 0 "gpr_operand" "=d")
2753        (minus:SI (match_operand:SI 1 "gpr_operand" "0")
2754		  (eq:SI (match_operand:CC 2 "br_flag_operand" "b")
2755			 (const_int 1))))]
2756  ""
2757  "sub%T2 %0,%1,1"
2758  [(set_attr "length" "4")
2759   (set_attr "type" "either")
2760   ;; Not strictly true -- we could combine conditions.
2761   (set_attr "predicable" "no")])
2762
2763;; ::::::::::::::::::::
2764;; ::
2765;; :: Call and branch instructions
2766;; ::
2767;; ::::::::::::::::::::
2768
2769;; Subroutine call instruction returning no value.  Operand 0 is the function
2770;; to call; operand 1 is the number of bytes of arguments pushed (in mode
2771;; `SImode', except it is normally a `const_int'); operand 2 is the number of
2772;; registers used as operands.
2773
2774;; On most machines, operand 2 is not actually stored into the RTL pattern.  It
2775;; is supplied for the sake of some RISC machines which need to put this
2776;; information into the assembler code; they can put it in the RTL instead of
2777;; operand 1.
2778
2779(define_expand "call"
2780  [(parallel [(call (match_operand 0 "call_operand" "")
2781		    (match_operand 1 "" ""))
2782	      (use (match_operand 2 "" ""))
2783	      (clobber (match_dup 3))])]
2784  ""
2785  "
2786{
2787  if (GET_CODE (XEXP (operands[0], 0)) == SUBREG)
2788    XEXP (operands[0], 0) = copy_addr_to_reg (XEXP (operands[0], 0));
2789
2790  if (!operands[2])
2791    operands[2] = const0_rtx;
2792
2793  operands[3] = gen_rtx (REG, Pmode, GPR_LINK);
2794}")
2795
2796(define_insn "*call_internal"
2797  [(call (match_operand:QI 0 "call_operand" "R,S")
2798	 (match_operand 1 "" ""))
2799   (use (match_operand 2 "" ""))
2800   (clobber (match_operand 3 "" "=d,d"))]
2801  ""
2802  "@
2803    jsr%: %0
2804    bsr%: %0"
2805  [(set_attr "length" "4,8")
2806   (set_attr "type" "mu,long")])
2807
2808;; Subroutine call instruction returning a value.  Operand 0 is the hard
2809;; register in which the value is returned.  There are three more operands, the
2810;; same as the three operands of the `call' instruction (but with numbers
2811;; increased by one).
2812
2813;; Subroutines that return `BLKmode' objects use the `call' insn.
2814
2815(define_expand "call_value"
2816  [(parallel [(set (match_operand 0 "gpr_operand" "")
2817		   (call (match_operand 1 "call_operand" "")
2818			 (match_operand 2 "" "")))
2819	     (use (match_operand 3 "" ""))
2820	     (clobber (match_dup 4))])]
2821  ""
2822  "
2823{
2824  if (GET_CODE (XEXP (operands[1], 0)) == SUBREG)
2825    XEXP (operands[1], 0) = copy_addr_to_reg (XEXP (operands[1], 0));
2826
2827  if (!operands[3])
2828    operands[3] = const0_rtx;
2829
2830  operands[4] = gen_rtx (REG, Pmode, GPR_LINK);
2831}")
2832
2833(define_insn "*call_value_internal"
2834  [(set (match_operand 0 "gpr_operand" "=d,d")
2835	(call (match_operand:QI 1 "call_operand" "R,S")
2836	      (match_operand 2 "" "")))
2837	(use (match_operand 3 "" ""))
2838	(clobber (match_operand 4 "" "=d,d"))]
2839  ""
2840  "@
2841    jsr%: %1
2842    bsr%: %1"
2843  [(set_attr "length" "4,8")
2844   (set_attr "type" "mu,long")])
2845
2846;; Subroutine return
2847(define_expand "return"
2848  [(return)]
2849  "direct_return ()"
2850  "")
2851
2852(define_insn "*return_internal"
2853  [(return)]
2854  "reload_completed"
2855  "jmp link"
2856  [(set_attr "length" "4")
2857   (set_attr "type" "mu")
2858   (set_attr "predicable" "no")])
2859
2860(define_insn "*cond_return_true"
2861  [(set (pc)
2862	(if_then_else (match_operator:CC 0 "condexec_branch_operator"
2863			[(match_operand:CC 1 "br_flag_operand" "b")
2864			 (const_int 0)])
2865	  (return)
2866	  (pc)))]
2867  "reload_completed"
2868  "jmp%F0 link"
2869  [(set_attr "length" "4")
2870   (set_attr "type" "mu")
2871   (set_attr "predicable" "no")])
2872
2873(define_insn "*cond_return_false"
2874  [(set (pc)
2875	(if_then_else (match_operator:CC 0 "condexec_branch_operator"
2876			[(match_operand:CC 1 "br_flag_operand" "b")
2877			 (const_int 0)])
2878	  (pc)
2879	  (return)))]
2880  "reload_completed"
2881  "jmp%T0 link"
2882  [(set_attr "length" "4")
2883   (set_attr "type" "mu")
2884   (set_attr "predicable" "no")])
2885
2886;; Normal unconditional jump
2887(define_insn "jump"
2888  [(set (pc) (label_ref (match_operand 0 "" "")))]
2889  ""
2890  "bra %l0"
2891  [(set_attr "type" "br")
2892   (set_attr "predicable" "no")])
2893
2894;; Indirect jump through a register
2895(define_insn "indirect_jump"
2896  [(set (pc) (match_operand:SI 0 "gpr_operand" "d"))]
2897  ""
2898  "jmp %0"
2899  [(set_attr "length" "4")
2900   (set_attr "type" "mu")
2901   (set_attr "predicable" "no")])
2902
2903;; Instruction to jump to a variable address.  This is a low-level capability
2904;; which can be used to implement a dispatch table when there is no `casesi'
2905;; pattern.
2906
2907;; This pattern requires two operands: the address or offset, and a label which
2908;; should immediately precede the jump table.  If the macro
2909;; `CASE_VECTOR_PC_RELATIVE' is defined then the first operand is an offset
2910;; which counts from the address of the table; otherwise, it is an absolute
2911;; address to jump to.  In either case, the first operand has mode `Pmode'.
2912
2913;; The `tablejump' insn is always the last insn before the jump table it uses.
2914;; Its assembler code normally has no need to use the second operand, but you
2915;; should incorporate it in the RTL pattern so that the jump optimizer will not
2916;; delete the table as unreachable code.
2917
2918(define_insn "tablejump"
2919  [(set (pc) (match_operand:SI 0 "gpr_operand" "d"))
2920   (use (label_ref (match_operand 1 "" "")))]
2921  ""
2922  "jmp %0"
2923  [(set_attr "length" "4")
2924   (set_attr "type" "mu")
2925   (set_attr "predicable" "no")])
2926
2927
2928
2929;; ::::::::::::::::::::
2930;; ::
2931;; :: Prologue and Epilogue instructions
2932;; ::
2933;; ::::::::::::::::::::
2934
2935;; Called after register allocation to add any instructions needed for the
2936;; prologue.  Using a prologue insn is favored compared to putting all of the
2937;; instructions in output_function_prologue (), since it allows the scheduler
2938;; to intermix instructions with the saves of the caller saved registers.  In
2939;; some cases, it might be necessary to emit a barrier instruction as the last
2940;; insn to prevent such scheduling.
2941
2942(define_expand "prologue"
2943  [(const_int 1)]
2944  ""
2945  "
2946{
2947  d30v_expand_prologue ();
2948  DONE;
2949}")
2950
2951;; Called after register allocation to add any instructions needed for the
2952;; epilogue.  Using an epilogue insn is favored compared to putting all of the
2953;; instructions in output_function_epilogue (), since it allows the scheduler
2954;; to intermix instructions with the saves of the caller saved registers.  In
2955;; some cases, it might be necessary to emit a barrier instruction as the last
2956;; insn to prevent such scheduling.
2957
2958(define_expand "epilogue"
2959  [(const_int 2)]
2960  ""
2961  "
2962{
2963  d30v_expand_epilogue ();
2964  DONE;
2965}")
2966
2967(define_expand "eh_epilogue"
2968  [(use (match_operand:DI 0 "register_operand" "r"))
2969   (use (match_operand:DI 1 "register_operand" "r"))
2970   (use (match_operand:DI 2 "register_operand" "r"))]
2971  ""
2972  "
2973{
2974  cfun->machine->eh_epilogue_sp_ofs = operands[1];
2975  if (GET_CODE (operands[2]) != REG || REGNO (operands[2]) != GPR_LINK)
2976    {
2977      rtx ra = gen_rtx_REG (Pmode, GPR_LINK);
2978      emit_move_insn (ra, operands[2]);
2979      operands[2] = ra;
2980    }
2981}")
2982
2983
2984;; ::::::::::::::::::::
2985;; ::
2986;; :: Conditional move instructions
2987;; ::
2988;; ::::::::::::::::::::
2989
2990;; Conditionally move operand 2 or operand 3 into operand 0 according to the
2991;; comparison in operand 1.  If the comparison is true, operand 2 is moved into
2992;; operand 0, otherwise operand 3 is moved.
2993
2994;; The mode of the operands being compared need not be the same as the operands
2995;; being moved.  Some machines, sparc64 for example, have instructions that
2996;; conditionally move an integer value based on the floating point condition
2997;; codes and vice versa.
2998
2999;; If the machine does not have conditional move instructions, do not
3000;; define these patterns.
3001
3002;; Note we don't allow the general form of conditional store to be generated --
3003;; we always generate two separate if_then_elses's
3004(define_expand "movqicc"
3005  [(set (match_operand:QI 0 "move_output_operand" "")
3006	(if_then_else:QI (match_operand 1 "" "")
3007			 (match_operand:QI 2 "move_input_operand" "")
3008			 (match_operand:QI 3 "move_input_operand" "")))]
3009  "TARGET_COND_MOVE"
3010  "
3011{
3012  if (!d30v_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
3013    FAIL;
3014
3015  DONE;
3016}")
3017
3018(define_insn "*movqicc_internal"
3019  [(set (match_operand:QI 0 "gpr_operand" "=d,d,d,d,d,c,d,d,d,d,d,c,?&d")
3020	(if_then_else:QI (match_operator:CC 1 "condexec_test_operator"
3021					    [(match_operand:CC 2 "br_flag_operand" "b,b,b,b,b,b,b,b,b,b,b,b,b")
3022					     (const_int 0)])
3023			 (match_operand:QI 3 "move_input_operand" "dI,i,Q,m,c,d,0,0,0,0,0,0,dim")
3024			 (match_operand:QI 4 "move_input_operand" "0,0,0,0,0,0,dI,i,Q,m,c,d,dim")))]
3025  ""
3026  "#"
3027  [(set_attr "length" "4,8,4,8,4,4,4,8,4,8,4,4,16")
3028   (set_attr "type" "either,long,sload,lload,mu,mu,either,long,sload,lload,mu,mu,multi")
3029   (set_attr "predicable" "no")])
3030
3031;; If we have: a = (test) ? a : b, or a = (test) ? b : a, we can split it
3032;; before reload to allow combine to substitute in early.
3033;; ??? Not until we teach reload how to do conditional spills, we can't.
3034(define_split
3035  [(set (match_operand:QI 0 "move_output_operand" "")
3036	(if_then_else:QI (match_operator:CC 1 "condexec_test_operator"
3037			   [(match_operand:CC 2 "br_flag_operand" "")
3038			    (const_int 0)])
3039			 (match_operand:QI 3 "move_input_operand" "")
3040			 (match_dup 0)))]
3041  "reload_completed"
3042  [(cond_exec (match_dup 1)
3043     (set (match_dup 0) (match_dup 3)))]
3044  "")
3045
3046(define_split
3047  [(set (match_operand:QI 0 "move_output_operand" "")
3048	(if_then_else:QI (match_operator:CC 1 "condexec_test_operator"
3049			   [(match_operand:CC 2 "br_flag_operand" "")
3050			    (const_int 0)])
3051			 (match_dup 0)
3052			 (match_operand:QI 3 "move_input_operand" "")))]
3053  "reload_completed"
3054  [(cond_exec (match_dup 4)
3055     (set (match_dup 0) (match_dup 3)))]
3056  "
3057{
3058  if (GET_CODE (operands[1]) == EQ)
3059    operands[4] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3060  else
3061    operands[4] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3062}")
3063
3064(define_split
3065  [(set (match_operand:QI 0 "move_output_operand" "")
3066	(if_then_else:QI (match_operator:CC 1 "condexec_test_operator"
3067			   [(match_operand:CC 2 "br_flag_operand" "")
3068			    (const_int 0)])
3069			 (match_operand:QI 3 "move_input_operand" "")
3070			 (match_operand:QI 4 "move_input_operand" "")))]
3071  "reload_completed"
3072  [(cond_exec (match_dup 1)
3073     (set (match_dup 0) (match_dup 3)))
3074   (cond_exec (match_dup 5)
3075     (set (match_dup 0) (match_dup 4)))]
3076  "
3077{
3078  if (GET_CODE (operands[1]) == EQ)
3079    operands[5] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3080  else
3081    operands[5] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3082}")
3083
3084(define_expand "movhicc"
3085  [(set (match_operand:HI 0 "move_output_operand" "")
3086	(if_then_else:HI (match_operand 1 "" "")
3087			 (match_operand:HI 2 "move_input_operand" "")
3088			 (match_operand:HI 3 "move_input_operand" "")))]
3089  "TARGET_COND_MOVE"
3090  "
3091{
3092  if (!d30v_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
3093    FAIL;
3094
3095  DONE;
3096}")
3097
3098(define_insn "*movhicc_internal"
3099  [(set (match_operand:HI 0 "gpr_operand" "=d,d,d,d,d,c,d,d,d,d,d,c,?&d")
3100	(if_then_else:HI
3101	  (match_operator:CC 1 "condexec_test_operator"
3102	    [(match_operand:CC 2 "br_flag_operand" "b,b,b,b,b,b,b,b,b,b,b,b,b")
3103	     (const_int 0)])
3104	  (match_operand:HI 3 "move_input_operand" "dI,i,Q,m,c,d,0,0,0,0,0,0,dim")
3105	  (match_operand:HI 4 "move_input_operand" "0,0,0,0,0,0,dI,i,Q,m,c,d,dim")))]
3106  ""
3107  "#"
3108  [(set_attr "length" "4,8,4,8,4,4,4,8,4,8,4,4,16")
3109   (set_attr "type" "either,long,sload,lload,mu,mu,either,long,sload,lload,mu,mu,multi")
3110   (set_attr "predicable" "no")])
3111
3112;; If we have: a = (test) ? a : b, or a = (test) ? b : a, we can split it
3113;; before reload to allow combine to substitute in early.
3114;; ??? Not until we teach reload how to do conditional spills, we can't.
3115(define_split
3116  [(set (match_operand:HI 0 "move_output_operand" "")
3117	(if_then_else:HI (match_operator:CC 1 "condexec_test_operator"
3118			   [(match_operand:CC 2 "br_flag_operand" "")
3119			    (const_int 0)])
3120			 (match_operand:HI 3 "move_input_operand" "")
3121			 (match_dup 0)))]
3122  "reload_completed"
3123  [(cond_exec (match_dup 1)
3124     (set (match_dup 0) (match_dup 3)))]
3125  "")
3126
3127(define_split
3128  [(set (match_operand:HI 0 "move_output_operand" "")
3129	(if_then_else:HI (match_operator:CC 1 "condexec_test_operator"
3130			   [(match_operand:CC 2 "br_flag_operand" "")
3131			    (const_int 0)])
3132			 (match_dup 0)
3133			 (match_operand:HI 3 "move_input_operand" "")))]
3134  "reload_completed"
3135  [(cond_exec (match_dup 4)
3136     (set (match_dup 0) (match_dup 3)))]
3137  "
3138{
3139  if (GET_CODE (operands[1]) == EQ)
3140    operands[4] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3141  else
3142    operands[4] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3143}")
3144
3145(define_split
3146  [(set (match_operand:HI 0 "move_output_operand" "")
3147	(if_then_else:HI (match_operator:CC 1 "condexec_test_operator"
3148			   [(match_operand:CC 2 "br_flag_operand" "")
3149			    (const_int 0)])
3150			 (match_operand:HI 3 "move_input_operand" "")
3151			 (match_operand:HI 4 "move_input_operand" "")))]
3152  "reload_completed"
3153  [(cond_exec (match_dup 1)
3154     (set (match_dup 0) (match_dup 3)))
3155   (cond_exec (match_dup 5)
3156     (set (match_dup 0) (match_dup 4)))]
3157  "
3158{
3159  if (GET_CODE (operands[1]) == EQ)
3160    operands[5] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3161  else
3162    operands[5] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3163}")
3164
3165(define_expand "movsicc"
3166  [(set (match_operand:SI 0 "move_output_operand" "")
3167	(if_then_else:SI (match_operand 1 "" "")
3168			 (match_operand:SI 2 "move_input_operand" "")
3169			 (match_operand:SI 3 "move_input_operand" "")))]
3170  "TARGET_COND_MOVE"
3171  "
3172{
3173  if (!d30v_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
3174    FAIL;
3175
3176  DONE;
3177}")
3178
3179(define_insn "*movsicc_internal"
3180  [(set (match_operand:SI 0 "move_output_operand" "=d,d,d,d,d,c,d,d,d,d,d,c,?&d")
3181	(if_then_else:SI
3182	  (match_operator:CC 1 "condexec_test_operator"
3183	    [(match_operand:CC 2 "br_flag_operand" "b,b,b,b,b,b,b,b,b,b,b,b,b")
3184	     (const_int 0)])
3185	  (match_operand:SI 3 "move_input_operand" "dI,i,Q,m,c,d,0,0,0,0,0,0,dim")
3186	  (match_operand:SI 4 "move_input_operand" "0,0,0,0,0,0,dI,i,Q,m,c,d,dim")))]
3187  ""
3188  "#"
3189  [(set_attr "length" "4,8,4,8,4,4,4,8,4,8,4,4,16")
3190   (set_attr "type" "either,long,sload,lload,mu,mu,either,long,sload,lload,mu,mu,multi")
3191   (set_attr "predicable" "no")])
3192
3193;; If we have: a = (test) ? a : b, or a = (test) ? b : a, we can split it
3194;; before reload to allow combine to substitute in early.
3195;; ??? Not until we teach reload how to do conditional spills, we can't.
3196(define_split
3197  [(set (match_operand:SI 0 "move_output_operand" "")
3198	(if_then_else:SI (match_operator:CC 1 "condexec_test_operator"
3199			   [(match_operand:CC 2 "br_flag_operand" "")
3200			    (const_int 0)])
3201			 (match_operand:SI 3 "move_input_operand" "")
3202			 (match_dup 0)))]
3203  "reload_completed"
3204  [(cond_exec (match_dup 1)
3205     (set (match_dup 0) (match_dup 3)))]
3206  "")
3207
3208(define_split
3209  [(set (match_operand:SI 0 "move_output_operand" "")
3210	(if_then_else:SI (match_operator:CC 1 "condexec_test_operator"
3211			   [(match_operand:CC 2 "br_flag_operand" "")
3212			    (const_int 0)])
3213			 (match_dup 0)
3214			 (match_operand:SI 3 "move_input_operand" "")))]
3215  "reload_completed"
3216  [(cond_exec (match_dup 4)
3217     (set (match_dup 0) (match_dup 3)))]
3218  "
3219{
3220  if (GET_CODE (operands[1]) == EQ)
3221    operands[4] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3222  else
3223    operands[4] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3224}")
3225
3226(define_split
3227  [(set (match_operand:SI 0 "move_output_operand" "")
3228	(if_then_else:SI (match_operator:CC 1 "condexec_test_operator"
3229			   [(match_operand:CC 2 "br_flag_operand" "")
3230			    (const_int 0)])
3231			 (match_operand:SI 3 "move_input_operand" "")
3232			 (match_operand:SI 4 "move_input_operand" "")))]
3233  "reload_completed"
3234  [(cond_exec (match_dup 1)
3235     (set (match_dup 0) (match_dup 3)))
3236   (cond_exec (match_dup 5)
3237     (set (match_dup 0) (match_dup 4)))]
3238  "
3239{
3240  if (GET_CODE (operands[1]) == EQ)
3241    operands[5] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3242  else
3243    operands[5] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3244}")
3245
3246(define_expand "movsfcc"
3247  [(set (match_operand:SF 0 "move_output_operand" "")
3248	(if_then_else:SF (match_operand 1 "" "")
3249			 (match_operand:SF 2 "move_input_operand" "")
3250			 (match_operand:SF 3 "move_input_operand" "")))]
3251  "TARGET_COND_MOVE"
3252  "
3253{
3254  if (!d30v_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
3255    FAIL;
3256
3257  DONE;
3258}")
3259
3260(define_insn "*movsfcc_internal"
3261  [(set (match_operand:SF 0 "gpr_operand" "=d,d,d,d,d,d,d,d,?&d")
3262	(if_then_else:SF
3263	  (match_operator:CC 1 "condexec_test_operator"
3264	    [(match_operand:CC 2 "br_flag_operand" "b,b,b,b,b,b,b,b,b")
3265	     (const_int 0)])
3266	  (match_operand:SF 3 "move_input_operand" "dG,F,Q,m,0,0,0,0,dim")
3267	  (match_operand:SF 4 "move_input_operand" "0,0,0,0,dG,F,Q,m,dim")))]
3268  ""
3269  "#"
3270  [(set_attr "length" "4,8,4,8,4,8,4,8,16")
3271   (set_attr "type" "either,long,sload,lload,either,long,sload,lload,multi")
3272   (set_attr "predicable" "no")])
3273
3274(define_split
3275  [(set (match_operand:SF 0 "move_output_operand" "")
3276	(if_then_else:SF (match_operator:CC 1 "condexec_test_operator"
3277			   [(match_operand:CC 2 "br_flag_operand" "")
3278			    (const_int 0)])
3279			 (match_operand:SF 3 "move_input_operand" "")
3280			 (match_dup 0)))]
3281  "reload_completed"
3282  [(cond_exec (match_dup 1)
3283     (set (match_dup 0) (match_dup 3)))]
3284  "")
3285
3286(define_split
3287  [(set (match_operand:SF 0 "move_output_operand" "")
3288	(if_then_else:SF (match_operator:CC 1 "condexec_test_operator"
3289			   [(match_operand:CC 2 "br_flag_operand" "")
3290			    (const_int 0)])
3291			 (match_dup 0)
3292			 (match_operand:SF 3 "move_input_operand" "")))]
3293  "reload_completed"
3294  [(cond_exec (match_dup 4)
3295     (set (match_dup 0) (match_dup 3)))]
3296  "
3297{
3298  if (GET_CODE (operands[1]) == EQ)
3299    operands[4] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3300  else
3301    operands[4] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3302}")
3303
3304(define_split
3305  [(set (match_operand:SF 0 "move_output_operand" "")
3306	(if_then_else:SF (match_operator:CC 1 "condexec_test_operator"
3307			   [(match_operand:CC 2 "br_flag_operand" "")
3308			    (const_int 0)])
3309			 (match_operand:SF 3 "move_input_operand" "")
3310			 (match_operand:SF 4 "move_input_operand" "")))]
3311  "reload_completed"
3312  [(cond_exec (match_dup 1)
3313     (set (match_dup 0) (match_dup 3)))
3314   (cond_exec (match_dup 5)
3315     (set (match_dup 0) (match_dup 4)))]
3316  "
3317{
3318  if (GET_CODE (operands[1]) == EQ)
3319    operands[5] = gen_rtx_NE (CCmode, operands[2], const0_rtx);
3320  else
3321    operands[5] = gen_rtx_EQ (CCmode, operands[2], const0_rtx);
3322}")
3323
3324
3325;; ::::::::::::::::::::
3326;; ::
3327;; :: Miscellaneous instructions
3328;; ::
3329;; ::::::::::::::::::::
3330
3331;; No operation, needed in case the user uses -g but not -O.
3332(define_insn "nop"
3333  [(const_int 0)]
3334  ""
3335  "nop || nop"
3336  [(set_attr "length" "8")
3337   (set_attr "type" "long")
3338   (set_attr "predicable" "no")])
3339
3340;; Pseudo instruction that prevents the scheduler from moving code above this
3341;; point.
3342(define_insn "blockage"
3343  [(unspec_volatile [(const_int 0)] 0)]
3344  ""
3345  ""
3346  [(set_attr "length" "0")
3347   (set_attr "type" "unknown")
3348   (set_attr "predicable" "no")])
3349
3350;; ::::::::::::::::::::
3351;; ::
3352;; :: Conditional execution
3353;; ::
3354;; ::::::::::::::::::::
3355
3356(define_cond_exec
3357  [(match_operator:CC 0 "condexec_test_operator"
3358     [(match_operand:CC 1 "br_flag_operand" "b")
3359      (const_int 0)])]
3360  ""
3361  "")
3362