1 ;; GCC machine description for CRIS cpu cores.
2 ;; Copyright (C) 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006
3 ;; Free Software Foundation, Inc.
4 ;; Contributed by Axis Communications.
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 ;; The original PO technology requires these to be ordered by speed,
24 ;; so that assigner will pick the fastest.
26 ;; See files "md.texi" and "rtl.def" for documentation on define_insn,
29 ;; The function cris_notice_update_cc in cris.c handles condition code
30 ;; updates for most instructions, helped by the "cc" attribute.
32 ;; There are several instructions that are orthogonal in size, and seems
33 ;; they could be matched by a single pattern without a specified size
34 ;; for the operand that is orthogonal. However, this did not work on
35 ;; gcc-2.7.2 (and probably not on gcc-2.8.1), relating to that when a
36 ;; constant is substituted into an operand, the actual mode must be
37 ;; deduced from the pattern. There is reasonable hope that that has been
38 ;; fixed, so FIXME: try again.
40 ;; You will notice that three-operand alternatives ("=r", "r", "!To")
41 ;; are marked with a "!" constraint modifier to avoid being reloaded
42 ;; into. This is because gcc would otherwise prefer to use the constant
43 ;; pool and its offsettable address instead of reloading to an
44 ;; ("=r", "0", "i") alternative. Also, the constant-pool support was not
45 ;; only suboptimal but also buggy in 2.7.2, ??? maybe only in 2.6.3.
47 ;; All insns that look like (set (...) (plus (...) (reg:SI 8)))
48 ;; get problems when reloading r8 (frame pointer) to r14 + offs (stack
49 ;; pointer). Thus the instructions that get into trouble have specific
50 ;; checks against matching frame_pointer_rtx.
51 ;; ??? But it should be re-checked for gcc > 2.7.2
52 ;; FIXME: This changed some time ago (from 2000-03-16) for gcc-2.9x.
54 ;; FIXME: When PIC, all [rX=rY+S] could be enabled to match
55 ;; [rX=gotless_symbol].
56 ;; The movsi for a gotless symbol could be split (post reload).
59 ;; 0 PLT reference from call expansion: operand 0 is the address,
60 ;; the mode is VOIDmode. Always wrapped in CONST.
61 ;; 1 Stack frame deallocation barrier.
62 ;; 2 The address of the global offset table as a source operand.
63 ;; 3 The address of a global-offset-table-relative symbol + offset.
64 ;; 4 The offset within GOT of a symbol.
65 ;; 5 The offset within GOT of a symbol that has a PLT.
67 (define_constants ; FIXME: reorder sanely.
69 (CRIS_UNSPEC_FRAME_DEALLOC 1)
71 (CRIS_UNSPEC_GOTREL 3)
72 (CRIS_UNSPEC_GOTREAD 4)
73 (CRIS_UNSPEC_PLTGOTREAD 5)])
78 (CRIS_STATIC_CHAIN_REGNUM 7)
87 ;; We need an attribute to define whether an instruction can be put in
88 ;; a branch-delay slot or not, and whether it has a delay slot.
90 ;; Branches and return instructions have a delay slot, and cannot
91 ;; themselves be put in a delay slot. This has changed *for short
92 ;; branches only* between architecture variants, but the possible win
93 ;; is presumed negligible compared to the added complexity of the machine
94 ;; description: one would have to add always-correct infrastructure to
95 ;; distinguish short branches.
97 ;; Whether an instruction can be put in a delay slot depends on the
98 ;; instruction (all short instructions except jumps and branches)
99 ;; and the addressing mode (must not be prefixed or referring to pc).
100 ;; In short, any "slottable" instruction must be 16 bit and not refer
101 ;; to pc, or alter it.
103 ;; The possible values are "yes", "no" and "has_slot". Yes/no means if
104 ;; the insn is slottable or not. Has_slot means that the insn is a
105 ;; return insn or branch insn (which are not considered slottable since
106 ;; that is generally true). Having the seemingly illogical value
107 ;; "has_slot" means we do not have to add another attribute just to say
108 ;; that an insn has a delay-slot, since it also infers that it is not
109 ;; slottable. Better names for the attribute were found to be longer and
110 ;; not add readability to the machine description.
112 ;; The default that is defined here for this attribute is "no", not
113 ;; slottable, not having a delay-slot, so there's no need to worry about
114 ;; it being wrong for non-branch and return instructions.
115 ;; The default could depend on the kind of insn and the addressing
116 ;; mode, but that would need more attributes and hairier, more error
119 ;; There is an extra memory constraint, 'Q', which recognizes an indirect
120 ;; register. The constraints 'Q' and '>' together match all possible
121 ;; memory operands that are slottable.
122 ;; For other operands, you need to check if it has a valid "slottable"
123 ;; quick-immediate operand, where the particular signedness-variation
124 ;; may match the constraints 'I' or 'J'.), and include it in the
125 ;; constraint pattern for the slottable pattern. An alternative using
126 ;; only "r" constraints is most often slottable.
128 (define_attr "slottable" "no,yes,has_slot" (const_string "no"))
130 ;; We also need attributes to sanely determine the condition code
131 ;; state. See cris_notice_update_cc for how this is used.
133 (define_attr "cc" "none,clobber,normal" (const_string "normal"))
135 ;; At the moment, this attribute is just used to help bb-reorder do its
136 ;; work; the default 0 doesn't help it. Many insns have other lengths,
137 ;; though none are shorter.
138 (define_attr "length" "" (const_int 2))
140 ;; A branch or return has one delay-slot. The instruction in the
141 ;; delay-slot is always executed, independent of whether the branch is
142 ;; taken or not. Note that besides setting "slottable" to "has_slot",
143 ;; there also has to be a "%#" at the end of a "delayed" instruction
144 ;; output pattern (for "jump" this means "ba %l0%#"), so print_operand can
145 ;; catch it and print a "nop" if necessary. This method was stolen from
148 (define_delay (eq_attr "slottable" "has_slot")
149 [(eq_attr "slottable" "yes") (nil) (nil)])
151 ;; Iterator definitions.
153 ;; For the "usual" pattern size alternatives.
154 (define_mode_macro BWD [SI HI QI])
155 (define_mode_macro WD [SI HI])
156 (define_mode_macro BW [HI QI])
157 (define_mode_attr S [(SI "HI") (HI "QI")])
158 (define_mode_attr s [(SI "hi") (HI "qi")])
159 (define_mode_attr m [(SI ".d") (HI ".w") (QI ".b")])
160 (define_mode_attr mm [(SI ".w") (HI ".b")])
161 (define_mode_attr nbitsm1 [(SI "31") (HI "15") (QI "7")])
163 ;; For the sign_extend+zero_extend variants.
164 (define_code_macro szext [sign_extend zero_extend])
165 (define_code_attr u [(sign_extend "") (zero_extend "u")])
166 (define_code_attr su [(sign_extend "s") (zero_extend "u")])
168 ;; For the shift variants.
169 (define_code_macro shift [ashiftrt lshiftrt ashift])
170 (define_code_macro shiftrt [ashiftrt lshiftrt])
171 (define_code_attr shlr [(ashiftrt "ashr") (lshiftrt "lshr") (ashift "ashl")])
172 (define_code_attr slr [(ashiftrt "asr") (lshiftrt "lsr") (ashift "lsl")])
174 (define_code_macro ncond [eq ne gtu ltu geu leu])
175 (define_code_macro ocond [gt le])
176 (define_code_macro rcond [lt ge])
177 (define_code_attr CC [(eq "eq") (ne "ne") (gt "gt") (gtu "hi") (lt "lt")
178 (ltu "lo") (ge "ge") (geu "hs") (le "le") (leu "ls")])
179 (define_code_attr rCC [(eq "ne") (ne "eq") (gt "le") (gtu "ls") (lt "ge")
180 (ltu "hs") (ge "lt") (geu "lo") (le "gt") (leu "hi")])
181 (define_code_attr oCC [(lt "mi") (ge "pl")])
182 (define_code_attr roCC [(lt "pl") (ge "mi")])
184 ;; Operand and operator predicates.
186 (include "predicates.md")
192 ;; Allow register and offsettable mem operands only; post-increment is
193 ;; not worth the trouble.
197 (match_operand:DI 0 "nonimmediate_operand" "r,o"))]
199 "test.d %M0\;ax\;test.d %H0")
201 ;; No test insns with side-effect on the mem addressing.
203 ;; See note on cmp-insns with side-effects (or lack of them)
205 ;; Normal named test patterns from SI on.
206 ;; FIXME: Seems they should change to be in order smallest..largest.
208 (define_insn "tst<mode>"
210 (match_operand:BWD 0 "nonimmediate_operand" "r,Q>,m"))]
213 [(set_attr "slottable" "yes,yes,no")])
215 ;; It seems that the position of the sign-bit and the fact that 0.0 is
216 ;; all 0-bits would make "tstsf" a straight-forward implementation;
217 ;; either "test.d" it for positive/negative or "btstq 30,r" it for
220 ;; FIXME: Do that some time; check next_cc0_user to determine if
221 ;; zero or negative is tested for.
225 ;; We could optimize the sizes of the immediate operands for various
226 ;; cases, but that is not worth it because of the very little usage of
227 ;; DImode for anything else but a structure/block-mode. Just do the
228 ;; obvious stuff for the straight-forward constraint letters.
232 (compare (match_operand:DI 0 "nonimmediate_operand" "r,r,r,r,r,r,o")
233 (match_operand:DI 1 "general_operand" "K,I,P,n,r,o,r")))]
236 cmpq %1,%M0\;ax\;cmpq 0,%H0
237 cmpq %1,%M0\;ax\;cmpq -1,%H0
238 cmp%e1.%z1 %1,%M0\;ax\;cmpq %H1,%H0
239 cmp.d %M1,%M0\;ax\;cmp.d %H1,%H0
240 cmp.d %M1,%M0\;ax\;cmp.d %H1,%H0
241 cmp.d %M1,%M0\;ax\;cmp.d %H1,%H0
242 cmp.d %M0,%M1\;ax\;cmp.d %H0,%H1")
244 ;; Note that compare insns with side effect addressing mode (e.g.):
246 ;; cmp.S [rx=ry+i],rz;
247 ;; cmp.S [%3=%1+%2],%0
249 ;; are *not* usable for gcc since the reloader *does not accept*
250 ;; cc0-changing insns with side-effects other than setting the condition
251 ;; codes. The reason is that the reload stage *may* cause another insn to
252 ;; be output after the main instruction, in turn invalidating cc0 for the
253 ;; insn using the test. (This does not apply to the CRIS case, since a
254 ;; reload for output -- move to memory -- does not change the condition
255 ;; code. Unfortunately we have no way to describe that at the moment. I
256 ;; think code would improve being in the order of one percent faster.
258 ;; We have cmps and cmpu (compare reg w. sign/zero extended mem).
259 ;; These are mostly useful for compares in SImode, using 8 or 16-bit
260 ;; constants, but sometimes gcc will find its way to use it for other
261 ;; (memory) operands. Avoid side-effect patterns, though (see above).
263 (define_insn "*cmp_ext<mode>"
266 (match_operand:SI 0 "register_operand" "r,r")
267 (match_operator:SI 2 "cris_extend_operator"
268 [(match_operand:BW 1 "memory_operand" "Q>,m")])))]
271 [(set_attr "slottable" "yes,no")])
273 ;; Swap operands; it seems the canonical look (if any) is not enforced.
275 ;; FIXME: Investigate that.
277 (define_insn "*cmp_swapext<mode>"
280 (match_operator:SI 2 "cris_extend_operator"
281 [(match_operand:BW 0 "memory_operand" "Q>,m")])
282 (match_operand:SI 1 "register_operand" "r,r")))]
284 "cmp%e2<m> %0,%1" ; The function cris_notice_update_cc knows about
285 ; swapped operands to compares.
286 [(set_attr "slottable" "yes,no")])
288 ;; The "normal" compare patterns, from SI on.
293 (match_operand:SI 0 "nonimmediate_operand" "r,r,r, r,Q>,Q>,r,r,m,m")
294 (match_operand:SI 1 "general_operand" "I,r,Q>,M,M, r, P,g,M,r")))]
307 [(set_attr "slottable" "yes,yes,yes,yes,yes,yes,no,no,no,no")])
309 (define_insn "cmp<mode>"
312 (match_operand:BW 0 "nonimmediate_operand" "r,r, r,Q>,Q>,r,m,m")
313 (match_operand:BW 1 "general_operand" "r,Q>,M,M, r, g,M,r")))]
324 [(set_attr "slottable" "yes,yes,yes,yes,yes,no,no,no")])
326 ;; Pattern matching the BTST insn.
327 ;; It is useful for "if (i & val)" constructs, where val is an exact
328 ;; power of 2, or if val + 1 is a power of two, where we check for a bunch
329 ;; of zeros starting at bit 0).
331 ;; SImode. This mode is the only one needed, since gcc automatically
332 ;; extends subregs for lower-size modes. FIXME: Add testcase.
336 (match_operand:SI 0 "nonmemory_operand" "r,r,r,r,r,r,n")
337 (match_operand:SI 1 "const_int_operand" "K,n,K,n,K,n,n")
338 (match_operand:SI 2 "nonmemory_operand" "M,M,K,n,r,r,r")))]
339 ;; Either it is a single bit, or consecutive ones starting at 0.
340 "GET_CODE (operands[1]) == CONST_INT
341 && (operands[1] == const1_rtx || operands[2] == const0_rtx)
342 && (REG_S_P (operands[0])
343 || (operands[1] == const1_rtx
344 && REG_S_P (operands[2])
345 && GET_CODE (operands[0]) == CONST_INT
346 && exact_log2 (INTVAL (operands[0])) >= 0))"
348 ;; The last "&&" condition above should be caught by some kind of
349 ;; canonicalization in gcc, but we can easily help with it here.
350 ;; It results from expressions of the type
351 ;; "power_of_2_value & (1 << y)".
353 ;; Since there may be codes with tests in on bits (in constant position)
354 ;; beyond the size of a word, handle that by assuming those bits are 0.
355 ;; GCC should handle that, but it's a matter of easily-added belts while
356 ;; having suspenders.
366 [(set_attr "slottable" "yes")])
370 ;; The whole mandatory movdi family is here; expander, "anonymous"
371 ;; recognizer and splitter. We're forced to have a movdi pattern,
372 ;; although GCC should be able to split it up itself. Normally it can,
373 ;; but if other insns have DI operands (as is the case here), reload
374 ;; must be able to generate or match a movdi. many testcases fail at
375 ;; -O3 or -fssa if we don't have this. FIXME: Fix GCC... See
376 ;; <URL:http://gcc.gnu.org/ml/gcc-patches/2000-04/msg00104.html>.
377 ;; However, a patch from Richard Kenner (similar to the cause of
378 ;; discussion at the URL above), indicates otherwise. See
379 ;; <URL:http://gcc.gnu.org/ml/gcc-patches/2000-04/msg00554.html>.
380 ;; The truth has IMO is not been decided yet, so check from time to
381 ;; time by disabling the movdi patterns.
383 ;; To appease testcase gcc.c-torture/execute/920501-2.c (and others) at
384 ;; -O0, we need a movdi as a temporary measure. Here's how things fail:
385 ;; A cmpdi RTX needs reloading (global):
386 ;; (insn 185 326 186 (set (cc0)
387 ;; (compare (mem/f:DI (reg/v:SI 22) 0)
388 ;; (const_int 1 [0x1]))) 4 {cmpdi} (nil)
390 ;; Now, reg 22 is reloaded for input address, and the mem is also moved
391 ;; out of the instruction (into a register), since one of the operands
392 ;; must be a register. Reg 22 is reloaded (into reg 10), and the mem is
393 ;; moved out and synthesized in SImode parts (reg 9, reg 10 - should be ok
394 ;; wrt. overlap). The bad things happen with the synthesis in
395 ;; emit_move_insn_1; the location where to substitute reg 10 is lost into
396 ;; two new RTX:es, both still having reg 22. Later on, the left-over reg
397 ;; 22 is recognized to have an equivalent in memory which is substituted
398 ;; straight in, and we end up with an unrecognizable insn:
399 ;; (insn 325 324 326 (set (reg:SI 9 r9)
400 ;; (mem/f:SI (mem:SI (plus:SI (reg:SI 8 r8)
401 ;; (const_int -84 [0xffffffac])) 0) 0)) -1 (nil)
403 ;; which is the first part of the reloaded synthesized "movdi".
404 ;; The right thing would be to add equivalent replacement locations for
405 ;; insn with pseudos that need more reloading. The question is where.
407 (define_expand "movdi"
408 [(set (match_operand:DI 0 "nonimmediate_operand" "")
409 (match_operand:DI 1 "general_operand" ""))]
412 if (GET_CODE (operands[0]) == MEM && operands[1] != const0_rtx)
413 operands[1] = copy_to_mode_reg (DImode, operands[1]);
415 /* Some other ports (as of 2001-09-10 for example mcore and romp) also
416 prefer to split up constants early, like this. The testcase in
417 gcc.c-torture/execute/961213-1.c shows that CSE2 gets confused by the
418 resulting subreg sets when using the construct from mcore (as of FSF
419 CVS, version -r 1.5), and it believes that the high part (the last one
420 emitted) is the final value. This construct from romp seems more
421 robust, especially considering the head comments from
422 emit_no_conflict_block. */
423 if ((GET_CODE (operands[1]) == CONST_INT
424 || GET_CODE (operands[1]) == CONST_DOUBLE)
425 && ! reload_completed
426 && ! reload_in_progress)
429 rtx op0 = operands[0];
430 rtx op1 = operands[1];
433 emit_move_insn (operand_subword (op0, 0, 1, DImode),
434 operand_subword (op1, 0, 1, DImode));
435 emit_move_insn (operand_subword (op0, 1, 1, DImode),
436 operand_subword (op1, 1, 1, DImode));
437 insns = get_insns ();
440 emit_no_conflict_block (insns, op0, op1, 0, op1);
445 (define_insn "*movdi_insn"
446 [(set (match_operand:DI 0 "nonimmediate_operand" "=r,rx,m")
447 (match_operand:DI 1 "general_operand" "rx,g,rxM"))]
448 "register_operand (operands[0], DImode)
449 || register_operand (operands[1], DImode)
450 || operands[1] == const0_rtx"
454 [(set (match_operand:DI 0 "nonimmediate_operand" "")
455 (match_operand:DI 1 "general_operand" ""))]
458 "operands[2] = cris_split_movdx (operands);")
460 ;; Side-effect patterns for move.S1 [rx=ry+rx.S2],rw
461 ;; and move.S1 [rx=ry+i],rz
462 ;; Then movs.S1 and movu.S1 for both modes.
464 ;; move.S1 [rx=ry+rz.S],rw avoiding when rx is ry, or rw is rx
465 ;; FIXME: These could have anonymous mode for operand 0.
467 (define_insn "*mov_side<mode>_biap"
468 [(set (match_operand:BW 0 "register_operand" "=r,r")
470 (mult:SI (match_operand:SI 1 "register_operand" "r,r")
471 (match_operand:SI 2 "const_int_operand" "n,n"))
472 (match_operand:SI 3 "register_operand" "r,r"))))
473 (set (match_operand:SI 4 "register_operand" "=*3,r")
474 (plus:SI (mult:SI (match_dup 1)
477 "cris_side_effect_mode_ok (MULT, operands, 4, 3, 1, 2, 0)"
480 move<m> [%4=%3+%1%T2],%0")
482 (define_insn "*mov_sidesisf_biap"
483 [(set (match_operand 0 "register_operand" "=r,r,x,x")
485 (mult:SI (match_operand:SI 1 "register_operand" "r,r,r,r")
486 (match_operand:SI 2 "const_int_operand" "n,n,n,n"))
487 (match_operand:SI 3 "register_operand" "r,r,r,r"))))
488 (set (match_operand:SI 4 "register_operand" "=*3,r,*3,r")
489 (plus:SI (mult:SI (match_dup 1)
492 "GET_MODE_SIZE (GET_MODE (operands[0])) == UNITS_PER_WORD
493 && cris_side_effect_mode_ok (MULT, operands, 4, 3, 1, 2, 0)"
496 move.%s0 [%4=%3+%1%T2],%0
498 move [%4=%3+%1%T2],%0")
500 ;; move.S1 [rx=ry+i],rz
501 ;; avoiding move.S1 [ry=ry+i],rz
502 ;; and move.S1 [rz=ry+i],rz
503 ;; Note that "i" is allowed to be a register.
505 (define_insn "*mov_side<mode>"
506 [(set (match_operand:BW 0 "register_operand" "=r,r,r,r,r")
508 (plus:SI (match_operand:SI 1 "cris_bdap_operand" "%r,r,r,R,R")
509 (match_operand:SI 2 "cris_bdap_operand" "r>Rn,r,>Rn,r,r"))))
510 (set (match_operand:SI 3 "register_operand" "=*1,r,r,*2,r")
511 (plus:SI (match_dup 1)
513 "cris_side_effect_mode_ok (PLUS, operands, 3, 1, 2, -1, 0)"
515 if ((which_alternative == 0 || which_alternative == 3)
516 && (GET_CODE (operands[2]) != CONST_INT
517 || INTVAL (operands[2]) > 127
518 || INTVAL (operands[2]) < -128
519 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'N')
520 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'J')))
522 if (which_alternative == 4)
523 return "move<m> [%3=%2%S1],%0";
524 return "move<m> [%3=%1%S2],%0";
527 (define_insn "*mov_sidesisf"
528 [(set (match_operand 0 "register_operand" "=r,r,r,x,x,x,r,r,x,x")
531 (match_operand:SI 1 "cris_bdap_operand" "%r,r,r,r,r,r,R,R,R,R")
532 (match_operand:SI 2 "cris_bdap_operand" "r>Rn,r,>Rn,r>Rn,r,>Rn,r,r,r,r"))))
533 (set (match_operand:SI 3 "register_operand" "=*1,r,r,*1,r,r,*2,r,*2,r")
534 (plus:SI (match_dup 1)
536 "GET_MODE_SIZE (GET_MODE (operands[0])) == UNITS_PER_WORD
537 && cris_side_effect_mode_ok (PLUS, operands, 3, 1, 2, -1, 0)"
539 if ((which_alternative == 0
540 || which_alternative == 3
541 || which_alternative == 6
542 || which_alternative == 8)
543 && (GET_CODE (operands[2]) != CONST_INT
544 || INTVAL (operands[2]) > 127
545 || INTVAL (operands[2]) < -128
546 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'N')
547 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'J')))
549 if (which_alternative < 3)
550 return "move.%s0 [%3=%1%S2],%0";
551 if (which_alternative == 7)
552 return "move.%s0 [%3=%2%S1],%0";
553 if (which_alternative == 9)
554 return "move [%3=%2%S1],%0";
555 return "move [%3=%1%S2],%0";
558 ;; Other way around; move to memory.
560 ;; Note that the condition (which for side-effect patterns is usually a
561 ;; call to cris_side_effect_mode_ok), isn't consulted for register
562 ;; allocation preferences -- constraints is the method for that. The
563 ;; drawback is that we can't exclude register allocation to cause
564 ;; "move.s rw,[rx=ry+rz.S]" when rw==rx without also excluding rx==ry or
565 ;; rx==rz if we use an earlyclobber modifier for the constraint for rx.
566 ;; Instead of that, we recognize and split the cases where dangerous
567 ;; register combinations are spotted: where a register is set in the
568 ;; side-effect, and used in the main insn. We don't handle the case where
569 ;; the set in the main insn overlaps the set in the side-effect; that case
570 ;; must be handled in gcc. We handle just the case where the set in the
571 ;; side-effect overlaps the input operand of the main insn (i.e. just
575 ;; move.s rz,[ry=rx+rw.S]
577 (define_insn "*mov_side<mode>_biap_mem"
578 [(set (mem:BW (plus:SI
579 (mult:SI (match_operand:SI 0 "register_operand" "r,r,r")
580 (match_operand:SI 1 "const_int_operand" "n,n,n"))
581 (match_operand:SI 2 "register_operand" "r,r,r")))
582 (match_operand:BW 3 "register_operand" "r,r,r"))
583 (set (match_operand:SI 4 "register_operand" "=*2,!3,r")
584 (plus:SI (mult:SI (match_dup 0)
587 "cris_side_effect_mode_ok (MULT, operands, 4, 2, 0, 1, 3)"
591 move<m> %3,[%4=%2+%0%T1]")
593 (define_insn "*mov_sidesisf_biap_mem"
595 (mult:SI (match_operand:SI 0 "register_operand" "r,r,r,r,r,r")
596 (match_operand:SI 1 "const_int_operand" "n,n,n,n,n,n"))
597 (match_operand:SI 2 "register_operand" "r,r,r,r,r,r")))
598 (match_operand 3 "register_operand" "r,r,r,x,x,x"))
599 (set (match_operand:SI 4 "register_operand" "=*2,!3,r,*2,!3,r")
600 (plus:SI (mult:SI (match_dup 0)
603 "GET_MODE_SIZE (GET_MODE (operands[3])) == UNITS_PER_WORD
604 && cris_side_effect_mode_ok (MULT, operands, 4, 2, 0, 1, 3)"
608 move.%s3 %3,[%4=%2+%0%T1]
611 move %3,[%4=%2+%0%T1]")
613 ;; Split for the case above where we're out of luck with register
614 ;; allocation (again, the condition isn't checked for that), and we end up
615 ;; with the set in the side-effect getting the same register as the input
620 [(set (match_operator
623 (mult:SI (match_operand:SI 0 "register_operand" "")
624 (match_operand:SI 1 "const_int_operand" ""))
625 (match_operand:SI 2 "register_operand" ""))])
626 (match_operand 3 "register_operand" ""))
627 (set (match_operand:SI 4 "register_operand" "")
628 (plus:SI (mult:SI (match_dup 0)
631 "reload_completed && reg_overlap_mentioned_p (operands[4], operands[3])"
632 [(set (match_dup 5) (match_dup 3))
633 (set (match_dup 4) (match_dup 2))
635 (plus:SI (mult:SI (match_dup 0)
639 = replace_equiv_address (operands[6],
640 gen_rtx_PLUS (SImode,
641 gen_rtx_MULT (SImode,
646 ;; move.s rx,[ry=rz+i]
647 ;; FIXME: These could have anonymous mode for operand 2.
651 (define_insn "*mov_side<mode>_mem"
653 (plus:SI (match_operand:SI 0 "cris_bdap_operand" "%r,r,r,r,R,R,R")
654 (match_operand:SI 1 "cris_bdap_operand" "r>Rn,r>Rn,r,>Rn,r,r,r")))
655 (match_operand:BW 2 "register_operand" "r,r,r,r,r,r,r"))
656 (set (match_operand:SI 3 "register_operand" "=*0,!*2,r,r,*1,!*2,r")
657 (plus:SI (match_dup 0)
659 "cris_side_effect_mode_ok (PLUS, operands, 3, 0, 1, -1, 2)"
661 if ((which_alternative == 0 || which_alternative == 4)
662 && (GET_CODE (operands[1]) != CONST_INT
663 || INTVAL (operands[1]) > 127
664 || INTVAL (operands[1]) < -128
665 || CONST_OK_FOR_LETTER_P (INTVAL (operands[1]), 'N')
666 || CONST_OK_FOR_LETTER_P (INTVAL (operands[1]), 'J')))
668 if (which_alternative == 1 || which_alternative == 5)
670 if (which_alternative == 6)
671 return "move.%s2 %2,[%3=%1%S0]";
672 return "move<m> %2,[%3=%0%S1]";
677 (define_insn "*mov_sidesisf_mem"
681 0 "cris_bdap_operand"
682 "%r, r, r,r, r, r,r, R,R, R,R, R")
684 1 "cris_bdap_operand"
685 "r>Rn,r>Rn,r,>Rn,r>Rn,r,>Rn,r,r, r,r, r")))
686 (match_operand 2 "register_operand"
687 "r, r, r,r, x, x,x, r,r, r,x, x"))
688 (set (match_operand:SI 3 "register_operand"
689 "=*0,!2, r,r, *0, r,r, *1,!*2,r,*1,r")
690 (plus:SI (match_dup 0)
692 "GET_MODE_SIZE (GET_MODE (operands[2])) == UNITS_PER_WORD
693 && cris_side_effect_mode_ok (PLUS, operands, 3, 0, 1, -1, 2)"
695 if ((which_alternative == 0 || which_alternative == 4)
696 && (GET_CODE (operands[1]) != CONST_INT
697 || INTVAL (operands[1]) > 127
698 || INTVAL (operands[1]) < -128
699 || CONST_OK_FOR_LETTER_P (INTVAL (operands[1]), 'N')
700 || CONST_OK_FOR_LETTER_P (INTVAL (operands[1]), 'J')))
702 if (which_alternative == 1
703 || which_alternative == 7
704 || which_alternative == 8
705 || which_alternative == 10)
707 if (which_alternative < 4)
708 return "move.%s2 %2,[%3=%0%S1]";
709 if (which_alternative == 9)
710 return "move.%s2 %2,[%3=%1%S0]";
711 if (which_alternative == 11)
712 return "move %2,[%3=%1%S0]";
713 return "move %2,[%3=%0%S1]";
716 ;; Like the biap case, a split where the set in the side-effect gets the
717 ;; same register as the input register to the main insn, since the
718 ;; condition isn't checked at register allocation.
722 [(set (match_operator
725 (match_operand:SI 0 "cris_bdap_operand" "")
726 (match_operand:SI 1 "cris_bdap_operand" ""))])
727 (match_operand 2 "register_operand" ""))
728 (set (match_operand:SI 3 "register_operand" "")
729 (plus:SI (match_dup 0) (match_dup 1)))])]
730 "reload_completed && reg_overlap_mentioned_p (operands[3], operands[2])"
731 [(set (match_dup 4) (match_dup 2))
732 (set (match_dup 3) (match_dup 0))
733 (set (match_dup 3) (plus:SI (match_dup 3) (match_dup 1)))]
736 ;; Clear memory side-effect patterns. It is hard to get to the mode if
737 ;; the MEM was anonymous, so there will be one for each mode.
739 ;; clear.[bwd] [ry=rx+rw.s2]
741 (define_insn "*clear_side<mode>_biap"
742 [(set (mem:BWD (plus:SI
743 (mult:SI (match_operand:SI 0 "register_operand" "r,r")
744 (match_operand:SI 1 "const_int_operand" "n,n"))
745 (match_operand:SI 2 "register_operand" "r,r")))
747 (set (match_operand:SI 3 "register_operand" "=*2,r")
748 (plus:SI (mult:SI (match_dup 0)
751 "cris_side_effect_mode_ok (MULT, operands, 3, 2, 0, 1, -1)"
754 clear<m> [%3=%2+%0%T1]")
756 ;; clear.[bwd] [ry=rz+i]
758 (define_insn "*clear_side<mode>"
760 (plus:SI (match_operand:SI 0 "cris_bdap_operand" "%r,r,r,R,R")
761 (match_operand:SI 1 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")))
763 (set (match_operand:SI 2 "register_operand" "=*0,r,r,*1,r")
764 (plus:SI (match_dup 0)
766 "cris_side_effect_mode_ok (PLUS, operands, 2, 0, 1, -1, -1)"
768 if ((which_alternative == 0 || which_alternative == 3)
769 && (GET_CODE (operands[1]) != CONST_INT
770 || INTVAL (operands[1]) > 127
771 || INTVAL (operands[1]) < -128
772 || CONST_OK_FOR_LETTER_P (INTVAL (operands[1]), 'N')
773 || CONST_OK_FOR_LETTER_P (INTVAL (operands[1]), 'J')))
775 if (which_alternative == 4)
776 return "clear<m> [%2=%1%S0]";
777 return "clear<m> [%2=%0%S1]";
780 ;; Normal move patterns from SI on.
782 (define_expand "movsi"
784 (match_operand:SI 0 "nonimmediate_operand" "")
785 (match_operand:SI 1 "cris_general_operand_or_symbol" ""))]
788 /* If the output goes to a MEM, make sure we have zero or a register as
790 if (GET_CODE (operands[0]) == MEM
791 && ! REG_S_P (operands[1])
792 && operands[1] != const0_rtx
794 operands[1] = force_reg (SImode, operands[1]);
796 /* If we're generating PIC and have an incoming symbol, validize it to a
797 general operand or something that will match a special pattern.
799 FIXME: Do we *have* to recognize anything that would normally be a
800 valid symbol? Can we exclude global PIC addresses with an added
803 && CONSTANT_ADDRESS_P (operands[1])
804 && !cris_valid_pic_const (operands[1]))
806 enum cris_pic_symbol_type t = cris_pic_symbol_type_of (operands[1]);
808 gcc_assert (t != cris_no_symbol);
810 if (! REG_S_P (operands[0]))
812 /* We must have a register as destination for what we're about to
813 do, and for the patterns we generate. */
814 CRIS_ASSERT (!no_new_pseudos);
815 operands[1] = force_reg (SImode, operands[1]);
819 /* FIXME: add a REG_EQUAL (or is it REG_EQUIV) note to the
820 destination register for the symbol. It might not be
821 worth it. Measure. */
822 current_function_uses_pic_offset_table = 1;
823 if (t == cris_gotrel_symbol)
825 /* Change a "move.d sym(+offs),rN" into (allocate register rM)
826 "move.d (const (plus (unspec [sym]
827 CRIS_UNSPEC_GOTREL) offs)),rM" "add.d rPIC,rM,rN" */
828 rtx tem, rm, rn = operands[0];
829 rtx sym = GET_CODE (operands[1]) != CONST
830 ? operands[1] : get_related_value (operands[1]);
831 HOST_WIDE_INT offs = get_integer_term (operands[1]);
833 gcc_assert (! no_new_pseudos);
834 tem = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, sym),
837 tem = plus_constant (tem, offs);
838 rm = gen_reg_rtx (Pmode);
839 emit_move_insn (rm, gen_rtx_CONST (Pmode, tem));
840 if (expand_binop (Pmode, add_optab, rm, pic_offset_table_rtx,
841 rn, 0, OPTAB_LIB_WIDEN) != rn)
842 internal_error ("expand_binop failed in movsi gotrel");
845 else if (t == cris_got_symbol)
847 /* Change a "move.d sym,rN" into (allocate register rM, rO)
848 "move.d (const (unspec [sym] CRIS_UNSPEC_GOTREAD)),rM"
849 "add.d rPIC,rM,rO", "move.d [rO],rN" with
850 the memory access marked as read-only. */
851 rtx tem, mem, rm, ro, rn = operands[0];
852 gcc_assert (! no_new_pseudos);
853 tem = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, operands[1]),
854 CRIS_UNSPEC_GOTREAD);
855 rm = gen_reg_rtx (Pmode);
856 emit_move_insn (rm, gen_rtx_CONST (Pmode, tem));
857 ro = gen_reg_rtx (Pmode);
858 if (expand_binop (Pmode, add_optab, rm, pic_offset_table_rtx,
859 ro, 0, OPTAB_LIB_WIDEN) != ro)
860 internal_error ("expand_binop failed in movsi got");
861 mem = gen_rtx_MEM (Pmode, ro);
863 /* This MEM doesn't alias anything. Whether it
864 aliases other same symbols is unimportant. */
865 set_mem_alias_set (mem, new_alias_set ());
866 MEM_NOTRAP_P (mem) = 1;
867 MEM_READONLY_P (mem) = 1;
868 emit_move_insn (rn, mem);
873 /* We get here when we have to change something that would
874 be recognizable if it wasn't PIC. A ``sym'' is ok for
875 PIC symbols both with and without a GOT entry. And ``sym
876 + offset'' is ok for local symbols, so the only thing it
877 could be, is a global symbol with an offset. Check and
879 rtx reg = gen_reg_rtx (Pmode);
880 rtx sym = get_related_value (operands[1]);
881 HOST_WIDE_INT offs = get_integer_term (operands[1]);
883 gcc_assert (! no_new_pseudos
884 && t == cris_got_symbol_needing_fixup
885 && sym != NULL_RTX && offs != 0);
887 emit_move_insn (reg, sym);
888 if (expand_binop (SImode, add_optab, reg,
889 GEN_INT (offs), operands[0], 0,
890 OPTAB_LIB_WIDEN) != operands[0])
891 internal_error ("expand_binop failed in movsi got+offs");
898 (define_insn "*movsi_got_load"
899 [(set (reg:SI CRIS_GOT_REGNUM) (unspec:SI [(const_int 0)] CRIS_UNSPEC_GOT))]
901 "move.d $pc,%:\;sub.d .:GOTOFF,%:"
902 [(set_attr "cc" "clobber")])
904 (define_insn "*movsi_internal"
906 (match_operand:SI 0 "nonimmediate_operand" "=r,r, r,Q>,r,Q>,g,r,r, r,g,rQ>,x, m,x")
907 ;; Note that we prefer not to use the S alternative (if for some reason
908 ;; it competes with others), but g matches S.
909 (match_operand:SI 1 "general_operand" "r,Q>,M,M, I,r, M,n,!S,g,r,x, rQ>,x,gi"))]
912 /* Better to have c-switch here; it is worth it to optimize the size of
913 move insns. The alternative would be to try to find more constraint
914 letters. FIXME: Check again. It seems this could shrink a bit. */
915 switch (which_alternative)
922 return "move.d %1,%0";
928 return "move %d1,%0";
935 /* Constants -32..31 except 0. */
937 return "moveq %1,%0";
939 /* We can win a little on constants -32768..-33, 32..65535. */
941 if (INTVAL (operands[1]) > 0 && INTVAL (operands[1]) < 65536)
943 if (INTVAL (operands[1]) < 256)
944 return "movu.b %1,%0";
945 return "movu.w %1,%0";
947 else if (INTVAL (operands[1]) >= -32768 && INTVAL (operands[1]) < 32768)
949 if (INTVAL (operands[1]) >= -128 && INTVAL (operands[1]) < 128)
950 return "movs.b %1,%0";
951 return "movs.w %1,%0";
953 return "move.d %1,%0";
957 rtx tem = operands[1];
958 gcc_assert (GET_CODE (tem) == CONST);
960 if (GET_CODE (tem) == PLUS
961 && GET_CODE (XEXP (tem, 0)) == UNSPEC
962 && XINT (XEXP (tem, 0), 1) == CRIS_UNSPEC_GOTREL
963 && GET_CODE (XEXP (tem, 1)) == CONST_INT)
965 gcc_assert (GET_CODE (tem) == UNSPEC);
966 switch (XINT (tem, 1))
968 case CRIS_UNSPEC_GOTREAD:
969 case CRIS_UNSPEC_PLTGOTREAD:
970 /* Using sign-extend mostly to be consistent with the
971 indexed addressing mode. */
973 return "movs.w %1,%0";
974 case CRIS_UNSPEC_GOTREL:
975 case CRIS_UNSPEC_PLT:
976 return "move.d %1,%0";
983 return "BOGUS: %1 to %0";
986 [(set_attr "slottable" "yes,yes,yes,yes,yes,yes,no,no,no,no,no,yes,yes,no,no")
987 (set_attr "cc" "*,*,*,*,*,*,*,*,*,*,*,none,none,none,none")])
989 ;; Extend operations with side-effect from mem to register, using
990 ;; MOVS/MOVU. These are from mem to register only.
996 ;; FIXME: Can we omit extend to HImode, since GCC should truncate for
997 ;; HImode by itself? Perhaps use only anonymous modes?
999 (define_insn "*ext_sideqihi_biap"
1000 [(set (match_operand:HI 0 "register_operand" "=r,r")
1002 5 "cris_extend_operator"
1004 (mult:SI (match_operand:SI 1 "register_operand" "r,r")
1005 (match_operand:SI 2 "const_int_operand" "n,n"))
1006 (match_operand:SI 3 "register_operand" "r,r")))]))
1007 (set (match_operand:SI 4 "register_operand" "=*3,r")
1008 (plus:SI (mult:SI (match_dup 1)
1011 "cris_side_effect_mode_ok (MULT, operands, 4, 3, 1, 2, 0)"
1014 mov%e5.%m5 [%4=%3+%1%T2],%0")
1016 (define_insn "*ext_side<mode>si_biap"
1017 [(set (match_operand:SI 0 "register_operand" "=r,r")
1019 5 "cris_extend_operator"
1021 (mult:SI (match_operand:SI 1 "register_operand" "r,r")
1022 (match_operand:SI 2 "const_int_operand" "n,n"))
1023 (match_operand:SI 3 "register_operand" "r,r")))]))
1024 (set (match_operand:SI 4 "register_operand" "=*3,r")
1025 (plus:SI (mult:SI (match_dup 1)
1028 "cris_side_effect_mode_ok (MULT, operands, 4, 3, 1, 2, 0)"
1031 mov%e5<m> [%4=%3+%1%T2],%0")
1033 ;; Same but [rx=ry+i]
1037 (define_insn "*ext_sideqihi"
1038 [(set (match_operand:HI 0 "register_operand" "=r,r,r,r,r")
1040 4 "cris_extend_operator"
1042 (match_operand:SI 1 "cris_bdap_operand" "%r,r,r,R,R")
1043 (match_operand:SI 2 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")))]))
1044 (set (match_operand:SI 3 "register_operand" "=*1,r,r,*2,r")
1045 (plus:SI (match_dup 1)
1047 "cris_side_effect_mode_ok (PLUS, operands, 3, 1, 2, -1, 0)"
1049 if ((which_alternative == 0 || which_alternative == 3)
1050 && (GET_CODE (operands[2]) != CONST_INT
1051 || INTVAL (operands[2]) > 127
1052 || INTVAL (operands[2]) < -128
1053 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'N')
1054 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'J')))
1056 if (which_alternative == 4)
1057 return "mov%e4.%m4 [%3=%2%S1],%0";
1058 return "mov%e4.%m4 [%3=%1%S2],%0";
1061 (define_insn "*ext_side<mode>si"
1062 [(set (match_operand:SI 0 "register_operand" "=r,r,r,r,r")
1064 4 "cris_extend_operator"
1066 (match_operand:SI 1 "cris_bdap_operand" "%r,r,r,R,R")
1067 (match_operand:SI 2 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")))]))
1068 (set (match_operand:SI 3 "register_operand" "=*1,r,r,*2,r")
1069 (plus:SI (match_dup 1)
1071 "cris_side_effect_mode_ok (PLUS, operands, 3, 1, 2, -1, 0)"
1073 if ((which_alternative == 0 || which_alternative == 3)
1074 && (GET_CODE (operands[2]) != CONST_INT
1075 || INTVAL (operands[2]) > 127
1076 || INTVAL (operands[2]) < -128
1077 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'N')
1078 || CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'J')))
1080 if (which_alternative == 4)
1081 return "mov%e4<m> [%3=%2%S1],%0";
1082 return "mov%e4<m> [%3=%1%S2],%0";
1085 ;; FIXME: See movsi.
1087 (define_insn "movhi"
1089 (match_operand:HI 0 "nonimmediate_operand" "=r,r, r,Q>,r,Q>,r,r,r,g,g,r,r,x")
1090 (match_operand:HI 1 "general_operand" "r,Q>,M,M, I,r, L,O,n,M,r,g,x,r"))]
1093 switch (which_alternative)
1100 return "move.w %1,%0";
1103 return "move %1,%0";
1107 return "clear.w %0";
1109 return "moveq %1,%0";
1112 if (INTVAL (operands[1]) < 256 && INTVAL (operands[1]) >= -128)
1114 if (INTVAL (operands[1]) > 0)
1115 return "movu.b %1,%0";
1116 return "movs.b %1,%0";
1118 return "move.w %1,%0";
1120 return "movEq %b1,%0";
1122 return "BOGUS: %1 to %0";
1125 [(set_attr "slottable" "yes,yes,yes,yes,yes,yes,no,yes,no,no,no,no,yes,yes")
1126 (set_attr "cc" "*,*,none,none,*,none,*,clobber,*,none,none,*,none,none")])
1128 (define_insn "movstricthi"
1131 (match_operand:HI 0 "nonimmediate_operand" "+r,r, r,Q>,Q>,g,r,g"))
1132 (match_operand:HI 1 "general_operand" "r,Q>,M,M, r, M,g,r"))]
1143 [(set_attr "slottable" "yes,yes,yes,yes,yes,no,no,no")])
1145 (define_expand "reload_in<mode>"
1146 [(set (match_operand:BW 2 "register_operand" "=r")
1147 (match_operand:BW 1 "memory_operand" "m"))
1148 (set (match_operand:BW 0 "register_operand" "=x")
1153 (define_expand "reload_out<mode>"
1154 [(set (match_operand:BW 2 "register_operand" "=r")
1155 (match_operand:BW 1 "register_operand" "x"))
1156 (set (match_operand:BW 0 "memory_operand" "=m")
1161 (define_insn "movqi"
1162 [(set (match_operand:QI 0 "nonimmediate_operand" "=r,Q>,r, r,Q>,r,g,g,r,r,r,x")
1163 (match_operand:QI 1 "general_operand" "r,r, Q>,M,M, I,M,r,O,g,x,r"))]
1178 [(set_attr "slottable" "yes,yes,yes,yes,yes,yes,no,no,yes,no,yes,yes")
1179 (set_attr "cc" "*,*,*,*,*,*,*,*,clobber,*,none,none")])
1181 (define_insn "movstrictqi"
1182 [(set (strict_low_part
1183 (match_operand:QI 0 "nonimmediate_operand" "+r,Q>,r, r,Q>,g,g,r"))
1184 (match_operand:QI 1 "general_operand" "r,r, Q>,M,M, M,r,g"))]
1195 [(set_attr "slottable" "yes,yes,yes,yes,yes,no,no,no")])
1197 ;; The valid "quick" bit-patterns are, except for 0.0, denormalized
1198 ;; values REALLY close to 0, and some NaN:s (I think; their exponent is
1199 ;; all ones); the worthwhile one is "0.0".
1200 ;; It will use clear, so we know ALL types of immediate 0 never change cc.
1202 (define_insn "movsf"
1203 [(set (match_operand:SF 0 "nonimmediate_operand" "=r,Q>,r, r,Q>,g,g,r,r,x,Q>,m,x, x")
1204 (match_operand:SF 1 "general_operand" "r,r, Q>,G,G, G,r,g,x,r,x, x,Q>,g"))]
1221 [(set_attr "slottable" "yes,yes,yes,yes,yes,no,no,no,yes,yes,yes,no,yes,no")])
1223 ;; Note that the memory layout of the registers is the reverse of that
1224 ;; of the standard patterns "load_multiple" and "store_multiple".
1225 (define_insn "*cris_load_multiple"
1226 [(match_parallel 0 "cris_load_multiple_op"
1227 [(set (match_operand:SI 1 "register_operand" "=r,r")
1228 (match_operand:SI 2 "memory_operand" "Q,m"))])]
1231 [(set_attr "cc" "none")
1232 (set_attr "slottable" "yes,no")
1233 ;; Not true, but setting the length to 0 causes return sequences (ret
1234 ;; movem) to have the cost they had when (return) included the movem
1235 ;; and reduces the performance penalty taken for needing to emit an
1236 ;; epilogue (in turn copied by bb-reorder) instead of return patterns.
1237 ;; FIXME: temporary change until all insn lengths are correctly
1238 ;; described. FIXME: have better target control over bb-reorder.
1239 (set_attr "length" "0")])
1241 (define_insn "*cris_store_multiple"
1242 [(match_parallel 0 "cris_store_multiple_op"
1243 [(set (match_operand:SI 2 "memory_operand" "=Q,m")
1244 (match_operand:SI 1 "register_operand" "r,r"))])]
1247 [(set_attr "cc" "none")
1248 (set_attr "slottable" "yes,no")])
1251 ;; Sign- and zero-extend insns with standard names.
1252 ;; Those for integer source operand are ordered with the widest source
1257 (define_insn "extendsidi2"
1258 [(set (match_operand:DI 0 "register_operand" "=r")
1259 (sign_extend:DI (match_operand:SI 1 "general_operand" "g")))]
1261 "move.d %1,%M0\;smi %H0\;neg.d %H0,%H0")
1263 (define_insn "extend<mode>di2"
1264 [(set (match_operand:DI 0 "register_operand" "=r")
1265 (sign_extend:DI (match_operand:BW 1 "general_operand" "g")))]
1267 "movs<m> %1,%M0\;smi %H0\;neg.d %H0,%H0")
1269 (define_insn "extend<mode>si2"
1270 [(set (match_operand:SI 0 "register_operand" "=r,r,r")
1271 (sign_extend:SI (match_operand:BW 1 "general_operand" "r,Q>,g")))]
1274 [(set_attr "slottable" "yes,yes,no")])
1276 ;; To do a byte->word extension, extend to dword, exept that the top half
1277 ;; of the register will be clobbered. FIXME: Perhaps this is not needed.
1279 (define_insn "extendqihi2"
1280 [(set (match_operand:HI 0 "register_operand" "=r,r,r")
1281 (sign_extend:HI (match_operand:QI 1 "general_operand" "r,Q>,g")))]
1284 [(set_attr "slottable" "yes,yes,no")])
1287 ;; Zero-extend. The DImode ones are synthesized by gcc, so we don't
1288 ;; specify them here.
1290 (define_insn "zero_extend<mode>si2"
1291 [(set (match_operand:SI 0 "register_operand" "=r,r,r")
1293 (match_operand:BW 1 "nonimmediate_operand" "r,Q>,m")))]
1296 [(set_attr "slottable" "yes,yes,no")])
1298 ;; Same comment as sign-extend QImode to HImode above applies.
1300 (define_insn "zero_extendqihi2"
1301 [(set (match_operand:HI 0 "register_operand" "=r,r,r")
1303 (match_operand:QI 1 "nonimmediate_operand" "r,Q>,m")))]
1306 [(set_attr "slottable" "yes,yes,no")])
1308 ;; All kinds of arithmetic and logical instructions.
1310 ;; First, anonymous patterns to match addressing modes with
1313 ;; op.S [rx=ry+I],rz; (add, sub, or, and, bound).
1317 (define_insn "*op_side<mode>_biap"
1318 [(set (match_operand:BWD 0 "register_operand" "=r,r")
1320 6 "cris_orthogonal_operator"
1321 [(match_operand:BWD 1 "register_operand" "0,0")
1323 (mult:SI (match_operand:SI 2 "register_operand" "r,r")
1324 (match_operand:SI 3 "const_int_operand" "n,n"))
1325 (match_operand:SI 4 "register_operand" "r,r")))]))
1326 (set (match_operand:SI 5 "register_operand" "=*4,r")
1327 (plus:SI (mult:SI (match_dup 2)
1330 "cris_side_effect_mode_ok (MULT, operands, 5, 4, 2, 3, 0)"
1333 %x6<m> [%5=%4+%2%T3],%0")
1335 ;; [rx=ry+i] ([%4=%2+%3])
1337 (define_insn "*op_side<mode>"
1338 [(set (match_operand:BWD 0 "register_operand" "=r,r,r,r,r")
1340 5 "cris_orthogonal_operator"
1341 [(match_operand:BWD 1 "register_operand" "0,0,0,0,0")
1343 (match_operand:SI 2 "cris_bdap_operand" "%r,r,r,R,R")
1344 (match_operand:SI 3 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")))]))
1345 (set (match_operand:SI 4 "register_operand" "=*2,r,r,*3,r")
1346 (plus:SI (match_dup 2)
1348 "cris_side_effect_mode_ok (PLUS, operands, 4, 2, 3, -1, 0)"
1350 if ((which_alternative == 0 || which_alternative == 3)
1351 && (GET_CODE (operands[3]) != CONST_INT
1352 || INTVAL (operands[3]) > 127
1353 || INTVAL (operands[3]) < -128
1354 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'N')
1355 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'J')))
1357 if (which_alternative == 4)
1358 return "%x5.%s0 [%4=%3%S2],%0";
1359 return "%x5<m> [%4=%2%S3],%0";
1362 ;; To match all cases for commutative operations we may have to have the
1363 ;; following pattern for add, or & and. I do not know really, but it does
1364 ;; not break anything.
1366 ;; FIXME: This really ought to be checked.
1368 ;; op.S [rx=ry+I],rz;
1372 (define_insn "*op_swap_side<mode>_biap"
1373 [(set (match_operand:BWD 0 "register_operand" "=r,r")
1375 6 "cris_commutative_orth_op"
1377 (mult:SI (match_operand:SI 2 "register_operand" "r,r")
1378 (match_operand:SI 3 "const_int_operand" "n,n"))
1379 (match_operand:SI 4 "register_operand" "r,r")))
1380 (match_operand:BWD 1 "register_operand" "0,0")]))
1381 (set (match_operand:SI 5 "register_operand" "=*4,r")
1382 (plus:SI (mult:SI (match_dup 2)
1385 "cris_side_effect_mode_ok (MULT, operands, 5, 4, 2, 3, 0)"
1388 %x6<m> [%5=%4+%2%T3],%0")
1390 ;; [rx=ry+i] ([%4=%2+%3])
1391 ;; FIXME: These could have anonymous mode for operand 0.
1395 (define_insn "*op_swap_side<mode>"
1396 [(set (match_operand:BWD 0 "register_operand" "=r,r,r,r,r")
1398 5 "cris_commutative_orth_op"
1400 (plus:SI (match_operand:SI 2 "cris_bdap_operand" "%r,r,r,R,R")
1401 (match_operand:SI 3 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")))
1402 (match_operand:BWD 1 "register_operand" "0,0,0,0,0")]))
1403 (set (match_operand:SI 4 "register_operand" "=*2,r,r,*3,r")
1404 (plus:SI (match_dup 2)
1406 "cris_side_effect_mode_ok (PLUS, operands, 4, 2, 3, -1, 0)"
1408 if ((which_alternative == 0 || which_alternative == 3)
1409 && (GET_CODE (operands[3]) != CONST_INT
1410 || INTVAL (operands[3]) > 127
1411 || INTVAL (operands[3]) < -128
1412 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'N')
1413 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'J')))
1415 if (which_alternative == 4)
1416 return "%x5<m> [%4=%3%S2],%0";
1417 return "%x5<m> [%4=%2%S3],%0";
1420 ;; Add operations, standard names.
1422 ;; Note that for the 'P' constraint, the high part can be -1 or 0. We
1423 ;; output the insn through the 'A' output modifier as "adds.w" and "addq",
1425 (define_insn "adddi3"
1426 [(set (match_operand:DI 0 "register_operand" "=r,r,r,&r,&r")
1427 (plus:DI (match_operand:DI 1 "register_operand" "%0,0,0,0,r")
1428 (match_operand:DI 2 "general_operand" "J,N,P,g,!To")))]
1431 addq %2,%M0\;ax\;addq 0,%H0
1432 subq %n2,%M0\;ax\;subq 0,%H0
1433 add%e2.%z2 %2,%M0\;ax\;%A2 %H2,%H0
1434 add.d %M2,%M0\;ax\;add.d %H2,%H0
1435 add.d %M2,%M1,%M0\;ax\;add.d %H2,%H1,%H0")
1437 (define_insn "addsi3"
1438 [(set (match_operand:SI 0 "register_operand" "=r,r, r,r,r,r, r,r, r")
1440 (match_operand:SI 1 "register_operand" "%0,0, 0,0,0,0, 0,r, r")
1441 (match_operand:SI 2 "general_operand" "r,Q>,J,N,n,!S,g,!To,0")))]
1443 ;; The last constraint is due to that after reload, the '%' is not
1444 ;; honored, and canonicalization doesn't care about keeping the same
1445 ;; register as in destination. This will happen after insn splitting.
1446 ;; gcc <= 2.7.2. FIXME: Check for gcc-2.9x
1450 switch (which_alternative)
1454 return "add.d %2,%0";
1456 return "addq %2,%0";
1458 return "subq %n2,%0";
1460 /* 'Known value', but not in -63..63.
1461 Check if addu/subu may be used. */
1462 if (INTVAL (operands[2]) > 0)
1464 if (INTVAL (operands[2]) < 256)
1465 return "addu.b %2,%0";
1466 if (INTVAL (operands[2]) < 65536)
1467 return "addu.w %2,%0";
1471 if (INTVAL (operands[2]) >= -255)
1472 return "subu.b %n2,%0";
1473 if (INTVAL (operands[2]) >= -65535)
1474 return "subu.w %n2,%0";
1476 return "add.d %2,%0";
1479 rtx tem = operands[2];
1480 gcc_assert (GET_CODE (tem) == CONST);
1481 tem = XEXP (tem, 0);
1482 if (GET_CODE (tem) == PLUS
1483 && GET_CODE (XEXP (tem, 0)) == UNSPEC
1484 && XINT (XEXP (tem, 0), 1) == CRIS_UNSPEC_GOTREL
1485 && GET_CODE (XEXP (tem, 1)) == CONST_INT)
1486 tem = XEXP (tem, 0);
1487 gcc_assert (GET_CODE (tem) == UNSPEC);
1488 switch (XINT (tem, 1))
1490 case CRIS_UNSPEC_GOTREAD:
1491 case CRIS_UNSPEC_PLTGOTREAD:
1492 /* Using sign-extend mostly to be consistent with the
1493 indexed addressing mode. */
1495 return "adds.w %2,%0";
1497 case CRIS_UNSPEC_PLT:
1498 case CRIS_UNSPEC_GOTREL:
1499 return "add.d %2,%0";
1505 return "add.d %2,%0";
1507 return "add.d %2,%1,%0";
1509 return "add.d %1,%0";
1511 return "BOGUS addsi %2+%1 to %0";
1514 [(set_attr "slottable" "yes,yes,yes,yes,no,no,no,no,yes")])
1516 (define_insn "addhi3"
1517 [(set (match_operand:HI 0 "register_operand" "=r,r, r,r,r,r")
1518 (plus:HI (match_operand:HI 1 "register_operand" "%0,0, 0,0,0,r")
1519 (match_operand:HI 2 "general_operand" "r,Q>,J,N,g,!To")))]
1528 [(set_attr "slottable" "yes,yes,yes,yes,no,no")
1529 (set_attr "cc" "normal,normal,clobber,clobber,normal,normal")])
1531 (define_insn "addqi3"
1532 [(set (match_operand:QI 0 "register_operand" "=r,r, r,r,r,r,r")
1533 (plus:QI (match_operand:QI 1 "register_operand" "%0,0, 0,0,0,0,r")
1534 (match_operand:QI 2 "general_operand" "r,Q>,J,N,O,g,!To")))]
1544 [(set_attr "slottable" "yes,yes,yes,yes,yes,no,no")
1545 (set_attr "cc" "normal,normal,clobber,clobber,clobber,normal,normal")])
1549 ;; Note that because of insn canonicalization these will *seldom* but
1550 ;; rarely be used with a known constant as an operand.
1552 ;; Note that for the 'P' constraint, the high part can be -1 or 0. We
1553 ;; output the insn through the 'D' output modifier as "subs.w" and "subq",
1555 (define_insn "subdi3"
1556 [(set (match_operand:DI 0 "register_operand" "=r,r,r,&r,&r")
1557 (minus:DI (match_operand:DI 1 "register_operand" "0,0,0,0,r")
1558 (match_operand:DI 2 "general_operand" "J,N,P,g,!To")))]
1561 subq %2,%M0\;ax\;subq 0,%H0
1562 addq %n2,%M0\;ax\;addq 0,%H0
1563 sub%e2.%z2 %2,%M0\;ax\;%D2 %H2,%H0
1564 sub.d %M2,%M0\;ax\;sub.d %H2,%H0
1565 sub.d %M2,%M1,%M0\;ax\;sub.d %H2,%H1,%H0")
1567 (define_insn "subsi3"
1568 [(set (match_operand:SI 0 "register_operand" "=r,r, r,r,r,r,r,r")
1570 (match_operand:SI 1 "register_operand" "0,0, 0,0,0,0,0,r")
1571 (match_operand:SI 2 "general_operand" "r,Q>,J,N,P,n,g,!To")))]
1574 ;; This does not do the optimal: "addu.w 65535,r0" when %2 is negative.
1575 ;; But then again, %2 should not be negative.
1586 [(set_attr "slottable" "yes,yes,yes,yes,no,no,no,no")])
1588 (define_insn "sub<mode>3"
1589 [(set (match_operand:BW 0 "register_operand" "=r,r, r,r,r,r")
1590 (minus:BW (match_operand:BW 1 "register_operand" "0,0, 0,0,0,r")
1591 (match_operand:BW 2 "general_operand" "r,Q>,J,N,g,!To")))]
1600 [(set_attr "slottable" "yes,yes,yes,yes,no,no")
1601 (set_attr "cc" "normal,normal,clobber,clobber,normal,normal")])
1603 ;; CRIS has some add/sub-with-sign/zero-extend instructions.
1604 ;; Although these perform sign/zero-extension to SImode, they are
1605 ;; equally applicable for the HImode case.
1606 ;; FIXME: Check; GCC should handle the widening.
1607 ;; Note that these must be located after the normal add/sub patterns,
1608 ;; so not to get constants into any less specific operands.
1610 ;; Extend with add/sub and side-effect.
1612 ;; ADDS/SUBS/ADDU/SUBU and BOUND, which needs a check for zero_extend
1614 ;; adds/subs/addu/subu bound [rx=ry+rz.S]
1617 ;; FIXME: GCC should widen.
1619 (define_insn "*extopqihi_side_biap"
1620 [(set (match_operand:HI 0 "register_operand" "=r,r")
1622 6 "cris_additive_operand_extend_operator"
1623 [(match_operand:HI 1 "register_operand" "0,0")
1625 7 "cris_extend_operator"
1627 (mult:SI (match_operand:SI 2 "register_operand" "r,r")
1628 (match_operand:SI 3 "const_int_operand" "n,n"))
1629 (match_operand:SI 4 "register_operand" "r,r")))])]))
1630 (set (match_operand:SI 5 "register_operand" "=*4,r")
1631 (plus:SI (mult:SI (match_dup 2)
1634 "cris_side_effect_mode_ok (MULT, operands, 5, 4, 2, 3, 0)"
1637 %x6%e7.%m7 [%5=%4+%2%T3],%0")
1639 (define_insn "*extop<mode>si_side_biap"
1640 [(set (match_operand:SI 0 "register_operand" "=r,r")
1642 6 "cris_operand_extend_operator"
1643 [(match_operand:SI 1 "register_operand" "0,0")
1645 7 "cris_extend_operator"
1647 (mult:SI (match_operand:SI 2 "register_operand" "r,r")
1648 (match_operand:SI 3 "const_int_operand" "n,n"))
1649 (match_operand:SI 4 "register_operand" "r,r")))])]))
1650 (set (match_operand:SI 5 "register_operand" "=*4,r")
1651 (plus:SI (mult:SI (match_dup 2)
1654 "(GET_CODE (operands[6]) != UMIN || GET_CODE (operands[7]) == ZERO_EXTEND)
1655 && cris_side_effect_mode_ok (MULT, operands, 5, 4, 2, 3, 0)"
1658 %x6%e7<m> [%5=%4+%2%T3],%0")
1665 (define_insn "*extopqihi_side"
1666 [(set (match_operand:HI 0 "register_operand" "=r,r,r,r,r")
1668 5 "cris_additive_operand_extend_operator"
1669 [(match_operand:HI 1 "register_operand" "0,0,0,0,0")
1671 6 "cris_extend_operator"
1673 (plus:SI (match_operand:SI 2 "cris_bdap_operand" "%r,r,r,R,R")
1674 (match_operand:SI 3 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")
1676 (set (match_operand:SI 4 "register_operand" "=*2,r,r,*3,r")
1677 (plus:SI (match_dup 2)
1679 "cris_side_effect_mode_ok (PLUS, operands, 4, 2, 3, -1, 0)"
1681 if ((which_alternative == 0 || which_alternative == 3)
1682 && (GET_CODE (operands[3]) != CONST_INT
1683 || INTVAL (operands[3]) > 127
1684 || INTVAL (operands[3]) < -128
1685 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'N')
1686 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'J')))
1688 if (which_alternative == 4)
1689 return "%x5%E6.%m6 [%4=%3%S2],%0";
1690 return "%x5%E6.%m6 [%4=%2%S3],%0";
1693 (define_insn "*extop<mode>si_side"
1694 [(set (match_operand:SI 0 "register_operand" "=r,r,r,r,r")
1696 5 "cris_operand_extend_operator"
1697 [(match_operand:SI 1 "register_operand" "0,0,0,0,0")
1699 6 "cris_extend_operator"
1701 (plus:SI (match_operand:SI 2 "cris_bdap_operand" "%r,r,r,R,R")
1702 (match_operand:SI 3 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")
1704 (set (match_operand:SI 4 "register_operand" "=*2,r,r,*3,r")
1705 (plus:SI (match_dup 2)
1707 "(GET_CODE (operands[5]) != UMIN || GET_CODE (operands[6]) == ZERO_EXTEND)
1708 && cris_side_effect_mode_ok (PLUS, operands, 4, 2, 3, -1, 0)"
1710 if ((which_alternative == 0 || which_alternative == 3)
1711 && (GET_CODE (operands[3]) != CONST_INT
1712 || INTVAL (operands[3]) > 127
1713 || INTVAL (operands[3]) < -128
1714 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'N')
1715 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'J')))
1717 if (which_alternative == 4)
1718 return "%x5%E6<m> [%4=%3%S2],%0";
1719 return "%x5%E6<m> [%4=%2%S3],%0";
1723 ;; As with op.S we may have to add special pattern to match commuted
1724 ;; operands to adds/addu and bound
1726 ;; adds/addu/bound [rx=ry+rz.S]
1729 ;; FIXME: GCC should widen.
1731 (define_insn "*extopqihi_swap_side_biap"
1732 [(set (match_operand:HI 0 "register_operand" "=r,r")
1735 6 "cris_extend_operator"
1737 (mult:SI (match_operand:SI 2 "register_operand" "r,r")
1738 (match_operand:SI 3 "const_int_operand" "n,n"))
1739 (match_operand:SI 4 "register_operand" "r,r")))])
1740 (match_operand:HI 1 "register_operand" "0,0")))
1741 (set (match_operand:SI 5 "register_operand" "=*4,r")
1742 (plus:SI (mult:SI (match_dup 2)
1745 "cris_side_effect_mode_ok (MULT, operands, 5, 4, 2, 3, 0)"
1748 add%e6.b [%5=%4+%2%T3],%0")
1750 (define_insn "*extop<mode>si_swap_side_biap"
1751 [(set (match_operand:SI 0 "register_operand" "=r,r")
1753 7 "cris_plus_or_bound_operator"
1755 6 "cris_extend_operator"
1757 (mult:SI (match_operand:SI 2 "register_operand" "r,r")
1758 (match_operand:SI 3 "const_int_operand" "n,n"))
1759 (match_operand:SI 4 "register_operand" "r,r")))])
1760 (match_operand:SI 1 "register_operand" "0,0")]))
1761 (set (match_operand:SI 5 "register_operand" "=*4,r")
1762 (plus:SI (mult:SI (match_dup 2)
1765 "(GET_CODE (operands[7]) != UMIN || GET_CODE (operands[6]) == ZERO_EXTEND)
1766 && cris_side_effect_mode_ok (MULT, operands, 5, 4, 2, 3, 0)"
1769 %x7%E6<m> [%5=%4+%2%T3],%0")
1772 ;; FIXME: GCC should widen.
1776 (define_insn "*extopqihi_swap_side"
1777 [(set (match_operand:HI 0 "register_operand" "=r,r,r,r,r")
1780 5 "cris_extend_operator"
1782 (match_operand:SI 2 "cris_bdap_operand" "%r,r,r,R,R")
1783 (match_operand:SI 3 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")))])
1784 (match_operand:HI 1 "register_operand" "0,0,0,0,0")))
1785 (set (match_operand:SI 4 "register_operand" "=*2,r,r,*3,r")
1786 (plus:SI (match_dup 2)
1788 "cris_side_effect_mode_ok (PLUS, operands, 4, 2, 3, -1, 0)"
1790 if ((which_alternative == 0 || which_alternative == 3)
1791 && (GET_CODE (operands[3]) != CONST_INT
1792 || INTVAL (operands[3]) > 127
1793 || INTVAL (operands[3]) < -128
1794 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'N')
1795 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'J')))
1797 if (which_alternative == 4)
1798 return "add%e5.b [%4=%3%S2],%0";
1799 return "add%e5.b [%4=%2%S3],%0";
1802 (define_insn "*extop<mode>si_swap_side"
1803 [(set (match_operand:SI 0 "register_operand" "=r,r,r,r,r")
1805 6 "cris_plus_or_bound_operator"
1807 5 "cris_extend_operator"
1809 (match_operand:SI 2 "cris_bdap_operand" "%r,r,r,R,R")
1810 (match_operand:SI 3 "cris_bdap_operand" "r>Rn,r,>Rn,r,r")))])
1811 (match_operand:SI 1 "register_operand" "0,0,0,0,0")]))
1812 (set (match_operand:SI 4 "register_operand" "=*2,r,r,*3,r")
1813 (plus:SI (match_dup 2)
1815 "(GET_CODE (operands[6]) != UMIN || GET_CODE (operands[5]) == ZERO_EXTEND)
1816 && cris_side_effect_mode_ok (PLUS, operands, 4, 2, 3, -1, 0)"
1818 if ((which_alternative == 0 || which_alternative == 3)
1819 && (GET_CODE (operands[3]) != CONST_INT
1820 || INTVAL (operands[3]) > 127
1821 || INTVAL (operands[3]) < -128
1822 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'N')
1823 || CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'J')))
1825 if (which_alternative == 4)
1826 return \"%x6%E5.%m5 [%4=%3%S2],%0\";
1827 return "%x6%E5<m> [%4=%2%S3],%0";
1830 ;; Extend versions (zero/sign) of normal add/sub (no side-effects).
1833 ;; FIXME: GCC should widen.
1835 (define_insn "*extopqihi"
1836 [(set (match_operand:HI 0 "register_operand" "=r,r,r,r")
1838 3 "cris_additive_operand_extend_operator"
1839 [(match_operand:HI 1 "register_operand" "0,0,0,r")
1841 4 "cris_extend_operator"
1842 [(match_operand:QI 2 "nonimmediate_operand" "r,Q>,m,!To")])]))]
1843 "GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
1844 && (operands[1] != frame_pointer_rtx || GET_CODE (operands[3]) != PLUS)"
1849 %x3%E4.%m4 %2,%1,%0"
1850 [(set_attr "slottable" "yes,yes,no,no")
1851 (set_attr "cc" "clobber")])
1855 (define_insn "*extop<mode>si"
1856 [(set (match_operand:SI 0 "register_operand" "=r,r,r,r")
1858 3 "cris_operand_extend_operator"
1859 [(match_operand:SI 1 "register_operand" "0,0,0,r")
1861 4 "cris_extend_operator"
1862 [(match_operand:BW 2 "nonimmediate_operand" "r,Q>,m,!To")])]))]
1863 "(GET_CODE (operands[3]) != UMIN || GET_CODE (operands[4]) == ZERO_EXTEND)
1864 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
1865 && (operands[1] != frame_pointer_rtx || GET_CODE (operands[3]) != PLUS)"
1871 [(set_attr "slottable" "yes,yes,no,no")])
1874 ;; As with the side-effect patterns, may have to have swapped operands for add.
1875 ;; FIXME: *should* be redundant to gcc.
1879 (define_insn "*extopqihi_swap"
1880 [(set (match_operand:HI 0 "register_operand" "=r,r,r,r")
1883 3 "cris_extend_operator"
1884 [(match_operand:QI 2 "nonimmediate_operand" "r,Q>,m,!To")])
1885 (match_operand:HI 1 "register_operand" "0,0,0,r")))]
1886 "operands[1] != frame_pointer_rtx"
1892 [(set_attr "slottable" "yes,yes,no,no")
1893 (set_attr "cc" "clobber")])
1895 (define_insn "*extop<mode>si_swap"
1896 [(set (match_operand:SI 0 "register_operand" "=r,r,r,r")
1898 4 "cris_plus_or_bound_operator"
1900 3 "cris_extend_operator"
1901 [(match_operand:BW 2 "nonimmediate_operand" "r,Q>,m,!To")])
1902 (match_operand:SI 1 "register_operand" "0,0,0,r")]))]
1903 "(GET_CODE (operands[4]) != UMIN || GET_CODE (operands[3]) == ZERO_EXTEND)
1904 && operands[1] != frame_pointer_rtx"
1910 [(set_attr "slottable" "yes,yes,no,no")])
1912 ;; This is the special case when we use what corresponds to the
1913 ;; instruction above in "casesi". Do *not* change it to use the generic
1914 ;; pattern and "REG 15" as pc; I did that and it led to madness and
1915 ;; maintenance problems: Instead of (as imagined) recognizing and removing
1916 ;; or replacing this pattern with something simpler, other variant
1917 ;; patterns were recognized or combined, including some prefix variants
1918 ;; where the value in pc is not that of the next instruction (which means
1919 ;; this instruction actually *is* special and *should* be marked as such).
1920 ;; When switching from the "generic pattern match" approach to this simpler
1921 ;; approach, there were insignificant differences in gcc, ipps and
1922 ;; product code, somehow due to scratching reload behind the ear or
1923 ;; something. Testcase "gcc" looked .01% slower and 4 bytes bigger;
1924 ;; product code became .001% smaller but "looked better". The testcase
1925 ;; "ipps" was just different at register allocation).
1927 ;; Assumptions in the jump optimizer forces us to use IF_THEN_ELSE in this
1928 ;; pattern with the default-label as the else, with the "if" being
1929 ;; index-is-less-than the max number of cases plus one. The default-label
1930 ;; is attached to the end of the case-table at time of output.
1932 (define_insn "*casesi_adds_w"
1935 (ltu (match_operand:SI 0 "register_operand" "r")
1936 (match_operand:SI 1 "const_int_operand" "n"))
1937 (plus:SI (sign_extend:SI
1939 (plus:SI (mult:SI (match_dup 0) (const_int 2))
1942 (label_ref (match_operand 2 "" ""))))
1943 (use (label_ref (match_operand 3 "" "")))]
1945 "operands[0] != frame_pointer_rtx"
1947 "adds.w [$pc+%0.w],$pc"
1948 [(set_attr "cc" "clobber")])
1950 ;; Multiply instructions.
1952 ;; Sometimes powers of 2 (which are normally canonicalized to a
1953 ;; left-shift) appear here, as a result of address reloading.
1954 ;; As a special, for values 3 and 5, we can match with an addi, so add those.
1956 ;; FIXME: This may be unnecessary now.
1957 ;; Explicitly named for convenience of having a gen_... function.
1959 (define_insn "addi_mul"
1960 [(set (match_operand:SI 0 "register_operand" "=r")
1962 (match_operand:SI 1 "register_operand" "%0")
1963 (match_operand:SI 2 "const_int_operand" "n")))]
1964 "operands[0] != frame_pointer_rtx
1965 && operands[1] != frame_pointer_rtx
1966 && GET_CODE (operands[2]) == CONST_INT
1967 && (INTVAL (operands[2]) == 2
1968 || INTVAL (operands[2]) == 4 || INTVAL (operands[2]) == 3
1969 || INTVAL (operands[2]) == 5)"
1971 if (INTVAL (operands[2]) == 2)
1973 else if (INTVAL (operands[2]) == 4)
1975 else if (INTVAL (operands[2]) == 3)
1976 return "addi %0.w,%0";
1977 else if (INTVAL (operands[2]) == 5)
1978 return "addi %0.d,%0";
1979 return "BAD: adr_mulsi: %0=%1*%2";
1981 [(set_attr "slottable" "yes")
1982 ;; No flags are changed if this insn is "addi", but it does not seem
1983 ;; worth the trouble to distinguish that to the lslq cases.
1984 (set_attr "cc" "clobber")])
1986 ;; The addi insn as it is normally used.
1988 (define_insn "*addi"
1989 [(set (match_operand:SI 0 "register_operand" "=r")
1991 (mult:SI (match_operand:SI 2 "register_operand" "r")
1992 (match_operand:SI 3 "const_int_operand" "n"))
1993 (match_operand:SI 1 "register_operand" "0")))]
1994 "operands[0] != frame_pointer_rtx
1995 && operands[1] != frame_pointer_rtx
1996 && GET_CODE (operands[3]) == CONST_INT
1997 && (INTVAL (operands[3]) == 1
1998 || INTVAL (operands[3]) == 2 || INTVAL (operands[3]) == 4)"
2000 [(set_attr "slottable" "yes")
2001 (set_attr "cc" "none")])
2003 ;; The mstep instruction. Probably not useful by itself; it's to
2004 ;; non-linear wrt. the other insns. We used to expand to it, so at least
2007 (define_insn "mstep_shift"
2008 [(set (match_operand:SI 0 "register_operand" "=r")
2010 (lt:SI (cc0) (const_int 0))
2011 (plus:SI (ashift:SI (match_operand:SI 1 "register_operand" "0")
2013 (match_operand:SI 2 "register_operand" "r"))
2014 (ashift:SI (match_operand:SI 3 "register_operand" "0")
2018 [(set_attr "slottable" "yes")])
2020 ;; When illegitimate addresses are legitimized, sometimes gcc forgets
2021 ;; to canonicalize the multiplications.
2023 ;; FIXME: Check gcc > 2.7.2, remove and possibly fix in gcc.
2025 (define_insn "mstep_mul"
2026 [(set (match_operand:SI 0 "register_operand" "=r")
2028 (lt:SI (cc0) (const_int 0))
2029 (plus:SI (mult:SI (match_operand:SI 1 "register_operand" "0")
2031 (match_operand:SI 2 "register_operand" "r"))
2032 (mult:SI (match_operand:SI 3 "register_operand" "0")
2034 "operands[0] != frame_pointer_rtx
2035 && operands[1] != frame_pointer_rtx
2036 && operands[2] != frame_pointer_rtx
2037 && operands[3] != frame_pointer_rtx"
2039 [(set_attr "slottable" "yes")])
2041 (define_insn "<u>mul<s><mode>3"
2042 [(set (match_operand:WD 0 "register_operand" "=r")
2044 (szext:WD (match_operand:<S> 1 "register_operand" "%0"))
2045 (szext:WD (match_operand:<S> 2 "register_operand" "r"))))
2046 (clobber (match_scratch:SI 3 "=h"))]
2047 "TARGET_HAS_MUL_INSNS"
2048 "%!mul<su><mm> %2,%0"
2049 [(set (attr "slottable")
2050 (if_then_else (ne (symbol_ref "TARGET_MUL_BUG") (const_int 0))
2052 (const_string "yes")))
2053 ;; For umuls.[bwd] it's just N unusable here, but let's be safe.
2054 ;; For muls.b, this really extends to SImode, so cc should be
2055 ;; considered clobbered.
2056 ;; For muls.w, it's just N unusable here, but let's be safe.
2057 (set_attr "cc" "clobber")])
2059 ;; Note that gcc does not make use of such a thing as umulqisi3. It gets
2060 ;; confused and will erroneously use it instead of umulhisi3, failing (at
2061 ;; least) gcc.c-torture/execute/arith-rand.c at all optimization levels.
2062 ;; Inspection of optab code shows that there must be only one widening
2063 ;; multiplication per mode widened to.
2065 (define_insn "mulsi3"
2066 [(set (match_operand:SI 0 "register_operand" "=r")
2067 (mult:SI (match_operand:SI 1 "register_operand" "%0")
2068 (match_operand:SI 2 "register_operand" "r")))
2069 (clobber (match_scratch:SI 3 "=h"))]
2070 "TARGET_HAS_MUL_INSNS"
2072 [(set (attr "slottable")
2073 (if_then_else (ne (symbol_ref "TARGET_MUL_BUG") (const_int 0))
2075 (const_string "yes")))
2076 ;; Just N unusable here, but let's be safe.
2077 (set_attr "cc" "clobber")])
2079 ;; A few multiply variations.
2081 ;; When needed, we can get the high 32 bits from the overflow
2082 ;; register. We don't care to split and optimize these.
2084 ;; Note that cc0 is still valid after the move-from-overflow-register
2085 ;; insn; no special precaution need to be taken in cris_notice_update_cc.
2087 (define_insn "<u>mulsidi3"
2088 [(set (match_operand:DI 0 "register_operand" "=r")
2090 (szext:DI (match_operand:SI 1 "register_operand" "%0"))
2091 (szext:DI (match_operand:SI 2 "register_operand" "r"))))
2092 (clobber (match_scratch:SI 3 "=h"))]
2093 "TARGET_HAS_MUL_INSNS"
2094 "%!mul<su>.d %2,%M0\;move $mof,%H0")
2096 ;; These two patterns may be expressible by other means, perhaps by making
2097 ;; [u]?mulsidi3 a define_expand.
2099 ;; Due to register allocation braindamage, the clobber 1,2 alternatives
2100 ;; cause a move into the clobbered register *before* the insn, then
2101 ;; after the insn, mof is moved too, rather than the clobber assigned
2102 ;; the last mof target. This became apparent when making MOF and SRP
2103 ;; visible registers, with the necessary tweak to smulsi3_highpart.
2104 ;; Because these patterns are used in division by constants, that damage
2105 ;; is visible (ipps regression tests). Therefore the last two
2106 ;; alternatives, "helping" reload to avoid an unnecessary move, but
2107 ;; punished by force of one "?". Check code from "int d (int a) {return
2108 ;; a / 1000;}" and unsigned. FIXME: Comment above was for 3.2, revisit.
2110 (define_insn "<su>mulsi3_highpart"
2111 [(set (match_operand:SI 0 "nonimmediate_operand" "=h,h,?r,?r")
2115 (szext:DI (match_operand:SI 1 "register_operand" "r,r,0,r"))
2116 (szext:DI (match_operand:SI 2 "register_operand" "r,r,r,0")))
2118 (clobber (match_scratch:SI 3 "=1,2,h,h"))]
2119 "TARGET_HAS_MUL_INSNS"
2123 %!mul<su>.d %2,%1\;move $mof,%0
2124 %!mul<su>.d %1,%2\;move $mof,%0"
2125 [(set_attr "slottable" "yes,yes,no,no")
2126 (set_attr "cc" "clobber")])
2128 ;; Divide and modulus instructions. CRIS only has a step instruction.
2130 (define_insn "dstep_shift"
2131 [(set (match_operand:SI 0 "register_operand" "=r")
2133 (geu:SI (ashift:SI (match_operand:SI 1 "register_operand" "0")
2135 (match_operand:SI 2 "register_operand" "r"))
2136 (minus:SI (ashift:SI (match_operand:SI 3 "register_operand" "0")
2138 (match_operand:SI 4 "register_operand" "2"))
2139 (ashift:SI (match_operand:SI 5 "register_operand" "0")
2143 [(set_attr "slottable" "yes")])
2145 ;; Here's a variant with mult instead of ashift.
2147 ;; FIXME: This should be investigated. Which one matches through combination?
2149 (define_insn "dstep_mul"
2150 [(set (match_operand:SI 0 "register_operand" "=r")
2152 (geu:SI (mult:SI (match_operand:SI 1 "register_operand" "0")
2154 (match_operand:SI 2 "register_operand" "r"))
2155 (minus:SI (mult:SI (match_operand:SI 3 "register_operand" "0")
2157 (match_operand:SI 4 "register_operand" "2"))
2158 (mult:SI (match_operand:SI 5 "register_operand" "0")
2160 "operands[0] != frame_pointer_rtx
2161 && operands[1] != frame_pointer_rtx
2162 && operands[2] != frame_pointer_rtx
2163 && operands[3] != frame_pointer_rtx"
2165 [(set_attr "slottable" "yes")])
2167 ;; Logical operators.
2171 ;; There is no use in defining "anddi3", because gcc can expand this by
2172 ;; itself, and make reasonable code without interference.
2174 ;; If the first operand is memory or a register and is the same as the
2175 ;; second operand, and the third operand is -256 or -65536, we can use
2176 ;; CLEAR instead. Or, if the first operand is a register, and the third
2177 ;; operand is 255 or 65535, we can zero_extend.
2178 ;; GCC isn't smart enough to recognize these cases (yet), and they seem
2179 ;; to be common enough to be worthwhile.
2180 ;; FIXME: This should be made obsolete.
2182 (define_expand "andsi3"
2183 [(set (match_operand:SI 0 "nonimmediate_operand" "")
2184 (and:SI (match_operand:SI 1 "nonimmediate_operand" "")
2185 (match_operand:SI 2 "general_operand" "")))]
2188 if (! (GET_CODE (operands[2]) == CONST_INT
2189 && (((INTVAL (operands[2]) == -256
2190 || INTVAL (operands[2]) == -65536)
2191 && rtx_equal_p (operands[1], operands[0]))
2192 || ((INTVAL (operands[2]) == 255
2193 || INTVAL (operands[2]) == 65535)
2194 && REG_P (operands[0])))))
2196 /* Make intermediate steps if operand0 is not a register or
2197 operand1 is not a register, and hope that the reload pass will
2198 make something useful out of it. Note that the operands are
2199 *not* canonicalized. For the moment, I chicken out on this,
2200 because all or most ports do not describe 'and' with
2201 canonicalized operands, and I seem to remember magic in reload,
2202 checking that operand1 has constraint '%0', in which case
2203 operand0 and operand1 must have similar predicates.
2204 FIXME: Investigate. */
2205 rtx reg0 = REG_P (operands[0]) ? operands[0] : gen_reg_rtx (SImode);
2206 rtx reg1 = operands[1];
2210 emit_move_insn (reg0, reg1);
2214 emit_insn (gen_rtx_SET (SImode, reg0,
2215 gen_rtx_AND (SImode, reg1, operands[2])));
2217 /* Make sure we get the right *final* destination. */
2218 if (! REG_P (operands[0]))
2219 emit_move_insn (operands[0], reg0);
2225 ;; Some special cases of andsi3.
2227 (define_insn "*andsi_movu"
2228 [(set (match_operand:SI 0 "register_operand" "=r,r,r")
2229 (and:SI (match_operand:SI 1 "nonimmediate_operand" "%r,Q,To")
2230 (match_operand:SI 2 "const_int_operand" "n,n,n")))]
2231 "(INTVAL (operands[2]) == 255 || INTVAL (operands[2]) == 65535)
2232 && (GET_CODE (operands[1]) != MEM || ! MEM_VOLATILE_P (operands[1]))"
2234 [(set_attr "slottable" "yes,yes,no")])
2236 (define_insn "*andsi_clear"
2237 [(set (match_operand:SI 0 "nonimmediate_operand" "=r,r,Q,Q,To,To")
2238 (and:SI (match_operand:SI 1 "nonimmediate_operand" "%0,0,0,0,0,0")
2239 (match_operand:SI 2 "const_int_operand" "P,n,P,n,P,n")))]
2240 "(INTVAL (operands[2]) == -65536 || INTVAL (operands[2]) == -256)
2241 && (GET_CODE (operands[0]) != MEM || ! MEM_VOLATILE_P (operands[0]))"
2249 [(set_attr "slottable" "yes,yes,yes,yes,no,no")
2250 (set_attr "cc" "none")])
2252 ;; This is a catch-all pattern, taking care of everything that was not
2253 ;; matched in the insns above.
2255 ;; Sidenote: the tightening from "nonimmediate_operand" to
2256 ;; "register_operand" for operand 1 actually increased the register
2257 ;; pressure (worse code). That will hopefully change with an
2258 ;; improved reload pass.
2260 (define_insn "*expanded_andsi"
2261 [(set (match_operand:SI 0 "register_operand" "=r,r,r, r,r")
2262 (and:SI (match_operand:SI 1 "register_operand" "%0,0,0, 0,r")
2263 (match_operand:SI 2 "general_operand" "I,r,Q>,g,!To")))]
2271 [(set_attr "slottable" "yes,yes,yes,no,no")])
2273 ;; For both QI and HI we may use the quick patterns. This results in
2274 ;; useless condition codes, but that is used rarely enough for it to
2275 ;; normally be a win (could check ahead for use of cc0, but seems to be
2276 ;; more pain than win).
2278 ;; FIXME: See note for andsi3
2280 (define_expand "andhi3"
2281 [(set (match_operand:HI 0 "nonimmediate_operand" "")
2282 (and:HI (match_operand:HI 1 "nonimmediate_operand" "")
2283 (match_operand:HI 2 "general_operand" "")))]
2286 if (! (GET_CODE (operands[2]) == CONST_INT
2287 && (((INTVAL (operands[2]) == -256
2288 || INTVAL (operands[2]) == 65280)
2289 && rtx_equal_p (operands[1], operands[0]))
2290 || (INTVAL (operands[2]) == 255
2291 && REG_P (operands[0])))))
2293 /* See comment for andsi3. */
2294 rtx reg0 = REG_P (operands[0]) ? operands[0] : gen_reg_rtx (HImode);
2295 rtx reg1 = operands[1];
2299 emit_move_insn (reg0, reg1);
2303 emit_insn (gen_rtx_SET (HImode, reg0,
2304 gen_rtx_AND (HImode, reg1, operands[2])));
2306 /* Make sure we get the right destination. */
2307 if (! REG_P (operands[0]))
2308 emit_move_insn (operands[0], reg0);
2314 ;; Some fast andhi3 special cases.
2316 (define_insn "*andhi_movu"
2317 [(set (match_operand:HI 0 "register_operand" "=r,r,r")
2318 (and:HI (match_operand:HI 1 "nonimmediate_operand" "r,Q,To")
2320 "GET_CODE (operands[1]) != MEM || ! MEM_VOLATILE_P (operands[1])"
2322 [(set_attr "slottable" "yes,yes,no")])
2324 (define_insn "*andhi_clear"
2325 [(set (match_operand:HI 0 "nonimmediate_operand" "=r,Q,To")
2326 (and:HI (match_operand:HI 1 "nonimmediate_operand" "0,0,0")
2328 "GET_CODE (operands[0]) != MEM || ! MEM_VOLATILE_P (operands[0])"
2330 [(set_attr "slottable" "yes,yes,no")
2331 (set_attr "cc" "none")])
2333 ;; Catch-all andhi3 pattern.
2335 (define_insn "*expanded_andhi"
2336 [(set (match_operand:HI 0 "register_operand" "=r,r,r, r,r,r,r")
2337 (and:HI (match_operand:HI 1 "register_operand" "%0,0,0, 0,0,0,r")
2338 (match_operand:HI 2 "general_operand" "I,r,Q>,L,O,g,!To")))]
2340 ;; Sidenote: the tightening from "general_operand" to
2341 ;; "register_operand" for operand 1 actually increased the register
2342 ;; pressure (worse code). That will hopefully change with an
2343 ;; improved reload pass.
2354 [(set_attr "slottable" "yes,yes,yes,no,yes,no,no")
2355 (set_attr "cc" "clobber,normal,normal,normal,clobber,normal,normal")])
2357 ;; A strict_low_part pattern.
2359 (define_insn "*andhi_lowpart"
2360 [(set (strict_low_part
2361 (match_operand:HI 0 "register_operand" "=r,r, r,r,r,r"))
2362 (and:HI (match_operand:HI 1 "register_operand" "%0,0, 0,0,0,r")
2363 (match_operand:HI 2 "general_operand" "r,Q>,L,O,g,!To")))]
2372 [(set_attr "slottable" "yes,yes,no,yes,no,no")
2373 (set_attr "cc" "normal,normal,normal,clobber,normal,normal")])
2375 (define_insn "andqi3"
2376 [(set (match_operand:QI 0 "register_operand" "=r,r,r, r,r,r")
2377 (and:QI (match_operand:QI 1 "register_operand" "%0,0,0, 0,0,r")
2378 (match_operand:QI 2 "general_operand" "I,r,Q>,O,g,!To")))]
2387 [(set_attr "slottable" "yes,yes,yes,yes,no,no")
2388 (set_attr "cc" "clobber,normal,normal,clobber,normal,normal")])
2390 (define_insn "*andqi_lowpart"
2391 [(set (strict_low_part
2392 (match_operand:QI 0 "register_operand" "=r,r, r,r,r"))
2393 (and:QI (match_operand:QI 1 "register_operand" "%0,0, 0,0,r")
2394 (match_operand:QI 2 "general_operand" "r,Q>,O,g,!To")))]
2402 [(set_attr "slottable" "yes,yes,yes,no,no")
2403 (set_attr "cc" "normal,normal,clobber,normal,normal")])
2407 ;; Same comment as anddi3 applies here - no need for such a pattern.
2409 ;; It seems there's no need to jump through hoops to get good code such as
2412 (define_insn "iorsi3"
2413 [(set (match_operand:SI 0 "register_operand" "=r,r,r, r,r,r")
2414 (ior:SI (match_operand:SI 1 "register_operand" "%0,0,0, 0,0,r")
2415 (match_operand:SI 2 "general_operand" "I, r,Q>,n,g,!To")))]
2424 [(set_attr "slottable" "yes,yes,yes,no,no,no")
2425 (set_attr "cc" "normal,normal,normal,clobber,normal,normal")])
2427 (define_insn "iorhi3"
2428 [(set (match_operand:HI 0 "register_operand" "=r,r,r, r,r,r,r")
2429 (ior:HI (match_operand:HI 1 "register_operand" "%0,0,0, 0,0,0,r")
2430 (match_operand:HI 2 "general_operand" "I,r,Q>,L,O,g,!To")))]
2440 [(set_attr "slottable" "yes,yes,yes,no,yes,no,no")
2441 (set_attr "cc" "clobber,normal,normal,normal,clobber,normal,normal")])
2443 (define_insn "iorqi3"
2444 [(set (match_operand:QI 0 "register_operand" "=r,r,r, r,r,r")
2445 (ior:QI (match_operand:QI 1 "register_operand" "%0,0,0, 0,0,r")
2446 (match_operand:QI 2 "general_operand" "I,r,Q>,O,g,!To")))]
2455 [(set_attr "slottable" "yes,yes,yes,yes,no,no")
2456 (set_attr "cc" "clobber,normal,normal,clobber,normal,normal")])
2460 ;; See comment about "anddi3" for xordi3 - no need for such a pattern.
2461 ;; FIXME: Do we really need the shorter variants?
2463 (define_insn "xorsi3"
2464 [(set (match_operand:SI 0 "register_operand" "=r")
2465 (xor:SI (match_operand:SI 1 "register_operand" "%0")
2466 (match_operand:SI 2 "register_operand" "r")))]
2469 [(set_attr "slottable" "yes")])
2471 (define_insn "xor<mode>3"
2472 [(set (match_operand:BW 0 "register_operand" "=r")
2473 (xor:BW (match_operand:BW 1 "register_operand" "%0")
2474 (match_operand:BW 2 "register_operand" "r")))]
2477 [(set_attr "slottable" "yes")
2478 (set_attr "cc" "clobber")])
2482 ;; Questionable use, here mostly as a (slightly usable) define_expand
2485 (define_expand "negsf2"
2488 (parallel [(set (match_operand:SF 0 "register_operand" "=r")
2489 (neg:SF (match_operand:SF 1
2490 "register_operand" "0")))
2491 (use (match_dup 2))])]
2494 operands[2] = gen_reg_rtx (SImode);
2495 operands[3] = GEN_INT (1 << 31);
2498 (define_insn "*expanded_negsf2"
2499 [(set (match_operand:SF 0 "register_operand" "=r")
2500 (neg:SF (match_operand:SF 1 "register_operand" "0")))
2501 (use (match_operand:SI 2 "register_operand" "r"))]
2504 [(set_attr "slottable" "yes")])
2506 ;; No "negdi2" although we could make one up that may be faster than
2507 ;; the one in libgcc.
2509 (define_insn "neg<mode>2"
2510 [(set (match_operand:BWD 0 "register_operand" "=r")
2511 (neg:BWD (match_operand:BWD 1 "register_operand" "r")))]
2514 [(set_attr "slottable" "yes")])
2518 ;; See comment on anddi3 - no need for a DImode pattern.
2519 ;; See also xor comment.
2521 (define_insn "one_cmplsi2"
2522 [(set (match_operand:SI 0 "register_operand" "=r")
2523 (not:SI (match_operand:SI 1 "register_operand" "0")))]
2526 [(set_attr "slottable" "yes")])
2528 (define_insn "one_cmpl<mode>2"
2529 [(set (match_operand:BW 0 "register_operand" "=r")
2530 (not:BW (match_operand:BW 1 "register_operand" "0")))]
2533 [(set_attr "slottable" "yes")
2534 (set_attr "cc" "clobber")])
2536 ;; Arithmetic/Logical shift right (and SI left).
2538 (define_insn "<shlr>si3"
2539 [(set (match_operand:SI 0 "register_operand" "=r")
2540 (shift:SI (match_operand:SI 1 "register_operand" "0")
2541 (match_operand:SI 2 "nonmemory_operand" "Kr")))]
2544 if (REG_S_P (operands[2]))
2545 return "<slr>.d %2,%0";
2547 return "<slr>q %2,%0";
2549 [(set_attr "slottable" "yes")])
2551 ;; Since gcc gets lost, and forgets to zero-extend the source (or mask
2552 ;; the destination) when it changes shifts of lower modes into SImode,
2553 ;; it is better to make these expands an anonymous patterns instead of
2554 ;; the more correct define_insns. This occurs when gcc thinks that is
2555 ;; is better to widen to SImode and use immediate shift count.
2557 ;; FIXME: Is this legacy or still true for gcc >= 2.7.2?
2559 ;; FIXME: Can't parametrize sign_extend and zero_extend (before
2560 ;; mentioning "shiftrt"), so we need two patterns.
2561 (define_expand "ashr<mode>3"
2563 (sign_extend:SI (match_operand:BW 1 "nonimmediate_operand" "")))
2565 (zero_extend:SI (match_operand:BW 2 "nonimmediate_operand" "")))
2566 (set (match_dup 5) (ashiftrt:SI (match_dup 3) (match_dup 4)))
2567 (set (match_operand:BW 0 "general_operand" "")
2568 (subreg:BW (match_dup 5) 0))]
2573 for (i = 3; i < 6; i++)
2574 operands[i] = gen_reg_rtx (SImode);
2577 (define_expand "lshr<mode>3"
2579 (zero_extend:SI (match_operand:BW 1 "nonimmediate_operand" "")))
2581 (zero_extend:SI (match_operand:BW 2 "nonimmediate_operand" "")))
2582 (set (match_dup 5) (lshiftrt:SI (match_dup 3) (match_dup 4)))
2583 (set (match_operand:BW 0 "general_operand" "")
2584 (subreg:BW (match_dup 5) 0))]
2589 for (i = 3; i < 6; i++)
2590 operands[i] = gen_reg_rtx (SImode);
2593 (define_insn "*expanded_<shlr><mode>"
2594 [(set (match_operand:BW 0 "register_operand" "=r")
2595 (shiftrt:BW (match_operand:BW 1 "register_operand" "0")
2596 (match_operand:BW 2 "register_operand" "r")))]
2599 [(set_attr "slottable" "yes")])
2601 (define_insn "*<shlr><mode>_lowpart"
2602 [(set (strict_low_part (match_operand:BW 0 "register_operand" "+r"))
2603 (shiftrt:BW (match_dup 0)
2604 (match_operand:BW 1 "register_operand" "r")))]
2607 [(set_attr "slottable" "yes")])
2609 ;; Arithmetic/logical shift left.
2611 ;; For narrower modes than SI, we can use lslq although it makes cc
2612 ;; unusable. The win is that we do not have to reload the shift-count
2615 (define_insn "ashl<mode>3"
2616 [(set (match_operand:BW 0 "register_operand" "=r,r")
2617 (ashift:BW (match_operand:BW 1 "register_operand" "0,0")
2618 (match_operand:BW 2 "nonmemory_operand" "r,K")))]
2622 (GET_CODE (operands[2]) == CONST_INT
2623 && INTVAL (operands[2]) > <nbitsm1>)
2625 : (CONSTANT_P (operands[2])
2626 ? "lslq %2,%0" : "lsl<m> %2,%0");
2628 [(set_attr "slottable" "yes")
2629 (set_attr "cc" "normal,clobber")])
2631 ;; A strict_low_part matcher.
2633 (define_insn "*ashl<mode>_lowpart"
2634 [(set (strict_low_part (match_operand:BW 0 "register_operand" "+r"))
2635 (ashift:BW (match_dup 0)
2636 (match_operand:HI 1 "register_operand" "r")))]
2639 [(set_attr "slottable" "yes")])
2641 ;; Various strange insns that gcc likes.
2643 ;; Fortunately, it is simple to construct an abssf (although it may not
2644 ;; be very much used in practice).
2646 (define_insn "abssf2"
2647 [(set (match_operand:SF 0 "register_operand" "=r")
2648 (abs:SF (match_operand:SF 1 "register_operand" "0")))]
2650 "lslq 1,%0\;lsrq 1,%0")
2652 (define_insn "abssi2"
2653 [(set (match_operand:SI 0 "register_operand" "=r")
2654 (abs:SI (match_operand:SI 1 "register_operand" "r")))]
2657 [(set_attr "slottable" "yes")])
2659 ;; FIXME: GCC should be able to do these expansions itself.
2661 (define_expand "abs<mode>2"
2663 (sign_extend:SI (match_operand:BW 1 "general_operand" "")))
2664 (set (match_dup 3) (abs:SI (match_dup 2)))
2665 (set (match_operand:BW 0 "register_operand" "")
2666 (subreg:BW (match_dup 3) 0))]
2668 "operands[2] = gen_reg_rtx (SImode); operands[3] = gen_reg_rtx (SImode);")
2670 ;; Bound-insn. Defined to be the same as an unsigned minimum, which is an
2671 ;; operation supported by gcc. Used in casesi, but used now and then in
2674 (define_insn "uminsi3"
2675 [(set (match_operand:SI 0 "register_operand" "=r,r, r,r")
2676 (umin:SI (match_operand:SI 1 "register_operand" "%0,0, 0,r")
2677 (match_operand:SI 2 "general_operand" "r,Q>,g,!To")))]
2680 if (GET_CODE (operands[2]) == CONST_INT)
2682 /* Constant operands are zero-extended, so only 32-bit operands
2684 if (INTVAL (operands[2]) >= 0)
2686 if (INTVAL (operands[2]) < 256)
2687 return "bound.b %2,%0";
2689 if (INTVAL (operands[2]) < 65536)
2690 return "bound.w %2,%0";
2693 else if (which_alternative == 3)
2694 return "bound.d %2,%1,%0";
2696 return "bound.d %2,%0";
2698 [(set_attr "slottable" "yes,yes,no,no")])
2700 ;; Jump and branch insns.
2704 (label_ref (match_operand 0 "" "")))]
2707 [(set_attr "slottable" "has_slot")])
2709 ;; Testcase gcc.c-torture/compile/991213-3.c fails if we allow a constant
2710 ;; here, since the insn is not recognized as an indirect jump by
2711 ;; jmp_uses_reg_or_mem used by computed_jump_p. Perhaps it is a kludge to
2712 ;; change from general_operand to nonimmediate_operand (at least the docs
2713 ;; should be changed), but then again the pattern is called indirect_jump.
2714 (define_insn "indirect_jump"
2715 [(set (pc) (match_operand:SI 0 "nonimmediate_operand" "rm"))]
2719 ;; Return insn. Used whenever the epilogue is very simple; if it is only
2720 ;; a single ret or jump [sp+]. No allocated stack space or saved
2721 ;; registers are allowed.
2722 ;; Note that for this pattern, although named, it is ok to check the
2723 ;; context of the insn in the test, not only compiler switches.
2725 (define_expand "return"
2727 "cris_simple_epilogue ()"
2728 "cris_expand_return (cris_return_address_on_stack ()); DONE;")
2730 (define_insn "*return_expanded"
2734 return cris_return_address_on_stack_for_return ()
2735 ? "jump [$sp+]" : "ret%#";
2737 [(set (attr "slottable")
2740 "(cris_return_address_on_stack_for_return ())")
2743 (const_string "has_slot")))])
2745 (define_expand "prologue"
2747 "TARGET_PROLOGUE_EPILOGUE"
2748 "cris_expand_prologue (); DONE;")
2750 ;; Note that the (return) from the expander itself is always the last
2751 ;; insn in the epilogue.
2752 (define_expand "epilogue"
2754 "TARGET_PROLOGUE_EPILOGUE"
2755 "cris_expand_epilogue (); DONE;")
2757 ;; Conditional branches.
2759 ;; We suffer from the same overflow-bit-gets-in-the-way problem as
2760 ;; e.g. m68k, so we have to check if overflow bit is set on all "signed"
2763 (define_insn "b<ncond:code>"
2765 (if_then_else (ncond (cc0)
2767 (label_ref (match_operand 0 "" ""))
2771 [(set_attr "slottable" "has_slot")])
2773 (define_insn "b<ocond:code>"
2775 (if_then_else (ocond (cc0)
2777 (label_ref (match_operand 0 "" ""))
2782 (cc_prev_status.flags & CC_NO_OVERFLOW)
2783 ? 0 : "b<CC> %l0%#";
2785 [(set_attr "slottable" "has_slot")])
2787 (define_insn "b<rcond:code>"
2789 (if_then_else (rcond (cc0)
2791 (label_ref (match_operand 0 "" ""))
2796 (cc_prev_status.flags & CC_NO_OVERFLOW)
2797 ? "b<oCC> %l0%#" : "b<CC> %l0%#";
2799 [(set_attr "slottable" "has_slot")])
2801 ;; Reversed anonymous patterns to the ones above, as mandated.
2803 (define_insn "*b<ncond:code>_reversed"
2805 (if_then_else (ncond (cc0)
2808 (label_ref (match_operand 0 "" ""))))]
2811 [(set_attr "slottable" "has_slot")])
2813 (define_insn "*b<ocond:code>_reversed"
2815 (if_then_else (ocond (cc0)
2818 (label_ref (match_operand 0 "" ""))))]
2822 (cc_prev_status.flags & CC_NO_OVERFLOW)
2823 ? 0 : "b<rCC> %l0%#";
2825 [(set_attr "slottable" "has_slot")])
2827 (define_insn "*b<rcond:code>_reversed"
2829 (if_then_else (rcond (cc0)
2832 (label_ref (match_operand 0 "" ""))))]
2836 (cc_prev_status.flags & CC_NO_OVERFLOW)
2837 ? "b<roCC> %l0%#" : "b<rCC> %l0%#";
2839 [(set_attr "slottable" "has_slot")])
2841 ;; Set on condition: sCC.
2843 ;; Like bCC, we have to check the overflow bit for
2844 ;; signed conditions.
2846 (define_insn "s<ncond:code>"
2847 [(set (match_operand:SI 0 "register_operand" "=r")
2848 (ncond:SI (cc0) (const_int 0)))]
2851 [(set_attr "slottable" "yes")
2852 (set_attr "cc" "none")])
2854 (define_insn "s<rcond:code>"
2855 [(set (match_operand:SI 0 "register_operand" "=r")
2856 (rcond:SI (cc0) (const_int 0)))]
2860 (cc_prev_status.flags & CC_NO_OVERFLOW)
2861 ? "s<oCC> %0" : "s<CC> %0";
2863 [(set_attr "slottable" "yes")
2864 (set_attr "cc" "none")])
2866 (define_insn "s<ocond:code>"
2867 [(set (match_operand:SI 0 "register_operand" "=r")
2868 (ocond:SI (cc0) (const_int 0)))]
2872 (cc_prev_status.flags & CC_NO_OVERFLOW)
2875 [(set_attr "slottable" "yes")
2876 (set_attr "cc" "none")])
2880 ;; We need to make these patterns "expand", since the real operand is
2881 ;; hidden in a (mem:QI ) inside operand[0] (call_value: operand[1]),
2882 ;; and cannot be checked if it were a "normal" pattern.
2883 ;; Note that "call" and "call_value" are *always* called with a
2884 ;; mem-operand for operand 0 and 1 respective. What happens for combined
2885 ;; instructions is a different issue.
2887 (define_expand "call"
2888 [(parallel [(call (match_operand:QI 0 "cris_mem_call_operand" "")
2889 (match_operand 1 "general_operand" ""))
2890 (clobber (reg:SI CRIS_SRP_REGNUM))])]
2893 gcc_assert (GET_CODE (operands[0]) == MEM);
2895 cris_expand_pic_call_address (&operands[0]);
2898 ;; Accept *anything* as operand 1. Accept operands for operand 0 in
2899 ;; order of preference.
2901 (define_insn "*expanded_call"
2902 [(call (mem:QI (match_operand:SI
2903 0 "cris_general_operand_or_plt_symbol" "r,Q>,g"))
2904 (match_operand 1 "" ""))
2905 (clobber (reg:SI CRIS_SRP_REGNUM))]
2909 ;; Parallel when calculating and reusing address of indirect pointer
2910 ;; with simple offset. (Makes most sense with PIC.) It looks a bit
2911 ;; wrong not to have the clobber last, but that's the way combine
2912 ;; generates it (except it doesn' look into the *inner* mem, so this
2913 ;; just matches a peephole2). FIXME: investigate that.
2914 (define_insn "*expanded_call_side"
2917 (plus:SI (match_operand:SI 0 "cris_bdap_operand" "%r, r,r")
2918 (match_operand:SI 1 "cris_bdap_operand" "r>Rn,r,>Rn"))))
2919 (match_operand 2 "" ""))
2920 (clobber (reg:SI CRIS_SRP_REGNUM))
2921 (set (match_operand:SI 3 "register_operand" "=*0,r,r")
2922 (plus:SI (match_dup 0)
2924 "! TARGET_AVOID_GOTPLT"
2927 (define_expand "call_value"
2928 [(parallel [(set (match_operand 0 "" "")
2929 (call (match_operand:QI 1 "cris_mem_call_operand" "")
2930 (match_operand 2 "" "")))
2931 (clobber (reg:SI CRIS_SRP_REGNUM))])]
2934 gcc_assert (GET_CODE (operands[1]) == MEM);
2936 cris_expand_pic_call_address (&operands[1]);
2939 ;; Accept *anything* as operand 2. The validity other than "general" of
2940 ;; operand 0 will be checked elsewhere. Accept operands for operand 1 in
2941 ;; order of preference (Q includes r, but r is shorter, faster).
2942 ;; We also accept a PLT symbol. We output it as [rPIC+sym:GOTPLT] rather
2943 ;; than requiring getting rPIC + sym:PLT into a register.
2945 (define_insn "*expanded_call_value"
2946 [(set (match_operand 0 "nonimmediate_operand" "=g,g,g")
2947 (call (mem:QI (match_operand:SI
2948 1 "cris_general_operand_or_plt_symbol" "r,Q>,g"))
2949 (match_operand 2 "" "")))
2950 (clobber (reg:SI CRIS_SRP_REGNUM))]
2953 [(set_attr "cc" "clobber")])
2955 ;; See similar call special-case.
2956 (define_insn "*expanded_call_value_side"
2957 [(set (match_operand 0 "nonimmediate_operand" "=g,g,g")
2961 (plus:SI (match_operand:SI 1 "cris_bdap_operand" "%r, r,r")
2962 (match_operand:SI 2 "cris_bdap_operand" "r>Rn,r,>Rn"))))
2963 (match_operand 3 "" "")))
2964 (clobber (reg:SI CRIS_SRP_REGNUM))
2965 (set (match_operand:SI 4 "register_operand" "=*1,r,r")
2966 (plus:SI (match_dup 1)
2968 "! TARGET_AVOID_GOTPLT"
2970 [(set_attr "cc" "clobber")])
2972 ;; Used in debugging. No use for the direct pattern; unfilled
2973 ;; delayed-branches are taken care of by other means.
2979 [(set_attr "cc" "none")])
2981 ;; We need to stop accesses to the stack after the memory is
2982 ;; deallocated. Unfortunately, reorg doesn't look at naked clobbers,
2983 ;; e.g. (insn ... (clobber (mem:BLK (stack_pointer_rtx)))) and we don't
2984 ;; want to use a naked (unspec_volatile) as that would stop any
2985 ;; scheduling in the epilogue. Hence we model it as a "real" insn that
2986 ;; sets the memory in an unspecified manner. FIXME: Unfortunately it
2987 ;; still has the effect of an unspec_volatile.
2988 (define_insn "cris_frame_deallocated_barrier"
2989 [(set (mem:BLK (reg:SI CRIS_SP_REGNUM))
2990 (unspec:BLK [(const_int 0)] CRIS_UNSPEC_FRAME_DEALLOC))]
2993 [(set_attr "length" "0")])
2995 ;; We expand on casesi so we can use "bound" and "add offset fetched from
2996 ;; a table to pc" (adds.w [pc+%0.w],pc).
2998 ;; Note: if you change the "parallel" (or add anything after it) in
2999 ;; this expansion, you must change the macro ASM_OUTPUT_CASE_END
3000 ;; accordingly, to add the default case at the end of the jump-table.
3002 (define_expand "casesi"
3003 [(set (match_dup 5) (match_operand:SI 0 "general_operand" ""))
3005 (minus:SI (match_dup 5)
3006 (match_operand:SI 1 "const_int_operand" "n")))
3008 (umin:SI (match_dup 6)
3009 (match_operand:SI 2 "const_int_operand" "n")))
3013 (ltu (match_dup 7) (match_dup 2))
3014 (plus:SI (sign_extend:SI
3016 (plus:SI (mult:SI (match_dup 7) (const_int 2))
3019 (label_ref (match_operand 4 "" ""))))
3020 (use (label_ref (match_operand 3 "" "")))])]
3023 operands[2] = plus_constant (operands[2], 1);
3024 operands[5] = gen_reg_rtx (SImode);
3025 operands[6] = gen_reg_rtx (SImode);
3026 operands[7] = gen_reg_rtx (SImode);
3029 ;; Split-patterns. Some of them have modes unspecified. This
3030 ;; should always be ok; if for no other reason sparc.md has it as
3033 ;; When register_operand is specified for an operand, we can get a
3034 ;; subreg as well (Axis-990331), so don't just assume that REG_P is true
3035 ;; for a register_operand and that REGNO can be used as is. It is best to
3036 ;; guard with REG_P, unless it is worth it to adjust for the subreg case.
3038 ;; op [rx + 0],ry,rz
3039 ;; The index to rx is optimized into zero, and gone.
3041 ;; First, recognize bound [rx],ry,rz; where [rx] is zero-extended,
3042 ;; and add/sub [rx],ry,rz, with zero or sign-extend on [rx].
3046 ;; Lose if rz=ry or rx=rz.
3047 ;; Call this op-extend-split
3050 [(set (match_operand 0 "register_operand" "")
3052 4 "cris_operand_extend_operator"
3053 [(match_operand 1 "register_operand" "")
3055 3 "cris_extend_operator"
3056 [(match_operand 2 "memory_operand" "")])]))]
3057 "REG_P (operands[0])
3058 && REG_P (operands[1])
3059 && REGNO (operands[1]) != REGNO (operands[0])
3060 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3061 && REG_P (XEXP (operands[2], 0))
3062 && REGNO (XEXP (operands[2], 0)) != REGNO (operands[0])"
3068 (match_op_dup 3 [(match_dup 2)])]))]
3071 ;; As op-extend-split, but recognize and split op [rz],ry,rz into
3074 ;; Do this for plus or bound only, being commutative operations, since we
3075 ;; have swapped the operands.
3076 ;; Call this op-extend-split-rx=rz
3079 [(set (match_operand 0 "register_operand" "")
3081 4 "cris_plus_or_bound_operator"
3082 [(match_operand 1 "register_operand" "")
3084 3 "cris_extend_operator"
3085 [(match_operand 2 "memory_operand" "")])]))]
3086 "REG_P (operands[0])
3087 && REG_P (operands[1])
3088 && REGNO (operands[1]) != REGNO (operands[0])
3089 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3090 && REG_P (XEXP (operands[2], 0))
3091 && REGNO (XEXP (operands[2], 0)) == REGNO (operands[0])"
3093 (match_op_dup 3 [(match_dup 2)]))
3100 ;; As the op-extend-split, but swapped operands, and only for
3101 ;; plus or bound, being the commutative extend-operators. FIXME: Why is
3102 ;; this needed? Is it?
3103 ;; Call this op-extend-split-swapped
3106 [(set (match_operand 0 "register_operand" "")
3108 4 "cris_plus_or_bound_operator"
3110 3 "cris_extend_operator"
3111 [(match_operand 2 "memory_operand" "")])
3112 (match_operand 1 "register_operand" "")]))]
3113 "REG_P (operands[0])
3114 && REG_P (operands[1])
3115 && REGNO (operands[1]) != REGNO (operands[0])
3116 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3117 && REG_P (XEXP (operands[2], 0))
3118 && REGNO (XEXP (operands[2], 0)) != REGNO (operands[0])"
3124 (match_op_dup 3 [(match_dup 2)])]))]
3127 ;; As op-extend-split-rx=rz, but swapped operands, only for plus or
3128 ;; bound. Call this op-extend-split-swapped-rx=rz.
3131 [(set (match_operand 0 "register_operand" "")
3133 4 "cris_plus_or_bound_operator"
3135 3 "cris_extend_operator"
3136 [(match_operand 2 "memory_operand" "")])
3137 (match_operand 1 "register_operand" "")]))]
3138 "REG_P (operands[0])
3139 && REG_P (operands[1])
3140 && REGNO (operands[1]) != REGNO (operands[0])
3141 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3142 && REG_P (XEXP (operands[2], 0))
3143 && REGNO (XEXP (operands[2], 0)) == REGNO (operands[0])"
3145 (match_op_dup 3 [(match_dup 2)]))
3152 ;; As op-extend-split, but the mem operand is not extended.
3154 ;; op [rx],ry,rz changed into
3157 ;; lose if ry=rz or rx=rz
3158 ;; Call this op-extend.
3161 [(set (match_operand 0 "register_operand" "")
3163 3 "cris_orthogonal_operator"
3164 [(match_operand 1 "register_operand" "")
3165 (match_operand 2 "memory_operand" "")]))]
3166 "REG_P (operands[0])
3167 && REG_P (operands[1])
3168 && REGNO (operands[1]) != REGNO (operands[0])
3169 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3170 && REG_P (XEXP (operands[2], 0))
3171 && REGNO (XEXP (operands[2], 0)) != REGNO (operands[0])"
3180 ;; As op-extend-split-rx=rz, non-extended.
3181 ;; Call this op-split-rx=rz
3184 [(set (match_operand 0 "register_operand" "")
3186 3 "cris_commutative_orth_op"
3187 [(match_operand 2 "memory_operand" "")
3188 (match_operand 1 "register_operand" "")]))]
3189 "REG_P (operands[0])
3190 && REG_P (operands[1])
3191 && REGNO (operands[1]) != REGNO (operands[0])
3192 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3193 && REG_P (XEXP (operands[2], 0))
3194 && REGNO (XEXP (operands[2], 0)) != REGNO (operands[0])"
3203 ;; As op-extend-split-swapped, nonextended.
3204 ;; Call this op-split-swapped.
3207 [(set (match_operand 0 "register_operand" "")
3209 3 "cris_commutative_orth_op"
3210 [(match_operand 1 "register_operand" "")
3211 (match_operand 2 "memory_operand" "")]))]
3212 "REG_P (operands[0]) && REG_P (operands[1])
3213 && REGNO (operands[1]) != REGNO (operands[0])
3214 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3215 && REG_P (XEXP (operands[2], 0))
3216 && REGNO (XEXP (operands[2], 0)) == REGNO (operands[0])"
3225 ;; As op-extend-split-swapped-rx=rz, non-extended.
3226 ;; Call this op-split-swapped-rx=rz.
3229 [(set (match_operand 0 "register_operand" "")
3231 3 "cris_orthogonal_operator"
3232 [(match_operand 2 "memory_operand" "")
3233 (match_operand 1 "register_operand" "")]))]
3234 "REG_P (operands[0]) && REG_P (operands[1])
3235 && REGNO (operands[1]) != REGNO (operands[0])
3236 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3237 && REG_P (XEXP (operands[2], 0))
3238 && REGNO (XEXP (operands[2], 0)) == REGNO (operands[0])"
3247 ;; Splits for all cases in side-effect insns where (possibly after reload
3248 ;; and register allocation) rx and ry in [rx=ry+i] are equal.
3250 ;; move.S1 [rx=rx+rz.S2],ry
3254 [(set (match_operand 0 "register_operand" "")
3258 (mult:SI (match_operand:SI 1 "register_operand" "")
3259 (match_operand:SI 2 "const_int_operand" ""))
3260 (match_operand:SI 3 "register_operand" ""))]))
3261 (set (match_operand:SI 4 "register_operand" "")
3262 (plus:SI (mult:SI (match_dup 1)
3265 "REG_P (operands[3]) && REG_P (operands[4])
3266 && REGNO (operands[3]) == REGNO (operands[4])"
3267 [(set (match_dup 4) (plus:SI (mult:SI (match_dup 1) (match_dup 2))
3269 (set (match_dup 0) (match_dup 5))]
3270 "operands[5] = replace_equiv_address (operands[6], operands[3]);")
3272 ;; move.S1 [rx=rx+i],ry
3276 [(set (match_operand 0 "register_operand" "")
3279 [(plus:SI (match_operand:SI 1 "cris_bdap_operand" "")
3280 (match_operand:SI 2 "cris_bdap_operand" ""))]))
3281 (set (match_operand:SI 3 "register_operand" "")
3282 (plus:SI (match_dup 1)
3284 "(rtx_equal_p (operands[3], operands[1])
3285 || rtx_equal_p (operands[3], operands[2]))"
3286 [(set (match_dup 3) (plus:SI (match_dup 1) (match_dup 2)))
3287 (set (match_dup 0) (match_dup 4))]
3289 operands[4] = replace_equiv_address (operands[5], operands[3]);
3290 cris_order_for_addsi3 (operands, 1);
3293 ;; move.S1 ry,[rx=rx+rz.S2]
3297 [(set (match_operator
3300 (mult:SI (match_operand:SI 0 "register_operand" "")
3301 (match_operand:SI 1 "const_int_operand" ""))
3302 (match_operand:SI 2 "register_operand" ""))])
3303 (match_operand 3 "register_operand" ""))
3304 (set (match_operand:SI 4 "register_operand" "")
3305 (plus:SI (mult:SI (match_dup 0)
3308 "REG_P (operands[2]) && REG_P (operands[4])
3309 && REGNO (operands[4]) == REGNO (operands[2])"
3310 [(set (match_dup 4) (plus:SI (mult:SI (match_dup 0) (match_dup 1))
3312 (set (match_dup 5) (match_dup 3))]
3313 "operands[5] = replace_equiv_address (operands[6], operands[4]);")
3315 ;; move.S1 ry,[rx=rx+i]
3319 [(set (match_operator
3321 [(plus:SI (match_operand:SI 0 "cris_bdap_operand" "")
3322 (match_operand:SI 1 "cris_bdap_operand" ""))])
3323 (match_operand 2 "register_operand" ""))
3324 (set (match_operand:SI 3 "register_operand" "")
3325 (plus:SI (match_dup 0)
3327 "(rtx_equal_p (operands[3], operands[0])
3328 || rtx_equal_p (operands[3], operands[1]))"
3329 [(set (match_dup 3) (plus:SI (match_dup 0) (match_dup 1)))
3330 (set (match_dup 5) (match_dup 2))]
3332 operands[5] = replace_equiv_address (operands[6], operands[3]);
3333 cris_order_for_addsi3 (operands, 0);
3336 ;; clear.[bwd] [rx=rx+rz.S2]
3340 [(set (mem:BWD (plus:SI
3341 (mult:SI (match_operand:SI 0 "register_operand" "")
3342 (match_operand:SI 1 "const_int_operand" ""))
3343 (match_operand:SI 2 "register_operand" "")))
3345 (set (match_operand:SI 3 "register_operand" "")
3346 (plus:SI (mult:SI (match_dup 0)
3349 "REG_P (operands[2]) && REG_P (operands[3])
3350 && REGNO (operands[3]) == REGNO (operands[2])"
3351 [(set (match_dup 3) (plus:SI (mult:SI (match_dup 0) (match_dup 1))
3353 (set (mem:BWD (match_dup 3)) (const_int 0))]
3356 ;; clear.[bwd] [rx=rx+i]
3361 (plus:SI (match_operand:SI 0 "cris_bdap_operand" "")
3362 (match_operand:SI 1 "cris_bdap_operand" "")))
3364 (set (match_operand:SI 2 "register_operand" "")
3365 (plus:SI (match_dup 0)
3367 "(rtx_equal_p (operands[0], operands[2])
3368 || rtx_equal_p (operands[2], operands[1]))"
3369 [(set (match_dup 2) (plus:SI (match_dup 0) (match_dup 1)))
3370 (set (mem:BWD (match_dup 2)) (const_int 0))]
3371 "cris_order_for_addsi3 (operands, 0);")
3373 ;; mov(s|u).S1 [rx=rx+rz.S2],ry
3377 [(set (match_operand 0 "register_operand" "")
3379 5 "cris_extend_operator"
3381 (mult:SI (match_operand:SI 1 "register_operand" "")
3382 (match_operand:SI 2 "const_int_operand" ""))
3383 (match_operand:SI 3 "register_operand" "")))]))
3384 (set (match_operand:SI 4 "register_operand" "")
3385 (plus:SI (mult:SI (match_dup 1)
3388 "REG_P (operands[3])
3389 && REG_P (operands[4])
3390 && REGNO (operands[3]) == REGNO (operands[4])"
3391 [(set (match_dup 4) (plus:SI (mult:SI (match_dup 1) (match_dup 2))
3393 (set (match_dup 0) (match_op_dup 5 [(match_dup 6)]))]
3394 "operands[6] = replace_equiv_address (XEXP (operands[5], 0), operands[4]);")
3396 ;; mov(s|u).S1 [rx=rx+i],ry
3400 [(set (match_operand 0 "register_operand" "")
3402 4 "cris_extend_operator"
3404 (match_operand:SI 1 "cris_bdap_operand" "")
3405 (match_operand:SI 2 "cris_bdap_operand" "")))]))
3406 (set (match_operand:SI 3 "register_operand" "")
3407 (plus:SI (match_dup 1)
3409 "(rtx_equal_p (operands[1], operands[3])
3410 || rtx_equal_p (operands[2], operands[3]))"
3411 [(set (match_dup 3) (plus:SI (match_dup 1) (match_dup 2)))
3412 (set (match_dup 0) (match_op_dup 4 [(match_dup 5)]))]
3414 operands[5] = replace_equiv_address (XEXP (operands[4], 0), operands[3]);
3415 cris_order_for_addsi3 (operands, 1);
3418 ;; op.S1 [rx=rx+i],ry
3422 [(set (match_operand 0 "register_operand" "")
3424 5 "cris_orthogonal_operator"
3425 [(match_operand 1 "register_operand" "")
3427 (match_operand:SI 2 "cris_bdap_operand" "")
3428 (match_operand:SI 3 "cris_bdap_operand" "")))]))
3429 (set (match_operand:SI 4 "register_operand" "")
3430 (plus:SI (match_dup 2)
3432 "(rtx_equal_p (operands[4], operands[2])
3433 || rtx_equal_p (operands[4], operands[3]))"
3434 [(set (match_dup 4) (plus:SI (match_dup 2) (match_dup 3)))
3435 (set (match_dup 0) (match_op_dup 5 [(match_dup 1) (match_dup 6)]))]
3437 operands[6] = replace_equiv_address (XEXP (operands[5], 1), operands[4]);
3438 cris_order_for_addsi3 (operands, 2);
3441 ;; op.S1 [rx=rx+rz.S2],ry
3445 [(set (match_operand 0 "register_operand" "")
3447 6 "cris_orthogonal_operator"
3448 [(match_operand 1 "register_operand" "")
3450 (mult:SI (match_operand:SI 2 "register_operand" "")
3451 (match_operand:SI 3 "const_int_operand" ""))
3452 (match_operand:SI 4 "register_operand" "")))]))
3453 (set (match_operand:SI 5 "register_operand" "")
3454 (plus:SI (mult:SI (match_dup 2)
3457 "REG_P (operands[4])
3458 && REG_P (operands[5])
3459 && REGNO (operands[5]) == REGNO (operands[4])"
3460 [(set (match_dup 5) (plus:SI (mult:SI (match_dup 2) (match_dup 3))
3462 (set (match_dup 0) (match_op_dup 6 [(match_dup 1) (match_dup 7)]))]
3463 "operands[7] = replace_equiv_address (XEXP (operands[6], 1), operands[5]);")
3465 ;; op.S1 [rx=rx+rz.S2],ry (swapped)
3469 [(set (match_operand 0 "register_operand" "")
3471 6 "cris_commutative_orth_op"
3473 (mult:SI (match_operand:SI 2 "register_operand" "")
3474 (match_operand:SI 3 "const_int_operand" ""))
3475 (match_operand:SI 4 "register_operand" "")))
3476 (match_operand 1 "register_operand" "")]))
3477 (set (match_operand:SI 5 "register_operand" "")
3478 (plus:SI (mult:SI (match_dup 2)
3481 "REG_P (operands[4])
3482 && REG_P (operands[5])
3483 && REGNO (operands[5]) == REGNO (operands[4])"
3484 [(set (match_dup 5) (plus:SI (mult:SI (match_dup 2) (match_dup 3))
3486 (set (match_dup 0) (match_op_dup 6 [(match_dup 7) (match_dup 1)]))]
3487 "operands[7] = replace_equiv_address (XEXP (operands[6], 0), operands[5]);")
3489 ;; op.S1 [rx=rx+i],ry (swapped)
3493 [(set (match_operand 0 "register_operand" "")
3495 5 "cris_commutative_orth_op"
3497 (plus:SI (match_operand:SI 2 "cris_bdap_operand" "")
3498 (match_operand:SI 3 "cris_bdap_operand" "")))
3499 (match_operand 1 "register_operand" "")]))
3500 (set (match_operand:SI 4 "register_operand" "")
3501 (plus:SI (match_dup 2)
3503 "(rtx_equal_p (operands[4], operands[2])
3504 || rtx_equal_p (operands[4], operands[3]))"
3505 [(set (match_dup 4) (plus:SI (match_dup 2) (match_dup 3)))
3506 (set (match_dup 0) (match_op_dup 5 [(match_dup 6) (match_dup 1)]))]
3508 operands[6] = replace_equiv_address (XEXP (operands[5], 0), operands[4]);
3509 cris_order_for_addsi3 (operands, 2);
3512 ;; op(s|u).S1 [rx=rx+rz.S2],ry
3516 [(set (match_operand 0 "register_operand" "")
3518 6 "cris_operand_extend_operator"
3519 [(match_operand 1 "register_operand" "")
3521 7 "cris_extend_operator"
3523 (mult:SI (match_operand:SI 2 "register_operand" "")
3524 (match_operand:SI 3 "const_int_operand" ""))
3525 (match_operand:SI 4 "register_operand" "")))])]))
3526 (set (match_operand:SI 5 "register_operand" "")
3527 (plus:SI (mult:SI (match_dup 2)
3530 "REG_P (operands[4])
3531 && REG_P (operands[5])
3532 && REGNO (operands[5]) == REGNO (operands[4])"
3533 [(set (match_dup 5) (plus:SI (mult:SI (match_dup 2) (match_dup 3))
3535 (set (match_dup 0) (match_op_dup 6 [(match_dup 1) (match_dup 8)]))]
3536 "operands[8] = gen_rtx_fmt_e (GET_CODE (operands[7]), GET_MODE (operands[7]),
3537 replace_equiv_address (XEXP (operands[7], 0),
3540 ;; op(s|u).S1 [rx=rx+i],ry
3544 [(set (match_operand 0 "register_operand" "")
3546 5 "cris_operand_extend_operator"
3547 [(match_operand 1 "register_operand" "")
3549 6 "cris_extend_operator"
3551 (plus:SI (match_operand:SI 2 "cris_bdap_operand" "")
3552 (match_operand:SI 3 "cris_bdap_operand" "")
3554 (set (match_operand:SI 4 "register_operand" "")
3555 (plus:SI (match_dup 2)
3557 "(rtx_equal_p (operands[4], operands[2])
3558 || rtx_equal_p (operands[4], operands[3]))"
3559 [(set (match_dup 4) (plus:SI (match_dup 2) (match_dup 3)))
3560 (set (match_dup 0) (match_op_dup 5 [(match_dup 1) (match_dup 7)]))]
3562 operands[7] = gen_rtx_fmt_e (GET_CODE (operands[6]), GET_MODE (operands[6]),
3563 replace_equiv_address (XEXP (operands[6], 0),
3565 cris_order_for_addsi3 (operands, 2);
3568 ;; op(s|u).S1 [rx=rx+rz.S2],ry (swapped, plus or bound)
3572 [(set (match_operand 0 "register_operand" "")
3574 7 "cris_plus_or_bound_operator"
3576 6 "cris_extend_operator"
3578 (mult:SI (match_operand:SI 2 "register_operand" "")
3579 (match_operand:SI 3 "const_int_operand" ""))
3580 (match_operand:SI 4 "register_operand" "")))])
3581 (match_operand 1 "register_operand" "")]))
3582 (set (match_operand:SI 5 "register_operand" "")
3583 (plus:SI (mult:SI (match_dup 2)
3586 "REG_P (operands[4]) && REG_P (operands[5])
3587 && REGNO (operands[5]) == REGNO (operands[4])"
3588 [(set (match_dup 5) (plus:SI (mult:SI (match_dup 2) (match_dup 3))
3590 (set (match_dup 0) (match_op_dup 6 [(match_dup 8) (match_dup 1)]))]
3591 "operands[8] = gen_rtx_fmt_e (GET_CODE (operands[6]), GET_MODE (operands[6]),
3592 replace_equiv_address (XEXP (operands[6], 0),
3595 ;; op(s|u).S1 [rx=rx+i],ry (swapped, plus or bound)
3599 [(set (match_operand 0 "register_operand" "")
3601 6 "cris_plus_or_bound_operator"
3603 5 "cris_extend_operator"
3605 (match_operand:SI 2 "cris_bdap_operand" "")
3606 (match_operand:SI 3 "cris_bdap_operand" "")))])
3607 (match_operand 1 "register_operand" "")]))
3608 (set (match_operand:SI 4 "register_operand" "")
3609 (plus:SI (match_dup 2)
3611 "(rtx_equal_p (operands[4], operands[2])
3612 || rtx_equal_p (operands[4], operands[3]))"
3613 [(set (match_dup 4) (plus:SI (match_dup 2) (match_dup 3)))
3614 (set (match_dup 0) (match_op_dup 6 [(match_dup 7) (match_dup 1)]))]
3616 operands[7] = gen_rtx_fmt_e (GET_CODE (operands[5]), GET_MODE (operands[5]),
3617 replace_equiv_address (XEXP (operands[5], 0),
3619 cris_order_for_addsi3 (operands, 2);
3622 ;; Splits for addressing prefixes that have no side-effects, so we can
3623 ;; fill a delay slot. Never split if we lose something, though.
3626 ;; move [indirect_ref],rx
3627 ;; where indirect ref = {const, [r+], [r]}, it costs as much as
3628 ;; move indirect_ref,rx
3630 ;; Take care not to allow indirect_ref = register.
3632 ;; We're not allowed to generate copies of registers with different mode
3633 ;; until after reload; copying pseudos upsets reload. CVS as of
3634 ;; 2001-08-24, unwind-dw2-fde.c, _Unwind_Find_FDE ICE in
3635 ;; cselib_invalidate_regno.
3637 (define_split ; indir_to_reg_split
3638 [(set (match_operand 0 "register_operand" "")
3639 (match_operand 1 "indirect_operand" ""))]
3641 && REG_P (operands[0])
3642 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3643 && (GET_CODE (XEXP (operands[1], 0)) == MEM
3644 || CONSTANT_P (XEXP (operands[1], 0)))
3645 && REGNO (operands[0]) < CRIS_LAST_GENERAL_REGISTER"
3646 [(set (match_dup 2) (match_dup 4))
3647 (set (match_dup 0) (match_dup 3))]
3648 "operands[2] = gen_rtx_REG (Pmode, REGNO (operands[0]));
3649 operands[3] = replace_equiv_address (operands[1], operands[2]);
3650 operands[4] = XEXP (operands[1], 0);")
3652 ;; As the above, but MOVS and MOVU.
3655 [(set (match_operand 0 "register_operand" "")
3657 4 "cris_extend_operator"
3658 [(match_operand 1 "indirect_operand" "")]))]
3660 && REG_P (operands[0])
3661 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD
3662 && (GET_CODE (XEXP (operands[1], 0)) == MEM
3663 || CONSTANT_P (XEXP (operands[1], 0)))"
3664 [(set (match_dup 2) (match_dup 5))
3665 (set (match_dup 0) (match_op_dup 4 [(match_dup 3)]))]
3666 "operands[2] = gen_rtx_REG (Pmode, REGNO (operands[0]));
3667 operands[3] = replace_equiv_address (XEXP (operands[4], 0), operands[2]);
3668 operands[5] = XEXP (operands[1], 0);")
3670 ;; Various peephole optimizations.
3672 ;; Watch out: when you exchange one set of instructions for another, the
3673 ;; condition codes setting must be the same, or you have to CC_INIT or
3674 ;; whatever is appropriate, in the pattern before you emit the
3675 ;; assembly text. This is best done here, not in cris_notice_update_cc,
3676 ;; to keep changes local to their cause.
3678 ;; Do not add patterns that you do not know will be matched.
3679 ;; Please also add a self-contained testcase.
3681 ;; We have trouble with and:s and shifts. Maybe something is broken in
3682 ;; gcc? Or it could just be that bit-field insn expansion is a bit
3683 ;; suboptimal when not having extzv insns.
3684 ;; Testcase for the following four peepholes: gcc.dg/cris-peep2-xsrand.c
3686 (define_peephole2 ; asrandb (peephole casesi+31)
3687 [(set (match_operand:SI 0 "register_operand" "")
3688 (ashiftrt:SI (match_dup 0)
3689 (match_operand:SI 1 "const_int_operand" "")))
3691 (and:SI (match_dup 0)
3692 (match_operand 2 "const_int_operand" "")))]
3693 "INTVAL (operands[2]) > 31
3694 && INTVAL (operands[2]) < 255
3695 && INTVAL (operands[1]) > 23
3696 /* Check that the and-operation enables us to use logical-shift. */
3697 && (INTVAL (operands[2])
3698 & ((HOST_WIDE_INT) -1 << (32 - INTVAL (operands[1])))) == 0"
3699 [(set (match_dup 0) (lshiftrt:SI (match_dup 0) (match_dup 1)))
3700 (set (match_dup 3) (and:QI (match_dup 3) (match_dup 4)))]
3701 ;; FIXME: CC0 is valid except for the M bit.
3703 operands[3] = gen_rtx_REG (QImode, REGNO (operands[0]));
3704 operands[4] = GEN_INT (trunc_int_for_mode (INTVAL (operands[2]), QImode));
3707 (define_peephole2 ; asrandw (peephole casesi+32)
3708 [(set (match_operand:SI 0 "register_operand" "")
3709 (ashiftrt:SI (match_dup 0)
3710 (match_operand:SI 1 "const_int_operand" "")))
3712 (and:SI (match_dup 0) (match_operand 2 "const_int_operand" "")))]
3713 "INTVAL (operands[2]) > 31
3714 && INTVAL (operands[2]) < 65535
3715 && INTVAL (operands[2]) != 255
3716 && INTVAL (operands[1]) > 15
3717 /* Check that the and-operation enables us to use logical-shift. */
3718 && (INTVAL (operands[2])
3719 & ((HOST_WIDE_INT) -1 << (32 - INTVAL (operands[1])))) == 0"
3720 [(set (match_dup 0) (lshiftrt:SI (match_dup 0) (match_dup 1)))
3721 (set (match_dup 3) (and:HI (match_dup 3) (match_dup 4)))]
3722 ;; FIXME: CC0 is valid except for the M bit.
3724 operands[3] = gen_rtx_REG (HImode, REGNO (operands[0]));
3725 operands[4] = GEN_INT (trunc_int_for_mode (INTVAL (operands[2]), HImode));
3728 (define_peephole2 ; lsrandb (peephole casesi+33)
3729 [(set (match_operand:SI 0 "register_operand" "")
3730 (lshiftrt:SI (match_dup 0)
3731 (match_operand:SI 1 "const_int_operand" "")))
3733 (and:SI (match_dup 0) (match_operand 2 "const_int_operand" "")))]
3734 "INTVAL (operands[2]) > 31
3735 && INTVAL (operands[2]) < 255
3736 && INTVAL (operands[1]) > 23"
3737 [(set (match_dup 0) (lshiftrt:SI (match_dup 0) (match_dup 1)))
3738 (set (match_dup 3) (and:QI (match_dup 3) (match_dup 4)))]
3739 ;; FIXME: CC0 is valid except for the M bit.
3741 operands[3] = gen_rtx_REG (QImode, REGNO (operands[0]));
3742 operands[4] = GEN_INT (trunc_int_for_mode (INTVAL (operands[2]), QImode));
3745 (define_peephole2 ; lsrandw (peephole casesi+34)
3746 [(set (match_operand:SI 0 "register_operand" "")
3747 (lshiftrt:SI (match_dup 0)
3748 (match_operand:SI 1 "const_int_operand" "")))
3750 (and:SI (match_dup 0) (match_operand 2 "const_int_operand" "")))]
3751 "INTVAL (operands[2]) > 31 && INTVAL (operands[2]) < 65535
3752 && INTVAL (operands[2]) != 255
3753 && INTVAL (operands[1]) > 15"
3754 [(set (match_dup 0) (lshiftrt:SI (match_dup 0) (match_dup 1)))
3755 (set (match_dup 3) (and:HI (match_dup 3) (match_dup 4)))]
3756 ;; FIXME: CC0 is valid except for the M bit.
3758 operands[3] = gen_rtx_REG (HImode, REGNO (operands[0]));
3759 operands[4] = GEN_INT (trunc_int_for_mode (INTVAL (operands[2]), HImode));
3767 ;; move [rx=rx+n],ry
3768 ;; when -128 <= n <= 127.
3769 ;; This will reduce the size of the assembler code for n = [-128..127],
3770 ;; and speed up accordingly. Don't match if the previous insn is
3771 ;; (set rx rz) because that combination is matched by another peephole.
3772 ;; No stable test-case.
3774 (define_peephole2 ; moversideqi (peephole casesi+35)
3775 [(set (match_operand:SI 0 "register_operand" "")
3776 (plus:SI (match_operand:SI 1 "register_operand" "")
3777 (match_operand:SI 2 "const_int_operand" "")))
3778 (set (match_operand 3 "register_operand" "")
3779 (match_operator 4 "cris_mem_op" [(match_dup 0)]))]
3780 "GET_MODE_SIZE (GET_MODE (operands[4])) <= UNITS_PER_WORD
3781 && REGNO (operands[3]) != REGNO (operands[0])
3782 && (BASE_P (operands[1]) || BASE_P (operands[2]))
3783 && ! CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'J')
3784 && ! CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'N')
3785 && (INTVAL (operands[2]) >= -128 && INTVAL (operands[2]) < 128)"
3787 [(set (match_dup 3) (match_dup 5))
3788 (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])]
3789 ;; Checking the previous insn is a bit too awkward for the condition.
3791 rtx prev = prev_nonnote_insn (curr_insn);
3792 if (prev != NULL_RTX)
3794 rtx set = single_set (prev);
3796 && REG_S_P (SET_DEST (set))
3797 && REGNO (SET_DEST (set)) == REGNO (operands[0])
3798 && REG_S_P (SET_SRC (set)))
3802 = replace_equiv_address (operands[4],
3803 gen_rtx_PLUS (SImode,
3804 operands[1], operands[2]));
3807 ;; Vice versa: move ry,[rx=rx+n]
3809 (define_peephole2 ; movemsideqi (peephole casesi+36)
3810 [(set (match_operand:SI 0 "register_operand" "")
3811 (plus:SI (match_operand:SI 1 "register_operand" "")
3812 (match_operand:SI 2 "const_int_operand" "")))
3813 (set (match_operator 3 "cris_mem_op" [(match_dup 0)])
3814 (match_operand 4 "register_operand" ""))]
3815 "GET_MODE_SIZE (GET_MODE (operands[4])) <= UNITS_PER_WORD
3816 && REGNO (operands[4]) != REGNO (operands[0])
3817 && (BASE_P (operands[1]) || BASE_P (operands[2]))
3818 && ! CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'J')
3819 && ! CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'N')
3820 && (INTVAL (operands[2]) >= -128 && INTVAL (operands[2]) < 128)"
3822 [(set (match_dup 5) (match_dup 4))
3823 (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])]
3825 = replace_equiv_address (operands[3],
3826 gen_rtx_PLUS (SImode,
3827 operands[1], operands[2]));")
3829 ;; As above, change:
3833 ;; op.d [rx=rx+n],ry
3834 ;; Saves when n = [-128..127].
3836 ;; Splitting and joining combinations for side-effect modes are slightly
3837 ;; out of hand. They probably will not save the time they take typing in,
3838 ;; not to mention the bugs that creep in. FIXME: Get rid of as many of
3839 ;; the splits and peepholes as possible.
3840 ;; No stable test-case.
3842 (define_peephole2 ; mover2side (peephole casesi+37)
3843 [(set (match_operand:SI 0 "register_operand" "")
3844 (plus:SI (match_operand:SI 1 "register_operand" "")
3845 (match_operand:SI 2 "const_int_operand" "")))
3846 (set (match_operand 3 "register_operand" "")
3847 (match_operator 4 "cris_orthogonal_operator"
3850 5 "cris_mem_op" [(match_dup 0)])]))]
3851 ;; FIXME: What about DFmode?
3852 ;; Change to GET_MODE_SIZE (GET_MODE (operands[3])) <= UNITS_PER_WORD?
3853 "GET_MODE (operands[3]) != DImode
3854 && REGNO (operands[0]) != REGNO (operands[3])
3855 && ! CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'J')
3856 && ! CONST_OK_FOR_LETTER_P (INTVAL (operands[2]), 'N')
3857 && INTVAL (operands[2]) >= -128
3858 && INTVAL (operands[2]) <= 127"
3860 [(set (match_dup 3) (match_op_dup 4 [(match_dup 3) (match_dup 6)]))
3861 (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])]
3863 = replace_equiv_address (operands[5],
3864 gen_rtx_PLUS (SImode,
3865 operands[1], operands[2]));")
3867 ;; Sometimes, for some reason the pattern
3871 ;; will occur. Solve this, and likewise for to-memory.
3872 ;; No stable test-case.
3874 (define_peephole2 ; moverside (peephole casesi+38)
3875 [(set (match_operand:SI 0 "register_operand" "")
3876 (match_operand:SI 1 "cris_bdap_biap_operand" ""))
3878 (plus:SI (match_operand:SI 2 "cris_bdap_biap_operand" "")
3879 (match_operand:SI 3 "cris_bdap_biap_operand" "")))
3880 (set (match_operand 4 "register_operand" "")
3881 (match_operator 5 "cris_mem_op" [(match_dup 0)]))]
3882 "(rtx_equal_p (operands[2], operands[0])
3883 || rtx_equal_p (operands[3], operands[0]))
3884 && cris_side_effect_mode_ok (PLUS, operands, 0,
3885 (REG_S_P (operands[1])
3887 : (rtx_equal_p (operands[2], operands[0])
3889 (! REG_S_P (operands[1])
3891 : (rtx_equal_p (operands[2], operands[0])
3895 [(set (match_dup 4) (match_dup 6))
3896 (set (match_dup 0) (plus:SI (match_dup 7) (match_dup 8)))])]
3899 = rtx_equal_p (operands[2], operands[0]) ? operands[3] : operands[2];
3901 /* Make sure we have canonical RTX so we match the insn pattern -
3902 not a constant in the first operand. We also require the order
3903 (plus reg mem) to match the final pattern. */
3904 if (CONSTANT_P (otherop) || MEM_P (otherop))
3906 operands[7] = operands[1];
3907 operands[8] = otherop;
3911 operands[7] = otherop;
3912 operands[8] = operands[1];
3915 = replace_equiv_address (operands[5],
3916 gen_rtx_PLUS (SImode,
3917 operands[7], operands[8]));
3920 ;; As above but to memory.
3921 ;; FIXME: Split movemside and moverside into variants and prune
3922 ;; the ones that don't trig.
3923 ;; No stable test-case.
3925 (define_peephole2 ; movemside (peephole casesi+39)
3926 [(set (match_operand:SI 0 "register_operand" "")
3927 (match_operand:SI 1 "cris_bdap_biap_operand" ""))
3929 (plus:SI (match_operand:SI 2 "cris_bdap_biap_operand" "")
3930 (match_operand:SI 3 "cris_bdap_biap_operand" "")))
3931 (set (match_operator 4 "cris_mem_op" [(match_dup 0)])
3932 (match_operand 5 "register_operand" ""))]
3933 "(rtx_equal_p (operands[2], operands[0])
3934 || rtx_equal_p (operands[3], operands[0]))
3935 && cris_side_effect_mode_ok (PLUS, operands, 0,
3936 (REG_S_P (operands[1])
3938 : (rtx_equal_p (operands[2], operands[0])
3940 (! REG_S_P (operands[1])
3942 : (rtx_equal_p (operands[2], operands[0])
3946 [(set (match_dup 6) (match_dup 5))
3947 (set (match_dup 0) (plus:SI (match_dup 7) (match_dup 8)))])]
3950 = rtx_equal_p (operands[2], operands[0]) ? operands[3] : operands[2];
3952 /* Make sure we have canonical RTX so we match the insn pattern -
3953 not a constant in the first operand. We also require the order
3954 (plus reg mem) to match the final pattern. */
3955 if (CONSTANT_P (otherop) || MEM_P (otherop))
3957 operands[7] = operands[1];
3958 operands[8] = otherop;
3962 operands[7] = otherop;
3963 operands[8] = operands[1];
3966 = replace_equiv_address (operands[4],
3967 gen_rtx_PLUS (SImode,
3968 operands[7], operands[8]));
3971 ;; Another spotted bad code:
3974 ;; No stable test-case.
3976 (define_peephole2 ; movei (peephole casesi+42)
3977 [(set (match_operand:SI 0 "register_operand" "")
3978 (match_operand:SI 1 "register_operand" ""))
3979 (set (match_operand 2 "register_operand" "")
3980 (match_operator 3 "cris_mem_op" [(match_dup 0)]))]
3981 "REGNO (operands[0]) == REGNO (operands[2])
3982 && (REGNO_REG_CLASS (REGNO (operands[0]))
3983 == REGNO_REG_CLASS (REGNO (operands[1])))
3984 && GET_MODE_SIZE (GET_MODE (operands[2])) <= UNITS_PER_WORD"
3985 [(set (match_dup 2) (match_dup 4))]
3986 "operands[4] = replace_equiv_address (operands[3], operands[1]);")
3988 ;; move.d [r10+16],r9
3991 ;; and.d [r10+16],r12,r9
3992 ;; With generalization of the operation, the size and the addressing mode.
3993 ;; This seems to be the result of a quirk in register allocation
3994 ;; missing the three-operand cases when having different predicates.
3995 ;; Maybe that it matters that it is a commutative operation.
3996 ;; This pattern helps that situation, but there's still the increased
3997 ;; register pressure.
3998 ;; Note that adding the noncommutative variant did not show any matches
3999 ;; in ipps and cc1, so it's not here.
4000 ;; No stable test-case.
4002 (define_peephole2 ; op3 (peephole casesi+44)
4003 [(set (match_operand 0 "register_operand" "")
4007 (match_operand:SI 1 "cris_bdap_biap_operand" "")
4008 (match_operand:SI 2 "cris_bdap_biap_operand" ""))]))
4011 5 "cris_commutative_orth_op"
4012 [(match_operand 3 "register_operand" "")
4013 (match_operand 4 "register_operand" "")]))]
4014 "(rtx_equal_p (operands[3], operands[0])
4015 || rtx_equal_p (operands[4], operands[0]))
4016 && ! rtx_equal_p (operands[3], operands[4])
4017 && (REG_S_P (operands[1]) || REG_S_P (operands[2]))
4018 && GET_MODE_SIZE (GET_MODE (operands[0])) <= UNITS_PER_WORD"
4019 [(set (match_dup 0) (match_op_dup 5 [(match_dup 7) (match_dup 6)]))]
4021 = rtx_equal_p (operands[3], operands[0]) ? operands[4] : operands[3];")
4023 ;; I cannot tell GCC (2.1, 2.7.2) how to correctly reload an instruction
4025 ;; and.b some_byte,const,reg_32
4026 ;; where reg_32 is the destination of the "three-address" code optimally.
4028 ;; movu.b some_byte,reg_32
4029 ;; and.b const,reg_32
4030 ;; but is turns into:
4031 ;; move.b some_byte,reg_32
4032 ;; and.d const,reg_32
4034 ;; Testcases: gcc.dg/cris-peep2-andu1.c gcc.dg/cris-peep2-andu2.c
4036 (define_peephole2 ; andu (casesi+45)
4037 [(set (match_operand:SI 0 "register_operand" "")
4038 (match_operand:SI 1 "nonimmediate_operand" ""))
4039 (set (match_operand:SI 2 "register_operand" "")
4040 (and:SI (match_dup 0)
4041 (match_operand:SI 3 "const_int_operand" "")))]
4042 ;; Since the size of the memory access could be made different here,
4043 ;; don't do this for a mem-volatile access.
4044 "REGNO (operands[2]) == REGNO (operands[0])
4045 && INTVAL (operands[3]) <= 65535 && INTVAL (operands[3]) >= 0
4046 && ! CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'I')
4047 && (GET_CODE (operands[1]) != MEM || ! MEM_VOLATILE_P (operands[1]))"
4048 ;; FIXME: CC0 valid except for M (i.e. CC_NOT_NEGATIVE).
4049 [(set (match_dup 0) (match_dup 4))
4050 (set (match_dup 5) (match_dup 6))]
4052 enum machine_mode zmode = INTVAL (operands[3]) <= 255 ? QImode : HImode;
4053 enum machine_mode amode
4054 = CONST_OK_FOR_LETTER_P (INTVAL (operands[3]), 'O') ? SImode : zmode;
4056 = (REG_S_P (operands[1])
4057 ? gen_rtx_REG (zmode, REGNO (operands[1]))
4058 : adjust_address (operands[1], zmode, 0));
4060 = gen_rtx_ZERO_EXTEND (SImode, op1);
4061 operands[5] = gen_rtx_REG (amode, REGNO (operands[0]));
4063 = gen_rtx_AND (amode, gen_rtx_REG (amode, REGNO (operands[0])),
4064 GEN_INT (trunc_int_for_mode (INTVAL (operands[3]),
4066 ? QImode : amode)));
4069 ;; Try and avoid GOTPLT reads escaping a call: transform them into
4070 ;; PLT. Curiously (but thankfully), peepholes for instructions
4071 ;; *without side-effects* that just feed a call (or call_value) are
4072 ;; not matched neither in a build or test-suite, so those patterns are
4075 ;; A "normal" move where we don't check the consumer.
4077 (define_peephole2 ; gotplt-to-plt
4079 (match_operand:SI 0 "register_operand" "")
4083 (reg:SI CRIS_GOT_REGNUM)
4085 (unspec:SI [(match_operand:SI 2 "cris_general_operand_or_symbol" "")]
4086 CRIS_UNSPEC_PLTGOTREAD)))]))]
4088 && cris_valid_pic_const (XEXP (XEXP (operands[1], 0), 1))
4089 && REGNO_REG_CLASS (REGNO (operands[0])) == REGNO_REG_CLASS (0)"
4090 [(set (match_dup 0) (const:SI (unspec:SI [(match_dup 2)] CRIS_UNSPEC_PLT)))
4091 (set (match_dup 0) (plus:SI (match_dup 0) (reg:SI CRIS_GOT_REGNUM)))]
4094 ;; And one set with a side-effect getting the PLTGOT offset.
4095 ;; First call and call_value variants.
4097 (define_peephole2 ; gotplt-to-plt-side-call
4100 (match_operand:SI 0 "register_operand" "")
4104 (reg:SI CRIS_GOT_REGNUM)
4106 (unspec:SI [(match_operand:SI
4107 2 "cris_general_operand_or_symbol" "")]
4108 CRIS_UNSPEC_PLTGOTREAD)))]))
4109 (set (match_operand:SI 3 "register_operand" "")
4110 (plus:SI (reg:SI CRIS_GOT_REGNUM)
4112 (unspec:SI [(match_dup 2)] CRIS_UNSPEC_PLTGOTREAD))))])
4113 (parallel [(call (mem:QI (match_dup 0))
4114 (match_operand 4 "" ""))
4115 (clobber (reg:SI CRIS_SRP_REGNUM))])]
4117 && cris_valid_pic_const (XEXP (XEXP (operands[1], 0), 1))
4118 && peep2_reg_dead_p (2, operands[0])"
4119 [(parallel [(call (mem:QI (match_dup 1))
4121 (clobber (reg:SI CRIS_SRP_REGNUM))
4123 (plus:SI (reg:SI CRIS_GOT_REGNUM)
4125 (unspec:SI [(match_dup 2)]
4126 CRIS_UNSPEC_PLTGOTREAD))))])]
4129 (define_peephole2 ; gotplt-to-plt-side-call-value
4132 (match_operand:SI 0 "register_operand" "")
4136 (reg:SI CRIS_GOT_REGNUM)
4138 (unspec:SI [(match_operand:SI
4139 2 "cris_general_operand_or_symbol" "")]
4140 CRIS_UNSPEC_PLTGOTREAD)))]))
4141 (set (match_operand:SI 3 "register_operand" "")
4142 (plus:SI (reg:SI CRIS_GOT_REGNUM)
4144 (unspec:SI [(match_dup 2)] CRIS_UNSPEC_PLTGOTREAD))))])
4145 (parallel [(set (match_operand 5 "" "")
4146 (call (mem:QI (match_dup 0))
4147 (match_operand 4 "" "")))
4148 (clobber (reg:SI CRIS_SRP_REGNUM))])]
4150 && cris_valid_pic_const (XEXP (XEXP (operands[1], 0), 1))
4151 && peep2_reg_dead_p (2, operands[0])"
4152 [(parallel [(set (match_dup 5)
4153 (call (mem:QI (match_dup 1))
4155 (clobber (reg:SI CRIS_SRP_REGNUM))
4157 (plus:SI (reg:SI CRIS_GOT_REGNUM)
4159 (unspec:SI [(match_dup 2)]
4160 CRIS_UNSPEC_PLTGOTREAD))))])]
4163 (define_peephole2 ; gotplt-to-plt-side
4166 (match_operand:SI 0 "register_operand" "")
4170 (reg:SI CRIS_GOT_REGNUM)
4172 (unspec:SI [(match_operand:SI
4173 2 "cris_general_operand_or_symbol" "")]
4174 CRIS_UNSPEC_PLTGOTREAD)))]))
4175 (set (match_operand:SI 3 "register_operand" "")
4176 (plus:SI (reg:SI CRIS_GOT_REGNUM)
4178 (unspec:SI [(match_dup 2)] CRIS_UNSPEC_PLTGOTREAD))))])]
4180 && cris_valid_pic_const (XEXP (XEXP (operands[1], 0), 1))
4181 && REGNO_REG_CLASS (REGNO (operands[0])) == REGNO_REG_CLASS (0)"
4183 (const:SI (unspec:SI [(match_dup 2)] CRIS_UNSPEC_PLTGOTREAD)))
4184 (set (match_dup 3) (plus:SI (match_dup 3) (reg:SI CRIS_GOT_REGNUM)))
4185 (set (match_dup 0) (const:SI (unspec:SI [(match_dup 2)] CRIS_UNSPEC_PLT)))
4186 (set (match_dup 0) (plus:SI (match_dup 0) (reg:SI CRIS_GOT_REGNUM)))]
4191 ;; comment-start: ";; "
4192 ;; eval: (set-syntax-table (copy-sequence (syntax-table)))
4193 ;; eval: (modify-syntax-entry ?[ "(]")
4194 ;; eval: (modify-syntax-entry ?] ")[")
4195 ;; eval: (modify-syntax-entry ?{ "(}")
4196 ;; eval: (modify-syntax-entry ?} "){")
4197 ;; eval: (setq indent-tabs-mode t)