1 ;; Frv Machine Description
2 ;; Copyright (C) 1999, 2000, 2001, 2003, 2004, 2005 Free Software Foundation,
4 ;; Contributed by Red Hat, Inc.
6 ;; This file is part of GCC.
8 ;; GCC is free software; you can redistribute it and/or modify
9 ;; it under the terms of the GNU General Public License as published by
10 ;; the Free Software Foundation; either version 2, or (at your option)
13 ;; GCC is distributed in the hope that it will be useful,
14 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
15 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16 ;; GNU General Public License for more details.
18 ;; You should have received a copy of the GNU General Public License
19 ;; along with GCC; see the file COPYING. If not, write to
20 ;; the Free Software Foundation, 51 Franklin Street, Fifth Floor,
21 ;; Boston, MA 02110-1301, USA.
23 ;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
26 ;; ::::::::::::::::::::
30 ;; ::::::::::::::::::::
32 ;; GOT constants must go 12/HI/LO for the splitter to work
38 (UNSPEC_PIC_PROLOGUE 3)
40 (UNSPEC_STACK_ADJUST 5)
41 (UNSPEC_EH_RETURN_EPILOGUE 6)
44 (UNSPEC_OPTIONAL_MEMBAR 9)
46 (UNSPEC_GETTLSOFF 200)
47 (UNSPEC_TLS_LOAD_GOTTLSOFF12 201)
48 (UNSPEC_TLS_INDIRECT_CALL 202)
49 (UNSPEC_TLS_TLSDESC_LDD 203)
50 (UNSPEC_TLS_TLSDESC_LDD_AUX 204)
51 (UNSPEC_TLS_TLSOFF_LD 205)
53 (UNSPEC_TLSOFF_HILO 207)
59 (R_FRV_FUNCDESC_GOT12 15)
60 (R_FRV_FUNCDESC_GOTHI 16)
61 (R_FRV_FUNCDESC_GOTLO 17)
62 (R_FRV_FUNCDESC_VALUE 18)
63 (R_FRV_FUNCDESC_GOTOFF12 19)
64 (R_FRV_FUNCDESC_GOTOFFHI 20)
65 (R_FRV_FUNCDESC_GOTOFFLO 21)
72 (R_FRV_GOTTLSOFF_HI 28)
73 (R_FRV_GOTTLSOFF_LO 29)
79 (R_FRV_GOTTLSDESCHI 35)
80 (R_FRV_GOTTLSDESCLO 36)
85 ;; LR_REG conflicts with definition in frv.h
90 (define_mode_macro IMODE [QI HI SI DI])
91 (define_mode_attr IMODEsuffix [(QI "b") (HI "h") (SI "") (DI "d")])
92 (define_mode_attr BREADsuffix [(QI "ub") (HI "uh") (SI "") (DI "d")])
94 ;; ::::::::::::::::::::
98 ;; ::::::::::::::::::::
100 ;; Standard Constraints
102 ;; `m' A memory operand is allowed, with any kind of address that the
103 ;; machine supports in general.
105 ;; `o' A memory operand is allowed, but only if the address is
106 ;; "offsettable". This means that adding a small integer (actually, the
107 ;; width in bytes of the operand, as determined by its machine mode) may be
108 ;; added to the address and the result is also a valid memory address.
110 ;; `V' A memory operand that is not offsettable. In other words,
111 ;; anything that would fit the `m' constraint but not the `o' constraint.
113 ;; `<' A memory operand with autodecrement addressing (either
114 ;; predecrement or postdecrement) is allowed.
116 ;; `>' A memory operand with autoincrement addressing (either
117 ;; preincrement or postincrement) is allowed.
119 ;; `r' A register operand is allowed provided that it is in a general
122 ;; `d', `a', `f', ...
123 ;; Other letters can be defined in machine-dependent fashion to stand for
124 ;; particular classes of registers. `d', `a' and `f' are defined on the
125 ;; 68000/68020 to stand for data, address and floating point registers.
127 ;; `i' An immediate integer operand (one with constant value) is allowed.
128 ;; This includes symbolic constants whose values will be known only at
131 ;; `n' An immediate integer operand with a known numeric value is allowed.
132 ;; Many systems cannot support assembly-time constants for operands less
133 ;; than a word wide. Constraints for these operands should use `n' rather
136 ;; 'I' First machine-dependent integer constant (6 bit signed ints).
137 ;; 'J' Second machine-dependent integer constant (10 bit signed ints).
138 ;; 'K' Third machine-dependent integer constant (-2048).
139 ;; 'L' Fourth machine-dependent integer constant (16 bit signed ints).
140 ;; 'M' Fifth machine-dependent integer constant (16 bit unsigned ints).
141 ;; 'N' Sixth machine-dependent integer constant (-2047..-1).
142 ;; 'O' Seventh machine-dependent integer constant (zero).
143 ;; 'P' Eighth machine-dependent integer constant (1..2047).
145 ;; Other letters in the range `I' through `P' may be defined in a
146 ;; machine-dependent fashion to permit immediate integer operands with
147 ;; explicit integer values in specified ranges. For example, on the 68000,
148 ;; `I' is defined to stand for the range of values 1 to 8. This is the
149 ;; range permitted as a shift count in the shift instructions.
151 ;; `E' An immediate floating operand (expression code `const_double') is
152 ;; allowed, but only if the target floating point format is the same as
153 ;; that of the host machine (on which the compiler is running).
155 ;; `F' An immediate floating operand (expression code `const_double') is
158 ;; 'G' First machine-dependent const_double.
159 ;; 'H' Second machine-dependent const_double.
161 ;; `s' An immediate integer operand whose value is not an explicit
162 ;; integer is allowed.
164 ;; This might appear strange; if an insn allows a constant operand with a
165 ;; value not known at compile time, it certainly must allow any known
166 ;; value. So why use `s' instead of `i'? Sometimes it allows better code
169 ;; For example, on the 68000 in a fullword instruction it is possible to
170 ;; use an immediate operand; but if the immediate value is between -128 and
171 ;; 127, better code results from loading the value into a register and
172 ;; using the register. This is because the load into the register can be
173 ;; done with a `moveq' instruction. We arrange for this to happen by
174 ;; defining the letter `K' to mean "any integer outside the range -128 to
175 ;; 127", and then specifying `Ks' in the operand constraints.
177 ;; `g' Any register, memory or immediate integer operand is allowed,
178 ;; except for registers that are not general registers.
180 ;; `X' Any operand whatsoever is allowed, even if it does not satisfy
181 ;; `general_operand'. This is normally used in the constraint of a
182 ;; `match_scratch' when certain alternatives will not actually require a
185 ;; `0' Match operand 0.
186 ;; `1' Match operand 1.
187 ;; `2' Match operand 2.
188 ;; `3' Match operand 3.
189 ;; `4' Match operand 4.
190 ;; `5' Match operand 5.
191 ;; `6' Match operand 6.
192 ;; `7' Match operand 7.
193 ;; `8' Match operand 8.
194 ;; `9' Match operand 9.
196 ;; An operand that matches the specified operand number is allowed. If a
197 ;; digit is used together with letters within the same alternative, the
198 ;; digit should come last.
200 ;; This is called a "matching constraint" and what it really means is that
201 ;; the assembler has only a single operand that fills two roles considered
202 ;; separate in the RTL insn. For example, an add insn has two input
203 ;; operands and one output operand in the RTL, but on most CISC machines an
204 ;; add instruction really has only two operands, one of them an
205 ;; input-output operand:
209 ;; Matching constraints are used in these circumstances. More precisely,
210 ;; the two operands that match must include one input-only operand and one
211 ;; output-only operand. Moreover, the digit must be a smaller number than
212 ;; the number of the operand that uses it in the constraint.
214 ;; For operands to match in a particular case usually means that they are
215 ;; identical-looking RTL expressions. But in a few special cases specific
216 ;; kinds of dissimilarity are allowed. For example, `*x' as an input
217 ;; operand will match `*x++' as an output operand. For proper results in
218 ;; such cases, the output template should always use the output-operand's
219 ;; number when printing the operand.
221 ;; `p' An operand that is a valid memory address is allowed. This is for
222 ;; "load address" and "push address" instructions.
224 ;; `p' in the constraint must be accompanied by `address_operand' as the
225 ;; predicate in the `match_operand'. This predicate interprets the mode
226 ;; specified in the `match_operand' as the mode of the memory reference for
227 ;; which the address would be valid.
229 ;; `Q` First non constant, non register machine-dependent insns
230 ;; `R` Second non constant, non register machine-dependent insns
231 ;; `S` Third non constant, non register machine-dependent insns
232 ;; `T` Fourth non constant, non register machine-dependent insns
233 ;; `U` Fifth non constant, non register machine-dependent insns
235 ;; Letters in the range `Q' through `U' may be defined in a
236 ;; machine-dependent fashion to stand for arbitrary operand types. The
237 ;; machine description macro `EXTRA_CONSTRAINT' is passed the operand as
238 ;; its first argument and the constraint letter as its second operand.
240 ;; A typical use for this would be to distinguish certain types of memory
241 ;; references that affect other insn operands.
243 ;; Do not define these constraint letters to accept register references
244 ;; (`reg'); the reload pass does not expect this and would not handle it
247 ;; Multiple Alternative Constraints
248 ;; `?' Disparage slightly the alternative that the `?' appears in, as a
249 ;; choice when no alternative applies exactly. The compiler regards this
250 ;; alternative as one unit more costly for each `?' that appears in it.
252 ;; `!' Disparage severely the alternative that the `!' appears in. This
253 ;; alternative can still be used if it fits without reloading, but if
254 ;; reloading is needed, some other alternative will be used.
256 ;; Constraint modifiers
257 ;; `=' Means that this operand is write-only for this instruction: the
258 ;; previous value is discarded and replaced by output data.
260 ;; `+' Means that this operand is both read and written by the
263 ;; When the compiler fixes up the operands to satisfy the constraints, it
264 ;; needs to know which operands are inputs to the instruction and which are
265 ;; outputs from it. `=' identifies an output; `+' identifies an operand
266 ;; that is both input and output; all other operands are assumed to be
269 ;; `&' Means (in a particular alternative) that this operand is written
270 ;; before the instruction is finished using the input operands. Therefore,
271 ;; this operand may not lie in a register that is used as an input operand
272 ;; or as part of any memory address.
274 ;; `&' applies only to the alternative in which it is written. In
275 ;; constraints with multiple alternatives, sometimes one alternative
276 ;; requires `&' while others do not.
278 ;; `&' does not obviate the need to write `='.
280 ;; `%' Declares the instruction to be commutative for this operand and the
281 ;; following operand. This means that the compiler may interchange the two
282 ;; operands if that is the cheapest way to make all operands fit the
283 ;; constraints. This is often used in patterns for addition instructions
284 ;; that really have only two operands: the result must go in one of the
287 ;; `#' Says that all following characters, up to the next comma, are to be
288 ;; ignored as a constraint. They are significant only for choosing
289 ;; register preferences.
291 ;; `*' Says that the following character should be ignored when choosing
292 ;; register preferences. `*' has no effect on the meaning of the
293 ;; constraint as a constraint, and no effect on reloading.
296 ;; ::::::::::::::::::::
300 ;; ::::::::::::::::::::
302 ;; The `define_attr' expression is used to define each attribute required by
303 ;; the target machine. It looks like:
305 ;; (define_attr NAME LIST-OF-VALUES DEFAULT)
307 ;; NAME is a string specifying the name of the attribute being defined.
309 ;; LIST-OF-VALUES is either a string that specifies a comma-separated list of
310 ;; values that can be assigned to the attribute, or a null string to indicate
311 ;; that the attribute takes numeric values.
313 ;; DEFAULT is an attribute expression that gives the value of this attribute
314 ;; for insns that match patterns whose definition does not include an explicit
315 ;; value for this attribute.
317 ;; For each defined attribute, a number of definitions are written to the
318 ;; `insn-attr.h' file. For cases where an explicit set of values is specified
319 ;; for an attribute, the following are defined:
321 ;; * A `#define' is written for the symbol `HAVE_ATTR_NAME'.
323 ;; * An enumeral class is defined for `attr_NAME' with elements of the
324 ;; form `UPPER-NAME_UPPER-VALUE' where the attribute name and value are first
325 ;; converted to upper case.
327 ;; * A function `get_attr_NAME' is defined that is passed an insn and
328 ;; returns the attribute value for that insn.
330 ;; For example, if the following is present in the `md' file:
332 ;; (define_attr "type" "branch,fp,load,store,arith" ...)
334 ;; the following lines will be written to the file `insn-attr.h'.
336 ;; #define HAVE_ATTR_type
337 ;; enum attr_type {TYPE_BRANCH, TYPE_FP, TYPE_LOAD, TYPE_STORE, TYPE_ARITH};
338 ;; extern enum attr_type get_attr_type ();
340 ;; If the attribute takes numeric values, no `enum' type will be defined and
341 ;; the function to obtain the attribute's value will return `int'.
343 (define_attr "length" "" (const_int 4))
345 ;; Processor type -- this attribute must exactly match the processor_type
346 ;; enumeration in frv-protos.h.
348 (define_attr "cpu" "generic,fr550,fr500,fr450,fr405,fr400,fr300,simple,tomcat"
349 (const (symbol_ref "frv_cpu_type")))
351 ;; Attribute is "yes" for branches and jumps that span too great a distance
352 ;; to be implemented in the most natural way. Such instructions will use
353 ;; a call instruction in some way.
355 (define_attr "far_jump" "yes,no" (const_string "no"))
358 ;; "unknown" must come last.
360 "int,sethi,setlo,mul,div,gload,gstore,fload,fstore,movfg,movgf,macc,scan,cut,branch,jump,jumpl,call,spr,trap,fnop,fsconv,fsadd,fscmp,fsmul,fsmadd,fsdiv,sqrt_single,fdconv,fdadd,fdcmp,fdmul,fdmadd,fddiv,sqrt_double,mnop,mlogic,maveh,msath,maddh,mqaddh,mpackh,munpackh,mdpackh,mbhconv,mrot,mshift,mexpdhw,mexpdhd,mwcut,mmulh,mmulxh,mmach,mmrdh,mqmulh,mqmulxh,mqmach,mcpx,mqcpx,mcut,mclracc,mclracca,mdunpackh,mbhconve,mrdacc,mwtacc,maddacc,mdaddacc,mabsh,mdrot,mcpl,mdcut,mqsath,mqlimh,mqshift,mset,ccr,multi,load_or_call,unknown"
361 (const_string "unknown"))
363 (define_attr "acc_group" "none,even,odd"
364 (symbol_ref "frv_acc_group (insn)"))
366 ;; Scheduling and Packing Overview
367 ;; -------------------------------
369 ;; FR-V instructions are divided into five groups: integer, floating-point,
370 ;; media, branch and control. Each group is associated with a separate set
371 ;; of processing units, the number and behavior of which depend on the target
372 ;; target processor. Integer units have names like I0 and I1, floating-point
373 ;; units have names like F0 and F1, and so on.
375 ;; Each member of the FR-V family has its own restrictions on which
376 ;; instructions can issue to which units. For example, some processors
377 ;; allow loads to issue to I0 or I1 while others only allow them to issue
378 ;; to I0. As well as these processor-specific restrictions, there is a
379 ;; general rule that an instruction can only issue to unit X + 1 if an
380 ;; instruction in the same packet issued to unit X.
382 ;; Sometimes the only way to honor these restrictions is by adding nops
383 ;; to a packet. For example, on the fr550, media instructions that access
384 ;; ACC4-7 can only issue to M1 or M3. It is therefore only possible to
385 ;; execute these instructions by packing them with something that issues
386 ;; to M0. When no useful M0 instruction exists, an "mnop" can be used
389 ;; Having decided which instructions should issue to which units, the packet
390 ;; should be ordered according to the following template:
392 ;; I0 F0/M0 I1 F1/M1 .... B0 B1 ...
394 ;; Note that VLIW packets execute strictly in parallel. Every instruction
395 ;; in the packet will stall until all input operands are ready. These
396 ;; operands are then read simultaneously before any registers are modified.
397 ;; This means that it's OK to have write-after-read hazards between
398 ;; instructions in the same packet, even if the write is listed earlier
401 ;; Three gcc passes are involved in generating VLIW packets:
403 ;; (1) The scheduler. This pass uses the standard scheduling code and
404 ;; behaves in much the same way as it would for a superscalar RISC
407 ;; (2) frv_reorg. This pass inserts nops into packets in order to meet
408 ;; the processor's issue requirements. It also has code to optimize
409 ;; the type of padding used to align labels.
411 ;; (3) frv_pack_insns. The final packing phase, which puts the
412 ;; instructions into assembly language order according to the
413 ;; "I0 F0/M0 ..." template above.
415 ;; In the ideal case, these three passes will agree on which instructions
416 ;; should be packed together, but this won't always happen. In particular:
418 ;; (a) (2) might not pack predicated instructions in the same way as (1).
419 ;; The scheduler tries to schedule predicated instructions for the
420 ;; worst case, assuming the predicate is true. However, if we have
421 ;; something like a predicated load, it isn't always possible to
422 ;; fill the load delay with useful instructions. (2) should then
423 ;; pack the user of the loaded value as aggressively as possible,
424 ;; in order to optimize the case when the predicate is false.
425 ;; See frv_pack_insn_p for more details.
427 ;; (b) The final shorten_branches pass runs between (2) and (3).
428 ;; Since (2) inserts nops, it is possible that some branches
429 ;; that were thought to be in range during (2) turned out to
430 ;; out-of-range in (3).
432 ;; All three passes use DFAs to model issue restrictions. The main
433 ;; question that the DFAs are supposed to answer is simply: can these
434 ;; instructions be packed together? The DFAs are not responsible for
435 ;; assigning instructions to execution units; that's the job of
436 ;; frv_sort_insn_group, see below for details.
438 ;; To get the best results, the DFAs should try to allow packets to
439 ;; be built in every possible order. This gives the scheduler more
440 ;; flexibility, removing the need for things like multipass lookahead.
441 ;; It also means we can take more advantage of inter-packet dependencies.
443 ;; For example, suppose we're compiling for the fr400 and we have:
446 ;; ldi @(gr6,gr0),gr4
448 ;; We can pack these instructions together by assigning the load to I0 and
449 ;; the addition to I1. However, because of the anti dependence between the
450 ;; two instructions, the scheduler must schedule the addition first.
451 ;; We should generally get better schedules if the DFA allows both
452 ;; (ldi, addi) and (addi, ldi), leaving the final packing pass to
453 ;; reorder the packet where appropriate.
455 ;; Almost all integer instructions can issue to any unit in the range I0
456 ;; to Ix, where the value of "x" depends on the type of instruction and
457 ;; on the target processor. The rules for other instruction groups are
460 ;; When the restrictions are as regular as this, we can get the desired
461 ;; behavior by claiming the DFA unit associated with the highest unused
462 ;; execution unit. For example, if an instruction can issue to I0 or I1,
463 ;; the DFA first tries to take the DFA unit associated with I1, and will
464 ;; only take I0's unit if I1 isn't free. (Note that, as mentioned above,
465 ;; the DFA does not assign instructions to units. An instruction that
466 ;; claims DFA unit I1 will not necessarily issue to I1 in the final packet.)
468 ;; There are some cases, such as the fr550 media restriction mentioned
469 ;; above, where the rule is not as simple as "any unit between 0 and X".
470 ;; Even so, allocating higher units first brings us close to the ideal.
472 ;; Having divided instructions into packets, passes (2) and (3) must
473 ;; assign instructions to specific execution units. They do this using
474 ;; the following algorithm:
476 ;; 1. Partition the instructions into groups (integer, float/media, etc.)
478 ;; 2. For each group of instructions:
480 ;; (a) Issue each instruction in the reset DFA state and use the
481 ;; DFA cpu_unit_query interface to find out which unit it picks
484 ;; (b) Sort the instructions into ascending order of picked units.
485 ;; Instructions that pick I1 first come after those that pick
486 ;; I0 first, and so on. Let S be the sorted sequence and S[i]
487 ;; be the ith element of it (counting from zero).
489 ;; (c) If this is the control or branch group, goto (i)
491 ;; (d) Find the largest L such that S[0]...S[L-1] can be issued
492 ;; consecutively from the reset state and such that the DFA
493 ;; claims unit X when S[X] is added. Let D be the DFA state
494 ;; after instructions S[0]...S[L-1] have been issued.
496 ;; (e) If L is the length of S, goto (i)
498 ;; (f) Let U be the number of units belonging to this group and #S be
499 ;; the length of S. Create a new sequence S' by concatenating
500 ;; S[L]...S[#S-1] and (U - #S) nops.
502 ;; (g) For each permutation S'' of S', try issuing S'' from last to
503 ;; first, starting with state D. See if the DFA claims unit
504 ;; X + L when each S''[X] is added. If so, set S to the
505 ;; concatenation of S[0]...S[L-1] and S'', then goto (i).
507 ;; (h) If (g) found no permutation, abort.
509 ;; (i) S is now the sorted sequence for this group, meaning that S[X]
510 ;; issues to unit X. Trim any unwanted nops from the end of S.
512 ;; The sequence calculated by (b) is trivially correct for control
513 ;; instructions since they can't be packed. It is also correct for branch
514 ;; instructions due to their simple issue requirements. For integer and
515 ;; floating-point/media instructions, the sequence calculated by (b) is
516 ;; often the correct answer; the rest of the algorithm is optimized for
517 ;; the case in which it is correct.
519 ;; If there were no irregularities in the issue restrictions then step
520 ;; (d) would not be needed. It is mainly there to cope with the fr550
521 ;; integer restrictions, where a store can issue to I1, but only if a store
522 ;; also issues to I0. (Note that if a packet has two stores, they will be
523 ;; at the beginning of the sequence calculated by (b).) It also copes
524 ;; with fr400 M-2 instructions, which must issue to M0, and which cannot
525 ;; be issued together with an mnop in M1.
527 ;; Step (g) is the main one for integer and float/media instructions.
528 ;; The first permutation it tries is S' itself (because, as noted above,
529 ;; the sequence calculated by (b) is often correct). If S' doesn't work,
530 ;; the implementation tries varying the beginning of the sequence first.
531 ;; Thus the nops towards the end of the sequence will only move to lower
532 ;; positions if absolutely necessary.
534 ;; The algorithm is theoretically exponential in the number of instructions
535 ;; in a group, although it's only O(n log(n)) if the sequence calculated by
536 ;; (b) is acceptable. In practice, the algorithm completes quickly even
537 ;; in the rare cases where (g) needs to try other permutations.
538 (define_automaton "integer, float_media, branch, control, idiv, div")
540 ;; The main issue units. Note that not all units are available on
542 (define_query_cpu_unit "i0,i1,i2,i3" "integer")
543 (define_query_cpu_unit "f0,f1,f2,f3" "float_media")
544 (define_query_cpu_unit "b0,b1" "branch")
545 (define_query_cpu_unit "c" "control")
548 (define_cpu_unit "idiv1,idiv2" "idiv")
549 (define_cpu_unit "div1,div2,root" "div")
551 ;; Control instructions cannot be packed with others.
552 (define_reservation "control" "i0+i1+i2+i3+f0+f1+f2+f3+b0+b1")
554 ;; Generic reservation for control insns
555 (define_insn_reservation "control" 1
556 (eq_attr "type" "trap,spr,unknown,multi")
559 ;; Reservation for relaxable calls to gettlsoff.
560 (define_insn_reservation "load_or_call" 3
561 (eq_attr "type" "load_or_call")
564 ;; ::::::::::::::::::::
566 ;; :: Generic/FR500 scheduler description
568 ;; ::::::::::::::::::::
571 ;; Synthetic units used to describe issue restrictions.
572 (define_automaton "fr500_integer")
573 (define_cpu_unit "fr500_load0,fr500_load1,fr500_store0" "fr500_integer")
574 (exclusion_set "fr500_load0,fr500_load1" "fr500_store0")
576 (define_bypass 0 "fr500_i1_sethi" "fr500_i1_setlo")
577 (define_insn_reservation "fr500_i1_sethi" 1
578 (and (eq_attr "cpu" "generic,fr500,tomcat")
579 (eq_attr "type" "sethi"))
582 (define_insn_reservation "fr500_i1_setlo" 1
583 (and (eq_attr "cpu" "generic,fr500,tomcat")
584 (eq_attr "type" "setlo"))
587 (define_insn_reservation "fr500_i1_int" 1
588 (and (eq_attr "cpu" "generic,fr500,tomcat")
589 (eq_attr "type" "int"))
592 (define_insn_reservation "fr500_i1_mul" 3
593 (and (eq_attr "cpu" "generic,fr500,tomcat")
594 (eq_attr "type" "mul"))
597 (define_insn_reservation "fr500_i1_div" 19
598 (and (eq_attr "cpu" "generic,fr500,tomcat")
599 (eq_attr "type" "div"))
600 "(i1|i0),(idiv1*18|idiv2*18)")
602 (define_insn_reservation "fr500_i2" 4
603 (and (eq_attr "cpu" "generic,fr500,tomcat")
604 (eq_attr "type" "gload,fload"))
605 "(i1|i0) + (fr500_load0|fr500_load1)")
607 (define_insn_reservation "fr500_i3" 0
608 (and (eq_attr "cpu" "generic,fr500,tomcat")
609 (eq_attr "type" "gstore,fstore"))
612 (define_insn_reservation "fr500_i4" 3
613 (and (eq_attr "cpu" "generic,fr500,tomcat")
614 (eq_attr "type" "movgf,movfg"))
617 (define_insn_reservation "fr500_i5" 0
618 (and (eq_attr "cpu" "generic,fr500,tomcat")
619 (eq_attr "type" "jumpl"))
623 ;; Branch-instructions
625 (define_insn_reservation "fr500_branch" 0
626 (and (eq_attr "cpu" "generic,fr500,tomcat")
627 (eq_attr "type" "jump,branch,ccr"))
630 (define_insn_reservation "fr500_call" 0
631 (and (eq_attr "cpu" "generic,fr500,tomcat")
632 (eq_attr "type" "call"))
635 ;; Floating point insns. The default latencies are for non-media
636 ;; instructions; media instructions incur an extra cycle.
638 (define_bypass 4 "fr500_farith" "fr500_m1,fr500_m2,fr500_m3,
639 fr500_m4,fr500_m5,fr500_m6")
640 (define_insn_reservation "fr500_farith" 3
641 (and (eq_attr "cpu" "generic,fr500,tomcat")
642 (eq_attr "type" "fnop,fsconv,fsadd,fsmul,fsmadd,fdconv,fdadd,fdmul,fdmadd"))
645 (define_insn_reservation "fr500_fcmp" 4
646 (and (eq_attr "cpu" "generic,fr500,tomcat")
647 (eq_attr "type" "fscmp,fdcmp"))
650 (define_bypass 11 "fr500_fdiv" "fr500_m1,fr500_m2,fr500_m3,
651 fr500_m4,fr500_m5,fr500_m6")
652 (define_insn_reservation "fr500_fdiv" 10
653 (and (eq_attr "cpu" "generic,fr500,tomcat")
654 (eq_attr "type" "fsdiv,fddiv"))
655 "(f1|f0),(div1*9 | div2*9)")
657 (define_bypass 16 "fr500_froot" "fr500_m1,fr500_m2,fr500_m3,
658 fr500_m4,fr500_m5,fr500_m6")
659 (define_insn_reservation "fr500_froot" 15
660 (and (eq_attr "cpu" "generic,fr500,tomcat")
661 (eq_attr "type" "sqrt_single,sqrt_double"))
664 ;; Media insns. Conflict table is as follows:
674 ;; where X indicates an invalid combination.
676 ;; Target registers are as follows:
685 ;; The default FPR latencies are for integer instructions.
686 ;; Floating-point instructions need one cycle more and media
687 ;; instructions need one cycle less.
688 (define_automaton "fr500_media")
689 (define_cpu_unit "fr500_m2_0,fr500_m2_1" "fr500_media")
690 (define_cpu_unit "fr500_m3_0,fr500_m3_1" "fr500_media")
691 (define_cpu_unit "fr500_m4_0,fr500_m4_1" "fr500_media")
692 (define_cpu_unit "fr500_m5" "fr500_media")
693 (define_cpu_unit "fr500_m6" "fr500_media")
695 (exclusion_set "fr500_m5,fr500_m6" "fr500_m2_0,fr500_m2_1,
696 fr500_m3_0,fr500_m3_1")
697 (exclusion_set "fr500_m6" "fr500_m4_0,fr500_m4_1,fr500_m5")
699 (define_bypass 2 "fr500_m1" "fr500_m1,fr500_m2,fr500_m3,
700 fr500_m4,fr500_m5,fr500_m6")
701 (define_bypass 4 "fr500_m1" "fr500_farith,fr500_fcmp,fr500_fdiv,fr500_froot")
702 (define_insn_reservation "fr500_m1" 3
703 (and (eq_attr "cpu" "generic,fr500,tomcat")
704 (eq_attr "type" "mnop,mlogic,maveh,msath,maddh,mqaddh"))
707 (define_bypass 2 "fr500_m2" "fr500_m1,fr500_m2,fr500_m3,
708 fr500_m4,fr500_m5,fr500_m6")
709 (define_bypass 4 "fr500_m2" "fr500_farith,fr500_fcmp,fr500_fdiv,fr500_froot")
710 (define_insn_reservation "fr500_m2" 3
711 (and (eq_attr "cpu" "generic,fr500,tomcat")
712 (eq_attr "type" "mrdacc,mpackh,munpackh,mbhconv,mrot,mshift,mexpdhw,mexpdhd,mwcut,mcut,mdunpackh,mbhconve"))
713 "(f1|f0) + (fr500_m2_0|fr500_m2_1)")
715 (define_bypass 1 "fr500_m3" "fr500_m4")
716 (define_insn_reservation "fr500_m3" 2
717 (and (eq_attr "cpu" "generic,fr500,tomcat")
718 (eq_attr "type" "mclracc,mwtacc"))
719 "(f1|f0) + (fr500_m3_0|fr500_m3_1)")
721 (define_bypass 1 "fr500_m4" "fr500_m4")
722 (define_insn_reservation "fr500_m4" 2
723 (and (eq_attr "cpu" "generic,fr500,tomcat")
724 (eq_attr "type" "mmulh,mmulxh,mmach,mmrdh,mqmulh,mqmulxh,mqmach,mcpx,mqcpx"))
725 "(f1|f0) + (fr500_m4_0|fr500_m4_1)")
727 (define_bypass 2 "fr500_m5" "fr500_m1,fr500_m2,fr500_m3,
728 fr500_m4,fr500_m5,fr500_m6")
729 (define_bypass 4 "fr500_m5" "fr500_farith,fr500_fcmp,fr500_fdiv,fr500_froot")
730 (define_insn_reservation "fr500_m5" 3
731 (and (eq_attr "cpu" "generic,fr500,tomcat")
732 (eq_attr "type" "mdpackh"))
733 "(f1|f0) + fr500_m5")
735 (define_bypass 1 "fr500_m6" "fr500_m4")
736 (define_insn_reservation "fr500_m6" 2
737 (and (eq_attr "cpu" "generic,fr500,tomcat")
738 (eq_attr "type" "mclracca"))
739 "(f1|f0) + fr500_m6")
741 ;; ::::::::::::::::::::
743 ;; :: FR400 scheduler description
745 ;; ::::::::::::::::::::
747 ;; Category 2 media instructions use both media units, but can be packed
748 ;; with non-media instructions. Use fr400_m1unit to claim the M1 unit
749 ;; without claiming a slot.
751 ;; Name Class Units Latency
752 ;; ==== ===== ===== =======
754 ;; sethi I1 I0/I1 0 -- does not interfere with setlo
759 ;; fload I2 I0 4 -- only 3 if read by a media insn
760 ;; gstore I3 I0 0 -- provides no result
761 ;; fstore I3 I0 0 -- provides no result
764 ;; jumpl I5 I0 0 -- provides no result
766 ;; (*) The results of these instructions can be read one cycle earlier
767 ;; than indicated. The penalty given is for instructions with write-after-
768 ;; write dependencies.
770 ;; The FR400 can only do loads and stores in I0, so we there's no danger
771 ;; of memory unit collision in the same packet. There's only one divide
774 (define_automaton "fr400_integer")
775 (define_cpu_unit "fr400_mul" "fr400_integer")
777 (define_insn_reservation "fr400_i1_int" 1
778 (and (eq_attr "cpu" "fr400,fr405,fr450")
779 (eq_attr "type" "int"))
782 (define_bypass 0 "fr400_i1_sethi" "fr400_i1_setlo")
783 (define_insn_reservation "fr400_i1_sethi" 1
784 (and (eq_attr "cpu" "fr400,fr405,fr450")
785 (eq_attr "type" "sethi"))
788 (define_insn_reservation "fr400_i1_setlo" 1
789 (and (eq_attr "cpu" "fr400,fr405,fr450")
790 (eq_attr "type" "setlo"))
793 ;; 3 is the worst case (write-after-write hazard).
794 (define_insn_reservation "fr400_i1_mul" 3
795 (and (eq_attr "cpu" "fr400,fr405")
796 (eq_attr "type" "mul"))
799 (define_insn_reservation "fr450_i1_mul" 2
800 (and (eq_attr "cpu" "fr450")
801 (eq_attr "type" "mul"))
804 (define_bypass 1 "fr400_i1_macc" "fr400_i1_macc")
805 (define_insn_reservation "fr400_i1_macc" 2
806 (and (eq_attr "cpu" "fr405,fr450")
807 (eq_attr "type" "macc"))
808 "(i0|i1) + fr400_mul")
810 (define_insn_reservation "fr400_i1_scan" 1
811 (and (eq_attr "cpu" "fr400,fr405,fr450")
812 (eq_attr "type" "scan"))
815 (define_insn_reservation "fr400_i1_cut" 2
816 (and (eq_attr "cpu" "fr405,fr450")
817 (eq_attr "type" "cut"))
820 ;; 20 is for a write-after-write hazard.
821 (define_insn_reservation "fr400_i1_div" 20
822 (and (eq_attr "cpu" "fr400,fr405")
823 (eq_attr "type" "div"))
826 (define_insn_reservation "fr450_i1_div" 19
827 (and (eq_attr "cpu" "fr450")
828 (eq_attr "type" "div"))
831 ;; 4 is for a write-after-write hazard.
832 (define_insn_reservation "fr400_i2" 4
833 (and (eq_attr "cpu" "fr400,fr405")
834 (eq_attr "type" "gload,fload"))
837 (define_insn_reservation "fr450_i2_gload" 3
838 (and (eq_attr "cpu" "fr450")
839 (eq_attr "type" "gload"))
842 ;; 4 is for a write-after-write hazard.
843 (define_insn_reservation "fr450_i2_fload" 4
844 (and (eq_attr "cpu" "fr450")
845 (eq_attr "type" "fload"))
848 (define_insn_reservation "fr400_i3" 0
849 (and (eq_attr "cpu" "fr400,fr405,fr450")
850 (eq_attr "type" "gstore,fstore"))
853 ;; 3 is for a write-after-write hazard.
854 (define_insn_reservation "fr400_i4" 3
855 (and (eq_attr "cpu" "fr400,fr405")
856 (eq_attr "type" "movfg,movgf"))
859 (define_insn_reservation "fr450_i4_movfg" 2
860 (and (eq_attr "cpu" "fr450")
861 (eq_attr "type" "movfg"))
864 ;; 3 is for a write-after-write hazard.
865 (define_insn_reservation "fr450_i4_movgf" 3
866 (and (eq_attr "cpu" "fr450")
867 (eq_attr "type" "movgf"))
870 (define_insn_reservation "fr400_i5" 0
871 (and (eq_attr "cpu" "fr400,fr405,fr450")
872 (eq_attr "type" "jumpl"))
875 ;; The bypass between FPR loads and media instructions, described above.
879 "fr400_m1_1,fr400_m1_2,\
880 fr400_m2_1,fr400_m2_2,\
881 fr400_m3_1,fr400_m3_2,\
882 fr400_m4_1,fr400_m4_2,\
885 ;; The branch instructions all use the B unit and produce no result.
887 (define_insn_reservation "fr400_b" 0
888 (and (eq_attr "cpu" "fr400,fr405,fr450")
889 (eq_attr "type" "jump,branch,ccr,call"))
892 ;; FP->FP moves are marked as "fsconv" instructions in the define_insns
893 ;; below, but are implemented on the FR400 using "mlogic" instructions.
894 ;; It's easier to class "fsconv" as a "m1:1" instruction than provide
895 ;; separate define_insns for the FR400.
897 ;; M1 instructions store their results in FPRs. Any instruction can read
898 ;; the result in the following cycle, so no penalty occurs.
900 (define_automaton "fr400_media")
901 (define_cpu_unit "fr400_m1a,fr400_m1b,fr400_m2a" "fr400_media")
902 (exclusion_set "fr400_m1a,fr400_m1b" "fr400_m2a")
904 (define_reservation "fr400_m1" "(f1|f0) + (fr400_m1a|fr400_m1b)")
905 (define_reservation "fr400_m2" "f0 + fr400_m2a")
907 (define_insn_reservation "fr400_m1_1" 1
908 (and (eq_attr "cpu" "fr400,fr405")
909 (eq_attr "type" "fsconv,mnop,mlogic,maveh,msath,maddh,mabsh,mset"))
912 (define_insn_reservation "fr400_m1_2" 1
913 (and (eq_attr "cpu" "fr400,fr405")
914 (eq_attr "type" "mqaddh,mqsath,mqlimh,mqshift"))
917 ;; M2 instructions store their results in accumulators, which are read
918 ;; by M2 or M4 media commands. M2 instructions can read the results in
919 ;; the following cycle, but M4 instructions must wait a cycle more.
922 "fr400_m2_1,fr400_m2_2"
923 "fr400_m2_1,fr400_m2_2")
925 (define_insn_reservation "fr400_m2_1" 2
926 (and (eq_attr "cpu" "fr400,fr405")
927 (eq_attr "type" "mmulh,mmulxh,mmach,mmrdh,mcpx,maddacc"))
930 (define_insn_reservation "fr400_m2_2" 2
931 (and (eq_attr "cpu" "fr400,fr405")
932 (eq_attr "type" "mqmulh,mqmulxh,mqmach,mqcpx,mdaddacc"))
935 ;; For our purposes, there seems to be little real difference between
936 ;; M1 and M3 instructions. Keep them separate anyway in case the distinction
939 (define_insn_reservation "fr400_m3_1" 1
940 (and (eq_attr "cpu" "fr400,fr405")
941 (eq_attr "type" "mpackh,mrot,mshift,mexpdhw"))
944 (define_insn_reservation "fr400_m3_2" 1
945 (and (eq_attr "cpu" "fr400,fr405")
946 (eq_attr "type" "munpackh,mdpackh,mbhconv,mexpdhd,mwcut,mdrot,mcpl"))
949 ;; M4 instructions write to accumulators or FPRs. MOVFG and STF
950 ;; instructions can read an FPR result in the following cycle, but
951 ;; M-unit instructions must wait a cycle more for either kind of result.
953 (define_bypass 1 "fr400_m4_1,fr400_m4_2" "fr400_i3,fr400_i4")
955 (define_insn_reservation "fr400_m4_1" 2
956 (and (eq_attr "cpu" "fr400,fr405")
957 (eq_attr "type" "mrdacc,mcut,mclracc"))
960 (define_insn_reservation "fr400_m4_2" 2
961 (and (eq_attr "cpu" "fr400,fr405")
962 (eq_attr "type" "mclracca,mdcut"))
965 ;; M5 instructions always incur a 1-cycle penalty.
967 (define_insn_reservation "fr400_m5" 2
968 (and (eq_attr "cpu" "fr400,fr405")
969 (eq_attr "type" "mwtacc"))
972 ;; ::::::::::::::::::::
974 ;; :: FR450 media scheduler description
976 ;; ::::::::::::::::::::
978 ;; The FR451 media restrictions are similar to the FR400's, but not as
979 ;; strict and not as regular. There are 6 categories with the following
983 ;; M-1 M-2 M-3 M-4 M-5 M-6
991 ;; where "x" indicates a conflict.
993 ;; There is no difference between M-1 and M-3 as far as issue
994 ;; restrictions are concerned, so they are combined as "m13".
996 ;; Units for odd-numbered categories. There can be two of these
998 (define_cpu_unit "fr450_m13a,fr450_m13b" "float_media")
999 (define_cpu_unit "fr450_m5a,fr450_m5b" "float_media")
1001 ;; Units for even-numbered categories. There can only be one per packet.
1002 (define_cpu_unit "fr450_m2a,fr450_m4a,fr450_m6a" "float_media")
1004 ;; Enforce the restriction matrix above.
1005 (exclusion_set "fr450_m2a,fr450_m4a,fr450_m6a" "fr450_m13a,fr450_m13b")
1006 (exclusion_set "fr450_m2a,fr450_m6a" "fr450_m5a,fr450_m5b")
1007 (exclusion_set "fr450_m4a,fr450_m6a" "fr450_m2a")
1009 (define_reservation "fr450_m13" "(f1|f0) + (fr450_m13a|fr450_m13b)")
1010 (define_reservation "fr450_m2" "f0 + fr450_m2a")
1011 (define_reservation "fr450_m4" "f0 + fr450_m4a")
1012 (define_reservation "fr450_m5" "(f1|f0) + (fr450_m5a|fr450_m5b)")
1013 (define_reservation "fr450_m6" "(f0|f1) + fr450_m6a")
1015 ;; MD-1, MD-3 and MD-8 instructions, which are the same as far
1016 ;; as scheduling is concerned. The inputs and outputs are FPRs.
1017 ;; Instructions that have 32-bit inputs and outputs belong to M-1 while
1018 ;; the rest belong to M-2.
1020 ;; ??? Arithmetic shifts (MD-6) have an extra cycle latency, but we don't
1021 ;; make the distinction between them and logical shifts.
1022 (define_insn_reservation "fr450_md138_1" 1
1023 (and (eq_attr "cpu" "fr450")
1024 (eq_attr "type" "fsconv,mnop,mlogic,maveh,msath,maddh,mabsh,mset,
1025 mrot,mshift,mexpdhw,mpackh"))
1028 (define_insn_reservation "fr450_md138_2" 1
1029 (and (eq_attr "cpu" "fr450")
1030 (eq_attr "type" "mqaddh,mqsath,mqlimh,
1031 mdrot,mwcut,mqshift,mexpdhd,
1032 munpackh,mdpackh,mbhconv,mcpl"))
1035 ;; MD-2 instructions. These take FPR or ACC inputs and produce an ACC output.
1036 ;; Instructions that write to double ACCs belong to M-3 while those that write
1037 ;; to quad ACCs belong to M-4.
1038 (define_insn_reservation "fr450_md2_3" 2
1039 (and (eq_attr "cpu" "fr450")
1040 (eq_attr "type" "mmulh,mmach,mcpx,mmulxh,mmrdh,maddacc"))
1043 (define_insn_reservation "fr450_md2_4" 2
1044 (and (eq_attr "cpu" "fr450")
1045 (eq_attr "type" "mqmulh,mqmach,mqcpx,mqmulxh,mdaddacc"))
1048 ;; Another MD-2 instruction can use the result on the following cycle.
1049 (define_bypass 1 "fr450_md2_3,fr450_md2_4" "fr450_md2_3,fr450_md2_4")
1051 ;; MD-4 instructions that write to ACCs.
1052 (define_insn_reservation "fr450_md4_3" 2
1053 (and (eq_attr "cpu" "fr450")
1054 (eq_attr "type" "mclracc"))
1057 (define_insn_reservation "fr450_md4_4" 3
1058 (and (eq_attr "cpu" "fr450")
1059 (eq_attr "type" "mclracca"))
1062 ;; MD-4 instructions that write to FPRs.
1063 (define_insn_reservation "fr450_md4_1" 2
1064 (and (eq_attr "cpu" "fr450")
1065 (eq_attr "type" "mcut"))
1068 (define_insn_reservation "fr450_md4_5" 2
1069 (and (eq_attr "cpu" "fr450")
1070 (eq_attr "type" "mrdacc"))
1073 (define_insn_reservation "fr450_md4_6" 2
1074 (and (eq_attr "cpu" "fr450")
1075 (eq_attr "type" "mdcut"))
1078 ;; Integer instructions can read the FPR result of an MD-4 instruction on
1079 ;; the following cycle.
1080 (define_bypass 1 "fr450_md4_1,fr450_md4_5,fr450_md4_6"
1081 "fr400_i3,fr450_i4_movfg")
1083 ;; MD-5 instructions, which belong to M-3. They take FPR inputs and
1085 (define_insn_reservation "fr450_md5_3" 2
1086 (and (eq_attr "cpu" "fr450")
1087 (eq_attr "type" "mwtacc"))
1090 ;; ::::::::::::::::::::
1092 ;; :: FR550 scheduler description
1094 ;; ::::::::::::::::::::
1096 ;; Prevent loads and stores from being issued in the same packet.
1097 ;; These units must go into the generic "integer" reservation because
1098 ;; of the constraints on fr550_store0 and fr550_store1.
1099 (define_cpu_unit "fr550_load0,fr550_load1" "integer")
1100 (define_cpu_unit "fr550_store0,fr550_store1" "integer")
1101 (exclusion_set "fr550_load0,fr550_load1" "fr550_store0,fr550_store1")
1103 ;; A store can only issue to I1 if one has also been issued to I0.
1104 (presence_set "fr550_store1" "fr550_store0")
1106 (define_bypass 0 "fr550_sethi" "fr550_setlo")
1107 (define_insn_reservation "fr550_sethi" 1
1108 (and (eq_attr "cpu" "fr550")
1109 (eq_attr "type" "sethi"))
1112 (define_insn_reservation "fr550_setlo" 1
1113 (and (eq_attr "cpu" "fr550")
1114 (eq_attr "type" "setlo"))
1117 (define_insn_reservation "fr550_int" 1
1118 (and (eq_attr "cpu" "fr550")
1119 (eq_attr "type" "int"))
1122 (define_insn_reservation "fr550_mul" 2
1123 (and (eq_attr "cpu" "fr550")
1124 (eq_attr "type" "mul"))
1127 (define_insn_reservation "fr550_div" 19
1128 (and (eq_attr "cpu" "fr550")
1129 (eq_attr "type" "div"))
1130 "(i1|i0),(idiv1*18 | idiv2*18)")
1132 (define_insn_reservation "fr550_load" 3
1133 (and (eq_attr "cpu" "fr550")
1134 (eq_attr "type" "gload,fload"))
1135 "(i1|i0)+(fr550_load0|fr550_load1)")
1137 ;; We can only issue a store to I1 if one was also issued to I0.
1138 ;; This means that, as far as frv_reorder_packet is concerned,
1139 ;; the instruction has the same priority as an I0-only instruction.
1140 (define_insn_reservation "fr550_store" 1
1141 (and (eq_attr "cpu" "fr550")
1142 (eq_attr "type" "gstore,fstore"))
1143 "(i0+fr550_store0)|(i1+fr550_store1)")
1145 (define_insn_reservation "fr550_transfer" 2
1146 (and (eq_attr "cpu" "fr550")
1147 (eq_attr "type" "movgf,movfg"))
1150 (define_insn_reservation "fr550_jumpl" 0
1151 (and (eq_attr "cpu" "fr550")
1152 (eq_attr "type" "jumpl"))
1155 (define_cpu_unit "fr550_ccr0,fr550_ccr1" "float_media")
1157 (define_insn_reservation "fr550_branch" 0
1158 (and (eq_attr "cpu" "fr550")
1159 (eq_attr "type" "jump,branch"))
1162 (define_insn_reservation "fr550_ccr" 0
1163 (and (eq_attr "cpu" "fr550")
1164 (eq_attr "type" "ccr"))
1165 "(b1|b0) + (fr550_ccr1|fr550_ccr0)")
1167 (define_insn_reservation "fr550_call" 0
1168 (and (eq_attr "cpu" "fr550")
1169 (eq_attr "type" "call"))
1172 (define_automaton "fr550_float_media")
1173 (define_cpu_unit "fr550_add0,fr550_add1" "fr550_float_media")
1175 ;; There are three possible combinations of floating-point/media instructions:
1177 ;; - one media and one float
1178 ;; - up to four float, no media
1179 ;; - up to four media, no float
1180 (define_cpu_unit "fr550_f0,fr550_f1,fr550_f2,fr550_f3" "fr550_float_media")
1181 (define_cpu_unit "fr550_m0,fr550_m1,fr550_m2,fr550_m3" "fr550_float_media")
1182 (exclusion_set "fr550_f1,fr550_f2,fr550_f3" "fr550_m1,fr550_m2,fr550_m3")
1184 (define_reservation "fr550_float" "fr550_f0|fr550_f1|fr550_f2|fr550_f3")
1185 (define_reservation "fr550_media" "fr550_m0|fr550_m1|fr550_m2|fr550_m3")
1187 (define_insn_reservation "fr550_f1" 0
1188 (and (eq_attr "cpu" "fr550")
1189 (eq_attr "type" "fnop"))
1190 "(f3|f2|f1|f0) + fr550_float")
1192 (define_insn_reservation "fr550_f2" 3
1193 (and (eq_attr "cpu" "fr550")
1194 (eq_attr "type" "fsconv,fsadd,fscmp"))
1195 "(f3|f2|f1|f0) + (fr550_add0|fr550_add1) + fr550_float")
1197 (define_insn_reservation "fr550_f3_mul" 3
1198 (and (eq_attr "cpu" "fr550")
1199 (eq_attr "type" "fsmul"))
1200 "(f1|f0) + fr550_float")
1202 (define_insn_reservation "fr550_f3_div" 10
1203 (and (eq_attr "cpu" "fr550")
1204 (eq_attr "type" "fsdiv"))
1205 "(f1|f0) + fr550_float")
1207 (define_insn_reservation "fr550_f3_sqrt" 15
1208 (and (eq_attr "cpu" "fr550")
1209 (eq_attr "type" "sqrt_single"))
1210 "(f1|f0) + fr550_float")
1212 ;; Synthetic units for enforcing media issue restrictions. Certain types
1213 ;; of insn in M2 conflict with certain types in M0:
1216 ;; MNOP MALU MSFT MMAC MSET
1219 ;; M0 MSFT - - x - x
1223 ;; where "x" indicates a conflict. The same restrictions apply to
1226 ;; In addition -- and this is the awkward bit! -- instructions that
1227 ;; access ACC0-3 can only issue to M0 or M2. Those that access ACC4-7
1228 ;; can only issue to M1 or M3. We refer to such instructions as "even"
1229 ;; and "odd" respectively.
1230 (define_cpu_unit "fr550_malu0,fr550_malu1" "float_media")
1231 (define_cpu_unit "fr550_malu2,fr550_malu3" "float_media")
1232 (define_cpu_unit "fr550_msft0,fr550_msft1" "float_media")
1233 (define_cpu_unit "fr550_mmac0,fr550_mmac1" "float_media")
1234 (define_cpu_unit "fr550_mmac2,fr550_mmac3" "float_media")
1235 (define_cpu_unit "fr550_mset0,fr550_mset1" "float_media")
1236 (define_cpu_unit "fr550_mset2,fr550_mset3" "float_media")
1238 (exclusion_set "fr550_malu0" "fr550_malu2")
1239 (exclusion_set "fr550_malu1" "fr550_malu3")
1241 (exclusion_set "fr550_msft0" "fr550_mset2")
1242 (exclusion_set "fr550_msft1" "fr550_mset3")
1244 (exclusion_set "fr550_mmac0" "fr550_mmac2")
1245 (exclusion_set "fr550_mmac1" "fr550_mmac3")
1247 ;; If an MSFT or MMAC instruction issues to a unit other than M0, we may
1248 ;; need to insert some nops. In the worst case, the packet will end up
1249 ;; having 4 integer instructions and 4 media instructions, leaving no
1250 ;; room for any branch instructions that the DFA might have accepted.
1252 ;; This doesn't matter for JUMP_INSNs and CALL_INSNs because they are
1253 ;; always the last instructions to be passed to the DFA, and could be
1254 ;; pushed out to a separate packet once the nops have been added.
1255 ;; However, it does cause problems for ccr instructions since they
1256 ;; can occur anywhere in the unordered packet.
1257 (exclusion_set "fr550_msft1,fr550_mmac1,fr550_mmac2,fr550_mmac3"
1258 "fr550_ccr0,fr550_ccr1")
1260 (define_reservation "fr550_malu"
1261 "(f3 + fr550_malu3) | (f2 + fr550_malu2)
1262 | (f1 + fr550_malu1) | (f0 + fr550_malu0)")
1264 (define_reservation "fr550_msft_even"
1267 (define_reservation "fr550_msft_odd"
1270 (define_reservation "fr550_msft_either"
1271 "(f1 + fr550_msft1) | (f0 + fr550_msft0)")
1273 (define_reservation "fr550_mmac_even"
1274 "(f2 + fr550_mmac2) | (f0 + fr550_mmac0)")
1276 (define_reservation "fr550_mmac_odd"
1277 "(f3 + fr550_mmac3) | (f1 + fr550_mmac1)")
1279 (define_reservation "fr550_mset"
1280 "(f3 + fr550_mset3) | (f2 + fr550_mset2)
1281 | (f1 + fr550_mset1) | (f0 + fr550_mset0)")
1283 (define_insn_reservation "fr550_mnop" 0
1284 (and (eq_attr "cpu" "fr550")
1285 (eq_attr "type" "mnop"))
1286 "fr550_media + (f3|f2|f1|f0)")
1288 (define_insn_reservation "fr550_malu" 2
1289 (and (eq_attr "cpu" "fr550")
1290 (eq_attr "type" "mlogic,maveh,msath,mabsh,maddh,mqaddh,mqsath"))
1291 "fr550_media + fr550_malu")
1293 ;; These insns only operate on FPRs and so don't need to be classified
1295 (define_insn_reservation "fr550_msft_1_either" 2
1296 (and (eq_attr "cpu" "fr550")
1297 (eq_attr "type" "mrot,mwcut,mshift,mexpdhw,mexpdhd,mpackh,
1298 munpackh,mdpackh,mbhconv,mdrot,mcpl"))
1299 "fr550_media + fr550_msft_either")
1301 ;; These insns read from ACC0-3.
1302 (define_insn_reservation "fr550_msft_1_even" 2
1303 (and (eq_attr "cpu" "fr550")
1304 (and (eq_attr "type" "mcut,mrdacc,mdcut")
1305 (eq_attr "acc_group" "even")))
1306 "fr550_media + fr550_msft_even")
1308 ;; These insns read from ACC4-7.
1309 (define_insn_reservation "fr550_msft_1_odd" 2
1310 (and (eq_attr "cpu" "fr550")
1311 (and (eq_attr "type" "mcut,mrdacc,mdcut")
1312 (eq_attr "acc_group" "odd")))
1313 "fr550_media + fr550_msft_odd")
1315 ;; MCLRACC with A=1 can issue to either M0 or M1.
1316 (define_insn_reservation "fr550_msft_2_either" 2
1317 (and (eq_attr "cpu" "fr550")
1318 (eq_attr "type" "mclracca"))
1319 "fr550_media + fr550_msft_either")
1321 ;; These insns write to ACC0-3.
1322 (define_insn_reservation "fr550_msft_2_even" 2
1323 (and (eq_attr "cpu" "fr550")
1324 (and (eq_attr "type" "mclracc,mwtacc")
1325 (eq_attr "acc_group" "even")))
1326 "fr550_media + fr550_msft_even")
1328 ;; These insns write to ACC4-7.
1329 (define_insn_reservation "fr550_msft_2_odd" 2
1330 (and (eq_attr "cpu" "fr550")
1331 (and (eq_attr "type" "mclracc,mwtacc")
1332 (eq_attr "acc_group" "odd")))
1333 "fr550_media + fr550_msft_odd")
1335 ;; These insns read from and write to ACC0-3.
1336 (define_insn_reservation "fr550_mmac_even" 2
1337 (and (eq_attr "cpu" "fr550")
1338 (and (eq_attr "type" "mmulh,mmulxh,mmach,mmrdh,mqmulh,mqmulxh,mqmach,
1339 maddacc,mdaddacc,mcpx,mqcpx")
1340 (eq_attr "acc_group" "even")))
1341 "fr550_media + fr550_mmac_even")
1343 ;; These insns read from and write to ACC4-7.
1344 (define_insn_reservation "fr550_mmac_odd" 2
1345 (and (eq_attr "cpu" "fr550")
1346 (and (eq_attr "type" "mmulh,mmulxh,mmach,mmrdh,mqmulh,mqmulxh,mqmach,
1347 maddacc,mdaddacc,mcpx,mqcpx")
1348 (eq_attr "acc_group" "odd")))
1349 "fr550_media + fr550_mmac_odd")
1351 (define_insn_reservation "fr550_mset" 1
1352 (and (eq_attr "cpu" "fr550")
1353 (eq_attr "type" "mset"))
1354 "fr550_media + fr550_mset")
1356 ;; ::::::::::::::::::::
1358 ;; :: Simple/FR300 scheduler description
1360 ;; ::::::::::::::::::::
1362 ;; Fr300 or simple processor. To describe it as 1 insn issue
1363 ;; processor, we use control unit.
1365 (define_insn_reservation "fr300_lat1" 1
1366 (and (eq_attr "cpu" "fr300,simple")
1367 (eq_attr "type" "!gload,fload,movfg,movgf"))
1370 (define_insn_reservation "fr300_lat2" 2
1371 (and (eq_attr "cpu" "fr300,simple")
1372 (eq_attr "type" "gload,fload,movfg,movgf"))
1376 ;; ::::::::::::::::::::
1380 ;; ::::::::::::::::::::
1382 ;; The insn attribute mechanism can be used to specify the requirements for
1383 ;; delay slots, if any, on a target machine. An instruction is said to require
1384 ;; a "delay slot" if some instructions that are physically after the
1385 ;; instruction are executed as if they were located before it. Classic
1386 ;; examples are branch and call instructions, which often execute the following
1387 ;; instruction before the branch or call is performed.
1389 ;; On some machines, conditional branch instructions can optionally "annul"
1390 ;; instructions in the delay slot. This means that the instruction will not be
1391 ;; executed for certain branch outcomes. Both instructions that annul if the
1392 ;; branch is true and instructions that annul if the branch is false are
1395 ;; Delay slot scheduling differs from instruction scheduling in that
1396 ;; determining whether an instruction needs a delay slot is dependent only
1397 ;; on the type of instruction being generated, not on data flow between the
1398 ;; instructions. See the next section for a discussion of data-dependent
1399 ;; instruction scheduling.
1401 ;; The requirement of an insn needing one or more delay slots is indicated via
1402 ;; the `define_delay' expression. It has the following form:
1404 ;; (define_delay TEST
1405 ;; [DELAY-1 ANNUL-TRUE-1 ANNUL-FALSE-1
1406 ;; DELAY-2 ANNUL-TRUE-2 ANNUL-FALSE-2
1409 ;; TEST is an attribute test that indicates whether this `define_delay' applies
1410 ;; to a particular insn. If so, the number of required delay slots is
1411 ;; determined by the length of the vector specified as the second argument. An
1412 ;; insn placed in delay slot N must satisfy attribute test DELAY-N.
1413 ;; ANNUL-TRUE-N is an attribute test that specifies which insns may be annulled
1414 ;; if the branch is true. Similarly, ANNUL-FALSE-N specifies which insns in
1415 ;; the delay slot may be annulled if the branch is false. If annulling is not
1416 ;; supported for that delay slot, `(nil)' should be coded.
1418 ;; For example, in the common case where branch and call insns require a single
1419 ;; delay slot, which may contain any insn other than a branch or call, the
1420 ;; following would be placed in the `md' file:
1422 ;; (define_delay (eq_attr "type" "branch,call")
1423 ;; [(eq_attr "type" "!branch,call") (nil) (nil)])
1425 ;; Multiple `define_delay' expressions may be specified. In this case, each
1426 ;; such expression specifies different delay slot requirements and there must
1427 ;; be no insn for which tests in two `define_delay' expressions are both true.
1429 ;; For example, if we have a machine that requires one delay slot for branches
1430 ;; but two for calls, no delay slot can contain a branch or call insn, and any
1431 ;; valid insn in the delay slot for the branch can be annulled if the branch is
1432 ;; true, we might represent this as follows:
1434 ;; (define_delay (eq_attr "type" "branch")
1435 ;; [(eq_attr "type" "!branch,call")
1436 ;; (eq_attr "type" "!branch,call")
1439 ;; (define_delay (eq_attr "type" "call")
1440 ;; [(eq_attr "type" "!branch,call") (nil) (nil)
1441 ;; (eq_attr "type" "!branch,call") (nil) (nil)])
1443 ;; Note - it is the backend's responsibility to fill any unfilled delay slots
1444 ;; at assembler generation time. This is usually done by adding a special print
1445 ;; operand to the delayed instruction, and then in the PRINT_OPERAND function
1446 ;; calling dbr_sequence_length() to determine how many delay slots were filled.
1449 ;; --------------<machine>.md-----------------
1450 ;; (define_insn "call"
1451 ;; [(call (match_operand 0 "memory_operand" "m")
1452 ;; (match_operand 1 "" ""))]
1454 ;; "call_delayed %0,%1,%2%#"
1455 ;; [(set_attr "length" "4")
1456 ;; (set_attr "type" "call")])
1458 ;; -------------<machine>.h-------------------
1459 ;; #define PRINT_OPERAND_PUNCT_VALID_P(CODE) (CODE == '#')
1461 ;; ------------<machine>.c------------------
1463 ;; machine_print_operand (file, x, code)
1471 ;; if (dbr_sequence_length () == 0)
1472 ;; fputs ("\n\tnop", file);
1475 ;; ::::::::::::::::::::
1477 ;; :: Notes on Patterns
1479 ;; ::::::::::::::::::::
1481 ;; If you need to construct a sequence of assembler instructions in order
1482 ;; to implement a pattern be sure to escape any backslashes and double quotes
1483 ;; that you use, e.g.:
1485 ;; (define_insn "an example"
1489 ;; { static char buffer [100];
1490 ;; sprintf (buffer, \"insn \\t %d\", REGNO (operands[1]));
1495 ;; Also if there is more than one instruction, they can be separated by \\;
1496 ;; which is a space saving synonym for \\n\\t:
1498 ;; (define_insn "another example"
1502 ;; { static char buffer [100];
1503 ;; sprintf (buffer, \"insn1 \\t %d\\;insn2 \\t %%1\",
1504 ;; REGNO (operands[1]));
1510 (include "predicates.md")
1512 ;; ::::::::::::::::::::
1516 ;; ::::::::::::::::::::
1518 ;; Wrap moves in define_expand to prevent memory->memory moves from being
1519 ;; generated at the RTL level, which generates better code for most machines
1520 ;; which can't do mem->mem moves.
1522 ;; If operand 0 is a `subreg' with mode M of a register whose own mode is wider
1523 ;; than M, the effect of this instruction is to store the specified value in
1524 ;; the part of the register that corresponds to mode M. The effect on the rest
1525 ;; of the register is undefined.
1527 ;; This class of patterns is special in several ways. First of all, each of
1528 ;; these names *must* be defined, because there is no other way to copy a datum
1529 ;; from one place to another.
1531 ;; Second, these patterns are not used solely in the RTL generation pass. Even
1532 ;; the reload pass can generate move insns to copy values from stack slots into
1533 ;; temporary registers. When it does so, one of the operands is a hard
1534 ;; register and the other is an operand that can need to be reloaded into a
1537 ;; Therefore, when given such a pair of operands, the pattern must
1538 ;; generate RTL which needs no reloading and needs no temporary
1539 ;; registers--no registers other than the operands. For example, if
1540 ;; you support the pattern with a `define_expand', then in such a
1541 ;; case the `define_expand' mustn't call `force_reg' or any other such
1542 ;; function which might generate new pseudo registers.
1544 ;; This requirement exists even for subword modes on a RISC machine
1545 ;; where fetching those modes from memory normally requires several
1546 ;; insns and some temporary registers. Look in `spur.md' to see how
1547 ;; the requirement can be satisfied.
1549 ;; During reload a memory reference with an invalid address may be passed as an
1550 ;; operand. Such an address will be replaced with a valid address later in the
1551 ;; reload pass. In this case, nothing may be done with the address except to
1552 ;; use it as it stands. If it is copied, it will not be replaced with a valid
1553 ;; address. No attempt should be made to make such an address into a valid
1554 ;; address and no routine (such as `change_address') that will do so may be
1555 ;; called. Note that `general_operand' will fail when applied to such an
1558 ;; The global variable `reload_in_progress' (which must be explicitly declared
1559 ;; if required) can be used to determine whether such special handling is
1562 ;; The variety of operands that have reloads depends on the rest of
1563 ;; the machine description, but typically on a RISC machine these can
1564 ;; only be pseudo registers that did not get hard registers, while on
1565 ;; other machines explicit memory references will get optional
1568 ;; If a scratch register is required to move an object to or from memory, it
1569 ;; can be allocated using `gen_reg_rtx' prior to reload. But this is
1570 ;; impossible during and after reload. If there are cases needing scratch
1571 ;; registers after reload, you must define `SECONDARY_INPUT_RELOAD_CLASS' and
1572 ;; perhaps also `SECONDARY_OUTPUT_RELOAD_CLASS' to detect them, and provide
1573 ;; patterns `reload_inM' or `reload_outM' to handle them.
1575 ;; The constraints on a `moveM' must permit moving any hard register to any
1576 ;; other hard register provided that `HARD_REGNO_MODE_OK' permits mode M in
1577 ;; both registers and `REGISTER_MOVE_COST' applied to their classes returns a
1580 ;; It is obligatory to support floating point `moveM' instructions
1581 ;; into and out of any registers that can hold fixed point values,
1582 ;; because unions and structures (which have modes `SImode' or
1583 ;; `DImode') can be in those registers and they may have floating
1586 ;; There may also be a need to support fixed point `moveM' instructions in and
1587 ;; out of floating point registers. Unfortunately, I have forgotten why this
1588 ;; was so, and I don't know whether it is still true. If `HARD_REGNO_MODE_OK'
1589 ;; rejects fixed point values in floating point registers, then the constraints
1590 ;; of the fixed point `moveM' instructions must be designed to avoid ever
1591 ;; trying to reload into a floating point register.
1593 (define_expand "movqi"
1594 [(set (match_operand:QI 0 "general_operand" "")
1595 (match_operand:QI 1 "general_operand" ""))]
1597 "{ frv_emit_move (QImode, operands[0], operands[1]); DONE; }")
1599 (define_insn "*movqi_load"
1600 [(set (match_operand:QI 0 "register_operand" "=d,f")
1601 (match_operand:QI 1 "frv_load_operand" "m,m"))]
1603 "* return output_move_single (operands, insn);"
1604 [(set_attr "length" "4")
1605 (set_attr "type" "gload,fload")])
1607 (define_insn "*movqi_internal"
1608 [(set (match_operand:QI 0 "move_destination_operand" "=d,d,m,m,?f,?f,?d,?m,f,d,f")
1609 (match_operand:QI 1 "move_source_operand" "L,d,d,O, d, f, f, f,GO,!m,!m"))]
1610 "register_operand(operands[0], QImode) || reg_or_0_operand (operands[1], QImode)"
1611 "* return output_move_single (operands, insn);"
1612 [(set_attr "length" "4")
1613 (set_attr "type" "int,int,gstore,gstore,movgf,fsconv,movfg,fstore,movgf,gload,fload")])
1615 (define_expand "movhi"
1616 [(set (match_operand:HI 0 "general_operand" "")
1617 (match_operand:HI 1 "general_operand" ""))]
1619 "{ frv_emit_move (HImode, operands[0], operands[1]); DONE; }")
1621 (define_insn "*movhi_load"
1622 [(set (match_operand:HI 0 "register_operand" "=d,f")
1623 (match_operand:HI 1 "frv_load_operand" "m,m"))]
1625 "* return output_move_single (operands, insn);"
1626 [(set_attr "length" "4")
1627 (set_attr "type" "gload,fload")])
1629 (define_insn "*movhi_internal"
1630 [(set (match_operand:HI 0 "move_destination_operand" "=d,d,d,m,m,?f,?f,?d,?m,f,d,f")
1631 (match_operand:HI 1 "move_source_operand" "L,n,d,d,O, d, f, f, f,GO,!m,!m"))]
1632 "register_operand(operands[0], HImode) || reg_or_0_operand (operands[1], HImode)"
1633 "* return output_move_single (operands, insn);"
1634 [(set_attr "length" "4,8,4,4,4,4,4,4,4,4,4,4")
1635 (set_attr "type" "int,multi,int,gstore,gstore,movgf,fsconv,movfg,fstore,movgf,gload,fload")])
1637 ;; Split 2 word load of constants into sethi/setlo instructions
1639 [(set (match_operand:HI 0 "integer_register_operand" "")
1640 (match_operand:HI 1 "int_2word_operand" ""))]
1643 (high:HI (match_dup 1)))
1645 (lo_sum:HI (match_dup 0)
1649 (define_insn "movhi_high"
1650 [(set (match_operand:HI 0 "integer_register_operand" "=d")
1651 (high:HI (match_operand:HI 1 "int_2word_operand" "i")))]
1654 [(set_attr "type" "sethi")
1655 (set_attr "length" "4")])
1657 (define_insn "movhi_lo_sum"
1658 [(set (match_operand:HI 0 "integer_register_operand" "+d")
1659 (lo_sum:HI (match_dup 0)
1660 (match_operand:HI 1 "int_2word_operand" "i")))]
1663 [(set_attr "type" "setlo")
1664 (set_attr "length" "4")])
1666 (define_expand "movsi"
1667 [(set (match_operand:SI 0 "move_destination_operand" "")
1668 (match_operand:SI 1 "move_source_operand" ""))]
1670 "{ frv_emit_move (SImode, operands[0], operands[1]); DONE; }")
1672 ;; Note - it is best to only have one movsi pattern and to handle
1673 ;; all the various contingencies by the use of alternatives. This
1674 ;; allows reload the greatest amount of flexibility (since reload will
1675 ;; only choose amongst alternatives for a selected insn, it will not
1676 ;; replace the insn with another one).
1678 ;; Unfortunately, we do have to separate out load-type moves from the rest,
1679 ;; and only allow memory source operands in the former. If we do memory and
1680 ;; constant loads in a single pattern, reload will be tempted to force
1681 ;; constants into memory when the destination is a floating-point register.
1682 ;; That may make a function use a PIC pointer when it didn't before, and we
1683 ;; cannot change PIC usage (and hence stack layout) so late in the game.
1684 ;; The resulting sequences for loading constants into FPRs are preferable
1685 ;; even when we're not generating PIC code.
1687 ;; However, if we don't accept input from memory at all in the generic
1688 ;; movsi pattern, reloads for asm instructions that reference pseudos
1689 ;; that end up assigned to memory will fail to match, because we
1690 ;; recognize them right after they're emitted, and we don't
1691 ;; re-recognize them again after the substitution for memory. So keep
1692 ;; a memory constraint available, just make sure reload won't be
1693 ;; tempted to use it.
1697 (define_insn "*movsi_load"
1698 [(set (match_operand:SI 0 "register_operand" "=d,f")
1699 (match_operand:SI 1 "frv_load_operand" "m,m"))]
1701 "* return output_move_single (operands, insn);"
1702 [(set_attr "length" "4")
1703 (set_attr "type" "gload,fload")])
1705 (define_insn "*movsi_got"
1706 [(set (match_operand:SI 0 "integer_register_operand" "=d")
1707 (match_operand:SI 1 "got12_operand" ""))]
1710 [(set_attr "type" "int")
1711 (set_attr "length" "4")])
1713 (define_insn "*movsi_high_got"
1714 [(set (match_operand:SI 0 "integer_register_operand" "=d")
1715 (high:SI (match_operand:SI 1 "const_unspec_operand" "")))]
1718 [(set_attr "type" "sethi")
1719 (set_attr "length" "4")])
1721 (define_insn "*movsi_lo_sum_got"
1722 [(set (match_operand:SI 0 "integer_register_operand" "=d")
1723 (lo_sum:SI (match_operand:SI 1 "integer_register_operand" "0")
1724 (match_operand:SI 2 "const_unspec_operand" "")))]
1727 [(set_attr "type" "setlo")
1728 (set_attr "length" "4")])
1730 (define_insn "*movsi_internal"
1731 [(set (match_operand:SI 0 "move_destination_operand" "=d,d,d,m,m,z,d,d,f,f,m,?f,?z,d,f")
1732 (match_operand:SI 1 "move_source_operand" "L,n,d,d,O,d,z,f,d,f,f,GO,GO,!m,!m"))]
1733 "register_operand (operands[0], SImode) || reg_or_0_operand (operands[1], SImode)"
1734 "* return output_move_single (operands, insn);"
1735 [(set_attr "length" "4,8,4,4,4,4,4,4,4,4,4,4,4,4,4")
1736 (set_attr "type" "int,multi,int,gstore,gstore,spr,spr,movfg,movgf,fsconv,fstore,movgf,spr,gload,fload")])
1738 ;; Split 2 word load of constants into sethi/setlo instructions
1739 (define_insn_and_split "*movsi_2word"
1740 [(set (match_operand:SI 0 "integer_register_operand" "=d")
1741 (match_operand:SI 1 "int_2word_operand" "i"))]
1746 (high:SI (match_dup 1)))
1748 (lo_sum:SI (match_dup 0)
1751 [(set_attr "length" "8")
1752 (set_attr "type" "multi")])
1754 (define_insn "movsi_high"
1755 [(set (match_operand:SI 0 "integer_register_operand" "=d")
1756 (high:SI (match_operand:SI 1 "int_2word_operand" "i")))]
1759 [(set_attr "type" "sethi")
1760 (set_attr "length" "4")])
1762 (define_insn "movsi_lo_sum"
1763 [(set (match_operand:SI 0 "integer_register_operand" "+d")
1764 (lo_sum:SI (match_dup 0)
1765 (match_operand:SI 1 "int_2word_operand" "i")))]
1768 [(set_attr "type" "setlo")
1769 (set_attr "length" "4")])
1771 (define_expand "movdi"
1772 [(set (match_operand:DI 0 "nonimmediate_operand" "")
1773 (match_operand:DI 1 "general_operand" ""))]
1775 "{ frv_emit_move (DImode, operands[0], operands[1]); DONE; }")
1777 (define_insn "*movdi_double"
1778 [(set (match_operand:DI 0 "move_destination_operand" "=e,?h,??d,??f,R,?R,??m,??m,e,?h,??d,??f,?e,??d,?h,??f,R,m,e,??d,e,??d,?h,??f")
1779 (match_operand:DI 1 "move_source_operand" " e,h,d,f,e,h,d,f,R,R,m,m,h,f,e,d,GO,GO,GO,GO,nF,nF,GO,GO"))]
1781 && (register_operand (operands[0], DImode)
1782 || reg_or_0_operand (operands[1], DImode))"
1783 "* return output_move_double (operands, insn);"
1784 [(set_attr "length" "8,4,8,8,4,4,8,8,4,4,8,8,4,8,4,8,4,8,8,8,16,16,8,8")
1785 (set_attr "type" "multi,fdconv,multi,multi,gstore,fstore,gstore,fstore,gload,fload,gload,fload,movfg,movfg,movgf,movgf,gstore,gstore,multi,multi,multi,multi,movgf,movgf")])
1787 (define_insn "*movdi_nodouble"
1788 [(set (match_operand:DI 0 "move_destination_operand" "=e,?h,??d,??f,R,?R,??m,??m,e,?h,??d,??f,?e,??d,?h,??f,R,m,e,??d,e,??d,?h,??f")
1789 (match_operand:DI 1 "move_source_operand" " e,h,d,f,e,h,d,f,R,R,m,m,h,f,e,d,GO,GO,GO,GO,nF,nF,GO,GO"))]
1791 && (register_operand (operands[0], DImode)
1792 || reg_or_0_operand (operands[1], DImode))"
1793 "* return output_move_double (operands, insn);"
1794 [(set_attr "length" "8,8,8,8,4,4,8,8,4,4,8,8,8,8,8,8,4,8,8,8,16,16,8,8")
1795 (set_attr "type" "multi,multi,multi,multi,gstore,fstore,gstore,fstore,gload,fload,gload,fload,movfg,movfg,movgf,movgf,gstore,gstore,multi,multi,multi,multi,movgf,movgf")])
1798 [(set (match_operand:DI 0 "register_operand" "")
1799 (match_operand:DI 1 "dbl_memory_two_insn_operand" ""))]
1802 "frv_split_double_load (operands[0], operands[1]);")
1805 [(set (match_operand:DI 0 "odd_reg_operand" "")
1806 (match_operand:DI 1 "memory_operand" ""))]
1809 "frv_split_double_load (operands[0], operands[1]);")
1812 [(set (match_operand:DI 0 "dbl_memory_two_insn_operand" "")
1813 (match_operand:DI 1 "reg_or_0_operand" ""))]
1816 "frv_split_double_store (operands[0], operands[1]);")
1819 [(set (match_operand:DI 0 "memory_operand" "")
1820 (match_operand:DI 1 "odd_reg_operand" ""))]
1823 "frv_split_double_store (operands[0], operands[1]);")
1826 [(set (match_operand:DI 0 "register_operand" "")
1827 (match_operand:DI 1 "register_operand" ""))]
1829 && (odd_reg_operand (operands[0], DImode)
1830 || odd_reg_operand (operands[1], DImode)
1831 || (integer_register_operand (operands[0], DImode)
1832 && integer_register_operand (operands[1], DImode))
1834 && fpr_operand (operands[0], DImode)
1835 && fpr_operand (operands[1], DImode)))"
1836 [(set (match_dup 2) (match_dup 4))
1837 (set (match_dup 3) (match_dup 5))]
1840 rtx op0 = operands[0];
1841 rtx op0_low = gen_lowpart (SImode, op0);
1842 rtx op0_high = gen_highpart (SImode, op0);
1843 rtx op1 = operands[1];
1844 rtx op1_low = gen_lowpart (SImode, op1);
1845 rtx op1_high = gen_highpart (SImode, op1);
1847 /* We normally copy the low-numbered register first. However, if the first
1848 register operand 0 is the same as the second register of operand 1, we
1849 must copy in the opposite order. */
1851 if (REGNO (op0_high) == REGNO (op1_low))
1853 operands[2] = op0_low;
1854 operands[3] = op0_high;
1855 operands[4] = op1_low;
1856 operands[5] = op1_high;
1860 operands[2] = op0_high;
1861 operands[3] = op0_low;
1862 operands[4] = op1_high;
1863 operands[5] = op1_low;
1868 [(set (match_operand:DI 0 "register_operand" "")
1869 (match_operand:DI 1 "const_int_operand" ""))]
1871 [(set (match_dup 2) (match_dup 4))
1872 (set (match_dup 3) (match_dup 5))]
1875 rtx op0 = operands[0];
1876 rtx op1 = operands[1];
1878 operands[2] = gen_highpart (SImode, op0);
1879 operands[3] = gen_lowpart (SImode, op0);
1880 if (HOST_BITS_PER_WIDE_INT <= 32)
1882 operands[4] = GEN_INT ((INTVAL (op1) < 0) ? -1 : 0);
1887 operands[4] = GEN_INT ((((unsigned HOST_WIDE_INT)INTVAL (op1) >> 16)
1888 >> 16) ^ ((unsigned HOST_WIDE_INT)1 << 31)
1889 - ((unsigned HOST_WIDE_INT)1 << 31));
1890 operands[5] = GEN_INT (trunc_int_for_mode (INTVAL (op1), SImode));
1895 [(set (match_operand:DI 0 "register_operand" "")
1896 (match_operand:DI 1 "const_double_operand" ""))]
1898 [(set (match_dup 2) (match_dup 4))
1899 (set (match_dup 3) (match_dup 5))]
1902 rtx op0 = operands[0];
1903 rtx op1 = operands[1];
1905 operands[2] = gen_highpart (SImode, op0);
1906 operands[3] = gen_lowpart (SImode, op0);
1907 operands[4] = GEN_INT (CONST_DOUBLE_HIGH (op1));
1908 operands[5] = GEN_INT (CONST_DOUBLE_LOW (op1));
1911 ;; Floating Point Moves
1913 ;; Note - Patterns for SF mode moves are compulsory, but
1914 ;; patterns for DF are optional, as GCC can synthesize them.
1916 (define_expand "movsf"
1917 [(set (match_operand:SF 0 "general_operand" "")
1918 (match_operand:SF 1 "general_operand" ""))]
1920 "{ frv_emit_move (SFmode, operands[0], operands[1]); DONE; }")
1923 [(set (match_operand:SF 0 "integer_register_operand" "")
1924 (match_operand:SF 1 "int_2word_operand" ""))]
1927 (high:SF (match_dup 1)))
1929 (lo_sum:SF (match_dup 0)
1933 (define_insn "*movsf_load_has_fprs"
1934 [(set (match_operand:SF 0 "register_operand" "=f,d")
1935 (match_operand:SF 1 "frv_load_operand" "m,m"))]
1937 "* return output_move_single (operands, insn);"
1938 [(set_attr "length" "4")
1939 (set_attr "type" "fload,gload")])
1941 (define_insn "*movsf_internal_has_fprs"
1942 [(set (match_operand:SF 0 "move_destination_operand" "=f,f,m,m,?f,?d,?d,m,?d")
1943 (match_operand:SF 1 "move_source_operand" "f,OG,f,OG,d,f,d,d,F"))]
1945 && (register_operand (operands[0], SFmode) || reg_or_0_operand (operands[1], SFmode))"
1946 "* return output_move_single (operands, insn);"
1947 [(set_attr "length" "4,4,4,4,4,4,4,4,8")
1948 (set_attr "type" "fsconv,movgf,fstore,gstore,movgf,movfg,int,gstore,multi")])
1950 ;; If we don't support the double instructions, prefer gprs over fprs, since it
1951 ;; will all be emulated
1952 (define_insn "*movsf_internal_no_fprs"
1953 [(set (match_operand:SF 0 "move_destination_operand" "=d,d,m,d,d")
1954 (match_operand:SF 1 "move_source_operand" " d,OG,dOG,m,F"))]
1956 && (register_operand (operands[0], SFmode) || reg_or_0_operand (operands[1], SFmode))"
1957 "* return output_move_single (operands, insn);"
1958 [(set_attr "length" "4,4,4,4,8")
1959 (set_attr "type" "int,int,gstore,gload,multi")])
1961 (define_insn "movsf_high"
1962 [(set (match_operand:SF 0 "integer_register_operand" "=d")
1963 (high:SF (match_operand:SF 1 "int_2word_operand" "i")))]
1966 [(set_attr "type" "sethi")
1967 (set_attr "length" "4")])
1969 (define_insn "movsf_lo_sum"
1970 [(set (match_operand:SF 0 "integer_register_operand" "+d")
1971 (lo_sum:SF (match_dup 0)
1972 (match_operand:SF 1 "int_2word_operand" "i")))]
1975 [(set_attr "type" "setlo")
1976 (set_attr "length" "4")])
1978 (define_expand "movdf"
1979 [(set (match_operand:DF 0 "nonimmediate_operand" "")
1980 (match_operand:DF 1 "general_operand" ""))]
1982 "{ frv_emit_move (DFmode, operands[0], operands[1]); DONE; }")
1984 (define_insn "*movdf_double"
1985 [(set (match_operand:DF 0 "move_destination_operand" "=h,?e,??f,??d,R,?R,??m,??m,h,?e,??f,??d,?h,??f,?e,??d,R,m,h,??f,e,??d,e,??d")
1986 (match_operand:DF 1 "move_source_operand" " h,e,f,d,h,e,f,d,R,R,m,m,e,d,h,f,GO,GO,GO,GO,GO,GO,F,F"))]
1988 && (register_operand (operands[0], DFmode)
1989 || reg_or_0_operand (operands[1], DFmode))"
1990 "* return output_move_double (operands, insn);"
1991 [(set_attr "length" "4,8,8,8,4,4,8,8,4,4,8,8,4,8,4,8,4,8,8,8,8,8,16,16")
1992 (set_attr "type" "fdconv,multi,multi,multi,fstore,gstore,fstore,gstore,fload,gload,fload,gload,movgf,movgf,movfg,movfg,gstore,gstore,movgf,movgf,multi,multi,multi,multi")])
1994 ;; If we don't support the double instructions, prefer gprs over fprs, since it
1995 ;; will all be emulated
1996 (define_insn "*movdf_nodouble"
1997 [(set (match_operand:DF 0 "move_destination_operand" "=e,?h,??d,??f,R,?R,??m,??m,e,?h,??d,??f,?e,??d,?h,??f,R,m,e,??d,e,??d,?h,??f")
1998 (match_operand:DF 1 "move_source_operand" " e,h,d,f,e,h,d,f,R,R,m,m,h,f,e,d,GO,GO,GO,GO,nF,nF,GO,GO"))]
2000 && (register_operand (operands[0], DFmode)
2001 || reg_or_0_operand (operands[1], DFmode))"
2002 "* return output_move_double (operands, insn);"
2003 [(set_attr "length" "8,8,8,8,4,4,8,8,4,4,8,8,8,8,8,8,4,8,8,8,16,16,8,8")
2004 (set_attr "type" "multi,multi,multi,multi,gstore,fstore,gstore,fstore,gload,fload,gload,fload,movfg,movfg,movgf,movgf,gstore,gstore,multi,multi,multi,multi,movgf,movgf")])
2007 [(set (match_operand:DF 0 "register_operand" "")
2008 (match_operand:DF 1 "dbl_memory_two_insn_operand" ""))]
2011 "frv_split_double_load (operands[0], operands[1]);")
2014 [(set (match_operand:DF 0 "odd_reg_operand" "")
2015 (match_operand:DF 1 "memory_operand" ""))]
2018 "frv_split_double_load (operands[0], operands[1]);")
2021 [(set (match_operand:DF 0 "dbl_memory_two_insn_operand" "")
2022 (match_operand:DF 1 "reg_or_0_operand" ""))]
2025 "frv_split_double_store (operands[0], operands[1]);")
2028 [(set (match_operand:DF 0 "memory_operand" "")
2029 (match_operand:DF 1 "odd_reg_operand" ""))]
2032 "frv_split_double_store (operands[0], operands[1]);")
2035 [(set (match_operand:DF 0 "register_operand" "")
2036 (match_operand:DF 1 "register_operand" ""))]
2038 && (odd_reg_operand (operands[0], DFmode)
2039 || odd_reg_operand (operands[1], DFmode)
2040 || (integer_register_operand (operands[0], DFmode)
2041 && integer_register_operand (operands[1], DFmode))
2043 && fpr_operand (operands[0], DFmode)
2044 && fpr_operand (operands[1], DFmode)))"
2045 [(set (match_dup 2) (match_dup 4))
2046 (set (match_dup 3) (match_dup 5))]
2049 rtx op0 = operands[0];
2050 rtx op0_low = gen_lowpart (SImode, op0);
2051 rtx op0_high = gen_highpart (SImode, op0);
2052 rtx op1 = operands[1];
2053 rtx op1_low = gen_lowpart (SImode, op1);
2054 rtx op1_high = gen_highpart (SImode, op1);
2056 /* We normally copy the low-numbered register first. However, if the first
2057 register operand 0 is the same as the second register of operand 1, we
2058 must copy in the opposite order. */
2060 if (REGNO (op0_high) == REGNO (op1_low))
2062 operands[2] = op0_low;
2063 operands[3] = op0_high;
2064 operands[4] = op1_low;
2065 operands[5] = op1_high;
2069 operands[2] = op0_high;
2070 operands[3] = op0_low;
2071 operands[4] = op1_high;
2072 operands[5] = op1_low;
2077 [(set (match_operand:DF 0 "register_operand" "")
2078 (match_operand:DF 1 "const_int_operand" ""))]
2080 [(set (match_dup 2) (match_dup 4))
2081 (set (match_dup 3) (match_dup 5))]
2084 rtx op0 = operands[0];
2085 rtx op1 = operands[1];
2087 operands[2] = gen_highpart (SImode, op0);
2088 operands[3] = gen_lowpart (SImode, op0);
2089 if (HOST_BITS_PER_WIDE_INT <= 32)
2091 operands[4] = GEN_INT ((INTVAL (op1) < 0) ? -1 : 0);
2096 operands[4] = GEN_INT ((((unsigned HOST_WIDE_INT)INTVAL (op1) >> 16)
2097 >> 16) ^ ((unsigned HOST_WIDE_INT)1 << 31)
2098 - ((unsigned HOST_WIDE_INT)1 << 31));
2099 operands[5] = GEN_INT (trunc_int_for_mode (INTVAL (op1), SImode));
2104 [(set (match_operand:DF 0 "register_operand" "")
2105 (match_operand:DF 1 "const_double_operand" ""))]
2107 [(set (match_dup 2) (match_dup 4))
2108 (set (match_dup 3) (match_dup 5))]
2111 rtx op0 = operands[0];
2112 rtx op1 = operands[1];
2116 REAL_VALUE_FROM_CONST_DOUBLE (rv, op1);
2117 REAL_VALUE_TO_TARGET_DOUBLE (rv, l);
2119 operands[2] = gen_highpart (SImode, op0);
2120 operands[3] = gen_lowpart (SImode, op0);
2121 operands[4] = GEN_INT (l[0]);
2122 operands[5] = GEN_INT (l[1]);
2125 ;; String/block move insn.
2126 ;; Argument 0 is the destination
2127 ;; Argument 1 is the source
2128 ;; Argument 2 is the length
2129 ;; Argument 3 is the alignment
2131 (define_expand "movmemsi"
2132 [(parallel [(set (match_operand:BLK 0 "" "")
2133 (match_operand:BLK 1 "" ""))
2134 (use (match_operand:SI 2 "" ""))
2135 (use (match_operand:SI 3 "" ""))])]
2139 if (frv_expand_block_move (operands))
2145 ;; String/block set insn.
2146 ;; Argument 0 is the destination
2147 ;; Argument 1 is the length
2148 ;; Argument 2 is the byte value -- ignore any value but zero
2149 ;; Argument 3 is the alignment
2151 (define_expand "setmemsi"
2152 [(parallel [(set (match_operand:BLK 0 "" "")
2153 (match_operand 2 "" ""))
2154 (use (match_operand:SI 1 "" ""))
2155 (use (match_operand:SI 3 "" ""))])]
2159 /* If value to set is not zero, use the library routine. */
2160 if (operands[2] != const0_rtx)
2163 if (frv_expand_block_clear (operands))
2170 ;; The "membar" part of a __builtin_read* or __builtin_write* function.
2171 ;; Operand 0 is a volatile reference to the memory that the function reads
2172 ;; or writes. Operand 1 is the address being accessed, or zero if the
2173 ;; address isn't a known constant. Operand 2 describes the __builtin
2174 ;; function (either FRV_IO_READ or FRV_IO_WRITE).
2175 (define_insn "optional_membar_<mode>"
2176 [(set (match_operand:IMODE 0 "memory_operand" "=m")
2177 (unspec:IMODE [(match_operand 1 "const_int_operand" "")
2178 (match_operand 2 "const_int_operand" "")]
2179 UNSPEC_OPTIONAL_MEMBAR))]
2182 [(set_attr "length" "4")])
2184 ;; ::::::::::::::::::::
2186 ;; :: Reload CC registers
2188 ;; ::::::::::::::::::::
2190 ;; Use as a define_expand so that cse/gcse/combine can't accidentally
2191 ;; create movcc insns.
2193 (define_expand "movcc"
2194 [(parallel [(set (match_operand:CC 0 "move_destination_operand" "")
2195 (match_operand:CC 1 "move_source_operand" ""))
2196 (clobber (match_dup 2))])]
2200 if (! reload_in_progress && ! reload_completed)
2203 operands[2] = gen_rtx_REG (CC_CCRmode, ICR_TEMP);
2206 (define_insn "*internal_movcc"
2207 [(set (match_operand:CC 0 "move_destination_operand" "=t,d,d,m,d")
2208 (match_operand:CC 1 "move_source_operand" "d,d,m,d,t"))
2209 (clobber (match_scratch:CC_CCR 2 "=X,X,X,X,&v"))]
2210 "reload_in_progress || reload_completed"
2217 [(set_attr "length" "4,4,4,4,20")
2218 (set_attr "type" "int,int,gload,gstore,multi")])
2220 ;; To move an ICC value to a GPR for a signed comparison, we create a value
2221 ;; that when compared to 0, sets the N and Z flags appropriately (we don't care
2222 ;; about the V and C flags, since these comparisons are signed).
2225 [(set (match_operand:CC 0 "integer_register_operand" "")
2226 (match_operand:CC 1 "icc_operand" ""))
2227 (clobber (match_operand:CC_CCR 2 "icr_operand" ""))]
2228 "reload_in_progress || reload_completed"
2232 rtx dest = simplify_gen_subreg (SImode, operands[0], CCmode, 0);
2233 rtx icc = operands[1];
2234 rtx icr = operands[2];
2238 emit_insn (gen_rtx_SET (VOIDmode, icr,
2239 gen_rtx_LT (CC_CCRmode, icc, const0_rtx)));
2241 emit_insn (gen_movsi (dest, const1_rtx));
2243 emit_insn (gen_rtx_COND_EXEC (VOIDmode,
2244 gen_rtx_NE (CC_CCRmode, icr, const0_rtx),
2245 gen_rtx_SET (VOIDmode, dest,
2246 gen_rtx_NEG (SImode, dest))));
2248 emit_insn (gen_rtx_SET (VOIDmode, icr,
2249 gen_rtx_EQ (CC_CCRmode, icc, const0_rtx)));
2251 emit_insn (gen_rtx_COND_EXEC (VOIDmode,
2252 gen_rtx_NE (CC_CCRmode, icr, const0_rtx),
2253 gen_rtx_SET (VOIDmode, dest, const0_rtx)));
2255 operands[3] = get_insns ();
2259 (define_expand "reload_incc"
2260 [(parallel [(set (match_operand:CC 2 "integer_register_operand" "=&d")
2261 (match_operand:CC 1 "memory_operand" "m"))
2262 (clobber (match_scratch:CC_CCR 3 ""))])
2263 (parallel [(set (match_operand:CC 0 "icc_operand" "=t")
2265 (clobber (match_scratch:CC_CCR 4 ""))])]
2269 (define_expand "reload_outcc"
2270 [(parallel [(set (match_operand:CC 2 "integer_register_operand" "=&d")
2271 (match_operand:CC 1 "icc_operand" "t"))
2272 (clobber (match_dup 3))])
2273 (parallel [(set (match_operand:CC 0 "memory_operand" "=m")
2275 (clobber (match_scratch:CC_CCR 4 ""))])]
2277 "operands[3] = gen_rtx_REG (CC_CCRmode, ICR_TEMP);")
2279 ;; Reload CC_UNSmode for unsigned integer comparisons
2280 ;; Use define_expand so that cse/gcse/combine can't create movcc_uns insns
2282 (define_expand "movcc_uns"
2283 [(parallel [(set (match_operand:CC_UNS 0 "move_destination_operand" "")
2284 (match_operand:CC_UNS 1 "move_source_operand" ""))
2285 (clobber (match_dup 2))])]
2289 if (! reload_in_progress && ! reload_completed)
2291 operands[2] = gen_rtx_REG (CC_CCRmode, ICR_TEMP);
2294 (define_insn "*internal_movcc_uns"
2295 [(set (match_operand:CC_UNS 0 "move_destination_operand" "=t,d,d,m,d")
2296 (match_operand:CC_UNS 1 "move_source_operand" "d,d,m,d,t"))
2297 (clobber (match_scratch:CC_CCR 2 "=X,X,X,X,&v"))]
2298 "reload_in_progress || reload_completed"
2305 [(set_attr "length" "4,4,4,4,20")
2306 (set_attr "type" "int,int,gload,gstore,multi")])
2308 ;; To move an ICC value to a GPR for an unsigned comparison, we create a value
2309 ;; that when compared to 1, sets the Z, V, and C flags appropriately (we don't
2310 ;; care about the N flag, since these comparisons are unsigned).
2313 [(set (match_operand:CC_UNS 0 "integer_register_operand" "")
2314 (match_operand:CC_UNS 1 "icc_operand" ""))
2315 (clobber (match_operand:CC_CCR 2 "icr_operand" ""))]
2316 "reload_in_progress || reload_completed"
2320 rtx dest = simplify_gen_subreg (SImode, operands[0], CC_UNSmode, 0);
2321 rtx icc = operands[1];
2322 rtx icr = operands[2];
2326 emit_insn (gen_rtx_SET (VOIDmode, icr,
2327 gen_rtx_GTU (CC_CCRmode, icc, const0_rtx)));
2329 emit_insn (gen_movsi (dest, const1_rtx));
2331 emit_insn (gen_rtx_COND_EXEC (VOIDmode,
2332 gen_rtx_NE (CC_CCRmode, icr, const0_rtx),
2333 gen_addsi3 (dest, dest, dest)));
2335 emit_insn (gen_rtx_SET (VOIDmode, icr,
2336 gen_rtx_LTU (CC_CCRmode, icc, const0_rtx)));
2338 emit_insn (gen_rtx_COND_EXEC (VOIDmode,
2339 gen_rtx_NE (CC_CCRmode, icr, const0_rtx),
2340 gen_rtx_SET (VOIDmode, dest, const0_rtx)));
2342 operands[3] = get_insns ();
2346 (define_expand "reload_incc_uns"
2347 [(parallel [(set (match_operand:CC_UNS 2 "integer_register_operand" "=&d")
2348 (match_operand:CC_UNS 1 "memory_operand" "m"))
2349 (clobber (match_scratch:CC_CCR 3 ""))])
2350 (parallel [(set (match_operand:CC_UNS 0 "icc_operand" "=t")
2352 (clobber (match_scratch:CC_CCR 4 ""))])]
2356 (define_expand "reload_outcc_uns"
2357 [(parallel [(set (match_operand:CC_UNS 2 "integer_register_operand" "=&d")
2358 (match_operand:CC_UNS 1 "icc_operand" "t"))
2359 (clobber (match_dup 3))])
2360 (parallel [(set (match_operand:CC_UNS 0 "memory_operand" "=m")
2362 (clobber (match_scratch:CC_CCR 4 ""))])]
2364 "operands[3] = gen_rtx_REG (CC_CCRmode, ICR_TEMP);")
2366 ;; Reload CC_NZmode. This is mostly the same as the CCmode and CC_UNSmode
2367 ;; handling, but it uses different sequences for moving between GPRs and ICCs.
2369 (define_expand "movcc_nz"
2370 [(parallel [(set (match_operand:CC_NZ 0 "move_destination_operand" "")
2371 (match_operand:CC_NZ 1 "move_source_operand" ""))
2372 (clobber (match_dup 2))])]
2376 if (!reload_in_progress && !reload_completed)
2378 operands[2] = gen_rtx_REG (CC_CCRmode, ICR_TEMP);
2381 (define_insn "*internal_movcc_nz"
2382 [(set (match_operand:CC_NZ 0 "move_destination_operand" "=t,d,d,m,d")
2383 (match_operand:CC_NZ 1 "move_source_operand" "d,d,m,d,t"))
2384 (clobber (match_scratch:CC_CCR 2 "=X,X,X,X,&v"))]
2385 "reload_in_progress || reload_completed"
2392 [(set_attr "length" "4,4,4,4,20")
2393 (set_attr "type" "int,int,gload,gstore,multi")])
2395 ;; Set the destination to a value that, when compared with zero, will
2396 ;; restore the value of the Z and N flags. The values of the other
2397 ;; flags don't matter. The sequence is:
2401 ;; csub gr0,op0,op0,op2
2405 [(set (match_operand:CC_NZ 0 "integer_register_operand" "")
2406 (match_operand:CC_NZ 1 "icc_operand" ""))
2407 (clobber (match_operand:CC_CCR 2 "icr_operand" ""))]
2408 "reload_in_progress || reload_completed"
2412 (ge:CC_CCR (match_dup 1)
2414 (cond_exec (ne:CC_CCR (match_dup 2)
2417 (neg:SI (match_dup 3))))
2419 (eq:CC_CCR (match_dup 1)
2421 (cond_exec (ne:CC_CCR (match_dup 2)
2423 (set (match_dup 3) (const_int 0)))]
2424 "operands[3] = simplify_gen_subreg (SImode, operands[0], CC_NZmode, 0);")
2426 (define_expand "reload_incc_nz"
2427 [(parallel [(set (match_operand:CC_NZ 2 "integer_register_operand" "=&d")
2428 (match_operand:CC_NZ 1 "memory_operand" "m"))
2429 (clobber (match_scratch:CC_CCR 3 ""))])
2430 (parallel [(set (match_operand:CC_NZ 0 "icc_operand" "=t")
2432 (clobber (match_scratch:CC_CCR 4 ""))])]
2436 (define_expand "reload_outcc_nz"
2437 [(parallel [(set (match_operand:CC_NZ 2 "integer_register_operand" "=&d")
2438 (match_operand:CC_NZ 1 "icc_operand" "t"))
2439 (clobber (match_dup 3))])
2440 (parallel [(set (match_operand:CC_NZ 0 "memory_operand" "=m")
2442 (clobber (match_scratch:CC_CCR 4 ""))])]
2444 "operands[3] = gen_rtx_REG (CC_CCRmode, ICR_TEMP);")
2446 ;; Reload CC_FPmode for floating point comparisons
2447 ;; We use a define_expand here so that cse/gcse/combine can't accidentally
2448 ;; create movcc insns. If this was a named define_insn, we would not be able
2449 ;; to make it conditional on reload.
2451 (define_expand "movcc_fp"
2452 [(set (match_operand:CC_FP 0 "movcc_fp_destination_operand" "")
2453 (match_operand:CC_FP 1 "move_source_operand" ""))]
2457 if (! reload_in_progress && ! reload_completed)
2461 (define_insn "*movcc_fp_internal"
2462 [(set (match_operand:CC_FP 0 "movcc_fp_destination_operand" "=d,d,d,m")
2463 (match_operand:CC_FP 1 "move_source_operand" "u,d,m,d"))]
2464 "TARGET_HAS_FPRS && (reload_in_progress || reload_completed)"
2470 [(set_attr "length" "12,4,4,4")
2471 (set_attr "type" "multi,int,gload,gstore")])
2474 (define_expand "reload_incc_fp"
2475 [(match_operand:CC_FP 0 "fcc_operand" "=u")
2476 (match_operand:CC_FP 1 "gpr_or_memory_operand_with_scratch" "m")
2477 (match_operand:TI 2 "integer_register_operand" "=&d")]
2481 rtx cc_op2 = simplify_gen_subreg (CC_FPmode, operands[2], TImode, 0);
2482 rtx int_op2 = simplify_gen_subreg (SImode, operands[2], TImode, 0);
2483 rtx temp1 = simplify_gen_subreg (SImode, operands[2], TImode, 4);
2484 rtx temp2 = simplify_gen_subreg (SImode, operands[2], TImode, 8);
2485 int shift = CC_SHIFT_RIGHT (REGNO (operands[0]));
2488 if (!gpr_or_memory_operand (operands[1], CC_FPmode))
2491 rtx temp3 = simplify_gen_subreg (SImode, operands[2], TImode, 12);
2493 gcc_assert (GET_CODE (operands[1]) == MEM);
2495 addr = XEXP (operands[1], 0);
2497 gcc_assert (GET_CODE (addr) == PLUS);
2499 emit_move_insn (temp3, XEXP (addr, 1));
2501 operands[1] = replace_equiv_address (operands[1],
2502 gen_rtx_PLUS (GET_MODE (addr),
2507 emit_insn (gen_movcc_fp (cc_op2, operands[1]));
2509 emit_insn (gen_ashlsi3 (int_op2, int_op2, GEN_INT (shift)));
2511 mask = ~ ((HOST_WIDE_INT)CC_MASK << shift);
2512 emit_insn (gen_movsi (temp1, GEN_INT (mask)));
2513 emit_insn (gen_update_fcc (operands[0], int_op2, temp1, temp2));
2517 (define_expand "reload_outcc_fp"
2518 [(set (match_operand:CC_FP 2 "integer_register_operand" "=&d")
2519 (match_operand:CC_FP 1 "fcc_operand" "u"))
2520 (set (match_operand:CC_FP 0 "memory_operand" "=m")
2525 ;; Convert a FCC value to gpr
2526 (define_insn "read_fcc"
2527 [(set (match_operand:SI 0 "integer_register_operand" "=d")
2528 (unspec:SI [(match_operand:CC_FP 1 "fcc_operand" "u")]
2532 [(set_attr "type" "spr")
2533 (set_attr "length" "4")])
2536 [(set (match_operand:CC_FP 0 "integer_register_operand" "")
2537 (match_operand:CC_FP 1 "fcc_operand" ""))]
2538 "reload_completed && TARGET_HAS_FPRS"
2542 rtx int_op0 = simplify_gen_subreg (SImode, operands[0], CC_FPmode, 0);
2543 int shift = CC_SHIFT_RIGHT (REGNO (operands[1]));
2547 emit_insn (gen_read_fcc (int_op0, operands[1]));
2549 emit_insn (gen_lshrsi3 (int_op0, int_op0, GEN_INT (shift)));
2551 emit_insn (gen_andsi3 (int_op0, int_op0, GEN_INT (CC_MASK)));
2553 operands[2] = get_insns ();
2557 ;; Move a gpr value to FCC.
2559 ;; Operand1 = reloaded value shifted appropriately
2560 ;; Operand2 = mask to eliminate current register
2561 ;; Operand3 = temporary to load/store ccr
2562 (define_insn "update_fcc"
2563 [(set (match_operand:CC_FP 0 "fcc_operand" "=u")
2564 (unspec:CC_FP [(match_operand:SI 1 "integer_register_operand" "d")
2565 (match_operand:SI 2 "integer_register_operand" "d")]
2567 (clobber (match_operand:SI 3 "integer_register_operand" "=&d"))]
2569 "movsg ccr, %3\;and %2, %3, %3\;or %1, %3, %3\;movgs %3, ccr"
2570 [(set_attr "type" "multi")
2571 (set_attr "length" "16")])
2573 ;; Reload CC_CCRmode for conditional execution registers
2574 (define_insn "movcc_ccr"
2575 [(set (match_operand:CC_CCR 0 "move_destination_operand" "=d,d,d,m,v,?w,C,d")
2576 (match_operand:CC_CCR 1 "move_source_operand" "C,d,m,d,n,n,C,L"))]
2587 [(set_attr "length" "8,4,4,4,8,12,4,4")
2588 (set_attr "type" "multi,int,gload,gstore,multi,multi,ccr,int")])
2590 (define_expand "reload_incc_ccr"
2591 [(match_operand:CC_CCR 0 "cr_operand" "=C")
2592 (match_operand:CC_CCR 1 "memory_operand" "m")
2593 (match_operand:CC_CCR 2 "integer_register_operand" "=&d")]
2597 rtx icc = gen_rtx_REG (CCmode, ICC_TEMP);
2598 rtx int_op2 = simplify_gen_subreg (SImode, operands[2], CC_CCRmode, 0);
2599 rtx icr = (ICR_P (REGNO (operands[0]))
2600 ? operands[0] : gen_rtx_REG (CC_CCRmode, ICR_TEMP));
2602 emit_insn (gen_movcc_ccr (operands[2], operands[1]));
2603 emit_insn (gen_cmpsi_cc (icc, int_op2, const0_rtx));
2604 emit_insn (gen_movcc_ccr (icr, gen_rtx_NE (CC_CCRmode, icc, const0_rtx)));
2606 if (! ICR_P (REGNO (operands[0])))
2607 emit_insn (gen_movcc_ccr (operands[0], icr));
2612 (define_expand "reload_outcc_ccr"
2613 [(set (match_operand:CC_CCR 2 "integer_register_operand" "=&d")
2614 (match_operand:CC_CCR 1 "cr_operand" "C"))
2615 (set (match_operand:CC_CCR 0 "memory_operand" "=m")
2621 [(set (match_operand:CC_CCR 0 "integer_register_operand" "")
2622 (match_operand:CC_CCR 1 "cr_operand" ""))]
2627 rtx int_op0 = simplify_gen_subreg (SImode, operands[0], CC_CCRmode, 0);
2630 emit_move_insn (operands[0], const1_rtx);
2631 emit_insn (gen_rtx_COND_EXEC (VOIDmode,
2632 gen_rtx_EQ (CC_CCRmode,
2635 gen_rtx_SET (VOIDmode, int_op0,
2638 operands[2] = get_insns ();
2643 [(set (match_operand:CC_CCR 0 "cr_operand" "")
2644 (match_operand:CC_CCR 1 "const_int_operand" ""))]
2649 rtx icc = gen_rtx_REG (CCmode, ICC_TEMP);
2650 rtx r0 = gen_rtx_REG (SImode, GPR_FIRST);
2651 rtx icr = (ICR_P (REGNO (operands[0]))
2652 ? operands[0] : gen_rtx_REG (CC_CCRmode, ICR_TEMP));
2656 emit_insn (gen_cmpsi_cc (icc, r0, const0_rtx));
2658 emit_insn (gen_movcc_ccr (icr,
2659 gen_rtx_fmt_ee (((INTVAL (operands[1]) == 0)
2660 ? EQ : NE), CC_CCRmode,
2663 if (! ICR_P (REGNO (operands[0])))
2664 emit_insn (gen_movcc_ccr (operands[0], icr));
2666 operands[2] = get_insns ();
2671 ;; ::::::::::::::::::::
2675 ;; ::::::::::::::::::::
2677 ;; Signed conversions from a smaller integer to a larger integer
2679 ;; These operations are optional. If they are not
2680 ;; present GCC will synthesize them for itself
2681 ;; Even though frv does not provide these instructions, we define them
2682 ;; to allow load + sign extend to be collapsed together
2683 (define_insn "extendqihi2"
2684 [(set (match_operand:HI 0 "integer_register_operand" "=d,d")
2685 (sign_extend:HI (match_operand:QI 1 "gpr_or_memory_operand" "d,m")))]
2690 [(set_attr "length" "8,4")
2691 (set_attr "type" "multi,gload")])
2694 [(set (match_operand:HI 0 "integer_register_operand" "")
2695 (sign_extend:HI (match_operand:QI 1 "integer_register_operand" "")))]
2701 rtx op0 = gen_lowpart (SImode, operands[0]);
2702 rtx op1 = gen_lowpart (SImode, operands[1]);
2703 rtx shift = GEN_INT (24);
2705 operands[2] = gen_ashlsi3 (op0, op1, shift);
2706 operands[3] = gen_ashrsi3 (op0, op0, shift);
2709 (define_insn "extendqisi2"
2710 [(set (match_operand:SI 0 "integer_register_operand" "=d,d")
2711 (sign_extend:SI (match_operand:QI 1 "gpr_or_memory_operand" "d,m")))]
2716 [(set_attr "length" "8,4")
2717 (set_attr "type" "multi,gload")])
2720 [(set (match_operand:SI 0 "integer_register_operand" "")
2721 (sign_extend:SI (match_operand:QI 1 "integer_register_operand" "")))]
2727 rtx op0 = gen_lowpart (SImode, operands[0]);
2728 rtx op1 = gen_lowpart (SImode, operands[1]);
2729 rtx shift = GEN_INT (24);
2731 operands[2] = gen_ashlsi3 (op0, op1, shift);
2732 operands[3] = gen_ashrsi3 (op0, op0, shift);
2735 ;;(define_insn "extendqidi2"
2736 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2737 ;; (sign_extend:DI (match_operand:QI 1 "general_operand" "g")))]
2739 ;; "extendqihi2 %0,%1"
2740 ;; [(set_attr "length" "4")])
2742 (define_insn "extendhisi2"
2743 [(set (match_operand:SI 0 "integer_register_operand" "=d,d")
2744 (sign_extend:SI (match_operand:HI 1 "gpr_or_memory_operand" "d,m")))]
2749 [(set_attr "length" "8,4")
2750 (set_attr "type" "multi,gload")])
2753 [(set (match_operand:SI 0 "integer_register_operand" "")
2754 (sign_extend:SI (match_operand:HI 1 "integer_register_operand" "")))]
2760 rtx op0 = gen_lowpart (SImode, operands[0]);
2761 rtx op1 = gen_lowpart (SImode, operands[1]);
2762 rtx shift = GEN_INT (16);
2764 operands[2] = gen_ashlsi3 (op0, op1, shift);
2765 operands[3] = gen_ashrsi3 (op0, op0, shift);
2768 ;;(define_insn "extendhidi2"
2769 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2770 ;; (sign_extend:DI (match_operand:HI 1 "general_operand" "g")))]
2772 ;; "extendhihi2 %0,%1"
2773 ;; [(set_attr "length" "4")])
2775 ;;(define_insn "extendsidi2"
2776 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2777 ;; (sign_extend:DI (match_operand:SI 1 "general_operand" "g")))]
2779 ;; "extendsidi2 %0,%1"
2780 ;; [(set_attr "length" "4")])
2782 ;; Unsigned conversions from a smaller integer to a larger integer
2783 (define_insn "zero_extendqihi2"
2784 [(set (match_operand:HI 0 "integer_register_operand" "=d,d,d")
2786 (match_operand:QI 1 "gpr_or_memory_operand" "d,L,m")))]
2792 [(set_attr "length" "4")
2793 (set_attr "type" "int,int,gload")])
2795 (define_insn "zero_extendqisi2"
2796 [(set (match_operand:SI 0 "integer_register_operand" "=d,d,d")
2798 (match_operand:QI 1 "gpr_or_memory_operand" "d,L,m")))]
2804 [(set_attr "length" "4")
2805 (set_attr "type" "int,int,gload")])
2807 ;;(define_insn "zero_extendqidi2"
2808 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2809 ;; (zero_extend:DI (match_operand:QI 1 "general_operand" "g")))]
2811 ;; "zero_extendqihi2 %0,%1"
2812 ;; [(set_attr "length" "4")])
2814 ;; Do not set the type for the sethi to "sethi", since the scheduler will think
2815 ;; the sethi takes 0 cycles as part of allowing sethi/setlo to be in the same
2816 ;; VLIW instruction.
2817 (define_insn "zero_extendhisi2"
2818 [(set (match_operand:SI 0 "integer_register_operand" "=d,d")
2819 (zero_extend:SI (match_operand:HI 1 "gpr_or_memory_operand" "0,m")))]
2824 [(set_attr "length" "4")
2825 (set_attr "type" "int,gload")])
2827 ;;(define_insn "zero_extendhidi2"
2828 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2829 ;; (zero_extend:DI (match_operand:HI 1 "general_operand" "g")))]
2831 ;; "zero_extendhihi2 %0,%1"
2832 ;; [(set_attr "length" "4")])
2834 ;;(define_insn "zero_extendsidi2"
2835 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2836 ;; (zero_extend:DI (match_operand:SI 1 "general_operand" "g")))]
2838 ;; "zero_extendsidi2 %0,%1"
2839 ;; [(set_attr "length" "4")])
2841 ;;;; Convert between floating point types of different sizes.
2843 ;;(define_insn "extendsfdf2"
2844 ;; [(set (match_operand:DF 0 "register_operand" "=r")
2845 ;; (float_extend:DF (match_operand:SF 1 "register_operand" "r")))]
2847 ;; "extendsfdf2 %0,%1"
2848 ;; [(set_attr "length" "4")])
2850 ;;(define_insn "truncdfsf2"
2851 ;; [(set (match_operand:SF 0 "register_operand" "=r")
2852 ;; (float_truncate:SF (match_operand:DF 1 "register_operand" "r")))]
2854 ;; "truncdfsf2 %0,%1"
2855 ;; [(set_attr "length" "4")])
2857 ;;;; Convert between signed integer types and floating point.
2858 (define_insn "floatsisf2"
2859 [(set (match_operand:SF 0 "fpr_operand" "=f")
2860 (float:SF (match_operand:SI 1 "fpr_operand" "f")))]
2863 [(set_attr "length" "4")
2864 (set_attr "type" "fsconv")])
2866 (define_insn "floatsidf2"
2867 [(set (match_operand:DF 0 "fpr_operand" "=h")
2868 (float:DF (match_operand:SI 1 "fpr_operand" "f")))]
2869 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
2871 [(set_attr "length" "4")
2872 (set_attr "type" "fdconv")])
2874 ;;(define_insn "floatdisf2"
2875 ;; [(set (match_operand:SF 0 "register_operand" "=r")
2876 ;; (float:SF (match_operand:DI 1 "register_operand" "r")))]
2878 ;; "floatdisf2 %0,%1"
2879 ;; [(set_attr "length" "4")])
2881 ;;(define_insn "floatdidf2"
2882 ;; [(set (match_operand:DF 0 "register_operand" "=r")
2883 ;; (float:DF (match_operand:DI 1 "register_operand" "r")))]
2885 ;; "floatdidf2 %0,%1"
2886 ;; [(set_attr "length" "4")])
2888 (define_insn "fix_truncsfsi2"
2889 [(set (match_operand:SI 0 "fpr_operand" "=f")
2890 (fix:SI (match_operand:SF 1 "fpr_operand" "f")))]
2893 [(set_attr "length" "4")
2894 (set_attr "type" "fsconv")])
2896 (define_insn "fix_truncdfsi2"
2897 [(set (match_operand:SI 0 "fpr_operand" "=f")
2898 (fix:SI (match_operand:DF 1 "fpr_operand" "h")))]
2899 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
2901 [(set_attr "length" "4")
2902 (set_attr "type" "fdconv")])
2904 ;;(define_insn "fix_truncsfdi2"
2905 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2906 ;; (fix:DI (match_operand:SF 1 "register_operand" "r")))]
2908 ;; "fix_truncsfdi2 %0,%1"
2909 ;; [(set_attr "length" "4")])
2911 ;;(define_insn "fix_truncdfdi2"
2912 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2913 ;; (fix:DI (match_operand:DF 1 "register_operand" "r")))]
2915 ;; "fix_truncdfdi2 %0,%1"
2916 ;; [(set_attr "length" "4")])
2918 ;;;; Convert between unsigned integer types and floating point.
2920 ;;(define_insn "floatunssisf2"
2921 ;; [(set (match_operand:SF 0 "register_operand" "=r")
2922 ;; (unsigned_float:SF (match_operand:SI 1 "register_operand" "r")))]
2924 ;; "floatunssisf2 %0,%1"
2925 ;; [(set_attr "length" "4")])
2927 ;;(define_insn "floatunssidf2"
2928 ;; [(set (match_operand:DF 0 "register_operand" "=r")
2929 ;; (unsigned_float:DF (match_operand:SI 1 "register_operand" "r")))]
2931 ;; "floatunssidf2 %0,%1"
2932 ;; [(set_attr "length" "4")])
2934 ;;(define_insn "floatunsdisf2"
2935 ;; [(set (match_operand:SF 0 "register_operand" "=r")
2936 ;; (unsigned_float:SF (match_operand:DI 1 "register_operand" "r")))]
2938 ;; "floatunsdisf2 %0,%1"
2939 ;; [(set_attr "length" "4")])
2941 ;;(define_insn "floatunsdidf2"
2942 ;; [(set (match_operand:DF 0 "register_operand" "=r")
2943 ;; (unsigned_float:DF (match_operand:DI 1 "register_operand" "r")))]
2945 ;; "floatunsdidf2 %0,%1"
2946 ;; [(set_attr "length" "4")])
2948 ;;(define_insn "fixuns_truncsfsi2"
2949 ;; [(set (match_operand:SI 0 "register_operand" "=r")
2950 ;; (unsigned_fix:SI (match_operand:SF 1 "register_operand" "r")))]
2952 ;; "fixuns_truncsfsi2 %0,%1"
2953 ;; [(set_attr "length" "4")])
2955 ;;(define_insn "fixuns_truncdfsi2"
2956 ;; [(set (match_operand:SI 0 "register_operand" "=r")
2957 ;; (unsigned_fix:SI (match_operand:DF 1 "register_operand" "r")))]
2959 ;; "fixuns_truncdfsi2 %0,%1"
2960 ;; [(set_attr "length" "4")])
2962 ;;(define_insn "fixuns_truncsfdi2"
2963 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2964 ;; (unsigned_fix:DI (match_operand:SF 1 "register_operand" "r")))]
2966 ;; "fixuns_truncsfdi2 %0,%1"
2967 ;; [(set_attr "length" "4")])
2969 ;;(define_insn "fixuns_truncdfdi2"
2970 ;; [(set (match_operand:DI 0 "register_operand" "=r")
2971 ;; (unsigned_fix:DI (match_operand:DF 1 "register_operand" "r")))]
2973 ;; "fixuns_truncdfdi2 %0,%1"
2974 ;; [(set_attr "length" "4")])
2977 ;; ::::::::::::::::::::
2979 ;; :: 32 bit Integer arithmetic
2981 ;; ::::::::::::::::::::
2984 (define_insn "addsi3"
2985 [(set (match_operand:SI 0 "integer_register_operand" "=d")
2986 (plus:SI (match_operand:SI 1 "integer_register_operand" "%d")
2987 (match_operand:SI 2 "gpr_or_int12_operand" "dNOPQ")))]
2990 [(set_attr "length" "4")
2991 (set_attr "type" "int")])
2993 ;; Subtraction. No need to worry about constants, since the compiler
2994 ;; canonicalizes them into addsi3's. We prevent SUBREG's here to work around a
2995 ;; combine bug, that combines the 32x32->upper 32 bit multiply that uses a
2996 ;; SUBREG with a minus that shows up in modulus by constants.
2997 (define_insn "subsi3"
2998 [(set (match_operand:SI 0 "integer_register_operand" "=d")
2999 (minus:SI (match_operand:SI 1 "gpr_no_subreg_operand" "d")
3000 (match_operand:SI 2 "gpr_no_subreg_operand" "d")))]
3003 [(set_attr "length" "4")
3004 (set_attr "type" "int")])
3006 ;; Signed multiplication producing 64 bit results from 32 bit inputs
3007 ;; Note, frv doesn't have a 32x32->32 bit multiply, but the compiler
3008 ;; will do the 32x32->64 bit multiply and use the bottom word.
3009 (define_expand "mulsidi3"
3010 [(set (match_operand:DI 0 "integer_register_operand" "")
3011 (mult:DI (sign_extend:DI (match_operand:SI 1 "integer_register_operand" ""))
3012 (sign_extend:DI (match_operand:SI 2 "gpr_or_int12_operand" ""))))]
3016 if (GET_CODE (operands[2]) == CONST_INT)
3018 emit_insn (gen_mulsidi3_const (operands[0], operands[1], operands[2]));
3023 (define_insn "*mulsidi3_reg"
3024 [(set (match_operand:DI 0 "even_gpr_operand" "=e")
3025 (mult:DI (sign_extend:DI (match_operand:SI 1 "integer_register_operand" "%d"))
3026 (sign_extend:DI (match_operand:SI 2 "integer_register_operand" "d"))))]
3029 [(set_attr "length" "4")
3030 (set_attr "type" "mul")])
3032 (define_insn "mulsidi3_const"
3033 [(set (match_operand:DI 0 "even_gpr_operand" "=e")
3034 (mult:DI (sign_extend:DI (match_operand:SI 1 "integer_register_operand" "d"))
3035 (match_operand:SI 2 "int12_operand" "NOP")))]
3038 [(set_attr "length" "4")
3039 (set_attr "type" "mul")])
3041 ;; Unsigned multiplication producing 64 bit results from 32 bit inputs
3042 (define_expand "umulsidi3"
3043 [(set (match_operand:DI 0 "even_gpr_operand" "")
3044 (mult:DI (zero_extend:DI (match_operand:SI 1 "integer_register_operand" ""))
3045 (zero_extend:DI (match_operand:SI 2 "gpr_or_int12_operand" ""))))]
3049 if (GET_CODE (operands[2]) == CONST_INT)
3051 emit_insn (gen_umulsidi3_const (operands[0], operands[1], operands[2]));
3056 (define_insn "*mulsidi3_reg"
3057 [(set (match_operand:DI 0 "even_gpr_operand" "=e")
3058 (mult:DI (zero_extend:DI (match_operand:SI 1 "integer_register_operand" "%d"))
3059 (zero_extend:DI (match_operand:SI 2 "integer_register_operand" "d"))))]
3062 [(set_attr "length" "4")
3063 (set_attr "type" "mul")])
3065 (define_insn "umulsidi3_const"
3066 [(set (match_operand:DI 0 "even_gpr_operand" "=e")
3067 (mult:DI (zero_extend:DI (match_operand:SI 1 "integer_register_operand" "d"))
3068 (match_operand:SI 2 "int12_operand" "NOP")))]
3071 [(set_attr "length" "4")
3072 (set_attr "type" "mul")])
3075 (define_insn "divsi3"
3076 [(set (match_operand:SI 0 "register_operand" "=d,d")
3077 (div:SI (match_operand:SI 1 "register_operand" "d,d")
3078 (match_operand:SI 2 "gpr_or_int12_operand" "d,NOP")))]
3081 [(set_attr "length" "4")
3082 (set_attr "type" "div")])
3084 ;; Unsigned Division
3085 (define_insn "udivsi3"
3086 [(set (match_operand:SI 0 "register_operand" "=d,d")
3087 (udiv:SI (match_operand:SI 1 "register_operand" "d,d")
3088 (match_operand:SI 2 "gpr_or_int12_operand" "d,NOP")))]
3091 [(set_attr "length" "4")
3092 (set_attr "type" "div")])
3095 (define_insn "negsi2"
3096 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3097 (neg:SI (match_operand:SI 1 "integer_register_operand" "d")))]
3100 [(set_attr "length" "4")
3101 (set_attr "type" "int")])
3103 ;; Find first one bit
3104 ;; (define_insn "ffssi2"
3105 ;; [(set (match_operand:SI 0 "register_operand" "=r")
3106 ;; (ffs:SI (match_operand:SI 1 "register_operand" "r")))]
3109 ;; [(set_attr "length" "4")])
3112 ;; ::::::::::::::::::::
3114 ;; :: 64 bit Integer arithmetic
3116 ;; ::::::::::::::::::::
3119 (define_insn_and_split "adddi3"
3120 [(set (match_operand:DI 0 "integer_register_operand" "=&e,e")
3121 (plus:DI (match_operand:DI 1 "integer_register_operand" "%e,0")
3122 (match_operand:DI 2 "gpr_or_int10_operand" "eJ,eJ")))
3123 (clobber (match_scratch:CC 3 "=t,t"))]
3134 for (op = 0; op < 3; op++)
3135 for (part = 0; part < 2; part++)
3136 parts[op][part] = simplify_gen_subreg (SImode, operands[op],
3137 DImode, part * UNITS_PER_WORD);
3139 operands[4] = gen_adddi3_lower (parts[0][1], parts[1][1], parts[2][1],
3141 operands[5] = gen_adddi3_upper (parts[0][0], parts[1][0], parts[2][0],
3142 copy_rtx (operands[3]));
3144 [(set_attr "length" "8")
3145 (set_attr "type" "multi")])
3147 ;; Subtraction No need to worry about constants, since the compiler
3148 ;; canonicalizes them into adddi3's.
3149 (define_insn_and_split "subdi3"
3150 [(set (match_operand:DI 0 "integer_register_operand" "=&e,e,e")
3151 (minus:DI (match_operand:DI 1 "integer_register_operand" "e,0,e")
3152 (match_operand:DI 2 "integer_register_operand" "e,e,0")))
3153 (clobber (match_scratch:CC 3 "=t,t,t"))]
3161 rtx op0_high = gen_highpart (SImode, operands[0]);
3162 rtx op1_high = gen_highpart (SImode, operands[1]);
3163 rtx op2_high = gen_highpart (SImode, operands[2]);
3164 rtx op0_low = gen_lowpart (SImode, operands[0]);
3165 rtx op1_low = gen_lowpart (SImode, operands[1]);
3166 rtx op2_low = gen_lowpart (SImode, operands[2]);
3167 rtx op3 = operands[3];
3169 operands[4] = gen_subdi3_lower (op0_low, op1_low, op2_low, op3);
3170 operands[5] = gen_subdi3_upper (op0_high, op1_high, op2_high, op3);
3172 [(set_attr "length" "8")
3173 (set_attr "type" "multi")])
3175 ;; Patterns for addsi3/subdi3 after splitting
3176 (define_insn "adddi3_lower"
3177 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3178 (plus:SI (match_operand:SI 1 "integer_register_operand" "d")
3179 (match_operand:SI 2 "gpr_or_int10_operand" "dJ")))
3180 (set (match_operand:CC 3 "icc_operand" "=t")
3181 (compare:CC (plus:SI (match_dup 1)
3185 "add%I2cc %1,%2,%0,%3"
3186 [(set_attr "length" "4")
3187 (set_attr "type" "int")])
3189 (define_insn "adddi3_upper"
3190 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3191 (plus:SI (match_operand:SI 1 "integer_register_operand" "d")
3192 (plus:SI (match_operand:SI 2 "gpr_or_int10_operand" "dJ")
3193 (match_operand:CC 3 "icc_operand" "t"))))]
3195 "addx%I2 %1,%2,%0,%3"
3196 [(set_attr "length" "4")
3197 (set_attr "type" "int")])
3199 (define_insn "subdi3_lower"
3200 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3201 (minus:SI (match_operand:SI 1 "integer_register_operand" "d")
3202 (match_operand:SI 2 "integer_register_operand" "d")))
3203 (set (match_operand:CC 3 "icc_operand" "=t")
3204 (compare:CC (plus:SI (match_dup 1)
3209 [(set_attr "length" "4")
3210 (set_attr "type" "int")])
3212 (define_insn "subdi3_upper"
3213 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3214 (minus:SI (match_operand:SI 1 "integer_register_operand" "d")
3215 (minus:SI (match_operand:SI 2 "integer_register_operand" "d")
3216 (match_operand:CC 3 "icc_operand" "t"))))]
3219 [(set_attr "length" "4")
3220 (set_attr "type" "int")])
3222 (define_insn_and_split "negdi2"
3223 [(set (match_operand:DI 0 "integer_register_operand" "=&e,e")
3224 (neg:DI (match_operand:DI 1 "integer_register_operand" "e,0")))
3225 (clobber (match_scratch:CC 2 "=t,t"))]
3233 rtx op0_high = gen_highpart (SImode, operands[0]);
3234 rtx op1_high = gen_rtx_REG (SImode, GPR_FIRST);
3235 rtx op2_high = gen_highpart (SImode, operands[1]);
3236 rtx op0_low = gen_lowpart (SImode, operands[0]);
3237 rtx op1_low = op1_high;
3238 rtx op2_low = gen_lowpart (SImode, operands[1]);
3239 rtx op3 = operands[2];
3241 operands[3] = gen_subdi3_lower (op0_low, op1_low, op2_low, op3);
3242 operands[4] = gen_subdi3_upper (op0_high, op1_high, op2_high, op3);
3244 [(set_attr "length" "8")
3245 (set_attr "type" "multi")])
3247 ;; Multiplication (same size)
3248 ;; (define_insn "muldi3"
3249 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3250 ;; (mult:DI (match_operand:DI 1 "register_operand" "%r")
3251 ;; (match_operand:DI 2 "nonmemory_operand" "ri")))]
3253 ;; "muldi3 %0,%1,%2"
3254 ;; [(set_attr "length" "4")])
3257 ;; (define_insn "divdi3"
3258 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3259 ;; (div:DI (match_operand:DI 1 "register_operand" "r")
3260 ;; (match_operand:DI 2 "nonmemory_operand" "ri")))]
3262 ;; "divdi3 %0,%1,%2"
3263 ;; [(set_attr "length" "4")])
3265 ;; Undsgned Division
3266 ;; (define_insn "udivdi3"
3267 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3268 ;; (udiv:DI (match_operand:DI 1 "register_operand" "r")
3269 ;; (match_operand:DI 2 "nonmemory_operand" "ri")))]
3271 ;; "udivdi3 %0,%1,%2"
3272 ;; [(set_attr "length" "4")])
3275 ;; (define_insn "negdi2"
3276 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3277 ;; (neg:DI (match_operand:DI 1 "register_operand" "r")))]
3280 ;; [(set_attr "length" "4")])
3282 ;; Find first one bit
3283 ;; (define_insn "ffsdi2"
3284 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3285 ;; (ffs:DI (match_operand:DI 1 "register_operand" "r")))]
3288 ;; [(set_attr "length" "4")])
3291 ;; ::::::::::::::::::::
3293 ;; :: 32 bit floating point arithmetic
3295 ;; ::::::::::::::::::::
3298 (define_insn "addsf3"
3299 [(set (match_operand:SF 0 "fpr_operand" "=f")
3300 (plus:SF (match_operand:SF 1 "fpr_operand" "%f")
3301 (match_operand:SF 2 "fpr_operand" "f")))]
3304 [(set_attr "length" "4")
3305 (set_attr "type" "fsadd")])
3308 (define_insn "subsf3"
3309 [(set (match_operand:SF 0 "fpr_operand" "=f")
3310 (minus:SF (match_operand:SF 1 "fpr_operand" "f")
3311 (match_operand:SF 2 "fpr_operand" "f")))]
3314 [(set_attr "length" "4")
3315 (set_attr "type" "fsadd")])
3318 (define_insn "mulsf3"
3319 [(set (match_operand:SF 0 "fpr_operand" "=f")
3320 (mult:SF (match_operand:SF 1 "fpr_operand" "%f")
3321 (match_operand:SF 2 "fpr_operand" "f")))]
3324 [(set_attr "length" "4")
3325 (set_attr "type" "fsmul")])
3327 ;; Multiplication with addition/subtraction
3328 (define_insn "*muladdsf4"
3329 [(set (match_operand:SF 0 "fpr_operand" "=f")
3330 (plus:SF (mult:SF (match_operand:SF 1 "fpr_operand" "%f")
3331 (match_operand:SF 2 "fpr_operand" "f"))
3332 (match_operand:SF 3 "fpr_operand" "0")))]
3333 "TARGET_HARD_FLOAT && TARGET_MULADD"
3335 [(set_attr "length" "4")
3336 (set_attr "type" "fsmadd")])
3338 (define_insn "*mulsubsf4"
3339 [(set (match_operand:SF 0 "fpr_operand" "=f")
3340 (minus:SF (mult:SF (match_operand:SF 1 "fpr_operand" "%f")
3341 (match_operand:SF 2 "fpr_operand" "f"))
3342 (match_operand:SF 3 "fpr_operand" "0")))]
3343 "TARGET_HARD_FLOAT && TARGET_MULADD"
3345 [(set_attr "length" "4")
3346 (set_attr "type" "fsmadd")])
3349 (define_insn "divsf3"
3350 [(set (match_operand:SF 0 "fpr_operand" "=f")
3351 (div:SF (match_operand:SF 1 "fpr_operand" "f")
3352 (match_operand:SF 2 "fpr_operand" "f")))]
3355 [(set_attr "length" "4")
3356 (set_attr "type" "fsdiv")])
3359 (define_insn "negsf2"
3360 [(set (match_operand:SF 0 "fpr_operand" "=f")
3361 (neg:SF (match_operand:SF 1 "fpr_operand" "f")))]
3364 [(set_attr "length" "4")
3365 (set_attr "type" "fsconv")])
3368 (define_insn "abssf2"
3369 [(set (match_operand:SF 0 "fpr_operand" "=f")
3370 (abs:SF (match_operand:SF 1 "fpr_operand" "f")))]
3373 [(set_attr "length" "4")
3374 (set_attr "type" "fsconv")])
3377 (define_insn "sqrtsf2"
3378 [(set (match_operand:SF 0 "fpr_operand" "=f")
3379 (sqrt:SF (match_operand:SF 1 "fpr_operand" "f")))]
3382 [(set_attr "length" "4")
3383 (set_attr "type" "sqrt_single")])
3386 ;; ::::::::::::::::::::
3388 ;; :: 64 bit floating point arithmetic
3390 ;; ::::::::::::::::::::
3393 (define_insn "adddf3"
3394 [(set (match_operand:DF 0 "even_fpr_operand" "=h")
3395 (plus:DF (match_operand:DF 1 "fpr_operand" "%h")
3396 (match_operand:DF 2 "fpr_operand" "h")))]
3397 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3399 [(set_attr "length" "4")
3400 (set_attr "type" "fdadd")])
3403 (define_insn "subdf3"
3404 [(set (match_operand:DF 0 "even_fpr_operand" "=h")
3405 (minus:DF (match_operand:DF 1 "fpr_operand" "h")
3406 (match_operand:DF 2 "fpr_operand" "h")))]
3407 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3409 [(set_attr "length" "4")
3410 (set_attr "type" "fdadd")])
3413 (define_insn "muldf3"
3414 [(set (match_operand:DF 0 "even_fpr_operand" "=h")
3415 (mult:DF (match_operand:DF 1 "fpr_operand" "%h")
3416 (match_operand:DF 2 "fpr_operand" "h")))]
3417 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3419 [(set_attr "length" "4")
3420 (set_attr "type" "fdmul")])
3422 ;; Multiplication with addition/subtraction
3423 (define_insn "*muladddf4"
3424 [(set (match_operand:DF 0 "fpr_operand" "=f")
3425 (plus:DF (mult:DF (match_operand:DF 1 "fpr_operand" "%f")
3426 (match_operand:DF 2 "fpr_operand" "f"))
3427 (match_operand:DF 3 "fpr_operand" "0")))]
3428 "TARGET_HARD_FLOAT && TARGET_DOUBLE && TARGET_MULADD"
3430 [(set_attr "length" "4")
3431 (set_attr "type" "fdmadd")])
3433 (define_insn "*mulsubdf4"
3434 [(set (match_operand:DF 0 "fpr_operand" "=f")
3435 (minus:DF (mult:DF (match_operand:DF 1 "fpr_operand" "%f")
3436 (match_operand:DF 2 "fpr_operand" "f"))
3437 (match_operand:DF 3 "fpr_operand" "0")))]
3438 "TARGET_HARD_FLOAT && TARGET_DOUBLE && TARGET_MULADD"
3440 [(set_attr "length" "4")
3441 (set_attr "type" "fdmadd")])
3444 (define_insn "divdf3"
3445 [(set (match_operand:DF 0 "even_fpr_operand" "=h")
3446 (div:DF (match_operand:DF 1 "fpr_operand" "h")
3447 (match_operand:DF 2 "fpr_operand" "h")))]
3448 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3450 [(set_attr "length" "4")
3451 (set_attr "type" "fddiv")])
3454 (define_insn "negdf2"
3455 [(set (match_operand:DF 0 "even_fpr_operand" "=h")
3456 (neg:DF (match_operand:DF 1 "fpr_operand" "h")))]
3457 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3459 [(set_attr "length" "4")
3460 (set_attr "type" "fdconv")])
3463 (define_insn "absdf2"
3464 [(set (match_operand:DF 0 "even_fpr_operand" "=h")
3465 (abs:DF (match_operand:DF 1 "fpr_operand" "h")))]
3466 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3468 [(set_attr "length" "4")
3469 (set_attr "type" "fdconv")])
3472 (define_insn "sqrtdf2"
3473 [(set (match_operand:DF 0 "even_fpr_operand" "=h")
3474 (sqrt:DF (match_operand:DF 1 "fpr_operand" "h")))]
3475 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3477 [(set_attr "length" "4")
3478 (set_attr "type" "sqrt_double")])
3481 ;; ::::::::::::::::::::
3483 ;; :: 32 bit Integer Shifts and Rotates
3485 ;; ::::::::::::::::::::
3487 ;; Arithmetic Shift Left
3488 (define_insn "ashlsi3"
3489 [(set (match_operand:SI 0 "integer_register_operand" "=d,d")
3490 (ashift:SI (match_operand:SI 1 "integer_register_operand" "d,d")
3491 (match_operand:SI 2 "gpr_or_int12_operand" "d,NOP")))]
3494 [(set_attr "length" "4")
3495 (set_attr "type" "int")])
3497 ;; Arithmetic Shift Right
3498 (define_insn "ashrsi3"
3499 [(set (match_operand:SI 0 "integer_register_operand" "=d,d")
3500 (ashiftrt:SI (match_operand:SI 1 "integer_register_operand" "d,d")
3501 (match_operand:SI 2 "gpr_or_int12_operand" "d,NOP")))]
3504 [(set_attr "length" "4")
3505 (set_attr "type" "int")])
3507 ;; Logical Shift Right
3508 (define_insn "lshrsi3"
3509 [(set (match_operand:SI 0 "integer_register_operand" "=d,d")
3510 (lshiftrt:SI (match_operand:SI 1 "integer_register_operand" "d,d")
3511 (match_operand:SI 2 "gpr_or_int12_operand" "d,NOP")))]
3514 [(set_attr "length" "4")
3515 (set_attr "type" "int")])
3518 ;; (define_insn "rotlsi3"
3519 ;; [(set (match_operand:SI 0 "register_operand" "=r")
3520 ;; (rotate:SI (match_operand:SI 1 "register_operand" "r")
3521 ;; (match_operand:SI 2 "nonmemory_operand" "ri")))]
3523 ;; "rotlsi3 %0,%1,%2"
3524 ;; [(set_attr "length" "4")])
3527 ;; (define_insn "rotrsi3"
3528 ;; [(set (match_operand:SI 0 "register_operand" "=r")
3529 ;; (rotatert:SI (match_operand:SI 1 "register_operand" "r")
3530 ;; (match_operand:SI 2 "nonmemory_operand" "ri")))]
3532 ;; "rotrsi3 %0,%1,%2"
3533 ;; [(set_attr "length" "4")])
3536 ;; ::::::::::::::::::::
3538 ;; :: 64 bit Integer Shifts and Rotates
3540 ;; ::::::::::::::::::::
3542 ;; Arithmetic Shift Left
3543 ;; (define_insn "ashldi3"
3544 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3545 ;; (ashift:DI (match_operand:DI 1 "register_operand" "r")
3546 ;; (match_operand:SI 2 "nonmemory_operand" "ri")))]
3548 ;; "ashldi3 %0,%1,%2"
3549 ;; [(set_attr "length" "4")])
3551 ;; Arithmetic Shift Right
3552 ;; (define_insn "ashrdi3"
3553 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3554 ;; (ashiftrt:DI (match_operand:DI 1 "register_operand" "r")
3555 ;; (match_operand:SI 2 "nonmemory_operand" "ri")))]
3557 ;; "ashrdi3 %0,%1,%2"
3558 ;; [(set_attr "length" "4")])
3560 ;; Logical Shift Right
3561 ;; (define_insn "lshrdi3"
3562 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3563 ;; (lshiftrt:DI (match_operand:DI 1 "register_operand" "r")
3564 ;; (match_operand:SI 2 "nonmemory_operand" "ri")))]
3566 ;; "lshrdi3 %0,%1,%2"
3567 ;; [(set_attr "length" "4")])
3570 ;; (define_insn "rotldi3"
3571 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3572 ;; (rotate:DI (match_operand:DI 1 "register_operand" "r")
3573 ;; (match_operand:SI 2 "nonmemory_operand" "ri")))]
3575 ;; "rotldi3 %0,%1,%2"
3576 ;; [(set_attr "length" "4")])
3579 ;; (define_insn "rotrdi3"
3580 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3581 ;; (rotatert:DI (match_operand:DI 1 "register_operand" "r")
3582 ;; (match_operand:SI 2 "nonmemory_operand" "ri")))]
3584 ;; "rotrdi3 %0,%1,%2"
3585 ;; [(set_attr "length" "4")])
3588 ;; ::::::::::::::::::::
3590 ;; :: 32 Bit Integer Logical operations
3592 ;; ::::::::::::::::::::
3594 ;; Logical AND, 32 bit integers
3595 (define_insn "andsi3_media"
3596 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "=d,f")
3597 (and:SI (match_operand:SI 1 "gpr_or_fpr_operand" "%d,f")
3598 (match_operand:SI 2 "gpr_fpr_or_int12_operand" "dNOP,f")))]
3603 [(set_attr "length" "4")
3604 (set_attr "type" "int,mlogic")])
3606 (define_insn "andsi3_nomedia"
3607 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3608 (and:SI (match_operand:SI 1 "integer_register_operand" "%d")
3609 (match_operand:SI 2 "gpr_or_int12_operand" "dNOP")))]
3612 [(set_attr "length" "4")
3613 (set_attr "type" "int")])
3615 (define_expand "andsi3"
3616 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "")
3617 (and:SI (match_operand:SI 1 "gpr_or_fpr_operand" "")
3618 (match_operand:SI 2 "gpr_fpr_or_int12_operand" "")))]
3622 ;; Inclusive OR, 32 bit integers
3623 (define_insn "iorsi3_media"
3624 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "=d,f")
3625 (ior:SI (match_operand:SI 1 "gpr_or_fpr_operand" "%d,f")
3626 (match_operand:SI 2 "gpr_fpr_or_int12_operand" "dNOP,f")))]
3631 [(set_attr "length" "4")
3632 (set_attr "type" "int,mlogic")])
3634 (define_insn "iorsi3_nomedia"
3635 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3636 (ior:SI (match_operand:SI 1 "integer_register_operand" "%d")
3637 (match_operand:SI 2 "gpr_or_int12_operand" "dNOP")))]
3640 [(set_attr "length" "4")
3641 (set_attr "type" "int")])
3643 (define_expand "iorsi3"
3644 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "")
3645 (ior:SI (match_operand:SI 1 "gpr_or_fpr_operand" "")
3646 (match_operand:SI 2 "gpr_fpr_or_int12_operand" "")))]
3650 ;; Exclusive OR, 32 bit integers
3651 (define_insn "xorsi3_media"
3652 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "=d,f")
3653 (xor:SI (match_operand:SI 1 "gpr_or_fpr_operand" "%d,f")
3654 (match_operand:SI 2 "gpr_fpr_or_int12_operand" "dNOP,f")))]
3659 [(set_attr "length" "4")
3660 (set_attr "type" "int,mlogic")])
3662 (define_insn "xorsi3_nomedia"
3663 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3664 (xor:SI (match_operand:SI 1 "integer_register_operand" "%d")
3665 (match_operand:SI 2 "gpr_or_int12_operand" "dNOP")))]
3668 [(set_attr "length" "4")
3669 (set_attr "type" "int")])
3671 (define_expand "xorsi3"
3672 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "")
3673 (xor:SI (match_operand:SI 1 "gpr_or_fpr_operand" "")
3674 (match_operand:SI 2 "gpr_fpr_or_int12_operand" "")))]
3678 ;; One's complement, 32 bit integers
3679 (define_insn "one_cmplsi2_media"
3680 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "=d,f")
3681 (not:SI (match_operand:SI 1 "gpr_or_fpr_operand" "d,f")))]
3686 [(set_attr "length" "4")
3687 (set_attr "type" "int,mlogic")])
3689 (define_insn "one_cmplsi2_nomedia"
3690 [(set (match_operand:SI 0 "integer_register_operand" "=d")
3691 (not:SI (match_operand:SI 1 "integer_register_operand" "d")))]
3694 [(set_attr "length" "4")
3695 (set_attr "type" "int")])
3697 (define_expand "one_cmplsi2"
3698 [(set (match_operand:SI 0 "gpr_or_fpr_operand" "")
3699 (not:SI (match_operand:SI 1 "gpr_or_fpr_operand" "")))]
3704 ;; ::::::::::::::::::::
3706 ;; :: 64 Bit Integer Logical operations
3708 ;; ::::::::::::::::::::
3710 ;; Logical AND, 64 bit integers
3711 ;; (define_insn "anddi3"
3712 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3713 ;; (and:DI (match_operand:DI 1 "register_operand" "%r")
3714 ;; (match_operand:DI 2 "nonmemory_operand" "ri")))]
3716 ;; "anddi3 %0,%1,%2"
3717 ;; [(set_attr "length" "4")])
3719 ;; Inclusive OR, 64 bit integers
3720 ;; (define_insn "iordi3"
3721 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3722 ;; (ior:DI (match_operand:DI 1 "register_operand" "%r")
3723 ;; (match_operand:DI 2 "nonmemory_operand" "ri")))]
3725 ;; "iordi3 %0,%1,%2"
3726 ;; [(set_attr "length" "4")])
3728 ;; Exclusive OR, 64 bit integers
3729 ;; (define_insn "xordi3"
3730 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3731 ;; (xor:DI (match_operand:DI 1 "register_operand" "%r")
3732 ;; (match_operand:DI 2 "nonmemory_operand" "ri")))]
3734 ;; "xordi3 %0,%1,%2"
3735 ;; [(set_attr "length" "4")])
3737 ;; One's complement, 64 bit integers
3738 ;; (define_insn "one_cmpldi2"
3739 ;; [(set (match_operand:DI 0 "register_operand" "=r")
3740 ;; (not:DI (match_operand:DI 1 "register_operand" "r")))]
3743 ;; [(set_attr "length" "4")])
3746 ;; ::::::::::::::::::::
3748 ;; :: Combination of integer operation with comparison
3750 ;; ::::::::::::::::::::
3752 (define_insn "*combo_intop_compare1"
3753 [(set (match_operand:CC_NZ 0 "icc_operand" "=t")
3755 (match_operator:SI 1 "intop_compare_operator"
3756 [(match_operand:SI 2 "integer_register_operand" "d")
3757 (match_operand:SI 3 "gpr_or_int10_operand" "dJ")])
3760 "%O1%I3cc %2, %3, %., %0"
3761 [(set_attr "type" "int")
3762 (set_attr "length" "4")])
3764 (define_insn "*combo_intop_compare2"
3765 [(set (match_operand:CC_NZ 0 "icc_operand" "=t")
3767 (match_operator:SI 1 "intop_compare_operator"
3768 [(match_operand:SI 2 "integer_register_operand" "d")
3769 (match_operand:SI 3 "gpr_or_int10_operand" "dJ")])
3771 (set (match_operand:SI 4 "integer_register_operand" "=d")
3772 (match_operator:SI 5 "intop_compare_operator"
3775 "GET_CODE (operands[1]) == GET_CODE (operands[5])"
3776 "%O1%I3cc %2, %3, %4, %0"
3777 [(set_attr "type" "int")
3778 (set_attr "length" "4")])
3780 ;; ::::::::::::::::::::
3784 ;; ::::::::::::::::::::
3786 ;; Note, we store the operands in the comparison insns, and use them later
3787 ;; when generating the branch or scc operation.
3789 ;; First the routines called by the machine independent part of the compiler
3790 (define_expand "cmpsi"
3792 (compare (match_operand:SI 0 "integer_register_operand" "")
3793 (match_operand:SI 1 "gpr_or_int10_operand" "")))]
3797 frv_compare_op0 = operands[0];
3798 frv_compare_op1 = operands[1];
3802 ;(define_expand "cmpdi"
3804 ; (compare (match_operand:DI 0 "register_operand" "")
3805 ; (match_operand:DI 1 "nonmemory_operand" "")))]
3809 ; frv_compare_op0 = operands[0];
3810 ; frv_compare_op1 = operands[1];
3814 (define_expand "cmpsf"
3816 (compare (match_operand:SF 0 "fpr_operand" "")
3817 (match_operand:SF 1 "fpr_operand" "")))]
3821 frv_compare_op0 = operands[0];
3822 frv_compare_op1 = operands[1];
3826 (define_expand "cmpdf"
3828 (compare (match_operand:DF 0 "fpr_operand" "")
3829 (match_operand:DF 1 "fpr_operand" "")))]
3830 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3833 frv_compare_op0 = operands[0];
3834 frv_compare_op1 = operands[1];
3838 ;; Now, the actual comparisons, generated by the branch and/or scc operations
3840 (define_insn "cmpsi_cc"
3841 [(set (match_operand:CC 0 "icc_operand" "=t,t")
3842 (compare:CC (match_operand:SI 1 "integer_register_operand" "d,d")
3843 (match_operand:SI 2 "gpr_or_int10_operand" "d,J")))]
3846 [(set_attr "length" "4")
3847 (set_attr "type" "int")])
3849 (define_insn "*cmpsi_cc_uns"
3850 [(set (match_operand:CC_UNS 0 "icc_operand" "=t,t")
3851 (compare:CC_UNS (match_operand:SI 1 "integer_register_operand" "d,d")
3852 (match_operand:SI 2 "gpr_or_int10_operand" "d,J")))]
3855 [(set_attr "length" "4")
3856 (set_attr "type" "int")])
3858 ;; The only requirement for a CC_NZmode GPR or memory value is that
3859 ;; comparing it against zero must set the Z and N flags appropriately.
3860 ;; The source operand is therefore a valid CC_NZmode value.
3861 (define_insn "*cmpsi_cc_nz"
3862 [(set (match_operand:CC_NZ 0 "nonimmediate_operand" "=t,d,m")
3863 (compare:CC_NZ (match_operand:SI 1 "integer_register_operand" "d,d,d")
3870 [(set_attr "length" "4,4,4")
3871 (set_attr "type" "int,int,gstore")])
3873 (define_insn "*cmpsf_cc_fp"
3874 [(set (match_operand:CC_FP 0 "fcc_operand" "=u")
3875 (compare:CC_FP (match_operand:SF 1 "fpr_operand" "f")
3876 (match_operand:SF 2 "fpr_operand" "f")))]
3879 [(set_attr "length" "4")
3880 (set_attr "type" "fscmp")])
3882 (define_insn "*cmpdf_cc_fp"
3883 [(set (match_operand:CC_FP 0 "fcc_operand" "=u")
3884 (compare:CC_FP (match_operand:DF 1 "even_fpr_operand" "h")
3885 (match_operand:DF 2 "even_fpr_operand" "h")))]
3886 "TARGET_HARD_FLOAT && TARGET_DOUBLE"
3888 [(set_attr "length" "4")
3889 (set_attr "type" "fdcmp")])
3892 ;; ::::::::::::::::::::
3896 ;; ::::::::::::::::::::
3898 ;; Define_expands called by the machine independent part of the compiler
3899 ;; to allocate a new comparison register. Each of these named patterns
3900 ;; must be present, and they cannot be amalgamated into one pattern.
3902 ;; If a fixed condition code register is being used, (as opposed to, say,
3903 ;; using cc0), then the expands should look like this:
3905 ;; (define_expand "<name_of_test>"
3906 ;; [(set (reg:CC <number_of_CC_register>)
3907 ;; (compare:CC (match_dup 1)
3910 ;; (if_then_else (eq:CC (reg:CC <number_of_CC_register>)
3912 ;; (label_ref (match_operand 0 "" ""))
3916 ;; operands[1] = frv_compare_op0;
3917 ;; operands[2] = frv_compare_op1;
3921 (define_expand "beq"
3922 [(use (match_operand 0 "" ""))]
3926 if (! frv_emit_cond_branch (EQ, operands[0]))
3932 (define_expand "bne"
3933 [(use (match_operand 0 "" ""))]
3937 if (! frv_emit_cond_branch (NE, operands[0]))
3943 (define_expand "blt"
3944 [(use (match_operand 0 "" ""))]
3948 if (! frv_emit_cond_branch (LT, operands[0]))
3954 (define_expand "ble"
3955 [(use (match_operand 0 "" ""))]
3959 if (! frv_emit_cond_branch (LE, operands[0]))
3965 (define_expand "bgt"
3966 [(use (match_operand 0 "" ""))]
3970 if (! frv_emit_cond_branch (GT, operands[0]))
3976 (define_expand "bge"
3977 [(use (match_operand 0 "" ""))]
3981 if (! frv_emit_cond_branch (GE, operands[0]))
3987 (define_expand "bltu"
3988 [(use (match_operand 0 "" ""))]
3992 if (! frv_emit_cond_branch (LTU, operands[0]))
3998 (define_expand "bleu"
3999 [(use (match_operand 0 "" ""))]
4003 if (! frv_emit_cond_branch (LEU, operands[0]))
4009 (define_expand "bgtu"
4010 [(use (match_operand 0 "" ""))]
4014 if (! frv_emit_cond_branch (GTU, operands[0]))
4020 (define_expand "bgeu"
4021 [(use (match_operand 0 "" ""))]
4025 if (! frv_emit_cond_branch (GEU, operands[0]))
4031 ;; Actual branches. We must allow for the (label_ref) and the (pc) to be
4032 ;; swapped. If they are swapped, it reverses the sense of the branch.
4034 ;; Note - unlike the define expands above, these patterns can be amalgamated
4035 ;; into one pattern for branch-if-true and one for branch-if-false. This does
4036 ;; require an operand operator to select the correct branch mnemonic.
4038 ;; If a fixed condition code register is being used, (as opposed to, say,
4039 ;; using cc0), then the expands could look like this:
4041 ;; (define_insn "*branch_true"
4043 ;; (if_then_else (match_operator:CC 0 "comparison_operator"
4044 ;; [(reg:CC <number_of_CC_register>)
4046 ;; (label_ref (match_operand 1 "" ""))
4050 ;; [(set_attr "length" "4")]
4053 ;; In the above example the %B is a directive to frv_print_operand()
4054 ;; to decode and print the correct branch mnemonic.
4056 (define_insn "*branch_int_true"
4058 (if_then_else (match_operator 0 "integer_relational_operator"
4059 [(match_operand 1 "icc_operand" "t")
4061 (label_ref (match_operand 2 "" ""))
4066 if (get_attr_length (insn) == 4)
4067 return \"b%c0 %1,%#,%l2\";
4069 return \"b%C0 %1,%#,1f\;call %l2\\n1:\";
4071 [(set (attr "length")
4073 (and (ge (minus (match_dup 2) (pc)) (const_int -32768))
4074 (le (minus (match_dup 2) (pc)) (const_int 32764)))
4077 (set (attr "far_jump")
4079 (eq_attr "length" "4")
4081 (const_string "yes")))
4084 (eq_attr "length" "4")
4085 (const_string "branch")
4086 (const_string "multi")))])
4088 (define_insn "*branch_int_false"
4090 (if_then_else (match_operator 0 "integer_relational_operator"
4091 [(match_operand 1 "icc_operand" "t")
4094 (label_ref (match_operand 2 "" ""))))]
4098 if (get_attr_length (insn) == 4)
4099 return \"b%C0 %1,%#,%l2\";
4101 return \"b%c0 %1,%#,1f\;call %l2\\n1:\";
4103 [(set (attr "length")
4105 (and (ge (minus (match_dup 2) (pc)) (const_int -32768))
4106 (le (minus (match_dup 2) (pc)) (const_int 32764)))
4109 (set (attr "far_jump")
4111 (eq_attr "length" "4")
4113 (const_string "yes")))
4116 (eq_attr "length" "4")
4117 (const_string "branch")
4118 (const_string "multi")))])
4120 (define_insn "*branch_fp_true"
4122 (if_then_else (match_operator:CC_FP 0 "float_relational_operator"
4123 [(match_operand 1 "fcc_operand" "u")
4125 (label_ref (match_operand 2 "" ""))
4130 if (get_attr_length (insn) == 4)
4131 return \"fb%f0 %1,%#,%l2\";
4133 return \"fb%F0 %1,%#,1f\;call %l2\\n1:\";
4135 [(set (attr "length")
4137 (and (ge (minus (match_dup 2) (pc)) (const_int -32768))
4138 (le (minus (match_dup 2) (pc)) (const_int 32764)))
4141 (set (attr "far_jump")
4143 (eq_attr "length" "4")
4145 (const_string "yes")))
4148 (eq_attr "length" "4")
4149 (const_string "branch")
4150 (const_string "multi")))])
4152 (define_insn "*branch_fp_false"
4154 (if_then_else (match_operator:CC_FP 0 "float_relational_operator"
4155 [(match_operand 1 "fcc_operand" "u")
4158 (label_ref (match_operand 2 "" ""))))]
4162 if (get_attr_length (insn) == 4)
4163 return \"fb%F0 %1,%#,%l2\";
4165 return \"fb%f0 %1,%#,1f\;call %l2\\n1:\";
4167 [(set (attr "length")
4169 (and (ge (minus (match_dup 2) (pc)) (const_int -32768))
4170 (le (minus (match_dup 2) (pc)) (const_int 32764)))
4173 (set (attr "far_jump")
4175 (eq_attr "length" "4")
4177 (const_string "yes")))
4180 (eq_attr "length" "4")
4181 (const_string "branch")
4182 (const_string "multi")))])
4185 ;; ::::::::::::::::::::
4187 ;; :: Set flag operations
4189 ;; ::::::::::::::::::::
4191 ;; Define_expands called by the machine independent part of the compiler
4192 ;; to allocate a new comparison register
4194 (define_expand "seq"
4195 [(match_operand:SI 0 "integer_register_operand" "")]
4199 if (! frv_emit_scc (EQ, operands[0]))
4205 (define_expand "sne"
4206 [(match_operand:SI 0 "integer_register_operand" "")]
4210 if (! frv_emit_scc (NE, operands[0]))
4216 (define_expand "slt"
4217 [(match_operand:SI 0 "integer_register_operand" "")]
4221 if (! frv_emit_scc (LT, operands[0]))
4227 (define_expand "sle"
4228 [(match_operand:SI 0 "integer_register_operand" "")]
4232 if (! frv_emit_scc (LE, operands[0]))
4238 (define_expand "sgt"
4239 [(match_operand:SI 0 "integer_register_operand" "")]
4243 if (! frv_emit_scc (GT, operands[0]))
4249 (define_expand "sge"
4250 [(match_operand:SI 0 "integer_register_operand" "")]
4254 if (! frv_emit_scc (GE, operands[0]))
4260 (define_expand "sltu"
4261 [(match_operand:SI 0 "integer_register_operand" "")]
4265 if (! frv_emit_scc (LTU, operands[0]))
4271 (define_expand "sleu"
4272 [(match_operand:SI 0 "integer_register_operand" "")]
4276 if (! frv_emit_scc (LEU, operands[0]))
4282 (define_expand "sgtu"
4283 [(match_operand:SI 0 "integer_register_operand" "")]
4287 if (! frv_emit_scc (GTU, operands[0]))
4293 (define_expand "sgeu"
4294 [(match_operand:SI 0 "integer_register_operand" "")]
4298 if (! frv_emit_scc (GEU, operands[0]))
4304 (define_insn "*scc_int"
4305 [(set (match_operand:SI 0 "integer_register_operand" "=d")
4306 (match_operator:SI 1 "integer_relational_operator"
4307 [(match_operand 2 "icc_operand" "t")
4309 (clobber (match_operand:CC_CCR 3 "icr_operand" "=v"))]
4312 [(set_attr "length" "12")
4313 (set_attr "type" "multi")])
4315 (define_insn "*scc_float"
4316 [(set (match_operand:SI 0 "integer_register_operand" "=d")
4317 (match_operator:SI 1 "float_relational_operator"
4318 [(match_operand:CC_FP 2 "fcc_operand" "u")
4320 (clobber (match_operand:CC_CCR 3 "fcr_operand" "=w"))]
4323 [(set_attr "length" "12")
4324 (set_attr "type" "multi")])
4326 ;; XXX -- add reload_completed to the splits, because register allocation
4327 ;; currently isn't ready to see cond_exec packets.
4329 [(set (match_operand:SI 0 "integer_register_operand" "")
4330 (match_operator:SI 1 "relational_operator"
4331 [(match_operand 2 "cc_operand" "")
4333 (clobber (match_operand 3 "cr_operand" ""))]
4336 "operands[4] = frv_split_scc (operands[0], operands[1], operands[2],
4337 operands[3], (HOST_WIDE_INT) 1);")
4339 (define_insn "*scc_neg1_int"
4340 [(set (match_operand:SI 0 "integer_register_operand" "=d")
4341 (neg:SI (match_operator:SI 1 "integer_relational_operator"
4342 [(match_operand 2 "icc_operand" "t")
4344 (clobber (match_operand:CC_CCR 3 "icr_operand" "=v"))]
4347 [(set_attr "length" "12")
4348 (set_attr "type" "multi")])
4350 (define_insn "*scc_neg1_float"
4351 [(set (match_operand:SI 0 "integer_register_operand" "=d")
4352 (neg:SI (match_operator:SI 1 "float_relational_operator"
4353 [(match_operand:CC_FP 2 "fcc_operand" "u")
4355 (clobber (match_operand:CC_CCR 3 "fcr_operand" "=w"))]
4358 [(set_attr "length" "12")
4359 (set_attr "type" "multi")])
4362 [(set (match_operand:SI 0 "integer_register_operand" "")
4363 (neg:SI (match_operator:SI 1 "relational_operator"
4364 [(match_operand 2 "cc_operand" "")
4366 (clobber (match_operand 3 "cr_operand" ""))]
4369 "operands[4] = frv_split_scc (operands[0], operands[1], operands[2],
4370 operands[3], (HOST_WIDE_INT) -1);")
4373 ;; ::::::::::::::::::::
4375 ;; :: Conditionally executed instructions
4377 ;; ::::::::::::::::::::
4379 ;; Convert ICC/FCC comparison into CCR bits so we can do conditional execution
4380 (define_insn "*ck_signed"
4381 [(set (match_operand:CC_CCR 0 "icr_operand" "=v")
4382 (match_operator:CC_CCR 1 "integer_relational_operator"
4383 [(match_operand 2 "icc_operand" "t")
4387 [(set_attr "length" "4")
4388 (set_attr "type" "ccr")])
4390 (define_insn "*fck_float"
4391 [(set (match_operand:CC_CCR 0 "fcr_operand" "=w")
4392 (match_operator:CC_CCR 1 "float_relational_operator"
4393 [(match_operand:CC_FP 2 "fcc_operand" "u")
4397 [(set_attr "length" "4")
4398 (set_attr "type" "ccr")])
4400 ;; Conditionally convert ICC/FCC comparison into CCR bits to provide && and ||
4401 ;; tests in conditional execution
4402 (define_insn "cond_exec_ck"
4403 [(set (match_operand:CC_CCR 0 "cr_operand" "=v,w")
4404 (if_then_else:CC_CCR (match_operator 1 "ccr_eqne_operator"
4405 [(match_operand 2 "cr_operand" "C,C")
4407 (match_operator 3 "relational_operator"
4408 [(match_operand 4 "cc_operand" "t,u")
4413 cck%c3 %4, %0, %2, %e1
4414 cfck%f3 %4, %0, %2, %e1"
4415 [(set_attr "length" "4")
4416 (set_attr "type" "ccr")])
4418 ;; Conditionally set a register to either 0 or another register
4419 (define_insn "*cond_exec_movqi"
4421 (match_operator 0 "ccr_eqne_operator"
4422 [(match_operand 1 "cr_operand" "C,C,C,C,C,C")
4424 (set (match_operand:QI 2 "condexec_dest_operand" "=d,d,U,?f,?f,?d")
4425 (match_operand:QI 3 "condexec_source_operand" "dO,U,dO,f,d,f")))]
4426 "register_operand(operands[2], QImode) || reg_or_0_operand (operands[3], QImode)"
4427 "* return output_condmove_single (operands, insn);"
4428 [(set_attr "length" "4")
4429 (set_attr "type" "int,gload,gstore,fsconv,movgf,movfg")])
4431 (define_insn "*cond_exec_movhi"
4433 (match_operator 0 "ccr_eqne_operator"
4434 [(match_operand 1 "cr_operand" "C,C,C,C,C,C")
4436 (set (match_operand:HI 2 "condexec_dest_operand" "=d,d,U,?f,?f,?d")
4437 (match_operand:HI 3 "condexec_source_operand" "dO,U,dO,f,d,f")))]
4438 "register_operand(operands[2], HImode) || reg_or_0_operand (operands[3], HImode)"
4439 "* return output_condmove_single (operands, insn);"
4440 [(set_attr "length" "4")
4441 (set_attr "type" "int,gload,gstore,fsconv,movgf,movfg")])
4443 (define_insn "*cond_exec_movsi"
4445 (match_operator 0 "ccr_eqne_operator"
4446 [(match_operand 1 "cr_operand" "C,C,C,C,C,C,C,C")
4448 (set (match_operand:SI 2 "condexec_dest_operand" "=d,d,U,?f,?f,?d,?f,?m")
4449 (match_operand:SI 3 "condexec_source_operand" "dO,U,dO,f,d,f,m,f")))]
4450 "register_operand(operands[2], SImode) || reg_or_0_operand (operands[3], SImode)"
4451 "* return output_condmove_single (operands, insn);"
4452 [(set_attr "length" "4")
4453 (set_attr "type" "int,gload,gstore,fsconv,movgf,movfg,fload,fstore")])
4456 (define_insn "*cond_exec_movsf_has_fprs"
4458 (match_operator 0 "ccr_eqne_operator"
4459 [(match_operand 1 "cr_operand" "C,C,C,C,C,C,C,C,C,C")
4461 (set (match_operand:SF 2 "condexec_dest_operand" "=f,?d,?d,?f,f,f,?d,U,?U,U")
4462 (match_operand:SF 3 "condexec_source_operand" "f,d,f,d,G,U,U,f,d,G")))]
4464 "* return output_condmove_single (operands, insn);"
4465 [(set_attr "length" "4")
4466 (set_attr "type" "fsconv,int,movgf,movfg,movgf,fload,gload,fstore,gstore,gstore")])
4468 (define_insn "*cond_exec_movsf_no_fprs"
4470 (match_operator 0 "ccr_eqne_operator"
4471 [(match_operand 1 "cr_operand" "C,C,C")
4473 (set (match_operand:SF 2 "condexec_dest_operand" "=d,d,U")
4474 (match_operand:SF 3 "condexec_source_operand" "d,U,dG")))]
4476 "* return output_condmove_single (operands, insn);"
4477 [(set_attr "length" "4")
4478 (set_attr "type" "int,gload,gstore")])
4480 (define_insn "*cond_exec_si_binary1"
4482 (match_operator 0 "ccr_eqne_operator"
4483 [(match_operand 1 "cr_operand" "C")
4485 (set (match_operand:SI 2 "integer_register_operand" "=d")
4486 (match_operator:SI 3 "condexec_si_binary_operator"
4487 [(match_operand:SI 4 "integer_register_operand" "d")
4488 (match_operand:SI 5 "integer_register_operand" "d")])))]
4492 switch (GET_CODE (operands[3]))
4494 case PLUS: return \"cadd %4, %z5, %2, %1, %e0\";
4495 case MINUS: return \"csub %4, %z5, %2, %1, %e0\";
4496 case AND: return \"cand %4, %z5, %2, %1, %e0\";
4497 case IOR: return \"cor %4, %z5, %2, %1, %e0\";
4498 case XOR: return \"cxor %4, %z5, %2, %1, %e0\";
4499 case ASHIFT: return \"csll %4, %z5, %2, %1, %e0\";
4500 case ASHIFTRT: return \"csra %4, %z5, %2, %1, %e0\";
4501 case LSHIFTRT: return \"csrl %4, %z5, %2, %1, %e0\";
4502 default: gcc_unreachable ();
4505 [(set_attr "length" "4")
4506 (set_attr "type" "int")])
4508 (define_insn "*cond_exec_si_binary2"
4510 (match_operator 0 "ccr_eqne_operator"
4511 [(match_operand 1 "cr_operand" "C")
4513 (set (match_operand:SI 2 "fpr_operand" "=f")
4514 (match_operator:SI 3 "condexec_si_media_operator"
4515 [(match_operand:SI 4 "fpr_operand" "f")
4516 (match_operand:SI 5 "fpr_operand" "f")])))]
4520 switch (GET_CODE (operands[3]))
4522 case AND: return \"cmand %4, %5, %2, %1, %e0\";
4523 case IOR: return \"cmor %4, %5, %2, %1, %e0\";
4524 case XOR: return \"cmxor %4, %5, %2, %1, %e0\";
4525 default: gcc_unreachable ();
4528 [(set_attr "length" "4")
4529 (set_attr "type" "mlogic")])
4531 ;; Note, flow does not (currently) know how to handle an operation that uses
4532 ;; only part of the hard registers allocated for a multiregister value, such as
4533 ;; DImode in this case if the user is only interested in the lower 32-bits. So
4534 ;; we emit a USE of the entire register after the csmul instruction so it won't
4535 ;; get confused. See frv_ifcvt_modify_insn for more details.
4537 (define_insn "*cond_exec_si_smul"
4539 (match_operator 0 "ccr_eqne_operator"
4540 [(match_operand 1 "cr_operand" "C")
4542 (set (match_operand:DI 2 "even_gpr_operand" "=e")
4543 (mult:DI (sign_extend:DI (match_operand:SI 3 "integer_register_operand" "%d"))
4544 (sign_extend:DI (match_operand:SI 4 "integer_register_operand" "d")))))]
4546 "csmul %3, %4, %2, %1, %e0"
4547 [(set_attr "length" "4")
4548 (set_attr "type" "mul")])
4550 (define_insn "*cond_exec_si_divide"
4552 (match_operator 0 "ccr_eqne_operator"
4553 [(match_operand 1 "cr_operand" "C")
4555 (set (match_operand:SI 2 "integer_register_operand" "=d")
4556 (match_operator:SI 3 "condexec_si_divide_operator"
4557 [(match_operand:SI 4 "integer_register_operand" "d")
4558 (match_operand:SI 5 "integer_register_operand" "d")])))]
4562 switch (GET_CODE (operands[3]))
4564 case DIV: return \"csdiv %4, %z5, %2, %1, %e0\";
4565 case UDIV: return \"cudiv %4, %z5, %2, %1, %e0\";
4566 default: gcc_unreachable ();
4569 [(set_attr "length" "4")
4570 (set_attr "type" "div")])
4572 (define_insn "*cond_exec_si_unary1"
4574 (match_operator 0 "ccr_eqne_operator"
4575 [(match_operand 1 "cr_operand" "C")
4577 (set (match_operand:SI 2 "integer_register_operand" "=d")
4578 (match_operator:SI 3 "condexec_si_unary_operator"
4579 [(match_operand:SI 4 "integer_register_operand" "d")])))]
4583 switch (GET_CODE (operands[3]))
4585 case NOT: return \"cnot %4, %2, %1, %e0\";
4586 case NEG: return \"csub %., %4, %2, %1, %e0\";
4587 default: gcc_unreachable ();
4590 [(set_attr "length" "4")
4591 (set_attr "type" "int")])
4593 (define_insn "*cond_exec_si_unary2"
4595 (match_operator 0 "ccr_eqne_operator"
4596 [(match_operand 1 "cr_operand" "C")
4598 (set (match_operand:SI 2 "fpr_operand" "=f")
4599 (not:SI (match_operand:SI 3 "fpr_operand" "f"))))]
4601 "cmnot %3, %2, %1, %e0"
4602 [(set_attr "length" "4")
4603 (set_attr "type" "mlogic")])
4605 (define_insn "*cond_exec_cmpsi_cc"
4607 (match_operator 0 "ccr_eqne_operator"
4608 [(match_operand 1 "cr_operand" "C")
4610 (set (match_operand:CC 2 "icc_operand" "=t")
4611 (compare:CC (match_operand:SI 3 "integer_register_operand" "d")
4612 (match_operand:SI 4 "reg_or_0_operand" "dO"))))]
4614 && REGNO (operands[1]) == REGNO (operands[2]) - ICC_FIRST + ICR_FIRST"
4615 "ccmp %3, %z4, %1, %e0"
4616 [(set_attr "length" "4")
4617 (set_attr "type" "int")])
4619 (define_insn "*cond_exec_cmpsi_cc_uns"
4621 (match_operator 0 "ccr_eqne_operator"
4622 [(match_operand 1 "cr_operand" "C")
4624 (set (match_operand:CC_UNS 2 "icc_operand" "=t")
4625 (compare:CC_UNS (match_operand:SI 3 "integer_register_operand" "d")
4626 (match_operand:SI 4 "reg_or_0_operand" "dO"))))]
4628 && REGNO (operands[1]) == REGNO (operands[2]) - ICC_FIRST + ICR_FIRST"
4629 "ccmp %3, %z4, %1, %e0"
4630 [(set_attr "length" "4")
4631 (set_attr "type" "int")])
4633 (define_insn "*cond_exec_cmpsi_cc_nz"
4635 (match_operator 0 "ccr_eqne_operator"
4636 [(match_operand 1 "cr_operand" "C")
4638 (set (match_operand:CC_NZ 2 "icc_operand" "=t")
4639 (compare:CC_NZ (match_operand:SI 3 "integer_register_operand" "d")
4642 && REGNO (operands[1]) == REGNO (operands[2]) - ICC_FIRST + ICR_FIRST"
4643 "ccmp %3, %., %1, %e0"
4644 [(set_attr "length" "4")
4645 (set_attr "type" "int")])
4647 (define_insn "*cond_exec_sf_conv"
4649 (match_operator 0 "ccr_eqne_operator"
4650 [(match_operand 1 "cr_operand" "C")
4652 (set (match_operand:SF 2 "fpr_operand" "=f")
4653 (match_operator:SF 3 "condexec_sf_conv_operator"
4654 [(match_operand:SF 4 "fpr_operand" "f")])))]
4658 switch (GET_CODE (operands[3]))
4660 case ABS: return \"cfabss %4, %2, %1, %e0\";
4661 case NEG: return \"cfnegs %4, %2, %1, %e0\";
4662 default: gcc_unreachable ();
4665 [(set_attr "length" "4")
4666 (set_attr "type" "fsconv")])
4668 (define_insn "*cond_exec_sf_add"
4670 (match_operator 0 "ccr_eqne_operator"
4671 [(match_operand 1 "cr_operand" "C")
4673 (set (match_operand:SF 2 "fpr_operand" "=f")
4674 (match_operator:SF 3 "condexec_sf_add_operator"
4675 [(match_operand:SF 4 "fpr_operand" "f")
4676 (match_operand:SF 5 "fpr_operand" "f")])))]
4680 switch (GET_CODE (operands[3]))
4682 case PLUS: return \"cfadds %4, %5, %2, %1, %e0\";
4683 case MINUS: return \"cfsubs %4, %5, %2, %1, %e0\";
4684 default: gcc_unreachable ();
4687 [(set_attr "length" "4")
4688 (set_attr "type" "fsadd")])
4690 (define_insn "*cond_exec_sf_mul"
4692 (match_operator 0 "ccr_eqne_operator"
4693 [(match_operand 1 "cr_operand" "C")
4695 (set (match_operand:SF 2 "fpr_operand" "=f")
4696 (mult:SF (match_operand:SF 3 "fpr_operand" "f")
4697 (match_operand:SF 4 "fpr_operand" "f"))))]
4699 "cfmuls %3, %4, %2, %1, %e0"
4700 [(set_attr "length" "4")
4701 (set_attr "type" "fsmul")])
4703 (define_insn "*cond_exec_sf_div"
4705 (match_operator 0 "ccr_eqne_operator"
4706 [(match_operand 1 "cr_operand" "C")
4708 (set (match_operand:SF 2 "fpr_operand" "=f")
4709 (div:SF (match_operand:SF 3 "fpr_operand" "f")
4710 (match_operand:SF 4 "fpr_operand" "f"))))]
4712 "cfdivs %3, %4, %2, %1, %e0"
4713 [(set_attr "length" "4")
4714 (set_attr "type" "fsdiv")])
4716 (define_insn "*cond_exec_sf_sqrt"
4718 (match_operator 0 "ccr_eqne_operator"
4719 [(match_operand 1 "cr_operand" "C")
4721 (set (match_operand:SF 2 "fpr_operand" "=f")
4722 (sqrt:SF (match_operand:SF 3 "fpr_operand" "f"))))]
4724 "cfsqrts %3, %2, %1, %e0"
4725 [(set_attr "length" "4")
4726 (set_attr "type" "fsdiv")])
4728 (define_insn "*cond_exec_cmpsi_cc_fp"
4730 (match_operator 0 "ccr_eqne_operator"
4731 [(match_operand 1 "cr_operand" "C")
4733 (set (match_operand:CC_FP 2 "fcc_operand" "=u")
4734 (compare:CC_FP (match_operand:SF 3 "fpr_operand" "f")
4735 (match_operand:SF 4 "fpr_operand" "f"))))]
4736 "reload_completed && TARGET_HARD_FLOAT
4737 && REGNO (operands[1]) == REGNO (operands[2]) - FCC_FIRST + FCR_FIRST"
4738 "cfcmps %3, %4, %2, %1, %e0"
4739 [(set_attr "length" "4")
4740 (set_attr "type" "fsconv")])
4743 ;; ::::::::::::::::::::
4745 ;; :: Logical operations on CR registers
4747 ;; ::::::::::::::::::::
4749 ;; We use UNSPEC to encode andcr/iorcr/etc. rather than the normal RTL
4750 ;; operations, since the RTL operations only have an idea of TRUE and FALSE,
4751 ;; while the CRs have TRUE, FALSE, and UNDEFINED.
4753 (define_expand "andcr"
4754 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4755 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4756 (match_operand:CC_CCR 2 "cr_operand" "")
4757 (const_int 0)] UNSPEC_CR_LOGIC))]
4761 (define_expand "orcr"
4762 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4763 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4764 (match_operand:CC_CCR 2 "cr_operand" "")
4765 (const_int 1)] UNSPEC_CR_LOGIC))]
4769 (define_expand "xorcr"
4770 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4771 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4772 (match_operand:CC_CCR 2 "cr_operand" "")
4773 (const_int 2)] UNSPEC_CR_LOGIC))]
4777 (define_expand "nandcr"
4778 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4779 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4780 (match_operand:CC_CCR 2 "cr_operand" "")
4781 (const_int 3)] UNSPEC_CR_LOGIC))]
4785 (define_expand "norcr"
4786 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4787 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4788 (match_operand:CC_CCR 2 "cr_operand" "")
4789 (const_int 4)] UNSPEC_CR_LOGIC))]
4793 (define_expand "andncr"
4794 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4795 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4796 (match_operand:CC_CCR 2 "cr_operand" "")
4797 (const_int 5)] UNSPEC_CR_LOGIC))]
4801 (define_expand "orncr"
4802 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4803 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4804 (match_operand:CC_CCR 2 "cr_operand" "")
4805 (const_int 6)] UNSPEC_CR_LOGIC))]
4809 (define_expand "nandncr"
4810 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4811 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4812 (match_operand:CC_CCR 2 "cr_operand" "")
4813 (const_int 7)] UNSPEC_CR_LOGIC))]
4817 (define_expand "norncr"
4818 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4819 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4820 (match_operand:CC_CCR 2 "cr_operand" "")
4821 (const_int 8)] UNSPEC_CR_LOGIC))]
4825 (define_expand "notcr"
4826 [(set (match_operand:CC_CCR 0 "cr_operand" "")
4827 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "")
4829 (const_int 9)] UNSPEC_CR_LOGIC))]
4833 (define_insn "*logical_cr"
4834 [(set (match_operand:CC_CCR 0 "cr_operand" "=C")
4835 (unspec:CC_CCR [(match_operand:CC_CCR 1 "cr_operand" "C")
4836 (match_operand:CC_CCR 2 "cr_operand" "C")
4837 (match_operand:SI 3 "const_int_operand" "n")]
4842 switch (INTVAL (operands[3]))
4845 case 0: return \"andcr %1, %2, %0\";
4846 case 1: return \"orcr %1, %2, %0\";
4847 case 2: return \"xorcr %1, %2, %0\";
4848 case 3: return \"nandcr %1, %2, %0\";
4849 case 4: return \"norcr %1, %2, %0\";
4850 case 5: return \"andncr %1, %2, %0\";
4851 case 6: return \"orncr %1, %2, %0\";
4852 case 7: return \"nandncr %1, %2, %0\";
4853 case 8: return \"norncr %1, %2, %0\";
4854 case 9: return \"notcr %1, %0\";
4857 fatal_insn (\"logical_cr\", insn);
4859 [(set_attr "length" "4")
4860 (set_attr "type" "ccr")])
4863 ;; ::::::::::::::::::::
4865 ;; :: Conditional move instructions
4867 ;; ::::::::::::::::::::
4870 ;; - conditional moves based on floating-point comparisons require
4871 ;; TARGET_HARD_FLOAT, because an FPU is required to do the comparison.
4873 ;; - conditional moves between FPRs based on integer comparisons
4874 ;; require TARGET_HAS_FPRS.
4876 (define_expand "movqicc"
4877 [(set (match_operand:QI 0 "integer_register_operand" "")
4878 (if_then_else:QI (match_operand 1 "" "")
4879 (match_operand:QI 2 "gpr_or_int_operand" "")
4880 (match_operand:QI 3 "gpr_or_int_operand" "")))]
4884 if (!frv_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
4890 (define_insn "*movqicc_internal1_int"
4891 [(set (match_operand:QI 0 "integer_register_operand" "=d,d,d")
4892 (if_then_else:QI (match_operator 1 "integer_relational_operator"
4893 [(match_operand 2 "icc_operand" "t,t,t")
4895 (match_operand:QI 3 "reg_or_0_operand" "0,dO,dO")
4896 (match_operand:QI 4 "reg_or_0_operand" "dO,0,dO")))
4897 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v"))]
4900 [(set_attr "length" "8,8,12")
4901 (set_attr "type" "multi")])
4903 (define_insn "*movqicc_internal1_float"
4904 [(set (match_operand:QI 0 "integer_register_operand" "=d,d,d")
4905 (if_then_else:QI (match_operator:CC_FP 1 "float_relational_operator"
4906 [(match_operand:CC_FP 2 "fcc_operand" "u,u,u")
4908 (match_operand:QI 3 "reg_or_0_operand" "0,dO,dO")
4909 (match_operand:QI 4 "reg_or_0_operand" "dO,0,dO")))
4910 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w"))]
4913 [(set_attr "length" "8,8,12")
4914 (set_attr "type" "multi")])
4916 (define_insn "*movqicc_internal2_int"
4917 [(set (match_operand:QI 0 "integer_register_operand" "=d,d,d,d,d")
4918 (if_then_else:QI (match_operator 1 "integer_relational_operator"
4919 [(match_operand 2 "icc_operand" "t,t,t,t,t")
4921 (match_operand:QI 3 "const_int_operand" "O,O,L,n,n")
4922 (match_operand:QI 4 "const_int_operand" "L,n,O,O,n")))
4923 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v,v,v"))]
4924 "(INTVAL (operands[3]) == 0
4925 || INTVAL (operands[4]) == 0
4926 || (IN_RANGE_P (INTVAL (operands[3]), -2048, 2047)
4927 && IN_RANGE_P (INTVAL (operands[4]) - INTVAL (operands[3]), -2048, 2047)))"
4929 [(set_attr "length" "8,12,8,12,12")
4930 (set_attr "type" "multi")])
4932 (define_insn "*movqicc_internal2_float"
4933 [(set (match_operand:QI 0 "integer_register_operand" "=d,d,d,d,d")
4934 (if_then_else:QI (match_operator:CC_FP 1 "float_relational_operator"
4935 [(match_operand:CC_FP 2 "fcc_operand" "u,u,u,u,u")
4937 (match_operand:QI 3 "const_int_operand" "O,O,L,n,n")
4938 (match_operand:QI 4 "const_int_operand" "L,n,O,O,n")))
4939 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w,w,w"))]
4941 && (INTVAL (operands[3]) == 0
4942 || INTVAL (operands[4]) == 0
4943 || (IN_RANGE_P (INTVAL (operands[3]), -2048, 2047)
4944 && IN_RANGE_P (INTVAL (operands[4]) - INTVAL (operands[3]), -2048, 2047)))"
4946 [(set_attr "length" "8,12,8,12,12")
4947 (set_attr "type" "multi")])
4950 [(set (match_operand:QI 0 "integer_register_operand" "")
4951 (if_then_else:QI (match_operator 1 "relational_operator"
4952 [(match_operand 2 "cc_operand" "")
4954 (match_operand:QI 3 "gpr_or_int_operand" "")
4955 (match_operand:QI 4 "gpr_or_int_operand" "")))
4956 (clobber (match_operand:CC_CCR 5 "cr_operand" ""))]
4959 "operands[6] = frv_split_cond_move (operands);")
4961 (define_expand "movhicc"
4962 [(set (match_operand:HI 0 "integer_register_operand" "")
4963 (if_then_else:HI (match_operand 1 "" "")
4964 (match_operand:HI 2 "gpr_or_int_operand" "")
4965 (match_operand:HI 3 "gpr_or_int_operand" "")))]
4969 if (!frv_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
4975 (define_insn "*movhicc_internal1_int"
4976 [(set (match_operand:HI 0 "integer_register_operand" "=d,d,d")
4977 (if_then_else:HI (match_operator 1 "integer_relational_operator"
4978 [(match_operand 2 "icc_operand" "t,t,t")
4980 (match_operand:HI 3 "reg_or_0_operand" "0,dO,dO")
4981 (match_operand:HI 4 "reg_or_0_operand" "dO,0,dO")))
4982 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v"))]
4985 [(set_attr "length" "8,8,12")
4986 (set_attr "type" "multi")])
4988 (define_insn "*movhicc_internal1_float"
4989 [(set (match_operand:HI 0 "integer_register_operand" "=d,d,d")
4990 (if_then_else:HI (match_operator:CC_FP 1 "float_relational_operator"
4991 [(match_operand:CC_FP 2 "fcc_operand" "u,u,u")
4993 (match_operand:HI 3 "reg_or_0_operand" "0,dO,dO")
4994 (match_operand:HI 4 "reg_or_0_operand" "dO,0,dO")))
4995 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w"))]
4998 [(set_attr "length" "8,8,12")
4999 (set_attr "type" "multi")])
5001 (define_insn "*movhicc_internal2_int"
5002 [(set (match_operand:HI 0 "integer_register_operand" "=d,d,d,d,d")
5003 (if_then_else:HI (match_operator 1 "integer_relational_operator"
5004 [(match_operand 2 "icc_operand" "t,t,t,t,t")
5006 (match_operand:HI 3 "const_int_operand" "O,O,L,n,n")
5007 (match_operand:HI 4 "const_int_operand" "L,n,O,O,n")))
5008 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v,v,v"))]
5009 "(INTVAL (operands[3]) == 0
5010 || INTVAL (operands[4]) == 0
5011 || (IN_RANGE_P (INTVAL (operands[3]), -2048, 2047)
5012 && IN_RANGE_P (INTVAL (operands[4]) - INTVAL (operands[3]), -2048, 2047)))"
5014 [(set_attr "length" "8,12,8,12,12")
5015 (set_attr "type" "multi")])
5017 (define_insn "*movhicc_internal2_float"
5018 [(set (match_operand:HI 0 "integer_register_operand" "=d,d,d,d,d")
5019 (if_then_else:HI (match_operator:CC_FP 1 "float_relational_operator"
5020 [(match_operand:CC_FP 2 "fcc_operand" "u,u,u,u,u")
5022 (match_operand:HI 3 "const_int_operand" "O,O,L,n,n")
5023 (match_operand:HI 4 "const_int_operand" "L,n,O,O,n")))
5024 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w,w,w"))]
5026 && (INTVAL (operands[3]) == 0
5027 || INTVAL (operands[4]) == 0
5028 || (IN_RANGE_P (INTVAL (operands[3]), -2048, 2047)
5029 && IN_RANGE_P (INTVAL (operands[4]) - INTVAL (operands[3]), -2048, 2047)))"
5031 [(set_attr "length" "8,12,8,12,12")
5032 (set_attr "type" "multi")])
5035 [(set (match_operand:HI 0 "integer_register_operand" "")
5036 (if_then_else:HI (match_operator 1 "relational_operator"
5037 [(match_operand 2 "cc_operand" "")
5039 (match_operand:HI 3 "gpr_or_int_operand" "")
5040 (match_operand:HI 4 "gpr_or_int_operand" "")))
5041 (clobber (match_operand:CC_CCR 5 "cr_operand" ""))]
5044 "operands[6] = frv_split_cond_move (operands);")
5046 (define_expand "movsicc"
5047 [(set (match_operand:SI 0 "integer_register_operand" "")
5048 (if_then_else:SI (match_operand 1 "" "")
5049 (match_operand:SI 2 "gpr_or_int_operand" "")
5050 (match_operand:SI 3 "gpr_or_int_operand" "")))]
5054 if (!frv_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
5060 (define_insn "*movsicc_internal1_int"
5061 [(set (match_operand:SI 0 "integer_register_operand" "=d,d,d")
5062 (if_then_else:SI (match_operator 1 "integer_relational_operator"
5063 [(match_operand 2 "icc_operand" "t,t,t")
5065 (match_operand:SI 3 "reg_or_0_operand" "0,dO,dO")
5066 (match_operand:SI 4 "reg_or_0_operand" "dO,0,dO")))
5067 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v"))]
5070 [(set_attr "length" "8,8,12")
5071 (set_attr "type" "multi")])
5073 (define_insn "*movsicc_internal1_float"
5074 [(set (match_operand:SI 0 "integer_register_operand" "=d,d,d")
5075 (if_then_else:SI (match_operator:CC_FP 1 "float_relational_operator"
5076 [(match_operand:CC_FP 2 "fcc_operand" "u,u,u")
5078 (match_operand:SI 3 "reg_or_0_operand" "0,dO,dO")
5079 (match_operand:SI 4 "reg_or_0_operand" "dO,0,dO")))
5080 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w"))]
5083 [(set_attr "length" "8,8,12")
5084 (set_attr "type" "multi")])
5086 (define_insn "*movsicc_internal2_int"
5087 [(set (match_operand:SI 0 "integer_register_operand" "=d,d,d,d,d")
5088 (if_then_else:SI (match_operator 1 "integer_relational_operator"
5089 [(match_operand 2 "icc_operand" "t,t,t,t,t")
5091 (match_operand:SI 3 "const_int_operand" "O,O,L,n,n")
5092 (match_operand:SI 4 "const_int_operand" "L,n,O,O,n")))
5093 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v,v,v"))]
5094 "(INTVAL (operands[3]) == 0
5095 || INTVAL (operands[4]) == 0
5096 || (IN_RANGE_P (INTVAL (operands[3]), -2048, 2047)
5097 && IN_RANGE_P (INTVAL (operands[4]) - INTVAL (operands[3]), -2048, 2047)))"
5099 [(set_attr "length" "8,12,8,12,12")
5100 (set_attr "type" "multi")])
5102 (define_insn "*movsicc_internal2_float"
5103 [(set (match_operand:SI 0 "integer_register_operand" "=d,d,d,d,d")
5104 (if_then_else:SI (match_operator:CC_FP 1 "float_relational_operator"
5105 [(match_operand:CC_FP 2 "fcc_operand" "u,u,u,u,u")
5107 (match_operand:SI 3 "const_int_operand" "O,O,L,n,n")
5108 (match_operand:SI 4 "const_int_operand" "L,n,O,O,n")))
5109 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w,w,w"))]
5111 && (INTVAL (operands[3]) == 0
5112 || INTVAL (operands[4]) == 0
5113 || (IN_RANGE_P (INTVAL (operands[3]), -2048, 2047)
5114 && IN_RANGE_P (INTVAL (operands[4]) - INTVAL (operands[3]), -2048, 2047)))"
5116 [(set_attr "length" "8,12,8,12,12")
5117 (set_attr "type" "multi")])
5120 [(set (match_operand:SI 0 "integer_register_operand" "")
5121 (if_then_else:SI (match_operator 1 "relational_operator"
5122 [(match_operand 2 "cc_operand" "")
5124 (match_operand:SI 3 "gpr_or_int_operand" "")
5125 (match_operand:SI 4 "gpr_or_int_operand" "")))
5126 (clobber (match_operand:CC_CCR 5 "cr_operand" ""))]
5129 "operands[6] = frv_split_cond_move (operands);")
5131 (define_expand "movsfcc"
5132 [(set (match_operand:SF 0 "register_operand" "")
5133 (if_then_else:SF (match_operand 1 "" "")
5134 (match_operand:SF 2 "register_operand" "")
5135 (match_operand:SF 3 "register_operand" "")))]
5139 if (!frv_emit_cond_move (operands[0], operands[1], operands[2], operands[3]))
5145 (define_insn "*movsfcc_has_fprs_int"
5146 [(set (match_operand:SF 0 "register_operand" "=f,f,f,?f,?f,?d")
5147 (if_then_else:SF (match_operator 1 "integer_relational_operator"
5148 [(match_operand 2 "icc_operand" "t,t,t,t,t,t")
5150 (match_operand:SF 3 "register_operand" "0,f,f,f,d,fd")
5151 (match_operand:SF 4 "register_operand" "f,0,f,d,fd,fd")))
5152 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v,v,v,v"))]
5155 [(set_attr "length" "8,8,12,12,12,12")
5156 (set_attr "type" "multi")])
5158 (define_insn "*movsfcc_hardfloat_float"
5159 [(set (match_operand:SF 0 "register_operand" "=f,f,f,?f,?f,?d")
5160 (if_then_else:SF (match_operator:CC_FP 1 "float_relational_operator"
5161 [(match_operand:CC_FP 2 "fcc_operand" "u,u,u,u,u,u")
5163 (match_operand:SF 3 "register_operand" "0,f,f,f,d,fd")
5164 (match_operand:SF 4 "register_operand" "f,0,f,d,fd,fd")))
5165 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w,w,w,w"))]
5168 [(set_attr "length" "8,8,12,12,12,12")
5169 (set_attr "type" "multi")])
5171 (define_insn "*movsfcc_no_fprs_int"
5172 [(set (match_operand:SF 0 "integer_register_operand" "=d,d,d")
5173 (if_then_else:SF (match_operator 1 "integer_relational_operator"
5174 [(match_operand 2 "icc_operand" "t,t,t")
5176 (match_operand:SF 3 "integer_register_operand" "0,d,d")
5177 (match_operand:SF 4 "integer_register_operand" "d,0,d")))
5178 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v"))]
5181 [(set_attr "length" "8,8,12")
5182 (set_attr "type" "multi")])
5185 [(set (match_operand:SF 0 "register_operand" "")
5186 (if_then_else:SF (match_operator 1 "relational_operator"
5187 [(match_operand 2 "cc_operand" "")
5189 (match_operand:SF 3 "register_operand" "")
5190 (match_operand:SF 4 "register_operand" "")))
5191 (clobber (match_operand:CC_CCR 5 "cr_operand" ""))]
5194 "operands[6] = frv_split_cond_move (operands);")
5197 ;; ::::::::::::::::::::
5199 ;; :: Minimum, maximum, and integer absolute value
5201 ;; ::::::::::::::::::::
5203 ;; These 'instructions' are provided to give the compiler a slightly better
5204 ;; nudge at register allocation, then it would if it constructed the
5205 ;; instructions from basic building blocks (since it indicates it prefers one
5206 ;; of the operands to be the same as the destination. It also helps the
5207 ;; earlier passes of the compiler, by not breaking things into small basic
5210 (define_expand "abssi2"
5211 [(parallel [(set (match_operand:SI 0 "integer_register_operand" "")
5212 (abs:SI (match_operand:SI 1 "integer_register_operand" "")))
5213 (clobber (match_dup 2))
5214 (clobber (match_dup 3))])]
5218 operands[2] = gen_reg_rtx (CCmode);
5219 operands[3] = gen_reg_rtx (CC_CCRmode);
5222 (define_insn_and_split "*abssi2_internal"
5223 [(set (match_operand:SI 0 "integer_register_operand" "=d,d")
5224 (abs:SI (match_operand:SI 1 "integer_register_operand" "0,d")))
5225 (clobber (match_operand:CC 2 "icc_operand" "=t,t"))
5226 (clobber (match_operand:CC_CCR 3 "icr_operand" "=v,v"))]
5231 "operands[4] = frv_split_abs (operands);"
5232 [(set_attr "length" "12,16")
5233 (set_attr "type" "multi")])
5235 (define_expand "sminsi3"
5236 [(parallel [(set (match_operand:SI 0 "integer_register_operand" "")
5237 (smin:SI (match_operand:SI 1 "integer_register_operand" "")
5238 (match_operand:SI 2 "gpr_or_int10_operand" "")))
5239 (clobber (match_dup 3))
5240 (clobber (match_dup 4))])]
5244 operands[3] = gen_reg_rtx (CCmode);
5245 operands[4] = gen_reg_rtx (CC_CCRmode);
5248 (define_expand "smaxsi3"
5249 [(parallel [(set (match_operand:SI 0 "integer_register_operand" "")
5250 (smax:SI (match_operand:SI 1 "integer_register_operand" "")
5251 (match_operand:SI 2 "gpr_or_int10_operand" "")))
5252 (clobber (match_dup 3))
5253 (clobber (match_dup 4))])]
5257 operands[3] = gen_reg_rtx (CCmode);
5258 operands[4] = gen_reg_rtx (CC_CCRmode);
5261 (define_insn_and_split "*minmax_si_signed"
5262 [(set (match_operand:SI 0 "integer_register_operand" "=d,d,&d")
5263 (match_operator:SI 1 "minmax_operator"
5264 [(match_operand:SI 2 "integer_register_operand" "%0,dO,d")
5265 (match_operand:SI 3 "gpr_or_int10_operand" "dO,0,dJ")]))
5266 (clobber (match_operand:CC 4 "icc_operand" "=t,t,t"))
5267 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v"))]
5272 "operands[6] = frv_split_minmax (operands);"
5273 [(set_attr "length" "12,12,16")
5274 (set_attr "type" "multi")])
5276 (define_expand "uminsi3"
5277 [(parallel [(set (match_operand:SI 0 "integer_register_operand" "")
5278 (umin:SI (match_operand:SI 1 "integer_register_operand" "")
5279 (match_operand:SI 2 "gpr_or_int10_operand" "")))
5280 (clobber (match_dup 3))
5281 (clobber (match_dup 4))])]
5285 operands[3] = gen_reg_rtx (CC_UNSmode);
5286 operands[4] = gen_reg_rtx (CC_CCRmode);
5289 (define_expand "umaxsi3"
5290 [(parallel [(set (match_operand:SI 0 "integer_register_operand" "")
5291 (umax:SI (match_operand:SI 1 "integer_register_operand" "")
5292 (match_operand:SI 2 "gpr_or_int10_operand" "")))
5293 (clobber (match_dup 3))
5294 (clobber (match_dup 4))])]
5298 operands[3] = gen_reg_rtx (CC_UNSmode);
5299 operands[4] = gen_reg_rtx (CC_CCRmode);
5302 (define_insn_and_split "*minmax_si_unsigned"
5303 [(set (match_operand:SI 0 "integer_register_operand" "=d,d,&d")
5304 (match_operator:SI 1 "minmax_operator"
5305 [(match_operand:SI 2 "integer_register_operand" "%0,dO,d")
5306 (match_operand:SI 3 "gpr_or_int10_operand" "dO,0,dJ")]))
5307 (clobber (match_operand:CC_UNS 4 "icc_operand" "=t,t,t"))
5308 (clobber (match_operand:CC_CCR 5 "icr_operand" "=v,v,v"))]
5313 "operands[6] = frv_split_minmax (operands);"
5314 [(set_attr "length" "12,12,16")
5315 (set_attr "type" "multi")])
5317 (define_expand "sminsf3"
5318 [(parallel [(set (match_operand:SF 0 "fpr_operand" "")
5319 (smin:SF (match_operand:SF 1 "fpr_operand" "")
5320 (match_operand:SF 2 "fpr_operand" "")))
5321 (clobber (match_dup 3))
5322 (clobber (match_dup 4))])]
5323 "TARGET_COND_MOVE && TARGET_HARD_FLOAT"
5326 operands[3] = gen_reg_rtx (CC_FPmode);
5327 operands[4] = gen_reg_rtx (CC_CCRmode);
5330 (define_expand "smaxsf3"
5331 [(parallel [(set (match_operand:SF 0 "fpr_operand" "")
5332 (smax:SF (match_operand:SF 1 "fpr_operand" "")
5333 (match_operand:SF 2 "fpr_operand" "")))
5334 (clobber (match_dup 3))
5335 (clobber (match_dup 4))])]
5336 "TARGET_COND_MOVE && TARGET_HARD_FLOAT"
5339 operands[3] = gen_reg_rtx (CC_FPmode);
5340 operands[4] = gen_reg_rtx (CC_CCRmode);
5343 (define_insn_and_split "*minmax_sf"
5344 [(set (match_operand:SF 0 "fpr_operand" "=f,f,f")
5345 (match_operator:SF 1 "minmax_operator"
5346 [(match_operand:SF 2 "fpr_operand" "%0,f,f")
5347 (match_operand:SF 3 "fpr_operand" "f,0,f")]))
5348 (clobber (match_operand:CC_FP 4 "fcc_operand" "=u,u,u"))
5349 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w"))]
5350 "TARGET_COND_MOVE && TARGET_HARD_FLOAT"
5354 "operands[6] = frv_split_minmax (operands);"
5355 [(set_attr "length" "12,12,16")
5356 (set_attr "type" "multi")])
5358 (define_expand "smindf3"
5359 [(parallel [(set (match_operand:DF 0 "fpr_operand" "")
5360 (smin:DF (match_operand:DF 1 "fpr_operand" "")
5361 (match_operand:DF 2 "fpr_operand" "")))
5362 (clobber (match_dup 3))
5363 (clobber (match_dup 4))])]
5364 "TARGET_COND_MOVE && TARGET_HARD_FLOAT && TARGET_DOUBLE"
5367 operands[3] = gen_reg_rtx (CC_FPmode);
5368 operands[4] = gen_reg_rtx (CC_CCRmode);
5371 (define_expand "smaxdf3"
5372 [(parallel [(set (match_operand:DF 0 "fpr_operand" "")
5373 (smax:DF (match_operand:DF 1 "fpr_operand" "")
5374 (match_operand:DF 2 "fpr_operand" "")))
5375 (clobber (match_dup 3))
5376 (clobber (match_dup 4))])]
5377 "TARGET_COND_MOVE && TARGET_HARD_FLOAT && TARGET_DOUBLE"
5380 operands[3] = gen_reg_rtx (CC_FPmode);
5381 operands[4] = gen_reg_rtx (CC_CCRmode);
5384 (define_insn_and_split "*minmax_df"
5385 [(set (match_operand:DF 0 "fpr_operand" "=f,f,f")
5386 (match_operator:DF 1 "minmax_operator"
5387 [(match_operand:DF 2 "fpr_operand" "%0,f,f")
5388 (match_operand:DF 3 "fpr_operand" "f,0,f")]))
5389 (clobber (match_operand:CC_FP 4 "fcc_operand" "=u,u,u"))
5390 (clobber (match_operand:CC_CCR 5 "fcr_operand" "=w,w,w"))]
5391 "TARGET_COND_MOVE && TARGET_HARD_FLOAT && TARGET_DOUBLE"
5395 "operands[6] = frv_split_minmax (operands);"
5396 [(set_attr "length" "12,12,16")
5397 (set_attr "type" "multi")])
5400 ;; ::::::::::::::::::::
5402 ;; :: Call and branch instructions
5404 ;; ::::::::::::::::::::
5406 ;; Subroutine call instruction returning no value. Operand 0 is the function
5407 ;; to call; operand 1 is the number of bytes of arguments pushed (in mode
5408 ;; `SImode', except it is normally a `const_int'); operand 2 is the number of
5409 ;; registers used as operands.
5411 ;; On most machines, operand 2 is not actually stored into the RTL pattern. It
5412 ;; is supplied for the sake of some RISC machines which need to put this
5413 ;; information into the assembler code; they can put it in the RTL instead of
5416 (define_expand "call"
5417 [(use (match_operand:QI 0 "" ""))
5418 (use (match_operand 1 "" ""))
5419 (use (match_operand 2 "" ""))
5420 (use (match_operand 3 "" ""))]
5424 rtx lr = gen_rtx_REG (Pmode, LR_REGNO);
5427 gcc_assert (GET_CODE (operands[0]) == MEM);
5429 addr = XEXP (operands[0], 0);
5430 if (! call_operand (addr, Pmode))
5431 addr = force_reg (Pmode, addr);
5434 operands[2] = const0_rtx;
5437 frv_expand_fdpic_call (operands, false, false);
5439 emit_call_insn (gen_call_internal (addr, operands[1], operands[2], lr));
5444 (define_insn "call_internal"
5445 [(call (mem:QI (match_operand:SI 0 "call_operand" "S,dNOP"))
5446 (match_operand 1 "" ""))
5447 (use (match_operand 2 "" ""))
5448 (clobber (match_operand:SI 3 "lr_operand" "=l,l"))]
5453 [(set_attr "length" "4")
5454 (set_attr "type" "call,jumpl")])
5456 ;; The odd use of GR0 within the UNSPEC below prevents cseing or
5457 ;; hoisting function descriptor loads out of loops. This is almost
5458 ;; never desirable, since if we preserve the function descriptor in a
5459 ;; pair of registers, it takes two insns to move it to gr14/gr15, and
5460 ;; if it's in the stack, we just waste space with the store, since
5461 ;; we'll have to load back from memory anyway. And, in the worst
5462 ;; case, we may end up reusing a function descriptor still pointing at
5463 ;; a PLT entry, instead of to the resolved function, which means going
5464 ;; through the resolver for every call that uses the outdated value.
5467 ;; The explicit MEM inside the SPEC prevents the compiler from moving
5468 ;; the load before a branch after a NULL test, or before a store that
5469 ;; initializes a function descriptor.
5471 (define_insn "movdi_ldd"
5472 [(set (match_operand:DI 0 "fdpic_fptr_operand" "=e")
5473 (unspec:DI [(mem:DI (match_operand:SI 1 "ldd_address_operand" "p"))
5474 (reg:SI 0)] UNSPEC_LDD))]
5477 [(set_attr "length" "4")
5478 (set_attr "type" "gload")])
5480 (define_insn "call_fdpicdi"
5481 [(call (mem:QI (match_operand:DI 0 "fdpic_fptr_operand" "W"))
5482 (match_operand 1 "" ""))
5483 (clobber (match_operand:SI 2 "lr_operand" "=l"))]
5486 [(set_attr "length" "4")
5487 (set_attr "type" "jumpl")])
5489 (define_insn "call_fdpicsi"
5490 [(call (mem:QI (match_operand:SI 0 "call_operand" "S,dNOP"))
5491 (match_operand 1 "" ""))
5492 (use (match_operand 2 "" ""))
5493 (use (match_operand:SI 3 "fdpic_operand" "Z,Z"))
5494 (clobber (match_operand:SI 4 "lr_operand" "=l,l"))]
5499 [(set_attr "length" "4")
5500 (set_attr "type" "call,jumpl")])
5502 (define_expand "sibcall"
5503 [(use (match_operand:QI 0 "" ""))
5504 (use (match_operand 1 "" ""))
5505 (use (match_operand 2 "" ""))
5506 (use (match_operand 3 "" ""))]
5512 gcc_assert (GET_CODE (operands[0]) == MEM);
5514 addr = XEXP (operands[0], 0);
5515 if (! sibcall_operand (addr, Pmode))
5516 addr = force_reg (Pmode, addr);
5519 operands[2] = const0_rtx;
5522 frv_expand_fdpic_call (operands, false, true);
5524 emit_call_insn (gen_sibcall_internal (addr, operands[1], operands[2]));
5529 ;; It might seem that these sibcall patterns are missing references to
5530 ;; LR, but they're not necessary because sibcall_epilogue will make
5531 ;; sure LR is restored, and having LR here will set
5532 ;; regs_ever_used[REG_LR], forcing it to be saved on the stack, and
5533 ;; then restored in sibcalls and regular return code paths, even if
5534 ;; the function becomes a leaf function after tail-call elimination.
5536 ;; We must not use a call-saved register here. `W' limits ourselves
5537 ;; to gr14 or gr15, but since we're almost running out of constraint
5538 ;; letters, and most other call-clobbered registers are often used for
5539 ;; argument-passing, this will do.
5540 (define_insn "sibcall_internal"
5541 [(call (mem:QI (match_operand:SI 0 "sibcall_operand" "WNOP"))
5542 (match_operand 1 "" ""))
5543 (use (match_operand 2 "" ""))
5547 [(set_attr "length" "4")
5548 (set_attr "type" "jumpl")])
5550 (define_insn "sibcall_fdpicdi"
5551 [(call (mem:QI (match_operand:DI 0 "fdpic_fptr_operand" "W"))
5552 (match_operand 1 "" ""))
5556 [(set_attr "length" "4")
5557 (set_attr "type" "jumpl")])
5560 ;; Subroutine call instruction returning a value. Operand 0 is the hard
5561 ;; register in which the value is returned. There are three more operands, the
5562 ;; same as the three operands of the `call' instruction (but with numbers
5563 ;; increased by one).
5565 ;; Subroutines that return `BLKmode' objects use the `call' insn.
5567 (define_expand "call_value"
5568 [(use (match_operand 0 "" ""))
5569 (use (match_operand:QI 1 "" ""))
5570 (use (match_operand 2 "" ""))
5571 (use (match_operand 3 "" ""))
5572 (use (match_operand 4 "" ""))]
5576 rtx lr = gen_rtx_REG (Pmode, LR_REGNO);
5579 gcc_assert (GET_CODE (operands[1]) == MEM);
5581 addr = XEXP (operands[1], 0);
5582 if (! call_operand (addr, Pmode))
5583 addr = force_reg (Pmode, addr);
5586 operands[3] = const0_rtx;
5589 frv_expand_fdpic_call (operands, true, false);
5591 emit_call_insn (gen_call_value_internal (operands[0], addr, operands[2],
5597 (define_insn "call_value_internal"
5598 [(set (match_operand 0 "register_operand" "=d,d")
5599 (call (mem:QI (match_operand:SI 1 "call_operand" "S,dNOP"))
5600 (match_operand 2 "" "")))
5601 (use (match_operand 3 "" ""))
5602 (clobber (match_operand:SI 4 "lr_operand" "=l,l"))]
5607 [(set_attr "length" "4")
5608 (set_attr "type" "call,jumpl")])
5610 (define_insn "call_value_fdpicdi"
5611 [(set (match_operand 0 "register_operand" "=d")
5612 (call (mem:QI (match_operand:DI 1 "fdpic_fptr_operand" "W"))
5613 (match_operand 2 "" "")))
5614 (clobber (match_operand:SI 3 "lr_operand" "=l"))]
5617 [(set_attr "length" "4")
5618 (set_attr "type" "jumpl")])
5620 (define_insn "call_value_fdpicsi"
5621 [(set (match_operand 0 "register_operand" "=d,d")
5622 (call (mem:QI (match_operand:SI 1 "call_operand" "S,dNOP"))
5623 (match_operand 2 "" "")))
5624 (use (match_operand 3 "" ""))
5625 (use (match_operand:SI 4 "fdpic_operand" "Z,Z"))
5626 (clobber (match_operand:SI 5 "lr_operand" "=l,l"))]
5631 [(set_attr "length" "4")
5632 (set_attr "type" "call,jumpl")])
5634 (define_expand "sibcall_value"
5635 [(use (match_operand 0 "" ""))
5636 (use (match_operand:QI 1 "" ""))
5637 (use (match_operand 2 "" ""))
5638 (use (match_operand 3 "" ""))
5639 (use (match_operand 4 "" ""))]
5645 gcc_assert (GET_CODE (operands[1]) == MEM);
5647 addr = XEXP (operands[1], 0);
5648 if (! sibcall_operand (addr, Pmode))
5649 addr = force_reg (Pmode, addr);
5652 operands[3] = const0_rtx;
5655 frv_expand_fdpic_call (operands, true, true);
5657 emit_call_insn (gen_sibcall_value_internal (operands[0], addr, operands[2],
5662 (define_insn "sibcall_value_internal"
5663 [(set (match_operand 0 "register_operand" "=d")
5664 (call (mem:QI (match_operand:SI 1 "sibcall_operand" "WNOP"))
5665 (match_operand 2 "" "")))
5666 (use (match_operand 3 "" ""))
5670 [(set_attr "length" "4")
5671 (set_attr "type" "jumpl")])
5673 (define_insn "sibcall_value_fdpicdi"
5674 [(set (match_operand 0 "register_operand" "=d")
5675 (call (mem:QI (match_operand:DI 1 "fdpic_fptr_operand" "W"))
5676 (match_operand 2 "" "")))
5680 [(set_attr "length" "4")
5681 (set_attr "type" "jumpl")])
5683 ;; return instruction generated instead of jmp to epilog
5684 (define_expand "return"
5685 [(parallel [(return)
5687 (use (const_int 1))])]
5688 "direct_return_p ()"
5691 operands[0] = gen_rtx_REG (Pmode, LR_REGNO);
5694 ;; return instruction generated by the epilogue
5695 (define_expand "epilogue_return"
5696 [(parallel [(return)
5697 (use (match_operand:SI 0 "register_operand" ""))
5698 (use (const_int 0))])]
5702 (define_insn "*return_internal"
5704 (use (match_operand:SI 0 "register_operand" "l,d"))
5705 (use (match_operand:SI 1 "immediate_operand" "n,n"))]
5710 [(set_attr "length" "4")
5711 (set_attr "type" "jump,jumpl")])
5713 (define_insn "*return_true"
5715 (if_then_else (match_operator 0 "integer_relational_operator"
5716 [(match_operand 1 "icc_operand" "t")
5720 "direct_return_p ()"
5722 [(set_attr "length" "4")
5723 (set_attr "type" "jump")])
5725 (define_insn "*return_false"
5727 (if_then_else (match_operator 0 "integer_relational_operator"
5728 [(match_operand 1 "icc_operand" "t")
5732 "direct_return_p ()"
5734 [(set_attr "length" "4")
5735 (set_attr "type" "jump")])
5737 ;; A version of addsi3 for deallocating stack space at the end of the
5738 ;; epilogue. The addition is done in parallel with an (unspec_volatile),
5739 ;; which represents the clobbering of the deallocated space.
5740 (define_insn "stack_adjust"
5741 [(set (match_operand:SI 0 "register_operand" "=d")
5742 (plus:SI (match_operand:SI 1 "register_operand" "d")
5743 (match_operand:SI 2 "general_operand" "dNOP")))
5744 (unspec_volatile [(const_int 0)] UNSPEC_STACK_ADJUST)]
5747 [(set_attr "length" "4")
5748 (set_attr "type" "int")])
5750 ;; Normal unconditional jump
5752 ;; Use the "call" instruction for long branches, but prefer to use "bra" for
5753 ;; short ones since it does not force us to save the link register.
5755 ;; This define_insn uses the branch-shortening code to decide which
5756 ;; instruction it emits. Since the main branch-shortening interface is
5757 ;; through get_attr_length(), the two alternatives must be given different
5758 ;; lengths. Here we pretend that the far jump is 8 rather than 4 bytes
5759 ;; long, though both alternatives are really the same size.
5761 [(set (pc) (label_ref (match_operand 0 "" "")))]
5765 if (get_attr_length (insn) == 4)
5768 return \"call %l0\";
5770 [(set (attr "length")
5772 (and (ge (minus (match_dup 0) (pc)) (const_int -32768))
5773 (le (minus (match_dup 0) (pc)) (const_int 32764)))
5776 (set (attr "far_jump")
5778 (eq_attr "length" "4")
5780 (const_string "yes")))
5783 (eq_attr "length" "4")
5784 (const_string "jump")
5785 (const_string "call")))])
5787 ;; Indirect jump through a register
5788 (define_insn "indirect_jump"
5789 [(set (pc) (match_operand:SI 0 "register_operand" "d,l"))]
5794 [(set_attr "length" "4")
5795 (set_attr "type" "jumpl,branch")])
5797 ;; Instruction to jump to a variable address. This is a low-level capability
5798 ;; which can be used to implement a dispatch table when there is no `casesi'
5799 ;; pattern. Either the 'casesi' pattern or the 'tablejump' pattern, or both,
5800 ;; MUST be present in this file.
5802 ;; This pattern requires two operands: the address or offset, and a label which
5803 ;; should immediately precede the jump table. If the macro
5804 ;; `CASE_VECTOR_PC_RELATIVE' is defined then the first operand is an offset
5805 ;; which counts from the address of the table; otherwise, it is an absolute
5806 ;; address to jump to. In either case, the first operand has mode `Pmode'.
5808 ;; The `tablejump' insn is always the last insn before the jump table it uses.
5809 ;; Its assembler code normally has no need to use the second operand, but you
5810 ;; should incorporate it in the RTL pattern so that the jump optimizer will not
5811 ;; delete the table as unreachable code.
5813 (define_expand "tablejump"
5814 [(parallel [(set (pc) (match_operand:SI 0 "address_operand" "p"))
5815 (use (label_ref (match_operand 1 "" "")))])]
5819 (define_insn "tablejump_insn"
5820 [(set (pc) (match_operand:SI 0 "address_operand" "p"))
5821 (use (label_ref (match_operand 1 "" "")))]
5824 [(set_attr "length" "4")
5825 (set_attr "type" "jumpl")])
5827 ;; Implement switch statements when generating PIC code. Switches are
5828 ;; implemented by `tablejump' when not using -fpic.
5830 ;; Emit code here to do the range checking and make the index zero based.
5831 ;; operand 0 is the index
5832 ;; operand 1 is the lower bound
5833 ;; operand 2 is the range of indices (highest - lowest + 1)
5834 ;; operand 3 is the label that precedes the table itself
5835 ;; operand 4 is the fall through label
5837 (define_expand "casesi"
5838 [(use (match_operand:SI 0 "integer_register_operand" ""))
5839 (use (match_operand:SI 1 "const_int_operand" ""))
5840 (use (match_operand:SI 2 "const_int_operand" ""))
5841 (use (match_operand 3 "" ""))
5842 (use (match_operand 4 "" ""))]
5848 rtx low = operands[1];
5849 rtx range = operands[2];
5850 rtx table = operands[3];
5852 rtx fail = operands[4];
5857 gcc_assert (GET_CODE (operands[1]) == CONST_INT);
5859 gcc_assert (GET_CODE (operands[2]) == CONST_INT);
5861 /* If we can't generate an immediate instruction, promote to register. */
5862 if (! IN_RANGE_P (INTVAL (range), -2048, 2047))
5863 range = force_reg (SImode, range);
5865 /* If low bound is 0, we don't have to subtract it. */
5866 if (INTVAL (operands[1]) == 0)
5870 indx = gen_reg_rtx (SImode);
5871 if (IN_RANGE_P (INTVAL (low), -2047, 2048))
5872 emit_insn (gen_addsi3 (indx, operands[0], GEN_INT (- INTVAL (low))));
5874 emit_insn (gen_subsi3 (indx, operands[0], force_reg (SImode, low)));
5877 /* Do an unsigned comparison (in the proper mode) between the index
5878 expression and the value which represents the length of the range.
5879 Since we just finished subtracting the lower bound of the range
5880 from the index expression, this comparison allows us to simultaneously
5881 check that the original index expression value is both greater than
5882 or equal to the minimum value of the range and less than or equal to
5883 the maximum value of the range. */
5885 emit_cmp_and_jump_insns (indx, range, GTU, NULL_RTX, SImode, 1, fail);
5887 /* Move the table address to a register. */
5888 treg = gen_reg_rtx (Pmode);
5889 emit_insn (gen_movsi (treg, gen_rtx_LABEL_REF (VOIDmode, table)));
5891 /* Scale index-low by wordsize. */
5892 scale = gen_reg_rtx (SImode);
5893 emit_insn (gen_ashlsi3 (scale, indx, const2_rtx));
5895 /* Load the address, add the start of the table back in,
5897 mem = gen_rtx_MEM (SImode, gen_rtx_PLUS (Pmode, scale, treg));
5898 reg2 = gen_reg_rtx (SImode);
5899 reg3 = gen_reg_rtx (SImode);
5900 emit_insn (gen_movsi (reg2, mem));
5901 emit_insn (gen_addsi3 (reg3, reg2, treg));
5902 emit_jump_insn (gen_tablejump_insn (reg3, table));
5907 ;; ::::::::::::::::::::
5909 ;; :: Prologue and Epilogue instructions
5911 ;; ::::::::::::::::::::
5913 ;; Called after register allocation to add any instructions needed for the
5914 ;; prologue. Using a prologue insn is favored compared to putting all of the
5915 ;; instructions in the FUNCTION_PROLOGUE macro, since it allows the scheduler
5916 ;; to intermix instructions with the saves of the caller saved registers. In
5917 ;; some cases, it might be necessary to emit a barrier instruction as the last
5918 ;; insn to prevent such scheduling.
5919 (define_expand "prologue"
5924 frv_expand_prologue ();
5928 ;; Called after register allocation to add any instructions needed for the
5929 ;; epilogue. Using an epilogue insn is favored compared to putting all of the
5930 ;; instructions in the FUNCTION_EPILOGUE macro, since it allows the scheduler
5931 ;; to intermix instructions with the restores of the caller saved registers.
5932 ;; In some cases, it might be necessary to emit a barrier instruction as the
5933 ;; first insn to prevent such scheduling.
5934 (define_expand "epilogue"
5939 frv_expand_epilogue (true);
5943 ;; This pattern, if defined, emits RTL for exit from a function without the final
5944 ;; branch back to the calling function. This pattern will be emitted before any
5945 ;; sibling call (aka tail call) sites.
5947 ;; The sibcall_epilogue pattern must not clobber any arguments used for
5948 ;; parameter passing or any stack slots for arguments passed to the current
5950 (define_expand "sibcall_epilogue"
5955 frv_expand_epilogue (false);
5959 ;; Set up the pic register to hold the address of the pic table
5960 (define_insn "pic_prologue"
5961 [(set (match_operand:SI 0 "integer_register_operand" "=d")
5962 (unspec_volatile:SI [(const_int 0)] UNSPEC_PIC_PROLOGUE))
5963 (clobber (match_operand:SI 1 "lr_operand" "=l"))
5964 (clobber (match_operand:SI 2 "integer_register_operand" "=d"))]
5968 static int frv_pic_labelno = 0;
5970 operands[3] = GEN_INT (frv_pic_labelno++);
5971 return \"call %P3\\n%P3:\;movsg %1, %0\;sethi #gprelhi(%P3), %2\;setlo #gprello(%P3), %2\;sub %0,%2,%0\";
5973 [(set_attr "length" "16")
5974 (set_attr "type" "multi")])
5976 ;; ::::::::::::::::::::
5978 ;; :: Miscellaneous instructions
5980 ;; ::::::::::::::::::::
5982 ;; No operation, needed in case the user uses -g but not -O.
5987 [(set_attr "length" "4")
5988 (set_attr "type" "int")])
5994 [(set_attr "length" "4")
5995 (set_attr "type" "fnop")])
6001 [(set_attr "length" "4")
6002 (set_attr "type" "mnop")])
6004 ;; Pseudo instruction that prevents the scheduler from moving code above this
6005 ;; point. Note, type unknown is used to make sure the VLIW instructions are
6006 ;; not continued past this point.
6007 (define_insn "blockage"
6008 [(unspec_volatile [(const_int 0)] UNSPEC_BLOCKAGE)]
6011 [(set_attr "length" "0")
6012 (set_attr "type" "unknown")])
6014 ;; ::::::::::::::::::::
6016 ;; :: Media instructions
6018 ;; ::::::::::::::::::::
6020 ;; Unimplemented instructions:
6024 [(UNSPEC_MLOGIC 100)
6031 (UNSPEC_MUNPACKH 107)
6032 (UNSPEC_MDPACKH 108)
6037 (UNSPEC_MEXPDHW 113)
6038 (UNSPEC_MEXPDHD 114)
6045 (UNSPEC_MQMULXH 121)
6051 (UNSPEC_MRDACCG 127)
6053 (UNSPEC_MWTACCG 129)
6055 (UNSPEC_MCLRACC 131)
6056 (UNSPEC_MCLRACCA 132)
6059 (UNSPEC_MDUNPACKH 135)
6060 (UNSPEC_MDUNPACKH_INTERNAL 136)
6062 (UNSPEC_MBTOHE_INTERNAL 138)
6064 (UNSPEC_MBTOHE_INTERNAL 138)
6065 (UNSPEC_MQMACH2 139)
6066 (UNSPEC_MADDACC 140)
6067 (UNSPEC_MDADDACC 141)
6069 (UNSPEC_MDROTLI 143)
6072 (UNSPEC_MDCUTSSI 146)
6073 (UNSPEC_MQSATHS 147)
6074 (UNSPEC_MHSETLOS 148)
6075 (UNSPEC_MHSETLOH 149)
6076 (UNSPEC_MHSETHIS 150)
6077 (UNSPEC_MHSETHIH 151)
6078 (UNSPEC_MHDSETS 152)
6079 (UNSPEC_MHDSETH 153)
6080 (UNSPEC_MQLCLRHS 154)
6081 (UNSPEC_MQLMTHS 155)
6082 (UNSPEC_MQSLLHI 156)
6083 (UNSPEC_MQSRAHI 157)
6084 (UNSPEC_MASACCS 158)
6085 (UNSPEC_MDASACCS 159)
6088 ;; Logic operations: type "mlogic"
6090 (define_expand "mand"
6091 [(set (match_operand:SI 0 "fpr_operand" "")
6092 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6093 (match_operand:SI 2 "fpr_operand" "")
6097 "operands[3] = GEN_INT (FRV_BUILTIN_MAND);")
6099 (define_expand "mor"
6100 [(set (match_operand:SI 0 "fpr_operand" "")
6101 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6102 (match_operand:SI 2 "fpr_operand" "")
6106 "operands[3] = GEN_INT (FRV_BUILTIN_MOR);")
6108 (define_expand "mxor"
6109 [(set (match_operand:SI 0 "fpr_operand" "")
6110 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6111 (match_operand:SI 2 "fpr_operand" "")
6115 "operands[3] = GEN_INT (FRV_BUILTIN_MXOR);")
6117 (define_insn "*mlogic"
6118 [(set (match_operand:SI 0 "fpr_operand" "=f")
6119 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6120 (match_operand:SI 2 "fpr_operand" "f")
6121 (match_operand:SI 3 "const_int_operand" "n")]
6126 switch (INTVAL (operands[3]))
6129 case FRV_BUILTIN_MAND: return \"mand %1, %2, %0\";
6130 case FRV_BUILTIN_MOR: return \"mor %1, %2, %0\";
6131 case FRV_BUILTIN_MXOR: return \"mxor %1, %2, %0\";
6134 fatal_insn (\"Bad media insn, mlogic\", insn);
6136 [(set_attr "length" "4")
6137 (set_attr "type" "mlogic")])
6139 (define_insn "*cond_exec_mlogic"
6141 (match_operator 0 "ccr_eqne_operator"
6142 [(match_operand 1 "cr_operand" "C")
6144 (set (match_operand:SI 2 "fpr_operand" "=f")
6145 (unspec:SI [(match_operand:SI 3 "fpr_operand" "f")
6146 (match_operand:SI 4 "fpr_operand" "f")
6147 (match_operand:SI 5 "const_int_operand" "n")]
6152 switch (INTVAL (operands[5]))
6155 case FRV_BUILTIN_MAND: return \"cmand %3, %4, %2, %1, %e0\";
6156 case FRV_BUILTIN_MOR: return \"cmor %3, %4, %2, %1, %e0\";
6157 case FRV_BUILTIN_MXOR: return \"cmxor %3, %4, %2, %1, %e0\";
6160 fatal_insn (\"Bad media insn, cond_exec_mlogic\", insn);
6162 [(set_attr "length" "4")
6163 (set_attr "type" "mlogic")])
6165 ;; Logical not: type "mlogic"
6168 [(set (match_operand:SI 0 "fpr_operand" "=f")
6169 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")] UNSPEC_MNOT))]
6172 [(set_attr "length" "4")
6173 (set_attr "type" "mlogic")])
6175 (define_insn "*cond_exec_mnot"
6177 (match_operator 0 "ccr_eqne_operator"
6178 [(match_operand 1 "cr_operand" "C")
6180 (set (match_operand:SI 2 "fpr_operand" "=f")
6181 (unspec:SI [(match_operand:SI 3 "fpr_operand" "f")] UNSPEC_MNOT)))]
6183 "cmnot %3, %2, %1, %e0"
6184 [(set_attr "length" "4")
6185 (set_attr "type" "mlogic")])
6187 ;; Dual average (halfword): type "maveh"
6189 (define_insn "maveh"
6190 [(set (match_operand:SI 0 "fpr_operand" "=f")
6191 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6192 (match_operand:SI 2 "fpr_operand" "f")]
6196 [(set_attr "length" "4")
6197 (set_attr "type" "maveh")])
6199 ;; Dual saturation (halfword): type "msath"
6201 (define_expand "msaths"
6202 [(set (match_operand:SI 0 "fpr_operand" "=f")
6203 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6204 (match_operand:SI 2 "fpr_operand" "f")
6208 "operands[3] = GEN_INT (FRV_BUILTIN_MSATHS);")
6210 (define_expand "msathu"
6211 [(set (match_operand:SI 0 "fpr_operand" "=f")
6212 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6213 (match_operand:SI 2 "fpr_operand" "f")
6217 "operands[3] = GEN_INT (FRV_BUILTIN_MSATHU);")
6219 (define_insn "*msath"
6220 [(set (match_operand:SI 0 "fpr_operand" "=f")
6221 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6222 (match_operand:SI 2 "fpr_operand" "f")
6223 (match_operand:SI 3 "const_int_operand" "n")]
6228 switch (INTVAL (operands[3]))
6231 case FRV_BUILTIN_MSATHS: return \"msaths %1, %2, %0\";
6232 case FRV_BUILTIN_MSATHU: return \"msathu %1, %2, %0\";
6235 fatal_insn (\"Bad media insn, msath\", insn);
6237 [(set_attr "length" "4")
6238 (set_attr "type" "msath")])
6240 ;; Dual addition/subtraction with saturation (halfword): type "maddh"
6242 (define_expand "maddhss"
6243 [(set (match_operand:SI 0 "fpr_operand" "=f")
6244 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6245 (match_operand:SI 2 "fpr_operand" "f")
6249 "operands[3] = GEN_INT (FRV_BUILTIN_MADDHSS);")
6251 (define_expand "maddhus"
6252 [(set (match_operand:SI 0 "fpr_operand" "=f")
6253 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6254 (match_operand:SI 2 "fpr_operand" "f")
6258 "operands[3] = GEN_INT (FRV_BUILTIN_MADDHUS);")
6260 (define_expand "msubhss"
6261 [(set (match_operand:SI 0 "fpr_operand" "=f")
6262 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6263 (match_operand:SI 2 "fpr_operand" "f")
6267 "operands[3] = GEN_INT (FRV_BUILTIN_MSUBHSS);")
6269 (define_expand "msubhus"
6270 [(set (match_operand:SI 0 "fpr_operand" "=f")
6271 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6272 (match_operand:SI 2 "fpr_operand" "f")
6276 "operands[3] = GEN_INT (FRV_BUILTIN_MSUBHUS);")
6278 (define_insn "*maddh"
6279 [(set (match_operand:SI 0 "fpr_operand" "=f")
6280 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6281 (match_operand:SI 2 "fpr_operand" "f")
6282 (match_operand:SI 3 "const_int_operand" "n")]
6287 switch (INTVAL (operands[3]))
6290 case FRV_BUILTIN_MADDHSS: return \"maddhss %1, %2, %0\";
6291 case FRV_BUILTIN_MADDHUS: return \"maddhus %1, %2, %0\";
6292 case FRV_BUILTIN_MSUBHSS: return \"msubhss %1, %2, %0\";
6293 case FRV_BUILTIN_MSUBHUS: return \"msubhus %1, %2, %0\";
6296 fatal_insn (\"Bad media insn, maddh\", insn);
6298 [(set_attr "length" "4")
6299 (set_attr "type" "maddh")])
6301 (define_insn "*cond_exec_maddh"
6303 (match_operator 0 "ccr_eqne_operator"
6304 [(match_operand 1 "cr_operand" "C")
6306 (set (match_operand:SI 2 "fpr_operand" "=f")
6307 (unspec:SI [(match_operand:SI 3 "fpr_operand" "f")
6308 (match_operand:SI 4 "fpr_operand" "f")
6309 (match_operand:SI 5 "const_int_operand" "n")]
6314 switch (INTVAL (operands[5]))
6317 case FRV_BUILTIN_MADDHSS: return \"cmaddhss %3, %4, %2, %1, %e0\";
6318 case FRV_BUILTIN_MADDHUS: return \"cmaddhus %3, %4, %2, %1, %e0\";
6319 case FRV_BUILTIN_MSUBHSS: return \"cmsubhss %3, %4, %2, %1, %e0\";
6320 case FRV_BUILTIN_MSUBHUS: return \"cmsubhus %3, %4, %2, %1, %e0\";
6323 fatal_insn (\"Bad media insn, cond_exec_maddh\", insn);
6325 [(set_attr "length" "4")
6326 (set_attr "type" "maddh")])
6328 ;; Quad addition/subtraction with saturation (halfword): type "mqaddh"
6330 (define_expand "mqaddhss"
6331 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6332 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
6333 (match_operand:DI 2 "even_fpr_operand" "h")
6337 "operands[3] = GEN_INT (FRV_BUILTIN_MQADDHSS);")
6339 (define_expand "mqaddhus"
6340 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6341 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
6342 (match_operand:DI 2 "even_fpr_operand" "h")
6346 "operands[3] = GEN_INT (FRV_BUILTIN_MQADDHUS);")
6348 (define_expand "mqsubhss"
6349 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6350 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
6351 (match_operand:DI 2 "even_fpr_operand" "h")
6355 "operands[3] = GEN_INT (FRV_BUILTIN_MQSUBHSS);")
6357 (define_expand "mqsubhus"
6358 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6359 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
6360 (match_operand:DI 2 "even_fpr_operand" "h")
6364 "operands[3] = GEN_INT (FRV_BUILTIN_MQSUBHUS);")
6366 (define_insn "*mqaddh"
6367 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6368 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
6369 (match_operand:DI 2 "even_fpr_operand" "h")
6370 (match_operand:SI 3 "const_int_operand" "n")]
6375 switch (INTVAL (operands[3]))
6378 case FRV_BUILTIN_MQADDHSS: return \"mqaddhss %1, %2, %0\";
6379 case FRV_BUILTIN_MQADDHUS: return \"mqaddhus %1, %2, %0\";
6380 case FRV_BUILTIN_MQSUBHSS: return \"mqsubhss %1, %2, %0\";
6381 case FRV_BUILTIN_MQSUBHUS: return \"mqsubhus %1, %2, %0\";
6384 fatal_insn (\"Bad media insn, mqaddh\", insn);
6386 [(set_attr "length" "4")
6387 (set_attr "type" "mqaddh")])
6389 (define_insn "*cond_exec_mqaddh"
6391 (match_operator 0 "ccr_eqne_operator"
6392 [(match_operand 1 "cr_operand" "C")
6394 (set (match_operand:DI 2 "even_fpr_operand" "=h")
6395 (unspec:DI [(match_operand:DI 3 "even_fpr_operand" "h")
6396 (match_operand:DI 4 "even_fpr_operand" "h")
6397 (match_operand:SI 5 "const_int_operand" "n")]
6402 switch (INTVAL (operands[5]))
6405 case FRV_BUILTIN_MQADDHSS: return \"cmqaddhss %3, %4, %2, %1, %e0\";
6406 case FRV_BUILTIN_MQADDHUS: return \"cmqaddhus %3, %4, %2, %1, %e0\";
6407 case FRV_BUILTIN_MQSUBHSS: return \"cmqsubhss %3, %4, %2, %1, %e0\";
6408 case FRV_BUILTIN_MQSUBHUS: return \"cmqsubhus %3, %4, %2, %1, %e0\";
6411 fatal_insn (\"Bad media insn, cond_exec_mqaddh\", insn);
6413 [(set_attr "length" "4")
6414 (set_attr "type" "mqaddh")])
6416 ;; Pack halfword: type "mpackh"
6418 (define_insn "mpackh"
6419 [(set (match_operand:SI 0 "fpr_operand" "=f")
6420 (unspec:SI [(match_operand:HI 1 "fpr_operand" "f")
6421 (match_operand:HI 2 "fpr_operand" "f")]
6425 [(set_attr "length" "4")
6426 (set_attr "type" "mpackh")])
6428 ;; Unpack halfword: type "mpackh"
6430 (define_insn "munpackh"
6431 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6432 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")]
6436 [(set_attr "length" "4")
6437 (set_attr "type" "munpackh")])
6439 ;; Dual pack halfword: type "mdpackh"
6441 (define_insn "mdpackh"
6442 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6443 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
6444 (match_operand:DI 2 "even_fpr_operand" "h")]
6447 "mdpackh %1, %2, %0"
6448 [(set_attr "length" "4")
6449 (set_attr "type" "mdpackh")])
6451 ;; Byte-halfword conversion: type "mbhconv"
6453 (define_insn "mbtoh"
6454 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6455 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")]
6459 [(set_attr "length" "4")
6460 (set_attr "type" "mbhconv")])
6462 (define_insn "*cond_exec_mbtoh"
6464 (match_operator 0 "ccr_eqne_operator"
6465 [(match_operand 1 "cr_operand" "C")
6467 (set (match_operand:DI 2 "even_fpr_operand" "=h")
6468 (unspec:DI [(match_operand:SI 3 "fpr_operand" "f")]
6471 "cmbtoh %3, %2, %1, %e0"
6472 [(set_attr "length" "4")
6473 (set_attr "type" "mbhconv")])
6475 (define_insn "mhtob"
6476 [(set (match_operand:SI 0 "fpr_operand" "=f")
6477 (unspec:SI [(match_operand:DI 1 "even_fpr_operand" "h")]
6481 [(set_attr "length" "4")
6482 (set_attr "type" "mbhconv")])
6484 (define_insn "*cond_exec_mhtob"
6486 (match_operator 0 "ccr_eqne_operator"
6487 [(match_operand 1 "cr_operand" "C")
6489 (set (match_operand:SI 2 "fpr_operand" "=f")
6490 (unspec:SI [(match_operand:DI 3 "even_fpr_operand" "h")]
6493 "cmhtob %3, %2, %1, %e0"
6494 [(set_attr "length" "4")
6495 (set_attr "type" "mbhconv")])
6497 ;; Rotate: type "mrot"
6499 (define_expand "mrotli"
6500 [(set (match_operand:SI 0 "fpr_operand" "")
6501 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6502 (match_operand:SI 2 "uint5_operand" "")
6506 "operands[3] = GEN_INT (FRV_BUILTIN_MROTLI);")
6508 (define_expand "mrotri"
6509 [(set (match_operand:SI 0 "fpr_operand" "")
6510 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6511 (match_operand:SI 2 "uint5_operand" "")
6515 "operands[3] = GEN_INT (FRV_BUILTIN_MROTRI);")
6517 (define_insn "*mrot"
6518 [(set (match_operand:SI 0 "fpr_operand" "=f")
6519 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6520 (match_operand:SI 2 "uint5_operand" "I")
6521 (match_operand:SI 3 "const_int_operand" "n")]
6526 switch (INTVAL (operands[3]))
6529 case FRV_BUILTIN_MROTLI: return \"mrotli %1, %2, %0\";
6530 case FRV_BUILTIN_MROTRI: return \"mrotri %1, %2, %0\";
6533 fatal_insn (\"Bad media insn, mrot\", insn);
6535 [(set_attr "length" "4")
6536 (set_attr "type" "mrot")])
6538 ;; Dual shift halfword: type "msh"
6540 (define_expand "msllhi"
6541 [(set (match_operand:SI 0 "fpr_operand" "")
6542 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6543 (match_operand:SI 2 "uint4_operand" "")
6547 "operands[3] = GEN_INT (FRV_BUILTIN_MSLLHI);")
6549 (define_expand "msrlhi"
6550 [(set (match_operand:SI 0 "fpr_operand" "")
6551 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6552 (match_operand:SI 2 "uint4_operand" "")
6556 "operands[3] = GEN_INT (FRV_BUILTIN_MSRLHI);")
6558 (define_expand "msrahi"
6559 [(set (match_operand:SI 0 "fpr_operand" "")
6560 (unspec:SI [(match_operand:SI 1 "fpr_operand" "")
6561 (match_operand:SI 2 "uint4_operand" "")
6565 "operands[3] = GEN_INT (FRV_BUILTIN_MSRAHI);")
6567 (define_insn "*mshift"
6568 [(set (match_operand:SI 0 "fpr_operand" "=f")
6569 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6570 (match_operand:SI 2 "uint4_operand" "I")
6571 (match_operand:SI 3 "const_int_operand" "n")]
6576 switch (INTVAL (operands[3]))
6579 case FRV_BUILTIN_MSLLHI: return \"msllhi %1, %2, %0\";
6580 case FRV_BUILTIN_MSRLHI: return \"msrlhi %1, %2, %0\";
6581 case FRV_BUILTIN_MSRAHI: return \"msrahi %1, %2, %0\";
6584 fatal_insn (\"Bad media insn, mshift\", insn);
6586 [(set_attr "length" "4")
6587 (set_attr "type" "mshift")])
6589 ;; Expand halfword to word: type "mexpdhw"
6591 (define_insn "mexpdhw"
6592 [(set (match_operand:SI 0 "fpr_operand" "=f")
6593 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
6594 (match_operand:SI 2 "uint1_operand" "I")]
6597 "mexpdhw %1, %2, %0"
6598 [(set_attr "length" "4")
6599 (set_attr "type" "mexpdhw")])
6601 (define_insn "*cond_exec_mexpdhw"
6603 (match_operator 0 "ccr_eqne_operator"
6604 [(match_operand 1 "cr_operand" "C")
6606 (set (match_operand:SI 2 "fpr_operand" "=f")
6607 (unspec:SI [(match_operand:SI 3 "fpr_operand" "f")
6608 (match_operand:SI 4 "uint1_operand" "I")]
6611 "cmexpdhw %3, %4, %2, %1, %e0"
6612 [(set_attr "length" "4")
6613 (set_attr "type" "mexpdhw")])
6615 ;; Expand halfword to double: type "mexpdhd"
6617 (define_insn "mexpdhd"
6618 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
6619 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")
6620 (match_operand:SI 2 "uint1_operand" "I")]
6623 "mexpdhd %1, %2, %0"
6624 [(set_attr "length" "4")
6625 (set_attr "type" "mexpdhd")])
6627 (define_insn "*cond_exec_mexpdhd"
6629 (match_operator 0 "ccr_eqne_operator"
6630 [(match_operand 1 "cr_operand" "C")
6632 (set (match_operand:DI 2 "even_fpr_operand" "=h")
6633 (unspec:DI [(match_operand:SI 3 "fpr_operand" "f")
6634 (match_operand:SI 4 "uint1_operand" "I")]
6637 "cmexpdhd %3, %4, %2, %1, %e0"
6638 [(set_attr "length" "4")
6639 (set_attr "type" "mexpdhd")])
6641 ;; FR cut: type "mwcut"
6643 (define_insn "mwcut"
6644 [(set (match_operand:SI 0 "fpr_operand" "=f")
6645 (unspec:SI [(match_operand:DI 1 "fpr_operand" "f")
6646 (match_operand:SI 2 "fpr_or_int6_operand" "fI")]
6649 "mwcut%i2 %1, %2, %0"
6650 [(set_attr "length" "4")
6651 (set_attr "type" "mwcut")])
6653 ;; Dual multiplication (halfword): type "mmulh"
6655 (define_expand "mmulhs"
6656 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
6657 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")
6658 (match_operand:SI 2 "fpr_operand" "f")
6661 (set (match_operand:HI 3 "accg_operand" "=B")
6662 (unspec:HI [(const_int 0)] UNSPEC_MMULH))])]
6664 "operands[4] = GEN_INT (FRV_BUILTIN_MMULHS);")
6666 (define_expand "mmulhu"
6667 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
6668 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")
6669 (match_operand:SI 2 "fpr_operand" "f")
6672 (set (match_operand:HI 3 "accg_operand" "=B")
6673 (unspec:HI [(const_int 0)] UNSPEC_MMULH))])]
6675 "operands[4] = GEN_INT (FRV_BUILTIN_MMULHU);")
6677 (define_insn "*mmulh"
6678 [(set (match_operand:DI 0 "even_acc_operand" "=b")
6679 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")
6680 (match_operand:SI 2 "fpr_operand" "f")
6681 (match_operand:SI 3 "const_int_operand" "n")]
6683 (set (match_operand:HI 4 "accg_operand" "=B")
6684 (unspec:HI [(const_int 0)] UNSPEC_MMULH))]
6688 switch (INTVAL (operands[3]))
6691 case FRV_BUILTIN_MMULHS: return \"mmulhs %1, %2, %0\";
6692 case FRV_BUILTIN_MMULHU: return \"mmulhu %1, %2, %0\";
6695 fatal_insn (\"Bad media insn, mmulh\", insn);
6697 [(set_attr "length" "4")
6698 (set_attr "type" "mmulh")])
6700 (define_insn "*cond_exec_mmulh"
6702 (match_operator 0 "ccr_eqne_operator"
6703 [(match_operand 1 "cr_operand" "C")
6705 (parallel [(set (match_operand:DI 2 "even_acc_operand" "=b")
6706 (unspec:DI [(match_operand:SI 3 "fpr_operand" "f")
6707 (match_operand:SI 4 "fpr_operand" "f")
6708 (match_operand:SI 5 "const_int_operand" "n")]
6710 (set (match_operand:HI 6 "accg_operand" "=B")
6711 (unspec:HI [(const_int 0)] UNSPEC_MMULH))]))]
6715 switch (INTVAL (operands[5]))
6718 case FRV_BUILTIN_MMULHS: return \"cmmulhs %3, %4, %2, %1, %e0\";
6719 case FRV_BUILTIN_MMULHU: return \"cmmulhu %3, %4, %2, %1, %e0\";
6722 fatal_insn (\"Bad media insn, cond_exec_mmulh\", insn);
6724 [(set_attr "length" "4")
6725 (set_attr "type" "mmulh")])
6727 ;; Dual cross multiplication (halfword): type "mmulxh"
6729 (define_expand "mmulxhs"
6730 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
6731 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")
6732 (match_operand:SI 2 "fpr_operand" "f")
6735 (set (match_operand:HI 3 "accg_operand" "=B")
6736 (unspec:HI [(const_int 0)] UNSPEC_MMULXH))])]
6738 "operands[4] = GEN_INT (FRV_BUILTIN_MMULXHS);")
6740 (define_expand "mmulxhu"
6741 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
6742 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")
6743 (match_operand:SI 2 "fpr_operand" "f")
6746 (set (match_operand:HI 3 "accg_operand" "=B")
6747 (unspec:HI [(const_int 0)] UNSPEC_MMULXH))])]
6749 "operands[4] = GEN_INT (FRV_BUILTIN_MMULXHU);")
6751 (define_insn "*mmulxh"
6752 [(set (match_operand:DI 0 "even_acc_operand" "=b")
6753 (unspec:DI [(match_operand:SI 1 "fpr_operand" "f")
6754 (match_operand:SI 2 "fpr_operand" "f")
6755 (match_operand:SI 3 "const_int_operand" "n")]
6757 (set (match_operand:HI 4 "accg_operand" "=B")
6758 (unspec:HI [(const_int 0)] UNSPEC_MMULXH))]
6762 switch (INTVAL (operands[3]))
6765 case FRV_BUILTIN_MMULXHS: return \"mmulxhs %1, %2, %0\";
6766 case FRV_BUILTIN_MMULXHU: return \"mmulxhu %1, %2, %0\";
6769 fatal_insn (\"Bad media insn, mmulxh\", insn);
6771 [(set_attr "length" "4")
6772 (set_attr "type" "mmulxh")])
6774 ;; Dual product-sum (halfword): type "mmach"
6776 (define_expand "mmachs"
6777 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "+b")
6778 (unspec:DI [(match_dup 0)
6779 (match_operand:SI 1 "fpr_operand" "f")
6780 (match_operand:SI 2 "fpr_operand" "f")
6781 (match_operand:HI 3 "accg_operand" "+B")
6785 (unspec:HI [(const_int 0)] UNSPEC_MMACH))])]
6787 "operands[4] = GEN_INT (FRV_BUILTIN_MMACHS);")
6789 (define_expand "mmachu"
6790 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "+b")
6791 (unspec:DI [(match_dup 0)
6792 (match_operand:SI 1 "fpr_operand" "f")
6793 (match_operand:SI 2 "fpr_operand" "f")
6794 (match_operand:HI 3 "accg_operand" "+B")
6798 (unspec:HI [(const_int 0)] UNSPEC_MMACH))])]
6800 "operands[4] = GEN_INT (FRV_BUILTIN_MMACHU);")
6802 (define_insn "*mmach"
6803 [(set (match_operand:DI 0 "even_acc_operand" "+b")
6804 (unspec:DI [(match_dup 0)
6805 (match_operand:SI 1 "fpr_operand" "f")
6806 (match_operand:SI 2 "fpr_operand" "f")
6807 (match_operand:HI 3 "accg_operand" "+B")
6808 (match_operand:SI 4 "const_int_operand" "n")]
6810 (set (match_dup 3) (unspec:HI [(const_int 0)] UNSPEC_MMACH))]
6814 switch (INTVAL (operands[4]))
6817 case FRV_BUILTIN_MMACHS: return \"mmachs %1, %2, %0\";
6818 case FRV_BUILTIN_MMACHU: return \"mmachu %1, %2, %0\";
6821 fatal_insn (\"Bad media insn, mmach\", insn);
6823 [(set_attr "length" "4")
6824 (set_attr "type" "mmach")])
6826 (define_insn "*cond_exec_mmach"
6828 (match_operator 0 "ccr_eqne_operator"
6829 [(match_operand 1 "cr_operand" "C")
6831 (parallel [(set (match_operand:DI 2 "even_acc_operand" "+b")
6832 (unspec:DI [(match_dup 2)
6833 (match_operand:SI 3 "fpr_operand" "f")
6834 (match_operand:SI 4 "fpr_operand" "f")
6835 (match_operand:HI 5 "accg_operand" "+B")
6836 (match_operand:SI 6 "const_int_operand" "n")]
6839 (unspec:HI [(const_int 0)] UNSPEC_MMACH))]))]
6843 switch (INTVAL (operands[6]))
6846 case FRV_BUILTIN_MMACHS: return \"cmmachs %3, %4, %2, %1, %e0\";
6847 case FRV_BUILTIN_MMACHU: return \"cmmachu %3, %4, %2, %1, %e0\";
6850 fatal_insn (\"Bad media insn, cond_exec_mmach\", insn);
6852 [(set_attr "length" "4")
6853 (set_attr "type" "mmach")])
6855 ;; Dual product-difference: type "mmrdh"
6857 (define_expand "mmrdhs"
6858 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "+b")
6859 (unspec:DI [(match_dup 0)
6860 (match_operand:SI 1 "fpr_operand" "f")
6861 (match_operand:SI 2 "fpr_operand" "f")
6862 (match_operand:HI 3 "accg_operand" "+B")
6866 (unspec:HI [(const_int 0)] UNSPEC_MMRDH))])]
6868 "operands[4] = GEN_INT (FRV_BUILTIN_MMRDHS);")
6870 (define_expand "mmrdhu"
6871 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "+b")
6872 (unspec:DI [(match_dup 0)
6873 (match_operand:SI 1 "fpr_operand" "f")
6874 (match_operand:SI 2 "fpr_operand" "f")
6875 (match_operand:HI 3 "accg_operand" "+B")
6879 (unspec:HI [(const_int 0)] UNSPEC_MMRDH))])]
6881 "operands[4] = GEN_INT (FRV_BUILTIN_MMRDHU);")
6883 (define_insn "*mmrdh"
6884 [(set (match_operand:DI 0 "even_acc_operand" "+b")
6885 (unspec:DI [(match_dup 0)
6886 (match_operand:SI 1 "fpr_operand" "f")
6887 (match_operand:SI 2 "fpr_operand" "f")
6888 (match_operand:HI 3 "accg_operand" "+B")
6889 (match_operand:SI 4 "const_int_operand" "n")]
6892 (unspec:HI [(const_int 0)] UNSPEC_MMRDH))]
6896 switch (INTVAL (operands[4]))
6899 case FRV_BUILTIN_MMRDHS: return \"mmrdhs %1, %2, %0\";
6900 case FRV_BUILTIN_MMRDHU: return \"mmrdhu %1, %2, %0\";
6903 fatal_insn (\"Bad media insn, mrdh\", insn);
6905 [(set_attr "length" "4")
6906 (set_attr "type" "mmrdh")])
6908 ;; Quad multiply (halfword): type "mqmulh"
6910 (define_expand "mqmulhs"
6911 [(parallel [(set (match_operand:V4SI 0 "quad_acc_operand" "=A")
6912 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")
6913 (match_operand:DI 2 "even_fpr_operand" "h")
6916 (set (match_operand:V4QI 3 "accg_operand" "=B")
6917 (unspec:V4QI [(const_int 0)] UNSPEC_MQMULH))])]
6919 "operands[4] = GEN_INT (FRV_BUILTIN_MQMULHS);")
6921 (define_expand "mqmulhu"
6922 [(parallel [(set (match_operand:V4SI 0 "quad_acc_operand" "=A")
6923 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")
6924 (match_operand:DI 2 "even_fpr_operand" "h")
6927 (set (match_operand:V4QI 3 "accg_operand" "=B")
6928 (unspec:V4QI [(const_int 0)] UNSPEC_MQMULH))])]
6930 "operands[4] = GEN_INT (FRV_BUILTIN_MQMULHU);")
6932 (define_insn "*mqmulh"
6933 [(set (match_operand:V4SI 0 "quad_acc_operand" "=A")
6934 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")
6935 (match_operand:DI 2 "even_fpr_operand" "h")
6936 (match_operand:SI 3 "const_int_operand" "n")]
6938 (set (match_operand:V4QI 4 "accg_operand" "=B")
6939 (unspec:V4QI [(const_int 0)] UNSPEC_MQMULH))]
6943 switch (INTVAL (operands[3]))
6946 case FRV_BUILTIN_MQMULHS: return \"mqmulhs %1, %2, %0\";
6947 case FRV_BUILTIN_MQMULHU: return \"mqmulhu %1, %2, %0\";
6950 fatal_insn (\"Bad media insn, mqmulh\", insn);
6952 [(set_attr "length" "4")
6953 (set_attr "type" "mqmulh")])
6955 (define_insn "*cond_exec_mqmulh"
6957 (match_operator 0 "ccr_eqne_operator"
6958 [(match_operand 1 "cr_operand" "C")
6960 (parallel [(set (match_operand:V4SI 2 "quad_acc_operand" "=A")
6961 (unspec:V4SI [(match_operand:DI 3 "even_fpr_operand" "h")
6962 (match_operand:DI 4 "even_fpr_operand" "h")
6963 (match_operand:SI 5 "const_int_operand" "n")]
6965 (set (match_operand:V4QI 6 "accg_operand" "=B")
6966 (unspec:V4QI [(const_int 0)] UNSPEC_MQMULH))]))]
6970 switch (INTVAL (operands[5]))
6973 case FRV_BUILTIN_MQMULHS: return \"cmqmulhs %3, %4, %2, %1, %e0\";
6974 case FRV_BUILTIN_MQMULHU: return \"cmqmulhu %3, %4, %2, %1, %e0\";
6977 fatal_insn (\"Bad media insn, cond_exec_mqmulh\", insn);
6979 [(set_attr "length" "4")
6980 (set_attr "type" "mqmulh")])
6982 ;; Quad cross multiply (halfword): type "mqmulxh"
6984 (define_expand "mqmulxhs"
6985 [(parallel [(set (match_operand:V4SI 0 "quad_acc_operand" "=A")
6986 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")
6987 (match_operand:DI 2 "even_fpr_operand" "h")
6990 (set (match_operand:V4QI 3 "accg_operand" "=B")
6991 (unspec:V4QI [(const_int 0)] UNSPEC_MQMULXH))])]
6993 "operands[4] = GEN_INT (FRV_BUILTIN_MQMULXHS);")
6995 (define_expand "mqmulxhu"
6996 [(parallel [(set (match_operand:V4SI 0 "quad_acc_operand" "=A")
6997 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")
6998 (match_operand:DI 2 "even_fpr_operand" "h")
7001 (set (match_operand:V4QI 3 "accg_operand" "=B")
7002 (unspec:V4QI [(const_int 0)] UNSPEC_MQMULXH))])]
7004 "operands[4] = GEN_INT (FRV_BUILTIN_MQMULXHU);")
7006 (define_insn "*mqmulxh"
7007 [(set (match_operand:V4SI 0 "quad_acc_operand" "=A")
7008 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")
7009 (match_operand:DI 2 "even_fpr_operand" "h")
7010 (match_operand:SI 3 "const_int_operand" "n")]
7012 (set (match_operand:V4QI 4 "accg_operand" "=B")
7013 (unspec:V4QI [(const_int 0)] UNSPEC_MQMULXH))]
7017 switch (INTVAL (operands[3]))
7020 case FRV_BUILTIN_MQMULXHS: return \"mqmulxhs %1, %2, %0\";
7021 case FRV_BUILTIN_MQMULXHU: return \"mqmulxhu %1, %2, %0\";
7024 fatal_insn (\"Bad media insn, mqmulxh\", insn);
7026 [(set_attr "length" "4")
7027 (set_attr "type" "mqmulxh")])
7029 ;; Quad product-sum (halfword): type "mqmach"
7031 (define_expand "mqmachs"
7032 [(parallel [(set (match_operand:V4SI 0 "even_acc_operand" "+A")
7033 (unspec:V4SI [(match_dup 0)
7034 (match_operand:DI 1 "even_fpr_operand" "h")
7035 (match_operand:DI 2 "even_fpr_operand" "h")
7036 (match_operand:V4QI 3 "accg_operand" "+B")
7040 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH))])]
7042 "operands[4] = GEN_INT (FRV_BUILTIN_MQMACHS);")
7044 (define_expand "mqmachu"
7045 [(parallel [(set (match_operand:V4SI 0 "even_acc_operand" "+A")
7046 (unspec:V4SI [(match_dup 0)
7047 (match_operand:DI 1 "even_fpr_operand" "h")
7048 (match_operand:DI 2 "even_fpr_operand" "h")
7049 (match_operand:V4QI 3 "accg_operand" "+B")
7053 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH))])]
7055 "operands[4] = GEN_INT (FRV_BUILTIN_MQMACHU);")
7057 (define_insn "*mqmach"
7058 [(set (match_operand:V4SI 0 "even_acc_operand" "+A")
7059 (unspec:V4SI [(match_dup 0)
7060 (match_operand:DI 1 "even_fpr_operand" "h")
7061 (match_operand:DI 2 "even_fpr_operand" "h")
7062 (match_operand:V4QI 3 "accg_operand" "+B")
7063 (match_operand:SI 4 "const_int_operand" "n")]
7066 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH))]
7070 switch (INTVAL (operands[4]))
7073 case FRV_BUILTIN_MQMACHS: return \"mqmachs %1, %2, %0\";
7074 case FRV_BUILTIN_MQMACHU: return \"mqmachu %1, %2, %0\";
7077 fatal_insn (\"Bad media insn, mqmach\", insn);
7079 [(set_attr "length" "4")
7080 (set_attr "type" "mqmach")])
7082 (define_insn "*cond_exec_mqmach"
7084 (match_operator 0 "ccr_eqne_operator"
7085 [(match_operand 1 "cr_operand" "C")
7087 (parallel [(set (match_operand:V4SI 2 "even_acc_operand" "+A")
7088 (unspec:V4SI [(match_dup 2)
7089 (match_operand:DI 3 "even_fpr_operand" "h")
7090 (match_operand:DI 4 "even_fpr_operand" "h")
7091 (match_operand:V4QI 5 "accg_operand" "+B")
7092 (match_operand:SI 6 "const_int_operand" "n")]
7095 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH))]))]
7099 switch (INTVAL (operands[6]))
7102 case FRV_BUILTIN_MQMACHS: return \"cmqmachs %3, %4, %2, %1, %e0\";
7103 case FRV_BUILTIN_MQMACHU: return \"cmqmachu %3, %4, %2, %1, %e0\";
7106 fatal_insn (\"Bad media insn, cond_exec_mqmach\", insn);
7108 [(set_attr "length" "4")
7109 (set_attr "type" "mqmach")])
7111 ;; Dual complex number product-sum (halfword)
7113 (define_expand "mcpxrs"
7114 [(parallel [(set (match_operand:SI 0 "acc_operand" "=a")
7115 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
7116 (match_operand:SI 2 "fpr_operand" "f")
7119 (set (match_operand:QI 3 "accg_operand" "=B")
7120 (unspec:QI [(const_int 0)] UNSPEC_MCPX))])]
7122 "operands[4] = GEN_INT (FRV_BUILTIN_MCPXRS);")
7124 (define_expand "mcpxru"
7125 [(parallel [(set (match_operand:SI 0 "acc_operand" "=a")
7126 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
7127 (match_operand:SI 2 "fpr_operand" "f")
7130 (set (match_operand:QI 3 "accg_operand" "=B")
7131 (unspec:QI [(const_int 0)] UNSPEC_MCPX))])]
7133 "operands[4] = GEN_INT (FRV_BUILTIN_MCPXRU);")
7135 (define_expand "mcpxis"
7136 [(parallel [(set (match_operand:SI 0 "acc_operand" "=a")
7137 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
7138 (match_operand:SI 2 "fpr_operand" "f")
7141 (set (match_operand:QI 3 "accg_operand" "=B")
7142 (unspec:QI [(const_int 0)] UNSPEC_MCPX))])]
7144 "operands[4] = GEN_INT (FRV_BUILTIN_MCPXIS);")
7146 (define_expand "mcpxiu"
7147 [(parallel [(set (match_operand:SI 0 "acc_operand" "=a")
7148 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
7149 (match_operand:SI 2 "fpr_operand" "f")
7152 (set (match_operand:QI 3 "accg_operand" "=B")
7153 (unspec:QI [(const_int 0)] UNSPEC_MCPX))])]
7155 "operands[4] = GEN_INT (FRV_BUILTIN_MCPXIU);")
7157 (define_insn "*mcpx"
7158 [(parallel [(set (match_operand:SI 0 "acc_operand" "=a")
7159 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
7160 (match_operand:SI 2 "fpr_operand" "f")
7161 (match_operand:SI 3 "const_int_operand" "n")]
7163 (set (match_operand:QI 4 "accg_operand" "=B")
7164 (unspec:QI [(const_int 0)] UNSPEC_MCPX))])]
7168 switch (INTVAL (operands[3]))
7171 case FRV_BUILTIN_MCPXRS: return \"mcpxrs %1, %2, %0\";
7172 case FRV_BUILTIN_MCPXRU: return \"mcpxru %1, %2, %0\";
7173 case FRV_BUILTIN_MCPXIS: return \"mcpxis %1, %2, %0\";
7174 case FRV_BUILTIN_MCPXIU: return \"mcpxiu %1, %2, %0\";
7177 fatal_insn (\"Bad media insn, mcpx\", insn);
7179 [(set_attr "length" "4")
7180 (set_attr "type" "mcpx")])
7182 (define_insn "*cond_exec_mcpx"
7184 (match_operator 0 "ccr_eqne_operator"
7185 [(match_operand 1 "cr_operand" "C")
7187 (parallel [(set (match_operand:SI 2 "acc_operand" "=a")
7188 (unspec:SI [(match_operand:SI 3 "fpr_operand" "f")
7189 (match_operand:SI 4 "fpr_operand" "f")
7190 (match_operand:SI 5 "const_int_operand" "n")]
7192 (set (match_operand:QI 6 "accg_operand" "=B")
7193 (unspec:QI [(const_int 0)] UNSPEC_MCPX))]))]
7197 switch (INTVAL (operands[5]))
7200 case FRV_BUILTIN_MCPXRS: return \"cmcpxrs %3, %4, %2, %1, %e0\";
7201 case FRV_BUILTIN_MCPXRU: return \"cmcpxru %3, %4, %2, %1, %e0\";
7202 case FRV_BUILTIN_MCPXIS: return \"cmcpxis %3, %4, %2, %1, %e0\";
7203 case FRV_BUILTIN_MCPXIU: return \"cmcpxiu %3, %4, %2, %1, %e0\";
7206 fatal_insn (\"Bad media insn, cond_exec_mcpx\", insn);
7208 [(set_attr "length" "4")
7209 (set_attr "type" "mcpx")])
7211 ;; Quad complex number product-sum (halfword): type "mqcpx"
7213 (define_expand "mqcpxrs"
7214 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
7215 (unspec:DI [(match_operand:DI 1 "fpr_operand" "f")
7216 (match_operand:DI 2 "fpr_operand" "f")
7219 (set (match_operand:HI 3 "accg_operand" "=B")
7220 (unspec:HI [(const_int 0)] UNSPEC_MQCPX))])]
7222 "operands[4] = GEN_INT (FRV_BUILTIN_MQCPXRS);")
7224 (define_expand "mqcpxru"
7225 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
7226 (unspec:DI [(match_operand:DI 1 "fpr_operand" "f")
7227 (match_operand:DI 2 "fpr_operand" "f")
7230 (set (match_operand:HI 3 "accg_operand" "=B")
7231 (unspec:HI [(const_int 0)] UNSPEC_MQCPX))])]
7233 "operands[4] = GEN_INT (FRV_BUILTIN_MQCPXRU);")
7235 (define_expand "mqcpxis"
7236 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
7237 (unspec:DI [(match_operand:DI 1 "fpr_operand" "f")
7238 (match_operand:DI 2 "fpr_operand" "f")
7241 (set (match_operand:HI 3 "accg_operand" "=B")
7242 (unspec:HI [(const_int 0)] UNSPEC_MQCPX))])]
7244 "operands[4] = GEN_INT (FRV_BUILTIN_MQCPXIS);")
7246 (define_expand "mqcpxiu"
7247 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "=b")
7248 (unspec:DI [(match_operand:DI 1 "fpr_operand" "f")
7249 (match_operand:DI 2 "fpr_operand" "f")
7252 (set (match_operand:HI 3 "accg_operand" "=B")
7253 (unspec:HI [(const_int 0)] UNSPEC_MQCPX))])]
7255 "operands[4] = GEN_INT (FRV_BUILTIN_MQCPXIU);")
7257 (define_insn "*mqcpx"
7258 [(set (match_operand:DI 0 "even_acc_operand" "=b")
7259 (unspec:DI [(match_operand:DI 1 "fpr_operand" "f")
7260 (match_operand:DI 2 "fpr_operand" "f")
7261 (match_operand:SI 3 "const_int_operand" "n")]
7263 (set (match_operand:HI 4 "accg_operand" "=B")
7264 (unspec:HI [(const_int 0)] UNSPEC_MQCPX))]
7268 switch (INTVAL (operands[3]))
7271 case FRV_BUILTIN_MQCPXRS: return \"mqcpxrs %1, %2, %0\";
7272 case FRV_BUILTIN_MQCPXRU: return \"mqcpxru %1, %2, %0\";
7273 case FRV_BUILTIN_MQCPXIS: return \"mqcpxis %1, %2, %0\";
7274 case FRV_BUILTIN_MQCPXIU: return \"mqcpxiu %1, %2, %0\";
7277 fatal_insn (\"Bad media insn, mqcpx\", insn);
7279 [(set_attr "length" "4")
7280 (set_attr "type" "mqcpx")])
7284 (define_expand "mcut"
7285 [(set (match_operand:SI 0 "fpr_operand" "=f")
7286 (unspec:SI [(match_operand:SI 1 "acc_operand" "a")
7287 (match_operand:SI 2 "fpr_or_int6_operand" "fI")
7288 (match_operand:QI 3 "accg_operand" "B")
7292 "operands[4] = GEN_INT (FRV_BUILTIN_MCUT);")
7294 (define_expand "mcutss"
7295 [(set (match_operand:SI 0 "fpr_operand" "=f")
7296 (unspec:SI [(match_operand:SI 1 "acc_operand" "a")
7297 (match_operand:SI 2 "fpr_or_int6_operand" "fI")
7298 (match_operand:QI 3 "accg_operand" "B")
7302 "operands[4] = GEN_INT (FRV_BUILTIN_MCUTSS);")
7304 (define_insn "*mcut"
7305 [(set (match_operand:SI 0 "fpr_operand" "=f")
7306 (unspec:SI [(match_operand:SI 1 "acc_operand" "a")
7307 (match_operand:SI 2 "fpr_or_int6_operand" "fI")
7308 (match_operand:QI 3 "accg_operand" "B")
7309 (match_operand:SI 4 "const_int_operand" "n")]
7314 switch (INTVAL (operands[4]))
7317 case FRV_BUILTIN_MCUT: return \"mcut%i2 %1, %2, %0\";
7318 case FRV_BUILTIN_MCUTSS: return \"mcutss%i2 %1, %2, %0\";
7321 fatal_insn (\"Bad media insn, mcut\", insn);
7323 [(set_attr "length" "4")
7324 (set_attr "type" "mcut")])
7326 ;; Accumulator read: type "mrdacc"
7328 (define_insn "mrdacc"
7329 [(set (match_operand:SI 0 "fpr_operand" "=f")
7330 (unspec:SI [(match_operand:SI 1 "acc_operand" "a")] UNSPEC_MRDACC))]
7333 [(set_attr "length" "4")
7334 (set_attr "type" "mrdacc")])
7336 (define_insn "mrdaccg"
7337 [(set (match_operand:SI 0 "fpr_operand" "=f")
7338 (unspec:SI [(match_operand:QI 1 "accg_operand" "B")] UNSPEC_MRDACCG))]
7341 [(set_attr "length" "4")
7342 (set_attr "type" "mrdacc")])
7344 ;; Accumulator write: type "mwtacc"
7346 (define_insn "mwtacc"
7347 [(set (match_operand:SI 0 "acc_operand" "=a")
7348 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")] UNSPEC_MWTACC))]
7351 [(set_attr "length" "4")
7352 (set_attr "type" "mwtacc")])
7354 (define_insn "mwtaccg"
7355 [(set (match_operand:QI 0 "accg_operand" "=B")
7356 (unspec:QI [(match_operand:SI 1 "fpr_operand" "f")] UNSPEC_MWTACCG))]
7359 [(set_attr "length" "4")
7360 (set_attr "type" "mwtacc")])
7362 ;; Trap: This one executes on the control unit, not the media units.
7364 (define_insn "mtrap"
7365 [(unspec_volatile [(const_int 0)] UNSPEC_MTRAP)]
7368 [(set_attr "length" "4")
7369 (set_attr "type" "trap")])
7371 ;; Clear single accumulator: type "mclracc"
7373 (define_insn "mclracc_internal"
7374 [(set (match_operand:SI 0 "acc_operand" "=a")
7375 (unspec:SI [(const_int 0)] UNSPEC_MCLRACC))
7376 (set (match_operand:QI 1 "accg_operand" "=B")
7377 (unspec:QI [(const_int 0)] UNSPEC_MCLRACC))]
7380 [(set_attr "length" "4")
7381 (set_attr "type" "mclracc")])
7383 (define_expand "mclracc"
7384 [(parallel [(set (match_operand:SI 0 "acc_operand" "=a")
7385 (unspec:SI [(const_int 0)] UNSPEC_MCLRACC))
7387 (unspec:QI [(const_int 0)] UNSPEC_MCLRACC))])]
7391 if (GET_CODE (operands[0]) != REG || !ACC_P (REGNO (operands[0])))
7394 operands[1] = frv_matching_accg_for_acc (operands[0]);
7397 ;; Clear all accumulators: type "mclracca"
7399 (define_insn "mclracca8_internal"
7400 [(set (match_operand:V4SI 0 "quad_acc_operand" "=b")
7401 (unspec:V4SI [(const_int 0)] UNSPEC_MCLRACCA))
7402 (set (match_operand:V4SI 1 "quad_acc_operand" "=b")
7403 (unspec:V4SI [(const_int 0)] UNSPEC_MCLRACCA))
7404 (set (match_operand:V4QI 2 "accg_operand" "=B")
7405 (unspec:V4QI [(const_int 0)] UNSPEC_MCLRACCA))
7406 (set (match_operand:V4QI 3 "accg_operand" "=B")
7407 (unspec:V4QI [(const_int 0)] UNSPEC_MCLRACCA))]
7408 "TARGET_MEDIA && TARGET_ACC_8"
7410 [(set_attr "length" "4")
7411 (set_attr "type" "mclracca")])
7413 (define_insn "mclracca4_internal"
7414 [(set (match_operand:V4SI 0 "quad_acc_operand" "=b")
7415 (unspec:V4SI [(const_int 0)] UNSPEC_MCLRACCA))
7416 (set (match_operand:V4QI 1 "accg_operand" "=B")
7417 (unspec:V4QI [(const_int 0)] UNSPEC_MCLRACCA))]
7418 "TARGET_MEDIA && TARGET_ACC_4"
7420 [(set_attr "length" "4")
7421 (set_attr "type" "mclracca")])
7423 (define_expand "mclracca8"
7424 [(parallel [(set (match_dup 0) (unspec:V4SI [(const_int 0)] UNSPEC_MCLRACCA))
7425 (set (match_dup 1) (unspec:V4SI [(const_int 0)] UNSPEC_MCLRACCA))
7426 (set (match_dup 2) (unspec:V4QI [(const_int 0)] UNSPEC_MCLRACCA))
7427 (set (match_dup 3) (unspec:V4QI [(const_int 0)] UNSPEC_MCLRACCA))])]
7428 "TARGET_MEDIA && TARGET_ACC_8"
7431 operands[0] = gen_rtx_REG (V4SImode, ACC_FIRST);
7432 operands[1] = gen_rtx_REG (V4SImode, ACC_FIRST + (~3 & ACC_MASK));
7433 operands[2] = gen_rtx_REG (V4QImode, ACCG_FIRST);
7434 operands[3] = gen_rtx_REG (V4QImode, ACCG_FIRST + (~3 & ACC_MASK));
7437 (define_expand "mclracca4"
7438 [(parallel [(set (match_dup 0) (unspec:V4SI [(const_int 0)] UNSPEC_MCLRACCA))
7439 (set (match_dup 1) (unspec:V4QI [(const_int 0)] UNSPEC_MCLRACCA))])]
7440 "TARGET_MEDIA && TARGET_ACC_4"
7443 operands[0] = gen_rtx_REG (V4SImode, ACC_FIRST);
7444 operands[1] = gen_rtx_REG (V4QImode, ACCG_FIRST);
7447 (define_insn "mcop1"
7448 [(set (match_operand:SI 0 "fpr_operand" "=f")
7449 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
7450 (match_operand:SI 2 "fpr_operand" "f")] UNSPEC_MCOP1))]
7453 [(set_attr "length" "4")
7454 ;; What is the class of the insn ???
7455 (set_attr "type" "multi")])
7457 (define_insn "mcop2"
7458 [(set (match_operand:SI 0 "fpr_operand" "=f")
7459 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")
7460 (match_operand:SI 2 "fpr_operand" "f")] UNSPEC_MCOP2))]
7463 [(set_attr "length" "4")
7464 ;; What is the class of the insn ???
7465 (set_attr "type" "multi")])
7467 (define_insn "*mdunpackh_internal"
7468 [(set (match_operand:V4SI 0 "quad_fpr_operand" "=x")
7469 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")]
7470 UNSPEC_MDUNPACKH_INTERNAL))]
7473 [(set_attr "length" "4")
7474 (set_attr "type" "mdunpackh")])
7476 (define_insn_and_split "mdunpackh"
7477 [(set (match_operand:V4SI 0 "memory_operand" "=o")
7478 (unspec:V4SI [(match_operand:DI 1 "even_fpr_operand" "h")]
7480 (clobber (match_scratch:V4SI 2 "=x"))]
7485 (unspec:V4SI [(match_dup 1)] UNSPEC_MDUNPACKH_INTERNAL))
7492 operands[3] = change_address (operands[0], DImode, NULL_RTX);
7493 operands[4] = gen_rtx_REG (DImode, REGNO (operands[2]));
7494 operands[5] = frv_index_memory (operands[0], DImode, 1);
7495 operands[6] = gen_rtx_REG (DImode, REGNO (operands[2])+2);
7497 [(set_attr "length" "20")
7498 (set_attr "type" "multi")])
7500 (define_insn "*mbtohe_internal"
7501 [(set (match_operand:V4SI 0 "quad_fpr_operand" "=x")
7502 (unspec:V4SI [(match_operand:SI 1 "fpr_operand" "f")]
7503 UNSPEC_MBTOHE_INTERNAL))]
7506 [(set_attr "length" "4")
7507 (set_attr "type" "mbhconve")])
7509 (define_insn_and_split "mbtohe"
7510 [(set (match_operand:V4SI 0 "memory_operand" "=o")
7511 (unspec:V4SI [(match_operand:SI 1 "fpr_operand" "f")]
7513 (clobber (match_scratch:V4SI 2 "=x"))]
7518 (unspec:V4SI [(match_dup 1)] UNSPEC_MBTOHE_INTERNAL))
7525 operands[3] = change_address (operands[0], DImode, NULL_RTX);
7526 operands[4] = gen_rtx_REG (DImode, REGNO (operands[2]));
7527 operands[5] = frv_index_memory (operands[0], DImode, 1);
7528 operands[6] = gen_rtx_REG (DImode, REGNO (operands[2])+2);
7530 [(set_attr "length" "20")
7531 (set_attr "type" "multi")])
7533 ;; Quad product-sum (halfword) instructions only found on the FR400.
7536 (define_expand "mqxmachs"
7537 [(parallel [(set (match_operand:V4SI 0 "quad_acc_operand" "")
7538 (unspec:V4SI [(match_dup 0)
7539 (match_operand:DI 1 "even_fpr_operand" "")
7540 (match_operand:DI 2 "even_fpr_operand" "")
7541 (match_operand:V4QI 3 "accg_operand" "")
7545 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH2))])]
7547 "operands[4] = GEN_INT (FRV_BUILTIN_MQXMACHS);")
7549 (define_expand "mqxmacxhs"
7550 [(parallel [(set (match_operand:V4SI 0 "quad_acc_operand" "")
7551 (unspec:V4SI [(match_dup 0)
7552 (match_operand:DI 1 "even_fpr_operand" "")
7553 (match_operand:DI 2 "even_fpr_operand" "")
7554 (match_operand:V4QI 3 "accg_operand" "")
7558 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH2))])]
7560 "operands[4] = GEN_INT (FRV_BUILTIN_MQXMACXHS);")
7562 (define_expand "mqmacxhs"
7563 [(parallel [(set (match_operand:V4SI 0 "quad_acc_operand" "")
7564 (unspec:V4SI [(match_dup 0)
7565 (match_operand:DI 1 "even_fpr_operand" "")
7566 (match_operand:DI 2 "even_fpr_operand" "")
7567 (match_operand:V4QI 3 "accg_operand" "")
7571 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH2))])]
7573 "operands[4] = GEN_INT (FRV_BUILTIN_MQMACXHS);")
7575 (define_insn "*mqmach2"
7576 [(set (match_operand:V4SI 0 "quad_acc_operand" "+A")
7577 (unspec:V4SI [(match_dup 0)
7578 (match_operand:DI 1 "even_fpr_operand" "h")
7579 (match_operand:DI 2 "even_fpr_operand" "h")
7580 (match_operand:V4QI 3 "accg_operand" "+B")
7581 (match_operand:SI 4 "const_int_operand" "n")]
7584 (unspec:V4QI [(const_int 0)] UNSPEC_MQMACH2))]
7588 switch (INTVAL (operands[4]))
7591 case FRV_BUILTIN_MQXMACHS: return \"mqxmachs %1, %2, %0\";
7592 case FRV_BUILTIN_MQXMACXHS: return \"mqxmacxhs %1, %2, %0\";
7593 case FRV_BUILTIN_MQMACXHS: return \"mqmacxhs %1, %2, %0\";
7596 fatal_insn (\"Bad media insn, mqmach2\", insn);
7598 [(set_attr "length" "4")
7599 (set_attr "type" "mqmach")])
7601 ;; Accumulator addition/subtraction: type "maddacc"
7603 (define_expand "maddaccs"
7604 [(parallel [(set (match_operand:SI 0 "acc_operand" "")
7605 (unspec:SI [(match_operand:DI 1 "even_acc_operand" "")]
7607 (set (match_operand:QI 2 "accg_operand" "")
7608 (unspec:QI [(match_operand:HI 3 "accg_operand" "")
7612 "operands[4] = GEN_INT (FRV_BUILTIN_MADDACCS);")
7614 (define_expand "msubaccs"
7615 [(parallel [(set (match_operand:SI 0 "acc_operand" "")
7616 (unspec:SI [(match_operand:DI 1 "even_acc_operand" "")]
7618 (set (match_operand:QI 2 "accg_operand" "")
7619 (unspec:QI [(match_operand:HI 3 "accg_operand" "")
7623 "operands[4] = GEN_INT (FRV_BUILTIN_MSUBACCS);")
7625 (define_insn "masaccs"
7626 [(set (match_operand:DI 0 "even_acc_operand" "=b")
7627 (unspec:DI [(match_operand:DI 1 "even_acc_operand" "b")]
7629 (set (match_operand:HI 2 "accg_operand" "=B")
7630 (unspec:HI [(match_operand:HI 3 "accg_operand" "B")]
7634 [(set_attr "length" "4")
7635 (set_attr "type" "maddacc")])
7637 (define_insn "*maddacc"
7638 [(set (match_operand:SI 0 "acc_operand" "=a")
7639 (unspec:SI [(match_operand:DI 1 "even_acc_operand" "b")]
7641 (set (match_operand:QI 2 "accg_operand" "=B")
7642 (unspec:QI [(match_operand:HI 3 "accg_operand" "B")
7643 (match_operand:SI 4 "const_int_operand" "n")]
7648 switch (INTVAL (operands[4]))
7651 case FRV_BUILTIN_MADDACCS: return \"maddaccs %1, %0\";
7652 case FRV_BUILTIN_MSUBACCS: return \"msubaccs %1, %0\";
7655 fatal_insn (\"Bad media insn, maddacc\", insn);
7657 [(set_attr "length" "4")
7658 (set_attr "type" "maddacc")])
7660 ;; Dual accumulator addition/subtraction: type "mdaddacc"
7662 (define_expand "mdaddaccs"
7663 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "")
7664 (unspec:DI [(match_operand:V4SI 1 "quad_acc_operand" "")]
7666 (set (match_operand:HI 2 "accg_operand" "")
7667 (unspec:HI [(match_operand:V4QI 3 "accg_operand" "")
7669 UNSPEC_MDADDACC))])]
7671 "operands[4] = GEN_INT (FRV_BUILTIN_MDADDACCS);")
7673 (define_expand "mdsubaccs"
7674 [(parallel [(set (match_operand:DI 0 "even_acc_operand" "")
7675 (unspec:DI [(match_operand:V4SI 1 "quad_acc_operand" "")]
7677 (set (match_operand:HI 2 "accg_operand" "")
7678 (unspec:HI [(match_operand:V4QI 3 "accg_operand" "")
7680 UNSPEC_MDADDACC))])]
7682 "operands[4] = GEN_INT (FRV_BUILTIN_MDSUBACCS);")
7684 (define_insn "mdasaccs"
7685 [(set (match_operand:V4SI 0 "quad_acc_operand" "=A")
7686 (unspec:V4SI [(match_operand:V4SI 1 "quad_acc_operand" "A")]
7688 (set (match_operand:V4QI 2 "accg_operand" "=B")
7689 (unspec:V4QI [(match_operand:V4QI 3 "accg_operand" "B")]
7693 [(set_attr "length" "4")
7694 (set_attr "type" "mdaddacc")])
7696 (define_insn "*mdaddacc"
7697 [(set (match_operand:DI 0 "even_acc_operand" "=b")
7698 (unspec:DI [(match_operand:V4SI 1 "quad_acc_operand" "A")]
7700 (set (match_operand:HI 2 "accg_operand" "=B")
7701 (unspec:HI [(match_operand:V4QI 3 "accg_operand" "B")
7702 (match_operand:SI 4 "const_int_operand" "n")]
7707 switch (INTVAL (operands[4]))
7710 case FRV_BUILTIN_MDADDACCS: return \"mdaddaccs %1, %0\";
7711 case FRV_BUILTIN_MDSUBACCS: return \"mdsubaccs %1, %0\";
7714 fatal_insn (\"Bad media insn, mdaddacc\", insn);
7716 [(set_attr "length" "4")
7717 (set_attr "type" "mdaddacc")])
7719 ;; Dual absolute (halfword): type "mabsh"
7721 (define_insn "mabshs"
7722 [(set (match_operand:SI 0 "fpr_operand" "=f")
7723 (unspec:SI [(match_operand:SI 1 "fpr_operand" "f")] UNSPEC_MABSHS))]
7726 [(set_attr "length" "4")
7727 (set_attr "type" "mabsh")])
7729 ;; Dual rotate: type "mdrot"
7731 (define_insn "mdrotli"
7732 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
7733 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
7734 (match_operand:SI 2 "uint5_operand" "I")]
7737 "mdrotli %1, %2, %0"
7738 [(set_attr "length" "4")
7739 (set_attr "type" "mdrot")])
7741 ;; Dual coupling (concatenation): type "mcpl"
7743 (define_insn "mcplhi"
7744 [(set (match_operand:SI 0 "fpr_operand" "=f")
7745 (unspec:SI [(match_operand:DI 1 "fpr_operand" "h")
7746 (match_operand:SI 2 "uint4_operand" "I")]
7750 [(set_attr "length" "4")
7751 (set_attr "type" "mcpl")])
7753 (define_insn "mcpli"
7754 [(set (match_operand:SI 0 "fpr_operand" "=f")
7755 (unspec:SI [(match_operand:DI 1 "fpr_operand" "h")
7756 (match_operand:SI 2 "uint5_operand" "I")]
7760 [(set_attr "length" "4")
7761 (set_attr "type" "mcpl")])
7763 ;; Dual cut: type "mdcut"
7765 (define_insn "mdcutssi"
7766 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
7767 (unspec:DI [(match_operand:DI 1 "even_acc_operand" "b")
7768 (match_operand:SI 2 "int6_operand" "I")
7769 (match_operand:HI 3 "accg_operand" "B")]
7772 "mdcutssi %1, %2, %0"
7773 [(set_attr "length" "4")
7774 (set_attr "type" "mdcut")])
7776 ;; Quad saturate (halfword): type "mqsath"
7778 (define_insn "mqsaths"
7779 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
7780 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
7781 (match_operand:DI 2 "even_fpr_operand" "h")]
7784 "mqsaths %1, %2, %0"
7785 [(set_attr "length" "4")
7786 (set_attr "type" "mqsath")])
7788 ;; Quad limit instructions: type "mqlimh"
7790 (define_insn "mqlclrhs"
7791 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
7792 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
7793 (match_operand:DI 2 "even_fpr_operand" "h")]
7795 "TARGET_MEDIA_FR450"
7796 "mqlclrhs %1, %2, %0"
7797 [(set_attr "length" "4")
7798 (set_attr "type" "mqlimh")])
7800 (define_insn "mqlmths"
7801 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
7802 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
7803 (match_operand:DI 2 "even_fpr_operand" "h")]
7805 "TARGET_MEDIA_FR450"
7806 "mqlmths %1, %2, %0"
7807 [(set_attr "length" "4")
7808 (set_attr "type" "mqlimh")])
7810 (define_insn "mqsllhi"
7811 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
7812 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
7813 (match_operand:SI 2 "int6_operand" "I")]
7815 "TARGET_MEDIA_FR450"
7816 "mqsllhi %1, %2, %0"
7817 [(set_attr "length" "4")
7818 (set_attr "type" "mqshift")])
7820 (define_insn "mqsrahi"
7821 [(set (match_operand:DI 0 "even_fpr_operand" "=h")
7822 (unspec:DI [(match_operand:DI 1 "even_fpr_operand" "h")
7823 (match_operand:SI 2 "int6_operand" "I")]
7825 "TARGET_MEDIA_FR450"
7826 "mqsrahi %1, %2, %0"
7827 [(set_attr "length" "4")
7828 (set_attr "type" "mqshift")])
7830 ;; Set hi/lo instructions: type "mset"
7832 (define_insn "mhsetlos"
7833 [(set (match_operand:SI 0 "fpr_operand" "=f")
7834 (unspec:SI [(match_operand:SI 1 "fpr_operand" "0")
7835 (match_operand:SI 2 "int12_operand" "NOP")]
7839 [(set_attr "length" "4")
7840 (set_attr "type" "mset")])
7842 (define_insn "mhsetloh"
7843 [(set (match_operand:SI 0 "fpr_operand" "=f")
7844 (unspec:SI [(match_operand:SI 1 "fpr_operand" "0")
7845 (match_operand:SI 2 "int5_operand" "I")]
7849 [(set_attr "length" "4")
7850 (set_attr "type" "mset")])
7852 (define_insn "mhsethis"
7853 [(set (match_operand:SI 0 "fpr_operand" "=f")
7854 (unspec:SI [(match_operand:SI 1 "fpr_operand" "0")
7855 (match_operand:SI 2 "int12_operand" "NOP")]
7859 [(set_attr "length" "4")
7860 (set_attr "type" "mset")])
7862 (define_insn "mhsethih"
7863 [(set (match_operand:SI 0 "fpr_operand" "=f")
7864 (unspec:SI [(match_operand:SI 1 "fpr_operand" "0")
7865 (match_operand:SI 2 "int5_operand" "I")]
7869 [(set_attr "length" "4")
7870 (set_attr "type" "mset")])
7872 (define_insn "mhdsets"
7873 [(set (match_operand:SI 0 "fpr_operand" "=f")
7874 (unspec:SI [(match_operand:SI 1 "int12_operand" "NOP")]
7878 [(set_attr "length" "4")
7879 (set_attr "type" "mset")])
7881 (define_insn "mhdseth"
7882 [(set (match_operand:SI 0 "fpr_operand" "=f")
7883 (unspec:SI [(match_operand:SI 1 "fpr_operand" "0")
7884 (match_operand:SI 2 "int5_operand" "I")]
7888 [(set_attr "length" "4")
7889 (set_attr "type" "mset")])
7891 ;;-----------------------------------------------------------------------------
7893 (define_expand "symGOT2reg"
7894 [(match_operand:SI 0 "" "")
7895 (match_operand:SI 1 "" "")
7896 (match_operand:SI 2 "" "")
7897 (match_operand:SI 3 "" "")]
7903 insn = emit_insn (gen_symGOT2reg_i (operands[0], operands[1], operands[2], operands[3]));
7905 MEM_READONLY_P (SET_SRC (PATTERN (insn))) = 1;
7907 REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_EQUAL, operands[1],
7913 (define_expand "symGOT2reg_i"
7914 [(set (match_operand:SI 0 "" "")
7915 (mem:SI (plus:SI (match_operand:SI 2 "" "")
7916 (const:SI (unspec:SI [(match_operand:SI 1 "" "")
7917 (match_operand:SI 3 "" "")]
7922 (define_expand "symGOT2reg_hilo"
7924 (high:SI (const:SI (unspec:SI [(match_operand:SI 1 "" "")
7925 (match_dup 4)] UNSPEC_GOT))))
7927 (lo_sum:SI (match_dup 6)
7928 (const:SI (unspec:SI [(match_dup 1)
7929 (match_operand:SI 3 "" "")]
7931 (set (match_operand:SI 0 "" "")
7932 (mem:SI (plus:SI (match_dup 5)
7933 (match_operand:SI 2 "" ""))))
7939 operands[6] = operands[5] = operands[0];
7942 operands[6] = gen_reg_rtx (SImode);
7943 operands[5] = gen_reg_rtx (SImode);
7946 operands[4] = GEN_INT (INTVAL (operands[3]) + 1);
7947 operands[3] = GEN_INT (INTVAL (operands[3]) + 2);
7950 (define_expand "symGOTOFF2reg_hilo"
7952 (high:SI (const:SI (unspec:SI [(match_operand:SI 1 "" "")
7953 (match_dup 4)] UNSPEC_GOT))))
7955 (lo_sum:SI (match_dup 6)
7956 (const:SI (unspec:SI [(match_dup 1)
7957 (match_operand:SI 3 "" "")]
7959 (set (match_operand:SI 0 "" "")
7960 (plus:SI (match_dup 5)
7961 (match_operand:SI 2 "" "")))
7967 operands[6] = operands[5] = operands[0];
7970 operands[6] = gen_reg_rtx (SImode);
7971 operands[5] = gen_reg_rtx (SImode);
7974 operands[4] = GEN_INT (INTVAL (operands[3]) + 1);
7975 operands[3] = GEN_INT (INTVAL (operands[3]) + 2);
7978 (define_expand "symGOTOFF2reg"
7979 [(match_operand:SI 0 "" "")
7980 (match_operand:SI 1 "" "")
7981 (match_operand:SI 2 "" "")
7982 (match_operand:SI 3 "" "")]
7986 rtx insn = emit_insn (gen_symGOTOFF2reg_i (operands[0], operands[1], operands[2], operands[3]));
7988 REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_EQUAL, operands[1],
7994 (define_expand "symGOTOFF2reg_i"
7995 [(set (match_operand:SI 0 "" "")
7996 (plus:SI (match_operand:SI 2 "" "")
7998 (unspec:SI [(match_operand:SI 1 "" "")
7999 (match_operand:SI 3 "" "")]
8004 (define_expand "symGPREL2reg"
8005 [(match_operand:SI 0 "" "")
8006 (match_operand:SI 1 "" "")
8007 (match_operand:SI 2 "" "")
8008 (match_operand:SI 3 "" "")
8016 operands[4] = operands[0];
8018 operands[4] = gen_reg_rtx (SImode);
8020 emit_insn (frv_gen_GPsym2reg (operands[4], operands[2]));
8022 insn = emit_insn (gen_symGOTOFF2reg_i (operands[0], operands[1],
8023 operands[4], operands[3]));
8025 REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_EQUAL, operands[1],
8031 (define_expand "symGPREL2reg_hilo"
8032 [(match_operand:SI 0 "" "")
8033 (match_operand:SI 1 "" "")
8034 (match_operand:SI 2 "" "")
8035 (match_operand:SI 3 "" "")
8044 emit_insn (gen_symGOT2reg (operands[0], operands[1], operands[2],
8045 GEN_INT (R_FRV_GOT12)));
8049 operands[4] = gen_reg_rtx (SImode);
8051 emit_insn (frv_gen_GPsym2reg (operands[4], operands[2]));
8053 insn = emit_insn (gen_symGOTOFF2reg_hilo (operands[0], operands[1],
8054 operands[4], operands[3]));
8056 REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_EQUAL, operands[1],
8073 (UNSPEC_PREFETCH0 163)
8074 (UNSPEC_PREFETCH 164)
8075 (UNSPEC_IACCreadll 165)
8076 (UNSPEC_IACCreadl 166)
8077 (UNSPEC_IACCsetll 167)
8078 (UNSPEC_IACCsetl 168)
8087 [(set (match_operand:DI 0 "integer_register_operand" "=d")
8088 (unspec:DI [(match_operand:SI 1 "integer_register_operand" "d")
8089 (match_operand:SI 2 "integer_register_operand" "d")]
8093 [(set_attr "length" "4")
8094 (set_attr "type" "mul")])
8097 [(set (match_operand:DI 0 "integer_register_operand" "=d")
8098 (unspec:DI [(match_operand:SI 1 "integer_register_operand" "d")
8099 (match_operand:SI 2 "integer_register_operand" "d")]
8103 [(set_attr "length" "4")
8104 (set_attr "type" "mul")])
8106 (define_insn "smass"
8107 [(set (reg:DI IACC0_REG)
8108 (unspec:DI [(match_operand:SI 0 "integer_register_operand" "d")
8109 (match_operand:SI 1 "integer_register_operand" "d")
8112 "TARGET_FR405_BUILTINS"
8114 [(set_attr "length" "4")
8115 (set_attr "type" "macc")])
8117 (define_insn "smsss"
8118 [(set (reg:DI IACC0_REG)
8119 (unspec:DI [(match_operand:SI 0 "integer_register_operand" "d")
8120 (match_operand:SI 1 "integer_register_operand" "d")
8123 "TARGET_FR405_BUILTINS"
8125 [(set_attr "length" "4")
8126 (set_attr "type" "macc")])
8129 [(set (reg:DI IACC0_REG)
8130 (unspec:DI [(match_operand:SI 0 "integer_register_operand" "d")
8131 (match_operand:SI 1 "integer_register_operand" "d")]
8133 "TARGET_FR405_BUILTINS"
8135 [(set_attr "length" "4")
8136 (set_attr "type" "macc")])
8138 (define_insn "addss"
8139 [(set (match_operand:SI 0 "integer_register_operand" "=d")
8140 (unspec:SI [(match_operand:SI 1 "integer_register_operand" "d")
8141 (match_operand:SI 2 "integer_register_operand" "d")]
8143 "TARGET_FR405_BUILTINS"
8145 [(set_attr "length" "4")
8146 (set_attr "type" "int")])
8148 (define_insn "subss"
8149 [(set (match_operand:SI 0 "integer_register_operand" "=d")
8150 (unspec:SI [(match_operand:SI 1 "integer_register_operand" "d")
8151 (match_operand:SI 2 "integer_register_operand" "d")]
8153 "TARGET_FR405_BUILTINS"
8155 [(set_attr "length" "4")
8156 (set_attr "type" "int")])
8158 (define_insn "slass"
8159 [(set (match_operand:SI 0 "integer_register_operand" "=d")
8160 (unspec:SI [(match_operand:SI 1 "integer_register_operand" "d")
8161 (match_operand:SI 2 "integer_register_operand" "d")]
8163 "TARGET_FR405_BUILTINS"
8165 [(set_attr "length" "4")
8166 (set_attr "type" "int")])
8169 [(set (match_operand:SI 0 "integer_register_operand" "=d")
8170 (unspec:SI [(match_operand:SI 1 "integer_register_operand" "d")
8171 (match_operand:SI 2 "integer_register_operand" "d")]
8175 [(set_attr "length" "4")
8176 (set_attr "type" "scan")])
8178 (define_insn "scutss"
8179 [(set (match_operand:SI 0 "integer_register_operand" "=d")
8180 (unspec:SI [(match_operand:SI 1 "integer_register_operand" "d")
8183 "TARGET_FR405_BUILTINS"
8185 [(set_attr "length" "4")
8186 (set_attr "type" "cut")])
8188 (define_insn "frv_prefetch0"
8189 [(prefetch (unspec:SI [(match_operand:SI 0 "register_operand" "r")]
8195 [(set_attr "length" "4")])
8197 (define_insn "frv_prefetch"
8198 [(prefetch (unspec:SI [(match_operand:SI 0 "register_operand" "r")]
8202 "TARGET_FR500_FR550_BUILTINS"
8203 "nop.p\\n\\tnldub @(%0, gr0), gr0"
8204 [(set_attr "length" "8")])
8208 (define_insn "call_gettlsoff"
8209 [(set (match_operand:SI 0 "register_operand" "=D09")
8211 [(match_operand:SI 1 "symbolic_operand" "")]
8213 (clobber (reg:SI GR8_REG))
8214 (clobber (reg:SI LRREG))
8215 (use (match_operand:SI 2 "register_operand" "D15"))]
8217 "call #gettlsoff(%a1)"
8218 [(set_attr "length" "4")
8219 (set_attr "type" "load_or_call")])
8221 ;; We have to expand this like a libcall (it sort of actually is)
8222 ;; because otherwise sched may move, for example, an insn that sets up
8223 ;; GR8 for a subsequence call before the *tls_indirect_call insn, and
8224 ;; then reload won't be able to fix things up.
8225 (define_expand "tls_indirect_call"
8226 [(set (reg:DI GR8_REG)
8227 (match_operand:DI 2 "register_operand" ""))
8229 [(set (reg:SI GR9_REG)
8231 [(match_operand:SI 1 "symbolic_operand" "")
8233 UNSPEC_TLS_INDIRECT_CALL))
8234 (clobber (reg:SI GR8_REG))
8235 (clobber (reg:SI LRREG))
8236 (use (match_operand:SI 3 "register_operand" ""))])
8237 (set (match_operand:SI 0 "register_operand" "")
8241 (define_insn "*tls_indirect_call"
8242 [(set (reg:SI GR9_REG)
8244 [(match_operand:SI 0 "symbolic_operand" "")
8246 UNSPEC_TLS_INDIRECT_CALL))
8247 (clobber (reg:SI GR8_REG))
8248 (clobber (reg:SI LRREG))
8249 ;; If there was a way to represent the fact that we don't need GR9
8250 ;; or GR15 to be set before this instruction (it could be in
8251 ;; parallel), we could use it here. This change wouldn't apply to
8252 ;; call_gettlsoff, thought, since the linker may turn the latter
8253 ;; into ldi @(gr15,offset),gr9.
8254 (use (match_operand:SI 1 "register_operand" "D15"))]
8256 "calll #gettlsoff(%a0)@(gr8,gr0)"
8257 [(set_attr "length" "4")
8258 (set_attr "type" "jumpl")])
8260 (define_insn "tls_load_gottlsoff12"
8261 [(set (match_operand:SI 0 "register_operand" "=r")
8263 [(match_operand:SI 1 "symbolic_operand" "")
8264 (match_operand:SI 2 "register_operand" "r")]
8265 UNSPEC_TLS_LOAD_GOTTLSOFF12))]
8267 "ldi @(%2, #gottlsoff12(%1)), %0"
8268 [(set_attr "length" "4")])
8270 (define_expand "tlsoff_hilo"
8271 [(set (match_operand:SI 0 "register_operand" "=r")
8272 (high:SI (const:SI (unspec:SI
8273 [(match_operand:SI 1 "symbolic_operand" "")
8274 (match_operand:SI 2 "immediate_operand" "n")]
8277 (lo_sum:SI (match_dup 0)
8278 (const:SI (unspec:SI [(match_dup 1)
8279 (match_dup 3)] UNSPEC_GOT))))]
8283 operands[3] = GEN_INT (INTVAL (operands[2]) + 1);
8286 ;; Just like movdi_ldd, but with relaxation annotations.
8287 (define_insn "tls_tlsdesc_ldd"
8288 [(set (match_operand:DI 0 "register_operand" "=r")
8289 (unspec:DI [(mem:DI (unspec:SI
8290 [(match_operand:SI 1 "register_operand" "r")
8291 (match_operand:SI 2 "register_operand" "r")
8292 (match_operand:SI 3 "symbolic_operand" "")]
8293 UNSPEC_TLS_TLSDESC_LDD_AUX))]
8294 UNSPEC_TLS_TLSDESC_LDD))]
8296 "ldd #tlsdesc(%a3)@(%1,%2), %0"
8297 [(set_attr "length" "4")
8298 (set_attr "type" "gload")])
8300 (define_insn "tls_tlsoff_ld"
8301 [(set (match_operand:SI 0 "register_operand" "=r")
8303 [(match_operand:SI 1 "register_operand" "r")
8304 (match_operand:SI 2 "register_operand" "r")
8305 (match_operand:SI 3 "symbolic_operand" "")]
8306 UNSPEC_TLS_TLSOFF_LD)))]
8308 "ld #tlsoff(%a3)@(%1,%2), %0"
8309 [(set_attr "length" "4")
8310 (set_attr "type" "gload")])
8312 (define_insn "tls_lddi"
8313 [(set (match_operand:DI 0 "register_operand" "=r")
8314 (unspec:DI [(match_operand:SI 1 "symbolic_operand" "")
8315 (match_operand:SI 2 "register_operand" "d")]
8318 "lddi @(%2, #gottlsdesc12(%a1)), %0"
8319 [(set_attr "length" "4")
8320 (set_attr "type" "gload")])