* arm.c (arm_cirrus_insn_p): Delete.
[official-gcc.git] / gcc / config / arm / arm.md
blob52bdb398d7d5616552ff74500cf4a84f4c3dd524
1 ;;- Machine description for ARM for GNU compiler
2 ;;  Copyright 1991, 1993, 1994, 1995, 1996, 1996, 1997, 1998, 1999, 2000,
3 ;;  2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011, 2012
4 ;;  Free Software Foundation, Inc.
5 ;;  Contributed by Pieter `Tiggr' Schoenmakers (rcpieter@win.tue.nl)
6 ;;  and Martin Simmons (@harleqn.co.uk).
7 ;;  More major hacks by Richard Earnshaw (rearnsha@arm.com).
9 ;; This file is part of GCC.
11 ;; GCC is free software; you can redistribute it and/or modify it
12 ;; under the terms of the GNU General Public License as published
13 ;; by the Free Software Foundation; either version 3, or (at your
14 ;; option) any later version.
16 ;; GCC is distributed in the hope that it will be useful, but WITHOUT
17 ;; ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
18 ;; or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public
19 ;; License for more details.
21 ;; You should have received a copy of the GNU General Public License
22 ;; along with GCC; see the file COPYING3.  If not see
23 ;; <http://www.gnu.org/licenses/>.
25 ;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
28 ;;---------------------------------------------------------------------------
29 ;; Constants
31 ;; Register numbers
32 (define_constants
33   [(R0_REGNUM        0)         ; First CORE register
34    (R1_REGNUM        1)         ; Second CORE 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    (CC_REGNUM       24)         ; Condition code pseudo register
40    (LAST_ARM_REGNUM 15)         ;
41    (FPA_F0_REGNUM   16)         ; FIRST_FPA_REGNUM
42    (FPA_F7_REGNUM   23)         ; LAST_FPA_REGNUM
43   ]
45 ;; 3rd operand to select_dominance_cc_mode
46 (define_constants
47   [(DOM_CC_X_AND_Y  0)
48    (DOM_CC_NX_OR_Y  1)
49    (DOM_CC_X_OR_Y   2)
50   ]
52 ;; conditional compare combination
53 (define_constants
54   [(CMP_CMP 0)
55    (CMN_CMP 1)
56    (CMP_CMN 2)
57    (CMN_CMN 3)
58    (NUM_OF_COND_CMP 4)
59   ]
62 ;; UNSPEC Usage:
63 ;; Note: sin and cos are no-longer used.
64 ;; Unspec enumerators for Neon are defined in neon.md.
65 ;; Unspec enumerators for iwmmxt2 are defined in iwmmxt2.md
67 (define_c_enum "unspec" [
68   UNSPEC_SIN            ; `sin' operation (MODE_FLOAT):
69                         ;   operand 0 is the result,
70                         ;   operand 1 the parameter.
71   UNPSEC_COS            ; `cos' operation (MODE_FLOAT):
72                         ;   operand 0 is the result,
73                         ;   operand 1 the parameter.
74   UNSPEC_PUSH_MULT      ; `push multiple' operation:
75                         ;   operand 0 is the first register,
76                         ;   subsequent registers are in parallel (use ...)
77                         ;   expressions.
78   UNSPEC_PIC_SYM        ; A symbol that has been treated properly for pic
79                         ; usage, that is, we will add the pic_register
80                         ; value to it before trying to dereference it.
81   UNSPEC_PIC_BASE       ; Add PC and all but the last operand together,
82                         ; The last operand is the number of a PIC_LABEL
83                         ; that points at the containing instruction.
84   UNSPEC_PRLG_STK       ; A special barrier that prevents frame accesses
85                         ; being scheduled before the stack adjustment insn.
86   UNSPEC_PROLOGUE_USE   ; As USE insns are not meaningful after reload,
87                         ; this unspec is used to prevent the deletion of
88                         ; instructions setting registers for EH handling
89                         ; and stack frame generation.  Operand 0 is the
90                         ; register to "use".
91   UNSPEC_CHECK_ARCH     ; Set CCs to indicate 26-bit or 32-bit mode.
92   UNSPEC_WSHUFH         ; Used by the intrinsic form of the iWMMXt WSHUFH instruction.
93   UNSPEC_WACC           ; Used by the intrinsic form of the iWMMXt WACC instruction.
94   UNSPEC_TMOVMSK        ; Used by the intrinsic form of the iWMMXt TMOVMSK instruction.
95   UNSPEC_WSAD           ; Used by the intrinsic form of the iWMMXt WSAD instruction.
96   UNSPEC_WSADZ          ; Used by the intrinsic form of the iWMMXt WSADZ instruction.
97   UNSPEC_WMACS          ; Used by the intrinsic form of the iWMMXt WMACS instruction.
98   UNSPEC_WMACU          ; Used by the intrinsic form of the iWMMXt WMACU instruction.
99   UNSPEC_WMACSZ         ; Used by the intrinsic form of the iWMMXt WMACSZ instruction.
100   UNSPEC_WMACUZ         ; Used by the intrinsic form of the iWMMXt WMACUZ instruction.
101   UNSPEC_CLRDI          ; Used by the intrinsic form of the iWMMXt CLRDI instruction.
102   UNSPEC_WALIGNI        ; Used by the intrinsic form of the iWMMXt WALIGN instruction.
103   UNSPEC_TLS            ; A symbol that has been treated properly for TLS usage.
104   UNSPEC_PIC_LABEL      ; A label used for PIC access that does not appear in the
105                         ; instruction stream.
106   UNSPEC_PIC_OFFSET     ; A symbolic 12-bit OFFSET that has been treated
107                         ; correctly for PIC usage.
108   UNSPEC_GOTSYM_OFF     ; The offset of the start of the GOT from a
109                         ; a given symbolic address.
110   UNSPEC_THUMB1_CASESI  ; A Thumb1 compressed dispatch-table call.
111   UNSPEC_RBIT           ; rbit operation.
112   UNSPEC_SYMBOL_OFFSET  ; The offset of the start of the symbol from
113                         ; another symbolic address.
114   UNSPEC_MEMORY_BARRIER ; Represent a memory barrier.
115   UNSPEC_UNALIGNED_LOAD ; Used to represent ldr/ldrh instructions that access
116                         ; unaligned locations, on architectures which support
117                         ; that.
118   UNSPEC_UNALIGNED_STORE ; Same for str/strh.
119   UNSPEC_PIC_UNIFIED    ; Create a common pic addressing form.
120   UNSPEC_LL             ; Represent an unpaired load-register-exclusive.
123 ;; UNSPEC_VOLATILE Usage:
125 (define_c_enum "unspecv" [
126   VUNSPEC_BLOCKAGE      ; `blockage' insn to prevent scheduling across an
127                         ;   insn in the code.
128   VUNSPEC_EPILOGUE      ; `epilogue' insn, used to represent any part of the
129                         ;   instruction epilogue sequence that isn't expanded
130                         ;   into normal RTL.  Used for both normal and sibcall
131                         ;   epilogues.
132   VUNSPEC_THUMB1_INTERWORK ; `prologue_thumb1_interwork' insn, used to swap
133                         ;   modes from arm to thumb.
134   VUNSPEC_ALIGN         ; `align' insn.  Used at the head of a minipool table
135                         ;   for inlined constants.
136   VUNSPEC_POOL_END      ; `end-of-table'.  Used to mark the end of a minipool
137                         ;   table.
138   VUNSPEC_POOL_1        ; `pool-entry(1)'.  An entry in the constant pool for
139                         ;   an 8-bit object.
140   VUNSPEC_POOL_2        ; `pool-entry(2)'.  An entry in the constant pool for
141                         ;   a 16-bit object.
142   VUNSPEC_POOL_4        ; `pool-entry(4)'.  An entry in the constant pool for
143                         ;   a 32-bit object.
144   VUNSPEC_POOL_8        ; `pool-entry(8)'.  An entry in the constant pool for
145                         ;   a 64-bit object.
146   VUNSPEC_POOL_16       ; `pool-entry(16)'.  An entry in the constant pool for
147                         ;   a 128-bit object.
148   VUNSPEC_TMRC          ; Used by the iWMMXt TMRC instruction.
149   VUNSPEC_TMCR          ; Used by the iWMMXt TMCR instruction.
150   VUNSPEC_ALIGN8        ; 8-byte alignment version of VUNSPEC_ALIGN
151   VUNSPEC_WCMP_EQ       ; Used by the iWMMXt WCMPEQ instructions
152   VUNSPEC_WCMP_GTU      ; Used by the iWMMXt WCMPGTU instructions
153   VUNSPEC_WCMP_GT       ; Used by the iwMMXT WCMPGT instructions
154   VUNSPEC_EH_RETURN     ; Use to override the return address for exception
155                         ; handling.
156   VUNSPEC_ATOMIC_CAS    ; Represent an atomic compare swap.
157   VUNSPEC_ATOMIC_XCHG   ; Represent an atomic exchange.
158   VUNSPEC_ATOMIC_OP     ; Represent an atomic operation.
159   VUNSPEC_LL            ; Represent a load-register-exclusive.
160   VUNSPEC_SC            ; Represent a store-register-exclusive.
163 ;;---------------------------------------------------------------------------
164 ;; Attributes
166 ;; Processor type.  This is created automatically from arm-cores.def.
167 (include "arm-tune.md")
169 ; IS_THUMB is set to 'yes' when we are generating Thumb code, and 'no' when
170 ; generating ARM code.  This is used to control the length of some insn
171 ; patterns that share the same RTL in both ARM and Thumb code.
172 (define_attr "is_thumb" "no,yes" (const (symbol_ref "thumb_code")))
174 ; IS_ARCH6 is set to 'yes' when we are generating code form ARMv6.
175 (define_attr "is_arch6" "no,yes" (const (symbol_ref "arm_arch6")))
177 ; IS_THUMB1 is set to 'yes' iff we are generating Thumb-1 code.
178 (define_attr "is_thumb1" "no,yes" (const (symbol_ref "thumb1_code")))
180 ;; Operand number of an input operand that is shifted.  Zero if the
181 ;; given instruction does not shift one of its input operands.
182 (define_attr "shift" "" (const_int 0))
184 ; Floating Point Unit.  If we only have floating point emulation, then there
185 ; is no point in scheduling the floating point insns.  (Well, for best
186 ; performance we should try and group them together).
187 (define_attr "fpu" "none,fpa,fpe2,fpe3,maverick,vfp"
188   (const (symbol_ref "arm_fpu_attr")))
190 ; LENGTH of an instruction (in bytes)
191 (define_attr "length" ""
192   (const_int 4))
194 ; The architecture which supports the instruction (or alternative).
195 ; This can be "a" for ARM, "t" for either of the Thumbs, "32" for
196 ; TARGET_32BIT, "t1" or "t2" to specify a specific Thumb mode.  "v6"
197 ; for ARM or Thumb-2 with arm_arch6, and nov6 for ARM without
198 ; arm_arch6.  This attribute is used to compute attribute "enabled",
199 ; use type "any" to enable an alternative in all cases.
200 (define_attr "arch" "any,a,t,32,t1,t2,v6,nov6,onlya8,neon_onlya8,nota8,neon_nota8,iwmmxt,iwmmxt2"
201   (const_string "any"))
203 (define_attr "arch_enabled" "no,yes"
204   (cond [(eq_attr "arch" "any")
205          (const_string "yes")
207          (and (eq_attr "arch" "a")
208               (match_test "TARGET_ARM"))
209          (const_string "yes")
211          (and (eq_attr "arch" "t")
212               (match_test "TARGET_THUMB"))
213          (const_string "yes")
215          (and (eq_attr "arch" "t1")
216               (match_test "TARGET_THUMB1"))
217          (const_string "yes")
219          (and (eq_attr "arch" "t2")
220               (match_test "TARGET_THUMB2"))
221          (const_string "yes")
223          (and (eq_attr "arch" "32")
224               (match_test "TARGET_32BIT"))
225          (const_string "yes")
227          (and (eq_attr "arch" "v6")
228               (match_test "TARGET_32BIT && arm_arch6"))
229          (const_string "yes")
231          (and (eq_attr "arch" "nov6")
232               (match_test "TARGET_32BIT && !arm_arch6"))
233          (const_string "yes")
235          (and (eq_attr "arch" "onlya8")
236               (eq_attr "tune" "cortexa8"))
237          (const_string "yes")
239          (and (eq_attr "arch" "neon_onlya8")
240               (eq_attr "tune" "cortexa8")
241               (match_test "TARGET_NEON"))
242          (const_string "yes")
244          (and (eq_attr "arch" "nota8")
245               (not (eq_attr "tune" "cortexa8")))
246          (const_string "yes")
248          (and (eq_attr "arch" "neon_nota8")
249               (not (eq_attr "tune" "cortexa8"))
250               (match_test "TARGET_NEON"))
251          (const_string "yes")
253          (and (eq_attr "arch" "iwmmxt2")
254               (match_test "TARGET_REALLY_IWMMXT2"))
255          (const_string "yes")]
257         (const_string "no")))
259 ; Allows an insn to disable certain alternatives for reasons other than
260 ; arch support.
261 (define_attr "insn_enabled" "no,yes"
262   (const_string "yes"))
264 ; Enable all alternatives that are both arch_enabled and insn_enabled.
265  (define_attr "enabled" "no,yes"
266    (if_then_else (eq_attr "insn_enabled" "yes")
267                (if_then_else (eq_attr "arch_enabled" "yes")
268                              (const_string "yes")
269                              (const_string "no"))
270                 (const_string "no")))
272 ; POOL_RANGE is how far away from a constant pool entry that this insn
273 ; can be placed.  If the distance is zero, then this insn will never
274 ; reference the pool.
275 ; NEG_POOL_RANGE is nonzero for insns that can reference a constant pool entry
276 ; before its address.  It is set to <max_range> - (8 + <data_size>).
277 (define_attr "arm_pool_range" "" (const_int 0))
278 (define_attr "thumb2_pool_range" "" (const_int 0))
279 (define_attr "arm_neg_pool_range" "" (const_int 0))
280 (define_attr "thumb2_neg_pool_range" "" (const_int 0))
282 (define_attr "pool_range" ""
283   (cond [(eq_attr "is_thumb" "yes") (attr "thumb2_pool_range")]
284         (attr "arm_pool_range")))
285 (define_attr "neg_pool_range" ""
286   (cond [(eq_attr "is_thumb" "yes") (attr "thumb2_neg_pool_range")]
287         (attr "arm_neg_pool_range")))
289 ; An assembler sequence may clobber the condition codes without us knowing.
290 ; If such an insn references the pool, then we have no way of knowing how,
291 ; so use the most conservative value for pool_range.
292 (define_asm_attributes
293  [(set_attr "conds" "clob")
294   (set_attr "length" "4")
295   (set_attr "pool_range" "250")])
297 ;; The instruction used to implement a particular pattern.  This
298 ;; information is used by pipeline descriptions to provide accurate
299 ;; scheduling information.
301 (define_attr "insn"
302         "mov,mvn,smulxy,smlaxy,smlalxy,smulwy,smlawx,mul,muls,mla,mlas,umull,umulls,umlal,umlals,smull,smulls,smlal,smlals,smlawy,smuad,smuadx,smlad,smladx,smusd,smusdx,smlsd,smlsdx,smmul,smmulr,smmla,umaal,smlald,smlsld,clz,mrs,msr,xtab,sdiv,udiv,sat,other"
303         (const_string "other"))
305 ; TYPE attribute is used to detect floating point instructions which, if
306 ; running on a co-processor can run in parallel with other, basic instructions
307 ; If write-buffer scheduling is enabled then it can also be used in the
308 ; scheduling of writes.
310 ; Classification of each insn
311 ; Note: vfp.md has different meanings for some of these, and some further
312 ; types as well.  See that file for details.
313 ; alu           any alu  instruction that doesn't hit memory or fp
314 ;               regs or have a shifted source operand
315 ; alu_shift     any data instruction that doesn't hit memory or fp
316 ;               regs, but has a source operand shifted by a constant
317 ; alu_shift_reg any data instruction that doesn't hit memory or fp
318 ;               regs, but has a source operand shifted by a register value
319 ; mult          a multiply instruction
320 ; block         blockage insn, this blocks all functional units
321 ; float         a floating point arithmetic operation (subject to expansion)
322 ; fdivd         DFmode floating point division
323 ; fdivs         SFmode floating point division
324 ; fmul          Floating point multiply
325 ; ffmul         Fast floating point multiply
326 ; farith        Floating point arithmetic (4 cycle)
327 ; ffarith       Fast floating point arithmetic (2 cycle)
328 ; float_em      a floating point arithmetic operation that is normally emulated
329 ;               even on a machine with an fpa.
330 ; f_fpa_load    a floating point load from memory. Only for the FPA.
331 ; f_fpa_store   a floating point store to memory. Only for the FPA.
332 ; f_load[sd]    A single/double load from memory. Used for VFP unit.
333 ; f_store[sd]   A single/double store to memory. Used for VFP unit.
334 ; f_flag        a transfer of co-processor flags to the CPSR
335 ; f_mem_r       a transfer of a floating point register to a real reg via mem
336 ; r_mem_f       the reverse of f_mem_r
337 ; f_2_r         fast transfer float to arm (no memory needed)
338 ; r_2_f         fast transfer arm to float
339 ; f_cvt         convert floating<->integral
340 ; branch        a branch
341 ; call          a subroutine call
342 ; load_byte     load byte(s) from memory to arm registers
343 ; load1         load 1 word from memory to arm registers
344 ; load2         load 2 words from memory to arm registers
345 ; load3         load 3 words from memory to arm registers
346 ; load4         load 4 words from memory to arm registers
347 ; store         store 1 word to memory from arm registers
348 ; store2        store 2 words
349 ; store3        store 3 words
350 ; store4        store 4 (or more) words
353 (define_attr "type"
354         "alu,alu_shift,alu_shift_reg,mult,block,float,fdivx,fdivd,fdivs,fmul,fmuls,fmuld,fmacs,fmacd,ffmul,farith,ffarith,f_flag,float_em,f_fpa_load,f_fpa_store,f_loads,f_loadd,f_stores,f_stored,f_mem_r,r_mem_f,f_2_r,r_2_f,f_cvt,branch,call,load_byte,load1,load2,load3,load4,store1,store2,store3,store4,fconsts,fconstd,fadds,faddd,ffariths,ffarithd,fcmps,fcmpd,fcpys"
355         (if_then_else 
356          (eq_attr "insn" "smulxy,smlaxy,smlalxy,smulwy,smlawx,mul,muls,mla,mlas,umull,umulls,umlal,umlals,smull,smulls,smlal,smlals")
357          (const_string "mult")
358          (const_string "alu")))
360 ; Is this an (integer side) multiply with a 64-bit result?
361 (define_attr "mul64" "no,yes"
362              (if_then_else
363                (eq_attr "insn" "smlalxy,umull,umulls,umlal,umlals,smull,smulls,smlal,smlals")
364                (const_string "yes")
365                (const_string "no")))
367 ; wtype for WMMX insn scheduling purposes.
368 (define_attr "wtype"
369         "none,wor,wxor,wand,wandn,wmov,tmcrr,tmrrc,wldr,wstr,tmcr,tmrc,wadd,wsub,wmul,wmac,wavg2,tinsr,textrm,wshufh,wcmpeq,wcmpgt,wmax,wmin,wpack,wunpckih,wunpckil,wunpckeh,wunpckel,wror,wsra,wsrl,wsll,wmadd,tmia,tmiaph,tmiaxy,tbcst,tmovmsk,wacc,waligni,walignr,tandc,textrc,torc,torvsc,wsad,wabs,wabsdiff,waddsubhx,wsubaddhx,wavg4,wmulw,wqmulm,wqmulwm,waddbhus,wqmiaxy,wmiaxy,wmiawxy,wmerge" (const_string "none"))
371 ; Load scheduling, set from the arm_ld_sched variable
372 ; initialized by arm_option_override()
373 (define_attr "ldsched" "no,yes" (const (symbol_ref "arm_ld_sched")))
375 ;; Classification of NEON instructions for scheduling purposes.
376 ;; Do not set this attribute and the "type" attribute together in
377 ;; any one instruction pattern.
378 (define_attr "neon_type"
379    "neon_int_1,\
380    neon_int_2,\
381    neon_int_3,\
382    neon_int_4,\
383    neon_int_5,\
384    neon_vqneg_vqabs,\
385    neon_vmov,\
386    neon_vaba,\
387    neon_vsma,\
388    neon_vaba_qqq,\
389    neon_mul_ddd_8_16_qdd_16_8_long_32_16_long,\
390    neon_mul_qqq_8_16_32_ddd_32,\
391    neon_mul_qdd_64_32_long_qqd_16_ddd_32_scalar_64_32_long_scalar,\
392    neon_mla_ddd_8_16_qdd_16_8_long_32_16_long,\
393    neon_mla_qqq_8_16,\
394    neon_mla_ddd_32_qqd_16_ddd_32_scalar_qdd_64_32_long_scalar_qdd_64_32_long,\
395    neon_mla_qqq_32_qqd_32_scalar,\
396    neon_mul_ddd_16_scalar_32_16_long_scalar,\
397    neon_mul_qqd_32_scalar,\
398    neon_mla_ddd_16_scalar_qdd_32_16_long_scalar,\
399    neon_shift_1,\
400    neon_shift_2,\
401    neon_shift_3,\
402    neon_vshl_ddd,\
403    neon_vqshl_vrshl_vqrshl_qqq,\
404    neon_vsra_vrsra,\
405    neon_fp_vadd_ddd_vabs_dd,\
406    neon_fp_vadd_qqq_vabs_qq,\
407    neon_fp_vsum,\
408    neon_fp_vmul_ddd,\
409    neon_fp_vmul_qqd,\
410    neon_fp_vmla_ddd,\
411    neon_fp_vmla_qqq,\
412    neon_fp_vmla_ddd_scalar,\
413    neon_fp_vmla_qqq_scalar,\
414    neon_fp_vrecps_vrsqrts_ddd,\
415    neon_fp_vrecps_vrsqrts_qqq,\
416    neon_bp_simple,\
417    neon_bp_2cycle,\
418    neon_bp_3cycle,\
419    neon_ldr,\
420    neon_str,\
421    neon_vld1_1_2_regs,\
422    neon_vld1_3_4_regs,\
423    neon_vld2_2_regs_vld1_vld2_all_lanes,\
424    neon_vld2_4_regs,\
425    neon_vld3_vld4,\
426    neon_vst1_1_2_regs_vst2_2_regs,\
427    neon_vst1_3_4_regs,\
428    neon_vst2_4_regs_vst3_vst4,\
429    neon_vst3_vst4,\
430    neon_vld1_vld2_lane,\
431    neon_vld3_vld4_lane,\
432    neon_vst1_vst2_lane,\
433    neon_vst3_vst4_lane,\
434    neon_vld3_vld4_all_lanes,\
435    neon_mcr,\
436    neon_mcr_2_mcrr,\
437    neon_mrc,\
438    neon_mrrc,\
439    neon_ldm_2,\
440    neon_stm_2,\
441    none"
442  (const_string "none"))
444 ; condition codes: this one is used by final_prescan_insn to speed up
445 ; conditionalizing instructions.  It saves having to scan the rtl to see if
446 ; it uses or alters the condition codes.
448 ; USE means that the condition codes are used by the insn in the process of
449 ;   outputting code, this means (at present) that we can't use the insn in
450 ;   inlined branches
452 ; SET means that the purpose of the insn is to set the condition codes in a
453 ;   well defined manner.
455 ; CLOB means that the condition codes are altered in an undefined manner, if
456 ;   they are altered at all
458 ; UNCONDITIONAL means the instruction can not be conditionally executed and
459 ;   that the instruction does not use or alter the condition codes.
461 ; NOCOND means that the instruction does not use or alter the condition
462 ;   codes but can be converted into a conditionally exectuted instruction.
464 (define_attr "conds" "use,set,clob,unconditional,nocond"
465         (if_then_else
466          (ior (eq_attr "is_thumb1" "yes")
467               (eq_attr "type" "call"))
468          (const_string "clob")
469          (if_then_else (eq_attr "neon_type" "none")
470           (const_string "nocond")
471           (const_string "unconditional"))))
473 ; Predicable means that the insn can be conditionally executed based on
474 ; an automatically added predicate (additional patterns are generated by 
475 ; gen...).  We default to 'no' because no Thumb patterns match this rule
476 ; and not all ARM patterns do.
477 (define_attr "predicable" "no,yes" (const_string "no"))
479 ; Only model the write buffer for ARM6 and ARM7.  Earlier processors don't
480 ; have one.  Later ones, such as StrongARM, have write-back caches, so don't
481 ; suffer blockages enough to warrant modelling this (and it can adversely
482 ; affect the schedule).
483 (define_attr "model_wbuf" "no,yes" (const (symbol_ref "arm_tune_wbuf")))
485 ; WRITE_CONFLICT implies that a read following an unrelated write is likely
486 ; to stall the processor.  Used with model_wbuf above.
487 (define_attr "write_conflict" "no,yes"
488   (if_then_else (eq_attr "type"
489                  "block,float_em,f_fpa_load,f_fpa_store,f_mem_r,r_mem_f,call,load1")
490                 (const_string "yes")
491                 (const_string "no")))
493 ; Classify the insns into those that take one cycle and those that take more
494 ; than one on the main cpu execution unit.
495 (define_attr "core_cycles" "single,multi"
496   (if_then_else (eq_attr "type"
497                  "alu,alu_shift,float,fdivx,fdivd,fdivs,fmul,ffmul,farith,ffarith")
498                 (const_string "single")
499                 (const_string "multi")))
501 ;; FAR_JUMP is "yes" if a BL instruction is used to generate a branch to a
502 ;; distant label.  Only applicable to Thumb code.
503 (define_attr "far_jump" "yes,no" (const_string "no"))
506 ;; The number of machine instructions this pattern expands to.
507 ;; Used for Thumb-2 conditional execution.
508 (define_attr "ce_count" "" (const_int 1))
510 ;;---------------------------------------------------------------------------
511 ;; Mode iterators
513 (include "iterators.md")
515 ;;---------------------------------------------------------------------------
516 ;; Predicates
518 (include "predicates.md")
519 (include "constraints.md")
521 ;;---------------------------------------------------------------------------
522 ;; Pipeline descriptions
524 (define_attr "tune_cortexr4" "yes,no"
525   (const (if_then_else
526           (eq_attr "tune" "cortexr4,cortexr4f,cortexr5")
527           (const_string "yes")
528           (const_string "no"))))
530 ;; True if the generic scheduling description should be used.
532 (define_attr "generic_sched" "yes,no"
533   (const (if_then_else
534           (ior (eq_attr "tune" "fa526,fa626,fa606te,fa626te,fmp626,fa726te,arm926ejs,arm1020e,arm1026ejs,arm1136js,arm1136jfs,cortexa5,cortexa8,cortexa9,cortexa15,cortexm4")
535                (eq_attr "tune_cortexr4" "yes"))
536           (const_string "no")
537           (const_string "yes"))))
539 (define_attr "generic_vfp" "yes,no"
540   (const (if_then_else
541           (and (eq_attr "fpu" "vfp")
542                (eq_attr "tune" "!arm1020e,arm1022e,cortexa5,cortexa8,cortexa9,cortexm4")
543                (eq_attr "tune_cortexr4" "no"))
544           (const_string "yes")
545           (const_string "no"))))
547 (include "marvell-f-iwmmxt.md")
548 (include "arm-generic.md")
549 (include "arm926ejs.md")
550 (include "arm1020e.md")
551 (include "arm1026ejs.md")
552 (include "arm1136jfs.md")
553 (include "fa526.md")
554 (include "fa606te.md")
555 (include "fa626te.md")
556 (include "fmp626.md")
557 (include "fa726te.md")
558 (include "cortex-a5.md")
559 (include "cortex-a8.md")
560 (include "cortex-a9.md")
561 (include "cortex-a15.md")
562 (include "cortex-r4.md")
563 (include "cortex-r4f.md")
564 (include "cortex-m4.md")
565 (include "cortex-m4-fpu.md")
566 (include "vfp11.md")
569 ;;---------------------------------------------------------------------------
570 ;; Insn patterns
572 ;; Addition insns.
574 ;; Note: For DImode insns, there is normally no reason why operands should
575 ;; not be in the same register, what we don't want is for something being
576 ;; written to partially overlap something that is an input.
578 (define_expand "adddi3"
579  [(parallel
580    [(set (match_operand:DI           0 "s_register_operand" "")
581           (plus:DI (match_operand:DI 1 "s_register_operand" "")
582                    (match_operand:DI 2 "s_register_operand" "")))
583     (clobber (reg:CC CC_REGNUM))])]
584   "TARGET_EITHER"
585   "
586   if (TARGET_THUMB1)
587     {
588       if (GET_CODE (operands[1]) != REG)
589         operands[1] = force_reg (DImode, operands[1]);
590       if (GET_CODE (operands[2]) != REG)
591         operands[2] = force_reg (DImode, operands[2]);
592      }
593   "
596 (define_insn "*thumb1_adddi3"
597   [(set (match_operand:DI          0 "register_operand" "=l")
598         (plus:DI (match_operand:DI 1 "register_operand" "%0")
599                  (match_operand:DI 2 "register_operand" "l")))
600    (clobber (reg:CC CC_REGNUM))
601   ]
602   "TARGET_THUMB1"
603   "add\\t%Q0, %Q0, %Q2\;adc\\t%R0, %R0, %R2"
604   [(set_attr "length" "4")]
607 (define_insn_and_split "*arm_adddi3"
608   [(set (match_operand:DI          0 "s_register_operand" "=&r,&r")
609         (plus:DI (match_operand:DI 1 "s_register_operand" "%0, 0")
610                  (match_operand:DI 2 "s_register_operand" "r,  0")))
611    (clobber (reg:CC CC_REGNUM))]
612   "TARGET_32BIT && !TARGET_NEON"
613   "#"
614   "TARGET_32BIT && reload_completed
615    && ! (TARGET_NEON && IS_VFP_REGNUM (REGNO (operands[0])))"
616   [(parallel [(set (reg:CC_C CC_REGNUM)
617                    (compare:CC_C (plus:SI (match_dup 1) (match_dup 2))
618                                  (match_dup 1)))
619               (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])
620    (set (match_dup 3) (plus:SI (plus:SI (match_dup 4) (match_dup 5))
621                                (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))))]
622   "
623   {
624     operands[3] = gen_highpart (SImode, operands[0]);
625     operands[0] = gen_lowpart (SImode, operands[0]);
626     operands[4] = gen_highpart (SImode, operands[1]);
627     operands[1] = gen_lowpart (SImode, operands[1]);
628     operands[5] = gen_highpart (SImode, operands[2]);
629     operands[2] = gen_lowpart (SImode, operands[2]);
630   }"
631   [(set_attr "conds" "clob")
632    (set_attr "length" "8")]
635 (define_insn_and_split "*adddi_sesidi_di"
636   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
637         (plus:DI (sign_extend:DI
638                   (match_operand:SI 2 "s_register_operand" "r,r"))
639                  (match_operand:DI 1 "s_register_operand" "0,r")))
640    (clobber (reg:CC CC_REGNUM))]
641   "TARGET_32BIT"
642   "#"
643   "TARGET_32BIT && reload_completed"
644   [(parallel [(set (reg:CC_C CC_REGNUM)
645                    (compare:CC_C (plus:SI (match_dup 1) (match_dup 2))
646                                  (match_dup 1)))
647               (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])
648    (set (match_dup 3) (plus:SI (plus:SI (ashiftrt:SI (match_dup 2)
649                                                      (const_int 31))
650                                         (match_dup 4))
651                                (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))))]
652   "
653   {
654     operands[3] = gen_highpart (SImode, operands[0]);
655     operands[0] = gen_lowpart (SImode, operands[0]);
656     operands[4] = gen_highpart (SImode, operands[1]);
657     operands[1] = gen_lowpart (SImode, operands[1]);
658     operands[2] = gen_lowpart (SImode, operands[2]);
659   }"
660   [(set_attr "conds" "clob")
661    (set_attr "length" "8")]
664 (define_insn_and_split "*adddi_zesidi_di"
665   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
666         (plus:DI (zero_extend:DI
667                   (match_operand:SI 2 "s_register_operand" "r,r"))
668                  (match_operand:DI 1 "s_register_operand" "0,r")))
669    (clobber (reg:CC CC_REGNUM))]
670   "TARGET_32BIT"
671   "#"
672   "TARGET_32BIT && reload_completed"
673   [(parallel [(set (reg:CC_C CC_REGNUM)
674                    (compare:CC_C (plus:SI (match_dup 1) (match_dup 2))
675                                  (match_dup 1)))
676               (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])
677    (set (match_dup 3) (plus:SI (plus:SI (match_dup 4) (const_int 0))
678                                (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))))]
679   "
680   {
681     operands[3] = gen_highpart (SImode, operands[0]);
682     operands[0] = gen_lowpart (SImode, operands[0]);
683     operands[4] = gen_highpart (SImode, operands[1]);
684     operands[1] = gen_lowpart (SImode, operands[1]);
685     operands[2] = gen_lowpart (SImode, operands[2]);
686   }"
687   [(set_attr "conds" "clob")
688    (set_attr "length" "8")]
691 (define_expand "addsi3"
692   [(set (match_operand:SI          0 "s_register_operand" "")
693         (plus:SI (match_operand:SI 1 "s_register_operand" "")
694                  (match_operand:SI 2 "reg_or_int_operand" "")))]
695   "TARGET_EITHER"
696   "
697   if (TARGET_32BIT && GET_CODE (operands[2]) == CONST_INT)
698     {
699       arm_split_constant (PLUS, SImode, NULL_RTX,
700                           INTVAL (operands[2]), operands[0], operands[1],
701                           optimize && can_create_pseudo_p ());
702       DONE;
703     }
704   "
707 ; If there is a scratch available, this will be faster than synthesizing the
708 ; addition.
709 (define_peephole2
710   [(match_scratch:SI 3 "r")
711    (set (match_operand:SI          0 "arm_general_register_operand" "")
712         (plus:SI (match_operand:SI 1 "arm_general_register_operand" "")
713                  (match_operand:SI 2 "const_int_operand"  "")))]
714   "TARGET_32BIT &&
715    !(const_ok_for_arm (INTVAL (operands[2]))
716      || const_ok_for_arm (-INTVAL (operands[2])))
717     && const_ok_for_arm (~INTVAL (operands[2]))"
718   [(set (match_dup 3) (match_dup 2))
719    (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 3)))]
720   ""
723 ;; The r/r/k alternative is required when reloading the address
724 ;;  (plus (reg rN) (reg sp)) into (reg rN).  In this case reload will
725 ;; put the duplicated register first, and not try the commutative version.
726 (define_insn_and_split "*arm_addsi3"
727   [(set (match_operand:SI          0 "s_register_operand" "=r, k,r,r, k, r, k,r, k, r")
728         (plus:SI (match_operand:SI 1 "s_register_operand" "%rk,k,r,rk,k, rk,k,rk,k, rk")
729                  (match_operand:SI 2 "reg_or_int_operand" "rI,rI,k,Pj,Pj,L, L,PJ,PJ,?n")))]
730   "TARGET_32BIT"
731   "@
732    add%?\\t%0, %1, %2
733    add%?\\t%0, %1, %2
734    add%?\\t%0, %2, %1
735    addw%?\\t%0, %1, %2
736    addw%?\\t%0, %1, %2
737    sub%?\\t%0, %1, #%n2
738    sub%?\\t%0, %1, #%n2
739    subw%?\\t%0, %1, #%n2
740    subw%?\\t%0, %1, #%n2
741    #"
742   "TARGET_32BIT
743    && GET_CODE (operands[2]) == CONST_INT
744    && !const_ok_for_op (INTVAL (operands[2]), PLUS)
745    && (reload_completed || !arm_eliminable_register (operands[1]))"
746   [(clobber (const_int 0))]
747   "
748   arm_split_constant (PLUS, SImode, curr_insn,
749                       INTVAL (operands[2]), operands[0],
750                       operands[1], 0);
751   DONE;
752   "
753   [(set_attr "length" "4,4,4,4,4,4,4,4,4,16")
754    (set_attr "predicable" "yes")
755    (set_attr "arch" "*,*,*,t2,t2,*,*,t2,t2,*")]
758 (define_insn_and_split "*thumb1_addsi3"
759   [(set (match_operand:SI          0 "register_operand" "=l,l,l,*rk,*hk,l,k,l,l,l")
760         (plus:SI (match_operand:SI 1 "register_operand" "%0,0,l,*0,*0,k,k,0,l,k")
761                  (match_operand:SI 2 "nonmemory_operand" "I,J,lL,*hk,*rk,M,O,Pa,Pb,Pc")))]
762   "TARGET_THUMB1"
763   "*
764    static const char * const asms[] = 
765    {
766      \"add\\t%0, %0, %2\",
767      \"sub\\t%0, %0, #%n2\",
768      \"add\\t%0, %1, %2\",
769      \"add\\t%0, %0, %2\",
770      \"add\\t%0, %0, %2\",
771      \"add\\t%0, %1, %2\",
772      \"add\\t%0, %1, %2\",
773      \"#\",
774      \"#\",
775      \"#\"
776    };
777    if ((which_alternative == 2 || which_alternative == 6)
778        && GET_CODE (operands[2]) == CONST_INT
779        && INTVAL (operands[2]) < 0)
780      return \"sub\\t%0, %1, #%n2\";
781    return asms[which_alternative];
782   "
783   "&& reload_completed && CONST_INT_P (operands[2])
784    && ((operands[1] != stack_pointer_rtx
785         && (INTVAL (operands[2]) > 255 || INTVAL (operands[2]) < -255))
786        || (operands[1] == stack_pointer_rtx
787            && INTVAL (operands[2]) > 1020))"
788   [(set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))
789    (set (match_dup 0) (plus:SI (match_dup 0) (match_dup 3)))]
790   {
791     HOST_WIDE_INT offset = INTVAL (operands[2]);
792     if (operands[1] == stack_pointer_rtx)
793       offset -= 1020;
794     else
795       {
796         if (offset > 255)
797           offset = 255;
798         else if (offset < -255)
799           offset = -255;
800       }
801     operands[3] = GEN_INT (offset);
802     operands[2] = GEN_INT (INTVAL (operands[2]) - offset);
803   }
804   [(set_attr "length" "2,2,2,2,2,2,2,4,4,4")]
807 ;; Reloading and elimination of the frame pointer can
808 ;; sometimes cause this optimization to be missed.
809 (define_peephole2
810   [(set (match_operand:SI 0 "arm_general_register_operand" "")
811         (match_operand:SI 1 "const_int_operand" ""))
812    (set (match_dup 0)
813         (plus:SI (match_dup 0) (reg:SI SP_REGNUM)))]
814   "TARGET_THUMB1
815    && (unsigned HOST_WIDE_INT) (INTVAL (operands[1])) < 1024
816    && (INTVAL (operands[1]) & 3) == 0"
817   [(set (match_dup 0) (plus:SI (reg:SI SP_REGNUM) (match_dup 1)))]
818   ""
821 (define_insn "addsi3_compare0"
822   [(set (reg:CC_NOOV CC_REGNUM)
823         (compare:CC_NOOV
824          (plus:SI (match_operand:SI 1 "s_register_operand" "r, r")
825                   (match_operand:SI 2 "arm_add_operand"    "rI,L"))
826          (const_int 0)))
827    (set (match_operand:SI 0 "s_register_operand" "=r,r")
828         (plus:SI (match_dup 1) (match_dup 2)))]
829   "TARGET_ARM"
830   "@
831    add%.\\t%0, %1, %2
832    sub%.\\t%0, %1, #%n2"
833   [(set_attr "conds" "set")]
836 (define_insn "*addsi3_compare0_scratch"
837   [(set (reg:CC_NOOV CC_REGNUM)
838         (compare:CC_NOOV
839          (plus:SI (match_operand:SI 0 "s_register_operand" "r, r")
840                   (match_operand:SI 1 "arm_add_operand"    "rI,L"))
841          (const_int 0)))]
842   "TARGET_ARM"
843   "@
844    cmn%?\\t%0, %1
845    cmp%?\\t%0, #%n1"
846   [(set_attr "conds" "set")
847    (set_attr "predicable" "yes")]
850 (define_insn "*compare_negsi_si"
851   [(set (reg:CC_Z CC_REGNUM)
852         (compare:CC_Z
853          (neg:SI (match_operand:SI 0 "s_register_operand" "r"))
854          (match_operand:SI 1 "s_register_operand" "r")))]
855   "TARGET_32BIT"
856   "cmn%?\\t%1, %0"
857   [(set_attr "conds" "set")
858    (set_attr "predicable" "yes")]
861 ;; This is the canonicalization of addsi3_compare0_for_combiner when the
862 ;; addend is a constant.
863 (define_insn "*cmpsi2_addneg"
864   [(set (reg:CC CC_REGNUM)
865         (compare:CC
866          (match_operand:SI 1 "s_register_operand" "r,r")
867          (match_operand:SI 2 "arm_addimm_operand" "L,I")))
868    (set (match_operand:SI 0 "s_register_operand" "=r,r")
869         (plus:SI (match_dup 1)
870                  (match_operand:SI 3 "arm_addimm_operand" "I,L")))]
871   "TARGET_32BIT && INTVAL (operands[2]) == -INTVAL (operands[3])"
872   "@
873    add%.\\t%0, %1, %3
874    sub%.\\t%0, %1, #%n3"
875   [(set_attr "conds" "set")]
878 ;; Convert the sequence
879 ;;  sub  rd, rn, #1
880 ;;  cmn  rd, #1 (equivalent to cmp rd, #-1)
881 ;;  bne  dest
882 ;; into
883 ;;  subs rd, rn, #1
884 ;;  bcs  dest   ((unsigned)rn >= 1)
885 ;; similarly for the beq variant using bcc.
886 ;; This is a common looping idiom (while (n--))
887 (define_peephole2
888   [(set (match_operand:SI 0 "arm_general_register_operand" "")
889         (plus:SI (match_operand:SI 1 "arm_general_register_operand" "")
890                  (const_int -1)))
891    (set (match_operand 2 "cc_register" "")
892         (compare (match_dup 0) (const_int -1)))
893    (set (pc)
894         (if_then_else (match_operator 3 "equality_operator"
895                        [(match_dup 2) (const_int 0)])
896                       (match_operand 4 "" "")
897                       (match_operand 5 "" "")))]
898   "TARGET_32BIT && peep2_reg_dead_p (3, operands[2])"
899   [(parallel[
900     (set (match_dup 2)
901          (compare:CC
902           (match_dup 1) (const_int 1)))
903     (set (match_dup 0) (plus:SI (match_dup 1) (const_int -1)))])
904    (set (pc)
905         (if_then_else (match_op_dup 3 [(match_dup 2) (const_int 0)])
906                       (match_dup 4)
907                       (match_dup 5)))]
908   "operands[2] = gen_rtx_REG (CCmode, CC_REGNUM);
909    operands[3] = gen_rtx_fmt_ee ((GET_CODE (operands[3]) == NE
910                                   ? GEU : LTU),
911                                  VOIDmode, 
912                                  operands[2], const0_rtx);"
915 ;; The next four insns work because they compare the result with one of
916 ;; the operands, and we know that the use of the condition code is
917 ;; either GEU or LTU, so we can use the carry flag from the addition
918 ;; instead of doing the compare a second time.
919 (define_insn "*addsi3_compare_op1"
920   [(set (reg:CC_C CC_REGNUM)
921         (compare:CC_C
922          (plus:SI (match_operand:SI 1 "s_register_operand" "r,r")
923                   (match_operand:SI 2 "arm_add_operand" "rI,L"))
924          (match_dup 1)))
925    (set (match_operand:SI 0 "s_register_operand" "=r,r")
926         (plus:SI (match_dup 1) (match_dup 2)))]
927   "TARGET_32BIT"
928   "@
929    add%.\\t%0, %1, %2
930    sub%.\\t%0, %1, #%n2"
931   [(set_attr "conds" "set")]
934 (define_insn "*addsi3_compare_op2"
935   [(set (reg:CC_C CC_REGNUM)
936         (compare:CC_C
937          (plus:SI (match_operand:SI 1 "s_register_operand" "r,r")
938                   (match_operand:SI 2 "arm_add_operand" "rI,L"))
939          (match_dup 2)))
940    (set (match_operand:SI 0 "s_register_operand" "=r,r")
941         (plus:SI (match_dup 1) (match_dup 2)))]
942   "TARGET_32BIT"
943   "@
944    add%.\\t%0, %1, %2
945    sub%.\\t%0, %1, #%n2"
946   [(set_attr "conds" "set")]
949 (define_insn "*compare_addsi2_op0"
950   [(set (reg:CC_C CC_REGNUM)
951         (compare:CC_C
952          (plus:SI (match_operand:SI 0 "s_register_operand" "r,r")
953                   (match_operand:SI 1 "arm_add_operand" "rI,L"))
954          (match_dup 0)))]
955   "TARGET_32BIT"
956   "@
957    cmn%?\\t%0, %1
958    cmp%?\\t%0, #%n1"
959   [(set_attr "conds" "set")
960    (set_attr "predicable" "yes")]
963 (define_insn "*compare_addsi2_op1"
964   [(set (reg:CC_C CC_REGNUM)
965         (compare:CC_C
966          (plus:SI (match_operand:SI 0 "s_register_operand" "r,r")
967                   (match_operand:SI 1 "arm_add_operand" "rI,L"))
968          (match_dup 1)))]
969   "TARGET_32BIT"
970   "@
971    cmn%?\\t%0, %1
972    cmp%?\\t%0, #%n1"
973   [(set_attr "conds" "set")
974    (set_attr "predicable" "yes")]
977 (define_insn "*addsi3_carryin_<optab>"
978   [(set (match_operand:SI 0 "s_register_operand" "=r")
979         (plus:SI (plus:SI (match_operand:SI 1 "s_register_operand" "%r")
980                           (match_operand:SI 2 "arm_rhs_operand" "rI"))
981                  (LTUGEU:SI (reg:<cnb> CC_REGNUM) (const_int 0))))]
982   "TARGET_32BIT"
983   "adc%?\\t%0, %1, %2"
984   [(set_attr "conds" "use")]
987 (define_insn "*addsi3_carryin_alt2_<optab>"
988   [(set (match_operand:SI 0 "s_register_operand" "=r")
989         (plus:SI (plus:SI (LTUGEU:SI (reg:<cnb> CC_REGNUM) (const_int 0))
990                           (match_operand:SI 1 "s_register_operand" "%r"))
991                  (match_operand:SI 2 "arm_rhs_operand" "rI")))]
992   "TARGET_32BIT"
993   "adc%?\\t%0, %1, %2"
994   [(set_attr "conds" "use")]
997 (define_insn "*addsi3_carryin_shift_<optab>"
998   [(set (match_operand:SI 0 "s_register_operand" "=r")
999         (plus:SI (plus:SI
1000                   (match_operator:SI 2 "shift_operator"
1001                     [(match_operand:SI 3 "s_register_operand" "r")
1002                      (match_operand:SI 4 "reg_or_int_operand" "rM")])
1003                   (match_operand:SI 1 "s_register_operand" "r"))
1004                  (LTUGEU:SI (reg:<cnb> CC_REGNUM) (const_int 0))))]
1005   "TARGET_32BIT"
1006   "adc%?\\t%0, %1, %3%S2"
1007   [(set_attr "conds" "use")
1008    (set (attr "type") (if_then_else (match_operand 4 "const_int_operand" "")
1009                       (const_string "alu_shift")
1010                       (const_string "alu_shift_reg")))]
1013 (define_insn "*addsi3_carryin_clobercc_<optab>"
1014   [(set (match_operand:SI 0 "s_register_operand" "=r")
1015         (plus:SI (plus:SI (match_operand:SI 1 "s_register_operand" "%r")
1016                           (match_operand:SI 2 "arm_rhs_operand" "rI"))
1017                  (LTUGEU:SI (reg:<cnb> CC_REGNUM) (const_int 0))))
1018    (clobber (reg:CC CC_REGNUM))]
1019    "TARGET_32BIT"
1020    "adc%.\\t%0, %1, %2"
1021    [(set_attr "conds" "set")]
1024 (define_expand "incscc"
1025   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1026         (plus:SI (match_operator:SI 2 "arm_comparison_operator"
1027                     [(match_operand:CC 3 "cc_register" "") (const_int 0)])
1028                  (match_operand:SI 1 "s_register_operand" "0,?r")))]
1029   "TARGET_32BIT"
1030   ""
1033 (define_insn "*arm_incscc"
1034   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
1035         (plus:SI (match_operator:SI 2 "arm_comparison_operator"
1036                     [(match_operand:CC 3 "cc_register" "") (const_int 0)])
1037                  (match_operand:SI 1 "s_register_operand" "0,?r")))]
1038   "TARGET_ARM"
1039   "@
1040   add%d2\\t%0, %1, #1
1041   mov%D2\\t%0, %1\;add%d2\\t%0, %1, #1"
1042   [(set_attr "conds" "use")
1043    (set_attr "length" "4,8")]
1046 ; transform ((x << y) - 1) to ~(~(x-1) << y)  Where X is a constant.
1047 (define_split
1048   [(set (match_operand:SI 0 "s_register_operand" "")
1049         (plus:SI (ashift:SI (match_operand:SI 1 "const_int_operand" "")
1050                             (match_operand:SI 2 "s_register_operand" ""))
1051                  (const_int -1)))
1052    (clobber (match_operand:SI 3 "s_register_operand" ""))]
1053   "TARGET_32BIT"
1054   [(set (match_dup 3) (match_dup 1))
1055    (set (match_dup 0) (not:SI (ashift:SI (match_dup 3) (match_dup 2))))]
1056   "
1057   operands[1] = GEN_INT (~(INTVAL (operands[1]) - 1));
1060 (define_expand "addsf3"
1061   [(set (match_operand:SF          0 "s_register_operand" "")
1062         (plus:SF (match_operand:SF 1 "s_register_operand" "")
1063                  (match_operand:SF 2 "arm_float_add_operand" "")))]
1064   "TARGET_32BIT && TARGET_HARD_FLOAT"
1065   "
1068 (define_expand "adddf3"
1069   [(set (match_operand:DF          0 "s_register_operand" "")
1070         (plus:DF (match_operand:DF 1 "s_register_operand" "")
1071                  (match_operand:DF 2 "arm_float_add_operand" "")))]
1072   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
1073   "
1076 (define_expand "subdi3"
1077  [(parallel
1078    [(set (match_operand:DI            0 "s_register_operand" "")
1079           (minus:DI (match_operand:DI 1 "s_register_operand" "")
1080                     (match_operand:DI 2 "s_register_operand" "")))
1081     (clobber (reg:CC CC_REGNUM))])]
1082   "TARGET_EITHER"
1083   "
1084   if (TARGET_THUMB1)
1085     {
1086       if (GET_CODE (operands[1]) != REG)
1087         operands[1] = force_reg (DImode, operands[1]);
1088       if (GET_CODE (operands[2]) != REG)
1089         operands[2] = force_reg (DImode, operands[2]);
1090      }  
1091   "
1094 (define_insn "*arm_subdi3"
1095   [(set (match_operand:DI           0 "s_register_operand" "=&r,&r,&r")
1096         (minus:DI (match_operand:DI 1 "s_register_operand" "0,r,0")
1097                   (match_operand:DI 2 "s_register_operand" "r,0,0")))
1098    (clobber (reg:CC CC_REGNUM))]
1099   "TARGET_32BIT && !TARGET_NEON"
1100   "subs\\t%Q0, %Q1, %Q2\;sbc\\t%R0, %R1, %R2"
1101   [(set_attr "conds" "clob")
1102    (set_attr "length" "8")]
1105 (define_insn "*thumb_subdi3"
1106   [(set (match_operand:DI           0 "register_operand" "=l")
1107         (minus:DI (match_operand:DI 1 "register_operand"  "0")
1108                   (match_operand:DI 2 "register_operand"  "l")))
1109    (clobber (reg:CC CC_REGNUM))]
1110   "TARGET_THUMB1"
1111   "sub\\t%Q0, %Q0, %Q2\;sbc\\t%R0, %R0, %R2"
1112   [(set_attr "length" "4")]
1115 (define_insn "*subdi_di_zesidi"
1116   [(set (match_operand:DI           0 "s_register_operand" "=&r,&r")
1117         (minus:DI (match_operand:DI 1 "s_register_operand"  "0,r")
1118                   (zero_extend:DI
1119                    (match_operand:SI 2 "s_register_operand"  "r,r"))))
1120    (clobber (reg:CC CC_REGNUM))]
1121   "TARGET_32BIT"
1122   "subs\\t%Q0, %Q1, %2\;sbc\\t%R0, %R1, #0"
1123   [(set_attr "conds" "clob")
1124    (set_attr "length" "8")]
1127 (define_insn "*subdi_di_sesidi"
1128   [(set (match_operand:DI            0 "s_register_operand" "=&r,&r")
1129         (minus:DI (match_operand:DI  1 "s_register_operand"  "0,r")
1130                   (sign_extend:DI
1131                    (match_operand:SI 2 "s_register_operand"  "r,r"))))
1132    (clobber (reg:CC CC_REGNUM))]
1133   "TARGET_32BIT"
1134   "subs\\t%Q0, %Q1, %2\;sbc\\t%R0, %R1, %2, asr #31"
1135   [(set_attr "conds" "clob")
1136    (set_attr "length" "8")]
1139 (define_insn "*subdi_zesidi_di"
1140   [(set (match_operand:DI            0 "s_register_operand" "=&r,&r")
1141         (minus:DI (zero_extend:DI
1142                    (match_operand:SI 2 "s_register_operand"  "r,r"))
1143                   (match_operand:DI  1 "s_register_operand" "0,r")))
1144    (clobber (reg:CC CC_REGNUM))]
1145   "TARGET_ARM"
1146   "rsbs\\t%Q0, %Q1, %2\;rsc\\t%R0, %R1, #0"
1147   [(set_attr "conds" "clob")
1148    (set_attr "length" "8")]
1151 (define_insn "*subdi_sesidi_di"
1152   [(set (match_operand:DI            0 "s_register_operand" "=&r,&r")
1153         (minus:DI (sign_extend:DI
1154                    (match_operand:SI 2 "s_register_operand"   "r,r"))
1155                   (match_operand:DI  1 "s_register_operand"  "0,r")))
1156    (clobber (reg:CC CC_REGNUM))]
1157   "TARGET_ARM"
1158   "rsbs\\t%Q0, %Q1, %2\;rsc\\t%R0, %R1, %2, asr #31"
1159   [(set_attr "conds" "clob")
1160    (set_attr "length" "8")]
1163 (define_insn "*subdi_zesidi_zesidi"
1164   [(set (match_operand:DI            0 "s_register_operand" "=r")
1165         (minus:DI (zero_extend:DI
1166                    (match_operand:SI 1 "s_register_operand"  "r"))
1167                   (zero_extend:DI
1168                    (match_operand:SI 2 "s_register_operand"  "r"))))
1169    (clobber (reg:CC CC_REGNUM))]
1170   "TARGET_32BIT"
1171   "subs\\t%Q0, %1, %2\;sbc\\t%R0, %1, %1"
1172   [(set_attr "conds" "clob")
1173    (set_attr "length" "8")]
1176 (define_expand "subsi3"
1177   [(set (match_operand:SI           0 "s_register_operand" "")
1178         (minus:SI (match_operand:SI 1 "reg_or_int_operand" "")
1179                   (match_operand:SI 2 "s_register_operand" "")))]
1180   "TARGET_EITHER"
1181   "
1182   if (GET_CODE (operands[1]) == CONST_INT)
1183     {
1184       if (TARGET_32BIT)
1185         {
1186           arm_split_constant (MINUS, SImode, NULL_RTX,
1187                               INTVAL (operands[1]), operands[0],
1188                               operands[2], optimize && can_create_pseudo_p ());
1189           DONE;
1190         }
1191       else /* TARGET_THUMB1 */
1192         operands[1] = force_reg (SImode, operands[1]);
1193     }
1194   "
1197 (define_insn "thumb1_subsi3_insn"
1198   [(set (match_operand:SI           0 "register_operand" "=l")
1199         (minus:SI (match_operand:SI 1 "register_operand" "l")
1200                   (match_operand:SI 2 "reg_or_int_operand" "lPd")))]
1201   "TARGET_THUMB1"
1202   "sub\\t%0, %1, %2"
1203   [(set_attr "length" "2")
1204    (set_attr "conds" "set")])
1206 ; ??? Check Thumb-2 split length
1207 (define_insn_and_split "*arm_subsi3_insn"
1208   [(set (match_operand:SI           0 "s_register_operand" "=r,r,rk,r")
1209         (minus:SI (match_operand:SI 1 "reg_or_int_operand" "rI,r,k,?n")
1210                   (match_operand:SI 2 "reg_or_int_operand" "r,rI,r, r")))]
1211   "TARGET_32BIT"
1212   "@
1213    rsb%?\\t%0, %2, %1
1214    sub%?\\t%0, %1, %2
1215    sub%?\\t%0, %1, %2
1216    #"
1217   "&& (GET_CODE (operands[1]) == CONST_INT
1218        && !const_ok_for_arm (INTVAL (operands[1])))"
1219   [(clobber (const_int 0))]
1220   "
1221   arm_split_constant (MINUS, SImode, curr_insn,
1222                       INTVAL (operands[1]), operands[0], operands[2], 0);
1223   DONE;
1224   "
1225   [(set_attr "length" "4,4,4,16")
1226    (set_attr "predicable" "yes")]
1229 (define_peephole2
1230   [(match_scratch:SI 3 "r")
1231    (set (match_operand:SI 0 "arm_general_register_operand" "")
1232         (minus:SI (match_operand:SI 1 "const_int_operand" "")
1233                   (match_operand:SI 2 "arm_general_register_operand" "")))]
1234   "TARGET_32BIT
1235    && !const_ok_for_arm (INTVAL (operands[1]))
1236    && const_ok_for_arm (~INTVAL (operands[1]))"
1237   [(set (match_dup 3) (match_dup 1))
1238    (set (match_dup 0) (minus:SI (match_dup 3) (match_dup 2)))]
1239   ""
1242 (define_insn "*subsi3_compare0"
1243   [(set (reg:CC_NOOV CC_REGNUM)
1244         (compare:CC_NOOV
1245          (minus:SI (match_operand:SI 1 "arm_rhs_operand" "r,I")
1246                    (match_operand:SI 2 "arm_rhs_operand" "rI,r"))
1247          (const_int 0)))
1248    (set (match_operand:SI 0 "s_register_operand" "=r,r")
1249         (minus:SI (match_dup 1) (match_dup 2)))]
1250   "TARGET_32BIT"
1251   "@
1252    sub%.\\t%0, %1, %2
1253    rsb%.\\t%0, %2, %1"
1254   [(set_attr "conds" "set")]
1257 (define_insn "*subsi3_compare"
1258   [(set (reg:CC CC_REGNUM)
1259         (compare:CC (match_operand:SI 1 "arm_rhs_operand" "r,I")
1260                     (match_operand:SI 2 "arm_rhs_operand" "rI,r")))
1261    (set (match_operand:SI 0 "s_register_operand" "=r,r")
1262         (minus:SI (match_dup 1) (match_dup 2)))]
1263   "TARGET_32BIT"
1264   "@
1265    sub%.\\t%0, %1, %2
1266    rsb%.\\t%0, %2, %1"
1267   [(set_attr "conds" "set")]
1270 (define_expand "decscc"
1271   [(set (match_operand:SI            0 "s_register_operand" "=r,r")
1272         (minus:SI (match_operand:SI  1 "s_register_operand" "0,?r")
1273                   (match_operator:SI 2 "arm_comparison_operator"
1274                    [(match_operand   3 "cc_register" "") (const_int 0)])))]
1275   "TARGET_32BIT"
1276   ""
1279 (define_insn "*arm_decscc"
1280   [(set (match_operand:SI            0 "s_register_operand" "=r,r")
1281         (minus:SI (match_operand:SI  1 "s_register_operand" "0,?r")
1282                   (match_operator:SI 2 "arm_comparison_operator"
1283                    [(match_operand   3 "cc_register" "") (const_int 0)])))]
1284   "TARGET_ARM"
1285   "@
1286    sub%d2\\t%0, %1, #1
1287    mov%D2\\t%0, %1\;sub%d2\\t%0, %1, #1"
1288   [(set_attr "conds" "use")
1289    (set_attr "length" "*,8")]
1292 (define_expand "subsf3"
1293   [(set (match_operand:SF           0 "s_register_operand" "")
1294         (minus:SF (match_operand:SF 1 "arm_float_rhs_operand" "")
1295                   (match_operand:SF 2 "arm_float_rhs_operand" "")))]
1296   "TARGET_32BIT && TARGET_HARD_FLOAT"
1297   "
1300 (define_expand "subdf3"
1301   [(set (match_operand:DF           0 "s_register_operand" "")
1302         (minus:DF (match_operand:DF 1 "arm_float_rhs_operand" "")
1303                   (match_operand:DF 2 "arm_float_rhs_operand" "")))]
1304   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
1305   "
1309 ;; Multiplication insns
1311 (define_expand "mulsi3"
1312   [(set (match_operand:SI          0 "s_register_operand" "")
1313         (mult:SI (match_operand:SI 2 "s_register_operand" "")
1314                  (match_operand:SI 1 "s_register_operand" "")))]
1315   "TARGET_EITHER"
1316   ""
1319 ;; Use `&' and then `0' to prevent the operands 0 and 1 being the same
1320 (define_insn "*arm_mulsi3"
1321   [(set (match_operand:SI          0 "s_register_operand" "=&r,&r")
1322         (mult:SI (match_operand:SI 2 "s_register_operand" "r,r")
1323                  (match_operand:SI 1 "s_register_operand" "%0,r")))]
1324   "TARGET_32BIT && !arm_arch6"
1325   "mul%?\\t%0, %2, %1"
1326   [(set_attr "insn" "mul")
1327    (set_attr "predicable" "yes")]
1330 (define_insn "*arm_mulsi3_v6"
1331   [(set (match_operand:SI          0 "s_register_operand" "=r")
1332         (mult:SI (match_operand:SI 1 "s_register_operand" "r")
1333                  (match_operand:SI 2 "s_register_operand" "r")))]
1334   "TARGET_32BIT && arm_arch6"
1335   "mul%?\\t%0, %1, %2"
1336   [(set_attr "insn" "mul")
1337    (set_attr "predicable" "yes")]
1340 ; Unfortunately with the Thumb the '&'/'0' trick can fails when operands 
1341 ; 1 and 2; are the same, because reload will make operand 0 match 
1342 ; operand 1 without realizing that this conflicts with operand 2.  We fix 
1343 ; this by adding another alternative to match this case, and then `reload' 
1344 ; it ourselves.  This alternative must come first.
1345 (define_insn "*thumb_mulsi3"
1346   [(set (match_operand:SI          0 "register_operand" "=&l,&l,&l")
1347         (mult:SI (match_operand:SI 1 "register_operand" "%l,*h,0")
1348                  (match_operand:SI 2 "register_operand" "l,l,l")))]
1349   "TARGET_THUMB1 && !arm_arch6"
1350   "*
1351   if (which_alternative < 2)
1352     return \"mov\\t%0, %1\;mul\\t%0, %2\";
1353   else
1354     return \"mul\\t%0, %2\";
1355   "
1356   [(set_attr "length" "4,4,2")
1357    (set_attr "insn" "mul")]
1360 (define_insn "*thumb_mulsi3_v6"
1361   [(set (match_operand:SI          0 "register_operand" "=l,l,l")
1362         (mult:SI (match_operand:SI 1 "register_operand" "0,l,0")
1363                  (match_operand:SI 2 "register_operand" "l,0,0")))]
1364   "TARGET_THUMB1 && arm_arch6"
1365   "@
1366    mul\\t%0, %2
1367    mul\\t%0, %1
1368    mul\\t%0, %1"
1369   [(set_attr "length" "2")
1370    (set_attr "insn" "mul")]
1373 (define_insn "*mulsi3_compare0"
1374   [(set (reg:CC_NOOV CC_REGNUM)
1375         (compare:CC_NOOV (mult:SI
1376                           (match_operand:SI 2 "s_register_operand" "r,r")
1377                           (match_operand:SI 1 "s_register_operand" "%0,r"))
1378                          (const_int 0)))
1379    (set (match_operand:SI 0 "s_register_operand" "=&r,&r")
1380         (mult:SI (match_dup 2) (match_dup 1)))]
1381   "TARGET_ARM && !arm_arch6"
1382   "mul%.\\t%0, %2, %1"
1383   [(set_attr "conds" "set")
1384    (set_attr "insn" "muls")]
1387 (define_insn "*mulsi3_compare0_v6"
1388   [(set (reg:CC_NOOV CC_REGNUM)
1389         (compare:CC_NOOV (mult:SI
1390                           (match_operand:SI 2 "s_register_operand" "r")
1391                           (match_operand:SI 1 "s_register_operand" "r"))
1392                          (const_int 0)))
1393    (set (match_operand:SI 0 "s_register_operand" "=r")
1394         (mult:SI (match_dup 2) (match_dup 1)))]
1395   "TARGET_ARM && arm_arch6 && optimize_size"
1396   "mul%.\\t%0, %2, %1"
1397   [(set_attr "conds" "set")
1398    (set_attr "insn" "muls")]
1401 (define_insn "*mulsi_compare0_scratch"
1402   [(set (reg:CC_NOOV CC_REGNUM)
1403         (compare:CC_NOOV (mult:SI
1404                           (match_operand:SI 2 "s_register_operand" "r,r")
1405                           (match_operand:SI 1 "s_register_operand" "%0,r"))
1406                          (const_int 0)))
1407    (clobber (match_scratch:SI 0 "=&r,&r"))]
1408   "TARGET_ARM && !arm_arch6"
1409   "mul%.\\t%0, %2, %1"
1410   [(set_attr "conds" "set")
1411    (set_attr "insn" "muls")]
1414 (define_insn "*mulsi_compare0_scratch_v6"
1415   [(set (reg:CC_NOOV CC_REGNUM)
1416         (compare:CC_NOOV (mult:SI
1417                           (match_operand:SI 2 "s_register_operand" "r")
1418                           (match_operand:SI 1 "s_register_operand" "r"))
1419                          (const_int 0)))
1420    (clobber (match_scratch:SI 0 "=r"))]
1421   "TARGET_ARM && arm_arch6 && optimize_size"
1422   "mul%.\\t%0, %2, %1"
1423   [(set_attr "conds" "set")
1424    (set_attr "insn" "muls")]
1427 ;; Unnamed templates to match MLA instruction.
1429 (define_insn "*mulsi3addsi"
1430   [(set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r,&r")
1431         (plus:SI
1432           (mult:SI (match_operand:SI 2 "s_register_operand" "r,r,r,r")
1433                    (match_operand:SI 1 "s_register_operand" "%0,r,0,r"))
1434           (match_operand:SI 3 "s_register_operand" "r,r,0,0")))]
1435   "TARGET_32BIT && !arm_arch6"
1436   "mla%?\\t%0, %2, %1, %3"
1437   [(set_attr "insn" "mla")
1438    (set_attr "predicable" "yes")]
1441 (define_insn "*mulsi3addsi_v6"
1442   [(set (match_operand:SI 0 "s_register_operand" "=r")
1443         (plus:SI
1444           (mult:SI (match_operand:SI 2 "s_register_operand" "r")
1445                    (match_operand:SI 1 "s_register_operand" "r"))
1446           (match_operand:SI 3 "s_register_operand" "r")))]
1447   "TARGET_32BIT && arm_arch6"
1448   "mla%?\\t%0, %2, %1, %3"
1449   [(set_attr "insn" "mla")
1450    (set_attr "predicable" "yes")]
1453 (define_insn "*mulsi3addsi_compare0"
1454   [(set (reg:CC_NOOV CC_REGNUM)
1455         (compare:CC_NOOV
1456          (plus:SI (mult:SI
1457                    (match_operand:SI 2 "s_register_operand" "r,r,r,r")
1458                    (match_operand:SI 1 "s_register_operand" "%0,r,0,r"))
1459                   (match_operand:SI 3 "s_register_operand" "r,r,0,0"))
1460          (const_int 0)))
1461    (set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r,&r")
1462         (plus:SI (mult:SI (match_dup 2) (match_dup 1))
1463                  (match_dup 3)))]
1464   "TARGET_ARM && arm_arch6"
1465   "mla%.\\t%0, %2, %1, %3"
1466   [(set_attr "conds" "set")
1467    (set_attr "insn" "mlas")]
1470 (define_insn "*mulsi3addsi_compare0_v6"
1471   [(set (reg:CC_NOOV CC_REGNUM)
1472         (compare:CC_NOOV
1473          (plus:SI (mult:SI
1474                    (match_operand:SI 2 "s_register_operand" "r")
1475                    (match_operand:SI 1 "s_register_operand" "r"))
1476                   (match_operand:SI 3 "s_register_operand" "r"))
1477          (const_int 0)))
1478    (set (match_operand:SI 0 "s_register_operand" "=r")
1479         (plus:SI (mult:SI (match_dup 2) (match_dup 1))
1480                  (match_dup 3)))]
1481   "TARGET_ARM && arm_arch6 && optimize_size"
1482   "mla%.\\t%0, %2, %1, %3"
1483   [(set_attr "conds" "set")
1484    (set_attr "insn" "mlas")]
1487 (define_insn "*mulsi3addsi_compare0_scratch"
1488   [(set (reg:CC_NOOV CC_REGNUM)
1489         (compare:CC_NOOV
1490          (plus:SI (mult:SI
1491                    (match_operand:SI 2 "s_register_operand" "r,r,r,r")
1492                    (match_operand:SI 1 "s_register_operand" "%0,r,0,r"))
1493                   (match_operand:SI 3 "s_register_operand" "?r,r,0,0"))
1494          (const_int 0)))
1495    (clobber (match_scratch:SI 0 "=&r,&r,&r,&r"))]
1496   "TARGET_ARM && !arm_arch6"
1497   "mla%.\\t%0, %2, %1, %3"
1498   [(set_attr "conds" "set")
1499    (set_attr "insn" "mlas")]
1502 (define_insn "*mulsi3addsi_compare0_scratch_v6"
1503   [(set (reg:CC_NOOV CC_REGNUM)
1504         (compare:CC_NOOV
1505          (plus:SI (mult:SI
1506                    (match_operand:SI 2 "s_register_operand" "r")
1507                    (match_operand:SI 1 "s_register_operand" "r"))
1508                   (match_operand:SI 3 "s_register_operand" "r"))
1509          (const_int 0)))
1510    (clobber (match_scratch:SI 0 "=r"))]
1511   "TARGET_ARM && arm_arch6 && optimize_size"
1512   "mla%.\\t%0, %2, %1, %3"
1513   [(set_attr "conds" "set")
1514    (set_attr "insn" "mlas")]
1517 (define_insn "*mulsi3subsi"
1518   [(set (match_operand:SI 0 "s_register_operand" "=r")
1519         (minus:SI
1520           (match_operand:SI 3 "s_register_operand" "r")
1521           (mult:SI (match_operand:SI 2 "s_register_operand" "r")
1522                    (match_operand:SI 1 "s_register_operand" "r"))))]
1523   "TARGET_32BIT && arm_arch_thumb2"
1524   "mls%?\\t%0, %2, %1, %3"
1525   [(set_attr "insn" "mla")
1526    (set_attr "predicable" "yes")]
1529 (define_expand "maddsidi4"
1530   [(set (match_operand:DI 0 "s_register_operand" "")
1531         (plus:DI
1532          (mult:DI
1533           (sign_extend:DI (match_operand:SI 1 "s_register_operand" ""))
1534           (sign_extend:DI (match_operand:SI 2 "s_register_operand" "")))
1535          (match_operand:DI 3 "s_register_operand" "")))]
1536   "TARGET_32BIT && arm_arch3m"
1537   "")
1539 (define_insn "*mulsidi3adddi"
1540   [(set (match_operand:DI 0 "s_register_operand" "=&r")
1541         (plus:DI
1542          (mult:DI
1543           (sign_extend:DI (match_operand:SI 2 "s_register_operand" "%r"))
1544           (sign_extend:DI (match_operand:SI 3 "s_register_operand" "r")))
1545          (match_operand:DI 1 "s_register_operand" "0")))]
1546   "TARGET_32BIT && arm_arch3m && !arm_arch6"
1547   "smlal%?\\t%Q0, %R0, %3, %2"
1548   [(set_attr "insn" "smlal")
1549    (set_attr "predicable" "yes")]
1552 (define_insn "*mulsidi3adddi_v6"
1553   [(set (match_operand:DI 0 "s_register_operand" "=r")
1554         (plus:DI
1555          (mult:DI
1556           (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r"))
1557           (sign_extend:DI (match_operand:SI 3 "s_register_operand" "r")))
1558          (match_operand:DI 1 "s_register_operand" "0")))]
1559   "TARGET_32BIT && arm_arch6"
1560   "smlal%?\\t%Q0, %R0, %3, %2"
1561   [(set_attr "insn" "smlal")
1562    (set_attr "predicable" "yes")]
1565 ;; 32x32->64 widening multiply.
1566 ;; As with mulsi3, the only difference between the v3-5 and v6+
1567 ;; versions of these patterns is the requirement that the output not
1568 ;; overlap the inputs, but that still means we have to have a named
1569 ;; expander and two different starred insns.
1571 (define_expand "mulsidi3"
1572   [(set (match_operand:DI 0 "s_register_operand" "")
1573         (mult:DI
1574          (sign_extend:DI (match_operand:SI 1 "s_register_operand" ""))
1575          (sign_extend:DI (match_operand:SI 2 "s_register_operand" ""))))]
1576   "TARGET_32BIT && arm_arch3m"
1577   ""
1580 (define_insn "*mulsidi3_nov6"
1581   [(set (match_operand:DI 0 "s_register_operand" "=&r")
1582         (mult:DI
1583          (sign_extend:DI (match_operand:SI 1 "s_register_operand" "%r"))
1584          (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r"))))]
1585   "TARGET_32BIT && arm_arch3m && !arm_arch6"
1586   "smull%?\\t%Q0, %R0, %1, %2"
1587   [(set_attr "insn" "smull")
1588    (set_attr "predicable" "yes")]
1591 (define_insn "*mulsidi3_v6"
1592   [(set (match_operand:DI 0 "s_register_operand" "=r")
1593         (mult:DI
1594          (sign_extend:DI (match_operand:SI 1 "s_register_operand" "r"))
1595          (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r"))))]
1596   "TARGET_32BIT && arm_arch6"
1597   "smull%?\\t%Q0, %R0, %1, %2"
1598   [(set_attr "insn" "smull")
1599    (set_attr "predicable" "yes")]
1602 (define_expand "umulsidi3"
1603   [(set (match_operand:DI 0 "s_register_operand" "")
1604         (mult:DI
1605          (zero_extend:DI (match_operand:SI 1 "s_register_operand" ""))
1606          (zero_extend:DI (match_operand:SI 2 "s_register_operand" ""))))]
1607   "TARGET_32BIT && arm_arch3m"
1608   ""
1611 (define_insn "*umulsidi3_nov6"
1612   [(set (match_operand:DI 0 "s_register_operand" "=&r")
1613         (mult:DI
1614          (zero_extend:DI (match_operand:SI 1 "s_register_operand" "%r"))
1615          (zero_extend:DI (match_operand:SI 2 "s_register_operand" "r"))))]
1616   "TARGET_32BIT && arm_arch3m && !arm_arch6"
1617   "umull%?\\t%Q0, %R0, %1, %2"
1618   [(set_attr "insn" "umull")
1619    (set_attr "predicable" "yes")]
1622 (define_insn "*umulsidi3_v6"
1623   [(set (match_operand:DI 0 "s_register_operand" "=r")
1624         (mult:DI
1625          (zero_extend:DI (match_operand:SI 1 "s_register_operand" "r"))
1626          (zero_extend:DI (match_operand:SI 2 "s_register_operand" "r"))))]
1627   "TARGET_32BIT && arm_arch6"
1628   "umull%?\\t%Q0, %R0, %1, %2"
1629   [(set_attr "insn" "umull")
1630    (set_attr "predicable" "yes")]
1633 (define_expand "umaddsidi4"
1634   [(set (match_operand:DI 0 "s_register_operand" "")
1635         (plus:DI
1636          (mult:DI
1637           (zero_extend:DI (match_operand:SI 1 "s_register_operand" ""))
1638           (zero_extend:DI (match_operand:SI 2 "s_register_operand" "")))
1639          (match_operand:DI 3 "s_register_operand" "")))]
1640   "TARGET_32BIT && arm_arch3m"
1641   "")
1643 (define_insn "*umulsidi3adddi"
1644   [(set (match_operand:DI 0 "s_register_operand" "=&r")
1645         (plus:DI
1646          (mult:DI
1647           (zero_extend:DI (match_operand:SI 2 "s_register_operand" "%r"))
1648           (zero_extend:DI (match_operand:SI 3 "s_register_operand" "r")))
1649          (match_operand:DI 1 "s_register_operand" "0")))]
1650   "TARGET_32BIT && arm_arch3m && !arm_arch6"
1651   "umlal%?\\t%Q0, %R0, %3, %2"
1652   [(set_attr "insn" "umlal")
1653    (set_attr "predicable" "yes")]
1656 (define_insn "*umulsidi3adddi_v6"
1657   [(set (match_operand:DI 0 "s_register_operand" "=r")
1658         (plus:DI
1659          (mult:DI
1660           (zero_extend:DI (match_operand:SI 2 "s_register_operand" "r"))
1661           (zero_extend:DI (match_operand:SI 3 "s_register_operand" "r")))
1662          (match_operand:DI 1 "s_register_operand" "0")))]
1663   "TARGET_32BIT && arm_arch6"
1664   "umlal%?\\t%Q0, %R0, %3, %2"
1665   [(set_attr "insn" "umlal")
1666    (set_attr "predicable" "yes")]
1669 (define_expand "smulsi3_highpart"
1670   [(parallel
1671     [(set (match_operand:SI 0 "s_register_operand" "")
1672           (truncate:SI
1673            (lshiftrt:DI
1674             (mult:DI
1675              (sign_extend:DI (match_operand:SI 1 "s_register_operand" ""))
1676              (sign_extend:DI (match_operand:SI 2 "s_register_operand" "")))
1677             (const_int 32))))
1678      (clobber (match_scratch:SI 3 ""))])]
1679   "TARGET_32BIT && arm_arch3m"
1680   ""
1683 (define_insn "*smulsi3_highpart_nov6"
1684   [(set (match_operand:SI 0 "s_register_operand" "=&r,&r")
1685         (truncate:SI
1686          (lshiftrt:DI
1687           (mult:DI
1688            (sign_extend:DI (match_operand:SI 1 "s_register_operand" "%0,r"))
1689            (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r,r")))
1690           (const_int 32))))
1691    (clobber (match_scratch:SI 3 "=&r,&r"))]
1692   "TARGET_32BIT && arm_arch3m && !arm_arch6"
1693   "smull%?\\t%3, %0, %2, %1"
1694   [(set_attr "insn" "smull")
1695    (set_attr "predicable" "yes")]
1698 (define_insn "*smulsi3_highpart_v6"
1699   [(set (match_operand:SI 0 "s_register_operand" "=r")
1700         (truncate:SI
1701          (lshiftrt:DI
1702           (mult:DI
1703            (sign_extend:DI (match_operand:SI 1 "s_register_operand" "r"))
1704            (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r")))
1705           (const_int 32))))
1706    (clobber (match_scratch:SI 3 "=r"))]
1707   "TARGET_32BIT && arm_arch6"
1708   "smull%?\\t%3, %0, %2, %1"
1709   [(set_attr "insn" "smull")
1710    (set_attr "predicable" "yes")]
1713 (define_expand "umulsi3_highpart"
1714   [(parallel
1715     [(set (match_operand:SI 0 "s_register_operand" "")
1716           (truncate:SI
1717            (lshiftrt:DI
1718             (mult:DI
1719              (zero_extend:DI (match_operand:SI 1 "s_register_operand" ""))
1720               (zero_extend:DI (match_operand:SI 2 "s_register_operand" "")))
1721             (const_int 32))))
1722      (clobber (match_scratch:SI 3 ""))])]
1723   "TARGET_32BIT && arm_arch3m"
1724   ""
1727 (define_insn "*umulsi3_highpart_nov6"
1728   [(set (match_operand:SI 0 "s_register_operand" "=&r,&r")
1729         (truncate:SI
1730          (lshiftrt:DI
1731           (mult:DI
1732            (zero_extend:DI (match_operand:SI 1 "s_register_operand" "%0,r"))
1733            (zero_extend:DI (match_operand:SI 2 "s_register_operand" "r,r")))
1734           (const_int 32))))
1735    (clobber (match_scratch:SI 3 "=&r,&r"))]
1736   "TARGET_32BIT && arm_arch3m && !arm_arch6"
1737   "umull%?\\t%3, %0, %2, %1"
1738   [(set_attr "insn" "umull")
1739    (set_attr "predicable" "yes")]
1742 (define_insn "*umulsi3_highpart_v6"
1743   [(set (match_operand:SI 0 "s_register_operand" "=r")
1744         (truncate:SI
1745          (lshiftrt:DI
1746           (mult:DI
1747            (zero_extend:DI (match_operand:SI 1 "s_register_operand" "r"))
1748            (zero_extend:DI (match_operand:SI 2 "s_register_operand" "r")))
1749           (const_int 32))))
1750    (clobber (match_scratch:SI 3 "=r"))]
1751   "TARGET_32BIT && arm_arch6"
1752   "umull%?\\t%3, %0, %2, %1"
1753   [(set_attr "insn" "umull")
1754    (set_attr "predicable" "yes")]
1757 (define_insn "mulhisi3"
1758   [(set (match_operand:SI 0 "s_register_operand" "=r")
1759         (mult:SI (sign_extend:SI
1760                   (match_operand:HI 1 "s_register_operand" "%r"))
1761                  (sign_extend:SI
1762                   (match_operand:HI 2 "s_register_operand" "r"))))]
1763   "TARGET_DSP_MULTIPLY"
1764   "smulbb%?\\t%0, %1, %2"
1765   [(set_attr "insn" "smulxy")
1766    (set_attr "predicable" "yes")]
1769 (define_insn "*mulhisi3tb"
1770   [(set (match_operand:SI 0 "s_register_operand" "=r")
1771         (mult:SI (ashiftrt:SI
1772                   (match_operand:SI 1 "s_register_operand" "r")
1773                   (const_int 16))
1774                  (sign_extend:SI
1775                   (match_operand:HI 2 "s_register_operand" "r"))))]
1776   "TARGET_DSP_MULTIPLY"
1777   "smultb%?\\t%0, %1, %2"
1778   [(set_attr "insn" "smulxy")
1779    (set_attr "predicable" "yes")]
1782 (define_insn "*mulhisi3bt"
1783   [(set (match_operand:SI 0 "s_register_operand" "=r")
1784         (mult:SI (sign_extend:SI
1785                   (match_operand:HI 1 "s_register_operand" "r"))
1786                  (ashiftrt:SI
1787                   (match_operand:SI 2 "s_register_operand" "r")
1788                   (const_int 16))))]
1789   "TARGET_DSP_MULTIPLY"
1790   "smulbt%?\\t%0, %1, %2"
1791   [(set_attr "insn" "smulxy")
1792    (set_attr "predicable" "yes")]
1795 (define_insn "*mulhisi3tt"
1796   [(set (match_operand:SI 0 "s_register_operand" "=r")
1797         (mult:SI (ashiftrt:SI
1798                   (match_operand:SI 1 "s_register_operand" "r")
1799                   (const_int 16))
1800                  (ashiftrt:SI
1801                   (match_operand:SI 2 "s_register_operand" "r")
1802                   (const_int 16))))]
1803   "TARGET_DSP_MULTIPLY"
1804   "smultt%?\\t%0, %1, %2"
1805   [(set_attr "insn" "smulxy")
1806    (set_attr "predicable" "yes")]
1809 (define_insn "maddhisi4"
1810   [(set (match_operand:SI 0 "s_register_operand" "=r")
1811         (plus:SI (mult:SI (sign_extend:SI
1812                            (match_operand:HI 1 "s_register_operand" "r"))
1813                           (sign_extend:SI
1814                            (match_operand:HI 2 "s_register_operand" "r")))
1815                  (match_operand:SI 3 "s_register_operand" "r")))]
1816   "TARGET_DSP_MULTIPLY"
1817   "smlabb%?\\t%0, %1, %2, %3"
1818   [(set_attr "insn" "smlaxy")
1819    (set_attr "predicable" "yes")]
1822 ;; Note: there is no maddhisi4ibt because this one is canonical form
1823 (define_insn "*maddhisi4tb"
1824   [(set (match_operand:SI 0 "s_register_operand" "=r")
1825         (plus:SI (mult:SI (ashiftrt:SI
1826                            (match_operand:SI 1 "s_register_operand" "r")
1827                            (const_int 16))
1828                           (sign_extend:SI
1829                            (match_operand:HI 2 "s_register_operand" "r")))
1830                  (match_operand:SI 3 "s_register_operand" "r")))]
1831   "TARGET_DSP_MULTIPLY"
1832   "smlatb%?\\t%0, %1, %2, %3"
1833   [(set_attr "insn" "smlaxy")
1834    (set_attr "predicable" "yes")]
1837 (define_insn "*maddhisi4tt"
1838   [(set (match_operand:SI 0 "s_register_operand" "=r")
1839         (plus:SI (mult:SI (ashiftrt:SI
1840                            (match_operand:SI 1 "s_register_operand" "r")
1841                            (const_int 16))
1842                           (ashiftrt:SI
1843                            (match_operand:SI 2 "s_register_operand" "r")
1844                            (const_int 16)))
1845                  (match_operand:SI 3 "s_register_operand" "r")))]
1846   "TARGET_DSP_MULTIPLY"
1847   "smlatt%?\\t%0, %1, %2, %3"
1848   [(set_attr "insn" "smlaxy")
1849    (set_attr "predicable" "yes")]
1852 (define_insn "maddhidi4"
1853   [(set (match_operand:DI 0 "s_register_operand" "=r")
1854         (plus:DI
1855           (mult:DI (sign_extend:DI
1856                     (match_operand:HI 1 "s_register_operand" "r"))
1857                    (sign_extend:DI
1858                     (match_operand:HI 2 "s_register_operand" "r")))
1859           (match_operand:DI 3 "s_register_operand" "0")))]
1860   "TARGET_DSP_MULTIPLY"
1861   "smlalbb%?\\t%Q0, %R0, %1, %2"
1862   [(set_attr "insn" "smlalxy")
1863    (set_attr "predicable" "yes")])
1865 ;; Note: there is no maddhidi4ibt because this one is canonical form
1866 (define_insn "*maddhidi4tb"
1867   [(set (match_operand:DI 0 "s_register_operand" "=r")
1868         (plus:DI
1869           (mult:DI (sign_extend:DI
1870                     (ashiftrt:SI
1871                      (match_operand:SI 1 "s_register_operand" "r")
1872                      (const_int 16)))
1873                    (sign_extend:DI
1874                     (match_operand:HI 2 "s_register_operand" "r")))
1875           (match_operand:DI 3 "s_register_operand" "0")))]
1876   "TARGET_DSP_MULTIPLY"
1877   "smlaltb%?\\t%Q0, %R0, %1, %2"
1878   [(set_attr "insn" "smlalxy")
1879    (set_attr "predicable" "yes")])
1881 (define_insn "*maddhidi4tt"
1882   [(set (match_operand:DI 0 "s_register_operand" "=r")
1883         (plus:DI
1884           (mult:DI (sign_extend:DI
1885                     (ashiftrt:SI
1886                      (match_operand:SI 1 "s_register_operand" "r")
1887                      (const_int 16)))
1888                    (sign_extend:DI
1889                     (ashiftrt:SI
1890                      (match_operand:SI 2 "s_register_operand" "r")
1891                      (const_int 16))))
1892           (match_operand:DI 3 "s_register_operand" "0")))]
1893   "TARGET_DSP_MULTIPLY"
1894   "smlaltt%?\\t%Q0, %R0, %1, %2"
1895   [(set_attr "insn" "smlalxy")
1896    (set_attr "predicable" "yes")])
1898 (define_expand "mulsf3"
1899   [(set (match_operand:SF          0 "s_register_operand" "")
1900         (mult:SF (match_operand:SF 1 "s_register_operand" "")
1901                  (match_operand:SF 2 "arm_float_rhs_operand" "")))]
1902   "TARGET_32BIT && TARGET_HARD_FLOAT"
1903   "
1906 (define_expand "muldf3"
1907   [(set (match_operand:DF          0 "s_register_operand" "")
1908         (mult:DF (match_operand:DF 1 "s_register_operand" "")
1909                  (match_operand:DF 2 "arm_float_rhs_operand" "")))]
1910   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
1911   "
1914 ;; Division insns
1916 (define_expand "divsf3"
1917   [(set (match_operand:SF 0 "s_register_operand" "")
1918         (div:SF (match_operand:SF 1 "arm_float_rhs_operand" "")
1919                 (match_operand:SF 2 "arm_float_rhs_operand" "")))]
1920   "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP"
1921   "")
1923 (define_expand "divdf3"
1924   [(set (match_operand:DF 0 "s_register_operand" "")
1925         (div:DF (match_operand:DF 1 "arm_float_rhs_operand" "")
1926                 (match_operand:DF 2 "arm_float_rhs_operand" "")))]
1927   "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
1928   "")
1930 ;; Boolean and,ior,xor insns
1932 ;; Split up double word logical operations
1934 ;; Split up simple DImode logical operations.  Simply perform the logical
1935 ;; operation on the upper and lower halves of the registers.
1936 (define_split
1937   [(set (match_operand:DI 0 "s_register_operand" "")
1938         (match_operator:DI 6 "logical_binary_operator"
1939           [(match_operand:DI 1 "s_register_operand" "")
1940            (match_operand:DI 2 "s_register_operand" "")]))]
1941   "TARGET_32BIT && reload_completed
1942    && ! (TARGET_NEON && IS_VFP_REGNUM (REGNO (operands[0])))
1943    && ! IS_IWMMXT_REGNUM (REGNO (operands[0]))"
1944   [(set (match_dup 0) (match_op_dup:SI 6 [(match_dup 1) (match_dup 2)]))
1945    (set (match_dup 3) (match_op_dup:SI 6 [(match_dup 4) (match_dup 5)]))]
1946   "
1947   {
1948     operands[3] = gen_highpart (SImode, operands[0]);
1949     operands[0] = gen_lowpart (SImode, operands[0]);
1950     operands[4] = gen_highpart (SImode, operands[1]);
1951     operands[1] = gen_lowpart (SImode, operands[1]);
1952     operands[5] = gen_highpart (SImode, operands[2]);
1953     operands[2] = gen_lowpart (SImode, operands[2]);
1954   }"
1957 (define_split
1958   [(set (match_operand:DI 0 "s_register_operand" "")
1959         (match_operator:DI 6 "logical_binary_operator"
1960           [(sign_extend:DI (match_operand:SI 2 "s_register_operand" ""))
1961            (match_operand:DI 1 "s_register_operand" "")]))]
1962   "TARGET_32BIT && reload_completed"
1963   [(set (match_dup 0) (match_op_dup:SI 6 [(match_dup 1) (match_dup 2)]))
1964    (set (match_dup 3) (match_op_dup:SI 6
1965                         [(ashiftrt:SI (match_dup 2) (const_int 31))
1966                          (match_dup 4)]))]
1967   "
1968   {
1969     operands[3] = gen_highpart (SImode, operands[0]);
1970     operands[0] = gen_lowpart (SImode, operands[0]);
1971     operands[4] = gen_highpart (SImode, operands[1]);
1972     operands[1] = gen_lowpart (SImode, operands[1]);
1973     operands[5] = gen_highpart (SImode, operands[2]);
1974     operands[2] = gen_lowpart (SImode, operands[2]);
1975   }"
1978 ;; The zero extend of operand 2 means we can just copy the high part of
1979 ;; operand1 into operand0.
1980 (define_split
1981   [(set (match_operand:DI 0 "s_register_operand" "")
1982         (ior:DI
1983           (zero_extend:DI (match_operand:SI 2 "s_register_operand" ""))
1984           (match_operand:DI 1 "s_register_operand" "")))]
1985   "TARGET_32BIT && operands[0] != operands[1] && reload_completed"
1986   [(set (match_dup 0) (ior:SI (match_dup 1) (match_dup 2)))
1987    (set (match_dup 3) (match_dup 4))]
1988   "
1989   {
1990     operands[4] = gen_highpart (SImode, operands[1]);
1991     operands[3] = gen_highpart (SImode, operands[0]);
1992     operands[0] = gen_lowpart (SImode, operands[0]);
1993     operands[1] = gen_lowpart (SImode, operands[1]);
1994   }"
1997 ;; The zero extend of operand 2 means we can just copy the high part of
1998 ;; operand1 into operand0.
1999 (define_split
2000   [(set (match_operand:DI 0 "s_register_operand" "")
2001         (xor:DI
2002           (zero_extend:DI (match_operand:SI 2 "s_register_operand" ""))
2003           (match_operand:DI 1 "s_register_operand" "")))]
2004   "TARGET_32BIT && operands[0] != operands[1] && reload_completed"
2005   [(set (match_dup 0) (xor:SI (match_dup 1) (match_dup 2)))
2006    (set (match_dup 3) (match_dup 4))]
2007   "
2008   {
2009     operands[4] = gen_highpart (SImode, operands[1]);
2010     operands[3] = gen_highpart (SImode, operands[0]);
2011     operands[0] = gen_lowpart (SImode, operands[0]);
2012     operands[1] = gen_lowpart (SImode, operands[1]);
2013   }"
2016 (define_expand "anddi3"
2017   [(set (match_operand:DI         0 "s_register_operand" "")
2018         (and:DI (match_operand:DI 1 "s_register_operand" "")
2019                 (match_operand:DI 2 "neon_inv_logic_op2" "")))]
2020   "TARGET_32BIT"
2021   ""
2024 (define_insn "*anddi3_insn"
2025   [(set (match_operand:DI         0 "s_register_operand" "=&r,&r")
2026         (and:DI (match_operand:DI 1 "s_register_operand"  "%0,r")
2027                 (match_operand:DI 2 "s_register_operand"   "r,r")))]
2028   "TARGET_32BIT && !TARGET_IWMMXT && !TARGET_NEON"
2029   "#"
2030   [(set_attr "length" "8")]
2033 (define_insn_and_split "*anddi_zesidi_di"
2034   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2035         (and:DI (zero_extend:DI
2036                  (match_operand:SI 2 "s_register_operand" "r,r"))
2037                 (match_operand:DI 1 "s_register_operand" "0,r")))]
2038   "TARGET_32BIT"
2039   "#"
2040   "TARGET_32BIT && reload_completed"
2041   ; The zero extend of operand 2 clears the high word of the output
2042   ; operand.
2043   [(set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))
2044    (set (match_dup 3) (const_int 0))]
2045   "
2046   {
2047     operands[3] = gen_highpart (SImode, operands[0]);
2048     operands[0] = gen_lowpart (SImode, operands[0]);
2049     operands[1] = gen_lowpart (SImode, operands[1]);
2050   }"
2051   [(set_attr "length" "8")]
2054 (define_insn "*anddi_sesdi_di"
2055   [(set (match_operand:DI          0 "s_register_operand" "=&r,&r")
2056         (and:DI (sign_extend:DI
2057                  (match_operand:SI 2 "s_register_operand" "r,r"))
2058                 (match_operand:DI  1 "s_register_operand" "0,r")))]
2059   "TARGET_32BIT"
2060   "#"
2061   [(set_attr "length" "8")]
2064 (define_expand "andsi3"
2065   [(set (match_operand:SI         0 "s_register_operand" "")
2066         (and:SI (match_operand:SI 1 "s_register_operand" "")
2067                 (match_operand:SI 2 "reg_or_int_operand" "")))]
2068   "TARGET_EITHER"
2069   "
2070   if (TARGET_32BIT)
2071     {
2072       if (GET_CODE (operands[2]) == CONST_INT)
2073         {
2074           if (INTVAL (operands[2]) == 255 && arm_arch6)
2075             {
2076               operands[1] = convert_to_mode (QImode, operands[1], 1);
2077               emit_insn (gen_thumb2_zero_extendqisi2_v6 (operands[0],
2078                                                          operands[1]));
2079             }
2080           else
2081             arm_split_constant (AND, SImode, NULL_RTX,
2082                                 INTVAL (operands[2]), operands[0],
2083                                 operands[1],
2084                                 optimize && can_create_pseudo_p ());
2086           DONE;
2087         }
2088     }
2089   else /* TARGET_THUMB1 */
2090     {
2091       if (GET_CODE (operands[2]) != CONST_INT)
2092         {
2093           rtx tmp = force_reg (SImode, operands[2]);
2094           if (rtx_equal_p (operands[0], operands[1]))
2095             operands[2] = tmp;
2096           else
2097             {
2098               operands[2] = operands[1];
2099               operands[1] = tmp;
2100             }
2101         }
2102       else
2103         {
2104           int i;
2105           
2106           if (((unsigned HOST_WIDE_INT) ~INTVAL (operands[2])) < 256)
2107             {
2108               operands[2] = force_reg (SImode,
2109                                        GEN_INT (~INTVAL (operands[2])));
2110               
2111               emit_insn (gen_thumb1_bicsi3 (operands[0], operands[2], operands[1]));
2112               
2113               DONE;
2114             }
2116           for (i = 9; i <= 31; i++)
2117             {
2118               if ((((HOST_WIDE_INT) 1) << i) - 1 == INTVAL (operands[2]))
2119                 {
2120                   emit_insn (gen_extzv (operands[0], operands[1], GEN_INT (i),
2121                                         const0_rtx));
2122                   DONE;
2123                 }
2124               else if ((((HOST_WIDE_INT) 1) << i) - 1
2125                        == ~INTVAL (operands[2]))
2126                 {
2127                   rtx shift = GEN_INT (i);
2128                   rtx reg = gen_reg_rtx (SImode);
2129                 
2130                   emit_insn (gen_lshrsi3 (reg, operands[1], shift));
2131                   emit_insn (gen_ashlsi3 (operands[0], reg, shift));
2132                   
2133                   DONE;
2134                 }
2135             }
2137           operands[2] = force_reg (SImode, operands[2]);
2138         }
2139     }
2140   "
2143 ; ??? Check split length for Thumb-2
2144 (define_insn_and_split "*arm_andsi3_insn"
2145   [(set (match_operand:SI         0 "s_register_operand" "=r,r,r")
2146         (and:SI (match_operand:SI 1 "s_register_operand" "r,r,r")
2147                 (match_operand:SI 2 "reg_or_int_operand" "rI,K,?n")))]
2148   "TARGET_32BIT"
2149   "@
2150    and%?\\t%0, %1, %2
2151    bic%?\\t%0, %1, #%B2
2152    #"
2153   "TARGET_32BIT
2154    && GET_CODE (operands[2]) == CONST_INT
2155    && !(const_ok_for_arm (INTVAL (operands[2]))
2156         || const_ok_for_arm (~INTVAL (operands[2])))"
2157   [(clobber (const_int 0))]
2158   "
2159   arm_split_constant  (AND, SImode, curr_insn, 
2160                        INTVAL (operands[2]), operands[0], operands[1], 0);
2161   DONE;
2162   "
2163   [(set_attr "length" "4,4,16")
2164    (set_attr "predicable" "yes")]
2167 (define_insn "*thumb1_andsi3_insn"
2168   [(set (match_operand:SI         0 "register_operand" "=l")
2169         (and:SI (match_operand:SI 1 "register_operand" "%0")
2170                 (match_operand:SI 2 "register_operand" "l")))]
2171   "TARGET_THUMB1"
2172   "and\\t%0, %2"
2173   [(set_attr "length" "2")
2174    (set_attr "conds" "set")])
2176 (define_insn "*andsi3_compare0"
2177   [(set (reg:CC_NOOV CC_REGNUM)
2178         (compare:CC_NOOV
2179          (and:SI (match_operand:SI 1 "s_register_operand" "r,r")
2180                  (match_operand:SI 2 "arm_not_operand" "rI,K"))
2181          (const_int 0)))
2182    (set (match_operand:SI          0 "s_register_operand" "=r,r")
2183         (and:SI (match_dup 1) (match_dup 2)))]
2184   "TARGET_32BIT"
2185   "@
2186    and%.\\t%0, %1, %2
2187    bic%.\\t%0, %1, #%B2"
2188   [(set_attr "conds" "set")]
2191 (define_insn "*andsi3_compare0_scratch"
2192   [(set (reg:CC_NOOV CC_REGNUM)
2193         (compare:CC_NOOV
2194          (and:SI (match_operand:SI 0 "s_register_operand" "r,r")
2195                  (match_operand:SI 1 "arm_not_operand" "rI,K"))
2196          (const_int 0)))
2197    (clobber (match_scratch:SI 2 "=X,r"))]
2198   "TARGET_32BIT"
2199   "@
2200    tst%?\\t%0, %1
2201    bic%.\\t%2, %0, #%B1"
2202   [(set_attr "conds" "set")]
2205 (define_insn "*zeroextractsi_compare0_scratch"
2206   [(set (reg:CC_NOOV CC_REGNUM)
2207         (compare:CC_NOOV (zero_extract:SI
2208                           (match_operand:SI 0 "s_register_operand" "r")
2209                           (match_operand 1 "const_int_operand" "n")
2210                           (match_operand 2 "const_int_operand" "n"))
2211                          (const_int 0)))]
2212   "TARGET_32BIT
2213   && (INTVAL (operands[2]) >= 0 && INTVAL (operands[2]) < 32
2214       && INTVAL (operands[1]) > 0 
2215       && INTVAL (operands[1]) + (INTVAL (operands[2]) & 1) <= 8
2216       && INTVAL (operands[1]) + INTVAL (operands[2]) <= 32)"
2217   "*
2218   operands[1] = GEN_INT (((1 << INTVAL (operands[1])) - 1)
2219                          << INTVAL (operands[2]));
2220   output_asm_insn (\"tst%?\\t%0, %1\", operands);
2221   return \"\";
2222   "
2223   [(set_attr "conds" "set")
2224    (set_attr "predicable" "yes")]
2227 (define_insn_and_split "*ne_zeroextractsi"
2228   [(set (match_operand:SI 0 "s_register_operand" "=r")
2229         (ne:SI (zero_extract:SI
2230                 (match_operand:SI 1 "s_register_operand" "r")
2231                 (match_operand:SI 2 "const_int_operand" "n")
2232                 (match_operand:SI 3 "const_int_operand" "n"))
2233                (const_int 0)))
2234    (clobber (reg:CC CC_REGNUM))]
2235   "TARGET_32BIT
2236    && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
2237        && INTVAL (operands[2]) > 0 
2238        && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
2239        && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)"
2240   "#"
2241   "TARGET_32BIT
2242    && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
2243        && INTVAL (operands[2]) > 0 
2244        && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
2245        && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)"
2246   [(parallel [(set (reg:CC_NOOV CC_REGNUM)
2247                    (compare:CC_NOOV (and:SI (match_dup 1) (match_dup 2))
2248                                     (const_int 0)))
2249               (set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))])
2250    (set (match_dup 0)
2251         (if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
2252                          (match_dup 0) (const_int 1)))]
2253   "
2254   operands[2] = GEN_INT (((1 << INTVAL (operands[2])) - 1)
2255                          << INTVAL (operands[3])); 
2256   "
2257   [(set_attr "conds" "clob")
2258    (set (attr "length")
2259         (if_then_else (eq_attr "is_thumb" "yes")
2260                       (const_int 12)
2261                       (const_int 8)))]
2264 (define_insn_and_split "*ne_zeroextractsi_shifted"
2265   [(set (match_operand:SI 0 "s_register_operand" "=r")
2266         (ne:SI (zero_extract:SI
2267                 (match_operand:SI 1 "s_register_operand" "r")
2268                 (match_operand:SI 2 "const_int_operand" "n")
2269                 (const_int 0))
2270                (const_int 0)))
2271    (clobber (reg:CC CC_REGNUM))]
2272   "TARGET_ARM"
2273   "#"
2274   "TARGET_ARM"
2275   [(parallel [(set (reg:CC_NOOV CC_REGNUM)
2276                    (compare:CC_NOOV (ashift:SI (match_dup 1) (match_dup 2))
2277                                     (const_int 0)))
2278               (set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))])
2279    (set (match_dup 0)
2280         (if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
2281                          (match_dup 0) (const_int 1)))]
2282   "
2283   operands[2] = GEN_INT (32 - INTVAL (operands[2]));
2284   "
2285   [(set_attr "conds" "clob")
2286    (set_attr "length" "8")]
2289 (define_insn_and_split "*ite_ne_zeroextractsi"
2290   [(set (match_operand:SI 0 "s_register_operand" "=r")
2291         (if_then_else:SI (ne (zero_extract:SI
2292                               (match_operand:SI 1 "s_register_operand" "r")
2293                               (match_operand:SI 2 "const_int_operand" "n")
2294                               (match_operand:SI 3 "const_int_operand" "n"))
2295                              (const_int 0))
2296                          (match_operand:SI 4 "arm_not_operand" "rIK")
2297                          (const_int 0)))
2298    (clobber (reg:CC CC_REGNUM))]
2299   "TARGET_ARM
2300    && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
2301        && INTVAL (operands[2]) > 0 
2302        && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
2303        && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)
2304    && !reg_overlap_mentioned_p (operands[0], operands[4])"
2305   "#"
2306   "TARGET_ARM
2307    && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
2308        && INTVAL (operands[2]) > 0 
2309        && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
2310        && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)
2311    && !reg_overlap_mentioned_p (operands[0], operands[4])"
2312   [(parallel [(set (reg:CC_NOOV CC_REGNUM)
2313                    (compare:CC_NOOV (and:SI (match_dup 1) (match_dup 2))
2314                                     (const_int 0)))
2315               (set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))])
2316    (set (match_dup 0)
2317         (if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
2318                          (match_dup 0) (match_dup 4)))]
2319   "
2320   operands[2] = GEN_INT (((1 << INTVAL (operands[2])) - 1)
2321                          << INTVAL (operands[3])); 
2322   "
2323   [(set_attr "conds" "clob")
2324    (set_attr "length" "8")]
2327 (define_insn_and_split "*ite_ne_zeroextractsi_shifted"
2328   [(set (match_operand:SI 0 "s_register_operand" "=r")
2329         (if_then_else:SI (ne (zero_extract:SI
2330                               (match_operand:SI 1 "s_register_operand" "r")
2331                               (match_operand:SI 2 "const_int_operand" "n")
2332                               (const_int 0))
2333                              (const_int 0))
2334                          (match_operand:SI 3 "arm_not_operand" "rIK")
2335                          (const_int 0)))
2336    (clobber (reg:CC CC_REGNUM))]
2337   "TARGET_ARM && !reg_overlap_mentioned_p (operands[0], operands[3])"
2338   "#"
2339   "TARGET_ARM && !reg_overlap_mentioned_p (operands[0], operands[3])"
2340   [(parallel [(set (reg:CC_NOOV CC_REGNUM)
2341                    (compare:CC_NOOV (ashift:SI (match_dup 1) (match_dup 2))
2342                                     (const_int 0)))
2343               (set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))])
2344    (set (match_dup 0)
2345         (if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
2346                          (match_dup 0) (match_dup 3)))]
2347   "
2348   operands[2] = GEN_INT (32 - INTVAL (operands[2]));
2349   "
2350   [(set_attr "conds" "clob")
2351    (set_attr "length" "8")]
2354 (define_split
2355   [(set (match_operand:SI 0 "s_register_operand" "")
2356         (zero_extract:SI (match_operand:SI 1 "s_register_operand" "")
2357                          (match_operand:SI 2 "const_int_operand" "")
2358                          (match_operand:SI 3 "const_int_operand" "")))
2359    (clobber (match_operand:SI 4 "s_register_operand" ""))]
2360   "TARGET_THUMB1"
2361   [(set (match_dup 4) (ashift:SI (match_dup 1) (match_dup 2)))
2362    (set (match_dup 0) (lshiftrt:SI (match_dup 4) (match_dup 3)))]
2363   "{
2364      HOST_WIDE_INT temp = INTVAL (operands[2]);
2366      operands[2] = GEN_INT (32 - temp - INTVAL (operands[3]));
2367      operands[3] = GEN_INT (32 - temp);
2368    }"
2371 ;; ??? Use Thumb-2 has bitfield insert/extract instructions.
2372 (define_split
2373   [(set (match_operand:SI 0 "s_register_operand" "")
2374         (match_operator:SI 1 "shiftable_operator"
2375          [(zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
2376                            (match_operand:SI 3 "const_int_operand" "")
2377                            (match_operand:SI 4 "const_int_operand" ""))
2378           (match_operand:SI 5 "s_register_operand" "")]))
2379    (clobber (match_operand:SI 6 "s_register_operand" ""))]
2380   "TARGET_ARM"
2381   [(set (match_dup 6) (ashift:SI (match_dup 2) (match_dup 3)))
2382    (set (match_dup 0)
2383         (match_op_dup 1
2384          [(lshiftrt:SI (match_dup 6) (match_dup 4))
2385           (match_dup 5)]))]
2386   "{
2387      HOST_WIDE_INT temp = INTVAL (operands[3]);
2389      operands[3] = GEN_INT (32 - temp - INTVAL (operands[4]));
2390      operands[4] = GEN_INT (32 - temp);
2391    }"
2393   
2394 (define_split
2395   [(set (match_operand:SI 0 "s_register_operand" "")
2396         (sign_extract:SI (match_operand:SI 1 "s_register_operand" "")
2397                          (match_operand:SI 2 "const_int_operand" "")
2398                          (match_operand:SI 3 "const_int_operand" "")))]
2399   "TARGET_THUMB1"
2400   [(set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))
2401    (set (match_dup 0) (ashiftrt:SI (match_dup 0) (match_dup 3)))]
2402   "{
2403      HOST_WIDE_INT temp = INTVAL (operands[2]);
2405      operands[2] = GEN_INT (32 - temp - INTVAL (operands[3]));
2406      operands[3] = GEN_INT (32 - temp);
2407    }"
2410 (define_split
2411   [(set (match_operand:SI 0 "s_register_operand" "")
2412         (match_operator:SI 1 "shiftable_operator"
2413          [(sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
2414                            (match_operand:SI 3 "const_int_operand" "")
2415                            (match_operand:SI 4 "const_int_operand" ""))
2416           (match_operand:SI 5 "s_register_operand" "")]))
2417    (clobber (match_operand:SI 6 "s_register_operand" ""))]
2418   "TARGET_ARM"
2419   [(set (match_dup 6) (ashift:SI (match_dup 2) (match_dup 3)))
2420    (set (match_dup 0)
2421         (match_op_dup 1
2422          [(ashiftrt:SI (match_dup 6) (match_dup 4))
2423           (match_dup 5)]))]
2424   "{
2425      HOST_WIDE_INT temp = INTVAL (operands[3]);
2427      operands[3] = GEN_INT (32 - temp - INTVAL (operands[4]));
2428      operands[4] = GEN_INT (32 - temp);
2429    }"
2431   
2432 ;;; ??? This pattern is bogus.  If operand3 has bits outside the range
2433 ;;; represented by the bitfield, then this will produce incorrect results.
2434 ;;; Somewhere, the value needs to be truncated.  On targets like the m68k,
2435 ;;; which have a real bit-field insert instruction, the truncation happens
2436 ;;; in the bit-field insert instruction itself.  Since arm does not have a
2437 ;;; bit-field insert instruction, we would have to emit code here to truncate
2438 ;;; the value before we insert.  This loses some of the advantage of having
2439 ;;; this insv pattern, so this pattern needs to be reevalutated.
2441 (define_expand "insv"
2442   [(set (zero_extract (match_operand 0 "nonimmediate_operand" "")
2443                       (match_operand 1 "general_operand" "")
2444                       (match_operand 2 "general_operand" ""))
2445         (match_operand 3 "reg_or_int_operand" ""))]
2446   "TARGET_ARM || arm_arch_thumb2"
2447   "
2448   {
2449     int start_bit = INTVAL (operands[2]);
2450     int width = INTVAL (operands[1]);
2451     HOST_WIDE_INT mask = (((HOST_WIDE_INT)1) << width) - 1;
2452     rtx target, subtarget;
2454     if (arm_arch_thumb2)
2455       {
2456         if (unaligned_access && MEM_P (operands[0])
2457             && s_register_operand (operands[3], GET_MODE (operands[3]))
2458             && (width == 16 || width == 32) && (start_bit % BITS_PER_UNIT) == 0)
2459           {
2460             rtx base_addr;
2462             if (BYTES_BIG_ENDIAN)
2463               start_bit = GET_MODE_BITSIZE (GET_MODE (operands[3])) - width
2464                           - start_bit;
2466             if (width == 32)
2467               {
2468                 base_addr = adjust_address (operands[0], SImode,
2469                                             start_bit / BITS_PER_UNIT);
2470                 emit_insn (gen_unaligned_storesi (base_addr, operands[3]));
2471               }
2472             else
2473               {
2474                 rtx tmp = gen_reg_rtx (HImode);
2476                 base_addr = adjust_address (operands[0], HImode,
2477                                             start_bit / BITS_PER_UNIT);
2478                 emit_move_insn (tmp, gen_lowpart (HImode, operands[3]));
2479                 emit_insn (gen_unaligned_storehi (base_addr, tmp));
2480               }
2481             DONE;
2482           }
2483         else if (s_register_operand (operands[0], GET_MODE (operands[0])))
2484           {
2485             bool use_bfi = TRUE;
2487             if (GET_CODE (operands[3]) == CONST_INT)
2488               {
2489                 HOST_WIDE_INT val = INTVAL (operands[3]) & mask;
2491                 if (val == 0)
2492                   {
2493                     emit_insn (gen_insv_zero (operands[0], operands[1],
2494                                               operands[2]));
2495                     DONE;
2496                   }
2498                 /* See if the set can be done with a single orr instruction.  */
2499                 if (val == mask && const_ok_for_arm (val << start_bit))
2500                   use_bfi = FALSE;
2501               }
2503             if (use_bfi)
2504               {
2505                 if (GET_CODE (operands[3]) != REG)
2506                   operands[3] = force_reg (SImode, operands[3]);
2508                 emit_insn (gen_insv_t2 (operands[0], operands[1], operands[2],
2509                                         operands[3]));
2510                 DONE;
2511               }
2512           }
2513         else
2514           FAIL;
2515       }
2517     if (!s_register_operand (operands[0], GET_MODE (operands[0])))
2518       FAIL;
2520     target = copy_rtx (operands[0]);
2521     /* Avoid using a subreg as a subtarget, and avoid writing a paradoxical 
2522        subreg as the final target.  */
2523     if (GET_CODE (target) == SUBREG)
2524       {
2525         subtarget = gen_reg_rtx (SImode);
2526         if (GET_MODE_SIZE (GET_MODE (SUBREG_REG (target)))
2527             < GET_MODE_SIZE (SImode))
2528           target = SUBREG_REG (target);
2529       }
2530     else
2531       subtarget = target;    
2533     if (GET_CODE (operands[3]) == CONST_INT)
2534       {
2535         /* Since we are inserting a known constant, we may be able to
2536            reduce the number of bits that we have to clear so that
2537            the mask becomes simple.  */
2538         /* ??? This code does not check to see if the new mask is actually
2539            simpler.  It may not be.  */
2540         rtx op1 = gen_reg_rtx (SImode);
2541         /* ??? Truncate operand3 to fit in the bitfield.  See comment before
2542            start of this pattern.  */
2543         HOST_WIDE_INT op3_value = mask & INTVAL (operands[3]);
2544         HOST_WIDE_INT mask2 = ((mask & ~op3_value) << start_bit);
2546         emit_insn (gen_andsi3 (op1, operands[0],
2547                                gen_int_mode (~mask2, SImode)));
2548         emit_insn (gen_iorsi3 (subtarget, op1,
2549                                gen_int_mode (op3_value << start_bit, SImode)));
2550       }
2551     else if (start_bit == 0
2552              && !(const_ok_for_arm (mask)
2553                   || const_ok_for_arm (~mask)))
2554       {
2555         /* A Trick, since we are setting the bottom bits in the word,
2556            we can shift operand[3] up, operand[0] down, OR them together
2557            and rotate the result back again.  This takes 3 insns, and
2558            the third might be mergeable into another op.  */
2559         /* The shift up copes with the possibility that operand[3] is
2560            wider than the bitfield.  */
2561         rtx op0 = gen_reg_rtx (SImode);
2562         rtx op1 = gen_reg_rtx (SImode);
2564         emit_insn (gen_ashlsi3 (op0, operands[3], GEN_INT (32 - width)));
2565         emit_insn (gen_lshrsi3 (op1, operands[0], operands[1]));
2566         emit_insn (gen_iorsi3  (op1, op1, op0));
2567         emit_insn (gen_rotlsi3 (subtarget, op1, operands[1]));
2568       }
2569     else if ((width + start_bit == 32)
2570              && !(const_ok_for_arm (mask)
2571                   || const_ok_for_arm (~mask)))
2572       {
2573         /* Similar trick, but slightly less efficient.  */
2575         rtx op0 = gen_reg_rtx (SImode);
2576         rtx op1 = gen_reg_rtx (SImode);
2578         emit_insn (gen_ashlsi3 (op0, operands[3], GEN_INT (32 - width)));
2579         emit_insn (gen_ashlsi3 (op1, operands[0], operands[1]));
2580         emit_insn (gen_lshrsi3 (op1, op1, operands[1]));
2581         emit_insn (gen_iorsi3 (subtarget, op1, op0));
2582       }
2583     else
2584       {
2585         rtx op0 = gen_int_mode (mask, SImode);
2586         rtx op1 = gen_reg_rtx (SImode);
2587         rtx op2 = gen_reg_rtx (SImode);
2589         if (!(const_ok_for_arm (mask) || const_ok_for_arm (~mask)))
2590           {
2591             rtx tmp = gen_reg_rtx (SImode);
2593             emit_insn (gen_movsi (tmp, op0));
2594             op0 = tmp;
2595           }
2597         /* Mask out any bits in operand[3] that are not needed.  */
2598            emit_insn (gen_andsi3 (op1, operands[3], op0));
2600         if (GET_CODE (op0) == CONST_INT
2601             && (const_ok_for_arm (mask << start_bit)
2602                 || const_ok_for_arm (~(mask << start_bit))))
2603           {
2604             op0 = gen_int_mode (~(mask << start_bit), SImode);
2605             emit_insn (gen_andsi3 (op2, operands[0], op0));
2606           }
2607         else
2608           {
2609             if (GET_CODE (op0) == CONST_INT)
2610               {
2611                 rtx tmp = gen_reg_rtx (SImode);
2613                 emit_insn (gen_movsi (tmp, op0));
2614                 op0 = tmp;
2615               }
2617             if (start_bit != 0)
2618               emit_insn (gen_ashlsi3 (op0, op0, operands[2]));
2619             
2620             emit_insn (gen_andsi_notsi_si (op2, operands[0], op0));
2621           }
2623         if (start_bit != 0)
2624           emit_insn (gen_ashlsi3 (op1, op1, operands[2]));
2626         emit_insn (gen_iorsi3 (subtarget, op1, op2));
2627       }
2629     if (subtarget != target)
2630       {
2631         /* If TARGET is still a SUBREG, then it must be wider than a word,
2632            so we must be careful only to set the subword we were asked to.  */
2633         if (GET_CODE (target) == SUBREG)
2634           emit_move_insn (target, subtarget);
2635         else
2636           emit_move_insn (target, gen_lowpart (GET_MODE (target), subtarget));
2637       }
2639     DONE;
2640   }"
2643 (define_insn "insv_zero"
2644   [(set (zero_extract:SI (match_operand:SI 0 "s_register_operand" "+r")
2645                          (match_operand:SI 1 "const_int_operand" "M")
2646                          (match_operand:SI 2 "const_int_operand" "M"))
2647         (const_int 0))]
2648   "arm_arch_thumb2"
2649   "bfc%?\t%0, %2, %1"
2650   [(set_attr "length" "4")
2651    (set_attr "predicable" "yes")]
2654 (define_insn "insv_t2"
2655   [(set (zero_extract:SI (match_operand:SI 0 "s_register_operand" "+r")
2656                          (match_operand:SI 1 "const_int_operand" "M")
2657                          (match_operand:SI 2 "const_int_operand" "M"))
2658         (match_operand:SI 3 "s_register_operand" "r"))]
2659   "arm_arch_thumb2"
2660   "bfi%?\t%0, %3, %2, %1"
2661   [(set_attr "length" "4")
2662    (set_attr "predicable" "yes")]
2665 ; constants for op 2 will never be given to these patterns.
2666 (define_insn_and_split "*anddi_notdi_di"
2667   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2668         (and:DI (not:DI (match_operand:DI 1 "s_register_operand" "0,r"))
2669                 (match_operand:DI 2 "s_register_operand" "r,0")))]
2670   "TARGET_32BIT"
2671   "#"
2672   "TARGET_32BIT && reload_completed
2673    && ! (TARGET_NEON && IS_VFP_REGNUM (REGNO (operands[0])))
2674    && ! IS_IWMMXT_REGNUM (REGNO (operands[0]))"
2675   [(set (match_dup 0) (and:SI (not:SI (match_dup 1)) (match_dup 2)))
2676    (set (match_dup 3) (and:SI (not:SI (match_dup 4)) (match_dup 5)))]
2677   "
2678   {
2679     operands[3] = gen_highpart (SImode, operands[0]);
2680     operands[0] = gen_lowpart (SImode, operands[0]);
2681     operands[4] = gen_highpart (SImode, operands[1]);
2682     operands[1] = gen_lowpart (SImode, operands[1]);
2683     operands[5] = gen_highpart (SImode, operands[2]);
2684     operands[2] = gen_lowpart (SImode, operands[2]);
2685   }"
2686   [(set_attr "length" "8")
2687    (set_attr "predicable" "yes")]
2689   
2690 (define_insn_and_split "*anddi_notzesidi_di"
2691   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2692         (and:DI (not:DI (zero_extend:DI
2693                          (match_operand:SI 2 "s_register_operand" "r,r")))
2694                 (match_operand:DI 1 "s_register_operand" "0,?r")))]
2695   "TARGET_32BIT"
2696   "@
2697    bic%?\\t%Q0, %Q1, %2
2698    #"
2699   ; (not (zero_extend ...)) allows us to just copy the high word from
2700   ; operand1 to operand0.
2701   "TARGET_32BIT
2702    && reload_completed
2703    && operands[0] != operands[1]"
2704   [(set (match_dup 0) (and:SI (not:SI (match_dup 2)) (match_dup 1)))
2705    (set (match_dup 3) (match_dup 4))]
2706   "
2707   {
2708     operands[3] = gen_highpart (SImode, operands[0]);
2709     operands[0] = gen_lowpart (SImode, operands[0]);
2710     operands[4] = gen_highpart (SImode, operands[1]);
2711     operands[1] = gen_lowpart (SImode, operands[1]);
2712   }"
2713   [(set_attr "length" "4,8")
2714    (set_attr "predicable" "yes")]
2716   
2717 (define_insn_and_split "*anddi_notsesidi_di"
2718   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2719         (and:DI (not:DI (sign_extend:DI
2720                          (match_operand:SI 2 "s_register_operand" "r,r")))
2721                 (match_operand:DI 1 "s_register_operand" "0,r")))]
2722   "TARGET_32BIT"
2723   "#"
2724   "TARGET_32BIT && reload_completed"
2725   [(set (match_dup 0) (and:SI (not:SI (match_dup 2)) (match_dup 1)))
2726    (set (match_dup 3) (and:SI (not:SI
2727                                 (ashiftrt:SI (match_dup 2) (const_int 31)))
2728                                (match_dup 4)))]
2729   "
2730   {
2731     operands[3] = gen_highpart (SImode, operands[0]);
2732     operands[0] = gen_lowpart (SImode, operands[0]);
2733     operands[4] = gen_highpart (SImode, operands[1]);
2734     operands[1] = gen_lowpart (SImode, operands[1]);
2735   }"
2736   [(set_attr "length" "8")
2737    (set_attr "predicable" "yes")]
2739   
2740 (define_insn "andsi_notsi_si"
2741   [(set (match_operand:SI 0 "s_register_operand" "=r")
2742         (and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2743                 (match_operand:SI 1 "s_register_operand" "r")))]
2744   "TARGET_32BIT"
2745   "bic%?\\t%0, %1, %2"
2746   [(set_attr "predicable" "yes")]
2749 (define_insn "thumb1_bicsi3"
2750   [(set (match_operand:SI                 0 "register_operand" "=l")
2751         (and:SI (not:SI (match_operand:SI 1 "register_operand" "l"))
2752                 (match_operand:SI         2 "register_operand" "0")))]
2753   "TARGET_THUMB1"
2754   "bic\\t%0, %1"
2755   [(set_attr "length" "2")
2756    (set_attr "conds" "set")])
2758 (define_insn "andsi_not_shiftsi_si"
2759   [(set (match_operand:SI 0 "s_register_operand" "=r")
2760         (and:SI (not:SI (match_operator:SI 4 "shift_operator"
2761                          [(match_operand:SI 2 "s_register_operand" "r")
2762                           (match_operand:SI 3 "arm_rhs_operand" "rM")]))
2763                 (match_operand:SI 1 "s_register_operand" "r")))]
2764   "TARGET_ARM"
2765   "bic%?\\t%0, %1, %2%S4"
2766   [(set_attr "predicable" "yes")
2767    (set_attr "shift" "2")
2768    (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
2769                       (const_string "alu_shift")
2770                       (const_string "alu_shift_reg")))]
2773 (define_insn "*andsi_notsi_si_compare0"
2774   [(set (reg:CC_NOOV CC_REGNUM)
2775         (compare:CC_NOOV
2776          (and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2777                  (match_operand:SI 1 "s_register_operand" "r"))
2778          (const_int 0)))
2779    (set (match_operand:SI 0 "s_register_operand" "=r")
2780         (and:SI (not:SI (match_dup 2)) (match_dup 1)))]
2781   "TARGET_32BIT"
2782   "bic%.\\t%0, %1, %2"
2783   [(set_attr "conds" "set")]
2786 (define_insn "*andsi_notsi_si_compare0_scratch"
2787   [(set (reg:CC_NOOV CC_REGNUM)
2788         (compare:CC_NOOV
2789          (and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2790                  (match_operand:SI 1 "s_register_operand" "r"))
2791          (const_int 0)))
2792    (clobber (match_scratch:SI 0 "=r"))]
2793   "TARGET_32BIT"
2794   "bic%.\\t%0, %1, %2"
2795   [(set_attr "conds" "set")]
2798 (define_expand "iordi3"
2799   [(set (match_operand:DI         0 "s_register_operand" "")
2800         (ior:DI (match_operand:DI 1 "s_register_operand" "")
2801                 (match_operand:DI 2 "neon_logic_op2" "")))]
2802   "TARGET_32BIT"
2803   ""
2806 (define_insn "*iordi3_insn"
2807   [(set (match_operand:DI         0 "s_register_operand" "=&r,&r")
2808         (ior:DI (match_operand:DI 1 "s_register_operand"  "%0,r")
2809                 (match_operand:DI 2 "s_register_operand"   "r,r")))]
2810   "TARGET_32BIT && !TARGET_IWMMXT && !TARGET_NEON"
2811   "#"
2812   [(set_attr "length" "8")
2813    (set_attr "predicable" "yes")]
2816 (define_insn "*iordi_zesidi_di"
2817   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2818         (ior:DI (zero_extend:DI
2819                  (match_operand:SI 2 "s_register_operand" "r,r"))
2820                 (match_operand:DI 1 "s_register_operand" "0,?r")))]
2821   "TARGET_32BIT"
2822   "@
2823    orr%?\\t%Q0, %Q1, %2
2824    #"
2825   [(set_attr "length" "4,8")
2826    (set_attr "predicable" "yes")]
2829 (define_insn "*iordi_sesidi_di"
2830   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2831         (ior:DI (sign_extend:DI
2832                  (match_operand:SI 2 "s_register_operand" "r,r"))
2833                 (match_operand:DI 1 "s_register_operand" "0,r")))]
2834   "TARGET_32BIT"
2835   "#"
2836   [(set_attr "length" "8")
2837    (set_attr "predicable" "yes")]
2840 (define_expand "iorsi3"
2841   [(set (match_operand:SI         0 "s_register_operand" "")
2842         (ior:SI (match_operand:SI 1 "s_register_operand" "")
2843                 (match_operand:SI 2 "reg_or_int_operand" "")))]
2844   "TARGET_EITHER"
2845   "
2846   if (GET_CODE (operands[2]) == CONST_INT)
2847     {
2848       if (TARGET_32BIT)
2849         {
2850           arm_split_constant (IOR, SImode, NULL_RTX,
2851                               INTVAL (operands[2]), operands[0], operands[1],
2852                               optimize && can_create_pseudo_p ());
2853           DONE;
2854         }
2855       else /* TARGET_THUMB1 */
2856         {
2857           rtx tmp = force_reg (SImode, operands[2]);
2858           if (rtx_equal_p (operands[0], operands[1]))
2859             operands[2] = tmp;
2860           else
2861             {
2862               operands[2] = operands[1];
2863               operands[1] = tmp;
2864             }
2865         }
2866     }
2867   "
2870 (define_insn_and_split "*iorsi3_insn"
2871   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
2872         (ior:SI (match_operand:SI 1 "s_register_operand" "%r,r,r")
2873                 (match_operand:SI 2 "reg_or_int_operand" "rI,K,?n")))]
2874   "TARGET_32BIT"
2875   "@
2876    orr%?\\t%0, %1, %2
2877    orn%?\\t%0, %1, #%B2
2878    #"
2879   "TARGET_32BIT
2880    && GET_CODE (operands[2]) == CONST_INT
2881    && !(const_ok_for_arm (INTVAL (operands[2]))
2882         || (TARGET_THUMB2 && const_ok_for_arm (~INTVAL (operands[2]))))"
2883   [(clobber (const_int 0))]
2885   arm_split_constant (IOR, SImode, curr_insn, 
2886                       INTVAL (operands[2]), operands[0], operands[1], 0);
2887   DONE;
2889   [(set_attr "length" "4,4,16")
2890    (set_attr "arch" "32,t2,32")
2891    (set_attr "predicable" "yes")])
2893 (define_insn "*thumb1_iorsi3_insn"
2894   [(set (match_operand:SI         0 "register_operand" "=l")
2895         (ior:SI (match_operand:SI 1 "register_operand" "%0")
2896                 (match_operand:SI 2 "register_operand" "l")))]
2897   "TARGET_THUMB1"
2898   "orr\\t%0, %2"
2899   [(set_attr "length" "2")
2900    (set_attr "conds" "set")])
2902 (define_peephole2
2903   [(match_scratch:SI 3 "r")
2904    (set (match_operand:SI 0 "arm_general_register_operand" "")
2905         (ior:SI (match_operand:SI 1 "arm_general_register_operand" "")
2906                 (match_operand:SI 2 "const_int_operand" "")))]
2907   "TARGET_ARM
2908    && !const_ok_for_arm (INTVAL (operands[2]))
2909    && const_ok_for_arm (~INTVAL (operands[2]))"
2910   [(set (match_dup 3) (match_dup 2))
2911    (set (match_dup 0) (ior:SI (match_dup 1) (match_dup 3)))]
2912   ""
2915 (define_insn "*iorsi3_compare0"
2916   [(set (reg:CC_NOOV CC_REGNUM)
2917         (compare:CC_NOOV (ior:SI (match_operand:SI 1 "s_register_operand" "%r")
2918                                  (match_operand:SI 2 "arm_rhs_operand" "rI"))
2919                          (const_int 0)))
2920    (set (match_operand:SI 0 "s_register_operand" "=r")
2921         (ior:SI (match_dup 1) (match_dup 2)))]
2922   "TARGET_32BIT"
2923   "orr%.\\t%0, %1, %2"
2924   [(set_attr "conds" "set")]
2927 (define_insn "*iorsi3_compare0_scratch"
2928   [(set (reg:CC_NOOV CC_REGNUM)
2929         (compare:CC_NOOV (ior:SI (match_operand:SI 1 "s_register_operand" "%r")
2930                                  (match_operand:SI 2 "arm_rhs_operand" "rI"))
2931                          (const_int 0)))
2932    (clobber (match_scratch:SI 0 "=r"))]
2933   "TARGET_32BIT"
2934   "orr%.\\t%0, %1, %2"
2935   [(set_attr "conds" "set")]
2938 (define_expand "xordi3"
2939   [(set (match_operand:DI         0 "s_register_operand" "")
2940         (xor:DI (match_operand:DI 1 "s_register_operand" "")
2941                 (match_operand:DI 2 "s_register_operand" "")))]
2942   "TARGET_32BIT"
2943   ""
2946 (define_insn "*xordi3_insn"
2947   [(set (match_operand:DI         0 "s_register_operand" "=&r,&r")
2948         (xor:DI (match_operand:DI 1 "s_register_operand"  "%0,r")
2949                 (match_operand:DI 2 "s_register_operand"   "r,r")))]
2950   "TARGET_32BIT && !TARGET_IWMMXT && !TARGET_NEON"
2951   "#"
2952   [(set_attr "length" "8")
2953    (set_attr "predicable" "yes")]
2956 (define_insn "*xordi_zesidi_di"
2957   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2958         (xor:DI (zero_extend:DI
2959                  (match_operand:SI 2 "s_register_operand" "r,r"))
2960                 (match_operand:DI 1 "s_register_operand" "0,?r")))]
2961   "TARGET_32BIT"
2962   "@
2963    eor%?\\t%Q0, %Q1, %2
2964    #"
2965   [(set_attr "length" "4,8")
2966    (set_attr "predicable" "yes")]
2969 (define_insn "*xordi_sesidi_di"
2970   [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2971         (xor:DI (sign_extend:DI
2972                  (match_operand:SI 2 "s_register_operand" "r,r"))
2973                 (match_operand:DI 1 "s_register_operand" "0,r")))]
2974   "TARGET_32BIT"
2975   "#"
2976   [(set_attr "length" "8")
2977    (set_attr "predicable" "yes")]
2980 (define_expand "xorsi3"
2981   [(set (match_operand:SI         0 "s_register_operand" "")
2982         (xor:SI (match_operand:SI 1 "s_register_operand" "")
2983                 (match_operand:SI 2 "reg_or_int_operand" "")))]
2984   "TARGET_EITHER"
2985   "if (GET_CODE (operands[2]) == CONST_INT)
2986     {
2987       if (TARGET_32BIT)
2988         {
2989           arm_split_constant (XOR, SImode, NULL_RTX,
2990                               INTVAL (operands[2]), operands[0], operands[1],
2991                               optimize && can_create_pseudo_p ());
2992           DONE;
2993         }
2994       else /* TARGET_THUMB1 */
2995         {
2996           rtx tmp = force_reg (SImode, operands[2]);
2997           if (rtx_equal_p (operands[0], operands[1]))
2998             operands[2] = tmp;
2999           else
3000             {
3001               operands[2] = operands[1];
3002               operands[1] = tmp;
3003             }
3004         }
3005     }"
3008 (define_insn_and_split "*arm_xorsi3"
3009   [(set (match_operand:SI         0 "s_register_operand" "=r,r")
3010         (xor:SI (match_operand:SI 1 "s_register_operand" "%r,r")
3011                 (match_operand:SI 2 "reg_or_int_operand" "rI,?n")))]
3012   "TARGET_32BIT"
3013   "@
3014    eor%?\\t%0, %1, %2
3015    #"
3016   "TARGET_32BIT
3017    && GET_CODE (operands[2]) == CONST_INT
3018    && !const_ok_for_arm (INTVAL (operands[2]))"
3019   [(clobber (const_int 0))]
3021   arm_split_constant (XOR, SImode, curr_insn,
3022                       INTVAL (operands[2]), operands[0], operands[1], 0);
3023   DONE;
3025   [(set_attr "length" "4,16")
3026    (set_attr "predicable" "yes")]
3029 (define_insn "*thumb1_xorsi3_insn"
3030   [(set (match_operand:SI         0 "register_operand" "=l")
3031         (xor:SI (match_operand:SI 1 "register_operand" "%0")
3032                 (match_operand:SI 2 "register_operand" "l")))]
3033   "TARGET_THUMB1"
3034   "eor\\t%0, %2"
3035   [(set_attr "length" "2")
3036    (set_attr "conds" "set")])
3038 (define_insn "*xorsi3_compare0"
3039   [(set (reg:CC_NOOV CC_REGNUM)
3040         (compare:CC_NOOV (xor:SI (match_operand:SI 1 "s_register_operand" "r")
3041                                  (match_operand:SI 2 "arm_rhs_operand" "rI"))
3042                          (const_int 0)))
3043    (set (match_operand:SI 0 "s_register_operand" "=r")
3044         (xor:SI (match_dup 1) (match_dup 2)))]
3045   "TARGET_32BIT"
3046   "eor%.\\t%0, %1, %2"
3047   [(set_attr "conds" "set")]
3050 (define_insn "*xorsi3_compare0_scratch"
3051   [(set (reg:CC_NOOV CC_REGNUM)
3052         (compare:CC_NOOV (xor:SI (match_operand:SI 0 "s_register_operand" "r")
3053                                  (match_operand:SI 1 "arm_rhs_operand" "rI"))
3054                          (const_int 0)))]
3055   "TARGET_32BIT"
3056   "teq%?\\t%0, %1"
3057   [(set_attr "conds" "set")]
3060 ; By splitting (IOR (AND (NOT A) (NOT B)) C) as D = AND (IOR A B) (NOT C), 
3061 ; (NOT D) we can sometimes merge the final NOT into one of the following
3062 ; insns.
3064 (define_split
3065   [(set (match_operand:SI 0 "s_register_operand" "")
3066         (ior:SI (and:SI (not:SI (match_operand:SI 1 "s_register_operand" ""))
3067                         (not:SI (match_operand:SI 2 "arm_rhs_operand" "")))
3068                 (match_operand:SI 3 "arm_rhs_operand" "")))
3069    (clobber (match_operand:SI 4 "s_register_operand" ""))]
3070   "TARGET_32BIT"
3071   [(set (match_dup 4) (and:SI (ior:SI (match_dup 1) (match_dup 2))
3072                               (not:SI (match_dup 3))))
3073    (set (match_dup 0) (not:SI (match_dup 4)))]
3074   ""
3077 (define_insn "*andsi_iorsi3_notsi"
3078   [(set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r")
3079         (and:SI (ior:SI (match_operand:SI 1 "s_register_operand" "%0,r,r")
3080                         (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI"))
3081                 (not:SI (match_operand:SI 3 "arm_rhs_operand" "rI,rI,rI"))))]
3082   "TARGET_32BIT"
3083   "orr%?\\t%0, %1, %2\;bic%?\\t%0, %0, %3"
3084   [(set_attr "length" "8")
3085    (set_attr "ce_count" "2")
3086    (set_attr "predicable" "yes")]
3089 ; ??? Are these four splitters still beneficial when the Thumb-2 bitfield
3090 ; insns are available?
3091 (define_split
3092   [(set (match_operand:SI 0 "s_register_operand" "")
3093         (match_operator:SI 1 "logical_binary_operator"
3094          [(zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
3095                            (match_operand:SI 3 "const_int_operand" "")
3096                            (match_operand:SI 4 "const_int_operand" ""))
3097           (match_operator:SI 9 "logical_binary_operator"
3098            [(lshiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3099                          (match_operand:SI 6 "const_int_operand" ""))
3100             (match_operand:SI 7 "s_register_operand" "")])]))
3101    (clobber (match_operand:SI 8 "s_register_operand" ""))]
3102   "TARGET_32BIT
3103    && GET_CODE (operands[1]) == GET_CODE (operands[9])
3104    && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3105   [(set (match_dup 8)
3106         (match_op_dup 1
3107          [(ashift:SI (match_dup 2) (match_dup 4))
3108           (match_dup 5)]))
3109    (set (match_dup 0)
3110         (match_op_dup 1
3111          [(lshiftrt:SI (match_dup 8) (match_dup 6))
3112           (match_dup 7)]))]
3113   "
3114   operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3117 (define_split
3118   [(set (match_operand:SI 0 "s_register_operand" "")
3119         (match_operator:SI 1 "logical_binary_operator"
3120          [(match_operator:SI 9 "logical_binary_operator"
3121            [(lshiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3122                          (match_operand:SI 6 "const_int_operand" ""))
3123             (match_operand:SI 7 "s_register_operand" "")])
3124           (zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
3125                            (match_operand:SI 3 "const_int_operand" "")
3126                            (match_operand:SI 4 "const_int_operand" ""))]))
3127    (clobber (match_operand:SI 8 "s_register_operand" ""))]
3128   "TARGET_32BIT
3129    && GET_CODE (operands[1]) == GET_CODE (operands[9])
3130    && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3131   [(set (match_dup 8)
3132         (match_op_dup 1
3133          [(ashift:SI (match_dup 2) (match_dup 4))
3134           (match_dup 5)]))
3135    (set (match_dup 0)
3136         (match_op_dup 1
3137          [(lshiftrt:SI (match_dup 8) (match_dup 6))
3138           (match_dup 7)]))]
3139   "
3140   operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3143 (define_split
3144   [(set (match_operand:SI 0 "s_register_operand" "")
3145         (match_operator:SI 1 "logical_binary_operator"
3146          [(sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
3147                            (match_operand:SI 3 "const_int_operand" "")
3148                            (match_operand:SI 4 "const_int_operand" ""))
3149           (match_operator:SI 9 "logical_binary_operator"
3150            [(ashiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3151                          (match_operand:SI 6 "const_int_operand" ""))
3152             (match_operand:SI 7 "s_register_operand" "")])]))
3153    (clobber (match_operand:SI 8 "s_register_operand" ""))]
3154   "TARGET_32BIT
3155    && GET_CODE (operands[1]) == GET_CODE (operands[9])
3156    && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3157   [(set (match_dup 8)
3158         (match_op_dup 1
3159          [(ashift:SI (match_dup 2) (match_dup 4))
3160           (match_dup 5)]))
3161    (set (match_dup 0)
3162         (match_op_dup 1
3163          [(ashiftrt:SI (match_dup 8) (match_dup 6))
3164           (match_dup 7)]))]
3165   "
3166   operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3169 (define_split
3170   [(set (match_operand:SI 0 "s_register_operand" "")
3171         (match_operator:SI 1 "logical_binary_operator"
3172          [(match_operator:SI 9 "logical_binary_operator"
3173            [(ashiftrt:SI (match_operand:SI 5 "s_register_operand" "")
3174                          (match_operand:SI 6 "const_int_operand" ""))
3175             (match_operand:SI 7 "s_register_operand" "")])
3176           (sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
3177                            (match_operand:SI 3 "const_int_operand" "")
3178                            (match_operand:SI 4 "const_int_operand" ""))]))
3179    (clobber (match_operand:SI 8 "s_register_operand" ""))]
3180   "TARGET_32BIT
3181    && GET_CODE (operands[1]) == GET_CODE (operands[9])
3182    && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
3183   [(set (match_dup 8)
3184         (match_op_dup 1
3185          [(ashift:SI (match_dup 2) (match_dup 4))
3186           (match_dup 5)]))
3187    (set (match_dup 0)
3188         (match_op_dup 1
3189          [(ashiftrt:SI (match_dup 8) (match_dup 6))
3190           (match_dup 7)]))]
3191   "
3192   operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
3196 ;; Minimum and maximum insns
3198 (define_expand "smaxsi3"
3199   [(parallel [
3200     (set (match_operand:SI 0 "s_register_operand" "")
3201          (smax:SI (match_operand:SI 1 "s_register_operand" "")
3202                   (match_operand:SI 2 "arm_rhs_operand" "")))
3203     (clobber (reg:CC CC_REGNUM))])]
3204   "TARGET_32BIT"
3205   "
3206   if (operands[2] == const0_rtx || operands[2] == constm1_rtx)
3207     {
3208       /* No need for a clobber of the condition code register here.  */
3209       emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3210                               gen_rtx_SMAX (SImode, operands[1],
3211                                             operands[2])));
3212       DONE;
3213     }
3216 (define_insn "*smax_0"
3217   [(set (match_operand:SI 0 "s_register_operand" "=r")
3218         (smax:SI (match_operand:SI 1 "s_register_operand" "r")
3219                  (const_int 0)))]
3220   "TARGET_32BIT"
3221   "bic%?\\t%0, %1, %1, asr #31"
3222   [(set_attr "predicable" "yes")]
3225 (define_insn "*smax_m1"
3226   [(set (match_operand:SI 0 "s_register_operand" "=r")
3227         (smax:SI (match_operand:SI 1 "s_register_operand" "r")
3228                  (const_int -1)))]
3229   "TARGET_32BIT"
3230   "orr%?\\t%0, %1, %1, asr #31"
3231   [(set_attr "predicable" "yes")]
3234 (define_insn "*arm_smax_insn"
3235   [(set (match_operand:SI          0 "s_register_operand" "=r,r")
3236         (smax:SI (match_operand:SI 1 "s_register_operand"  "%0,?r")
3237                  (match_operand:SI 2 "arm_rhs_operand"    "rI,rI")))
3238    (clobber (reg:CC CC_REGNUM))]
3239   "TARGET_ARM"
3240   "@
3241    cmp\\t%1, %2\;movlt\\t%0, %2
3242    cmp\\t%1, %2\;movge\\t%0, %1\;movlt\\t%0, %2"
3243   [(set_attr "conds" "clob")
3244    (set_attr "length" "8,12")]
3247 (define_expand "sminsi3"
3248   [(parallel [
3249     (set (match_operand:SI 0 "s_register_operand" "")
3250          (smin:SI (match_operand:SI 1 "s_register_operand" "")
3251                   (match_operand:SI 2 "arm_rhs_operand" "")))
3252     (clobber (reg:CC CC_REGNUM))])]
3253   "TARGET_32BIT"
3254   "
3255   if (operands[2] == const0_rtx)
3256     {
3257       /* No need for a clobber of the condition code register here.  */
3258       emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3259                               gen_rtx_SMIN (SImode, operands[1],
3260                                             operands[2])));
3261       DONE;
3262     }
3265 (define_insn "*smin_0"
3266   [(set (match_operand:SI 0 "s_register_operand" "=r")
3267         (smin:SI (match_operand:SI 1 "s_register_operand" "r")
3268                  (const_int 0)))]
3269   "TARGET_32BIT"
3270   "and%?\\t%0, %1, %1, asr #31"
3271   [(set_attr "predicable" "yes")]
3274 (define_insn "*arm_smin_insn"
3275   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3276         (smin:SI (match_operand:SI 1 "s_register_operand" "%0,?r")
3277                  (match_operand:SI 2 "arm_rhs_operand" "rI,rI")))
3278    (clobber (reg:CC CC_REGNUM))]
3279   "TARGET_ARM"
3280   "@
3281    cmp\\t%1, %2\;movge\\t%0, %2
3282    cmp\\t%1, %2\;movlt\\t%0, %1\;movge\\t%0, %2"
3283   [(set_attr "conds" "clob")
3284    (set_attr "length" "8,12")]
3287 (define_expand "umaxsi3"
3288   [(parallel [
3289     (set (match_operand:SI 0 "s_register_operand" "")
3290          (umax:SI (match_operand:SI 1 "s_register_operand" "")
3291                   (match_operand:SI 2 "arm_rhs_operand" "")))
3292     (clobber (reg:CC CC_REGNUM))])]
3293   "TARGET_32BIT"
3294   ""
3297 (define_insn "*arm_umaxsi3"
3298   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
3299         (umax:SI (match_operand:SI 1 "s_register_operand" "0,r,?r")
3300                  (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
3301    (clobber (reg:CC CC_REGNUM))]
3302   "TARGET_ARM"
3303   "@
3304    cmp\\t%1, %2\;movcc\\t%0, %2
3305    cmp\\t%1, %2\;movcs\\t%0, %1
3306    cmp\\t%1, %2\;movcs\\t%0, %1\;movcc\\t%0, %2"
3307   [(set_attr "conds" "clob")
3308    (set_attr "length" "8,8,12")]
3311 (define_expand "uminsi3"
3312   [(parallel [
3313     (set (match_operand:SI 0 "s_register_operand" "")
3314          (umin:SI (match_operand:SI 1 "s_register_operand" "")
3315                   (match_operand:SI 2 "arm_rhs_operand" "")))
3316     (clobber (reg:CC CC_REGNUM))])]
3317   "TARGET_32BIT"
3318   ""
3321 (define_insn "*arm_uminsi3"
3322   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
3323         (umin:SI (match_operand:SI 1 "s_register_operand" "0,r,?r")
3324                  (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
3325    (clobber (reg:CC CC_REGNUM))]
3326   "TARGET_ARM"
3327   "@
3328    cmp\\t%1, %2\;movcs\\t%0, %2
3329    cmp\\t%1, %2\;movcc\\t%0, %1
3330    cmp\\t%1, %2\;movcc\\t%0, %1\;movcs\\t%0, %2"
3331   [(set_attr "conds" "clob")
3332    (set_attr "length" "8,8,12")]
3335 (define_insn "*store_minmaxsi"
3336   [(set (match_operand:SI 0 "memory_operand" "=m")
3337         (match_operator:SI 3 "minmax_operator"
3338          [(match_operand:SI 1 "s_register_operand" "r")
3339           (match_operand:SI 2 "s_register_operand" "r")]))
3340    (clobber (reg:CC CC_REGNUM))]
3341   "TARGET_32BIT"
3342   "*
3343   operands[3] = gen_rtx_fmt_ee (minmax_code (operands[3]), SImode,
3344                                 operands[1], operands[2]);
3345   output_asm_insn (\"cmp\\t%1, %2\", operands);
3346   if (TARGET_THUMB2)
3347     output_asm_insn (\"ite\t%d3\", operands);
3348   output_asm_insn (\"str%d3\\t%1, %0\", operands);
3349   output_asm_insn (\"str%D3\\t%2, %0\", operands);
3350   return \"\";
3351   "
3352   [(set_attr "conds" "clob")
3353    (set (attr "length")
3354         (if_then_else (eq_attr "is_thumb" "yes")
3355                       (const_int 14)
3356                       (const_int 12)))
3357    (set_attr "type" "store1")]
3360 ; Reject the frame pointer in operand[1], since reloading this after
3361 ; it has been eliminated can cause carnage.
3362 (define_insn "*minmax_arithsi"
3363   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3364         (match_operator:SI 4 "shiftable_operator"
3365          [(match_operator:SI 5 "minmax_operator"
3366            [(match_operand:SI 2 "s_register_operand" "r,r")
3367             (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
3368           (match_operand:SI 1 "s_register_operand" "0,?r")]))
3369    (clobber (reg:CC CC_REGNUM))]
3370   "TARGET_32BIT && !arm_eliminable_register (operands[1])"
3371   "*
3372   {
3373     enum rtx_code code = GET_CODE (operands[4]);
3374     bool need_else;
3376     if (which_alternative != 0 || operands[3] != const0_rtx
3377         || (code != PLUS && code != IOR && code != XOR))
3378       need_else = true;
3379     else
3380       need_else = false;
3382     operands[5] = gen_rtx_fmt_ee (minmax_code (operands[5]), SImode,
3383                                   operands[2], operands[3]);
3384     output_asm_insn (\"cmp\\t%2, %3\", operands);
3385     if (TARGET_THUMB2)
3386       {
3387         if (need_else)
3388           output_asm_insn (\"ite\\t%d5\", operands);
3389         else
3390           output_asm_insn (\"it\\t%d5\", operands);
3391       }
3392     output_asm_insn (\"%i4%d5\\t%0, %1, %2\", operands);
3393     if (need_else)
3394       output_asm_insn (\"%i4%D5\\t%0, %1, %3\", operands);
3395     return \"\";
3396   }"
3397   [(set_attr "conds" "clob")
3398    (set (attr "length")
3399         (if_then_else (eq_attr "is_thumb" "yes")
3400                       (const_int 14)
3401                       (const_int 12)))]
3404 (define_code_iterator SAT [smin smax])
3405 (define_code_iterator SATrev [smin smax])
3406 (define_code_attr SATlo [(smin "1") (smax "2")])
3407 (define_code_attr SAThi [(smin "2") (smax "1")])
3409 (define_insn "*satsi_<SAT:code>"
3410   [(set (match_operand:SI 0 "s_register_operand" "=r")
3411         (SAT:SI (SATrev:SI (match_operand:SI 3 "s_register_operand" "r")
3412                            (match_operand:SI 1 "const_int_operand" "i"))
3413                 (match_operand:SI 2 "const_int_operand" "i")))]
3414   "TARGET_32BIT && arm_arch6 && <SAT:CODE> != <SATrev:CODE>
3415    && arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>], NULL, NULL)"
3417   int mask;
3418   bool signed_sat;
3419   if (!arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>],
3420                                &mask, &signed_sat))
3421     gcc_unreachable ();
3423   operands[1] = GEN_INT (mask);
3424   if (signed_sat)
3425     return "ssat%?\t%0, %1, %3";
3426   else
3427     return "usat%?\t%0, %1, %3";
3429   [(set_attr "predicable" "yes")
3430    (set_attr "insn" "sat")])
3432 (define_insn "*satsi_<SAT:code>_shift"
3433   [(set (match_operand:SI 0 "s_register_operand" "=r")
3434         (SAT:SI (SATrev:SI (match_operator:SI 3 "sat_shift_operator"
3435                              [(match_operand:SI 4 "s_register_operand" "r")
3436                               (match_operand:SI 5 "const_int_operand" "i")])
3437                            (match_operand:SI 1 "const_int_operand" "i"))
3438                 (match_operand:SI 2 "const_int_operand" "i")))]
3439   "TARGET_32BIT && arm_arch6 && <SAT:CODE> != <SATrev:CODE>
3440    && arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>], NULL, NULL)"
3442   int mask;
3443   bool signed_sat;
3444   if (!arm_sat_operator_match (operands[<SAT:SATlo>], operands[<SAT:SAThi>],
3445                                &mask, &signed_sat))
3446     gcc_unreachable ();
3448   operands[1] = GEN_INT (mask);
3449   if (signed_sat)
3450     return "ssat%?\t%0, %1, %4%S3";
3451   else
3452     return "usat%?\t%0, %1, %4%S3";
3454   [(set_attr "predicable" "yes")
3455    (set_attr "insn" "sat")
3456    (set_attr "shift" "3")
3457    (set_attr "type" "alu_shift")])
3459 ;; Shift and rotation insns
3461 (define_expand "ashldi3"
3462   [(set (match_operand:DI            0 "s_register_operand" "")
3463         (ashift:DI (match_operand:DI 1 "s_register_operand" "")
3464                    (match_operand:SI 2 "reg_or_int_operand" "")))]
3465   "TARGET_32BIT"
3466   "
3467   if (!CONST_INT_P (operands[2]) && TARGET_REALLY_IWMMXT)
3468     ; /* No special preparation statements; expand pattern as above.  */
3469   else
3470     {
3471       rtx scratch1, scratch2;
3473       if (CONST_INT_P (operands[2])
3474           && (HOST_WIDE_INT) INTVAL (operands[2]) == 1)
3475         {
3476           emit_insn (gen_arm_ashldi3_1bit (operands[0], operands[1]));
3477           DONE;
3478         }
3480       /* Ideally we should use iwmmxt here if we could know that operands[1]
3481          ends up already living in an iwmmxt register. Otherwise it's
3482          cheaper to have the alternate code being generated than moving
3483          values to iwmmxt regs and back.  */
3485       /* If we're optimizing for size, we prefer the libgcc calls.  */
3486       if (optimize_function_for_size_p (cfun))
3487         FAIL;
3489       /* Expand operation using core-registers.
3490          'FAIL' would achieve the same thing, but this is a bit smarter.  */
3491       scratch1 = gen_reg_rtx (SImode);
3492       scratch2 = gen_reg_rtx (SImode);
3493       arm_emit_coreregs_64bit_shift (ASHIFT, operands[0], operands[1],
3494                                      operands[2], scratch1, scratch2);
3495       DONE;
3496     }
3497   "
3500 (define_insn "arm_ashldi3_1bit"
3501   [(set (match_operand:DI            0 "s_register_operand" "=r,&r")
3502         (ashift:DI (match_operand:DI 1 "s_register_operand" "0,r")
3503                    (const_int 1)))
3504    (clobber (reg:CC CC_REGNUM))]
3505   "TARGET_32BIT"
3506   "movs\\t%Q0, %Q1, asl #1\;adc\\t%R0, %R1, %R1"
3507   [(set_attr "conds" "clob")
3508    (set_attr "length" "8")]
3511 (define_expand "ashlsi3"
3512   [(set (match_operand:SI            0 "s_register_operand" "")
3513         (ashift:SI (match_operand:SI 1 "s_register_operand" "")
3514                    (match_operand:SI 2 "arm_rhs_operand" "")))]
3515   "TARGET_EITHER"
3516   "
3517   if (GET_CODE (operands[2]) == CONST_INT
3518       && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
3519     {
3520       emit_insn (gen_movsi (operands[0], const0_rtx));
3521       DONE;
3522     }
3523   "
3526 (define_insn "*thumb1_ashlsi3"
3527   [(set (match_operand:SI            0 "register_operand" "=l,l")
3528         (ashift:SI (match_operand:SI 1 "register_operand" "l,0")
3529                    (match_operand:SI 2 "nonmemory_operand" "N,l")))]
3530   "TARGET_THUMB1"
3531   "lsl\\t%0, %1, %2"
3532   [(set_attr "length" "2")
3533    (set_attr "conds" "set")])
3535 (define_expand "ashrdi3"
3536   [(set (match_operand:DI              0 "s_register_operand" "")
3537         (ashiftrt:DI (match_operand:DI 1 "s_register_operand" "")
3538                      (match_operand:SI 2 "reg_or_int_operand" "")))]
3539   "TARGET_32BIT"
3540   "
3541   if (!CONST_INT_P (operands[2]) && TARGET_REALLY_IWMMXT)
3542     ; /* No special preparation statements; expand pattern as above.  */
3543   else
3544     {
3545       rtx scratch1, scratch2;
3547       if (CONST_INT_P (operands[2])
3548           && (HOST_WIDE_INT) INTVAL (operands[2]) == 1)
3549         {
3550           emit_insn (gen_arm_ashrdi3_1bit (operands[0], operands[1]));
3551           DONE;
3552         }
3554       /* Ideally we should use iwmmxt here if we could know that operands[1]
3555          ends up already living in an iwmmxt register. Otherwise it's
3556          cheaper to have the alternate code being generated than moving
3557          values to iwmmxt regs and back.  */
3559       /* If we're optimizing for size, we prefer the libgcc calls.  */
3560       if (optimize_function_for_size_p (cfun))
3561         FAIL;
3563       /* Expand operation using core-registers.
3564          'FAIL' would achieve the same thing, but this is a bit smarter.  */
3565       scratch1 = gen_reg_rtx (SImode);
3566       scratch2 = gen_reg_rtx (SImode);
3567       arm_emit_coreregs_64bit_shift (ASHIFTRT, operands[0], operands[1],
3568                                      operands[2], scratch1, scratch2);
3569       DONE;
3570     }
3571   "
3574 (define_insn "arm_ashrdi3_1bit"
3575   [(set (match_operand:DI              0 "s_register_operand" "=r,&r")
3576         (ashiftrt:DI (match_operand:DI 1 "s_register_operand" "0,r")
3577                      (const_int 1)))
3578    (clobber (reg:CC CC_REGNUM))]
3579   "TARGET_32BIT"
3580   "movs\\t%R0, %R1, asr #1\;mov\\t%Q0, %Q1, rrx"
3581   [(set_attr "conds" "clob")
3582    (set_attr "insn" "mov")
3583    (set_attr "length" "8")]
3586 (define_expand "ashrsi3"
3587   [(set (match_operand:SI              0 "s_register_operand" "")
3588         (ashiftrt:SI (match_operand:SI 1 "s_register_operand" "")
3589                      (match_operand:SI 2 "arm_rhs_operand" "")))]
3590   "TARGET_EITHER"
3591   "
3592   if (GET_CODE (operands[2]) == CONST_INT
3593       && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
3594     operands[2] = GEN_INT (31);
3595   "
3598 (define_insn "*thumb1_ashrsi3"
3599   [(set (match_operand:SI              0 "register_operand" "=l,l")
3600         (ashiftrt:SI (match_operand:SI 1 "register_operand" "l,0")
3601                      (match_operand:SI 2 "nonmemory_operand" "N,l")))]
3602   "TARGET_THUMB1"
3603   "asr\\t%0, %1, %2"
3604   [(set_attr "length" "2")
3605    (set_attr "conds" "set")])
3607 (define_expand "lshrdi3"
3608   [(set (match_operand:DI              0 "s_register_operand" "")
3609         (lshiftrt:DI (match_operand:DI 1 "s_register_operand" "")
3610                      (match_operand:SI 2 "reg_or_int_operand" "")))]
3611   "TARGET_32BIT"
3612   "
3613   if (!CONST_INT_P (operands[2]) && TARGET_REALLY_IWMMXT)
3614     ; /* No special preparation statements; expand pattern as above.  */
3615   else
3616     {
3617       rtx scratch1, scratch2;
3619       if (CONST_INT_P (operands[2])
3620           && (HOST_WIDE_INT) INTVAL (operands[2]) == 1)
3621         {
3622           emit_insn (gen_arm_lshrdi3_1bit (operands[0], operands[1]));
3623           DONE;
3624         }
3626       /* Ideally we should use iwmmxt here if we could know that operands[1]
3627          ends up already living in an iwmmxt register. Otherwise it's
3628          cheaper to have the alternate code being generated than moving
3629          values to iwmmxt regs and back.  */
3631       /* If we're optimizing for size, we prefer the libgcc calls.  */
3632       if (optimize_function_for_size_p (cfun))
3633         FAIL;
3635       /* Expand operation using core-registers.
3636          'FAIL' would achieve the same thing, but this is a bit smarter.  */
3637       scratch1 = gen_reg_rtx (SImode);
3638       scratch2 = gen_reg_rtx (SImode);
3639       arm_emit_coreregs_64bit_shift (LSHIFTRT, operands[0], operands[1],
3640                                      operands[2], scratch1, scratch2);
3641       DONE;
3642     }
3643   "
3646 (define_insn "arm_lshrdi3_1bit"
3647   [(set (match_operand:DI              0 "s_register_operand" "=r,&r")
3648         (lshiftrt:DI (match_operand:DI 1 "s_register_operand" "0,r")
3649                      (const_int 1)))
3650    (clobber (reg:CC CC_REGNUM))]
3651   "TARGET_32BIT"
3652   "movs\\t%R0, %R1, lsr #1\;mov\\t%Q0, %Q1, rrx"
3653   [(set_attr "conds" "clob")
3654    (set_attr "insn" "mov")
3655    (set_attr "length" "8")]
3658 (define_expand "lshrsi3"
3659   [(set (match_operand:SI              0 "s_register_operand" "")
3660         (lshiftrt:SI (match_operand:SI 1 "s_register_operand" "")
3661                      (match_operand:SI 2 "arm_rhs_operand" "")))]
3662   "TARGET_EITHER"
3663   "
3664   if (GET_CODE (operands[2]) == CONST_INT
3665       && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
3666     {
3667       emit_insn (gen_movsi (operands[0], const0_rtx));
3668       DONE;
3669     }
3670   "
3673 (define_insn "*thumb1_lshrsi3"
3674   [(set (match_operand:SI              0 "register_operand" "=l,l")
3675         (lshiftrt:SI (match_operand:SI 1 "register_operand" "l,0")
3676                      (match_operand:SI 2 "nonmemory_operand" "N,l")))]
3677   "TARGET_THUMB1"
3678   "lsr\\t%0, %1, %2"
3679   [(set_attr "length" "2")
3680    (set_attr "conds" "set")])
3682 (define_expand "rotlsi3"
3683   [(set (match_operand:SI              0 "s_register_operand" "")
3684         (rotatert:SI (match_operand:SI 1 "s_register_operand" "")
3685                      (match_operand:SI 2 "reg_or_int_operand" "")))]
3686   "TARGET_32BIT"
3687   "
3688   if (GET_CODE (operands[2]) == CONST_INT)
3689     operands[2] = GEN_INT ((32 - INTVAL (operands[2])) % 32);
3690   else
3691     {
3692       rtx reg = gen_reg_rtx (SImode);
3693       emit_insn (gen_subsi3 (reg, GEN_INT (32), operands[2]));
3694       operands[2] = reg;
3695     }
3696   "
3699 (define_expand "rotrsi3"
3700   [(set (match_operand:SI              0 "s_register_operand" "")
3701         (rotatert:SI (match_operand:SI 1 "s_register_operand" "")
3702                      (match_operand:SI 2 "arm_rhs_operand" "")))]
3703   "TARGET_EITHER"
3704   "
3705   if (TARGET_32BIT)
3706     {
3707       if (GET_CODE (operands[2]) == CONST_INT
3708           && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
3709         operands[2] = GEN_INT (INTVAL (operands[2]) % 32);
3710     }
3711   else /* TARGET_THUMB1 */
3712     {
3713       if (GET_CODE (operands [2]) == CONST_INT)
3714         operands [2] = force_reg (SImode, operands[2]);
3715     }
3716   "
3719 (define_insn "*thumb1_rotrsi3"
3720   [(set (match_operand:SI              0 "register_operand" "=l")
3721         (rotatert:SI (match_operand:SI 1 "register_operand" "0")
3722                      (match_operand:SI 2 "register_operand" "l")))]
3723   "TARGET_THUMB1"
3724   "ror\\t%0, %0, %2"
3725   [(set_attr "length" "2")]
3728 (define_insn "*arm_shiftsi3"
3729   [(set (match_operand:SI   0 "s_register_operand" "=r")
3730         (match_operator:SI  3 "shift_operator"
3731          [(match_operand:SI 1 "s_register_operand"  "r")
3732           (match_operand:SI 2 "reg_or_int_operand" "rM")]))]
3733   "TARGET_32BIT"
3734   "* return arm_output_shift(operands, 0);"
3735   [(set_attr "predicable" "yes")
3736    (set_attr "shift" "1")
3737    (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
3738                       (const_string "alu_shift")
3739                       (const_string "alu_shift_reg")))]
3742 (define_insn "*shiftsi3_compare0"
3743   [(set (reg:CC_NOOV CC_REGNUM)
3744         (compare:CC_NOOV (match_operator:SI 3 "shift_operator"
3745                           [(match_operand:SI 1 "s_register_operand" "r")
3746                            (match_operand:SI 2 "arm_rhs_operand" "rM")])
3747                          (const_int 0)))
3748    (set (match_operand:SI 0 "s_register_operand" "=r")
3749         (match_op_dup 3 [(match_dup 1) (match_dup 2)]))]
3750   "TARGET_32BIT"
3751   "* return arm_output_shift(operands, 1);"
3752   [(set_attr "conds" "set")
3753    (set_attr "shift" "1")
3754    (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
3755                       (const_string "alu_shift")
3756                       (const_string "alu_shift_reg")))]
3759 (define_insn "*shiftsi3_compare0_scratch"
3760   [(set (reg:CC_NOOV CC_REGNUM)
3761         (compare:CC_NOOV (match_operator:SI 3 "shift_operator"
3762                           [(match_operand:SI 1 "s_register_operand" "r")
3763                            (match_operand:SI 2 "arm_rhs_operand" "rM")])
3764                          (const_int 0)))
3765    (clobber (match_scratch:SI 0 "=r"))]
3766   "TARGET_32BIT"
3767   "* return arm_output_shift(operands, 1);"
3768   [(set_attr "conds" "set")
3769    (set_attr "shift" "1")]
3772 (define_insn "*not_shiftsi"
3773   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3774         (not:SI (match_operator:SI 3 "shift_operator"
3775                  [(match_operand:SI 1 "s_register_operand" "r,r")
3776                   (match_operand:SI 2 "shift_amount_operand" "M,rM")])))]
3777   "TARGET_32BIT"
3778   "mvn%?\\t%0, %1%S3"
3779   [(set_attr "predicable" "yes")
3780    (set_attr "shift" "1")
3781    (set_attr "insn" "mvn")
3782    (set_attr "arch" "32,a")
3783    (set_attr "type" "alu_shift,alu_shift_reg")])
3785 (define_insn "*not_shiftsi_compare0"
3786   [(set (reg:CC_NOOV CC_REGNUM)
3787         (compare:CC_NOOV
3788          (not:SI (match_operator:SI 3 "shift_operator"
3789                   [(match_operand:SI 1 "s_register_operand" "r,r")
3790                    (match_operand:SI 2 "shift_amount_operand" "M,rM")]))
3791          (const_int 0)))
3792    (set (match_operand:SI 0 "s_register_operand" "=r,r")
3793         (not:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])))]
3794   "TARGET_32BIT"
3795   "mvn%.\\t%0, %1%S3"
3796   [(set_attr "conds" "set")
3797    (set_attr "shift" "1")
3798    (set_attr "insn" "mvn")
3799    (set_attr "arch" "32,a")
3800    (set_attr "type" "alu_shift,alu_shift_reg")])
3802 (define_insn "*not_shiftsi_compare0_scratch"
3803   [(set (reg:CC_NOOV CC_REGNUM)
3804         (compare:CC_NOOV
3805          (not:SI (match_operator:SI 3 "shift_operator"
3806                   [(match_operand:SI 1 "s_register_operand" "r,r")
3807                    (match_operand:SI 2 "shift_amount_operand" "M,rM")]))
3808          (const_int 0)))
3809    (clobber (match_scratch:SI 0 "=r,r"))]
3810   "TARGET_32BIT"
3811   "mvn%.\\t%0, %1%S3"
3812   [(set_attr "conds" "set")
3813    (set_attr "shift" "1")
3814    (set_attr "insn" "mvn")
3815    (set_attr "arch" "32,a")
3816    (set_attr "type" "alu_shift,alu_shift_reg")])
3818 ;; We don't really have extzv, but defining this using shifts helps
3819 ;; to reduce register pressure later on.
3821 (define_expand "extzv"
3822   [(set (match_operand 0 "s_register_operand" "")
3823         (zero_extract (match_operand 1 "nonimmediate_operand" "")
3824                       (match_operand 2 "const_int_operand" "")
3825                       (match_operand 3 "const_int_operand" "")))]
3826   "TARGET_THUMB1 || arm_arch_thumb2"
3827   "
3828   {
3829     HOST_WIDE_INT lshift = 32 - INTVAL (operands[2]) - INTVAL (operands[3]);
3830     HOST_WIDE_INT rshift = 32 - INTVAL (operands[2]);
3831     
3832     if (arm_arch_thumb2)
3833       {
3834         HOST_WIDE_INT width = INTVAL (operands[2]);
3835         HOST_WIDE_INT bitpos = INTVAL (operands[3]);
3837         if (unaligned_access && MEM_P (operands[1])
3838             && (width == 16 || width == 32) && (bitpos % BITS_PER_UNIT) == 0)
3839           {
3840             rtx base_addr;
3842             if (BYTES_BIG_ENDIAN)
3843               bitpos = GET_MODE_BITSIZE (GET_MODE (operands[0])) - width
3844                        - bitpos;
3846             if (width == 32)
3847               {
3848                 base_addr = adjust_address (operands[1], SImode,
3849                                             bitpos / BITS_PER_UNIT);
3850                 emit_insn (gen_unaligned_loadsi (operands[0], base_addr));
3851               }
3852             else
3853               {
3854                 rtx dest = operands[0];
3855                 rtx tmp = gen_reg_rtx (SImode);
3857                 /* We may get a paradoxical subreg here.  Strip it off.  */
3858                 if (GET_CODE (dest) == SUBREG
3859                     && GET_MODE (dest) == SImode
3860                     && GET_MODE (SUBREG_REG (dest)) == HImode)
3861                   dest = SUBREG_REG (dest);
3863                 if (GET_MODE_BITSIZE (GET_MODE (dest)) != width)
3864                   FAIL;
3866                 base_addr = adjust_address (operands[1], HImode,
3867                                             bitpos / BITS_PER_UNIT);
3868                 emit_insn (gen_unaligned_loadhiu (tmp, base_addr));
3869                 emit_move_insn (gen_lowpart (SImode, dest), tmp);
3870               }
3871             DONE;
3872           }
3873         else if (s_register_operand (operands[1], GET_MODE (operands[1])))
3874           {
3875             emit_insn (gen_extzv_t2 (operands[0], operands[1], operands[2],
3876                                      operands[3]));
3877             DONE;
3878           }
3879         else
3880           FAIL;
3881       }
3882     
3883     if (!s_register_operand (operands[1], GET_MODE (operands[1])))
3884       FAIL;
3886     operands[3] = GEN_INT (rshift);
3887     
3888     if (lshift == 0)
3889       {
3890         emit_insn (gen_lshrsi3 (operands[0], operands[1], operands[3]));
3891         DONE;
3892       }
3893       
3894     emit_insn (gen_extzv_t1 (operands[0], operands[1], GEN_INT (lshift),
3895                              operands[3], gen_reg_rtx (SImode)));
3896     DONE;
3897   }"
3900 ;; Helper for extzv, for the Thumb-1 register-shifts case.
3902 (define_expand "extzv_t1"
3903   [(set (match_operand:SI 4 "s_register_operand" "")
3904         (ashift:SI (match_operand:SI 1 "nonimmediate_operand" "")
3905                    (match_operand:SI 2 "const_int_operand" "")))
3906    (set (match_operand:SI 0 "s_register_operand" "")
3907         (lshiftrt:SI (match_dup 4)
3908                      (match_operand:SI 3 "const_int_operand" "")))]
3909   "TARGET_THUMB1"
3910   "")
3912 (define_expand "extv"
3913   [(set (match_operand 0 "s_register_operand" "")
3914         (sign_extract (match_operand 1 "nonimmediate_operand" "")
3915                       (match_operand 2 "const_int_operand" "")
3916                       (match_operand 3 "const_int_operand" "")))]
3917   "arm_arch_thumb2"
3919   HOST_WIDE_INT width = INTVAL (operands[2]);
3920   HOST_WIDE_INT bitpos = INTVAL (operands[3]);
3922   if (unaligned_access && MEM_P (operands[1]) && (width == 16 || width == 32)
3923       && (bitpos % BITS_PER_UNIT)  == 0)
3924     {
3925       rtx base_addr;
3926       
3927       if (BYTES_BIG_ENDIAN)
3928         bitpos = GET_MODE_BITSIZE (GET_MODE (operands[0])) - width - bitpos;
3929       
3930       if (width == 32)
3931         {
3932           base_addr = adjust_address (operands[1], SImode,
3933                                       bitpos / BITS_PER_UNIT);
3934           emit_insn (gen_unaligned_loadsi (operands[0], base_addr));
3935         }
3936       else
3937         {
3938           rtx dest = operands[0];
3939           rtx tmp = gen_reg_rtx (SImode);
3940           
3941           /* We may get a paradoxical subreg here.  Strip it off.  */
3942           if (GET_CODE (dest) == SUBREG
3943               && GET_MODE (dest) == SImode
3944               && GET_MODE (SUBREG_REG (dest)) == HImode)
3945             dest = SUBREG_REG (dest);
3946           
3947           if (GET_MODE_BITSIZE (GET_MODE (dest)) != width)
3948             FAIL;
3949           
3950           base_addr = adjust_address (operands[1], HImode,
3951                                       bitpos / BITS_PER_UNIT);
3952           emit_insn (gen_unaligned_loadhis (tmp, base_addr));
3953           emit_move_insn (gen_lowpart (SImode, dest), tmp);
3954         }
3956       DONE;
3957     }
3958   else if (!s_register_operand (operands[1], GET_MODE (operands[1])))
3959     FAIL;
3960   else if (GET_MODE (operands[0]) == SImode
3961            && GET_MODE (operands[1]) == SImode)
3962     {
3963       emit_insn (gen_extv_regsi (operands[0], operands[1], operands[2],
3964                                  operands[3]));
3965       DONE;
3966     }
3968   FAIL;
3971 ; Helper to expand register forms of extv with the proper modes.
3973 (define_expand "extv_regsi"
3974   [(set (match_operand:SI 0 "s_register_operand" "")
3975         (sign_extract:SI (match_operand:SI 1 "s_register_operand" "")
3976                          (match_operand 2 "const_int_operand" "")
3977                          (match_operand 3 "const_int_operand" "")))]
3978   ""
3982 ; ARMv6+ unaligned load/store instructions (used for packed structure accesses).
3984 (define_insn "unaligned_loadsi"
3985   [(set (match_operand:SI 0 "s_register_operand" "=l,r")
3986         (unspec:SI [(match_operand:SI 1 "memory_operand" "Uw,m")]
3987                    UNSPEC_UNALIGNED_LOAD))]
3988   "unaligned_access && TARGET_32BIT"
3989   "ldr%?\t%0, %1\t@ unaligned"
3990   [(set_attr "arch" "t2,any")
3991    (set_attr "length" "2,4")
3992    (set_attr "predicable" "yes")
3993    (set_attr "type" "load1")])
3995 (define_insn "unaligned_loadhis"
3996   [(set (match_operand:SI 0 "s_register_operand" "=l,r")
3997         (sign_extend:SI
3998           (unspec:HI [(match_operand:HI 1 "memory_operand" "Uw,m")]
3999                      UNSPEC_UNALIGNED_LOAD)))]
4000   "unaligned_access && TARGET_32BIT"
4001   "ldr%(sh%)\t%0, %1\t@ unaligned"
4002   [(set_attr "arch" "t2,any")
4003    (set_attr "length" "2,4")
4004    (set_attr "predicable" "yes")
4005    (set_attr "type" "load_byte")])
4007 (define_insn "unaligned_loadhiu"
4008   [(set (match_operand:SI 0 "s_register_operand" "=l,r")
4009         (zero_extend:SI
4010           (unspec:HI [(match_operand:HI 1 "memory_operand" "Uw,m")]
4011                      UNSPEC_UNALIGNED_LOAD)))]
4012   "unaligned_access && TARGET_32BIT"
4013   "ldr%(h%)\t%0, %1\t@ unaligned"
4014   [(set_attr "arch" "t2,any")
4015    (set_attr "length" "2,4")
4016    (set_attr "predicable" "yes")
4017    (set_attr "type" "load_byte")])
4019 (define_insn "unaligned_storesi"
4020   [(set (match_operand:SI 0 "memory_operand" "=Uw,m")
4021         (unspec:SI [(match_operand:SI 1 "s_register_operand" "l,r")]
4022                    UNSPEC_UNALIGNED_STORE))]
4023   "unaligned_access && TARGET_32BIT"
4024   "str%?\t%1, %0\t@ unaligned"
4025   [(set_attr "arch" "t2,any")
4026    (set_attr "length" "2,4")
4027    (set_attr "predicable" "yes")
4028    (set_attr "type" "store1")])
4030 (define_insn "unaligned_storehi"
4031   [(set (match_operand:HI 0 "memory_operand" "=Uw,m")
4032         (unspec:HI [(match_operand:HI 1 "s_register_operand" "l,r")]
4033                    UNSPEC_UNALIGNED_STORE))]
4034   "unaligned_access && TARGET_32BIT"
4035   "str%(h%)\t%1, %0\t@ unaligned"
4036   [(set_attr "arch" "t2,any")
4037    (set_attr "length" "2,4")
4038    (set_attr "predicable" "yes")
4039    (set_attr "type" "store1")])
4041 (define_insn "*extv_reg"
4042   [(set (match_operand:SI 0 "s_register_operand" "=r")
4043         (sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
4044                          (match_operand:SI 2 "const_int_operand" "M")
4045                          (match_operand:SI 3 "const_int_operand" "M")))]
4046   "arm_arch_thumb2"
4047   "sbfx%?\t%0, %1, %3, %2"
4048   [(set_attr "length" "4")
4049    (set_attr "predicable" "yes")]
4052 (define_insn "extzv_t2"
4053   [(set (match_operand:SI 0 "s_register_operand" "=r")
4054         (zero_extract:SI (match_operand:SI 1 "s_register_operand" "r")
4055                          (match_operand:SI 2 "const_int_operand" "M")
4056                          (match_operand:SI 3 "const_int_operand" "M")))]
4057   "arm_arch_thumb2"
4058   "ubfx%?\t%0, %1, %3, %2"
4059   [(set_attr "length" "4")
4060    (set_attr "predicable" "yes")]
4064 ;; Division instructions
4065 (define_insn "divsi3"
4066   [(set (match_operand:SI         0 "s_register_operand" "=r")
4067         (div:SI (match_operand:SI 1 "s_register_operand"  "r")
4068                 (match_operand:SI 2 "s_register_operand"  "r")))]
4069   "TARGET_IDIV"
4070   "sdiv%?\t%0, %1, %2"
4071   [(set_attr "predicable" "yes")
4072    (set_attr "insn" "sdiv")]
4075 (define_insn "udivsi3"
4076   [(set (match_operand:SI          0 "s_register_operand" "=r")
4077         (udiv:SI (match_operand:SI 1 "s_register_operand"  "r")
4078                  (match_operand:SI 2 "s_register_operand"  "r")))]
4079   "TARGET_IDIV"
4080   "udiv%?\t%0, %1, %2"
4081   [(set_attr "predicable" "yes")
4082    (set_attr "insn" "udiv")]
4086 ;; Unary arithmetic insns
4088 (define_expand "negdi2"
4089  [(parallel
4090    [(set (match_operand:DI 0 "s_register_operand" "")
4091          (neg:DI (match_operand:DI 1 "s_register_operand" "")))
4092     (clobber (reg:CC CC_REGNUM))])]
4093   "TARGET_EITHER"
4094   {
4095     if (TARGET_NEON)
4096       {
4097         emit_insn (gen_negdi2_neon (operands[0], operands[1]));
4098         DONE;
4099       }
4100   }
4103 ;; The constraints here are to prevent a *partial* overlap (where %Q0 == %R1).
4104 ;; The first alternative allows the common case of a *full* overlap.
4105 (define_insn "*arm_negdi2"
4106   [(set (match_operand:DI         0 "s_register_operand" "=r,&r")
4107         (neg:DI (match_operand:DI 1 "s_register_operand"  "0,r")))
4108    (clobber (reg:CC CC_REGNUM))]
4109   "TARGET_ARM"
4110   "rsbs\\t%Q0, %Q1, #0\;rsc\\t%R0, %R1, #0"
4111   [(set_attr "conds" "clob")
4112    (set_attr "length" "8")]
4115 (define_insn "*thumb1_negdi2"
4116   [(set (match_operand:DI 0 "register_operand" "=&l")
4117         (neg:DI (match_operand:DI 1 "register_operand" "l")))
4118    (clobber (reg:CC CC_REGNUM))]
4119   "TARGET_THUMB1"
4120   "mov\\t%R0, #0\;neg\\t%Q0, %Q1\;sbc\\t%R0, %R1"
4121   [(set_attr "length" "6")]
4124 (define_expand "negsi2"
4125   [(set (match_operand:SI         0 "s_register_operand" "")
4126         (neg:SI (match_operand:SI 1 "s_register_operand" "")))]
4127   "TARGET_EITHER"
4128   ""
4131 (define_insn "*arm_negsi2"
4132   [(set (match_operand:SI         0 "s_register_operand" "=r")
4133         (neg:SI (match_operand:SI 1 "s_register_operand" "r")))]
4134   "TARGET_32BIT"
4135   "rsb%?\\t%0, %1, #0"
4136   [(set_attr "predicable" "yes")]
4139 (define_insn "*thumb1_negsi2"
4140   [(set (match_operand:SI         0 "register_operand" "=l")
4141         (neg:SI (match_operand:SI 1 "register_operand" "l")))]
4142   "TARGET_THUMB1"
4143   "neg\\t%0, %1"
4144   [(set_attr "length" "2")]
4147 (define_expand "negsf2"
4148   [(set (match_operand:SF         0 "s_register_operand" "")
4149         (neg:SF (match_operand:SF 1 "s_register_operand" "")))]
4150   "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP"
4151   ""
4154 (define_expand "negdf2"
4155   [(set (match_operand:DF         0 "s_register_operand" "")
4156         (neg:DF (match_operand:DF 1 "s_register_operand" "")))]
4157   "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
4158   "")
4160 ;; abssi2 doesn't really clobber the condition codes if a different register
4161 ;; is being set.  To keep things simple, assume during rtl manipulations that
4162 ;; it does, but tell the final scan operator the truth.  Similarly for
4163 ;; (neg (abs...))
4165 (define_expand "abssi2"
4166   [(parallel
4167     [(set (match_operand:SI         0 "s_register_operand" "")
4168           (abs:SI (match_operand:SI 1 "s_register_operand" "")))
4169      (clobber (match_dup 2))])]
4170   "TARGET_EITHER"
4171   "
4172   if (TARGET_THUMB1)
4173     operands[2] = gen_rtx_SCRATCH (SImode);
4174   else
4175     operands[2] = gen_rtx_REG (CCmode, CC_REGNUM);
4178 (define_insn "*arm_abssi2"
4179   [(set (match_operand:SI 0 "s_register_operand" "=r,&r")
4180         (abs:SI (match_operand:SI 1 "s_register_operand" "0,r")))
4181    (clobber (reg:CC CC_REGNUM))]
4182   "TARGET_ARM"
4183   "@
4184    cmp\\t%0, #0\;rsblt\\t%0, %0, #0
4185    eor%?\\t%0, %1, %1, asr #31\;sub%?\\t%0, %0, %1, asr #31"
4186   [(set_attr "conds" "clob,*")
4187    (set_attr "shift" "1")
4188    ;; predicable can't be set based on the variant, so left as no
4189    (set_attr "length" "8")]
4192 (define_insn_and_split "*thumb1_abssi2"
4193   [(set (match_operand:SI 0 "s_register_operand" "=l")
4194         (abs:SI (match_operand:SI 1 "s_register_operand" "l")))
4195    (clobber (match_scratch:SI 2 "=&l"))]
4196   "TARGET_THUMB1"
4197   "#"
4198   "TARGET_THUMB1 && reload_completed"
4199   [(set (match_dup 2) (ashiftrt:SI (match_dup 1) (const_int 31)))
4200    (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))
4201    (set (match_dup 0) (xor:SI (match_dup 0) (match_dup 2)))]
4202   ""
4203   [(set_attr "length" "6")]
4206 (define_insn "*arm_neg_abssi2"
4207   [(set (match_operand:SI 0 "s_register_operand" "=r,&r")
4208         (neg:SI (abs:SI (match_operand:SI 1 "s_register_operand" "0,r"))))
4209    (clobber (reg:CC CC_REGNUM))]
4210   "TARGET_ARM"
4211   "@
4212    cmp\\t%0, #0\;rsbgt\\t%0, %0, #0
4213    eor%?\\t%0, %1, %1, asr #31\;rsb%?\\t%0, %0, %1, asr #31"
4214   [(set_attr "conds" "clob,*")
4215    (set_attr "shift" "1")
4216    ;; predicable can't be set based on the variant, so left as no
4217    (set_attr "length" "8")]
4220 (define_insn_and_split "*thumb1_neg_abssi2"
4221   [(set (match_operand:SI 0 "s_register_operand" "=l")
4222         (neg:SI (abs:SI (match_operand:SI 1 "s_register_operand" "l"))))
4223    (clobber (match_scratch:SI 2 "=&l"))]
4224   "TARGET_THUMB1"
4225   "#"
4226   "TARGET_THUMB1 && reload_completed"
4227   [(set (match_dup 2) (ashiftrt:SI (match_dup 1) (const_int 31)))
4228    (set (match_dup 0) (minus:SI (match_dup 2) (match_dup 1)))
4229    (set (match_dup 0) (xor:SI (match_dup 0) (match_dup 2)))]
4230   ""
4231   [(set_attr "length" "6")]
4234 (define_expand "abssf2"
4235   [(set (match_operand:SF         0 "s_register_operand" "")
4236         (abs:SF (match_operand:SF 1 "s_register_operand" "")))]
4237   "TARGET_32BIT && TARGET_HARD_FLOAT"
4238   "")
4240 (define_expand "absdf2"
4241   [(set (match_operand:DF         0 "s_register_operand" "")
4242         (abs:DF (match_operand:DF 1 "s_register_operand" "")))]
4243   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
4244   "")
4246 (define_expand "sqrtsf2"
4247   [(set (match_operand:SF 0 "s_register_operand" "")
4248         (sqrt:SF (match_operand:SF 1 "s_register_operand" "")))]
4249   "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP"
4250   "")
4252 (define_expand "sqrtdf2"
4253   [(set (match_operand:DF 0 "s_register_operand" "")
4254         (sqrt:DF (match_operand:DF 1 "s_register_operand" "")))]
4255   "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
4256   "")
4258 (define_insn_and_split "one_cmpldi2"
4259   [(set (match_operand:DI 0 "s_register_operand"         "=w,&r,&r,?w")
4260         (not:DI (match_operand:DI 1 "s_register_operand" " w, 0, r, w")))]
4261   "TARGET_32BIT"
4262   "@
4263    vmvn\t%P0, %P1
4264    #
4265    #
4266    vmvn\t%P0, %P1"
4267   "TARGET_32BIT && reload_completed
4268    && arm_general_register_operand (operands[0], DImode)"
4269   [(set (match_dup 0) (not:SI (match_dup 1)))
4270    (set (match_dup 2) (not:SI (match_dup 3)))]
4271   "
4272   {
4273     operands[2] = gen_highpart (SImode, operands[0]);
4274     operands[0] = gen_lowpart (SImode, operands[0]);
4275     operands[3] = gen_highpart (SImode, operands[1]);
4276     operands[1] = gen_lowpart (SImode, operands[1]);
4277   }"
4278   [(set_attr "length" "*,8,8,*")
4279    (set_attr "predicable" "no,yes,yes,no")
4280    (set_attr "neon_type" "neon_int_1,*,*,neon_int_1")
4281    (set_attr "arch" "neon_nota8,*,*,neon_onlya8")]
4284 (define_expand "one_cmplsi2"
4285   [(set (match_operand:SI         0 "s_register_operand" "")
4286         (not:SI (match_operand:SI 1 "s_register_operand" "")))]
4287   "TARGET_EITHER"
4288   ""
4291 (define_insn "*arm_one_cmplsi2"
4292   [(set (match_operand:SI         0 "s_register_operand" "=r")
4293         (not:SI (match_operand:SI 1 "s_register_operand"  "r")))]
4294   "TARGET_32BIT"
4295   "mvn%?\\t%0, %1"
4296   [(set_attr "predicable" "yes")
4297    (set_attr "insn" "mvn")]
4300 (define_insn "*thumb1_one_cmplsi2"
4301   [(set (match_operand:SI         0 "register_operand" "=l")
4302         (not:SI (match_operand:SI 1 "register_operand"  "l")))]
4303   "TARGET_THUMB1"
4304   "mvn\\t%0, %1"
4305   [(set_attr "length" "2")
4306    (set_attr "insn" "mvn")]
4309 (define_insn "*notsi_compare0"
4310   [(set (reg:CC_NOOV CC_REGNUM)
4311         (compare:CC_NOOV (not:SI (match_operand:SI 1 "s_register_operand" "r"))
4312                          (const_int 0)))
4313    (set (match_operand:SI 0 "s_register_operand" "=r")
4314         (not:SI (match_dup 1)))]
4315   "TARGET_32BIT"
4316   "mvn%.\\t%0, %1"
4317   [(set_attr "conds" "set")
4318    (set_attr "insn" "mvn")]
4321 (define_insn "*notsi_compare0_scratch"
4322   [(set (reg:CC_NOOV CC_REGNUM)
4323         (compare:CC_NOOV (not:SI (match_operand:SI 1 "s_register_operand" "r"))
4324                          (const_int 0)))
4325    (clobber (match_scratch:SI 0 "=r"))]
4326   "TARGET_32BIT"
4327   "mvn%.\\t%0, %1"
4328   [(set_attr "conds" "set")
4329    (set_attr "insn" "mvn")]
4332 ;; Fixed <--> Floating conversion insns
4334 (define_expand "floatsihf2"
4335   [(set (match_operand:HF           0 "general_operand" "")
4336         (float:HF (match_operand:SI 1 "general_operand" "")))]
4337   "TARGET_EITHER"
4338   "
4339   {
4340     rtx op1 = gen_reg_rtx (SFmode);
4341     expand_float (op1, operands[1], 0);
4342     op1 = convert_to_mode (HFmode, op1, 0);
4343     emit_move_insn (operands[0], op1);
4344     DONE;
4345   }"
4348 (define_expand "floatdihf2"
4349   [(set (match_operand:HF           0 "general_operand" "")
4350         (float:HF (match_operand:DI 1 "general_operand" "")))]
4351   "TARGET_EITHER"
4352   "
4353   {
4354     rtx op1 = gen_reg_rtx (SFmode);
4355     expand_float (op1, operands[1], 0);
4356     op1 = convert_to_mode (HFmode, op1, 0);
4357     emit_move_insn (operands[0], op1);
4358     DONE;
4359   }"
4362 (define_expand "floatsisf2"
4363   [(set (match_operand:SF           0 "s_register_operand" "")
4364         (float:SF (match_operand:SI 1 "s_register_operand" "")))]
4365   "TARGET_32BIT && TARGET_HARD_FLOAT"
4366   "
4369 (define_expand "floatsidf2"
4370   [(set (match_operand:DF           0 "s_register_operand" "")
4371         (float:DF (match_operand:SI 1 "s_register_operand" "")))]
4372   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
4373   "
4376 (define_expand "fix_trunchfsi2"
4377   [(set (match_operand:SI         0 "general_operand" "")
4378         (fix:SI (fix:HF (match_operand:HF 1 "general_operand"  ""))))]
4379   "TARGET_EITHER"
4380   "
4381   {
4382     rtx op1 = convert_to_mode (SFmode, operands[1], 0);
4383     expand_fix (operands[0], op1, 0);
4384     DONE;
4385   }"
4388 (define_expand "fix_trunchfdi2"
4389   [(set (match_operand:DI         0 "general_operand" "")
4390         (fix:DI (fix:HF (match_operand:HF 1 "general_operand"  ""))))]
4391   "TARGET_EITHER"
4392   "
4393   {
4394     rtx op1 = convert_to_mode (SFmode, operands[1], 0);
4395     expand_fix (operands[0], op1, 0);
4396     DONE;
4397   }"
4400 (define_expand "fix_truncsfsi2"
4401   [(set (match_operand:SI         0 "s_register_operand" "")
4402         (fix:SI (fix:SF (match_operand:SF 1 "s_register_operand"  ""))))]
4403   "TARGET_32BIT && TARGET_HARD_FLOAT"
4404   "
4407 (define_expand "fix_truncdfsi2"
4408   [(set (match_operand:SI         0 "s_register_operand" "")
4409         (fix:SI (fix:DF (match_operand:DF 1 "s_register_operand"  ""))))]
4410   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
4411   "
4414 ;; Truncation insns
4416 (define_expand "truncdfsf2"
4417   [(set (match_operand:SF  0 "s_register_operand" "")
4418         (float_truncate:SF
4419          (match_operand:DF 1 "s_register_operand" "")))]
4420   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
4421   ""
4424 /* DFmode -> HFmode conversions have to go through SFmode.  */
4425 (define_expand "truncdfhf2"
4426   [(set (match_operand:HF  0 "general_operand" "")
4427         (float_truncate:HF
4428          (match_operand:DF 1 "general_operand" "")))]
4429   "TARGET_EITHER"
4430   "
4431   {
4432     rtx op1;
4433     op1 = convert_to_mode (SFmode, operands[1], 0);
4434     op1 = convert_to_mode (HFmode, op1, 0);
4435     emit_move_insn (operands[0], op1);
4436     DONE;
4437   }"
4440 ;; Zero and sign extension instructions.
4442 (define_insn "zero_extend<mode>di2"
4443   [(set (match_operand:DI 0 "s_register_operand" "=r")
4444         (zero_extend:DI (match_operand:QHSI 1 "<qhs_zextenddi_op>"
4445                                             "<qhs_zextenddi_cstr>")))]
4446   "TARGET_32BIT <qhs_zextenddi_cond>"
4447   "#"
4448   [(set_attr "length" "8")
4449    (set_attr "ce_count" "2")
4450    (set_attr "predicable" "yes")]
4453 (define_insn "extend<mode>di2"
4454   [(set (match_operand:DI 0 "s_register_operand" "=r")
4455         (sign_extend:DI (match_operand:QHSI 1 "<qhs_extenddi_op>"
4456                                             "<qhs_extenddi_cstr>")))]
4457   "TARGET_32BIT <qhs_sextenddi_cond>"
4458   "#"
4459   [(set_attr "length" "8")
4460    (set_attr "ce_count" "2")
4461    (set_attr "shift" "1")
4462    (set_attr "predicable" "yes")]
4465 ;; Splits for all extensions to DImode
4466 (define_split
4467   [(set (match_operand:DI 0 "s_register_operand" "")
4468         (zero_extend:DI (match_operand 1 "nonimmediate_operand" "")))]
4469   "TARGET_32BIT"
4470   [(set (match_dup 0) (match_dup 1))]
4472   rtx lo_part = gen_lowpart (SImode, operands[0]);
4473   enum machine_mode src_mode = GET_MODE (operands[1]);
4475   if (REG_P (operands[0])
4476       && !reg_overlap_mentioned_p (operands[0], operands[1]))
4477     emit_clobber (operands[0]);
4478   if (!REG_P (lo_part) || src_mode != SImode
4479       || !rtx_equal_p (lo_part, operands[1]))
4480     {
4481       if (src_mode == SImode)
4482         emit_move_insn (lo_part, operands[1]);
4483       else
4484         emit_insn (gen_rtx_SET (VOIDmode, lo_part,
4485                                 gen_rtx_ZERO_EXTEND (SImode, operands[1])));
4486       operands[1] = lo_part;
4487     }
4488   operands[0] = gen_highpart (SImode, operands[0]);
4489   operands[1] = const0_rtx;
4492 (define_split
4493   [(set (match_operand:DI 0 "s_register_operand" "")
4494         (sign_extend:DI (match_operand 1 "nonimmediate_operand" "")))]
4495   "TARGET_32BIT"
4496   [(set (match_dup 0) (ashiftrt:SI (match_dup 1) (const_int 31)))]
4498   rtx lo_part = gen_lowpart (SImode, operands[0]);
4499   enum machine_mode src_mode = GET_MODE (operands[1]);
4501   if (REG_P (operands[0])
4502       && !reg_overlap_mentioned_p (operands[0], operands[1]))
4503     emit_clobber (operands[0]);
4505   if (!REG_P (lo_part) || src_mode != SImode
4506       || !rtx_equal_p (lo_part, operands[1]))
4507     {
4508       if (src_mode == SImode)
4509         emit_move_insn (lo_part, operands[1]);
4510       else
4511         emit_insn (gen_rtx_SET (VOIDmode, lo_part,
4512                                 gen_rtx_SIGN_EXTEND (SImode, operands[1])));
4513       operands[1] = lo_part;
4514     }
4515   operands[0] = gen_highpart (SImode, operands[0]);
4518 (define_expand "zero_extendhisi2"
4519   [(set (match_operand:SI 0 "s_register_operand" "")
4520         (zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "")))]
4521   "TARGET_EITHER"
4523   if (TARGET_ARM && !arm_arch4 && MEM_P (operands[1]))
4524     {
4525       emit_insn (gen_movhi_bytes (operands[0], operands[1]));
4526       DONE;
4527     }
4528   if (!arm_arch6 && !MEM_P (operands[1]))
4529     {
4530       rtx t = gen_lowpart (SImode, operands[1]);
4531       rtx tmp = gen_reg_rtx (SImode);
4532       emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (16)));
4533       emit_insn (gen_lshrsi3 (operands[0], tmp, GEN_INT (16)));
4534       DONE;
4535     }
4538 (define_split
4539   [(set (match_operand:SI 0 "s_register_operand" "")
4540         (zero_extend:SI (match_operand:HI 1 "s_register_operand" "")))]
4541   "!TARGET_THUMB2 && !arm_arch6"
4542   [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 16)))
4543    (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 16)))]
4545   operands[2] = gen_lowpart (SImode, operands[1]);
4548 (define_insn "*thumb1_zero_extendhisi2"
4549   [(set (match_operand:SI 0 "register_operand" "=l,l")
4550         (zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "l,m")))]
4551   "TARGET_THUMB1"
4553   rtx mem;
4555   if (which_alternative == 0 && arm_arch6)
4556     return "uxth\t%0, %1";
4557   if (which_alternative == 0)
4558     return "#";
4560   mem = XEXP (operands[1], 0);
4562   if (GET_CODE (mem) == CONST)
4563     mem = XEXP (mem, 0);
4564     
4565   if (GET_CODE (mem) == PLUS)
4566     {
4567       rtx a = XEXP (mem, 0);
4569       /* This can happen due to bugs in reload.  */
4570       if (GET_CODE (a) == REG && REGNO (a) == SP_REGNUM)
4571         {
4572           rtx ops[2];
4573           ops[0] = operands[0];
4574           ops[1] = a;
4575       
4576           output_asm_insn ("mov\t%0, %1", ops);
4578           XEXP (mem, 0) = operands[0];
4579        }
4580     }
4581     
4582   return "ldrh\t%0, %1";
4584   [(set_attr_alternative "length"
4585                          [(if_then_else (eq_attr "is_arch6" "yes")
4586                                        (const_int 2) (const_int 4))
4587                          (const_int 4)])
4588    (set_attr "type" "alu_shift,load_byte")]
4591 (define_insn "*arm_zero_extendhisi2"
4592   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4593         (zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,m")))]
4594   "TARGET_ARM && arm_arch4 && !arm_arch6"
4595   "@
4596    #
4597    ldr%(h%)\\t%0, %1"
4598   [(set_attr "type" "alu_shift,load_byte")
4599    (set_attr "predicable" "yes")]
4602 (define_insn "*arm_zero_extendhisi2_v6"
4603   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4604         (zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,m")))]
4605   "TARGET_ARM && arm_arch6"
4606   "@
4607    uxth%?\\t%0, %1
4608    ldr%(h%)\\t%0, %1"
4609   [(set_attr "type" "alu_shift,load_byte")
4610    (set_attr "predicable" "yes")]
4613 (define_insn "*arm_zero_extendhisi2addsi"
4614   [(set (match_operand:SI 0 "s_register_operand" "=r")
4615         (plus:SI (zero_extend:SI (match_operand:HI 1 "s_register_operand" "r"))
4616                  (match_operand:SI 2 "s_register_operand" "r")))]
4617   "TARGET_INT_SIMD"
4618   "uxtah%?\\t%0, %2, %1"
4619   [(set_attr "type" "alu_shift")
4620    (set_attr "predicable" "yes")]
4623 (define_expand "zero_extendqisi2"
4624   [(set (match_operand:SI 0 "s_register_operand" "")
4625         (zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "")))]
4626   "TARGET_EITHER"
4628   if (TARGET_ARM && !arm_arch6 && GET_CODE (operands[1]) != MEM)
4629     {
4630       emit_insn (gen_andsi3 (operands[0],
4631                              gen_lowpart (SImode, operands[1]),
4632                                           GEN_INT (255)));
4633       DONE;
4634     }
4635   if (!arm_arch6 && !MEM_P (operands[1]))
4636     {
4637       rtx t = gen_lowpart (SImode, operands[1]);
4638       rtx tmp = gen_reg_rtx (SImode);
4639       emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (24)));
4640       emit_insn (gen_lshrsi3 (operands[0], tmp, GEN_INT (24)));
4641       DONE;
4642     }
4645 (define_split
4646   [(set (match_operand:SI 0 "s_register_operand" "")
4647         (zero_extend:SI (match_operand:QI 1 "s_register_operand" "")))]
4648   "!arm_arch6"
4649   [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 24)))
4650    (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 24)))]
4652   operands[2] = simplify_gen_subreg (SImode, operands[1], QImode, 0);
4653   if (TARGET_ARM)
4654     {
4655       emit_insn (gen_andsi3 (operands[0], operands[2], GEN_INT (255)));
4656       DONE;
4657     }
4660 (define_insn "*thumb1_zero_extendqisi2"
4661   [(set (match_operand:SI 0 "register_operand" "=l,l")
4662         (zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "l,m")))]
4663   "TARGET_THUMB1 && !arm_arch6"
4664   "@
4665    #
4666    ldrb\\t%0, %1"
4667   [(set_attr "length" "4,2")
4668    (set_attr "type" "alu_shift,load_byte")
4669    (set_attr "pool_range" "*,32")]
4672 (define_insn "*thumb1_zero_extendqisi2_v6"
4673   [(set (match_operand:SI 0 "register_operand" "=l,l")
4674         (zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "l,m")))]
4675   "TARGET_THUMB1 && arm_arch6"
4676   "@
4677    uxtb\\t%0, %1
4678    ldrb\\t%0, %1"
4679   [(set_attr "length" "2")
4680    (set_attr "type" "alu_shift,load_byte")]
4683 (define_insn "*arm_zero_extendqisi2"
4684   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4685         (zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "r,m")))]
4686   "TARGET_ARM && !arm_arch6"
4687   "@
4688    #
4689    ldr%(b%)\\t%0, %1\\t%@ zero_extendqisi2"
4690   [(set_attr "length" "8,4")
4691    (set_attr "type" "alu_shift,load_byte")
4692    (set_attr "predicable" "yes")]
4695 (define_insn "*arm_zero_extendqisi2_v6"
4696   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4697         (zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "r,m")))]
4698   "TARGET_ARM && arm_arch6"
4699   "@
4700    uxtb%(%)\\t%0, %1
4701    ldr%(b%)\\t%0, %1\\t%@ zero_extendqisi2"
4702   [(set_attr "type" "alu_shift,load_byte")
4703    (set_attr "predicable" "yes")]
4706 (define_insn "*arm_zero_extendqisi2addsi"
4707   [(set (match_operand:SI 0 "s_register_operand" "=r")
4708         (plus:SI (zero_extend:SI (match_operand:QI 1 "s_register_operand" "r"))
4709                  (match_operand:SI 2 "s_register_operand" "r")))]
4710   "TARGET_INT_SIMD"
4711   "uxtab%?\\t%0, %2, %1"
4712   [(set_attr "predicable" "yes")
4713    (set_attr "insn" "xtab")
4714    (set_attr "type" "alu_shift")]
4717 (define_split
4718   [(set (match_operand:SI 0 "s_register_operand" "")
4719         (zero_extend:SI (subreg:QI (match_operand:SI 1 "" "") 0)))
4720    (clobber (match_operand:SI 2 "s_register_operand" ""))]
4721   "TARGET_32BIT && (GET_CODE (operands[1]) != MEM) && ! BYTES_BIG_ENDIAN"
4722   [(set (match_dup 2) (match_dup 1))
4723    (set (match_dup 0) (and:SI (match_dup 2) (const_int 255)))]
4724   ""
4727 (define_split
4728   [(set (match_operand:SI 0 "s_register_operand" "")
4729         (zero_extend:SI (subreg:QI (match_operand:SI 1 "" "") 3)))
4730    (clobber (match_operand:SI 2 "s_register_operand" ""))]
4731   "TARGET_32BIT && (GET_CODE (operands[1]) != MEM) && BYTES_BIG_ENDIAN"
4732   [(set (match_dup 2) (match_dup 1))
4733    (set (match_dup 0) (and:SI (match_dup 2) (const_int 255)))]
4734   ""
4738 (define_split
4739   [(set (match_operand:SI 0 "s_register_operand" "")
4740         (ior_xor:SI (and:SI (ashift:SI
4741                              (match_operand:SI 1 "s_register_operand" "")
4742                              (match_operand:SI 2 "const_int_operand" ""))
4743                             (match_operand:SI 3 "const_int_operand" ""))
4744                     (zero_extend:SI
4745                      (match_operator 5 "subreg_lowpart_operator"
4746                       [(match_operand:SI 4 "s_register_operand" "")]))))]
4747   "TARGET_32BIT
4748    && ((unsigned HOST_WIDE_INT) INTVAL (operands[3])
4749        == (GET_MODE_MASK (GET_MODE (operands[5]))
4750            & (GET_MODE_MASK (GET_MODE (operands[5]))
4751               << (INTVAL (operands[2])))))"
4752   [(set (match_dup 0) (ior_xor:SI (ashift:SI (match_dup 1) (match_dup 2))
4753                                   (match_dup 4)))
4754    (set (match_dup 0) (zero_extend:SI (match_dup 5)))]
4755   "operands[5] = gen_lowpart (GET_MODE (operands[5]), operands[0]);"
4758 (define_insn "*compareqi_eq0"
4759   [(set (reg:CC_Z CC_REGNUM)
4760         (compare:CC_Z (match_operand:QI 0 "s_register_operand" "r")
4761                          (const_int 0)))]
4762   "TARGET_32BIT"
4763   "tst%?\\t%0, #255"
4764   [(set_attr "conds" "set")
4765    (set_attr "predicable" "yes")]
4768 (define_expand "extendhisi2"
4769   [(set (match_operand:SI 0 "s_register_operand" "")
4770         (sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "")))]
4771   "TARGET_EITHER"
4773   if (TARGET_THUMB1)
4774     {
4775       emit_insn (gen_thumb1_extendhisi2 (operands[0], operands[1]));
4776       DONE;
4777     }
4778   if (MEM_P (operands[1]) && TARGET_ARM && !arm_arch4)
4779     {
4780       emit_insn (gen_extendhisi2_mem (operands[0], operands[1]));
4781       DONE;
4782     }
4784   if (!arm_arch6 && !MEM_P (operands[1]))
4785     {
4786       rtx t = gen_lowpart (SImode, operands[1]);
4787       rtx tmp = gen_reg_rtx (SImode);
4788       emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (16)));
4789       emit_insn (gen_ashrsi3 (operands[0], tmp, GEN_INT (16)));
4790       DONE;
4791     }
4794 (define_split
4795   [(parallel
4796     [(set (match_operand:SI 0 "register_operand" "")
4797           (sign_extend:SI (match_operand:HI 1 "register_operand" "")))
4798      (clobber (match_scratch:SI 2 ""))])]
4799   "!arm_arch6"
4800   [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 16)))
4801    (set (match_dup 0) (ashiftrt:SI (match_dup 0) (const_int 16)))]
4803   operands[2] = simplify_gen_subreg (SImode, operands[1], HImode, 0);
4806 ;; We used to have an early-clobber on the scratch register here.
4807 ;; However, there's a bug somewhere in reload which means that this
4808 ;; can be partially ignored during spill allocation if the memory
4809 ;; address also needs reloading; this causes us to die later on when
4810 ;; we try to verify the operands.  Fortunately, we don't really need
4811 ;; the early-clobber: we can always use operand 0 if operand 2
4812 ;; overlaps the address.
4813 (define_insn "thumb1_extendhisi2"
4814   [(set (match_operand:SI 0 "register_operand" "=l,l")
4815         (sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "l,m")))
4816    (clobber (match_scratch:SI 2 "=X,l"))]
4817   "TARGET_THUMB1"
4818   "*
4819   {
4820     rtx ops[4];
4821     rtx mem;
4823     if (which_alternative == 0 && !arm_arch6)
4824       return \"#\";
4825     if (which_alternative == 0)
4826       return \"sxth\\t%0, %1\";
4828     mem = XEXP (operands[1], 0);
4830     /* This code used to try to use 'V', and fix the address only if it was
4831        offsettable, but this fails for e.g. REG+48 because 48 is outside the
4832        range of QImode offsets, and offsettable_address_p does a QImode
4833        address check.  */
4834        
4835     if (GET_CODE (mem) == CONST)
4836       mem = XEXP (mem, 0);
4837     
4838     if (GET_CODE (mem) == LABEL_REF)
4839       return \"ldr\\t%0, %1\";
4840     
4841     if (GET_CODE (mem) == PLUS)
4842       {
4843         rtx a = XEXP (mem, 0);
4844         rtx b = XEXP (mem, 1);
4846         if (GET_CODE (a) == LABEL_REF
4847             && GET_CODE (b) == CONST_INT)
4848           return \"ldr\\t%0, %1\";
4850         if (GET_CODE (b) == REG)
4851           return \"ldrsh\\t%0, %1\";
4852           
4853         ops[1] = a;
4854         ops[2] = b;
4855       }
4856     else
4857       {
4858         ops[1] = mem;
4859         ops[2] = const0_rtx;
4860       }
4861       
4862     gcc_assert (GET_CODE (ops[1]) == REG);
4864     ops[0] = operands[0];
4865     if (reg_mentioned_p (operands[2], ops[1]))
4866       ops[3] = ops[0];
4867     else
4868       ops[3] = operands[2];
4869     output_asm_insn (\"mov\\t%3, %2\;ldrsh\\t%0, [%1, %3]\", ops);
4870     return \"\";
4871   }"
4872   [(set_attr_alternative "length"
4873                          [(if_then_else (eq_attr "is_arch6" "yes")
4874                                         (const_int 2) (const_int 4))
4875                           (const_int 4)])
4876    (set_attr "type" "alu_shift,load_byte")
4877    (set_attr "pool_range" "*,1020")]
4880 ;; This pattern will only be used when ldsh is not available
4881 (define_expand "extendhisi2_mem"
4882   [(set (match_dup 2) (zero_extend:SI (match_operand:HI 1 "" "")))
4883    (set (match_dup 3)
4884         (zero_extend:SI (match_dup 7)))
4885    (set (match_dup 6) (ashift:SI (match_dup 4) (const_int 24)))
4886    (set (match_operand:SI 0 "" "")
4887         (ior:SI (ashiftrt:SI (match_dup 6) (const_int 16)) (match_dup 5)))]
4888   "TARGET_ARM"
4889   "
4890   {
4891     rtx mem1, mem2;
4892     rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
4894     mem1 = change_address (operands[1], QImode, addr);
4895     mem2 = change_address (operands[1], QImode,
4896                            plus_constant (Pmode, addr, 1));
4897     operands[0] = gen_lowpart (SImode, operands[0]);
4898     operands[1] = mem1;
4899     operands[2] = gen_reg_rtx (SImode);
4900     operands[3] = gen_reg_rtx (SImode);
4901     operands[6] = gen_reg_rtx (SImode);
4902     operands[7] = mem2;
4904     if (BYTES_BIG_ENDIAN)
4905       {
4906         operands[4] = operands[2];
4907         operands[5] = operands[3];
4908       }
4909     else
4910       {
4911         operands[4] = operands[3];
4912         operands[5] = operands[2];
4913       }
4914   }"
4917 (define_split
4918   [(set (match_operand:SI 0 "register_operand" "")
4919         (sign_extend:SI (match_operand:HI 1 "register_operand" "")))]
4920   "!arm_arch6"
4921   [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 16)))
4922    (set (match_dup 0) (ashiftrt:SI (match_dup 0) (const_int 16)))]
4924   operands[2] = simplify_gen_subreg (SImode, operands[1], HImode, 0);
4927 (define_insn "*arm_extendhisi2"
4928   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4929         (sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,m")))]
4930   "TARGET_ARM && arm_arch4 && !arm_arch6"
4931   "@
4932    #
4933    ldr%(sh%)\\t%0, %1"
4934   [(set_attr "length" "8,4")
4935    (set_attr "type" "alu_shift,load_byte")
4936    (set_attr "predicable" "yes")
4937    (set_attr "pool_range" "*,256")
4938    (set_attr "neg_pool_range" "*,244")]
4941 ;; ??? Check Thumb-2 pool range
4942 (define_insn "*arm_extendhisi2_v6"
4943   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
4944         (sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,m")))]
4945   "TARGET_32BIT && arm_arch6"
4946   "@
4947    sxth%?\\t%0, %1
4948    ldr%(sh%)\\t%0, %1"
4949   [(set_attr "type" "alu_shift,load_byte")
4950    (set_attr "predicable" "yes")
4951    (set_attr "pool_range" "*,256")
4952    (set_attr "neg_pool_range" "*,244")]
4955 (define_insn "*arm_extendhisi2addsi"
4956   [(set (match_operand:SI 0 "s_register_operand" "=r")
4957         (plus:SI (sign_extend:SI (match_operand:HI 1 "s_register_operand" "r"))
4958                  (match_operand:SI 2 "s_register_operand" "r")))]
4959   "TARGET_INT_SIMD"
4960   "sxtah%?\\t%0, %2, %1"
4963 (define_expand "extendqihi2"
4964   [(set (match_dup 2)
4965         (ashift:SI (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op" "")
4966                    (const_int 24)))
4967    (set (match_operand:HI 0 "s_register_operand" "")
4968         (ashiftrt:SI (match_dup 2)
4969                      (const_int 24)))]
4970   "TARGET_ARM"
4971   "
4972   {
4973     if (arm_arch4 && GET_CODE (operands[1]) == MEM)
4974       {
4975         emit_insn (gen_rtx_SET (VOIDmode,
4976                                 operands[0],
4977                                 gen_rtx_SIGN_EXTEND (HImode, operands[1])));
4978         DONE;
4979       }
4980     if (!s_register_operand (operands[1], QImode))
4981       operands[1] = copy_to_mode_reg (QImode, operands[1]);
4982     operands[0] = gen_lowpart (SImode, operands[0]);
4983     operands[1] = gen_lowpart (SImode, operands[1]);
4984     operands[2] = gen_reg_rtx (SImode);
4985   }"
4988 (define_insn "*arm_extendqihi_insn"
4989   [(set (match_operand:HI 0 "s_register_operand" "=r")
4990         (sign_extend:HI (match_operand:QI 1 "arm_extendqisi_mem_op" "Uq")))]
4991   "TARGET_ARM && arm_arch4"
4992   "ldr%(sb%)\\t%0, %1"
4993   [(set_attr "type" "load_byte")
4994    (set_attr "predicable" "yes")
4995    (set_attr "pool_range" "256")
4996    (set_attr "neg_pool_range" "244")]
4999 (define_expand "extendqisi2"
5000   [(set (match_operand:SI 0 "s_register_operand" "")
5001         (sign_extend:SI (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op" "")))]
5002   "TARGET_EITHER"
5004   if (!arm_arch4 && MEM_P (operands[1]))
5005     operands[1] = copy_to_mode_reg (QImode, operands[1]);
5007   if (!arm_arch6 && !MEM_P (operands[1]))
5008     {
5009       rtx t = gen_lowpart (SImode, operands[1]);
5010       rtx tmp = gen_reg_rtx (SImode);
5011       emit_insn (gen_ashlsi3 (tmp, t, GEN_INT (24)));
5012       emit_insn (gen_ashrsi3 (operands[0], tmp, GEN_INT (24)));
5013       DONE;
5014     }
5017 (define_split
5018   [(set (match_operand:SI 0 "register_operand" "")
5019         (sign_extend:SI (match_operand:QI 1 "register_operand" "")))]
5020   "!arm_arch6"
5021   [(set (match_dup 0) (ashift:SI (match_dup 2) (const_int 24)))
5022    (set (match_dup 0) (ashiftrt:SI (match_dup 0) (const_int 24)))]
5024   operands[2] = simplify_gen_subreg (SImode, operands[1], QImode, 0);
5027 (define_insn "*arm_extendqisi"
5028   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5029         (sign_extend:SI (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op" "r,Uq")))]
5030   "TARGET_ARM && arm_arch4 && !arm_arch6"
5031   "@
5032    #
5033    ldr%(sb%)\\t%0, %1"
5034   [(set_attr "length" "8,4")
5035    (set_attr "type" "alu_shift,load_byte")
5036    (set_attr "predicable" "yes")
5037    (set_attr "pool_range" "*,256")
5038    (set_attr "neg_pool_range" "*,244")]
5041 (define_insn "*arm_extendqisi_v6"
5042   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
5043         (sign_extend:SI
5044          (match_operand:QI 1 "arm_reg_or_extendqisi_mem_op" "r,Uq")))]
5045   "TARGET_ARM && arm_arch6"
5046   "@
5047    sxtb%?\\t%0, %1
5048    ldr%(sb%)\\t%0, %1"
5049   [(set_attr "type" "alu_shift,load_byte")
5050    (set_attr "predicable" "yes")
5051    (set_attr "pool_range" "*,256")
5052    (set_attr "neg_pool_range" "*,244")]
5055 (define_insn "*arm_extendqisi2addsi"
5056   [(set (match_operand:SI 0 "s_register_operand" "=r")
5057         (plus:SI (sign_extend:SI (match_operand:QI 1 "s_register_operand" "r"))
5058                  (match_operand:SI 2 "s_register_operand" "r")))]
5059   "TARGET_INT_SIMD"
5060   "sxtab%?\\t%0, %2, %1"
5061   [(set_attr "type" "alu_shift")
5062    (set_attr "insn" "xtab")
5063    (set_attr "predicable" "yes")]
5066 (define_split
5067   [(set (match_operand:SI 0 "register_operand" "")
5068         (sign_extend:SI (match_operand:QI 1 "memory_operand" "")))]
5069   "TARGET_THUMB1 && reload_completed"
5070   [(set (match_dup 0) (match_dup 2))
5071    (set (match_dup 0) (sign_extend:SI (match_dup 3)))]
5073   rtx addr = XEXP (operands[1], 0);
5075   if (GET_CODE (addr) == CONST)
5076     addr = XEXP (addr, 0);
5078   if (GET_CODE (addr) == PLUS
5079       && REG_P (XEXP (addr, 0)) && REG_P (XEXP (addr, 1)))
5080     /* No split necessary.  */
5081     FAIL;
5083   if (GET_CODE (addr) == PLUS
5084       && !REG_P (XEXP (addr, 0)) && !REG_P (XEXP (addr, 1)))
5085     FAIL;
5087   if (reg_overlap_mentioned_p (operands[0], addr))
5088     {
5089       rtx t = gen_lowpart (QImode, operands[0]);
5090       emit_move_insn (t, operands[1]);
5091       emit_insn (gen_thumb1_extendqisi2 (operands[0], t));
5092       DONE;
5093     }
5095   if (REG_P (addr))
5096     {
5097       addr = gen_rtx_PLUS (Pmode, addr, operands[0]);
5098       operands[2] = const0_rtx;
5099     }
5100   else if (GET_CODE (addr) != PLUS)
5101     FAIL;
5102   else if (REG_P (XEXP (addr, 0)))
5103     {
5104       operands[2] = XEXP (addr, 1);
5105       addr = gen_rtx_PLUS (Pmode, XEXP (addr, 0), operands[0]);
5106     }
5107   else
5108     {
5109       operands[2] = XEXP (addr, 0);
5110       addr = gen_rtx_PLUS (Pmode, XEXP (addr, 1), operands[0]);
5111     }
5113   operands[3] = change_address (operands[1], QImode, addr);
5116 (define_peephole2
5117   [(set (match_operand:SI 0 "register_operand" "")
5118         (plus:SI (match_dup 0) (match_operand 1 "const_int_operand")))
5119    (set (match_operand:SI 2 "register_operand" "") (const_int 0))
5120    (set (match_operand:SI 3 "register_operand" "")
5121         (sign_extend:SI (match_operand:QI 4 "memory_operand" "")))]
5122   "TARGET_THUMB1
5123    && GET_CODE (XEXP (operands[4], 0)) == PLUS
5124    && rtx_equal_p (operands[0], XEXP (XEXP (operands[4], 0), 0))
5125    && rtx_equal_p (operands[2], XEXP (XEXP (operands[4], 0), 1))
5126    && (peep2_reg_dead_p (3, operands[0])
5127        || rtx_equal_p (operands[0], operands[3]))
5128    && (peep2_reg_dead_p (3, operands[2])
5129        || rtx_equal_p (operands[2], operands[3]))"
5130   [(set (match_dup 2) (match_dup 1))
5131    (set (match_dup 3) (sign_extend:SI (match_dup 4)))]
5133   rtx addr = gen_rtx_PLUS (Pmode, operands[0], operands[2]);
5134   operands[4] = change_address (operands[4], QImode, addr);
5137 (define_insn "thumb1_extendqisi2"
5138   [(set (match_operand:SI 0 "register_operand" "=l,l,l")
5139         (sign_extend:SI (match_operand:QI 1 "nonimmediate_operand" "l,V,m")))]
5140   "TARGET_THUMB1"
5142   rtx addr;
5144   if (which_alternative == 0 && arm_arch6)
5145     return "sxtb\\t%0, %1";
5146   if (which_alternative == 0)
5147     return "#";
5149   addr = XEXP (operands[1], 0);
5150   if (GET_CODE (addr) == PLUS
5151       && REG_P (XEXP (addr, 0)) && REG_P (XEXP (addr, 1)))
5152     return "ldrsb\\t%0, %1";
5153       
5154   return "#";
5156   [(set_attr_alternative "length"
5157                          [(if_then_else (eq_attr "is_arch6" "yes")
5158                                         (const_int 2) (const_int 4))
5159                           (const_int 2)
5160                           (if_then_else (eq_attr "is_arch6" "yes")
5161                                         (const_int 4) (const_int 6))])
5162    (set_attr "type" "alu_shift,load_byte,load_byte")]
5165 (define_expand "extendsfdf2"
5166   [(set (match_operand:DF                  0 "s_register_operand" "")
5167         (float_extend:DF (match_operand:SF 1 "s_register_operand"  "")))]
5168   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
5169   ""
5172 /* HFmode -> DFmode conversions have to go through SFmode.  */
5173 (define_expand "extendhfdf2"
5174   [(set (match_operand:DF                  0 "general_operand" "")
5175         (float_extend:DF (match_operand:HF 1 "general_operand"  "")))]
5176   "TARGET_EITHER"
5177   "
5178   {
5179     rtx op1;
5180     op1 = convert_to_mode (SFmode, operands[1], 0);
5181     op1 = convert_to_mode (DFmode, op1, 0);
5182     emit_insn (gen_movdf (operands[0], op1));
5183     DONE;
5184   }"
5187 ;; Move insns (including loads and stores)
5189 ;; XXX Just some ideas about movti.
5190 ;; I don't think these are a good idea on the arm, there just aren't enough
5191 ;; registers
5192 ;;(define_expand "loadti"
5193 ;;  [(set (match_operand:TI 0 "s_register_operand" "")
5194 ;;      (mem:TI (match_operand:SI 1 "address_operand" "")))]
5195 ;;  "" "")
5197 ;;(define_expand "storeti"
5198 ;;  [(set (mem:TI (match_operand:TI 0 "address_operand" ""))
5199 ;;      (match_operand:TI 1 "s_register_operand" ""))]
5200 ;;  "" "")
5202 ;;(define_expand "movti"
5203 ;;  [(set (match_operand:TI 0 "general_operand" "")
5204 ;;      (match_operand:TI 1 "general_operand" ""))]
5205 ;;  ""
5206 ;;  "
5208 ;;  rtx insn;
5210 ;;  if (GET_CODE (operands[0]) == MEM && GET_CODE (operands[1]) == MEM)
5211 ;;    operands[1] = copy_to_reg (operands[1]);
5212 ;;  if (GET_CODE (operands[0]) == MEM)
5213 ;;    insn = gen_storeti (XEXP (operands[0], 0), operands[1]);
5214 ;;  else if (GET_CODE (operands[1]) == MEM)
5215 ;;    insn = gen_loadti (operands[0], XEXP (operands[1], 0));
5216 ;;  else
5217 ;;    FAIL;
5219 ;;  emit_insn (insn);
5220 ;;  DONE;
5221 ;;}")
5223 ;; Recognize garbage generated above.
5225 ;;(define_insn ""
5226 ;;  [(set (match_operand:TI 0 "general_operand" "=r,r,r,<,>,m")
5227 ;;      (match_operand:TI 1 "general_operand" "<,>,m,r,r,r"))]
5228 ;;  ""
5229 ;;  "*
5230 ;;  {
5231 ;;    register mem = (which_alternative < 3);
5232 ;;    register const char *template;
5234 ;;    operands[mem] = XEXP (operands[mem], 0);
5235 ;;    switch (which_alternative)
5236 ;;      {
5237 ;;      case 0: template = \"ldmdb\\t%1!, %M0\"; break;
5238 ;;      case 1: template = \"ldmia\\t%1!, %M0\"; break;
5239 ;;      case 2: template = \"ldmia\\t%1, %M0\"; break;
5240 ;;      case 3: template = \"stmdb\\t%0!, %M1\"; break;
5241 ;;      case 4: template = \"stmia\\t%0!, %M1\"; break;
5242 ;;      case 5: template = \"stmia\\t%0, %M1\"; break;
5243 ;;      }
5244 ;;    output_asm_insn (template, operands);
5245 ;;    return \"\";
5246 ;;  }")
5248 (define_expand "movdi"
5249   [(set (match_operand:DI 0 "general_operand" "")
5250         (match_operand:DI 1 "general_operand" ""))]
5251   "TARGET_EITHER"
5252   "
5253   if (can_create_pseudo_p ())
5254     {
5255       if (GET_CODE (operands[0]) != REG)
5256         operands[1] = force_reg (DImode, operands[1]);
5257     }
5258   "
5261 (define_insn "*arm_movdi"
5262   [(set (match_operand:DI 0 "nonimmediate_di_operand" "=r, r, r, r, m")
5263         (match_operand:DI 1 "di_operand"              "rDa,Db,Dc,mi,r"))]
5264   "TARGET_32BIT
5265    && !(TARGET_HARD_FLOAT && TARGET_VFP)
5266    && !TARGET_IWMMXT
5267    && (   register_operand (operands[0], DImode)
5268        || register_operand (operands[1], DImode))"
5269   "*
5270   switch (which_alternative)
5271     {
5272     case 0:
5273     case 1:
5274     case 2:
5275       return \"#\";
5276     default:
5277       return output_move_double (operands, true, NULL);
5278     }
5279   "
5280   [(set_attr "length" "8,12,16,8,8")
5281    (set_attr "type" "*,*,*,load2,store2")
5282    (set_attr "arm_pool_range" "*,*,*,1020,*")
5283    (set_attr "arm_neg_pool_range" "*,*,*,1004,*")
5284    (set_attr "thumb2_pool_range" "*,*,*,4096,*")
5285    (set_attr "thumb2_neg_pool_range" "*,*,*,0,*")]
5288 (define_split
5289   [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
5290         (match_operand:ANY64 1 "const_double_operand" ""))]
5291   "TARGET_32BIT
5292    && reload_completed
5293    && (arm_const_double_inline_cost (operands[1])
5294        <= ((optimize_size || arm_ld_sched) ? 3 : 4))"
5295   [(const_int 0)]
5296   "
5297   arm_split_constant (SET, SImode, curr_insn,
5298                       INTVAL (gen_lowpart (SImode, operands[1])),
5299                       gen_lowpart (SImode, operands[0]), NULL_RTX, 0);
5300   arm_split_constant (SET, SImode, curr_insn,
5301                       INTVAL (gen_highpart_mode (SImode,
5302                                                  GET_MODE (operands[0]),
5303                                                  operands[1])),
5304                       gen_highpart (SImode, operands[0]), NULL_RTX, 0);
5305   DONE;
5306   "
5309 ; If optimizing for size, or if we have load delay slots, then 
5310 ; we want to split the constant into two separate operations. 
5311 ; In both cases this may split a trivial part into a single data op
5312 ; leaving a single complex constant to load.  We can also get longer
5313 ; offsets in a LDR which means we get better chances of sharing the pool
5314 ; entries.  Finally, we can normally do a better job of scheduling
5315 ; LDR instructions than we can with LDM.
5316 ; This pattern will only match if the one above did not.
5317 (define_split
5318   [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
5319         (match_operand:ANY64 1 "const_double_operand" ""))]
5320   "TARGET_ARM && reload_completed
5321    && arm_const_double_by_parts (operands[1])"
5322   [(set (match_dup 0) (match_dup 1))
5323    (set (match_dup 2) (match_dup 3))]
5324   "
5325   operands[2] = gen_highpart (SImode, operands[0]);
5326   operands[3] = gen_highpart_mode (SImode, GET_MODE (operands[0]),
5327                                    operands[1]);
5328   operands[0] = gen_lowpart (SImode, operands[0]);
5329   operands[1] = gen_lowpart (SImode, operands[1]);
5330   "
5333 (define_split
5334   [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
5335         (match_operand:ANY64 1 "arm_general_register_operand" ""))]
5336   "TARGET_EITHER && reload_completed"
5337   [(set (match_dup 0) (match_dup 1))
5338    (set (match_dup 2) (match_dup 3))]
5339   "
5340   operands[2] = gen_highpart (SImode, operands[0]);
5341   operands[3] = gen_highpart (SImode, operands[1]);
5342   operands[0] = gen_lowpart (SImode, operands[0]);
5343   operands[1] = gen_lowpart (SImode, operands[1]);
5345   /* Handle a partial overlap.  */
5346   if (rtx_equal_p (operands[0], operands[3]))
5347     {
5348       rtx tmp0 = operands[0];
5349       rtx tmp1 = operands[1];
5351       operands[0] = operands[2];
5352       operands[1] = operands[3];
5353       operands[2] = tmp0;
5354       operands[3] = tmp1;
5355     }
5356   "
5359 ;; We can't actually do base+index doubleword loads if the index and
5360 ;; destination overlap.  Split here so that we at least have chance to
5361 ;; schedule.
5362 (define_split
5363   [(set (match_operand:DI 0 "s_register_operand" "")
5364         (mem:DI (plus:SI (match_operand:SI 1 "s_register_operand" "")
5365                          (match_operand:SI 2 "s_register_operand" ""))))]
5366   "TARGET_LDRD
5367   && reg_overlap_mentioned_p (operands[0], operands[1])
5368   && reg_overlap_mentioned_p (operands[0], operands[2])"
5369   [(set (match_dup 4)
5370         (plus:SI (match_dup 1)
5371                  (match_dup 2)))
5372    (set (match_dup 0)
5373         (mem:DI (match_dup 4)))]
5374   "
5375   operands[4] = gen_rtx_REG (SImode, REGNO(operands[0]));
5376   "
5379 ;;; ??? This should have alternatives for constants.
5380 ;;; ??? This was originally identical to the movdf_insn pattern.
5381 ;;; ??? The 'i' constraint looks funny, but it should always be replaced by
5382 ;;; thumb_reorg with a memory reference.
5383 (define_insn "*thumb1_movdi_insn"
5384   [(set (match_operand:DI 0 "nonimmediate_operand" "=l,l,l,l,>,l, m,*r")
5385         (match_operand:DI 1 "general_operand"      "l, I,J,>,l,mi,l,*r"))]
5386   "TARGET_THUMB1
5387    && (   register_operand (operands[0], DImode)
5388        || register_operand (operands[1], DImode))"
5389   "*
5390   {
5391   switch (which_alternative)
5392     {
5393     default:
5394     case 0:
5395       if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
5396         return \"add\\t%0,  %1,  #0\;add\\t%H0, %H1, #0\";
5397       return   \"add\\t%H0, %H1, #0\;add\\t%0,  %1,  #0\";
5398     case 1:
5399       return \"mov\\t%Q0, %1\;mov\\t%R0, #0\";
5400     case 2:
5401       operands[1] = GEN_INT (- INTVAL (operands[1]));
5402       return \"mov\\t%Q0, %1\;neg\\t%Q0, %Q0\;asr\\t%R0, %Q0, #31\";
5403     case 3:
5404       return \"ldmia\\t%1, {%0, %H0}\";
5405     case 4:
5406       return \"stmia\\t%0, {%1, %H1}\";
5407     case 5:
5408       return thumb_load_double_from_address (operands);
5409     case 6:
5410       operands[2] = gen_rtx_MEM (SImode,
5411                              plus_constant (Pmode, XEXP (operands[0], 0), 4));
5412       output_asm_insn (\"str\\t%1, %0\;str\\t%H1, %2\", operands);
5413       return \"\";
5414     case 7:
5415       if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
5416         return \"mov\\t%0, %1\;mov\\t%H0, %H1\";
5417       return \"mov\\t%H0, %H1\;mov\\t%0, %1\";
5418     }
5419   }"
5420   [(set_attr "length" "4,4,6,2,2,6,4,4")
5421    (set_attr "type" "*,*,*,load2,store2,load2,store2,*")
5422    (set_attr "insn" "*,mov,*,*,*,*,*,mov")
5423    (set_attr "pool_range" "*,*,*,*,*,1020,*,*")]
5426 (define_expand "movsi"
5427   [(set (match_operand:SI 0 "general_operand" "")
5428         (match_operand:SI 1 "general_operand" ""))]
5429   "TARGET_EITHER"
5430   "
5431   {
5432   rtx base, offset, tmp;
5434   if (TARGET_32BIT)
5435     {
5436       /* Everything except mem = const or mem = mem can be done easily.  */
5437       if (GET_CODE (operands[0]) == MEM)
5438         operands[1] = force_reg (SImode, operands[1]);
5439       if (arm_general_register_operand (operands[0], SImode)
5440           && GET_CODE (operands[1]) == CONST_INT
5441           && !(const_ok_for_arm (INTVAL (operands[1]))
5442                || const_ok_for_arm (~INTVAL (operands[1]))))
5443         {
5444            arm_split_constant (SET, SImode, NULL_RTX,
5445                                INTVAL (operands[1]), operands[0], NULL_RTX,
5446                                optimize && can_create_pseudo_p ());
5447           DONE;
5448         }
5450       if (TARGET_USE_MOVT && !target_word_relocations
5451           && GET_CODE (operands[1]) == SYMBOL_REF
5452           && !flag_pic && !arm_tls_referenced_p (operands[1]))
5453         {
5454           arm_emit_movpair (operands[0], operands[1]);
5455           DONE;
5456         }
5457     }
5458   else /* TARGET_THUMB1...  */
5459     {
5460       if (can_create_pseudo_p ())
5461         {
5462           if (GET_CODE (operands[0]) != REG)
5463             operands[1] = force_reg (SImode, operands[1]);
5464         }
5465     }
5467   if (ARM_OFFSETS_MUST_BE_WITHIN_SECTIONS_P)
5468     {
5469       split_const (operands[1], &base, &offset);
5470       if (GET_CODE (base) == SYMBOL_REF
5471           && !offset_within_block_p (base, INTVAL (offset)))
5472         {
5473           tmp = can_create_pseudo_p () ? gen_reg_rtx (SImode) : operands[0];
5474           emit_move_insn (tmp, base);
5475           emit_insn (gen_addsi3 (operands[0], tmp, offset));
5476           DONE;
5477         }
5478     }
5480   /* Recognize the case where operand[1] is a reference to thread-local
5481      data and load its address to a register.  */
5482   if (arm_tls_referenced_p (operands[1]))
5483     {
5484       rtx tmp = operands[1];
5485       rtx addend = NULL;
5487       if (GET_CODE (tmp) == CONST && GET_CODE (XEXP (tmp, 0)) == PLUS)
5488         {
5489           addend = XEXP (XEXP (tmp, 0), 1);
5490           tmp = XEXP (XEXP (tmp, 0), 0);
5491         }
5493       gcc_assert (GET_CODE (tmp) == SYMBOL_REF);
5494       gcc_assert (SYMBOL_REF_TLS_MODEL (tmp) != 0);
5496       tmp = legitimize_tls_address (tmp,
5497                                     !can_create_pseudo_p () ? operands[0] : 0);
5498       if (addend)
5499         {
5500           tmp = gen_rtx_PLUS (SImode, tmp, addend);
5501           tmp = force_operand (tmp, operands[0]);
5502         }
5503       operands[1] = tmp;
5504     }
5505   else if (flag_pic
5506            && (CONSTANT_P (operands[1])
5507                || symbol_mentioned_p (operands[1])
5508                || label_mentioned_p (operands[1])))
5509       operands[1] = legitimize_pic_address (operands[1], SImode,
5510                                             (!can_create_pseudo_p ()
5511                                              ? operands[0]
5512                                              : 0));
5513   }
5514   "
5517 ;; The ARM LO_SUM and HIGH are backwards - HIGH sets the low bits, and
5518 ;; LO_SUM adds in the high bits.  Fortunately these are opaque operations
5519 ;; so this does not matter.
5520 (define_insn "*arm_movt"
5521   [(set (match_operand:SI 0 "nonimmediate_operand" "=r")
5522         (lo_sum:SI (match_operand:SI 1 "nonimmediate_operand" "0")
5523                    (match_operand:SI 2 "general_operand"      "i")))]
5524   "arm_arch_thumb2"
5525   "movt%?\t%0, #:upper16:%c2"
5526   [(set_attr "predicable" "yes")
5527    (set_attr "length" "4")]
5530 (define_insn "*arm_movsi_insn"
5531   [(set (match_operand:SI 0 "nonimmediate_operand" "=rk,r,r,r,rk,m")
5532         (match_operand:SI 1 "general_operand"      "rk, I,K,j,mi,rk"))]
5533   "TARGET_ARM && ! TARGET_IWMMXT
5534    && !(TARGET_HARD_FLOAT && TARGET_VFP)
5535    && (   register_operand (operands[0], SImode)
5536        || register_operand (operands[1], SImode))"
5537   "@
5538    mov%?\\t%0, %1
5539    mov%?\\t%0, %1
5540    mvn%?\\t%0, #%B1
5541    movw%?\\t%0, %1
5542    ldr%?\\t%0, %1
5543    str%?\\t%1, %0"
5544   [(set_attr "type" "*,*,*,*,load1,store1")
5545    (set_attr "insn" "mov,mov,mvn,mov,*,*")
5546    (set_attr "predicable" "yes")
5547    (set_attr "pool_range" "*,*,*,*,4096,*")
5548    (set_attr "neg_pool_range" "*,*,*,*,4084,*")]
5551 (define_split
5552   [(set (match_operand:SI 0 "arm_general_register_operand" "")
5553         (match_operand:SI 1 "const_int_operand" ""))]
5554   "TARGET_32BIT
5555   && (!(const_ok_for_arm (INTVAL (operands[1]))
5556         || const_ok_for_arm (~INTVAL (operands[1]))))"
5557   [(clobber (const_int 0))]
5558   "
5559   arm_split_constant (SET, SImode, NULL_RTX, 
5560                       INTVAL (operands[1]), operands[0], NULL_RTX, 0);
5561   DONE;
5562   "
5565 (define_insn "*thumb1_movsi_insn"
5566   [(set (match_operand:SI 0 "nonimmediate_operand" "=l,l,l,l,l,>,l, m,*l*h*k")
5567         (match_operand:SI 1 "general_operand"      "l, I,J,K,>,l,mi,l,*l*h*k"))]
5568   "TARGET_THUMB1
5569    && (   register_operand (operands[0], SImode) 
5570        || register_operand (operands[1], SImode))"
5571   "@
5572    mov  %0, %1
5573    mov  %0, %1
5574    #
5575    #
5576    ldmia\\t%1, {%0}
5577    stmia\\t%0, {%1}
5578    ldr\\t%0, %1
5579    str\\t%1, %0
5580    mov\\t%0, %1"
5581   [(set_attr "length" "2,2,4,4,2,2,2,2,2")
5582    (set_attr "type" "*,*,*,*,load1,store1,load1,store1,*")
5583    (set_attr "pool_range" "*,*,*,*,*,*,1020,*,*")
5584    (set_attr "conds" "set,clob,*,*,nocond,nocond,nocond,nocond,nocond")])
5586 (define_split 
5587   [(set (match_operand:SI 0 "register_operand" "")
5588         (match_operand:SI 1 "const_int_operand" ""))]
5589   "TARGET_THUMB1 && satisfies_constraint_J (operands[1])"
5590   [(set (match_dup 2) (match_dup 1))
5591    (set (match_dup 0) (neg:SI (match_dup 2)))]
5592   "
5593   {
5594     operands[1] = GEN_INT (- INTVAL (operands[1]));
5595     operands[2] = can_create_pseudo_p () ? gen_reg_rtx (SImode) : operands[0];
5596   }"
5599 (define_split 
5600   [(set (match_operand:SI 0 "register_operand" "")
5601         (match_operand:SI 1 "const_int_operand" ""))]
5602   "TARGET_THUMB1 && satisfies_constraint_K (operands[1])"
5603   [(set (match_dup 2) (match_dup 1))
5604    (set (match_dup 0) (ashift:SI (match_dup 2) (match_dup 3)))]
5605   "
5606   {
5607     unsigned HOST_WIDE_INT val = INTVAL (operands[1]) & 0xffffffffu;
5608     unsigned HOST_WIDE_INT mask = 0xff;
5609     int i;
5610     
5611     for (i = 0; i < 25; i++)
5612       if ((val & (mask << i)) == val)
5613         break;
5615     /* Don't split if the shift is zero.  */
5616     if (i == 0)
5617       FAIL;
5619     operands[1] = GEN_INT (val >> i);
5620     operands[2] = can_create_pseudo_p () ? gen_reg_rtx (SImode) : operands[0];
5621     operands[3] = GEN_INT (i);
5622   }"
5625 ;; For thumb1 split imm move [256-510] into mov [1-255] and add #255
5626 (define_split 
5627   [(set (match_operand:SI 0 "register_operand" "")
5628         (match_operand:SI 1 "const_int_operand" ""))]
5629   "TARGET_THUMB1 && satisfies_constraint_Pe (operands[1])"
5630   [(set (match_dup 2) (match_dup 1))
5631    (set (match_dup 0) (plus:SI (match_dup 2) (match_dup 3)))]
5632   "
5633   {
5634     operands[1] = GEN_INT (INTVAL (operands[1]) - 255);
5635     operands[2] = can_create_pseudo_p () ? gen_reg_rtx (SImode) : operands[0];
5636     operands[3] = GEN_INT (255);
5637   }"
5640 ;; When generating pic, we need to load the symbol offset into a register.
5641 ;; So that the optimizer does not confuse this with a normal symbol load
5642 ;; we use an unspec.  The offset will be loaded from a constant pool entry,
5643 ;; since that is the only type of relocation we can use.
5645 ;; Wrap calculation of the whole PIC address in a single pattern for the
5646 ;; benefit of optimizers, particularly, PRE and HOIST.  Calculation of
5647 ;; a PIC address involves two loads from memory, so we want to CSE it
5648 ;; as often as possible.
5649 ;; This pattern will be split into one of the pic_load_addr_* patterns
5650 ;; and a move after GCSE optimizations.
5652 ;; Note: Update arm.c: legitimize_pic_address() when changing this pattern.
5653 (define_expand "calculate_pic_address"
5654   [(set (match_operand:SI 0 "register_operand" "")
5655         (mem:SI (plus:SI (match_operand:SI 1 "register_operand" "")
5656                          (unspec:SI [(match_operand:SI 2 "" "")]
5657                                     UNSPEC_PIC_SYM))))]
5658   "flag_pic"
5661 ;; Split calculate_pic_address into pic_load_addr_* and a move.
5662 (define_split
5663   [(set (match_operand:SI 0 "register_operand" "")
5664         (mem:SI (plus:SI (match_operand:SI 1 "register_operand" "")
5665                          (unspec:SI [(match_operand:SI 2 "" "")]
5666                                     UNSPEC_PIC_SYM))))]
5667   "flag_pic"
5668   [(set (match_dup 3) (unspec:SI [(match_dup 2)] UNSPEC_PIC_SYM))
5669    (set (match_dup 0) (mem:SI (plus:SI (match_dup 1) (match_dup 3))))]
5670   "operands[3] = can_create_pseudo_p () ? gen_reg_rtx (SImode) : operands[0];"
5673 ;; operand1 is the memory address to go into 
5674 ;; pic_load_addr_32bit.
5675 ;; operand2 is the PIC label to be emitted 
5676 ;; from pic_add_dot_plus_eight.
5677 ;; We do this to allow hoisting of the entire insn.
5678 (define_insn_and_split "pic_load_addr_unified"
5679   [(set (match_operand:SI 0 "s_register_operand" "=r,r,l")
5680         (unspec:SI [(match_operand:SI 1 "" "mX,mX,mX") 
5681                     (match_operand:SI 2 "" "")] 
5682                     UNSPEC_PIC_UNIFIED))]
5683  "flag_pic"
5684  "#"
5685  "&& reload_completed"
5686  [(set (match_dup 0) (unspec:SI [(match_dup 1)] UNSPEC_PIC_SYM))
5687   (set (match_dup 0) (unspec:SI [(match_dup 0) (match_dup 3)
5688                                  (match_dup 2)] UNSPEC_PIC_BASE))]
5689  "operands[3] = TARGET_THUMB ? GEN_INT (4) : GEN_INT (8);"
5690  [(set_attr "type" "load1,load1,load1")
5691   (set_attr "pool_range" "4096,4096,1024")
5692   (set_attr "neg_pool_range" "4084,0,0")
5693   (set_attr "arch"  "a,t2,t1")    
5694   (set_attr "length" "8,6,4")]
5697 ;; The rather odd constraints on the following are to force reload to leave
5698 ;; the insn alone, and to force the minipool generation pass to then move
5699 ;; the GOT symbol to memory.
5701 (define_insn "pic_load_addr_32bit"
5702   [(set (match_operand:SI 0 "s_register_operand" "=r")
5703         (unspec:SI [(match_operand:SI 1 "" "mX")] UNSPEC_PIC_SYM))]
5704   "TARGET_32BIT && flag_pic"
5705   "ldr%?\\t%0, %1"
5706   [(set_attr "type" "load1")
5707    (set_attr "pool_range" "4096")
5708    (set (attr "neg_pool_range")
5709         (if_then_else (eq_attr "is_thumb" "no")
5710                       (const_int 4084)
5711                       (const_int 0)))]
5714 (define_insn "pic_load_addr_thumb1"
5715   [(set (match_operand:SI 0 "s_register_operand" "=l")
5716         (unspec:SI [(match_operand:SI 1 "" "mX")] UNSPEC_PIC_SYM))]
5717   "TARGET_THUMB1 && flag_pic"
5718   "ldr\\t%0, %1"
5719   [(set_attr "type" "load1")
5720    (set (attr "pool_range") (const_int 1024))]
5723 (define_insn "pic_add_dot_plus_four"
5724   [(set (match_operand:SI 0 "register_operand" "=r")
5725         (unspec:SI [(match_operand:SI 1 "register_operand" "0")
5726                     (const_int 4)
5727                     (match_operand 2 "" "")]
5728                    UNSPEC_PIC_BASE))]
5729   "TARGET_THUMB"
5730   "*
5731   (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
5732                                      INTVAL (operands[2]));
5733   return \"add\\t%0, %|pc\";
5734   "
5735   [(set_attr "length" "2")]
5738 (define_insn "pic_add_dot_plus_eight"
5739   [(set (match_operand:SI 0 "register_operand" "=r")
5740         (unspec:SI [(match_operand:SI 1 "register_operand" "r")
5741                     (const_int 8)
5742                     (match_operand 2 "" "")]
5743                    UNSPEC_PIC_BASE))]
5744   "TARGET_ARM"
5745   "*
5746     (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
5747                                        INTVAL (operands[2]));
5748     return \"add%?\\t%0, %|pc, %1\";
5749   "
5750   [(set_attr "predicable" "yes")]
5753 (define_insn "tls_load_dot_plus_eight"
5754   [(set (match_operand:SI 0 "register_operand" "=r")
5755         (mem:SI (unspec:SI [(match_operand:SI 1 "register_operand" "r")
5756                             (const_int 8)
5757                             (match_operand 2 "" "")]
5758                            UNSPEC_PIC_BASE)))]
5759   "TARGET_ARM"
5760   "*
5761     (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
5762                                        INTVAL (operands[2]));
5763     return \"ldr%?\\t%0, [%|pc, %1]\t\t@ tls_load_dot_plus_eight\";
5764   "
5765   [(set_attr "predicable" "yes")]
5768 ;; PIC references to local variables can generate pic_add_dot_plus_eight
5769 ;; followed by a load.  These sequences can be crunched down to
5770 ;; tls_load_dot_plus_eight by a peephole.
5772 (define_peephole2
5773   [(set (match_operand:SI 0 "register_operand" "")
5774         (unspec:SI [(match_operand:SI 3 "register_operand" "")
5775                     (const_int 8)
5776                     (match_operand 1 "" "")]
5777                    UNSPEC_PIC_BASE))
5778    (set (match_operand:SI 2 "arm_general_register_operand" "")
5779         (mem:SI (match_dup 0)))]
5780   "TARGET_ARM && peep2_reg_dead_p (2, operands[0])"
5781   [(set (match_dup 2)
5782         (mem:SI (unspec:SI [(match_dup 3)
5783                             (const_int 8)
5784                             (match_dup 1)]
5785                            UNSPEC_PIC_BASE)))]
5786   ""
5789 (define_insn "pic_offset_arm"
5790   [(set (match_operand:SI 0 "register_operand" "=r")
5791         (mem:SI (plus:SI (match_operand:SI 1 "register_operand" "r")
5792                          (unspec:SI [(match_operand:SI 2 "" "X")]
5793                                     UNSPEC_PIC_OFFSET))))]
5794   "TARGET_VXWORKS_RTP && TARGET_ARM && flag_pic"
5795   "ldr%?\\t%0, [%1,%2]"
5796   [(set_attr "type" "load1")]
5799 (define_expand "builtin_setjmp_receiver"
5800   [(label_ref (match_operand 0 "" ""))]
5801   "flag_pic"
5802   "
5804   /* r3 is clobbered by set/longjmp, so we can use it as a scratch
5805      register.  */
5806   if (arm_pic_register != INVALID_REGNUM)
5807     arm_load_pic_register (1UL << 3);
5808   DONE;
5811 ;; If copying one reg to another we can set the condition codes according to
5812 ;; its value.  Such a move is common after a return from subroutine and the
5813 ;; result is being tested against zero.
5815 (define_insn "*movsi_compare0"
5816   [(set (reg:CC CC_REGNUM)
5817         (compare:CC (match_operand:SI 1 "s_register_operand" "0,r")
5818                     (const_int 0)))
5819    (set (match_operand:SI 0 "s_register_operand" "=r,r")
5820         (match_dup 1))]
5821   "TARGET_32BIT"
5822   "@
5823    cmp%?\\t%0, #0
5824    sub%.\\t%0, %1, #0"
5825   [(set_attr "conds" "set")]
5828 ;; Subroutine to store a half word from a register into memory.
5829 ;; Operand 0 is the source register (HImode)
5830 ;; Operand 1 is the destination address in a register (SImode)
5832 ;; In both this routine and the next, we must be careful not to spill
5833 ;; a memory address of reg+large_const into a separate PLUS insn, since this
5834 ;; can generate unrecognizable rtl.
5836 (define_expand "storehi"
5837   [;; store the low byte
5838    (set (match_operand 1 "" "") (match_dup 3))
5839    ;; extract the high byte
5840    (set (match_dup 2)
5841         (ashiftrt:SI (match_operand 0 "" "") (const_int 8)))
5842    ;; store the high byte
5843    (set (match_dup 4) (match_dup 5))]
5844   "TARGET_ARM"
5845   "
5846   {
5847     rtx op1 = operands[1];
5848     rtx addr = XEXP (op1, 0);
5849     enum rtx_code code = GET_CODE (addr);
5851     if ((code == PLUS && GET_CODE (XEXP (addr, 1)) != CONST_INT)
5852         || code == MINUS)
5853       op1 = replace_equiv_address (operands[1], force_reg (SImode, addr));
5855     operands[4] = adjust_address (op1, QImode, 1);
5856     operands[1] = adjust_address (operands[1], QImode, 0);
5857     operands[3] = gen_lowpart (QImode, operands[0]);
5858     operands[0] = gen_lowpart (SImode, operands[0]);
5859     operands[2] = gen_reg_rtx (SImode);
5860     operands[5] = gen_lowpart (QImode, operands[2]);
5861   }"
5864 (define_expand "storehi_bigend"
5865   [(set (match_dup 4) (match_dup 3))
5866    (set (match_dup 2)
5867         (ashiftrt:SI (match_operand 0 "" "") (const_int 8)))
5868    (set (match_operand 1 "" "") (match_dup 5))]
5869   "TARGET_ARM"
5870   "
5871   {
5872     rtx op1 = operands[1];
5873     rtx addr = XEXP (op1, 0);
5874     enum rtx_code code = GET_CODE (addr);
5876     if ((code == PLUS && GET_CODE (XEXP (addr, 1)) != CONST_INT)
5877         || code == MINUS)
5878       op1 = replace_equiv_address (op1, force_reg (SImode, addr));
5880     operands[4] = adjust_address (op1, QImode, 1);
5881     operands[1] = adjust_address (operands[1], QImode, 0);
5882     operands[3] = gen_lowpart (QImode, operands[0]);
5883     operands[0] = gen_lowpart (SImode, operands[0]);
5884     operands[2] = gen_reg_rtx (SImode);
5885     operands[5] = gen_lowpart (QImode, operands[2]);
5886   }"
5889 ;; Subroutine to store a half word integer constant into memory.
5890 (define_expand "storeinthi"
5891   [(set (match_operand 0 "" "")
5892         (match_operand 1 "" ""))
5893    (set (match_dup 3) (match_dup 2))]
5894   "TARGET_ARM"
5895   "
5896   {
5897     HOST_WIDE_INT value = INTVAL (operands[1]);
5898     rtx addr = XEXP (operands[0], 0);
5899     rtx op0 = operands[0];
5900     enum rtx_code code = GET_CODE (addr);
5902     if ((code == PLUS && GET_CODE (XEXP (addr, 1)) != CONST_INT)
5903         || code == MINUS)
5904       op0 = replace_equiv_address (op0, force_reg (SImode, addr));
5906     operands[1] = gen_reg_rtx (SImode);
5907     if (BYTES_BIG_ENDIAN)
5908       {
5909         emit_insn (gen_movsi (operands[1], GEN_INT ((value >> 8) & 255)));
5910         if ((value & 255) == ((value >> 8) & 255))
5911           operands[2] = operands[1];
5912         else
5913           {
5914             operands[2] = gen_reg_rtx (SImode);
5915             emit_insn (gen_movsi (operands[2], GEN_INT (value & 255)));
5916           }
5917       }
5918     else
5919       {
5920         emit_insn (gen_movsi (operands[1], GEN_INT (value & 255)));
5921         if ((value & 255) == ((value >> 8) & 255))
5922           operands[2] = operands[1];
5923         else
5924           {
5925             operands[2] = gen_reg_rtx (SImode);
5926             emit_insn (gen_movsi (operands[2], GEN_INT ((value >> 8) & 255)));
5927           }
5928       }
5930     operands[3] = adjust_address (op0, QImode, 1);
5931     operands[0] = adjust_address (operands[0], QImode, 0);
5932     operands[2] = gen_lowpart (QImode, operands[2]);
5933     operands[1] = gen_lowpart (QImode, operands[1]);
5934   }"
5937 (define_expand "storehi_single_op"
5938   [(set (match_operand:HI 0 "memory_operand" "")
5939         (match_operand:HI 1 "general_operand" ""))]
5940   "TARGET_32BIT && arm_arch4"
5941   "
5942   if (!s_register_operand (operands[1], HImode))
5943     operands[1] = copy_to_mode_reg (HImode, operands[1]);
5944   "
5947 (define_expand "movhi"
5948   [(set (match_operand:HI 0 "general_operand" "")
5949         (match_operand:HI 1 "general_operand" ""))]
5950   "TARGET_EITHER"
5951   "
5952   if (TARGET_ARM)
5953     {
5954       if (can_create_pseudo_p ())
5955         {
5956           if (GET_CODE (operands[0]) == MEM)
5957             {
5958               if (arm_arch4)
5959                 {
5960                   emit_insn (gen_storehi_single_op (operands[0], operands[1]));
5961                   DONE;
5962                 }
5963               if (GET_CODE (operands[1]) == CONST_INT)
5964                 emit_insn (gen_storeinthi (operands[0], operands[1]));
5965               else
5966                 {
5967                   if (GET_CODE (operands[1]) == MEM)
5968                     operands[1] = force_reg (HImode, operands[1]);
5969                   if (BYTES_BIG_ENDIAN)
5970                     emit_insn (gen_storehi_bigend (operands[1], operands[0]));
5971                   else
5972                    emit_insn (gen_storehi (operands[1], operands[0]));
5973                 }
5974               DONE;
5975             }
5976           /* Sign extend a constant, and keep it in an SImode reg.  */
5977           else if (GET_CODE (operands[1]) == CONST_INT)
5978             {
5979               rtx reg = gen_reg_rtx (SImode);
5980               HOST_WIDE_INT val = INTVAL (operands[1]) & 0xffff;
5982               /* If the constant is already valid, leave it alone.  */
5983               if (!const_ok_for_arm (val))
5984                 {
5985                   /* If setting all the top bits will make the constant 
5986                      loadable in a single instruction, then set them.  
5987                      Otherwise, sign extend the number.  */
5989                   if (const_ok_for_arm (~(val | ~0xffff)))
5990                     val |= ~0xffff;
5991                   else if (val & 0x8000)
5992                     val |= ~0xffff;
5993                 }
5995               emit_insn (gen_movsi (reg, GEN_INT (val)));
5996               operands[1] = gen_lowpart (HImode, reg);
5997             }
5998           else if (arm_arch4 && optimize && can_create_pseudo_p ()
5999                    && GET_CODE (operands[1]) == MEM)
6000             {
6001               rtx reg = gen_reg_rtx (SImode);
6003               emit_insn (gen_zero_extendhisi2 (reg, operands[1]));
6004               operands[1] = gen_lowpart (HImode, reg);
6005             }
6006           else if (!arm_arch4)
6007             {
6008               if (GET_CODE (operands[1]) == MEM)
6009                 {
6010                   rtx base;
6011                   rtx offset = const0_rtx;
6012                   rtx reg = gen_reg_rtx (SImode);
6014                   if ((GET_CODE (base = XEXP (operands[1], 0)) == REG
6015                        || (GET_CODE (base) == PLUS
6016                            && (GET_CODE (offset = XEXP (base, 1))
6017                                == CONST_INT)
6018                            && ((INTVAL(offset) & 1) != 1)
6019                            && GET_CODE (base = XEXP (base, 0)) == REG))
6020                       && REGNO_POINTER_ALIGN (REGNO (base)) >= 32)
6021                     {
6022                       rtx new_rtx;
6024                       new_rtx = widen_memory_access (operands[1], SImode,
6025                                                      ((INTVAL (offset) & ~3)
6026                                                       - INTVAL (offset)));
6027                       emit_insn (gen_movsi (reg, new_rtx));
6028                       if (((INTVAL (offset) & 2) != 0)
6029                           ^ (BYTES_BIG_ENDIAN ? 1 : 0))
6030                         {
6031                           rtx reg2 = gen_reg_rtx (SImode);
6033                           emit_insn (gen_lshrsi3 (reg2, reg, GEN_INT (16)));
6034                           reg = reg2;
6035                         }
6036                     }
6037                   else
6038                     emit_insn (gen_movhi_bytes (reg, operands[1]));
6040                   operands[1] = gen_lowpart (HImode, reg);
6041                }
6042            }
6043         }
6044       /* Handle loading a large integer during reload.  */
6045       else if (GET_CODE (operands[1]) == CONST_INT
6046                && !const_ok_for_arm (INTVAL (operands[1]))
6047                && !const_ok_for_arm (~INTVAL (operands[1])))
6048         {
6049           /* Writing a constant to memory needs a scratch, which should
6050              be handled with SECONDARY_RELOADs.  */
6051           gcc_assert (GET_CODE (operands[0]) == REG);
6053           operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
6054           emit_insn (gen_movsi (operands[0], operands[1]));
6055           DONE;
6056        }
6057     }
6058   else if (TARGET_THUMB2)
6059     {
6060       /* Thumb-2 can do everything except mem=mem and mem=const easily.  */
6061       if (can_create_pseudo_p ())
6062         {
6063           if (GET_CODE (operands[0]) != REG)
6064             operands[1] = force_reg (HImode, operands[1]);
6065           /* Zero extend a constant, and keep it in an SImode reg.  */
6066           else if (GET_CODE (operands[1]) == CONST_INT)
6067             {
6068               rtx reg = gen_reg_rtx (SImode);
6069               HOST_WIDE_INT val = INTVAL (operands[1]) & 0xffff;
6071               emit_insn (gen_movsi (reg, GEN_INT (val)));
6072               operands[1] = gen_lowpart (HImode, reg);
6073             }
6074         }
6075     }
6076   else /* TARGET_THUMB1 */
6077     {
6078       if (can_create_pseudo_p ())
6079         {
6080           if (GET_CODE (operands[1]) == CONST_INT)
6081             {
6082               rtx reg = gen_reg_rtx (SImode);
6084               emit_insn (gen_movsi (reg, operands[1]));
6085               operands[1] = gen_lowpart (HImode, reg);
6086             }
6088           /* ??? We shouldn't really get invalid addresses here, but this can
6089              happen if we are passed a SP (never OK for HImode/QImode) or 
6090              virtual register (also rejected as illegitimate for HImode/QImode)
6091              relative address.  */
6092           /* ??? This should perhaps be fixed elsewhere, for instance, in
6093              fixup_stack_1, by checking for other kinds of invalid addresses,
6094              e.g. a bare reference to a virtual register.  This may confuse the
6095              alpha though, which must handle this case differently.  */
6096           if (GET_CODE (operands[0]) == MEM
6097               && !memory_address_p (GET_MODE (operands[0]),
6098                                     XEXP (operands[0], 0)))
6099             operands[0]
6100               = replace_equiv_address (operands[0],
6101                                        copy_to_reg (XEXP (operands[0], 0)));
6102    
6103           if (GET_CODE (operands[1]) == MEM
6104               && !memory_address_p (GET_MODE (operands[1]),
6105                                     XEXP (operands[1], 0)))
6106             operands[1]
6107               = replace_equiv_address (operands[1],
6108                                        copy_to_reg (XEXP (operands[1], 0)));
6110           if (GET_CODE (operands[1]) == MEM && optimize > 0)
6111             {
6112               rtx reg = gen_reg_rtx (SImode);
6114               emit_insn (gen_zero_extendhisi2 (reg, operands[1]));
6115               operands[1] = gen_lowpart (HImode, reg);
6116             }
6118           if (GET_CODE (operands[0]) == MEM)
6119             operands[1] = force_reg (HImode, operands[1]);
6120         }
6121       else if (GET_CODE (operands[1]) == CONST_INT
6122                 && !satisfies_constraint_I (operands[1]))
6123         {
6124           /* Handle loading a large integer during reload.  */
6126           /* Writing a constant to memory needs a scratch, which should
6127              be handled with SECONDARY_RELOADs.  */
6128           gcc_assert (GET_CODE (operands[0]) == REG);
6130           operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
6131           emit_insn (gen_movsi (operands[0], operands[1]));
6132           DONE;
6133         }
6134     }
6135   "
6138 (define_insn "*thumb1_movhi_insn"
6139   [(set (match_operand:HI 0 "nonimmediate_operand" "=l,l,m,*r,*h,l")
6140         (match_operand:HI 1 "general_operand"       "l,m,l,*h,*r,I"))]
6141   "TARGET_THUMB1
6142    && (   register_operand (operands[0], HImode)
6143        || register_operand (operands[1], HImode))"
6144   "*
6145   switch (which_alternative)
6146     {
6147     case 0: return \"add        %0, %1, #0\";
6148     case 2: return \"strh       %1, %0\";
6149     case 3: return \"mov        %0, %1\";
6150     case 4: return \"mov        %0, %1\";
6151     case 5: return \"mov        %0, %1\";
6152     default: gcc_unreachable ();
6153     case 1:
6154       /* The stack pointer can end up being taken as an index register.
6155           Catch this case here and deal with it.  */
6156       if (GET_CODE (XEXP (operands[1], 0)) == PLUS
6157           && GET_CODE (XEXP (XEXP (operands[1], 0), 0)) == REG
6158           && REGNO    (XEXP (XEXP (operands[1], 0), 0)) == SP_REGNUM)
6159         {
6160           rtx ops[2];
6161           ops[0] = operands[0];
6162           ops[1] = XEXP (XEXP (operands[1], 0), 0);
6163       
6164           output_asm_insn (\"mov        %0, %1\", ops);
6166           XEXP (XEXP (operands[1], 0), 0) = operands[0];
6167     
6168         }
6169       return \"ldrh     %0, %1\";
6170     }"
6171   [(set_attr "length" "2,4,2,2,2,2")
6172    (set_attr "type" "*,load1,store1,*,*,*")
6173    (set_attr "conds" "clob,nocond,nocond,nocond,nocond,clob")])
6176 (define_expand "movhi_bytes"
6177   [(set (match_dup 2) (zero_extend:SI (match_operand:HI 1 "" "")))
6178    (set (match_dup 3)
6179         (zero_extend:SI (match_dup 6)))
6180    (set (match_operand:SI 0 "" "")
6181          (ior:SI (ashift:SI (match_dup 4) (const_int 8)) (match_dup 5)))]
6182   "TARGET_ARM"
6183   "
6184   {
6185     rtx mem1, mem2;
6186     rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
6188     mem1 = change_address (operands[1], QImode, addr);
6189     mem2 = change_address (operands[1], QImode,
6190                            plus_constant (Pmode, addr, 1));
6191     operands[0] = gen_lowpart (SImode, operands[0]);
6192     operands[1] = mem1;
6193     operands[2] = gen_reg_rtx (SImode);
6194     operands[3] = gen_reg_rtx (SImode);
6195     operands[6] = mem2;
6197     if (BYTES_BIG_ENDIAN)
6198       {
6199         operands[4] = operands[2];
6200         operands[5] = operands[3];
6201       }
6202     else
6203       {
6204         operands[4] = operands[3];
6205         operands[5] = operands[2];
6206       }
6207   }"
6210 (define_expand "movhi_bigend"
6211   [(set (match_dup 2)
6212         (rotate:SI (subreg:SI (match_operand:HI 1 "memory_operand" "") 0)
6213                    (const_int 16)))
6214    (set (match_dup 3)
6215         (ashiftrt:SI (match_dup 2) (const_int 16)))
6216    (set (match_operand:HI 0 "s_register_operand" "")
6217         (match_dup 4))]
6218   "TARGET_ARM"
6219   "
6220   operands[2] = gen_reg_rtx (SImode);
6221   operands[3] = gen_reg_rtx (SImode);
6222   operands[4] = gen_lowpart (HImode, operands[3]);
6223   "
6226 ;; Pattern to recognize insn generated default case above
6227 (define_insn "*movhi_insn_arch4"
6228   [(set (match_operand:HI 0 "nonimmediate_operand" "=r,r,m,r")
6229         (match_operand:HI 1 "general_operand"      "rI,K,r,mi"))]
6230   "TARGET_ARM
6231    && arm_arch4
6232    && (register_operand (operands[0], HImode)
6233        || register_operand (operands[1], HImode))"
6234   "@
6235    mov%?\\t%0, %1\\t%@ movhi
6236    mvn%?\\t%0, #%B1\\t%@ movhi
6237    str%(h%)\\t%1, %0\\t%@ movhi
6238    ldr%(h%)\\t%0, %1\\t%@ movhi"
6239   [(set_attr "type" "*,*,store1,load1")
6240    (set_attr "predicable" "yes")
6241    (set_attr "insn" "mov,mvn,*,*")
6242    (set_attr "pool_range" "*,*,*,256")
6243    (set_attr "neg_pool_range" "*,*,*,244")]
6246 (define_insn "*movhi_bytes"
6247   [(set (match_operand:HI 0 "s_register_operand" "=r,r")
6248         (match_operand:HI 1 "arm_rhs_operand"  "rI,K"))]
6249   "TARGET_ARM"
6250   "@
6251    mov%?\\t%0, %1\\t%@ movhi
6252    mvn%?\\t%0, #%B1\\t%@ movhi"
6253   [(set_attr "predicable" "yes")
6254    (set_attr "insn" "mov,mvn")]
6257 (define_expand "thumb_movhi_clobber"
6258   [(set (match_operand:HI     0 "memory_operand"   "")
6259         (match_operand:HI     1 "register_operand" ""))
6260    (clobber (match_operand:DI 2 "register_operand" ""))]
6261   "TARGET_THUMB1"
6262   "
6263   if (strict_memory_address_p (HImode, XEXP (operands[0], 0))
6264       && REGNO (operands[1]) <= LAST_LO_REGNUM)
6265     {
6266       emit_insn (gen_movhi (operands[0], operands[1]));
6267       DONE;
6268     }
6269   /* XXX Fixme, need to handle other cases here as well.  */
6270   gcc_unreachable ();
6271   "
6273         
6274 ;; We use a DImode scratch because we may occasionally need an additional
6275 ;; temporary if the address isn't offsettable -- push_reload doesn't seem
6276 ;; to take any notice of the "o" constraints on reload_memory_operand operand.
6277 (define_expand "reload_outhi"
6278   [(parallel [(match_operand:HI 0 "arm_reload_memory_operand" "=o")
6279               (match_operand:HI 1 "s_register_operand"        "r")
6280               (match_operand:DI 2 "s_register_operand"        "=&l")])]
6281   "TARGET_EITHER"
6282   "if (TARGET_ARM)
6283      arm_reload_out_hi (operands);
6284    else
6285      thumb_reload_out_hi (operands);
6286   DONE;
6287   "
6290 (define_expand "reload_inhi"
6291   [(parallel [(match_operand:HI 0 "s_register_operand" "=r")
6292               (match_operand:HI 1 "arm_reload_memory_operand" "o")
6293               (match_operand:DI 2 "s_register_operand" "=&r")])]
6294   "TARGET_EITHER"
6295   "
6296   if (TARGET_ARM)
6297     arm_reload_in_hi (operands);
6298   else
6299     thumb_reload_out_hi (operands);
6300   DONE;
6303 (define_expand "movqi"
6304   [(set (match_operand:QI 0 "general_operand" "")
6305         (match_operand:QI 1 "general_operand" ""))]
6306   "TARGET_EITHER"
6307   "
6308   /* Everything except mem = const or mem = mem can be done easily */
6310   if (can_create_pseudo_p ())
6311     {
6312       if (GET_CODE (operands[1]) == CONST_INT)
6313         {
6314           rtx reg = gen_reg_rtx (SImode);
6316           /* For thumb we want an unsigned immediate, then we are more likely 
6317              to be able to use a movs insn.  */
6318           if (TARGET_THUMB)
6319             operands[1] = GEN_INT (INTVAL (operands[1]) & 255);
6321           emit_insn (gen_movsi (reg, operands[1]));
6322           operands[1] = gen_lowpart (QImode, reg);
6323         }
6325       if (TARGET_THUMB)
6326         {
6327           /* ??? We shouldn't really get invalid addresses here, but this can
6328              happen if we are passed a SP (never OK for HImode/QImode) or
6329              virtual register (also rejected as illegitimate for HImode/QImode)
6330              relative address.  */
6331           /* ??? This should perhaps be fixed elsewhere, for instance, in
6332              fixup_stack_1, by checking for other kinds of invalid addresses,
6333              e.g. a bare reference to a virtual register.  This may confuse the
6334              alpha though, which must handle this case differently.  */
6335           if (GET_CODE (operands[0]) == MEM
6336               && !memory_address_p (GET_MODE (operands[0]),
6337                                      XEXP (operands[0], 0)))
6338             operands[0]
6339               = replace_equiv_address (operands[0],
6340                                        copy_to_reg (XEXP (operands[0], 0)));
6341           if (GET_CODE (operands[1]) == MEM
6342               && !memory_address_p (GET_MODE (operands[1]),
6343                                     XEXP (operands[1], 0)))
6344              operands[1]
6345                = replace_equiv_address (operands[1],
6346                                         copy_to_reg (XEXP (operands[1], 0)));
6347         }
6349       if (GET_CODE (operands[1]) == MEM && optimize > 0)
6350         {
6351           rtx reg = gen_reg_rtx (SImode);
6353           emit_insn (gen_zero_extendqisi2 (reg, operands[1]));
6354           operands[1] = gen_lowpart (QImode, reg);
6355         }
6357       if (GET_CODE (operands[0]) == MEM)
6358         operands[1] = force_reg (QImode, operands[1]);
6359     }
6360   else if (TARGET_THUMB
6361            && GET_CODE (operands[1]) == CONST_INT
6362            && !satisfies_constraint_I (operands[1]))
6363     {
6364       /* Handle loading a large integer during reload.  */
6366       /* Writing a constant to memory needs a scratch, which should
6367          be handled with SECONDARY_RELOADs.  */
6368       gcc_assert (GET_CODE (operands[0]) == REG);
6370       operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
6371       emit_insn (gen_movsi (operands[0], operands[1]));
6372       DONE;
6373     }
6374   "
6378 (define_insn "*arm_movqi_insn"
6379   [(set (match_operand:QI 0 "nonimmediate_operand" "=r,r,l,Uu,r,m")
6380         (match_operand:QI 1 "general_operand" "rI,K,Uu,l,m,r"))]
6381   "TARGET_32BIT
6382    && (   register_operand (operands[0], QImode)
6383        || register_operand (operands[1], QImode))"
6384   "@
6385    mov%?\\t%0, %1
6386    mvn%?\\t%0, #%B1
6387    ldr%(b%)\\t%0, %1
6388    str%(b%)\\t%1, %0
6389    ldr%(b%)\\t%0, %1
6390    str%(b%)\\t%1, %0"
6391   [(set_attr "type" "*,*,load1,store1,load1,store1")
6392    (set_attr "insn" "mov,mvn,*,*,*,*")
6393    (set_attr "predicable" "yes")
6394    (set_attr "arch" "any,any,t2,t2,any,any")
6395    (set_attr "length" "4,4,2,2,4,4")]
6398 (define_insn "*thumb1_movqi_insn"
6399   [(set (match_operand:QI 0 "nonimmediate_operand" "=l,l,m,*r,*h,l")
6400         (match_operand:QI 1 "general_operand"      "l, m,l,*h,*r,I"))]
6401   "TARGET_THUMB1
6402    && (   register_operand (operands[0], QImode)
6403        || register_operand (operands[1], QImode))"
6404   "@
6405    add\\t%0, %1, #0
6406    ldrb\\t%0, %1
6407    strb\\t%1, %0
6408    mov\\t%0, %1
6409    mov\\t%0, %1
6410    mov\\t%0, %1"
6411   [(set_attr "length" "2")
6412    (set_attr "type" "*,load1,store1,*,*,*")
6413    (set_attr "insn" "*,*,*,mov,mov,mov")
6414    (set_attr "pool_range" "*,32,*,*,*,*")
6415    (set_attr "conds" "clob,nocond,nocond,nocond,nocond,clob")])
6417 ;; HFmode moves
6418 (define_expand "movhf"
6419   [(set (match_operand:HF 0 "general_operand" "")
6420         (match_operand:HF 1 "general_operand" ""))]
6421   "TARGET_EITHER"
6422   "
6423   if (TARGET_32BIT)
6424     {
6425       if (GET_CODE (operands[0]) == MEM)
6426         operands[1] = force_reg (HFmode, operands[1]);
6427     }
6428   else /* TARGET_THUMB1 */
6429     {
6430       if (can_create_pseudo_p ())
6431         {
6432            if (GET_CODE (operands[0]) != REG)
6433              operands[1] = force_reg (HFmode, operands[1]);
6434         }
6435     }
6436   "
6439 (define_insn "*arm32_movhf"
6440   [(set (match_operand:HF 0 "nonimmediate_operand" "=r,m,r,r")
6441         (match_operand:HF 1 "general_operand"      " m,r,r,F"))]
6442   "TARGET_32BIT && !(TARGET_HARD_FLOAT && TARGET_FP16)
6443    && (   s_register_operand (operands[0], HFmode)
6444        || s_register_operand (operands[1], HFmode))"
6445   "*
6446   switch (which_alternative)
6447     {
6448     case 0:     /* ARM register from memory */
6449       return \"ldr%(h%)\\t%0, %1\\t%@ __fp16\";
6450     case 1:     /* memory from ARM register */
6451       return \"str%(h%)\\t%1, %0\\t%@ __fp16\";
6452     case 2:     /* ARM register from ARM register */
6453       return \"mov%?\\t%0, %1\\t%@ __fp16\";
6454     case 3:     /* ARM register from constant */
6455       {
6456         REAL_VALUE_TYPE r;
6457         long bits;
6458         rtx ops[4];
6460         REAL_VALUE_FROM_CONST_DOUBLE (r, operands[1]);
6461         bits = real_to_target (NULL, &r, HFmode);
6462         ops[0] = operands[0];
6463         ops[1] = GEN_INT (bits);
6464         ops[2] = GEN_INT (bits & 0xff00);
6465         ops[3] = GEN_INT (bits & 0x00ff);
6467         if (arm_arch_thumb2)
6468           output_asm_insn (\"movw%?\\t%0, %1\", ops);
6469         else
6470           output_asm_insn (\"mov%?\\t%0, %2\;orr%?\\t%0, %0, %3\", ops);
6471         return \"\";
6472        }
6473     default:
6474       gcc_unreachable ();
6475     }
6476   "
6477   [(set_attr "conds" "unconditional")
6478    (set_attr "type" "load1,store1,*,*")
6479    (set_attr "insn" "*,*,mov,mov")
6480    (set_attr "length" "4,4,4,8")
6481    (set_attr "predicable" "yes")]
6484 (define_insn "*thumb1_movhf"
6485   [(set (match_operand:HF     0 "nonimmediate_operand" "=l,l,m,*r,*h")
6486         (match_operand:HF     1 "general_operand"      "l,mF,l,*h,*r"))]
6487   "TARGET_THUMB1
6488    && (   s_register_operand (operands[0], HFmode) 
6489        || s_register_operand (operands[1], HFmode))"
6490   "*
6491   switch (which_alternative)
6492     {
6493     case 1:
6494       {
6495         rtx addr;
6496         gcc_assert (GET_CODE(operands[1]) == MEM);
6497         addr = XEXP (operands[1], 0);
6498         if (GET_CODE (addr) == LABEL_REF
6499             || (GET_CODE (addr) == CONST
6500                 && GET_CODE (XEXP (addr, 0)) == PLUS
6501                 && GET_CODE (XEXP (XEXP (addr, 0), 0)) == LABEL_REF
6502                 && GET_CODE (XEXP (XEXP (addr, 0), 1)) == CONST_INT))
6503           {
6504             /* Constant pool entry.  */
6505             return \"ldr\\t%0, %1\";
6506           }
6507         return \"ldrh\\t%0, %1\";
6508       }
6509     case 2: return \"strh\\t%1, %0\";
6510     default: return \"mov\\t%0, %1\";
6511     }
6512   "
6513   [(set_attr "length" "2")
6514    (set_attr "type" "*,load1,store1,*,*")
6515    (set_attr "insn" "mov,*,*,mov,mov")
6516    (set_attr "pool_range" "*,1020,*,*,*")
6517    (set_attr "conds" "clob,nocond,nocond,nocond,nocond")])
6519 (define_expand "movsf"
6520   [(set (match_operand:SF 0 "general_operand" "")
6521         (match_operand:SF 1 "general_operand" ""))]
6522   "TARGET_EITHER"
6523   "
6524   if (TARGET_32BIT)
6525     {
6526       if (GET_CODE (operands[0]) == MEM)
6527         operands[1] = force_reg (SFmode, operands[1]);
6528     }
6529   else /* TARGET_THUMB1 */
6530     {
6531       if (can_create_pseudo_p ())
6532         {
6533            if (GET_CODE (operands[0]) != REG)
6534              operands[1] = force_reg (SFmode, operands[1]);
6535         }
6536     }
6537   "
6540 ;; Transform a floating-point move of a constant into a core register into
6541 ;; an SImode operation.
6542 (define_split
6543   [(set (match_operand:SF 0 "arm_general_register_operand" "")
6544         (match_operand:SF 1 "immediate_operand" ""))]
6545   "TARGET_EITHER
6546    && reload_completed
6547    && GET_CODE (operands[1]) == CONST_DOUBLE"
6548   [(set (match_dup 2) (match_dup 3))]
6549   "
6550   operands[2] = gen_lowpart (SImode, operands[0]);
6551   operands[3] = gen_lowpart (SImode, operands[1]);
6552   if (operands[2] == 0 || operands[3] == 0)
6553     FAIL;
6554   "
6557 (define_insn "*arm_movsf_soft_insn"
6558   [(set (match_operand:SF 0 "nonimmediate_operand" "=r,r,m")
6559         (match_operand:SF 1 "general_operand"  "r,mE,r"))]
6560   "TARGET_32BIT
6561    && TARGET_SOFT_FLOAT
6562    && (GET_CODE (operands[0]) != MEM
6563        || register_operand (operands[1], SFmode))"
6564   "@
6565    mov%?\\t%0, %1
6566    ldr%?\\t%0, %1\\t%@ float
6567    str%?\\t%1, %0\\t%@ float"
6568   [(set_attr "predicable" "yes")
6569    (set_attr "type" "*,load1,store1")
6570    (set_attr "insn" "mov,*,*")
6571    (set_attr "pool_range" "*,4096,*")
6572    (set_attr "arm_neg_pool_range" "*,4084,*")
6573    (set_attr "thumb2_neg_pool_range" "*,0,*")]
6576 ;;; ??? This should have alternatives for constants.
6577 (define_insn "*thumb1_movsf_insn"
6578   [(set (match_operand:SF     0 "nonimmediate_operand" "=l,l,>,l, m,*r,*h")
6579         (match_operand:SF     1 "general_operand"      "l, >,l,mF,l,*h,*r"))]
6580   "TARGET_THUMB1
6581    && (   register_operand (operands[0], SFmode) 
6582        || register_operand (operands[1], SFmode))"
6583   "@
6584    add\\t%0, %1, #0
6585    ldmia\\t%1, {%0}
6586    stmia\\t%0, {%1}
6587    ldr\\t%0, %1
6588    str\\t%1, %0
6589    mov\\t%0, %1
6590    mov\\t%0, %1"
6591   [(set_attr "length" "2")
6592    (set_attr "type" "*,load1,store1,load1,store1,*,*")
6593    (set_attr "pool_range" "*,*,*,1020,*,*,*")
6594    (set_attr "insn" "*,*,*,*,*,mov,mov")
6595    (set_attr "conds" "clob,nocond,nocond,nocond,nocond,nocond,nocond")]
6598 (define_expand "movdf"
6599   [(set (match_operand:DF 0 "general_operand" "")
6600         (match_operand:DF 1 "general_operand" ""))]
6601   "TARGET_EITHER"
6602   "
6603   if (TARGET_32BIT)
6604     {
6605       if (GET_CODE (operands[0]) == MEM)
6606         operands[1] = force_reg (DFmode, operands[1]);
6607     }
6608   else /* TARGET_THUMB */
6609     {
6610       if (can_create_pseudo_p ())
6611         {
6612           if (GET_CODE (operands[0]) != REG)
6613             operands[1] = force_reg (DFmode, operands[1]);
6614         }
6615     }
6616   "
6619 ;; Reloading a df mode value stored in integer regs to memory can require a
6620 ;; scratch reg.
6621 (define_expand "reload_outdf"
6622   [(match_operand:DF 0 "arm_reload_memory_operand" "=o")
6623    (match_operand:DF 1 "s_register_operand" "r")
6624    (match_operand:SI 2 "s_register_operand" "=&r")]
6625   "TARGET_THUMB2"
6626   "
6627   {
6628     enum rtx_code code = GET_CODE (XEXP (operands[0], 0));
6630     if (code == REG)
6631       operands[2] = XEXP (operands[0], 0);
6632     else if (code == POST_INC || code == PRE_DEC)
6633       {
6634         operands[0] = gen_rtx_SUBREG (DImode, operands[0], 0);
6635         operands[1] = gen_rtx_SUBREG (DImode, operands[1], 0);
6636         emit_insn (gen_movdi (operands[0], operands[1]));
6637         DONE;
6638       }
6639     else if (code == PRE_INC)
6640       {
6641         rtx reg = XEXP (XEXP (operands[0], 0), 0);
6643         emit_insn (gen_addsi3 (reg, reg, GEN_INT (8)));
6644         operands[2] = reg;
6645       }
6646     else if (code == POST_DEC)
6647       operands[2] = XEXP (XEXP (operands[0], 0), 0);
6648     else
6649       emit_insn (gen_addsi3 (operands[2], XEXP (XEXP (operands[0], 0), 0),
6650                              XEXP (XEXP (operands[0], 0), 1)));
6652     emit_insn (gen_rtx_SET (VOIDmode,
6653                             replace_equiv_address (operands[0], operands[2]),
6654                             operands[1]));
6656     if (code == POST_DEC)
6657       emit_insn (gen_addsi3 (operands[2], operands[2], GEN_INT (-8)));
6659     DONE;
6660   }"
6663 (define_insn "*movdf_soft_insn"
6664   [(set (match_operand:DF 0 "nonimmediate_soft_df_operand" "=r,r,r,r,m")
6665         (match_operand:DF 1 "soft_df_operand" "rDa,Db,Dc,mF,r"))]
6666   "TARGET_32BIT && TARGET_SOFT_FLOAT
6667    && (   register_operand (operands[0], DFmode)
6668        || register_operand (operands[1], DFmode))"
6669   "*
6670   switch (which_alternative)
6671     {
6672     case 0:
6673     case 1:
6674     case 2:
6675       return \"#\";
6676     default:
6677       return output_move_double (operands, true, NULL);
6678     }
6679   "
6680   [(set_attr "length" "8,12,16,8,8")
6681    (set_attr "type" "*,*,*,load2,store2")
6682    (set_attr "pool_range" "*,*,*,1020,*")
6683    (set_attr "arm_neg_pool_range" "*,*,*,1004,*")
6684    (set_attr "thumb2_neg_pool_range" "*,*,*,0,*")]
6687 ;;; ??? This should have alternatives for constants.
6688 ;;; ??? This was originally identical to the movdi_insn pattern.
6689 ;;; ??? The 'F' constraint looks funny, but it should always be replaced by
6690 ;;; thumb_reorg with a memory reference.
6691 (define_insn "*thumb_movdf_insn"
6692   [(set (match_operand:DF 0 "nonimmediate_operand" "=l,l,>,l, m,*r")
6693         (match_operand:DF 1 "general_operand"      "l, >,l,mF,l,*r"))]
6694   "TARGET_THUMB1
6695    && (   register_operand (operands[0], DFmode)
6696        || register_operand (operands[1], DFmode))"
6697   "*
6698   switch (which_alternative)
6699     {
6700     default:
6701     case 0:
6702       if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
6703         return \"add\\t%0, %1, #0\;add\\t%H0, %H1, #0\";
6704       return \"add\\t%H0, %H1, #0\;add\\t%0, %1, #0\";
6705     case 1:
6706       return \"ldmia\\t%1, {%0, %H0}\";
6707     case 2:
6708       return \"stmia\\t%0, {%1, %H1}\";
6709     case 3:
6710       return thumb_load_double_from_address (operands);
6711     case 4:
6712       operands[2] = gen_rtx_MEM (SImode,
6713                                  plus_constant (Pmode,
6714                                                 XEXP (operands[0], 0), 4));
6715       output_asm_insn (\"str\\t%1, %0\;str\\t%H1, %2\", operands);
6716       return \"\";
6717     case 5:
6718       if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
6719         return \"mov\\t%0, %1\;mov\\t%H0, %H1\";
6720       return \"mov\\t%H0, %H1\;mov\\t%0, %1\";
6721     }
6722   "
6723   [(set_attr "length" "4,2,2,6,4,4")
6724    (set_attr "type" "*,load2,store2,load2,store2,*")
6725    (set_attr "insn" "*,*,*,*,*,mov")
6726    (set_attr "pool_range" "*,*,*,1020,*,*")]
6730 ;; load- and store-multiple insns
6731 ;; The arm can load/store any set of registers, provided that they are in
6732 ;; ascending order, but these expanders assume a contiguous set.
6734 (define_expand "load_multiple"
6735   [(match_par_dup 3 [(set (match_operand:SI 0 "" "")
6736                           (match_operand:SI 1 "" ""))
6737                      (use (match_operand:SI 2 "" ""))])]
6738   "TARGET_32BIT"
6740   HOST_WIDE_INT offset = 0;
6742   /* Support only fixed point registers.  */
6743   if (GET_CODE (operands[2]) != CONST_INT
6744       || INTVAL (operands[2]) > 14
6745       || INTVAL (operands[2]) < 2
6746       || GET_CODE (operands[1]) != MEM
6747       || GET_CODE (operands[0]) != REG
6748       || REGNO (operands[0]) > (LAST_ARM_REGNUM - 1)
6749       || REGNO (operands[0]) + INTVAL (operands[2]) > LAST_ARM_REGNUM)
6750     FAIL;
6752   operands[3]
6753     = arm_gen_load_multiple (arm_regs_in_sequence + REGNO (operands[0]),
6754                              INTVAL (operands[2]),
6755                              force_reg (SImode, XEXP (operands[1], 0)),
6756                              FALSE, operands[1], &offset);
6759 (define_expand "store_multiple"
6760   [(match_par_dup 3 [(set (match_operand:SI 0 "" "")
6761                           (match_operand:SI 1 "" ""))
6762                      (use (match_operand:SI 2 "" ""))])]
6763   "TARGET_32BIT"
6765   HOST_WIDE_INT offset = 0;
6767   /* Support only fixed point registers.  */
6768   if (GET_CODE (operands[2]) != CONST_INT
6769       || INTVAL (operands[2]) > 14
6770       || INTVAL (operands[2]) < 2
6771       || GET_CODE (operands[1]) != REG
6772       || GET_CODE (operands[0]) != MEM
6773       || REGNO (operands[1]) > (LAST_ARM_REGNUM - 1)
6774       || REGNO (operands[1]) + INTVAL (operands[2]) > LAST_ARM_REGNUM)
6775     FAIL;
6777   operands[3]
6778     = arm_gen_store_multiple (arm_regs_in_sequence + REGNO (operands[1]),
6779                               INTVAL (operands[2]),
6780                               force_reg (SImode, XEXP (operands[0], 0)),
6781                               FALSE, operands[0], &offset);
6785 ;; Move a block of memory if it is word aligned and MORE than 2 words long.
6786 ;; We could let this apply for blocks of less than this, but it clobbers so
6787 ;; many registers that there is then probably a better way.
6789 (define_expand "movmemqi"
6790   [(match_operand:BLK 0 "general_operand" "")
6791    (match_operand:BLK 1 "general_operand" "")
6792    (match_operand:SI 2 "const_int_operand" "")
6793    (match_operand:SI 3 "const_int_operand" "")]
6794   "TARGET_EITHER"
6795   "
6796   if (TARGET_32BIT)
6797     {
6798       if (arm_gen_movmemqi (operands))
6799         DONE;
6800       FAIL;
6801     }
6802   else /* TARGET_THUMB1 */
6803     {
6804       if (   INTVAL (operands[3]) != 4
6805           || INTVAL (operands[2]) > 48)
6806         FAIL;
6808       thumb_expand_movmemqi (operands);
6809       DONE;
6810     }
6811   "
6814 ;; Thumb block-move insns
6816 (define_insn "movmem12b"
6817   [(set (mem:SI (match_operand:SI 2 "register_operand" "0"))
6818         (mem:SI (match_operand:SI 3 "register_operand" "1")))
6819    (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
6820         (mem:SI (plus:SI (match_dup 3) (const_int 4))))
6821    (set (mem:SI (plus:SI (match_dup 2) (const_int 8)))
6822         (mem:SI (plus:SI (match_dup 3) (const_int 8))))
6823    (set (match_operand:SI 0 "register_operand" "=l")
6824         (plus:SI (match_dup 2) (const_int 12)))
6825    (set (match_operand:SI 1 "register_operand" "=l")
6826         (plus:SI (match_dup 3) (const_int 12)))
6827    (clobber (match_scratch:SI 4 "=&l"))
6828    (clobber (match_scratch:SI 5 "=&l"))
6829    (clobber (match_scratch:SI 6 "=&l"))]
6830   "TARGET_THUMB1"
6831   "* return thumb_output_move_mem_multiple (3, operands);"
6832   [(set_attr "length" "4")
6833    ; This isn't entirely accurate...  It loads as well, but in terms of
6834    ; scheduling the following insn it is better to consider it as a store
6835    (set_attr "type" "store3")]
6838 (define_insn "movmem8b"
6839   [(set (mem:SI (match_operand:SI 2 "register_operand" "0"))
6840         (mem:SI (match_operand:SI 3 "register_operand" "1")))
6841    (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
6842         (mem:SI (plus:SI (match_dup 3) (const_int 4))))
6843    (set (match_operand:SI 0 "register_operand" "=l")
6844         (plus:SI (match_dup 2) (const_int 8)))
6845    (set (match_operand:SI 1 "register_operand" "=l")
6846         (plus:SI (match_dup 3) (const_int 8)))
6847    (clobber (match_scratch:SI 4 "=&l"))
6848    (clobber (match_scratch:SI 5 "=&l"))]
6849   "TARGET_THUMB1"
6850   "* return thumb_output_move_mem_multiple (2, operands);"
6851   [(set_attr "length" "4")
6852    ; This isn't entirely accurate...  It loads as well, but in terms of
6853    ; scheduling the following insn it is better to consider it as a store
6854    (set_attr "type" "store2")]
6859 ;; Compare & branch insns
6860 ;; The range calculations are based as follows:
6861 ;; For forward branches, the address calculation returns the address of
6862 ;; the next instruction.  This is 2 beyond the branch instruction.
6863 ;; For backward branches, the address calculation returns the address of
6864 ;; the first instruction in this pattern (cmp).  This is 2 before the branch
6865 ;; instruction for the shortest sequence, and 4 before the branch instruction
6866 ;; if we have to jump around an unconditional branch.
6867 ;; To the basic branch range the PC offset must be added (this is +4).
6868 ;; So for forward branches we have 
6869 ;;   (pos_range - pos_base_offs + pc_offs) = (pos_range - 2 + 4).
6870 ;; And for backward branches we have 
6871 ;;   (neg_range - neg_base_offs + pc_offs) = (neg_range - (-2 or -4) + 4).
6873 ;; For a 'b'       pos_range = 2046, neg_range = -2048 giving (-2040->2048).
6874 ;; For a 'b<cond>' pos_range = 254,  neg_range = -256  giving (-250 ->256).
6876 (define_expand "cbranchsi4"
6877   [(set (pc) (if_then_else
6878               (match_operator 0 "expandable_comparison_operator"
6879                [(match_operand:SI 1 "s_register_operand" "")
6880                 (match_operand:SI 2 "nonmemory_operand" "")])
6881               (label_ref (match_operand 3 "" ""))
6882               (pc)))]
6883   "TARGET_EITHER"
6884   "
6885   if (!TARGET_THUMB1)
6886     {
6887       if (!arm_validize_comparison (&operands[0], &operands[1], &operands[2]))
6888         FAIL;
6889       emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
6890                                       operands[3]));
6891       DONE;
6892     }
6893   if (thumb1_cmpneg_operand (operands[2], SImode))
6894     {
6895       emit_jump_insn (gen_cbranchsi4_scratch (NULL, operands[1], operands[2],
6896                                               operands[3], operands[0]));
6897       DONE;
6898     }
6899   if (!thumb1_cmp_operand (operands[2], SImode))
6900     operands[2] = force_reg (SImode, operands[2]);
6901   ")
6903 ;; A pattern to recognize a special situation and optimize for it.
6904 ;; On the thumb, zero-extension from memory is preferrable to sign-extension
6905 ;; due to the available addressing modes.  Hence, convert a signed comparison
6906 ;; with zero into an unsigned comparison with 127 if possible.
6907 (define_expand "cbranchqi4"
6908   [(set (pc) (if_then_else
6909               (match_operator 0 "lt_ge_comparison_operator"
6910                [(match_operand:QI 1 "memory_operand" "")
6911                 (match_operand:QI 2 "const0_operand" "")])
6912               (label_ref (match_operand 3 "" ""))
6913               (pc)))]
6914   "TARGET_THUMB1"
6916   rtx xops[4];
6917   xops[1] = gen_reg_rtx (SImode);
6918   emit_insn (gen_zero_extendqisi2 (xops[1], operands[1]));
6919   xops[2] = GEN_INT (127);
6920   xops[0] = gen_rtx_fmt_ee (GET_CODE (operands[0]) == GE ? LEU : GTU,
6921                             VOIDmode, xops[1], xops[2]);
6922   xops[3] = operands[3];
6923   emit_insn (gen_cbranchsi4 (xops[0], xops[1], xops[2], xops[3]));
6924   DONE;
6927 (define_expand "cbranchsf4"
6928   [(set (pc) (if_then_else
6929               (match_operator 0 "expandable_comparison_operator"
6930                [(match_operand:SF 1 "s_register_operand" "")
6931                 (match_operand:SF 2 "arm_float_compare_operand" "")])
6932               (label_ref (match_operand 3 "" ""))
6933               (pc)))]
6934   "TARGET_32BIT && TARGET_HARD_FLOAT"
6935   "emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
6936                                    operands[3])); DONE;"
6939 (define_expand "cbranchdf4"
6940   [(set (pc) (if_then_else
6941               (match_operator 0 "expandable_comparison_operator"
6942                [(match_operand:DF 1 "s_register_operand" "")
6943                 (match_operand:DF 2 "arm_float_compare_operand" "")])
6944               (label_ref (match_operand 3 "" ""))
6945               (pc)))]
6946   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
6947   "emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
6948                                    operands[3])); DONE;"
6951 (define_expand "cbranchdi4"
6952   [(set (pc) (if_then_else
6953               (match_operator 0 "expandable_comparison_operator"
6954                [(match_operand:DI 1 "cmpdi_operand" "")
6955                 (match_operand:DI 2 "cmpdi_operand" "")])
6956               (label_ref (match_operand 3 "" ""))
6957               (pc)))]
6958   "TARGET_32BIT"
6959   "{
6960      /* We should not have two constants.  */
6961      gcc_assert (GET_MODE (operands[1]) == DImode
6962                  || GET_MODE (operands[2]) == DImode);
6964      if (!arm_validize_comparison (&operands[0], &operands[1], &operands[2]))            
6965        FAIL;
6966      emit_jump_insn (gen_cbranch_cc (operands[0], operands[1], operands[2],
6967                                        operands[3]));
6968      DONE;
6969    }"
6972 (define_insn "cbranchsi4_insn"
6973   [(set (pc) (if_then_else
6974               (match_operator 0 "arm_comparison_operator"
6975                [(match_operand:SI 1 "s_register_operand" "l,l*h")
6976                 (match_operand:SI 2 "thumb1_cmp_operand" "lI*h,*r")])
6977               (label_ref (match_operand 3 "" ""))
6978               (pc)))]
6979   "TARGET_THUMB1"
6981   rtx t = cfun->machine->thumb1_cc_insn;
6982   if (t != NULL_RTX)
6983     {
6984       if (!rtx_equal_p (cfun->machine->thumb1_cc_op0, operands[1])
6985           || !rtx_equal_p (cfun->machine->thumb1_cc_op1, operands[2]))
6986         t = NULL_RTX;
6987       if (cfun->machine->thumb1_cc_mode == CC_NOOVmode)
6988         {
6989           if (!noov_comparison_operator (operands[0], VOIDmode))
6990             t = NULL_RTX;
6991         }
6992       else if (cfun->machine->thumb1_cc_mode != CCmode)
6993         t = NULL_RTX;
6994     }
6995   if (t == NULL_RTX)
6996     {
6997       output_asm_insn ("cmp\t%1, %2", operands);
6998       cfun->machine->thumb1_cc_insn = insn;
6999       cfun->machine->thumb1_cc_op0 = operands[1];
7000       cfun->machine->thumb1_cc_op1 = operands[2];
7001       cfun->machine->thumb1_cc_mode = CCmode;
7002     }
7003   else
7004     /* Ensure we emit the right type of condition code on the jump.  */
7005     XEXP (operands[0], 0) = gen_rtx_REG (cfun->machine->thumb1_cc_mode,
7006                                          CC_REGNUM);
7008   switch (get_attr_length (insn))
7009     {
7010     case 4:  return \"b%d0\\t%l3\";
7011     case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
7012     default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
7013     }
7015   [(set (attr "far_jump")
7016         (if_then_else
7017             (eq_attr "length" "8")
7018             (const_string "yes")
7019             (const_string "no")))
7020    (set (attr "length") 
7021         (if_then_else
7022             (and (ge (minus (match_dup 3) (pc)) (const_int -250))
7023                  (le (minus (match_dup 3) (pc)) (const_int 256)))
7024             (const_int 4)
7025             (if_then_else
7026                 (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
7027                      (le (minus (match_dup 3) (pc)) (const_int 2048)))
7028                 (const_int 6)
7029                 (const_int 8))))]
7032 (define_insn "cbranchsi4_scratch"
7033   [(set (pc) (if_then_else
7034               (match_operator 4 "arm_comparison_operator"
7035                [(match_operand:SI 1 "s_register_operand" "l,0")
7036                 (match_operand:SI 2 "thumb1_cmpneg_operand" "L,J")])
7037               (label_ref (match_operand 3 "" ""))
7038               (pc)))
7039    (clobber (match_scratch:SI 0 "=l,l"))]
7040   "TARGET_THUMB1"
7041   "*
7042   output_asm_insn (\"add\\t%0, %1, #%n2\", operands);
7044   switch (get_attr_length (insn))
7045     {
7046     case 4:  return \"b%d4\\t%l3\";
7047     case 6:  return \"b%D4\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
7048     default: return \"b%D4\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
7049     }
7050   "
7051   [(set (attr "far_jump")
7052         (if_then_else
7053             (eq_attr "length" "8")
7054             (const_string "yes")
7055             (const_string "no")))
7056    (set (attr "length") 
7057         (if_then_else
7058             (and (ge (minus (match_dup 3) (pc)) (const_int -250))
7059                  (le (minus (match_dup 3) (pc)) (const_int 256)))
7060             (const_int 4)
7061             (if_then_else
7062                 (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
7063                      (le (minus (match_dup 3) (pc)) (const_int 2048)))
7064                 (const_int 6)
7065                 (const_int 8))))]
7068 ;; Two peepholes to generate subtract of 0 instead of a move if the
7069 ;; condition codes will be useful.
7070 (define_peephole2
7071   [(set (match_operand:SI 0 "low_register_operand" "")
7072         (match_operand:SI 1 "low_register_operand" ""))
7073    (set (pc)
7074         (if_then_else (match_operator 2 "arm_comparison_operator"
7075                        [(match_dup 1) (const_int 0)])
7076                       (label_ref (match_operand 3 "" ""))
7077                       (pc)))]
7078   "TARGET_THUMB1"
7079   [(set (match_dup 0) (minus:SI (match_dup 1) (const_int 0)))
7080    (set (pc)
7081         (if_then_else (match_op_dup 2 [(match_dup 0) (const_int 0)])
7082                       (label_ref (match_dup 3))
7083                       (pc)))]
7084   "")
7086 ;; Sigh!  This variant shouldn't be needed, but combine often fails to
7087 ;; merge cases like this because the op1 is a hard register in
7088 ;; arm_class_likely_spilled_p.
7089 (define_peephole2
7090   [(set (match_operand:SI 0 "low_register_operand" "")
7091         (match_operand:SI 1 "low_register_operand" ""))
7092    (set (pc)
7093         (if_then_else (match_operator 2 "arm_comparison_operator"
7094                        [(match_dup 0) (const_int 0)])
7095                       (label_ref (match_operand 3 "" ""))
7096                       (pc)))]
7097   "TARGET_THUMB1"
7098   [(set (match_dup 0) (minus:SI (match_dup 1) (const_int 0)))
7099    (set (pc)
7100         (if_then_else (match_op_dup 2 [(match_dup 0) (const_int 0)])
7101                       (label_ref (match_dup 3))
7102                       (pc)))]
7103   "")
7105 (define_insn "*negated_cbranchsi4"
7106   [(set (pc)
7107         (if_then_else
7108          (match_operator 0 "equality_operator"
7109           [(match_operand:SI 1 "s_register_operand" "l")
7110            (neg:SI (match_operand:SI 2 "s_register_operand" "l"))])
7111          (label_ref (match_operand 3 "" ""))
7112          (pc)))]
7113   "TARGET_THUMB1"
7114   "*
7115   output_asm_insn (\"cmn\\t%1, %2\", operands);
7116   switch (get_attr_length (insn))
7117     {
7118     case 4:  return \"b%d0\\t%l3\";
7119     case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
7120     default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
7121     }
7122   "
7123   [(set (attr "far_jump")
7124         (if_then_else
7125             (eq_attr "length" "8")
7126             (const_string "yes")
7127             (const_string "no")))
7128    (set (attr "length") 
7129         (if_then_else
7130             (and (ge (minus (match_dup 3) (pc)) (const_int -250))
7131                  (le (minus (match_dup 3) (pc)) (const_int 256)))
7132             (const_int 4)
7133             (if_then_else
7134                 (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
7135                      (le (minus (match_dup 3) (pc)) (const_int 2048)))
7136                 (const_int 6)
7137                 (const_int 8))))]
7140 (define_insn "*tbit_cbranch"
7141   [(set (pc)
7142         (if_then_else
7143          (match_operator 0 "equality_operator"
7144           [(zero_extract:SI (match_operand:SI 1 "s_register_operand" "l")
7145                             (const_int 1)
7146                             (match_operand:SI 2 "const_int_operand" "i"))
7147            (const_int 0)])
7148          (label_ref (match_operand 3 "" ""))
7149          (pc)))
7150    (clobber (match_scratch:SI 4 "=l"))]
7151   "TARGET_THUMB1"
7152   "*
7153   {
7154   rtx op[3];
7155   op[0] = operands[4];
7156   op[1] = operands[1];
7157   op[2] = GEN_INT (32 - 1 - INTVAL (operands[2]));
7159   output_asm_insn (\"lsl\\t%0, %1, %2\", op);
7160   switch (get_attr_length (insn))
7161     {
7162     case 4:  return \"b%d0\\t%l3\";
7163     case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
7164     default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
7165     }
7166   }"
7167   [(set (attr "far_jump")
7168         (if_then_else
7169             (eq_attr "length" "8")
7170             (const_string "yes")
7171             (const_string "no")))
7172    (set (attr "length") 
7173         (if_then_else
7174             (and (ge (minus (match_dup 3) (pc)) (const_int -250))
7175                  (le (minus (match_dup 3) (pc)) (const_int 256)))
7176             (const_int 4)
7177             (if_then_else
7178                 (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
7179                      (le (minus (match_dup 3) (pc)) (const_int 2048)))
7180                 (const_int 6)
7181                 (const_int 8))))]
7183   
7184 (define_insn "*tlobits_cbranch"
7185   [(set (pc)
7186         (if_then_else
7187          (match_operator 0 "equality_operator"
7188           [(zero_extract:SI (match_operand:SI 1 "s_register_operand" "l")
7189                             (match_operand:SI 2 "const_int_operand" "i")
7190                             (const_int 0))
7191            (const_int 0)])
7192          (label_ref (match_operand 3 "" ""))
7193          (pc)))
7194    (clobber (match_scratch:SI 4 "=l"))]
7195   "TARGET_THUMB1"
7196   "*
7197   {
7198   rtx op[3];
7199   op[0] = operands[4];
7200   op[1] = operands[1];
7201   op[2] = GEN_INT (32 - INTVAL (operands[2]));
7203   output_asm_insn (\"lsl\\t%0, %1, %2\", op);
7204   switch (get_attr_length (insn))
7205     {
7206     case 4:  return \"b%d0\\t%l3\";
7207     case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
7208     default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
7209     }
7210   }"
7211   [(set (attr "far_jump")
7212         (if_then_else
7213             (eq_attr "length" "8")
7214             (const_string "yes")
7215             (const_string "no")))
7216    (set (attr "length") 
7217         (if_then_else
7218             (and (ge (minus (match_dup 3) (pc)) (const_int -250))
7219                  (le (minus (match_dup 3) (pc)) (const_int 256)))
7220             (const_int 4)
7221             (if_then_else
7222                 (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
7223                      (le (minus (match_dup 3) (pc)) (const_int 2048)))
7224                 (const_int 6)
7225                 (const_int 8))))]
7228 (define_insn "*tstsi3_cbranch"
7229   [(set (pc)
7230         (if_then_else
7231          (match_operator 3 "equality_operator"
7232           [(and:SI (match_operand:SI 0 "s_register_operand" "%l")
7233                    (match_operand:SI 1 "s_register_operand" "l"))
7234            (const_int 0)])
7235          (label_ref (match_operand 2 "" ""))
7236          (pc)))]
7237   "TARGET_THUMB1"
7238   "*
7239   {
7240   output_asm_insn (\"tst\\t%0, %1\", operands);
7241   switch (get_attr_length (insn))
7242     {
7243     case 4:  return \"b%d3\\t%l2\";
7244     case 6:  return \"b%D3\\t.LCB%=\;b\\t%l2\\t%@long jump\\n.LCB%=:\";
7245     default: return \"b%D3\\t.LCB%=\;bl\\t%l2\\t%@far jump\\n.LCB%=:\";
7246     }
7247   }"
7248   [(set (attr "far_jump")
7249         (if_then_else
7250             (eq_attr "length" "8")
7251             (const_string "yes")
7252             (const_string "no")))
7253    (set (attr "length") 
7254         (if_then_else
7255             (and (ge (minus (match_dup 2) (pc)) (const_int -250))
7256                  (le (minus (match_dup 2) (pc)) (const_int 256)))
7257             (const_int 4)
7258             (if_then_else
7259                 (and (ge (minus (match_dup 2) (pc)) (const_int -2040))
7260                      (le (minus (match_dup 2) (pc)) (const_int 2048)))
7261                 (const_int 6)
7262                 (const_int 8))))]
7264   
7265 (define_insn "*cbranchne_decr1"
7266   [(set (pc)
7267         (if_then_else (match_operator 3 "equality_operator"
7268                        [(match_operand:SI 2 "s_register_operand" "l,l,1,l")
7269                         (const_int 0)])
7270                       (label_ref (match_operand 4 "" ""))
7271                       (pc)))
7272    (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,*?h,*?m,*?m")
7273         (plus:SI (match_dup 2) (const_int -1)))
7274    (clobber (match_scratch:SI 1 "=X,l,&l,&l"))]
7275   "TARGET_THUMB1"
7276   "*
7277    {
7278      rtx cond[2];
7279      cond[0] = gen_rtx_fmt_ee ((GET_CODE (operands[3]) == NE
7280                                 ? GEU : LTU),
7281                                VOIDmode, operands[2], const1_rtx);
7282      cond[1] = operands[4];
7284      if (which_alternative == 0)
7285        output_asm_insn (\"sub\\t%0, %2, #1\", operands);
7286      else if (which_alternative == 1)
7287        {
7288          /* We must provide an alternative for a hi reg because reload 
7289             cannot handle output reloads on a jump instruction, but we
7290             can't subtract into that.  Fortunately a mov from lo to hi
7291             does not clobber the condition codes.  */
7292          output_asm_insn (\"sub\\t%1, %2, #1\", operands);
7293          output_asm_insn (\"mov\\t%0, %1\", operands);
7294        }
7295      else
7296        {
7297          /* Similarly, but the target is memory.  */
7298          output_asm_insn (\"sub\\t%1, %2, #1\", operands);
7299          output_asm_insn (\"str\\t%1, %0\", operands);
7300        }
7302      switch (get_attr_length (insn) - (which_alternative ? 2 : 0))
7303        {
7304          case 4:
7305            output_asm_insn (\"b%d0\\t%l1\", cond);
7306            return \"\";
7307          case 6:
7308            output_asm_insn (\"b%D0\\t.LCB%=\", cond);
7309            return \"b\\t%l4\\t%@long jump\\n.LCB%=:\";
7310          default:
7311            output_asm_insn (\"b%D0\\t.LCB%=\", cond);
7312            return \"bl\\t%l4\\t%@far jump\\n.LCB%=:\";
7313        }
7314    }
7315   "
7316   [(set (attr "far_jump")
7317         (if_then_else
7318             (ior (and (eq (symbol_ref ("which_alternative"))
7319                           (const_int 0))
7320                       (eq_attr "length" "8"))
7321                  (eq_attr "length" "10"))
7322             (const_string "yes")
7323             (const_string "no")))
7324    (set_attr_alternative "length"
7325       [
7326        ;; Alternative 0
7327        (if_then_else
7328          (and (ge (minus (match_dup 4) (pc)) (const_int -250))
7329               (le (minus (match_dup 4) (pc)) (const_int 256)))
7330          (const_int 4)
7331          (if_then_else
7332            (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
7333                 (le (minus (match_dup 4) (pc)) (const_int 2048)))
7334            (const_int 6)
7335            (const_int 8)))
7336        ;; Alternative 1
7337        (if_then_else
7338          (and (ge (minus (match_dup 4) (pc)) (const_int -248))
7339               (le (minus (match_dup 4) (pc)) (const_int 256)))
7340          (const_int 6)
7341          (if_then_else
7342            (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
7343                 (le (minus (match_dup 4) (pc)) (const_int 2048)))
7344            (const_int 8)
7345            (const_int 10)))
7346        ;; Alternative 2
7347        (if_then_else
7348          (and (ge (minus (match_dup 4) (pc)) (const_int -248))
7349               (le (minus (match_dup 4) (pc)) (const_int 256)))
7350          (const_int 6)
7351          (if_then_else
7352            (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
7353                 (le (minus (match_dup 4) (pc)) (const_int 2048)))
7354            (const_int 8)
7355            (const_int 10)))
7356        ;; Alternative 3
7357        (if_then_else
7358          (and (ge (minus (match_dup 4) (pc)) (const_int -248))
7359               (le (minus (match_dup 4) (pc)) (const_int 256)))
7360          (const_int 6)
7361          (if_then_else
7362            (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
7363                 (le (minus (match_dup 4) (pc)) (const_int 2048)))
7364            (const_int 8)
7365            (const_int 10)))])]
7368 (define_insn "*addsi3_cbranch"
7369   [(set (pc)
7370         (if_then_else
7371          (match_operator 4 "arm_comparison_operator"
7372           [(plus:SI
7373             (match_operand:SI 2 "s_register_operand" "%0,l,*l,1,1,1")
7374             (match_operand:SI 3 "reg_or_int_operand" "IJ,lL,*l,lIJ,lIJ,lIJ"))
7375            (const_int 0)])
7376          (label_ref (match_operand 5 "" ""))
7377          (pc)))
7378    (set
7379     (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,l,*!h,*?h,*?m,*?m")
7380     (plus:SI (match_dup 2) (match_dup 3)))
7381    (clobber (match_scratch:SI 1 "=X,X,l,l,&l,&l"))]
7382   "TARGET_THUMB1
7383    && (GET_CODE (operands[4]) == EQ
7384        || GET_CODE (operands[4]) == NE
7385        || GET_CODE (operands[4]) == GE
7386        || GET_CODE (operands[4]) == LT)"
7387   "*
7388    {
7389      rtx cond[3];
7391      cond[0] = (which_alternative < 2) ? operands[0] : operands[1];
7392      cond[1] = operands[2];
7393      cond[2] = operands[3];
7395      if (GET_CODE (cond[2]) == CONST_INT && INTVAL (cond[2]) < 0)
7396        output_asm_insn (\"sub\\t%0, %1, #%n2\", cond);
7397      else
7398        output_asm_insn (\"add\\t%0, %1, %2\", cond);
7400      if (which_alternative >= 2
7401          && which_alternative < 4)
7402        output_asm_insn (\"mov\\t%0, %1\", operands);
7403      else if (which_alternative >= 4)
7404        output_asm_insn (\"str\\t%1, %0\", operands);
7406      switch (get_attr_length (insn) - ((which_alternative >= 2) ? 2 : 0))
7407        {
7408          case 4:
7409            return \"b%d4\\t%l5\";
7410          case 6:
7411            return \"b%D4\\t.LCB%=\;b\\t%l5\\t%@long jump\\n.LCB%=:\";
7412          default:
7413            return \"b%D4\\t.LCB%=\;bl\\t%l5\\t%@far jump\\n.LCB%=:\";
7414        }
7415    }
7416   "
7417   [(set (attr "far_jump")
7418         (if_then_else
7419             (ior (and (lt (symbol_ref ("which_alternative"))
7420                           (const_int 2))
7421                       (eq_attr "length" "8"))
7422                  (eq_attr "length" "10"))
7423             (const_string "yes")
7424             (const_string "no")))
7425    (set (attr "length")
7426      (if_then_else
7427        (lt (symbol_ref ("which_alternative"))
7428                        (const_int 2))
7429        (if_then_else
7430          (and (ge (minus (match_dup 5) (pc)) (const_int -250))
7431               (le (minus (match_dup 5) (pc)) (const_int 256)))
7432          (const_int 4)
7433          (if_then_else
7434            (and (ge (minus (match_dup 5) (pc)) (const_int -2040))
7435                 (le (minus (match_dup 5) (pc)) (const_int 2048)))
7436            (const_int 6)
7437            (const_int 8)))
7438        (if_then_else
7439          (and (ge (minus (match_dup 5) (pc)) (const_int -248))
7440               (le (minus (match_dup 5) (pc)) (const_int 256)))
7441          (const_int 6)
7442          (if_then_else
7443            (and (ge (minus (match_dup 5) (pc)) (const_int -2038))
7444                 (le (minus (match_dup 5) (pc)) (const_int 2048)))
7445            (const_int 8)
7446            (const_int 10)))))]
7449 (define_insn "*addsi3_cbranch_scratch"
7450   [(set (pc)
7451         (if_then_else
7452          (match_operator 3 "arm_comparison_operator"
7453           [(plus:SI
7454             (match_operand:SI 1 "s_register_operand" "%l,l,l,0")
7455             (match_operand:SI 2 "reg_or_int_operand" "J,l,L,IJ"))
7456            (const_int 0)])
7457          (label_ref (match_operand 4 "" ""))
7458          (pc)))
7459    (clobber (match_scratch:SI 0 "=X,X,l,l"))]
7460   "TARGET_THUMB1
7461    && (GET_CODE (operands[3]) == EQ
7462        || GET_CODE (operands[3]) == NE
7463        || GET_CODE (operands[3]) == GE
7464        || GET_CODE (operands[3]) == LT)"
7465   "*
7466    {
7467      switch (which_alternative)
7468        {
7469        case 0:
7470          output_asm_insn (\"cmp\t%1, #%n2\", operands);
7471          break;
7472        case 1:
7473          output_asm_insn (\"cmn\t%1, %2\", operands);
7474          break;
7475        case 2:
7476          if (INTVAL (operands[2]) < 0)
7477            output_asm_insn (\"sub\t%0, %1, %2\", operands);
7478          else
7479            output_asm_insn (\"add\t%0, %1, %2\", operands);
7480          break;
7481        case 3:
7482          if (INTVAL (operands[2]) < 0)
7483            output_asm_insn (\"sub\t%0, %0, %2\", operands);
7484          else
7485            output_asm_insn (\"add\t%0, %0, %2\", operands);
7486          break;
7487        }
7489      switch (get_attr_length (insn))
7490        {
7491          case 4:
7492            return \"b%d3\\t%l4\";
7493          case 6:
7494            return \"b%D3\\t.LCB%=\;b\\t%l4\\t%@long jump\\n.LCB%=:\";
7495          default:
7496            return \"b%D3\\t.LCB%=\;bl\\t%l4\\t%@far jump\\n.LCB%=:\";
7497        }
7498    }
7499   "
7500   [(set (attr "far_jump")
7501         (if_then_else
7502             (eq_attr "length" "8")
7503             (const_string "yes")
7504             (const_string "no")))
7505    (set (attr "length")
7506        (if_then_else
7507          (and (ge (minus (match_dup 4) (pc)) (const_int -250))
7508               (le (minus (match_dup 4) (pc)) (const_int 256)))
7509          (const_int 4)
7510          (if_then_else
7511            (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
7512                 (le (minus (match_dup 4) (pc)) (const_int 2048)))
7513            (const_int 6)
7514            (const_int 8))))]
7518 ;; Comparison and test insns
7520 (define_insn "*arm_cmpsi_insn"
7521   [(set (reg:CC CC_REGNUM)
7522         (compare:CC (match_operand:SI 0 "s_register_operand" "l,r,r,r")
7523                     (match_operand:SI 1 "arm_add_operand"    "Py,r,rI,L")))]
7524   "TARGET_32BIT"
7525   "@
7526    cmp%?\\t%0, %1
7527    cmp%?\\t%0, %1
7528    cmp%?\\t%0, %1
7529    cmn%?\\t%0, #%n1"
7530   [(set_attr "conds" "set")
7531    (set_attr "arch" "t2,t2,any,any")
7532    (set_attr "length" "2,2,4,4")
7533    (set_attr "predicable" "yes")]
7536 (define_insn "*cmpsi_shiftsi"
7537   [(set (reg:CC CC_REGNUM)
7538         (compare:CC (match_operand:SI   0 "s_register_operand" "r,r")
7539                     (match_operator:SI  3 "shift_operator"
7540                      [(match_operand:SI 1 "s_register_operand" "r,r")
7541                       (match_operand:SI 2 "shift_amount_operand" "M,rM")])))]
7542   "TARGET_32BIT"
7543   "cmp%?\\t%0, %1%S3"
7544   [(set_attr "conds" "set")
7545    (set_attr "shift" "1")
7546    (set_attr "arch" "32,a")
7547    (set_attr "type" "alu_shift,alu_shift_reg")])
7549 (define_insn "*cmpsi_shiftsi_swp"
7550   [(set (reg:CC_SWP CC_REGNUM)
7551         (compare:CC_SWP (match_operator:SI 3 "shift_operator"
7552                          [(match_operand:SI 1 "s_register_operand" "r,r")
7553                           (match_operand:SI 2 "shift_amount_operand" "M,rM")])
7554                         (match_operand:SI 0 "s_register_operand" "r,r")))]
7555   "TARGET_32BIT"
7556   "cmp%?\\t%0, %1%S3"
7557   [(set_attr "conds" "set")
7558    (set_attr "shift" "1")
7559    (set_attr "arch" "32,a")
7560    (set_attr "type" "alu_shift,alu_shift_reg")])
7562 (define_insn "*arm_cmpsi_negshiftsi_si"
7563   [(set (reg:CC_Z CC_REGNUM)
7564         (compare:CC_Z
7565          (neg:SI (match_operator:SI 1 "shift_operator"
7566                     [(match_operand:SI 2 "s_register_operand" "r")
7567                      (match_operand:SI 3 "reg_or_int_operand" "rM")]))
7568          (match_operand:SI 0 "s_register_operand" "r")))]
7569   "TARGET_ARM"
7570   "cmn%?\\t%0, %2%S1"
7571   [(set_attr "conds" "set")
7572    (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
7573                                     (const_string "alu_shift")
7574                                     (const_string "alu_shift_reg")))
7575    (set_attr "predicable" "yes")]
7578 ;; DImode comparisons.  The generic code generates branches that
7579 ;; if-conversion can not reduce to a conditional compare, so we do
7580 ;; that directly.
7582 (define_insn "*arm_cmpdi_insn"
7583   [(set (reg:CC_NCV CC_REGNUM)
7584         (compare:CC_NCV (match_operand:DI 0 "s_register_operand" "r")
7585                         (match_operand:DI 1 "arm_di_operand"       "rDi")))
7586    (clobber (match_scratch:SI 2 "=r"))]
7587   "TARGET_32BIT"
7588   "cmp\\t%Q0, %Q1\;sbcs\\t%2, %R0, %R1"
7589   [(set_attr "conds" "set")
7590    (set_attr "length" "8")]
7593 (define_insn "*arm_cmpdi_unsigned"
7594   [(set (reg:CC_CZ CC_REGNUM)
7595         (compare:CC_CZ (match_operand:DI 0 "s_register_operand" "r")
7596                        (match_operand:DI 1 "arm_di_operand"     "rDi")))]
7597   "TARGET_32BIT"
7598   "cmp\\t%R0, %R1\;it eq\;cmpeq\\t%Q0, %Q1"
7599   [(set_attr "conds" "set")
7600    (set_attr "length" "8")]
7603 (define_insn "*arm_cmpdi_zero"
7604   [(set (reg:CC_Z CC_REGNUM)
7605         (compare:CC_Z (match_operand:DI 0 "s_register_operand" "r")
7606                       (const_int 0)))
7607    (clobber (match_scratch:SI 1 "=r"))]
7608   "TARGET_32BIT"
7609   "orr%.\\t%1, %Q0, %R0"
7610   [(set_attr "conds" "set")]
7613 (define_insn "*thumb_cmpdi_zero"
7614   [(set (reg:CC_Z CC_REGNUM)
7615         (compare:CC_Z (match_operand:DI 0 "s_register_operand" "l")
7616                       (const_int 0)))
7617    (clobber (match_scratch:SI 1 "=l"))]
7618   "TARGET_THUMB1"
7619   "orr\\t%1, %Q0, %R0"
7620   [(set_attr "conds" "set")
7621    (set_attr "length" "2")]
7624 ; This insn allows redundant compares to be removed by cse, nothing should
7625 ; ever appear in the output file since (set (reg x) (reg x)) is a no-op that
7626 ; is deleted later on. The match_dup will match the mode here, so that
7627 ; mode changes of the condition codes aren't lost by this even though we don't
7628 ; specify what they are.
7630 (define_insn "*deleted_compare"
7631   [(set (match_operand 0 "cc_register" "") (match_dup 0))]
7632   "TARGET_32BIT"
7633   "\\t%@ deleted compare"
7634   [(set_attr "conds" "set")
7635    (set_attr "length" "0")]
7639 ;; Conditional branch insns
7641 (define_expand "cbranch_cc"
7642   [(set (pc)
7643         (if_then_else (match_operator 0 "" [(match_operand 1 "" "")
7644                                             (match_operand 2 "" "")])
7645                       (label_ref (match_operand 3 "" ""))
7646                       (pc)))]
7647   "TARGET_32BIT"
7648   "operands[1] = arm_gen_compare_reg (GET_CODE (operands[0]),
7649                                       operands[1], operands[2], NULL_RTX);
7650    operands[2] = const0_rtx;"
7654 ;; Patterns to match conditional branch insns.
7657 (define_insn "arm_cond_branch"
7658   [(set (pc)
7659         (if_then_else (match_operator 1 "arm_comparison_operator"
7660                        [(match_operand 2 "cc_register" "") (const_int 0)])
7661                       (label_ref (match_operand 0 "" ""))
7662                       (pc)))]
7663   "TARGET_32BIT"
7664   "*
7665   if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
7666     {
7667       arm_ccfsm_state += 2;
7668       return \"\";
7669     }
7670   return \"b%d1\\t%l0\";
7671   "
7672   [(set_attr "conds" "use")
7673    (set_attr "type" "branch")
7674    (set (attr "length")
7675         (if_then_else
7676            (and (match_test "TARGET_THUMB2")
7677                 (and (ge (minus (match_dup 0) (pc)) (const_int -250))
7678                      (le (minus (match_dup 0) (pc)) (const_int 256))))
7679            (const_int 2)
7680            (const_int 4)))]
7683 (define_insn "*arm_cond_branch_reversed"
7684   [(set (pc)
7685         (if_then_else (match_operator 1 "arm_comparison_operator"
7686                        [(match_operand 2 "cc_register" "") (const_int 0)])
7687                       (pc)
7688                       (label_ref (match_operand 0 "" ""))))]
7689   "TARGET_32BIT"
7690   "*
7691   if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
7692     {
7693       arm_ccfsm_state += 2;
7694       return \"\";
7695     }
7696   return \"b%D1\\t%l0\";
7697   "
7698   [(set_attr "conds" "use")
7699    (set_attr "type" "branch")
7700    (set (attr "length")
7701         (if_then_else
7702            (and (match_test "TARGET_THUMB2")
7703                 (and (ge (minus (match_dup 0) (pc)) (const_int -250))
7704                      (le (minus (match_dup 0) (pc)) (const_int 256))))
7705            (const_int 2)
7706            (const_int 4)))]
7711 ; scc insns
7713 (define_expand "cstore_cc"
7714   [(set (match_operand:SI 0 "s_register_operand" "")
7715         (match_operator:SI 1 "" [(match_operand 2 "" "")
7716                                  (match_operand 3 "" "")]))]
7717   "TARGET_32BIT"
7718   "operands[2] = arm_gen_compare_reg (GET_CODE (operands[1]),
7719                                       operands[2], operands[3], NULL_RTX);
7720    operands[3] = const0_rtx;"
7723 (define_insn "*mov_scc"
7724   [(set (match_operand:SI 0 "s_register_operand" "=r")
7725         (match_operator:SI 1 "arm_comparison_operator"
7726          [(match_operand 2 "cc_register" "") (const_int 0)]))]
7727   "TARGET_ARM"
7728   "mov%D1\\t%0, #0\;mov%d1\\t%0, #1"
7729   [(set_attr "conds" "use")
7730    (set_attr "insn" "mov")
7731    (set_attr "length" "8")]
7734 (define_insn "*mov_negscc"
7735   [(set (match_operand:SI 0 "s_register_operand" "=r")
7736         (neg:SI (match_operator:SI 1 "arm_comparison_operator"
7737                  [(match_operand 2 "cc_register" "") (const_int 0)])))]
7738   "TARGET_ARM"
7739   "mov%D1\\t%0, #0\;mvn%d1\\t%0, #0"
7740   [(set_attr "conds" "use")
7741    (set_attr "insn" "mov")
7742    (set_attr "length" "8")]
7745 (define_insn "*mov_notscc"
7746   [(set (match_operand:SI 0 "s_register_operand" "=r")
7747         (not:SI (match_operator:SI 1 "arm_comparison_operator"
7748                  [(match_operand 2 "cc_register" "") (const_int 0)])))]
7749   "TARGET_ARM"
7750   "mvn%D1\\t%0, #0\;mvn%d1\\t%0, #1"
7751   [(set_attr "conds" "use")
7752    (set_attr "insn" "mov")
7753    (set_attr "length" "8")]
7756 (define_expand "cstoresi4"
7757   [(set (match_operand:SI 0 "s_register_operand" "")
7758         (match_operator:SI 1 "expandable_comparison_operator"
7759          [(match_operand:SI 2 "s_register_operand" "")
7760           (match_operand:SI 3 "reg_or_int_operand" "")]))]
7761   "TARGET_32BIT || TARGET_THUMB1"
7762   "{
7763   rtx op3, scratch, scratch2;
7765   if (!TARGET_THUMB1)
7766     {
7767       if (!arm_add_operand (operands[3], SImode))
7768         operands[3] = force_reg (SImode, operands[3]);
7769       emit_insn (gen_cstore_cc (operands[0], operands[1],
7770                                 operands[2], operands[3]));
7771       DONE;
7772     }
7774   if (operands[3] == const0_rtx)
7775     {
7776       switch (GET_CODE (operands[1]))
7777         {
7778         case EQ:
7779           emit_insn (gen_cstoresi_eq0_thumb1 (operands[0], operands[2]));
7780           break;
7782         case NE:
7783           emit_insn (gen_cstoresi_ne0_thumb1 (operands[0], operands[2]));
7784           break;
7786         case LE:
7787           scratch = expand_binop (SImode, add_optab, operands[2], constm1_rtx,
7788                                   NULL_RTX, 0, OPTAB_WIDEN);
7789           scratch = expand_binop (SImode, ior_optab, operands[2], scratch,
7790                                   NULL_RTX, 0, OPTAB_WIDEN);
7791           expand_binop (SImode, lshr_optab, scratch, GEN_INT (31),
7792                         operands[0], 1, OPTAB_WIDEN);
7793           break;
7795         case GE:
7796           scratch = expand_unop (SImode, one_cmpl_optab, operands[2],
7797                                  NULL_RTX, 1);
7798           expand_binop (SImode, lshr_optab, scratch, GEN_INT (31),
7799                         NULL_RTX, 1, OPTAB_WIDEN);
7800           break;
7802         case GT:
7803           scratch = expand_binop (SImode, ashr_optab, operands[2],
7804                                   GEN_INT (31), NULL_RTX, 0, OPTAB_WIDEN);
7805           scratch = expand_binop (SImode, sub_optab, scratch, operands[2],
7806                                   NULL_RTX, 0, OPTAB_WIDEN);
7807           expand_binop (SImode, lshr_optab, scratch, GEN_INT (31), operands[0],
7808                         0, OPTAB_WIDEN);
7809           break;
7811         /* LT is handled by generic code.  No need for unsigned with 0.  */
7812         default:
7813           FAIL;
7814         }
7815       DONE;
7816     }
7818   switch (GET_CODE (operands[1]))
7819     {
7820     case EQ:
7821       scratch = expand_binop (SImode, sub_optab, operands[2], operands[3],
7822                               NULL_RTX, 0, OPTAB_WIDEN);
7823       emit_insn (gen_cstoresi_eq0_thumb1 (operands[0], scratch));
7824       break;
7826     case NE:
7827       scratch = expand_binop (SImode, sub_optab, operands[2], operands[3],
7828                               NULL_RTX, 0, OPTAB_WIDEN);
7829       emit_insn (gen_cstoresi_ne0_thumb1 (operands[0], scratch));
7830       break;
7832     case LE:
7833       op3 = force_reg (SImode, operands[3]);
7835       scratch = expand_binop (SImode, lshr_optab, operands[2], GEN_INT (31),
7836                               NULL_RTX, 1, OPTAB_WIDEN);
7837       scratch2 = expand_binop (SImode, ashr_optab, op3, GEN_INT (31),
7838                               NULL_RTX, 0, OPTAB_WIDEN);
7839       emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch2,
7840                                           op3, operands[2]));
7841       break;
7843     case GE:
7844       op3 = operands[3];
7845       if (!thumb1_cmp_operand (op3, SImode))
7846         op3 = force_reg (SImode, op3);
7847       scratch = expand_binop (SImode, ashr_optab, operands[2], GEN_INT (31),
7848                               NULL_RTX, 0, OPTAB_WIDEN);
7849       scratch2 = expand_binop (SImode, lshr_optab, op3, GEN_INT (31),
7850                                NULL_RTX, 1, OPTAB_WIDEN);
7851       emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch2,
7852                                           operands[2], op3));
7853       break;
7855     case LEU:
7856       op3 = force_reg (SImode, operands[3]);
7857       scratch = force_reg (SImode, const0_rtx);
7858       emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch,
7859                                           op3, operands[2]));
7860       break;
7862     case GEU:
7863       op3 = operands[3];
7864       if (!thumb1_cmp_operand (op3, SImode))
7865         op3 = force_reg (SImode, op3);
7866       scratch = force_reg (SImode, const0_rtx);
7867       emit_insn (gen_thumb1_addsi3_addgeu (operands[0], scratch, scratch,
7868                                           operands[2], op3));
7869       break;
7871     case LTU:
7872       op3 = operands[3];
7873       if (!thumb1_cmp_operand (op3, SImode))
7874         op3 = force_reg (SImode, op3);
7875       scratch = gen_reg_rtx (SImode);
7876       emit_insn (gen_cstoresi_ltu_thumb1 (operands[0], operands[2], op3));
7877       break;
7879     case GTU:
7880       op3 = force_reg (SImode, operands[3]);
7881       scratch = gen_reg_rtx (SImode);
7882       emit_insn (gen_cstoresi_ltu_thumb1 (operands[0], op3, operands[2]));
7883       break;
7885     /* No good sequences for GT, LT.  */
7886     default:
7887       FAIL;
7888     }
7889   DONE;
7892 (define_expand "cstoresf4"
7893   [(set (match_operand:SI 0 "s_register_operand" "")
7894         (match_operator:SI 1 "expandable_comparison_operator"
7895          [(match_operand:SF 2 "s_register_operand" "")
7896           (match_operand:SF 3 "arm_float_compare_operand" "")]))]
7897   "TARGET_32BIT && TARGET_HARD_FLOAT"
7898   "emit_insn (gen_cstore_cc (operands[0], operands[1],
7899                              operands[2], operands[3])); DONE;"
7902 (define_expand "cstoredf4"
7903   [(set (match_operand:SI 0 "s_register_operand" "")
7904         (match_operator:SI 1 "expandable_comparison_operator"
7905          [(match_operand:DF 2 "s_register_operand" "")
7906           (match_operand:DF 3 "arm_float_compare_operand" "")]))]
7907   "TARGET_32BIT && TARGET_HARD_FLOAT && !TARGET_VFP_SINGLE"
7908   "emit_insn (gen_cstore_cc (operands[0], operands[1],
7909                              operands[2], operands[3])); DONE;"
7912 (define_expand "cstoredi4"
7913   [(set (match_operand:SI 0 "s_register_operand" "")
7914         (match_operator:SI 1 "expandable_comparison_operator"
7915          [(match_operand:DI 2 "cmpdi_operand" "")
7916           (match_operand:DI 3 "cmpdi_operand" "")]))]
7917   "TARGET_32BIT"
7918   "{
7919      /* We should not have two constants.  */
7920      gcc_assert (GET_MODE (operands[2]) == DImode
7921                  || GET_MODE (operands[3]) == DImode);
7923      if (!arm_validize_comparison (&operands[1],
7924                                    &operands[2],
7925                                    &operands[3]))
7926        FAIL;
7927      emit_insn (gen_cstore_cc (operands[0], operands[1], operands[2],
7928                                  operands[3]));
7929      DONE;
7930    }"
7933 (define_expand "cstoresi_eq0_thumb1"
7934   [(parallel
7935     [(set (match_operand:SI 0 "s_register_operand" "")
7936           (eq:SI (match_operand:SI 1 "s_register_operand" "")
7937                  (const_int 0)))
7938      (clobber (match_dup:SI 2))])]
7939   "TARGET_THUMB1"
7940   "operands[2] = gen_reg_rtx (SImode);"
7943 (define_expand "cstoresi_ne0_thumb1"
7944   [(parallel
7945     [(set (match_operand:SI 0 "s_register_operand" "")
7946           (ne:SI (match_operand:SI 1 "s_register_operand" "")
7947                  (const_int 0)))
7948      (clobber (match_dup:SI 2))])]
7949   "TARGET_THUMB1"
7950   "operands[2] = gen_reg_rtx (SImode);"
7953 (define_insn "*cstoresi_eq0_thumb1_insn"
7954   [(set (match_operand:SI 0 "s_register_operand" "=&l,l")
7955         (eq:SI (match_operand:SI 1 "s_register_operand" "l,0")
7956                (const_int 0)))
7957    (clobber (match_operand:SI 2 "s_register_operand" "=X,l"))]
7958   "TARGET_THUMB1"
7959   "@
7960    neg\\t%0, %1\;adc\\t%0, %0, %1
7961    neg\\t%2, %1\;adc\\t%0, %1, %2"
7962   [(set_attr "length" "4")]
7965 (define_insn "*cstoresi_ne0_thumb1_insn"
7966   [(set (match_operand:SI 0 "s_register_operand" "=l")
7967         (ne:SI (match_operand:SI 1 "s_register_operand" "0")
7968                (const_int 0)))
7969    (clobber (match_operand:SI 2 "s_register_operand" "=l"))]
7970   "TARGET_THUMB1"
7971   "sub\\t%2, %1, #1\;sbc\\t%0, %1, %2"
7972   [(set_attr "length" "4")]
7975 ;; Used as part of the expansion of thumb ltu and gtu sequences
7976 (define_insn "cstoresi_nltu_thumb1"
7977   [(set (match_operand:SI 0 "s_register_operand" "=l,l")
7978         (neg:SI (ltu:SI (match_operand:SI 1 "s_register_operand" "l,*h")
7979                         (match_operand:SI 2 "thumb1_cmp_operand" "lI*h,*r"))))]
7980   "TARGET_THUMB1"
7981   "cmp\\t%1, %2\;sbc\\t%0, %0, %0"
7982   [(set_attr "length" "4")]
7985 (define_insn_and_split "cstoresi_ltu_thumb1"
7986   [(set (match_operand:SI 0 "s_register_operand" "=l,l")
7987         (ltu:SI (match_operand:SI 1 "s_register_operand" "l,*h")
7988                 (match_operand:SI 2 "thumb1_cmp_operand" "lI*h,*r")))]
7989   "TARGET_THUMB1"
7990   "#"
7991   "TARGET_THUMB1"
7992   [(set (match_dup 3)
7993         (neg:SI (ltu:SI (match_dup 1) (match_dup 2))))
7994    (set (match_dup 0) (neg:SI (match_dup 3)))]
7995   "operands[3] = gen_reg_rtx (SImode);"
7996   [(set_attr "length" "4")]
7999 ;; Used as part of the expansion of thumb les sequence.
8000 (define_insn "thumb1_addsi3_addgeu"
8001   [(set (match_operand:SI 0 "s_register_operand" "=l")
8002         (plus:SI (plus:SI (match_operand:SI 1 "s_register_operand" "%0")
8003                           (match_operand:SI 2 "s_register_operand" "l"))
8004                  (geu:SI (match_operand:SI 3 "s_register_operand" "l")
8005                          (match_operand:SI 4 "thumb1_cmp_operand" "lI"))))]
8006   "TARGET_THUMB1"
8007   "cmp\\t%3, %4\;adc\\t%0, %1, %2"
8008   [(set_attr "length" "4")]
8012 ;; Conditional move insns
8014 (define_expand "movsicc"
8015   [(set (match_operand:SI 0 "s_register_operand" "")
8016         (if_then_else:SI (match_operand 1 "expandable_comparison_operator" "")
8017                          (match_operand:SI 2 "arm_not_operand" "")
8018                          (match_operand:SI 3 "arm_not_operand" "")))]
8019   "TARGET_32BIT"
8020   "
8021   {
8022     enum rtx_code code;
8023     rtx ccreg;
8025     if (!arm_validize_comparison (&operands[1], &XEXP (operands[1], 0), 
8026                                   &XEXP (operands[1], 1)))
8027       FAIL;
8028     
8029     code = GET_CODE (operands[1]);
8030     ccreg = arm_gen_compare_reg (code, XEXP (operands[1], 0),
8031                                  XEXP (operands[1], 1), NULL_RTX);
8032     operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
8033   }"
8036 (define_expand "movsfcc"
8037   [(set (match_operand:SF 0 "s_register_operand" "")
8038         (if_then_else:SF (match_operand 1 "expandable_comparison_operator" "")
8039                          (match_operand:SF 2 "s_register_operand" "")
8040                          (match_operand:SF 3 "arm_float_add_operand" "")))]
8041   "TARGET_32BIT && TARGET_HARD_FLOAT"
8042   "
8043   {
8044     enum rtx_code code = GET_CODE (operands[1]);
8045     rtx ccreg;
8047     if (!arm_validize_comparison (&operands[1], &XEXP (operands[1], 0), 
8048                                   &XEXP (operands[1], 1)))
8049        FAIL;
8051     code = GET_CODE (operands[1]);
8052     ccreg = arm_gen_compare_reg (code, XEXP (operands[1], 0),
8053                                  XEXP (operands[1], 1), NULL_RTX);
8054     operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
8055   }"
8058 (define_expand "movdfcc"
8059   [(set (match_operand:DF 0 "s_register_operand" "")
8060         (if_then_else:DF (match_operand 1 "expandable_comparison_operator" "")
8061                          (match_operand:DF 2 "s_register_operand" "")
8062                          (match_operand:DF 3 "arm_float_add_operand" "")))]
8063   "TARGET_32BIT && TARGET_HARD_FLOAT && TARGET_VFP_DOUBLE"
8064   "
8065   {
8066     enum rtx_code code = GET_CODE (operands[1]);
8067     rtx ccreg;
8069     if (!arm_validize_comparison (&operands[1], &XEXP (operands[1], 0), 
8070                                   &XEXP (operands[1], 1)))
8071        FAIL;
8072     code = GET_CODE (operands[1]);
8073     ccreg = arm_gen_compare_reg (code, XEXP (operands[1], 0),
8074                                  XEXP (operands[1], 1), NULL_RTX);
8075     operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
8076   }"
8079 (define_insn "*movsicc_insn"
8080   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r,r,r,r,r")
8081         (if_then_else:SI
8082          (match_operator 3 "arm_comparison_operator"
8083           [(match_operand 4 "cc_register" "") (const_int 0)])
8084          (match_operand:SI 1 "arm_not_operand" "0,0,rI,K,rI,rI,K,K")
8085          (match_operand:SI 2 "arm_not_operand" "rI,K,0,0,rI,K,rI,K")))]
8086   "TARGET_ARM"
8087   "@
8088    mov%D3\\t%0, %2
8089    mvn%D3\\t%0, #%B2
8090    mov%d3\\t%0, %1
8091    mvn%d3\\t%0, #%B1
8092    mov%d3\\t%0, %1\;mov%D3\\t%0, %2
8093    mov%d3\\t%0, %1\;mvn%D3\\t%0, #%B2
8094    mvn%d3\\t%0, #%B1\;mov%D3\\t%0, %2
8095    mvn%d3\\t%0, #%B1\;mvn%D3\\t%0, #%B2"
8096   [(set_attr "length" "4,4,4,4,8,8,8,8")
8097    (set_attr "conds" "use")
8098    (set_attr "insn" "mov,mvn,mov,mvn,mov,mov,mvn,mvn")]
8101 (define_insn "*movsfcc_soft_insn"
8102   [(set (match_operand:SF 0 "s_register_operand" "=r,r")
8103         (if_then_else:SF (match_operator 3 "arm_comparison_operator"
8104                           [(match_operand 4 "cc_register" "") (const_int 0)])
8105                          (match_operand:SF 1 "s_register_operand" "0,r")
8106                          (match_operand:SF 2 "s_register_operand" "r,0")))]
8107   "TARGET_ARM && TARGET_SOFT_FLOAT"
8108   "@
8109    mov%D3\\t%0, %2
8110    mov%d3\\t%0, %1"
8111   [(set_attr "conds" "use")
8112    (set_attr "insn" "mov")]
8116 ;; Jump and linkage insns
8118 (define_expand "jump"
8119   [(set (pc)
8120         (label_ref (match_operand 0 "" "")))]
8121   "TARGET_EITHER"
8122   ""
8125 (define_insn "*arm_jump"
8126   [(set (pc)
8127         (label_ref (match_operand 0 "" "")))]
8128   "TARGET_32BIT"
8129   "*
8130   {
8131     if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
8132       {
8133         arm_ccfsm_state += 2;
8134         return \"\";
8135       }
8136     return \"b%?\\t%l0\";
8137   }
8138   "
8139   [(set_attr "predicable" "yes")
8140    (set (attr "length")
8141         (if_then_else
8142            (and (match_test "TARGET_THUMB2")
8143                 (and (ge (minus (match_dup 0) (pc)) (const_int -2044))
8144                      (le (minus (match_dup 0) (pc)) (const_int 2048))))
8145            (const_int 2)
8146            (const_int 4)))]
8149 (define_insn "*thumb_jump"
8150   [(set (pc)
8151         (label_ref (match_operand 0 "" "")))]
8152   "TARGET_THUMB1"
8153   "*
8154   if (get_attr_length (insn) == 2)
8155     return \"b\\t%l0\";
8156   return \"bl\\t%l0\\t%@ far jump\";
8157   "
8158   [(set (attr "far_jump")
8159         (if_then_else
8160             (eq_attr "length" "4")
8161             (const_string "yes")
8162             (const_string "no")))
8163    (set (attr "length") 
8164         (if_then_else
8165             (and (ge (minus (match_dup 0) (pc)) (const_int -2044))
8166                  (le (minus (match_dup 0) (pc)) (const_int 2048)))
8167             (const_int 2)
8168             (const_int 4)))]
8171 (define_expand "call"
8172   [(parallel [(call (match_operand 0 "memory_operand" "")
8173                     (match_operand 1 "general_operand" ""))
8174               (use (match_operand 2 "" ""))
8175               (clobber (reg:SI LR_REGNUM))])]
8176   "TARGET_EITHER"
8177   "
8178   {
8179     rtx callee, pat;
8180     
8181     /* In an untyped call, we can get NULL for operand 2.  */
8182     if (operands[2] == NULL_RTX)
8183       operands[2] = const0_rtx;
8184       
8185     /* Decide if we should generate indirect calls by loading the
8186        32-bit address of the callee into a register before performing the
8187        branch and link.  */
8188     callee = XEXP (operands[0], 0);
8189     if (GET_CODE (callee) == SYMBOL_REF
8190         ? arm_is_long_call_p (SYMBOL_REF_DECL (callee))
8191         : !REG_P (callee))
8192       XEXP (operands[0], 0) = force_reg (Pmode, callee);
8194     pat = gen_call_internal (operands[0], operands[1], operands[2]);
8195     arm_emit_call_insn (pat, XEXP (operands[0], 0));
8196     DONE;
8197   }"
8200 (define_expand "call_internal"
8201   [(parallel [(call (match_operand 0 "memory_operand" "")
8202                     (match_operand 1 "general_operand" ""))
8203               (use (match_operand 2 "" ""))
8204               (clobber (reg:SI LR_REGNUM))])])
8206 (define_insn "*call_reg_armv5"
8207   [(call (mem:SI (match_operand:SI 0 "s_register_operand" "r"))
8208          (match_operand 1 "" ""))
8209    (use (match_operand 2 "" ""))
8210    (clobber (reg:SI LR_REGNUM))]
8211   "TARGET_ARM && arm_arch5"
8212   "blx%?\\t%0"
8213   [(set_attr "type" "call")]
8216 (define_insn "*call_reg_arm"
8217   [(call (mem:SI (match_operand:SI 0 "s_register_operand" "r"))
8218          (match_operand 1 "" ""))
8219    (use (match_operand 2 "" ""))
8220    (clobber (reg:SI LR_REGNUM))]
8221   "TARGET_ARM && !arm_arch5"
8222   "*
8223   return output_call (operands);
8224   "
8225   ;; length is worst case, normally it is only two
8226   [(set_attr "length" "12")
8227    (set_attr "type" "call")]
8231 ;; Note: not used for armv5+ because the sequence used (ldr pc, ...) is not
8232 ;; considered a function call by the branch predictor of some cores (PR40887).
8233 ;; Falls back to blx rN (*call_reg_armv5).
8235 (define_insn "*call_mem"
8236   [(call (mem:SI (match_operand:SI 0 "call_memory_operand" "m"))
8237          (match_operand 1 "" ""))
8238    (use (match_operand 2 "" ""))
8239    (clobber (reg:SI LR_REGNUM))]
8240   "TARGET_ARM && !arm_arch5"
8241   "*
8242   return output_call_mem (operands);
8243   "
8244   [(set_attr "length" "12")
8245    (set_attr "type" "call")]
8248 (define_insn "*call_reg_thumb1_v5"
8249   [(call (mem:SI (match_operand:SI 0 "register_operand" "l*r"))
8250          (match_operand 1 "" ""))
8251    (use (match_operand 2 "" ""))
8252    (clobber (reg:SI LR_REGNUM))]
8253   "TARGET_THUMB1 && arm_arch5"
8254   "blx\\t%0"
8255   [(set_attr "length" "2")
8256    (set_attr "type" "call")]
8259 (define_insn "*call_reg_thumb1"
8260   [(call (mem:SI (match_operand:SI 0 "register_operand" "l*r"))
8261          (match_operand 1 "" ""))
8262    (use (match_operand 2 "" ""))
8263    (clobber (reg:SI LR_REGNUM))]
8264   "TARGET_THUMB1 && !arm_arch5"
8265   "*
8266   {
8267     if (!TARGET_CALLER_INTERWORKING)
8268       return thumb_call_via_reg (operands[0]);
8269     else if (operands[1] == const0_rtx)
8270       return \"bl\\t%__interwork_call_via_%0\";
8271     else if (frame_pointer_needed)
8272       return \"bl\\t%__interwork_r7_call_via_%0\";
8273     else
8274       return \"bl\\t%__interwork_r11_call_via_%0\";
8275   }"
8276   [(set_attr "type" "call")]
8279 (define_expand "call_value"
8280   [(parallel [(set (match_operand       0 "" "")
8281                    (call (match_operand 1 "memory_operand" "")
8282                          (match_operand 2 "general_operand" "")))
8283               (use (match_operand 3 "" ""))
8284               (clobber (reg:SI LR_REGNUM))])]
8285   "TARGET_EITHER"
8286   "
8287   {
8288     rtx pat, callee;
8289     
8290     /* In an untyped call, we can get NULL for operand 2.  */
8291     if (operands[3] == 0)
8292       operands[3] = const0_rtx;
8293       
8294     /* Decide if we should generate indirect calls by loading the
8295        32-bit address of the callee into a register before performing the
8296        branch and link.  */
8297     callee = XEXP (operands[1], 0);
8298     if (GET_CODE (callee) == SYMBOL_REF
8299         ? arm_is_long_call_p (SYMBOL_REF_DECL (callee))
8300         : !REG_P (callee))
8301       XEXP (operands[1], 0) = force_reg (Pmode, callee);
8303     pat = gen_call_value_internal (operands[0], operands[1],
8304                                    operands[2], operands[3]);
8305     arm_emit_call_insn (pat, XEXP (operands[1], 0));
8306     DONE;
8307   }"
8310 (define_expand "call_value_internal"
8311   [(parallel [(set (match_operand       0 "" "")
8312                    (call (match_operand 1 "memory_operand" "")
8313                          (match_operand 2 "general_operand" "")))
8314               (use (match_operand 3 "" ""))
8315               (clobber (reg:SI LR_REGNUM))])])
8317 (define_insn "*call_value_reg_armv5"
8318   [(set (match_operand 0 "" "")
8319         (call (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
8320               (match_operand 2 "" "")))
8321    (use (match_operand 3 "" ""))
8322    (clobber (reg:SI LR_REGNUM))]
8323   "TARGET_ARM && arm_arch5"
8324   "blx%?\\t%1"
8325   [(set_attr "type" "call")]
8328 (define_insn "*call_value_reg_arm"
8329   [(set (match_operand 0 "" "")
8330         (call (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
8331               (match_operand 2 "" "")))
8332    (use (match_operand 3 "" ""))
8333    (clobber (reg:SI LR_REGNUM))]
8334   "TARGET_ARM && !arm_arch5"
8335   "*
8336   return output_call (&operands[1]);
8337   "
8338   [(set_attr "length" "12")
8339    (set_attr "type" "call")]
8342 ;; Note: see *call_mem
8344 (define_insn "*call_value_mem"
8345   [(set (match_operand 0 "" "")
8346         (call (mem:SI (match_operand:SI 1 "call_memory_operand" "m"))
8347               (match_operand 2 "" "")))
8348    (use (match_operand 3 "" ""))
8349    (clobber (reg:SI LR_REGNUM))]
8350   "TARGET_ARM && !arm_arch5 && (!CONSTANT_ADDRESS_P (XEXP (operands[1], 0)))"
8351   "*
8352   return output_call_mem (&operands[1]);
8353   "
8354   [(set_attr "length" "12")
8355    (set_attr "type" "call")]
8358 (define_insn "*call_value_reg_thumb1_v5"
8359   [(set (match_operand 0 "" "")
8360         (call (mem:SI (match_operand:SI 1 "register_operand" "l*r"))
8361               (match_operand 2 "" "")))
8362    (use (match_operand 3 "" ""))
8363    (clobber (reg:SI LR_REGNUM))]
8364   "TARGET_THUMB1 && arm_arch5"
8365   "blx\\t%1"
8366   [(set_attr "length" "2")
8367    (set_attr "type" "call")]
8370 (define_insn "*call_value_reg_thumb1"
8371   [(set (match_operand 0 "" "")
8372         (call (mem:SI (match_operand:SI 1 "register_operand" "l*r"))
8373               (match_operand 2 "" "")))
8374    (use (match_operand 3 "" ""))
8375    (clobber (reg:SI LR_REGNUM))]
8376   "TARGET_THUMB1 && !arm_arch5"
8377   "*
8378   {
8379     if (!TARGET_CALLER_INTERWORKING)
8380       return thumb_call_via_reg (operands[1]);
8381     else if (operands[2] == const0_rtx)
8382       return \"bl\\t%__interwork_call_via_%1\";
8383     else if (frame_pointer_needed)
8384       return \"bl\\t%__interwork_r7_call_via_%1\";
8385     else
8386       return \"bl\\t%__interwork_r11_call_via_%1\";
8387   }"
8388   [(set_attr "type" "call")]
8391 ;; Allow calls to SYMBOL_REFs specially as they are not valid general addresses
8392 ;; The 'a' causes the operand to be treated as an address, i.e. no '#' output.
8394 (define_insn "*call_symbol"
8395   [(call (mem:SI (match_operand:SI 0 "" ""))
8396          (match_operand 1 "" ""))
8397    (use (match_operand 2 "" ""))
8398    (clobber (reg:SI LR_REGNUM))]
8399   "TARGET_32BIT
8400    && (GET_CODE (operands[0]) == SYMBOL_REF)
8401    && !arm_is_long_call_p (SYMBOL_REF_DECL (operands[0]))"
8402   "*
8403   {
8404     return NEED_PLT_RELOC ? \"bl%?\\t%a0(PLT)\" : \"bl%?\\t%a0\";
8405   }"
8406   [(set_attr "type" "call")]
8409 (define_insn "*call_value_symbol"
8410   [(set (match_operand 0 "" "")
8411         (call (mem:SI (match_operand:SI 1 "" ""))
8412         (match_operand:SI 2 "" "")))
8413    (use (match_operand 3 "" ""))
8414    (clobber (reg:SI LR_REGNUM))]
8415   "TARGET_32BIT
8416    && (GET_CODE (operands[1]) == SYMBOL_REF)
8417    && !arm_is_long_call_p (SYMBOL_REF_DECL (operands[1]))"
8418   "*
8419   {
8420     return NEED_PLT_RELOC ? \"bl%?\\t%a1(PLT)\" : \"bl%?\\t%a1\";
8421   }"
8422   [(set_attr "type" "call")]
8425 (define_insn "*call_insn"
8426   [(call (mem:SI (match_operand:SI 0 "" ""))
8427          (match_operand:SI 1 "" ""))
8428    (use (match_operand 2 "" ""))
8429    (clobber (reg:SI LR_REGNUM))]
8430   "TARGET_THUMB1
8431    && GET_CODE (operands[0]) == SYMBOL_REF
8432    && !arm_is_long_call_p (SYMBOL_REF_DECL (operands[0]))"
8433   "bl\\t%a0"
8434   [(set_attr "length" "4")
8435    (set_attr "type" "call")]
8438 (define_insn "*call_value_insn"
8439   [(set (match_operand 0 "" "")
8440         (call (mem:SI (match_operand 1 "" ""))
8441               (match_operand 2 "" "")))
8442    (use (match_operand 3 "" ""))
8443    (clobber (reg:SI LR_REGNUM))]
8444   "TARGET_THUMB1
8445    && GET_CODE (operands[1]) == SYMBOL_REF
8446    && !arm_is_long_call_p (SYMBOL_REF_DECL (operands[1]))"
8447   "bl\\t%a1"
8448   [(set_attr "length" "4")
8449    (set_attr "type" "call")]
8452 ;; We may also be able to do sibcalls for Thumb, but it's much harder...
8453 (define_expand "sibcall"
8454   [(parallel [(call (match_operand 0 "memory_operand" "")
8455                     (match_operand 1 "general_operand" ""))
8456               (return)
8457               (use (match_operand 2 "" ""))])]
8458   "TARGET_32BIT"
8459   "
8460   {
8461     if (operands[2] == NULL_RTX)
8462       operands[2] = const0_rtx;
8463   }"
8466 (define_expand "sibcall_value"
8467   [(parallel [(set (match_operand 0 "" "")
8468                    (call (match_operand 1 "memory_operand" "")
8469                          (match_operand 2 "general_operand" "")))
8470               (return)
8471               (use (match_operand 3 "" ""))])]
8472   "TARGET_32BIT"
8473   "
8474   {
8475     if (operands[3] == NULL_RTX)
8476       operands[3] = const0_rtx;
8477   }"
8480 (define_insn "*sibcall_insn"
8481  [(call (mem:SI (match_operand:SI 0 "" "X"))
8482         (match_operand 1 "" ""))
8483   (return)
8484   (use (match_operand 2 "" ""))]
8485   "TARGET_32BIT && GET_CODE (operands[0]) == SYMBOL_REF"
8486   "*
8487   return NEED_PLT_RELOC ? \"b%?\\t%a0(PLT)\" : \"b%?\\t%a0\";
8488   "
8489   [(set_attr "type" "call")]
8492 (define_insn "*sibcall_value_insn"
8493  [(set (match_operand 0 "" "")
8494        (call (mem:SI (match_operand:SI 1 "" "X"))
8495              (match_operand 2 "" "")))
8496   (return)
8497   (use (match_operand 3 "" ""))]
8498   "TARGET_32BIT && GET_CODE (operands[1]) == SYMBOL_REF"
8499   "*
8500   return NEED_PLT_RELOC ? \"b%?\\t%a1(PLT)\" : \"b%?\\t%a1\";
8501   "
8502   [(set_attr "type" "call")]
8505 (define_expand "return"
8506   [(return)]
8507   "TARGET_32BIT && USE_RETURN_INSN (FALSE)"
8508   "")
8510 ;; Often the return insn will be the same as loading from memory, so set attr
8511 (define_insn "*arm_return"
8512   [(return)]
8513   "TARGET_ARM && USE_RETURN_INSN (FALSE)"
8514   "*
8515   {
8516     if (arm_ccfsm_state == 2)
8517       {
8518         arm_ccfsm_state += 2;
8519         return \"\";
8520       }
8521     return output_return_instruction (const_true_rtx, TRUE, FALSE);
8522   }"
8523   [(set_attr "type" "load1")
8524    (set_attr "length" "12")
8525    (set_attr "predicable" "yes")]
8528 (define_insn "*cond_return"
8529   [(set (pc)
8530         (if_then_else (match_operator 0 "arm_comparison_operator"
8531                        [(match_operand 1 "cc_register" "") (const_int 0)])
8532                       (return)
8533                       (pc)))]
8534   "TARGET_ARM && USE_RETURN_INSN (TRUE)"
8535   "*
8536   {
8537     if (arm_ccfsm_state == 2)
8538       {
8539         arm_ccfsm_state += 2;
8540         return \"\";
8541       }
8542     return output_return_instruction (operands[0], TRUE, FALSE);
8543   }"
8544   [(set_attr "conds" "use")
8545    (set_attr "length" "12")
8546    (set_attr "type" "load1")]
8549 (define_insn "*cond_return_inverted"
8550   [(set (pc)
8551         (if_then_else (match_operator 0 "arm_comparison_operator"
8552                        [(match_operand 1 "cc_register" "") (const_int 0)])
8553                       (pc)
8554                       (return)))]
8555   "TARGET_ARM && USE_RETURN_INSN (TRUE)"
8556   "*
8557   {
8558     if (arm_ccfsm_state == 2)
8559       {
8560         arm_ccfsm_state += 2;
8561         return \"\";
8562       }
8563     return output_return_instruction (operands[0], TRUE, TRUE);
8564   }"
8565   [(set_attr "conds" "use")
8566    (set_attr "length" "12")
8567    (set_attr "type" "load1")]
8570 ;; Generate a sequence of instructions to determine if the processor is
8571 ;; in 26-bit or 32-bit mode, and return the appropriate return address
8572 ;; mask.
8574 (define_expand "return_addr_mask"
8575   [(set (match_dup 1)
8576       (compare:CC_NOOV (unspec [(const_int 0)] UNSPEC_CHECK_ARCH)
8577                        (const_int 0)))
8578    (set (match_operand:SI 0 "s_register_operand" "")
8579       (if_then_else:SI (eq (match_dup 1) (const_int 0))
8580                        (const_int -1)
8581                        (const_int 67108860)))] ; 0x03fffffc
8582   "TARGET_ARM"
8583   "
8584   operands[1] = gen_rtx_REG (CC_NOOVmode, CC_REGNUM);
8585   ")
8587 (define_insn "*check_arch2"
8588   [(set (match_operand:CC_NOOV 0 "cc_register" "")
8589       (compare:CC_NOOV (unspec [(const_int 0)] UNSPEC_CHECK_ARCH)
8590                        (const_int 0)))]
8591   "TARGET_ARM"
8592   "teq\\t%|r0, %|r0\;teq\\t%|pc, %|pc"
8593   [(set_attr "length" "8")
8594    (set_attr "conds" "set")]
8597 ;; Call subroutine returning any type.
8599 (define_expand "untyped_call"
8600   [(parallel [(call (match_operand 0 "" "")
8601                     (const_int 0))
8602               (match_operand 1 "" "")
8603               (match_operand 2 "" "")])]
8604   "TARGET_EITHER"
8605   "
8606   {
8607     int i;
8608     rtx par = gen_rtx_PARALLEL (VOIDmode,
8609                                 rtvec_alloc (XVECLEN (operands[2], 0)));
8610     rtx addr = gen_reg_rtx (Pmode);
8611     rtx mem;
8612     int size = 0;
8614     emit_move_insn (addr, XEXP (operands[1], 0));
8615     mem = change_address (operands[1], BLKmode, addr);
8617     for (i = 0; i < XVECLEN (operands[2], 0); i++)
8618       {
8619         rtx src = SET_SRC (XVECEXP (operands[2], 0, i));
8621         /* Default code only uses r0 as a return value, but we could
8622            be using anything up to 4 registers.  */
8623         if (REGNO (src) == R0_REGNUM)
8624           src = gen_rtx_REG (TImode, R0_REGNUM);
8626         XVECEXP (par, 0, i) = gen_rtx_EXPR_LIST (VOIDmode, src,
8627                                                  GEN_INT (size));
8628         size += GET_MODE_SIZE (GET_MODE (src));
8629       }
8631     emit_call_insn (GEN_CALL_VALUE (par, operands[0], const0_rtx, NULL,
8632                                     const0_rtx));
8634     size = 0;
8636     for (i = 0; i < XVECLEN (par, 0); i++)
8637       {
8638         HOST_WIDE_INT offset = 0;
8639         rtx reg = XEXP (XVECEXP (par, 0, i), 0);
8641         if (size != 0)
8642           emit_move_insn (addr, plus_constant (Pmode, addr, size));
8644         mem = change_address (mem, GET_MODE (reg), NULL);
8645         if (REGNO (reg) == R0_REGNUM)
8646           {
8647             /* On thumb we have to use a write-back instruction.  */
8648             emit_insn (arm_gen_store_multiple (arm_regs_in_sequence, 4, addr,
8649                        TARGET_THUMB ? TRUE : FALSE, mem, &offset));
8650             size = TARGET_ARM ? 16 : 0;
8651           }
8652         else
8653           {
8654             emit_move_insn (mem, reg);
8655             size = GET_MODE_SIZE (GET_MODE (reg));
8656           }
8657       }
8659     /* The optimizer does not know that the call sets the function value
8660        registers we stored in the result block.  We avoid problems by
8661        claiming that all hard registers are used and clobbered at this
8662        point.  */
8663     emit_insn (gen_blockage ());
8665     DONE;
8666   }"
8669 (define_expand "untyped_return"
8670   [(match_operand:BLK 0 "memory_operand" "")
8671    (match_operand 1 "" "")]
8672   "TARGET_EITHER"
8673   "
8674   {
8675     int i;
8676     rtx addr = gen_reg_rtx (Pmode);
8677     rtx mem;
8678     int size = 0;
8680     emit_move_insn (addr, XEXP (operands[0], 0));
8681     mem = change_address (operands[0], BLKmode, addr);
8683     for (i = 0; i < XVECLEN (operands[1], 0); i++)
8684       {
8685         HOST_WIDE_INT offset = 0;
8686         rtx reg = SET_DEST (XVECEXP (operands[1], 0, i));
8688         if (size != 0)
8689           emit_move_insn (addr, plus_constant (Pmode, addr, size));
8691         mem = change_address (mem, GET_MODE (reg), NULL);
8692         if (REGNO (reg) == R0_REGNUM)
8693           {
8694             /* On thumb we have to use a write-back instruction.  */
8695             emit_insn (arm_gen_load_multiple (arm_regs_in_sequence, 4, addr,
8696                        TARGET_THUMB ? TRUE : FALSE, mem, &offset));
8697             size = TARGET_ARM ? 16 : 0;
8698           }
8699         else
8700           {
8701             emit_move_insn (reg, mem);
8702             size = GET_MODE_SIZE (GET_MODE (reg));
8703           }
8704       }
8706     /* Emit USE insns before the return.  */
8707     for (i = 0; i < XVECLEN (operands[1], 0); i++)
8708       emit_use (SET_DEST (XVECEXP (operands[1], 0, i)));
8710     /* Construct the return.  */
8711     expand_naked_return ();
8713     DONE;
8714   }"
8717 ;; UNSPEC_VOLATILE is considered to use and clobber all hard registers and
8718 ;; all of memory.  This blocks insns from being moved across this point.
8720 (define_insn "blockage"
8721   [(unspec_volatile [(const_int 0)] VUNSPEC_BLOCKAGE)]
8722   "TARGET_EITHER"
8723   ""
8724   [(set_attr "length" "0")
8725    (set_attr "type" "block")]
8728 (define_expand "casesi"
8729   [(match_operand:SI 0 "s_register_operand" "") ; index to jump on
8730    (match_operand:SI 1 "const_int_operand" "")  ; lower bound
8731    (match_operand:SI 2 "const_int_operand" "")  ; total range
8732    (match_operand:SI 3 "" "")                   ; table label
8733    (match_operand:SI 4 "" "")]                  ; Out of range label
8734   "TARGET_32BIT || optimize_size || flag_pic"
8735   "
8736   {
8737     enum insn_code code;
8738     if (operands[1] != const0_rtx)
8739       {
8740         rtx reg = gen_reg_rtx (SImode);
8742         emit_insn (gen_addsi3 (reg, operands[0],
8743                                gen_int_mode (-INTVAL (operands[1]),
8744                                              SImode)));
8745         operands[0] = reg;
8746       }
8748     if (TARGET_ARM)
8749       code = CODE_FOR_arm_casesi_internal;
8750     else if (TARGET_THUMB1)
8751       code = CODE_FOR_thumb1_casesi_internal_pic;
8752     else if (flag_pic)
8753       code = CODE_FOR_thumb2_casesi_internal_pic;
8754     else
8755       code = CODE_FOR_thumb2_casesi_internal;
8757     if (!insn_data[(int) code].operand[1].predicate(operands[2], SImode))
8758       operands[2] = force_reg (SImode, operands[2]);
8760     emit_jump_insn (GEN_FCN ((int) code) (operands[0], operands[2],
8761                                           operands[3], operands[4]));
8762     DONE;
8763   }"
8766 ;; The USE in this pattern is needed to tell flow analysis that this is
8767 ;; a CASESI insn.  It has no other purpose.
8768 (define_insn "arm_casesi_internal"
8769   [(parallel [(set (pc)
8770                (if_then_else
8771                 (leu (match_operand:SI 0 "s_register_operand" "r")
8772                      (match_operand:SI 1 "arm_rhs_operand" "rI"))
8773                 (mem:SI (plus:SI (mult:SI (match_dup 0) (const_int 4))
8774                                  (label_ref (match_operand 2 "" ""))))
8775                 (label_ref (match_operand 3 "" ""))))
8776               (clobber (reg:CC CC_REGNUM))
8777               (use (label_ref (match_dup 2)))])]
8778   "TARGET_ARM"
8779   "*
8780     if (flag_pic)
8781       return \"cmp\\t%0, %1\;addls\\t%|pc, %|pc, %0, asl #2\;b\\t%l3\";
8782     return   \"cmp\\t%0, %1\;ldrls\\t%|pc, [%|pc, %0, asl #2]\;b\\t%l3\";
8783   "
8784   [(set_attr "conds" "clob")
8785    (set_attr "length" "12")]
8788 (define_expand "thumb1_casesi_internal_pic"
8789   [(match_operand:SI 0 "s_register_operand" "")
8790    (match_operand:SI 1 "thumb1_cmp_operand" "")
8791    (match_operand 2 "" "")
8792    (match_operand 3 "" "")]
8793   "TARGET_THUMB1"
8794   {
8795     rtx reg0;
8796     rtx test = gen_rtx_GTU (VOIDmode, operands[0], operands[1]);
8797     emit_jump_insn (gen_cbranchsi4 (test, operands[0], operands[1],
8798                                     operands[3]));
8799     reg0 = gen_rtx_REG (SImode, 0);
8800     emit_move_insn (reg0, operands[0]);
8801     emit_jump_insn (gen_thumb1_casesi_dispatch (operands[2]/*, operands[3]*/));
8802     DONE;
8803   }
8806 (define_insn "thumb1_casesi_dispatch"
8807   [(parallel [(set (pc) (unspec [(reg:SI 0)
8808                                  (label_ref (match_operand 0 "" ""))
8809 ;;                               (label_ref (match_operand 1 "" ""))
8811                          UNSPEC_THUMB1_CASESI))
8812               (clobber (reg:SI IP_REGNUM))
8813               (clobber (reg:SI LR_REGNUM))])]
8814   "TARGET_THUMB1"
8815   "* return thumb1_output_casesi(operands);"
8816   [(set_attr "length" "4")]
8819 (define_expand "indirect_jump"
8820   [(set (pc)
8821         (match_operand:SI 0 "s_register_operand" ""))]
8822   "TARGET_EITHER"
8823   "
8824   /* Thumb-2 doesn't have mov pc, reg.  Explicitly set the low bit of the
8825      address and use bx.  */
8826   if (TARGET_THUMB2)
8827     {
8828       rtx tmp;
8829       tmp = gen_reg_rtx (SImode);
8830       emit_insn (gen_iorsi3 (tmp, operands[0], GEN_INT(1)));
8831       operands[0] = tmp;
8832     }
8833   "
8836 ;; NB Never uses BX.
8837 (define_insn "*arm_indirect_jump"
8838   [(set (pc)
8839         (match_operand:SI 0 "s_register_operand" "r"))]
8840   "TARGET_ARM"
8841   "mov%?\\t%|pc, %0\\t%@ indirect register jump"
8842   [(set_attr "predicable" "yes")]
8845 (define_insn "*load_indirect_jump"
8846   [(set (pc)
8847         (match_operand:SI 0 "memory_operand" "m"))]
8848   "TARGET_ARM"
8849   "ldr%?\\t%|pc, %0\\t%@ indirect memory jump"
8850   [(set_attr "type" "load1")
8851    (set_attr "pool_range" "4096")
8852    (set_attr "neg_pool_range" "4084")
8853    (set_attr "predicable" "yes")]
8856 ;; NB Never uses BX.
8857 (define_insn "*thumb1_indirect_jump"
8858   [(set (pc)
8859         (match_operand:SI 0 "register_operand" "l*r"))]
8860   "TARGET_THUMB1"
8861   "mov\\tpc, %0"
8862   [(set_attr "conds" "clob")
8863    (set_attr "length" "2")]
8867 ;; Misc insns
8869 (define_insn "nop"
8870   [(const_int 0)]
8871   "TARGET_EITHER"
8872   "*
8873   if (TARGET_UNIFIED_ASM)
8874     return \"nop\";
8875   if (TARGET_ARM)
8876     return \"mov%?\\t%|r0, %|r0\\t%@ nop\";
8877   return  \"mov\\tr8, r8\";
8878   "
8879   [(set (attr "length")
8880         (if_then_else (eq_attr "is_thumb" "yes")
8881                       (const_int 2)
8882                       (const_int 4)))]
8886 ;; Patterns to allow combination of arithmetic, cond code and shifts
8888 (define_insn "*arith_shiftsi"
8889   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r")
8890         (match_operator:SI 1 "shiftable_operator"
8891           [(match_operator:SI 3 "shift_operator"
8892              [(match_operand:SI 4 "s_register_operand" "r,r,r,r")
8893               (match_operand:SI 5 "shift_amount_operand" "M,M,M,r")])
8894            (match_operand:SI 2 "s_register_operand" "rk,rk,r,rk")]))]
8895   "TARGET_32BIT"
8896   "%i1%?\\t%0, %2, %4%S3"
8897   [(set_attr "predicable" "yes")
8898    (set_attr "shift" "4")
8899    (set_attr "arch" "a,t2,t2,a")
8900    ;; Thumb2 doesn't allow the stack pointer to be used for 
8901    ;; operand1 for all operations other than add and sub. In this case 
8902    ;; the minus operation is a candidate for an rsub and hence needs
8903    ;; to be disabled.
8904    ;; We have to make sure to disable the fourth alternative if
8905    ;; the shift_operator is MULT, since otherwise the insn will
8906    ;; also match a multiply_accumulate pattern and validate_change
8907    ;; will allow a replacement of the constant with a register
8908    ;; despite the checks done in shift_operator.
8909    (set_attr_alternative "insn_enabled"
8910                          [(const_string "yes")
8911                           (if_then_else
8912                            (match_operand:SI 1 "add_operator" "")
8913                            (const_string "yes") (const_string "no"))
8914                           (const_string "yes")
8915                           (if_then_else
8916                            (match_operand:SI 3 "mult_operator" "")
8917                            (const_string "no") (const_string "yes"))])
8918    (set_attr "type" "alu_shift,alu_shift,alu_shift,alu_shift_reg")])
8920 (define_split
8921   [(set (match_operand:SI 0 "s_register_operand" "")
8922         (match_operator:SI 1 "shiftable_operator"
8923          [(match_operator:SI 2 "shiftable_operator"
8924            [(match_operator:SI 3 "shift_operator"
8925              [(match_operand:SI 4 "s_register_operand" "")
8926               (match_operand:SI 5 "reg_or_int_operand" "")])
8927             (match_operand:SI 6 "s_register_operand" "")])
8928           (match_operand:SI 7 "arm_rhs_operand" "")]))
8929    (clobber (match_operand:SI 8 "s_register_operand" ""))]
8930   "TARGET_32BIT"
8931   [(set (match_dup 8)
8932         (match_op_dup 2 [(match_op_dup 3 [(match_dup 4) (match_dup 5)])
8933                          (match_dup 6)]))
8934    (set (match_dup 0)
8935         (match_op_dup 1 [(match_dup 8) (match_dup 7)]))]
8936   "")
8938 (define_insn "*arith_shiftsi_compare0"
8939   [(set (reg:CC_NOOV CC_REGNUM)
8940         (compare:CC_NOOV
8941          (match_operator:SI 1 "shiftable_operator"
8942           [(match_operator:SI 3 "shift_operator"
8943             [(match_operand:SI 4 "s_register_operand" "r,r")
8944              (match_operand:SI 5 "shift_amount_operand" "M,r")])
8945            (match_operand:SI 2 "s_register_operand" "r,r")])
8946          (const_int 0)))
8947    (set (match_operand:SI 0 "s_register_operand" "=r,r")
8948         (match_op_dup 1 [(match_op_dup 3 [(match_dup 4) (match_dup 5)])
8949                          (match_dup 2)]))]
8950   "TARGET_32BIT"
8951   "%i1%.\\t%0, %2, %4%S3"
8952   [(set_attr "conds" "set")
8953    (set_attr "shift" "4")
8954    (set_attr "arch" "32,a")
8955    (set_attr "type" "alu_shift,alu_shift_reg")])
8957 (define_insn "*arith_shiftsi_compare0_scratch"
8958   [(set (reg:CC_NOOV CC_REGNUM)
8959         (compare:CC_NOOV
8960          (match_operator:SI 1 "shiftable_operator"
8961           [(match_operator:SI 3 "shift_operator"
8962             [(match_operand:SI 4 "s_register_operand" "r,r")
8963              (match_operand:SI 5 "shift_amount_operand" "M,r")])
8964            (match_operand:SI 2 "s_register_operand" "r,r")])
8965          (const_int 0)))
8966    (clobber (match_scratch:SI 0 "=r,r"))]
8967   "TARGET_32BIT"
8968   "%i1%.\\t%0, %2, %4%S3"
8969   [(set_attr "conds" "set")
8970    (set_attr "shift" "4")
8971    (set_attr "arch" "32,a")
8972    (set_attr "type" "alu_shift,alu_shift_reg")])
8974 (define_insn "*sub_shiftsi"
8975   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
8976         (minus:SI (match_operand:SI 1 "s_register_operand" "r,r")
8977                   (match_operator:SI 2 "shift_operator"
8978                    [(match_operand:SI 3 "s_register_operand" "r,r")
8979                     (match_operand:SI 4 "shift_amount_operand" "M,r")])))]
8980   "TARGET_32BIT"
8981   "sub%?\\t%0, %1, %3%S2"
8982   [(set_attr "predicable" "yes")
8983    (set_attr "shift" "3")
8984    (set_attr "arch" "32,a")
8985    (set_attr "type" "alu_shift,alu_shift_reg")])
8987 (define_insn "*sub_shiftsi_compare0"
8988   [(set (reg:CC_NOOV CC_REGNUM)
8989         (compare:CC_NOOV
8990          (minus:SI (match_operand:SI 1 "s_register_operand" "r,r")
8991                    (match_operator:SI 2 "shift_operator"
8992                     [(match_operand:SI 3 "s_register_operand" "r,r")
8993                      (match_operand:SI 4 "shift_amount_operand" "M,rM")]))
8994          (const_int 0)))
8995    (set (match_operand:SI 0 "s_register_operand" "=r,r")
8996         (minus:SI (match_dup 1)
8997                   (match_op_dup 2 [(match_dup 3) (match_dup 4)])))]
8998   "TARGET_32BIT"
8999   "sub%.\\t%0, %1, %3%S2"
9000   [(set_attr "conds" "set")
9001    (set_attr "shift" "3")
9002    (set_attr "arch" "32,a")
9003    (set_attr "type" "alu_shift,alu_shift_reg")])
9005 (define_insn "*sub_shiftsi_compare0_scratch"
9006   [(set (reg:CC_NOOV CC_REGNUM)
9007         (compare:CC_NOOV
9008          (minus:SI (match_operand:SI 1 "s_register_operand" "r,r")
9009                    (match_operator:SI 2 "shift_operator"
9010                     [(match_operand:SI 3 "s_register_operand" "r,r")
9011                      (match_operand:SI 4 "shift_amount_operand" "M,rM")]))
9012          (const_int 0)))
9013    (clobber (match_scratch:SI 0 "=r,r"))]
9014   "TARGET_32BIT"
9015   "sub%.\\t%0, %1, %3%S2"
9016   [(set_attr "conds" "set")
9017    (set_attr "shift" "3")
9018    (set_attr "arch" "32,a")
9019    (set_attr "type" "alu_shift,alu_shift_reg")])
9022 (define_insn "*and_scc"
9023   [(set (match_operand:SI 0 "s_register_operand" "=r")
9024         (and:SI (match_operator:SI 1 "arm_comparison_operator"
9025                  [(match_operand 3 "cc_register" "") (const_int 0)])
9026                 (match_operand:SI 2 "s_register_operand" "r")))]
9027   "TARGET_ARM"
9028   "mov%D1\\t%0, #0\;and%d1\\t%0, %2, #1"
9029   [(set_attr "conds" "use")
9030    (set_attr "insn" "mov")
9031    (set_attr "length" "8")]
9034 (define_insn "*ior_scc"
9035   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9036         (ior:SI (match_operator:SI 2 "arm_comparison_operator"
9037                  [(match_operand 3 "cc_register" "") (const_int 0)])
9038                 (match_operand:SI 1 "s_register_operand" "0,?r")))]
9039   "TARGET_ARM"
9040   "@
9041    orr%d2\\t%0, %1, #1
9042    mov%D2\\t%0, %1\;orr%d2\\t%0, %1, #1"
9043   [(set_attr "conds" "use")
9044    (set_attr "length" "4,8")]
9047 ; A series of splitters for the compare_scc pattern below.  Note that
9048 ; order is important.
9049 (define_split
9050   [(set (match_operand:SI 0 "s_register_operand" "")
9051         (lt:SI (match_operand:SI 1 "s_register_operand" "")
9052                (const_int 0)))
9053    (clobber (reg:CC CC_REGNUM))]
9054   "TARGET_32BIT && reload_completed"
9055   [(set (match_dup 0) (lshiftrt:SI (match_dup 1) (const_int 31)))])
9057 (define_split
9058   [(set (match_operand:SI 0 "s_register_operand" "")
9059         (ge:SI (match_operand:SI 1 "s_register_operand" "")
9060                (const_int 0)))
9061    (clobber (reg:CC CC_REGNUM))]
9062   "TARGET_32BIT && reload_completed"
9063   [(set (match_dup 0) (not:SI (match_dup 1)))
9064    (set (match_dup 0) (lshiftrt:SI (match_dup 0) (const_int 31)))])
9066 (define_split
9067   [(set (match_operand:SI 0 "s_register_operand" "")
9068         (eq:SI (match_operand:SI 1 "s_register_operand" "")
9069                (const_int 0)))
9070    (clobber (reg:CC CC_REGNUM))]
9071   "TARGET_32BIT && reload_completed"
9072   [(parallel
9073     [(set (reg:CC CC_REGNUM)
9074           (compare:CC (const_int 1) (match_dup 1)))
9075      (set (match_dup 0)
9076           (minus:SI (const_int 1) (match_dup 1)))])
9077    (cond_exec (ltu:CC (reg:CC CC_REGNUM) (const_int 0))
9078               (set (match_dup 0) (const_int 0)))])
9080 (define_split
9081   [(set (match_operand:SI 0 "s_register_operand" "")
9082         (ne:SI (match_operand:SI 1 "s_register_operand" "")
9083                (match_operand:SI 2 "const_int_operand" "")))
9084    (clobber (reg:CC CC_REGNUM))]
9085   "TARGET_32BIT && reload_completed"
9086   [(parallel
9087     [(set (reg:CC CC_REGNUM)
9088           (compare:CC (match_dup 1) (match_dup 2)))
9089      (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 3)))])
9090    (cond_exec (ne:CC (reg:CC CC_REGNUM) (const_int 0))
9091               (set (match_dup 0) (const_int 1)))]
9093   operands[3] = GEN_INT (-INTVAL (operands[2]));
9096 (define_split
9097   [(set (match_operand:SI 0 "s_register_operand" "")
9098         (ne:SI (match_operand:SI 1 "s_register_operand" "")
9099                (match_operand:SI 2 "arm_add_operand" "")))
9100    (clobber (reg:CC CC_REGNUM))]
9101   "TARGET_32BIT && reload_completed"
9102   [(parallel
9103     [(set (reg:CC_NOOV CC_REGNUM)
9104           (compare:CC_NOOV (minus:SI (match_dup 1) (match_dup 2))
9105                            (const_int 0)))
9106      (set (match_dup 0) (minus:SI (match_dup 1) (match_dup 2)))])
9107    (cond_exec (ne:CC_NOOV (reg:CC_NOOV CC_REGNUM) (const_int 0))
9108               (set (match_dup 0) (const_int 1)))])
9110 (define_insn_and_split "*compare_scc"
9111   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9112         (match_operator:SI 1 "arm_comparison_operator"
9113          [(match_operand:SI 2 "s_register_operand" "r,r")
9114           (match_operand:SI 3 "arm_add_operand" "rI,L")]))
9115    (clobber (reg:CC CC_REGNUM))]
9116   "TARGET_32BIT"
9117   "#"
9118   "&& reload_completed"
9119   [(set (reg:CC CC_REGNUM) (compare:CC (match_dup 2) (match_dup 3)))
9120    (cond_exec (match_dup 4) (set (match_dup 0) (const_int 0)))
9121    (cond_exec (match_dup 5) (set (match_dup 0) (const_int 1)))]
9123   rtx tmp1;
9124   enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
9125                                            operands[2], operands[3]);
9126   enum rtx_code rc = GET_CODE (operands[1]);
9128   tmp1 = gen_rtx_REG (mode, CC_REGNUM);
9130   operands[5] = gen_rtx_fmt_ee (rc, VOIDmode, tmp1, const0_rtx);
9131   if (mode == CCFPmode || mode == CCFPEmode)
9132     rc = reverse_condition_maybe_unordered (rc);
9133   else
9134     rc = reverse_condition (rc);
9135   operands[4] = gen_rtx_fmt_ee (rc, VOIDmode, tmp1, const0_rtx);
9138 ;; Attempt to improve the sequence generated by the compare_scc splitters
9139 ;; not to use conditional execution.
9140 (define_peephole2
9141   [(set (reg:CC CC_REGNUM)
9142         (compare:CC (match_operand:SI 1 "register_operand" "")
9143                     (match_operand:SI 2 "arm_rhs_operand" "")))
9144    (cond_exec (ne (reg:CC CC_REGNUM) (const_int 0))
9145               (set (match_operand:SI 0 "register_operand" "") (const_int 0)))
9146    (cond_exec (eq (reg:CC CC_REGNUM) (const_int 0))
9147               (set (match_dup 0) (const_int 1)))
9148    (match_scratch:SI 3 "r")]
9149   "TARGET_32BIT"
9150   [(parallel
9151     [(set (reg:CC CC_REGNUM)
9152           (compare:CC (match_dup 1) (match_dup 2)))
9153      (set (match_dup 3) (minus:SI (match_dup 1) (match_dup 2)))])
9154    (parallel
9155     [(set (reg:CC CC_REGNUM)
9156           (compare:CC (const_int 0) (match_dup 3)))
9157      (set (match_dup 0) (minus:SI (const_int 0) (match_dup 3)))])
9158    (parallel
9159     [(set (match_dup 0)
9160           (plus:SI (plus:SI (match_dup 0) (match_dup 3))
9161                    (geu:SI (reg:CC CC_REGNUM) (const_int 0))))
9162      (clobber (reg:CC CC_REGNUM))])])
9164 (define_insn "*cond_move"
9165   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9166         (if_then_else:SI (match_operator 3 "equality_operator"
9167                           [(match_operator 4 "arm_comparison_operator"
9168                             [(match_operand 5 "cc_register" "") (const_int 0)])
9169                            (const_int 0)])
9170                          (match_operand:SI 1 "arm_rhs_operand" "0,rI,?rI")
9171                          (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))]
9172   "TARGET_ARM"
9173   "*
9174     if (GET_CODE (operands[3]) == NE)
9175       {
9176         if (which_alternative != 1)
9177           output_asm_insn (\"mov%D4\\t%0, %2\", operands);
9178         if (which_alternative != 0)
9179           output_asm_insn (\"mov%d4\\t%0, %1\", operands);
9180         return \"\";
9181       }
9182     if (which_alternative != 0)
9183       output_asm_insn (\"mov%D4\\t%0, %1\", operands);
9184     if (which_alternative != 1)
9185       output_asm_insn (\"mov%d4\\t%0, %2\", operands);
9186     return \"\";
9187   "
9188   [(set_attr "conds" "use")
9189    (set_attr "insn" "mov")
9190    (set_attr "length" "4,4,8")]
9193 (define_insn "*cond_arith"
9194   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9195         (match_operator:SI 5 "shiftable_operator" 
9196          [(match_operator:SI 4 "arm_comparison_operator"
9197            [(match_operand:SI 2 "s_register_operand" "r,r")
9198             (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
9199           (match_operand:SI 1 "s_register_operand" "0,?r")]))
9200    (clobber (reg:CC CC_REGNUM))]
9201   "TARGET_ARM"
9202   "*
9203     if (GET_CODE (operands[4]) == LT && operands[3] == const0_rtx)
9204       return \"%i5\\t%0, %1, %2, lsr #31\";
9206     output_asm_insn (\"cmp\\t%2, %3\", operands);
9207     if (GET_CODE (operands[5]) == AND)
9208       output_asm_insn (\"mov%D4\\t%0, #0\", operands);
9209     else if (GET_CODE (operands[5]) == MINUS)
9210       output_asm_insn (\"rsb%D4\\t%0, %1, #0\", operands);
9211     else if (which_alternative != 0)
9212       output_asm_insn (\"mov%D4\\t%0, %1\", operands);
9213     return \"%i5%d4\\t%0, %1, #1\";
9214   "
9215   [(set_attr "conds" "clob")
9216    (set_attr "length" "12")]
9219 (define_insn "*cond_sub"
9220   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9221         (minus:SI (match_operand:SI 1 "s_register_operand" "0,?r")
9222                   (match_operator:SI 4 "arm_comparison_operator"
9223                    [(match_operand:SI 2 "s_register_operand" "r,r")
9224                     (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))
9225    (clobber (reg:CC CC_REGNUM))]
9226   "TARGET_ARM"
9227   "*
9228     output_asm_insn (\"cmp\\t%2, %3\", operands);
9229     if (which_alternative != 0)
9230       output_asm_insn (\"mov%D4\\t%0, %1\", operands);
9231     return \"sub%d4\\t%0, %1, #1\";
9232   "
9233   [(set_attr "conds" "clob")
9234    (set_attr "length" "8,12")]
9237 (define_insn "*cmp_ite0"
9238   [(set (match_operand 6 "dominant_cc_register" "")
9239         (compare
9240          (if_then_else:SI
9241           (match_operator 4 "arm_comparison_operator"
9242            [(match_operand:SI 0 "s_register_operand"
9243                 "l,l,l,r,r,r,r,r,r")
9244             (match_operand:SI 1 "arm_add_operand"
9245                 "lPy,lPy,lPy,rI,L,rI,L,rI,L")])
9246           (match_operator:SI 5 "arm_comparison_operator"
9247            [(match_operand:SI 2 "s_register_operand"
9248                 "l,r,r,l,l,r,r,r,r")
9249             (match_operand:SI 3 "arm_add_operand"
9250                 "lPy,rI,L,lPy,lPy,rI,rI,L,L")])
9251           (const_int 0))
9252          (const_int 0)))]
9253   "TARGET_32BIT"
9254   "*
9255   {
9256     static const char * const cmp1[NUM_OF_COND_CMP][2] =
9257     {
9258       {\"cmp%d5\\t%0, %1\",
9259        \"cmp%d4\\t%2, %3\"},
9260       {\"cmn%d5\\t%0, #%n1\",
9261        \"cmp%d4\\t%2, %3\"},
9262       {\"cmp%d5\\t%0, %1\",
9263        \"cmn%d4\\t%2, #%n3\"},
9264       {\"cmn%d5\\t%0, #%n1\",
9265        \"cmn%d4\\t%2, #%n3\"}
9266     };
9267     static const char * const cmp2[NUM_OF_COND_CMP][2] =
9268     {
9269       {\"cmp\\t%2, %3\",
9270        \"cmp\\t%0, %1\"},
9271       {\"cmp\\t%2, %3\",
9272        \"cmn\\t%0, #%n1\"},
9273       {\"cmn\\t%2, #%n3\",
9274        \"cmp\\t%0, %1\"},
9275       {\"cmn\\t%2, #%n3\",
9276        \"cmn\\t%0, #%n1\"}
9277     };
9278     static const char * const ite[2] =
9279     {
9280       \"it\\t%d5\",
9281       \"it\\t%d4\"
9282     };
9283     static const int cmp_idx[9] = {CMP_CMP, CMP_CMP, CMP_CMN,
9284                                    CMP_CMP, CMN_CMP, CMP_CMP,
9285                                    CMN_CMP, CMP_CMN, CMN_CMN};
9286     int swap =
9287       comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
9289     output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
9290     if (TARGET_THUMB2) {
9291       output_asm_insn (ite[swap], operands);
9292     }
9293     output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
9294     return \"\";
9295   }"
9296   [(set_attr "conds" "set")
9297    (set_attr "arch" "t2,t2,t2,t2,t2,any,any,any,any")
9298    (set_attr_alternative "length"
9299       [(const_int 6)
9300        (const_int 8)
9301        (const_int 8)
9302        (const_int 8)
9303        (const_int 8)
9304        (if_then_else (eq_attr "is_thumb" "no")
9305            (const_int 8)
9306            (const_int 10))
9307        (if_then_else (eq_attr "is_thumb" "no")
9308            (const_int 8)
9309            (const_int 10))
9310        (if_then_else (eq_attr "is_thumb" "no")
9311            (const_int 8)
9312            (const_int 10))
9313        (if_then_else (eq_attr "is_thumb" "no")
9314            (const_int 8)
9315            (const_int 10))])]
9318 (define_insn "*cmp_ite1"
9319   [(set (match_operand 6 "dominant_cc_register" "")
9320         (compare
9321          (if_then_else:SI
9322           (match_operator 4 "arm_comparison_operator"
9323            [(match_operand:SI 0 "s_register_operand"
9324                 "l,l,l,r,r,r,r,r,r")
9325             (match_operand:SI 1 "arm_add_operand"
9326                 "lPy,lPy,lPy,rI,L,rI,L,rI,L")])
9327           (match_operator:SI 5 "arm_comparison_operator"
9328            [(match_operand:SI 2 "s_register_operand"
9329                 "l,r,r,l,l,r,r,r,r")
9330             (match_operand:SI 3 "arm_add_operand"
9331                 "lPy,rI,L,lPy,lPy,rI,rI,L,L")])
9332           (const_int 1))
9333          (const_int 0)))]
9334   "TARGET_32BIT"
9335   "*
9336   {
9337     static const char * const cmp1[NUM_OF_COND_CMP][2] =
9338     {
9339       {\"cmp\\t%0, %1\",
9340        \"cmp\\t%2, %3\"},
9341       {\"cmn\\t%0, #%n1\",
9342        \"cmp\\t%2, %3\"},
9343       {\"cmp\\t%0, %1\",
9344        \"cmn\\t%2, #%n3\"},
9345       {\"cmn\\t%0, #%n1\",
9346        \"cmn\\t%2, #%n3\"}
9347     };
9348     static const char * const cmp2[NUM_OF_COND_CMP][2] =
9349     {
9350       {\"cmp%d4\\t%2, %3\",
9351        \"cmp%D5\\t%0, %1\"},
9352       {\"cmp%d4\\t%2, %3\",
9353        \"cmn%D5\\t%0, #%n1\"},
9354       {\"cmn%d4\\t%2, #%n3\",
9355        \"cmp%D5\\t%0, %1\"},
9356       {\"cmn%d4\\t%2, #%n3\",
9357        \"cmn%D5\\t%0, #%n1\"}
9358     };
9359     static const char * const ite[2] =
9360     {
9361       \"it\\t%d4\",
9362       \"it\\t%D5\"
9363     };
9364     static const int cmp_idx[9] = {CMP_CMP, CMP_CMP, CMP_CMN,
9365                                    CMP_CMP, CMN_CMP, CMP_CMP,
9366                                    CMN_CMP, CMP_CMN, CMN_CMN};
9367     int swap =
9368       comparison_dominates_p (GET_CODE (operands[5]),
9369                               reverse_condition (GET_CODE (operands[4])));
9371     output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
9372     if (TARGET_THUMB2) {
9373       output_asm_insn (ite[swap], operands);
9374     }
9375     output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
9376     return \"\";
9377   }"
9378   [(set_attr "conds" "set")
9379    (set_attr "arch" "t2,t2,t2,t2,t2,any,any,any,any")
9380    (set_attr_alternative "length"
9381       [(const_int 6)
9382        (const_int 8)
9383        (const_int 8)
9384        (const_int 8)
9385        (const_int 8)
9386        (if_then_else (eq_attr "is_thumb" "no")
9387            (const_int 8)
9388            (const_int 10))
9389        (if_then_else (eq_attr "is_thumb" "no")
9390            (const_int 8)
9391            (const_int 10))
9392        (if_then_else (eq_attr "is_thumb" "no")
9393            (const_int 8)
9394            (const_int 10))
9395        (if_then_else (eq_attr "is_thumb" "no")
9396            (const_int 8)
9397            (const_int 10))])]
9400 (define_insn "*cmp_and"
9401   [(set (match_operand 6 "dominant_cc_register" "")
9402         (compare
9403          (and:SI
9404           (match_operator 4 "arm_comparison_operator"
9405            [(match_operand:SI 0 "s_register_operand" 
9406                 "l,l,l,r,r,r,r,r,r")
9407             (match_operand:SI 1 "arm_add_operand" 
9408                 "lPy,lPy,lPy,rI,L,rI,L,rI,L")])
9409           (match_operator:SI 5 "arm_comparison_operator"
9410            [(match_operand:SI 2 "s_register_operand" 
9411                 "l,r,r,l,l,r,r,r,r")
9412             (match_operand:SI 3 "arm_add_operand" 
9413                 "lPy,rI,L,lPy,lPy,rI,rI,L,L")]))
9414          (const_int 0)))]
9415   "TARGET_32BIT"
9416   "*
9417   {
9418     static const char *const cmp1[NUM_OF_COND_CMP][2] =
9419     {
9420       {\"cmp%d5\\t%0, %1\",
9421        \"cmp%d4\\t%2, %3\"},
9422       {\"cmn%d5\\t%0, #%n1\",
9423        \"cmp%d4\\t%2, %3\"},
9424       {\"cmp%d5\\t%0, %1\",
9425        \"cmn%d4\\t%2, #%n3\"},
9426       {\"cmn%d5\\t%0, #%n1\",
9427        \"cmn%d4\\t%2, #%n3\"}
9428     };
9429     static const char *const cmp2[NUM_OF_COND_CMP][2] =
9430     {
9431       {\"cmp\\t%2, %3\",
9432        \"cmp\\t%0, %1\"},
9433       {\"cmp\\t%2, %3\",
9434        \"cmn\\t%0, #%n1\"},
9435       {\"cmn\\t%2, #%n3\",
9436        \"cmp\\t%0, %1\"},
9437       {\"cmn\\t%2, #%n3\",
9438        \"cmn\\t%0, #%n1\"}
9439     };
9440     static const char *const ite[2] =
9441     {
9442       \"it\\t%d5\",
9443       \"it\\t%d4\"
9444     };
9445     static const int cmp_idx[9] = {CMP_CMP, CMP_CMP, CMP_CMN,
9446                                    CMP_CMP, CMN_CMP, CMP_CMP,
9447                                    CMN_CMP, CMP_CMN, CMN_CMN};
9448     int swap =
9449       comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
9451     output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
9452     if (TARGET_THUMB2) {
9453       output_asm_insn (ite[swap], operands);
9454     }
9455     output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
9456     return \"\";
9457   }"
9458   [(set_attr "conds" "set")
9459    (set_attr "predicable" "no")
9460    (set_attr "arch" "t2,t2,t2,t2,t2,any,any,any,any")
9461    (set_attr_alternative "length"
9462       [(const_int 6)
9463        (const_int 8)
9464        (const_int 8)
9465        (const_int 8)
9466        (const_int 8)
9467        (if_then_else (eq_attr "is_thumb" "no")
9468            (const_int 8)
9469            (const_int 10))
9470        (if_then_else (eq_attr "is_thumb" "no")
9471            (const_int 8)
9472            (const_int 10))
9473        (if_then_else (eq_attr "is_thumb" "no")
9474            (const_int 8)
9475            (const_int 10))
9476        (if_then_else (eq_attr "is_thumb" "no")
9477            (const_int 8)
9478            (const_int 10))])]
9481 (define_insn "*cmp_ior"
9482   [(set (match_operand 6 "dominant_cc_register" "")
9483         (compare
9484          (ior:SI
9485           (match_operator 4 "arm_comparison_operator"
9486            [(match_operand:SI 0 "s_register_operand"
9487                 "l,l,l,r,r,r,r,r,r")
9488             (match_operand:SI 1 "arm_add_operand"
9489                 "lPy,lPy,lPy,rI,L,rI,L,rI,L")])
9490           (match_operator:SI 5 "arm_comparison_operator"
9491            [(match_operand:SI 2 "s_register_operand"
9492                 "l,r,r,l,l,r,r,r,r")
9493             (match_operand:SI 3 "arm_add_operand"
9494                 "lPy,rI,L,lPy,lPy,rI,rI,L,L")]))
9495          (const_int 0)))]
9496   "TARGET_32BIT"
9497   "*
9498   {
9499     static const char *const cmp1[NUM_OF_COND_CMP][2] =
9500     {
9501       {\"cmp\\t%0, %1\",
9502        \"cmp\\t%2, %3\"},
9503       {\"cmn\\t%0, #%n1\",
9504        \"cmp\\t%2, %3\"},
9505       {\"cmp\\t%0, %1\",
9506        \"cmn\\t%2, #%n3\"},
9507       {\"cmn\\t%0, #%n1\",
9508        \"cmn\\t%2, #%n3\"}
9509     };
9510     static const char *const cmp2[NUM_OF_COND_CMP][2] =
9511     {
9512       {\"cmp%D4\\t%2, %3\",
9513        \"cmp%D5\\t%0, %1\"},
9514       {\"cmp%D4\\t%2, %3\",
9515        \"cmn%D5\\t%0, #%n1\"},
9516       {\"cmn%D4\\t%2, #%n3\",
9517        \"cmp%D5\\t%0, %1\"},
9518       {\"cmn%D4\\t%2, #%n3\",
9519        \"cmn%D5\\t%0, #%n1\"}
9520     };
9521     static const char *const ite[2] =
9522     {
9523       \"it\\t%D4\",
9524       \"it\\t%D5\"
9525     };
9526     static const int cmp_idx[9] = {CMP_CMP, CMP_CMP, CMP_CMN,
9527                                    CMP_CMP, CMN_CMP, CMP_CMP,
9528                                    CMN_CMP, CMP_CMN, CMN_CMN};
9529     int swap =
9530       comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
9532     output_asm_insn (cmp1[cmp_idx[which_alternative]][swap], operands);
9533     if (TARGET_THUMB2) {
9534       output_asm_insn (ite[swap], operands);
9535     }
9536     output_asm_insn (cmp2[cmp_idx[which_alternative]][swap], operands);
9537     return \"\";
9538   }
9539   "
9540   [(set_attr "conds" "set")
9541    (set_attr "arch" "t2,t2,t2,t2,t2,any,any,any,any")
9542    (set_attr_alternative "length"
9543       [(const_int 6)
9544        (const_int 8)
9545        (const_int 8)
9546        (const_int 8)
9547        (const_int 8)
9548        (if_then_else (eq_attr "is_thumb" "no")
9549            (const_int 8)
9550            (const_int 10))
9551        (if_then_else (eq_attr "is_thumb" "no")
9552            (const_int 8)
9553            (const_int 10))
9554        (if_then_else (eq_attr "is_thumb" "no")
9555            (const_int 8)
9556            (const_int 10))
9557        (if_then_else (eq_attr "is_thumb" "no")
9558            (const_int 8)
9559            (const_int 10))])]
9562 (define_insn_and_split "*ior_scc_scc"
9563   [(set (match_operand:SI 0 "s_register_operand" "=r")
9564         (ior:SI (match_operator:SI 3 "arm_comparison_operator"
9565                  [(match_operand:SI 1 "s_register_operand" "r")
9566                   (match_operand:SI 2 "arm_add_operand" "rIL")])
9567                 (match_operator:SI 6 "arm_comparison_operator"
9568                  [(match_operand:SI 4 "s_register_operand" "r")
9569                   (match_operand:SI 5 "arm_add_operand" "rIL")])))
9570    (clobber (reg:CC CC_REGNUM))]
9571   "TARGET_32BIT
9572    && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_OR_Y)
9573        != CCmode)"
9574   "#"
9575   "TARGET_32BIT && reload_completed"
9576   [(set (match_dup 7)
9577         (compare
9578          (ior:SI
9579           (match_op_dup 3 [(match_dup 1) (match_dup 2)])
9580           (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
9581          (const_int 0)))
9582    (set (match_dup 0) (ne:SI (match_dup 7) (const_int 0)))]
9583   "operands[7]
9584      = gen_rtx_REG (arm_select_dominance_cc_mode (operands[3], operands[6],
9585                                                   DOM_CC_X_OR_Y),
9586                     CC_REGNUM);"
9587   [(set_attr "conds" "clob")
9588    (set_attr "length" "16")])
9590 ; If the above pattern is followed by a CMP insn, then the compare is 
9591 ; redundant, since we can rework the conditional instruction that follows.
9592 (define_insn_and_split "*ior_scc_scc_cmp"
9593   [(set (match_operand 0 "dominant_cc_register" "")
9594         (compare (ior:SI (match_operator:SI 3 "arm_comparison_operator"
9595                           [(match_operand:SI 1 "s_register_operand" "r")
9596                            (match_operand:SI 2 "arm_add_operand" "rIL")])
9597                          (match_operator:SI 6 "arm_comparison_operator"
9598                           [(match_operand:SI 4 "s_register_operand" "r")
9599                            (match_operand:SI 5 "arm_add_operand" "rIL")]))
9600                  (const_int 0)))
9601    (set (match_operand:SI 7 "s_register_operand" "=r")
9602         (ior:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])
9603                 (match_op_dup 6 [(match_dup 4) (match_dup 5)])))]
9604   "TARGET_32BIT"
9605   "#"
9606   "TARGET_32BIT && reload_completed"
9607   [(set (match_dup 0)
9608         (compare
9609          (ior:SI
9610           (match_op_dup 3 [(match_dup 1) (match_dup 2)])
9611           (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
9612          (const_int 0)))
9613    (set (match_dup 7) (ne:SI (match_dup 0) (const_int 0)))]
9614   ""
9615   [(set_attr "conds" "set")
9616    (set_attr "length" "16")])
9618 (define_insn_and_split "*and_scc_scc"
9619   [(set (match_operand:SI 0 "s_register_operand" "=r")
9620         (and:SI (match_operator:SI 3 "arm_comparison_operator"
9621                  [(match_operand:SI 1 "s_register_operand" "r")
9622                   (match_operand:SI 2 "arm_add_operand" "rIL")])
9623                 (match_operator:SI 6 "arm_comparison_operator"
9624                  [(match_operand:SI 4 "s_register_operand" "r")
9625                   (match_operand:SI 5 "arm_add_operand" "rIL")])))
9626    (clobber (reg:CC CC_REGNUM))]
9627   "TARGET_32BIT
9628    && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
9629        != CCmode)"
9630   "#"
9631   "TARGET_32BIT && reload_completed
9632    && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
9633        != CCmode)"
9634   [(set (match_dup 7)
9635         (compare
9636          (and:SI
9637           (match_op_dup 3 [(match_dup 1) (match_dup 2)])
9638           (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
9639          (const_int 0)))
9640    (set (match_dup 0) (ne:SI (match_dup 7) (const_int 0)))]
9641   "operands[7]
9642      = gen_rtx_REG (arm_select_dominance_cc_mode (operands[3], operands[6],
9643                                                   DOM_CC_X_AND_Y),
9644                     CC_REGNUM);"
9645   [(set_attr "conds" "clob")
9646    (set_attr "length" "16")])
9648 ; If the above pattern is followed by a CMP insn, then the compare is 
9649 ; redundant, since we can rework the conditional instruction that follows.
9650 (define_insn_and_split "*and_scc_scc_cmp"
9651   [(set (match_operand 0 "dominant_cc_register" "")
9652         (compare (and:SI (match_operator:SI 3 "arm_comparison_operator"
9653                           [(match_operand:SI 1 "s_register_operand" "r")
9654                            (match_operand:SI 2 "arm_add_operand" "rIL")])
9655                          (match_operator:SI 6 "arm_comparison_operator"
9656                           [(match_operand:SI 4 "s_register_operand" "r")
9657                            (match_operand:SI 5 "arm_add_operand" "rIL")]))
9658                  (const_int 0)))
9659    (set (match_operand:SI 7 "s_register_operand" "=r")
9660         (and:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])
9661                 (match_op_dup 6 [(match_dup 4) (match_dup 5)])))]
9662   "TARGET_32BIT"
9663   "#"
9664   "TARGET_32BIT && reload_completed"
9665   [(set (match_dup 0)
9666         (compare
9667          (and:SI
9668           (match_op_dup 3 [(match_dup 1) (match_dup 2)])
9669           (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
9670          (const_int 0)))
9671    (set (match_dup 7) (ne:SI (match_dup 0) (const_int 0)))]
9672   ""
9673   [(set_attr "conds" "set")
9674    (set_attr "length" "16")])
9676 ;; If there is no dominance in the comparison, then we can still save an
9677 ;; instruction in the AND case, since we can know that the second compare
9678 ;; need only zero the value if false (if true, then the value is already
9679 ;; correct).
9680 (define_insn_and_split "*and_scc_scc_nodom"
9681   [(set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r")
9682         (and:SI (match_operator:SI 3 "arm_comparison_operator"
9683                  [(match_operand:SI 1 "s_register_operand" "r,r,0")
9684                   (match_operand:SI 2 "arm_add_operand" "rIL,0,rIL")])
9685                 (match_operator:SI 6 "arm_comparison_operator"
9686                  [(match_operand:SI 4 "s_register_operand" "r,r,r")
9687                   (match_operand:SI 5 "arm_add_operand" "rIL,rIL,rIL")])))
9688    (clobber (reg:CC CC_REGNUM))]
9689   "TARGET_32BIT
9690    && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
9691        == CCmode)"
9692   "#"
9693   "TARGET_32BIT && reload_completed"
9694   [(parallel [(set (match_dup 0)
9695                    (match_op_dup 3 [(match_dup 1) (match_dup 2)]))
9696               (clobber (reg:CC CC_REGNUM))])
9697    (set (match_dup 7) (match_op_dup 8 [(match_dup 4) (match_dup 5)]))
9698    (set (match_dup 0)
9699         (if_then_else:SI (match_op_dup 6 [(match_dup 7) (const_int 0)])
9700                          (match_dup 0)
9701                          (const_int 0)))]
9702   "operands[7] = gen_rtx_REG (SELECT_CC_MODE (GET_CODE (operands[6]),
9703                                               operands[4], operands[5]),
9704                               CC_REGNUM);
9705    operands[8] = gen_rtx_COMPARE (GET_MODE (operands[7]), operands[4],
9706                                   operands[5]);"
9707   [(set_attr "conds" "clob")
9708    (set_attr "length" "20")])
9710 (define_split
9711   [(set (reg:CC_NOOV CC_REGNUM)
9712         (compare:CC_NOOV (ior:SI
9713                           (and:SI (match_operand:SI 0 "s_register_operand" "")
9714                                   (const_int 1))
9715                           (match_operator:SI 1 "arm_comparison_operator"
9716                            [(match_operand:SI 2 "s_register_operand" "")
9717                             (match_operand:SI 3 "arm_add_operand" "")]))
9718                          (const_int 0)))
9719    (clobber (match_operand:SI 4 "s_register_operand" ""))]
9720   "TARGET_ARM"
9721   [(set (match_dup 4)
9722         (ior:SI (match_op_dup 1 [(match_dup 2) (match_dup 3)])
9723                 (match_dup 0)))
9724    (set (reg:CC_NOOV CC_REGNUM)
9725         (compare:CC_NOOV (and:SI (match_dup 4) (const_int 1))
9726                          (const_int 0)))]
9727   "")
9729 (define_split
9730   [(set (reg:CC_NOOV CC_REGNUM)
9731         (compare:CC_NOOV (ior:SI
9732                           (match_operator:SI 1 "arm_comparison_operator"
9733                            [(match_operand:SI 2 "s_register_operand" "")
9734                             (match_operand:SI 3 "arm_add_operand" "")])
9735                           (and:SI (match_operand:SI 0 "s_register_operand" "")
9736                                   (const_int 1)))
9737                          (const_int 0)))
9738    (clobber (match_operand:SI 4 "s_register_operand" ""))]
9739   "TARGET_ARM"
9740   [(set (match_dup 4)
9741         (ior:SI (match_op_dup 1 [(match_dup 2) (match_dup 3)])
9742                 (match_dup 0)))
9743    (set (reg:CC_NOOV CC_REGNUM)
9744         (compare:CC_NOOV (and:SI (match_dup 4) (const_int 1))
9745                          (const_int 0)))]
9746   "")
9747 ;; ??? The conditional patterns above need checking for Thumb-2 usefulness
9749 (define_insn "*negscc"
9750   [(set (match_operand:SI 0 "s_register_operand" "=r")
9751         (neg:SI (match_operator 3 "arm_comparison_operator"
9752                  [(match_operand:SI 1 "s_register_operand" "r")
9753                   (match_operand:SI 2 "arm_rhs_operand" "rI")])))
9754    (clobber (reg:CC CC_REGNUM))]
9755   "TARGET_ARM"
9756   "*
9757   if (GET_CODE (operands[3]) == LT && operands[2] == const0_rtx)
9758     return \"mov\\t%0, %1, asr #31\";
9760   if (GET_CODE (operands[3]) == NE)
9761     return \"subs\\t%0, %1, %2\;mvnne\\t%0, #0\";
9763   output_asm_insn (\"cmp\\t%1, %2\", operands);
9764   output_asm_insn (\"mov%D3\\t%0, #0\", operands);
9765   return \"mvn%d3\\t%0, #0\";
9766   "
9767   [(set_attr "conds" "clob")
9768    (set_attr "length" "12")]
9771 (define_insn "movcond"
9772   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9773         (if_then_else:SI
9774          (match_operator 5 "arm_comparison_operator"
9775           [(match_operand:SI 3 "s_register_operand" "r,r,r")
9776            (match_operand:SI 4 "arm_add_operand" "rIL,rIL,rIL")])
9777          (match_operand:SI 1 "arm_rhs_operand" "0,rI,?rI")
9778          (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
9779    (clobber (reg:CC CC_REGNUM))]
9780   "TARGET_ARM"
9781   "*
9782   if (GET_CODE (operands[5]) == LT
9783       && (operands[4] == const0_rtx))
9784     {
9785       if (which_alternative != 1 && GET_CODE (operands[1]) == REG)
9786         {
9787           if (operands[2] == const0_rtx)
9788             return \"and\\t%0, %1, %3, asr #31\";
9789           return \"ands\\t%0, %1, %3, asr #32\;movcc\\t%0, %2\";
9790         }
9791       else if (which_alternative != 0 && GET_CODE (operands[2]) == REG)
9792         {
9793           if (operands[1] == const0_rtx)
9794             return \"bic\\t%0, %2, %3, asr #31\";
9795           return \"bics\\t%0, %2, %3, asr #32\;movcs\\t%0, %1\";
9796         }
9797       /* The only case that falls through to here is when both ops 1 & 2
9798          are constants.  */
9799     }
9801   if (GET_CODE (operands[5]) == GE
9802       && (operands[4] == const0_rtx))
9803     {
9804       if (which_alternative != 1 && GET_CODE (operands[1]) == REG)
9805         {
9806           if (operands[2] == const0_rtx)
9807             return \"bic\\t%0, %1, %3, asr #31\";
9808           return \"bics\\t%0, %1, %3, asr #32\;movcs\\t%0, %2\";
9809         }
9810       else if (which_alternative != 0 && GET_CODE (operands[2]) == REG)
9811         {
9812           if (operands[1] == const0_rtx)
9813             return \"and\\t%0, %2, %3, asr #31\";
9814           return \"ands\\t%0, %2, %3, asr #32\;movcc\\t%0, %1\";
9815         }
9816       /* The only case that falls through to here is when both ops 1 & 2
9817          are constants.  */
9818     }
9819   if (GET_CODE (operands[4]) == CONST_INT
9820       && !const_ok_for_arm (INTVAL (operands[4])))
9821     output_asm_insn (\"cmn\\t%3, #%n4\", operands);
9822   else
9823     output_asm_insn (\"cmp\\t%3, %4\", operands);
9824   if (which_alternative != 0)
9825     output_asm_insn (\"mov%d5\\t%0, %1\", operands);
9826   if (which_alternative != 1)
9827     output_asm_insn (\"mov%D5\\t%0, %2\", operands);
9828   return \"\";
9829   "
9830   [(set_attr "conds" "clob")
9831    (set_attr "length" "8,8,12")]
9834 ;; ??? The patterns below need checking for Thumb-2 usefulness.
9836 (define_insn "*ifcompare_plus_move"
9837   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9838         (if_then_else:SI (match_operator 6 "arm_comparison_operator"
9839                           [(match_operand:SI 4 "s_register_operand" "r,r")
9840                            (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
9841                          (plus:SI
9842                           (match_operand:SI 2 "s_register_operand" "r,r")
9843                           (match_operand:SI 3 "arm_add_operand" "rIL,rIL"))
9844                          (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))
9845    (clobber (reg:CC CC_REGNUM))]
9846   "TARGET_ARM"
9847   "#"
9848   [(set_attr "conds" "clob")
9849    (set_attr "length" "8,12")]
9852 (define_insn "*if_plus_move"
9853   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r")
9854         (if_then_else:SI
9855          (match_operator 4 "arm_comparison_operator"
9856           [(match_operand 5 "cc_register" "") (const_int 0)])
9857          (plus:SI
9858           (match_operand:SI 2 "s_register_operand" "r,r,r,r")
9859           (match_operand:SI 3 "arm_add_operand" "rI,L,rI,L"))
9860          (match_operand:SI 1 "arm_rhs_operand" "0,0,?rI,?rI")))]
9861   "TARGET_ARM"
9862   "@
9863    add%d4\\t%0, %2, %3
9864    sub%d4\\t%0, %2, #%n3
9865    add%d4\\t%0, %2, %3\;mov%D4\\t%0, %1
9866    sub%d4\\t%0, %2, #%n3\;mov%D4\\t%0, %1"
9867   [(set_attr "conds" "use")
9868    (set_attr "length" "4,4,8,8")
9869    (set_attr "type" "*,*,*,*")]
9872 (define_insn "*ifcompare_move_plus"
9873   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9874         (if_then_else:SI (match_operator 6 "arm_comparison_operator"
9875                           [(match_operand:SI 4 "s_register_operand" "r,r")
9876                            (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
9877                          (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
9878                          (plus:SI
9879                           (match_operand:SI 2 "s_register_operand" "r,r")
9880                           (match_operand:SI 3 "arm_add_operand" "rIL,rIL"))))
9881    (clobber (reg:CC CC_REGNUM))]
9882   "TARGET_ARM"
9883   "#"
9884   [(set_attr "conds" "clob")
9885    (set_attr "length" "8,12")]
9888 (define_insn "*if_move_plus"
9889   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r")
9890         (if_then_else:SI
9891          (match_operator 4 "arm_comparison_operator"
9892           [(match_operand 5 "cc_register" "") (const_int 0)])
9893          (match_operand:SI 1 "arm_rhs_operand" "0,0,?rI,?rI")
9894          (plus:SI
9895           (match_operand:SI 2 "s_register_operand" "r,r,r,r")
9896           (match_operand:SI 3 "arm_add_operand" "rI,L,rI,L"))))]
9897   "TARGET_ARM"
9898   "@
9899    add%D4\\t%0, %2, %3
9900    sub%D4\\t%0, %2, #%n3
9901    add%D4\\t%0, %2, %3\;mov%d4\\t%0, %1
9902    sub%D4\\t%0, %2, #%n3\;mov%d4\\t%0, %1"
9903   [(set_attr "conds" "use")
9904    (set_attr "length" "4,4,8,8")
9905    (set_attr "type" "*,*,*,*")]
9908 (define_insn "*ifcompare_arith_arith"
9909   [(set (match_operand:SI 0 "s_register_operand" "=r")
9910         (if_then_else:SI (match_operator 9 "arm_comparison_operator"
9911                           [(match_operand:SI 5 "s_register_operand" "r")
9912                            (match_operand:SI 6 "arm_add_operand" "rIL")])
9913                          (match_operator:SI 8 "shiftable_operator"
9914                           [(match_operand:SI 1 "s_register_operand" "r")
9915                            (match_operand:SI 2 "arm_rhs_operand" "rI")])
9916                          (match_operator:SI 7 "shiftable_operator"
9917                           [(match_operand:SI 3 "s_register_operand" "r")
9918                            (match_operand:SI 4 "arm_rhs_operand" "rI")])))
9919    (clobber (reg:CC CC_REGNUM))]
9920   "TARGET_ARM"
9921   "#"
9922   [(set_attr "conds" "clob")
9923    (set_attr "length" "12")]
9926 (define_insn "*if_arith_arith"
9927   [(set (match_operand:SI 0 "s_register_operand" "=r")
9928         (if_then_else:SI (match_operator 5 "arm_comparison_operator"
9929                           [(match_operand 8 "cc_register" "") (const_int 0)])
9930                          (match_operator:SI 6 "shiftable_operator"
9931                           [(match_operand:SI 1 "s_register_operand" "r")
9932                            (match_operand:SI 2 "arm_rhs_operand" "rI")])
9933                          (match_operator:SI 7 "shiftable_operator"
9934                           [(match_operand:SI 3 "s_register_operand" "r")
9935                            (match_operand:SI 4 "arm_rhs_operand" "rI")])))]
9936   "TARGET_ARM"
9937   "%I6%d5\\t%0, %1, %2\;%I7%D5\\t%0, %3, %4"
9938   [(set_attr "conds" "use")
9939    (set_attr "length" "8")]
9942 (define_insn "*ifcompare_arith_move"
9943   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9944         (if_then_else:SI (match_operator 6 "arm_comparison_operator"
9945                           [(match_operand:SI 2 "s_register_operand" "r,r")
9946                            (match_operand:SI 3 "arm_add_operand" "rIL,rIL")])
9947                          (match_operator:SI 7 "shiftable_operator"
9948                           [(match_operand:SI 4 "s_register_operand" "r,r")
9949                            (match_operand:SI 5 "arm_rhs_operand" "rI,rI")])
9950                          (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))
9951    (clobber (reg:CC CC_REGNUM))]
9952   "TARGET_ARM"
9953   "*
9954   /* If we have an operation where (op x 0) is the identity operation and
9955      the conditional operator is LT or GE and we are comparing against zero and
9956      everything is in registers then we can do this in two instructions.  */
9957   if (operands[3] == const0_rtx
9958       && GET_CODE (operands[7]) != AND
9959       && GET_CODE (operands[5]) == REG
9960       && GET_CODE (operands[1]) == REG 
9961       && REGNO (operands[1]) == REGNO (operands[4])
9962       && REGNO (operands[4]) != REGNO (operands[0]))
9963     {
9964       if (GET_CODE (operands[6]) == LT)
9965         return \"and\\t%0, %5, %2, asr #31\;%I7\\t%0, %4, %0\";
9966       else if (GET_CODE (operands[6]) == GE)
9967         return \"bic\\t%0, %5, %2, asr #31\;%I7\\t%0, %4, %0\";
9968     }
9969   if (GET_CODE (operands[3]) == CONST_INT
9970       && !const_ok_for_arm (INTVAL (operands[3])))
9971     output_asm_insn (\"cmn\\t%2, #%n3\", operands);
9972   else
9973     output_asm_insn (\"cmp\\t%2, %3\", operands);
9974   output_asm_insn (\"%I7%d6\\t%0, %4, %5\", operands);
9975   if (which_alternative != 0)
9976     return \"mov%D6\\t%0, %1\";
9977   return \"\";
9978   "
9979   [(set_attr "conds" "clob")
9980    (set_attr "length" "8,12")]
9983 (define_insn "*if_arith_move"
9984   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9985         (if_then_else:SI (match_operator 4 "arm_comparison_operator"
9986                           [(match_operand 6 "cc_register" "") (const_int 0)])
9987                          (match_operator:SI 5 "shiftable_operator"
9988                           [(match_operand:SI 2 "s_register_operand" "r,r")
9989                            (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
9990                          (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))]
9991   "TARGET_ARM"
9992   "@
9993    %I5%d4\\t%0, %2, %3
9994    %I5%d4\\t%0, %2, %3\;mov%D4\\t%0, %1"
9995   [(set_attr "conds" "use")
9996    (set_attr "length" "4,8")
9997    (set_attr "type" "*,*")]
10000 (define_insn "*ifcompare_move_arith"
10001   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10002         (if_then_else:SI (match_operator 6 "arm_comparison_operator"
10003                           [(match_operand:SI 4 "s_register_operand" "r,r")
10004                            (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
10005                          (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
10006                          (match_operator:SI 7 "shiftable_operator"
10007                           [(match_operand:SI 2 "s_register_operand" "r,r")
10008                            (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))
10009    (clobber (reg:CC CC_REGNUM))]
10010   "TARGET_ARM"
10011   "*
10012   /* If we have an operation where (op x 0) is the identity operation and
10013      the conditional operator is LT or GE and we are comparing against zero and
10014      everything is in registers then we can do this in two instructions */
10015   if (operands[5] == const0_rtx
10016       && GET_CODE (operands[7]) != AND
10017       && GET_CODE (operands[3]) == REG
10018       && GET_CODE (operands[1]) == REG 
10019       && REGNO (operands[1]) == REGNO (operands[2])
10020       && REGNO (operands[2]) != REGNO (operands[0]))
10021     {
10022       if (GET_CODE (operands[6]) == GE)
10023         return \"and\\t%0, %3, %4, asr #31\;%I7\\t%0, %2, %0\";
10024       else if (GET_CODE (operands[6]) == LT)
10025         return \"bic\\t%0, %3, %4, asr #31\;%I7\\t%0, %2, %0\";
10026     }
10028   if (GET_CODE (operands[5]) == CONST_INT
10029       && !const_ok_for_arm (INTVAL (operands[5])))
10030     output_asm_insn (\"cmn\\t%4, #%n5\", operands);
10031   else
10032     output_asm_insn (\"cmp\\t%4, %5\", operands);
10034   if (which_alternative != 0)
10035     output_asm_insn (\"mov%d6\\t%0, %1\", operands);
10036   return \"%I7%D6\\t%0, %2, %3\";
10037   "
10038   [(set_attr "conds" "clob")
10039    (set_attr "length" "8,12")]
10042 (define_insn "*if_move_arith"
10043   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10044         (if_then_else:SI
10045          (match_operator 4 "arm_comparison_operator"
10046           [(match_operand 6 "cc_register" "") (const_int 0)])
10047          (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
10048          (match_operator:SI 5 "shiftable_operator"
10049           [(match_operand:SI 2 "s_register_operand" "r,r")
10050            (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))]
10051   "TARGET_ARM"
10052   "@
10053    %I5%D4\\t%0, %2, %3
10054    %I5%D4\\t%0, %2, %3\;mov%d4\\t%0, %1"
10055   [(set_attr "conds" "use")
10056    (set_attr "length" "4,8")
10057    (set_attr "type" "*,*")]
10060 (define_insn "*ifcompare_move_not"
10061   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10062         (if_then_else:SI
10063          (match_operator 5 "arm_comparison_operator"
10064           [(match_operand:SI 3 "s_register_operand" "r,r")
10065            (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
10066          (match_operand:SI 1 "arm_not_operand" "0,?rIK")
10067          (not:SI
10068           (match_operand:SI 2 "s_register_operand" "r,r"))))
10069    (clobber (reg:CC CC_REGNUM))]
10070   "TARGET_ARM"
10071   "#"
10072   [(set_attr "conds" "clob")
10073    (set_attr "length" "8,12")]
10076 (define_insn "*if_move_not"
10077   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10078         (if_then_else:SI
10079          (match_operator 4 "arm_comparison_operator"
10080           [(match_operand 3 "cc_register" "") (const_int 0)])
10081          (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
10082          (not:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))))]
10083   "TARGET_ARM"
10084   "@
10085    mvn%D4\\t%0, %2
10086    mov%d4\\t%0, %1\;mvn%D4\\t%0, %2
10087    mvn%d4\\t%0, #%B1\;mvn%D4\\t%0, %2"
10088   [(set_attr "conds" "use")
10089    (set_attr "insn" "mvn")
10090    (set_attr "length" "4,8,8")]
10093 (define_insn "*ifcompare_not_move"
10094   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10095         (if_then_else:SI 
10096          (match_operator 5 "arm_comparison_operator"
10097           [(match_operand:SI 3 "s_register_operand" "r,r")
10098            (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
10099          (not:SI
10100           (match_operand:SI 2 "s_register_operand" "r,r"))
10101          (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
10102    (clobber (reg:CC CC_REGNUM))]
10103   "TARGET_ARM"
10104   "#"
10105   [(set_attr "conds" "clob")
10106    (set_attr "length" "8,12")]
10109 (define_insn "*if_not_move"
10110   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10111         (if_then_else:SI
10112          (match_operator 4 "arm_comparison_operator"
10113           [(match_operand 3 "cc_register" "") (const_int 0)])
10114          (not:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))
10115          (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
10116   "TARGET_ARM"
10117   "@
10118    mvn%d4\\t%0, %2
10119    mov%D4\\t%0, %1\;mvn%d4\\t%0, %2
10120    mvn%D4\\t%0, #%B1\;mvn%d4\\t%0, %2"
10121   [(set_attr "conds" "use")
10122    (set_attr "insn" "mvn")
10123    (set_attr "length" "4,8,8")]
10126 (define_insn "*ifcompare_shift_move"
10127   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10128         (if_then_else:SI
10129          (match_operator 6 "arm_comparison_operator"
10130           [(match_operand:SI 4 "s_register_operand" "r,r")
10131            (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
10132          (match_operator:SI 7 "shift_operator"
10133           [(match_operand:SI 2 "s_register_operand" "r,r")
10134            (match_operand:SI 3 "arm_rhs_operand" "rM,rM")])
10135          (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
10136    (clobber (reg:CC CC_REGNUM))]
10137   "TARGET_ARM"
10138   "#"
10139   [(set_attr "conds" "clob")
10140    (set_attr "length" "8,12")]
10143 (define_insn "*if_shift_move"
10144   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10145         (if_then_else:SI
10146          (match_operator 5 "arm_comparison_operator"
10147           [(match_operand 6 "cc_register" "") (const_int 0)])
10148          (match_operator:SI 4 "shift_operator"
10149           [(match_operand:SI 2 "s_register_operand" "r,r,r")
10150            (match_operand:SI 3 "arm_rhs_operand" "rM,rM,rM")])
10151          (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
10152   "TARGET_ARM"
10153   "@
10154    mov%d5\\t%0, %2%S4
10155    mov%D5\\t%0, %1\;mov%d5\\t%0, %2%S4
10156    mvn%D5\\t%0, #%B1\;mov%d5\\t%0, %2%S4"
10157   [(set_attr "conds" "use")
10158    (set_attr "shift" "2")
10159    (set_attr "length" "4,8,8")
10160    (set_attr "insn" "mov")
10161    (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
10162                       (const_string "alu_shift")
10163                       (const_string "alu_shift_reg")))]
10166 (define_insn "*ifcompare_move_shift"
10167   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10168         (if_then_else:SI
10169          (match_operator 6 "arm_comparison_operator"
10170           [(match_operand:SI 4 "s_register_operand" "r,r")
10171            (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
10172          (match_operand:SI 1 "arm_not_operand" "0,?rIK")
10173          (match_operator:SI 7 "shift_operator"
10174           [(match_operand:SI 2 "s_register_operand" "r,r")
10175            (match_operand:SI 3 "arm_rhs_operand" "rM,rM")])))
10176    (clobber (reg:CC CC_REGNUM))]
10177   "TARGET_ARM"
10178   "#"
10179   [(set_attr "conds" "clob")
10180    (set_attr "length" "8,12")]
10183 (define_insn "*if_move_shift"
10184   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10185         (if_then_else:SI
10186          (match_operator 5 "arm_comparison_operator"
10187           [(match_operand 6 "cc_register" "") (const_int 0)])
10188          (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
10189          (match_operator:SI 4 "shift_operator"
10190           [(match_operand:SI 2 "s_register_operand" "r,r,r")
10191            (match_operand:SI 3 "arm_rhs_operand" "rM,rM,rM")])))]
10192   "TARGET_ARM"
10193   "@
10194    mov%D5\\t%0, %2%S4
10195    mov%d5\\t%0, %1\;mov%D5\\t%0, %2%S4
10196    mvn%d5\\t%0, #%B1\;mov%D5\\t%0, %2%S4"
10197   [(set_attr "conds" "use")
10198    (set_attr "shift" "2")
10199    (set_attr "length" "4,8,8")
10200    (set_attr "insn" "mov")
10201    (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
10202                       (const_string "alu_shift")
10203                       (const_string "alu_shift_reg")))]
10206 (define_insn "*ifcompare_shift_shift"
10207   [(set (match_operand:SI 0 "s_register_operand" "=r")
10208         (if_then_else:SI
10209          (match_operator 7 "arm_comparison_operator"
10210           [(match_operand:SI 5 "s_register_operand" "r")
10211            (match_operand:SI 6 "arm_add_operand" "rIL")])
10212          (match_operator:SI 8 "shift_operator"
10213           [(match_operand:SI 1 "s_register_operand" "r")
10214            (match_operand:SI 2 "arm_rhs_operand" "rM")])
10215          (match_operator:SI 9 "shift_operator"
10216           [(match_operand:SI 3 "s_register_operand" "r")
10217            (match_operand:SI 4 "arm_rhs_operand" "rM")])))
10218    (clobber (reg:CC CC_REGNUM))]
10219   "TARGET_ARM"
10220   "#"
10221   [(set_attr "conds" "clob")
10222    (set_attr "length" "12")]
10225 (define_insn "*if_shift_shift"
10226   [(set (match_operand:SI 0 "s_register_operand" "=r")
10227         (if_then_else:SI
10228          (match_operator 5 "arm_comparison_operator"
10229           [(match_operand 8 "cc_register" "") (const_int 0)])
10230          (match_operator:SI 6 "shift_operator"
10231           [(match_operand:SI 1 "s_register_operand" "r")
10232            (match_operand:SI 2 "arm_rhs_operand" "rM")])
10233          (match_operator:SI 7 "shift_operator"
10234           [(match_operand:SI 3 "s_register_operand" "r")
10235            (match_operand:SI 4 "arm_rhs_operand" "rM")])))]
10236   "TARGET_ARM"
10237   "mov%d5\\t%0, %1%S6\;mov%D5\\t%0, %3%S7"
10238   [(set_attr "conds" "use")
10239    (set_attr "shift" "1")
10240    (set_attr "length" "8")
10241    (set_attr "insn" "mov")
10242    (set (attr "type") (if_then_else
10243                         (and (match_operand 2 "const_int_operand" "")
10244                              (match_operand 4 "const_int_operand" ""))
10245                       (const_string "alu_shift")
10246                       (const_string "alu_shift_reg")))]
10249 (define_insn "*ifcompare_not_arith"
10250   [(set (match_operand:SI 0 "s_register_operand" "=r")
10251         (if_then_else:SI
10252          (match_operator 6 "arm_comparison_operator"
10253           [(match_operand:SI 4 "s_register_operand" "r")
10254            (match_operand:SI 5 "arm_add_operand" "rIL")])
10255          (not:SI (match_operand:SI 1 "s_register_operand" "r"))
10256          (match_operator:SI 7 "shiftable_operator"
10257           [(match_operand:SI 2 "s_register_operand" "r")
10258            (match_operand:SI 3 "arm_rhs_operand" "rI")])))
10259    (clobber (reg:CC CC_REGNUM))]
10260   "TARGET_ARM"
10261   "#"
10262   [(set_attr "conds" "clob")
10263    (set_attr "length" "12")]
10266 (define_insn "*if_not_arith"
10267   [(set (match_operand:SI 0 "s_register_operand" "=r")
10268         (if_then_else:SI
10269          (match_operator 5 "arm_comparison_operator"
10270           [(match_operand 4 "cc_register" "") (const_int 0)])
10271          (not:SI (match_operand:SI 1 "s_register_operand" "r"))
10272          (match_operator:SI 6 "shiftable_operator"
10273           [(match_operand:SI 2 "s_register_operand" "r")
10274            (match_operand:SI 3 "arm_rhs_operand" "rI")])))]
10275   "TARGET_ARM"
10276   "mvn%d5\\t%0, %1\;%I6%D5\\t%0, %2, %3"
10277   [(set_attr "conds" "use")
10278    (set_attr "insn" "mvn")
10279    (set_attr "length" "8")]
10282 (define_insn "*ifcompare_arith_not"
10283   [(set (match_operand:SI 0 "s_register_operand" "=r")
10284         (if_then_else:SI
10285          (match_operator 6 "arm_comparison_operator"
10286           [(match_operand:SI 4 "s_register_operand" "r")
10287            (match_operand:SI 5 "arm_add_operand" "rIL")])
10288          (match_operator:SI 7 "shiftable_operator"
10289           [(match_operand:SI 2 "s_register_operand" "r")
10290            (match_operand:SI 3 "arm_rhs_operand" "rI")])
10291          (not:SI (match_operand:SI 1 "s_register_operand" "r"))))
10292    (clobber (reg:CC CC_REGNUM))]
10293   "TARGET_ARM"
10294   "#"
10295   [(set_attr "conds" "clob")
10296    (set_attr "length" "12")]
10299 (define_insn "*if_arith_not"
10300   [(set (match_operand:SI 0 "s_register_operand" "=r")
10301         (if_then_else:SI
10302          (match_operator 5 "arm_comparison_operator"
10303           [(match_operand 4 "cc_register" "") (const_int 0)])
10304          (match_operator:SI 6 "shiftable_operator"
10305           [(match_operand:SI 2 "s_register_operand" "r")
10306            (match_operand:SI 3 "arm_rhs_operand" "rI")])
10307          (not:SI (match_operand:SI 1 "s_register_operand" "r"))))]
10308   "TARGET_ARM"
10309   "mvn%D5\\t%0, %1\;%I6%d5\\t%0, %2, %3"
10310   [(set_attr "conds" "use")
10311    (set_attr "insn" "mvn")
10312    (set_attr "length" "8")]
10315 (define_insn "*ifcompare_neg_move"
10316   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10317         (if_then_else:SI
10318          (match_operator 5 "arm_comparison_operator"
10319           [(match_operand:SI 3 "s_register_operand" "r,r")
10320            (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
10321          (neg:SI (match_operand:SI 2 "s_register_operand" "r,r"))
10322          (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
10323    (clobber (reg:CC CC_REGNUM))]
10324   "TARGET_ARM"
10325   "#"
10326   [(set_attr "conds" "clob")
10327    (set_attr "length" "8,12")]
10330 (define_insn "*if_neg_move"
10331   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10332         (if_then_else:SI
10333          (match_operator 4 "arm_comparison_operator"
10334           [(match_operand 3 "cc_register" "") (const_int 0)])
10335          (neg:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))
10336          (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
10337   "TARGET_ARM"
10338   "@
10339    rsb%d4\\t%0, %2, #0
10340    mov%D4\\t%0, %1\;rsb%d4\\t%0, %2, #0
10341    mvn%D4\\t%0, #%B1\;rsb%d4\\t%0, %2, #0"
10342   [(set_attr "conds" "use")
10343    (set_attr "length" "4,8,8")]
10346 (define_insn "*ifcompare_move_neg"
10347   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10348         (if_then_else:SI
10349          (match_operator 5 "arm_comparison_operator"
10350           [(match_operand:SI 3 "s_register_operand" "r,r")
10351            (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
10352          (match_operand:SI 1 "arm_not_operand" "0,?rIK")
10353          (neg:SI (match_operand:SI 2 "s_register_operand" "r,r"))))
10354    (clobber (reg:CC CC_REGNUM))]
10355   "TARGET_ARM"
10356   "#"
10357   [(set_attr "conds" "clob")
10358    (set_attr "length" "8,12")]
10361 (define_insn "*if_move_neg"
10362   [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
10363         (if_then_else:SI
10364          (match_operator 4 "arm_comparison_operator"
10365           [(match_operand 3 "cc_register" "") (const_int 0)])
10366          (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
10367          (neg:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))))]
10368   "TARGET_ARM"
10369   "@
10370    rsb%D4\\t%0, %2, #0
10371    mov%d4\\t%0, %1\;rsb%D4\\t%0, %2, #0
10372    mvn%d4\\t%0, #%B1\;rsb%D4\\t%0, %2, #0"
10373   [(set_attr "conds" "use")
10374    (set_attr "length" "4,8,8")]
10377 (define_insn "*arith_adjacentmem"
10378   [(set (match_operand:SI 0 "s_register_operand" "=r")
10379         (match_operator:SI 1 "shiftable_operator"
10380          [(match_operand:SI 2 "memory_operand" "m")
10381           (match_operand:SI 3 "memory_operand" "m")]))
10382    (clobber (match_scratch:SI 4 "=r"))]
10383   "TARGET_ARM && adjacent_mem_locations (operands[2], operands[3])"
10384   "*
10385   {
10386     rtx ldm[3];
10387     rtx arith[4];
10388     rtx base_reg;
10389     HOST_WIDE_INT val1 = 0, val2 = 0;
10391     if (REGNO (operands[0]) > REGNO (operands[4]))
10392       {
10393         ldm[1] = operands[4];
10394         ldm[2] = operands[0];
10395       }
10396     else
10397       {
10398         ldm[1] = operands[0];
10399         ldm[2] = operands[4];
10400       }
10402     base_reg = XEXP (operands[2], 0);
10404     if (!REG_P (base_reg))
10405       {
10406         val1 = INTVAL (XEXP (base_reg, 1));
10407         base_reg = XEXP (base_reg, 0);
10408       }
10410     if (!REG_P (XEXP (operands[3], 0)))
10411       val2 = INTVAL (XEXP (XEXP (operands[3], 0), 1));
10413     arith[0] = operands[0];
10414     arith[3] = operands[1];
10416     if (val1 < val2)
10417       {
10418         arith[1] = ldm[1];
10419         arith[2] = ldm[2];
10420       }
10421     else
10422       {
10423         arith[1] = ldm[2];
10424         arith[2] = ldm[1];
10425       }
10427     ldm[0] = base_reg;
10428     if (val1 !=0 && val2 != 0)
10429       {
10430         rtx ops[3];
10432         if (val1 == 4 || val2 == 4)
10433           /* Other val must be 8, since we know they are adjacent and neither
10434              is zero.  */
10435           output_asm_insn (\"ldm%(ib%)\\t%0, {%1, %2}\", ldm);
10436         else if (const_ok_for_arm (val1) || const_ok_for_arm (-val1))
10437           {
10438             ldm[0] = ops[0] = operands[4];
10439             ops[1] = base_reg;
10440             ops[2] = GEN_INT (val1);
10441             output_add_immediate (ops);
10442             if (val1 < val2)
10443               output_asm_insn (\"ldm%(ia%)\\t%0, {%1, %2}\", ldm);
10444             else
10445               output_asm_insn (\"ldm%(da%)\\t%0, {%1, %2}\", ldm);
10446           }
10447         else
10448           {
10449             /* Offset is out of range for a single add, so use two ldr.  */
10450             ops[0] = ldm[1];
10451             ops[1] = base_reg;
10452             ops[2] = GEN_INT (val1);
10453             output_asm_insn (\"ldr%?\\t%0, [%1, %2]\", ops);
10454             ops[0] = ldm[2];
10455             ops[2] = GEN_INT (val2);
10456             output_asm_insn (\"ldr%?\\t%0, [%1, %2]\", ops);
10457           }
10458       }
10459     else if (val1 != 0)
10460       {
10461         if (val1 < val2)
10462           output_asm_insn (\"ldm%(da%)\\t%0, {%1, %2}\", ldm);
10463         else
10464           output_asm_insn (\"ldm%(ia%)\\t%0, {%1, %2}\", ldm);
10465       }
10466     else
10467       {
10468         if (val1 < val2)
10469           output_asm_insn (\"ldm%(ia%)\\t%0, {%1, %2}\", ldm);
10470         else
10471           output_asm_insn (\"ldm%(da%)\\t%0, {%1, %2}\", ldm);
10472       }
10473     output_asm_insn (\"%I3%?\\t%0, %1, %2\", arith);
10474     return \"\";
10475   }"
10476   [(set_attr "length" "12")
10477    (set_attr "predicable" "yes")
10478    (set_attr "type" "load1")]
10481 ; This pattern is never tried by combine, so do it as a peephole
10483 (define_peephole2
10484   [(set (match_operand:SI 0 "arm_general_register_operand" "")
10485         (match_operand:SI 1 "arm_general_register_operand" ""))
10486    (set (reg:CC CC_REGNUM)
10487         (compare:CC (match_dup 1) (const_int 0)))]
10488   "TARGET_ARM"
10489   [(parallel [(set (reg:CC CC_REGNUM) (compare:CC (match_dup 1) (const_int 0)))
10490               (set (match_dup 0) (match_dup 1))])]
10491   ""
10494 (define_split
10495   [(set (match_operand:SI 0 "s_register_operand" "")
10496         (and:SI (ge:SI (match_operand:SI 1 "s_register_operand" "")
10497                        (const_int 0))
10498                 (neg:SI (match_operator:SI 2 "arm_comparison_operator"
10499                          [(match_operand:SI 3 "s_register_operand" "")
10500                           (match_operand:SI 4 "arm_rhs_operand" "")]))))
10501    (clobber (match_operand:SI 5 "s_register_operand" ""))]
10502   "TARGET_ARM"
10503   [(set (match_dup 5) (not:SI (ashiftrt:SI (match_dup 1) (const_int 31))))
10504    (set (match_dup 0) (and:SI (match_op_dup 2 [(match_dup 3) (match_dup 4)])
10505                               (match_dup 5)))]
10506   ""
10509 ;; This split can be used because CC_Z mode implies that the following
10510 ;; branch will be an equality, or an unsigned inequality, so the sign
10511 ;; extension is not needed.
10513 (define_split
10514   [(set (reg:CC_Z CC_REGNUM)
10515         (compare:CC_Z
10516          (ashift:SI (subreg:SI (match_operand:QI 0 "memory_operand" "") 0)
10517                     (const_int 24))
10518          (match_operand 1 "const_int_operand" "")))
10519    (clobber (match_scratch:SI 2 ""))]
10520   "TARGET_ARM
10521    && (((unsigned HOST_WIDE_INT) INTVAL (operands[1]))
10522        == (((unsigned HOST_WIDE_INT) INTVAL (operands[1])) >> 24) << 24)"
10523   [(set (match_dup 2) (zero_extend:SI (match_dup 0)))
10524    (set (reg:CC CC_REGNUM) (compare:CC (match_dup 2) (match_dup 1)))]
10525   "
10526   operands[1] = GEN_INT (((unsigned long) INTVAL (operands[1])) >> 24);
10527   "
10529 ;; ??? Check the patterns above for Thumb-2 usefulness
10531 (define_expand "prologue"
10532   [(clobber (const_int 0))]
10533   "TARGET_EITHER"
10534   "if (TARGET_32BIT)
10535      arm_expand_prologue ();
10536    else
10537      thumb1_expand_prologue ();
10538   DONE;
10539   "
10542 (define_expand "epilogue"
10543   [(clobber (const_int 0))]
10544   "TARGET_EITHER"
10545   "
10546   if (crtl->calls_eh_return)
10547     emit_insn (gen_prologue_use (gen_rtx_REG (Pmode, 2)));
10548   if (TARGET_THUMB1)
10549     thumb1_expand_epilogue ();
10550   else if (USE_RETURN_INSN (FALSE))
10551     {
10552       emit_jump_insn (gen_return ());
10553       DONE;
10554     }
10555   emit_jump_insn (gen_rtx_UNSPEC_VOLATILE (VOIDmode,
10556         gen_rtvec (1, ret_rtx), VUNSPEC_EPILOGUE));
10557   DONE;
10558   "
10561 (define_insn "prologue_thumb1_interwork"
10562   [(unspec_volatile [(const_int 0)] VUNSPEC_THUMB1_INTERWORK)]
10563   "TARGET_THUMB1"
10564   "* return thumb1_output_interwork ();"
10565   [(set_attr "length" "8")]
10568 ;; Note - although unspec_volatile's USE all hard registers,
10569 ;; USEs are ignored after relaod has completed.  Thus we need
10570 ;; to add an unspec of the link register to ensure that flow
10571 ;; does not think that it is unused by the sibcall branch that
10572 ;; will replace the standard function epilogue.
10573 (define_insn "sibcall_epilogue"
10574   [(parallel [(unspec:SI [(reg:SI LR_REGNUM)] UNSPEC_PROLOGUE_USE)
10575               (unspec_volatile [(return)] VUNSPEC_EPILOGUE)])]
10576   "TARGET_32BIT"
10577   "*
10578   if (use_return_insn (FALSE, next_nonnote_insn (insn)))
10579     return output_return_instruction (const_true_rtx, FALSE, FALSE);
10580   return arm_output_epilogue (next_nonnote_insn (insn));
10581   "
10582 ;; Length is absolute worst case
10583   [(set_attr "length" "44")
10584    (set_attr "type" "block")
10585    ;; We don't clobber the conditions, but the potential length of this
10586    ;; operation is sufficient to make conditionalizing the sequence 
10587    ;; unlikely to be profitable.
10588    (set_attr "conds" "clob")]
10591 (define_insn "*epilogue_insns"
10592   [(unspec_volatile [(return)] VUNSPEC_EPILOGUE)]
10593   "TARGET_EITHER"
10594   "*
10595   if (TARGET_32BIT)
10596     return arm_output_epilogue (NULL);
10597   else /* TARGET_THUMB1 */
10598     return thumb1_unexpanded_epilogue ();
10599   "
10600   ; Length is absolute worst case
10601   [(set_attr "length" "44")
10602    (set_attr "type" "block")
10603    ;; We don't clobber the conditions, but the potential length of this
10604    ;; operation is sufficient to make conditionalizing the sequence 
10605    ;; unlikely to be profitable.
10606    (set_attr "conds" "clob")]
10609 (define_expand "eh_epilogue"
10610   [(use (match_operand:SI 0 "register_operand" ""))
10611    (use (match_operand:SI 1 "register_operand" ""))
10612    (use (match_operand:SI 2 "register_operand" ""))]
10613   "TARGET_EITHER"
10614   "
10615   {
10616     cfun->machine->eh_epilogue_sp_ofs = operands[1];
10617     if (GET_CODE (operands[2]) != REG || REGNO (operands[2]) != 2)
10618       {
10619         rtx ra = gen_rtx_REG (Pmode, 2);
10621         emit_move_insn (ra, operands[2]);
10622         operands[2] = ra;
10623       }
10624     /* This is a hack -- we may have crystalized the function type too
10625        early.  */
10626     cfun->machine->func_type = 0;
10627   }"
10630 ;; This split is only used during output to reduce the number of patterns
10631 ;; that need assembler instructions adding to them.  We allowed the setting
10632 ;; of the conditions to be implicit during rtl generation so that
10633 ;; the conditional compare patterns would work.  However this conflicts to
10634 ;; some extent with the conditional data operations, so we have to split them
10635 ;; up again here.
10637 ;; ??? Need to audit these splitters for Thumb-2.  Why isn't normal
10638 ;; conditional execution sufficient?
10640 (define_split
10641   [(set (match_operand:SI 0 "s_register_operand" "")
10642         (if_then_else:SI (match_operator 1 "arm_comparison_operator"
10643                           [(match_operand 2 "" "") (match_operand 3 "" "")])
10644                          (match_dup 0)
10645                          (match_operand 4 "" "")))
10646    (clobber (reg:CC CC_REGNUM))]
10647   "TARGET_ARM && reload_completed"
10648   [(set (match_dup 5) (match_dup 6))
10649    (cond_exec (match_dup 7)
10650               (set (match_dup 0) (match_dup 4)))]
10651   "
10652   {
10653     enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
10654                                              operands[2], operands[3]);
10655     enum rtx_code rc = GET_CODE (operands[1]);
10657     operands[5] = gen_rtx_REG (mode, CC_REGNUM);
10658     operands[6] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
10659     if (mode == CCFPmode || mode == CCFPEmode)
10660       rc = reverse_condition_maybe_unordered (rc);
10661     else
10662       rc = reverse_condition (rc);
10664     operands[7] = gen_rtx_fmt_ee (rc, VOIDmode, operands[5], const0_rtx);
10665   }"
10668 (define_split
10669   [(set (match_operand:SI 0 "s_register_operand" "")
10670         (if_then_else:SI (match_operator 1 "arm_comparison_operator"
10671                           [(match_operand 2 "" "") (match_operand 3 "" "")])
10672                          (match_operand 4 "" "")
10673                          (match_dup 0)))
10674    (clobber (reg:CC CC_REGNUM))]
10675   "TARGET_ARM && reload_completed"
10676   [(set (match_dup 5) (match_dup 6))
10677    (cond_exec (match_op_dup 1 [(match_dup 5) (const_int 0)])
10678               (set (match_dup 0) (match_dup 4)))]
10679   "
10680   {
10681     enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
10682                                              operands[2], operands[3]);
10684     operands[5] = gen_rtx_REG (mode, CC_REGNUM);
10685     operands[6] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
10686   }"
10689 (define_split
10690   [(set (match_operand:SI 0 "s_register_operand" "")
10691         (if_then_else:SI (match_operator 1 "arm_comparison_operator"
10692                           [(match_operand 2 "" "") (match_operand 3 "" "")])
10693                          (match_operand 4 "" "")
10694                          (match_operand 5 "" "")))
10695    (clobber (reg:CC CC_REGNUM))]
10696   "TARGET_ARM && reload_completed"
10697   [(set (match_dup 6) (match_dup 7))
10698    (cond_exec (match_op_dup 1 [(match_dup 6) (const_int 0)])
10699               (set (match_dup 0) (match_dup 4)))
10700    (cond_exec (match_dup 8)
10701               (set (match_dup 0) (match_dup 5)))]
10702   "
10703   {
10704     enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
10705                                              operands[2], operands[3]);
10706     enum rtx_code rc = GET_CODE (operands[1]);
10708     operands[6] = gen_rtx_REG (mode, CC_REGNUM);
10709     operands[7] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
10710     if (mode == CCFPmode || mode == CCFPEmode)
10711       rc = reverse_condition_maybe_unordered (rc);
10712     else
10713       rc = reverse_condition (rc);
10715     operands[8] = gen_rtx_fmt_ee (rc, VOIDmode, operands[6], const0_rtx);
10716   }"
10719 (define_split
10720   [(set (match_operand:SI 0 "s_register_operand" "")
10721         (if_then_else:SI (match_operator 1 "arm_comparison_operator"
10722                           [(match_operand:SI 2 "s_register_operand" "")
10723                            (match_operand:SI 3 "arm_add_operand" "")])
10724                          (match_operand:SI 4 "arm_rhs_operand" "")
10725                          (not:SI
10726                           (match_operand:SI 5 "s_register_operand" ""))))
10727    (clobber (reg:CC CC_REGNUM))]
10728   "TARGET_ARM && reload_completed"
10729   [(set (match_dup 6) (match_dup 7))
10730    (cond_exec (match_op_dup 1 [(match_dup 6) (const_int 0)])
10731               (set (match_dup 0) (match_dup 4)))
10732    (cond_exec (match_dup 8)
10733               (set (match_dup 0) (not:SI (match_dup 5))))]
10734   "
10735   {
10736     enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
10737                                              operands[2], operands[3]);
10738     enum rtx_code rc = GET_CODE (operands[1]);
10740     operands[6] = gen_rtx_REG (mode, CC_REGNUM);
10741     operands[7] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
10742     if (mode == CCFPmode || mode == CCFPEmode)
10743       rc = reverse_condition_maybe_unordered (rc);
10744     else
10745       rc = reverse_condition (rc);
10747     operands[8] = gen_rtx_fmt_ee (rc, VOIDmode, operands[6], const0_rtx);
10748   }"
10751 (define_insn "*cond_move_not"
10752   [(set (match_operand:SI 0 "s_register_operand" "=r,r")
10753         (if_then_else:SI (match_operator 4 "arm_comparison_operator"
10754                           [(match_operand 3 "cc_register" "") (const_int 0)])
10755                          (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
10756                          (not:SI
10757                           (match_operand:SI 2 "s_register_operand" "r,r"))))]
10758   "TARGET_ARM"
10759   "@
10760    mvn%D4\\t%0, %2
10761    mov%d4\\t%0, %1\;mvn%D4\\t%0, %2"
10762   [(set_attr "conds" "use")
10763    (set_attr "insn" "mvn")
10764    (set_attr "length" "4,8")]
10767 ;; The next two patterns occur when an AND operation is followed by a
10768 ;; scc insn sequence 
10770 (define_insn "*sign_extract_onebit"
10771   [(set (match_operand:SI 0 "s_register_operand" "=r")
10772         (sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
10773                          (const_int 1)
10774                          (match_operand:SI 2 "const_int_operand" "n")))
10775     (clobber (reg:CC CC_REGNUM))]
10776   "TARGET_ARM"
10777   "*
10778     operands[2] = GEN_INT (1 << INTVAL (operands[2]));
10779     output_asm_insn (\"ands\\t%0, %1, %2\", operands);
10780     return \"mvnne\\t%0, #0\";
10781   "
10782   [(set_attr "conds" "clob")
10783    (set_attr "length" "8")]
10786 (define_insn "*not_signextract_onebit"
10787   [(set (match_operand:SI 0 "s_register_operand" "=r")
10788         (not:SI
10789          (sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
10790                           (const_int 1)
10791                           (match_operand:SI 2 "const_int_operand" "n"))))
10792    (clobber (reg:CC CC_REGNUM))]
10793   "TARGET_ARM"
10794   "*
10795     operands[2] = GEN_INT (1 << INTVAL (operands[2]));
10796     output_asm_insn (\"tst\\t%1, %2\", operands);
10797     output_asm_insn (\"mvneq\\t%0, #0\", operands);
10798     return \"movne\\t%0, #0\";
10799   "
10800   [(set_attr "conds" "clob")
10801    (set_attr "length" "12")]
10803 ;; ??? The above patterns need auditing for Thumb-2
10805 ;; Push multiple registers to the stack.  Registers are in parallel (use ...)
10806 ;; expressions.  For simplicity, the first register is also in the unspec
10807 ;; part.
10808 ;; To avoid the usage of GNU extension, the length attribute is computed
10809 ;; in a C function arm_attr_length_push_multi.
10810 (define_insn "*push_multi"
10811   [(match_parallel 2 "multi_register_push"
10812     [(set (match_operand:BLK 0 "push_mult_memory_operand" "")
10813           (unspec:BLK [(match_operand:SI 1 "s_register_operand" "")]
10814                       UNSPEC_PUSH_MULT))])]
10815   ""
10816   "*
10817   {
10818     int num_saves = XVECLEN (operands[2], 0);
10819      
10820     /* For the StrongARM at least it is faster to
10821        use STR to store only a single register.
10822        In Thumb mode always use push, and the assembler will pick
10823        something appropriate.  */
10824     if (num_saves == 1 && TARGET_ARM)
10825       output_asm_insn (\"str%?\\t%1, [%m0, #-4]!\", operands);
10826     else
10827       {
10828         int i;
10829         char pattern[100];
10831         if (TARGET_ARM)
10832             strcpy (pattern, \"stm%(fd%)\\t%m0!, {%1\");
10833         else if (TARGET_THUMB2)
10834             strcpy (pattern, \"push%?\\t{%1\");
10835         else
10836             strcpy (pattern, \"push\\t{%1\");
10838         for (i = 1; i < num_saves; i++)
10839           {
10840             strcat (pattern, \", %|\");
10841             strcat (pattern,
10842                     reg_names[REGNO (XEXP (XVECEXP (operands[2], 0, i), 0))]);
10843           }
10845         strcat (pattern, \"}\");
10846         output_asm_insn (pattern, operands);
10847       }
10849     return \"\";
10850   }"
10851   [(set_attr "type" "store4")
10852    (set (attr "length")
10853         (symbol_ref "arm_attr_length_push_multi (operands[2], operands[1])"))]
10856 (define_insn "stack_tie"
10857   [(set (mem:BLK (scratch))
10858         (unspec:BLK [(match_operand:SI 0 "s_register_operand" "rk")
10859                      (match_operand:SI 1 "s_register_operand" "rk")]
10860                     UNSPEC_PRLG_STK))]
10861   ""
10862   ""
10863   [(set_attr "length" "0")]
10866 ;; Special patterns for dealing with the constant pool
10868 (define_insn "align_4"
10869   [(unspec_volatile [(const_int 0)] VUNSPEC_ALIGN)]
10870   "TARGET_EITHER"
10871   "*
10872   assemble_align (32);
10873   return \"\";
10874   "
10877 (define_insn "align_8"
10878   [(unspec_volatile [(const_int 0)] VUNSPEC_ALIGN8)]
10879   "TARGET_EITHER"
10880   "*
10881   assemble_align (64);
10882   return \"\";
10883   "
10886 (define_insn "consttable_end"
10887   [(unspec_volatile [(const_int 0)] VUNSPEC_POOL_END)]
10888   "TARGET_EITHER"
10889   "*
10890   making_const_table = FALSE;
10891   return \"\";
10892   "
10895 (define_insn "consttable_1"
10896   [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_1)]
10897   "TARGET_THUMB1"
10898   "*
10899   making_const_table = TRUE;
10900   assemble_integer (operands[0], 1, BITS_PER_WORD, 1);
10901   assemble_zeros (3);
10902   return \"\";
10903   "
10904   [(set_attr "length" "4")]
10907 (define_insn "consttable_2"
10908   [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_2)]
10909   "TARGET_THUMB1"
10910   "*
10911   making_const_table = TRUE;
10912   gcc_assert (GET_MODE_CLASS (GET_MODE (operands[0])) != MODE_FLOAT);
10913   assemble_integer (operands[0], 2, BITS_PER_WORD, 1);
10914   assemble_zeros (2);
10915   return \"\";
10916   "
10917   [(set_attr "length" "4")]
10920 (define_insn "consttable_4"
10921   [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_4)]
10922   "TARGET_EITHER"
10923   "*
10924   {
10925     rtx x = operands[0];
10926     making_const_table = TRUE;
10927     switch (GET_MODE_CLASS (GET_MODE (x)))
10928       {
10929       case MODE_FLOAT:
10930         if (GET_MODE (x) == HFmode)
10931           arm_emit_fp16_const (x);
10932         else
10933           {
10934             REAL_VALUE_TYPE r;
10935             REAL_VALUE_FROM_CONST_DOUBLE (r, x);
10936             assemble_real (r, GET_MODE (x), BITS_PER_WORD);
10937           }
10938         break;
10939       default:
10940         /* XXX: Sometimes gcc does something really dumb and ends up with
10941            a HIGH in a constant pool entry, usually because it's trying to
10942            load into a VFP register.  We know this will always be used in
10943            combination with a LO_SUM which ignores the high bits, so just
10944            strip off the HIGH.  */
10945         if (GET_CODE (x) == HIGH)
10946           x = XEXP (x, 0);
10947         assemble_integer (x, 4, BITS_PER_WORD, 1);
10948         mark_symbol_refs_as_used (x);
10949         break;
10950       }
10951     return \"\";
10952   }"
10953   [(set_attr "length" "4")]
10956 (define_insn "consttable_8"
10957   [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_8)]
10958   "TARGET_EITHER"
10959   "*
10960   {
10961     making_const_table = TRUE;
10962     switch (GET_MODE_CLASS (GET_MODE (operands[0])))
10963       {
10964        case MODE_FLOAT:
10965         {
10966           REAL_VALUE_TYPE r;
10967           REAL_VALUE_FROM_CONST_DOUBLE (r, operands[0]);
10968           assemble_real (r, GET_MODE (operands[0]), BITS_PER_WORD);
10969           break;
10970         }
10971       default:
10972         assemble_integer (operands[0], 8, BITS_PER_WORD, 1);
10973         break;
10974       }
10975     return \"\";
10976   }"
10977   [(set_attr "length" "8")]
10980 (define_insn "consttable_16"
10981   [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_16)]
10982   "TARGET_EITHER"
10983   "*
10984   {
10985     making_const_table = TRUE;
10986     switch (GET_MODE_CLASS (GET_MODE (operands[0])))
10987       {
10988        case MODE_FLOAT:
10989         {
10990           REAL_VALUE_TYPE r;
10991           REAL_VALUE_FROM_CONST_DOUBLE (r, operands[0]);
10992           assemble_real (r, GET_MODE (operands[0]), BITS_PER_WORD);
10993           break;
10994         }
10995       default:
10996         assemble_integer (operands[0], 16, BITS_PER_WORD, 1);
10997         break;
10998       }
10999     return \"\";
11000   }"
11001   [(set_attr "length" "16")]
11004 ;; Miscellaneous Thumb patterns
11006 (define_expand "tablejump"
11007   [(parallel [(set (pc) (match_operand:SI 0 "register_operand" ""))
11008               (use (label_ref (match_operand 1 "" "")))])]
11009   "TARGET_THUMB1"
11010   "
11011   if (flag_pic)
11012     {
11013       /* Hopefully, CSE will eliminate this copy.  */
11014       rtx reg1 = copy_addr_to_reg (gen_rtx_LABEL_REF (Pmode, operands[1]));
11015       rtx reg2 = gen_reg_rtx (SImode);
11017       emit_insn (gen_addsi3 (reg2, operands[0], reg1));
11018       operands[0] = reg2;
11019     }
11020   "
11023 ;; NB never uses BX.
11024 (define_insn "*thumb1_tablejump"
11025   [(set (pc) (match_operand:SI 0 "register_operand" "l*r"))
11026    (use (label_ref (match_operand 1 "" "")))]
11027   "TARGET_THUMB1"
11028   "mov\\t%|pc, %0"
11029   [(set_attr "length" "2")]
11032 ;; V5 Instructions,
11034 (define_insn "clzsi2"
11035   [(set (match_operand:SI 0 "s_register_operand" "=r")
11036         (clz:SI (match_operand:SI 1 "s_register_operand" "r")))]
11037   "TARGET_32BIT && arm_arch5"
11038   "clz%?\\t%0, %1"
11039   [(set_attr "predicable" "yes")
11040    (set_attr "insn" "clz")])
11042 (define_insn "rbitsi2"
11043   [(set (match_operand:SI 0 "s_register_operand" "=r")
11044         (unspec:SI [(match_operand:SI 1 "s_register_operand" "r")] UNSPEC_RBIT))]
11045   "TARGET_32BIT && arm_arch_thumb2"
11046   "rbit%?\\t%0, %1"
11047   [(set_attr "predicable" "yes")
11048    (set_attr "insn" "clz")])
11050 (define_expand "ctzsi2"
11051  [(set (match_operand:SI           0 "s_register_operand" "")
11052        (ctz:SI (match_operand:SI  1 "s_register_operand" "")))]
11053   "TARGET_32BIT && arm_arch_thumb2"
11054   "
11055    {
11056      rtx tmp = gen_reg_rtx (SImode); 
11057      emit_insn (gen_rbitsi2 (tmp, operands[1]));
11058      emit_insn (gen_clzsi2 (operands[0], tmp));
11059    }
11060    DONE;
11061   "
11064 ;; V5E instructions.
11066 (define_insn "prefetch"
11067   [(prefetch (match_operand:SI 0 "address_operand" "p")
11068              (match_operand:SI 1 "" "")
11069              (match_operand:SI 2 "" ""))]
11070   "TARGET_32BIT && arm_arch5e"
11071   "pld\\t%a0")
11073 ;; General predication pattern
11075 (define_cond_exec
11076   [(match_operator 0 "arm_comparison_operator"
11077     [(match_operand 1 "cc_register" "")
11078      (const_int 0)])]
11079   "TARGET_32BIT"
11080   ""
11083 (define_insn "prologue_use"
11084   [(unspec:SI [(match_operand:SI 0 "register_operand" "")] UNSPEC_PROLOGUE_USE)]
11085   ""
11086   "%@ %0 needed for prologue"
11087   [(set_attr "length" "0")]
11091 ;; Patterns for exception handling
11093 (define_expand "eh_return"
11094   [(use (match_operand 0 "general_operand" ""))]
11095   "TARGET_EITHER"
11096   "
11097   {
11098     if (TARGET_32BIT)
11099       emit_insn (gen_arm_eh_return (operands[0]));
11100     else
11101       emit_insn (gen_thumb_eh_return (operands[0]));
11102     DONE;
11103   }"
11105                                    
11106 ;; We can't expand this before we know where the link register is stored.
11107 (define_insn_and_split "arm_eh_return"
11108   [(unspec_volatile [(match_operand:SI 0 "s_register_operand" "r")]
11109                     VUNSPEC_EH_RETURN)
11110    (clobber (match_scratch:SI 1 "=&r"))]
11111   "TARGET_ARM"
11112   "#"
11113   "&& reload_completed"
11114   [(const_int 0)]
11115   "
11116   {
11117     arm_set_return_address (operands[0], operands[1]);
11118     DONE;
11119   }"
11122 (define_insn_and_split "thumb_eh_return"
11123   [(unspec_volatile [(match_operand:SI 0 "s_register_operand" "l")]
11124                     VUNSPEC_EH_RETURN)
11125    (clobber (match_scratch:SI 1 "=&l"))]
11126   "TARGET_THUMB1"
11127   "#"
11128   "&& reload_completed"
11129   [(const_int 0)]
11130   "
11131   {
11132     thumb_set_return_address (operands[0], operands[1]);
11133     DONE;
11134   }"
11138 ;; TLS support
11140 (define_insn "load_tp_hard"
11141   [(set (match_operand:SI 0 "register_operand" "=r")
11142         (unspec:SI [(const_int 0)] UNSPEC_TLS))]
11143   "TARGET_HARD_TP"
11144   "mrc%?\\tp15, 0, %0, c13, c0, 3\\t@ load_tp_hard"
11145   [(set_attr "predicable" "yes")]
11148 ;; Doesn't clobber R1-R3.  Must use r0 for the first operand.
11149 (define_insn "load_tp_soft"
11150   [(set (reg:SI 0) (unspec:SI [(const_int 0)] UNSPEC_TLS))
11151    (clobber (reg:SI LR_REGNUM))
11152    (clobber (reg:SI IP_REGNUM))
11153    (clobber (reg:CC CC_REGNUM))]
11154   "TARGET_SOFT_TP"
11155   "bl\\t__aeabi_read_tp\\t@ load_tp_soft"
11156   [(set_attr "conds" "clob")]
11159 ;; tls descriptor call
11160 (define_insn "tlscall"
11161   [(set (reg:SI R0_REGNUM)
11162         (unspec:SI [(reg:SI R0_REGNUM)
11163                     (match_operand:SI 0 "" "X")
11164                     (match_operand 1 "" "")] UNSPEC_TLS))
11165    (clobber (reg:SI R1_REGNUM))
11166    (clobber (reg:SI LR_REGNUM))
11167    (clobber (reg:SI CC_REGNUM))]
11168   "TARGET_GNU2_TLS"
11169   {
11170     targetm.asm_out.internal_label (asm_out_file, "LPIC",
11171                                     INTVAL (operands[1]));
11172     return "bl\\t%c0(tlscall)";
11173   }
11174   [(set_attr "conds" "clob")
11175    (set_attr "length" "4")]
11180 ;; We only care about the lower 16 bits of the constant 
11181 ;; being inserted into the upper 16 bits of the register.
11182 (define_insn "*arm_movtas_ze" 
11183   [(set (zero_extract:SI (match_operand:SI 0 "s_register_operand" "+r")
11184                    (const_int 16)
11185                    (const_int 16))
11186         (match_operand:SI 1 "const_int_operand" ""))]
11187   "arm_arch_thumb2"
11188   "movt%?\t%0, %L1"
11189  [(set_attr "predicable" "yes")
11190    (set_attr "length" "4")]
11193 (define_insn "*arm_rev"
11194   [(set (match_operand:SI 0 "s_register_operand" "=r")
11195         (bswap:SI (match_operand:SI 1 "s_register_operand" "r")))]
11196   "TARGET_32BIT && arm_arch6"
11197   "rev%?\t%0, %1"
11198   [(set_attr "predicable" "yes")
11199    (set_attr "length" "4")]
11202 (define_insn "*thumb1_rev"
11203   [(set (match_operand:SI 0 "s_register_operand" "=l")
11204         (bswap:SI (match_operand:SI 1 "s_register_operand" "l")))]
11205   "TARGET_THUMB1 && arm_arch6"
11206    "rev\t%0, %1"
11207   [(set_attr "length" "2")]
11210 (define_expand "arm_legacy_rev"
11211   [(set (match_operand:SI 2 "s_register_operand" "")
11212         (xor:SI (rotatert:SI (match_operand:SI 1 "s_register_operand" "")
11213                              (const_int 16))
11214                 (match_dup 1)))
11215    (set (match_dup 2)
11216         (lshiftrt:SI (match_dup 2)
11217                      (const_int 8)))
11218    (set (match_operand:SI 3 "s_register_operand" "")
11219         (rotatert:SI (match_dup 1)
11220                      (const_int 8)))
11221    (set (match_dup 2)
11222         (and:SI (match_dup 2)
11223                 (const_int -65281)))
11224    (set (match_operand:SI 0 "s_register_operand" "")
11225         (xor:SI (match_dup 3)
11226                 (match_dup 2)))]
11227   "TARGET_32BIT"
11228   ""
11231 ;; Reuse temporaries to keep register pressure down.
11232 (define_expand "thumb_legacy_rev"
11233   [(set (match_operand:SI 2 "s_register_operand" "")
11234      (ashift:SI (match_operand:SI 1 "s_register_operand" "")
11235                 (const_int 24)))
11236    (set (match_operand:SI 3 "s_register_operand" "")
11237      (lshiftrt:SI (match_dup 1)
11238                   (const_int 24)))
11239    (set (match_dup 3)
11240      (ior:SI (match_dup 3)
11241              (match_dup 2)))
11242    (set (match_operand:SI 4 "s_register_operand" "")
11243      (const_int 16))
11244    (set (match_operand:SI 5 "s_register_operand" "")
11245      (rotatert:SI (match_dup 1)
11246                   (match_dup 4)))
11247    (set (match_dup 2)
11248      (ashift:SI (match_dup 5)
11249                 (const_int 24)))
11250    (set (match_dup 5)
11251      (lshiftrt:SI (match_dup 5)
11252                   (const_int 24)))
11253    (set (match_dup 5)
11254      (ior:SI (match_dup 5)
11255              (match_dup 2)))
11256    (set (match_dup 5)
11257      (rotatert:SI (match_dup 5)
11258                   (match_dup 4)))
11259    (set (match_operand:SI 0 "s_register_operand" "")
11260      (ior:SI (match_dup 5)
11261              (match_dup 3)))]
11262   "TARGET_THUMB"
11263   ""
11266 (define_expand "bswapsi2"
11267   [(set (match_operand:SI 0 "s_register_operand" "=r")
11268         (bswap:SI (match_operand:SI 1 "s_register_operand" "r")))]
11269 "TARGET_EITHER && (arm_arch6 || !optimize_size)"
11271     if (!arm_arch6)
11272       {
11273         rtx op2 = gen_reg_rtx (SImode);
11274         rtx op3 = gen_reg_rtx (SImode);
11276         if (TARGET_THUMB)
11277           {
11278             rtx op4 = gen_reg_rtx (SImode);
11279             rtx op5 = gen_reg_rtx (SImode);
11281             emit_insn (gen_thumb_legacy_rev (operands[0], operands[1],
11282                                              op2, op3, op4, op5));
11283           }
11284         else
11285           {
11286             emit_insn (gen_arm_legacy_rev (operands[0], operands[1],
11287                                            op2, op3));
11288           }
11290         DONE;
11291       }
11292   "
11295 ;; Load the load/store multiple patterns
11296 (include "ldmstm.md")
11297 ;; Vector bits common to IWMMXT and Neon
11298 (include "vec-common.md")
11299 ;; Load the Intel Wireless Multimedia Extension patterns
11300 (include "iwmmxt.md")
11301 ;; Load the VFP co-processor patterns
11302 (include "vfp.md")
11303 ;; Thumb-2 patterns
11304 (include "thumb2.md")
11305 ;; Neon patterns
11306 (include "neon.md")
11307 ;; Synchronization Primitives
11308 (include "sync.md")
11309 ;; Fixed-point patterns
11310 (include "arm-fixed.md")