1;;- Machine description for ARM for GNU compiler
2;;  Copyright (C) 1991-2020 Free Software Foundation, Inc.
3;;  Contributed by Pieter `Tiggr' Schoenmakers (rcpieter@win.tue.nl)
4;;  and Martin Simmons (@harleqn.co.uk).
5;;  More major hacks by Richard Earnshaw (rearnsha@arm.com).
6
7;; This file is part of GCC.
8
9;; GCC is free software; you can redistribute it and/or modify it
10;; under the terms of the GNU General Public License as published
11;; by the Free Software Foundation; either version 3, or (at your
12;; option) any later version.
13
14;; GCC is distributed in the hope that it will be useful, but WITHOUT
15;; ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
16;; or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public
17;; License for more details.
18
19;; You should have received a copy of the GNU General Public License
20;; along with GCC; see the file COPYING3.  If not see
21;; <http://www.gnu.org/licenses/>.
22
23;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
24
25
26;;---------------------------------------------------------------------------
27;; Constants
28
29;; Register numbers -- All machine registers should be defined here
30(define_constants
31  [(R0_REGNUM         0)	; First CORE register
32   (R1_REGNUM	      1)	; Second CORE register
33   (R4_REGNUM	      4)	; Fifth CORE register
34   (FDPIC_REGNUM      9)	; FDPIC register
35   (IP_REGNUM	     12)	; Scratch register
36   (SP_REGNUM	     13)	; Stack pointer
37   (LR_REGNUM        14)	; Return address register
38   (PC_REGNUM	     15)	; Program counter
39   (LAST_ARM_REGNUM  15)	;
40   (CC_REGNUM       100)	; Condition code pseudo register
41   (VFPCC_REGNUM    101)	; VFP Condition code pseudo register
42   (APSRQ_REGNUM    104)	; Q bit pseudo register
43   (APSRGE_REGNUM   105)	; GE bits pseudo register
44   (VPR_REGNUM      106)	; Vector Predication Register - MVE register.
45  ]
46)
47;; 3rd operand to select_dominance_cc_mode
48(define_constants
49  [(DOM_CC_X_AND_Y  0)
50   (DOM_CC_NX_OR_Y  1)
51   (DOM_CC_X_OR_Y   2)
52  ]
53)
54;; conditional compare combination
55(define_constants
56  [(CMP_CMP 0)
57   (CMN_CMP 1)
58   (CMP_CMN 2)
59   (CMN_CMN 3)
60   (NUM_OF_COND_CMP 4)
61  ]
62)
63
64
65;;---------------------------------------------------------------------------
66;; Attributes
67
68;; Processor type.  This is created automatically from arm-cores.def.
69(include "arm-tune.md")
70
71;; Instruction classification types
72(include "types.md")
73
74; IS_THUMB is set to 'yes' when we are generating Thumb code, and 'no' when
75; generating ARM code.  This is used to control the length of some insn
76; patterns that share the same RTL in both ARM and Thumb code.
77(define_attr "is_thumb" "yes,no"
78  (const (if_then_else (symbol_ref "TARGET_THUMB")
79		       (const_string "yes") (const_string "no"))))
80
81; IS_ARCH6 is set to 'yes' when we are generating code form ARMv6.
82(define_attr "is_arch6" "no,yes" (const (symbol_ref "arm_arch6")))
83
84; IS_THUMB1 is set to 'yes' iff we are generating Thumb-1 code.
85(define_attr "is_thumb1" "yes,no"
86  (const (if_then_else (symbol_ref "TARGET_THUMB1")
87		       (const_string "yes") (const_string "no"))))
88
89; Mark an instruction as suitable for "short IT" blocks in Thumb-2.
90; The arm_restrict_it flag enables the "short IT" feature which
91; restricts IT blocks to a single 16-bit instruction.
92; This attribute should only be used on 16-bit Thumb-2 instructions
93; which may be predicated (the "predicable" attribute must be set).
94(define_attr "predicable_short_it" "no,yes" (const_string "no"))
95
96; Mark an instruction as suitable for "short IT" blocks in Thumb-2.
97; This attribute should only be used on instructions which may emit
98; an IT block in their expansion which is not a short IT.
99(define_attr "enabled_for_short_it" "no,yes" (const_string "yes"))
100
101; Mark an instruction sequence as the required way of loading a
102; constant when -mpure-code is enabled (which implies
103; arm_disable_literal_pool)
104(define_attr "required_for_purecode" "no,yes" (const_string "no"))
105
106;; Operand number of an input operand that is shifted.  Zero if the
107;; given instruction does not shift one of its input operands.
108(define_attr "shift" "" (const_int 0))
109
110;; [For compatibility with AArch64 in pipeline models]
111;; Attribute that specifies whether or not the instruction touches fp
112;; registers.
113(define_attr "fp" "no,yes" (const_string "no"))
114
115; Floating Point Unit.  If we only have floating point emulation, then there
116; is no point in scheduling the floating point insns.  (Well, for best
117; performance we should try and group them together).
118(define_attr "fpu" "none,vfp"
119  (const (symbol_ref "arm_fpu_attr")))
120
121; Predicated means that the insn form is conditionally executed based on a
122; predicate.  We default to 'no' because no Thumb patterns match this rule
123; and not all ARM insns do.
124(define_attr "predicated" "yes,no" (const_string "no"))
125
126; LENGTH of an instruction (in bytes)
127(define_attr "length" ""
128  (const_int 4))
129
130; The architecture which supports the instruction (or alternative).
131; This can be "a" for ARM, "t" for either of the Thumbs, "32" for
132; TARGET_32BIT, "t1" or "t2" to specify a specific Thumb mode.  "v6"
133; for ARM or Thumb-2 with arm_arch6, and nov6 for ARM without
134; arm_arch6.  "v6t2" for Thumb-2 with arm_arch6 and "v8mb" for ARMv8-M
135; Baseline.  This attribute is used to compute attribute "enabled",
136; use type "any" to enable an alternative in all cases.
137(define_attr "arch" "any,a,t,32,t1,t2,v6,nov6,v6t2,v8mb,iwmmxt,iwmmxt2,armv6_or_vfpv3,neon,mve"
138  (const_string "any"))
139
140(define_attr "arch_enabled" "no,yes"
141  (cond [(eq_attr "arch" "any")
142	 (const_string "yes")
143
144	 (and (eq_attr "arch" "a")
145	      (match_test "TARGET_ARM"))
146	 (const_string "yes")
147
148	 (and (eq_attr "arch" "t")
149	      (match_test "TARGET_THUMB"))
150	 (const_string "yes")
151
152	 (and (eq_attr "arch" "t1")
153	      (match_test "TARGET_THUMB1"))
154	 (const_string "yes")
155
156	 (and (eq_attr "arch" "t2")
157	      (match_test "TARGET_THUMB2"))
158	 (const_string "yes")
159
160	 (and (eq_attr "arch" "32")
161	      (match_test "TARGET_32BIT"))
162	 (const_string "yes")
163
164	 (and (eq_attr "arch" "v6")
165	      (match_test "TARGET_32BIT && arm_arch6"))
166	 (const_string "yes")
167
168	 (and (eq_attr "arch" "nov6")
169	      (match_test "TARGET_32BIT && !arm_arch6"))
170	 (const_string "yes")
171
172	 (and (eq_attr "arch" "v6t2")
173	      (match_test "TARGET_32BIT && arm_arch6 && arm_arch_thumb2"))
174	 (const_string "yes")
175
176	 (and (eq_attr "arch" "v8mb")
177	      (match_test "TARGET_THUMB1 && arm_arch8"))
178	 (const_string "yes")
179
180	 (and (eq_attr "arch" "iwmmxt2")
181	      (match_test "TARGET_REALLY_IWMMXT2"))
182	 (const_string "yes")
183
184	 (and (eq_attr "arch" "armv6_or_vfpv3")
185	      (match_test "arm_arch6 || TARGET_VFP3"))
186	 (const_string "yes")
187
188	 (and (eq_attr "arch" "neon")
189	      (match_test "TARGET_NEON"))
190	 (const_string "yes")
191
192	 (and (eq_attr "arch" "mve")
193	      (match_test "TARGET_HAVE_MVE"))
194	 (const_string "yes")
195	]
196
197	(const_string "no")))
198
199(define_attr "opt" "any,speed,size"
200  (const_string "any"))
201
202(define_attr "opt_enabled" "no,yes"
203  (cond [(eq_attr "opt" "any")
204         (const_string "yes")
205
206	 (and (eq_attr "opt" "speed")
207	      (match_test "optimize_function_for_speed_p (cfun)"))
208	 (const_string "yes")
209
210	 (and (eq_attr "opt" "size")
211	      (match_test "optimize_function_for_size_p (cfun)"))
212	 (const_string "yes")]
213	(const_string "no")))
214
215(define_attr "use_literal_pool" "no,yes"
216   (cond [(and (eq_attr "type" "f_loads,f_loadd")
217	       (match_test "CONSTANT_P (operands[1])"))
218	  (const_string "yes")]
219	 (const_string "no")))
220
221; Enable all alternatives that are both arch_enabled and insn_enabled.
222; FIXME:: opt_enabled has been temporarily removed till the time we have
223; an attribute that allows the use of such alternatives.
224; This depends on caching of speed_p, size_p on a per
225; alternative basis. The problem is that the enabled attribute
226; cannot depend on any state that is not cached or is not constant
227; for a compilation unit. We probably need a generic "hot/cold"
228; alternative which if implemented can help with this. We disable this
229; until such a time as this is implemented and / or the improvements or
230; regressions with removing this attribute are double checked.
231; See ashldi3_neon and <shift>di3_neon in neon.md.
232
233 (define_attr "enabled" "no,yes"
234   (cond [(and (eq_attr "predicable_short_it" "no")
235	       (and (eq_attr "predicated" "yes")
236	            (match_test "arm_restrict_it")))
237	  (const_string "no")
238
239	  (and (eq_attr "enabled_for_short_it" "no")
240	       (match_test "arm_restrict_it"))
241	  (const_string "no")
242
243	  (and (eq_attr "required_for_purecode" "yes")
244	       (not (match_test "arm_disable_literal_pool")))
245	  (const_string "no")
246
247	  (eq_attr "arch_enabled" "no")
248	  (const_string "no")]
249	 (const_string "yes")))
250
251; POOL_RANGE is how far away from a constant pool entry that this insn
252; can be placed.  If the distance is zero, then this insn will never
253; reference the pool.
254; Note that for Thumb constant pools the PC value is rounded down to the
255; nearest multiple of four.  Therefore, THUMB2_POOL_RANGE (and POOL_RANGE for
256; Thumb insns) should be set to <max_range> - 2.
257; NEG_POOL_RANGE is nonzero for insns that can reference a constant pool entry
258; before its address.  It is set to <max_range> - (8 + <data_size>).
259(define_attr "arm_pool_range" "" (const_int 0))
260(define_attr "thumb2_pool_range" "" (const_int 0))
261(define_attr "arm_neg_pool_range" "" (const_int 0))
262(define_attr "thumb2_neg_pool_range" "" (const_int 0))
263
264(define_attr "pool_range" ""
265  (cond [(eq_attr "is_thumb" "yes") (attr "thumb2_pool_range")]
266	(attr "arm_pool_range")))
267(define_attr "neg_pool_range" ""
268  (cond [(eq_attr "is_thumb" "yes") (attr "thumb2_neg_pool_range")]
269	(attr "arm_neg_pool_range")))
270
271; An assembler sequence may clobber the condition codes without us knowing.
272; If such an insn references the pool, then we have no way of knowing how,
273; so use the most conservative value for pool_range.
274(define_asm_attributes
275 [(set_attr "conds" "clob")
276  (set_attr "length" "4")
277  (set_attr "pool_range" "250")])
278
279; Load scheduling, set from the arm_ld_sched variable
280; initialized by arm_option_override()
281(define_attr "ldsched" "no,yes" (const (symbol_ref "arm_ld_sched")))
282
283; condition codes: this one is used by final_prescan_insn to speed up
284; conditionalizing instructions.  It saves having to scan the rtl to see if
285; it uses or alters the condition codes.
286;
287; USE means that the condition codes are used by the insn in the process of
288;   outputting code, this means (at present) that we can't use the insn in
289;   inlined branches
290;
291; SET means that the purpose of the insn is to set the condition codes in a
292;   well defined manner.
293;
294; CLOB means that the condition codes are altered in an undefined manner, if
295;   they are altered at all
296;
297; UNCONDITIONAL means the instruction cannot be conditionally executed and
298;   that the instruction does not use or alter the condition codes.
299;
300; NOCOND means that the instruction does not use or alter the condition
301;   codes but can be converted into a conditionally exectuted instruction.
302
303(define_attr "conds" "use,set,clob,unconditional,nocond"
304	(if_then_else
305	 (ior (eq_attr "is_thumb1" "yes")
306	      (eq_attr "type" "call"))
307	 (const_string "clob")
308         (if_then_else
309	  (ior (eq_attr "is_neon_type" "yes")
310	       (eq_attr "is_mve_type" "yes"))
311	  (const_string "unconditional")
312	  (const_string "nocond"))))
313
314; Predicable means that the insn can be conditionally executed based on
315; an automatically added predicate (additional patterns are generated by
316; gen...).  We default to 'no' because no Thumb patterns match this rule
317; and not all ARM patterns do.
318(define_attr "predicable" "no,yes" (const_string "no"))
319
320; Only model the write buffer for ARM6 and ARM7.  Earlier processors don't
321; have one.  Later ones, such as StrongARM, have write-back caches, so don't
322; suffer blockages enough to warrant modelling this (and it can adversely
323; affect the schedule).
324(define_attr "model_wbuf" "no,yes" (const (symbol_ref "arm_tune_wbuf")))
325
326; WRITE_CONFLICT implies that a read following an unrelated write is likely
327; to stall the processor.  Used with model_wbuf above.
328(define_attr "write_conflict" "no,yes"
329  (if_then_else (eq_attr "type"
330		 "block,call,load_4")
331		(const_string "yes")
332		(const_string "no")))
333
334; Classify the insns into those that take one cycle and those that take more
335; than one on the main cpu execution unit.
336(define_attr "core_cycles" "single,multi"
337  (if_then_else (eq_attr "type"
338    "adc_imm, adc_reg, adcs_imm, adcs_reg, adr, alu_ext, alu_imm, alu_sreg,\
339    alu_shift_imm, alu_shift_reg, alu_dsp_reg, alus_ext, alus_imm, alus_sreg,\
340    alus_shift_imm, alus_shift_reg, bfm, csel, rev, logic_imm, logic_reg,\
341    logic_shift_imm, logic_shift_reg, logics_imm, logics_reg,\
342    logics_shift_imm, logics_shift_reg, extend, shift_imm, float, fcsel,\
343    wmmx_wor, wmmx_wxor, wmmx_wand, wmmx_wandn, wmmx_wmov, wmmx_tmcrr,\
344    wmmx_tmrrc, wmmx_wldr, wmmx_wstr, wmmx_tmcr, wmmx_tmrc, wmmx_wadd,\
345    wmmx_wsub, wmmx_wmul, wmmx_wmac, wmmx_wavg2, wmmx_tinsr, wmmx_textrm,\
346    wmmx_wshufh, wmmx_wcmpeq, wmmx_wcmpgt, wmmx_wmax, wmmx_wmin, wmmx_wpack,\
347    wmmx_wunpckih, wmmx_wunpckil, wmmx_wunpckeh, wmmx_wunpckel, wmmx_wror,\
348    wmmx_wsra, wmmx_wsrl, wmmx_wsll, wmmx_wmadd, wmmx_tmia, wmmx_tmiaph,\
349    wmmx_tmiaxy, wmmx_tbcst, wmmx_tmovmsk, wmmx_wacc, wmmx_waligni,\
350    wmmx_walignr, wmmx_tandc, wmmx_textrc, wmmx_torc, wmmx_torvsc, wmmx_wsad,\
351    wmmx_wabs, wmmx_wabsdiff, wmmx_waddsubhx, wmmx_wsubaddhx, wmmx_wavg4,\
352    wmmx_wmulw, wmmx_wqmulm, wmmx_wqmulwm, wmmx_waddbhus, wmmx_wqmiaxy,\
353    wmmx_wmiaxy, wmmx_wmiawxy, wmmx_wmerge")
354		(const_string "single")
355	        (const_string "multi")))
356
357;; FAR_JUMP is "yes" if a BL instruction is used to generate a branch to a
358;; distant label.  Only applicable to Thumb code.
359(define_attr "far_jump" "yes,no" (const_string "no"))
360
361
362;; The number of machine instructions this pattern expands to.
363;; Used for Thumb-2 conditional execution.
364(define_attr "ce_count" "" (const_int 1))
365
366;;---------------------------------------------------------------------------
367;; Unspecs
368
369(include "unspecs.md")
370
371;;---------------------------------------------------------------------------
372;; Mode iterators
373
374(include "iterators.md")
375
376;;---------------------------------------------------------------------------
377;; Predicates
378
379(include "predicates.md")
380(include "constraints.md")
381
382;;---------------------------------------------------------------------------
383;; Pipeline descriptions
384
385(define_attr "tune_cortexr4" "yes,no"
386  (const (if_then_else
387	  (eq_attr "tune" "cortexr4,cortexr4f,cortexr5")
388	  (const_string "yes")
389	  (const_string "no"))))
390
391;; True if the generic scheduling description should be used.
392
393(define_attr "generic_sched" "yes,no"
394  (const (if_then_else
395          (ior (eq_attr "tune" "fa526,fa626,fa606te,fa626te,fmp626,fa726te,\
396                                arm926ejs,arm10e,arm1026ejs,arm1136js,\
397                                arm1136jfs,cortexa5,cortexa7,cortexa8,\
398                                cortexa9,cortexa12,cortexa15,cortexa17,\
399                                cortexa53,cortexa57,cortexm4,cortexm7,\
400				exynosm1,marvell_pj4,xgene1")
401	       (eq_attr "tune_cortexr4" "yes"))
402          (const_string "no")
403          (const_string "yes"))))
404
405(define_attr "generic_vfp" "yes,no"
406  (const (if_then_else
407	  (and (eq_attr "fpu" "vfp")
408	       (eq_attr "tune" "!arm10e,cortexa5,cortexa7,\
409                                cortexa8,cortexa9,cortexa53,cortexm4,\
410                                cortexm7,marvell_pj4,xgene1")
411	       (eq_attr "tune_cortexr4" "no"))
412	  (const_string "yes")
413	  (const_string "no"))))
414
415(include "marvell-f-iwmmxt.md")
416(include "arm-generic.md")
417(include "arm926ejs.md")
418(include "arm1020e.md")
419(include "arm1026ejs.md")
420(include "arm1136jfs.md")
421(include "fa526.md")
422(include "fa606te.md")
423(include "fa626te.md")
424(include "fmp626.md")
425(include "fa726te.md")
426(include "cortex-a5.md")
427(include "cortex-a7.md")
428(include "cortex-a8.md")
429(include "cortex-a9.md")
430(include "cortex-a15.md")
431(include "cortex-a17.md")
432(include "cortex-a53.md")
433(include "cortex-a57.md")
434(include "cortex-r4.md")
435(include "cortex-r4f.md")
436(include "cortex-m7.md")
437(include "cortex-m4.md")
438(include "cortex-m4-fpu.md")
439(include "exynos-m1.md")
440(include "vfp11.md")
441(include "marvell-pj4.md")
442(include "xgene1.md")
443
444;; define_subst and associated attributes
445
446(define_subst "add_setq"
447  [(set (match_operand:SI 0 "" "")
448        (match_operand:SI 1 "" ""))]
449  ""
450  [(set (match_dup 0)
451        (match_dup 1))
452   (set (reg:CC APSRQ_REGNUM)
453	(unspec:CC [(reg:CC APSRQ_REGNUM)] UNSPEC_Q_SET))])
454
455(define_subst_attr "add_clobber_q_name" "add_setq" "" "_setq")
456(define_subst_attr "add_clobber_q_pred" "add_setq" "!ARM_Q_BIT_READ"
457		   "ARM_Q_BIT_READ")
458
459;;---------------------------------------------------------------------------
460;; Insn patterns
461;;
462;; Addition insns.
463
464;; Note: For DImode insns, there is normally no reason why operands should
465;; not be in the same register, what we don't want is for something being
466;; written to partially overlap something that is an input.
467
468(define_expand "adddi3"
469 [(parallel
470   [(set (match_operand:DI           0 "s_register_operand")
471	  (plus:DI (match_operand:DI 1 "s_register_operand")
472		   (match_operand:DI 2 "reg_or_int_operand")))
473    (clobber (reg:CC CC_REGNUM))])]
474  "TARGET_EITHER"
475  "
476  if (TARGET_THUMB1)
477    {
478      if (!REG_P (operands[2]))
479	operands[2] = force_reg (DImode, operands[2]);
480    }
481  else
482    {
483      rtx lo_result, hi_result, lo_dest, hi_dest;
484      rtx lo_op1, hi_op1, lo_op2, hi_op2;
485      arm_decompose_di_binop (operands[1], operands[2], &lo_op1, &hi_op1,
486			      &lo_op2, &hi_op2);
487      lo_result = lo_dest = gen_lowpart (SImode, operands[0]);
488      hi_result = hi_dest = gen_highpart (SImode, operands[0]);
489
490      if (lo_op2 == const0_rtx)
491	{
492	  lo_dest = lo_op1;
493	  if (!arm_add_operand (hi_op2, SImode))
494	    hi_op2 = force_reg (SImode, hi_op2);
495	  /* Assume hi_op2 won't also be zero.  */
496	  emit_insn (gen_addsi3 (hi_dest, hi_op1, hi_op2));
497	}
498      else
499	{
500	  if (!arm_add_operand (lo_op2, SImode))
501	    lo_op2 = force_reg (SImode, lo_op2);
502	  if (!arm_not_operand (hi_op2, SImode))
503	    hi_op2 = force_reg (SImode, hi_op2);
504
505	  emit_insn (gen_addsi3_compare_op1 (lo_dest, lo_op1, lo_op2));
506	  rtx carry = gen_rtx_LTU (SImode, gen_rtx_REG (CC_Cmode, CC_REGNUM),
507				   const0_rtx);
508	  if (hi_op2 == const0_rtx)
509	    emit_insn (gen_add0si3_carryin (hi_dest, hi_op1, carry));
510	  else
511	    emit_insn (gen_addsi3_carryin (hi_dest, hi_op1, hi_op2, carry));
512	}
513
514      if (lo_result != lo_dest)
515	emit_move_insn (lo_result, lo_dest);
516      if (hi_result != hi_dest)
517	emit_move_insn (gen_highpart (SImode, operands[0]), hi_dest);
518      DONE;
519    }
520  "
521)
522
523(define_expand "addvsi4"
524  [(match_operand:SI 0 "s_register_operand")
525   (match_operand:SI 1 "s_register_operand")
526   (match_operand:SI 2 "arm_add_operand")
527   (match_operand 3 "")]
528  "TARGET_32BIT"
529{
530  if (CONST_INT_P (operands[2]))
531    emit_insn (gen_addsi3_compareV_imm (operands[0], operands[1], operands[2]));
532  else
533    emit_insn (gen_addsi3_compareV_reg (operands[0], operands[1], operands[2]));
534  arm_gen_unlikely_cbranch (NE, CC_Vmode, operands[3]);
535
536  DONE;
537})
538
539(define_expand "addvdi4"
540  [(match_operand:DI 0 "s_register_operand")
541   (match_operand:DI 1 "s_register_operand")
542   (match_operand:DI 2 "reg_or_int_operand")
543   (match_operand 3 "")]
544  "TARGET_32BIT"
545{
546  rtx lo_result, hi_result;
547  rtx lo_op1, hi_op1, lo_op2, hi_op2;
548  arm_decompose_di_binop (operands[1], operands[2], &lo_op1, &hi_op1,
549			  &lo_op2, &hi_op2);
550  lo_result = gen_lowpart (SImode, operands[0]);
551  hi_result = gen_highpart (SImode, operands[0]);
552
553  if (lo_op2 == const0_rtx)
554    {
555      emit_move_insn (lo_result, lo_op1);
556      if (!arm_add_operand (hi_op2, SImode))
557	hi_op2 = force_reg (SImode, hi_op2);
558
559      emit_insn (gen_addvsi4 (hi_result, hi_op1, hi_op2, operands[3]));
560    }
561  else
562    {
563      if (!arm_add_operand (lo_op2, SImode))
564	lo_op2 = force_reg (SImode, lo_op2);
565      if (!arm_not_operand (hi_op2, SImode))
566	hi_op2 = force_reg (SImode, hi_op2);
567
568      emit_insn (gen_addsi3_compare_op1 (lo_result, lo_op1, lo_op2));
569
570      if (hi_op2 == const0_rtx)
571        emit_insn (gen_addsi3_cin_vout_0 (hi_result, hi_op1));
572      else if (CONST_INT_P (hi_op2))
573        emit_insn (gen_addsi3_cin_vout_imm (hi_result, hi_op1, hi_op2));
574      else
575        emit_insn (gen_addsi3_cin_vout_reg (hi_result, hi_op1, hi_op2));
576
577      arm_gen_unlikely_cbranch (NE, CC_Vmode, operands[3]);
578    }
579
580  DONE;
581})
582
583(define_expand "addsi3_cin_vout_reg"
584  [(parallel
585    [(set (match_dup 3)
586	  (compare:CC_V
587	   (plus:DI
588	    (plus:DI (match_dup 4)
589		     (sign_extend:DI (match_operand:SI 1 "s_register_operand")))
590	    (sign_extend:DI (match_operand:SI 2 "s_register_operand")))
591	   (sign_extend:DI (plus:SI (plus:SI (match_dup 5) (match_dup 1))
592				    (match_dup 2)))))
593     (set (match_operand:SI 0 "s_register_operand")
594	  (plus:SI (plus:SI (match_dup 5) (match_dup 1))
595		   (match_dup 2)))])]
596  "TARGET_32BIT"
597  {
598    operands[3] = gen_rtx_REG (CC_Vmode, CC_REGNUM);
599    rtx ccin = gen_rtx_REG (CC_Cmode, CC_REGNUM);
600    operands[4] = gen_rtx_LTU (DImode, ccin, const0_rtx);
601    operands[5] = gen_rtx_LTU (SImode, ccin, const0_rtx);
602  }
603)
604
605(define_insn "*addsi3_cin_vout_reg_insn"
606  [(set (reg:CC_V CC_REGNUM)
607	(compare:CC_V
608	 (plus:DI
609	  (plus:DI
610	   (match_operand:DI 3 "arm_carry_operation" "")
611	   (sign_extend:DI (match_operand:SI 1 "s_register_operand" "%0,r")))
612	  (sign_extend:DI (match_operand:SI 2 "s_register_operand" "l,r")))
613	 (sign_extend:DI
614	  (plus:SI (plus:SI (match_operand:SI 4 "arm_carry_operation" "")
615			    (match_dup 1))
616		   (match_dup 2)))))
617   (set (match_operand:SI 0 "s_register_operand" "=l,r")
618	(plus:SI (plus:SI (match_dup 4) (match_dup 1))
619		 (match_dup 2)))]
620  "TARGET_32BIT"
621  "@
622   adcs%?\\t%0, %0, %2
623   adcs%?\\t%0, %1, %2"
624  [(set_attr "type" "alus_sreg")
625   (set_attr "arch" "t2,*")
626   (set_attr "length" "2,4")]
627)
628
629(define_expand "addsi3_cin_vout_imm"
630  [(parallel
631    [(set (match_dup 3)
632	  (compare:CC_V
633	   (plus:DI
634	    (plus:DI (match_dup 4)
635		     (sign_extend:DI (match_operand:SI 1 "s_register_operand")))
636	    (match_dup 2))
637	   (sign_extend:DI (plus:SI (plus:SI (match_dup 5) (match_dup 1))
638				    (match_dup 2)))))
639     (set (match_operand:SI 0 "s_register_operand")
640	  (plus:SI (plus:SI (match_dup 5) (match_dup 1))
641		   (match_operand 2 "arm_adcimm_operand")))])]
642  "TARGET_32BIT"
643  {
644    operands[3] = gen_rtx_REG (CC_Vmode, CC_REGNUM);
645    rtx ccin = gen_rtx_REG (CC_Cmode, CC_REGNUM);
646    operands[4] = gen_rtx_LTU (DImode, ccin, const0_rtx);
647    operands[5] = gen_rtx_LTU (SImode, ccin, const0_rtx);
648  }
649)
650
651(define_insn "*addsi3_cin_vout_imm_insn"
652  [(set (reg:CC_V CC_REGNUM)
653	(compare:CC_V
654	 (plus:DI
655	  (plus:DI
656	   (match_operand:DI 3 "arm_carry_operation" "")
657	   (sign_extend:DI (match_operand:SI 1 "s_register_operand" "r,r")))
658	  (match_operand 2 "arm_adcimm_operand" "I,K"))
659	 (sign_extend:DI
660	  (plus:SI (plus:SI (match_operand:SI 4 "arm_carry_operation" "")
661			    (match_dup 1))
662		   (match_dup 2)))))
663   (set (match_operand:SI 0 "s_register_operand" "=r,r")
664	(plus:SI (plus:SI (match_dup 4) (match_dup 1))
665		 (match_dup 2)))]
666  "TARGET_32BIT"
667  "@
668   adcs%?\\t%0, %1, %2
669   sbcs%?\\t%0, %1, #%B2"
670  [(set_attr "type" "alus_imm")]
671)
672
673(define_expand "addsi3_cin_vout_0"
674  [(parallel
675    [(set (match_dup 2)
676	  (compare:CC_V
677	   (plus:DI (match_dup 3)
678		    (sign_extend:DI (match_operand:SI 1 "s_register_operand")))
679	   (sign_extend:DI (plus:SI (match_dup 4) (match_dup 1)))))
680     (set (match_operand:SI 0 "s_register_operand")
681	  (plus:SI (match_dup 4) (match_dup 1)))])]
682  "TARGET_32BIT"
683  {
684    operands[2] = gen_rtx_REG (CC_Vmode, CC_REGNUM);
685    rtx ccin = gen_rtx_REG (CC_Cmode, CC_REGNUM);
686    operands[3] = gen_rtx_LTU (DImode, ccin, const0_rtx);
687    operands[4] = gen_rtx_LTU (SImode, ccin, const0_rtx);
688  }
689)
690
691(define_insn "*addsi3_cin_vout_0_insn"
692  [(set (reg:CC_V CC_REGNUM)
693	(compare:CC_V
694	 (plus:DI
695	  (match_operand:DI 2 "arm_carry_operation" "")
696	  (sign_extend:DI (match_operand:SI 1 "s_register_operand" "r")))
697	 (sign_extend:DI (plus:SI
698			  (match_operand:SI 3 "arm_carry_operation" "")
699			  (match_dup 1)))))
700   (set (match_operand:SI 0 "s_register_operand" "=r")
701	(plus:SI (match_dup 3) (match_dup 1)))]
702  "TARGET_32BIT"
703  "adcs%?\\t%0, %1, #0"
704  [(set_attr "type" "alus_imm")]
705)
706
707(define_expand "uaddvsi4"
708  [(match_operand:SI 0 "s_register_operand")
709   (match_operand:SI 1 "s_register_operand")
710   (match_operand:SI 2 "arm_add_operand")
711   (match_operand 3 "")]
712  "TARGET_32BIT"
713{
714  emit_insn (gen_addsi3_compare_op1 (operands[0], operands[1], operands[2]));
715  arm_gen_unlikely_cbranch (LTU, CC_Cmode, operands[3]);
716
717  DONE;
718})
719
720(define_expand "uaddvdi4"
721  [(match_operand:DI 0 "s_register_operand")
722   (match_operand:DI 1 "s_register_operand")
723   (match_operand:DI 2 "reg_or_int_operand")
724   (match_operand 3 "")]
725  "TARGET_32BIT"
726{
727  rtx lo_result, hi_result;
728  rtx lo_op1, hi_op1, lo_op2, hi_op2;
729  arm_decompose_di_binop (operands[1], operands[2], &lo_op1, &hi_op1,
730			  &lo_op2, &hi_op2);
731  lo_result = gen_lowpart (SImode, operands[0]);
732  hi_result = gen_highpart (SImode, operands[0]);
733
734  if (lo_op2 == const0_rtx)
735    {
736      emit_move_insn (lo_result, lo_op1);
737      if (!arm_add_operand (hi_op2, SImode))
738	hi_op2 = force_reg (SImode, hi_op2);
739
740      emit_insn (gen_uaddvsi4 (hi_result, hi_op1, hi_op2, operands[3]));
741    }
742  else
743    {
744      if (!arm_add_operand (lo_op2, SImode))
745	lo_op2 = force_reg (SImode, lo_op2);
746      if (!arm_not_operand (hi_op2, SImode))
747	hi_op2 = force_reg (SImode, hi_op2);
748
749      emit_insn (gen_addsi3_compare_op1 (lo_result, lo_op1, lo_op2));
750
751      if (hi_op2 == const0_rtx)
752        emit_insn (gen_addsi3_cin_cout_0 (hi_result, hi_op1));
753      else if (CONST_INT_P (hi_op2))
754        emit_insn (gen_addsi3_cin_cout_imm (hi_result, hi_op1, hi_op2));
755      else
756        emit_insn (gen_addsi3_cin_cout_reg (hi_result, hi_op1, hi_op2));
757
758      arm_gen_unlikely_cbranch (GEU, CC_ADCmode, operands[3]);
759    }
760
761  DONE;
762})
763
764(define_expand "addsi3_cin_cout_reg"
765  [(parallel
766    [(set (match_dup 3)
767	  (compare:CC_ADC
768	   (plus:DI
769	    (plus:DI (match_dup 4)
770		     (zero_extend:DI (match_operand:SI 1 "s_register_operand")))
771	    (zero_extend:DI (match_operand:SI 2 "s_register_operand")))
772	   (const_int 4294967296)))
773     (set (match_operand:SI 0 "s_register_operand")
774	  (plus:SI (plus:SI (match_dup 5) (match_dup 1))
775		   (match_dup 2)))])]
776  "TARGET_32BIT"
777  {
778    operands[3] = gen_rtx_REG (CC_ADCmode, CC_REGNUM);
779    rtx ccin = gen_rtx_REG (CC_Cmode, CC_REGNUM);
780    operands[4] = gen_rtx_LTU (DImode, ccin, const0_rtx);
781    operands[5] = gen_rtx_LTU (SImode, ccin, const0_rtx);
782  }
783)
784
785(define_insn "*addsi3_cin_cout_reg_insn"
786  [(set (reg:CC_ADC CC_REGNUM)
787	(compare:CC_ADC
788	 (plus:DI
789	  (plus:DI
790	   (match_operand:DI 3 "arm_carry_operation" "")
791	   (zero_extend:DI (match_operand:SI 1 "s_register_operand" "%0,r")))
792	  (zero_extend:DI (match_operand:SI 2 "s_register_operand" "l,r")))
793	(const_int 4294967296)))
794   (set (match_operand:SI 0 "s_register_operand" "=l,r")
795	(plus:SI (plus:SI (match_operand:SI 4 "arm_carry_operation" "")
796			  (match_dup 1))
797		 (match_dup 2)))]
798  "TARGET_32BIT"
799  "@
800   adcs%?\\t%0, %0, %2
801   adcs%?\\t%0, %1, %2"
802  [(set_attr "type" "alus_sreg")
803   (set_attr "arch" "t2,*")
804   (set_attr "length" "2,4")]
805)
806
807(define_expand "addsi3_cin_cout_imm"
808  [(parallel
809    [(set (match_dup 3)
810	  (compare:CC_ADC
811	   (plus:DI
812	    (plus:DI (match_dup 4)
813		     (zero_extend:DI (match_operand:SI 1 "s_register_operand")))
814	    (match_dup 6))
815	   (const_int 4294967296)))
816     (set (match_operand:SI 0 "s_register_operand")
817	  (plus:SI (plus:SI (match_dup 5) (match_dup 1))
818		   (match_operand:SI 2 "arm_adcimm_operand")))])]
819  "TARGET_32BIT"
820  {
821    operands[3] = gen_rtx_REG (CC_ADCmode, CC_REGNUM);
822    rtx ccin = gen_rtx_REG (CC_Cmode, CC_REGNUM);
823    operands[4] = gen_rtx_LTU (DImode, ccin, const0_rtx);
824    operands[5] = gen_rtx_LTU (SImode, ccin, const0_rtx);
825    operands[6] = GEN_INT (UINTVAL (operands[2]) & 0xffffffff);
826  }
827)
828
829(define_insn "*addsi3_cin_cout_imm_insn"
830  [(set (reg:CC_ADC CC_REGNUM)
831	(compare:CC_ADC
832	 (plus:DI
833	  (plus:DI
834	   (match_operand:DI 3 "arm_carry_operation" "")
835	   (zero_extend:DI (match_operand:SI 1 "s_register_operand" "r,r")))
836	  (match_operand:DI 5 "const_int_operand" "n,n"))
837	(const_int 4294967296)))
838   (set (match_operand:SI 0 "s_register_operand" "=r,r")
839	(plus:SI (plus:SI (match_operand:SI 4 "arm_carry_operation" "")
840			  (match_dup 1))
841		 (match_operand:SI 2 "arm_adcimm_operand" "I,K")))]
842  "TARGET_32BIT
843   && (UINTVAL (operands[2]) & 0xffffffff) == UINTVAL (operands[5])"
844  "@
845   adcs%?\\t%0, %1, %2
846   sbcs%?\\t%0, %1, #%B2"
847  [(set_attr "type" "alus_imm")]
848)
849
850(define_expand "addsi3_cin_cout_0"
851  [(parallel
852    [(set (match_dup 2)
853	  (compare:CC_ADC
854	   (plus:DI (match_dup 3)
855		    (zero_extend:DI (match_operand:SI 1 "s_register_operand")))
856	   (const_int 4294967296)))
857     (set (match_operand:SI 0 "s_register_operand")
858	  (plus:SI (match_dup 4) (match_dup 1)))])]
859  "TARGET_32BIT"
860  {
861    operands[2] = gen_rtx_REG (CC_ADCmode, CC_REGNUM);
862    rtx ccin = gen_rtx_REG (CC_Cmode, CC_REGNUM);
863    operands[3] = gen_rtx_LTU (DImode, ccin, const0_rtx);
864    operands[4] = gen_rtx_LTU (SImode, ccin, const0_rtx);
865  }
866)
867
868(define_insn "*addsi3_cin_cout_0_insn"
869  [(set (reg:CC_ADC CC_REGNUM)
870	(compare:CC_ADC
871	 (plus:DI
872	  (match_operand:DI 2 "arm_carry_operation" "")
873	  (zero_extend:DI (match_operand:SI 1 "s_register_operand" "r")))
874	(const_int 4294967296)))
875   (set (match_operand:SI 0 "s_register_operand" "=r")
876	(plus:SI (match_operand:SI 3 "arm_carry_operation" "") (match_dup 1)))]
877  "TARGET_32BIT"
878  "adcs%?\\t%0, %1, #0"
879  [(set_attr "type" "alus_imm")]
880)
881
882(define_expand "addsi3"
883  [(set (match_operand:SI          0 "s_register_operand")
884	(plus:SI (match_operand:SI 1 "s_register_operand")
885		 (match_operand:SI 2 "reg_or_int_operand")))]
886  "TARGET_EITHER"
887  "
888  if (TARGET_32BIT && CONST_INT_P (operands[2]))
889    {
890      arm_split_constant (PLUS, SImode, NULL_RTX,
891	                  INTVAL (operands[2]), operands[0], operands[1],
892			  optimize && can_create_pseudo_p ());
893      DONE;
894    }
895  "
896)
897
898; If there is a scratch available, this will be faster than synthesizing the
899; addition.
900(define_peephole2
901  [(match_scratch:SI 3 "r")
902   (set (match_operand:SI          0 "arm_general_register_operand" "")
903	(plus:SI (match_operand:SI 1 "arm_general_register_operand" "")
904		 (match_operand:SI 2 "const_int_operand"  "")))]
905  "TARGET_32BIT &&
906   !(const_ok_for_arm (INTVAL (operands[2]))
907     || const_ok_for_arm (-INTVAL (operands[2])))
908    && const_ok_for_arm (~INTVAL (operands[2]))"
909  [(set (match_dup 3) (match_dup 2))
910   (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 3)))]
911  ""
912)
913
914;; The r/r/k alternative is required when reloading the address
915;;  (plus (reg rN) (reg sp)) into (reg rN).  In this case reload will
916;; put the duplicated register first, and not try the commutative version.
917(define_insn_and_split "*arm_addsi3"
918  [(set (match_operand:SI          0 "s_register_operand" "=rk,l,l ,l ,r ,k ,r,k ,r ,k ,r ,k,k,r ,k ,r")
919	(plus:SI (match_operand:SI 1 "s_register_operand" "%0 ,l,0 ,l ,rk,k ,r,r ,rk,k ,rk,k,r,rk,k ,rk")
920		 (match_operand:SI 2 "reg_or_int_operand" "rk ,l,Py,Pd,rI,rI,k,rI,Pj,Pj,L ,L,L,PJ,PJ,?n")))]
921  "TARGET_32BIT"
922  "@
923   add%?\\t%0, %0, %2
924   add%?\\t%0, %1, %2
925   add%?\\t%0, %1, %2
926   add%?\\t%0, %1, %2
927   add%?\\t%0, %1, %2
928   add%?\\t%0, %1, %2
929   add%?\\t%0, %2, %1
930   add%?\\t%0, %1, %2
931   addw%?\\t%0, %1, %2
932   addw%?\\t%0, %1, %2
933   sub%?\\t%0, %1, #%n2
934   sub%?\\t%0, %1, #%n2
935   sub%?\\t%0, %1, #%n2
936   subw%?\\t%0, %1, #%n2
937   subw%?\\t%0, %1, #%n2
938   #"
939  "TARGET_32BIT
940   && CONST_INT_P (operands[2])
941   && !const_ok_for_op (INTVAL (operands[2]), PLUS)
942   && (reload_completed || !arm_eliminable_register (operands[1]))"
943  [(clobber (const_int 0))]
944  "
945  arm_split_constant (PLUS, SImode, curr_insn,
946	              INTVAL (operands[2]), operands[0],
947		      operands[1], 0);
948  DONE;
949  "
950  [(set_attr "length" "2,4,4,4,4,4,4,4,4,4,4,4,4,4,4,16")
951   (set_attr "predicable" "yes")
952   (set_attr "predicable_short_it" "yes,yes,yes,yes,no,no,no,no,no,no,no,no,no,no,no,no")
953   (set_attr "arch" "t2,t2,t2,t2,*,*,*,a,t2,t2,*,*,a,t2,t2,*")
954   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
955		      (const_string "alu_imm")
956		      (const_string "alu_sreg")))
957 ]
958)
959
960(define_insn "addsi3_compareV_reg"
961  [(set (reg:CC_V CC_REGNUM)
962	(compare:CC_V
963	  (plus:DI
964	    (sign_extend:DI (match_operand:SI 1 "register_operand" "%l,0,r"))
965	    (sign_extend:DI (match_operand:SI 2 "register_operand" "l,r,r")))
966	  (sign_extend:DI (plus:SI (match_dup 1) (match_dup 2)))))
967   (set (match_operand:SI 0 "register_operand" "=l,r,r")
968	(plus:SI (match_dup 1) (match_dup 2)))]
969  "TARGET_32BIT"
970  "adds%?\\t%0, %1, %2"
971  [(set_attr "conds" "set")
972   (set_attr "arch" "t2,t2,*")
973   (set_attr "length" "2,2,4")
974   (set_attr "type" "alus_sreg")]
975)
976
977(define_insn "*addsi3_compareV_reg_nosum"
978  [(set (reg:CC_V CC_REGNUM)
979	(compare:CC_V
980	  (plus:DI
981	    (sign_extend:DI (match_operand:SI 0 "register_operand" "%l,r"))
982	    (sign_extend:DI (match_operand:SI 1 "register_operand" "l,r")))
983	  (sign_extend:DI (plus:SI (match_dup 0) (match_dup 1)))))]
984  "TARGET_32BIT"
985  "cmn%?\\t%0, %1"
986  [(set_attr "conds" "set")
987   (set_attr "arch" "t2,*")
988   (set_attr "length" "2,4")
989   (set_attr "type" "alus_sreg")]
990)
991
992(define_insn "subvsi3_intmin"
993  [(set (reg:CC_V CC_REGNUM)
994	(compare:CC_V
995	  (plus:DI
996	    (sign_extend:DI
997	     (match_operand:SI 1 "register_operand" "r"))
998	    (const_int 2147483648))
999	  (sign_extend:DI (plus:SI (match_dup 1) (const_int -2147483648)))))
1000   (set (match_operand:SI 0 "register_operand" "=r")
1001	(plus:SI (match_dup 1) (const_int -2147483648)))]
1002  "TARGET_32BIT"
1003  "subs%?\\t%0, %1, #-2147483648"
1004  [(set_attr "conds" "set")
1005   (set_attr "type" "alus_imm")]
1006)
1007
1008(define_insn "addsi3_compareV_imm"
1009  [(set (reg:CC_V CC_REGNUM)
1010	(compare:CC_V
1011	  (plus:DI
1012	    (sign_extend:DI
1013	     (match_operand:SI 1 "register_operand" "l,0,l,0,r,r"))
1014	    (match_operand 2 "arm_addimm_operand" "Pd,Py,Px,Pw,I,L"))
1015	  (sign_extend:DI (plus:SI (match_dup 1) (match_dup 2)))))
1016   (set (match_operand:SI 0 "register_operand" "=l,l,l,l,r,r")
1017	(plus:SI (match_dup 1) (match_dup 2)))]
1018  "TARGET_32BIT
1019   && INTVAL (operands[2]) == ARM_SIGN_EXTEND (INTVAL (operands[2]))"
1020  "@
1021   adds%?\\t%0, %1, %2
1022   adds%?\\t%0, %0, %2
1023   subs%?\\t%0, %1, #%n2
1024   subs%?\\t%0, %0, #%n2
1025   adds%?\\t%0, %1, %2
1026   subs%?\\t%0, %1, #%n2"
1027  [(set_attr "conds" "set")
1028   (set_attr "arch" "t2,t2,t2,t2,*,*")
1029   (set_attr "length" "2,2,2,2,4,4")
1030   (set_attr "type" "alus_imm")]
1031)
1032
1033(define_insn "addsi3_compareV_imm_nosum"
1034  [(set (reg:CC_V CC_REGNUM)
1035	(compare:CC_V
1036	  (plus:DI
1037	    (sign_extend:DI
1038	     (match_operand:SI 0 "register_operand" "l,r,r"))
1039	    (match_operand 1 "arm_addimm_operand" "Pw,I,L"))
1040	  (sign_extend:DI (plus:SI (match_dup 0) (match_dup 1)))))]
1041  "TARGET_32BIT
1042   && INTVAL (operands[1]) == ARM_SIGN_EXTEND (INTVAL (operands[1]))"
1043  "@
1044   cmp%?\\t%0, #%n1
1045   cmn%?\\t%0, %1
1046   cmp%?\\t%0, #%n1"
1047  [(set_attr "conds" "set")
1048   (set_attr "arch" "t2,*,*")
1049   (set_attr "length" "2,4,4")
1050   (set_attr "type" "alus_imm")]
1051)
1052
1053;; We can handle more constants efficently if we can clobber either a scratch
1054;; or the other source operand.  We deliberately leave this late as in
1055;; high register pressure situations it's not worth forcing any reloads.
1056(define_peephole2
1057  [(match_scratch:SI 2 "l")
1058   (set (reg:CC_V CC_REGNUM)
1059	(compare:CC_V
1060	  (plus:DI
1061	    (sign_extend:DI
1062	     (match_operand:SI 0 "low_register_operand"))
1063	    (match_operand 1 "const_int_operand"))
1064	  (sign_extend:DI (plus:SI (match_dup 0) (match_dup 1)))))]
1065  "TARGET_THUMB2
1066   && satisfies_constraint_Pd (operands[1])"
1067  [(parallel[
1068    (set (reg:CC_V CC_REGNUM)
1069	 (compare:CC_V
1070	  (plus:DI (sign_extend:DI (match_dup 0))
1071		   (sign_extend:DI (match_dup 1)))
1072	  (sign_extend:DI (plus:SI (match_dup 0) (match_dup 1)))))
1073    (set (match_dup 2) (plus:SI (match_dup 0) (match_dup 1)))])]
1074)
1075
1076(define_peephole2
1077  [(set (reg:CC_V CC_REGNUM)
1078	(compare:CC_V
1079	  (plus:DI
1080	    (sign_extend:DI
1081	     (match_operand:SI 0 "low_register_operand"))
1082	    (match_operand 1 "const_int_operand"))
1083	  (sign_extend:DI (plus:SI (match_dup 0) (match_dup 1)))))]
1084  "TARGET_THUMB2
1085   && dead_or_set_p (peep2_next_insn (0), operands[0])
1086   && satisfies_constraint_Py (operands[1])"
1087  [(parallel[
1088    (set (reg:CC_V CC_REGNUM)
1089	 (compare:CC_V
1090	  (plus:DI (sign_extend:DI (match_dup 0))
1091		   (sign_extend:DI (match_dup 1)))
1092	  (sign_extend:DI (plus:SI (match_dup 0) (match_dup 1)))))
1093    (set (match_dup 0) (plus:SI (match_dup 0) (match_dup 1)))])]
1094)
1095
1096(define_insn "addsi3_compare0"
1097  [(set (reg:CC_NZ CC_REGNUM)
1098	(compare:CC_NZ
1099	 (plus:SI (match_operand:SI 1 "s_register_operand" "r, r,r")
1100		  (match_operand:SI 2 "arm_add_operand"    "I,L,r"))
1101	 (const_int 0)))
1102   (set (match_operand:SI 0 "s_register_operand" "=r,r,r")
1103	(plus:SI (match_dup 1) (match_dup 2)))]
1104  "TARGET_ARM"
1105  "@
1106   adds%?\\t%0, %1, %2
1107   subs%?\\t%0, %1, #%n2
1108   adds%?\\t%0, %1, %2"
1109  [(set_attr "conds" "set")
1110   (set_attr "type" "alus_imm,alus_imm,alus_sreg")]
1111)
1112
1113(define_insn "*addsi3_compare0_scratch"
1114  [(set (reg:CC_NZ CC_REGNUM)
1115	(compare:CC_NZ
1116	 (plus:SI (match_operand:SI 0 "s_register_operand" "r, r, r")
1117		  (match_operand:SI 1 "arm_add_operand"    "I,L, r"))
1118	 (const_int 0)))]
1119  "TARGET_ARM"
1120  "@
1121   cmn%?\\t%0, %1
1122   cmp%?\\t%0, #%n1
1123   cmn%?\\t%0, %1"
1124  [(set_attr "conds" "set")
1125   (set_attr "predicable" "yes")
1126   (set_attr "type" "alus_imm,alus_imm,alus_sreg")]
1127)
1128
1129(define_insn "*compare_negsi_si"
1130  [(set (reg:CC_Z CC_REGNUM)
1131	(compare:CC_Z
1132	 (neg:SI (match_operand:SI 0 "s_register_operand" "l,r"))
1133	 (match_operand:SI 1 "s_register_operand" "l,r")))]
1134  "TARGET_32BIT"
1135  "cmn%?\\t%1, %0"
1136  [(set_attr "conds" "set")
1137   (set_attr "predicable" "yes")
1138   (set_attr "arch" "t2,*")
1139   (set_attr "length" "2,4")
1140   (set_attr "predicable_short_it" "yes,no")
1141   (set_attr "type" "alus_sreg")]
1142)
1143
1144;; This is the canonicalization of subsi3_compare when the
1145;; addend is a constant.
1146(define_insn "cmpsi2_addneg"
1147  [(set (reg:CC CC_REGNUM)
1148	(compare:CC
1149	 (match_operand:SI 1 "s_register_operand" "r,r")
1150	 (match_operand:SI 2 "arm_addimm_operand" "I,L")))
1151   (set (match_operand:SI 0 "s_register_operand" "=r,r")
1152	(plus:SI (match_dup 1)
1153		 (match_operand:SI 3 "arm_addimm_operand" "L,I")))]
1154  "TARGET_32BIT
1155   && (INTVAL (operands[2])
1156       == trunc_int_for_mode (-INTVAL (operands[3]), SImode))"
1157{
1158  /* For 0 and INT_MIN it is essential that we use subs, as adds will result
1159     in different condition codes (like cmn rather than like cmp), so that
1160     alternative comes first.  Both alternatives can match for any 0x??000000
1161     where except for 0 and INT_MIN it doesn't matter what we choose, and also
1162     for -1 and 1 with TARGET_THUMB2, in that case prefer instruction with #1
1163     as it is shorter.  */
1164  if (which_alternative == 0 && operands[3] != const1_rtx)
1165    return "subs%?\\t%0, %1, #%n3";
1166  else
1167    return "adds%?\\t%0, %1, %3";
1168}
1169  [(set_attr "conds" "set")
1170   (set_attr "type" "alus_sreg")]
1171)
1172
1173;; Convert the sequence
1174;;  sub  rd, rn, #1
1175;;  cmn  rd, #1	(equivalent to cmp rd, #-1)
1176;;  bne  dest
1177;; into
1178;;  subs rd, rn, #1
1179;;  bcs  dest	((unsigned)rn >= 1)
1180;; similarly for the beq variant using bcc.
1181;; This is a common looping idiom (while (n--))
1182(define_peephole2
1183  [(set (match_operand:SI 0 "arm_general_register_operand" "")
1184	(plus:SI (match_operand:SI 1 "arm_general_register_operand" "")
1185		 (const_int -1)))
1186   (set (match_operand 2 "cc_register" "")
1187	(compare (match_dup 0) (const_int -1)))
1188   (set (pc)
1189	(if_then_else (match_operator 3 "equality_operator"
1190		       [(match_dup 2) (const_int 0)])
1191		      (match_operand 4 "" "")
1192		      (match_operand 5 "" "")))]
1193  "TARGET_32BIT && peep2_reg_dead_p (3, operands[2])"
1194  [(parallel[
1195    (set (match_dup 2)
1196	 (compare:CC
1197	  (match_dup 1) (const_int 1)))
1198    (set (match_dup 0) (plus:SI (match_dup 1) (const_int -1)))])
1199   (set (pc)
1200	(if_then_else (match_op_dup 3 [(match_dup 2) (const_int 0)])
1201		      (match_dup 4)
1202		      (match_dup 5)))]
1203  "operands[2] = gen_rtx_REG (CCmode, CC_REGNUM);
1204   operands[3] = gen_rtx_fmt_ee ((GET_CODE (operands[3]) == NE
1205				  ? GEU : LTU),
1206				 VOIDmode,
1207				 operands[2], const0_rtx);"
1208)
1209
1210;; The next four insns work because they compare the result with one of
1211;; the operands, and we know that the use of the condition code is
1212;; either GEU or LTU, so we can use the carry flag from the addition
1213;; instead of doing the compare a second time.
1214(define_insn "addsi3_compare_op1"
1215  [(set (reg:CC_C CC_REGNUM)
1216	(compare:CC_C
1217	 (plus:SI (match_operand:SI 1 "s_register_operand" "l,0,l,0,rk,rk")
1218		  (match_operand:SI 2 "arm_add_operand" "lPd,Py,lPx,Pw,rkI,L"))
1219	 (match_dup 1)))
1220   (set (match_operand:SI 0 "s_register_operand" "=l,l,l,l,rk,rk")
1221	(plus:SI (match_dup 1) (match_dup 2)))]
1222  "TARGET_32BIT"
1223  "@
1224   adds%?\\t%0, %1, %2
1225   adds%?\\t%0, %0, %2
1226   subs%?\\t%0, %1, #%n2
1227   subs%?\\t%0, %0, #%n2
1228   adds%?\\t%0, %1, %2
1229   subs%?\\t%0, %1, #%n2"
1230  [(set_attr "conds" "set")
1231   (set_attr "arch" "t2,t2,t2,t2,*,*")
1232   (set_attr "length" "2,2,2,2,4,4")
1233   (set (attr "type")
1234	(if_then_else (match_operand 2 "const_int_operand")
1235		      (const_string "alu_imm")
1236		      (const_string "alu_sreg")))]
1237)
1238
1239(define_insn "*addsi3_compare_op2"
1240  [(set (reg:CC_C CC_REGNUM)
1241	(compare:CC_C
1242	 (plus:SI (match_operand:SI 1 "s_register_operand" "l,0,l,0,r,r")
1243		  (match_operand:SI 2 "arm_add_operand" "lPd,Py,lPx,Pw,rI,L"))
1244	 (match_dup 2)))
1245   (set (match_operand:SI 0 "s_register_operand" "=l,l,l,l,r,r")
1246	(plus:SI (match_dup 1) (match_dup 2)))]
1247  "TARGET_32BIT"
1248  "@
1249   adds%?\\t%0, %1, %2
1250   adds%?\\t%0, %0, %2
1251   subs%?\\t%0, %1, #%n2
1252   subs%?\\t%0, %0, #%n2
1253   adds%?\\t%0, %1, %2
1254   subs%?\\t%0, %1, #%n2"
1255  [(set_attr "conds" "set")
1256   (set_attr "arch" "t2,t2,t2,t2,*,*")
1257   (set_attr "length" "2,2,2,2,4,4")
1258   (set (attr "type")
1259	(if_then_else (match_operand 2 "const_int_operand")
1260		      (const_string "alu_imm")
1261		      (const_string "alu_sreg")))]
1262)
1263
1264(define_insn "*compare_addsi2_op0"
1265  [(set (reg:CC_C CC_REGNUM)
1266        (compare:CC_C
1267          (plus:SI (match_operand:SI 0 "s_register_operand" "l,l,r,r")
1268                   (match_operand:SI 1 "arm_add_operand"    "l,Pw,rI,L"))
1269          (match_dup 0)))]
1270  "TARGET_32BIT"
1271  "@
1272   cmn%?\\t%0, %1
1273   cmp%?\\t%0, #%n1
1274   cmn%?\\t%0, %1
1275   cmp%?\\t%0, #%n1"
1276  [(set_attr "conds" "set")
1277   (set_attr "predicable" "yes")
1278   (set_attr "arch" "t2,t2,*,*")
1279   (set_attr "predicable_short_it" "yes,yes,no,no")
1280   (set_attr "length" "2,2,4,4")
1281   (set (attr "type")
1282	(if_then_else (match_operand 1 "const_int_operand")
1283		      (const_string "alu_imm")
1284		      (const_string "alu_sreg")))]
1285)
1286
1287(define_insn "*compare_addsi2_op1"
1288  [(set (reg:CC_C CC_REGNUM)
1289        (compare:CC_C
1290          (plus:SI (match_operand:SI 0 "s_register_operand" "l,l,r,r")
1291                   (match_operand:SI 1 "arm_add_operand" "l,Pw,rI,L"))
1292          (match_dup 1)))]
1293  "TARGET_32BIT"
1294  "@
1295   cmn%?\\t%0, %1
1296   cmp%?\\t%0, #%n1
1297   cmn%?\\t%0, %1
1298   cmp%?\\t%0, #%n1"
1299  [(set_attr "conds" "set")
1300   (set_attr "predicable" "yes")
1301   (set_attr "arch" "t2,t2,*,*")
1302   (set_attr "predicable_short_it" "yes,yes,no,no")
1303   (set_attr "length" "2,2,4,4")
1304   (set (attr "type")
1305	(if_then_else (match_operand 1 "const_int_operand")
1306		      (const_string "alu_imm")
1307		      (const_string "alu_sreg")))]
1308 )
1309
1310(define_insn "addsi3_carryin"
1311  [(set (match_operand:SI 0 "s_register_operand" "=l,r,r")
1312        (plus:SI (plus:SI (match_operand:SI 1 "s_register_operand" "%l,r,r")
1313                          (match_operand:SI 2 "arm_not_operand" "0,rI,K"))
1314                 (match_operand:SI 3 "arm_carry_operation" "")))]
1315  "TARGET_32BIT"
1316  "@
1317   adc%?\\t%0, %1, %2
1318   adc%?\\t%0, %1, %2
1319   sbc%?\\t%0, %1, #%B2"
1320  [(set_attr "conds" "use")
1321   (set_attr "predicable" "yes")
1322   (set_attr "arch" "t2,*,*")
1323   (set_attr "length" "4")
1324   (set_attr "predicable_short_it" "yes,no,no")
1325   (set_attr "type" "adc_reg,adc_reg,adc_imm")]
1326)
1327
1328;; Canonicalization of the above when the immediate is zero.
1329(define_insn "add0si3_carryin"
1330  [(set (match_operand:SI 0 "s_register_operand" "=r")
1331	(plus:SI (match_operand:SI 2 "arm_carry_operation" "")
1332		 (match_operand:SI 1 "arm_not_operand" "r")))]
1333  "TARGET_32BIT"
1334  "adc%?\\t%0, %1, #0"
1335  [(set_attr "conds" "use")
1336   (set_attr "predicable" "yes")
1337   (set_attr "length" "4")
1338   (set_attr "type" "adc_imm")]
1339)
1340
1341(define_insn "*addsi3_carryin_alt2"
1342  [(set (match_operand:SI 0 "s_register_operand" "=l,r,r")
1343        (plus:SI (plus:SI (match_operand:SI 3 "arm_carry_operation" "")
1344                          (match_operand:SI 1 "s_register_operand" "%l,r,r"))
1345                 (match_operand:SI 2 "arm_not_operand" "l,rI,K")))]
1346  "TARGET_32BIT"
1347  "@
1348   adc%?\\t%0, %1, %2
1349   adc%?\\t%0, %1, %2
1350   sbc%?\\t%0, %1, #%B2"
1351  [(set_attr "conds" "use")
1352   (set_attr "predicable" "yes")
1353   (set_attr "arch" "t2,*,*")
1354   (set_attr "length" "4")
1355   (set_attr "predicable_short_it" "yes,no,no")
1356   (set_attr "type" "adc_reg,adc_reg,adc_imm")]
1357)
1358
1359(define_insn "*addsi3_carryin_shift"
1360  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1361	(plus:SI (plus:SI
1362		  (match_operator:SI 2 "shift_operator"
1363		    [(match_operand:SI 3 "s_register_operand" "r,r")
1364		     (match_operand:SI 4 "shift_amount_operand" "M,r")])
1365		  (match_operand:SI 5 "arm_carry_operation" ""))
1366		 (match_operand:SI 1 "s_register_operand" "r,r")))]
1367  "TARGET_32BIT"
1368  "adc%?\\t%0, %1, %3%S2"
1369  [(set_attr "conds" "use")
1370   (set_attr "arch" "32,a")
1371   (set_attr "shift" "3")
1372   (set_attr "predicable" "yes")
1373   (set_attr "type" "alu_shift_imm,alu_shift_reg")]
1374)
1375
1376(define_insn "*addsi3_carryin_clobercc"
1377  [(set (match_operand:SI 0 "s_register_operand" "=r")
1378	(plus:SI (plus:SI (match_operand:SI 1 "s_register_operand" "%r")
1379			  (match_operand:SI 2 "arm_rhs_operand" "rI"))
1380		 (match_operand:SI 3 "arm_carry_operation" "")))
1381   (clobber (reg:CC CC_REGNUM))]
1382   "TARGET_32BIT"
1383   "adcs%?\\t%0, %1, %2"
1384   [(set_attr "conds" "set")
1385    (set_attr "type" "adcs_reg")]
1386)
1387
1388(define_expand "subvsi4"
1389  [(match_operand:SI 0 "s_register_operand")
1390   (match_operand:SI 1 "arm_rhs_operand")
1391   (match_operand:SI 2 "arm_add_operand")
1392   (match_operand 3 "")]
1393  "TARGET_32BIT"
1394{
1395  if (CONST_INT_P (operands[1]) && CONST_INT_P (operands[2]))
1396    {
1397      /* If both operands are constants we can decide the result statically.  */
1398      wi::overflow_type overflow;
1399      wide_int val = wi::sub (rtx_mode_t (operands[1], SImode),
1400			      rtx_mode_t (operands[2], SImode),
1401			      SIGNED, &overflow);
1402      emit_move_insn (operands[0], GEN_INT (val.to_shwi ()));
1403      if (overflow != wi::OVF_NONE)
1404	emit_jump_insn (gen_jump (operands[3]));
1405      DONE;
1406    }
1407  else if (CONST_INT_P (operands[2]))
1408    {
1409      operands[2] = GEN_INT (-INTVAL (operands[2]));
1410      /* Special case for INT_MIN.  */
1411      if (INTVAL (operands[2]) == 0x80000000)
1412	emit_insn (gen_subvsi3_intmin (operands[0], operands[1]));
1413      else
1414	emit_insn (gen_addsi3_compareV_imm (operands[0], operands[1],
1415					  operands[2]));
1416    }
1417  else if (CONST_INT_P (operands[1]))
1418    emit_insn (gen_subvsi3_imm1 (operands[0], operands[1], operands[2]));
1419  else
1420    emit_insn (gen_subvsi3 (operands[0], operands[1], operands[2]));
1421
1422  arm_gen_unlikely_cbranch (NE, CC_Vmode, operands[3]);
1423  DONE;
1424})
1425
1426(define_expand "subvdi4"
1427  [(match_operand:DI 0 "s_register_operand")
1428   (match_operand:DI 1 "reg_or_int_operand")
1429   (match_operand:DI 2 "reg_or_int_operand")
1430   (match_operand 3 "")]
1431  "TARGET_32BIT"
1432{
1433  rtx lo_result, hi_result;
1434  rtx lo_op1, hi_op1, lo_op2, hi_op2;
1435  lo_result = gen_lowpart (SImode, operands[0]);
1436  hi_result = gen_highpart (SImode, operands[0]);
1437  machine_mode mode = CCmode;
1438
1439  if (CONST_INT_P (operands[1]) && CONST_INT_P (operands[2]))
1440    {
1441      /* If both operands are constants we can decide the result statically.  */
1442      wi::overflow_type overflow;
1443      wide_int val = wi::sub (rtx_mode_t (operands[1], DImode),
1444			      rtx_mode_t (operands[2], DImode),
1445			      SIGNED, &overflow);
1446      emit_move_insn (operands[0], GEN_INT (val.to_shwi ()));
1447      if (overflow != wi::OVF_NONE)
1448	emit_jump_insn (gen_jump (operands[3]));
1449      DONE;
1450    }
1451  else if (CONST_INT_P (operands[1]))
1452    {
1453      arm_decompose_di_binop (operands[2], operands[1], &lo_op2, &hi_op2,
1454			      &lo_op1, &hi_op1);
1455      if (const_ok_for_arm (INTVAL (lo_op1)))
1456	{
1457	  emit_insn (gen_rsb_imm_compare (lo_result, lo_op1, lo_op2,
1458					  GEN_INT (~UINTVAL (lo_op1))));
1459	  /* We could potentially use RSC here in Arm state, but not
1460	     in Thumb, so it's probably not worth the effort of handling
1461	     this.  */
1462	  hi_op1 = force_reg (SImode, hi_op1);
1463	  mode = CC_RSBmode;
1464	  goto highpart;
1465	}
1466      operands[1] = force_reg (DImode, operands[1]);
1467    }
1468
1469  arm_decompose_di_binop (operands[1], operands[2], &lo_op1, &hi_op1,
1470			  &lo_op2, &hi_op2);
1471  if (lo_op2 == const0_rtx)
1472    {
1473      emit_move_insn (lo_result, lo_op1);
1474      if (!arm_add_operand (hi_op2, SImode))
1475        hi_op2 = force_reg (SImode, hi_op2);
1476      emit_insn (gen_subvsi4 (hi_result, hi_op1, hi_op2, operands[3]));
1477      DONE;
1478    }
1479
1480  if (CONST_INT_P (lo_op2) && !arm_addimm_operand (lo_op2, SImode))
1481    lo_op2 = force_reg (SImode, lo_op2);
1482  if (CONST_INT_P (lo_op2))
1483    emit_insn (gen_cmpsi2_addneg (lo_result, lo_op1, lo_op2,
1484				  gen_int_mode (-INTVAL (lo_op2), SImode)));
1485  else
1486    emit_insn (gen_subsi3_compare1 (lo_result, lo_op1, lo_op2));
1487
1488 highpart:
1489  if (!arm_not_operand (hi_op2, SImode))
1490    hi_op2 = force_reg (SImode, hi_op2);
1491  rtx ccreg = gen_rtx_REG (mode, CC_REGNUM);
1492  if (CONST_INT_P (hi_op2))
1493    emit_insn (gen_subvsi3_borrow_imm (hi_result, hi_op1, hi_op2,
1494				       gen_rtx_LTU (SImode, ccreg, const0_rtx),
1495				       gen_rtx_LTU (DImode, ccreg,
1496						    const0_rtx)));
1497  else
1498    emit_insn (gen_subvsi3_borrow (hi_result, hi_op1, hi_op2,
1499				   gen_rtx_LTU (SImode, ccreg, const0_rtx),
1500				   gen_rtx_LTU (DImode, ccreg, const0_rtx)));
1501  arm_gen_unlikely_cbranch (NE, CC_Vmode, operands[3]);
1502
1503  DONE;
1504})
1505
1506(define_expand "usubvsi4"
1507  [(match_operand:SI 0 "s_register_operand")
1508   (match_operand:SI 1 "arm_rhs_operand")
1509   (match_operand:SI 2 "arm_add_operand")
1510   (match_operand 3 "")]
1511  "TARGET_32BIT"
1512{
1513  machine_mode mode = CCmode;
1514  if (CONST_INT_P (operands[1]) && CONST_INT_P (operands[2]))
1515    {
1516      /* If both operands are constants we can decide the result statically.  */
1517      wi::overflow_type overflow;
1518      wide_int val = wi::sub (rtx_mode_t (operands[1], SImode),
1519			      rtx_mode_t (operands[2], SImode),
1520			      UNSIGNED, &overflow);
1521      emit_move_insn (operands[0], GEN_INT (val.to_shwi ()));
1522      if (overflow != wi::OVF_NONE)
1523	emit_jump_insn (gen_jump (operands[3]));
1524      DONE;
1525    }
1526  else if (CONST_INT_P (operands[2]))
1527    emit_insn (gen_cmpsi2_addneg (operands[0], operands[1], operands[2],
1528				  gen_int_mode (-INTVAL (operands[2]),
1529						SImode)));
1530  else if (CONST_INT_P (operands[1]))
1531    {
1532      mode = CC_RSBmode;
1533      emit_insn (gen_rsb_imm_compare (operands[0], operands[1], operands[2],
1534				      GEN_INT (~UINTVAL (operands[1]))));
1535    }
1536  else
1537    emit_insn (gen_subsi3_compare1 (operands[0], operands[1], operands[2]));
1538  arm_gen_unlikely_cbranch (LTU, mode, operands[3]);
1539
1540  DONE;
1541})
1542
1543(define_expand "usubvdi4"
1544  [(match_operand:DI 0 "s_register_operand")
1545   (match_operand:DI 1 "reg_or_int_operand")
1546   (match_operand:DI 2 "reg_or_int_operand")
1547   (match_operand 3 "")]
1548  "TARGET_32BIT"
1549{
1550  rtx lo_result, hi_result;
1551  rtx lo_op1, hi_op1, lo_op2, hi_op2;
1552  lo_result = gen_lowpart (SImode, operands[0]);
1553  hi_result = gen_highpart (SImode, operands[0]);
1554  machine_mode mode = CCmode;
1555
1556  if (CONST_INT_P (operands[1]) && CONST_INT_P (operands[2]))
1557    {
1558      /* If both operands are constants we can decide the result statically.  */
1559      wi::overflow_type overflow;
1560      wide_int val = wi::sub (rtx_mode_t (operands[1], DImode),
1561			      rtx_mode_t (operands[2], DImode),
1562			      UNSIGNED, &overflow);
1563      emit_move_insn (operands[0], GEN_INT (val.to_shwi ()));
1564      if (overflow != wi::OVF_NONE)
1565	emit_jump_insn (gen_jump (operands[3]));
1566      DONE;
1567    }
1568  else if (CONST_INT_P (operands[1]))
1569    {
1570      arm_decompose_di_binop (operands[2], operands[1], &lo_op2, &hi_op2,
1571			      &lo_op1, &hi_op1);
1572      if (const_ok_for_arm (INTVAL (lo_op1)))
1573	{
1574	  emit_insn (gen_rsb_imm_compare (lo_result, lo_op1, lo_op2,
1575					  GEN_INT (~UINTVAL (lo_op1))));
1576	  /* We could potentially use RSC here in Arm state, but not
1577	     in Thumb, so it's probably not worth the effort of handling
1578	     this.  */
1579	  hi_op1 = force_reg (SImode, hi_op1);
1580	  mode = CC_RSBmode;
1581	  goto highpart;
1582	}
1583      operands[1] = force_reg (DImode, operands[1]);
1584    }
1585
1586  arm_decompose_di_binop (operands[1], operands[2], &lo_op1, &hi_op1,
1587			  &lo_op2, &hi_op2);
1588  if (lo_op2 == const0_rtx)
1589    {
1590      emit_move_insn (lo_result, lo_op1);
1591      if (!arm_add_operand (hi_op2, SImode))
1592        hi_op2 = force_reg (SImode, hi_op2);
1593      emit_insn (gen_usubvsi4 (hi_result, hi_op1, hi_op2, operands[3]));
1594      DONE;
1595    }
1596
1597  if (CONST_INT_P (lo_op2) && !arm_addimm_operand (lo_op2, SImode))
1598    lo_op2 = force_reg (SImode, lo_op2);
1599  if (CONST_INT_P (lo_op2))
1600    emit_insn (gen_cmpsi2_addneg (lo_result, lo_op1, lo_op2,
1601				  gen_int_mode (-INTVAL (lo_op2), SImode)));
1602  else
1603    emit_insn (gen_subsi3_compare1 (lo_result, lo_op1, lo_op2));
1604
1605 highpart:
1606  if (!arm_not_operand (hi_op2, SImode))
1607    hi_op2 = force_reg (SImode, hi_op2);
1608  rtx ccreg = gen_rtx_REG (mode, CC_REGNUM);
1609  if (CONST_INT_P (hi_op2))
1610    emit_insn (gen_usubvsi3_borrow_imm (hi_result, hi_op1, hi_op2,
1611					GEN_INT (UINTVAL (hi_op2) & 0xffffffff),
1612					gen_rtx_LTU (SImode, ccreg, const0_rtx),
1613					gen_rtx_LTU (DImode, ccreg,
1614						     const0_rtx)));
1615  else
1616    emit_insn (gen_usubvsi3_borrow (hi_result, hi_op1, hi_op2,
1617				    gen_rtx_LTU (SImode, ccreg, const0_rtx),
1618				    gen_rtx_LTU (DImode, ccreg, const0_rtx)));
1619  arm_gen_unlikely_cbranch (LTU, CC_Bmode, operands[3]);
1620
1621  DONE;
1622})
1623
1624(define_insn "subsi3_compare1"
1625  [(set (reg:CC CC_REGNUM)
1626	(compare:CC
1627	  (match_operand:SI 1 "register_operand" "r")
1628	  (match_operand:SI 2 "register_operand" "r")))
1629   (set (match_operand:SI 0 "register_operand" "=r")
1630	(minus:SI (match_dup 1) (match_dup 2)))]
1631  "TARGET_32BIT"
1632  "subs%?\\t%0, %1, %2"
1633  [(set_attr "conds" "set")
1634   (set_attr "type" "alus_sreg")]
1635)
1636
1637(define_insn "subvsi3"
1638  [(set (reg:CC_V CC_REGNUM)
1639	(compare:CC_V
1640	 (minus:DI
1641	  (sign_extend:DI (match_operand:SI 1 "s_register_operand" "l,r"))
1642	  (sign_extend:DI (match_operand:SI 2 "s_register_operand" "l,r")))
1643	 (sign_extend:DI (minus:SI (match_dup 1) (match_dup 2)))))
1644   (set (match_operand:SI 0 "s_register_operand" "=l,r")
1645	(minus:SI (match_dup 1) (match_dup 2)))]
1646  "TARGET_32BIT"
1647  "subs%?\\t%0, %1, %2"
1648  [(set_attr "conds" "set")
1649   (set_attr "arch" "t2,*")
1650   (set_attr "length" "2,4")
1651   (set_attr "type" "alus_sreg")]
1652)
1653
1654(define_insn "subvsi3_imm1"
1655  [(set (reg:CC_V CC_REGNUM)
1656	(compare:CC_V
1657	 (minus:DI
1658	  (match_operand 1 "arm_immediate_operand" "I")
1659	  (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r")))
1660	 (sign_extend:DI (minus:SI (match_dup 1) (match_dup 2)))))
1661   (set (match_operand:SI 0 "s_register_operand" "=r")
1662	(minus:SI (match_dup 1) (match_dup 2)))]
1663  "TARGET_32BIT"
1664  "rsbs%?\\t%0, %2, %1"
1665  [(set_attr "conds" "set")
1666   (set_attr "type" "alus_imm")]
1667)
1668
1669(define_insn "subsi3_carryin"
1670  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
1671	(minus:SI (minus:SI (match_operand:SI 1 "reg_or_int_operand" "r,I,Pz")
1672			    (match_operand:SI 2 "s_register_operand" "r,r,r"))
1673		  (match_operand:SI 3 "arm_borrow_operation" "")))]
1674  "TARGET_32BIT"
1675  "@
1676   sbc%?\\t%0, %1, %2
1677   rsc%?\\t%0, %2, %1
1678   sbc%?\\t%0, %2, %2, lsl #1"
1679  [(set_attr "conds" "use")
1680   (set_attr "arch" "*,a,t2")
1681   (set_attr "predicable" "yes")
1682   (set_attr "type" "adc_reg,adc_imm,alu_shift_imm")]
1683)
1684
1685;; Special canonicalization of the above when operand1 == (const_int 1):
1686;; in this case the 'borrow' needs to treated like subtracting from the carry.
1687(define_insn "rsbsi_carryin_reg"
1688  [(set (match_operand:SI 0 "s_register_operand" "=r")
1689	(minus:SI (match_operand:SI 1 "arm_carry_operation" "")
1690		  (match_operand:SI 2 "s_register_operand" "r")))]
1691  "TARGET_ARM"
1692  "rsc%?\\t%0, %2, #1"
1693  [(set_attr "conds" "use")
1694   (set_attr "predicable" "yes")
1695   (set_attr "type" "adc_imm")]
1696)
1697
1698;; SBC performs Rn - Rm - ~C, but -Rm = ~Rm + 1 => Rn + ~Rm + 1 - ~C
1699;; => Rn + ~Rm + C, which is essentially ADC Rd, Rn, ~Rm
1700(define_insn "*add_not_cin"
1701  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1702	(plus:SI
1703	 (plus:SI (not:SI (match_operand:SI 1 "s_register_operand" "r,r"))
1704		  (match_operand:SI 3 "arm_carry_operation" ""))
1705	 (match_operand:SI 2 "arm_rhs_operand" "r,I")))]
1706  "TARGET_ARM || (TARGET_THUMB2 && !CONST_INT_P (operands[2]))"
1707  "@
1708   sbc%?\\t%0, %2, %1
1709   rsc%?\\t%0, %1, %2"
1710  [(set_attr "conds" "use")
1711   (set_attr "predicable" "yes")
1712   (set_attr "arch" "*,a")
1713   (set_attr "type" "adc_reg,adc_imm")]
1714)
1715
1716;; On Arm we can also use the same trick when the non-inverted operand is
1717;; shifted, using RSC.
1718(define_insn "add_not_shift_cin"
1719  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1720	(plus:SI
1721	 (plus:SI (match_operator:SI 3 "shift_operator"
1722		   [(match_operand:SI 1 "s_register_operand" "r,r")
1723		    (match_operand:SI 2 "shift_amount_operand" "M,r")])
1724		  (not:SI (match_operand:SI 4 "s_register_operand" "r,r")))
1725	 (match_operand:SI 5 "arm_carry_operation" "")))]
1726  "TARGET_ARM"
1727  "rsc%?\\t%0, %4, %1%S3"
1728  [(set_attr "conds" "use")
1729   (set_attr "predicable" "yes")
1730   (set_attr "type" "alu_shift_imm,alu_shift_reg")]
1731)
1732
1733(define_insn "cmpsi3_carryin_<CC_EXTEND>out"
1734  [(set (reg:<CC_EXTEND> CC_REGNUM)
1735	(compare:<CC_EXTEND>
1736	 (SE:DI (match_operand:SI 1 "s_register_operand" "0,r"))
1737	 (plus:DI (match_operand:DI 3 "arm_borrow_operation" "")
1738		  (SE:DI (match_operand:SI 2 "s_register_operand" "l,r")))))
1739   (clobber (match_scratch:SI 0 "=l,r"))]
1740  "TARGET_32BIT"
1741  "sbcs\\t%0, %1, %2"
1742  [(set_attr "conds" "set")
1743   (set_attr "arch" "t2,*")
1744   (set_attr "length" "2,4")
1745   (set_attr "type" "adc_reg")]
1746)
1747
1748;; Similar to the above, but handling a constant which has a different
1749;; canonicalization.
1750(define_insn "cmpsi3_imm_carryin_<CC_EXTEND>out"
1751  [(set (reg:<CC_EXTEND> CC_REGNUM)
1752	(compare:<CC_EXTEND>
1753	 (SE:DI (match_operand:SI 1 "s_register_operand" "r,r"))
1754	 (plus:DI (match_operand:DI 3 "arm_borrow_operation" "")
1755		  (match_operand:DI 2 "arm_adcimm_operand" "I,K"))))
1756   (clobber (match_scratch:SI 0 "=l,r"))]
1757  "TARGET_32BIT"
1758  "@
1759   sbcs\\t%0, %1, %2
1760   adcs\\t%0, %1, #%B2"
1761  [(set_attr "conds" "set")
1762   (set_attr "type" "adc_imm")]
1763)
1764
1765;; Further canonicalization when the constant is zero.
1766(define_insn "cmpsi3_0_carryin_<CC_EXTEND>out"
1767  [(set (reg:<CC_EXTEND> CC_REGNUM)
1768	(compare:<CC_EXTEND>
1769	 (SE:DI (match_operand:SI 1 "s_register_operand" "r,r"))
1770	 (match_operand:DI 2 "arm_borrow_operation" "")))
1771   (clobber (match_scratch:SI 0 "=l,r"))]
1772  "TARGET_32BIT"
1773  "sbcs\\t%0, %1, #0"
1774  [(set_attr "conds" "set")
1775   (set_attr "type" "adc_imm")]
1776)
1777
1778(define_insn "*subsi3_carryin_const"
1779  [(set (match_operand:SI 0 "s_register_operand" "=r")
1780	(minus:SI (plus:SI
1781		   (match_operand:SI 1 "s_register_operand" "r")
1782		   (match_operand:SI 2 "arm_neg_immediate_operand" "L"))
1783		  (match_operand:SI 3 "arm_borrow_operation" "")))]
1784  "TARGET_32BIT"
1785  "sbc\\t%0, %1, #%n2"
1786  [(set_attr "conds" "use")
1787   (set_attr "type" "adc_imm")]
1788)
1789
1790(define_insn "*subsi3_carryin_const0"
1791  [(set (match_operand:SI 0 "s_register_operand" "=r")
1792	(minus:SI (match_operand:SI 1 "s_register_operand" "r")
1793		  (match_operand:SI 2 "arm_borrow_operation" "")))]
1794  "TARGET_32BIT"
1795  "sbc\\t%0, %1, #0"
1796  [(set_attr "conds" "use")
1797   (set_attr "type" "adc_imm")]
1798)
1799
1800(define_insn "*subsi3_carryin_shift"
1801  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1802	(minus:SI (minus:SI
1803		   (match_operand:SI 1 "s_register_operand" "r,r")
1804		   (match_operator:SI 2 "shift_operator"
1805		    [(match_operand:SI 3 "s_register_operand" "r,r")
1806		     (match_operand:SI 4 "shift_amount_operand" "M,r")]))
1807		  (match_operand:SI 5 "arm_borrow_operation" "")))]
1808  "TARGET_32BIT"
1809  "sbc%?\\t%0, %1, %3%S2"
1810  [(set_attr "conds" "use")
1811   (set_attr "arch" "32,a")
1812   (set_attr "shift" "3")
1813   (set_attr "predicable" "yes")
1814   (set_attr "type" "alu_shift_imm,alu_shift_reg")]
1815)
1816
1817(define_insn "*subsi3_carryin_shift_alt"
1818  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1819	(minus:SI (minus:SI
1820		   (match_operand:SI 1 "s_register_operand" "r,r")
1821		   (match_operand:SI 5 "arm_borrow_operation" ""))
1822		  (match_operator:SI 2 "shift_operator"
1823		   [(match_operand:SI 3 "s_register_operand" "r,r")
1824		    (match_operand:SI 4 "shift_amount_operand" "M,r")])))]
1825  "TARGET_32BIT"
1826  "sbc%?\\t%0, %1, %3%S2"
1827  [(set_attr "conds" "use")
1828   (set_attr "arch" "32,a")
1829   (set_attr "shift" "3")
1830   (set_attr "predicable" "yes")
1831   (set_attr "type" "alu_shift_imm,alu_shift_reg")]
1832)
1833
1834;; No RSC in Thumb2
1835(define_insn "*rsbsi3_carryin_shift"
1836  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1837	(minus:SI (minus:SI
1838		   (match_operator:SI 2 "shift_operator"
1839		    [(match_operand:SI 3 "s_register_operand" "r,r")
1840		     (match_operand:SI 4 "shift_amount_operand" "M,r")])
1841		   (match_operand:SI 1 "s_register_operand" "r,r"))
1842		  (match_operand:SI 5 "arm_borrow_operation" "")))]
1843  "TARGET_ARM"
1844  "rsc%?\\t%0, %1, %3%S2"
1845  [(set_attr "conds" "use")
1846   (set_attr "predicable" "yes")
1847   (set_attr "type" "alu_shift_imm,alu_shift_reg")]
1848)
1849
1850(define_insn "*rsbsi3_carryin_shift_alt"
1851  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1852	(minus:SI (minus:SI
1853		   (match_operator:SI 2 "shift_operator"
1854		    [(match_operand:SI 3 "s_register_operand" "r,r")
1855		     (match_operand:SI 4 "shift_amount_operand" "M,r")])
1856		    (match_operand:SI 5 "arm_borrow_operation" ""))
1857		  (match_operand:SI 1 "s_register_operand" "r,r")))]
1858  "TARGET_ARM"
1859  "rsc%?\\t%0, %1, %3%S2"
1860  [(set_attr "conds" "use")
1861   (set_attr "predicable" "yes")
1862   (set_attr "type" "alu_shift_imm,alu_shift_reg")]
1863)
1864
1865; transform ((x << y) - 1) to ~(~(x-1) << y)  Where X is a constant.
1866(define_split
1867  [(set (match_operand:SI 0 "s_register_operand" "")
1868	(plus:SI (ashift:SI (match_operand:SI 1 "const_int_operand" "")
1869			    (match_operand:SI 2 "s_register_operand" ""))
1870		 (const_int -1)))
1871   (clobber (match_operand:SI 3 "s_register_operand" ""))]
1872  "TARGET_32BIT"
1873  [(set (match_dup 3) (match_dup 1))
1874   (set (match_dup 0) (not:SI (ashift:SI (match_dup 3) (match_dup 2))))]
1875  "
1876  operands[1] = GEN_INT (~(INTVAL (operands[1]) - 1));
1877")
1878
1879(define_expand "addsf3"
1880  [(set (match_operand:SF          0 "s_register_operand")
1881	(plus:SF (match_operand:SF 1 "s_register_operand")
1882		 (match_operand:SF 2 "s_register_operand")))]
1883  "TARGET_32BIT && TARGET_HARD_FLOAT"
1884  "
1885")
1886
1887(define_expand "adddf3"
1888  [(set (match_operand:DF          0 "s_register_operand")
1889	(plus:DF (match_operand:DF 1 "s_register_operand")
1890		 (match_operand:DF 2 "s_register_operand")))]
1891  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
1892  "
1893")
1894
1895(define_expand "subdi3"
1896 [(parallel
1897   [(set (match_operand:DI            0 "s_register_operand")
1898	  (minus:DI (match_operand:DI 1 "reg_or_int_operand")
1899		    (match_operand:DI 2 "s_register_operand")))
1900    (clobber (reg:CC CC_REGNUM))])]
1901  "TARGET_EITHER"
1902  "
1903  if (TARGET_THUMB1)
1904    {
1905      if (!REG_P (operands[1]))
1906	operands[1] = force_reg (DImode, operands[1]);
1907    }
1908  else
1909    {
1910      rtx lo_result, hi_result, lo_dest, hi_dest;
1911      rtx lo_op1, hi_op1, lo_op2, hi_op2;
1912      rtx condition;
1913
1914      /* Since operands[1] may be an integer, pass it second, so that
1915	 any necessary simplifications will be done on the decomposed
1916	 constant.  */
1917      arm_decompose_di_binop (operands[2], operands[1], &lo_op2, &hi_op2,
1918			      &lo_op1, &hi_op1);
1919      lo_result = lo_dest = gen_lowpart (SImode, operands[0]);
1920      hi_result = hi_dest = gen_highpart (SImode, operands[0]);
1921
1922      if (!arm_rhs_operand (lo_op1, SImode))
1923	lo_op1 = force_reg (SImode, lo_op1);
1924
1925      if ((TARGET_THUMB2 && ! s_register_operand (hi_op1, SImode))
1926	  || !arm_rhs_operand (hi_op1, SImode))
1927	hi_op1 = force_reg (SImode, hi_op1);
1928
1929      rtx cc_reg;
1930      if (lo_op1 == const0_rtx)
1931	{
1932	  cc_reg = gen_rtx_REG (CC_RSBmode, CC_REGNUM);
1933	  emit_insn (gen_negsi2_0compare (lo_dest, lo_op2));
1934	}
1935      else if (CONST_INT_P (lo_op1))
1936	{
1937	  cc_reg = gen_rtx_REG (CC_RSBmode, CC_REGNUM);
1938	  emit_insn (gen_rsb_imm_compare (lo_dest, lo_op1, lo_op2,
1939					  GEN_INT (~UINTVAL (lo_op1))));
1940	}
1941      else
1942	{
1943	  cc_reg = gen_rtx_REG (CCmode, CC_REGNUM);
1944	  emit_insn (gen_subsi3_compare (lo_dest, lo_op1, lo_op2));
1945	}
1946
1947      condition = gen_rtx_LTU (SImode, cc_reg, const0_rtx);
1948
1949      if (hi_op1 == const0_rtx)
1950        emit_insn (gen_negsi2_carryin (hi_dest, hi_op2, condition));
1951      else
1952	emit_insn (gen_subsi3_carryin (hi_dest, hi_op1, hi_op2, condition));
1953
1954      if (lo_result != lo_dest)
1955	emit_move_insn (lo_result, lo_dest);
1956
1957      if (hi_result != hi_dest)
1958	emit_move_insn (hi_result, hi_dest);
1959
1960      DONE;
1961    }
1962  "
1963)
1964
1965(define_expand "subsi3"
1966  [(set (match_operand:SI           0 "s_register_operand")
1967	(minus:SI (match_operand:SI 1 "reg_or_int_operand")
1968		  (match_operand:SI 2 "s_register_operand")))]
1969  "TARGET_EITHER"
1970  "
1971  if (CONST_INT_P (operands[1]))
1972    {
1973      if (TARGET_32BIT)
1974        {
1975	  if (DONT_EARLY_SPLIT_CONSTANT (INTVAL (operands[1]), MINUS))
1976	    operands[1] = force_reg (SImode, operands[1]);
1977	  else
1978	    {
1979	      arm_split_constant (MINUS, SImode, NULL_RTX,
1980				  INTVAL (operands[1]), operands[0],
1981				  operands[2],
1982				  optimize && can_create_pseudo_p ());
1983	      DONE;
1984	    }
1985	}
1986      else /* TARGET_THUMB1 */
1987        operands[1] = force_reg (SImode, operands[1]);
1988    }
1989  "
1990)
1991
1992; ??? Check Thumb-2 split length
1993(define_insn_and_split "*arm_subsi3_insn"
1994  [(set (match_operand:SI           0 "s_register_operand" "=l,l ,l ,l ,r,r,r,rk,r")
1995	(minus:SI (match_operand:SI 1 "reg_or_int_operand" "l ,0 ,l ,Pz,I,r,r,k ,?n")
1996		  (match_operand:SI 2 "reg_or_int_operand" "l ,Py,Pd,l ,r,I,r,r ,r")))]
1997  "TARGET_32BIT"
1998  "@
1999   sub%?\\t%0, %1, %2
2000   sub%?\\t%0, %2
2001   sub%?\\t%0, %1, %2
2002   rsb%?\\t%0, %2, %1
2003   rsb%?\\t%0, %2, %1
2004   sub%?\\t%0, %1, %2
2005   sub%?\\t%0, %1, %2
2006   sub%?\\t%0, %1, %2
2007   #"
2008  "&& (CONST_INT_P (operands[1])
2009       && !const_ok_for_arm (INTVAL (operands[1])))"
2010  [(clobber (const_int 0))]
2011  "
2012  arm_split_constant (MINUS, SImode, curr_insn,
2013                      INTVAL (operands[1]), operands[0], operands[2], 0);
2014  DONE;
2015  "
2016  [(set_attr "length" "4,4,4,4,4,4,4,4,16")
2017   (set_attr "arch" "t2,t2,t2,t2,*,*,*,*,*")
2018   (set_attr "predicable" "yes")
2019   (set_attr "predicable_short_it" "yes,yes,yes,yes,no,no,no,no,no")
2020   (set_attr "type" "alu_sreg,alu_sreg,alu_sreg,alu_sreg,alu_imm,alu_imm,alu_sreg,alu_sreg,multiple")]
2021)
2022
2023(define_peephole2
2024  [(match_scratch:SI 3 "r")
2025   (set (match_operand:SI 0 "arm_general_register_operand" "")
2026	(minus:SI (match_operand:SI 1 "const_int_operand" "")
2027		  (match_operand:SI 2 "arm_general_register_operand" "")))]
2028  "TARGET_32BIT
2029   && !const_ok_for_arm (INTVAL (operands[1]))
2030   && const_ok_for_arm (~INTVAL (operands[1]))"
2031  [(set (match_dup 3) (match_dup 1))
2032   (set (match_dup 0) (minus:SI (match_dup 3) (match_dup 2)))]
2033  ""
2034)
2035
2036(define_insn "subsi3_compare0"
2037  [(set (reg:CC_NZ CC_REGNUM)
2038	(compare:CC_NZ
2039	 (minus:SI (match_operand:SI 1 "arm_rhs_operand" "r,r,I")
2040		   (match_operand:SI 2 "arm_rhs_operand" "I,r,r"))
2041	 (const_int 0)))
2042   (set (match_operand:SI 0 "s_register_operand" "=r,r,r")
2043	(minus:SI (match_dup 1) (match_dup 2)))]
2044  "TARGET_32BIT"
2045  "@
2046   subs%?\\t%0, %1, %2
2047   subs%?\\t%0, %1, %2
2048   rsbs%?\\t%0, %2, %1"
2049  [(set_attr "conds" "set")
2050   (set_attr "type"  "alus_imm,alus_sreg,alus_sreg")]
2051)
2052
2053(define_insn "subsi3_compare"
2054  [(set (reg:CC CC_REGNUM)
2055	(compare:CC (match_operand:SI 1 "arm_rhs_operand" "r,r,I")
2056		    (match_operand:SI 2 "arm_rhs_operand" "I,r,r")))
2057   (set (match_operand:SI 0 "s_register_operand" "=r,r,r")
2058	(minus:SI (match_dup 1) (match_dup 2)))]
2059  "TARGET_32BIT"
2060  "@
2061   subs%?\\t%0, %1, %2
2062   subs%?\\t%0, %1, %2
2063   rsbs%?\\t%0, %2, %1"
2064  [(set_attr "conds" "set")
2065   (set_attr "type" "alus_imm,alus_sreg,alus_imm")]
2066)
2067
2068;; To keep the comparison in canonical form we express it as (~reg cmp ~0)
2069;; rather than (0 cmp reg).  This gives the same results for unsigned
2070;; and equality compares which is what we mostly need here.
2071(define_insn "rsb_imm_compare"
2072  [(set (reg:CC_RSB CC_REGNUM)
2073	(compare:CC_RSB (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2074			(match_operand 3 "const_int_operand" "")))
2075   (set (match_operand:SI 0 "s_register_operand" "=r")
2076	(minus:SI (match_operand 1 "arm_immediate_operand" "I")
2077		  (match_dup 2)))]
2078  "TARGET_32BIT && ~UINTVAL (operands[1]) == UINTVAL (operands[3])"
2079  "rsbs\\t%0, %2, %1"
2080  [(set_attr "conds" "set")
2081   (set_attr "type" "alus_imm")]
2082)
2083
2084;; Similarly, but the result is unused.
2085(define_insn "rsb_imm_compare_scratch"
2086  [(set (reg:CC_RSB CC_REGNUM)
2087	(compare:CC_RSB (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2088			(match_operand 1 "arm_not_immediate_operand" "K")))
2089   (clobber (match_scratch:SI 0 "=r"))]
2090  "TARGET_32BIT"
2091  "rsbs\\t%0, %2, #%B1"
2092  [(set_attr "conds" "set")
2093   (set_attr "type" "alus_imm")]
2094)
2095
2096;; Compare the sum of a value plus a carry against a constant.  Uses
2097;; RSC, so the result is swapped.  Only available on Arm
2098(define_insn "rscsi3_<CC_EXTEND>out_scratch"
2099  [(set (reg:CC_SWP CC_REGNUM)
2100	(compare:CC_SWP
2101	 (plus:DI (SE:DI (match_operand:SI 2 "s_register_operand" "r"))
2102		  (match_operand:DI 3 "arm_borrow_operation" ""))
2103	 (match_operand 1 "arm_immediate_operand" "I")))
2104   (clobber (match_scratch:SI 0 "=r"))]
2105  "TARGET_ARM"
2106  "rscs\\t%0, %2, %1"
2107  [(set_attr "conds" "set")
2108   (set_attr "type" "alus_imm")]
2109)
2110
2111(define_insn "usubvsi3_borrow"
2112  [(set (reg:CC_B CC_REGNUM)
2113	(compare:CC_B
2114	 (zero_extend:DI (match_operand:SI 1 "s_register_operand" "0,r"))
2115	 (plus:DI (match_operand:DI 4 "arm_borrow_operation" "")
2116	          (zero_extend:DI
2117		   (match_operand:SI 2 "s_register_operand" "l,r")))))
2118   (set (match_operand:SI 0 "s_register_operand" "=l,r")
2119	(minus:SI (match_dup 1)
2120		  (plus:SI (match_operand:SI 3 "arm_borrow_operation" "")
2121			   (match_dup 2))))]
2122  "TARGET_32BIT"
2123  "sbcs%?\\t%0, %1, %2"
2124  [(set_attr "conds" "set")
2125   (set_attr "arch" "t2,*")
2126   (set_attr "length" "2,4")]
2127)
2128
2129(define_insn "usubvsi3_borrow_imm"
2130  [(set (reg:CC_B CC_REGNUM)
2131	(compare:CC_B
2132	 (zero_extend:DI (match_operand:SI 1 "s_register_operand" "r,r"))
2133	 (plus:DI (match_operand:DI 5 "arm_borrow_operation" "")
2134		  (match_operand:DI 3 "const_int_operand" "n,n"))))
2135   (set (match_operand:SI 0 "s_register_operand" "=r,r")
2136	(minus:SI (match_dup 1)
2137		  (plus:SI (match_operand:SI 4 "arm_borrow_operation" "")
2138			   (match_operand:SI 2 "arm_adcimm_operand" "I,K"))))]
2139  "TARGET_32BIT
2140   && (UINTVAL (operands[2]) & 0xffffffff) == UINTVAL (operands[3])"
2141  "@
2142  sbcs%?\\t%0, %1, %2
2143  adcs%?\\t%0, %1, #%B2"
2144  [(set_attr "conds" "set")
2145   (set_attr "type" "alus_imm")]
2146)
2147
2148(define_insn "subvsi3_borrow"
2149  [(set (reg:CC_V CC_REGNUM)
2150	(compare:CC_V
2151	 (minus:DI
2152	  (minus:DI
2153	   (sign_extend:DI (match_operand:SI 1 "s_register_operand" "0,r"))
2154	   (sign_extend:DI (match_operand:SI 2 "s_register_operand" "l,r")))
2155	  (match_operand:DI 4 "arm_borrow_operation" ""))
2156	 (sign_extend:DI
2157	  (minus:SI (minus:SI (match_dup 1) (match_dup 2))
2158		    (match_operand:SI 3 "arm_borrow_operation" "")))))
2159   (set (match_operand:SI 0 "s_register_operand" "=l,r")
2160	(minus:SI (minus:SI (match_dup 1) (match_dup 2))
2161		  (match_dup 3)))]
2162  "TARGET_32BIT"
2163  "sbcs%?\\t%0, %1, %2"
2164  [(set_attr "conds" "set")
2165   (set_attr "arch" "t2,*")
2166   (set_attr "length" "2,4")]
2167)
2168
2169(define_insn "subvsi3_borrow_imm"
2170  [(set (reg:CC_V CC_REGNUM)
2171	(compare:CC_V
2172	 (minus:DI
2173	  (minus:DI
2174	   (sign_extend:DI (match_operand:SI 1 "s_register_operand" "r,r"))
2175	   (match_operand 2 "arm_adcimm_operand" "I,K"))
2176	  (match_operand:DI 4 "arm_borrow_operation" ""))
2177	 (sign_extend:DI
2178	  (minus:SI (minus:SI (match_dup 1) (match_dup 2))
2179		    (match_operand:SI 3 "arm_borrow_operation" "")))))
2180   (set (match_operand:SI 0 "s_register_operand" "=r,r")
2181	(minus:SI (minus:SI (match_dup 1) (match_dup 2))
2182		  (match_dup 3)))]
2183  "TARGET_32BIT
2184   && INTVAL (operands[2]) == ARM_SIGN_EXTEND (INTVAL (operands[2]))"
2185  "@
2186  sbcs%?\\t%0, %1, %2
2187  adcs%?\\t%0, %1, #%B2"
2188  [(set_attr "conds" "set")
2189   (set_attr "type" "alus_imm")]
2190)
2191
2192(define_expand "subsf3"
2193  [(set (match_operand:SF           0 "s_register_operand")
2194	(minus:SF (match_operand:SF 1 "s_register_operand")
2195		  (match_operand:SF 2 "s_register_operand")))]
2196  "TARGET_32BIT && TARGET_HARD_FLOAT"
2197  "
2198")
2199
2200(define_expand "subdf3"
2201  [(set (match_operand:DF           0 "s_register_operand")
2202	(minus:DF (match_operand:DF 1 "s_register_operand")
2203		  (match_operand:DF 2 "s_register_operand")))]
2204  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
2205  "
2206")
2207
2208
2209;; Multiplication insns
2210
2211(define_expand "mulhi3"
2212  [(set (match_operand:HI 0 "s_register_operand")
2213	(mult:HI (match_operand:HI 1 "s_register_operand")
2214		 (match_operand:HI 2 "s_register_operand")))]
2215  "TARGET_DSP_MULTIPLY"
2216  "
2217  {
2218    rtx result = gen_reg_rtx (SImode);
2219    emit_insn (gen_mulhisi3 (result, operands[1], operands[2]));
2220    emit_move_insn (operands[0], gen_lowpart (HImode, result));
2221    DONE;
2222  }"
2223)
2224
2225(define_expand "mulsi3"
2226  [(set (match_operand:SI          0 "s_register_operand")
2227	(mult:SI (match_operand:SI 2 "s_register_operand")
2228		 (match_operand:SI 1 "s_register_operand")))]
2229  "TARGET_EITHER"
2230  ""
2231)
2232
2233;; Use `&' and then `0' to prevent operands 0 and 2 being the same
2234(define_insn "*mul"
2235  [(set (match_operand:SI          0 "s_register_operand" "=l,r,&r,&r")
2236	(mult:SI (match_operand:SI 2 "s_register_operand" "l,r,r,r")
2237		 (match_operand:SI 1 "s_register_operand" "%0,r,0,r")))]
2238  "TARGET_32BIT"
2239  "mul%?\\t%0, %2, %1"
2240  [(set_attr "type" "mul")
2241   (set_attr "predicable" "yes")
2242   (set_attr "arch" "t2,v6,nov6,nov6")
2243   (set_attr "length" "4")
2244   (set_attr "predicable_short_it" "yes,no,*,*")]
2245)
2246
2247;; MLA and MLS instruction. Use operand 1 for the accumulator to prefer
2248;; reusing the same register.
2249
2250(define_insn "*mla"
2251  [(set (match_operand:SI 0 "s_register_operand" "=r,&r,&r,&r")
2252	(plus:SI
2253	  (mult:SI (match_operand:SI 3 "s_register_operand" "r,r,r,r")
2254		   (match_operand:SI 2 "s_register_operand" "%r,r,0,r"))
2255	  (match_operand:SI 1 "s_register_operand" "r,0,r,r")))]
2256  "TARGET_32BIT"
2257  "mla%?\\t%0, %3, %2, %1"
2258  [(set_attr "type" "mla")
2259   (set_attr "predicable" "yes")
2260   (set_attr "arch" "v6,nov6,nov6,nov6")]
2261)
2262
2263(define_insn "*mls"
2264  [(set (match_operand:SI 0 "s_register_operand" "=r")
2265	(minus:SI
2266	  (match_operand:SI 1 "s_register_operand" "r")
2267	  (mult:SI (match_operand:SI 3 "s_register_operand" "r")
2268		   (match_operand:SI 2 "s_register_operand" "r"))))]
2269  "TARGET_32BIT && arm_arch_thumb2"
2270  "mls%?\\t%0, %3, %2, %1"
2271  [(set_attr "type" "mla")
2272   (set_attr "predicable" "yes")]
2273)
2274
2275(define_insn "*mulsi3_compare0"
2276  [(set (reg:CC_NZ CC_REGNUM)
2277	(compare:CC_NZ (mult:SI
2278			  (match_operand:SI 2 "s_register_operand" "r,r")
2279			  (match_operand:SI 1 "s_register_operand" "%0,r"))
2280			 (const_int 0)))
2281   (set (match_operand:SI 0 "s_register_operand" "=&r,&r")
2282	(mult:SI (match_dup 2) (match_dup 1)))]
2283  "TARGET_ARM && !arm_arch6"
2284  "muls%?\\t%0, %2, %1"
2285  [(set_attr "conds" "set")
2286   (set_attr "type" "muls")]
2287)
2288
2289(define_insn "*mulsi3_compare0_v6"
2290  [(set (reg:CC_NZ CC_REGNUM)
2291	(compare:CC_NZ (mult:SI
2292			  (match_operand:SI 2 "s_register_operand" "r")
2293			  (match_operand:SI 1 "s_register_operand" "r"))
2294			 (const_int 0)))
2295   (set (match_operand:SI 0 "s_register_operand" "=r")
2296	(mult:SI (match_dup 2) (match_dup 1)))]
2297  "TARGET_ARM && arm_arch6 && optimize_size"
2298  "muls%?\\t%0, %2, %1"
2299  [(set_attr "conds" "set")
2300   (set_attr "type" "muls")]
2301)
2302
2303(define_insn "*mulsi_compare0_scratch"
2304  [(set (reg:CC_NZ CC_REGNUM)
2305	(compare:CC_NZ (mult:SI
2306			  (match_operand:SI 2 "s_register_operand" "r,r")
2307			  (match_operand:SI 1 "s_register_operand" "%0,r"))
2308			 (const_int 0)))
2309   (clobber (match_scratch:SI 0 "=&r,&r"))]
2310  "TARGET_ARM && !arm_arch6"
2311  "muls%?\\t%0, %2, %1"
2312  [(set_attr "conds" "set")
2313   (set_attr "type" "muls")]
2314)
2315
2316(define_insn "*mulsi_compare0_scratch_v6"
2317  [(set (reg:CC_NZ CC_REGNUM)
2318	(compare:CC_NZ (mult:SI
2319			  (match_operand:SI 2 "s_register_operand" "r")
2320			  (match_operand:SI 1 "s_register_operand" "r"))
2321			 (const_int 0)))
2322   (clobber (match_scratch:SI 0 "=r"))]
2323  "TARGET_ARM && arm_arch6 && optimize_size"
2324  "muls%?\\t%0, %2, %1"
2325  [(set_attr "conds" "set")
2326   (set_attr "type" "muls")]
2327)
2328
2329(define_insn "*mulsi3addsi_compare0"
2330  [(set (reg:CC_NZ CC_REGNUM)
2331	(compare:CC_NZ
2332	 (plus:SI (mult:SI
2333		   (match_operand:SI 2 "s_register_operand" "r,r,r,r")
2334		   (match_operand:SI 1 "s_register_operand" "%0,r,0,r"))
2335		  (match_operand:SI 3 "s_register_operand" "r,r,0,0"))
2336	 (const_int 0)))
2337   (set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r,&r")
2338	(plus:SI (mult:SI (match_dup 2) (match_dup 1))
2339		 (match_dup 3)))]
2340  "TARGET_ARM && arm_arch6"
2341  "mlas%?\\t%0, %2, %1, %3"
2342  [(set_attr "conds" "set")
2343   (set_attr "type" "mlas")]
2344)
2345
2346(define_insn "*mulsi3addsi_compare0_v6"
2347  [(set (reg:CC_NZ CC_REGNUM)
2348	(compare:CC_NZ
2349	 (plus:SI (mult:SI
2350		   (match_operand:SI 2 "s_register_operand" "r")
2351		   (match_operand:SI 1 "s_register_operand" "r"))
2352		  (match_operand:SI 3 "s_register_operand" "r"))
2353	 (const_int 0)))
2354   (set (match_operand:SI 0 "s_register_operand" "=r")
2355	(plus:SI (mult:SI (match_dup 2) (match_dup 1))
2356		 (match_dup 3)))]
2357  "TARGET_ARM && arm_arch6 && optimize_size"
2358  "mlas%?\\t%0, %2, %1, %3"
2359  [(set_attr "conds" "set")
2360   (set_attr "type" "mlas")]
2361)
2362
2363(define_insn "*mulsi3addsi_compare0_scratch"
2364  [(set (reg:CC_NZ CC_REGNUM)
2365	(compare:CC_NZ
2366	 (plus:SI (mult:SI
2367		   (match_operand:SI 2 "s_register_operand" "r,r,r,r")
2368		   (match_operand:SI 1 "s_register_operand" "%0,r,0,r"))
2369		  (match_operand:SI 3 "s_register_operand" "?r,r,0,0"))
2370	 (const_int 0)))
2371   (clobber (match_scratch:SI 0 "=&r,&r,&r,&r"))]
2372  "TARGET_ARM && !arm_arch6"
2373  "mlas%?\\t%0, %2, %1, %3"
2374  [(set_attr "conds" "set")
2375   (set_attr "type" "mlas")]
2376)
2377
2378(define_insn "*mulsi3addsi_compare0_scratch_v6"
2379  [(set (reg:CC_NZ CC_REGNUM)
2380	(compare:CC_NZ
2381	 (plus:SI (mult:SI
2382		   (match_operand:SI 2 "s_register_operand" "r")
2383		   (match_operand:SI 1 "s_register_operand" "r"))
2384		  (match_operand:SI 3 "s_register_operand" "r"))
2385	 (const_int 0)))
2386   (clobber (match_scratch:SI 0 "=r"))]
2387  "TARGET_ARM && arm_arch6 && optimize_size"
2388  "mlas%?\\t%0, %2, %1, %3"
2389  [(set_attr "conds" "set")
2390   (set_attr "type" "mlas")]
2391)
2392
2393;; 32x32->64 widening multiply.
2394;; The only difference between the v3-5 and v6+ versions is the requirement
2395;; that the output does not overlap with either input.
2396
2397(define_expand "<Us>mulsidi3"
2398  [(set (match_operand:DI 0 "s_register_operand")
2399	(mult:DI
2400	 (SE:DI (match_operand:SI 1 "s_register_operand"))
2401	 (SE:DI (match_operand:SI 2 "s_register_operand"))))]
2402  "TARGET_32BIT"
2403  {
2404      emit_insn (gen_<US>mull (gen_lowpart (SImode, operands[0]),
2405			       gen_highpart (SImode, operands[0]),
2406			       operands[1], operands[2]));
2407      DONE;
2408  }
2409)
2410
2411(define_insn "<US>mull"
2412  [(set (match_operand:SI 0 "s_register_operand" "=r,&r")
2413	(mult:SI
2414	 (match_operand:SI 2 "s_register_operand" "%r,r")
2415	 (match_operand:SI 3 "s_register_operand" "r,r")))
2416   (set (match_operand:SI 1 "s_register_operand" "=r,&r")
2417	(truncate:SI
2418	 (lshiftrt:DI
2419	  (mult:DI (SE:DI (match_dup 2)) (SE:DI (match_dup 3)))
2420	  (const_int 32))))]
2421  "TARGET_32BIT"
2422  "<US>mull%?\\t%0, %1, %2, %3"
2423  [(set_attr "type" "umull")
2424   (set_attr "predicable" "yes")
2425   (set_attr "arch" "v6,nov6")]
2426)
2427
2428(define_expand "<Us>maddsidi4"
2429  [(set (match_operand:DI 0 "s_register_operand")
2430	(plus:DI
2431	 (mult:DI
2432	  (SE:DI (match_operand:SI 1 "s_register_operand"))
2433	  (SE:DI (match_operand:SI 2 "s_register_operand")))
2434	 (match_operand:DI 3 "s_register_operand")))]
2435  "TARGET_32BIT"
2436  {
2437      emit_insn (gen_<US>mlal (gen_lowpart (SImode, operands[0]),
2438			       gen_lowpart (SImode, operands[3]),
2439			       gen_highpart (SImode, operands[0]),
2440			       gen_highpart (SImode, operands[3]),
2441			       operands[1], operands[2]));
2442      DONE;
2443  }
2444)
2445
2446(define_insn "<US>mlal"
2447  [(set (match_operand:SI 0 "s_register_operand" "=r,&r")
2448	(plus:SI
2449	 (mult:SI
2450	  (match_operand:SI 4 "s_register_operand" "%r,r")
2451	  (match_operand:SI 5 "s_register_operand" "r,r"))
2452	 (match_operand:SI 1 "s_register_operand" "0,0")))
2453   (set (match_operand:SI 2 "s_register_operand" "=r,&r")
2454	(plus:SI
2455	 (truncate:SI
2456	  (lshiftrt:DI
2457	   (plus:DI
2458	    (mult:DI (SE:DI (match_dup 4)) (SE:DI (match_dup 5)))
2459	    (zero_extend:DI (match_dup 1)))
2460	   (const_int 32)))
2461	 (match_operand:SI 3 "s_register_operand" "2,2")))]
2462  "TARGET_32BIT"
2463  "<US>mlal%?\\t%0, %2, %4, %5"
2464  [(set_attr "type" "umlal")
2465   (set_attr "predicable" "yes")
2466   (set_attr "arch" "v6,nov6")]
2467)
2468
2469(define_expand "<US>mulsi3_highpart"
2470  [(parallel
2471    [(set (match_operand:SI 0 "s_register_operand")
2472	  (truncate:SI
2473	   (lshiftrt:DI
2474	    (mult:DI
2475	     (SE:DI (match_operand:SI 1 "s_register_operand"))
2476	     (SE:DI (match_operand:SI 2 "s_register_operand")))
2477	    (const_int 32))))
2478     (clobber (match_scratch:SI 3 ""))])]
2479  "TARGET_32BIT"
2480  ""
2481)
2482
2483(define_insn "*<US>mull_high"
2484  [(set (match_operand:SI 0 "s_register_operand" "=r,&r,&r")
2485	(truncate:SI
2486	 (lshiftrt:DI
2487	  (mult:DI
2488	   (SE:DI (match_operand:SI 1 "s_register_operand" "%r,0,r"))
2489	   (SE:DI (match_operand:SI 2 "s_register_operand" "r,r,r")))
2490	  (const_int 32))))
2491   (clobber (match_scratch:SI 3 "=r,&r,&r"))]
2492  "TARGET_32BIT"
2493  "<US>mull%?\\t%3, %0, %2, %1"
2494  [(set_attr "type" "umull")
2495   (set_attr "predicable" "yes")
2496   (set_attr "arch" "v6,nov6,nov6")]
2497)
2498
2499(define_insn "mulhisi3"
2500  [(set (match_operand:SI 0 "s_register_operand" "=r")
2501	(mult:SI (sign_extend:SI
2502		  (match_operand:HI 1 "s_register_operand" "%r"))
2503		 (sign_extend:SI
2504		  (match_operand:HI 2 "s_register_operand" "r"))))]
2505  "TARGET_DSP_MULTIPLY"
2506  "smulbb%?\\t%0, %1, %2"
2507  [(set_attr "type" "smulxy")
2508   (set_attr "predicable" "yes")]
2509)
2510
2511(define_insn "*mulhisi3tb"
2512  [(set (match_operand:SI 0 "s_register_operand" "=r")
2513	(mult:SI (ashiftrt:SI
2514		  (match_operand:SI 1 "s_register_operand" "r")
2515		  (const_int 16))
2516		 (sign_extend:SI
2517		  (match_operand:HI 2 "s_register_operand" "r"))))]
2518  "TARGET_DSP_MULTIPLY"
2519  "smultb%?\\t%0, %1, %2"
2520  [(set_attr "type" "smulxy")
2521   (set_attr "predicable" "yes")]
2522)
2523
2524(define_insn "*mulhisi3bt"
2525  [(set (match_operand:SI 0 "s_register_operand" "=r")
2526	(mult:SI (sign_extend:SI
2527		  (match_operand:HI 1 "s_register_operand" "r"))
2528		 (ashiftrt:SI
2529		  (match_operand:SI 2 "s_register_operand" "r")
2530		  (const_int 16))))]
2531  "TARGET_DSP_MULTIPLY"
2532  "smulbt%?\\t%0, %1, %2"
2533  [(set_attr "type" "smulxy")
2534   (set_attr "predicable" "yes")]
2535)
2536
2537(define_insn "*mulhisi3tt"
2538  [(set (match_operand:SI 0 "s_register_operand" "=r")
2539	(mult:SI (ashiftrt:SI
2540		  (match_operand:SI 1 "s_register_operand" "r")
2541		  (const_int 16))
2542		 (ashiftrt:SI
2543		  (match_operand:SI 2 "s_register_operand" "r")
2544		  (const_int 16))))]
2545  "TARGET_DSP_MULTIPLY"
2546  "smultt%?\\t%0, %1, %2"
2547  [(set_attr "type" "smulxy")
2548   (set_attr "predicable" "yes")]
2549)
2550
2551(define_expand "maddhisi4"
2552  [(set (match_operand:SI 0 "s_register_operand")
2553	(plus:SI (mult:SI (sign_extend:SI
2554			   (match_operand:HI 1 "s_register_operand"))
2555			  (sign_extend:SI
2556			   (match_operand:HI 2 "s_register_operand")))
2557		 (match_operand:SI 3 "s_register_operand")))]
2558  "TARGET_DSP_MULTIPLY"
2559  {
2560    /* If this function reads the Q bit from ACLE intrinsics break up the
2561       multiplication and accumulation as an overflow during accumulation will
2562       clobber the Q flag.  */
2563    if (ARM_Q_BIT_READ)
2564      {
2565	rtx tmp = gen_reg_rtx (SImode);
2566	emit_insn (gen_mulhisi3 (tmp, operands[1], operands[2]));
2567	emit_insn (gen_addsi3 (operands[0], tmp, operands[3]));
2568	DONE;
2569      }
2570  }
2571)
2572
2573(define_insn "*arm_maddhisi4"
2574  [(set (match_operand:SI 0 "s_register_operand" "=r")
2575	(plus:SI (mult:SI (sign_extend:SI
2576			   (match_operand:HI 1 "s_register_operand" "r"))
2577			  (sign_extend:SI
2578			   (match_operand:HI 2 "s_register_operand" "r")))
2579		 (match_operand:SI 3 "s_register_operand" "r")))]
2580  "TARGET_DSP_MULTIPLY && !ARM_Q_BIT_READ"
2581  "smlabb%?\\t%0, %1, %2, %3"
2582  [(set_attr "type" "smlaxy")
2583   (set_attr "predicable" "yes")]
2584)
2585
2586(define_insn "arm_smlabb_setq"
2587  [(set (match_operand:SI 0 "s_register_operand" "=r")
2588	(plus:SI (mult:SI (sign_extend:SI
2589			   (match_operand:HI 1 "s_register_operand" "r"))
2590			  (sign_extend:SI
2591			   (match_operand:HI 2 "s_register_operand" "r")))
2592		 (match_operand:SI 3 "s_register_operand" "r")))
2593   (set (reg:CC APSRQ_REGNUM)
2594	(unspec:CC [(reg:CC APSRQ_REGNUM)] UNSPEC_Q_SET))]
2595  "TARGET_DSP_MULTIPLY"
2596  "smlabb%?\\t%0, %1, %2, %3"
2597  [(set_attr "type" "smlaxy")
2598   (set_attr "predicable" "yes")]
2599)
2600
2601(define_expand "arm_smlabb"
2602 [(match_operand:SI 0 "s_register_operand")
2603  (match_operand:SI 1 "s_register_operand")
2604  (match_operand:SI 2 "s_register_operand")
2605  (match_operand:SI 3 "s_register_operand")]
2606  "TARGET_DSP_MULTIPLY"
2607  {
2608    rtx mult1 = gen_lowpart (HImode, operands[1]);
2609    rtx mult2 = gen_lowpart (HImode, operands[2]);
2610    if (ARM_Q_BIT_READ)
2611      emit_insn (gen_arm_smlabb_setq (operands[0], mult1, mult2, operands[3]));
2612    else
2613      emit_insn (gen_maddhisi4 (operands[0], mult1, mult2, operands[3]));
2614    DONE;
2615  }
2616)
2617
2618;; Note: there is no maddhisi4ibt because this one is canonical form
2619(define_insn "maddhisi4tb"
2620  [(set (match_operand:SI 0 "s_register_operand" "=r")
2621	(plus:SI (mult:SI (ashiftrt:SI
2622			   (match_operand:SI 1 "s_register_operand" "r")
2623			   (const_int 16))
2624			  (sign_extend:SI
2625			   (match_operand:HI 2 "s_register_operand" "r")))
2626		 (match_operand:SI 3 "s_register_operand" "r")))]
2627  "TARGET_DSP_MULTIPLY && !ARM_Q_BIT_READ"
2628  "smlatb%?\\t%0, %1, %2, %3"
2629  [(set_attr "type" "smlaxy")
2630   (set_attr "predicable" "yes")]
2631)
2632
2633(define_insn "arm_smlatb_setq"
2634  [(set (match_operand:SI 0 "s_register_operand" "=r")
2635	(plus:SI (mult:SI (ashiftrt:SI
2636			   (match_operand:SI 1 "s_register_operand" "r")
2637			   (const_int 16))
2638			  (sign_extend:SI
2639			   (match_operand:HI 2 "s_register_operand" "r")))
2640		 (match_operand:SI 3 "s_register_operand" "r")))
2641   (set (reg:CC APSRQ_REGNUM)
2642	(unspec:CC [(reg:CC APSRQ_REGNUM)] UNSPEC_Q_SET))]
2643  "TARGET_DSP_MULTIPLY"
2644  "smlatb%?\\t%0, %1, %2, %3"
2645  [(set_attr "type" "smlaxy")
2646   (set_attr "predicable" "yes")]
2647)
2648
2649(define_expand "arm_smlatb"
2650 [(match_operand:SI 0 "s_register_operand")
2651  (match_operand:SI 1 "s_register_operand")
2652  (match_operand:SI 2 "s_register_operand")
2653  (match_operand:SI 3 "s_register_operand")]
2654  "TARGET_DSP_MULTIPLY"
2655  {
2656    rtx mult2 = gen_lowpart (HImode, operands[2]);
2657    if (ARM_Q_BIT_READ)
2658      emit_insn (gen_arm_smlatb_setq (operands[0], operands[1],
2659				      mult2, operands[3]));
2660    else
2661      emit_insn (gen_maddhisi4tb (operands[0], operands[1],
2662				  mult2, operands[3]));
2663    DONE;
2664  }
2665)
2666
2667(define_insn "maddhisi4tt"
2668  [(set (match_operand:SI 0 "s_register_operand" "=r")
2669	(plus:SI (mult:SI (ashiftrt:SI
2670			   (match_operand:SI 1 "s_register_operand" "r")
2671			   (const_int 16))
2672			  (ashiftrt:SI
2673			   (match_operand:SI 2 "s_register_operand" "r")
2674			   (const_int 16)))
2675		 (match_operand:SI 3 "s_register_operand" "r")))]
2676  "TARGET_DSP_MULTIPLY && !ARM_Q_BIT_READ"
2677  "smlatt%?\\t%0, %1, %2, %3"
2678  [(set_attr "type" "smlaxy")
2679   (set_attr "predicable" "yes")]
2680)
2681
2682(define_insn "arm_smlatt_setq"
2683  [(set (match_operand:SI 0 "s_register_operand" "=r")
2684	(plus:SI (mult:SI (ashiftrt:SI
2685			   (match_operand:SI 1 "s_register_operand" "r")
2686			   (const_int 16))
2687			  (ashiftrt:SI
2688			   (match_operand:SI 2 "s_register_operand" "r")
2689			   (const_int 16)))
2690		 (match_operand:SI 3 "s_register_operand" "r")))
2691   (set (reg:CC APSRQ_REGNUM)
2692	(unspec:CC [(reg:CC APSRQ_REGNUM)] UNSPEC_Q_SET))]
2693  "TARGET_DSP_MULTIPLY"
2694  "smlatt%?\\t%0, %1, %2, %3"
2695  [(set_attr "type" "smlaxy")
2696   (set_attr "predicable" "yes")]
2697)
2698
2699(define_expand "arm_smlatt"
2700 [(match_operand:SI 0 "s_register_operand")
2701  (match_operand:SI 1 "s_register_operand")
2702  (match_operand:SI 2 "s_register_operand")
2703  (match_operand:SI 3 "s_register_operand")]
2704  "TARGET_DSP_MULTIPLY"
2705  {
2706    if (ARM_Q_BIT_READ)
2707      emit_insn (gen_arm_smlatt_setq (operands[0], operands[1],
2708				      operands[2], operands[3]));
2709    else
2710      emit_insn (gen_maddhisi4tt (operands[0], operands[1],
2711				  operands[2], operands[3]));
2712    DONE;
2713  }
2714)
2715
2716(define_insn "maddhidi4"
2717  [(set (match_operand:DI 0 "s_register_operand" "=r")
2718	(plus:DI
2719	  (mult:DI (sign_extend:DI
2720		    (match_operand:HI 1 "s_register_operand" "r"))
2721		   (sign_extend:DI
2722		    (match_operand:HI 2 "s_register_operand" "r")))
2723	  (match_operand:DI 3 "s_register_operand" "0")))]
2724  "TARGET_DSP_MULTIPLY"
2725  "smlalbb%?\\t%Q0, %R0, %1, %2"
2726  [(set_attr "type" "smlalxy")
2727   (set_attr "predicable" "yes")])
2728
2729;; Note: there is no maddhidi4ibt because this one is canonical form
2730(define_insn "*maddhidi4tb"
2731  [(set (match_operand:DI 0 "s_register_operand" "=r")
2732	(plus:DI
2733	  (mult:DI (sign_extend:DI
2734		    (ashiftrt:SI
2735		     (match_operand:SI 1 "s_register_operand" "r")
2736		     (const_int 16)))
2737		   (sign_extend:DI
2738		    (match_operand:HI 2 "s_register_operand" "r")))
2739	  (match_operand:DI 3 "s_register_operand" "0")))]
2740  "TARGET_DSP_MULTIPLY"
2741  "smlaltb%?\\t%Q0, %R0, %1, %2"
2742  [(set_attr "type" "smlalxy")
2743   (set_attr "predicable" "yes")])
2744
2745(define_insn "*maddhidi4tt"
2746  [(set (match_operand:DI 0 "s_register_operand" "=r")
2747	(plus:DI
2748	  (mult:DI (sign_extend:DI
2749		    (ashiftrt:SI
2750		     (match_operand:SI 1 "s_register_operand" "r")
2751		     (const_int 16)))
2752		   (sign_extend:DI
2753		    (ashiftrt:SI
2754		     (match_operand:SI 2 "s_register_operand" "r")
2755		     (const_int 16))))
2756	  (match_operand:DI 3 "s_register_operand" "0")))]
2757  "TARGET_DSP_MULTIPLY"
2758  "smlaltt%?\\t%Q0, %R0, %1, %2"
2759  [(set_attr "type" "smlalxy")
2760   (set_attr "predicable" "yes")])
2761
2762(define_insn "arm_<smlaw_op><add_clobber_q_name>_insn"
2763  [(set (match_operand:SI 0 "s_register_operand" "=r")
2764	(unspec:SI
2765	   [(match_operand:SI 1 "s_register_operand" "r")
2766	    (match_operand:SI 2 "s_register_operand" "r")
2767	    (match_operand:SI 3 "s_register_operand" "r")]
2768	   SMLAWBT))]
2769  "TARGET_DSP_MULTIPLY && <add_clobber_q_pred>"
2770  "<smlaw_op>%?\\t%0, %1, %2, %3"
2771  [(set_attr "type" "smlaxy")
2772   (set_attr "predicable" "yes")]
2773)
2774
2775(define_expand "arm_<smlaw_op>"
2776  [(set (match_operand:SI 0 "s_register_operand")
2777	(unspec:SI
2778	   [(match_operand:SI 1 "s_register_operand")
2779	    (match_operand:SI 2 "s_register_operand")
2780	    (match_operand:SI 3 "s_register_operand")]
2781	   SMLAWBT))]
2782  "TARGET_DSP_MULTIPLY"
2783  {
2784    if (ARM_Q_BIT_READ)
2785      emit_insn (gen_arm_<smlaw_op>_setq_insn (operands[0], operands[1],
2786					       operands[2], operands[3]));
2787    else
2788      emit_insn (gen_arm_<smlaw_op>_insn (operands[0], operands[1],
2789					  operands[2], operands[3]));
2790    DONE;
2791  }
2792)
2793
2794(define_expand "mulsf3"
2795  [(set (match_operand:SF          0 "s_register_operand")
2796	(mult:SF (match_operand:SF 1 "s_register_operand")
2797		 (match_operand:SF 2 "s_register_operand")))]
2798  "TARGET_32BIT && TARGET_HARD_FLOAT"
2799  "
2800")
2801
2802(define_expand "muldf3"
2803  [(set (match_operand:DF          0 "s_register_operand")
2804	(mult:DF (match_operand:DF 1 "s_register_operand")
2805		 (match_operand:DF 2 "s_register_operand")))]
2806  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
2807  "
2808")
2809
2810;; Division insns
2811
2812(define_expand "divsf3"
2813  [(set (match_operand:SF 0 "s_register_operand")
2814	(div:SF (match_operand:SF 1 "s_register_operand")
2815		(match_operand:SF 2 "s_register_operand")))]
2816  "TARGET_32BIT && TARGET_HARD_FLOAT"
2817  "")
2818
2819(define_expand "divdf3"
2820  [(set (match_operand:DF 0 "s_register_operand")
2821	(div:DF (match_operand:DF 1 "s_register_operand")
2822		(match_operand:DF 2 "s_register_operand")))]
2823  "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
2824  "")
2825
2826
2827; Expand logical operations.  The mid-end expander does not split off memory
2828; operands or complex immediates, which leads to fewer LDRD/STRD instructions.
2829; So an explicit expander is needed to generate better code.
2830
2831(define_expand "<LOGICAL:optab>di3"
2832  [(set (match_operand:DI	  0 "s_register_operand")
2833	(LOGICAL:DI (match_operand:DI 1 "s_register_operand")
2834		    (match_operand:DI 2 "arm_<optab>di_operand")))]
2835  "TARGET_32BIT"
2836  {
2837      rtx low  = simplify_gen_binary (<CODE>, SImode,
2838				      gen_lowpart (SImode, operands[1]),
2839				      gen_lowpart (SImode, operands[2]));
2840      rtx high = simplify_gen_binary (<CODE>, SImode,
2841				      gen_highpart (SImode, operands[1]),
2842				      gen_highpart_mode (SImode, DImode,
2843							 operands[2]));
2844
2845      emit_insn (gen_rtx_SET (gen_lowpart (SImode, operands[0]), low));
2846      emit_insn (gen_rtx_SET (gen_highpart (SImode, operands[0]), high));
2847      DONE;
2848  }
2849)
2850
2851(define_expand "one_cmpldi2"
2852  [(set (match_operand:DI 0 "s_register_operand")
2853	(not:DI (match_operand:DI 1 "s_register_operand")))]
2854  "TARGET_32BIT"
2855  {
2856      rtx low  = simplify_gen_unary (NOT, SImode,
2857				     gen_lowpart (SImode, operands[1]),
2858				     SImode);
2859      rtx high = simplify_gen_unary (NOT, SImode,
2860				     gen_highpart_mode (SImode, DImode,
2861							operands[1]),
2862				     SImode);
2863
2864      emit_insn (gen_rtx_SET (gen_lowpart (SImode, operands[0]), low));
2865      emit_insn (gen_rtx_SET (gen_highpart (SImode, operands[0]), high));
2866      DONE;
2867  }
2868)
2869
2870;; Split DImode and, ior, xor operations.  Simply perform the logical
2871;; operation on the upper and lower halves of the registers.
2872;; This is needed for atomic operations in arm_split_atomic_op.
2873;; Avoid splitting IWMMXT instructions.
2874(define_split
2875  [(set (match_operand:DI 0 "s_register_operand" "")
2876	(match_operator:DI 6 "logical_binary_operator"
2877	  [(match_operand:DI 1 "s_register_operand" "")
2878	   (match_operand:DI 2 "s_register_operand" "")]))]
2879  "TARGET_32BIT && reload_completed
2880   && ! IS_IWMMXT_REGNUM (REGNO (operands[0]))"
2881  [(set (match_dup 0) (match_op_dup:SI 6 [(match_dup 1) (match_dup 2)]))
2882   (set (match_dup 3) (match_op_dup:SI 6 [(match_dup 4) (match_dup 5)]))]
2883  "
2884  {
2885    operands[3] = gen_highpart (SImode, operands[0]);
2886    operands[0] = gen_lowpart (SImode, operands[0]);
2887    operands[4] = gen_highpart (SImode, operands[1]);
2888    operands[1] = gen_lowpart (SImode, operands[1]);
2889    operands[5] = gen_highpart (SImode, operands[2]);
2890    operands[2] = gen_lowpart (SImode, operands[2]);
2891  }"
2892)
2893
2894;; Split DImode not (needed for atomic operations in arm_split_atomic_op).
2895;; Unconditionally split since there is no SIMD DImode NOT pattern.
2896(define_split
2897  [(set (match_operand:DI 0 "s_register_operand")
2898	(not:DI (match_operand:DI 1 "s_register_operand")))]
2899  "TARGET_32BIT"
2900  [(set (match_dup 0) (not:SI (match_dup 1)))
2901   (set (match_dup 2) (not:SI (match_dup 3)))]
2902  "
2903  {
2904    operands[2] = gen_highpart (SImode, operands[0]);
2905    operands[0] = gen_lowpart (SImode, operands[0]);
2906    operands[3] = gen_highpart (SImode, operands[1]);
2907    operands[1] = gen_lowpart (SImode, operands[1]);
2908  }"
2909)
2910
2911(define_expand "andsi3"
2912  [(set (match_operand:SI         0 "s_register_operand")
2913	(and:SI (match_operand:SI 1 "s_register_operand")
2914		(match_operand:SI 2 "reg_or_int_operand")))]
2915  "TARGET_EITHER"
2916  "
2917  if (TARGET_32BIT)
2918    {
2919      if (CONST_INT_P (operands[2]))
2920        {
2921	  if (INTVAL (operands[2]) == 255 && arm_arch6)
2922	    {
2923	      operands[1] = convert_to_mode (QImode, operands[1], 1);
2924	      emit_insn (gen_thumb2_zero_extendqisi2_v6 (operands[0],
2925							 operands[1]));
2926	      DONE;
2927	    }
2928	  else if (DONT_EARLY_SPLIT_CONSTANT (INTVAL (operands[2]), AND))
2929	    operands[2] = force_reg (SImode, operands[2]);
2930	  else
2931	    {
2932	      arm_split_constant (AND, SImode, NULL_RTX,
2933				  INTVAL (operands[2]), operands[0],
2934				  operands[1],
2935				  optimize && can_create_pseudo_p ());
2936
2937	      DONE;
2938	    }
2939        }
2940    }
2941  else /* TARGET_THUMB1 */
2942    {
2943      if (!CONST_INT_P (operands[2]))
2944        {
2945          rtx tmp = force_reg (SImode, operands[2]);
2946	  if (rtx_equal_p (operands[0], operands[1]))
2947	    operands[2] = tmp;
2948	  else
2949	    {
2950              operands[2] = operands[1];
2951              operands[1] = tmp;
2952	    }
2953        }
2954      else
2955        {
2956          int i;
2957
2958          if (((unsigned HOST_WIDE_INT) ~INTVAL (operands[2])) < 256)
2959  	    {
2960	      operands[2] = force_reg (SImode,
2961				       GEN_INT (~INTVAL (operands[2])));
2962
2963	      emit_insn (gen_thumb1_bicsi3 (operands[0], operands[2], operands[1]));
2964
2965	      DONE;
2966	    }
2967
2968          for (i = 9; i <= 31; i++)
2969	    {
2970	      if ((HOST_WIDE_INT_1 << i) - 1 == INTVAL (operands[2]))
2971	        {
2972	          emit_insn (gen_extzv (operands[0], operands[1], GEN_INT (i),
2973			 	        const0_rtx));
2974	          DONE;
2975	        }
2976	      else if ((HOST_WIDE_INT_1 << i) - 1
2977		       == ~INTVAL (operands[2]))
2978	        {
2979	          rtx shift = GEN_INT (i);
2980	          rtx reg = gen_reg_rtx (SImode);
2981
2982	          emit_insn (gen_lshrsi3 (reg, operands[1], shift));
2983	          emit_insn (gen_ashlsi3 (operands[0], reg, shift));
2984
2985	          DONE;
2986	        }
2987	    }
2988
2989          operands[2] = force_reg (SImode, operands[2]);
2990        }
2991    }
2992  "
2993)
2994
2995; ??? Check split length for Thumb-2
2996(define_insn_and_split "*arm_andsi3_insn"
2997  [(set (match_operand:SI         0 "s_register_operand" "=r,l,r,r,r")
2998	(and:SI (match_operand:SI 1 "s_register_operand" "%r,0,r,r,r")
2999		(match_operand:SI 2 "reg_or_int_operand" "I,l,K,r,?n")))]
3000  "TARGET_32BIT"
3001  "@
3002   and%?\\t%0, %1, %2
3003   and%?\\t%0, %1, %2
3004   bic%?\\t%0, %1, #%B2
3005   and%?\\t%0, %1, %2
3006   #"
3007  "TARGET_32BIT
3008   && CONST_INT_P (operands[2])
3009   && !(const_ok_for_arm (INTVAL (operands[2]))
3010	|| const_ok_for_arm (~INTVAL (operands[2])))"
3011  [(clobber (const_int 0))]
3012  "
3013  arm_split_constant  (AND, SImode, curr_insn,
3014	               INTVAL (operands[2]), operands[0], operands[1], 0);
3015  DONE;
3016  "
3017  [(set_attr "length" "4,4,4,4,16")
3018   (set_attr "predicable" "yes")
3019   (set_attr "predicable_short_it" "no,yes,no,no,no")
3020   (set_attr "type" "logic_imm,logic_imm,logic_reg,logic_reg,logic_imm")]
3021)
3022
3023(define_insn "*andsi3_compare0"
3024  [(set (reg:CC_NZ CC_REGNUM)
3025	(compare:CC_NZ
3026	 (and:SI (match_operand:SI 1 "s_register_operand" "r,r,r")
3027		 (match_operand:SI 2 "arm_not_operand" "I,K,r"))
3028	 (const_int 0)))
3029   (set (match_operand:SI          0 "s_register_operand" "=r,r,r")
3030	(and:SI (match_dup 1) (match_dup 2)))]
3031  "TARGET_32BIT"
3032  "@
3033   ands%?\\t%0, %1, %2
3034   bics%?\\t%0, %1, #%B2
3035   ands%?\\t%0, %1, %2"
3036  [(set_attr "conds" "set")
3037   (set_attr "type" "logics_imm,logics_imm,logics_reg")]
3038)
3039
3040(define_insn "*andsi3_compare0_scratch"
3041  [(set (reg:CC_NZ CC_REGNUM)
3042	(compare:CC_NZ
3043	 (and:SI (match_operand:SI 0 "s_register_operand" "r,r,r")
3044		 (match_operand:SI 1 "arm_not_operand" "I,K,r"))
3045	 (const_int 0)))
3046   (clobber (match_scratch:SI 2 "=X,r,X"))]
3047  "TARGET_32BIT"
3048  "@
3049   tst%?\\t%0, %1
3050   bics%?\\t%2, %0, #%B1
3051   tst%?\\t%0, %1"
3052  [(set_attr "conds" "set")
3053   (set_attr "type"  "logics_imm,logics_imm,logics_reg")]
3054)
3055
3056(define_insn "*zeroextractsi_compare0_scratch"
3057  [(set (reg:CC_NZ CC_REGNUM)
3058	(compare:CC_NZ (zero_extract:SI
3059			  (match_operand:SI 0 "s_register_operand" "r")
3060			  (match_operand 1 "const_int_operand" "n")
3061			  (match_operand 2 "const_int_operand" "n"))
3062			 (const_int 0)))]
3063  "TARGET_32BIT
3064  && (INTVAL (operands[2]) >= 0 && INTVAL (operands[2]) < 32
3065      && INTVAL (operands[1]) > 0
3066      && INTVAL (operands[1]) + (INTVAL (operands[2]) & 1) <= 8
3067      && INTVAL (operands[1]) + INTVAL (operands[2]) <= 32)"
3068  "*
3069  operands[1] = GEN_INT (((1 << INTVAL (operands[1])) - 1)
3070			 << INTVAL (operands[2]));
3071  output_asm_insn (\"tst%?\\t%0, %1\", operands);
3072  return \"\";
3073  "
3074  [(set_attr "conds" "set")
3075   (set_attr "predicable" "yes")
3076   (set_attr "type" "logics_imm")]
3077)
3078
3079(define_insn_and_split "*ne_zeroextractsi"
3080  [(set (match_operand:SI 0 "s_register_operand" "=r")
3081	(ne:SI (zero_extract:SI
3082		(match_operand:SI 1 "s_register_operand" "r")
3083		(match_operand:SI 2 "const_int_operand" "n")
3084		(match_operand:SI 3 "const_int_operand" "n"))
3085	       (const_int 0)))
3086   (clobber (reg:CC CC_REGNUM))]
3087  "TARGET_32BIT
3088   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
3089       && INTVAL (operands[2]) > 0
3090       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
3091       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)"
3092  "#"
3093  "TARGET_32BIT
3094   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
3095       && INTVAL (operands[2]) > 0
3096       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
3097       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)"
3098  [(parallel [(set (reg:CC_NZ CC_REGNUM)
3099		   (compare:CC_NZ (and:SI (match_dup 1) (match_dup 2))
3100				    (const_int 0)))
3101	      (set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))])
3102   (set (match_dup 0)
3103	(if_then_else:SI (eq (reg:CC_NZ CC_REGNUM) (const_int 0))
3104			 (match_dup 0) (const_int 1)))]
3105  "
3106  operands[2] = GEN_INT (((1 << INTVAL (operands[2])) - 1)
3107			 << INTVAL (operands[3]));
3108  "
3109  [(set_attr "conds" "clob")
3110   (set (attr "length")
3111	(if_then_else (eq_attr "is_thumb" "yes")
3112		      (const_int 12)
3113		      (const_int 8)))
3114   (set_attr "type" "multiple")]
3115)
3116
3117(define_insn_and_split "*ne_zeroextractsi_shifted"
3118  [(set (match_operand:SI 0 "s_register_operand" "=r")
3119	(ne:SI (zero_extract:SI
3120		(match_operand:SI 1 "s_register_operand" "r")
3121		(match_operand:SI 2 "const_int_operand" "n")
3122		(const_int 0))
3123	       (const_int 0)))
3124   (clobber (reg:CC CC_REGNUM))]
3125  "TARGET_ARM"
3126  "#"
3127  "TARGET_ARM"
3128  [(parallel [(set (reg:CC_NZ CC_REGNUM)
3129		   (compare:CC_NZ (ashift:SI (match_dup 1) (match_dup 2))
3130				    (const_int 0)))
3131	      (set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))])
3132   (set (match_dup 0)
3133	(if_then_else:SI (eq (reg:CC_NZ CC_REGNUM) (const_int 0))
3134			 (match_dup 0) (const_int 1)))]
3135  "
3136  operands[2] = GEN_INT (32 - INTVAL (operands[2]));
3137  "
3138  [(set_attr "conds" "clob")
3139   (set_attr "length" "8")
3140   (set_attr "type" "multiple")]
3141)
3142
3143(define_insn_and_split "*ite_ne_zeroextractsi"
3144  [(set (match_operand:SI 0 "s_register_operand" "=r")
3145	(if_then_else:SI (ne (zero_extract:SI
3146			      (match_operand:SI 1 "s_register_operand" "r")
3147			      (match_operand:SI 2 "const_int_operand" "n")
3148			      (match_operand:SI 3 "const_int_operand" "n"))
3149			     (const_int 0))
3150			 (match_operand:SI 4 "arm_not_operand" "rIK")
3151			 (const_int 0)))
3152   (clobber (reg:CC CC_REGNUM))]
3153  "TARGET_ARM
3154   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
3155       && INTVAL (operands[2]) > 0
3156       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
3157       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)
3158   && !reg_overlap_mentioned_p (operands[0], operands[4])"
3159  "#"
3160  "TARGET_ARM
3161   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
3162       && INTVAL (operands[2]) > 0
3163       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
3164       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)
3165   && !reg_overlap_mentioned_p (operands[0], operands[4])"
3166  [(parallel [(set (reg:CC_NZ CC_REGNUM)
3167		   (compare:CC_NZ (and:SI (match_dup 1) (match_dup 2))
3168				    (const_int 0)))
3169	      (set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))])
3170   (set (match_dup 0)
3171	(if_then_else:SI (eq (reg:CC_NZ CC_REGNUM) (const_int 0))
3172			 (match_dup 0) (match_dup 4)))]
3173  "
3174  operands[2] = GEN_INT (((1 << INTVAL (operands[2])) - 1)
3175			 << INTVAL (operands[3]));
3176  "
3177  [(set_attr "conds" "clob")
3178   (set_attr "length" "8")
3179   (set_attr "type" "multiple")]
3180)
3181
3182(define_insn_and_split "*ite_ne_zeroextractsi_shifted"
3183  [(set (match_operand:SI 0 "s_register_operand" "=r")
3184	(if_then_else:SI (ne (zero_extract:SI
3185			      (match_operand:SI 1 "s_register_operand" "r")
3186			      (match_operand:SI 2 "const_int_operand" "n")
3187			      (const_int 0))
3188			     (const_int 0))
3189			 (match_operand:SI 3 "arm_not_operand" "rIK")
3190			 (const_int 0)))
3191   (clobber (reg:CC CC_REGNUM))]
3192  "TARGET_ARM && !reg_overlap_mentioned_p (operands[0], operands[3])"
3193  "#"
3194  "TARGET_ARM && !reg_overlap_mentioned_p (operands[0], operands[3])"
3195  [(parallel [(set (reg:CC_NZ CC_REGNUM)
3196		   (compare:CC_NZ (ashift:SI (match_dup 1) (match_dup 2))
3197				    (const_int 0)))
3198	      (set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))])
3199   (set (match_dup 0)
3200	(if_then_else:SI (eq (reg:CC_NZ CC_REGNUM) (const_int 0))
3201			 (match_dup 0) (match_dup 3)))]
3202  "
3203  operands[2] = GEN_INT (32 - INTVAL (operands[2]));
3204  "
3205  [(set_attr "conds" "clob")
3206   (set_attr "length" "8")
3207   (set_attr "type" "multiple")]
3208)
3209
3210;; ??? Use Thumb-2 has bitfield insert/extract instructions.
3211(define_split
3212  [(set (match_operand:SI 0 "s_register_operand" "")
3213	(match_operator:SI 1 "shiftable_operator"
3214	 [(zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
3215			   (match_operand:SI 3 "const_int_operand" "")
3216			   (match_operand:SI 4 "const_int_operand" ""))
3217	  (match_operand:SI 5 "s_register_operand" "")]))
3218   (clobber (match_operand:SI 6 "s_register_operand" ""))]
3219  "TARGET_ARM"
3220  [(set (match_dup 6) (ashift:SI (match_dup 2) (match_dup 3)))
3221   (set (match_dup 0)
3222	(match_op_dup 1
3223	 [(lshiftrt:SI (match_dup 6) (match_dup 4))
3224	  (match_dup 5)]))]
3225  "{
3226     HOST_WIDE_INT temp = INTVAL (operands[3]);
3227
3228     operands[3] = GEN_INT (32 - temp - INTVAL (operands[4]));
3229     operands[4] = GEN_INT (32 - temp);
3230   }"
3231)
3232
3233(define_split
3234  [(set (match_operand:SI 0 "s_register_operand" "")
3235	(match_operator:SI 1 "shiftable_operator"
3236	 [(sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
3237			   (match_operand:SI 3 "const_int_operand" "")
3238			   (match_operand:SI 4 "const_int_operand" ""))
3239	  (match_operand:SI 5 "s_register_operand" "")]))
3240   (clobber (match_operand:SI 6 "s_register_operand" ""))]
3241  "TARGET_ARM"
3242  [(set (match_dup 6) (ashift:SI (match_dup 2) (match_dup 3)))
3243   (set (match_dup 0)
3244	(match_op_dup 1
3245	 [(ashiftrt:SI (match_dup 6) (match_dup 4))
3246	  (match_dup 5)]))]
3247  "{
3248     HOST_WIDE_INT temp = INTVAL (operands[3]);
3249
3250     operands[3] = GEN_INT (32 - temp - INTVAL (operands[4]));
3251     operands[4] = GEN_INT (32 - temp);
3252   }"
3253)
3254
3255;;; ??? This pattern is bogus.  If operand3 has bits outside the range
3256;;; represented by the bitfield, then this will produce incorrect results.
3257;;; Somewhere, the value needs to be truncated.  On targets like the m68k,
3258;;; which have a real bit-field insert instruction, the truncation happens
3259;;; in the bit-field insert instruction itself.  Since arm does not have a
3260;;; bit-field insert instruction, we would have to emit code here to truncate
3261;;; the value before we insert.  This loses some of the advantage of having
3262;;; this insv pattern, so this pattern needs to be reevalutated.
3263
3264(define_expand "insv"
3265  [(set (zero_extract (match_operand 0 "nonimmediate_operand")
3266                      (match_operand 1 "general_operand")
3267                      (match_operand 2 "general_operand"))
3268        (match_operand 3 "reg_or_int_operand"))]
3269  "TARGET_ARM || arm_arch_thumb2"
3270  "
3271  {
3272    int start_bit = INTVAL (operands[2]);
3273    int width = INTVAL (operands[1]);
3274    HOST_WIDE_INT mask = (HOST_WIDE_INT_1 << width) - 1;
3275    rtx target, subtarget;
3276
3277    if (arm_arch_thumb2)
3278      {
3279        if (unaligned_access && MEM_P (operands[0])
3280	    && s_register_operand (operands[3], GET_MODE (operands[3]))
3281	    && (width == 16 || width == 32) && (start_bit % BITS_PER_UNIT) == 0)
3282	  {
3283	    rtx base_addr;
3284
3285	    if (BYTES_BIG_ENDIAN)
3286	      start_bit = GET_MODE_BITSIZE (GET_MODE (operands[3])) - width
3287			  - start_bit;
3288
3289	    if (width == 32)
3290	      {
3291	        base_addr = adjust_address (operands[0], SImode,
3292					    start_bit / BITS_PER_UNIT);
3293		emit_insn (gen_unaligned_storesi (base_addr, operands[3]));
3294	      }
3295	    else
3296	      {
3297	        rtx tmp = gen_reg_rtx (HImode);
3298
3299	        base_addr = adjust_address (operands[0], HImode,
3300					    start_bit / BITS_PER_UNIT);
3301		emit_move_insn (tmp, gen_lowpart (HImode, operands[3]));
3302		emit_insn (gen_unaligned_storehi (base_addr, tmp));
3303	      }
3304	    DONE;
3305	  }
3306	else if (s_register_operand (operands[0], GET_MODE (operands[0])))
3307	  {
3308	    bool use_bfi = TRUE;
3309
3310	    if (CONST_INT_P (operands[3]))
3311	      {
3312		HOST_WIDE_INT val = INTVAL (operands[3]) & mask;
3313
3314		if (val == 0)
3315		  {
3316		    emit_insn (gen_insv_zero (operands[0], operands[1],
3317					      operands[2]));
3318		    DONE;
3319		  }
3320
3321		/* See if the set can be done with a single orr instruction.  */
3322		if (val == mask && const_ok_for_arm (val << start_bit))
3323		  use_bfi = FALSE;
3324	      }
3325
3326	    if (use_bfi)
3327	      {
3328		if (!REG_P (operands[3]))
3329		  operands[3] = force_reg (SImode, operands[3]);
3330
3331		emit_insn (gen_insv_t2 (operands[0], operands[1], operands[2],
3332					operands[3]));
3333		DONE;
3334	      }
3335	  }
3336	else
3337	  FAIL;
3338      }
3339
3340    if (!s_register_operand (operands[0], GET_MODE (operands[0])))
3341      FAIL;
3342
3343    target = copy_rtx (operands[0]);
3344    /* Avoid using a subreg as a subtarget, and avoid writing a paradoxical
3345       subreg as the final target.  */
3346    if (GET_CODE (target) == SUBREG)
3347      {
3348	subtarget = gen_reg_rtx (SImode);
3349	if (GET_MODE_SIZE (GET_MODE (SUBREG_REG (target)))
3350	    < GET_MODE_SIZE (SImode))
3351	  target = SUBREG_REG (target);
3352      }
3353    else
3354      subtarget = target;
3355
3356    if (CONST_INT_P (operands[3]))
3357      {
3358	/* Since we are inserting a known constant, we may be able to
3359	   reduce the number of bits that we have to clear so that
3360	   the mask becomes simple.  */
3361	/* ??? This code does not check to see if the new mask is actually
3362	   simpler.  It may not be.  */
3363	rtx op1 = gen_reg_rtx (SImode);
3364	/* ??? Truncate operand3 to fit in the bitfield.  See comment before
3365	   start of this pattern.  */
3366	HOST_WIDE_INT op3_value = mask & INTVAL (operands[3]);
3367	HOST_WIDE_INT mask2 = ((mask & ~op3_value) << start_bit);
3368
3369	emit_insn (gen_andsi3 (op1, operands[0],
3370			       gen_int_mode (~mask2, SImode)));
3371	emit_insn (gen_iorsi3 (subtarget, op1,
3372			       gen_int_mode (op3_value << start_bit, SImode)));
3373      }
3374    else if (start_bit == 0
3375	     && !(const_ok_for_arm (mask)
3376		  || const_ok_for_arm (~mask)))
3377      {
3378	/* A Trick, since we are setting the bottom bits in the word,
3379	   we can shift operand[3] up, operand[0] down, OR them together
3380	   and rotate the result back again.  This takes 3 insns, and
3381	   the third might be mergeable into another op.  */
3382	/* The shift up copes with the possibility that operand[3] is
3383           wider than the bitfield.  */
3384	rtx op0 = gen_reg_rtx (SImode);
3385	rtx op1 = gen_reg_rtx (SImode);
3386
3387	emit_insn (gen_ashlsi3 (op0, operands[3], GEN_INT (32 - width)));
3388	emit_insn (gen_lshrsi3 (op1, operands[0], operands[1]));
3389	emit_insn (gen_iorsi3  (op1, op1, op0));
3390	emit_insn (gen_rotlsi3 (subtarget, op1, operands[1]));
3391      }
3392    else if ((width + start_bit == 32)
3393	     && !(const_ok_for_arm (mask)
3394		  || const_ok_for_arm (~mask)))
3395      {
3396	/* Similar trick, but slightly less efficient.  */
3397
3398	rtx op0 = gen_reg_rtx (SImode);
3399	rtx op1 = gen_reg_rtx (SImode);
3400
3401	emit_insn (gen_ashlsi3 (op0, operands[3], GEN_INT (32 - width)));
3402	emit_insn (gen_ashlsi3 (op1, operands[0], operands[1]));
3403	emit_insn (gen_lshrsi3 (op1, op1, operands[1]));
3404	emit_insn (gen_iorsi3 (subtarget, op1, op0));
3405      }
3406    else
3407      {
3408	rtx op0 = gen_int_mode (mask, SImode);
3409	rtx op1 = gen_reg_rtx (SImode);
3410	rtx op2 = gen_reg_rtx (SImode);
3411
3412	if (!(const_ok_for_arm (mask) || const_ok_for_arm (~mask)))
3413	  {
3414	    rtx tmp = gen_reg_rtx (SImode);
3415
3416	    emit_insn (gen_movsi (tmp, op0));
3417	    op0 = tmp;
3418	  }
3419
3420	/* Mask out any bits in operand[3] that are not needed.  */
3421	   emit_insn (gen_andsi3 (op1, operands[3], op0));
3422
3423	if (CONST_INT_P (op0)
3424	    && (const_ok_for_arm (mask << start_bit)
3425		|| const_ok_for_arm (~(mask << start_bit))))
3426	  {
3427	    op0 = gen_int_mode (~(mask << start_bit), SImode);
3428	    emit_insn (gen_andsi3 (op2, operands[0], op0));
3429	  }
3430	else
3431	  {
3432	    if (CONST_INT_P (op0))
3433	      {
3434		rtx tmp = gen_reg_rtx (SImode);
3435
3436		emit_insn (gen_movsi (tmp, op0));
3437		op0 = tmp;
3438	      }
3439
3440	    if (start_bit != 0)
3441	      emit_insn (gen_ashlsi3 (op0, op0, operands[2]));
3442
3443	    emit_insn (gen_andsi_notsi_si (op2, operands[0], op0));
3444	  }
3445
3446	if (start_bit != 0)
3447          emit_insn (gen_ashlsi3 (op1, op1, operands[2]));
3448
3449	emit_insn (gen_iorsi3 (subtarget, op1, op2));
3450      }
3451
3452    if (subtarget != target)
3453      {
3454	/* If TARGET is still a SUBREG, then it must be wider than a word,
3455	   so we must be careful only to set the subword we were asked to.  */
3456	if (GET_CODE (target) == SUBREG)
3457	  emit_move_insn (target, subtarget);
3458	else
3459	  emit_move_insn (target, gen_lowpart (GET_MODE (target), subtarget));
3460      }
3461
3462    DONE;
3463  }"
3464)
3465
3466(define_insn "insv_zero"
3467  [(set (zero_extract:SI (match_operand:SI 0 "s_register_operand" "+r")
3468                         (match_operand:SI 1 "const_int_M_operand" "M")
3469                         (match_operand:SI 2 "const_int_M_operand" "M"))
3470        (const_int 0))]
3471  "arm_arch_thumb2"
3472  "bfc%?\t%0, %2, %1"
3473  [(set_attr "length" "4")
3474   (set_attr "predicable" "yes")
3475   (set_attr "type" "bfm")]
3476)
3477
3478(define_insn "insv_t2"
3479  [(set (zero_extract:SI (match_operand:SI 0 "s_register_operand" "+r")
3480                         (match_operand:SI 1 "const_int_M_operand" "M")
3481                         (match_operand:SI 2 "const_int_M_operand" "M"))
3482        (match_operand:SI 3 "s_register_operand" "r"))]
3483  "arm_arch_thumb2"
3484  "bfi%?\t%0, %3, %2, %1"
3485  [(set_attr "length" "4")
3486   (set_attr "predicable" "yes")
3487   (set_attr "type" "bfm")]
3488)
3489
3490(define_insn "andsi_notsi_si"
3491  [(set (match_operand:SI 0 "s_register_operand" "=r")
3492	(and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
3493		(match_operand:SI 1 "s_register_operand" "r")))]
3494  "TARGET_32BIT"
3495  "bic%?\\t%0, %1, %2"
3496  [(set_attr "predicable" "yes")
3497   (set_attr "type" "logic_reg")]
3498)
3499
3500(define_insn "andsi_not_shiftsi_si"
3501  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3502	(and:SI (not:SI (match_operator:SI 4 "shift_operator"
3503			 [(match_operand:SI 2 "s_register_operand" "r,r")
3504			  (match_operand:SI 3 "shift_amount_operand" "M,r")]))
3505		(match_operand:SI 1 "s_register_operand" "r,r")))]
3506  "TARGET_32BIT"
3507  "bic%?\\t%0, %1, %2%S4"
3508  [(set_attr "predicable" "yes")
3509   (set_attr "shift" "2")
3510   (set_attr "arch" "32,a")
3511   (set_attr "type" "logic_shift_imm,logic_shift_reg")]
3512)
3513
3514;; Shifted bics pattern used to set up CC status register and not reusing
3515;; bics output.  Pattern restricts Thumb2 shift operand as bics for Thumb2
3516;; does not support shift by register.
3517(define_insn "andsi_not_shiftsi_si_scc_no_reuse"
3518  [(set (reg:CC_NZ CC_REGNUM)
3519	(compare:CC_NZ
3520		(and:SI (not:SI (match_operator:SI 0 "shift_operator"
3521			[(match_operand:SI 1 "s_register_operand" "r,r")
3522			 (match_operand:SI 2 "shift_amount_operand" "M,r")]))
3523			(match_operand:SI 3 "s_register_operand" "r,r"))
3524		(const_int 0)))
3525   (clobber (match_scratch:SI 4 "=r,r"))]
3526  "TARGET_32BIT"
3527  "bics%?\\t%4, %3, %1%S0"
3528  [(set_attr "predicable" "yes")
3529   (set_attr "arch" "32,a")
3530   (set_attr "conds" "set")
3531   (set_attr "shift" "1")
3532   (set_attr "type" "logic_shift_imm,logic_shift_reg")]
3533)
3534
3535;; Same as andsi_not_shiftsi_si_scc_no_reuse, but the bics result is also
3536;; getting reused later.
3537(define_insn "andsi_not_shiftsi_si_scc"
3538  [(parallel [(set (reg:CC_NZ CC_REGNUM)
3539	(compare:CC_NZ
3540		(and:SI (not:SI (match_operator:SI 0 "shift_operator"
3541			[(match_operand:SI 1 "s_register_operand" "r,r")
3542			 (match_operand:SI 2 "shift_amount_operand" "M,r")]))
3543			(match_operand:SI 3 "s_register_operand" "r,r"))
3544		(const_int 0)))
3545	(set (match_operand:SI 4 "s_register_operand" "=r,r")
3546	     (and:SI (not:SI (match_op_dup 0
3547		     [(match_dup 1)
3548		      (match_dup 2)]))
3549		     (match_dup 3)))])]
3550  "TARGET_32BIT"
3551  "bics%?\\t%4, %3, %1%S0"
3552  [(set_attr "predicable" "yes")
3553   (set_attr "arch" "32,a")
3554   (set_attr "conds" "set")
3555   (set_attr "shift" "1")
3556   (set_attr "type" "logic_shift_imm,logic_shift_reg")]
3557)
3558
3559(define_insn "*andsi_notsi_si_compare0"
3560  [(set (reg:CC_NZ CC_REGNUM)
3561	(compare:CC_NZ
3562	 (and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
3563		 (match_operand:SI 1 "s_register_operand" "r"))
3564	 (const_int 0)))
3565   (set (match_operand:SI 0 "s_register_operand" "=r")
3566	(and:SI (not:SI (match_dup 2)) (match_dup 1)))]
3567  "TARGET_32BIT"
3568  "bics\\t%0, %1, %2"
3569  [(set_attr "conds" "set")
3570   (set_attr "type" "logics_shift_reg")]
3571)
3572
3573(define_insn "*andsi_notsi_si_compare0_scratch"
3574  [(set (reg:CC_NZ CC_REGNUM)
3575	(compare:CC_NZ
3576	 (and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
3577		 (match_operand:SI 1 "s_register_operand" "r"))
3578	 (const_int 0)))
3579   (clobber (match_scratch:SI 0 "=r"))]
3580  "TARGET_32BIT"
3581  "bics\\t%0, %1, %2"
3582  [(set_attr "conds" "set")
3583   (set_attr "type" "logics_shift_reg")]
3584)
3585
3586(define_expand "iorsi3"
3587  [(set (match_operand:SI         0 "s_register_operand")
3588	(ior:SI (match_operand:SI 1 "s_register_operand")
3589		(match_operand:SI 2 "reg_or_int_operand")))]
3590  "TARGET_EITHER"
3591  "
3592  if (CONST_INT_P (operands[2]))
3593    {
3594      if (TARGET_32BIT)
3595        {
3596	  if (DONT_EARLY_SPLIT_CONSTANT (INTVAL (operands[2]), IOR))
3597	    operands[2] = force_reg (SImode, operands[2]);
3598	  else
3599	    {
3600	      arm_split_constant (IOR, SImode, NULL_RTX,
3601				  INTVAL (operands[2]), operands[0],
3602				  operands[1],
3603				  optimize && can_create_pseudo_p ());
3604	      DONE;
3605	    }
3606	}
3607      else /* TARGET_THUMB1 */
3608        {
3609          rtx tmp = force_reg (SImode, operands[2]);
3610	  if (rtx_equal_p (operands[0], operands[1]))
3611	    operands[2] = tmp;
3612	  else
3613	    {
3614              operands[2] = operands[1];
3615              operands[1] = tmp;
3616	    }
3617        }
3618    }
3619  "
3620)
3621
3622(define_insn_and_split "*iorsi3_insn"
3623  [(set (match_operand:SI 0 "s_register_operand" "=r,l,r,r,r")
3624	(ior:SI (match_operand:SI 1 "s_register_operand" "%r,0,r,r,r")
3625		(match_operand:SI 2 "reg_or_int_operand" "I,l,K,r,?n")))]
3626  "TARGET_32BIT"
3627  "@
3628   orr%?\\t%0, %1, %2
3629   orr%?\\t%0, %1, %2
3630   orn%?\\t%0, %1, #%B2
3631   orr%?\\t%0, %1, %2
3632   #"
3633  "TARGET_32BIT
3634   && CONST_INT_P (operands[2])
3635   && !(const_ok_for_arm (INTVAL (operands[2]))
3636        || (TARGET_THUMB2 && const_ok_for_arm (~INTVAL (operands[2]))))"
3637  [(clobber (const_int 0))]
3638{
3639  arm_split_constant (IOR, SImode, curr_insn,
3640                      INTVAL (operands[2]), operands[0], operands[1], 0);
3641  DONE;
3642}
3643  [(set_attr "length" "4,4,4,4,16")
3644   (set_attr "arch" "32,t2,t2,32,32")
3645   (set_attr "predicable" "yes")
3646   (set_attr "predicable_short_it" "no,yes,no,no,no")
3647   (set_attr "type" "logic_imm,logic_reg,logic_imm,logic_reg,logic_reg")]
3648)
3649
3650(define_peephole2
3651  [(match_scratch:SI 3 "r")
3652   (set (match_operand:SI 0 "arm_general_register_operand" "")
3653	(ior:SI (match_operand:SI 1 "arm_general_register_operand" "")
3654		(match_operand:SI 2 "const_int_operand" "")))]
3655  "TARGET_ARM
3656   && !const_ok_for_arm (INTVAL (operands[2]))
3657   && const_ok_for_arm (~INTVAL (operands[2]))"
3658  [(set (match_dup 3) (match_dup 2))
3659   (set (match_dup 0) (ior:SI (match_dup 1) (match_dup 3)))]
3660  ""
3661)
3662
3663(define_insn "*iorsi3_compare0"
3664  [(set (reg:CC_NZ CC_REGNUM)
3665	(compare:CC_NZ
3666	 (ior:SI (match_operand:SI 1 "s_register_operand" "%r,0,r")
3667		 (match_operand:SI 2 "arm_rhs_operand" "I,l,r"))
3668	 (const_int 0)))
3669   (set (match_operand:SI 0 "s_register_operand" "=r,l,r")
3670	(ior:SI (match_dup 1) (match_dup 2)))]
3671  "TARGET_32BIT"
3672  "orrs%?\\t%0, %1, %2"
3673  [(set_attr "conds" "set")
3674   (set_attr "arch" "*,t2,*")
3675   (set_attr "length" "4,2,4")
3676   (set_attr "type" "logics_imm,logics_reg,logics_reg")]
3677)
3678
3679(define_insn "*iorsi3_compare0_scratch"
3680  [(set (reg:CC_NZ CC_REGNUM)
3681	(compare:CC_NZ
3682	 (ior:SI (match_operand:SI 1 "s_register_operand" "%r,0,r")
3683		 (match_operand:SI 2 "arm_rhs_operand" "I,l,r"))
3684	 (const_int 0)))
3685   (clobber (match_scratch:SI 0 "=r,l,r"))]
3686  "TARGET_32BIT"
3687  "orrs%?\\t%0, %1, %2"
3688  [(set_attr "conds" "set")
3689   (set_attr "arch" "*,t2,*")
3690   (set_attr "length" "4,2,4")
3691   (set_attr "type" "logics_imm,logics_reg,logics_reg")]
3692)
3693
3694(define_expand "xorsi3"
3695  [(set (match_operand:SI         0 "s_register_operand")
3696	(xor:SI (match_operand:SI 1 "s_register_operand")
3697		(match_operand:SI 2 "reg_or_int_operand")))]
3698  "TARGET_EITHER"
3699  "if (CONST_INT_P (operands[2]))
3700    {
3701      if (TARGET_32BIT)
3702        {
3703	  if (DONT_EARLY_SPLIT_CONSTANT (INTVAL (operands[2]), XOR))
3704	    operands[2] = force_reg (SImode, operands[2]);
3705	  else
3706	    {
3707	      arm_split_constant (XOR, SImode, NULL_RTX,
3708				  INTVAL (operands[2]), operands[0],
3709				  operands[1],
3710				  optimize && can_create_pseudo_p ());
3711	      DONE;
3712	    }
3713	}
3714      else /* TARGET_THUMB1 */
3715        {
3716          rtx tmp = force_reg (SImode, operands[2]);
3717	  if (rtx_equal_p (operands[0], operands[1]))
3718	    operands[2] = tmp;
3719	  else
3720	    {
3721              operands[2] = operands[1];
3722              operands[1] = tmp;
3723	    }
3724        }
3725    }"
3726)
3727
3728(define_insn_and_split "*arm_xorsi3"
3729  [(set (match_operand:SI         0 "s_register_operand" "=r,l,r,r")
3730	(xor:SI (match_operand:SI 1 "s_register_operand" "%r,0,r,r")
3731		(match_operand:SI 2 "reg_or_int_operand" "I,l,r,?n")))]
3732  "TARGET_32BIT"
3733  "@
3734   eor%?\\t%0, %1, %2
3735   eor%?\\t%0, %1, %2
3736   eor%?\\t%0, %1, %2
3737   #"
3738  "TARGET_32BIT
3739   && CONST_INT_P (operands[2])
3740   && !const_ok_for_arm (INTVAL (operands[2]))"
3741  [(clobber (const_int 0))]
3742{
3743  arm_split_constant (XOR, SImode, curr_insn,
3744                      INTVAL (operands[2]), operands[0], operands[1], 0);
3745  DONE;
3746}
3747  [(set_attr "length" "4,4,4,16")
3748   (set_attr "predicable" "yes")
3749   (set_attr "predicable_short_it" "no,yes,no,no")
3750   (set_attr "type"  "logic_imm,logic_reg,logic_reg,multiple")]
3751)
3752
3753(define_insn "*xorsi3_compare0"
3754  [(set (reg:CC_NZ CC_REGNUM)
3755	(compare:CC_NZ (xor:SI (match_operand:SI 1 "s_register_operand" "r,r")
3756				 (match_operand:SI 2 "arm_rhs_operand" "I,r"))
3757			 (const_int 0)))
3758   (set (match_operand:SI 0 "s_register_operand" "=r,r")
3759	(xor:SI (match_dup 1) (match_dup 2)))]
3760  "TARGET_32BIT"
3761  "eors%?\\t%0, %1, %2"
3762  [(set_attr "conds" "set")
3763   (set_attr "type" "logics_imm,logics_reg")]
3764)
3765
3766(define_insn "*xorsi3_compare0_scratch"
3767  [(set (reg:CC_NZ CC_REGNUM)
3768	(compare:CC_NZ (xor:SI (match_operand:SI 0 "s_register_operand" "r,r")
3769				 (match_operand:SI 1 "arm_rhs_operand" "I,r"))
3770			 (const_int 0)))]
3771  "TARGET_32BIT"
3772  "teq%?\\t%0, %1"
3773  [(set_attr "conds" "set")
3774   (set_attr "type" "logics_imm,logics_reg")]
3775)
3776
3777; By splitting (IOR (AND (NOT A) (NOT B)) C) as D = AND (IOR A B) (NOT C),
3778; (NOT D) we can sometimes merge the final NOT into one of the following
3779; insns.
3780
3781(define_split
3782  [(set (match_operand:SI 0 "s_register_operand" "")
3783	(ior:SI (and:SI (not:SI (match_operand:SI 1 "s_register_operand" ""))
3784			(not:SI (match_operand:SI 2 "arm_rhs_operand" "")))
3785		(match_operand:SI 3 "arm_rhs_operand" "")))
3786   (clobber (match_operand:SI 4 "s_register_operand" ""))]
3787  "TARGET_32BIT"
3788  [(set (match_dup 4) (and:SI (ior:SI (match_dup 1) (match_dup 2))
3789			      (not:SI (match_dup 3))))
3790   (set (match_dup 0) (not:SI (match_dup 4)))]
3791  ""
3792)
3793
3794(define_insn_and_split "*andsi_iorsi3_notsi"
3795  [(set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r")
3796	(and:SI (ior:SI (match_operand:SI 1 "s_register_operand" "%0,r,r")
3797			(match_operand:SI 2 "arm_rhs_operand" "rI,0,rI"))
3798		(not:SI (match_operand:SI 3 "arm_rhs_operand" "rI,rI,rI"))))]
3799  "TARGET_32BIT"
3800  "#"   ; "orr%?\\t%0, %1, %2\;bic%?\\t%0, %0, %3"
3801  "&& reload_completed"
3802  [(set (match_dup 0) (ior:SI (match_dup 1) (match_dup 2)))
3803   (set (match_dup 0) (and:SI (match_dup 4) (match_dup 5)))]
3804  {
3805     /* If operands[3] is a constant make sure to fold the NOT into it
3806	to avoid creating a NOT of a CONST_INT.  */
3807    rtx not_rtx = simplify_gen_unary (NOT, SImode, operands[3], SImode);
3808    if (CONST_INT_P (not_rtx))
3809      {
3810	operands[4] = operands[0];
3811	operands[5] = not_rtx;
3812      }
3813    else
3814      {
3815	operands[5] = operands[0];
3816	operands[4] = not_rtx;
3817      }
3818  }
3819  [(set_attr "length" "8")
3820   (set_attr "ce_count" "2")
3821   (set_attr "predicable" "yes")
3822   (set_attr "type" "multiple")]
3823)
3824
3825; ??? Are these four splitters still beneficial when the Thumb-2 bitfield
3826; insns are available?
3827(define_split
3828  [(set (match_operand:SI 0 "s_register_operand" "")
3829	(match_operator:SI 1 "logical_binary_operator"
3830	 [(zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
3831			   (match_operand:SI 3 "const_int_operand" "")
3832			   (match_operand:SI 4 "const_int_operand" ""))
3833	  (match_operator:SI 9 "logical_binary_operator"
3834	   [(lshiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3835			 (match_operand:SI 6 "const_int_operand" ""))
3836	    (match_operand:SI 7 "s_register_operand" "")])]))
3837   (clobber (match_operand:SI 8 "s_register_operand" ""))]
3838  "TARGET_32BIT
3839   && GET_CODE (operands[1]) == GET_CODE (operands[9])
3840   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3841  [(set (match_dup 8)
3842	(match_op_dup 1
3843	 [(ashift:SI (match_dup 2) (match_dup 4))
3844	  (match_dup 5)]))
3845   (set (match_dup 0)
3846	(match_op_dup 1
3847	 [(lshiftrt:SI (match_dup 8) (match_dup 6))
3848	  (match_dup 7)]))]
3849  "
3850  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3851")
3852
3853(define_split
3854  [(set (match_operand:SI 0 "s_register_operand" "")
3855	(match_operator:SI 1 "logical_binary_operator"
3856	 [(match_operator:SI 9 "logical_binary_operator"
3857	   [(lshiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3858			 (match_operand:SI 6 "const_int_operand" ""))
3859	    (match_operand:SI 7 "s_register_operand" "")])
3860	  (zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
3861			   (match_operand:SI 3 "const_int_operand" "")
3862			   (match_operand:SI 4 "const_int_operand" ""))]))
3863   (clobber (match_operand:SI 8 "s_register_operand" ""))]
3864  "TARGET_32BIT
3865   && GET_CODE (operands[1]) == GET_CODE (operands[9])
3866   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3867  [(set (match_dup 8)
3868	(match_op_dup 1
3869	 [(ashift:SI (match_dup 2) (match_dup 4))
3870	  (match_dup 5)]))
3871   (set (match_dup 0)
3872	(match_op_dup 1
3873	 [(lshiftrt:SI (match_dup 8) (match_dup 6))
3874	  (match_dup 7)]))]
3875  "
3876  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3877")
3878
3879(define_split
3880  [(set (match_operand:SI 0 "s_register_operand" "")
3881	(match_operator:SI 1 "logical_binary_operator"
3882	 [(sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
3883			   (match_operand:SI 3 "const_int_operand" "")
3884			   (match_operand:SI 4 "const_int_operand" ""))
3885	  (match_operator:SI 9 "logical_binary_operator"
3886	   [(ashiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3887			 (match_operand:SI 6 "const_int_operand" ""))
3888	    (match_operand:SI 7 "s_register_operand" "")])]))
3889   (clobber (match_operand:SI 8 "s_register_operand" ""))]
3890  "TARGET_32BIT
3891   && GET_CODE (operands[1]) == GET_CODE (operands[9])
3892   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3893  [(set (match_dup 8)
3894	(match_op_dup 1
3895	 [(ashift:SI (match_dup 2) (match_dup 4))
3896	  (match_dup 5)]))
3897   (set (match_dup 0)
3898	(match_op_dup 1
3899	 [(ashiftrt:SI (match_dup 8) (match_dup 6))
3900	  (match_dup 7)]))]
3901  "
3902  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3903")
3904
3905(define_split
3906  [(set (match_operand:SI 0 "s_register_operand" "")
3907	(match_operator:SI 1 "logical_binary_operator"
3908	 [(match_operator:SI 9 "logical_binary_operator"
3909	   [(ashiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3910			 (match_operand:SI 6 "const_int_operand" ""))
3911	    (match_operand:SI 7 "s_register_operand" "")])
3912	  (sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
3913			   (match_operand:SI 3 "const_int_operand" "")
3914			   (match_operand:SI 4 "const_int_operand" ""))]))
3915   (clobber (match_operand:SI 8 "s_register_operand" ""))]
3916  "TARGET_32BIT
3917   && GET_CODE (operands[1]) == GET_CODE (operands[9])
3918   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3919  [(set (match_dup 8)
3920	(match_op_dup 1
3921	 [(ashift:SI (match_dup 2) (match_dup 4))
3922	  (match_dup 5)]))
3923   (set (match_dup 0)
3924	(match_op_dup 1
3925	 [(ashiftrt:SI (match_dup 8) (match_dup 6))
3926	  (match_dup 7)]))]
3927  "
3928  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3929")
3930
3931
3932;; Minimum and maximum insns
3933
3934(define_expand "smaxsi3"
3935  [(parallel [
3936    (set (match_operand:SI 0 "s_register_operand")
3937	 (smax:SI (match_operand:SI 1 "s_register_operand")
3938		  (match_operand:SI 2 "arm_rhs_operand")))
3939    (clobber (reg:CC CC_REGNUM))])]
3940  "TARGET_32BIT"
3941  "
3942  if (operands[2] == const0_rtx || operands[2] == constm1_rtx)
3943    {
3944      /* No need for a clobber of the condition code register here.  */
3945      emit_insn (gen_rtx_SET (operands[0],
3946			      gen_rtx_SMAX (SImode, operands[1],
3947					    operands[2])));
3948      DONE;
3949    }
3950")
3951
3952(define_insn "*smax_0"
3953  [(set (match_operand:SI 0 "s_register_operand" "=r")
3954	(smax:SI (match_operand:SI 1 "s_register_operand" "r")
3955		 (const_int 0)))]
3956  "TARGET_32BIT"
3957  "bic%?\\t%0, %1, %1, asr #31"
3958  [(set_attr "predicable" "yes")
3959   (set_attr "type" "logic_shift_reg")]
3960)
3961
3962(define_insn "*smax_m1"
3963  [(set (match_operand:SI 0 "s_register_operand" "=r")
3964	(smax:SI (match_operand:SI 1 "s_register_operand" "r")
3965		 (const_int -1)))]
3966  "TARGET_32BIT"
3967  "orr%?\\t%0, %1, %1, asr #31"
3968  [(set_attr "predicable" "yes")
3969   (set_attr "type" "logic_shift_reg")]
3970)
3971
3972(define_insn_and_split "*arm_smax_insn"
3973  [(set (match_operand:SI          0 "s_register_operand" "=r,r")
3974	(smax:SI (match_operand:SI 1 "s_register_operand"  "%0,?r")
3975		 (match_operand:SI 2 "arm_rhs_operand"    "rI,rI")))
3976   (clobber (reg:CC CC_REGNUM))]
3977  "TARGET_ARM"
3978  "#"
3979   ; cmp\\t%1, %2\;movlt\\t%0, %2
3980   ; cmp\\t%1, %2\;movge\\t%0, %1\;movlt\\t%0, %2"
3981  "TARGET_ARM"
3982  [(set (reg:CC CC_REGNUM)
3983        (compare:CC (match_dup 1) (match_dup 2)))
3984   (set (match_dup 0)
3985        (if_then_else:SI (ge:SI (reg:CC CC_REGNUM) (const_int 0))
3986                         (match_dup 1)
3987                         (match_dup 2)))]
3988  ""
3989  [(set_attr "conds" "clob")
3990   (set_attr "length" "8,12")
3991   (set_attr "type" "multiple")]
3992)
3993
3994(define_expand "sminsi3"
3995  [(parallel [
3996    (set (match_operand:SI 0 "s_register_operand")
3997	 (smin:SI (match_operand:SI 1 "s_register_operand")
3998		  (match_operand:SI 2 "arm_rhs_operand")))
3999    (clobber (reg:CC CC_REGNUM))])]
4000  "TARGET_32BIT"
4001  "
4002  if (operands[2] == const0_rtx)
4003    {
4004      /* No need for a clobber of the condition code register here.  */
4005      emit_insn (gen_rtx_SET (operands[0],
4006			      gen_rtx_SMIN (SImode, operands[1],
4007					    operands[2])));
4008      DONE;
4009    }
4010")
4011
4012(define_insn "*smin_0"
4013  [(set (match_operand:SI 0 "s_register_operand" "=r")
4014	(smin:SI (match_operand:SI 1 "s_register_operand" "r")
4015		 (const_int 0)))]
4016  "TARGET_32BIT"
4017  "and%?\\t%0, %1, %1, asr #31"
4018  [(set_attr "predicable" "yes")
4019   (set_attr "type" "logic_shift_reg")]
4020)
4021
4022(define_insn_and_split "*arm_smin_insn"
4023  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4024	(smin:SI (match_operand:SI 1 "s_register_operand" "%0,?r")
4025		 (match_operand:SI 2 "arm_rhs_operand" "rI,rI")))
4026   (clobber (reg:CC CC_REGNUM))]
4027  "TARGET_ARM"
4028  "#"
4029    ; cmp\\t%1, %2\;movge\\t%0, %2
4030    ; cmp\\t%1, %2\;movlt\\t%0, %1\;movge\\t%0, %2"
4031  "TARGET_ARM"
4032  [(set (reg:CC CC_REGNUM)
4033        (compare:CC (match_dup 1) (match_dup 2)))
4034   (set (match_dup 0)
4035        (if_then_else:SI (lt:SI (reg:CC CC_REGNUM) (const_int 0))
4036                         (match_dup 1)
4037                         (match_dup 2)))]
4038  ""
4039  [(set_attr "conds" "clob")
4040   (set_attr "length" "8,12")
4041   (set_attr "type" "multiple,multiple")]
4042)
4043
4044(define_expand "umaxsi3"
4045  [(parallel [
4046    (set (match_operand:SI 0 "s_register_operand")
4047	 (umax:SI (match_operand:SI 1 "s_register_operand")
4048		  (match_operand:SI 2 "arm_rhs_operand")))
4049    (clobber (reg:CC CC_REGNUM))])]
4050  "TARGET_32BIT"
4051  ""
4052)
4053
4054(define_insn_and_split "*arm_umaxsi3"
4055  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
4056	(umax:SI (match_operand:SI 1 "s_register_operand" "0,r,?r")
4057		 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
4058   (clobber (reg:CC CC_REGNUM))]
4059  "TARGET_ARM"
4060  "#"
4061    ; cmp\\t%1, %2\;movcc\\t%0, %2
4062    ; cmp\\t%1, %2\;movcs\\t%0, %1
4063    ; cmp\\t%1, %2\;movcs\\t%0, %1\;movcc\\t%0, %2"
4064  "TARGET_ARM"
4065  [(set (reg:CC CC_REGNUM)
4066        (compare:CC (match_dup 1) (match_dup 2)))
4067   (set (match_dup 0)
4068        (if_then_else:SI (geu:SI (reg:CC CC_REGNUM) (const_int 0))
4069                         (match_dup 1)
4070                         (match_dup 2)))]
4071  ""
4072  [(set_attr "conds" "clob")
4073   (set_attr "length" "8,8,12")
4074   (set_attr "type" "store_4")]
4075)
4076
4077(define_expand "uminsi3"
4078  [(parallel [
4079    (set (match_operand:SI 0 "s_register_operand")
4080	 (umin:SI (match_operand:SI 1 "s_register_operand")
4081		  (match_operand:SI 2 "arm_rhs_operand")))
4082    (clobber (reg:CC CC_REGNUM))])]
4083  "TARGET_32BIT"
4084  ""
4085)
4086
4087(define_insn_and_split "*arm_uminsi3"
4088  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
4089	(umin:SI (match_operand:SI 1 "s_register_operand" "0,r,?r")
4090		 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
4091   (clobber (reg:CC CC_REGNUM))]
4092  "TARGET_ARM"
4093  "#"
4094   ; cmp\\t%1, %2\;movcs\\t%0, %2
4095   ; cmp\\t%1, %2\;movcc\\t%0, %1
4096   ; cmp\\t%1, %2\;movcc\\t%0, %1\;movcs\\t%0, %2"
4097  "TARGET_ARM"
4098  [(set (reg:CC CC_REGNUM)
4099        (compare:CC (match_dup 1) (match_dup 2)))
4100   (set (match_dup 0)
4101        (if_then_else:SI (ltu:SI (reg:CC CC_REGNUM) (const_int 0))
4102                         (match_dup 1)
4103                         (match_dup 2)))]
4104  ""
4105  [(set_attr "conds" "clob")
4106   (set_attr "length" "8,8,12")
4107   (set_attr "type" "store_4")]
4108)
4109
4110(define_insn "*store_minmaxsi"
4111  [(set (match_operand:SI 0 "memory_operand" "=m")
4112	(match_operator:SI 3 "minmax_operator"
4113	 [(match_operand:SI 1 "s_register_operand" "r")
4114	  (match_operand:SI 2 "s_register_operand" "r")]))
4115   (clobber (reg:CC CC_REGNUM))]
4116  "TARGET_32BIT && optimize_function_for_size_p (cfun) && !arm_restrict_it"
4117  "*
4118  operands[3] = gen_rtx_fmt_ee (minmax_code (operands[3]), SImode,
4119				operands[1], operands[2]);
4120  output_asm_insn (\"cmp\\t%1, %2\", operands);
4121  if (TARGET_THUMB2)
4122    output_asm_insn (\"ite\t%d3\", operands);
4123  output_asm_insn (\"str%d3\\t%1, %0\", operands);
4124  output_asm_insn (\"str%D3\\t%2, %0\", operands);
4125  return \"\";
4126  "
4127  [(set_attr "conds" "clob")
4128   (set (attr "length")
4129	(if_then_else (eq_attr "is_thumb" "yes")
4130		      (const_int 14)
4131		      (const_int 12)))
4132   (set_attr "type" "store_4")]
4133)
4134
4135; Reject the frame pointer in operand[1], since reloading this after
4136; it has been eliminated can cause carnage.
4137(define_insn "*minmax_arithsi"
4138  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4139	(match_operator:SI 4 "shiftable_operator"
4140	 [(match_operator:SI 5 "minmax_operator"
4141	   [(match_operand:SI 2 "s_register_operand" "r,r")
4142	    (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
4143	  (match_operand:SI 1 "s_register_operand" "0,?r")]))
4144   (clobber (reg:CC CC_REGNUM))]
4145  "TARGET_32BIT && !arm_eliminable_register (operands[1]) && !arm_restrict_it"
4146  "*
4147  {
4148    enum rtx_code code = GET_CODE (operands[4]);
4149    bool need_else;
4150
4151    if (which_alternative != 0 || operands[3] != const0_rtx
4152        || (code != PLUS && code != IOR && code != XOR))
4153      need_else = true;
4154    else
4155      need_else = false;
4156
4157    operands[5] = gen_rtx_fmt_ee (minmax_code (operands[5]), SImode,
4158				  operands[2], operands[3]);
4159    output_asm_insn (\"cmp\\t%2, %3\", operands);
4160    if (TARGET_THUMB2)
4161      {
4162	if (need_else)
4163	  output_asm_insn (\"ite\\t%d5\", operands);
4164	else
4165	  output_asm_insn (\"it\\t%d5\", operands);
4166      }
4167    output_asm_insn (\"%i4%d5\\t%0, %1, %2\", operands);
4168    if (need_else)
4169      output_asm_insn (\"%i4%D5\\t%0, %1, %3\", operands);
4170    return \"\";
4171  }"
4172  [(set_attr "conds" "clob")
4173   (set (attr "length")
4174	(if_then_else (eq_attr "is_thumb" "yes")
4175		      (const_int 14)
4176		      (const_int 12)))
4177   (set_attr "type" "multiple")]
4178)
4179
4180; Reject the frame pointer in operand[1], since reloading this after
4181; it has been eliminated can cause carnage.
4182(define_insn_and_split "*minmax_arithsi_non_canon"
4183  [(set (match_operand:SI 0 "s_register_operand" "=Ts,Ts")
4184	(minus:SI
4185	 (match_operand:SI 1 "s_register_operand" "0,?Ts")
4186	  (match_operator:SI 4 "minmax_operator"
4187	   [(match_operand:SI 2 "s_register_operand" "Ts,Ts")
4188	    (match_operand:SI 3 "arm_rhs_operand" "TsI,TsI")])))
4189   (clobber (reg:CC CC_REGNUM))]
4190  "TARGET_32BIT && !arm_eliminable_register (operands[1])
4191   && !(arm_restrict_it && CONST_INT_P (operands[3]))"
4192  "#"
4193  "TARGET_32BIT && !arm_eliminable_register (operands[1]) && reload_completed"
4194  [(set (reg:CC CC_REGNUM)
4195        (compare:CC (match_dup 2) (match_dup 3)))
4196
4197   (cond_exec (match_op_dup 4 [(reg:CC CC_REGNUM) (const_int 0)])
4198              (set (match_dup 0)
4199                   (minus:SI (match_dup 1)
4200                             (match_dup 2))))
4201   (cond_exec (match_op_dup 5 [(reg:CC CC_REGNUM) (const_int 0)])
4202              (set (match_dup 0)
4203                   (match_dup 6)))]
4204  {
4205  machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
4206                                           operands[2], operands[3]);
4207  enum rtx_code rc = minmax_code (operands[4]);
4208  operands[4] = gen_rtx_fmt_ee (rc, VOIDmode,
4209                                operands[2], operands[3]);
4210
4211  if (mode == CCFPmode || mode == CCFPEmode)
4212    rc = reverse_condition_maybe_unordered (rc);
4213  else
4214    rc = reverse_condition (rc);
4215  operands[5] = gen_rtx_fmt_ee (rc, SImode, operands[2], operands[3]);
4216  if (CONST_INT_P (operands[3]))
4217    operands[6] = plus_constant (SImode, operands[1], -INTVAL (operands[3]));
4218  else
4219    operands[6] = gen_rtx_MINUS (SImode, operands[1], operands[3]);
4220  }
4221  [(set_attr "conds" "clob")
4222   (set (attr "length")
4223	(if_then_else (eq_attr "is_thumb" "yes")
4224		      (const_int 14)
4225		      (const_int 12)))
4226   (set_attr "type" "multiple")]
4227)
4228
4229
4230(define_expand "arm_<ss_op>"
4231  [(set (match_operand:SI 0 "s_register_operand")
4232	(SSPLUSMINUS:SI (match_operand:SI 1 "s_register_operand")
4233			(match_operand:SI 2 "s_register_operand")))]
4234  "TARGET_DSP_MULTIPLY"
4235  {
4236    if (ARM_Q_BIT_READ)
4237      emit_insn (gen_arm_<ss_op>_setq_insn (operands[0],
4238					    operands[1], operands[2]));
4239    else
4240      emit_insn (gen_arm_<ss_op>_insn (operands[0], operands[1], operands[2]));
4241    DONE;
4242  }
4243)
4244
4245(define_insn "arm_<ss_op><add_clobber_q_name>_insn"
4246  [(set (match_operand:SI 0 "s_register_operand" "=r")
4247	(SSPLUSMINUS:SI (match_operand:SI 1 "s_register_operand" "r")
4248			(match_operand:SI 2 "s_register_operand" "r")))]
4249  "TARGET_DSP_MULTIPLY && <add_clobber_q_pred>"
4250  "<ss_op>%?\t%0, %1, %2"
4251  [(set_attr "predicable" "yes")
4252   (set_attr "type" "alu_dsp_reg")]
4253)
4254
4255(define_code_iterator SAT [smin smax])
4256(define_code_attr SATrev [(smin "smax") (smax "smin")])
4257(define_code_attr SATlo [(smin "1") (smax "2")])
4258(define_code_attr SAThi [(smin "2") (smax "1")])
4259
4260(define_expand "arm_ssat"
4261  [(match_operand:SI 0 "s_register_operand")
4262   (match_operand:SI 1 "s_register_operand")
4263   (match_operand:SI 2 "const_int_operand")]
4264  "TARGET_32BIT && arm_arch6"
4265  {
4266    HOST_WIDE_INT val = INTVAL (operands[2]);
4267    /* The builtin checking code should have ensured the right
4268       range for the immediate.  */
4269    gcc_assert (IN_RANGE (val, 1, 32));
4270    HOST_WIDE_INT upper_bound = (HOST_WIDE_INT_1 << (val - 1)) - 1;
4271    HOST_WIDE_INT lower_bound = -upper_bound - 1;
4272    rtx up_rtx = gen_int_mode (upper_bound, SImode);
4273    rtx lo_rtx = gen_int_mode (lower_bound, SImode);
4274    if (ARM_Q_BIT_READ)
4275      emit_insn (gen_satsi_smin_setq (operands[0], lo_rtx,
4276				      up_rtx, operands[1]));
4277    else
4278      emit_insn (gen_satsi_smin (operands[0], lo_rtx, up_rtx, operands[1]));
4279    DONE;
4280  }
4281)
4282
4283(define_expand "arm_usat"
4284  [(match_operand:SI 0 "s_register_operand")
4285   (match_operand:SI 1 "s_register_operand")
4286   (match_operand:SI 2 "const_int_operand")]
4287  "TARGET_32BIT && arm_arch6"
4288  {
4289    HOST_WIDE_INT val = INTVAL (operands[2]);
4290    /* The builtin checking code should have ensured the right
4291       range for the immediate.  */
4292    gcc_assert (IN_RANGE (val, 0, 31));
4293    HOST_WIDE_INT upper_bound = (HOST_WIDE_INT_1 << val) - 1;
4294    rtx up_rtx = gen_int_mode (upper_bound, SImode);
4295    rtx lo_rtx = CONST0_RTX (SImode);
4296    if (ARM_Q_BIT_READ)
4297      emit_insn (gen_satsi_smin_setq (operands[0], lo_rtx, up_rtx,
4298				      operands[1]));
4299    else
4300      emit_insn (gen_satsi_smin (operands[0], lo_rtx, up_rtx, operands[1]));
4301    DONE;
4302  }
4303)
4304
4305(define_insn "arm_get_apsr"
4306  [(set (match_operand:SI 0 "s_register_operand" "=r")
4307	(unspec:SI [(reg:CC APSRQ_REGNUM)] UNSPEC_APSR_READ))]
4308  "TARGET_ARM_QBIT"
4309  "mrs%?\t%0, APSR"
4310  [(set_attr "predicable" "yes")
4311   (set_attr "conds" "use")]
4312)
4313
4314(define_insn "arm_set_apsr"
4315  [(set (reg:CC APSRQ_REGNUM)
4316	(unspec_volatile:CC
4317	  [(match_operand:SI 0 "s_register_operand" "r")] VUNSPEC_APSR_WRITE))]
4318  "TARGET_ARM_QBIT"
4319  "msr%?\tAPSR_nzcvq, %0"
4320  [(set_attr "predicable" "yes")
4321   (set_attr "conds" "set")]
4322)
4323
4324;; Read the APSR and extract the Q bit (bit 27)
4325(define_expand "arm_saturation_occurred"
4326  [(match_operand:SI 0 "s_register_operand")]
4327  "TARGET_ARM_QBIT"
4328  {
4329    rtx apsr = gen_reg_rtx (SImode);
4330    emit_insn (gen_arm_get_apsr (apsr));
4331    emit_insn (gen_extzv (operands[0], apsr, CONST1_RTX (SImode),
4332	       gen_int_mode (27, SImode)));
4333    DONE;
4334  }
4335)
4336
4337;; Read the APSR and set the Q bit (bit position 27) according to operand 0
4338(define_expand "arm_set_saturation"
4339  [(match_operand:SI 0 "reg_or_int_operand")]
4340  "TARGET_ARM_QBIT"
4341  {
4342    rtx apsr = gen_reg_rtx (SImode);
4343    emit_insn (gen_arm_get_apsr (apsr));
4344    rtx to_insert = gen_reg_rtx (SImode);
4345    if (CONST_INT_P (operands[0]))
4346      emit_move_insn (to_insert, operands[0] == CONST0_RTX (SImode)
4347				 ? CONST0_RTX (SImode) : CONST1_RTX (SImode));
4348    else
4349      {
4350        rtx cmp = gen_rtx_NE (SImode, operands[0], CONST0_RTX (SImode));
4351        emit_insn (gen_cstoresi4 (to_insert, cmp, operands[0],
4352				  CONST0_RTX (SImode)));
4353      }
4354    emit_insn (gen_insv (apsr, CONST1_RTX (SImode),
4355	       gen_int_mode (27, SImode), to_insert));
4356    emit_insn (gen_arm_set_apsr (apsr));
4357    DONE;
4358  }
4359)
4360
4361(define_insn "satsi_<SAT:code><add_clobber_q_name>"
4362  [(set (match_operand:SI 0 "s_register_operand" "=r")
4363        (SAT:SI (<SATrev>:SI (match_operand:SI 3 "s_register_operand" "r")
4364                           (match_operand:SI 1 "const_int_operand" "i"))
4365                (match_operand:SI 2 "const_int_operand" "i")))]
4366  "TARGET_32BIT && arm_arch6 && <add_clobber_q_pred>
4367   && arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>], NULL, NULL)"
4368{
4369  int mask;
4370  bool signed_sat;
4371  if (!arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>],
4372                               &mask, &signed_sat))
4373    gcc_unreachable ();
4374
4375  operands[1] = GEN_INT (mask);
4376  if (signed_sat)
4377    return "ssat%?\t%0, %1, %3";
4378  else
4379    return "usat%?\t%0, %1, %3";
4380}
4381  [(set_attr "predicable" "yes")
4382   (set_attr "type" "alus_imm")]
4383)
4384
4385(define_insn "*satsi_<SAT:code>_shift"
4386  [(set (match_operand:SI 0 "s_register_operand" "=r")
4387        (SAT:SI (<SATrev>:SI (match_operator:SI 3 "sat_shift_operator"
4388                             [(match_operand:SI 4 "s_register_operand" "r")
4389                              (match_operand:SI 5 "const_int_operand" "i")])
4390                           (match_operand:SI 1 "const_int_operand" "i"))
4391                (match_operand:SI 2 "const_int_operand" "i")))]
4392  "TARGET_32BIT && arm_arch6 && !ARM_Q_BIT_READ
4393   && arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>], NULL, NULL)"
4394{
4395  int mask;
4396  bool signed_sat;
4397  if (!arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>],
4398                               &mask, &signed_sat))
4399    gcc_unreachable ();
4400
4401  operands[1] = GEN_INT (mask);
4402  if (signed_sat)
4403    return "ssat%?\t%0, %1, %4%S3";
4404  else
4405    return "usat%?\t%0, %1, %4%S3";
4406}
4407  [(set_attr "predicable" "yes")
4408   (set_attr "shift" "3")
4409   (set_attr "type" "logic_shift_reg")])
4410
4411;; Custom Datapath Extension insns.
4412(define_insn "arm_cx1<mode>"
4413   [(set (match_operand:SIDI 0 "s_register_operand" "=r")
4414	 (unspec:SIDI [(match_operand:SI 1 "const_int_coproc_operand" "i")
4415	               (match_operand:SI 2 "const_int_ccde1_operand" "i")]
4416	    UNSPEC_CDE))]
4417   "TARGET_CDE"
4418   "cx1<cde_suffix>\\tp%c1, <cde_dest>, %2"
4419  [(set_attr "type" "coproc")]
4420)
4421
4422(define_insn "arm_cx1a<mode>"
4423   [(set (match_operand:SIDI 0 "s_register_operand" "=r")
4424	 (unspec:SIDI [(match_operand:SI 1 "const_int_coproc_operand" "i")
4425		       (match_operand:SIDI 2 "s_register_operand" "0")
4426	               (match_operand:SI 3 "const_int_ccde1_operand" "i")]
4427	    UNSPEC_CDEA))]
4428   "TARGET_CDE"
4429   "cx1<cde_suffix>a\\tp%c1, <cde_dest>, %3"
4430  [(set_attr "type" "coproc")]
4431)
4432
4433(define_insn "arm_cx2<mode>"
4434   [(set (match_operand:SIDI 0 "s_register_operand" "=r")
4435	 (unspec:SIDI [(match_operand:SI 1 "const_int_coproc_operand" "i")
4436		       (match_operand:SI 2 "s_register_operand" "r")
4437	               (match_operand:SI 3 "const_int_ccde2_operand" "i")]
4438	    UNSPEC_CDE))]
4439   "TARGET_CDE"
4440   "cx2<cde_suffix>\\tp%c1, <cde_dest>, %2, %3"
4441  [(set_attr "type" "coproc")]
4442)
4443
4444(define_insn "arm_cx2a<mode>"
4445   [(set (match_operand:SIDI 0 "s_register_operand" "=r")
4446	 (unspec:SIDI [(match_operand:SI 1 "const_int_coproc_operand" "i")
4447		       (match_operand:SIDI 2 "s_register_operand" "0")
4448		       (match_operand:SI 3 "s_register_operand" "r")
4449	               (match_operand:SI 4 "const_int_ccde2_operand" "i")]
4450	    UNSPEC_CDEA))]
4451   "TARGET_CDE"
4452   "cx2<cde_suffix>a\\tp%c1, <cde_dest>, %3, %4"
4453  [(set_attr "type" "coproc")]
4454)
4455
4456(define_insn "arm_cx3<mode>"
4457   [(set (match_operand:SIDI 0 "s_register_operand" "=r")
4458	 (unspec:SIDI [(match_operand:SI 1 "const_int_coproc_operand" "i")
4459		       (match_operand:SI 2 "s_register_operand" "r")
4460		       (match_operand:SI 3 "s_register_operand" "r")
4461	               (match_operand:SI 4 "const_int_ccde3_operand" "i")]
4462	    UNSPEC_CDE))]
4463   "TARGET_CDE"
4464   "cx3<cde_suffix>\\tp%c1, <cde_dest>, %2, %3, %4"
4465  [(set_attr "type" "coproc")]
4466)
4467
4468(define_insn "arm_cx3a<mode>"
4469   [(set (match_operand:SIDI 0 "s_register_operand" "=r")
4470	 (unspec:SIDI [(match_operand:SI 1 "const_int_coproc_operand" "i")
4471		       (match_operand:SIDI 2 "s_register_operand" "0")
4472		       (match_operand:SI 3 "s_register_operand" "r")
4473		       (match_operand:SI 4 "s_register_operand" "r")
4474                       (match_operand:SI 5 "const_int_ccde3_operand" "i")]
4475	    UNSPEC_CDEA))]
4476   "TARGET_CDE"
4477   "cx3<cde_suffix>a\\tp%c1, <cde_dest>, %3, %4, %5"
4478  [(set_attr "type" "coproc")]
4479)
4480
4481;; Shift and rotation insns
4482
4483(define_expand "ashldi3"
4484  [(set (match_operand:DI            0 "s_register_operand")
4485        (ashift:DI (match_operand:DI 1 "s_register_operand")
4486                   (match_operand:SI 2 "reg_or_int_operand")))]
4487  "TARGET_32BIT"
4488  "
4489  if (TARGET_HAVE_MVE && !BYTES_BIG_ENDIAN)
4490    {
4491      if (!reg_or_int_operand (operands[2], SImode))
4492        operands[2] = force_reg (SImode, operands[2]);
4493
4494      /* Armv8.1-M Mainline double shifts are not expanded.  */
4495      if (arm_reg_or_long_shift_imm (operands[2], GET_MODE (operands[2]))
4496	  && (REG_P (operands[2]) || INTVAL(operands[2]) != 32))
4497        {
4498	  if (!reg_overlap_mentioned_p(operands[0], operands[1]))
4499	    emit_insn (gen_movdi (operands[0], operands[1]));
4500
4501	  emit_insn (gen_thumb2_lsll (operands[0], operands[2]));
4502	  DONE;
4503	}
4504    }
4505
4506  arm_emit_coreregs_64bit_shift (ASHIFT, operands[0], operands[1],
4507				 operands[2], gen_reg_rtx (SImode),
4508				 gen_reg_rtx (SImode));
4509  DONE;
4510")
4511
4512(define_expand "ashlsi3"
4513  [(set (match_operand:SI            0 "s_register_operand")
4514	(ashift:SI (match_operand:SI 1 "s_register_operand")
4515		   (match_operand:SI 2 "arm_rhs_operand")))]
4516  "TARGET_EITHER"
4517  "
4518  if (CONST_INT_P (operands[2])
4519      && (UINTVAL (operands[2])) > 31)
4520    {
4521      emit_insn (gen_movsi (operands[0], const0_rtx));
4522      DONE;
4523    }
4524  "
4525)
4526
4527(define_expand "ashrdi3"
4528  [(set (match_operand:DI              0 "s_register_operand")
4529        (ashiftrt:DI (match_operand:DI 1 "s_register_operand")
4530                     (match_operand:SI 2 "reg_or_int_operand")))]
4531  "TARGET_32BIT"
4532  "
4533  /* Armv8.1-M Mainline double shifts are not expanded.  */
4534  if (TARGET_HAVE_MVE && !BYTES_BIG_ENDIAN
4535      && arm_reg_or_long_shift_imm (operands[2], GET_MODE (operands[2])))
4536    {
4537      if (!reg_overlap_mentioned_p(operands[0], operands[1]))
4538	emit_insn (gen_movdi (operands[0], operands[1]));
4539
4540      emit_insn (gen_thumb2_asrl (operands[0], operands[2]));
4541      DONE;
4542    }
4543
4544  arm_emit_coreregs_64bit_shift (ASHIFTRT, operands[0], operands[1],
4545				 operands[2], gen_reg_rtx (SImode),
4546				 gen_reg_rtx (SImode));
4547  DONE;
4548")
4549
4550(define_expand "ashrsi3"
4551  [(set (match_operand:SI              0 "s_register_operand")
4552	(ashiftrt:SI (match_operand:SI 1 "s_register_operand")
4553		     (match_operand:SI 2 "arm_rhs_operand")))]
4554  "TARGET_EITHER"
4555  "
4556  if (CONST_INT_P (operands[2])
4557      && UINTVAL (operands[2]) > 31)
4558    operands[2] = GEN_INT (31);
4559  "
4560)
4561
4562(define_expand "lshrdi3"
4563  [(set (match_operand:DI              0 "s_register_operand")
4564        (lshiftrt:DI (match_operand:DI 1 "s_register_operand")
4565                     (match_operand:SI 2 "reg_or_int_operand")))]
4566  "TARGET_32BIT"
4567  "
4568  /* Armv8.1-M Mainline double shifts are not expanded.  */
4569  if (TARGET_HAVE_MVE && !BYTES_BIG_ENDIAN
4570    && long_shift_imm (operands[2], GET_MODE (operands[2])))
4571    {
4572      if (!reg_overlap_mentioned_p(operands[0], operands[1]))
4573        emit_insn (gen_movdi (operands[0], operands[1]));
4574
4575      emit_insn (gen_thumb2_lsrl (operands[0], operands[2]));
4576      DONE;
4577    }
4578
4579  arm_emit_coreregs_64bit_shift (LSHIFTRT, operands[0], operands[1],
4580				 operands[2], gen_reg_rtx (SImode),
4581				 gen_reg_rtx (SImode));
4582  DONE;
4583")
4584
4585(define_expand "lshrsi3"
4586  [(set (match_operand:SI              0 "s_register_operand")
4587	(lshiftrt:SI (match_operand:SI 1 "s_register_operand")
4588		     (match_operand:SI 2 "arm_rhs_operand")))]
4589  "TARGET_EITHER"
4590  "
4591  if (CONST_INT_P (operands[2])
4592      && (UINTVAL (operands[2])) > 31)
4593    {
4594      emit_insn (gen_movsi (operands[0], const0_rtx));
4595      DONE;
4596    }
4597  "
4598)
4599
4600(define_expand "rotlsi3"
4601  [(set (match_operand:SI              0 "s_register_operand")
4602	(rotatert:SI (match_operand:SI 1 "s_register_operand")
4603		     (match_operand:SI 2 "reg_or_int_operand")))]
4604  "TARGET_32BIT"
4605  "
4606  if (CONST_INT_P (operands[2]))
4607    operands[2] = GEN_INT ((32 - INTVAL (operands[2])) % 32);
4608  else
4609    {
4610      rtx reg = gen_reg_rtx (SImode);
4611      emit_insn (gen_subsi3 (reg, GEN_INT (32), operands[2]));
4612      operands[2] = reg;
4613    }
4614  "
4615)
4616
4617(define_expand "rotrsi3"
4618  [(set (match_operand:SI              0 "s_register_operand")
4619	(rotatert:SI (match_operand:SI 1 "s_register_operand")
4620		     (match_operand:SI 2 "arm_rhs_operand")))]
4621  "TARGET_EITHER"
4622  "
4623  if (TARGET_32BIT)
4624    {
4625      if (CONST_INT_P (operands[2])
4626          && UINTVAL (operands[2]) > 31)
4627        operands[2] = GEN_INT (INTVAL (operands[2]) % 32);
4628    }
4629  else /* TARGET_THUMB1 */
4630    {
4631      if (CONST_INT_P (operands [2]))
4632        operands [2] = force_reg (SImode, operands[2]);
4633    }
4634  "
4635)
4636
4637(define_insn "*arm_shiftsi3"
4638  [(set (match_operand:SI   0 "s_register_operand" "=l,l,r,r")
4639	(match_operator:SI  3 "shift_operator"
4640	 [(match_operand:SI 1 "s_register_operand"  "0,l,r,r")
4641	  (match_operand:SI 2 "reg_or_int_operand" "l,M,M,r")]))]
4642  "TARGET_32BIT"
4643  "* return arm_output_shift(operands, 0);"
4644  [(set_attr "predicable" "yes")
4645   (set_attr "arch" "t2,t2,*,*")
4646   (set_attr "predicable_short_it" "yes,yes,no,no")
4647   (set_attr "length" "4")
4648   (set_attr "shift" "1")
4649   (set_attr "type" "alu_shift_reg,alu_shift_imm,alu_shift_imm,alu_shift_reg")]
4650)
4651
4652(define_insn "*shiftsi3_compare0"
4653  [(set (reg:CC_NZ CC_REGNUM)
4654	(compare:CC_NZ (match_operator:SI 3 "shift_operator"
4655			  [(match_operand:SI 1 "s_register_operand" "r,r")
4656			   (match_operand:SI 2 "arm_rhs_operand" "M,r")])
4657			 (const_int 0)))
4658   (set (match_operand:SI 0 "s_register_operand" "=r,r")
4659	(match_op_dup 3 [(match_dup 1) (match_dup 2)]))]
4660  "TARGET_32BIT"
4661  "* return arm_output_shift(operands, 1);"
4662  [(set_attr "conds" "set")
4663   (set_attr "shift" "1")
4664   (set_attr "type" "alus_shift_imm,alus_shift_reg")]
4665)
4666
4667(define_insn "*shiftsi3_compare0_scratch"
4668  [(set (reg:CC_NZ CC_REGNUM)
4669	(compare:CC_NZ (match_operator:SI 3 "shift_operator"
4670			  [(match_operand:SI 1 "s_register_operand" "r,r")
4671			   (match_operand:SI 2 "arm_rhs_operand" "M,r")])
4672			 (const_int 0)))
4673   (clobber (match_scratch:SI 0 "=r,r"))]
4674  "TARGET_32BIT"
4675  "* return arm_output_shift(operands, 1);"
4676  [(set_attr "conds" "set")
4677   (set_attr "shift" "1")
4678   (set_attr "type" "shift_imm,shift_reg")]
4679)
4680
4681(define_insn "*not_shiftsi"
4682  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4683	(not:SI (match_operator:SI 3 "shift_operator"
4684		 [(match_operand:SI 1 "s_register_operand" "r,r")
4685		  (match_operand:SI 2 "shift_amount_operand" "M,r")])))]
4686  "TARGET_32BIT"
4687  "mvn%?\\t%0, %1%S3"
4688  [(set_attr "predicable" "yes")
4689   (set_attr "shift" "1")
4690   (set_attr "arch" "32,a")
4691   (set_attr "type" "mvn_shift,mvn_shift_reg")])
4692
4693(define_insn "*not_shiftsi_compare0"
4694  [(set (reg:CC_NZ CC_REGNUM)
4695	(compare:CC_NZ
4696	 (not:SI (match_operator:SI 3 "shift_operator"
4697		  [(match_operand:SI 1 "s_register_operand" "r,r")
4698		   (match_operand:SI 2 "shift_amount_operand" "M,r")]))
4699	 (const_int 0)))
4700   (set (match_operand:SI 0 "s_register_operand" "=r,r")
4701	(not:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])))]
4702  "TARGET_32BIT"
4703  "mvns%?\\t%0, %1%S3"
4704  [(set_attr "conds" "set")
4705   (set_attr "shift" "1")
4706   (set_attr "arch" "32,a")
4707   (set_attr "type" "mvn_shift,mvn_shift_reg")])
4708
4709(define_insn "*not_shiftsi_compare0_scratch"
4710  [(set (reg:CC_NZ CC_REGNUM)
4711	(compare:CC_NZ
4712	 (not:SI (match_operator:SI 3 "shift_operator"
4713		  [(match_operand:SI 1 "s_register_operand" "r,r")
4714		   (match_operand:SI 2 "shift_amount_operand" "M,r")]))
4715	 (const_int 0)))
4716   (clobber (match_scratch:SI 0 "=r,r"))]
4717  "TARGET_32BIT"
4718  "mvns%?\\t%0, %1%S3"
4719  [(set_attr "conds" "set")
4720   (set_attr "shift" "1")
4721   (set_attr "arch" "32,a")
4722   (set_attr "type" "mvn_shift,mvn_shift_reg")])
4723
4724;; We don't really have extzv, but defining this using shifts helps
4725;; to reduce register pressure later on.
4726
4727(define_expand "extzv"
4728  [(set (match_operand 0 "s_register_operand")
4729	(zero_extract (match_operand 1 "nonimmediate_operand")
4730		      (match_operand 2 "const_int_operand")
4731		      (match_operand 3 "const_int_operand")))]
4732  "TARGET_THUMB1 || arm_arch_thumb2"
4733  "
4734  {
4735    HOST_WIDE_INT lshift = 32 - INTVAL (operands[2]) - INTVAL (operands[3]);
4736    HOST_WIDE_INT rshift = 32 - INTVAL (operands[2]);
4737
4738    if (arm_arch_thumb2)
4739      {
4740	HOST_WIDE_INT width = INTVAL (operands[2]);
4741	HOST_WIDE_INT bitpos = INTVAL (operands[3]);
4742
4743	if (unaligned_access && MEM_P (operands[1])
4744	    && (width == 16 || width == 32) && (bitpos % BITS_PER_UNIT) == 0)
4745	  {
4746	    rtx base_addr;
4747
4748	    if (BYTES_BIG_ENDIAN)
4749	      bitpos = GET_MODE_BITSIZE (GET_MODE (operands[0])) - width
4750		       - bitpos;
4751
4752	    if (width == 32)
4753              {
4754		base_addr = adjust_address (operands[1], SImode,
4755					    bitpos / BITS_PER_UNIT);
4756		emit_insn (gen_unaligned_loadsi (operands[0], base_addr));
4757              }
4758	    else
4759              {
4760		rtx dest = operands[0];
4761		rtx tmp = gen_reg_rtx (SImode);
4762
4763		/* We may get a paradoxical subreg here.  Strip it off.  */
4764		if (GET_CODE (dest) == SUBREG
4765		    && GET_MODE (dest) == SImode
4766		    && GET_MODE (SUBREG_REG (dest)) == HImode)
4767		  dest = SUBREG_REG (dest);
4768
4769		if (GET_MODE_BITSIZE (GET_MODE (dest)) != width)
4770		  FAIL;
4771
4772		base_addr = adjust_address (operands[1], HImode,
4773					    bitpos / BITS_PER_UNIT);
4774		emit_insn (gen_unaligned_loadhiu (tmp, base_addr));
4775		emit_move_insn (gen_lowpart (SImode, dest), tmp);
4776	      }
4777	    DONE;
4778	  }
4779	else if (s_register_operand (operands[1], GET_MODE (operands[1])))
4780	  {
4781	    emit_insn (gen_extzv_t2 (operands[0], operands[1], operands[2],
4782				     operands[3]));
4783	    DONE;
4784	  }
4785	else
4786	  FAIL;
4787      }
4788
4789    if (!s_register_operand (operands[1], GET_MODE (operands[1])))
4790      FAIL;
4791
4792    operands[3] = GEN_INT (rshift);
4793
4794    if (lshift == 0)
4795      {
4796        emit_insn (gen_lshrsi3 (operands[0], operands[1], operands[3]));
4797        DONE;
4798      }
4799
4800    emit_insn (gen_extzv_t1 (operands[0], operands[1], GEN_INT (lshift),
4801			     operands[3], gen_reg_rtx (SImode)));
4802    DONE;
4803  }"
4804)
4805
4806;; Helper for extzv, for the Thumb-1 register-shifts case.
4807
4808(define_expand "extzv_t1"
4809  [(set (match_operand:SI 4 "s_register_operand")
4810	(ashift:SI (match_operand:SI 1 "nonimmediate_operand")
4811		   (match_operand:SI 2 "const_int_operand")))
4812   (set (match_operand:SI 0 "s_register_operand")
4813	(lshiftrt:SI (match_dup 4)
4814		     (match_operand:SI 3 "const_int_operand")))]
4815  "TARGET_THUMB1"
4816  "")
4817
4818(define_expand "extv"
4819  [(set (match_operand 0 "s_register_operand")
4820	(sign_extract (match_operand 1 "nonimmediate_operand")
4821		      (match_operand 2 "const_int_operand")
4822		      (match_operand 3 "const_int_operand")))]
4823  "arm_arch_thumb2"
4824{
4825  HOST_WIDE_INT width = INTVAL (operands[2]);
4826  HOST_WIDE_INT bitpos = INTVAL (operands[3]);
4827
4828  if (unaligned_access && MEM_P (operands[1]) && (width == 16 || width == 32)
4829      && (bitpos % BITS_PER_UNIT)  == 0)
4830    {
4831      rtx base_addr;
4832
4833      if (BYTES_BIG_ENDIAN)
4834	bitpos = GET_MODE_BITSIZE (GET_MODE (operands[0])) - width - bitpos;
4835
4836      if (width == 32)
4837        {
4838	  base_addr = adjust_address (operands[1], SImode,
4839				      bitpos / BITS_PER_UNIT);
4840	  emit_insn (gen_unaligned_loadsi (operands[0], base_addr));
4841        }
4842      else
4843        {
4844	  rtx dest = operands[0];
4845	  rtx tmp = gen_reg_rtx (SImode);
4846
4847	  /* We may get a paradoxical subreg here.  Strip it off.  */
4848	  if (GET_CODE (dest) == SUBREG
4849	      && GET_MODE (dest) == SImode
4850	      && GET_MODE (SUBREG_REG (dest)) == HImode)
4851	    dest = SUBREG_REG (dest);
4852
4853	  if (GET_MODE_BITSIZE (GET_MODE (dest)) != width)
4854	    FAIL;
4855
4856	  base_addr = adjust_address (operands[1], HImode,
4857				      bitpos / BITS_PER_UNIT);
4858	  emit_insn (gen_unaligned_loadhis (tmp, base_addr));
4859	  emit_move_insn (gen_lowpart (SImode, dest), tmp);
4860	}
4861
4862      DONE;
4863    }
4864  else if (!s_register_operand (operands[1], GET_MODE (operands[1])))
4865    FAIL;
4866  else if (GET_MODE (operands[0]) == SImode
4867	   && GET_MODE (operands[1]) == SImode)
4868    {
4869      emit_insn (gen_extv_regsi (operands[0], operands[1], operands[2],
4870				 operands[3]));
4871      DONE;
4872    }
4873
4874  FAIL;
4875})
4876
4877; Helper to expand register forms of extv with the proper modes.
4878
4879(define_expand "extv_regsi"
4880  [(set (match_operand:SI 0 "s_register_operand")
4881	(sign_extract:SI (match_operand:SI 1 "s_register_operand")
4882			 (match_operand 2 "const_int_operand")
4883			 (match_operand 3 "const_int_operand")))]
4884  ""
4885{
4886})
4887
4888; ARMv6+ unaligned load/store instructions (used for packed structure accesses).
4889
4890(define_insn "unaligned_loaddi"
4891  [(set (match_operand:DI 0 "s_register_operand" "=r")
4892	(unspec:DI [(match_operand:DI 1 "memory_operand" "m")]
4893		   UNSPEC_UNALIGNED_LOAD))]
4894  "TARGET_32BIT && TARGET_LDRD"
4895  "*
4896  return output_move_double (operands, true, NULL);
4897  "
4898  [(set_attr "length" "8")
4899   (set_attr "type" "load_8")])
4900
4901(define_insn "unaligned_loadsi"
4902  [(set (match_operand:SI 0 "s_register_operand" "=l,l,r")
4903	(unspec:SI [(match_operand:SI 1 "memory_operand" "m,Uw,m")]
4904		   UNSPEC_UNALIGNED_LOAD))]
4905  "unaligned_access"
4906  "@
4907   ldr\t%0, %1\t@ unaligned
4908   ldr%?\t%0, %1\t@ unaligned
4909   ldr%?\t%0, %1\t@ unaligned"
4910  [(set_attr "arch" "t1,t2,32")
4911   (set_attr "length" "2,2,4")
4912   (set_attr "predicable" "no,yes,yes")
4913   (set_attr "predicable_short_it" "no,yes,no")
4914   (set_attr "type" "load_4")])
4915
4916;; The 16-bit Thumb1 variant of ldrsh requires two registers in the
4917;; address (there's no immediate format).  That's tricky to support
4918;; here and we don't really need this pattern for that case, so only
4919;; enable for 32-bit ISAs.
4920(define_insn "unaligned_loadhis"
4921  [(set (match_operand:SI 0 "s_register_operand" "=r")
4922	(sign_extend:SI
4923	  (unspec:HI [(match_operand:HI 1 "memory_operand" "Uh")]
4924		     UNSPEC_UNALIGNED_LOAD)))]
4925  "unaligned_access && TARGET_32BIT"
4926  "ldrsh%?\t%0, %1\t@ unaligned"
4927  [(set_attr "predicable" "yes")
4928   (set_attr "type" "load_byte")])
4929
4930(define_insn "unaligned_loadhiu"
4931  [(set (match_operand:SI 0 "s_register_operand" "=l,l,r")
4932	(zero_extend:SI
4933	  (unspec:HI [(match_operand:HI 1 "memory_operand" "m,Uw,m")]
4934		     UNSPEC_UNALIGNED_LOAD)))]
4935  "unaligned_access"
4936  "@
4937   ldrh\t%0, %1\t@ unaligned
4938   ldrh%?\t%0, %1\t@ unaligned
4939   ldrh%?\t%0, %1\t@ unaligned"
4940  [(set_attr "arch" "t1,t2,32")
4941   (set_attr "length" "2,2,4")
4942   (set_attr "predicable" "no,yes,yes")
4943   (set_attr "predicable_short_it" "no,yes,no")
4944   (set_attr "type" "load_byte")])
4945
4946(define_insn "unaligned_storedi"
4947  [(set (match_operand:DI 0 "memory_operand" "=m")
4948	(unspec:DI [(match_operand:DI 1 "s_register_operand" "r")]
4949		   UNSPEC_UNALIGNED_STORE))]
4950  "TARGET_32BIT && TARGET_LDRD"
4951  "*
4952  return output_move_double (operands, true, NULL);
4953  "
4954  [(set_attr "length" "8")
4955   (set_attr "type" "store_8")])
4956
4957(define_insn "unaligned_storesi"
4958  [(set (match_operand:SI 0 "memory_operand" "=m,Uw,m")
4959	(unspec:SI [(match_operand:SI 1 "s_register_operand" "l,l,r")]
4960		   UNSPEC_UNALIGNED_STORE))]
4961  "unaligned_access"
4962  "@
4963   str\t%1, %0\t@ unaligned
4964   str%?\t%1, %0\t@ unaligned
4965   str%?\t%1, %0\t@ unaligned"
4966  [(set_attr "arch" "t1,t2,32")
4967   (set_attr "length" "2,2,4")
4968   (set_attr "predicable" "no,yes,yes")
4969   (set_attr "predicable_short_it" "no,yes,no")
4970   (set_attr "type" "store_4")])
4971
4972(define_insn "unaligned_storehi"
4973  [(set (match_operand:HI 0 "memory_operand" "=m,Uw,m")
4974	(unspec:HI [(match_operand:HI 1 "s_register_operand" "l,l,r")]
4975		   UNSPEC_UNALIGNED_STORE))]
4976  "unaligned_access"
4977  "@
4978   strh\t%1, %0\t@ unaligned
4979   strh%?\t%1, %0\t@ unaligned
4980   strh%?\t%1, %0\t@ unaligned"
4981  [(set_attr "arch" "t1,t2,32")
4982   (set_attr "length" "2,2,4")
4983   (set_attr "predicable" "no,yes,yes")
4984   (set_attr "predicable_short_it" "no,yes,no")
4985   (set_attr "type" "store_4")])
4986
4987
4988(define_insn "*extv_reg"
4989  [(set (match_operand:SI 0 "s_register_operand" "=r")
4990	(sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
4991			  (match_operand:SI 2 "const_int_operand" "n")
4992			  (match_operand:SI 3 "const_int_operand" "n")))]
4993  "arm_arch_thumb2
4994   && IN_RANGE (INTVAL (operands[3]), 0, 31)
4995   && IN_RANGE (INTVAL (operands[2]), 1, 32 - INTVAL (operands[3]))"
4996  "sbfx%?\t%0, %1, %3, %2"
4997  [(set_attr "length" "4")
4998   (set_attr "predicable" "yes")
4999   (set_attr "type" "bfm")]
5000)
5001
5002(define_insn "extzv_t2"
5003  [(set (match_operand:SI 0 "s_register_operand" "=r")
5004	(zero_extract:SI (match_operand:SI 1 "s_register_operand" "r")
5005			  (match_operand:SI 2 "const_int_operand" "n")
5006			  (match_operand:SI 3 "const_int_operand" "n")))]
5007  "arm_arch_thumb2
5008   && IN_RANGE (INTVAL (operands[3]), 0, 31)
5009   && IN_RANGE (INTVAL (operands[2]), 1, 32 - INTVAL (operands[3]))"
5010  "ubfx%?\t%0, %1, %3, %2"
5011  [(set_attr "length" "4")
5012   (set_attr "predicable" "yes")
5013   (set_attr "type" "bfm")]
5014)
5015
5016
5017;; Division instructions
5018(define_insn "divsi3"
5019  [(set (match_operand:SI	  0 "s_register_operand" "=r,r")
5020	(div:SI (match_operand:SI 1 "s_register_operand"  "r,r")
5021		(match_operand:SI 2 "s_register_operand"  "r,r")))]
5022  "TARGET_IDIV"
5023  "@
5024   sdiv%?\t%0, %1, %2
5025   sdiv\t%0, %1, %2"
5026  [(set_attr "arch" "32,v8mb")
5027   (set_attr "predicable" "yes")
5028   (set_attr "type" "sdiv")]
5029)
5030
5031(define_insn "udivsi3"
5032  [(set (match_operand:SI	   0 "s_register_operand" "=r,r")
5033	(udiv:SI (match_operand:SI 1 "s_register_operand"  "r,r")
5034		 (match_operand:SI 2 "s_register_operand"  "r,r")))]
5035  "TARGET_IDIV"
5036  "@
5037   udiv%?\t%0, %1, %2
5038   udiv\t%0, %1, %2"
5039  [(set_attr "arch" "32,v8mb")
5040   (set_attr "predicable" "yes")
5041   (set_attr "type" "udiv")]
5042)
5043
5044
5045;; Unary arithmetic insns
5046
5047(define_expand "negv<SIDI:mode>3"
5048  [(match_operand:SIDI 0 "s_register_operand")
5049   (match_operand:SIDI 1 "s_register_operand")
5050   (match_operand 2 "")]
5051  "TARGET_32BIT"
5052{
5053  emit_insn (gen_subv<mode>4 (operands[0], const0_rtx, operands[1],
5054			      operands[2]));
5055  DONE;
5056})
5057
5058(define_expand "negsi2"
5059  [(set (match_operand:SI         0 "s_register_operand")
5060	(neg:SI (match_operand:SI 1 "s_register_operand")))]
5061  "TARGET_EITHER"
5062  ""
5063)
5064
5065(define_insn "*arm_negsi2"
5066  [(set (match_operand:SI         0 "s_register_operand" "=l,r")
5067	(neg:SI (match_operand:SI 1 "s_register_operand" "l,r")))]
5068  "TARGET_32BIT"
5069  "rsb%?\\t%0, %1, #0"
5070  [(set_attr "predicable" "yes")
5071   (set_attr "predicable_short_it" "yes,no")
5072   (set_attr "arch" "t2,*")
5073   (set_attr "length" "4")
5074   (set_attr "type" "alu_imm")]
5075)
5076
5077;; To keep the comparison in canonical form we express it as (~reg cmp ~0)
5078;; rather than (0 cmp reg).  This gives the same results for unsigned
5079;; and equality compares which is what we mostly need here.
5080(define_insn "negsi2_0compare"
5081  [(set (reg:CC_RSB CC_REGNUM)
5082	(compare:CC_RSB (not:SI (match_operand:SI 1 "s_register_operand" "l,r"))
5083			(const_int -1)))
5084   (set (match_operand:SI 0 "s_register_operand" "=l,r")
5085	(neg:SI (match_dup 1)))]
5086  "TARGET_32BIT"
5087  "@
5088   negs\\t%0, %1
5089   rsbs\\t%0, %1, #0"
5090  [(set_attr "conds" "set")
5091   (set_attr "arch" "t2,*")
5092   (set_attr "length" "2,*")
5093   (set_attr "type" "alus_imm")]
5094)
5095
5096(define_insn "negsi2_carryin"
5097  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5098	(minus:SI (neg:SI (match_operand:SI 1 "s_register_operand" "r,r"))
5099		  (match_operand:SI 2 "arm_borrow_operation" "")))]
5100  "TARGET_32BIT"
5101  "@
5102   rsc\\t%0, %1, #0
5103   sbc\\t%0, %1, %1, lsl #1"
5104  [(set_attr "conds" "use")
5105   (set_attr "arch" "a,t2")
5106   (set_attr "type" "adc_imm,adc_reg")]
5107)
5108
5109(define_expand "negsf2"
5110  [(set (match_operand:SF         0 "s_register_operand")
5111	(neg:SF (match_operand:SF 1 "s_register_operand")))]
5112  "TARGET_32BIT && TARGET_HARD_FLOAT"
5113  ""
5114)
5115
5116(define_expand "negdf2"
5117  [(set (match_operand:DF         0 "s_register_operand")
5118	(neg:DF (match_operand:DF 1 "s_register_operand")))]
5119  "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
5120  "")
5121
5122;; abssi2 doesn't really clobber the condition codes if a different register
5123;; is being set.  To keep things simple, assume during rtl manipulations that
5124;; it does, but tell the final scan operator the truth.  Similarly for
5125;; (neg (abs...))
5126
5127(define_expand "abssi2"
5128  [(parallel
5129    [(set (match_operand:SI         0 "s_register_operand")
5130	  (abs:SI (match_operand:SI 1 "s_register_operand")))
5131     (clobber (match_dup 2))])]
5132  "TARGET_EITHER"
5133  "
5134  if (TARGET_THUMB1)
5135    operands[2] = gen_rtx_SCRATCH (SImode);
5136  else
5137    operands[2] = gen_rtx_REG (CCmode, CC_REGNUM);
5138")
5139
5140(define_insn_and_split "*arm_abssi2"
5141  [(set (match_operand:SI 0 "s_register_operand" "=r,&r")
5142	(abs:SI (match_operand:SI 1 "s_register_operand" "0,r")))
5143   (clobber (reg:CC CC_REGNUM))]
5144  "TARGET_ARM"
5145  "#"
5146  "&& reload_completed"
5147  [(const_int 0)]
5148  {
5149   /* if (which_alternative == 0) */
5150   if (REGNO(operands[0]) == REGNO(operands[1]))
5151     {
5152      /* Emit the pattern:
5153         cmp\\t%0, #0\;rsblt\\t%0, %0, #0
5154         [(set (reg:CC CC_REGNUM)
5155               (compare:CC (match_dup 0) (const_int 0)))
5156          (cond_exec (lt:CC (reg:CC CC_REGNUM) (const_int 0))
5157                     (set (match_dup 0) (minus:SI (const_int 0) (match_dup 1))))]
5158      */
5159      emit_insn (gen_rtx_SET (gen_rtx_REG (CCmode, CC_REGNUM),
5160                              gen_rtx_COMPARE (CCmode, operands[0], const0_rtx)));
5161      emit_insn (gen_rtx_COND_EXEC (VOIDmode,
5162                                    (gen_rtx_LT (SImode,
5163                                                 gen_rtx_REG (CCmode, CC_REGNUM),
5164                                                 const0_rtx)),
5165                                    (gen_rtx_SET (operands[0],
5166                                                  (gen_rtx_MINUS (SImode,
5167                                                                  const0_rtx,
5168                                                                  operands[1]))))));
5169      DONE;
5170     }
5171   else
5172     {
5173      /* Emit the pattern:
5174         alt1: eor%?\\t%0, %1, %1, asr #31\;sub%?\\t%0, %0, %1, asr #31
5175         [(set (match_dup 0)
5176               (xor:SI (match_dup 1)
5177                       (ashiftrt:SI (match_dup 1) (const_int 31))))
5178          (set (match_dup 0)
5179               (minus:SI (match_dup 0)
5180                      (ashiftrt:SI (match_dup 1) (const_int 31))))]
5181      */
5182      emit_insn (gen_rtx_SET (operands[0],
5183                              gen_rtx_XOR (SImode,
5184                                           gen_rtx_ASHIFTRT (SImode,
5185                                                             operands[1],
5186                                                             GEN_INT (31)),
5187                                           operands[1])));
5188      emit_insn (gen_rtx_SET (operands[0],
5189                              gen_rtx_MINUS (SImode,
5190                                             operands[0],
5191                                             gen_rtx_ASHIFTRT (SImode,
5192                                                               operands[1],
5193                                                               GEN_INT (31)))));
5194      DONE;
5195     }
5196  }
5197  [(set_attr "conds" "clob,*")
5198   (set_attr "shift" "1")
5199   (set_attr "predicable" "no, yes")
5200   (set_attr "length" "8")
5201   (set_attr "type" "multiple")]
5202)
5203
5204(define_insn_and_split "*arm_neg_abssi2"
5205  [(set (match_operand:SI 0 "s_register_operand" "=r,&r")
5206	(neg:SI (abs:SI (match_operand:SI 1 "s_register_operand" "0,r"))))
5207   (clobber (reg:CC CC_REGNUM))]
5208  "TARGET_ARM"
5209  "#"
5210  "&& reload_completed"
5211  [(const_int 0)]
5212  {
5213   /* if (which_alternative == 0) */
5214   if (REGNO (operands[0]) == REGNO (operands[1]))
5215     {
5216      /* Emit the pattern:
5217         cmp\\t%0, #0\;rsbgt\\t%0, %0, #0
5218      */
5219      emit_insn (gen_rtx_SET (gen_rtx_REG (CCmode, CC_REGNUM),
5220                              gen_rtx_COMPARE (CCmode, operands[0], const0_rtx)));
5221      emit_insn (gen_rtx_COND_EXEC (VOIDmode,
5222                                    gen_rtx_GT (SImode,
5223                                                gen_rtx_REG (CCmode, CC_REGNUM),
5224                                                const0_rtx),
5225                                    gen_rtx_SET (operands[0],
5226                                                 (gen_rtx_MINUS (SImode,
5227                                                                 const0_rtx,
5228                                                                 operands[1])))));
5229     }
5230   else
5231     {
5232      /* Emit the pattern:
5233         eor%?\\t%0, %1, %1, asr #31\;rsb%?\\t%0, %0, %1, asr #31
5234      */
5235      emit_insn (gen_rtx_SET (operands[0],
5236                              gen_rtx_XOR (SImode,
5237                                           gen_rtx_ASHIFTRT (SImode,
5238                                                             operands[1],
5239                                                             GEN_INT (31)),
5240                                           operands[1])));
5241      emit_insn (gen_rtx_SET (operands[0],
5242                              gen_rtx_MINUS (SImode,
5243                                             gen_rtx_ASHIFTRT (SImode,
5244                                                               operands[1],
5245                                                               GEN_INT (31)),
5246                                             operands[0])));
5247     }
5248   DONE;
5249  }
5250  [(set_attr "conds" "clob,*")
5251   (set_attr "shift" "1")
5252   (set_attr "predicable" "no, yes")
5253   (set_attr "length" "8")
5254   (set_attr "type" "multiple")]
5255)
5256
5257(define_expand "abssf2"
5258  [(set (match_operand:SF         0 "s_register_operand")
5259	(abs:SF (match_operand:SF 1 "s_register_operand")))]
5260  "TARGET_32BIT && TARGET_HARD_FLOAT"
5261  "")
5262
5263(define_expand "absdf2"
5264  [(set (match_operand:DF         0 "s_register_operand")
5265	(abs:DF (match_operand:DF 1 "s_register_operand")))]
5266  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
5267  "")
5268
5269(define_expand "sqrtsf2"
5270  [(set (match_operand:SF 0 "s_register_operand")
5271	(sqrt:SF (match_operand:SF 1 "s_register_operand")))]
5272  "TARGET_32BIT && TARGET_HARD_FLOAT"
5273  "")
5274
5275(define_expand "sqrtdf2"
5276  [(set (match_operand:DF 0 "s_register_operand")
5277	(sqrt:DF (match_operand:DF 1 "s_register_operand")))]
5278  "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
5279  "")
5280
5281(define_expand "one_cmplsi2"
5282  [(set (match_operand:SI         0 "s_register_operand")
5283	(not:SI (match_operand:SI 1 "s_register_operand")))]
5284  "TARGET_EITHER"
5285  ""
5286)
5287
5288(define_insn "*arm_one_cmplsi2"
5289  [(set (match_operand:SI         0 "s_register_operand" "=l,r")
5290	(not:SI (match_operand:SI 1 "s_register_operand"  "l,r")))]
5291  "TARGET_32BIT"
5292  "mvn%?\\t%0, %1"
5293  [(set_attr "predicable" "yes")
5294   (set_attr "predicable_short_it" "yes,no")
5295   (set_attr "arch" "t2,*")
5296   (set_attr "length" "4")
5297   (set_attr "type" "mvn_reg")]
5298)
5299
5300(define_insn "*notsi_compare0"
5301  [(set (reg:CC_NZ CC_REGNUM)
5302	(compare:CC_NZ (not:SI (match_operand:SI 1 "s_register_operand" "r"))
5303			 (const_int 0)))
5304   (set (match_operand:SI 0 "s_register_operand" "=r")
5305	(not:SI (match_dup 1)))]
5306  "TARGET_32BIT"
5307  "mvns%?\\t%0, %1"
5308  [(set_attr "conds" "set")
5309   (set_attr "type" "mvn_reg")]
5310)
5311
5312(define_insn "*notsi_compare0_scratch"
5313  [(set (reg:CC_NZ CC_REGNUM)
5314	(compare:CC_NZ (not:SI (match_operand:SI 1 "s_register_operand" "r"))
5315			 (const_int 0)))
5316   (clobber (match_scratch:SI 0 "=r"))]
5317  "TARGET_32BIT"
5318  "mvns%?\\t%0, %1"
5319  [(set_attr "conds" "set")
5320   (set_attr "type" "mvn_reg")]
5321)
5322
5323;; Fixed <--> Floating conversion insns
5324
5325(define_expand "floatsihf2"
5326  [(set (match_operand:HF           0 "general_operand")
5327	(float:HF (match_operand:SI 1 "general_operand")))]
5328  "TARGET_EITHER"
5329  "
5330  {
5331    rtx op1 = gen_reg_rtx (SFmode);
5332    expand_float (op1, operands[1], 0);
5333    op1 = convert_to_mode (HFmode, op1, 0);
5334    emit_move_insn (operands[0], op1);
5335    DONE;
5336  }"
5337)
5338
5339(define_expand "floatdihf2"
5340  [(set (match_operand:HF           0 "general_operand")
5341	(float:HF (match_operand:DI 1 "general_operand")))]
5342  "TARGET_EITHER"
5343  "
5344  {
5345    rtx op1 = gen_reg_rtx (SFmode);
5346    expand_float (op1, operands[1], 0);
5347    op1 = convert_to_mode (HFmode, op1, 0);
5348    emit_move_insn (operands[0], op1);
5349    DONE;
5350  }"
5351)
5352
5353(define_expand "floatsisf2"
5354  [(set (match_operand:SF           0 "s_register_operand")
5355	(float:SF (match_operand:SI 1 "s_register_operand")))]
5356  "TARGET_32BIT && TARGET_HARD_FLOAT"
5357  "
5358")
5359
5360(define_expand "floatsidf2"
5361  [(set (match_operand:DF           0 "s_register_operand")
5362	(float:DF (match_operand:SI 1 "s_register_operand")))]
5363  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
5364  "
5365")
5366
5367(define_expand "fix_trunchfsi2"
5368  [(set (match_operand:SI         0 "general_operand")
5369	(fix:SI (fix:HF (match_operand:HF 1 "general_operand"))))]
5370  "TARGET_EITHER"
5371  "
5372  {
5373    rtx op1 = convert_to_mode (SFmode, operands[1], 0);
5374    expand_fix (operands[0], op1, 0);
5375    DONE;
5376  }"
5377)
5378
5379(define_expand "fix_trunchfdi2"
5380  [(set (match_operand:DI         0 "general_operand")
5381	(fix:DI (fix:HF (match_operand:HF 1 "general_operand"))))]
5382  "TARGET_EITHER"
5383  "
5384  {
5385    rtx op1 = convert_to_mode (SFmode, operands[1], 0);
5386    expand_fix (operands[0], op1, 0);
5387    DONE;
5388  }"
5389)
5390
5391(define_expand "fix_truncsfsi2"
5392  [(set (match_operand:SI         0 "s_register_operand")
5393	(fix:SI (fix:SF (match_operand:SF 1 "s_register_operand"))))]
5394  "TARGET_32BIT && TARGET_HARD_FLOAT"
5395  "
5396")
5397
5398(define_expand "fix_truncdfsi2"
5399  [(set (match_operand:SI         0 "s_register_operand")
5400	(fix:SI (fix:DF (match_operand:DF 1 "s_register_operand"))))]
5401  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
5402  "
5403")
5404
5405;; Truncation insns
5406
5407(define_expand "truncdfsf2"
5408  [(set (match_operand:SF  0 "s_register_operand")
5409	(float_truncate:SF
5410	 (match_operand:DF 1 "s_register_operand")))]
5411  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
5412  ""
5413)
5414
5415;; DFmode to HFmode conversions on targets without a single-step hardware
5416;; instruction for it would have to go through SFmode.  This is dangerous
5417;; as it introduces double rounding.
5418;;
5419;; Disable this pattern unless we are in an unsafe math mode, or we have
5420;; a single-step instruction.
5421
5422(define_expand "truncdfhf2"
5423  [(set (match_operand:HF  0 "s_register_operand")
5424	(float_truncate:HF
5425	 (match_operand:DF 1 "s_register_operand")))]
5426  "(TARGET_EITHER && flag_unsafe_math_optimizations)
5427   || (TARGET_32BIT && TARGET_FP16_TO_DOUBLE)"
5428{
5429  /* We don't have a direct instruction for this, so we must be in
5430     an unsafe math mode, and going via SFmode.  */
5431
5432  if (!(TARGET_32BIT && TARGET_FP16_TO_DOUBLE))
5433    {
5434      rtx op1;
5435      op1 = convert_to_mode (SFmode, operands[1], 0);
5436      op1 = convert_to_mode (HFmode, op1, 0);
5437      emit_move_insn (operands[0], op1);
5438      DONE;
5439    }
5440  /* Otherwise, we will pick this up as a single instruction with
5441     no intermediary rounding.  */
5442}
5443)
5444
5445;; Zero and sign extension instructions.
5446
5447(define_expand "zero_extend<mode>di2"
5448  [(set (match_operand:DI 0 "s_register_operand" "")
5449	(zero_extend:DI (match_operand:QHSI 1 "<qhs_zextenddi_op>" "")))]
5450  "TARGET_32BIT <qhs_zextenddi_cond>"
5451  {
5452    rtx res_lo, res_hi, op0_lo, op0_hi;
5453    res_lo = gen_lowpart (SImode, operands[0]);
5454    res_hi = gen_highpart (SImode, operands[0]);
5455    if (can_create_pseudo_p ())
5456      {
5457	op0_lo = <MODE>mode == SImode ? operands[1] : gen_reg_rtx (SImode);
5458	op0_hi = gen_reg_rtx (SImode);
5459      }
5460    else
5461      {
5462	op0_lo = <MODE>mode == SImode ? operands[1] : res_lo;
5463	op0_hi = res_hi;
5464      }
5465    if (<MODE>mode != SImode)
5466      emit_insn (gen_rtx_SET (op0_lo,
5467			      gen_rtx_ZERO_EXTEND (SImode, operands[1])));
5468    emit_insn (gen_movsi (op0_hi, const0_rtx));
5469    if (res_lo != op0_lo)
5470      emit_move_insn (res_lo, op0_lo);
5471    if (res_hi != op0_hi)
5472      emit_move_insn (res_hi, op0_hi);
5473    DONE;
5474  }
5475)
5476
5477(define_expand "extend<mode>di2"
5478  [(set (match_operand:DI 0 "s_register_operand" "")
5479	(sign_extend:DI (match_operand:QHSI 1 "<qhs_extenddi_op>" "")))]
5480  "TARGET_32BIT <qhs_sextenddi_cond>"
5481  {
5482    rtx res_lo, res_hi, op0_lo, op0_hi;
5483    res_lo = gen_lowpart (SImode, operands[0]);
5484    res_hi = gen_highpart (SImode, operands[0]);
5485    if (can_create_pseudo_p ())
5486      {
5487	op0_lo = <MODE>mode == SImode ? operands[1] : gen_reg_rtx (SImode);
5488	op0_hi = gen_reg_rtx (SImode);
5489      }
5490    else
5491      {
5492	op0_lo = <MODE>mode == SImode ? operands[1] : res_lo;
5493	op0_hi = res_hi;
5494      }
5495    if (<MODE>mode != SImode)
5496      emit_insn (gen_rtx_SET (op0_lo,
5497			      gen_rtx_SIGN_EXTEND (SImode, operands[1])));
5498    emit_insn (gen_ashrsi3 (op0_hi, op0_lo, GEN_INT (31)));
5499    if (res_lo != op0_lo)
5500      emit_move_insn (res_lo, op0_lo);
5501    if (res_hi != op0_hi)
5502      emit_move_insn (res_hi, op0_hi);
5503    DONE;
5504  }
5505)
5506
5507;; Splits for all extensions to DImode
5508(define_split
5509  [(set (match_operand:DI 0 "s_register_operand" "")
5510        (zero_extend:DI (match_operand 1 "nonimmediate_operand" "")))]
5511  "TARGET_32BIT"
5512  [(set (match_dup 0) (match_dup 1))]
5513{
5514  rtx lo_part = gen_lowpart (SImode, operands[0]);
5515  machine_mode src_mode = GET_MODE (operands[1]);
5516
5517  if (src_mode == SImode)
5518    emit_move_insn (lo_part, operands[1]);
5519  else
5520    emit_insn (gen_rtx_SET (lo_part,
5521			    gen_rtx_ZERO_EXTEND (SImode, operands[1])));
5522  operands[0] = gen_highpart (SImode, operands[0]);
5523  operands[1] = const0_rtx;
5524})
5525
5526(define_split
5527  [(set (match_operand:DI 0 "s_register_operand" "")
5528        (sign_extend:DI (match_operand 1 "nonimmediate_operand" "")))]
5529  "TARGET_32BIT"
5530  [(set (match_dup 0) (ashiftrt:SI (match_dup 1) (const_int 31)))]
5531{
5532  rtx lo_part = gen_lowpart (SImode, operands[0]);
5533  machine_mode src_mode = GET_MODE (operands[1]);
5534
5535  if (src_mode == SImode)
5536    emit_move_insn (lo_part, operands[1]);
5537  else
5538    emit_insn (gen_rtx_SET (lo_part,
5539			    gen_rtx_SIGN_EXTEND (SImode, operands[1])));
5540  operands[1] = lo_part;
5541  operands[0] = gen_highpart (SImode, operands[0]);
5542})
5543
5544(define_expand "zero_extendhisi2"
5545  [(set (match_operand:SI 0 "s_register_operand")
5546	(zero_extend:SI (match_operand:HI 1 "nonimmediate_operand")))]
5547  "TARGET_EITHER"
5548{
5549  if (TARGET_ARM && !arm_arch4 && MEM_P (operands[1]))
5550    {
5551      emit_insn (gen_movhi_bytes (operands[0], operands[1]));
5552      DONE;
5553    }
5554  if (!arm_arch6 && !MEM_P (operands[1]))
5555    {
5556      rtx t = gen_lowpart (SImode, operands[1]);
5557      rtx tmp = gen_reg_rtx (SImode);
5558      emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (16)));
5559      emit_insn (gen_lshrsi3 (operands[0], tmp, GEN_INT (16)));
5560      DONE;
5561    }
5562})
5563
5564(define_split
5565  [(set (match_operand:SI 0 "s_register_operand" "")
5566	(zero_extend:SI (match_operand:HI 1 "s_register_operand" "")))]
5567  "!TARGET_THUMB2 && !arm_arch6"
5568  [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 16)))
5569   (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 16)))]
5570{
5571  operands[2] = gen_lowpart (SImode, operands[1]);
5572})
5573
5574(define_insn "*arm_zero_extendhisi2"
5575  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5576	(zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,m")))]
5577  "TARGET_ARM && arm_arch4 && !arm_arch6"
5578  "@
5579   #
5580   ldrh%?\\t%0, %1"
5581  [(set_attr "type" "alu_shift_reg,load_byte")
5582   (set_attr "predicable" "yes")]
5583)
5584
5585(define_insn "*arm_zero_extendhisi2_v6"
5586  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5587	(zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,Uh")))]
5588  "TARGET_ARM && arm_arch6"
5589  "@
5590   uxth%?\\t%0, %1
5591   ldrh%?\\t%0, %1"
5592  [(set_attr "predicable" "yes")
5593   (set_attr "type" "extend,load_byte")]
5594)
5595
5596(define_insn "*arm_zero_extendhisi2addsi"
5597  [(set (match_operand:SI 0 "s_register_operand" "=r")
5598	(plus:SI (zero_extend:SI (match_operand:HI 1 "s_register_operand" "r"))
5599		 (match_operand:SI 2 "s_register_operand" "r")))]
5600  "TARGET_INT_SIMD"
5601  "uxtah%?\\t%0, %2, %1"
5602  [(set_attr "type" "alu_shift_reg")
5603   (set_attr "predicable" "yes")]
5604)
5605
5606(define_expand "zero_extendqisi2"
5607  [(set (match_operand:SI 0 "s_register_operand")
5608	(zero_extend:SI (match_operand:QI 1 "nonimmediate_operand")))]
5609  "TARGET_EITHER"
5610{
5611  if (TARGET_ARM && !arm_arch6 && !MEM_P (operands[1]))
5612    {
5613      emit_insn (gen_andsi3 (operands[0],
5614			     gen_lowpart (SImode, operands[1]),
5615					  GEN_INT (255)));
5616      DONE;
5617    }
5618  if (!arm_arch6 && !MEM_P (operands[1]))
5619    {
5620      rtx t = gen_lowpart (SImode, operands[1]);
5621      rtx tmp = gen_reg_rtx (SImode);
5622      emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (24)));
5623      emit_insn (gen_lshrsi3 (operands[0], tmp, GEN_INT (24)));
5624      DONE;
5625    }
5626})
5627
5628(define_split
5629  [(set (match_operand:SI 0 "s_register_operand" "")
5630	(zero_extend:SI (match_operand:QI 1 "s_register_operand" "")))]
5631  "!arm_arch6"
5632  [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 24)))
5633   (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 24)))]
5634{
5635  operands[2] = simplify_gen_subreg (SImode, operands[1], QImode, 0);
5636  if (TARGET_ARM)
5637    {
5638      emit_insn (gen_andsi3 (operands[0], operands[2], GEN_INT (255)));
5639      DONE;
5640    }
5641})
5642
5643(define_insn "*arm_zero_extendqisi2"
5644  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5645	(zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "r,m")))]
5646  "TARGET_ARM && !arm_arch6"
5647  "@
5648   #
5649   ldrb%?\\t%0, %1\\t%@ zero_extendqisi2"
5650  [(set_attr "length" "8,4")
5651   (set_attr "type" "alu_shift_reg,load_byte")
5652   (set_attr "predicable" "yes")]
5653)
5654
5655(define_insn "*arm_zero_extendqisi2_v6"
5656  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5657	(zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "r,Uh")))]
5658  "TARGET_ARM && arm_arch6"
5659  "@
5660   uxtb%?\\t%0, %1
5661   ldrb%?\\t%0, %1\\t%@ zero_extendqisi2"
5662  [(set_attr "type" "extend,load_byte")
5663   (set_attr "predicable" "yes")]
5664)
5665
5666(define_insn "*arm_zero_extendqisi2addsi"
5667  [(set (match_operand:SI 0 "s_register_operand" "=r")
5668	(plus:SI (zero_extend:SI (match_operand:QI 1 "s_register_operand" "r"))
5669		 (match_operand:SI 2 "s_register_operand" "r")))]
5670  "TARGET_INT_SIMD"
5671  "uxtab%?\\t%0, %2, %1"
5672  [(set_attr "predicable" "yes")
5673   (set_attr "type" "alu_shift_reg")]
5674)
5675
5676(define_split
5677  [(set (match_operand:SI 0 "s_register_operand" "")
5678	(zero_extend:SI (subreg:QI (match_operand:SI 1 "" "") 0)))
5679   (clobber (match_operand:SI 2 "s_register_operand" ""))]
5680  "TARGET_32BIT && (!MEM_P (operands[1])) && ! BYTES_BIG_ENDIAN"
5681  [(set (match_dup 2) (match_dup 1))
5682   (set (match_dup 0) (and:SI (match_dup 2) (const_int 255)))]
5683  ""
5684)
5685
5686(define_split
5687  [(set (match_operand:SI 0 "s_register_operand" "")
5688	(zero_extend:SI (subreg:QI (match_operand:SI 1 "" "") 3)))
5689   (clobber (match_operand:SI 2 "s_register_operand" ""))]
5690  "TARGET_32BIT && (!MEM_P (operands[1])) && BYTES_BIG_ENDIAN"
5691  [(set (match_dup 2) (match_dup 1))
5692   (set (match_dup 0) (and:SI (match_dup 2) (const_int 255)))]
5693  ""
5694)
5695
5696
5697(define_split
5698  [(set (match_operand:SI 0 "s_register_operand" "")
5699	(IOR_XOR:SI (and:SI (ashift:SI
5700			     (match_operand:SI 1 "s_register_operand" "")
5701			     (match_operand:SI 2 "const_int_operand" ""))
5702			    (match_operand:SI 3 "const_int_operand" ""))
5703		    (zero_extend:SI
5704		     (match_operator 5 "subreg_lowpart_operator"
5705		      [(match_operand:SI 4 "s_register_operand" "")]))))]
5706  "TARGET_32BIT
5707   && (UINTVAL (operands[3])
5708       == (GET_MODE_MASK (GET_MODE (operands[5]))
5709           & (GET_MODE_MASK (GET_MODE (operands[5]))
5710	      << (INTVAL (operands[2])))))"
5711  [(set (match_dup 0) (IOR_XOR:SI (ashift:SI (match_dup 1) (match_dup 2))
5712				  (match_dup 4)))
5713   (set (match_dup 0) (zero_extend:SI (match_dup 5)))]
5714  "operands[5] = gen_lowpart (GET_MODE (operands[5]), operands[0]);"
5715)
5716
5717(define_insn "*compareqi_eq0"
5718  [(set (reg:CC_Z CC_REGNUM)
5719	(compare:CC_Z (match_operand:QI 0 "s_register_operand" "r")
5720			 (const_int 0)))]
5721  "TARGET_32BIT"
5722  "tst%?\\t%0, #255"
5723  [(set_attr "conds" "set")
5724   (set_attr "predicable" "yes")
5725   (set_attr "type" "logic_imm")]
5726)
5727
5728(define_expand "extendhisi2"
5729  [(set (match_operand:SI 0 "s_register_operand")
5730	(sign_extend:SI (match_operand:HI 1 "nonimmediate_operand")))]
5731  "TARGET_EITHER"
5732{
5733  if (TARGET_THUMB1)
5734    {
5735      emit_insn (gen_thumb1_extendhisi2 (operands[0], operands[1]));
5736      DONE;
5737    }
5738  if (MEM_P (operands[1]) && TARGET_ARM && !arm_arch4)
5739    {
5740      emit_insn (gen_extendhisi2_mem (operands[0], operands[1]));
5741      DONE;
5742    }
5743
5744  if (!arm_arch6 && !MEM_P (operands[1]))
5745    {
5746      rtx t = gen_lowpart (SImode, operands[1]);
5747      rtx tmp = gen_reg_rtx (SImode);
5748      emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (16)));
5749      emit_insn (gen_ashrsi3 (operands[0], tmp, GEN_INT (16)));
5750      DONE;
5751    }
5752})
5753
5754(define_split
5755  [(parallel
5756    [(set (match_operand:SI 0 "register_operand" "")
5757	  (sign_extend:SI (match_operand:HI 1 "register_operand" "")))
5758     (clobber (match_scratch:SI 2 ""))])]
5759  "!arm_arch6"
5760  [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 16)))
5761   (set (match_dup 0) (ashiftrt:SI (match_dup 0) (const_int 16)))]
5762{
5763  operands[2] = simplify_gen_subreg (SImode, operands[1], HImode, 0);
5764})
5765
5766;; This pattern will only be used when ldsh is not available
5767(define_expand "extendhisi2_mem"
5768  [(set (match_dup 2) (zero_extend:SI (match_operand:HI 1 "" "")))
5769   (set (match_dup 3)
5770	(zero_extend:SI (match_dup 7)))
5771   (set (match_dup 6) (ashift:SI (match_dup 4) (const_int 24)))
5772   (set (match_operand:SI 0 "" "")
5773	(ior:SI (ashiftrt:SI (match_dup 6) (const_int 16)) (match_dup 5)))]
5774  "TARGET_ARM"
5775  "
5776  {
5777    rtx mem1, mem2;
5778    rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
5779
5780    mem1 = change_address (operands[1], QImode, addr);
5781    mem2 = change_address (operands[1], QImode,
5782			   plus_constant (Pmode, addr, 1));
5783    operands[0] = gen_lowpart (SImode, operands[0]);
5784    operands[1] = mem1;
5785    operands[2] = gen_reg_rtx (SImode);
5786    operands[3] = gen_reg_rtx (SImode);
5787    operands[6] = gen_reg_rtx (SImode);
5788    operands[7] = mem2;
5789
5790    if (BYTES_BIG_ENDIAN)
5791      {
5792	operands[4] = operands[2];
5793	operands[5] = operands[3];
5794      }
5795    else
5796      {
5797	operands[4] = operands[3];
5798	operands[5] = operands[2];
5799      }
5800  }"
5801)
5802
5803(define_split
5804  [(set (match_operand:SI 0 "register_operand" "")
5805	(sign_extend:SI (match_operand:HI 1 "register_operand" "")))]
5806  "!arm_arch6"
5807  [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 16)))
5808   (set (match_dup 0) (ashiftrt:SI (match_dup 0) (const_int 16)))]
5809{
5810  operands[2] = simplify_gen_subreg (SImode, operands[1], HImode, 0);
5811})
5812
5813(define_insn "*arm_extendhisi2"
5814  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5815	(sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,Uh")))]
5816  "TARGET_ARM && arm_arch4 && !arm_arch6"
5817  "@
5818   #
5819   ldrsh%?\\t%0, %1"
5820  [(set_attr "length" "8,4")
5821   (set_attr "type" "alu_shift_reg,load_byte")
5822   (set_attr "predicable" "yes")]
5823)
5824
5825;; ??? Check Thumb-2 pool range
5826(define_insn "*arm_extendhisi2_v6"
5827  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5828	(sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,Uh")))]
5829  "TARGET_32BIT && arm_arch6"
5830  "@
5831   sxth%?\\t%0, %1
5832   ldrsh%?\\t%0, %1"
5833  [(set_attr "type" "extend,load_byte")
5834   (set_attr "predicable" "yes")]
5835)
5836
5837(define_insn "*arm_extendhisi2addsi"
5838  [(set (match_operand:SI 0 "s_register_operand" "=r")
5839	(plus:SI (sign_extend:SI (match_operand:HI 1 "s_register_operand" "r"))
5840		 (match_operand:SI 2 "s_register_operand" "r")))]
5841  "TARGET_INT_SIMD"
5842  "sxtah%?\\t%0, %2, %1"
5843  [(set_attr "type" "alu_shift_reg")]
5844)
5845
5846(define_expand "extendqihi2"
5847  [(set (match_dup 2)
5848	(ashift:SI (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op")
5849		   (const_int 24)))
5850   (set (match_operand:HI 0 "s_register_operand")
5851	(ashiftrt:SI (match_dup 2)
5852		     (const_int 24)))]
5853  "TARGET_ARM"
5854  "
5855  {
5856    if (arm_arch4 && MEM_P (operands[1]))
5857      {
5858	emit_insn (gen_rtx_SET (operands[0],
5859				gen_rtx_SIGN_EXTEND (HImode, operands[1])));
5860	DONE;
5861      }
5862    if (!s_register_operand (operands[1], QImode))
5863      operands[1] = copy_to_mode_reg (QImode, operands[1]);
5864    operands[0] = gen_lowpart (SImode, operands[0]);
5865    operands[1] = gen_lowpart (SImode, operands[1]);
5866    operands[2] = gen_reg_rtx (SImode);
5867  }"
5868)
5869
5870(define_insn "*arm_extendqihi_insn"
5871  [(set (match_operand:HI 0 "s_register_operand" "=r")
5872	(sign_extend:HI (match_operand:QI 1 "arm_extendqisi_mem_op" "Uq")))]
5873  "TARGET_ARM && arm_arch4"
5874  "ldrsb%?\\t%0, %1"
5875  [(set_attr "type" "load_byte")
5876   (set_attr "predicable" "yes")]
5877)
5878
5879(define_expand "extendqisi2"
5880  [(set (match_operand:SI 0 "s_register_operand")
5881	(sign_extend:SI (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op")))]
5882  "TARGET_EITHER"
5883{
5884  if (!arm_arch4 && MEM_P (operands[1]))
5885    operands[1] = copy_to_mode_reg (QImode, operands[1]);
5886
5887  if (!arm_arch6 && !MEM_P (operands[1]))
5888    {
5889      rtx t = gen_lowpart (SImode, operands[1]);
5890      rtx tmp = gen_reg_rtx (SImode);
5891      emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (24)));
5892      emit_insn (gen_ashrsi3 (operands[0], tmp, GEN_INT (24)));
5893      DONE;
5894    }
5895})
5896
5897(define_split
5898  [(set (match_operand:SI 0 "register_operand" "")
5899	(sign_extend:SI (match_operand:QI 1 "register_operand" "")))]
5900  "!arm_arch6"
5901  [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 24)))
5902   (set (match_dup 0) (ashiftrt:SI (match_dup 0) (const_int 24)))]
5903{
5904  operands[2] = simplify_gen_subreg (SImode, operands[1], QImode, 0);
5905})
5906
5907(define_insn "*arm_extendqisi"
5908  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5909	(sign_extend:SI (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op" "r,Uq")))]
5910  "TARGET_ARM && arm_arch4 && !arm_arch6"
5911  "@
5912   #
5913   ldrsb%?\\t%0, %1"
5914  [(set_attr "length" "8,4")
5915   (set_attr "type" "alu_shift_reg,load_byte")
5916   (set_attr "predicable" "yes")]
5917)
5918
5919(define_insn "*arm_extendqisi_v6"
5920  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5921	(sign_extend:SI
5922	 (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op" "r,Uq")))]
5923  "TARGET_ARM && arm_arch6"
5924  "@
5925   sxtb%?\\t%0, %1
5926   ldrsb%?\\t%0, %1"
5927  [(set_attr "type" "extend,load_byte")
5928   (set_attr "predicable" "yes")]
5929)
5930
5931(define_insn "*arm_extendqisi2addsi"
5932  [(set (match_operand:SI 0 "s_register_operand" "=r")
5933	(plus:SI (sign_extend:SI (match_operand:QI 1 "s_register_operand" "r"))
5934		 (match_operand:SI 2 "s_register_operand" "r")))]
5935  "TARGET_INT_SIMD"
5936  "sxtab%?\\t%0, %2, %1"
5937  [(set_attr "type" "alu_shift_reg")
5938   (set_attr "predicable" "yes")]
5939)
5940
5941(define_insn "arm_<sup>xtb16"
5942  [(set (match_operand:SI 0 "s_register_operand" "=r")
5943	(unspec:SI
5944	  [(match_operand:SI 1 "s_register_operand" "r")] USXTB16))]
5945  "TARGET_INT_SIMD"
5946  "<sup>xtb16%?\\t%0, %1"
5947  [(set_attr "predicable" "yes")
5948   (set_attr "type" "alu_dsp_reg")])
5949
5950(define_insn "arm_<simd32_op>"
5951  [(set (match_operand:SI 0 "s_register_operand" "=r")
5952	(unspec:SI
5953	  [(match_operand:SI 1 "s_register_operand" "r")
5954	   (match_operand:SI 2 "s_register_operand" "r")] SIMD32_NOGE_BINOP))]
5955  "TARGET_INT_SIMD"
5956  "<simd32_op>%?\\t%0, %1, %2"
5957  [(set_attr "predicable" "yes")
5958   (set_attr "type" "alu_dsp_reg")])
5959
5960(define_insn "arm_usada8"
5961  [(set (match_operand:SI 0 "s_register_operand" "=r")
5962	(unspec:SI
5963	  [(match_operand:SI 1 "s_register_operand" "r")
5964	  (match_operand:SI 2 "s_register_operand" "r")
5965	  (match_operand:SI 3 "s_register_operand" "r")] UNSPEC_USADA8))]
5966  "TARGET_INT_SIMD"
5967  "usada8%?\\t%0, %1, %2, %3"
5968  [(set_attr "predicable" "yes")
5969   (set_attr "type" "alu_dsp_reg")])
5970
5971(define_insn "arm_<simd32_op>"
5972  [(set (match_operand:DI 0 "s_register_operand" "=r")
5973	(unspec:DI
5974	  [(match_operand:SI 1 "s_register_operand" "r")
5975	   (match_operand:SI 2 "s_register_operand" "r")
5976	   (match_operand:DI 3 "s_register_operand" "0")] SIMD32_DIMODE))]
5977  "TARGET_INT_SIMD"
5978  "<simd32_op>%?\\t%Q0, %R0, %1, %2"
5979  [(set_attr "predicable" "yes")
5980   (set_attr "type" "smlald")])
5981
5982(define_insn "arm_<simd32_op>"
5983  [(set (match_operand:SI 0 "s_register_operand" "=r")
5984	(unspec:SI
5985	  [(match_operand:SI 1 "s_register_operand" "r")
5986	   (match_operand:SI 2 "s_register_operand" "r")] SIMD32_GE))
5987   (set (reg:CC APSRGE_REGNUM)
5988	(unspec:CC [(reg:CC APSRGE_REGNUM)] UNSPEC_GE_SET))]
5989  "TARGET_INT_SIMD"
5990  "<simd32_op>%?\\t%0, %1, %2"
5991  [(set_attr "predicable" "yes")
5992   (set_attr "type" "alu_sreg")])
5993
5994(define_insn "arm_<simd32_op><add_clobber_q_name>_insn"
5995  [(set (match_operand:SI 0 "s_register_operand" "=r")
5996	(unspec:SI
5997	  [(match_operand:SI 1 "s_register_operand" "r")
5998	   (match_operand:SI 2 "s_register_operand" "r")
5999	   (match_operand:SI 3 "s_register_operand" "r")] SIMD32_TERNOP_Q))]
6000  "TARGET_INT_SIMD && <add_clobber_q_pred>"
6001  "<simd32_op>%?\\t%0, %1, %2, %3"
6002  [(set_attr "predicable" "yes")
6003   (set_attr "type" "alu_sreg")])
6004
6005(define_expand "arm_<simd32_op>"
6006  [(set (match_operand:SI 0 "s_register_operand")
6007	(unspec:SI
6008	  [(match_operand:SI 1 "s_register_operand")
6009	   (match_operand:SI 2 "s_register_operand")
6010	   (match_operand:SI 3 "s_register_operand")] SIMD32_TERNOP_Q))]
6011  "TARGET_INT_SIMD"
6012  {
6013    if (ARM_Q_BIT_READ)
6014      emit_insn (gen_arm_<simd32_op>_setq_insn (operands[0], operands[1],
6015						operands[2], operands[3]));
6016    else
6017      emit_insn (gen_arm_<simd32_op>_insn (operands[0], operands[1],
6018					   operands[2], operands[3]));
6019    DONE;
6020  }
6021)
6022
6023(define_insn "arm_<simd32_op><add_clobber_q_name>_insn"
6024  [(set (match_operand:SI 0 "s_register_operand" "=r")
6025	(unspec:SI
6026	  [(match_operand:SI 1 "s_register_operand" "r")
6027	   (match_operand:SI 2 "s_register_operand" "r")] SIMD32_BINOP_Q))]
6028  "TARGET_INT_SIMD && <add_clobber_q_pred>"
6029  "<simd32_op>%?\\t%0, %1, %2"
6030  [(set_attr "predicable" "yes")
6031   (set_attr "type" "alu_sreg")])
6032
6033(define_expand "arm_<simd32_op>"
6034  [(set (match_operand:SI 0 "s_register_operand")
6035	(unspec:SI
6036	  [(match_operand:SI 1 "s_register_operand")
6037	   (match_operand:SI 2 "s_register_operand")] SIMD32_BINOP_Q))]
6038  "TARGET_INT_SIMD"
6039  {
6040    if (ARM_Q_BIT_READ)
6041      emit_insn (gen_arm_<simd32_op>_setq_insn (operands[0], operands[1],
6042						operands[2]));
6043    else
6044      emit_insn (gen_arm_<simd32_op>_insn (operands[0], operands[1],
6045					   operands[2]));
6046    DONE;
6047  }
6048)
6049
6050(define_insn "arm_<simd32_op><add_clobber_q_name>_insn"
6051  [(set (match_operand:SI 0 "s_register_operand" "=r")
6052	(unspec:SI
6053	  [(match_operand:SI 1 "s_register_operand" "r")
6054	   (match_operand:SI 2 "<sup>sat16_imm" "i")] USSAT16))]
6055  "TARGET_INT_SIMD && <add_clobber_q_pred>"
6056  "<simd32_op>%?\\t%0, %2, %1"
6057  [(set_attr "predicable" "yes")
6058   (set_attr "type" "alu_sreg")])
6059
6060(define_expand "arm_<simd32_op>"
6061  [(set (match_operand:SI 0 "s_register_operand")
6062	(unspec:SI
6063	  [(match_operand:SI 1 "s_register_operand")
6064	   (match_operand:SI 2 "<sup>sat16_imm")] USSAT16))]
6065  "TARGET_INT_SIMD"
6066  {
6067    if (ARM_Q_BIT_READ)
6068      emit_insn (gen_arm_<simd32_op>_setq_insn (operands[0], operands[1],
6069						operands[2]));
6070    else
6071      emit_insn (gen_arm_<simd32_op>_insn (operands[0], operands[1],
6072					   operands[2]));
6073    DONE;
6074  }
6075)
6076
6077(define_insn "arm_sel"
6078  [(set (match_operand:SI 0 "s_register_operand" "=r")
6079	(unspec:SI
6080	  [(match_operand:SI 1 "s_register_operand" "r")
6081	   (match_operand:SI 2 "s_register_operand" "r")
6082	   (reg:CC APSRGE_REGNUM)] UNSPEC_SEL))]
6083  "TARGET_INT_SIMD"
6084  "sel%?\\t%0, %1, %2"
6085  [(set_attr "predicable" "yes")
6086   (set_attr "type" "alu_sreg")])
6087
6088(define_expand "extendsfdf2"
6089  [(set (match_operand:DF                  0 "s_register_operand")
6090	(float_extend:DF (match_operand:SF 1 "s_register_operand")))]
6091  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
6092  ""
6093)
6094
6095;; HFmode -> DFmode conversions where we don't have an instruction for it
6096;; must go through SFmode.
6097;;
6098;; This is always safe for an extend.
6099
6100(define_expand "extendhfdf2"
6101  [(set (match_operand:DF		   0 "s_register_operand")
6102	(float_extend:DF (match_operand:HF 1 "s_register_operand")))]
6103  "TARGET_EITHER"
6104{
6105  /* We don't have a direct instruction for this, so go via SFmode.  */
6106  if (!(TARGET_32BIT && TARGET_FP16_TO_DOUBLE))
6107    {
6108      rtx op1;
6109      op1 = convert_to_mode (SFmode, operands[1], 0);
6110      op1 = convert_to_mode (DFmode, op1, 0);
6111      emit_insn (gen_movdf (operands[0], op1));
6112      DONE;
6113    }
6114  /* Otherwise, we're done producing RTL and will pick up the correct
6115     pattern to do this with one rounding-step in a single instruction.  */
6116}
6117)
6118
6119;; Move insns (including loads and stores)
6120
6121;; XXX Just some ideas about movti.
6122;; I don't think these are a good idea on the arm, there just aren't enough
6123;; registers
6124;;(define_expand "loadti"
6125;;  [(set (match_operand:TI 0 "s_register_operand")
6126;;	(mem:TI (match_operand:SI 1 "address_operand")))]
6127;;  "" "")
6128
6129;;(define_expand "storeti"
6130;;  [(set (mem:TI (match_operand:TI 0 "address_operand"))
6131;;	(match_operand:TI 1 "s_register_operand"))]
6132;;  "" "")
6133
6134;;(define_expand "movti"
6135;;  [(set (match_operand:TI 0 "general_operand")
6136;;	(match_operand:TI 1 "general_operand"))]
6137;;  ""
6138;;  "
6139;;{
6140;;  rtx insn;
6141;;
6142;;  if (MEM_P (operands[0]) && MEM_P (operands[1]))
6143;;    operands[1] = copy_to_reg (operands[1]);
6144;;  if (MEM_P (operands[0]))
6145;;    insn = gen_storeti (XEXP (operands[0], 0), operands[1]);
6146;;  else if (MEM_P (operands[1]))
6147;;    insn = gen_loadti (operands[0], XEXP (operands[1], 0));
6148;;  else
6149;;    FAIL;
6150;;
6151;;  emit_insn (insn);
6152;;  DONE;
6153;;}")
6154
6155;; Recognize garbage generated above.
6156
6157;;(define_insn ""
6158;;  [(set (match_operand:TI 0 "general_operand" "=r,r,r,<,>,m")
6159;;	(match_operand:TI 1 "general_operand" "<,>,m,r,r,r"))]
6160;;  ""
6161;;  "*
6162;;  {
6163;;    register mem = (which_alternative < 3);
6164;;    register const char *template;
6165;;
6166;;    operands[mem] = XEXP (operands[mem], 0);
6167;;    switch (which_alternative)
6168;;      {
6169;;      case 0: template = \"ldmdb\\t%1!, %M0\"; break;
6170;;      case 1: template = \"ldmia\\t%1!, %M0\"; break;
6171;;      case 2: template = \"ldmia\\t%1, %M0\"; break;
6172;;      case 3: template = \"stmdb\\t%0!, %M1\"; break;
6173;;      case 4: template = \"stmia\\t%0!, %M1\"; break;
6174;;      case 5: template = \"stmia\\t%0, %M1\"; break;
6175;;      }
6176;;    output_asm_insn (template, operands);
6177;;    return \"\";
6178;;  }")
6179
6180(define_expand "movdi"
6181  [(set (match_operand:DI 0 "general_operand")
6182	(match_operand:DI 1 "general_operand"))]
6183  "TARGET_EITHER"
6184  "
6185  gcc_checking_assert (aligned_operand (operands[0], DImode));
6186  gcc_checking_assert (aligned_operand (operands[1], DImode));
6187  if (can_create_pseudo_p ())
6188    {
6189      if (!REG_P (operands[0]))
6190	operands[1] = force_reg (DImode, operands[1]);
6191    }
6192  if (REG_P (operands[0]) && REGNO (operands[0]) <= LAST_ARM_REGNUM
6193      && !targetm.hard_regno_mode_ok (REGNO (operands[0]), DImode))
6194    {
6195      /* Avoid LDRD's into an odd-numbered register pair in ARM state
6196	 when expanding function calls.  */
6197      gcc_assert (can_create_pseudo_p ());
6198      if (MEM_P (operands[1]) && MEM_VOLATILE_P (operands[1]))
6199	{
6200	  /* Perform load into legal reg pair first, then move.  */
6201	  rtx reg = gen_reg_rtx (DImode);
6202	  emit_insn (gen_movdi (reg, operands[1]));
6203	  operands[1] = reg;
6204	}
6205      emit_move_insn (gen_lowpart (SImode, operands[0]),
6206		      gen_lowpart (SImode, operands[1]));
6207      emit_move_insn (gen_highpart (SImode, operands[0]),
6208		      gen_highpart (SImode, operands[1]));
6209      DONE;
6210    }
6211  else if (REG_P (operands[1]) && REGNO (operands[1]) <= LAST_ARM_REGNUM
6212	   && !targetm.hard_regno_mode_ok (REGNO (operands[1]), DImode))
6213    {
6214      /* Avoid STRD's from an odd-numbered register pair in ARM state
6215	 when expanding function prologue.  */
6216      gcc_assert (can_create_pseudo_p ());
6217      rtx split_dest = (MEM_P (operands[0]) && MEM_VOLATILE_P (operands[0]))
6218		       ? gen_reg_rtx (DImode)
6219		       : operands[0];
6220      emit_move_insn (gen_lowpart (SImode, split_dest),
6221		      gen_lowpart (SImode, operands[1]));
6222      emit_move_insn (gen_highpart (SImode, split_dest),
6223		      gen_highpart (SImode, operands[1]));
6224      if (split_dest != operands[0])
6225	emit_insn (gen_movdi (operands[0], split_dest));
6226      DONE;
6227    }
6228  "
6229)
6230
6231(define_insn "*arm_movdi"
6232  [(set (match_operand:DI 0 "nonimmediate_di_operand" "=r, r, r, r, m")
6233	(match_operand:DI 1 "di_operand"              "rDa,Db,Dc,mi,r"))]
6234  "TARGET_32BIT
6235   && !(TARGET_HARD_FLOAT)
6236   && !(TARGET_HAVE_MVE || TARGET_HAVE_MVE_FLOAT)
6237   && !TARGET_IWMMXT
6238   && (   register_operand (operands[0], DImode)
6239       || register_operand (operands[1], DImode))"
6240  "*
6241  switch (which_alternative)
6242    {
6243    case 0:
6244    case 1:
6245    case 2:
6246      return \"#\";
6247    case 3:
6248      /* Cannot load it directly, split to load it via MOV / MOVT.  */
6249      if (!MEM_P (operands[1]) && arm_disable_literal_pool)
6250	return \"#\";
6251      /* Fall through.  */
6252    default:
6253      return output_move_double (operands, true, NULL);
6254    }
6255  "
6256  [(set_attr "length" "8,12,16,8,8")
6257   (set_attr "type" "multiple,multiple,multiple,load_8,store_8")
6258   (set_attr "arm_pool_range" "*,*,*,1020,*")
6259   (set_attr "arm_neg_pool_range" "*,*,*,1004,*")
6260   (set_attr "thumb2_pool_range" "*,*,*,4094,*")
6261   (set_attr "thumb2_neg_pool_range" "*,*,*,0,*")]
6262)
6263
6264(define_split
6265  [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
6266	(match_operand:ANY64 1 "immediate_operand" ""))]
6267  "TARGET_32BIT
6268   && reload_completed
6269   && (arm_disable_literal_pool
6270       || (arm_const_double_inline_cost (operands[1])
6271	   <= arm_max_const_double_inline_cost ()))"
6272  [(const_int 0)]
6273  "
6274  arm_split_constant (SET, SImode, curr_insn,
6275		      INTVAL (gen_lowpart (SImode, operands[1])),
6276		      gen_lowpart (SImode, operands[0]), NULL_RTX, 0);
6277  arm_split_constant (SET, SImode, curr_insn,
6278		      INTVAL (gen_highpart_mode (SImode,
6279						 GET_MODE (operands[0]),
6280						 operands[1])),
6281		      gen_highpart (SImode, operands[0]), NULL_RTX, 0);
6282  DONE;
6283  "
6284)
6285
6286; If optimizing for size, or if we have load delay slots, then
6287; we want to split the constant into two separate operations.
6288; In both cases this may split a trivial part into a single data op
6289; leaving a single complex constant to load.  We can also get longer
6290; offsets in a LDR which means we get better chances of sharing the pool
6291; entries.  Finally, we can normally do a better job of scheduling
6292; LDR instructions than we can with LDM.
6293; This pattern will only match if the one above did not.
6294(define_split
6295  [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
6296	(match_operand:ANY64 1 "const_double_operand" ""))]
6297  "TARGET_ARM && reload_completed
6298   && arm_const_double_by_parts (operands[1])"
6299  [(set (match_dup 0) (match_dup 1))
6300   (set (match_dup 2) (match_dup 3))]
6301  "
6302  operands[2] = gen_highpart (SImode, operands[0]);
6303  operands[3] = gen_highpart_mode (SImode, GET_MODE (operands[0]),
6304				   operands[1]);
6305  operands[0] = gen_lowpart (SImode, operands[0]);
6306  operands[1] = gen_lowpart (SImode, operands[1]);
6307  "
6308)
6309
6310(define_split
6311  [(set (match_operand:ANY64_BF 0 "arm_general_register_operand" "")
6312	(match_operand:ANY64_BF 1 "arm_general_register_operand" ""))]
6313  "TARGET_EITHER && reload_completed"
6314  [(set (match_dup 0) (match_dup 1))
6315   (set (match_dup 2) (match_dup 3))]
6316  "
6317  operands[2] = gen_highpart (SImode, operands[0]);
6318  operands[3] = gen_highpart (SImode, operands[1]);
6319  operands[0] = gen_lowpart (SImode, operands[0]);
6320  operands[1] = gen_lowpart (SImode, operands[1]);
6321
6322  /* Handle a partial overlap.  */
6323  if (rtx_equal_p (operands[0], operands[3]))
6324    {
6325      rtx tmp0 = operands[0];
6326      rtx tmp1 = operands[1];
6327
6328      operands[0] = operands[2];
6329      operands[1] = operands[3];
6330      operands[2] = tmp0;
6331      operands[3] = tmp1;
6332    }
6333  "
6334)
6335
6336;; We can't actually do base+index doubleword loads if the index and
6337;; destination overlap.  Split here so that we at least have chance to
6338;; schedule.
6339(define_split
6340  [(set (match_operand:DI 0 "s_register_operand" "")
6341	(mem:DI (plus:SI (match_operand:SI 1 "s_register_operand" "")
6342			 (match_operand:SI 2 "s_register_operand" ""))))]
6343  "TARGET_LDRD
6344  && reg_overlap_mentioned_p (operands[0], operands[1])
6345  && reg_overlap_mentioned_p (operands[0], operands[2])"
6346  [(set (match_dup 4)
6347	(plus:SI (match_dup 1)
6348		 (match_dup 2)))
6349   (set (match_dup 0)
6350	(mem:DI (match_dup 4)))]
6351  "
6352  operands[4] = gen_rtx_REG (SImode, REGNO(operands[0]));
6353  "
6354)
6355
6356(define_expand "movsi"
6357  [(set (match_operand:SI 0 "general_operand")
6358        (match_operand:SI 1 "general_operand"))]
6359  "TARGET_EITHER"
6360  "
6361  {
6362  rtx base, offset, tmp;
6363
6364  gcc_checking_assert (aligned_operand (operands[0], SImode));
6365  gcc_checking_assert (aligned_operand (operands[1], SImode));
6366  if (TARGET_32BIT || TARGET_HAVE_MOVT)
6367    {
6368      /* Everything except mem = const or mem = mem can be done easily.  */
6369      if (MEM_P (operands[0]))
6370        operands[1] = force_reg (SImode, operands[1]);
6371      if (arm_general_register_operand (operands[0], SImode)
6372	  && CONST_INT_P (operands[1])
6373          && !(const_ok_for_arm (INTVAL (operands[1]))
6374               || const_ok_for_arm (~INTVAL (operands[1]))))
6375        {
6376	   if (DONT_EARLY_SPLIT_CONSTANT (INTVAL (operands[1]), SET))
6377	     {
6378		emit_insn (gen_rtx_SET (operands[0], operands[1]));
6379		DONE;
6380	     }
6381	  else
6382	     {
6383		arm_split_constant (SET, SImode, NULL_RTX,
6384	                            INTVAL (operands[1]), operands[0], NULL_RTX,
6385			            optimize && can_create_pseudo_p ());
6386		DONE;
6387	     }
6388        }
6389    }
6390  else /* Target doesn't have MOVT...  */
6391    {
6392      if (can_create_pseudo_p ())
6393        {
6394          if (!REG_P (operands[0]))
6395	    operands[1] = force_reg (SImode, operands[1]);
6396        }
6397    }
6398
6399  split_const (operands[1], &base, &offset);
6400  if (INTVAL (offset) != 0
6401      && targetm.cannot_force_const_mem (SImode, operands[1]))
6402    {
6403      tmp = can_create_pseudo_p () ? gen_reg_rtx (SImode) : operands[0];
6404      emit_move_insn (tmp, base);
6405      emit_insn (gen_addsi3 (operands[0], tmp, offset));
6406      DONE;
6407    }
6408
6409  tmp = can_create_pseudo_p () ? NULL_RTX : operands[0];
6410
6411  /* Recognize the case where operand[1] is a reference to thread-local
6412     data and load its address to a register.  Offsets have been split off
6413     already.  */
6414  if (arm_tls_referenced_p (operands[1]))
6415    operands[1] = legitimize_tls_address (operands[1], tmp);
6416  else if (flag_pic
6417	   && (CONSTANT_P (operands[1])
6418	       || symbol_mentioned_p (operands[1])
6419	       || label_mentioned_p (operands[1])))
6420    operands[1] =
6421      legitimize_pic_address (operands[1], SImode, tmp, NULL_RTX, false);
6422  }
6423  "
6424)
6425
6426;; The ARM LO_SUM and HIGH are backwards - HIGH sets the low bits, and
6427;; LO_SUM adds in the high bits.  Fortunately these are opaque operations
6428;; so this does not matter.
6429(define_insn "*arm_movt"
6430  [(set (match_operand:SI 0 "nonimmediate_operand" "=r,r")
6431	(lo_sum:SI (match_operand:SI 1 "nonimmediate_operand" "0,0")
6432		   (match_operand:SI 2 "general_operand"      "i,i")))]
6433  "TARGET_HAVE_MOVT && arm_valid_symbolic_address_p (operands[2])"
6434  "@
6435   movt%?\t%0, #:upper16:%c2
6436   movt\t%0, #:upper16:%c2"
6437  [(set_attr "arch"  "32,v8mb")
6438   (set_attr "predicable" "yes")
6439   (set_attr "length" "4")
6440   (set_attr "type" "alu_sreg")]
6441)
6442
6443(define_insn "*arm_movsi_insn"
6444  [(set (match_operand:SI 0 "nonimmediate_operand" "=rk,r,r,r,rk,m")
6445	(match_operand:SI 1 "general_operand"      "rk, I,K,j,mi,rk"))]
6446  "TARGET_ARM && !TARGET_IWMMXT && !TARGET_HARD_FLOAT
6447   && (   register_operand (operands[0], SImode)
6448       || register_operand (operands[1], SImode))"
6449  "@
6450   mov%?\\t%0, %1
6451   mov%?\\t%0, %1
6452   mvn%?\\t%0, #%B1
6453   movw%?\\t%0, %1
6454   ldr%?\\t%0, %1
6455   str%?\\t%1, %0"
6456  [(set_attr "type" "mov_reg,mov_imm,mvn_imm,mov_imm,load_4,store_4")
6457   (set_attr "predicable" "yes")
6458   (set_attr "arch" "*,*,*,v6t2,*,*")
6459   (set_attr "pool_range" "*,*,*,*,4096,*")
6460   (set_attr "neg_pool_range" "*,*,*,*,4084,*")]
6461)
6462
6463(define_split
6464  [(set (match_operand:SI 0 "arm_general_register_operand" "")
6465	(match_operand:SI 1 "const_int_operand" ""))]
6466  "(TARGET_32BIT || TARGET_HAVE_MOVT)
6467  && (!(const_ok_for_arm (INTVAL (operands[1]))
6468        || const_ok_for_arm (~INTVAL (operands[1]))))"
6469  [(clobber (const_int 0))]
6470  "
6471  arm_split_constant (SET, SImode, NULL_RTX,
6472                      INTVAL (operands[1]), operands[0], NULL_RTX, 0);
6473  DONE;
6474  "
6475)
6476
6477;; A normal way to do (symbol + offset) requires three instructions at least
6478;; (depends on how big the offset is) as below:
6479;; movw r0, #:lower16:g
6480;; movw r0, #:upper16:g
6481;; adds r0, #4
6482;;
6483;; A better way would be:
6484;; movw r0, #:lower16:g+4
6485;; movw r0, #:upper16:g+4
6486;;
6487;; The limitation of this way is that the length of offset should be a 16-bit
6488;; signed value, because current assembler only supports REL type relocation for
6489;; such case.  If the more powerful RELA type is supported in future, we should
6490;; update this pattern to go with better way.
6491(define_split
6492  [(set (match_operand:SI 0 "arm_general_register_operand" "")
6493	(const:SI (plus:SI (match_operand:SI 1 "general_operand" "")
6494			   (match_operand:SI 2 "const_int_operand" ""))))]
6495  "TARGET_THUMB
6496   && TARGET_HAVE_MOVT
6497   && arm_disable_literal_pool
6498   && reload_completed
6499   && GET_CODE (operands[1]) == SYMBOL_REF"
6500  [(clobber (const_int 0))]
6501  "
6502    int offset = INTVAL (operands[2]);
6503
6504    if (offset < -0x8000 || offset > 0x7fff)
6505      {
6506	arm_emit_movpair (operands[0], operands[1]);
6507	emit_insn (gen_rtx_SET (operands[0],
6508				gen_rtx_PLUS (SImode, operands[0], operands[2])));
6509      }
6510    else
6511      {
6512	rtx op = gen_rtx_CONST (SImode,
6513				gen_rtx_PLUS (SImode, operands[1], operands[2]));
6514	arm_emit_movpair (operands[0], op);
6515      }
6516  "
6517)
6518
6519;; Split symbol_refs at the later stage (after cprop), instead of generating
6520;; movt/movw pair directly at expand.  Otherwise corresponding high_sum
6521;; and lo_sum would be merged back into memory load at cprop.  However,
6522;; if the default is to prefer movt/movw rather than a load from the constant
6523;; pool, the performance is better.
6524(define_split
6525  [(set (match_operand:SI 0 "arm_general_register_operand" "")
6526       (match_operand:SI 1 "general_operand" ""))]
6527  "TARGET_USE_MOVT && GET_CODE (operands[1]) == SYMBOL_REF
6528   && !target_word_relocations
6529   && !arm_tls_referenced_p (operands[1])"
6530  [(clobber (const_int 0))]
6531{
6532  arm_emit_movpair (operands[0], operands[1]);
6533  DONE;
6534})
6535
6536;; When generating pic, we need to load the symbol offset into a register.
6537;; So that the optimizer does not confuse this with a normal symbol load
6538;; we use an unspec.  The offset will be loaded from a constant pool entry,
6539;; since that is the only type of relocation we can use.
6540
6541;; Wrap calculation of the whole PIC address in a single pattern for the
6542;; benefit of optimizers, particularly, PRE and HOIST.  Calculation of
6543;; a PIC address involves two loads from memory, so we want to CSE it
6544;; as often as possible.
6545;; This pattern will be split into one of the pic_load_addr_* patterns
6546;; and a move after GCSE optimizations.
6547;;
6548;; Note: Update arm.c: legitimize_pic_address() when changing this pattern.
6549(define_expand "calculate_pic_address"
6550  [(set (match_operand:SI 0 "register_operand")
6551	(mem:SI (plus:SI (match_operand:SI 1 "register_operand")
6552			 (unspec:SI [(match_operand:SI 2 "" "")]
6553				    UNSPEC_PIC_SYM))))]
6554  "flag_pic"
6555)
6556
6557;; Split calculate_pic_address into pic_load_addr_* and a move.
6558(define_split
6559  [(set (match_operand:SI 0 "register_operand" "")
6560	(mem:SI (plus:SI (match_operand:SI 1 "register_operand" "")
6561			 (unspec:SI [(match_operand:SI 2 "" "")]
6562				    UNSPEC_PIC_SYM))))]
6563  "flag_pic"
6564  [(set (match_dup 3) (unspec:SI [(match_dup 2)] UNSPEC_PIC_SYM))
6565   (set (match_dup 0) (mem:SI (plus:SI (match_dup 1) (match_dup 3))))]
6566  "operands[3] = can_create_pseudo_p () ? gen_reg_rtx (SImode) : operands[0];"
6567)
6568
6569;; operand1 is the memory address to go into
6570;; pic_load_addr_32bit.
6571;; operand2 is the PIC label to be emitted
6572;; from pic_add_dot_plus_eight.
6573;; We do this to allow hoisting of the entire insn.
6574(define_insn_and_split "pic_load_addr_unified"
6575  [(set (match_operand:SI 0 "s_register_operand" "=r,r,l")
6576	(unspec:SI [(match_operand:SI 1 "" "mX,mX,mX")
6577		    (match_operand:SI 2 "" "")]
6578		    UNSPEC_PIC_UNIFIED))]
6579 "flag_pic"
6580 "#"
6581 "&& reload_completed"
6582 [(set (match_dup 0) (unspec:SI [(match_dup 1)] UNSPEC_PIC_SYM))
6583  (set (match_dup 0) (unspec:SI [(match_dup 0) (match_dup 3)
6584       		     		 (match_dup 2)] UNSPEC_PIC_BASE))]
6585 "operands[3] = TARGET_THUMB ? GEN_INT (4) : GEN_INT (8);"
6586 [(set_attr "type" "load_4,load_4,load_4")
6587  (set_attr "pool_range" "4096,4094,1022")
6588  (set_attr "neg_pool_range" "4084,0,0")
6589  (set_attr "arch"  "a,t2,t1")
6590  (set_attr "length" "8,6,4")]
6591)
6592
6593;; The rather odd constraints on the following are to force reload to leave
6594;; the insn alone, and to force the minipool generation pass to then move
6595;; the GOT symbol to memory.
6596
6597(define_insn "pic_load_addr_32bit"
6598  [(set (match_operand:SI 0 "s_register_operand" "=r")
6599	(unspec:SI [(match_operand:SI 1 "" "mX")] UNSPEC_PIC_SYM))]
6600  "TARGET_32BIT && flag_pic"
6601  "ldr%?\\t%0, %1"
6602  [(set_attr "type" "load_4")
6603   (set (attr "pool_range")
6604	(if_then_else (eq_attr "is_thumb" "no")
6605		      (const_int 4096)
6606		      (const_int 4094)))
6607   (set (attr "neg_pool_range")
6608	(if_then_else (eq_attr "is_thumb" "no")
6609		      (const_int 4084)
6610		      (const_int 0)))]
6611)
6612
6613(define_insn "pic_load_addr_thumb1"
6614  [(set (match_operand:SI 0 "s_register_operand" "=l")
6615	(unspec:SI [(match_operand:SI 1 "" "mX")] UNSPEC_PIC_SYM))]
6616  "TARGET_THUMB1 && flag_pic"
6617  "ldr\\t%0, %1"
6618  [(set_attr "type" "load_4")
6619   (set (attr "pool_range") (const_int 1018))]
6620)
6621
6622(define_insn "pic_add_dot_plus_four"
6623  [(set (match_operand:SI 0 "register_operand" "=r")
6624	(unspec:SI [(match_operand:SI 1 "register_operand" "0")
6625		    (const_int 4)
6626		    (match_operand 2 "" "")]
6627		   UNSPEC_PIC_BASE))]
6628  "TARGET_THUMB"
6629  "*
6630  (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
6631				     INTVAL (operands[2]));
6632  return \"add\\t%0, %|pc\";
6633  "
6634  [(set_attr "length" "2")
6635   (set_attr "type" "alu_sreg")]
6636)
6637
6638(define_insn "pic_add_dot_plus_eight"
6639  [(set (match_operand:SI 0 "register_operand" "=r")
6640	(unspec:SI [(match_operand:SI 1 "register_operand" "r")
6641		    (const_int 8)
6642		    (match_operand 2 "" "")]
6643		   UNSPEC_PIC_BASE))]
6644  "TARGET_ARM"
6645  "*
6646    (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
6647				       INTVAL (operands[2]));
6648    return \"add%?\\t%0, %|pc, %1\";
6649  "
6650  [(set_attr "predicable" "yes")
6651   (set_attr "type" "alu_sreg")]
6652)
6653
6654(define_insn "tls_load_dot_plus_eight"
6655  [(set (match_operand:SI 0 "register_operand" "=r")
6656	(mem:SI (unspec:SI [(match_operand:SI 1 "register_operand" "r")
6657			    (const_int 8)
6658			    (match_operand 2 "" "")]
6659			   UNSPEC_PIC_BASE)))]
6660  "TARGET_ARM"
6661  "*
6662    (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
6663				       INTVAL (operands[2]));
6664    return \"ldr%?\\t%0, [%|pc, %1]\t\t@ tls_load_dot_plus_eight\";
6665  "
6666  [(set_attr "predicable" "yes")
6667   (set_attr "type" "load_4")]
6668)
6669
6670;; PIC references to local variables can generate pic_add_dot_plus_eight
6671;; followed by a load.  These sequences can be crunched down to
6672;; tls_load_dot_plus_eight by a peephole.
6673
6674(define_peephole2
6675  [(set (match_operand:SI 0 "register_operand" "")
6676	(unspec:SI [(match_operand:SI 3 "register_operand" "")
6677		    (const_int 8)
6678		    (match_operand 1 "" "")]
6679		   UNSPEC_PIC_BASE))
6680   (set (match_operand:SI 2 "arm_general_register_operand" "")
6681	(mem:SI (match_dup 0)))]
6682  "TARGET_ARM && peep2_reg_dead_p (2, operands[0])"
6683  [(set (match_dup 2)
6684	(mem:SI (unspec:SI [(match_dup 3)
6685			    (const_int 8)
6686			    (match_dup 1)]
6687			   UNSPEC_PIC_BASE)))]
6688  ""
6689)
6690
6691(define_insn "pic_offset_arm"
6692  [(set (match_operand:SI 0 "register_operand" "=r")
6693	(mem:SI (plus:SI (match_operand:SI 1 "register_operand" "r")
6694			 (unspec:SI [(match_operand:SI 2 "" "X")]
6695				    UNSPEC_PIC_OFFSET))))]
6696  "TARGET_VXWORKS_RTP && TARGET_ARM && flag_pic"
6697  "ldr%?\\t%0, [%1,%2]"
6698  [(set_attr "type" "load_4")]
6699)
6700
6701(define_expand "builtin_setjmp_receiver"
6702  [(label_ref (match_operand 0 "" ""))]
6703  "flag_pic"
6704  "
6705{
6706  /* r3 is clobbered by set/longjmp, so we can use it as a scratch
6707     register.  */
6708  if (arm_pic_register != INVALID_REGNUM)
6709    arm_load_pic_register (1UL << 3, NULL_RTX);
6710  DONE;
6711}")
6712
6713;; If copying one reg to another we can set the condition codes according to
6714;; its value.  Such a move is common after a return from subroutine and the
6715;; result is being tested against zero.
6716
6717(define_insn "*movsi_compare0"
6718  [(set (reg:CC CC_REGNUM)
6719	(compare:CC (match_operand:SI 1 "s_register_operand" "0,0,l,rk,rk")
6720		    (const_int 0)))
6721   (set (match_operand:SI 0 "s_register_operand" "=l,rk,l,r,rk")
6722	(match_dup 1))]
6723  "TARGET_32BIT"
6724  "@
6725   cmp%?\\t%0, #0
6726   cmp%?\\t%0, #0
6727   subs%?\\t%0, %1, #0
6728   subs%?\\t%0, %1, #0
6729   subs%?\\t%0, %1, #0"
6730  [(set_attr "conds" "set")
6731   (set_attr "arch" "t2,*,t2,t2,a")
6732   (set_attr "type" "alus_imm")
6733   (set_attr "length" "2,4,2,4,4")]
6734)
6735
6736;; Subroutine to store a half word from a register into memory.
6737;; Operand 0 is the source register (HImode)
6738;; Operand 1 is the destination address in a register (SImode)
6739
6740;; In both this routine and the next, we must be careful not to spill
6741;; a memory address of reg+large_const into a separate PLUS insn, since this
6742;; can generate unrecognizable rtl.
6743
6744(define_expand "storehi"
6745  [;; store the low byte
6746   (set (match_operand 1 "" "") (match_dup 3))
6747   ;; extract the high byte
6748   (set (match_dup 2)
6749	(ashiftrt:SI (match_operand 0 "" "") (const_int 8)))
6750   ;; store the high byte
6751   (set (match_dup 4) (match_dup 5))]
6752  "TARGET_ARM"
6753  "
6754  {
6755    rtx op1 = operands[1];
6756    rtx addr = XEXP (op1, 0);
6757    enum rtx_code code = GET_CODE (addr);
6758
6759    if ((code == PLUS && !CONST_INT_P (XEXP (addr, 1)))
6760	|| code == MINUS)
6761      op1 = replace_equiv_address (operands[1], force_reg (SImode, addr));
6762
6763    operands[4] = adjust_address (op1, QImode, 1);
6764    operands[1] = adjust_address (operands[1], QImode, 0);
6765    operands[3] = gen_lowpart (QImode, operands[0]);
6766    operands[0] = gen_lowpart (SImode, operands[0]);
6767    operands[2] = gen_reg_rtx (SImode);
6768    operands[5] = gen_lowpart (QImode, operands[2]);
6769  }"
6770)
6771
6772(define_expand "storehi_bigend"
6773  [(set (match_dup 4) (match_dup 3))
6774   (set (match_dup 2)
6775	(ashiftrt:SI (match_operand 0 "" "") (const_int 8)))
6776   (set (match_operand 1 "" "")	(match_dup 5))]
6777  "TARGET_ARM"
6778  "
6779  {
6780    rtx op1 = operands[1];
6781    rtx addr = XEXP (op1, 0);
6782    enum rtx_code code = GET_CODE (addr);
6783
6784    if ((code == PLUS && !CONST_INT_P (XEXP (addr, 1)))
6785	|| code == MINUS)
6786      op1 = replace_equiv_address (op1, force_reg (SImode, addr));
6787
6788    operands[4] = adjust_address (op1, QImode, 1);
6789    operands[1] = adjust_address (operands[1], QImode, 0);
6790    operands[3] = gen_lowpart (QImode, operands[0]);
6791    operands[0] = gen_lowpart (SImode, operands[0]);
6792    operands[2] = gen_reg_rtx (SImode);
6793    operands[5] = gen_lowpart (QImode, operands[2]);
6794  }"
6795)
6796
6797;; Subroutine to store a half word integer constant into memory.
6798(define_expand "storeinthi"
6799  [(set (match_operand 0 "" "")
6800	(match_operand 1 "" ""))
6801   (set (match_dup 3) (match_dup 2))]
6802  "TARGET_ARM"
6803  "
6804  {
6805    HOST_WIDE_INT value = INTVAL (operands[1]);
6806    rtx addr = XEXP (operands[0], 0);
6807    rtx op0 = operands[0];
6808    enum rtx_code code = GET_CODE (addr);
6809
6810    if ((code == PLUS && !CONST_INT_P (XEXP (addr, 1)))
6811	|| code == MINUS)
6812      op0 = replace_equiv_address (op0, force_reg (SImode, addr));
6813
6814    operands[1] = gen_reg_rtx (SImode);
6815    if (BYTES_BIG_ENDIAN)
6816      {
6817	emit_insn (gen_movsi (operands[1], GEN_INT ((value >> 8) & 255)));
6818	if ((value & 255) == ((value >> 8) & 255))
6819	  operands[2] = operands[1];
6820	else
6821	  {
6822	    operands[2] = gen_reg_rtx (SImode);
6823	    emit_insn (gen_movsi (operands[2], GEN_INT (value & 255)));
6824	  }
6825      }
6826    else
6827      {
6828	emit_insn (gen_movsi (operands[1], GEN_INT (value & 255)));
6829	if ((value & 255) == ((value >> 8) & 255))
6830	  operands[2] = operands[1];
6831	else
6832	  {
6833	    operands[2] = gen_reg_rtx (SImode);
6834	    emit_insn (gen_movsi (operands[2], GEN_INT ((value >> 8) & 255)));
6835	  }
6836      }
6837
6838    operands[3] = adjust_address (op0, QImode, 1);
6839    operands[0] = adjust_address (operands[0], QImode, 0);
6840    operands[2] = gen_lowpart (QImode, operands[2]);
6841    operands[1] = gen_lowpart (QImode, operands[1]);
6842  }"
6843)
6844
6845(define_expand "storehi_single_op"
6846  [(set (match_operand:HI 0 "memory_operand")
6847	(match_operand:HI 1 "general_operand"))]
6848  "TARGET_32BIT && arm_arch4"
6849  "
6850  if (!s_register_operand (operands[1], HImode))
6851    operands[1] = copy_to_mode_reg (HImode, operands[1]);
6852  "
6853)
6854
6855(define_expand "movhi"
6856  [(set (match_operand:HI 0 "general_operand")
6857	(match_operand:HI 1 "general_operand"))]
6858  "TARGET_EITHER"
6859  "
6860  gcc_checking_assert (aligned_operand (operands[0], HImode));
6861  gcc_checking_assert (aligned_operand (operands[1], HImode));
6862  if (TARGET_ARM)
6863    {
6864      if (can_create_pseudo_p ())
6865        {
6866          if (MEM_P (operands[0]))
6867	    {
6868	      if (arm_arch4)
6869	        {
6870	          emit_insn (gen_storehi_single_op (operands[0], operands[1]));
6871	          DONE;
6872	        }
6873	      if (CONST_INT_P (operands[1]))
6874	        emit_insn (gen_storeinthi (operands[0], operands[1]));
6875	      else
6876	        {
6877	          if (MEM_P (operands[1]))
6878		    operands[1] = force_reg (HImode, operands[1]);
6879	          if (BYTES_BIG_ENDIAN)
6880		    emit_insn (gen_storehi_bigend (operands[1], operands[0]));
6881	          else
6882		   emit_insn (gen_storehi (operands[1], operands[0]));
6883	        }
6884	      DONE;
6885	    }
6886          /* Sign extend a constant, and keep it in an SImode reg.  */
6887          else if (CONST_INT_P (operands[1]))
6888	    {
6889	      rtx reg = gen_reg_rtx (SImode);
6890	      HOST_WIDE_INT val = INTVAL (operands[1]) & 0xffff;
6891
6892	      /* If the constant is already valid, leave it alone.  */
6893	      if (!const_ok_for_arm (val))
6894	        {
6895	          /* If setting all the top bits will make the constant
6896		     loadable in a single instruction, then set them.
6897		     Otherwise, sign extend the number.  */
6898
6899	          if (const_ok_for_arm (~(val | ~0xffff)))
6900		    val |= ~0xffff;
6901	          else if (val & 0x8000)
6902		    val |= ~0xffff;
6903	        }
6904
6905	      emit_insn (gen_movsi (reg, GEN_INT (val)));
6906	      operands[1] = gen_lowpart (HImode, reg);
6907	    }
6908	  else if (arm_arch4 && optimize && can_create_pseudo_p ()
6909		   && MEM_P (operands[1]))
6910	    {
6911	      rtx reg = gen_reg_rtx (SImode);
6912
6913	      emit_insn (gen_zero_extendhisi2 (reg, operands[1]));
6914	      operands[1] = gen_lowpart (HImode, reg);
6915	    }
6916          else if (!arm_arch4)
6917	    {
6918	      if (MEM_P (operands[1]))
6919	        {
6920		  rtx base;
6921		  rtx offset = const0_rtx;
6922		  rtx reg = gen_reg_rtx (SImode);
6923
6924		  if ((REG_P (base = XEXP (operands[1], 0))
6925		       || (GET_CODE (base) == PLUS
6926			   && (CONST_INT_P (offset = XEXP (base, 1)))
6927                           && ((INTVAL(offset) & 1) != 1)
6928			   && REG_P (base = XEXP (base, 0))))
6929		      && REGNO_POINTER_ALIGN (REGNO (base)) >= 32)
6930		    {
6931		      rtx new_rtx;
6932
6933		      new_rtx = widen_memory_access (operands[1], SImode,
6934						     ((INTVAL (offset) & ~3)
6935						      - INTVAL (offset)));
6936		      emit_insn (gen_movsi (reg, new_rtx));
6937		      if (((INTVAL (offset) & 2) != 0)
6938			  ^ (BYTES_BIG_ENDIAN ? 1 : 0))
6939			{
6940			  rtx reg2 = gen_reg_rtx (SImode);
6941
6942			  emit_insn (gen_lshrsi3 (reg2, reg, GEN_INT (16)));
6943			  reg = reg2;
6944			}
6945		    }
6946		  else
6947		    emit_insn (gen_movhi_bytes (reg, operands[1]));
6948
6949		  operands[1] = gen_lowpart (HImode, reg);
6950	       }
6951	   }
6952        }
6953      /* Handle loading a large integer during reload.  */
6954      else if (CONST_INT_P (operands[1])
6955	       && !const_ok_for_arm (INTVAL (operands[1]))
6956	       && !const_ok_for_arm (~INTVAL (operands[1])))
6957        {
6958          /* Writing a constant to memory needs a scratch, which should
6959	     be handled with SECONDARY_RELOADs.  */
6960          gcc_assert (REG_P (operands[0]));
6961
6962          operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
6963          emit_insn (gen_movsi (operands[0], operands[1]));
6964          DONE;
6965       }
6966    }
6967  else if (TARGET_THUMB2)
6968    {
6969      /* Thumb-2 can do everything except mem=mem and mem=const easily.  */
6970      if (can_create_pseudo_p ())
6971	{
6972	  if (!REG_P (operands[0]))
6973	    operands[1] = force_reg (HImode, operands[1]);
6974          /* Zero extend a constant, and keep it in an SImode reg.  */
6975          else if (CONST_INT_P (operands[1]))
6976	    {
6977	      rtx reg = gen_reg_rtx (SImode);
6978	      HOST_WIDE_INT val = INTVAL (operands[1]) & 0xffff;
6979
6980	      emit_insn (gen_movsi (reg, GEN_INT (val)));
6981	      operands[1] = gen_lowpart (HImode, reg);
6982	    }
6983	}
6984    }
6985  else /* TARGET_THUMB1 */
6986    {
6987      if (can_create_pseudo_p ())
6988        {
6989	  if (CONST_INT_P (operands[1]))
6990	    {
6991	      rtx reg = gen_reg_rtx (SImode);
6992
6993	      emit_insn (gen_movsi (reg, operands[1]));
6994	      operands[1] = gen_lowpart (HImode, reg);
6995	    }
6996
6997          /* ??? We shouldn't really get invalid addresses here, but this can
6998	     happen if we are passed a SP (never OK for HImode/QImode) or
6999	     virtual register (also rejected as illegitimate for HImode/QImode)
7000	     relative address.  */
7001          /* ??? This should perhaps be fixed elsewhere, for instance, in
7002	     fixup_stack_1, by checking for other kinds of invalid addresses,
7003	     e.g. a bare reference to a virtual register.  This may confuse the
7004	     alpha though, which must handle this case differently.  */
7005          if (MEM_P (operands[0])
7006	      && !memory_address_p (GET_MODE (operands[0]),
7007				    XEXP (operands[0], 0)))
7008	    operands[0]
7009	      = replace_equiv_address (operands[0],
7010				       copy_to_reg (XEXP (operands[0], 0)));
7011
7012          if (MEM_P (operands[1])
7013	      && !memory_address_p (GET_MODE (operands[1]),
7014				    XEXP (operands[1], 0)))
7015	    operands[1]
7016	      = replace_equiv_address (operands[1],
7017				       copy_to_reg (XEXP (operands[1], 0)));
7018
7019	  if (MEM_P (operands[1]) && optimize > 0)
7020	    {
7021	      rtx reg = gen_reg_rtx (SImode);
7022
7023	      emit_insn (gen_zero_extendhisi2 (reg, operands[1]));
7024	      operands[1] = gen_lowpart (HImode, reg);
7025	    }
7026
7027          if (MEM_P (operands[0]))
7028	    operands[1] = force_reg (HImode, operands[1]);
7029        }
7030      else if (CONST_INT_P (operands[1])
7031	        && !satisfies_constraint_I (operands[1]))
7032        {
7033	  /* Handle loading a large integer during reload.  */
7034
7035          /* Writing a constant to memory needs a scratch, which should
7036	     be handled with SECONDARY_RELOADs.  */
7037          gcc_assert (REG_P (operands[0]));
7038
7039          operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
7040          emit_insn (gen_movsi (operands[0], operands[1]));
7041          DONE;
7042        }
7043    }
7044  "
7045)
7046
7047(define_expand "movhi_bytes"
7048  [(set (match_dup 2) (zero_extend:SI (match_operand:HI 1 "" "")))
7049   (set (match_dup 3)
7050	(zero_extend:SI (match_dup 6)))
7051   (set (match_operand:SI 0 "" "")
7052	 (ior:SI (ashift:SI (match_dup 4) (const_int 8)) (match_dup 5)))]
7053  "TARGET_ARM"
7054  "
7055  {
7056    rtx mem1, mem2;
7057    rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
7058
7059    mem1 = change_address (operands[1], QImode, addr);
7060    mem2 = change_address (operands[1], QImode,
7061			   plus_constant (Pmode, addr, 1));
7062    operands[0] = gen_lowpart (SImode, operands[0]);
7063    operands[1] = mem1;
7064    operands[2] = gen_reg_rtx (SImode);
7065    operands[3] = gen_reg_rtx (SImode);
7066    operands[6] = mem2;
7067
7068    if (BYTES_BIG_ENDIAN)
7069      {
7070	operands[4] = operands[2];
7071	operands[5] = operands[3];
7072      }
7073    else
7074      {
7075	operands[4] = operands[3];
7076	operands[5] = operands[2];
7077      }
7078  }"
7079)
7080
7081(define_expand "movhi_bigend"
7082  [(set (match_dup 2)
7083	(rotate:SI (subreg:SI (match_operand:HI 1 "memory_operand") 0)
7084		   (const_int 16)))
7085   (set (match_dup 3)
7086	(ashiftrt:SI (match_dup 2) (const_int 16)))
7087   (set (match_operand:HI 0 "s_register_operand")
7088	(match_dup 4))]
7089  "TARGET_ARM"
7090  "
7091  operands[2] = gen_reg_rtx (SImode);
7092  operands[3] = gen_reg_rtx (SImode);
7093  operands[4] = gen_lowpart (HImode, operands[3]);
7094  "
7095)
7096
7097;; Pattern to recognize insn generated default case above
7098(define_insn "*movhi_insn_arch4"
7099  [(set (match_operand:HI 0 "nonimmediate_operand" "=r,r,r,m,r")
7100	(match_operand:HI 1 "general_operand"      "rIk,K,n,r,mi"))]
7101  "TARGET_ARM
7102   && arm_arch4 && !TARGET_HARD_FLOAT
7103   && (register_operand (operands[0], HImode)
7104       || register_operand (operands[1], HImode))"
7105  "@
7106   mov%?\\t%0, %1\\t%@ movhi
7107   mvn%?\\t%0, #%B1\\t%@ movhi
7108   movw%?\\t%0, %L1\\t%@ movhi
7109   strh%?\\t%1, %0\\t%@ movhi
7110   ldrh%?\\t%0, %1\\t%@ movhi"
7111  [(set_attr "predicable" "yes")
7112   (set_attr "pool_range" "*,*,*,*,256")
7113   (set_attr "neg_pool_range" "*,*,*,*,244")
7114   (set_attr "arch" "*,*,v6t2,*,*")
7115   (set_attr_alternative "type"
7116                         [(if_then_else (match_operand 1 "const_int_operand" "")
7117                                        (const_string "mov_imm" )
7118                                        (const_string "mov_reg"))
7119                          (const_string "mvn_imm")
7120                          (const_string "mov_imm")
7121                          (const_string "store_4")
7122                          (const_string "load_4")])]
7123)
7124
7125(define_insn "*movhi_bytes"
7126  [(set (match_operand:HI 0 "s_register_operand" "=r,r,r")
7127	(match_operand:HI 1 "arm_rhs_operand"  "I,rk,K"))]
7128  "TARGET_ARM && !TARGET_HARD_FLOAT"
7129  "@
7130   mov%?\\t%0, %1\\t%@ movhi
7131   mov%?\\t%0, %1\\t%@ movhi
7132   mvn%?\\t%0, #%B1\\t%@ movhi"
7133  [(set_attr "predicable" "yes")
7134   (set_attr "type" "mov_imm,mov_reg,mvn_imm")]
7135)
7136
7137;; We use a DImode scratch because we may occasionally need an additional
7138;; temporary if the address isn't offsettable -- push_reload doesn't seem
7139;; to take any notice of the "o" constraints on reload_memory_operand operand.
7140;; The reload_in<m> and reload_out<m> patterns require special constraints
7141;; to be correctly handled in default_secondary_reload function.
7142(define_expand "reload_outhi"
7143  [(parallel [(match_operand:HI 0 "arm_reload_memory_operand" "=o")
7144	      (match_operand:HI 1 "s_register_operand"        "r")
7145	      (match_operand:DI 2 "s_register_operand"        "=&l")])]
7146  "TARGET_EITHER"
7147  "if (TARGET_ARM)
7148     arm_reload_out_hi (operands);
7149   else
7150     thumb_reload_out_hi (operands);
7151  DONE;
7152  "
7153)
7154
7155(define_expand "reload_inhi"
7156  [(parallel [(match_operand:HI 0 "s_register_operand" "=r")
7157	      (match_operand:HI 1 "arm_reload_memory_operand" "o")
7158	      (match_operand:DI 2 "s_register_operand" "=&r")])]
7159  "TARGET_EITHER"
7160  "
7161  if (TARGET_ARM)
7162    arm_reload_in_hi (operands);
7163  else
7164    thumb_reload_out_hi (operands);
7165  DONE;
7166")
7167
7168(define_expand "movqi"
7169  [(set (match_operand:QI 0 "general_operand")
7170        (match_operand:QI 1 "general_operand"))]
7171  "TARGET_EITHER"
7172  "
7173  /* Everything except mem = const or mem = mem can be done easily */
7174
7175  if (can_create_pseudo_p ())
7176    {
7177      if (CONST_INT_P (operands[1]))
7178	{
7179	  rtx reg = gen_reg_rtx (SImode);
7180
7181	  /* For thumb we want an unsigned immediate, then we are more likely
7182	     to be able to use a movs insn.  */
7183	  if (TARGET_THUMB)
7184	    operands[1] = GEN_INT (INTVAL (operands[1]) & 255);
7185
7186	  emit_insn (gen_movsi (reg, operands[1]));
7187	  operands[1] = gen_lowpart (QImode, reg);
7188	}
7189
7190      if (TARGET_THUMB)
7191	{
7192          /* ??? We shouldn't really get invalid addresses here, but this can
7193	     happen if we are passed a SP (never OK for HImode/QImode) or
7194	     virtual register (also rejected as illegitimate for HImode/QImode)
7195	     relative address.  */
7196          /* ??? This should perhaps be fixed elsewhere, for instance, in
7197	     fixup_stack_1, by checking for other kinds of invalid addresses,
7198	     e.g. a bare reference to a virtual register.  This may confuse the
7199	     alpha though, which must handle this case differently.  */
7200          if (MEM_P (operands[0])
7201	      && !memory_address_p (GET_MODE (operands[0]),
7202		  		     XEXP (operands[0], 0)))
7203	    operands[0]
7204	      = replace_equiv_address (operands[0],
7205				       copy_to_reg (XEXP (operands[0], 0)));
7206          if (MEM_P (operands[1])
7207	      && !memory_address_p (GET_MODE (operands[1]),
7208				    XEXP (operands[1], 0)))
7209	     operands[1]
7210	       = replace_equiv_address (operands[1],
7211					copy_to_reg (XEXP (operands[1], 0)));
7212	}
7213
7214      if (MEM_P (operands[1]) && optimize > 0)
7215	{
7216	  rtx reg = gen_reg_rtx (SImode);
7217
7218	  emit_insn (gen_zero_extendqisi2 (reg, operands[1]));
7219	  operands[1] = gen_lowpart (QImode, reg);
7220	}
7221
7222      if (MEM_P (operands[0]))
7223	operands[1] = force_reg (QImode, operands[1]);
7224    }
7225  else if (TARGET_THUMB
7226	   && CONST_INT_P (operands[1])
7227	   && !satisfies_constraint_I (operands[1]))
7228    {
7229      /* Handle loading a large integer during reload.  */
7230
7231      /* Writing a constant to memory needs a scratch, which should
7232	 be handled with SECONDARY_RELOADs.  */
7233      gcc_assert (REG_P (operands[0]));
7234
7235      operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
7236      emit_insn (gen_movsi (operands[0], operands[1]));
7237      DONE;
7238    }
7239  "
7240)
7241
7242(define_insn "*arm_movqi_insn"
7243  [(set (match_operand:QI 0 "nonimmediate_operand" "=r,r,r,l,r,l,Uu,r,m")
7244	(match_operand:QI 1 "general_operand" "rk,rk,I,Py,K,Uu,l,Uh,r"))]
7245  "TARGET_32BIT
7246   && (   register_operand (operands[0], QImode)
7247       || register_operand (operands[1], QImode))"
7248  "@
7249   mov%?\\t%0, %1
7250   mov%?\\t%0, %1
7251   mov%?\\t%0, %1
7252   mov%?\\t%0, %1
7253   mvn%?\\t%0, #%B1
7254   ldrb%?\\t%0, %1
7255   strb%?\\t%1, %0
7256   ldrb%?\\t%0, %1
7257   strb%?\\t%1, %0"
7258  [(set_attr "type" "mov_reg,mov_reg,mov_imm,mov_imm,mvn_imm,load_4,store_4,load_4,store_4")
7259   (set_attr "predicable" "yes")
7260   (set_attr "predicable_short_it" "yes,yes,no,yes,no,no,no,no,no")
7261   (set_attr "arch" "t2,any,any,t2,any,t2,t2,any,any")
7262   (set_attr "length" "2,4,4,2,4,2,2,4,4")]
7263)
7264
7265;; HFmode and BFmode moves.
7266(define_expand "mov<mode>"
7267  [(set (match_operand:HFBF 0 "general_operand")
7268	(match_operand:HFBF 1 "general_operand"))]
7269  "TARGET_EITHER"
7270  "
7271  gcc_checking_assert (aligned_operand (operands[0], <MODE>mode));
7272  gcc_checking_assert (aligned_operand (operands[1], <MODE>mode));
7273  if (TARGET_32BIT)
7274    {
7275      if (MEM_P (operands[0]))
7276	operands[1] = force_reg (<MODE>mode, operands[1]);
7277    }
7278  else /* TARGET_THUMB1 */
7279    {
7280      if (can_create_pseudo_p ())
7281        {
7282           if (!REG_P (operands[0]))
7283	     operands[1] = force_reg (<MODE>mode, operands[1]);
7284        }
7285    }
7286  "
7287)
7288
7289(define_insn "*arm32_mov<mode>"
7290  [(set (match_operand:HFBF 0 "nonimmediate_operand" "=r,m,r,r")
7291	(match_operand:HFBF 1 "general_operand"	   " m,r,r,F"))]
7292  "TARGET_32BIT && !TARGET_HARD_FLOAT
7293   && (	  s_register_operand (operands[0], <MODE>mode)
7294       || s_register_operand (operands[1], <MODE>mode))"
7295  "*
7296  switch (which_alternative)
7297    {
7298    case 0:	/* ARM register from memory */
7299      return \"ldrh%?\\t%0, %1\\t%@ __<fporbf>\";
7300    case 1:	/* memory from ARM register */
7301      return \"strh%?\\t%1, %0\\t%@ __<fporbf>\";
7302    case 2:	/* ARM register from ARM register */
7303      return \"mov%?\\t%0, %1\\t%@ __<fporbf>\";
7304    case 3:	/* ARM register from constant */
7305      {
7306	long bits;
7307	rtx ops[4];
7308
7309	bits = real_to_target (NULL, CONST_DOUBLE_REAL_VALUE (operands[1]),
7310			       <MODE>mode);
7311	ops[0] = operands[0];
7312	ops[1] = GEN_INT (bits);
7313	ops[2] = GEN_INT (bits & 0xff00);
7314	ops[3] = GEN_INT (bits & 0x00ff);
7315
7316	if (arm_arch_thumb2)
7317	  output_asm_insn (\"movw%?\\t%0, %1\", ops);
7318	else
7319	  output_asm_insn (\"mov%?\\t%0, %2\;orr%?\\t%0, %0, %3\", ops);
7320	return \"\";
7321       }
7322    default:
7323      gcc_unreachable ();
7324    }
7325  "
7326  [(set_attr "conds" "unconditional")
7327   (set_attr "type" "load_4,store_4,mov_reg,multiple")
7328   (set_attr "length" "4,4,4,8")
7329   (set_attr "predicable" "yes")]
7330)
7331
7332(define_expand "movsf"
7333  [(set (match_operand:SF 0 "general_operand")
7334	(match_operand:SF 1 "general_operand"))]
7335  "TARGET_EITHER"
7336  "
7337  gcc_checking_assert (aligned_operand (operands[0], SFmode));
7338  gcc_checking_assert (aligned_operand (operands[1], SFmode));
7339  if (TARGET_32BIT)
7340    {
7341      if (MEM_P (operands[0]))
7342        operands[1] = force_reg (SFmode, operands[1]);
7343    }
7344  else /* TARGET_THUMB1 */
7345    {
7346      if (can_create_pseudo_p ())
7347        {
7348           if (!REG_P (operands[0]))
7349	     operands[1] = force_reg (SFmode, operands[1]);
7350        }
7351    }
7352
7353  /* Cannot load it directly, generate a load with clobber so that it can be
7354     loaded via GPR with MOV / MOVT.  */
7355  if (arm_disable_literal_pool
7356      && (REG_P (operands[0]) || SUBREG_P (operands[0]))
7357      && CONST_DOUBLE_P (operands[1])
7358      && TARGET_HARD_FLOAT
7359      && !vfp3_const_double_rtx (operands[1]))
7360    {
7361      rtx clobreg = gen_reg_rtx (SFmode);
7362      emit_insn (gen_no_literal_pool_sf_immediate (operands[0], operands[1],
7363						   clobreg));
7364      DONE;
7365    }
7366  "
7367)
7368
7369;; Transform a floating-point move of a constant into a core register into
7370;; an SImode operation.
7371(define_split
7372  [(set (match_operand:SF 0 "arm_general_register_operand" "")
7373	(match_operand:SF 1 "immediate_operand" ""))]
7374  "TARGET_EITHER
7375   && reload_completed
7376   && CONST_DOUBLE_P (operands[1])"
7377  [(set (match_dup 2) (match_dup 3))]
7378  "
7379  operands[2] = gen_lowpart (SImode, operands[0]);
7380  operands[3] = gen_lowpart (SImode, operands[1]);
7381  if (operands[2] == 0 || operands[3] == 0)
7382    FAIL;
7383  "
7384)
7385
7386(define_insn "*arm_movsf_soft_insn"
7387  [(set (match_operand:SF 0 "nonimmediate_operand" "=r,r,m")
7388	(match_operand:SF 1 "general_operand"  "r,mE,r"))]
7389  "TARGET_32BIT
7390   && TARGET_SOFT_FLOAT && !TARGET_HAVE_MVE
7391   && (!MEM_P (operands[0])
7392       || register_operand (operands[1], SFmode))"
7393{
7394  switch (which_alternative)
7395    {
7396    case 0: return \"mov%?\\t%0, %1\";
7397    case 1:
7398      /* Cannot load it directly, split to load it via MOV / MOVT.  */
7399      if (!MEM_P (operands[1]) && arm_disable_literal_pool)
7400	return \"#\";
7401      return \"ldr%?\\t%0, %1\\t%@ float\";
7402    case 2: return \"str%?\\t%1, %0\\t%@ float\";
7403    default: gcc_unreachable ();
7404    }
7405}
7406  [(set_attr "predicable" "yes")
7407   (set_attr "type" "mov_reg,load_4,store_4")
7408   (set_attr "arm_pool_range" "*,4096,*")
7409   (set_attr "thumb2_pool_range" "*,4094,*")
7410   (set_attr "arm_neg_pool_range" "*,4084,*")
7411   (set_attr "thumb2_neg_pool_range" "*,0,*")]
7412)
7413
7414;; Splitter for the above.
7415(define_split
7416  [(set (match_operand:SF 0 "s_register_operand")
7417	(match_operand:SF 1 "const_double_operand"))]
7418  "arm_disable_literal_pool && TARGET_SOFT_FLOAT"
7419  [(const_int 0)]
7420{
7421  long buf;
7422  real_to_target (&buf, CONST_DOUBLE_REAL_VALUE (operands[1]), SFmode);
7423  rtx cst = gen_int_mode (buf, SImode);
7424  emit_move_insn (simplify_gen_subreg (SImode, operands[0], SFmode, 0), cst);
7425  DONE;
7426}
7427)
7428
7429(define_expand "movdf"
7430  [(set (match_operand:DF 0 "general_operand")
7431	(match_operand:DF 1 "general_operand"))]
7432  "TARGET_EITHER"
7433  "
7434  gcc_checking_assert (aligned_operand (operands[0], DFmode));
7435  gcc_checking_assert (aligned_operand (operands[1], DFmode));
7436  if (TARGET_32BIT)
7437    {
7438      if (MEM_P (operands[0]))
7439        operands[1] = force_reg (DFmode, operands[1]);
7440    }
7441  else /* TARGET_THUMB */
7442    {
7443      if (can_create_pseudo_p ())
7444        {
7445          if (!REG_P (operands[0]))
7446	    operands[1] = force_reg (DFmode, operands[1]);
7447        }
7448    }
7449
7450  /* Cannot load it directly, generate a load with clobber so that it can be
7451     loaded via GPR with MOV / MOVT.  */
7452  if (arm_disable_literal_pool
7453      && (REG_P (operands[0]) || SUBREG_P (operands[0]))
7454      && CONSTANT_P (operands[1])
7455      && TARGET_HARD_FLOAT
7456      && !arm_const_double_rtx (operands[1])
7457      && !(TARGET_VFP_DOUBLE && vfp3_const_double_rtx (operands[1])))
7458    {
7459      rtx clobreg = gen_reg_rtx (DFmode);
7460      emit_insn (gen_no_literal_pool_df_immediate (operands[0], operands[1],
7461						   clobreg));
7462      DONE;
7463    }
7464  "
7465)
7466
7467;; Reloading a df mode value stored in integer regs to memory can require a
7468;; scratch reg.
7469;; Another reload_out<m> pattern that requires special constraints.
7470(define_expand "reload_outdf"
7471  [(match_operand:DF 0 "arm_reload_memory_operand" "=o")
7472   (match_operand:DF 1 "s_register_operand" "r")
7473   (match_operand:SI 2 "s_register_operand" "=&r")]
7474  "TARGET_THUMB2"
7475  "
7476  {
7477    enum rtx_code code = GET_CODE (XEXP (operands[0], 0));
7478
7479    if (code == REG)
7480      operands[2] = XEXP (operands[0], 0);
7481    else if (code == POST_INC || code == PRE_DEC)
7482      {
7483	operands[0] = gen_rtx_SUBREG (DImode, operands[0], 0);
7484	operands[1] = gen_rtx_SUBREG (DImode, operands[1], 0);
7485	emit_insn (gen_movdi (operands[0], operands[1]));
7486	DONE;
7487      }
7488    else if (code == PRE_INC)
7489      {
7490	rtx reg = XEXP (XEXP (operands[0], 0), 0);
7491
7492	emit_insn (gen_addsi3 (reg, reg, GEN_INT (8)));
7493	operands[2] = reg;
7494      }
7495    else if (code == POST_DEC)
7496      operands[2] = XEXP (XEXP (operands[0], 0), 0);
7497    else
7498      emit_insn (gen_addsi3 (operands[2], XEXP (XEXP (operands[0], 0), 0),
7499			     XEXP (XEXP (operands[0], 0), 1)));
7500
7501    emit_insn (gen_rtx_SET (replace_equiv_address (operands[0], operands[2]),
7502			    operands[1]));
7503
7504    if (code == POST_DEC)
7505      emit_insn (gen_addsi3 (operands[2], operands[2], GEN_INT (-8)));
7506
7507    DONE;
7508  }"
7509)
7510
7511(define_insn "*movdf_soft_insn"
7512  [(set (match_operand:DF 0 "nonimmediate_soft_df_operand" "=r,r,r,r,m")
7513       (match_operand:DF 1 "soft_df_operand" "rDa,Db,Dc,mF,r"))]
7514  "TARGET_32BIT && TARGET_SOFT_FLOAT && !TARGET_HAVE_MVE
7515   && (   register_operand (operands[0], DFmode)
7516       || register_operand (operands[1], DFmode))"
7517  "*
7518  switch (which_alternative)
7519    {
7520    case 0:
7521    case 1:
7522    case 2:
7523      return \"#\";
7524    case 3:
7525      /* Cannot load it directly, split to load it via MOV / MOVT.  */
7526      if (!MEM_P (operands[1]) && arm_disable_literal_pool)
7527	return \"#\";
7528      /* Fall through.  */
7529    default:
7530      return output_move_double (operands, true, NULL);
7531    }
7532  "
7533  [(set_attr "length" "8,12,16,8,8")
7534   (set_attr "type" "multiple,multiple,multiple,load_8,store_8")
7535   (set_attr "arm_pool_range" "*,*,*,1020,*")
7536   (set_attr "thumb2_pool_range" "*,*,*,1018,*")
7537   (set_attr "arm_neg_pool_range" "*,*,*,1004,*")
7538   (set_attr "thumb2_neg_pool_range" "*,*,*,0,*")]
7539)
7540
7541;; Splitter for the above.
7542(define_split
7543  [(set (match_operand:DF 0 "s_register_operand")
7544	(match_operand:DF 1 "const_double_operand"))]
7545  "arm_disable_literal_pool && TARGET_SOFT_FLOAT"
7546  [(const_int 0)]
7547{
7548  long buf[2];
7549  int order = BYTES_BIG_ENDIAN ? 1 : 0;
7550  real_to_target (buf, CONST_DOUBLE_REAL_VALUE (operands[1]), DFmode);
7551  unsigned HOST_WIDE_INT ival = zext_hwi (buf[order], 32);
7552  ival |= (zext_hwi (buf[1 - order], 32) << 32);
7553  rtx cst = gen_int_mode (ival, DImode);
7554  emit_move_insn (simplify_gen_subreg (DImode, operands[0], DFmode, 0), cst);
7555  DONE;
7556}
7557)
7558
7559
7560;; load- and store-multiple insns
7561;; The arm can load/store any set of registers, provided that they are in
7562;; ascending order, but these expanders assume a contiguous set.
7563
7564(define_expand "load_multiple"
7565  [(match_par_dup 3 [(set (match_operand:SI 0 "" "")
7566                          (match_operand:SI 1 "" ""))
7567                     (use (match_operand:SI 2 "" ""))])]
7568  "TARGET_32BIT"
7569{
7570  HOST_WIDE_INT offset = 0;
7571
7572  /* Support only fixed point registers.  */
7573  if (!CONST_INT_P (operands[2])
7574      || INTVAL (operands[2]) > MAX_LDM_STM_OPS
7575      || INTVAL (operands[2]) < 2
7576      || !MEM_P (operands[1])
7577      || !REG_P (operands[0])
7578      || REGNO (operands[0]) > (LAST_ARM_REGNUM - 1)
7579      || REGNO (operands[0]) + INTVAL (operands[2]) > LAST_ARM_REGNUM)
7580    FAIL;
7581
7582  operands[3]
7583    = arm_gen_load_multiple (arm_regs_in_sequence + REGNO (operands[0]),
7584			     INTVAL (operands[2]),
7585			     force_reg (SImode, XEXP (operands[1], 0)),
7586			     FALSE, operands[1], &offset);
7587})
7588
7589(define_expand "store_multiple"
7590  [(match_par_dup 3 [(set (match_operand:SI 0 "" "")
7591                          (match_operand:SI 1 "" ""))
7592                     (use (match_operand:SI 2 "" ""))])]
7593  "TARGET_32BIT"
7594{
7595  HOST_WIDE_INT offset = 0;
7596
7597  /* Support only fixed point registers.  */
7598  if (!CONST_INT_P (operands[2])
7599      || INTVAL (operands[2]) > MAX_LDM_STM_OPS
7600      || INTVAL (operands[2]) < 2
7601      || !REG_P (operands[1])
7602      || !MEM_P (operands[0])
7603      || REGNO (operands[1]) > (LAST_ARM_REGNUM - 1)
7604      || REGNO (operands[1]) + INTVAL (operands[2]) > LAST_ARM_REGNUM)
7605    FAIL;
7606
7607  operands[3]
7608    = arm_gen_store_multiple (arm_regs_in_sequence + REGNO (operands[1]),
7609			      INTVAL (operands[2]),
7610			      force_reg (SImode, XEXP (operands[0], 0)),
7611			      FALSE, operands[0], &offset);
7612})
7613
7614
7615(define_expand "setmemsi"
7616  [(match_operand:BLK 0 "general_operand")
7617   (match_operand:SI 1 "const_int_operand")
7618   (match_operand:SI 2 "const_int_operand")
7619   (match_operand:SI 3 "const_int_operand")]
7620  "TARGET_32BIT"
7621{
7622  if (arm_gen_setmem (operands))
7623    DONE;
7624
7625  FAIL;
7626})
7627
7628
7629;; Move a block of memory if it is word aligned and MORE than 2 words long.
7630;; We could let this apply for blocks of less than this, but it clobbers so
7631;; many registers that there is then probably a better way.
7632
7633(define_expand "cpymemqi"
7634  [(match_operand:BLK 0 "general_operand")
7635   (match_operand:BLK 1 "general_operand")
7636   (match_operand:SI 2 "const_int_operand")
7637   (match_operand:SI 3 "const_int_operand")]
7638  ""
7639  "
7640  if (TARGET_32BIT)
7641    {
7642      if (TARGET_LDRD && current_tune->prefer_ldrd_strd
7643          && !optimize_function_for_size_p (cfun))
7644        {
7645          if (gen_cpymem_ldrd_strd (operands))
7646            DONE;
7647          FAIL;
7648        }
7649
7650      if (arm_gen_cpymemqi (operands))
7651        DONE;
7652      FAIL;
7653    }
7654  else /* TARGET_THUMB1 */
7655    {
7656      if (   INTVAL (operands[3]) != 4
7657          || INTVAL (operands[2]) > 48)
7658        FAIL;
7659
7660      thumb_expand_cpymemqi (operands);
7661      DONE;
7662    }
7663  "
7664)
7665
7666
7667;; Compare & branch insns
7668;; The range calculations are based as follows:
7669;; For forward branches, the address calculation returns the address of
7670;; the next instruction.  This is 2 beyond the branch instruction.
7671;; For backward branches, the address calculation returns the address of
7672;; the first instruction in this pattern (cmp).  This is 2 before the branch
7673;; instruction for the shortest sequence, and 4 before the branch instruction
7674;; if we have to jump around an unconditional branch.
7675;; To the basic branch range the PC offset must be added (this is +4).
7676;; So for forward branches we have
7677;;   (pos_range - pos_base_offs + pc_offs) = (pos_range - 2 + 4).
7678;; And for backward branches we have
7679;;   (neg_range - neg_base_offs + pc_offs) = (neg_range - (-2 or -4) + 4).
7680;;
7681;; In 16-bit Thumb these ranges are:
7682;; For a 'b'       pos_range = 2046, neg_range = -2048 giving (-2040->2048).
7683;; For a 'b<cond>' pos_range = 254,  neg_range = -256  giving (-250 ->256).
7684
7685;; In 32-bit Thumb these ranges are:
7686;; For a 'b'       +/- 16MB is not checked for.
7687;; For a 'b<cond>' pos_range = 1048574,  neg_range = -1048576  giving
7688;; (-1048568 -> 1048576).
7689
7690(define_expand "cbranchsi4"
7691  [(set (pc) (if_then_else
7692	      (match_operator 0 "expandable_comparison_operator"
7693	       [(match_operand:SI 1 "s_register_operand")
7694	        (match_operand:SI 2 "nonmemory_operand")])
7695	      (label_ref (match_operand 3 "" ""))
7696	      (pc)))]
7697  "TARGET_EITHER"
7698  "
7699  if (!TARGET_THUMB1)
7700    {
7701      if (!arm_validize_comparison (&operands[0], &operands[1], &operands[2]))
7702        FAIL;
7703      emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
7704				      operands[3]));
7705      DONE;
7706    }
7707  if (thumb1_cmpneg_operand (operands[2], SImode))
7708    {
7709      emit_jump_insn (gen_cbranchsi4_scratch (NULL, operands[1], operands[2],
7710					      operands[3], operands[0]));
7711      DONE;
7712    }
7713  if (!thumb1_cmp_operand (operands[2], SImode))
7714    operands[2] = force_reg (SImode, operands[2]);
7715  ")
7716
7717(define_expand "cbranchsf4"
7718  [(set (pc) (if_then_else
7719	      (match_operator 0 "expandable_comparison_operator"
7720	       [(match_operand:SF 1 "s_register_operand")
7721	        (match_operand:SF 2 "vfp_compare_operand")])
7722	      (label_ref (match_operand 3 "" ""))
7723	      (pc)))]
7724  "TARGET_32BIT && TARGET_HARD_FLOAT"
7725  "emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
7726				   operands[3])); DONE;"
7727)
7728
7729(define_expand "cbranchdf4"
7730  [(set (pc) (if_then_else
7731	      (match_operator 0 "expandable_comparison_operator"
7732	       [(match_operand:DF 1 "s_register_operand")
7733	        (match_operand:DF 2 "vfp_compare_operand")])
7734	      (label_ref (match_operand 3 "" ""))
7735	      (pc)))]
7736  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
7737  "emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
7738				   operands[3])); DONE;"
7739)
7740
7741(define_expand "cbranchdi4"
7742  [(set (pc) (if_then_else
7743	      (match_operator 0 "expandable_comparison_operator"
7744	       [(match_operand:DI 1 "s_register_operand")
7745	        (match_operand:DI 2 "reg_or_int_operand")])
7746	      (label_ref (match_operand 3 "" ""))
7747	      (pc)))]
7748  "TARGET_32BIT"
7749  "{
7750     if (!arm_validize_comparison (&operands[0], &operands[1], &operands[2]))
7751       FAIL;
7752     emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
7753				       operands[3]));
7754     DONE;
7755   }"
7756)
7757
7758;; Comparison and test insns
7759
7760(define_insn "*arm_cmpsi_insn"
7761  [(set (reg:CC CC_REGNUM)
7762	(compare:CC (match_operand:SI 0 "s_register_operand" "l,r,r,r,r")
7763		    (match_operand:SI 1 "arm_add_operand"    "Py,r,r,I,L")))]
7764  "TARGET_32BIT"
7765  "@
7766   cmp%?\\t%0, %1
7767   cmp%?\\t%0, %1
7768   cmp%?\\t%0, %1
7769   cmp%?\\t%0, %1
7770   cmn%?\\t%0, #%n1"
7771  [(set_attr "conds" "set")
7772   (set_attr "arch" "t2,t2,any,any,any")
7773   (set_attr "length" "2,2,4,4,4")
7774   (set_attr "predicable" "yes")
7775   (set_attr "predicable_short_it" "yes,yes,yes,no,no")
7776   (set_attr "type" "alus_imm,alus_sreg,alus_sreg,alus_imm,alus_imm")]
7777)
7778
7779(define_insn "*cmpsi_shiftsi"
7780  [(set (reg:CC CC_REGNUM)
7781	(compare:CC (match_operand:SI   0 "s_register_operand" "r,r")
7782		    (match_operator:SI  3 "shift_operator"
7783		     [(match_operand:SI 1 "s_register_operand" "r,r")
7784		      (match_operand:SI 2 "shift_amount_operand" "M,r")])))]
7785  "TARGET_32BIT"
7786  "cmp\\t%0, %1%S3"
7787  [(set_attr "conds" "set")
7788   (set_attr "shift" "1")
7789   (set_attr "arch" "32,a")
7790   (set_attr "type" "alus_shift_imm,alus_shift_reg")])
7791
7792(define_insn "*cmpsi_shiftsi_swp"
7793  [(set (reg:CC_SWP CC_REGNUM)
7794	(compare:CC_SWP (match_operator:SI 3 "shift_operator"
7795			 [(match_operand:SI 1 "s_register_operand" "r,r")
7796			  (match_operand:SI 2 "shift_amount_operand" "M,r")])
7797			(match_operand:SI 0 "s_register_operand" "r,r")))]
7798  "TARGET_32BIT"
7799  "cmp%?\\t%0, %1%S3"
7800  [(set_attr "conds" "set")
7801   (set_attr "shift" "1")
7802   (set_attr "arch" "32,a")
7803   (set_attr "type" "alus_shift_imm,alus_shift_reg")])
7804
7805(define_insn "*arm_cmpsi_negshiftsi_si"
7806  [(set (reg:CC_Z CC_REGNUM)
7807	(compare:CC_Z
7808	 (neg:SI (match_operator:SI 1 "shift_operator"
7809		    [(match_operand:SI 2 "s_register_operand" "r,r")
7810		     (match_operand:SI 3 "shift_amount_operand" "M,r")]))
7811	 (match_operand:SI 0 "s_register_operand" "r,r")))]
7812  "TARGET_32BIT"
7813  "cmn%?\\t%0, %2%S1"
7814  [(set_attr "conds" "set")
7815   (set_attr "arch" "32,a")
7816   (set_attr "shift" "2")
7817   (set_attr "type" "alus_shift_imm,alus_shift_reg")
7818   (set_attr "predicable" "yes")]
7819)
7820
7821; This insn allows redundant compares to be removed by cse, nothing should
7822; ever appear in the output file since (set (reg x) (reg x)) is a no-op that
7823; is deleted later on. The match_dup will match the mode here, so that
7824; mode changes of the condition codes aren't lost by this even though we don't
7825; specify what they are.
7826
7827(define_insn "*deleted_compare"
7828  [(set (match_operand 0 "cc_register" "") (match_dup 0))]
7829  "TARGET_32BIT"
7830  "\\t%@ deleted compare"
7831  [(set_attr "conds" "set")
7832   (set_attr "length" "0")
7833   (set_attr "type" "no_insn")]
7834)
7835
7836
7837;; Conditional branch insns
7838
7839(define_expand "cbranch_cc"
7840  [(set (pc)
7841	(if_then_else (match_operator 0 "" [(match_operand 1 "" "")
7842					    (match_operand 2 "" "")])
7843		      (label_ref (match_operand 3 "" ""))
7844		      (pc)))]
7845  "TARGET_32BIT"
7846  "operands[1] = arm_gen_compare_reg (GET_CODE (operands[0]),
7847				      operands[1], operands[2], NULL_RTX);
7848   operands[2] = const0_rtx;"
7849)
7850
7851;;
7852;; Patterns to match conditional branch insns.
7853;;
7854
7855(define_insn "arm_cond_branch"
7856  [(set (pc)
7857	(if_then_else (match_operator 1 "arm_comparison_operator"
7858		       [(match_operand 2 "cc_register" "") (const_int 0)])
7859		      (label_ref (match_operand 0 "" ""))
7860		      (pc)))]
7861  "TARGET_32BIT"
7862  {
7863    if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
7864    {
7865      arm_ccfsm_state += 2;
7866      return "";
7867    }
7868    switch (get_attr_length (insn))
7869      {
7870	case 2: /* Thumb2 16-bit b{cond}.  */
7871	case 4: /* Thumb2 32-bit b{cond} or A32 b{cond}.  */
7872	  return "b%d1\t%l0";
7873	  break;
7874
7875	/* Thumb2 b{cond} out of range.  Use 16-bit b{cond} and
7876	   unconditional branch b.  */
7877	default: return arm_gen_far_branch (operands, 0, "Lbcond", "b%D1\t");
7878      }
7879  }
7880  [(set_attr "conds" "use")
7881   (set_attr "type" "branch")
7882   (set (attr "length")
7883    (if_then_else (match_test "!TARGET_THUMB2")
7884
7885      ;;Target is not Thumb2, therefore is A32.  Generate b{cond}.
7886      (const_int 4)
7887
7888      ;; Check if target is within 16-bit Thumb2 b{cond} range.
7889      (if_then_else (and (ge (minus (match_dup 0) (pc)) (const_int -250))
7890		         (le (minus (match_dup 0) (pc)) (const_int 256)))
7891
7892	;; Target is Thumb2, within narrow range.
7893	;; Generate b{cond}.
7894	(const_int 2)
7895
7896	;; Check if target is within 32-bit Thumb2 b{cond} range.
7897	(if_then_else (and (ge (minus (match_dup 0) (pc))(const_int -1048568))
7898			   (le (minus (match_dup 0) (pc)) (const_int 1048576)))
7899
7900	  ;; Target is Thumb2, within wide range.
7901	  ;; Generate b{cond}
7902	  (const_int 4)
7903	  ;; Target is Thumb2, out of range.
7904	  ;; Generate narrow b{cond} and unconditional branch b.
7905	  (const_int 6)))))]
7906)
7907
7908(define_insn "*arm_cond_branch_reversed"
7909  [(set (pc)
7910	(if_then_else (match_operator 1 "arm_comparison_operator"
7911		       [(match_operand 2 "cc_register" "") (const_int 0)])
7912		      (pc)
7913		      (label_ref (match_operand 0 "" ""))))]
7914  "TARGET_32BIT"
7915  {
7916    if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
7917    {
7918      arm_ccfsm_state += 2;
7919      return "";
7920    }
7921    switch (get_attr_length (insn))
7922      {
7923	case 2: /* Thumb2 16-bit b{cond}.  */
7924	case 4: /* Thumb2 32-bit b{cond} or A32 b{cond}.  */
7925	  return "b%D1\t%l0";
7926	  break;
7927
7928	/* Thumb2 b{cond} out of range.  Use 16-bit b{cond} and
7929	   unconditional branch b.  */
7930	default: return arm_gen_far_branch (operands, 0, "Lbcond", "b%d1\t");
7931      }
7932  }
7933  [(set_attr "conds" "use")
7934   (set_attr "type" "branch")
7935   (set (attr "length")
7936    (if_then_else (match_test "!TARGET_THUMB2")
7937
7938      ;;Target is not Thumb2, therefore is A32.  Generate b{cond}.
7939      (const_int 4)
7940
7941      ;; Check if target is within 16-bit Thumb2 b{cond} range.
7942      (if_then_else (and (ge (minus (match_dup 0) (pc)) (const_int -250))
7943			 (le (minus (match_dup 0) (pc)) (const_int 256)))
7944
7945	;; Target is Thumb2, within narrow range.
7946	;; Generate b{cond}.
7947	(const_int 2)
7948
7949	;; Check if target is within 32-bit Thumb2 b{cond} range.
7950	(if_then_else (and (ge (minus (match_dup 0) (pc))(const_int -1048568))
7951			   (le (minus (match_dup 0) (pc)) (const_int 1048576)))
7952
7953	  ;; Target is Thumb2, within wide range.
7954	  ;; Generate b{cond}.
7955	  (const_int 4)
7956	  ;; Target is Thumb2, out of range.
7957	  ;; Generate narrow b{cond} and unconditional branch b.
7958	  (const_int 6)))))]
7959)
7960
7961
7962
7963; scc insns
7964
7965(define_expand "cstore_cc"
7966  [(set (match_operand:SI 0 "s_register_operand")
7967	(match_operator:SI 1 "" [(match_operand 2 "" "")
7968				 (match_operand 3 "" "")]))]
7969  "TARGET_32BIT"
7970  "operands[2] = arm_gen_compare_reg (GET_CODE (operands[1]),
7971				      operands[2], operands[3], NULL_RTX);
7972   operands[3] = const0_rtx;"
7973)
7974
7975(define_insn_and_split "*mov_scc"
7976  [(set (match_operand:SI 0 "s_register_operand" "=r")
7977	(match_operator:SI 1 "arm_comparison_operator_mode"
7978	 [(match_operand 2 "cc_register" "") (const_int 0)]))]
7979  "TARGET_ARM"
7980  "#"   ; "mov%D1\\t%0, #0\;mov%d1\\t%0, #1"
7981  "TARGET_ARM"
7982  [(set (match_dup 0)
7983        (if_then_else:SI (match_dup 1)
7984                         (const_int 1)
7985                         (const_int 0)))]
7986  ""
7987  [(set_attr "conds" "use")
7988   (set_attr "length" "8")
7989   (set_attr "type" "multiple")]
7990)
7991
7992(define_insn "*negscc_borrow"
7993  [(set (match_operand:SI 0 "s_register_operand" "=r")
7994	(neg:SI (match_operand:SI 1 "arm_borrow_operation" "")))]
7995  "TARGET_32BIT"
7996  "sbc\\t%0, %0, %0"
7997  [(set_attr "conds" "use")
7998   (set_attr "length" "4")
7999   (set_attr "type" "adc_reg")]
8000)
8001
8002(define_insn_and_split "*mov_negscc"
8003  [(set (match_operand:SI 0 "s_register_operand" "=r")
8004	(neg:SI (match_operator:SI 1 "arm_comparison_operator_mode"
8005		 [(match_operand 2 "cc_register" "") (const_int 0)])))]
8006  "TARGET_ARM && !arm_borrow_operation (operands[1], SImode)"
8007  "#"   ; "mov%D1\\t%0, #0\;mvn%d1\\t%0, #0"
8008  "&& true"
8009  [(set (match_dup 0)
8010        (if_then_else:SI (match_dup 1)
8011                         (match_dup 3)
8012                         (const_int 0)))]
8013  {
8014    operands[3] = GEN_INT (~0);
8015  }
8016  [(set_attr "conds" "use")
8017   (set_attr "length" "8")
8018   (set_attr "type" "multiple")]
8019)
8020
8021(define_insn_and_split "*mov_notscc"
8022  [(set (match_operand:SI 0 "s_register_operand" "=r")
8023	(not:SI (match_operator:SI 1 "arm_comparison_operator"
8024		 [(match_operand 2 "cc_register" "") (const_int 0)])))]
8025  "TARGET_ARM"
8026  "#"   ; "mvn%D1\\t%0, #0\;mvn%d1\\t%0, #1"
8027  "TARGET_ARM"
8028  [(set (match_dup 0)
8029        (if_then_else:SI (match_dup 1)
8030                         (match_dup 3)
8031                         (match_dup 4)))]
8032  {
8033    operands[3] = GEN_INT (~1);
8034    operands[4] = GEN_INT (~0);
8035  }
8036  [(set_attr "conds" "use")
8037   (set_attr "length" "8")
8038   (set_attr "type" "multiple")]
8039)
8040
8041(define_expand "cstoresi4"
8042  [(set (match_operand:SI 0 "s_register_operand")
8043	(match_operator:SI 1 "expandable_comparison_operator"
8044	 [(match_operand:SI 2 "s_register_operand")
8045	  (match_operand:SI 3 "reg_or_int_operand")]))]
8046  "TARGET_32BIT || TARGET_THUMB1"
8047  "{
8048  rtx op3, scratch, scratch2;
8049
8050  if (!TARGET_THUMB1)
8051    {
8052      if (!arm_add_operand (operands[3], SImode))
8053	operands[3] = force_reg (SImode, operands[3]);
8054      emit_insn (gen_cstore_cc (operands[0], operands[1],
8055				operands[2], operands[3]));
8056      DONE;
8057    }
8058
8059  if (operands[3] == const0_rtx)
8060    {
8061      switch (GET_CODE (operands[1]))
8062	{
8063	case EQ:
8064	  emit_insn (gen_cstoresi_eq0_thumb1 (operands[0], operands[2]));
8065	  break;
8066
8067	case NE:
8068	  emit_insn (gen_cstoresi_ne0_thumb1 (operands[0], operands[2]));
8069	  break;
8070
8071	case LE:
8072          scratch = expand_binop (SImode, add_optab, operands[2], constm1_rtx,
8073				  NULL_RTX, 0, OPTAB_WIDEN);
8074          scratch = expand_binop (SImode, ior_optab, operands[2], scratch,
8075				  NULL_RTX, 0, OPTAB_WIDEN);
8076          expand_binop (SImode, lshr_optab, scratch, GEN_INT (31),
8077			operands[0], 1, OPTAB_WIDEN);
8078	  break;
8079
8080        case GE:
8081          scratch = expand_unop (SImode, one_cmpl_optab, operands[2],
8082				 NULL_RTX, 1);
8083          expand_binop (SImode, lshr_optab, scratch, GEN_INT (31),
8084			NULL_RTX, 1, OPTAB_WIDEN);
8085          break;
8086
8087        case GT:
8088          scratch = expand_binop (SImode, ashr_optab, operands[2],
8089				  GEN_INT (31), NULL_RTX, 0, OPTAB_WIDEN);
8090          scratch = expand_binop (SImode, sub_optab, scratch, operands[2],
8091				  NULL_RTX, 0, OPTAB_WIDEN);
8092          expand_binop (SImode, lshr_optab, scratch, GEN_INT (31), operands[0],
8093			0, OPTAB_WIDEN);
8094          break;
8095
8096	/* LT is handled by generic code.  No need for unsigned with 0.  */
8097	default:
8098	  FAIL;
8099	}
8100      DONE;
8101    }
8102
8103  switch (GET_CODE (operands[1]))
8104    {
8105    case EQ:
8106      scratch = expand_binop (SImode, sub_optab, operands[2], operands[3],
8107			      NULL_RTX, 0, OPTAB_WIDEN);
8108      emit_insn (gen_cstoresi_eq0_thumb1 (operands[0], scratch));
8109      break;
8110
8111    case NE:
8112      scratch = expand_binop (SImode, sub_optab, operands[2], operands[3],
8113			      NULL_RTX, 0, OPTAB_WIDEN);
8114      emit_insn (gen_cstoresi_ne0_thumb1 (operands[0], scratch));
8115      break;
8116
8117    case LE:
8118      op3 = force_reg (SImode, operands[3]);
8119
8120      scratch = expand_binop (SImode, lshr_optab, operands[2], GEN_INT (31),
8121			      NULL_RTX, 1, OPTAB_WIDEN);
8122      scratch2 = expand_binop (SImode, ashr_optab, op3, GEN_INT (31),
8123			      NULL_RTX, 0, OPTAB_WIDEN);
8124      emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch2,
8125					  op3, operands[2]));
8126      break;
8127
8128    case GE:
8129      op3 = operands[3];
8130      if (!thumb1_cmp_operand (op3, SImode))
8131        op3 = force_reg (SImode, op3);
8132      scratch = expand_binop (SImode, ashr_optab, operands[2], GEN_INT (31),
8133			      NULL_RTX, 0, OPTAB_WIDEN);
8134      scratch2 = expand_binop (SImode, lshr_optab, op3, GEN_INT (31),
8135			       NULL_RTX, 1, OPTAB_WIDEN);
8136      emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch2,
8137					  operands[2], op3));
8138      break;
8139
8140    case LEU:
8141      op3 = force_reg (SImode, operands[3]);
8142      scratch = force_reg (SImode, const0_rtx);
8143      emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch,
8144					  op3, operands[2]));
8145      break;
8146
8147    case GEU:
8148      op3 = operands[3];
8149      if (!thumb1_cmp_operand (op3, SImode))
8150        op3 = force_reg (SImode, op3);
8151      scratch = force_reg (SImode, const0_rtx);
8152      emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch,
8153					  operands[2], op3));
8154      break;
8155
8156    case LTU:
8157      op3 = operands[3];
8158      if (!thumb1_cmp_operand (op3, SImode))
8159        op3 = force_reg (SImode, op3);
8160      scratch = gen_reg_rtx (SImode);
8161      emit_insn (gen_cstoresi_ltu_thumb1 (operands[0], operands[2], op3));
8162      break;
8163
8164    case GTU:
8165      op3 = force_reg (SImode, operands[3]);
8166      scratch = gen_reg_rtx (SImode);
8167      emit_insn (gen_cstoresi_ltu_thumb1 (operands[0], op3, operands[2]));
8168      break;
8169
8170    /* No good sequences for GT, LT.  */
8171    default:
8172      FAIL;
8173    }
8174  DONE;
8175}")
8176
8177(define_expand "cstorehf4"
8178  [(set (match_operand:SI 0 "s_register_operand")
8179	(match_operator:SI 1 "expandable_comparison_operator"
8180	 [(match_operand:HF 2 "s_register_operand")
8181	  (match_operand:HF 3 "vfp_compare_operand")]))]
8182  "TARGET_VFP_FP16INST"
8183  {
8184    if (!arm_validize_comparison (&operands[1],
8185				  &operands[2],
8186				  &operands[3]))
8187       FAIL;
8188
8189    emit_insn (gen_cstore_cc (operands[0], operands[1],
8190			      operands[2], operands[3]));
8191    DONE;
8192  }
8193)
8194
8195(define_expand "cstoresf4"
8196  [(set (match_operand:SI 0 "s_register_operand")
8197	(match_operator:SI 1 "expandable_comparison_operator"
8198	 [(match_operand:SF 2 "s_register_operand")
8199	  (match_operand:SF 3 "vfp_compare_operand")]))]
8200  "TARGET_32BIT && TARGET_HARD_FLOAT"
8201  "emit_insn (gen_cstore_cc (operands[0], operands[1],
8202			     operands[2], operands[3])); DONE;"
8203)
8204
8205(define_expand "cstoredf4"
8206  [(set (match_operand:SI 0 "s_register_operand")
8207	(match_operator:SI 1 "expandable_comparison_operator"
8208	 [(match_operand:DF 2 "s_register_operand")
8209	  (match_operand:DF 3 "vfp_compare_operand")]))]
8210  "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
8211  "emit_insn (gen_cstore_cc (operands[0], operands[1],
8212			     operands[2], operands[3])); DONE;"
8213)
8214
8215(define_expand "cstoredi4"
8216  [(set (match_operand:SI 0 "s_register_operand")
8217	(match_operator:SI 1 "expandable_comparison_operator"
8218	 [(match_operand:DI 2 "s_register_operand")
8219	  (match_operand:DI 3 "reg_or_int_operand")]))]
8220  "TARGET_32BIT"
8221  "{
8222     if (!arm_validize_comparison (&operands[1],
8223     				   &operands[2],
8224				   &operands[3]))
8225       FAIL;
8226     emit_insn (gen_cstore_cc (operands[0], operands[1], operands[2],
8227		      	         operands[3]));
8228     DONE;
8229   }"
8230)
8231
8232
8233;; Conditional move insns
8234
8235(define_expand "movsicc"
8236  [(set (match_operand:SI 0 "s_register_operand")
8237	(if_then_else:SI (match_operand 1 "expandable_comparison_operator")
8238			 (match_operand:SI 2 "arm_not_operand")
8239			 (match_operand:SI 3 "arm_not_operand")))]
8240  "TARGET_32BIT"
8241  "
8242  {
8243    enum rtx_code code;
8244    rtx ccreg;
8245
8246    if (!arm_validize_comparison (&operands[1], &XEXP (operands[1], 0),
8247				  &XEXP (operands[1], 1)))
8248      FAIL;
8249
8250    code = GET_CODE (operands[1]);
8251    ccreg = arm_gen_compare_reg (code, XEXP (operands[1], 0),
8252				 XEXP (operands[1], 1), NULL_RTX);
8253    operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
8254  }"
8255)
8256
8257(define_expand "movhfcc"
8258  [(set (match_operand:HF 0 "s_register_operand")
8259	(if_then_else:HF (match_operand 1 "arm_cond_move_operator")
8260			 (match_operand:HF 2 "s_register_operand")
8261			 (match_operand:HF 3 "s_register_operand")))]
8262  "TARGET_VFP_FP16INST"
8263  "
8264  {
8265    enum rtx_code code = GET_CODE (operands[1]);
8266    rtx ccreg;
8267
8268    if (!arm_validize_comparison (&operands[1], &XEXP (operands[1], 0),
8269				  &XEXP (operands[1], 1)))
8270      FAIL;
8271
8272    code = GET_CODE (operands[1]);
8273    ccreg = arm_gen_compare_reg (code, XEXP (operands[1], 0),
8274				 XEXP (operands[1], 1), NULL_RTX);
8275    operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
8276  }"
8277)
8278
8279(define_expand "movsfcc"
8280  [(set (match_operand:SF 0 "s_register_operand")
8281	(if_then_else:SF (match_operand 1 "arm_cond_move_operator")
8282			 (match_operand:SF 2 "s_register_operand")
8283			 (match_operand:SF 3 "s_register_operand")))]
8284  "TARGET_32BIT && TARGET_HARD_FLOAT"
8285  "
8286  {
8287    enum rtx_code code = GET_CODE (operands[1]);
8288    rtx ccreg;
8289
8290    if (!arm_validize_comparison (&operands[1], &XEXP (operands[1], 0),
8291       				  &XEXP (operands[1], 1)))
8292       FAIL;
8293
8294    code = GET_CODE (operands[1]);
8295    ccreg = arm_gen_compare_reg (code, XEXP (operands[1], 0),
8296				 XEXP (operands[1], 1), NULL_RTX);
8297    operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
8298  }"
8299)
8300
8301(define_expand "movdfcc"
8302  [(set (match_operand:DF 0 "s_register_operand")
8303	(if_then_else:DF (match_operand 1 "arm_cond_move_operator")
8304			 (match_operand:DF 2 "s_register_operand")
8305			 (match_operand:DF 3 "s_register_operand")))]
8306  "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
8307  "
8308  {
8309    enum rtx_code code = GET_CODE (operands[1]);
8310    rtx ccreg;
8311
8312    if (!arm_validize_comparison (&operands[1], &XEXP (operands[1], 0),
8313       				  &XEXP (operands[1], 1)))
8314       FAIL;
8315    code = GET_CODE (operands[1]);
8316    ccreg = arm_gen_compare_reg (code, XEXP (operands[1], 0),
8317				 XEXP (operands[1], 1), NULL_RTX);
8318    operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
8319  }"
8320)
8321
8322(define_insn "*cmov<mode>"
8323    [(set (match_operand:SDF 0 "s_register_operand" "=<F_constraint>")
8324	(if_then_else:SDF (match_operator 1 "arm_vsel_comparison_operator"
8325			  [(match_operand 2 "cc_register" "") (const_int 0)])
8326			  (match_operand:SDF 3 "s_register_operand"
8327			                      "<F_constraint>")
8328			  (match_operand:SDF 4 "s_register_operand"
8329			                      "<F_constraint>")))]
8330  "TARGET_HARD_FLOAT && TARGET_VFP5 <vfp_double_cond>"
8331  "*
8332  {
8333    enum arm_cond_code code = maybe_get_arm_condition_code (operands[1]);
8334    switch (code)
8335      {
8336      case ARM_GE:
8337      case ARM_GT:
8338      case ARM_EQ:
8339      case ARM_VS:
8340        return \"vsel%d1.<V_if_elem>\\t%<V_reg>0, %<V_reg>3, %<V_reg>4\";
8341      case ARM_LT:
8342      case ARM_LE:
8343      case ARM_NE:
8344      case ARM_VC:
8345        return \"vsel%D1.<V_if_elem>\\t%<V_reg>0, %<V_reg>4, %<V_reg>3\";
8346      default:
8347        gcc_unreachable ();
8348      }
8349    return \"\";
8350  }"
8351  [(set_attr "conds" "use")
8352   (set_attr "type" "fcsel")]
8353)
8354
8355(define_insn "*cmovhf"
8356    [(set (match_operand:HF 0 "s_register_operand" "=t")
8357	(if_then_else:HF (match_operator 1 "arm_vsel_comparison_operator"
8358			 [(match_operand 2 "cc_register" "") (const_int 0)])
8359			  (match_operand:HF 3 "s_register_operand" "t")
8360			  (match_operand:HF 4 "s_register_operand" "t")))]
8361  "TARGET_VFP_FP16INST"
8362  "*
8363  {
8364    enum arm_cond_code code = maybe_get_arm_condition_code (operands[1]);
8365    switch (code)
8366      {
8367      case ARM_GE:
8368      case ARM_GT:
8369      case ARM_EQ:
8370      case ARM_VS:
8371	return \"vsel%d1.f16\\t%0, %3, %4\";
8372      case ARM_LT:
8373      case ARM_LE:
8374      case ARM_NE:
8375      case ARM_VC:
8376	return \"vsel%D1.f16\\t%0, %4, %3\";
8377      default:
8378	gcc_unreachable ();
8379      }
8380    return \"\";
8381  }"
8382  [(set_attr "conds" "use")
8383   (set_attr "type" "fcsel")]
8384)
8385
8386(define_insn_and_split "*movsicc_insn"
8387  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r,r,r,r,r")
8388	(if_then_else:SI
8389	 (match_operator 3 "arm_comparison_operator"
8390	  [(match_operand 4 "cc_register" "") (const_int 0)])
8391	 (match_operand:SI 1 "arm_not_operand" "0,0,rI,K,rI,rI,K,K")
8392	 (match_operand:SI 2 "arm_not_operand" "rI,K,0,0,rI,K,rI,K")))]
8393  "TARGET_ARM"
8394  "@
8395   mov%D3\\t%0, %2
8396   mvn%D3\\t%0, #%B2
8397   mov%d3\\t%0, %1
8398   mvn%d3\\t%0, #%B1
8399   #
8400   #
8401   #
8402   #"
8403   ; alt4: mov%d3\\t%0, %1\;mov%D3\\t%0, %2
8404   ; alt5: mov%d3\\t%0, %1\;mvn%D3\\t%0, #%B2
8405   ; alt6: mvn%d3\\t%0, #%B1\;mov%D3\\t%0, %2
8406   ; alt7: mvn%d3\\t%0, #%B1\;mvn%D3\\t%0, #%B2"
8407  "&& reload_completed"
8408  [(const_int 0)]
8409  {
8410    enum rtx_code rev_code;
8411    machine_mode mode;
8412    rtx rev_cond;
8413
8414    emit_insn (gen_rtx_COND_EXEC (VOIDmode,
8415                                  operands[3],
8416                                  gen_rtx_SET (operands[0], operands[1])));
8417
8418    rev_code = GET_CODE (operands[3]);
8419    mode = GET_MODE (operands[4]);
8420    if (mode == CCFPmode || mode == CCFPEmode)
8421      rev_code = reverse_condition_maybe_unordered (rev_code);
8422    else
8423      rev_code = reverse_condition (rev_code);
8424
8425    rev_cond = gen_rtx_fmt_ee (rev_code,
8426                               VOIDmode,
8427                               operands[4],
8428                               const0_rtx);
8429    emit_insn (gen_rtx_COND_EXEC (VOIDmode,
8430                                  rev_cond,
8431                                  gen_rtx_SET (operands[0], operands[2])));
8432    DONE;
8433  }
8434  [(set_attr "length" "4,4,4,4,8,8,8,8")
8435   (set_attr "conds" "use")
8436   (set_attr_alternative "type"
8437                         [(if_then_else (match_operand 2 "const_int_operand" "")
8438                                        (const_string "mov_imm")
8439                                        (const_string "mov_reg"))
8440                          (const_string "mvn_imm")
8441                          (if_then_else (match_operand 1 "const_int_operand" "")
8442                                        (const_string "mov_imm")
8443                                        (const_string "mov_reg"))
8444                          (const_string "mvn_imm")
8445                          (const_string "multiple")
8446                          (const_string "multiple")
8447                          (const_string "multiple")
8448                          (const_string "multiple")])]
8449)
8450
8451(define_insn "*movsfcc_soft_insn"
8452  [(set (match_operand:SF 0 "s_register_operand" "=r,r")
8453	(if_then_else:SF (match_operator 3 "arm_comparison_operator"
8454			  [(match_operand 4 "cc_register" "") (const_int 0)])
8455			 (match_operand:SF 1 "s_register_operand" "0,r")
8456			 (match_operand:SF 2 "s_register_operand" "r,0")))]
8457  "TARGET_ARM && TARGET_SOFT_FLOAT"
8458  "@
8459   mov%D3\\t%0, %2
8460   mov%d3\\t%0, %1"
8461  [(set_attr "conds" "use")
8462   (set_attr "type" "mov_reg")]
8463)
8464
8465
8466;; Jump and linkage insns
8467
8468(define_expand "jump"
8469  [(set (pc)
8470	(label_ref (match_operand 0 "" "")))]
8471  "TARGET_EITHER"
8472  ""
8473)
8474
8475(define_insn "*arm_jump"
8476  [(set (pc)
8477	(label_ref (match_operand 0 "" "")))]
8478  "TARGET_32BIT"
8479  "*
8480  {
8481    if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
8482      {
8483        arm_ccfsm_state += 2;
8484        return \"\";
8485      }
8486    return \"b%?\\t%l0\";
8487  }
8488  "
8489  [(set_attr "predicable" "yes")
8490   (set (attr "length")
8491	(if_then_else
8492	   (and (match_test "TARGET_THUMB2")
8493		(and (ge (minus (match_dup 0) (pc)) (const_int -2044))
8494		     (le (minus (match_dup 0) (pc)) (const_int 2048))))
8495	   (const_int 2)
8496	   (const_int 4)))
8497   (set_attr "type" "branch")]
8498)
8499
8500(define_expand "call"
8501  [(parallel [(call (match_operand 0 "memory_operand")
8502	            (match_operand 1 "general_operand"))
8503	      (use (match_operand 2 "" ""))
8504	      (clobber (reg:SI LR_REGNUM))])]
8505  "TARGET_EITHER"
8506  "
8507  {
8508    rtx callee, pat;
8509    tree addr = MEM_EXPR (operands[0]);
8510
8511    /* In an untyped call, we can get NULL for operand 2.  */
8512    if (operands[2] == NULL_RTX)
8513      operands[2] = const0_rtx;
8514
8515    /* Decide if we should generate indirect calls by loading the
8516       32-bit address of the callee into a register before performing the
8517       branch and link.  */
8518    callee = XEXP (operands[0], 0);
8519    if (GET_CODE (callee) == SYMBOL_REF
8520	? arm_is_long_call_p (SYMBOL_REF_DECL (callee))
8521	: !REG_P (callee))
8522      XEXP (operands[0], 0) = force_reg (Pmode, callee);
8523
8524    if (TARGET_FDPIC && !SYMBOL_REF_P (XEXP (operands[0], 0)))
8525	/* Indirect call: set r9 with FDPIC value of callee.  */
8526	XEXP (operands[0], 0)
8527	  = arm_load_function_descriptor (XEXP (operands[0], 0));
8528
8529    if (detect_cmse_nonsecure_call (addr))
8530      {
8531	pat = gen_nonsecure_call_internal (operands[0], operands[1],
8532					   operands[2]);
8533	emit_call_insn (pat);
8534      }
8535    else
8536      {
8537	pat = gen_call_internal (operands[0], operands[1], operands[2]);
8538	arm_emit_call_insn (pat, XEXP (operands[0], 0), false);
8539      }
8540
8541    /* Restore FDPIC register (r9) after call.  */
8542    if (TARGET_FDPIC)
8543      {
8544	rtx fdpic_reg = gen_rtx_REG (Pmode, FDPIC_REGNUM);
8545	rtx initial_fdpic_reg
8546	    = get_hard_reg_initial_val (Pmode, FDPIC_REGNUM);
8547
8548	emit_insn (gen_restore_pic_register_after_call (fdpic_reg,
8549							initial_fdpic_reg));
8550      }
8551
8552    DONE;
8553  }"
8554)
8555
8556(define_insn "restore_pic_register_after_call"
8557  [(set (match_operand:SI 0 "s_register_operand" "+r,r")
8558        (unspec:SI [(match_dup 0)
8559                    (match_operand:SI 1 "nonimmediate_operand" "r,m")]
8560                   UNSPEC_PIC_RESTORE))]
8561  ""
8562  "@
8563  mov\t%0, %1
8564  ldr\t%0, %1"
8565)
8566
8567(define_expand "call_internal"
8568  [(parallel [(call (match_operand 0 "memory_operand")
8569	            (match_operand 1 "general_operand"))
8570	      (use (match_operand 2 "" ""))
8571	      (clobber (reg:SI LR_REGNUM))])])
8572
8573(define_expand "nonsecure_call_internal"
8574  [(parallel [(call (unspec:SI [(match_operand 0 "memory_operand")]
8575			       UNSPEC_NONSECURE_MEM)
8576		    (match_operand 1 "general_operand"))
8577	      (use (match_operand 2 "" ""))
8578	      (clobber (reg:SI LR_REGNUM))])]
8579  "use_cmse"
8580  "
8581  {
8582    if (!TARGET_HAVE_FPCXT_CMSE)
8583      {
8584	rtx tmp =
8585	  copy_to_suggested_reg (XEXP (operands[0], 0),
8586				 gen_rtx_REG (SImode, R4_REGNUM),
8587				 SImode);
8588
8589	operands[0] = replace_equiv_address (operands[0], tmp);
8590      }
8591  }")
8592
8593(define_insn "*call_reg_armv5"
8594  [(call (mem:SI (match_operand:SI 0 "s_register_operand" "r"))
8595         (match_operand 1 "" ""))
8596   (use (match_operand 2 "" ""))
8597   (clobber (reg:SI LR_REGNUM))]
8598  "TARGET_ARM && arm_arch5t && !SIBLING_CALL_P (insn)"
8599  "blx%?\\t%0"
8600  [(set_attr "type" "call")]
8601)
8602
8603(define_insn "*call_reg_arm"
8604  [(call (mem:SI (match_operand:SI 0 "s_register_operand" "r"))
8605         (match_operand 1 "" ""))
8606   (use (match_operand 2 "" ""))
8607   (clobber (reg:SI LR_REGNUM))]
8608  "TARGET_ARM && !arm_arch5t && !SIBLING_CALL_P (insn)"
8609  "*
8610  return output_call (operands);
8611  "
8612  ;; length is worst case, normally it is only two
8613  [(set_attr "length" "12")
8614   (set_attr "type" "call")]
8615)
8616
8617
8618(define_expand "call_value"
8619  [(parallel [(set (match_operand       0 "" "")
8620	           (call (match_operand 1 "memory_operand")
8621		         (match_operand 2 "general_operand")))
8622	      (use (match_operand 3 "" ""))
8623	      (clobber (reg:SI LR_REGNUM))])]
8624  "TARGET_EITHER"
8625  "
8626  {
8627    rtx pat, callee;
8628    tree addr = MEM_EXPR (operands[1]);
8629
8630    /* In an untyped call, we can get NULL for operand 2.  */
8631    if (operands[3] == 0)
8632      operands[3] = const0_rtx;
8633
8634    /* Decide if we should generate indirect calls by loading the
8635       32-bit address of the callee into a register before performing the
8636       branch and link.  */
8637    callee = XEXP (operands[1], 0);
8638    if (GET_CODE (callee) == SYMBOL_REF
8639	? arm_is_long_call_p (SYMBOL_REF_DECL (callee))
8640	: !REG_P (callee))
8641      XEXP (operands[1], 0) = force_reg (Pmode, callee);
8642
8643    if (TARGET_FDPIC && !SYMBOL_REF_P (XEXP (operands[1], 0)))
8644	/* Indirect call: set r9 with FDPIC value of callee.  */
8645	XEXP (operands[1], 0)
8646	  = arm_load_function_descriptor (XEXP (operands[1], 0));
8647
8648    if (detect_cmse_nonsecure_call (addr))
8649      {
8650	pat = gen_nonsecure_call_value_internal (operands[0], operands[1],
8651						 operands[2], operands[3]);
8652	emit_call_insn (pat);
8653      }
8654    else
8655      {
8656	pat = gen_call_value_internal (operands[0], operands[1],
8657				       operands[2], operands[3]);
8658	arm_emit_call_insn (pat, XEXP (operands[1], 0), false);
8659      }
8660
8661    /* Restore FDPIC register (r9) after call.  */
8662    if (TARGET_FDPIC)
8663      {
8664	rtx fdpic_reg = gen_rtx_REG (Pmode, FDPIC_REGNUM);
8665	rtx initial_fdpic_reg
8666	    = get_hard_reg_initial_val (Pmode, FDPIC_REGNUM);
8667
8668	emit_insn (gen_restore_pic_register_after_call (fdpic_reg,
8669							initial_fdpic_reg));
8670      }
8671
8672    DONE;
8673  }"
8674)
8675
8676(define_expand "call_value_internal"
8677  [(parallel [(set (match_operand       0 "" "")
8678	           (call (match_operand 1 "memory_operand")
8679		         (match_operand 2 "general_operand")))
8680	      (use (match_operand 3 "" ""))
8681	      (clobber (reg:SI LR_REGNUM))])])
8682
8683(define_expand "nonsecure_call_value_internal"
8684  [(parallel [(set (match_operand       0 "" "")
8685		   (call (unspec:SI [(match_operand 1 "memory_operand")]
8686				    UNSPEC_NONSECURE_MEM)
8687			 (match_operand 2 "general_operand")))
8688	      (use (match_operand 3 "" ""))
8689	      (clobber (reg:SI LR_REGNUM))])]
8690  "use_cmse"
8691  "
8692  {
8693    if (!TARGET_HAVE_FPCXT_CMSE)
8694      {
8695	rtx tmp =
8696	  copy_to_suggested_reg (XEXP (operands[1], 0),
8697				 gen_rtx_REG (SImode, R4_REGNUM),
8698				 SImode);
8699
8700	operands[1] = replace_equiv_address (operands[1], tmp);
8701      }
8702  }")
8703
8704(define_insn "*call_value_reg_armv5"
8705  [(set (match_operand 0 "" "")
8706        (call (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
8707	      (match_operand 2 "" "")))
8708   (use (match_operand 3 "" ""))
8709   (clobber (reg:SI LR_REGNUM))]
8710  "TARGET_ARM && arm_arch5t && !SIBLING_CALL_P (insn)"
8711  "blx%?\\t%1"
8712  [(set_attr "type" "call")]
8713)
8714
8715(define_insn "*call_value_reg_arm"
8716  [(set (match_operand 0 "" "")
8717        (call (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
8718	      (match_operand 2 "" "")))
8719   (use (match_operand 3 "" ""))
8720   (clobber (reg:SI LR_REGNUM))]
8721  "TARGET_ARM && !arm_arch5t && !SIBLING_CALL_P (insn)"
8722  "*
8723  return output_call (&operands[1]);
8724  "
8725  [(set_attr "length" "12")
8726   (set_attr "type" "call")]
8727)
8728
8729;; Allow calls to SYMBOL_REFs specially as they are not valid general addresses
8730;; The 'a' causes the operand to be treated as an address, i.e. no '#' output.
8731
8732(define_insn "*call_symbol"
8733  [(call (mem:SI (match_operand:SI 0 "" ""))
8734	 (match_operand 1 "" ""))
8735   (use (match_operand 2 "" ""))
8736   (clobber (reg:SI LR_REGNUM))]
8737  "TARGET_32BIT
8738   && !SIBLING_CALL_P (insn)
8739   && (GET_CODE (operands[0]) == SYMBOL_REF)
8740   && !arm_is_long_call_p (SYMBOL_REF_DECL (operands[0]))"
8741  "*
8742  {
8743   rtx op = operands[0];
8744
8745   /* Switch mode now when possible.  */
8746   if (SYMBOL_REF_DECL (op) && !TREE_PUBLIC (SYMBOL_REF_DECL (op))
8747	&& arm_arch5t && arm_change_mode_p (SYMBOL_REF_DECL (op)))
8748      return NEED_PLT_RELOC ? \"blx%?\\t%a0(PLT)\" : \"blx%?\\t(%a0)\";
8749
8750    return NEED_PLT_RELOC ? \"bl%?\\t%a0(PLT)\" : \"bl%?\\t%a0\";
8751  }"
8752  [(set_attr "type" "call")]
8753)
8754
8755(define_insn "*call_value_symbol"
8756  [(set (match_operand 0 "" "")
8757	(call (mem:SI (match_operand:SI 1 "" ""))
8758	(match_operand:SI 2 "" "")))
8759   (use (match_operand 3 "" ""))
8760   (clobber (reg:SI LR_REGNUM))]
8761  "TARGET_32BIT
8762   && !SIBLING_CALL_P (insn)
8763   && (GET_CODE (operands[1]) == SYMBOL_REF)
8764   && !arm_is_long_call_p (SYMBOL_REF_DECL (operands[1]))"
8765  "*
8766  {
8767   rtx op = operands[1];
8768
8769   /* Switch mode now when possible.  */
8770   if (SYMBOL_REF_DECL (op) && !TREE_PUBLIC (SYMBOL_REF_DECL (op))
8771	&& arm_arch5t && arm_change_mode_p (SYMBOL_REF_DECL (op)))
8772      return NEED_PLT_RELOC ? \"blx%?\\t%a1(PLT)\" : \"blx%?\\t(%a1)\";
8773
8774    return NEED_PLT_RELOC ? \"bl%?\\t%a1(PLT)\" : \"bl%?\\t%a1\";
8775  }"
8776  [(set_attr "type" "call")]
8777)
8778
8779(define_expand "sibcall_internal"
8780  [(parallel [(call (match_operand 0 "memory_operand")
8781		    (match_operand 1 "general_operand"))
8782	      (return)
8783	      (use (match_operand 2 "" ""))])])
8784
8785;; We may also be able to do sibcalls for Thumb, but it's much harder...
8786(define_expand "sibcall"
8787  [(parallel [(call (match_operand 0 "memory_operand")
8788		    (match_operand 1 "general_operand"))
8789	      (return)
8790	      (use (match_operand 2 "" ""))])]
8791  "TARGET_32BIT"
8792  "
8793  {
8794    rtx pat;
8795
8796    if ((!REG_P (XEXP (operands[0], 0))
8797	 && GET_CODE (XEXP (operands[0], 0)) != SYMBOL_REF)
8798	|| (GET_CODE (XEXP (operands[0], 0)) == SYMBOL_REF
8799	    && arm_is_long_call_p (SYMBOL_REF_DECL (XEXP (operands[0], 0)))))
8800     XEXP (operands[0], 0) = force_reg (SImode, XEXP (operands[0], 0));
8801
8802    if (operands[2] == NULL_RTX)
8803      operands[2] = const0_rtx;
8804
8805    pat = gen_sibcall_internal (operands[0], operands[1], operands[2]);
8806    arm_emit_call_insn (pat, operands[0], true);
8807    DONE;
8808  }"
8809)
8810
8811(define_expand "sibcall_value_internal"
8812  [(parallel [(set (match_operand 0 "" "")
8813		   (call (match_operand 1 "memory_operand")
8814			 (match_operand 2 "general_operand")))
8815	      (return)
8816	      (use (match_operand 3 "" ""))])])
8817
8818(define_expand "sibcall_value"
8819  [(parallel [(set (match_operand 0 "" "")
8820		   (call (match_operand 1 "memory_operand")
8821			 (match_operand 2 "general_operand")))
8822	      (return)
8823	      (use (match_operand 3 "" ""))])]
8824  "TARGET_32BIT"
8825  "
8826  {
8827    rtx pat;
8828
8829    if ((!REG_P (XEXP (operands[1], 0))
8830	 && GET_CODE (XEXP (operands[1], 0)) != SYMBOL_REF)
8831	|| (GET_CODE (XEXP (operands[1], 0)) == SYMBOL_REF
8832	    && arm_is_long_call_p (SYMBOL_REF_DECL (XEXP (operands[1], 0)))))
8833     XEXP (operands[1], 0) = force_reg (SImode, XEXP (operands[1], 0));
8834
8835    if (operands[3] == NULL_RTX)
8836      operands[3] = const0_rtx;
8837
8838    pat = gen_sibcall_value_internal (operands[0], operands[1],
8839                                      operands[2], operands[3]);
8840    arm_emit_call_insn (pat, operands[1], true);
8841    DONE;
8842  }"
8843)
8844
8845(define_insn "*sibcall_insn"
8846 [(call (mem:SI (match_operand:SI 0 "call_insn_operand" "Cs, US"))
8847	(match_operand 1 "" ""))
8848  (return)
8849  (use (match_operand 2 "" ""))]
8850  "TARGET_32BIT && SIBLING_CALL_P (insn)"
8851  "*
8852  if (which_alternative == 1)
8853    return NEED_PLT_RELOC ? \"b%?\\t%a0(PLT)\" : \"b%?\\t%a0\";
8854  else
8855    {
8856      if (arm_arch5t || arm_arch4t)
8857	return \"bx%?\\t%0\\t%@ indirect register sibling call\";
8858      else
8859	return \"mov%?\\t%|pc, %0\\t%@ indirect register sibling call\";
8860    }
8861  "
8862  [(set_attr "type" "call")]
8863)
8864
8865(define_insn "*sibcall_value_insn"
8866 [(set (match_operand 0 "" "")
8867       (call (mem:SI (match_operand:SI 1 "call_insn_operand" "Cs,US"))
8868	     (match_operand 2 "" "")))
8869  (return)
8870  (use (match_operand 3 "" ""))]
8871  "TARGET_32BIT && SIBLING_CALL_P (insn)"
8872  "*
8873  if (which_alternative == 1)
8874   return NEED_PLT_RELOC ? \"b%?\\t%a1(PLT)\" : \"b%?\\t%a1\";
8875  else
8876    {
8877      if (arm_arch5t || arm_arch4t)
8878	return \"bx%?\\t%1\";
8879      else
8880	return \"mov%?\\t%|pc, %1\\t@ indirect sibling call \";
8881    }
8882  "
8883  [(set_attr "type" "call")]
8884)
8885
8886(define_expand "<return_str>return"
8887  [(RETURNS)]
8888  "(TARGET_ARM || (TARGET_THUMB2
8889                   && ARM_FUNC_TYPE (arm_current_func_type ()) == ARM_FT_NORMAL
8890                   && !IS_STACKALIGN (arm_current_func_type ())))
8891    <return_cond_false>"
8892  "
8893  {
8894    if (TARGET_THUMB2)
8895      {
8896        thumb2_expand_return (<return_simple_p>);
8897        DONE;
8898      }
8899  }
8900  "
8901)
8902
8903;; Often the return insn will be the same as loading from memory, so set attr
8904(define_insn "*arm_return"
8905  [(return)]
8906  "TARGET_ARM && USE_RETURN_INSN (FALSE)"
8907  "*
8908  {
8909    if (arm_ccfsm_state == 2)
8910      {
8911        arm_ccfsm_state += 2;
8912        return \"\";
8913      }
8914    return output_return_instruction (const_true_rtx, true, false, false);
8915  }"
8916  [(set_attr "type" "load_4")
8917   (set_attr "length" "12")
8918   (set_attr "predicable" "yes")]
8919)
8920
8921(define_insn "*cond_<return_str>return"
8922  [(set (pc)
8923        (if_then_else (match_operator 0 "arm_comparison_operator"
8924		       [(match_operand 1 "cc_register" "") (const_int 0)])
8925                      (RETURNS)
8926                      (pc)))]
8927  "TARGET_ARM  <return_cond_true>"
8928  "*
8929  {
8930    if (arm_ccfsm_state == 2)
8931      {
8932        arm_ccfsm_state += 2;
8933        return \"\";
8934      }
8935    return output_return_instruction (operands[0], true, false,
8936				      <return_simple_p>);
8937  }"
8938  [(set_attr "conds" "use")
8939   (set_attr "length" "12")
8940   (set_attr "type" "load_4")]
8941)
8942
8943(define_insn "*cond_<return_str>return_inverted"
8944  [(set (pc)
8945        (if_then_else (match_operator 0 "arm_comparison_operator"
8946		       [(match_operand 1 "cc_register" "") (const_int 0)])
8947                      (pc)
8948		      (RETURNS)))]
8949  "TARGET_ARM <return_cond_true>"
8950  "*
8951  {
8952    if (arm_ccfsm_state == 2)
8953      {
8954        arm_ccfsm_state += 2;
8955        return \"\";
8956      }
8957    return output_return_instruction (operands[0], true, true,
8958				      <return_simple_p>);
8959  }"
8960  [(set_attr "conds" "use")
8961   (set_attr "length" "12")
8962   (set_attr "type" "load_4")]
8963)
8964
8965(define_insn "*arm_simple_return"
8966  [(simple_return)]
8967  "TARGET_ARM"
8968  "*
8969  {
8970    if (arm_ccfsm_state == 2)
8971      {
8972        arm_ccfsm_state += 2;
8973        return \"\";
8974      }
8975    return output_return_instruction (const_true_rtx, true, false, true);
8976  }"
8977  [(set_attr "type" "branch")
8978   (set_attr "length" "4")
8979   (set_attr "predicable" "yes")]
8980)
8981
8982;; Generate a sequence of instructions to determine if the processor is
8983;; in 26-bit or 32-bit mode, and return the appropriate return address
8984;; mask.
8985
8986(define_expand "return_addr_mask"
8987  [(set (match_dup 1)
8988      (compare:CC_NZ (unspec [(const_int 0)] UNSPEC_CHECK_ARCH)
8989		       (const_int 0)))
8990   (set (match_operand:SI 0 "s_register_operand")
8991      (if_then_else:SI (eq (match_dup 1) (const_int 0))
8992		       (const_int -1)
8993		       (const_int 67108860)))] ; 0x03fffffc
8994  "TARGET_ARM"
8995  "
8996  operands[1] = gen_rtx_REG (CC_NZmode, CC_REGNUM);
8997  ")
8998
8999(define_insn "*check_arch2"
9000  [(set (match_operand:CC_NZ 0 "cc_register" "")
9001      (compare:CC_NZ (unspec [(const_int 0)] UNSPEC_CHECK_ARCH)
9002		       (const_int 0)))]
9003  "TARGET_ARM"
9004  "teq\\t%|r0, %|r0\;teq\\t%|pc, %|pc"
9005  [(set_attr "length" "8")
9006   (set_attr "conds" "set")
9007   (set_attr "type" "multiple")]
9008)
9009
9010;; Call subroutine returning any type.
9011
9012(define_expand "untyped_call"
9013  [(parallel [(call (match_operand 0 "" "")
9014		    (const_int 0))
9015	      (match_operand 1 "" "")
9016	      (match_operand 2 "" "")])]
9017  "TARGET_EITHER && !TARGET_FDPIC"
9018  "
9019  {
9020    int i;
9021    rtx par = gen_rtx_PARALLEL (VOIDmode,
9022				rtvec_alloc (XVECLEN (operands[2], 0)));
9023    rtx addr = gen_reg_rtx (Pmode);
9024    rtx mem;
9025    int size = 0;
9026
9027    emit_move_insn (addr, XEXP (operands[1], 0));
9028    mem = change_address (operands[1], BLKmode, addr);
9029
9030    for (i = 0; i < XVECLEN (operands[2], 0); i++)
9031      {
9032	rtx src = SET_SRC (XVECEXP (operands[2], 0, i));
9033
9034	/* Default code only uses r0 as a return value, but we could
9035	   be using anything up to 4 registers.  */
9036	if (REGNO (src) == R0_REGNUM)
9037	  src = gen_rtx_REG (TImode, R0_REGNUM);
9038
9039        XVECEXP (par, 0, i) = gen_rtx_EXPR_LIST (VOIDmode, src,
9040						 GEN_INT (size));
9041        size += GET_MODE_SIZE (GET_MODE (src));
9042      }
9043
9044    emit_call_insn (gen_call_value (par, operands[0], const0_rtx, NULL));
9045
9046    size = 0;
9047
9048    for (i = 0; i < XVECLEN (par, 0); i++)
9049      {
9050	HOST_WIDE_INT offset = 0;
9051	rtx reg = XEXP (XVECEXP (par, 0, i), 0);
9052
9053	if (size != 0)
9054	  emit_move_insn (addr, plus_constant (Pmode, addr, size));
9055
9056	mem = change_address (mem, GET_MODE (reg), NULL);
9057	if (REGNO (reg) == R0_REGNUM)
9058	  {
9059	    /* On thumb we have to use a write-back instruction.  */
9060	    emit_insn (arm_gen_store_multiple (arm_regs_in_sequence, 4, addr,
9061 		       TARGET_THUMB ? TRUE : FALSE, mem, &offset));
9062	    size = TARGET_ARM ? 16 : 0;
9063	  }
9064	else
9065	  {
9066	    emit_move_insn (mem, reg);
9067	    size = GET_MODE_SIZE (GET_MODE (reg));
9068	  }
9069      }
9070
9071    /* The optimizer does not know that the call sets the function value
9072       registers we stored in the result block.  We avoid problems by
9073       claiming that all hard registers are used and clobbered at this
9074       point.  */
9075    emit_insn (gen_blockage ());
9076
9077    DONE;
9078  }"
9079)
9080
9081(define_expand "untyped_return"
9082  [(match_operand:BLK 0 "memory_operand")
9083   (match_operand 1 "" "")]
9084  "TARGET_EITHER && !TARGET_FDPIC"
9085  "
9086  {
9087    int i;
9088    rtx addr = gen_reg_rtx (Pmode);
9089    rtx mem;
9090    int size = 0;
9091
9092    emit_move_insn (addr, XEXP (operands[0], 0));
9093    mem = change_address (operands[0], BLKmode, addr);
9094
9095    for (i = 0; i < XVECLEN (operands[1], 0); i++)
9096      {
9097	HOST_WIDE_INT offset = 0;
9098	rtx reg = SET_DEST (XVECEXP (operands[1], 0, i));
9099
9100	if (size != 0)
9101	  emit_move_insn (addr, plus_constant (Pmode, addr, size));
9102
9103	mem = change_address (mem, GET_MODE (reg), NULL);
9104	if (REGNO (reg) == R0_REGNUM)
9105	  {
9106	    /* On thumb we have to use a write-back instruction.  */
9107	    emit_insn (arm_gen_load_multiple (arm_regs_in_sequence, 4, addr,
9108 		       TARGET_THUMB ? TRUE : FALSE, mem, &offset));
9109	    size = TARGET_ARM ? 16 : 0;
9110	  }
9111	else
9112	  {
9113	    emit_move_insn (reg, mem);
9114	    size = GET_MODE_SIZE (GET_MODE (reg));
9115	  }
9116      }
9117
9118    /* Emit USE insns before the return.  */
9119    for (i = 0; i < XVECLEN (operands[1], 0); i++)
9120      emit_use (SET_DEST (XVECEXP (operands[1], 0, i)));
9121
9122    /* Construct the return.  */
9123    expand_naked_return ();
9124
9125    DONE;
9126  }"
9127)
9128
9129;; UNSPEC_VOLATILE is considered to use and clobber all hard registers and
9130;; all of memory.  This blocks insns from being moved across this point.
9131
9132(define_insn "blockage"
9133  [(unspec_volatile [(const_int 0)] VUNSPEC_BLOCKAGE)]
9134  "TARGET_EITHER"
9135  ""
9136  [(set_attr "length" "0")
9137   (set_attr "type" "block")]
9138)
9139
9140;; Since we hard code r0 here use the 'o' constraint to prevent
9141;; provoking undefined behaviour in the hardware with putting out
9142;; auto-increment operations with potentially r0 as the base register.
9143(define_insn "probe_stack"
9144  [(set (match_operand:SI 0 "memory_operand" "=o")
9145        (unspec:SI [(const_int 0)] UNSPEC_PROBE_STACK))]
9146  "TARGET_32BIT"
9147  "str%?\\tr0, %0"
9148  [(set_attr "type" "store_4")
9149   (set_attr "predicable" "yes")]
9150)
9151
9152(define_insn "probe_stack_range"
9153  [(set (match_operand:SI 0 "register_operand" "=r")
9154	(unspec_volatile:SI [(match_operand:SI 1 "register_operand" "0")
9155			     (match_operand:SI 2 "register_operand" "r")]
9156			     VUNSPEC_PROBE_STACK_RANGE))]
9157  "TARGET_32BIT"
9158{
9159  return output_probe_stack_range (operands[0], operands[2]);
9160}
9161  [(set_attr "type" "multiple")
9162   (set_attr "conds" "clob")]
9163)
9164
9165;; Named patterns for stack smashing protection.
9166(define_expand "stack_protect_combined_set"
9167  [(parallel
9168     [(set (match_operand:SI 0 "memory_operand")
9169	   (unspec:SI [(match_operand:SI 1 "guard_operand")]
9170		      UNSPEC_SP_SET))
9171      (clobber (match_scratch:SI 2 ""))
9172      (clobber (match_scratch:SI 3 ""))])]
9173  ""
9174  ""
9175)
9176
9177;; Use a separate insn from the above expand to be able to have the mem outside
9178;; the operand #1 when register allocation comes. This is needed to avoid LRA
9179;; try to reload the guard since we need to control how PIC access is done in
9180;; the -fpic/-fPIC case (see COMPUTE_NOW parameter when calling
9181;; legitimize_pic_address ()).
9182(define_insn_and_split "*stack_protect_combined_set_insn"
9183  [(set (match_operand:SI 0 "memory_operand" "=m,m")
9184	(unspec:SI [(mem:SI (match_operand:SI 1 "guard_addr_operand" "X,X"))]
9185		   UNSPEC_SP_SET))
9186   (clobber (match_scratch:SI 2 "=&l,&r"))
9187   (clobber (match_scratch:SI 3 "=&l,&r"))]
9188  ""
9189  "#"
9190  "reload_completed"
9191  [(parallel [(set (match_dup 0) (unspec:SI [(mem:SI (match_dup 2))]
9192					    UNSPEC_SP_SET))
9193	      (clobber (match_dup 2))])]
9194  "
9195{
9196  if (flag_pic)
9197    {
9198      rtx pic_reg;
9199
9200      if (TARGET_FDPIC)
9201	  pic_reg = gen_rtx_REG (Pmode, FDPIC_REGNUM);
9202      else
9203	  pic_reg = operands[3];
9204
9205      /* Forces recomputing of GOT base now.  */
9206      legitimize_pic_address (operands[1], SImode, operands[2], pic_reg,
9207			      true /*compute_now*/);
9208    }
9209  else
9210    {
9211      if (address_operand (operands[1], SImode))
9212	operands[2] = operands[1];
9213      else
9214	{
9215	  rtx mem = XEXP (force_const_mem (SImode, operands[1]), 0);
9216	  emit_move_insn (operands[2], mem);
9217	}
9218    }
9219}"
9220  [(set_attr "arch" "t1,32")]
9221)
9222
9223;; DO NOT SPLIT THIS INSN.  It's important for security reasons that the
9224;; canary value does not live beyond the life of this sequence.
9225(define_insn "*stack_protect_set_insn"
9226  [(set (match_operand:SI 0 "memory_operand" "=m,m")
9227	(unspec:SI [(mem:SI (match_operand:SI 1 "register_operand" "+&l,&r"))]
9228	 UNSPEC_SP_SET))
9229   (clobber (match_dup 1))]
9230  ""
9231  "@
9232   ldr\\t%1, [%1]\;str\\t%1, %0\;movs\t%1, #0
9233   ldr\\t%1, [%1]\;str\\t%1, %0\;mov\t%1, #0"
9234  [(set_attr "length" "8,12")
9235   (set_attr "conds" "clob,nocond")
9236   (set_attr "type" "multiple")
9237   (set_attr "arch" "t1,32")]
9238)
9239
9240(define_expand "stack_protect_combined_test"
9241  [(parallel
9242     [(set (pc)
9243	   (if_then_else
9244		(eq (match_operand:SI 0 "memory_operand")
9245		    (unspec:SI [(match_operand:SI 1 "guard_operand")]
9246			       UNSPEC_SP_TEST))
9247		(label_ref (match_operand 2))
9248		(pc)))
9249      (clobber (match_scratch:SI 3 ""))
9250      (clobber (match_scratch:SI 4 ""))
9251      (clobber (reg:CC CC_REGNUM))])]
9252  ""
9253  ""
9254)
9255
9256;; Use a separate insn from the above expand to be able to have the mem outside
9257;; the operand #1 when register allocation comes. This is needed to avoid LRA
9258;; try to reload the guard since we need to control how PIC access is done in
9259;; the -fpic/-fPIC case (see COMPUTE_NOW parameter when calling
9260;; legitimize_pic_address ()).
9261(define_insn_and_split "*stack_protect_combined_test_insn"
9262  [(set (pc)
9263	(if_then_else
9264		(eq (match_operand:SI 0 "memory_operand" "m,m")
9265		    (unspec:SI [(mem:SI (match_operand:SI 1 "guard_addr_operand" "X,X"))]
9266			       UNSPEC_SP_TEST))
9267		(label_ref (match_operand 2))
9268		(pc)))
9269   (clobber (match_scratch:SI 3 "=&l,&r"))
9270   (clobber (match_scratch:SI 4 "=&l,&r"))
9271   (clobber (reg:CC CC_REGNUM))]
9272  ""
9273  "#"
9274  "reload_completed"
9275  [(const_int 0)]
9276{
9277  rtx eq;
9278
9279  if (flag_pic)
9280    {
9281      rtx pic_reg;
9282
9283      if (TARGET_FDPIC)
9284	  pic_reg = gen_rtx_REG (Pmode, FDPIC_REGNUM);
9285      else
9286	  pic_reg = operands[4];
9287
9288      /* Forces recomputing of GOT base now.  */
9289      legitimize_pic_address (operands[1], SImode, operands[3], pic_reg,
9290			      true /*compute_now*/);
9291    }
9292  else
9293    {
9294      if (address_operand (operands[1], SImode))
9295	operands[3] = operands[1];
9296      else
9297	{
9298	  rtx mem = XEXP (force_const_mem (SImode, operands[1]), 0);
9299	  emit_move_insn (operands[3], mem);
9300	}
9301    }
9302  if (TARGET_32BIT)
9303    {
9304      emit_insn (gen_arm_stack_protect_test_insn (operands[4], operands[0],
9305						  operands[3]));
9306      rtx cc_reg = gen_rtx_REG (CC_Zmode, CC_REGNUM);
9307      eq = gen_rtx_EQ (CC_Zmode, cc_reg, const0_rtx);
9308      emit_jump_insn (gen_arm_cond_branch (operands[2], eq, cc_reg));
9309    }
9310  else
9311    {
9312      emit_insn (gen_thumb1_stack_protect_test_insn (operands[4], operands[0],
9313						     operands[3]));
9314      eq = gen_rtx_EQ (VOIDmode, operands[4], const0_rtx);
9315      emit_jump_insn (gen_cbranchsi4 (eq, operands[4], const0_rtx,
9316				      operands[2]));
9317    }
9318  DONE;
9319}
9320  [(set_attr "arch" "t1,32")]
9321)
9322
9323(define_insn "arm_stack_protect_test_insn"
9324  [(set (reg:CC_Z CC_REGNUM)
9325	(compare:CC_Z (unspec:SI [(match_operand:SI 1 "memory_operand" "m,m")
9326				  (mem:SI (match_operand:SI 2 "register_operand" "+l,r"))]
9327				 UNSPEC_SP_TEST)
9328		      (const_int 0)))
9329   (clobber (match_operand:SI 0 "register_operand" "=&l,&r"))
9330   (clobber (match_dup 2))]
9331  "TARGET_32BIT"
9332  "ldr\t%0, [%2]\;ldr\t%2, %1\;eors\t%0, %2, %0"
9333  [(set_attr "length" "8,12")
9334   (set_attr "conds" "set")
9335   (set_attr "type" "multiple")
9336   (set_attr "arch" "t,32")]
9337)
9338
9339(define_expand "casesi"
9340  [(match_operand:SI 0 "s_register_operand")	; index to jump on
9341   (match_operand:SI 1 "const_int_operand")	; lower bound
9342   (match_operand:SI 2 "const_int_operand")	; total range
9343   (match_operand:SI 3 "" "")			; table label
9344   (match_operand:SI 4 "" "")]			; Out of range label
9345  "(TARGET_32BIT || optimize_size || flag_pic) && !target_pure_code"
9346  "
9347  {
9348    enum insn_code code;
9349    if (operands[1] != const0_rtx)
9350      {
9351	rtx reg = gen_reg_rtx (SImode);
9352
9353	emit_insn (gen_addsi3 (reg, operands[0],
9354			       gen_int_mode (-INTVAL (operands[1]),
9355			       		     SImode)));
9356	operands[0] = reg;
9357      }
9358
9359    if (TARGET_ARM)
9360      code = CODE_FOR_arm_casesi_internal;
9361    else if (TARGET_THUMB1)
9362      code = CODE_FOR_thumb1_casesi_internal_pic;
9363    else if (flag_pic)
9364      code = CODE_FOR_thumb2_casesi_internal_pic;
9365    else
9366      code = CODE_FOR_thumb2_casesi_internal;
9367
9368    if (!insn_data[(int) code].operand[1].predicate(operands[2], SImode))
9369      operands[2] = force_reg (SImode, operands[2]);
9370
9371    emit_jump_insn (GEN_FCN ((int) code) (operands[0], operands[2],
9372					  operands[3], operands[4]));
9373    DONE;
9374  }"
9375)
9376
9377;; The USE in this pattern is needed to tell flow analysis that this is
9378;; a CASESI insn.  It has no other purpose.
9379(define_expand "arm_casesi_internal"
9380  [(parallel [(set (pc)
9381	       (if_then_else
9382		(leu (match_operand:SI 0 "s_register_operand")
9383		     (match_operand:SI 1 "arm_rhs_operand"))
9384		(match_dup 4)
9385		(label_ref:SI (match_operand 3 ""))))
9386	      (clobber (reg:CC CC_REGNUM))
9387	      (use (label_ref:SI (match_operand 2 "")))])]
9388  "TARGET_ARM"
9389{
9390  operands[4] = gen_rtx_MULT (SImode, operands[0], GEN_INT (4));
9391  operands[4] = gen_rtx_PLUS (SImode, operands[4],
9392			      gen_rtx_LABEL_REF (SImode, operands[2]));
9393  operands[4] = gen_rtx_MEM (SImode, operands[4]);
9394  MEM_READONLY_P (operands[4]) = 1;
9395  MEM_NOTRAP_P (operands[4]) = 1;
9396})
9397
9398(define_insn "*arm_casesi_internal"
9399  [(parallel [(set (pc)
9400	       (if_then_else
9401		(leu (match_operand:SI 0 "s_register_operand" "r")
9402		     (match_operand:SI 1 "arm_rhs_operand" "rI"))
9403		(mem:SI (plus:SI (mult:SI (match_dup 0) (const_int 4))
9404				 (label_ref:SI (match_operand 2 "" ""))))
9405		(label_ref:SI (match_operand 3 "" ""))))
9406	      (clobber (reg:CC CC_REGNUM))
9407	      (use (label_ref:SI (match_dup 2)))])]
9408  "TARGET_ARM"
9409  "*
9410    if (flag_pic)
9411      return \"cmp\\t%0, %1\;addls\\t%|pc, %|pc, %0, asl #2\;b\\t%l3\";
9412    return   \"cmp\\t%0, %1\;ldrls\\t%|pc, [%|pc, %0, asl #2]\;b\\t%l3\";
9413  "
9414  [(set_attr "conds" "clob")
9415   (set_attr "length" "12")
9416   (set_attr "type" "multiple")]
9417)
9418
9419(define_expand "indirect_jump"
9420  [(set (pc)
9421	(match_operand:SI 0 "s_register_operand"))]
9422  "TARGET_EITHER"
9423  "
9424  /* Thumb-2 doesn't have mov pc, reg.  Explicitly set the low bit of the
9425     address and use bx.  */
9426  if (TARGET_THUMB2)
9427    {
9428      rtx tmp;
9429      tmp = gen_reg_rtx (SImode);
9430      emit_insn (gen_iorsi3 (tmp, operands[0], GEN_INT(1)));
9431      operands[0] = tmp;
9432    }
9433  "
9434)
9435
9436;; NB Never uses BX.
9437(define_insn "*arm_indirect_jump"
9438  [(set (pc)
9439	(match_operand:SI 0 "s_register_operand" "r"))]
9440  "TARGET_ARM"
9441  "mov%?\\t%|pc, %0\\t%@ indirect register jump"
9442  [(set_attr "predicable" "yes")
9443   (set_attr "type" "branch")]
9444)
9445
9446(define_insn "*load_indirect_jump"
9447  [(set (pc)
9448	(match_operand:SI 0 "memory_operand" "m"))]
9449  "TARGET_ARM"
9450  "ldr%?\\t%|pc, %0\\t%@ indirect memory jump"
9451  [(set_attr "type" "load_4")
9452   (set_attr "pool_range" "4096")
9453   (set_attr "neg_pool_range" "4084")
9454   (set_attr "predicable" "yes")]
9455)
9456
9457
9458;; Misc insns
9459
9460(define_insn "nop"
9461  [(const_int 0)]
9462  "TARGET_EITHER"
9463  "nop"
9464  [(set (attr "length")
9465	(if_then_else (eq_attr "is_thumb" "yes")
9466		      (const_int 2)
9467		      (const_int 4)))
9468   (set_attr "type" "mov_reg")]
9469)
9470
9471(define_insn "trap"
9472  [(trap_if (const_int 1) (const_int 0))]
9473  ""
9474  "*
9475  if (TARGET_ARM)
9476    return \".inst\\t0xe7f000f0\";
9477  else
9478    return \".inst\\t0xdeff\";
9479  "
9480  [(set (attr "length")
9481	(if_then_else (eq_attr "is_thumb" "yes")
9482		      (const_int 2)
9483		      (const_int 4)))
9484   (set_attr "type" "trap")
9485   (set_attr "conds" "unconditional")]
9486)
9487
9488
9489;; Patterns to allow combination of arithmetic, cond code and shifts
9490
9491(define_insn "*<arith_shift_insn>_multsi"
9492  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9493	(SHIFTABLE_OPS:SI
9494	 (mult:SI (match_operand:SI 2 "s_register_operand" "r,r")
9495		  (match_operand:SI 3 "power_of_two_operand" ""))
9496	 (match_operand:SI 1 "s_register_operand" "rk,<t2_binop0>")))]
9497  "TARGET_32BIT"
9498  "<arith_shift_insn>%?\\t%0, %1, %2, lsl %b3"
9499  [(set_attr "predicable" "yes")
9500   (set_attr "shift" "2")
9501   (set_attr "arch" "a,t2")
9502   (set_attr "type" "alu_shift_imm")])
9503
9504(define_insn "*<arith_shift_insn>_shiftsi"
9505  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9506	(SHIFTABLE_OPS:SI
9507	 (match_operator:SI 2 "shift_nomul_operator"
9508	  [(match_operand:SI 3 "s_register_operand" "r,r,r")
9509	   (match_operand:SI 4 "shift_amount_operand" "M,M,r")])
9510	 (match_operand:SI 1 "s_register_operand" "rk,<t2_binop0>,rk")))]
9511  "TARGET_32BIT && GET_CODE (operands[2]) != MULT"
9512  "<arith_shift_insn>%?\\t%0, %1, %3%S2"
9513  [(set_attr "predicable" "yes")
9514   (set_attr "shift" "3")
9515   (set_attr "arch" "a,t2,a")
9516   (set_attr "type" "alu_shift_imm,alu_shift_imm,alu_shift_reg")])
9517
9518(define_split
9519  [(set (match_operand:SI 0 "s_register_operand" "")
9520	(match_operator:SI 1 "shiftable_operator"
9521	 [(match_operator:SI 2 "shiftable_operator"
9522	   [(match_operator:SI 3 "shift_operator"
9523	     [(match_operand:SI 4 "s_register_operand" "")
9524	      (match_operand:SI 5 "reg_or_int_operand" "")])
9525	    (match_operand:SI 6 "s_register_operand" "")])
9526	  (match_operand:SI 7 "arm_rhs_operand" "")]))
9527   (clobber (match_operand:SI 8 "s_register_operand" ""))]
9528  "TARGET_32BIT"
9529  [(set (match_dup 8)
9530	(match_op_dup 2 [(match_op_dup 3 [(match_dup 4) (match_dup 5)])
9531			 (match_dup 6)]))
9532   (set (match_dup 0)
9533	(match_op_dup 1 [(match_dup 8) (match_dup 7)]))]
9534  "")
9535
9536(define_insn "*arith_shiftsi_compare0"
9537  [(set (reg:CC_NZ CC_REGNUM)
9538        (compare:CC_NZ
9539	 (match_operator:SI 1 "shiftable_operator"
9540	  [(match_operator:SI 3 "shift_operator"
9541	    [(match_operand:SI 4 "s_register_operand" "r,r")
9542	     (match_operand:SI 5 "shift_amount_operand" "M,r")])
9543	   (match_operand:SI 2 "s_register_operand" "r,r")])
9544	 (const_int 0)))
9545   (set (match_operand:SI 0 "s_register_operand" "=r,r")
9546	(match_op_dup 1 [(match_op_dup 3 [(match_dup 4) (match_dup 5)])
9547			 (match_dup 2)]))]
9548  "TARGET_32BIT"
9549  "%i1s%?\\t%0, %2, %4%S3"
9550  [(set_attr "conds" "set")
9551   (set_attr "shift" "4")
9552   (set_attr "arch" "32,a")
9553   (set_attr "type" "alus_shift_imm,alus_shift_reg")])
9554
9555(define_insn "*arith_shiftsi_compare0_scratch"
9556  [(set (reg:CC_NZ CC_REGNUM)
9557        (compare:CC_NZ
9558	 (match_operator:SI 1 "shiftable_operator"
9559	  [(match_operator:SI 3 "shift_operator"
9560	    [(match_operand:SI 4 "s_register_operand" "r,r")
9561	     (match_operand:SI 5 "shift_amount_operand" "M,r")])
9562	   (match_operand:SI 2 "s_register_operand" "r,r")])
9563	 (const_int 0)))
9564   (clobber (match_scratch:SI 0 "=r,r"))]
9565  "TARGET_32BIT"
9566  "%i1s%?\\t%0, %2, %4%S3"
9567  [(set_attr "conds" "set")
9568   (set_attr "shift" "4")
9569   (set_attr "arch" "32,a")
9570   (set_attr "type" "alus_shift_imm,alus_shift_reg")])
9571
9572(define_insn "*sub_shiftsi"
9573  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9574	(minus:SI (match_operand:SI 1 "s_register_operand" "r,r")
9575		  (match_operator:SI 2 "shift_operator"
9576		   [(match_operand:SI 3 "s_register_operand" "r,r")
9577		    (match_operand:SI 4 "shift_amount_operand" "M,r")])))]
9578  "TARGET_32BIT"
9579  "sub%?\\t%0, %1, %3%S2"
9580  [(set_attr "predicable" "yes")
9581   (set_attr "predicable_short_it" "no")
9582   (set_attr "shift" "3")
9583   (set_attr "arch" "32,a")
9584   (set_attr "type" "alus_shift_imm,alus_shift_reg")])
9585
9586(define_insn "*sub_shiftsi_compare0"
9587  [(set (reg:CC_NZ CC_REGNUM)
9588	(compare:CC_NZ
9589	 (minus:SI (match_operand:SI 1 "s_register_operand" "r,r")
9590		   (match_operator:SI 2 "shift_operator"
9591		    [(match_operand:SI 3 "s_register_operand" "r,r")
9592		     (match_operand:SI 4 "shift_amount_operand" "M,r")]))
9593	 (const_int 0)))
9594   (set (match_operand:SI 0 "s_register_operand" "=r,r")
9595	(minus:SI (match_dup 1)
9596		  (match_op_dup 2 [(match_dup 3) (match_dup 4)])))]
9597  "TARGET_32BIT"
9598  "subs%?\\t%0, %1, %3%S2"
9599  [(set_attr "conds" "set")
9600   (set_attr "shift" "3")
9601   (set_attr "arch" "32,a")
9602   (set_attr "type" "alus_shift_imm,alus_shift_reg")])
9603
9604(define_insn "*sub_shiftsi_compare0_scratch"
9605  [(set (reg:CC_NZ CC_REGNUM)
9606	(compare:CC_NZ
9607	 (minus:SI (match_operand:SI 1 "s_register_operand" "r,r")
9608		   (match_operator:SI 2 "shift_operator"
9609		    [(match_operand:SI 3 "s_register_operand" "r,r")
9610		     (match_operand:SI 4 "shift_amount_operand" "M,r")]))
9611	 (const_int 0)))
9612   (clobber (match_scratch:SI 0 "=r,r"))]
9613  "TARGET_32BIT"
9614  "subs%?\\t%0, %1, %3%S2"
9615  [(set_attr "conds" "set")
9616   (set_attr "shift" "3")
9617   (set_attr "arch" "32,a")
9618   (set_attr "type" "alus_shift_imm,alus_shift_reg")])
9619
9620
9621(define_insn_and_split "*and_scc"
9622  [(set (match_operand:SI 0 "s_register_operand" "=r")
9623	(and:SI (match_operator:SI 1 "arm_comparison_operator"
9624		 [(match_operand 2 "cc_register" "") (const_int 0)])
9625		(match_operand:SI 3 "s_register_operand" "r")))]
9626  "TARGET_ARM"
9627  "#"   ; "mov%D1\\t%0, #0\;and%d1\\t%0, %3, #1"
9628  "&& reload_completed"
9629  [(cond_exec (match_dup 5) (set (match_dup 0) (const_int 0)))
9630   (cond_exec (match_dup 4) (set (match_dup 0)
9631                                 (and:SI (match_dup 3) (const_int 1))))]
9632  {
9633    machine_mode mode = GET_MODE (operands[2]);
9634    enum rtx_code rc = GET_CODE (operands[1]);
9635
9636    /* Note that operands[4] is the same as operands[1],
9637       but with VOIDmode as the result. */
9638    operands[4] = gen_rtx_fmt_ee (rc, VOIDmode, operands[2], const0_rtx);
9639    if (mode == CCFPmode || mode == CCFPEmode)
9640      rc = reverse_condition_maybe_unordered (rc);
9641    else
9642      rc = reverse_condition (rc);
9643    operands[5] = gen_rtx_fmt_ee (rc, VOIDmode, operands[2], const0_rtx);
9644  }
9645  [(set_attr "conds" "use")
9646   (set_attr "type" "multiple")
9647   (set_attr "length" "8")]
9648)
9649
9650(define_insn_and_split "*ior_scc"
9651  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9652	(ior:SI (match_operator:SI 1 "arm_comparison_operator"
9653		 [(match_operand 2 "cc_register" "") (const_int 0)])
9654		(match_operand:SI 3 "s_register_operand" "0,?r")))]
9655  "TARGET_ARM"
9656  "@
9657   orr%d1\\t%0, %3, #1
9658   #"
9659  "&& reload_completed
9660   && REGNO (operands [0]) != REGNO (operands[3])"
9661  ;; && which_alternative == 1
9662  ; mov%D1\\t%0, %3\;orr%d1\\t%0, %3, #1
9663  [(cond_exec (match_dup 5) (set (match_dup 0) (match_dup 3)))
9664   (cond_exec (match_dup 4) (set (match_dup 0)
9665                                 (ior:SI (match_dup 3) (const_int 1))))]
9666  {
9667    machine_mode mode = GET_MODE (operands[2]);
9668    enum rtx_code rc = GET_CODE (operands[1]);
9669
9670    /* Note that operands[4] is the same as operands[1],
9671       but with VOIDmode as the result. */
9672    operands[4] = gen_rtx_fmt_ee (rc, VOIDmode, operands[2], const0_rtx);
9673    if (mode == CCFPmode || mode == CCFPEmode)
9674      rc = reverse_condition_maybe_unordered (rc);
9675    else
9676      rc = reverse_condition (rc);
9677    operands[5] = gen_rtx_fmt_ee (rc, VOIDmode, operands[2], const0_rtx);
9678  }
9679  [(set_attr "conds" "use")
9680   (set_attr "length" "4,8")
9681   (set_attr "type" "logic_imm,multiple")]
9682)
9683
9684; A series of splitters for the compare_scc pattern below.  Note that
9685; order is important.
9686(define_split
9687  [(set (match_operand:SI 0 "s_register_operand" "")
9688	(lt:SI (match_operand:SI 1 "s_register_operand" "")
9689	       (const_int 0)))
9690   (clobber (reg:CC CC_REGNUM))]
9691  "TARGET_32BIT && reload_completed"
9692  [(set (match_dup 0) (lshiftrt:SI (match_dup 1) (const_int 31)))])
9693
9694(define_split
9695  [(set (match_operand:SI 0 "s_register_operand" "")
9696	(ge:SI (match_operand:SI 1 "s_register_operand" "")
9697	       (const_int 0)))
9698   (clobber (reg:CC CC_REGNUM))]
9699  "TARGET_32BIT && reload_completed"
9700  [(set (match_dup 0) (not:SI (match_dup 1)))
9701   (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 31)))])
9702
9703(define_split
9704  [(set (match_operand:SI 0 "s_register_operand" "")
9705	(eq:SI (match_operand:SI 1 "s_register_operand" "")
9706	       (const_int 0)))
9707   (clobber (reg:CC CC_REGNUM))]
9708  "arm_arch5t && TARGET_32BIT"
9709  [(set (match_dup 0) (clz:SI (match_dup 1)))
9710   (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 5)))]
9711)
9712
9713(define_split
9714  [(set (match_operand:SI 0 "s_register_operand" "")
9715	(eq:SI (match_operand:SI 1 "s_register_operand" "")
9716	       (const_int 0)))
9717   (clobber (reg:CC CC_REGNUM))]
9718  "TARGET_32BIT && reload_completed"
9719  [(parallel
9720    [(set (reg:CC CC_REGNUM)
9721	  (compare:CC (const_int 1) (match_dup 1)))
9722     (set (match_dup 0)
9723	  (minus:SI (const_int 1) (match_dup 1)))])
9724   (cond_exec (ltu:CC (reg:CC CC_REGNUM) (const_int 0))
9725	      (set (match_dup 0) (const_int 0)))])
9726
9727(define_split
9728  [(set (match_operand:SI 0 "s_register_operand" "")
9729	(ne:SI (match_operand:SI 1 "s_register_operand" "")
9730	       (match_operand:SI 2 "const_int_operand" "")))
9731   (clobber (reg:CC CC_REGNUM))]
9732  "TARGET_32BIT && reload_completed"
9733  [(parallel
9734    [(set (reg:CC CC_REGNUM)
9735	  (compare:CC (match_dup 1) (match_dup 2)))
9736     (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 3)))])
9737   (cond_exec (ne:CC (reg:CC CC_REGNUM) (const_int 0))
9738	      (set (match_dup 0) (const_int 1)))]
9739{
9740  operands[3] = gen_int_mode (-INTVAL (operands[2]), SImode);
9741})
9742
9743(define_split
9744  [(set (match_operand:SI 0 "s_register_operand" "")
9745	(ne:SI (match_operand:SI 1 "s_register_operand" "")
9746	       (match_operand:SI 2 "arm_add_operand" "")))
9747   (clobber (reg:CC CC_REGNUM))]
9748  "TARGET_32BIT && reload_completed"
9749  [(parallel
9750    [(set (reg:CC_NZ CC_REGNUM)
9751	  (compare:CC_NZ (minus:SI (match_dup 1) (match_dup 2))
9752			   (const_int 0)))
9753     (set (match_dup 0) (minus:SI (match_dup 1) (match_dup 2)))])
9754   (cond_exec (ne:CC_NZ (reg:CC_NZ CC_REGNUM) (const_int 0))
9755	      (set (match_dup 0) (const_int 1)))])
9756
9757(define_insn_and_split "*compare_scc"
9758  [(set (match_operand:SI 0 "s_register_operand" "=Ts,Ts")
9759	(match_operator:SI 1 "arm_comparison_operator"
9760	 [(match_operand:SI 2 "s_register_operand" "r,r")
9761	  (match_operand:SI 3 "arm_add_operand" "rI,L")]))
9762   (clobber (reg:CC CC_REGNUM))]
9763  "TARGET_32BIT"
9764  "#"
9765  "&& reload_completed"
9766  [(set (reg:CC CC_REGNUM) (compare:CC (match_dup 2) (match_dup 3)))
9767   (cond_exec (match_dup 4) (set (match_dup 0) (const_int 0)))
9768   (cond_exec (match_dup 5) (set (match_dup 0) (const_int 1)))]
9769{
9770  rtx tmp1;
9771  machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
9772					   operands[2], operands[3]);
9773  enum rtx_code rc = GET_CODE (operands[1]);
9774
9775  tmp1 = gen_rtx_REG (mode, CC_REGNUM);
9776
9777  operands[5] = gen_rtx_fmt_ee (rc, VOIDmode, tmp1, const0_rtx);
9778  if (mode == CCFPmode || mode == CCFPEmode)
9779    rc = reverse_condition_maybe_unordered (rc);
9780  else
9781    rc = reverse_condition (rc);
9782  operands[4] = gen_rtx_fmt_ee (rc, VOIDmode, tmp1, const0_rtx);
9783}
9784  [(set_attr "type" "multiple")]
9785)
9786
9787;; Attempt to improve the sequence generated by the compare_scc splitters
9788;; not to use conditional execution.
9789
9790;; Rd = (eq (reg1) (const_int0))  // ARMv5
9791;;	clz Rd, reg1
9792;;	lsr Rd, Rd, #5
9793(define_peephole2
9794  [(set (reg:CC CC_REGNUM)
9795	(compare:CC (match_operand:SI 1 "register_operand" "")
9796		    (const_int 0)))
9797   (cond_exec (ne (reg:CC CC_REGNUM) (const_int 0))
9798	      (set (match_operand:SI 0 "register_operand" "") (const_int 0)))
9799   (cond_exec (eq (reg:CC CC_REGNUM) (const_int 0))
9800	      (set (match_dup 0) (const_int 1)))]
9801  "arm_arch5t && TARGET_32BIT && peep2_regno_dead_p (3, CC_REGNUM)"
9802  [(set (match_dup 0) (clz:SI (match_dup 1)))
9803   (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 5)))]
9804)
9805
9806;; Rd = (eq (reg1) (const_int0))  // !ARMv5
9807;;	negs Rd, reg1
9808;;	adc  Rd, Rd, reg1
9809(define_peephole2
9810  [(set (reg:CC CC_REGNUM)
9811	(compare:CC (match_operand:SI 1 "register_operand" "")
9812		    (const_int 0)))
9813   (cond_exec (ne (reg:CC CC_REGNUM) (const_int 0))
9814	      (set (match_operand:SI 0 "register_operand" "") (const_int 0)))
9815   (cond_exec (eq (reg:CC CC_REGNUM) (const_int 0))
9816	      (set (match_dup 0) (const_int 1)))
9817   (match_scratch:SI 2 "r")]
9818  "TARGET_32BIT && peep2_regno_dead_p (3, CC_REGNUM)"
9819  [(parallel
9820    [(set (reg:CC CC_REGNUM)
9821	  (compare:CC (const_int 0) (match_dup 1)))
9822     (set (match_dup 2) (minus:SI (const_int 0) (match_dup 1)))])
9823   (set (match_dup 0)
9824	(plus:SI (plus:SI (match_dup 1) (match_dup 2))
9825		 (geu:SI (reg:CC CC_REGNUM) (const_int 0))))]
9826)
9827
9828;; Rd = (eq (reg1) (reg2/imm))	// ARMv5 and optimising for speed.
9829;;	sub  Rd, Reg1, reg2
9830;;	clz  Rd, Rd
9831;;	lsr  Rd, Rd, #5
9832(define_peephole2
9833  [(set (reg:CC CC_REGNUM)
9834	(compare:CC (match_operand:SI 1 "register_operand" "")
9835		    (match_operand:SI 2 "arm_rhs_operand" "")))
9836   (cond_exec (ne (reg:CC CC_REGNUM) (const_int 0))
9837	      (set (match_operand:SI 0 "register_operand" "") (const_int 0)))
9838   (cond_exec (eq (reg:CC CC_REGNUM) (const_int 0))
9839	      (set (match_dup 0) (const_int 1)))]
9840  "arm_arch5t && TARGET_32BIT && peep2_regno_dead_p (3, CC_REGNUM)
9841  && !(TARGET_THUMB2 && optimize_insn_for_size_p ())"
9842  [(set (match_dup 0) (minus:SI (match_dup 1) (match_dup 2)))
9843   (set (match_dup 0) (clz:SI (match_dup 0)))
9844   (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 5)))]
9845)
9846
9847
9848;; Rd = (eq (reg1) (reg2))	// ! ARMv5 or optimising for size.
9849;;	sub  T1, Reg1, reg2
9850;;	negs Rd, T1
9851;;	adc  Rd, Rd, T1
9852(define_peephole2
9853  [(set (reg:CC CC_REGNUM)
9854	(compare:CC (match_operand:SI 1 "register_operand" "")
9855		    (match_operand:SI 2 "arm_rhs_operand" "")))
9856   (cond_exec (ne (reg:CC CC_REGNUM) (const_int 0))
9857	      (set (match_operand:SI 0 "register_operand" "") (const_int 0)))
9858   (cond_exec (eq (reg:CC CC_REGNUM) (const_int 0))
9859	      (set (match_dup 0) (const_int 1)))
9860   (match_scratch:SI 3 "r")]
9861  "TARGET_32BIT && peep2_regno_dead_p (3, CC_REGNUM)"
9862  [(set (match_dup 3) (match_dup 4))
9863   (parallel
9864    [(set (reg:CC CC_REGNUM)
9865	  (compare:CC (const_int 0) (match_dup 3)))
9866     (set (match_dup 0) (minus:SI (const_int 0) (match_dup 3)))])
9867   (set (match_dup 0)
9868	(plus:SI (plus:SI (match_dup 0) (match_dup 3))
9869		 (geu:SI (reg:CC CC_REGNUM) (const_int 0))))]
9870  "
9871  if (CONST_INT_P (operands[2]))
9872    operands[4] = plus_constant (SImode, operands[1], -INTVAL (operands[2]));
9873  else
9874    operands[4] = gen_rtx_MINUS (SImode, operands[1], operands[2]);
9875  ")
9876
9877(define_insn "*cond_move"
9878  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9879	(if_then_else:SI (match_operator 3 "equality_operator"
9880			  [(match_operator 4 "arm_comparison_operator"
9881			    [(match_operand 5 "cc_register" "") (const_int 0)])
9882			   (const_int 0)])
9883			 (match_operand:SI 1 "arm_rhs_operand" "0,rI,?rI")
9884			 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))]
9885  "TARGET_ARM"
9886  "*
9887    if (GET_CODE (operands[3]) == NE)
9888      {
9889        if (which_alternative != 1)
9890	  output_asm_insn (\"mov%D4\\t%0, %2\", operands);
9891        if (which_alternative != 0)
9892	  output_asm_insn (\"mov%d4\\t%0, %1\", operands);
9893        return \"\";
9894      }
9895    if (which_alternative != 0)
9896      output_asm_insn (\"mov%D4\\t%0, %1\", operands);
9897    if (which_alternative != 1)
9898      output_asm_insn (\"mov%d4\\t%0, %2\", operands);
9899    return \"\";
9900  "
9901  [(set_attr "conds" "use")
9902   (set_attr_alternative "type"
9903                         [(if_then_else (match_operand 2 "const_int_operand" "")
9904                                        (const_string "mov_imm")
9905                                        (const_string "mov_reg"))
9906                          (if_then_else (match_operand 1 "const_int_operand" "")
9907                                        (const_string "mov_imm")
9908                                        (const_string "mov_reg"))
9909                          (const_string "multiple")])
9910   (set_attr "length" "4,4,8")]
9911)
9912
9913(define_insn "*cond_arith"
9914  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9915        (match_operator:SI 5 "shiftable_operator"
9916	 [(match_operator:SI 4 "arm_comparison_operator"
9917           [(match_operand:SI 2 "s_register_operand" "r,r")
9918	    (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
9919          (match_operand:SI 1 "s_register_operand" "0,?r")]))
9920   (clobber (reg:CC CC_REGNUM))]
9921  "TARGET_ARM"
9922  "*
9923    if (GET_CODE (operands[4]) == LT && operands[3] == const0_rtx)
9924      return \"%i5\\t%0, %1, %2, lsr #31\";
9925
9926    output_asm_insn (\"cmp\\t%2, %3\", operands);
9927    if (GET_CODE (operands[5]) == AND)
9928      output_asm_insn (\"mov%D4\\t%0, #0\", operands);
9929    else if (GET_CODE (operands[5]) == MINUS)
9930      output_asm_insn (\"rsb%D4\\t%0, %1, #0\", operands);
9931    else if (which_alternative != 0)
9932      output_asm_insn (\"mov%D4\\t%0, %1\", operands);
9933    return \"%i5%d4\\t%0, %1, #1\";
9934  "
9935  [(set_attr "conds" "clob")
9936   (set_attr "length" "12")
9937   (set_attr "type" "multiple")]
9938)
9939
9940(define_insn "*cond_sub"
9941  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9942        (minus:SI (match_operand:SI 1 "s_register_operand" "0,?r")
9943		  (match_operator:SI 4 "arm_comparison_operator"
9944                   [(match_operand:SI 2 "s_register_operand" "r,r")
9945		    (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))
9946   (clobber (reg:CC CC_REGNUM))]
9947  "TARGET_ARM"
9948  "*
9949    output_asm_insn (\"cmp\\t%2, %3\", operands);
9950    if (which_alternative != 0)
9951      output_asm_insn (\"mov%D4\\t%0, %1\", operands);
9952    return \"sub%d4\\t%0, %1, #1\";
9953  "
9954  [(set_attr "conds" "clob")
9955   (set_attr "length" "8,12")
9956   (set_attr "type" "multiple")]
9957)
9958
9959(define_insn "*cmp_ite0"
9960  [(set (match_operand 6 "dominant_cc_register" "")
9961	(compare
9962	 (if_then_else:SI
9963	  (match_operator 4 "arm_comparison_operator"
9964	   [(match_operand:SI 0 "s_register_operand"
9965	        "l,l,l,r,r,r,r,r,r")
9966	    (match_operand:SI 1 "arm_add_operand"
9967	        "lPy,lPy,lPy,rI,L,rI,L,rI,L")])
9968	  (match_operator:SI 5 "arm_comparison_operator"
9969	   [(match_operand:SI 2 "s_register_operand"
9970	        "l,r,r,l,l,r,r,r,r")
9971	    (match_operand:SI 3 "arm_add_operand"
9972	        "lPy,rI,L,lPy,lPy,rI,rI,L,L")])
9973	  (const_int 0))
9974	 (const_int 0)))]
9975  "TARGET_32BIT"
9976  "*
9977  {
9978    static const char * const cmp1[NUM_OF_COND_CMP][2] =
9979    {
9980      {\"cmp%d5\\t%0, %1\",
9981       \"cmp%d4\\t%2, %3\"},
9982      {\"cmn%d5\\t%0, #%n1\",
9983       \"cmp%d4\\t%2, %3\"},
9984      {\"cmp%d5\\t%0, %1\",
9985       \"cmn%d4\\t%2, #%n3\"},
9986      {\"cmn%d5\\t%0, #%n1\",
9987       \"cmn%d4\\t%2, #%n3\"}
9988    };
9989    static const char * const cmp2[NUM_OF_COND_CMP][2] =
9990    {
9991      {\"cmp\\t%2, %3\",
9992       \"cmp\\t%0, %1\"},
9993      {\"cmp\\t%2, %3\",
9994       \"cmn\\t%0, #%n1\"},
9995      {\"cmn\\t%2, #%n3\",
9996       \"cmp\\t%0, %1\"},
9997      {\"cmn\\t%2, #%n3\",
9998       \"cmn\\t%0, #%n1\"}
9999    };
10000    static const char * const ite[2] =
10001    {
10002      \"it\\t%d5\",
10003      \"it\\t%d4\"
10004    };
10005    static const int cmp_idx[9] = {CMP_CMP, CMP_CMP, CMP_CMN,
10006                                   CMP_CMP, CMN_CMP, CMP_CMP,
10007                                   CMN_CMP, CMP_CMN, CMN_CMN};
10008    int swap =
10009      comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
10010
10011    output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
10012    if (TARGET_THUMB2) {
10013      output_asm_insn (ite[swap], operands);
10014    }
10015    output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
10016    return \"\";
10017  }"
10018  [(set_attr "conds" "set")
10019   (set_attr "arch" "t2,t2,t2,t2,t2,any,any,any,any")
10020   (set_attr "enabled_for_short_it" "yes,no,no,no,no,no,no,no,no")
10021   (set_attr "type" "multiple")
10022   (set_attr_alternative "length"
10023      [(const_int 6)
10024       (const_int 8)
10025       (const_int 8)
10026       (const_int 8)
10027       (const_int 8)
10028       (if_then_else (eq_attr "is_thumb" "no")
10029           (const_int 8)
10030           (const_int 10))
10031       (if_then_else (eq_attr "is_thumb" "no")
10032           (const_int 8)
10033           (const_int 10))
10034       (if_then_else (eq_attr "is_thumb" "no")
10035           (const_int 8)
10036           (const_int 10))
10037       (if_then_else (eq_attr "is_thumb" "no")
10038           (const_int 8)
10039           (const_int 10))])]
10040)
10041
10042(define_insn "*cmp_ite1"
10043  [(set (match_operand 6 "dominant_cc_register" "")
10044	(compare
10045	 (if_then_else:SI
10046	  (match_operator 4 "arm_comparison_operator"
10047	   [(match_operand:SI 0 "s_register_operand"
10048	        "l,l,l,r,r,r,r,r,r")
10049	    (match_operand:SI 1 "arm_add_operand"
10050	        "lPy,lPy,lPy,rI,L,rI,L,rI,L")])
10051	  (match_operator:SI 5 "arm_comparison_operator"
10052	   [(match_operand:SI 2 "s_register_operand"
10053	        "l,r,r,l,l,r,r,r,r")
10054	    (match_operand:SI 3 "arm_add_operand"
10055	        "lPy,rI,L,lPy,lPy,rI,rI,L,L")])
10056	  (const_int 1))
10057	 (const_int 0)))]
10058  "TARGET_32BIT"
10059  "*
10060  {
10061    static const char * const cmp1[NUM_OF_COND_CMP][2] =
10062    {
10063      {\"cmp\\t%0, %1\",
10064       \"cmp\\t%2, %3\"},
10065      {\"cmn\\t%0, #%n1\",
10066       \"cmp\\t%2, %3\"},
10067      {\"cmp\\t%0, %1\",
10068       \"cmn\\t%2, #%n3\"},
10069      {\"cmn\\t%0, #%n1\",
10070       \"cmn\\t%2, #%n3\"}
10071    };
10072    static const char * const cmp2[NUM_OF_COND_CMP][2] =
10073    {
10074      {\"cmp%d4\\t%2, %3\",
10075       \"cmp%D5\\t%0, %1\"},
10076      {\"cmp%d4\\t%2, %3\",
10077       \"cmn%D5\\t%0, #%n1\"},
10078      {\"cmn%d4\\t%2, #%n3\",
10079       \"cmp%D5\\t%0, %1\"},
10080      {\"cmn%d4\\t%2, #%n3\",
10081       \"cmn%D5\\t%0, #%n1\"}
10082    };
10083    static const char * const ite[2] =
10084    {
10085      \"it\\t%d4\",
10086      \"it\\t%D5\"
10087    };
10088    static const int cmp_idx[9] = {CMP_CMP, CMP_CMP, CMP_CMN,
10089                                   CMP_CMP, CMN_CMP, CMP_CMP,
10090                                   CMN_CMP, CMP_CMN, CMN_CMN};
10091    int swap =
10092      comparison_dominates_p (GET_CODE (operands[5]),
10093			      reverse_condition (GET_CODE (operands[4])));
10094
10095    output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
10096    if (TARGET_THUMB2) {
10097      output_asm_insn (ite[swap], operands);
10098    }
10099    output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
10100    return \"\";
10101  }"
10102  [(set_attr "conds" "set")
10103   (set_attr "arch" "t2,t2,t2,t2,t2,any,any,any,any")
10104   (set_attr "enabled_for_short_it" "yes,no,no,no,no,no,no,no,no")
10105   (set_attr_alternative "length"
10106      [(const_int 6)
10107       (const_int 8)
10108       (const_int 8)
10109       (const_int 8)
10110       (const_int 8)
10111       (if_then_else (eq_attr "is_thumb" "no")
10112           (const_int 8)
10113           (const_int 10))
10114       (if_then_else (eq_attr "is_thumb" "no")
10115           (const_int 8)
10116           (const_int 10))
10117       (if_then_else (eq_attr "is_thumb" "no")
10118           (const_int 8)
10119           (const_int 10))
10120       (if_then_else (eq_attr "is_thumb" "no")
10121           (const_int 8)
10122           (const_int 10))])
10123   (set_attr "type" "multiple")]
10124)
10125
10126(define_insn "*cmp_and"
10127  [(set (match_operand 6 "dominant_cc_register" "")
10128	(compare
10129	 (and:SI
10130	  (match_operator 4 "arm_comparison_operator"
10131	   [(match_operand:SI 0 "s_register_operand"
10132	        "l,l,l,r,r,r,r,r,r,r")
10133	    (match_operand:SI 1 "arm_add_operand"
10134	        "lPy,lPy,lPy,rI,L,r,rI,L,rI,L")])
10135	  (match_operator:SI 5 "arm_comparison_operator"
10136	   [(match_operand:SI 2 "s_register_operand"
10137	        "l,r,r,l,l,r,r,r,r,r")
10138	    (match_operand:SI 3 "arm_add_operand"
10139	        "lPy,rI,L,lPy,lPy,r,rI,rI,L,L")]))
10140	 (const_int 0)))]
10141  "TARGET_32BIT"
10142  "*
10143  {
10144    static const char *const cmp1[NUM_OF_COND_CMP][2] =
10145    {
10146      {\"cmp%d5\\t%0, %1\",
10147       \"cmp%d4\\t%2, %3\"},
10148      {\"cmn%d5\\t%0, #%n1\",
10149       \"cmp%d4\\t%2, %3\"},
10150      {\"cmp%d5\\t%0, %1\",
10151       \"cmn%d4\\t%2, #%n3\"},
10152      {\"cmn%d5\\t%0, #%n1\",
10153       \"cmn%d4\\t%2, #%n3\"}
10154    };
10155    static const char *const cmp2[NUM_OF_COND_CMP][2] =
10156    {
10157      {\"cmp\\t%2, %3\",
10158       \"cmp\\t%0, %1\"},
10159      {\"cmp\\t%2, %3\",
10160       \"cmn\\t%0, #%n1\"},
10161      {\"cmn\\t%2, #%n3\",
10162       \"cmp\\t%0, %1\"},
10163      {\"cmn\\t%2, #%n3\",
10164       \"cmn\\t%0, #%n1\"}
10165    };
10166    static const char *const ite[2] =
10167    {
10168      \"it\\t%d5\",
10169      \"it\\t%d4\"
10170    };
10171    static const int cmp_idx[] = {CMP_CMP, CMP_CMP, CMP_CMN,
10172                                  CMP_CMP, CMN_CMP, CMP_CMP,
10173                                  CMP_CMP, CMN_CMP, CMP_CMN,
10174				  CMN_CMN};
10175    int swap =
10176      comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
10177
10178    output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
10179    if (TARGET_THUMB2) {
10180      output_asm_insn (ite[swap], operands);
10181    }
10182    output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
10183    return \"\";
10184  }"
10185  [(set_attr "conds" "set")
10186   (set_attr "predicable" "no")
10187   (set_attr "arch" "t2,t2,t2,t2,t2,t2,any,any,any,any")
10188   (set_attr "enabled_for_short_it" "yes,no,no,no,no,yes,no,no,no,no")
10189   (set_attr_alternative "length"
10190      [(const_int 6)
10191       (const_int 8)
10192       (const_int 8)
10193       (const_int 8)
10194       (const_int 8)
10195       (const_int 6)
10196       (if_then_else (eq_attr "is_thumb" "no")
10197           (const_int 8)
10198           (const_int 10))
10199       (if_then_else (eq_attr "is_thumb" "no")
10200           (const_int 8)
10201           (const_int 10))
10202       (if_then_else (eq_attr "is_thumb" "no")
10203           (const_int 8)
10204           (const_int 10))
10205       (if_then_else (eq_attr "is_thumb" "no")
10206           (const_int 8)
10207           (const_int 10))])
10208   (set_attr "type" "multiple")]
10209)
10210
10211(define_insn "*cmp_ior"
10212  [(set (match_operand 6 "dominant_cc_register" "")
10213	(compare
10214	 (ior:SI
10215	  (match_operator 4 "arm_comparison_operator"
10216	   [(match_operand:SI 0 "s_register_operand"
10217	        "l,l,l,r,r,r,r,r,r,r")
10218	    (match_operand:SI 1 "arm_add_operand"
10219	        "lPy,lPy,lPy,rI,L,r,rI,L,rI,L")])
10220	  (match_operator:SI 5 "arm_comparison_operator"
10221	   [(match_operand:SI 2 "s_register_operand"
10222	        "l,r,r,l,l,r,r,r,r,r")
10223	    (match_operand:SI 3 "arm_add_operand"
10224	        "lPy,rI,L,lPy,lPy,r,rI,rI,L,L")]))
10225	 (const_int 0)))]
10226  "TARGET_32BIT"
10227  "*
10228  {
10229    static const char *const cmp1[NUM_OF_COND_CMP][2] =
10230    {
10231      {\"cmp\\t%0, %1\",
10232       \"cmp\\t%2, %3\"},
10233      {\"cmn\\t%0, #%n1\",
10234       \"cmp\\t%2, %3\"},
10235      {\"cmp\\t%0, %1\",
10236       \"cmn\\t%2, #%n3\"},
10237      {\"cmn\\t%0, #%n1\",
10238       \"cmn\\t%2, #%n3\"}
10239    };
10240    static const char *const cmp2[NUM_OF_COND_CMP][2] =
10241    {
10242      {\"cmp%D4\\t%2, %3\",
10243       \"cmp%D5\\t%0, %1\"},
10244      {\"cmp%D4\\t%2, %3\",
10245       \"cmn%D5\\t%0, #%n1\"},
10246      {\"cmn%D4\\t%2, #%n3\",
10247       \"cmp%D5\\t%0, %1\"},
10248      {\"cmn%D4\\t%2, #%n3\",
10249       \"cmn%D5\\t%0, #%n1\"}
10250    };
10251    static const char *const ite[2] =
10252    {
10253      \"it\\t%D4\",
10254      \"it\\t%D5\"
10255    };
10256    static const int cmp_idx[] = {CMP_CMP, CMP_CMP, CMP_CMN,
10257                                  CMP_CMP, CMN_CMP, CMP_CMP,
10258				  CMP_CMP, CMN_CMP, CMP_CMN,
10259				  CMN_CMN};
10260    int swap =
10261      comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
10262
10263    output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
10264    if (TARGET_THUMB2) {
10265      output_asm_insn (ite[swap], operands);
10266    }
10267    output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
10268    return \"\";
10269  }
10270  "
10271  [(set_attr "conds" "set")
10272   (set_attr "arch" "t2,t2,t2,t2,t2,t2,any,any,any,any")
10273   (set_attr "enabled_for_short_it" "yes,no,no,no,no,yes,no,no,no,no")
10274   (set_attr_alternative "length"
10275      [(const_int 6)
10276       (const_int 8)
10277       (const_int 8)
10278       (const_int 8)
10279       (const_int 8)
10280       (const_int 6)
10281       (if_then_else (eq_attr "is_thumb" "no")
10282           (const_int 8)
10283           (const_int 10))
10284       (if_then_else (eq_attr "is_thumb" "no")
10285           (const_int 8)
10286           (const_int 10))
10287       (if_then_else (eq_attr "is_thumb" "no")
10288           (const_int 8)
10289           (const_int 10))
10290       (if_then_else (eq_attr "is_thumb" "no")
10291           (const_int 8)
10292           (const_int 10))])
10293   (set_attr "type" "multiple")]
10294)
10295
10296(define_insn_and_split "*ior_scc_scc"
10297  [(set (match_operand:SI 0 "s_register_operand" "=Ts,Ts")
10298	(ior:SI (match_operator:SI 3 "arm_comparison_operator"
10299		 [(match_operand:SI 1 "s_register_operand" "l,r")
10300		  (match_operand:SI 2 "arm_add_operand" "lPy,rIL")])
10301		(match_operator:SI 6 "arm_comparison_operator"
10302		 [(match_operand:SI 4 "s_register_operand" "l,r")
10303		  (match_operand:SI 5 "arm_add_operand" "lPy,rIL")])))
10304   (clobber (reg:CC CC_REGNUM))]
10305  "TARGET_32BIT
10306   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_OR_Y)
10307       != CCmode)"
10308  "#"
10309  "TARGET_32BIT && reload_completed"
10310  [(set (match_dup 7)
10311	(compare
10312	 (ior:SI
10313	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
10314	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
10315	 (const_int 0)))
10316   (set (match_dup 0) (ne:SI (match_dup 7) (const_int 0)))]
10317  "operands[7]
10318     = gen_rtx_REG (arm_select_dominance_cc_mode (operands[3], operands[6],
10319						  DOM_CC_X_OR_Y),
10320		    CC_REGNUM);"
10321  [(set_attr "conds" "clob")
10322   (set_attr "enabled_for_short_it" "yes,no")
10323   (set_attr "length" "16")
10324   (set_attr "type" "multiple")]
10325)
10326
10327; If the above pattern is followed by a CMP insn, then the compare is
10328; redundant, since we can rework the conditional instruction that follows.
10329(define_insn_and_split "*ior_scc_scc_cmp"
10330  [(set (match_operand 0 "dominant_cc_register" "")
10331	(compare (ior:SI (match_operator:SI 3 "arm_comparison_operator"
10332			  [(match_operand:SI 1 "s_register_operand" "l,r")
10333			   (match_operand:SI 2 "arm_add_operand" "lPy,rIL")])
10334			 (match_operator:SI 6 "arm_comparison_operator"
10335			  [(match_operand:SI 4 "s_register_operand" "l,r")
10336			   (match_operand:SI 5 "arm_add_operand" "lPy,rIL")]))
10337		 (const_int 0)))
10338   (set (match_operand:SI 7 "s_register_operand" "=Ts,Ts")
10339	(ior:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])
10340		(match_op_dup 6 [(match_dup 4) (match_dup 5)])))]
10341  "TARGET_32BIT"
10342  "#"
10343  "TARGET_32BIT && reload_completed"
10344  [(set (match_dup 0)
10345	(compare
10346	 (ior:SI
10347	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
10348	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
10349	 (const_int 0)))
10350   (set (match_dup 7) (ne:SI (match_dup 0) (const_int 0)))]
10351  ""
10352  [(set_attr "conds" "set")
10353   (set_attr "enabled_for_short_it" "yes,no")
10354   (set_attr "length" "16")
10355   (set_attr "type" "multiple")]
10356)
10357
10358(define_insn_and_split "*and_scc_scc"
10359  [(set (match_operand:SI 0 "s_register_operand" "=Ts,Ts")
10360	(and:SI (match_operator:SI 3 "arm_comparison_operator"
10361		 [(match_operand:SI 1 "s_register_operand" "l,r")
10362		  (match_operand:SI 2 "arm_add_operand" "lPy,rIL")])
10363		(match_operator:SI 6 "arm_comparison_operator"
10364		 [(match_operand:SI 4 "s_register_operand" "l,r")
10365		  (match_operand:SI 5 "arm_add_operand" "lPy,rIL")])))
10366   (clobber (reg:CC CC_REGNUM))]
10367  "TARGET_32BIT
10368   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
10369       != CCmode)"
10370  "#"
10371  "TARGET_32BIT && reload_completed
10372   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
10373       != CCmode)"
10374  [(set (match_dup 7)
10375	(compare
10376	 (and:SI
10377	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
10378	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
10379	 (const_int 0)))
10380   (set (match_dup 0) (ne:SI (match_dup 7) (const_int 0)))]
10381  "operands[7]
10382     = gen_rtx_REG (arm_select_dominance_cc_mode (operands[3], operands[6],
10383						  DOM_CC_X_AND_Y),
10384		    CC_REGNUM);"
10385  [(set_attr "conds" "clob")
10386   (set_attr "enabled_for_short_it" "yes,no")
10387   (set_attr "length" "16")
10388   (set_attr "type" "multiple")]
10389)
10390
10391; If the above pattern is followed by a CMP insn, then the compare is
10392; redundant, since we can rework the conditional instruction that follows.
10393(define_insn_and_split "*and_scc_scc_cmp"
10394  [(set (match_operand 0 "dominant_cc_register" "")
10395	(compare (and:SI (match_operator:SI 3 "arm_comparison_operator"
10396			  [(match_operand:SI 1 "s_register_operand" "l,r")
10397			   (match_operand:SI 2 "arm_add_operand" "lPy,rIL")])
10398			 (match_operator:SI 6 "arm_comparison_operator"
10399			  [(match_operand:SI 4 "s_register_operand" "l,r")
10400			   (match_operand:SI 5 "arm_add_operand" "lPy,rIL")]))
10401		 (const_int 0)))
10402   (set (match_operand:SI 7 "s_register_operand" "=Ts,Ts")
10403	(and:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])
10404		(match_op_dup 6 [(match_dup 4) (match_dup 5)])))]
10405  "TARGET_32BIT"
10406  "#"
10407  "TARGET_32BIT && reload_completed"
10408  [(set (match_dup 0)
10409	(compare
10410	 (and:SI
10411	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
10412	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
10413	 (const_int 0)))
10414   (set (match_dup 7) (ne:SI (match_dup 0) (const_int 0)))]
10415  ""
10416  [(set_attr "conds" "set")
10417   (set_attr "enabled_for_short_it" "yes,no")
10418   (set_attr "length" "16")
10419   (set_attr "type" "multiple")]
10420)
10421
10422;; If there is no dominance in the comparison, then we can still save an
10423;; instruction in the AND case, since we can know that the second compare
10424;; need only zero the value if false (if true, then the value is already
10425;; correct).
10426(define_insn_and_split "*and_scc_scc_nodom"
10427  [(set (match_operand:SI 0 "s_register_operand" "=&Ts,&Ts,&Ts")
10428	(and:SI (match_operator:SI 3 "arm_comparison_operator"
10429		 [(match_operand:SI 1 "s_register_operand" "r,r,0")
10430		  (match_operand:SI 2 "arm_add_operand" "rIL,0,rIL")])
10431		(match_operator:SI 6 "arm_comparison_operator"
10432		 [(match_operand:SI 4 "s_register_operand" "r,r,r")
10433		  (match_operand:SI 5 "arm_add_operand" "rIL,rIL,rIL")])))
10434   (clobber (reg:CC CC_REGNUM))]
10435  "TARGET_32BIT
10436   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
10437       == CCmode)"
10438  "#"
10439  "TARGET_32BIT && reload_completed"
10440  [(parallel [(set (match_dup 0)
10441		   (match_op_dup 3 [(match_dup 1) (match_dup 2)]))
10442	      (clobber (reg:CC CC_REGNUM))])
10443   (set (match_dup 7) (match_op_dup 8 [(match_dup 4) (match_dup 5)]))
10444   (set (match_dup 0)
10445	(if_then_else:SI (match_op_dup 6 [(match_dup 7) (const_int 0)])
10446			 (match_dup 0)
10447			 (const_int 0)))]
10448  "operands[7] = gen_rtx_REG (SELECT_CC_MODE (GET_CODE (operands[6]),
10449					      operands[4], operands[5]),
10450			      CC_REGNUM);
10451   operands[8] = gen_rtx_COMPARE (GET_MODE (operands[7]), operands[4],
10452				  operands[5]);"
10453  [(set_attr "conds" "clob")
10454   (set_attr "length" "20")
10455   (set_attr "type" "multiple")]
10456)
10457
10458(define_split
10459  [(set (reg:CC_NZ CC_REGNUM)
10460	(compare:CC_NZ (ior:SI
10461			  (and:SI (match_operand:SI 0 "s_register_operand" "")
10462				  (const_int 1))
10463			  (match_operator:SI 1 "arm_comparison_operator"
10464			   [(match_operand:SI 2 "s_register_operand" "")
10465			    (match_operand:SI 3 "arm_add_operand" "")]))
10466			 (const_int 0)))
10467   (clobber (match_operand:SI 4 "s_register_operand" ""))]
10468  "TARGET_ARM"
10469  [(set (match_dup 4)
10470	(ior:SI (match_op_dup 1 [(match_dup 2) (match_dup 3)])
10471		(match_dup 0)))
10472   (set (reg:CC_NZ CC_REGNUM)
10473	(compare:CC_NZ (and:SI (match_dup 4) (const_int 1))
10474			 (const_int 0)))]
10475  "")
10476
10477(define_split
10478  [(set (reg:CC_NZ CC_REGNUM)
10479	(compare:CC_NZ (ior:SI
10480			  (match_operator:SI 1 "arm_comparison_operator"
10481			   [(match_operand:SI 2 "s_register_operand" "")
10482			    (match_operand:SI 3 "arm_add_operand" "")])
10483			  (and:SI (match_operand:SI 0 "s_register_operand" "")
10484				  (const_int 1)))
10485			 (const_int 0)))
10486   (clobber (match_operand:SI 4 "s_register_operand" ""))]
10487  "TARGET_ARM"
10488  [(set (match_dup 4)
10489	(ior:SI (match_op_dup 1 [(match_dup 2) (match_dup 3)])
10490		(match_dup 0)))
10491   (set (reg:CC_NZ CC_REGNUM)
10492	(compare:CC_NZ (and:SI (match_dup 4) (const_int 1))
10493			 (const_int 0)))]
10494  "")
10495;; ??? The conditional patterns above need checking for Thumb-2 usefulness
10496
10497(define_insn_and_split "*negscc"
10498  [(set (match_operand:SI 0 "s_register_operand" "=r")
10499	(neg:SI (match_operator 3 "arm_comparison_operator"
10500		 [(match_operand:SI 1 "s_register_operand" "r")
10501		  (match_operand:SI 2 "arm_rhs_operand" "rI")])))
10502   (clobber (reg:CC CC_REGNUM))]
10503  "TARGET_ARM"
10504  "#"
10505  "&& reload_completed"
10506  [(const_int 0)]
10507  {
10508    rtx cc_reg = gen_rtx_REG (CCmode, CC_REGNUM);
10509
10510    if (GET_CODE (operands[3]) == LT && operands[2] == const0_rtx)
10511       {
10512         /* Emit mov\\t%0, %1, asr #31 */
10513         emit_insn (gen_rtx_SET (operands[0],
10514                                 gen_rtx_ASHIFTRT (SImode,
10515                                                   operands[1],
10516                                                   GEN_INT (31))));
10517         DONE;
10518       }
10519     else if (GET_CODE (operands[3]) == NE)
10520       {
10521        /* Emit subs\\t%0, %1, %2\;mvnne\\t%0, #0 */
10522        if (CONST_INT_P (operands[2]))
10523          emit_insn (gen_cmpsi2_addneg (operands[0], operands[1], operands[2],
10524                                        gen_int_mode (-INTVAL (operands[2]),
10525						      SImode)));
10526        else
10527          emit_insn (gen_subsi3_compare (operands[0], operands[1], operands[2]));
10528
10529        emit_insn (gen_rtx_COND_EXEC (VOIDmode,
10530                                      gen_rtx_NE (SImode,
10531                                                  cc_reg,
10532                                                  const0_rtx),
10533                                      gen_rtx_SET (operands[0],
10534                                                   GEN_INT (~0))));
10535        DONE;
10536      }
10537    else
10538      {
10539        /* Emit: cmp\\t%1, %2\;mov%D3\\t%0, #0\;mvn%d3\\t%0, #0 */
10540        emit_insn (gen_rtx_SET (cc_reg,
10541                                gen_rtx_COMPARE (CCmode, operands[1], operands[2])));
10542        enum rtx_code rc = GET_CODE (operands[3]);
10543
10544        rc = reverse_condition (rc);
10545        emit_insn (gen_rtx_COND_EXEC (VOIDmode,
10546                                      gen_rtx_fmt_ee (rc,
10547                                                      VOIDmode,
10548                                                      cc_reg,
10549                                                      const0_rtx),
10550                                      gen_rtx_SET (operands[0], const0_rtx)));
10551        rc = GET_CODE (operands[3]);
10552        emit_insn (gen_rtx_COND_EXEC (VOIDmode,
10553                                      gen_rtx_fmt_ee (rc,
10554                                                      VOIDmode,
10555                                                      cc_reg,
10556                                                      const0_rtx),
10557                                      gen_rtx_SET (operands[0],
10558                                                   GEN_INT (~0))));
10559        DONE;
10560      }
10561     FAIL;
10562  }
10563  [(set_attr "conds" "clob")
10564   (set_attr "length" "12")
10565   (set_attr "type" "multiple")]
10566)
10567
10568(define_insn_and_split "movcond_addsi"
10569  [(set (match_operand:SI 0 "s_register_operand" "=r,l,r")
10570	(if_then_else:SI
10571	 (match_operator 5 "comparison_operator"
10572	  [(plus:SI (match_operand:SI 3 "s_register_operand" "r,r,r")
10573	            (match_operand:SI 4 "arm_add_operand" "rIL,rIL,rIL"))
10574            (const_int 0)])
10575	 (match_operand:SI 1 "arm_rhs_operand" "rI,rPy,r")
10576	 (match_operand:SI 2 "arm_rhs_operand" "rI,rPy,r")))
10577   (clobber (reg:CC CC_REGNUM))]
10578   "TARGET_32BIT"
10579   "#"
10580   "&& reload_completed"
10581  [(set (reg:CC_NZ CC_REGNUM)
10582	(compare:CC_NZ
10583	 (plus:SI (match_dup 3)
10584		  (match_dup 4))
10585	 (const_int 0)))
10586   (set (match_dup 0) (match_dup 1))
10587   (cond_exec (match_dup 6)
10588	      (set (match_dup 0) (match_dup 2)))]
10589  "
10590  {
10591    machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[5]),
10592					     operands[3], operands[4]);
10593    enum rtx_code rc = GET_CODE (operands[5]);
10594    operands[6] = gen_rtx_REG (mode, CC_REGNUM);
10595    gcc_assert (!(mode == CCFPmode || mode == CCFPEmode));
10596    if (!REG_P (operands[2]) || REGNO (operands[2]) != REGNO (operands[0]))
10597      rc = reverse_condition (rc);
10598    else
10599      std::swap (operands[1], operands[2]);
10600
10601    operands[6] = gen_rtx_fmt_ee (rc, VOIDmode, operands[6], const0_rtx);
10602  }
10603  "
10604  [(set_attr "conds" "clob")
10605   (set_attr "enabled_for_short_it" "no,yes,yes")
10606   (set_attr "type" "multiple")]
10607)
10608
10609(define_insn "movcond"
10610  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10611	(if_then_else:SI
10612	 (match_operator 5 "arm_comparison_operator"
10613	  [(match_operand:SI 3 "s_register_operand" "r,r,r")
10614	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL,rIL")])
10615	 (match_operand:SI 1 "arm_rhs_operand" "0,rI,?rI")
10616	 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
10617   (clobber (reg:CC CC_REGNUM))]
10618  "TARGET_ARM"
10619  "*
10620  if (GET_CODE (operands[5]) == LT
10621      && (operands[4] == const0_rtx))
10622    {
10623      if (which_alternative != 1 && REG_P (operands[1]))
10624	{
10625	  if (operands[2] == const0_rtx)
10626	    return \"and\\t%0, %1, %3, asr #31\";
10627	  return \"ands\\t%0, %1, %3, asr #32\;movcc\\t%0, %2\";
10628	}
10629      else if (which_alternative != 0 && REG_P (operands[2]))
10630	{
10631	  if (operands[1] == const0_rtx)
10632	    return \"bic\\t%0, %2, %3, asr #31\";
10633	  return \"bics\\t%0, %2, %3, asr #32\;movcs\\t%0, %1\";
10634	}
10635      /* The only case that falls through to here is when both ops 1 & 2
10636	 are constants.  */
10637    }
10638
10639  if (GET_CODE (operands[5]) == GE
10640      && (operands[4] == const0_rtx))
10641    {
10642      if (which_alternative != 1 && REG_P (operands[1]))
10643	{
10644	  if (operands[2] == const0_rtx)
10645	    return \"bic\\t%0, %1, %3, asr #31\";
10646	  return \"bics\\t%0, %1, %3, asr #32\;movcs\\t%0, %2\";
10647	}
10648      else if (which_alternative != 0 && REG_P (operands[2]))
10649	{
10650	  if (operands[1] == const0_rtx)
10651	    return \"and\\t%0, %2, %3, asr #31\";
10652	  return \"ands\\t%0, %2, %3, asr #32\;movcc\\t%0, %1\";
10653	}
10654      /* The only case that falls through to here is when both ops 1 & 2
10655	 are constants.  */
10656    }
10657  if (CONST_INT_P (operands[4])
10658      && !const_ok_for_arm (INTVAL (operands[4])))
10659    output_asm_insn (\"cmn\\t%3, #%n4\", operands);
10660  else
10661    output_asm_insn (\"cmp\\t%3, %4\", operands);
10662  if (which_alternative != 0)
10663    output_asm_insn (\"mov%d5\\t%0, %1\", operands);
10664  if (which_alternative != 1)
10665    output_asm_insn (\"mov%D5\\t%0, %2\", operands);
10666  return \"\";
10667  "
10668  [(set_attr "conds" "clob")
10669   (set_attr "length" "8,8,12")
10670   (set_attr "type" "multiple")]
10671)
10672
10673;; ??? The patterns below need checking for Thumb-2 usefulness.
10674
10675(define_insn "*ifcompare_plus_move"
10676  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10677	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
10678			  [(match_operand:SI 4 "s_register_operand" "r,r")
10679			   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
10680			 (plus:SI
10681			  (match_operand:SI 2 "s_register_operand" "r,r")
10682			  (match_operand:SI 3 "arm_add_operand" "rIL,rIL"))
10683			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))
10684   (clobber (reg:CC CC_REGNUM))]
10685  "TARGET_ARM"
10686  "#"
10687  [(set_attr "conds" "clob")
10688   (set_attr "length" "8,12")
10689   (set_attr "type" "multiple")]
10690)
10691
10692(define_insn "*if_plus_move"
10693  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r")
10694	(if_then_else:SI
10695	 (match_operator 4 "arm_comparison_operator"
10696	  [(match_operand 5 "cc_register" "") (const_int 0)])
10697	 (plus:SI
10698	  (match_operand:SI 2 "s_register_operand" "r,r,r,r")
10699	  (match_operand:SI 3 "arm_add_operand" "rI,L,rI,L"))
10700	 (match_operand:SI 1 "arm_rhs_operand" "0,0,?rI,?rI")))]
10701  "TARGET_ARM"
10702  "@
10703   add%d4\\t%0, %2, %3
10704   sub%d4\\t%0, %2, #%n3
10705   add%d4\\t%0, %2, %3\;mov%D4\\t%0, %1
10706   sub%d4\\t%0, %2, #%n3\;mov%D4\\t%0, %1"
10707  [(set_attr "conds" "use")
10708   (set_attr "length" "4,4,8,8")
10709   (set_attr_alternative "type"
10710                         [(if_then_else (match_operand 3 "const_int_operand" "")
10711                                        (const_string "alu_imm" )
10712                                        (const_string "alu_sreg"))
10713                          (const_string "alu_imm")
10714                          (const_string "multiple")
10715                          (const_string "multiple")])]
10716)
10717
10718(define_insn "*ifcompare_move_plus"
10719  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10720	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
10721			  [(match_operand:SI 4 "s_register_operand" "r,r")
10722			   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
10723			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
10724			 (plus:SI
10725			  (match_operand:SI 2 "s_register_operand" "r,r")
10726			  (match_operand:SI 3 "arm_add_operand" "rIL,rIL"))))
10727   (clobber (reg:CC CC_REGNUM))]
10728  "TARGET_ARM"
10729  "#"
10730  [(set_attr "conds" "clob")
10731   (set_attr "length" "8,12")
10732   (set_attr "type" "multiple")]
10733)
10734
10735(define_insn "*if_move_plus"
10736  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r")
10737	(if_then_else:SI
10738	 (match_operator 4 "arm_comparison_operator"
10739	  [(match_operand 5 "cc_register" "") (const_int 0)])
10740	 (match_operand:SI 1 "arm_rhs_operand" "0,0,?rI,?rI")
10741	 (plus:SI
10742	  (match_operand:SI 2 "s_register_operand" "r,r,r,r")
10743	  (match_operand:SI 3 "arm_add_operand" "rI,L,rI,L"))))]
10744  "TARGET_ARM"
10745  "@
10746   add%D4\\t%0, %2, %3
10747   sub%D4\\t%0, %2, #%n3
10748   add%D4\\t%0, %2, %3\;mov%d4\\t%0, %1
10749   sub%D4\\t%0, %2, #%n3\;mov%d4\\t%0, %1"
10750  [(set_attr "conds" "use")
10751   (set_attr "length" "4,4,8,8")
10752   (set_attr_alternative "type"
10753                         [(if_then_else (match_operand 3 "const_int_operand" "")
10754                                        (const_string "alu_imm" )
10755                                        (const_string "alu_sreg"))
10756                          (const_string "alu_imm")
10757                          (const_string "multiple")
10758                          (const_string "multiple")])]
10759)
10760
10761(define_insn "*ifcompare_arith_arith"
10762  [(set (match_operand:SI 0 "s_register_operand" "=r")
10763	(if_then_else:SI (match_operator 9 "arm_comparison_operator"
10764			  [(match_operand:SI 5 "s_register_operand" "r")
10765			   (match_operand:SI 6 "arm_add_operand" "rIL")])
10766			 (match_operator:SI 8 "shiftable_operator"
10767			  [(match_operand:SI 1 "s_register_operand" "r")
10768			   (match_operand:SI 2 "arm_rhs_operand" "rI")])
10769			 (match_operator:SI 7 "shiftable_operator"
10770			  [(match_operand:SI 3 "s_register_operand" "r")
10771			   (match_operand:SI 4 "arm_rhs_operand" "rI")])))
10772   (clobber (reg:CC CC_REGNUM))]
10773  "TARGET_ARM"
10774  "#"
10775  [(set_attr "conds" "clob")
10776   (set_attr "length" "12")
10777   (set_attr "type" "multiple")]
10778)
10779
10780(define_insn "*if_arith_arith"
10781  [(set (match_operand:SI 0 "s_register_operand" "=r")
10782	(if_then_else:SI (match_operator 5 "arm_comparison_operator"
10783			  [(match_operand 8 "cc_register" "") (const_int 0)])
10784			 (match_operator:SI 6 "shiftable_operator"
10785			  [(match_operand:SI 1 "s_register_operand" "r")
10786			   (match_operand:SI 2 "arm_rhs_operand" "rI")])
10787			 (match_operator:SI 7 "shiftable_operator"
10788			  [(match_operand:SI 3 "s_register_operand" "r")
10789			   (match_operand:SI 4 "arm_rhs_operand" "rI")])))]
10790  "TARGET_ARM"
10791  "%I6%d5\\t%0, %1, %2\;%I7%D5\\t%0, %3, %4"
10792  [(set_attr "conds" "use")
10793   (set_attr "length" "8")
10794   (set_attr "type" "multiple")]
10795)
10796
10797(define_insn "*ifcompare_arith_move"
10798  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10799	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
10800			  [(match_operand:SI 2 "s_register_operand" "r,r")
10801			   (match_operand:SI 3 "arm_add_operand" "rIL,rIL")])
10802			 (match_operator:SI 7 "shiftable_operator"
10803			  [(match_operand:SI 4 "s_register_operand" "r,r")
10804			   (match_operand:SI 5 "arm_rhs_operand" "rI,rI")])
10805			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))
10806   (clobber (reg:CC CC_REGNUM))]
10807  "TARGET_ARM"
10808  "*
10809  /* If we have an operation where (op x 0) is the identity operation and
10810     the conditional operator is LT or GE and we are comparing against zero and
10811     everything is in registers then we can do this in two instructions.  */
10812  if (operands[3] == const0_rtx
10813      && GET_CODE (operands[7]) != AND
10814      && REG_P (operands[5])
10815      && REG_P (operands[1])
10816      && REGNO (operands[1]) == REGNO (operands[4])
10817      && REGNO (operands[4]) != REGNO (operands[0]))
10818    {
10819      if (GET_CODE (operands[6]) == LT)
10820	return \"and\\t%0, %5, %2, asr #31\;%I7\\t%0, %4, %0\";
10821      else if (GET_CODE (operands[6]) == GE)
10822	return \"bic\\t%0, %5, %2, asr #31\;%I7\\t%0, %4, %0\";
10823    }
10824  if (CONST_INT_P (operands[3])
10825      && !const_ok_for_arm (INTVAL (operands[3])))
10826    output_asm_insn (\"cmn\\t%2, #%n3\", operands);
10827  else
10828    output_asm_insn (\"cmp\\t%2, %3\", operands);
10829  output_asm_insn (\"%I7%d6\\t%0, %4, %5\", operands);
10830  if (which_alternative != 0)
10831    return \"mov%D6\\t%0, %1\";
10832  return \"\";
10833  "
10834  [(set_attr "conds" "clob")
10835   (set_attr "length" "8,12")
10836   (set_attr "type" "multiple")]
10837)
10838
10839(define_insn "*if_arith_move"
10840  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10841	(if_then_else:SI (match_operator 4 "arm_comparison_operator"
10842			  [(match_operand 6 "cc_register" "") (const_int 0)])
10843			 (match_operator:SI 5 "shiftable_operator"
10844			  [(match_operand:SI 2 "s_register_operand" "r,r")
10845			   (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
10846			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))]
10847  "TARGET_ARM"
10848  "@
10849   %I5%d4\\t%0, %2, %3
10850   %I5%d4\\t%0, %2, %3\;mov%D4\\t%0, %1"
10851  [(set_attr "conds" "use")
10852   (set_attr "length" "4,8")
10853   (set_attr_alternative "type"
10854                         [(if_then_else (match_operand 3 "const_int_operand" "")
10855                                        (const_string "alu_shift_imm" )
10856                                        (const_string "alu_shift_reg"))
10857                          (const_string "multiple")])]
10858)
10859
10860(define_insn "*ifcompare_move_arith"
10861  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10862	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
10863			  [(match_operand:SI 4 "s_register_operand" "r,r")
10864			   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
10865			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
10866			 (match_operator:SI 7 "shiftable_operator"
10867			  [(match_operand:SI 2 "s_register_operand" "r,r")
10868			   (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))
10869   (clobber (reg:CC CC_REGNUM))]
10870  "TARGET_ARM"
10871  "*
10872  /* If we have an operation where (op x 0) is the identity operation and
10873     the conditional operator is LT or GE and we are comparing against zero and
10874     everything is in registers then we can do this in two instructions */
10875  if (operands[5] == const0_rtx
10876      && GET_CODE (operands[7]) != AND
10877      && REG_P (operands[3])
10878      && REG_P (operands[1])
10879      && REGNO (operands[1]) == REGNO (operands[2])
10880      && REGNO (operands[2]) != REGNO (operands[0]))
10881    {
10882      if (GET_CODE (operands[6]) == GE)
10883	return \"and\\t%0, %3, %4, asr #31\;%I7\\t%0, %2, %0\";
10884      else if (GET_CODE (operands[6]) == LT)
10885	return \"bic\\t%0, %3, %4, asr #31\;%I7\\t%0, %2, %0\";
10886    }
10887
10888  if (CONST_INT_P (operands[5])
10889      && !const_ok_for_arm (INTVAL (operands[5])))
10890    output_asm_insn (\"cmn\\t%4, #%n5\", operands);
10891  else
10892    output_asm_insn (\"cmp\\t%4, %5\", operands);
10893
10894  if (which_alternative != 0)
10895    output_asm_insn (\"mov%d6\\t%0, %1\", operands);
10896  return \"%I7%D6\\t%0, %2, %3\";
10897  "
10898  [(set_attr "conds" "clob")
10899   (set_attr "length" "8,12")
10900   (set_attr "type" "multiple")]
10901)
10902
10903(define_insn "*if_move_arith"
10904  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10905	(if_then_else:SI
10906	 (match_operator 4 "arm_comparison_operator"
10907	  [(match_operand 6 "cc_register" "") (const_int 0)])
10908	 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
10909	 (match_operator:SI 5 "shiftable_operator"
10910	  [(match_operand:SI 2 "s_register_operand" "r,r")
10911	   (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))]
10912  "TARGET_ARM"
10913  "@
10914   %I5%D4\\t%0, %2, %3
10915   %I5%D4\\t%0, %2, %3\;mov%d4\\t%0, %1"
10916  [(set_attr "conds" "use")
10917   (set_attr "length" "4,8")
10918   (set_attr_alternative "type"
10919                         [(if_then_else (match_operand 3 "const_int_operand" "")
10920                                        (const_string "alu_shift_imm" )
10921                                        (const_string "alu_shift_reg"))
10922                          (const_string "multiple")])]
10923)
10924
10925(define_insn "*ifcompare_move_not"
10926  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10927	(if_then_else:SI
10928	 (match_operator 5 "arm_comparison_operator"
10929	  [(match_operand:SI 3 "s_register_operand" "r,r")
10930	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
10931	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")
10932	 (not:SI
10933	  (match_operand:SI 2 "s_register_operand" "r,r"))))
10934   (clobber (reg:CC CC_REGNUM))]
10935  "TARGET_ARM"
10936  "#"
10937  [(set_attr "conds" "clob")
10938   (set_attr "length" "8,12")
10939   (set_attr "type" "multiple")]
10940)
10941
10942(define_insn "*if_move_not"
10943  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10944	(if_then_else:SI
10945	 (match_operator 4 "arm_comparison_operator"
10946	  [(match_operand 3 "cc_register" "") (const_int 0)])
10947	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
10948	 (not:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))))]
10949  "TARGET_ARM"
10950  "@
10951   mvn%D4\\t%0, %2
10952   mov%d4\\t%0, %1\;mvn%D4\\t%0, %2
10953   mvn%d4\\t%0, #%B1\;mvn%D4\\t%0, %2"
10954  [(set_attr "conds" "use")
10955   (set_attr "type" "mvn_reg")
10956   (set_attr "length" "4,8,8")
10957   (set_attr "type" "mvn_reg,multiple,multiple")]
10958)
10959
10960(define_insn "*ifcompare_not_move"
10961  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10962	(if_then_else:SI
10963	 (match_operator 5 "arm_comparison_operator"
10964	  [(match_operand:SI 3 "s_register_operand" "r,r")
10965	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
10966	 (not:SI
10967	  (match_operand:SI 2 "s_register_operand" "r,r"))
10968	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
10969   (clobber (reg:CC CC_REGNUM))]
10970  "TARGET_ARM"
10971  "#"
10972  [(set_attr "conds" "clob")
10973   (set_attr "length" "8,12")
10974   (set_attr "type" "multiple")]
10975)
10976
10977(define_insn "*if_not_move"
10978  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10979	(if_then_else:SI
10980	 (match_operator 4 "arm_comparison_operator"
10981	  [(match_operand 3 "cc_register" "") (const_int 0)])
10982	 (not:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))
10983	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
10984  "TARGET_ARM"
10985  "@
10986   mvn%d4\\t%0, %2
10987   mov%D4\\t%0, %1\;mvn%d4\\t%0, %2
10988   mvn%D4\\t%0, #%B1\;mvn%d4\\t%0, %2"
10989  [(set_attr "conds" "use")
10990   (set_attr "type" "mvn_reg,multiple,multiple")
10991   (set_attr "length" "4,8,8")]
10992)
10993
10994(define_insn "*ifcompare_shift_move"
10995  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10996	(if_then_else:SI
10997	 (match_operator 6 "arm_comparison_operator"
10998	  [(match_operand:SI 4 "s_register_operand" "r,r")
10999	   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
11000	 (match_operator:SI 7 "shift_operator"
11001	  [(match_operand:SI 2 "s_register_operand" "r,r")
11002	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM")])
11003	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
11004   (clobber (reg:CC CC_REGNUM))]
11005  "TARGET_ARM"
11006  "#"
11007  [(set_attr "conds" "clob")
11008   (set_attr "length" "8,12")
11009   (set_attr "type" "multiple")]
11010)
11011
11012(define_insn "*if_shift_move"
11013  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
11014	(if_then_else:SI
11015	 (match_operator 5 "arm_comparison_operator"
11016	  [(match_operand 6 "cc_register" "") (const_int 0)])
11017	 (match_operator:SI 4 "shift_operator"
11018	  [(match_operand:SI 2 "s_register_operand" "r,r,r")
11019	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM,rM")])
11020	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
11021  "TARGET_ARM"
11022  "@
11023   mov%d5\\t%0, %2%S4
11024   mov%D5\\t%0, %1\;mov%d5\\t%0, %2%S4
11025   mvn%D5\\t%0, #%B1\;mov%d5\\t%0, %2%S4"
11026  [(set_attr "conds" "use")
11027   (set_attr "shift" "2")
11028   (set_attr "length" "4,8,8")
11029   (set_attr_alternative "type"
11030                         [(if_then_else (match_operand 3 "const_int_operand" "")
11031                                        (const_string "mov_shift" )
11032                                        (const_string "mov_shift_reg"))
11033                          (const_string "multiple")
11034                          (const_string "multiple")])]
11035)
11036
11037(define_insn "*ifcompare_move_shift"
11038  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
11039	(if_then_else:SI
11040	 (match_operator 6 "arm_comparison_operator"
11041	  [(match_operand:SI 4 "s_register_operand" "r,r")
11042	   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
11043	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")
11044	 (match_operator:SI 7 "shift_operator"
11045	  [(match_operand:SI 2 "s_register_operand" "r,r")
11046	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM")])))
11047   (clobber (reg:CC CC_REGNUM))]
11048  "TARGET_ARM"
11049  "#"
11050  [(set_attr "conds" "clob")
11051   (set_attr "length" "8,12")
11052   (set_attr "type" "multiple")]
11053)
11054
11055(define_insn "*if_move_shift"
11056  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
11057	(if_then_else:SI
11058	 (match_operator 5 "arm_comparison_operator"
11059	  [(match_operand 6 "cc_register" "") (const_int 0)])
11060	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
11061	 (match_operator:SI 4 "shift_operator"
11062	  [(match_operand:SI 2 "s_register_operand" "r,r,r")
11063	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM,rM")])))]
11064  "TARGET_ARM"
11065  "@
11066   mov%D5\\t%0, %2%S4
11067   mov%d5\\t%0, %1\;mov%D5\\t%0, %2%S4
11068   mvn%d5\\t%0, #%B1\;mov%D5\\t%0, %2%S4"
11069  [(set_attr "conds" "use")
11070   (set_attr "shift" "2")
11071   (set_attr "length" "4,8,8")
11072   (set_attr_alternative "type"
11073                         [(if_then_else (match_operand 3 "const_int_operand" "")
11074                                        (const_string "mov_shift" )
11075                                        (const_string "mov_shift_reg"))
11076                          (const_string "multiple")
11077                          (const_string "multiple")])]
11078)
11079
11080(define_insn "*ifcompare_shift_shift"
11081  [(set (match_operand:SI 0 "s_register_operand" "=r")
11082	(if_then_else:SI
11083	 (match_operator 7 "arm_comparison_operator"
11084	  [(match_operand:SI 5 "s_register_operand" "r")
11085	   (match_operand:SI 6 "arm_add_operand" "rIL")])
11086	 (match_operator:SI 8 "shift_operator"
11087	  [(match_operand:SI 1 "s_register_operand" "r")
11088	   (match_operand:SI 2 "arm_rhs_operand" "rM")])
11089	 (match_operator:SI 9 "shift_operator"
11090	  [(match_operand:SI 3 "s_register_operand" "r")
11091	   (match_operand:SI 4 "arm_rhs_operand" "rM")])))
11092   (clobber (reg:CC CC_REGNUM))]
11093  "TARGET_ARM"
11094  "#"
11095  [(set_attr "conds" "clob")
11096   (set_attr "length" "12")
11097   (set_attr "type" "multiple")]
11098)
11099
11100(define_insn "*if_shift_shift"
11101  [(set (match_operand:SI 0 "s_register_operand" "=r")
11102	(if_then_else:SI
11103	 (match_operator 5 "arm_comparison_operator"
11104	  [(match_operand 8 "cc_register" "") (const_int 0)])
11105	 (match_operator:SI 6 "shift_operator"
11106	  [(match_operand:SI 1 "s_register_operand" "r")
11107	   (match_operand:SI 2 "arm_rhs_operand" "rM")])
11108	 (match_operator:SI 7 "shift_operator"
11109	  [(match_operand:SI 3 "s_register_operand" "r")
11110	   (match_operand:SI 4 "arm_rhs_operand" "rM")])))]
11111  "TARGET_ARM"
11112  "mov%d5\\t%0, %1%S6\;mov%D5\\t%0, %3%S7"
11113  [(set_attr "conds" "use")
11114   (set_attr "shift" "1")
11115   (set_attr "length" "8")
11116   (set (attr "type") (if_then_else
11117		        (and (match_operand 2 "const_int_operand" "")
11118                             (match_operand 4 "const_int_operand" ""))
11119		      (const_string "mov_shift")
11120		      (const_string "mov_shift_reg")))]
11121)
11122
11123(define_insn "*ifcompare_not_arith"
11124  [(set (match_operand:SI 0 "s_register_operand" "=r")
11125	(if_then_else:SI
11126	 (match_operator 6 "arm_comparison_operator"
11127	  [(match_operand:SI 4 "s_register_operand" "r")
11128	   (match_operand:SI 5 "arm_add_operand" "rIL")])
11129	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))
11130	 (match_operator:SI 7 "shiftable_operator"
11131	  [(match_operand:SI 2 "s_register_operand" "r")
11132	   (match_operand:SI 3 "arm_rhs_operand" "rI")])))
11133   (clobber (reg:CC CC_REGNUM))]
11134  "TARGET_ARM"
11135  "#"
11136  [(set_attr "conds" "clob")
11137   (set_attr "length" "12")
11138   (set_attr "type" "multiple")]
11139)
11140
11141(define_insn "*if_not_arith"
11142  [(set (match_operand:SI 0 "s_register_operand" "=r")
11143	(if_then_else:SI
11144	 (match_operator 5 "arm_comparison_operator"
11145	  [(match_operand 4 "cc_register" "") (const_int 0)])
11146	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))
11147	 (match_operator:SI 6 "shiftable_operator"
11148	  [(match_operand:SI 2 "s_register_operand" "r")
11149	   (match_operand:SI 3 "arm_rhs_operand" "rI")])))]
11150  "TARGET_ARM"
11151  "mvn%d5\\t%0, %1\;%I6%D5\\t%0, %2, %3"
11152  [(set_attr "conds" "use")
11153   (set_attr "type" "mvn_reg")
11154   (set_attr "length" "8")]
11155)
11156
11157(define_insn "*ifcompare_arith_not"
11158  [(set (match_operand:SI 0 "s_register_operand" "=r")
11159	(if_then_else:SI
11160	 (match_operator 6 "arm_comparison_operator"
11161	  [(match_operand:SI 4 "s_register_operand" "r")
11162	   (match_operand:SI 5 "arm_add_operand" "rIL")])
11163	 (match_operator:SI 7 "shiftable_operator"
11164	  [(match_operand:SI 2 "s_register_operand" "r")
11165	   (match_operand:SI 3 "arm_rhs_operand" "rI")])
11166	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))))
11167   (clobber (reg:CC CC_REGNUM))]
11168  "TARGET_ARM"
11169  "#"
11170  [(set_attr "conds" "clob")
11171   (set_attr "length" "12")
11172   (set_attr "type" "multiple")]
11173)
11174
11175(define_insn "*if_arith_not"
11176  [(set (match_operand:SI 0 "s_register_operand" "=r")
11177	(if_then_else:SI
11178	 (match_operator 5 "arm_comparison_operator"
11179	  [(match_operand 4 "cc_register" "") (const_int 0)])
11180	 (match_operator:SI 6 "shiftable_operator"
11181	  [(match_operand:SI 2 "s_register_operand" "r")
11182	   (match_operand:SI 3 "arm_rhs_operand" "rI")])
11183	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))))]
11184  "TARGET_ARM"
11185  "mvn%D5\\t%0, %1\;%I6%d5\\t%0, %2, %3"
11186  [(set_attr "conds" "use")
11187   (set_attr "type" "multiple")
11188   (set_attr "length" "8")]
11189)
11190
11191(define_insn "*ifcompare_neg_move"
11192  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
11193	(if_then_else:SI
11194	 (match_operator 5 "arm_comparison_operator"
11195	  [(match_operand:SI 3 "s_register_operand" "r,r")
11196	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
11197	 (neg:SI (match_operand:SI 2 "s_register_operand" "r,r"))
11198	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
11199   (clobber (reg:CC CC_REGNUM))]
11200  "TARGET_ARM"
11201  "#"
11202  [(set_attr "conds" "clob")
11203   (set_attr "length" "8,12")
11204   (set_attr "type" "multiple")]
11205)
11206
11207(define_insn_and_split "*if_neg_move"
11208  [(set (match_operand:SI 0 "s_register_operand" "=l,r")
11209	(if_then_else:SI
11210	 (match_operator 4 "arm_comparison_operator"
11211	  [(match_operand 3 "cc_register" "") (const_int 0)])
11212	 (neg:SI (match_operand:SI 2 "s_register_operand" "l,r"))
11213	 (match_operand:SI 1 "s_register_operand" "0,0")))]
11214  "TARGET_32BIT"
11215  "#"
11216  "&& reload_completed"
11217  [(cond_exec (match_op_dup 4 [(match_dup 3) (const_int 0)])
11218	      (set (match_dup 0) (neg:SI (match_dup 2))))]
11219  ""
11220  [(set_attr "conds" "use")
11221   (set_attr "length" "4")
11222   (set_attr "arch" "t2,32")
11223   (set_attr "enabled_for_short_it" "yes,no")
11224   (set_attr "type" "logic_shift_imm")]
11225)
11226
11227(define_insn "*ifcompare_move_neg"
11228  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
11229	(if_then_else:SI
11230	 (match_operator 5 "arm_comparison_operator"
11231	  [(match_operand:SI 3 "s_register_operand" "r,r")
11232	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
11233	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")
11234	 (neg:SI (match_operand:SI 2 "s_register_operand" "r,r"))))
11235   (clobber (reg:CC CC_REGNUM))]
11236  "TARGET_ARM"
11237  "#"
11238  [(set_attr "conds" "clob")
11239   (set_attr "length" "8,12")
11240   (set_attr "type" "multiple")]
11241)
11242
11243(define_insn_and_split "*if_move_neg"
11244  [(set (match_operand:SI 0 "s_register_operand" "=l,r")
11245	(if_then_else:SI
11246	 (match_operator 4 "arm_comparison_operator"
11247	  [(match_operand 3 "cc_register" "") (const_int 0)])
11248	 (match_operand:SI 1 "s_register_operand" "0,0")
11249	 (neg:SI (match_operand:SI 2 "s_register_operand" "l,r"))))]
11250  "TARGET_32BIT"
11251  "#"
11252  "&& reload_completed"
11253  [(cond_exec (match_dup 5)
11254	      (set (match_dup 0) (neg:SI (match_dup 2))))]
11255  {
11256    machine_mode mode = GET_MODE (operands[3]);
11257    rtx_code rc = GET_CODE (operands[4]);
11258
11259    if (mode == CCFPmode || mode == CCFPEmode)
11260      rc = reverse_condition_maybe_unordered (rc);
11261    else
11262      rc = reverse_condition (rc);
11263
11264    operands[5] = gen_rtx_fmt_ee (rc, VOIDmode, operands[3], const0_rtx);
11265  }
11266  [(set_attr "conds" "use")
11267   (set_attr "length" "4")
11268   (set_attr "arch" "t2,32")
11269   (set_attr "enabled_for_short_it" "yes,no")
11270   (set_attr "type" "logic_shift_imm")]
11271)
11272
11273(define_insn "*arith_adjacentmem"
11274  [(set (match_operand:SI 0 "s_register_operand" "=r")
11275	(match_operator:SI 1 "shiftable_operator"
11276	 [(match_operand:SI 2 "memory_operand" "m")
11277	  (match_operand:SI 3 "memory_operand" "m")]))
11278   (clobber (match_scratch:SI 4 "=r"))]
11279  "TARGET_ARM && adjacent_mem_locations (operands[2], operands[3])"
11280  "*
11281  {
11282    rtx ldm[3];
11283    rtx arith[4];
11284    rtx base_reg;
11285    HOST_WIDE_INT val1 = 0, val2 = 0;
11286
11287    if (REGNO (operands[0]) > REGNO (operands[4]))
11288      {
11289	ldm[1] = operands[4];
11290	ldm[2] = operands[0];
11291      }
11292    else
11293      {
11294	ldm[1] = operands[0];
11295	ldm[2] = operands[4];
11296      }
11297
11298    base_reg = XEXP (operands[2], 0);
11299
11300    if (!REG_P (base_reg))
11301      {
11302	val1 = INTVAL (XEXP (base_reg, 1));
11303	base_reg = XEXP (base_reg, 0);
11304      }
11305
11306    if (!REG_P (XEXP (operands[3], 0)))
11307      val2 = INTVAL (XEXP (XEXP (operands[3], 0), 1));
11308
11309    arith[0] = operands[0];
11310    arith[3] = operands[1];
11311
11312    if (val1 < val2)
11313      {
11314	arith[1] = ldm[1];
11315	arith[2] = ldm[2];
11316      }
11317    else
11318      {
11319	arith[1] = ldm[2];
11320	arith[2] = ldm[1];
11321      }
11322
11323    ldm[0] = base_reg;
11324    if (val1 !=0 && val2 != 0)
11325      {
11326	rtx ops[3];
11327
11328	if (val1 == 4 || val2 == 4)
11329	  /* Other val must be 8, since we know they are adjacent and neither
11330	     is zero.  */
11331	  output_asm_insn (\"ldmib%?\\t%0, {%1, %2}\", ldm);
11332	else if (const_ok_for_arm (val1) || const_ok_for_arm (-val1))
11333	  {
11334	    ldm[0] = ops[0] = operands[4];
11335	    ops[1] = base_reg;
11336	    ops[2] = GEN_INT (val1);
11337	    output_add_immediate (ops);
11338	    if (val1 < val2)
11339	      output_asm_insn (\"ldmia%?\\t%0, {%1, %2}\", ldm);
11340	    else
11341	      output_asm_insn (\"ldmda%?\\t%0, {%1, %2}\", ldm);
11342	  }
11343	else
11344	  {
11345	    /* Offset is out of range for a single add, so use two ldr.  */
11346	    ops[0] = ldm[1];
11347	    ops[1] = base_reg;
11348	    ops[2] = GEN_INT (val1);
11349	    output_asm_insn (\"ldr%?\\t%0, [%1, %2]\", ops);
11350	    ops[0] = ldm[2];
11351	    ops[2] = GEN_INT (val2);
11352	    output_asm_insn (\"ldr%?\\t%0, [%1, %2]\", ops);
11353	  }
11354      }
11355    else if (val1 != 0)
11356      {
11357	if (val1 < val2)
11358	  output_asm_insn (\"ldmda%?\\t%0, {%1, %2}\", ldm);
11359	else
11360	  output_asm_insn (\"ldmia%?\\t%0, {%1, %2}\", ldm);
11361      }
11362    else
11363      {
11364	if (val1 < val2)
11365	  output_asm_insn (\"ldmia%?\\t%0, {%1, %2}\", ldm);
11366	else
11367	  output_asm_insn (\"ldmda%?\\t%0, {%1, %2}\", ldm);
11368      }
11369    output_asm_insn (\"%I3%?\\t%0, %1, %2\", arith);
11370    return \"\";
11371  }"
11372  [(set_attr "length" "12")
11373   (set_attr "predicable" "yes")
11374   (set_attr "type" "load_4")]
11375)
11376
11377; This pattern is never tried by combine, so do it as a peephole
11378
11379(define_peephole2
11380  [(set (match_operand:SI 0 "arm_general_register_operand" "")
11381	(match_operand:SI 1 "arm_general_register_operand" ""))
11382   (set (reg:CC CC_REGNUM)
11383	(compare:CC (match_dup 1) (const_int 0)))]
11384  "TARGET_ARM"
11385  [(parallel [(set (reg:CC CC_REGNUM) (compare:CC (match_dup 1) (const_int 0)))
11386	      (set (match_dup 0) (match_dup 1))])]
11387  ""
11388)
11389
11390(define_split
11391  [(set (match_operand:SI 0 "s_register_operand" "")
11392	(and:SI (ge:SI (match_operand:SI 1 "s_register_operand" "")
11393		       (const_int 0))
11394		(neg:SI (match_operator:SI 2 "arm_comparison_operator"
11395			 [(match_operand:SI 3 "s_register_operand" "")
11396			  (match_operand:SI 4 "arm_rhs_operand" "")]))))
11397   (clobber (match_operand:SI 5 "s_register_operand" ""))]
11398  "TARGET_ARM"
11399  [(set (match_dup 5) (not:SI (ashiftrt:SI (match_dup 1) (const_int 31))))
11400   (set (match_dup 0) (and:SI (match_op_dup 2 [(match_dup 3) (match_dup 4)])
11401			      (match_dup 5)))]
11402  ""
11403)
11404
11405;; This split can be used because CC_Z mode implies that the following
11406;; branch will be an equality, or an unsigned inequality, so the sign
11407;; extension is not needed.
11408
11409(define_split
11410  [(set (reg:CC_Z CC_REGNUM)
11411	(compare:CC_Z
11412	 (ashift:SI (subreg:SI (match_operand:QI 0 "memory_operand" "") 0)
11413		    (const_int 24))
11414	 (match_operand 1 "const_int_operand" "")))
11415   (clobber (match_scratch:SI 2 ""))]
11416  "TARGET_ARM
11417   && ((UINTVAL (operands[1]))
11418       == ((UINTVAL (operands[1])) >> 24) << 24)"
11419  [(set (match_dup 2) (zero_extend:SI (match_dup 0)))
11420   (set (reg:CC CC_REGNUM) (compare:CC (match_dup 2) (match_dup 1)))]
11421  "
11422  operands[1] = GEN_INT (((unsigned long) INTVAL (operands[1])) >> 24);
11423  "
11424)
11425;; ??? Check the patterns above for Thumb-2 usefulness
11426
11427(define_expand "prologue"
11428  [(clobber (const_int 0))]
11429  "TARGET_EITHER"
11430  "if (TARGET_32BIT)
11431     arm_expand_prologue ();
11432   else
11433     thumb1_expand_prologue ();
11434  DONE;
11435  "
11436)
11437
11438(define_expand "epilogue"
11439  [(clobber (const_int 0))]
11440  "TARGET_EITHER"
11441  "
11442  if (crtl->calls_eh_return)
11443    emit_insn (gen_force_register_use (gen_rtx_REG (Pmode, 2)));
11444  if (TARGET_THUMB1)
11445   {
11446     thumb1_expand_epilogue ();
11447     emit_jump_insn (gen_rtx_UNSPEC_VOLATILE (VOIDmode,
11448                     gen_rtvec (1, ret_rtx), VUNSPEC_EPILOGUE));
11449   }
11450  else if (HAVE_return)
11451   {
11452     /* HAVE_return is testing for USE_RETURN_INSN (FALSE).  Hence,
11453        no need for explicit testing again.  */
11454     emit_jump_insn (gen_return ());
11455   }
11456  else if (TARGET_32BIT)
11457   {
11458    arm_expand_epilogue (true);
11459   }
11460  DONE;
11461  "
11462)
11463
11464;; Note - although unspec_volatile's USE all hard registers,
11465;; USEs are ignored after relaod has completed.  Thus we need
11466;; to add an unspec of the link register to ensure that flow
11467;; does not think that it is unused by the sibcall branch that
11468;; will replace the standard function epilogue.
11469(define_expand "sibcall_epilogue"
11470   [(parallel [(unspec:SI [(reg:SI LR_REGNUM)] UNSPEC_REGISTER_USE)
11471               (unspec_volatile [(return)] VUNSPEC_EPILOGUE)])]
11472   "TARGET_32BIT"
11473   "
11474   arm_expand_epilogue (false);
11475   DONE;
11476   "
11477)
11478
11479(define_expand "eh_epilogue"
11480  [(use (match_operand:SI 0 "register_operand"))
11481   (use (match_operand:SI 1 "register_operand"))
11482   (use (match_operand:SI 2 "register_operand"))]
11483  "TARGET_EITHER"
11484  "
11485  {
11486    cfun->machine->eh_epilogue_sp_ofs = operands[1];
11487    if (!REG_P (operands[2]) || REGNO (operands[2]) != 2)
11488      {
11489	rtx ra = gen_rtx_REG (Pmode, 2);
11490
11491	emit_move_insn (ra, operands[2]);
11492	operands[2] = ra;
11493      }
11494    /* This is a hack -- we may have crystalized the function type too
11495       early.  */
11496    cfun->machine->func_type = 0;
11497  }"
11498)
11499
11500;; This split is only used during output to reduce the number of patterns
11501;; that need assembler instructions adding to them.  We allowed the setting
11502;; of the conditions to be implicit during rtl generation so that
11503;; the conditional compare patterns would work.  However this conflicts to
11504;; some extent with the conditional data operations, so we have to split them
11505;; up again here.
11506
11507;; ??? Need to audit these splitters for Thumb-2.  Why isn't normal
11508;; conditional execution sufficient?
11509
11510(define_split
11511  [(set (match_operand:SI 0 "s_register_operand" "")
11512	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
11513			  [(match_operand 2 "" "") (match_operand 3 "" "")])
11514			 (match_dup 0)
11515			 (match_operand 4 "" "")))
11516   (clobber (reg:CC CC_REGNUM))]
11517  "TARGET_ARM && reload_completed"
11518  [(set (match_dup 5) (match_dup 6))
11519   (cond_exec (match_dup 7)
11520	      (set (match_dup 0) (match_dup 4)))]
11521  "
11522  {
11523    machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
11524					     operands[2], operands[3]);
11525    enum rtx_code rc = GET_CODE (operands[1]);
11526
11527    operands[5] = gen_rtx_REG (mode, CC_REGNUM);
11528    operands[6] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
11529    if (mode == CCFPmode || mode == CCFPEmode)
11530      rc = reverse_condition_maybe_unordered (rc);
11531    else
11532      rc = reverse_condition (rc);
11533
11534    operands[7] = gen_rtx_fmt_ee (rc, VOIDmode, operands[5], const0_rtx);
11535  }"
11536)
11537
11538(define_split
11539  [(set (match_operand:SI 0 "s_register_operand" "")
11540	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
11541			  [(match_operand 2 "" "") (match_operand 3 "" "")])
11542			 (match_operand 4 "" "")
11543			 (match_dup 0)))
11544   (clobber (reg:CC CC_REGNUM))]
11545  "TARGET_ARM && reload_completed"
11546  [(set (match_dup 5) (match_dup 6))
11547   (cond_exec (match_op_dup 1 [(match_dup 5) (const_int 0)])
11548	      (set (match_dup 0) (match_dup 4)))]
11549  "
11550  {
11551    machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
11552					     operands[2], operands[3]);
11553
11554    operands[5] = gen_rtx_REG (mode, CC_REGNUM);
11555    operands[6] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
11556  }"
11557)
11558
11559(define_split
11560  [(set (match_operand:SI 0 "s_register_operand" "")
11561	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
11562			  [(match_operand 2 "" "") (match_operand 3 "" "")])
11563			 (match_operand 4 "" "")
11564			 (match_operand 5 "" "")))
11565   (clobber (reg:CC CC_REGNUM))]
11566  "TARGET_ARM && reload_completed"
11567  [(set (match_dup 6) (match_dup 7))
11568   (cond_exec (match_op_dup 1 [(match_dup 6) (const_int 0)])
11569	      (set (match_dup 0) (match_dup 4)))
11570   (cond_exec (match_dup 8)
11571	      (set (match_dup 0) (match_dup 5)))]
11572  "
11573  {
11574    machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
11575					     operands[2], operands[3]);
11576    enum rtx_code rc = GET_CODE (operands[1]);
11577
11578    operands[6] = gen_rtx_REG (mode, CC_REGNUM);
11579    operands[7] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
11580    if (mode == CCFPmode || mode == CCFPEmode)
11581      rc = reverse_condition_maybe_unordered (rc);
11582    else
11583      rc = reverse_condition (rc);
11584
11585    operands[8] = gen_rtx_fmt_ee (rc, VOIDmode, operands[6], const0_rtx);
11586  }"
11587)
11588
11589(define_split
11590  [(set (match_operand:SI 0 "s_register_operand" "")
11591	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
11592			  [(match_operand:SI 2 "s_register_operand" "")
11593			   (match_operand:SI 3 "arm_add_operand" "")])
11594			 (match_operand:SI 4 "arm_rhs_operand" "")
11595			 (not:SI
11596			  (match_operand:SI 5 "s_register_operand" ""))))
11597   (clobber (reg:CC CC_REGNUM))]
11598  "TARGET_ARM && reload_completed"
11599  [(set (match_dup 6) (match_dup 7))
11600   (cond_exec (match_op_dup 1 [(match_dup 6) (const_int 0)])
11601	      (set (match_dup 0) (match_dup 4)))
11602   (cond_exec (match_dup 8)
11603	      (set (match_dup 0) (not:SI (match_dup 5))))]
11604  "
11605  {
11606    machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
11607					     operands[2], operands[3]);
11608    enum rtx_code rc = GET_CODE (operands[1]);
11609
11610    operands[6] = gen_rtx_REG (mode, CC_REGNUM);
11611    operands[7] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
11612    if (mode == CCFPmode || mode == CCFPEmode)
11613      rc = reverse_condition_maybe_unordered (rc);
11614    else
11615      rc = reverse_condition (rc);
11616
11617    operands[8] = gen_rtx_fmt_ee (rc, VOIDmode, operands[6], const0_rtx);
11618  }"
11619)
11620
11621(define_insn "*cond_move_not"
11622  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
11623	(if_then_else:SI (match_operator 4 "arm_comparison_operator"
11624			  [(match_operand 3 "cc_register" "") (const_int 0)])
11625			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
11626			 (not:SI
11627			  (match_operand:SI 2 "s_register_operand" "r,r"))))]
11628  "TARGET_ARM"
11629  "@
11630   mvn%D4\\t%0, %2
11631   mov%d4\\t%0, %1\;mvn%D4\\t%0, %2"
11632  [(set_attr "conds" "use")
11633   (set_attr "type" "mvn_reg,multiple")
11634   (set_attr "length" "4,8")]
11635)
11636
11637;; The next two patterns occur when an AND operation is followed by a
11638;; scc insn sequence
11639
11640(define_insn "*sign_extract_onebit"
11641  [(set (match_operand:SI 0 "s_register_operand" "=r")
11642	(sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
11643			 (const_int 1)
11644			 (match_operand:SI 2 "const_int_operand" "n")))
11645    (clobber (reg:CC CC_REGNUM))]
11646  "TARGET_ARM"
11647  "*
11648    operands[2] = GEN_INT (1 << INTVAL (operands[2]));
11649    output_asm_insn (\"ands\\t%0, %1, %2\", operands);
11650    return \"mvnne\\t%0, #0\";
11651  "
11652  [(set_attr "conds" "clob")
11653   (set_attr "length" "8")
11654   (set_attr "type" "multiple")]
11655)
11656
11657(define_insn "*not_signextract_onebit"
11658  [(set (match_operand:SI 0 "s_register_operand" "=r")
11659	(not:SI
11660	 (sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
11661			  (const_int 1)
11662			  (match_operand:SI 2 "const_int_operand" "n"))))
11663   (clobber (reg:CC CC_REGNUM))]
11664  "TARGET_ARM"
11665  "*
11666    operands[2] = GEN_INT (1 << INTVAL (operands[2]));
11667    output_asm_insn (\"tst\\t%1, %2\", operands);
11668    output_asm_insn (\"mvneq\\t%0, #0\", operands);
11669    return \"movne\\t%0, #0\";
11670  "
11671  [(set_attr "conds" "clob")
11672   (set_attr "length" "12")
11673   (set_attr "type" "multiple")]
11674)
11675;; ??? The above patterns need auditing for Thumb-2
11676
11677;; Push multiple registers to the stack.  Registers are in parallel (use ...)
11678;; expressions.  For simplicity, the first register is also in the unspec
11679;; part.
11680;; To avoid the usage of GNU extension, the length attribute is computed
11681;; in a C function arm_attr_length_push_multi.
11682(define_insn "*push_multi"
11683  [(match_parallel 2 "multi_register_push"
11684    [(set (match_operand:BLK 0 "push_mult_memory_operand" "")
11685	  (unspec:BLK [(match_operand:SI 1 "s_register_operand" "")]
11686		      UNSPEC_PUSH_MULT))])]
11687  ""
11688  "*
11689  {
11690    int num_saves = XVECLEN (operands[2], 0);
11691
11692    /* For the StrongARM at least it is faster to
11693       use STR to store only a single register.
11694       In Thumb mode always use push, and the assembler will pick
11695       something appropriate.  */
11696    if (num_saves == 1 && TARGET_ARM)
11697      output_asm_insn (\"str%?\\t%1, [%m0, #-4]!\", operands);
11698    else
11699      {
11700	int i;
11701	char pattern[100];
11702
11703	if (TARGET_32BIT)
11704	    strcpy (pattern, \"push%?\\t{%1\");
11705	else
11706	    strcpy (pattern, \"push\\t{%1\");
11707
11708	for (i = 1; i < num_saves; i++)
11709	  {
11710	    strcat (pattern, \", %|\");
11711	    strcat (pattern,
11712		    reg_names[REGNO (XEXP (XVECEXP (operands[2], 0, i), 0))]);
11713	  }
11714
11715	strcat (pattern, \"}\");
11716	output_asm_insn (pattern, operands);
11717      }
11718
11719    return \"\";
11720  }"
11721  [(set_attr "type" "store_16")
11722   (set (attr "length")
11723	(symbol_ref "arm_attr_length_push_multi (operands[2], operands[1])"))]
11724)
11725
11726(define_insn "stack_tie"
11727  [(set (mem:BLK (scratch))
11728	(unspec:BLK [(match_operand:SI 0 "s_register_operand" "rk")
11729		     (match_operand:SI 1 "s_register_operand" "rk")]
11730		    UNSPEC_PRLG_STK))]
11731  ""
11732  ""
11733  [(set_attr "length" "0")
11734   (set_attr "type" "block")]
11735)
11736
11737;; Pop (as used in epilogue RTL)
11738;;
11739(define_insn "*load_multiple_with_writeback"
11740  [(match_parallel 0 "load_multiple_operation"
11741    [(set (match_operand:SI 1 "s_register_operand" "+rk")
11742          (plus:SI (match_dup 1)
11743                   (match_operand:SI 2 "const_int_I_operand" "I")))
11744     (set (match_operand:SI 3 "s_register_operand" "=rk")
11745          (mem:SI (match_dup 1)))
11746        ])]
11747  "TARGET_32BIT && (reload_in_progress || reload_completed)"
11748  "*
11749  {
11750    arm_output_multireg_pop (operands, /*return_pc=*/false,
11751                                       /*cond=*/const_true_rtx,
11752                                       /*reverse=*/false,
11753                                       /*update=*/true);
11754    return \"\";
11755  }
11756  "
11757  [(set_attr "type" "load_16")
11758   (set_attr "predicable" "yes")
11759   (set (attr "length")
11760	(symbol_ref "arm_attr_length_pop_multi (operands,
11761						/*return_pc=*/false,
11762						/*write_back_p=*/true)"))]
11763)
11764
11765;; Pop with return (as used in epilogue RTL)
11766;;
11767;; This instruction is generated when the registers are popped at the end of
11768;; epilogue.  Here, instead of popping the value into LR and then generating
11769;; jump to LR, value is popped into PC directly.  Hence, the pattern is combined
11770;;  with (return).
11771(define_insn "*pop_multiple_with_writeback_and_return"
11772  [(match_parallel 0 "pop_multiple_return"
11773    [(return)
11774     (set (match_operand:SI 1 "s_register_operand" "+rk")
11775          (plus:SI (match_dup 1)
11776                   (match_operand:SI 2 "const_int_I_operand" "I")))
11777     (set (match_operand:SI 3 "s_register_operand" "=rk")
11778          (mem:SI (match_dup 1)))
11779        ])]
11780  "TARGET_32BIT && (reload_in_progress || reload_completed)"
11781  "*
11782  {
11783    arm_output_multireg_pop (operands, /*return_pc=*/true,
11784                                       /*cond=*/const_true_rtx,
11785                                       /*reverse=*/false,
11786                                       /*update=*/true);
11787    return \"\";
11788  }
11789  "
11790  [(set_attr "type" "load_16")
11791   (set_attr "predicable" "yes")
11792   (set (attr "length")
11793	(symbol_ref "arm_attr_length_pop_multi (operands, /*return_pc=*/true,
11794						/*write_back_p=*/true)"))]
11795)
11796
11797(define_insn "*pop_multiple_with_return"
11798  [(match_parallel 0 "pop_multiple_return"
11799    [(return)
11800     (set (match_operand:SI 2 "s_register_operand" "=rk")
11801          (mem:SI (match_operand:SI 1 "s_register_operand" "rk")))
11802        ])]
11803  "TARGET_32BIT && (reload_in_progress || reload_completed)"
11804  "*
11805  {
11806    arm_output_multireg_pop (operands, /*return_pc=*/true,
11807                                       /*cond=*/const_true_rtx,
11808                                       /*reverse=*/false,
11809                                       /*update=*/false);
11810    return \"\";
11811  }
11812  "
11813  [(set_attr "type" "load_16")
11814   (set_attr "predicable" "yes")
11815   (set (attr "length")
11816	(symbol_ref "arm_attr_length_pop_multi (operands, /*return_pc=*/true,
11817						/*write_back_p=*/false)"))]
11818)
11819
11820;; Load into PC and return
11821(define_insn "*ldr_with_return"
11822  [(return)
11823   (set (reg:SI PC_REGNUM)
11824        (mem:SI (post_inc:SI (match_operand:SI 0 "s_register_operand" "+rk"))))]
11825  "TARGET_32BIT && (reload_in_progress || reload_completed)"
11826  "ldr%?\t%|pc, [%0], #4"
11827  [(set_attr "type" "load_4")
11828   (set_attr "predicable" "yes")]
11829)
11830;; Pop for floating point registers (as used in epilogue RTL)
11831(define_insn "*vfp_pop_multiple_with_writeback"
11832  [(match_parallel 0 "pop_multiple_fp"
11833    [(set (match_operand:SI 1 "s_register_operand" "+rk")
11834          (plus:SI (match_dup 1)
11835                   (match_operand:SI 2 "const_int_I_operand" "I")))
11836     (set (match_operand:DF 3 "vfp_hard_register_operand" "")
11837          (mem:DF (match_dup 1)))])]
11838  "TARGET_32BIT && TARGET_VFP_BASE"
11839  "*
11840  {
11841    int num_regs = XVECLEN (operands[0], 0);
11842    char pattern[100];
11843    rtx op_list[2];
11844    strcpy (pattern, \"vldm\\t\");
11845    strcat (pattern, reg_names[REGNO (SET_DEST (XVECEXP (operands[0], 0, 0)))]);
11846    strcat (pattern, \"!, {\");
11847    op_list[0] = XEXP (XVECEXP (operands[0], 0, 1), 0);
11848    strcat (pattern, \"%P0\");
11849    if ((num_regs - 1) > 1)
11850      {
11851        strcat (pattern, \"-%P1\");
11852        op_list [1] = XEXP (XVECEXP (operands[0], 0, num_regs - 1), 0);
11853      }
11854
11855    strcat (pattern, \"}\");
11856    output_asm_insn (pattern, op_list);
11857    return \"\";
11858  }
11859  "
11860  [(set_attr "type" "load_16")
11861   (set_attr "conds" "unconditional")
11862   (set_attr "predicable" "no")]
11863)
11864
11865;; Special patterns for dealing with the constant pool
11866
11867(define_insn "align_4"
11868  [(unspec_volatile [(const_int 0)] VUNSPEC_ALIGN)]
11869  "TARGET_EITHER"
11870  "*
11871  assemble_align (32);
11872  return \"\";
11873  "
11874  [(set_attr "type" "no_insn")]
11875)
11876
11877(define_insn "align_8"
11878  [(unspec_volatile [(const_int 0)] VUNSPEC_ALIGN8)]
11879  "TARGET_EITHER"
11880  "*
11881  assemble_align (64);
11882  return \"\";
11883  "
11884  [(set_attr "type" "no_insn")]
11885)
11886
11887(define_insn "consttable_end"
11888  [(unspec_volatile [(const_int 0)] VUNSPEC_POOL_END)]
11889  "TARGET_EITHER"
11890  "*
11891  making_const_table = FALSE;
11892  return \"\";
11893  "
11894  [(set_attr "type" "no_insn")]
11895)
11896
11897(define_insn "consttable_1"
11898  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_1)]
11899  "TARGET_EITHER"
11900  "*
11901  making_const_table = TRUE;
11902  assemble_integer (operands[0], 1, BITS_PER_WORD, 1);
11903  assemble_zeros (3);
11904  return \"\";
11905  "
11906  [(set_attr "length" "4")
11907   (set_attr "type" "no_insn")]
11908)
11909
11910(define_insn "consttable_2"
11911  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_2)]
11912  "TARGET_EITHER"
11913  "*
11914  {
11915    rtx x = operands[0];
11916    making_const_table = TRUE;
11917    switch (GET_MODE_CLASS (GET_MODE (x)))
11918      {
11919      case MODE_FLOAT:
11920	arm_emit_fp16_const (x);
11921	break;
11922      default:
11923	assemble_integer (operands[0], 2, BITS_PER_WORD, 1);
11924	assemble_zeros (2);
11925	break;
11926      }
11927    return \"\";
11928  }"
11929  [(set_attr "length" "4")
11930   (set_attr "type" "no_insn")]
11931)
11932
11933(define_insn "consttable_4"
11934  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_4)]
11935  "TARGET_EITHER"
11936  "*
11937  {
11938    rtx x = operands[0];
11939    making_const_table = TRUE;
11940    scalar_float_mode float_mode;
11941    if (is_a <scalar_float_mode> (GET_MODE (x), &float_mode))
11942      assemble_real (*CONST_DOUBLE_REAL_VALUE (x), float_mode, BITS_PER_WORD);
11943    else
11944      {
11945	/* XXX: Sometimes gcc does something really dumb and ends up with
11946	   a HIGH in a constant pool entry, usually because it's trying to
11947	   load into a VFP register.  We know this will always be used in
11948	   combination with a LO_SUM which ignores the high bits, so just
11949	   strip off the HIGH.  */
11950	if (GET_CODE (x) == HIGH)
11951	  x = XEXP (x, 0);
11952        assemble_integer (x, 4, BITS_PER_WORD, 1);
11953	mark_symbol_refs_as_used (x);
11954      }
11955    return \"\";
11956  }"
11957  [(set_attr "length" "4")
11958   (set_attr "type" "no_insn")]
11959)
11960
11961(define_insn "consttable_8"
11962  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_8)]
11963  "TARGET_EITHER"
11964  "*
11965  {
11966    making_const_table = TRUE;
11967    scalar_float_mode float_mode;
11968    if (is_a <scalar_float_mode> (GET_MODE (operands[0]), &float_mode))
11969      assemble_real (*CONST_DOUBLE_REAL_VALUE (operands[0]),
11970		     float_mode, BITS_PER_WORD);
11971    else
11972      assemble_integer (operands[0], 8, BITS_PER_WORD, 1);
11973    return \"\";
11974  }"
11975  [(set_attr "length" "8")
11976   (set_attr "type" "no_insn")]
11977)
11978
11979(define_insn "consttable_16"
11980  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_16)]
11981  "TARGET_EITHER"
11982  "*
11983  {
11984    making_const_table = TRUE;
11985    scalar_float_mode float_mode;
11986    if (is_a <scalar_float_mode> (GET_MODE (operands[0]), &float_mode))
11987      assemble_real (*CONST_DOUBLE_REAL_VALUE (operands[0]),
11988		     float_mode, BITS_PER_WORD);
11989    else
11990      assemble_integer (operands[0], 16, BITS_PER_WORD, 1);
11991    return \"\";
11992  }"
11993  [(set_attr "length" "16")
11994   (set_attr "type" "no_insn")]
11995)
11996
11997;; V5 Instructions,
11998
11999(define_insn "clzsi2"
12000  [(set (match_operand:SI 0 "s_register_operand" "=r")
12001	(clz:SI (match_operand:SI 1 "s_register_operand" "r")))]
12002  "TARGET_32BIT && arm_arch5t"
12003  "clz%?\\t%0, %1"
12004  [(set_attr "predicable" "yes")
12005   (set_attr "type" "clz")])
12006
12007(define_insn "rbitsi2"
12008  [(set (match_operand:SI 0 "s_register_operand" "=r")
12009	(unspec:SI [(match_operand:SI 1 "s_register_operand" "r")] UNSPEC_RBIT))]
12010  "TARGET_32BIT && arm_arch_thumb2"
12011  "rbit%?\\t%0, %1"
12012  [(set_attr "predicable" "yes")
12013   (set_attr "type" "clz")])
12014
12015;; Keep this as a CTZ expression until after reload and then split
12016;; into RBIT + CLZ.  Since RBIT is represented as an UNSPEC it is unlikely
12017;; to fold with any other expression.
12018
12019(define_insn_and_split "ctzsi2"
12020 [(set (match_operand:SI           0 "s_register_operand" "=r")
12021       (ctz:SI (match_operand:SI  1 "s_register_operand" "r")))]
12022  "TARGET_32BIT && arm_arch_thumb2"
12023  "#"
12024  "&& reload_completed"
12025  [(const_int 0)]
12026  "
12027  emit_insn (gen_rbitsi2 (operands[0], operands[1]));
12028  emit_insn (gen_clzsi2 (operands[0], operands[0]));
12029  DONE;
12030")
12031
12032;; V5E instructions.
12033
12034(define_insn "prefetch"
12035  [(prefetch (match_operand:SI 0 "address_operand" "p")
12036	     (match_operand:SI 1 "" "")
12037	     (match_operand:SI 2 "" ""))]
12038  "TARGET_32BIT && arm_arch5te"
12039  "pld\\t%a0"
12040  [(set_attr "type" "load_4")]
12041)
12042
12043;; General predication pattern
12044
12045(define_cond_exec
12046  [(match_operator 0 "arm_comparison_operator"
12047    [(match_operand 1 "cc_register" "")
12048     (const_int 0)])]
12049  "TARGET_32BIT
12050   && (!TARGET_NO_VOLATILE_CE || !volatile_refs_p (PATTERN (insn)))"
12051  ""
12052[(set_attr "predicated" "yes")]
12053)
12054
12055(define_insn "force_register_use"
12056  [(unspec:SI [(match_operand:SI 0 "register_operand" "")] UNSPEC_REGISTER_USE)]
12057  ""
12058  "%@ %0 needed"
12059  [(set_attr "length" "0")
12060   (set_attr "type" "no_insn")]
12061)
12062
12063
12064;; Patterns for exception handling
12065
12066(define_expand "eh_return"
12067  [(use (match_operand 0 "general_operand"))]
12068  "TARGET_EITHER"
12069  "
12070  {
12071    if (TARGET_32BIT)
12072      emit_insn (gen_arm_eh_return (operands[0]));
12073    else
12074      emit_insn (gen_thumb_eh_return (operands[0]));
12075    DONE;
12076  }"
12077)
12078
12079;; We can't expand this before we know where the link register is stored.
12080(define_insn_and_split "arm_eh_return"
12081  [(unspec_volatile [(match_operand:SI 0 "s_register_operand" "r")]
12082		    VUNSPEC_EH_RETURN)
12083   (clobber (match_scratch:SI 1 "=&r"))]
12084  "TARGET_ARM"
12085  "#"
12086  "&& reload_completed"
12087  [(const_int 0)]
12088  "
12089  {
12090    arm_set_return_address (operands[0], operands[1]);
12091    DONE;
12092  }"
12093)
12094
12095
12096;; TLS support
12097
12098(define_insn "load_tp_hard"
12099  [(set (match_operand:SI 0 "register_operand" "=r")
12100	(unspec:SI [(const_int 0)] UNSPEC_TLS))]
12101  "TARGET_HARD_TP"
12102  "mrc%?\\tp15, 0, %0, c13, c0, 3\\t@ load_tp_hard"
12103  [(set_attr "predicable" "yes")
12104   (set_attr "type" "mrs")]
12105)
12106
12107;; Doesn't clobber R1-R3.  Must use r0 for the first operand.
12108(define_insn "load_tp_soft_fdpic"
12109  [(set (reg:SI 0) (unspec:SI [(const_int 0)] UNSPEC_TLS))
12110   (clobber (reg:SI FDPIC_REGNUM))
12111   (clobber (reg:SI LR_REGNUM))
12112   (clobber (reg:SI IP_REGNUM))
12113   (clobber (reg:CC CC_REGNUM))]
12114  "TARGET_SOFT_TP && TARGET_FDPIC"
12115  "bl\\t__aeabi_read_tp\\t@ load_tp_soft"
12116  [(set_attr "conds" "clob")
12117   (set_attr "type" "branch")]
12118)
12119
12120;; Doesn't clobber R1-R3.  Must use r0 for the first operand.
12121(define_insn "load_tp_soft"
12122  [(set (reg:SI 0) (unspec:SI [(const_int 0)] UNSPEC_TLS))
12123   (clobber (reg:SI LR_REGNUM))
12124   (clobber (reg:SI IP_REGNUM))
12125   (clobber (reg:CC CC_REGNUM))]
12126  "TARGET_SOFT_TP && !TARGET_FDPIC"
12127  "bl\\t__aeabi_read_tp\\t@ load_tp_soft"
12128  [(set_attr "conds" "clob")
12129   (set_attr "type" "branch")]
12130)
12131
12132;; tls descriptor call
12133(define_insn "tlscall"
12134  [(set (reg:SI R0_REGNUM)
12135        (unspec:SI [(reg:SI R0_REGNUM)
12136                    (match_operand:SI 0 "" "X")
12137	            (match_operand 1 "" "")] UNSPEC_TLS))
12138   (clobber (reg:SI R1_REGNUM))
12139   (clobber (reg:SI LR_REGNUM))
12140   (clobber (reg:SI CC_REGNUM))]
12141  "TARGET_GNU2_TLS"
12142  {
12143    targetm.asm_out.internal_label (asm_out_file, "LPIC",
12144				    INTVAL (operands[1]));
12145    return "bl\\t%c0(tlscall)";
12146  }
12147  [(set_attr "conds" "clob")
12148   (set_attr "length" "4")
12149   (set_attr "type" "branch")]
12150)
12151
12152;; For thread pointer builtin
12153(define_expand "get_thread_pointersi"
12154  [(match_operand:SI 0 "s_register_operand")]
12155 ""
12156 "
12157 {
12158   arm_load_tp (operands[0]);
12159   DONE;
12160 }")
12161
12162;;
12163
12164;; We only care about the lower 16 bits of the constant
12165;; being inserted into the upper 16 bits of the register.
12166(define_insn "*arm_movtas_ze"
12167  [(set (zero_extract:SI (match_operand:SI 0 "s_register_operand" "+r,r")
12168                   (const_int 16)
12169                   (const_int 16))
12170        (match_operand:SI 1 "const_int_operand" ""))]
12171  "TARGET_HAVE_MOVT"
12172  "@
12173   movt%?\t%0, %L1
12174   movt\t%0, %L1"
12175 [(set_attr "arch" "32,v8mb")
12176  (set_attr "predicable" "yes")
12177  (set_attr "length" "4")
12178  (set_attr "type" "alu_sreg")]
12179)
12180
12181(define_insn "*arm_rev"
12182  [(set (match_operand:SI 0 "s_register_operand" "=l,l,r")
12183	(bswap:SI (match_operand:SI 1 "s_register_operand" "l,l,r")))]
12184  "arm_arch6"
12185  "@
12186   rev\t%0, %1
12187   rev%?\t%0, %1
12188   rev%?\t%0, %1"
12189  [(set_attr "arch" "t1,t2,32")
12190   (set_attr "length" "2,2,4")
12191   (set_attr "predicable" "no,yes,yes")
12192   (set_attr "type" "rev")]
12193)
12194
12195(define_expand "arm_legacy_rev"
12196  [(set (match_operand:SI 2 "s_register_operand")
12197	(xor:SI (rotatert:SI (match_operand:SI 1 "s_register_operand")
12198			     (const_int 16))
12199		(match_dup 1)))
12200   (set (match_dup 2)
12201	(lshiftrt:SI (match_dup 2)
12202		     (const_int 8)))
12203   (set (match_operand:SI 3 "s_register_operand")
12204	(rotatert:SI (match_dup 1)
12205		     (const_int 8)))
12206   (set (match_dup 2)
12207	(and:SI (match_dup 2)
12208		(const_int -65281)))
12209   (set (match_operand:SI 0 "s_register_operand")
12210	(xor:SI (match_dup 3)
12211		(match_dup 2)))]
12212  "TARGET_32BIT"
12213  ""
12214)
12215
12216;; Reuse temporaries to keep register pressure down.
12217(define_expand "thumb_legacy_rev"
12218  [(set (match_operand:SI 2 "s_register_operand")
12219     (ashift:SI (match_operand:SI 1 "s_register_operand")
12220                (const_int 24)))
12221   (set (match_operand:SI 3 "s_register_operand")
12222     (lshiftrt:SI (match_dup 1)
12223		  (const_int 24)))
12224   (set (match_dup 3)
12225     (ior:SI (match_dup 3)
12226	     (match_dup 2)))
12227   (set (match_operand:SI 4 "s_register_operand")
12228     (const_int 16))
12229   (set (match_operand:SI 5 "s_register_operand")
12230     (rotatert:SI (match_dup 1)
12231		  (match_dup 4)))
12232   (set (match_dup 2)
12233     (ashift:SI (match_dup 5)
12234                (const_int 24)))
12235   (set (match_dup 5)
12236     (lshiftrt:SI (match_dup 5)
12237		  (const_int 24)))
12238   (set (match_dup 5)
12239     (ior:SI (match_dup 5)
12240	     (match_dup 2)))
12241   (set (match_dup 5)
12242     (rotatert:SI (match_dup 5)
12243		  (match_dup 4)))
12244   (set (match_operand:SI 0 "s_register_operand")
12245     (ior:SI (match_dup 5)
12246             (match_dup 3)))]
12247  "TARGET_THUMB"
12248  ""
12249)
12250
12251;; ARM-specific expansion of signed mod by power of 2
12252;; using conditional negate.
12253;; For r0 % n where n is a power of 2 produce:
12254;; rsbs    r1, r0, #0
12255;; and     r0, r0, #(n - 1)
12256;; and     r1, r1, #(n - 1)
12257;; rsbpl   r0, r1, #0
12258
12259(define_expand "modsi3"
12260  [(match_operand:SI 0 "register_operand")
12261   (match_operand:SI 1 "register_operand")
12262   (match_operand:SI 2 "const_int_operand")]
12263  "TARGET_32BIT"
12264  {
12265    HOST_WIDE_INT val = INTVAL (operands[2]);
12266
12267    if (val <= 0
12268       || exact_log2 (val) <= 0)
12269      FAIL;
12270
12271    rtx mask = GEN_INT (val - 1);
12272
12273    /* In the special case of x0 % 2 we can do the even shorter:
12274	cmp     r0, #0
12275	and     r0, r0, #1
12276	rsblt   r0, r0, #0.  */
12277
12278    if (val == 2)
12279      {
12280	rtx cc_reg = arm_gen_compare_reg (LT,
12281					  operands[1], const0_rtx, NULL_RTX);
12282	rtx cond = gen_rtx_LT (SImode, cc_reg, const0_rtx);
12283	rtx masked = gen_reg_rtx (SImode);
12284
12285	emit_insn (gen_andsi3 (masked, operands[1], mask));
12286	emit_move_insn (operands[0],
12287			gen_rtx_IF_THEN_ELSE (SImode, cond,
12288					      gen_rtx_NEG (SImode,
12289							   masked),
12290					      masked));
12291	DONE;
12292      }
12293
12294    rtx neg_op = gen_reg_rtx (SImode);
12295    rtx_insn *insn = emit_insn (gen_subsi3_compare0 (neg_op, const0_rtx,
12296						      operands[1]));
12297
12298    /* Extract the condition register and mode.  */
12299    rtx cmp = XVECEXP (PATTERN (insn), 0, 0);
12300    rtx cc_reg = SET_DEST (cmp);
12301    rtx cond = gen_rtx_GE (SImode, cc_reg, const0_rtx);
12302
12303    emit_insn (gen_andsi3 (operands[0], operands[1], mask));
12304
12305    rtx masked_neg = gen_reg_rtx (SImode);
12306    emit_insn (gen_andsi3 (masked_neg, neg_op, mask));
12307
12308    /* We want a conditional negate here, but emitting COND_EXEC rtxes
12309       during expand does not always work.  Do an IF_THEN_ELSE instead.  */
12310    emit_move_insn (operands[0],
12311		    gen_rtx_IF_THEN_ELSE (SImode, cond,
12312					  gen_rtx_NEG (SImode, masked_neg),
12313					  operands[0]));
12314
12315
12316    DONE;
12317  }
12318)
12319
12320(define_expand "bswapsi2"
12321  [(set (match_operand:SI 0 "s_register_operand")
12322	(bswap:SI (match_operand:SI 1 "s_register_operand")))]
12323"TARGET_EITHER && (arm_arch6 || !optimize_size)"
12324"
12325    if (!arm_arch6)
12326      {
12327	rtx op2 = gen_reg_rtx (SImode);
12328	rtx op3 = gen_reg_rtx (SImode);
12329
12330	if (TARGET_THUMB)
12331	  {
12332	    rtx op4 = gen_reg_rtx (SImode);
12333	    rtx op5 = gen_reg_rtx (SImode);
12334
12335	    emit_insn (gen_thumb_legacy_rev (operands[0], operands[1],
12336					     op2, op3, op4, op5));
12337	  }
12338	else
12339	  {
12340	    emit_insn (gen_arm_legacy_rev (operands[0], operands[1],
12341					   op2, op3));
12342	  }
12343
12344	DONE;
12345      }
12346  "
12347)
12348
12349;; bswap16 patterns: use revsh and rev16 instructions for the signed
12350;; and unsigned variants, respectively. For rev16, expose
12351;; byte-swapping in the lower 16 bits only.
12352(define_insn "*arm_revsh"
12353  [(set (match_operand:SI 0 "s_register_operand" "=l,l,r")
12354	(sign_extend:SI (bswap:HI (match_operand:HI 1 "s_register_operand" "l,l,r"))))]
12355  "arm_arch6"
12356  "@
12357  revsh\t%0, %1
12358  revsh%?\t%0, %1
12359  revsh%?\t%0, %1"
12360  [(set_attr "arch" "t1,t2,32")
12361   (set_attr "length" "2,2,4")
12362   (set_attr "type" "rev")]
12363)
12364
12365(define_insn "*arm_rev16"
12366  [(set (match_operand:HI 0 "s_register_operand" "=l,l,r")
12367	(bswap:HI (match_operand:HI 1 "s_register_operand" "l,l,r")))]
12368  "arm_arch6"
12369  "@
12370   rev16\t%0, %1
12371   rev16%?\t%0, %1
12372   rev16%?\t%0, %1"
12373  [(set_attr "arch" "t1,t2,32")
12374   (set_attr "length" "2,2,4")
12375   (set_attr "type" "rev")]
12376)
12377
12378;; There are no canonicalisation rules for the position of the lshiftrt, ashift
12379;; operations within an IOR/AND RTX, therefore we have two patterns matching
12380;; each valid permutation.
12381
12382(define_insn "arm_rev16si2"
12383  [(set (match_operand:SI 0 "register_operand" "=l,l,r")
12384        (ior:SI (and:SI (ashift:SI (match_operand:SI 1 "register_operand" "l,l,r")
12385                                   (const_int 8))
12386                        (match_operand:SI 3 "const_int_operand" "n,n,n"))
12387                (and:SI (lshiftrt:SI (match_dup 1)
12388                                     (const_int 8))
12389                        (match_operand:SI 2 "const_int_operand" "n,n,n"))))]
12390  "arm_arch6
12391   && aarch_rev16_shleft_mask_imm_p (operands[3], SImode)
12392   && aarch_rev16_shright_mask_imm_p (operands[2], SImode)"
12393  "rev16\\t%0, %1"
12394  [(set_attr "arch" "t1,t2,32")
12395   (set_attr "length" "2,2,4")
12396   (set_attr "type" "rev")]
12397)
12398
12399(define_insn "arm_rev16si2_alt"
12400  [(set (match_operand:SI 0 "register_operand" "=l,l,r")
12401        (ior:SI (and:SI (lshiftrt:SI (match_operand:SI 1 "register_operand" "l,l,r")
12402                                     (const_int 8))
12403                        (match_operand:SI 2 "const_int_operand" "n,n,n"))
12404                (and:SI (ashift:SI (match_dup 1)
12405                                   (const_int 8))
12406                        (match_operand:SI 3 "const_int_operand" "n,n,n"))))]
12407  "arm_arch6
12408   && aarch_rev16_shleft_mask_imm_p (operands[3], SImode)
12409   && aarch_rev16_shright_mask_imm_p (operands[2], SImode)"
12410  "rev16\\t%0, %1"
12411  [(set_attr "arch" "t1,t2,32")
12412   (set_attr "length" "2,2,4")
12413   (set_attr "type" "rev")]
12414)
12415
12416(define_expand "bswaphi2"
12417  [(set (match_operand:HI 0 "s_register_operand")
12418	(bswap:HI (match_operand:HI 1 "s_register_operand")))]
12419"arm_arch6"
12420""
12421)
12422
12423;; Patterns for LDRD/STRD in Thumb2 mode
12424
12425(define_insn "*thumb2_ldrd"
12426  [(set (match_operand:SI 0 "s_register_operand" "=r")
12427        (mem:SI (plus:SI (match_operand:SI 1 "s_register_operand" "rk")
12428                         (match_operand:SI 2 "ldrd_strd_offset_operand" "Do"))))
12429   (set (match_operand:SI 3 "s_register_operand" "=r")
12430        (mem:SI (plus:SI (match_dup 1)
12431                         (match_operand:SI 4 "const_int_operand" ""))))]
12432  "TARGET_LDRD && TARGET_THUMB2 && reload_completed
12433     && ((INTVAL (operands[2]) + 4) == INTVAL (operands[4]))
12434     && (operands_ok_ldrd_strd (operands[0], operands[3],
12435                                  operands[1], INTVAL (operands[2]),
12436                                  false, true))"
12437  "ldrd%?\t%0, %3, [%1, %2]"
12438  [(set_attr "type" "load_8")
12439   (set_attr "predicable" "yes")])
12440
12441(define_insn "*thumb2_ldrd_base"
12442  [(set (match_operand:SI 0 "s_register_operand" "=r")
12443        (mem:SI (match_operand:SI 1 "s_register_operand" "rk")))
12444   (set (match_operand:SI 2 "s_register_operand" "=r")
12445        (mem:SI (plus:SI (match_dup 1)
12446                         (const_int 4))))]
12447  "TARGET_LDRD && TARGET_THUMB2 && reload_completed
12448     && (operands_ok_ldrd_strd (operands[0], operands[2],
12449                                  operands[1], 0, false, true))"
12450  "ldrd%?\t%0, %2, [%1]"
12451  [(set_attr "type" "load_8")
12452   (set_attr "predicable" "yes")])
12453
12454(define_insn "*thumb2_ldrd_base_neg"
12455  [(set (match_operand:SI 0 "s_register_operand" "=r")
12456	(mem:SI (plus:SI (match_operand:SI 1 "s_register_operand" "rk")
12457                         (const_int -4))))
12458   (set (match_operand:SI 2 "s_register_operand" "=r")
12459        (mem:SI (match_dup 1)))]
12460  "TARGET_LDRD && TARGET_THUMB2 && reload_completed
12461     && (operands_ok_ldrd_strd (operands[0], operands[2],
12462                                  operands[1], -4, false, true))"
12463  "ldrd%?\t%0, %2, [%1, #-4]"
12464  [(set_attr "type" "load_8")
12465   (set_attr "predicable" "yes")])
12466
12467(define_insn "*thumb2_strd"
12468  [(set (mem:SI (plus:SI (match_operand:SI 0 "s_register_operand" "rk")
12469                         (match_operand:SI 1 "ldrd_strd_offset_operand" "Do")))
12470        (match_operand:SI 2 "s_register_operand" "r"))
12471   (set (mem:SI (plus:SI (match_dup 0)
12472                         (match_operand:SI 3 "const_int_operand" "")))
12473        (match_operand:SI 4 "s_register_operand" "r"))]
12474  "TARGET_LDRD && TARGET_THUMB2 && reload_completed
12475     && ((INTVAL (operands[1]) + 4) == INTVAL (operands[3]))
12476     && (operands_ok_ldrd_strd (operands[2], operands[4],
12477                                  operands[0], INTVAL (operands[1]),
12478                                  false, false))"
12479  "strd%?\t%2, %4, [%0, %1]"
12480  [(set_attr "type" "store_8")
12481   (set_attr "predicable" "yes")])
12482
12483(define_insn "*thumb2_strd_base"
12484  [(set (mem:SI (match_operand:SI 0 "s_register_operand" "rk"))
12485        (match_operand:SI 1 "s_register_operand" "r"))
12486   (set (mem:SI (plus:SI (match_dup 0)
12487                         (const_int 4)))
12488        (match_operand:SI 2 "s_register_operand" "r"))]
12489  "TARGET_LDRD && TARGET_THUMB2 && reload_completed
12490     && (operands_ok_ldrd_strd (operands[1], operands[2],
12491                                  operands[0], 0, false, false))"
12492  "strd%?\t%1, %2, [%0]"
12493  [(set_attr "type" "store_8")
12494   (set_attr "predicable" "yes")])
12495
12496(define_insn "*thumb2_strd_base_neg"
12497  [(set (mem:SI (plus:SI (match_operand:SI 0 "s_register_operand" "rk")
12498                         (const_int -4)))
12499        (match_operand:SI 1 "s_register_operand" "r"))
12500   (set (mem:SI (match_dup 0))
12501        (match_operand:SI 2 "s_register_operand" "r"))]
12502  "TARGET_LDRD && TARGET_THUMB2 && reload_completed
12503     && (operands_ok_ldrd_strd (operands[1], operands[2],
12504                                  operands[0], -4, false, false))"
12505  "strd%?\t%1, %2, [%0, #-4]"
12506  [(set_attr "type" "store_8")
12507   (set_attr "predicable" "yes")])
12508
12509;; ARMv8 CRC32 instructions.
12510(define_insn "arm_<crc_variant>"
12511  [(set (match_operand:SI 0 "s_register_operand" "=r")
12512        (unspec:SI [(match_operand:SI 1 "s_register_operand" "r")
12513                    (match_operand:<crc_mode> 2 "s_register_operand" "r")]
12514         CRC))]
12515  "TARGET_CRC32"
12516  "<crc_variant>\\t%0, %1, %2"
12517  [(set_attr "type" "crc")
12518   (set_attr "conds" "unconditional")]
12519)
12520
12521;; Load the load/store double peephole optimizations.
12522(include "ldrdstrd.md")
12523
12524;; Load the load/store multiple patterns
12525(include "ldmstm.md")
12526
12527;; Patterns in ldmstm.md don't cover more than 4 registers. This pattern covers
12528;; large lists without explicit writeback generated for APCS_FRAME epilogue.
12529;; The operands are validated through the load_multiple_operation
12530;; match_parallel predicate rather than through constraints so enable it only
12531;; after reload.
12532(define_insn "*load_multiple"
12533  [(match_parallel 0 "load_multiple_operation"
12534    [(set (match_operand:SI 2 "s_register_operand" "=rk")
12535          (mem:SI (match_operand:SI 1 "s_register_operand" "rk")))
12536        ])]
12537  "TARGET_32BIT && reload_completed"
12538  "*
12539  {
12540    arm_output_multireg_pop (operands, /*return_pc=*/false,
12541                                       /*cond=*/const_true_rtx,
12542                                       /*reverse=*/false,
12543                                       /*update=*/false);
12544    return \"\";
12545  }
12546  "
12547  [(set_attr "predicable" "yes")]
12548)
12549
12550(define_expand "copysignsf3"
12551  [(match_operand:SF 0 "register_operand")
12552   (match_operand:SF 1 "register_operand")
12553   (match_operand:SF 2 "register_operand")]
12554  "TARGET_SOFT_FLOAT && arm_arch_thumb2"
12555  "{
12556     emit_move_insn (operands[0], operands[2]);
12557     emit_insn (gen_insv_t2 (simplify_gen_subreg (SImode, operands[0], SFmode, 0),
12558		GEN_INT (31), GEN_INT (0),
12559		simplify_gen_subreg (SImode, operands[1], SFmode, 0)));
12560     DONE;
12561  }"
12562)
12563
12564(define_expand "copysigndf3"
12565  [(match_operand:DF 0 "register_operand")
12566   (match_operand:DF 1 "register_operand")
12567   (match_operand:DF 2 "register_operand")]
12568  "TARGET_SOFT_FLOAT && arm_arch_thumb2"
12569  "{
12570     rtx op0_low = gen_lowpart (SImode, operands[0]);
12571     rtx op0_high = gen_highpart (SImode, operands[0]);
12572     rtx op1_low = gen_lowpart (SImode, operands[1]);
12573     rtx op1_high = gen_highpart (SImode, operands[1]);
12574     rtx op2_high = gen_highpart (SImode, operands[2]);
12575
12576     rtx scratch1 = gen_reg_rtx (SImode);
12577     rtx scratch2 = gen_reg_rtx (SImode);
12578     emit_move_insn (scratch1, op2_high);
12579     emit_move_insn (scratch2, op1_high);
12580
12581     emit_insn(gen_rtx_SET(scratch1,
12582			   gen_rtx_LSHIFTRT (SImode, op2_high, GEN_INT(31))));
12583     emit_insn(gen_insv_t2(scratch2, GEN_INT(1), GEN_INT(31), scratch1));
12584     emit_move_insn (op0_low, op1_low);
12585     emit_move_insn (op0_high, scratch2);
12586
12587     DONE;
12588  }"
12589)
12590
12591;; movmisalign patterns for HImode and SImode.
12592(define_expand "movmisalign<mode>"
12593  [(match_operand:HSI 0 "general_operand")
12594   (match_operand:HSI 1 "general_operand")]
12595  "unaligned_access"
12596{
12597  /* This pattern is not permitted to fail during expansion: if both arguments
12598     are non-registers (e.g. memory := constant), force operand 1 into a
12599     register.  */
12600  rtx (* gen_unaligned_load)(rtx, rtx);
12601  rtx tmp_dest = operands[0];
12602  if (!s_register_operand (operands[0], <MODE>mode)
12603      && !s_register_operand (operands[1], <MODE>mode))
12604    operands[1] = force_reg (<MODE>mode, operands[1]);
12605
12606  if (<MODE>mode == HImode)
12607   {
12608    gen_unaligned_load = gen_unaligned_loadhiu;
12609    tmp_dest = gen_reg_rtx (SImode);
12610   }
12611  else
12612    gen_unaligned_load = gen_unaligned_loadsi;
12613
12614  if (MEM_P (operands[1]))
12615   {
12616    emit_insn (gen_unaligned_load (tmp_dest, operands[1]));
12617    if (<MODE>mode == HImode)
12618      emit_move_insn (operands[0], gen_lowpart (HImode, tmp_dest));
12619   }
12620  else
12621    emit_insn (gen_unaligned_store<mode> (operands[0], operands[1]));
12622
12623  DONE;
12624})
12625
12626(define_insn "arm_<cdp>"
12627  [(unspec_volatile [(match_operand:SI 0 "immediate_operand" "n")
12628		     (match_operand:SI 1 "immediate_operand" "n")
12629		     (match_operand:SI 2 "immediate_operand" "n")
12630		     (match_operand:SI 3 "immediate_operand" "n")
12631		     (match_operand:SI 4 "immediate_operand" "n")
12632		     (match_operand:SI 5 "immediate_operand" "n")] CDPI)]
12633  "arm_coproc_builtin_available (VUNSPEC_<CDP>)"
12634{
12635  arm_const_bounds (operands[0], 0, 16);
12636  arm_const_bounds (operands[1], 0, 16);
12637  arm_const_bounds (operands[2], 0, (1 << 5));
12638  arm_const_bounds (operands[3], 0, (1 << 5));
12639  arm_const_bounds (operands[4], 0, (1 << 5));
12640  arm_const_bounds (operands[5], 0, 8);
12641  return "<cdp>\\tp%c0, %1, CR%c2, CR%c3, CR%c4, %5";
12642}
12643  [(set_attr "length" "4")
12644   (set_attr "type" "coproc")])
12645
12646(define_insn "*ldc"
12647  [(unspec_volatile [(match_operand:SI 0 "immediate_operand" "n")
12648		     (match_operand:SI 1 "immediate_operand" "n")
12649		     (match_operand:SI 2 "memory_operand" "Uz")] LDCI)]
12650  "arm_coproc_builtin_available (VUNSPEC_<LDC>)"
12651{
12652  arm_const_bounds (operands[0], 0, 16);
12653  arm_const_bounds (operands[1], 0, (1 << 5));
12654  return "<ldc>\\tp%c0, CR%c1, %2";
12655}
12656  [(set_attr "length" "4")
12657   (set_attr "type" "coproc")])
12658
12659(define_insn "*stc"
12660  [(unspec_volatile [(match_operand:SI 0 "immediate_operand" "n")
12661		     (match_operand:SI 1 "immediate_operand" "n")
12662		     (match_operand:SI 2 "memory_operand" "=Uz")] STCI)]
12663  "arm_coproc_builtin_available (VUNSPEC_<STC>)"
12664{
12665  arm_const_bounds (operands[0], 0, 16);
12666  arm_const_bounds (operands[1], 0, (1 << 5));
12667  return "<stc>\\tp%c0, CR%c1, %2";
12668}
12669  [(set_attr "length" "4")
12670   (set_attr "type" "coproc")])
12671
12672(define_expand "arm_<ldc>"
12673  [(unspec_volatile [(match_operand:SI 0 "immediate_operand")
12674		     (match_operand:SI 1 "immediate_operand")
12675		     (mem:SI (match_operand:SI 2 "s_register_operand"))] LDCI)]
12676  "arm_coproc_builtin_available (VUNSPEC_<LDC>)")
12677
12678(define_expand "arm_<stc>"
12679  [(unspec_volatile [(match_operand:SI 0 "immediate_operand")
12680		     (match_operand:SI 1 "immediate_operand")
12681		     (mem:SI (match_operand:SI 2 "s_register_operand"))] STCI)]
12682  "arm_coproc_builtin_available (VUNSPEC_<STC>)")
12683
12684(define_insn "arm_<mcr>"
12685  [(unspec_volatile [(match_operand:SI 0 "immediate_operand" "n")
12686		     (match_operand:SI 1 "immediate_operand" "n")
12687		     (match_operand:SI 2 "s_register_operand" "r")
12688		     (match_operand:SI 3 "immediate_operand" "n")
12689		     (match_operand:SI 4 "immediate_operand" "n")
12690		     (match_operand:SI 5 "immediate_operand" "n")] MCRI)
12691   (use (match_dup 2))]
12692  "arm_coproc_builtin_available (VUNSPEC_<MCR>)"
12693{
12694  arm_const_bounds (operands[0], 0, 16);
12695  arm_const_bounds (operands[1], 0, 8);
12696  arm_const_bounds (operands[3], 0, (1 << 5));
12697  arm_const_bounds (operands[4], 0, (1 << 5));
12698  arm_const_bounds (operands[5], 0, 8);
12699  return "<mcr>\\tp%c0, %1, %2, CR%c3, CR%c4, %5";
12700}
12701  [(set_attr "length" "4")
12702   (set_attr "type" "coproc")])
12703
12704(define_insn "arm_<mrc>"
12705  [(set (match_operand:SI 0 "s_register_operand" "=r")
12706	(unspec_volatile:SI [(match_operand:SI 1 "immediate_operand" "n")
12707			  (match_operand:SI 2 "immediate_operand" "n")
12708			  (match_operand:SI 3 "immediate_operand" "n")
12709			  (match_operand:SI 4 "immediate_operand" "n")
12710			  (match_operand:SI 5 "immediate_operand" "n")] MRCI))]
12711  "arm_coproc_builtin_available (VUNSPEC_<MRC>)"
12712{
12713  arm_const_bounds (operands[1], 0, 16);
12714  arm_const_bounds (operands[2], 0, 8);
12715  arm_const_bounds (operands[3], 0, (1 << 5));
12716  arm_const_bounds (operands[4], 0, (1 << 5));
12717  arm_const_bounds (operands[5], 0, 8);
12718  return "<mrc>\\tp%c1, %2, %0, CR%c3, CR%c4, %5";
12719}
12720  [(set_attr "length" "4")
12721   (set_attr "type" "coproc")])
12722
12723(define_insn "arm_<mcrr>"
12724  [(unspec_volatile [(match_operand:SI 0 "immediate_operand" "n")
12725		     (match_operand:SI 1 "immediate_operand" "n")
12726		     (match_operand:DI 2 "s_register_operand" "r")
12727		     (match_operand:SI 3 "immediate_operand" "n")] MCRRI)
12728   (use (match_dup 2))]
12729  "arm_coproc_builtin_available (VUNSPEC_<MCRR>)"
12730{
12731  arm_const_bounds (operands[0], 0, 16);
12732  arm_const_bounds (operands[1], 0, 8);
12733  arm_const_bounds (operands[3], 0, (1 << 5));
12734  return "<mcrr>\\tp%c0, %1, %Q2, %R2, CR%c3";
12735}
12736  [(set_attr "length" "4")
12737   (set_attr "type" "coproc")])
12738
12739(define_insn "arm_<mrrc>"
12740  [(set (match_operand:DI 0 "s_register_operand" "=r")
12741	(unspec_volatile:DI [(match_operand:SI 1 "immediate_operand" "n")
12742			  (match_operand:SI 2 "immediate_operand" "n")
12743			  (match_operand:SI 3 "immediate_operand" "n")] MRRCI))]
12744  "arm_coproc_builtin_available (VUNSPEC_<MRRC>)"
12745{
12746  arm_const_bounds (operands[1], 0, 16);
12747  arm_const_bounds (operands[2], 0, 8);
12748  arm_const_bounds (operands[3], 0, (1 << 5));
12749  return "<mrrc>\\tp%c1, %2, %Q0, %R0, CR%c3";
12750}
12751  [(set_attr "length" "4")
12752   (set_attr "type" "coproc")])
12753
12754(define_expand "speculation_barrier"
12755  [(unspec_volatile [(const_int 0)] VUNSPEC_SPECULATION_BARRIER)]
12756  "TARGET_EITHER"
12757  "
12758  /* For thumb1 (except Armv8 derivatives), and for pre-Armv7 we don't
12759     have a usable barrier (and probably don't need one in practice).
12760     But to be safe if such code is run on later architectures, call a
12761     helper function in libgcc that will do the thing for the active
12762     system.  */
12763  if (!(arm_arch7 || arm_arch8))
12764    {
12765      arm_emit_speculation_barrier_function ();
12766      DONE;
12767    }
12768  "
12769)
12770
12771;; Generate a hard speculation barrier when we have not enabled speculation
12772;; tracking.
12773(define_insn "*speculation_barrier_insn"
12774  [(unspec_volatile [(const_int 0)] VUNSPEC_SPECULATION_BARRIER)]
12775  "arm_arch7 || arm_arch8"
12776  "isb\;dsb\\tsy"
12777  [(set_attr "type" "block")
12778   (set_attr "length" "8")]
12779)
12780
12781;; Vector bits common to IWMMXT, Neon and MVE
12782(include "vec-common.md")
12783;; Load the Intel Wireless Multimedia Extension patterns
12784(include "iwmmxt.md")
12785;; Load the VFP co-processor patterns
12786(include "vfp.md")
12787;; Thumb-1 patterns
12788(include "thumb1.md")
12789;; Thumb-2 patterns
12790(include "thumb2.md")
12791;; Neon patterns
12792(include "neon.md")
12793;; Crypto patterns
12794(include "crypto.md")
12795;; Synchronization Primitives
12796(include "sync.md")
12797;; Fixed-point patterns
12798(include "arm-fixed.md")
12799;; M-profile Vector Extension
12800(include "mve.md")
12801