arm.md revision 260455
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  Free Software Foundation, Inc.
4;;  Contributed by Pieter `Tiggr' Schoenmakers (rcpieter@win.tue.nl)
5;;  and Martin Simmons (@harleqn.co.uk).
6;;  More major hacks by Richard Earnshaw (rearnsha@arm.com).
7
8;; This file is part of GCC.
9
10;; GCC is free software; you can redistribute it and/or modify it
11;; under the terms of the GNU General Public License as published
12;; by the Free Software Foundation; either version 2, or (at your
13;; option) any later version.
14
15;; GCC is distributed in the hope that it will be useful, but WITHOUT
16;; ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
17;; or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public
18;; License for more details.
19
20;; You should have received a copy of the GNU General Public License
21;; along with GCC; see the file COPYING.  If not, write to
22;; the Free Software Foundation, 51 Franklin Street, Fifth Floor,
23;; Boston, MA 02110-1301, USA.
24
25;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
26
27
28;;---------------------------------------------------------------------------
29;; Constants
30
31;; Register numbers
32(define_constants
33  [(R0_REGNUM        0)		; First CORE register
34   (IP_REGNUM	    12)		; Scratch register
35   (SP_REGNUM	    13)		; Stack pointer
36   (LR_REGNUM       14)		; Return address register
37   (PC_REGNUM	    15)		; Program counter
38   (CC_REGNUM       24)		; Condition code pseudo register
39   (LAST_ARM_REGNUM 15)		;
40   (FPA_F0_REGNUM   16)		; FIRST_FPA_REGNUM
41   (FPA_F7_REGNUM   23)		; LAST_FPA_REGNUM
42  ]
43)
44;; 3rd operand to select_dominance_cc_mode
45(define_constants
46  [(DOM_CC_X_AND_Y  0)
47   (DOM_CC_NX_OR_Y  1)
48   (DOM_CC_X_OR_Y   2)
49  ]
50)
51
52;; UNSPEC Usage:
53;; Note: sin and cos are no-longer used.
54
55(define_constants
56  [(UNSPEC_SIN       0)	; `sin' operation (MODE_FLOAT):
57			;   operand 0 is the result,
58			;   operand 1 the parameter.
59   (UNPSEC_COS	     1)	; `cos' operation (MODE_FLOAT):
60			;   operand 0 is the result,
61			;   operand 1 the parameter.
62   (UNSPEC_PUSH_MULT 2)	; `push multiple' operation:
63			;   operand 0 is the first register,
64			;   subsequent registers are in parallel (use ...)
65			;   expressions.
66   (UNSPEC_PIC_SYM   3) ; A symbol that has been treated properly for pic
67			;   usage, that is, we will add the pic_register
68			;   value to it before trying to dereference it.
69   (UNSPEC_PIC_BASE  4)	; Adding the PC value to the offset to the
70			;   GLOBAL_OFFSET_TABLE.  The operation is fully
71			;   described by the RTL but must be wrapped to
72			;   prevent combine from trying to rip it apart.
73   (UNSPEC_PRLG_STK  5) ; A special barrier that prevents frame accesses 
74			;   being scheduled before the stack adjustment insn.
75   (UNSPEC_PROLOGUE_USE 6) ; As USE insns are not meaningful after reload,
76   			; this unspec is used to prevent the deletion of
77   			; instructions setting registers for EH handling
78   			; and stack frame generation.  Operand 0 is the
79   			; register to "use".
80   (UNSPEC_CHECK_ARCH 7); Set CCs to indicate 26-bit or 32-bit mode.
81   (UNSPEC_WSHUFH    8) ; Used by the intrinsic form of the iWMMXt WSHUFH instruction.
82   (UNSPEC_WACC      9) ; Used by the intrinsic form of the iWMMXt WACC instruction.
83   (UNSPEC_TMOVMSK  10) ; Used by the intrinsic form of the iWMMXt TMOVMSK instruction.
84   (UNSPEC_WSAD     11) ; Used by the intrinsic form of the iWMMXt WSAD instruction.
85   (UNSPEC_WSADZ    12) ; Used by the intrinsic form of the iWMMXt WSADZ instruction.
86   (UNSPEC_WMACS    13) ; Used by the intrinsic form of the iWMMXt WMACS instruction.
87   (UNSPEC_WMACU    14) ; Used by the intrinsic form of the iWMMXt WMACU instruction.
88   (UNSPEC_WMACSZ   15) ; Used by the intrinsic form of the iWMMXt WMACSZ instruction.
89   (UNSPEC_WMACUZ   16) ; Used by the intrinsic form of the iWMMXt WMACUZ instruction.
90   (UNSPEC_CLRDI    17) ; Used by the intrinsic form of the iWMMXt CLRDI instruction.
91   (UNSPEC_WMADDS   18) ; Used by the intrinsic form of the iWMMXt WMADDS instruction.
92   (UNSPEC_WMADDU   19) ; Used by the intrinsic form of the iWMMXt WMADDU instruction.
93   (UNSPEC_TLS      20) ; A symbol that has been treated properly for TLS usage.
94   (UNSPEC_PIC_LABEL 21) ; A label used for PIC access that does not appear in the
95                         ; instruction stream.
96  ]
97)
98
99;; UNSPEC_VOLATILE Usage:
100
101(define_constants
102  [(VUNSPEC_BLOCKAGE 0) ; `blockage' insn to prevent scheduling across an
103			;   insn in the code.
104   (VUNSPEC_EPILOGUE 1) ; `epilogue' insn, used to represent any part of the
105			;   instruction epilogue sequence that isn't expanded
106			;   into normal RTL.  Used for both normal and sibcall
107			;   epilogues.
108   (VUNSPEC_ALIGN    2) ; `align' insn.  Used at the head of a minipool table 
109			;   for inlined constants.
110   (VUNSPEC_POOL_END 3) ; `end-of-table'.  Used to mark the end of a minipool
111			;   table.
112   (VUNSPEC_POOL_1   4) ; `pool-entry(1)'.  An entry in the constant pool for
113			;   an 8-bit object.
114   (VUNSPEC_POOL_2   5) ; `pool-entry(2)'.  An entry in the constant pool for
115			;   a 16-bit object.
116   (VUNSPEC_POOL_4   6) ; `pool-entry(4)'.  An entry in the constant pool for
117			;   a 32-bit object.
118   (VUNSPEC_POOL_8   7) ; `pool-entry(8)'.  An entry in the constant pool for
119			;   a 64-bit object.
120   (VUNSPEC_TMRC     8) ; Used by the iWMMXt TMRC instruction.
121   (VUNSPEC_TMCR     9) ; Used by the iWMMXt TMCR instruction.
122   (VUNSPEC_ALIGN8   10) ; 8-byte alignment version of VUNSPEC_ALIGN
123   (VUNSPEC_WCMP_EQ  11) ; Used by the iWMMXt WCMPEQ instructions
124   (VUNSPEC_WCMP_GTU 12) ; Used by the iWMMXt WCMPGTU instructions
125   (VUNSPEC_WCMP_GT  13) ; Used by the iwMMXT WCMPGT instructions
126   (VUNSPEC_EH_RETURN 20); Use to override the return address for exception
127			 ; handling.
128  ]
129)
130
131;;---------------------------------------------------------------------------
132;; Attributes
133
134; IS_THUMB is set to 'yes' when we are generating Thumb code, and 'no' when
135; generating ARM code.  This is used to control the length of some insn
136; patterns that share the same RTL in both ARM and Thumb code.
137(define_attr "is_thumb" "no,yes" (const (symbol_ref "thumb_code")))
138
139; IS_STRONGARM is set to 'yes' when compiling for StrongARM, it affects
140; scheduling decisions for the load unit and the multiplier.
141(define_attr "is_strongarm" "no,yes" (const (symbol_ref "arm_tune_strongarm")))
142
143; IS_XSCALE is set to 'yes' when compiling for XScale.
144(define_attr "is_xscale" "no,yes" (const (symbol_ref "arm_tune_xscale")))
145
146;; Operand number of an input operand that is shifted.  Zero if the
147;; given instruction does not shift one of its input operands.
148(define_attr "shift" "" (const_int 0))
149
150; Floating Point Unit.  If we only have floating point emulation, then there
151; is no point in scheduling the floating point insns.  (Well, for best
152; performance we should try and group them together).
153(define_attr "fpu" "none,fpa,fpe2,fpe3,maverick,vfp"
154  (const (symbol_ref "arm_fpu_attr")))
155
156; LENGTH of an instruction (in bytes)
157(define_attr "length" "" (const_int 4))
158
159; POOL_RANGE is how far away from a constant pool entry that this insn
160; can be placed.  If the distance is zero, then this insn will never
161; reference the pool.
162; NEG_POOL_RANGE is nonzero for insns that can reference a constant pool entry
163; before its address.
164(define_attr "pool_range" "" (const_int 0))
165(define_attr "neg_pool_range" "" (const_int 0))
166
167; An assembler sequence may clobber the condition codes without us knowing.
168; If such an insn references the pool, then we have no way of knowing how,
169; so use the most conservative value for pool_range.
170(define_asm_attributes
171 [(set_attr "conds" "clob")
172  (set_attr "length" "4")
173  (set_attr "pool_range" "250")])
174
175;; The instruction used to implement a particular pattern.  This
176;; information is used by pipeline descriptions to provide accurate
177;; scheduling information.
178
179(define_attr "insn"
180        "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,other"
181        (const_string "other"))
182
183; TYPE attribute is used to detect floating point instructions which, if
184; running on a co-processor can run in parallel with other, basic instructions
185; If write-buffer scheduling is enabled then it can also be used in the
186; scheduling of writes.
187
188; Classification of each insn
189; alu		any alu  instruction that doesn't hit memory or fp
190;		regs or have a shifted source operand
191; alu_shift	any data instruction that doesn't hit memory or fp
192;		regs, but has a source operand shifted by a constant
193; alu_shift_reg	any data instruction that doesn't hit memory or fp
194;		regs, but has a source operand shifted by a register value
195; mult		a multiply instruction
196; block		blockage insn, this blocks all functional units
197; float		a floating point arithmetic operation (subject to expansion)
198; fdivd		DFmode floating point division
199; fdivs		SFmode floating point division
200; fmul		Floating point multiply
201; ffmul		Fast floating point multiply
202; farith	Floating point arithmetic (4 cycle)
203; ffarith	Fast floating point arithmetic (2 cycle)
204; float_em	a floating point arithmetic operation that is normally emulated
205;		even on a machine with an fpa.
206; f_load	a floating point load from memory
207; f_store	a floating point store to memory
208; f_load[sd]	single/double load from memory
209; f_store[sd]	single/double store to memory
210; f_flag	a transfer of co-processor flags to the CPSR
211; f_mem_r	a transfer of a floating point register to a real reg via mem
212; r_mem_f	the reverse of f_mem_r
213; f_2_r		fast transfer float to arm (no memory needed)
214; r_2_f		fast transfer arm to float
215; f_cvt		convert floating<->integral
216; branch	a branch
217; call		a subroutine call
218; load_byte	load byte(s) from memory to arm registers
219; load1		load 1 word from memory to arm registers
220; load2         load 2 words from memory to arm registers
221; load3         load 3 words from memory to arm registers
222; load4         load 4 words from memory to arm registers
223; store		store 1 word to memory from arm registers
224; store2	store 2 words
225; store3	store 3 words
226; store4	store 4 (or more) words
227;  Additions for Cirrus Maverick co-processor:
228; mav_farith	Floating point arithmetic (4 cycle)
229; mav_dmult	Double multiplies (7 cycle)
230;
231(define_attr "type"
232	"alu,alu_shift,alu_shift_reg,mult,block,float,fdivx,fdivd,fdivs,fmul,ffmul,farith,ffarith,f_flag,float_em,f_load,f_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,mav_farith,mav_dmult" 
233	(if_then_else 
234	 (eq_attr "insn" "smulxy,smlaxy,smlalxy,smulwy,smlawx,mul,muls,mla,mlas,umull,umulls,umlal,umlals,smull,smulls,smlal,smlals")
235	 (const_string "mult")
236	 (const_string "alu")))
237
238; Load scheduling, set from the arm_ld_sched variable
239; initialized by arm_override_options() 
240(define_attr "ldsched" "no,yes" (const (symbol_ref "arm_ld_sched")))
241
242; condition codes: this one is used by final_prescan_insn to speed up
243; conditionalizing instructions.  It saves having to scan the rtl to see if
244; it uses or alters the condition codes.
245; 
246; USE means that the condition codes are used by the insn in the process of
247;   outputting code, this means (at present) that we can't use the insn in
248;   inlined branches
249;
250; SET means that the purpose of the insn is to set the condition codes in a
251;   well defined manner.
252;
253; CLOB means that the condition codes are altered in an undefined manner, if
254;   they are altered at all
255;
256; JUMP_CLOB is used when the condition cannot be represented by a single
257;   instruction (UNEQ and LTGT).  These cannot be predicated.
258;
259; NOCOND means that the condition codes are neither altered nor affect the
260;   output of this insn
261
262(define_attr "conds" "use,set,clob,jump_clob,nocond"
263	(if_then_else (eq_attr "type" "call")
264	 (const_string "clob")
265	 (const_string "nocond")))
266
267; Predicable means that the insn can be conditionally executed based on
268; an automatically added predicate (additional patterns are generated by 
269; gen...).  We default to 'no' because no Thumb patterns match this rule
270; and not all ARM patterns do.
271(define_attr "predicable" "no,yes" (const_string "no"))
272
273; Only model the write buffer for ARM6 and ARM7.  Earlier processors don't
274; have one.  Later ones, such as StrongARM, have write-back caches, so don't
275; suffer blockages enough to warrant modelling this (and it can adversely
276; affect the schedule).
277(define_attr "model_wbuf" "no,yes" (const (symbol_ref "arm_tune_wbuf")))
278
279; WRITE_CONFLICT implies that a read following an unrelated write is likely
280; to stall the processor.  Used with model_wbuf above.
281(define_attr "write_conflict" "no,yes"
282  (if_then_else (eq_attr "type"
283		 "block,float_em,f_load,f_store,f_mem_r,r_mem_f,call,load1")
284		(const_string "yes")
285		(const_string "no")))
286
287; Classify the insns into those that take one cycle and those that take more
288; than one on the main cpu execution unit.
289(define_attr "core_cycles" "single,multi"
290  (if_then_else (eq_attr "type"
291		 "alu,alu_shift,float,fdivx,fdivd,fdivs,fmul,ffmul,farith,ffarith")
292		(const_string "single")
293	        (const_string "multi")))
294
295;; FAR_JUMP is "yes" if a BL instruction is used to generate a branch to a
296;; distant label.  Only applicable to Thumb code.
297(define_attr "far_jump" "yes,no" (const_string "no"))
298
299
300;;---------------------------------------------------------------------------
301;; Mode macros
302
303; A list of modes that are exactly 64 bits in size.  We use this to expand
304; some splits that are the same for all modes when operating on ARM 
305; registers.
306(define_mode_macro ANY64 [DI DF V8QI V4HI V2SI V2SF])
307
308;;---------------------------------------------------------------------------
309;; Predicates
310
311(include "predicates.md")
312(include "constraints.md")
313
314;;---------------------------------------------------------------------------
315;; Pipeline descriptions
316
317;; Processor type.  This is created automatically from arm-cores.def.
318(include "arm-tune.md")
319
320;; True if the generic scheduling description should be used.
321
322(define_attr "generic_sched" "yes,no"
323  (const (if_then_else 
324          (eq_attr "tune" "arm926ejs,arm1020e,arm1026ejs,arm1136js,arm1136jfs") 
325          (const_string "no")
326          (const_string "yes"))))
327
328(define_attr "generic_vfp" "yes,no"
329  (const (if_then_else
330	  (and (eq_attr "fpu" "vfp")
331	       (eq_attr "tune" "!arm1020e,arm1022e"))
332	  (const_string "yes")
333	  (const_string "no"))))
334
335(include "arm-generic.md")
336(include "arm926ejs.md")
337(include "arm1020e.md")
338(include "arm1026ejs.md")
339(include "arm1136jfs.md")
340
341
342;;---------------------------------------------------------------------------
343;; Insn patterns
344;;
345;; Addition insns.
346
347;; Note: For DImode insns, there is normally no reason why operands should
348;; not be in the same register, what we don't want is for something being
349;; written to partially overlap something that is an input.
350;; Cirrus 64bit additions should not be split because we have a native
351;; 64bit addition instructions.
352
353(define_expand "adddi3"
354 [(parallel
355   [(set (match_operand:DI           0 "s_register_operand" "")
356	  (plus:DI (match_operand:DI 1 "s_register_operand" "")
357	           (match_operand:DI 2 "s_register_operand" "")))
358    (clobber (reg:CC CC_REGNUM))])]
359  "TARGET_EITHER"
360  "
361  if (TARGET_HARD_FLOAT && TARGET_MAVERICK)
362    {
363      if (!cirrus_fp_register (operands[0], DImode))
364        operands[0] = force_reg (DImode, operands[0]);
365      if (!cirrus_fp_register (operands[1], DImode))
366        operands[1] = force_reg (DImode, operands[1]);
367      emit_insn (gen_cirrus_adddi3 (operands[0], operands[1], operands[2]));
368      DONE;
369    }
370
371  if (TARGET_THUMB)
372    {
373      if (GET_CODE (operands[1]) != REG)
374        operands[1] = force_reg (SImode, operands[1]);
375      if (GET_CODE (operands[2]) != REG)
376        operands[2] = force_reg (SImode, operands[2]);
377     }
378  "
379)
380
381(define_insn "*thumb_adddi3"
382  [(set (match_operand:DI          0 "register_operand" "=l")
383	(plus:DI (match_operand:DI 1 "register_operand" "%0")
384		 (match_operand:DI 2 "register_operand" "l")))
385   (clobber (reg:CC CC_REGNUM))
386  ]
387  "TARGET_THUMB"
388  "add\\t%Q0, %Q0, %Q2\;adc\\t%R0, %R0, %R2"
389  [(set_attr "length" "4")]
390)
391
392(define_insn_and_split "*arm_adddi3"
393  [(set (match_operand:DI          0 "s_register_operand" "=&r,&r")
394	(plus:DI (match_operand:DI 1 "s_register_operand" "%0, 0")
395		 (match_operand:DI 2 "s_register_operand" "r,  0")))
396   (clobber (reg:CC CC_REGNUM))]
397  "TARGET_ARM && !(TARGET_HARD_FLOAT && TARGET_MAVERICK)"
398  "#"
399  "TARGET_ARM && reload_completed"
400  [(parallel [(set (reg:CC_C CC_REGNUM)
401		   (compare:CC_C (plus:SI (match_dup 1) (match_dup 2))
402				 (match_dup 1)))
403	      (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])
404   (set (match_dup 3) (plus:SI (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))
405			       (plus:SI (match_dup 4) (match_dup 5))))]
406  "
407  {
408    operands[3] = gen_highpart (SImode, operands[0]);
409    operands[0] = gen_lowpart (SImode, operands[0]);
410    operands[4] = gen_highpart (SImode, operands[1]);
411    operands[1] = gen_lowpart (SImode, operands[1]);
412    operands[5] = gen_highpart (SImode, operands[2]);
413    operands[2] = gen_lowpart (SImode, operands[2]);
414  }"
415  [(set_attr "conds" "clob")
416   (set_attr "length" "8")]
417)
418
419(define_insn_and_split "*adddi_sesidi_di"
420  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
421	(plus:DI (sign_extend:DI
422		  (match_operand:SI 2 "s_register_operand" "r,r"))
423		 (match_operand:DI 1 "s_register_operand" "r,0")))
424   (clobber (reg:CC CC_REGNUM))]
425  "TARGET_ARM && !(TARGET_HARD_FLOAT && TARGET_MAVERICK)"
426  "#"
427  "TARGET_ARM && reload_completed"
428  [(parallel [(set (reg:CC_C CC_REGNUM)
429		   (compare:CC_C (plus:SI (match_dup 1) (match_dup 2))
430				 (match_dup 1)))
431	      (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])
432   (set (match_dup 3) (plus:SI (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))
433			       (plus:SI (ashiftrt:SI (match_dup 2)
434						     (const_int 31))
435					(match_dup 4))))]
436  "
437  {
438    operands[3] = gen_highpart (SImode, operands[0]);
439    operands[0] = gen_lowpart (SImode, operands[0]);
440    operands[4] = gen_highpart (SImode, operands[1]);
441    operands[1] = gen_lowpart (SImode, operands[1]);
442    operands[2] = gen_lowpart (SImode, operands[2]);
443  }"
444  [(set_attr "conds" "clob")
445   (set_attr "length" "8")]
446)
447
448(define_insn_and_split "*adddi_zesidi_di"
449  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
450	(plus:DI (zero_extend:DI
451		  (match_operand:SI 2 "s_register_operand" "r,r"))
452		 (match_operand:DI 1 "s_register_operand" "r,0")))
453   (clobber (reg:CC CC_REGNUM))]
454  "TARGET_ARM && !(TARGET_HARD_FLOAT && TARGET_MAVERICK)"
455  "#"
456  "TARGET_ARM && reload_completed"
457  [(parallel [(set (reg:CC_C CC_REGNUM)
458		   (compare:CC_C (plus:SI (match_dup 1) (match_dup 2))
459				 (match_dup 1)))
460	      (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 2)))])
461   (set (match_dup 3) (plus:SI (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))
462			       (plus:SI (match_dup 4) (const_int 0))))]
463  "
464  {
465    operands[3] = gen_highpart (SImode, operands[0]);
466    operands[0] = gen_lowpart (SImode, operands[0]);
467    operands[4] = gen_highpart (SImode, operands[1]);
468    operands[1] = gen_lowpart (SImode, operands[1]);
469    operands[2] = gen_lowpart (SImode, operands[2]);
470  }"
471  [(set_attr "conds" "clob")
472   (set_attr "length" "8")]
473)
474
475(define_expand "addsi3"
476  [(set (match_operand:SI          0 "s_register_operand" "")
477	(plus:SI (match_operand:SI 1 "s_register_operand" "")
478		 (match_operand:SI 2 "reg_or_int_operand" "")))]
479  "TARGET_EITHER"
480  "
481  if (TARGET_ARM && GET_CODE (operands[2]) == CONST_INT)
482    {
483      arm_split_constant (PLUS, SImode, NULL_RTX,
484	                  INTVAL (operands[2]), operands[0], operands[1],
485			  optimize && !no_new_pseudos);
486      DONE;
487    }
488  "
489)
490
491; If there is a scratch available, this will be faster than synthesizing the
492; addition.
493(define_peephole2
494  [(match_scratch:SI 3 "r")
495   (set (match_operand:SI          0 "arm_general_register_operand" "")
496	(plus:SI (match_operand:SI 1 "arm_general_register_operand" "")
497		 (match_operand:SI 2 "const_int_operand"  "")))]
498  "TARGET_ARM &&
499   !(const_ok_for_arm (INTVAL (operands[2]))
500     || const_ok_for_arm (-INTVAL (operands[2])))
501    && const_ok_for_arm (~INTVAL (operands[2]))"
502  [(set (match_dup 3) (match_dup 2))
503   (set (match_dup 0) (plus:SI (match_dup 1) (match_dup 3)))]
504  ""
505)
506
507(define_insn_and_split "*arm_addsi3"
508  [(set (match_operand:SI          0 "s_register_operand" "=r,r,r")
509	(plus:SI (match_operand:SI 1 "s_register_operand" "%r,r,r")
510		 (match_operand:SI 2 "reg_or_int_operand" "rI,L,?n")))]
511  "TARGET_ARM"
512  "@
513   add%?\\t%0, %1, %2
514   sub%?\\t%0, %1, #%n2
515   #"
516  "TARGET_ARM &&
517   GET_CODE (operands[2]) == CONST_INT
518   && !(const_ok_for_arm (INTVAL (operands[2]))
519        || const_ok_for_arm (-INTVAL (operands[2])))"
520  [(clobber (const_int 0))]
521  "
522  arm_split_constant (PLUS, SImode, curr_insn,
523	              INTVAL (operands[2]), operands[0],
524		      operands[1], 0);
525  DONE;
526  "
527  [(set_attr "length" "4,4,16")
528   (set_attr "predicable" "yes")]
529)
530
531;; Register group 'k' is a single register group containing only the stack
532;; register.  Trying to reload it will always fail catastrophically,
533;; so never allow those alternatives to match if reloading is needed.
534
535(define_insn "*thumb_addsi3"
536  [(set (match_operand:SI          0 "register_operand" "=l,l,l,*r,*h,l,!k")
537	(plus:SI (match_operand:SI 1 "register_operand" "%0,0,l,*0,*0,!k,!k")
538		 (match_operand:SI 2 "nonmemory_operand" "I,J,lL,*h,*r,!M,!O")))]
539  "TARGET_THUMB"
540  "*
541   static const char * const asms[] = 
542   {
543     \"add\\t%0, %0, %2\",
544     \"sub\\t%0, %0, #%n2\",
545     \"add\\t%0, %1, %2\",
546     \"add\\t%0, %0, %2\",
547     \"add\\t%0, %0, %2\",
548     \"add\\t%0, %1, %2\",
549     \"add\\t%0, %1, %2\"
550   };
551   if ((which_alternative == 2 || which_alternative == 6)
552       && GET_CODE (operands[2]) == CONST_INT
553       && INTVAL (operands[2]) < 0)
554     return \"sub\\t%0, %1, #%n2\";
555   return asms[which_alternative];
556  "
557  [(set_attr "length" "2")]
558)
559
560;; Reloading and elimination of the frame pointer can
561;; sometimes cause this optimization to be missed.
562(define_peephole2
563  [(set (match_operand:SI 0 "arm_general_register_operand" "")
564	(match_operand:SI 1 "const_int_operand" ""))
565   (set (match_dup 0)
566	(plus:SI (match_dup 0) (reg:SI SP_REGNUM)))]
567  "TARGET_THUMB
568   && (unsigned HOST_WIDE_INT) (INTVAL (operands[1])) < 1024
569   && (INTVAL (operands[1]) & 3) == 0"
570  [(set (match_dup 0) (plus:SI (reg:SI SP_REGNUM) (match_dup 1)))]
571  ""
572)
573
574(define_insn "*addsi3_compare0"
575  [(set (reg:CC_NOOV CC_REGNUM)
576	(compare:CC_NOOV
577	 (plus:SI (match_operand:SI 1 "s_register_operand" "r, r")
578		  (match_operand:SI 2 "arm_add_operand"    "rI,L"))
579	 (const_int 0)))
580   (set (match_operand:SI 0 "s_register_operand" "=r,r")
581	(plus:SI (match_dup 1) (match_dup 2)))]
582  "TARGET_ARM"
583  "@
584   add%?s\\t%0, %1, %2
585   sub%?s\\t%0, %1, #%n2"
586  [(set_attr "conds" "set")]
587)
588
589(define_insn "*addsi3_compare0_scratch"
590  [(set (reg:CC_NOOV CC_REGNUM)
591	(compare:CC_NOOV
592	 (plus:SI (match_operand:SI 0 "s_register_operand" "r, r")
593		  (match_operand:SI 1 "arm_add_operand"    "rI,L"))
594	 (const_int 0)))]
595  "TARGET_ARM"
596  "@
597   cmn%?\\t%0, %1
598   cmp%?\\t%0, #%n1"
599  [(set_attr "conds" "set")]
600)
601
602(define_insn "*compare_negsi_si"
603  [(set (reg:CC_Z CC_REGNUM)
604	(compare:CC_Z
605	 (neg:SI (match_operand:SI 0 "s_register_operand" "r"))
606	 (match_operand:SI 1 "s_register_operand" "r")))]
607  "TARGET_ARM"
608  "cmn%?\\t%1, %0"
609  [(set_attr "conds" "set")]
610)
611
612;; This is the canonicalization of addsi3_compare0_for_combiner when the
613;; addend is a constant.
614(define_insn "*cmpsi2_addneg"
615  [(set (reg:CC CC_REGNUM)
616	(compare:CC
617	 (match_operand:SI 1 "s_register_operand" "r,r")
618	 (match_operand:SI 2 "arm_addimm_operand" "I,L")))
619   (set (match_operand:SI 0 "s_register_operand" "=r,r")
620	(plus:SI (match_dup 1)
621		 (match_operand:SI 3 "arm_addimm_operand" "L,I")))]
622  "TARGET_ARM && INTVAL (operands[2]) == -INTVAL (operands[3])"
623  "@
624   sub%?s\\t%0, %1, %2
625   add%?s\\t%0, %1, #%n2"
626  [(set_attr "conds" "set")]
627)
628
629;; Convert the sequence
630;;  sub  rd, rn, #1
631;;  cmn  rd, #1	(equivalent to cmp rd, #-1)
632;;  bne  dest
633;; into
634;;  subs rd, rn, #1
635;;  bcs  dest	((unsigned)rn >= 1)
636;; similarly for the beq variant using bcc.
637;; This is a common looping idiom (while (n--))
638(define_peephole2
639  [(set (match_operand:SI 0 "arm_general_register_operand" "")
640	(plus:SI (match_operand:SI 1 "arm_general_register_operand" "")
641		 (const_int -1)))
642   (set (match_operand 2 "cc_register" "")
643	(compare (match_dup 0) (const_int -1)))
644   (set (pc)
645	(if_then_else (match_operator 3 "equality_operator"
646		       [(match_dup 2) (const_int 0)])
647		      (match_operand 4 "" "")
648		      (match_operand 5 "" "")))]
649  "TARGET_ARM && peep2_reg_dead_p (3, operands[2])"
650  [(parallel[
651    (set (match_dup 2)
652	 (compare:CC
653	  (match_dup 1) (const_int 1)))
654    (set (match_dup 0) (plus:SI (match_dup 1) (const_int -1)))])
655   (set (pc)
656	(if_then_else (match_op_dup 3 [(match_dup 2) (const_int 0)])
657		      (match_dup 4)
658		      (match_dup 5)))]
659  "operands[2] = gen_rtx_REG (CCmode, CC_REGNUM);
660   operands[3] = gen_rtx_fmt_ee ((GET_CODE (operands[3]) == NE
661				  ? GEU : LTU),
662				 VOIDmode, 
663				 operands[2], const0_rtx);"
664)
665
666;; The next four insns work because they compare the result with one of
667;; the operands, and we know that the use of the condition code is
668;; either GEU or LTU, so we can use the carry flag from the addition
669;; instead of doing the compare a second time.
670(define_insn "*addsi3_compare_op1"
671  [(set (reg:CC_C CC_REGNUM)
672	(compare:CC_C
673	 (plus:SI (match_operand:SI 1 "s_register_operand" "r,r")
674		  (match_operand:SI 2 "arm_add_operand" "rI,L"))
675	 (match_dup 1)))
676   (set (match_operand:SI 0 "s_register_operand" "=r,r")
677	(plus:SI (match_dup 1) (match_dup 2)))]
678  "TARGET_ARM"
679  "@
680   add%?s\\t%0, %1, %2
681   sub%?s\\t%0, %1, #%n2"
682  [(set_attr "conds" "set")]
683)
684
685(define_insn "*addsi3_compare_op2"
686  [(set (reg:CC_C CC_REGNUM)
687	(compare:CC_C
688	 (plus:SI (match_operand:SI 1 "s_register_operand" "r,r")
689		  (match_operand:SI 2 "arm_add_operand" "rI,L"))
690	 (match_dup 2)))
691   (set (match_operand:SI 0 "s_register_operand" "=r,r")
692	(plus:SI (match_dup 1) (match_dup 2)))]
693  "TARGET_ARM"
694  "@
695   add%?s\\t%0, %1, %2
696   sub%?s\\t%0, %1, #%n2"
697  [(set_attr "conds" "set")]
698)
699
700(define_insn "*compare_addsi2_op0"
701  [(set (reg:CC_C CC_REGNUM)
702	(compare:CC_C
703	 (plus:SI (match_operand:SI 0 "s_register_operand" "r,r")
704		  (match_operand:SI 1 "arm_add_operand" "rI,L"))
705	 (match_dup 0)))]
706  "TARGET_ARM"
707  "@
708   cmn%?\\t%0, %1
709   cmp%?\\t%0, #%n1"
710  [(set_attr "conds" "set")]
711)
712
713(define_insn "*compare_addsi2_op1"
714  [(set (reg:CC_C CC_REGNUM)
715	(compare:CC_C
716	 (plus:SI (match_operand:SI 0 "s_register_operand" "r,r")
717		  (match_operand:SI 1 "arm_add_operand" "rI,L"))
718	 (match_dup 1)))]
719  "TARGET_ARM"
720  "@
721   cmn%?\\t%0, %1
722   cmp%?\\t%0, #%n1"
723  [(set_attr "conds" "set")]
724)
725
726(define_insn "*addsi3_carryin"
727  [(set (match_operand:SI 0 "s_register_operand" "=r")
728	(plus:SI (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))
729		 (plus:SI (match_operand:SI 1 "s_register_operand" "r")
730			  (match_operand:SI 2 "arm_rhs_operand" "rI"))))]
731  "TARGET_ARM"
732  "adc%?\\t%0, %1, %2"
733  [(set_attr "conds" "use")]
734)
735
736(define_insn "*addsi3_carryin_shift"
737  [(set (match_operand:SI 0 "s_register_operand" "=r")
738	(plus:SI (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))
739		 (plus:SI
740		   (match_operator:SI 2 "shift_operator"
741		      [(match_operand:SI 3 "s_register_operand" "r")
742		       (match_operand:SI 4 "reg_or_int_operand" "rM")])
743		    (match_operand:SI 1 "s_register_operand" "r"))))]
744  "TARGET_ARM"
745  "adc%?\\t%0, %1, %3%S2"
746  [(set_attr "conds" "use")
747   (set (attr "type") (if_then_else (match_operand 4 "const_int_operand" "")
748		      (const_string "alu_shift")
749		      (const_string "alu_shift_reg")))]
750)
751
752(define_insn "*addsi3_carryin_alt1"
753  [(set (match_operand:SI 0 "s_register_operand" "=r")
754	(plus:SI (plus:SI (match_operand:SI 1 "s_register_operand" "r")
755			  (match_operand:SI 2 "arm_rhs_operand" "rI"))
756		 (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))))]
757  "TARGET_ARM"
758  "adc%?\\t%0, %1, %2"
759  [(set_attr "conds" "use")]
760)
761
762(define_insn "*addsi3_carryin_alt2"
763  [(set (match_operand:SI 0 "s_register_operand" "=r")
764	(plus:SI (plus:SI (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))
765			  (match_operand:SI 1 "s_register_operand" "r"))
766		 (match_operand:SI 2 "arm_rhs_operand" "rI")))]
767  "TARGET_ARM"
768  "adc%?\\t%0, %1, %2"
769  [(set_attr "conds" "use")]
770)
771
772(define_insn "*addsi3_carryin_alt3"
773  [(set (match_operand:SI 0 "s_register_operand" "=r")
774	(plus:SI (plus:SI (ltu:SI (reg:CC_C CC_REGNUM) (const_int 0))
775			  (match_operand:SI 2 "arm_rhs_operand" "rI"))
776		 (match_operand:SI 1 "s_register_operand" "r")))]
777  "TARGET_ARM"
778  "adc%?\\t%0, %1, %2"
779  [(set_attr "conds" "use")]
780)
781
782(define_insn "incscc"
783  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
784        (plus:SI (match_operator:SI 2 "arm_comparison_operator"
785                    [(match_operand:CC 3 "cc_register" "") (const_int 0)])
786                 (match_operand:SI 1 "s_register_operand" "0,?r")))]
787  "TARGET_ARM"
788  "@
789  add%d2\\t%0, %1, #1
790  mov%D2\\t%0, %1\;add%d2\\t%0, %1, #1"
791  [(set_attr "conds" "use")
792   (set_attr "length" "4,8")]
793)
794
795; transform ((x << y) - 1) to ~(~(x-1) << y)  Where X is a constant.
796(define_split
797  [(set (match_operand:SI 0 "s_register_operand" "")
798	(plus:SI (ashift:SI (match_operand:SI 1 "const_int_operand" "")
799			    (match_operand:SI 2 "s_register_operand" ""))
800		 (const_int -1)))
801   (clobber (match_operand:SI 3 "s_register_operand" ""))]
802  "TARGET_ARM"
803  [(set (match_dup 3) (match_dup 1))
804   (set (match_dup 0) (not:SI (ashift:SI (match_dup 3) (match_dup 2))))]
805  "
806  operands[1] = GEN_INT (~(INTVAL (operands[1]) - 1));
807")
808
809(define_expand "addsf3"
810  [(set (match_operand:SF          0 "s_register_operand" "")
811	(plus:SF (match_operand:SF 1 "s_register_operand" "")
812		 (match_operand:SF 2 "arm_float_add_operand" "")))]
813  "TARGET_ARM && TARGET_HARD_FLOAT"
814  "
815  if (TARGET_MAVERICK
816      && !cirrus_fp_register (operands[2], SFmode))
817    operands[2] = force_reg (SFmode, operands[2]);
818")
819
820(define_expand "adddf3"
821  [(set (match_operand:DF          0 "s_register_operand" "")
822	(plus:DF (match_operand:DF 1 "s_register_operand" "")
823		 (match_operand:DF 2 "arm_float_add_operand" "")))]
824  "TARGET_ARM && TARGET_HARD_FLOAT"
825  "
826  if (TARGET_MAVERICK
827      && !cirrus_fp_register (operands[2], DFmode))
828    operands[2] = force_reg (DFmode, operands[2]);
829")
830
831(define_expand "subdi3"
832 [(parallel
833   [(set (match_operand:DI            0 "s_register_operand" "")
834	  (minus:DI (match_operand:DI 1 "s_register_operand" "")
835	            (match_operand:DI 2 "s_register_operand" "")))
836    (clobber (reg:CC CC_REGNUM))])]
837  "TARGET_EITHER"
838  "
839  if (TARGET_HARD_FLOAT && TARGET_MAVERICK
840      && TARGET_ARM
841      && cirrus_fp_register (operands[0], DImode)
842      && cirrus_fp_register (operands[1], DImode))
843    {
844      emit_insn (gen_cirrus_subdi3 (operands[0], operands[1], operands[2]));
845      DONE;
846    }
847
848  if (TARGET_THUMB)
849    {
850      if (GET_CODE (operands[1]) != REG)
851        operands[1] = force_reg (SImode, operands[1]);
852      if (GET_CODE (operands[2]) != REG)
853        operands[2] = force_reg (SImode, operands[2]);
854     }	
855  "
856)
857
858(define_insn "*arm_subdi3"
859  [(set (match_operand:DI           0 "s_register_operand" "=&r,&r,&r")
860	(minus:DI (match_operand:DI 1 "s_register_operand" "0,r,0")
861		  (match_operand:DI 2 "s_register_operand" "r,0,0")))
862   (clobber (reg:CC CC_REGNUM))]
863  "TARGET_ARM"
864  "subs\\t%Q0, %Q1, %Q2\;sbc\\t%R0, %R1, %R2"
865  [(set_attr "conds" "clob")
866   (set_attr "length" "8")]
867)
868
869(define_insn "*thumb_subdi3"
870  [(set (match_operand:DI           0 "register_operand" "=l")
871	(minus:DI (match_operand:DI 1 "register_operand"  "0")
872		  (match_operand:DI 2 "register_operand"  "l")))
873   (clobber (reg:CC CC_REGNUM))]
874  "TARGET_THUMB"
875  "sub\\t%Q0, %Q0, %Q2\;sbc\\t%R0, %R0, %R2"
876  [(set_attr "length" "4")]
877)
878
879(define_insn "*subdi_di_zesidi"
880  [(set (match_operand:DI           0 "s_register_operand" "=&r,&r")
881	(minus:DI (match_operand:DI 1 "s_register_operand"  "?r,0")
882		  (zero_extend:DI
883		   (match_operand:SI 2 "s_register_operand"  "r,r"))))
884   (clobber (reg:CC CC_REGNUM))]
885  "TARGET_ARM"
886  "subs\\t%Q0, %Q1, %2\;sbc\\t%R0, %R1, #0"
887  [(set_attr "conds" "clob")
888   (set_attr "length" "8")]
889)
890
891(define_insn "*subdi_di_sesidi"
892  [(set (match_operand:DI            0 "s_register_operand" "=&r,&r")
893	(minus:DI (match_operand:DI  1 "s_register_operand"  "r,0")
894		  (sign_extend:DI
895		   (match_operand:SI 2 "s_register_operand"  "r,r"))))
896   (clobber (reg:CC CC_REGNUM))]
897  "TARGET_ARM"
898  "subs\\t%Q0, %Q1, %2\;sbc\\t%R0, %R1, %2, asr #31"
899  [(set_attr "conds" "clob")
900   (set_attr "length" "8")]
901)
902
903(define_insn "*subdi_zesidi_di"
904  [(set (match_operand:DI            0 "s_register_operand" "=&r,&r")
905	(minus:DI (zero_extend:DI
906		   (match_operand:SI 2 "s_register_operand"  "r,r"))
907		  (match_operand:DI  1 "s_register_operand" "?r,0")))
908   (clobber (reg:CC CC_REGNUM))]
909  "TARGET_ARM"
910  "rsbs\\t%Q0, %Q1, %2\;rsc\\t%R0, %R1, #0"
911  [(set_attr "conds" "clob")
912   (set_attr "length" "8")]
913)
914
915(define_insn "*subdi_sesidi_di"
916  [(set (match_operand:DI            0 "s_register_operand" "=&r,&r")
917	(minus:DI (sign_extend:DI
918		   (match_operand:SI 2 "s_register_operand"   "r,r"))
919		  (match_operand:DI  1 "s_register_operand"  "?r,0")))
920   (clobber (reg:CC CC_REGNUM))]
921  "TARGET_ARM"
922  "rsbs\\t%Q0, %Q1, %2\;rsc\\t%R0, %R1, %2, asr #31"
923  [(set_attr "conds" "clob")
924   (set_attr "length" "8")]
925)
926
927(define_insn "*subdi_zesidi_zesidi"
928  [(set (match_operand:DI            0 "s_register_operand" "=r")
929	(minus:DI (zero_extend:DI
930		   (match_operand:SI 1 "s_register_operand"  "r"))
931		  (zero_extend:DI
932		   (match_operand:SI 2 "s_register_operand"  "r"))))
933   (clobber (reg:CC CC_REGNUM))]
934  "TARGET_ARM"
935  "subs\\t%Q0, %1, %2\;rsc\\t%R0, %1, %1"
936  [(set_attr "conds" "clob")
937   (set_attr "length" "8")]
938)
939
940(define_expand "subsi3"
941  [(set (match_operand:SI           0 "s_register_operand" "")
942	(minus:SI (match_operand:SI 1 "reg_or_int_operand" "")
943		  (match_operand:SI 2 "s_register_operand" "")))]
944  "TARGET_EITHER"
945  "
946  if (GET_CODE (operands[1]) == CONST_INT)
947    {
948      if (TARGET_ARM)
949        {
950          arm_split_constant (MINUS, SImode, NULL_RTX,
951	                      INTVAL (operands[1]), operands[0],
952	  		      operands[2], optimize && !no_new_pseudos);
953          DONE;
954	}
955      else /* TARGET_THUMB */
956        operands[1] = force_reg (SImode, operands[1]);
957    }
958  "
959)
960
961(define_insn "*thumb_subsi3_insn"
962  [(set (match_operand:SI           0 "register_operand" "=l")
963	(minus:SI (match_operand:SI 1 "register_operand" "l")
964		  (match_operand:SI 2 "register_operand" "l")))]
965  "TARGET_THUMB"
966  "sub\\t%0, %1, %2"
967  [(set_attr "length" "2")]
968)
969
970(define_insn_and_split "*arm_subsi3_insn"
971  [(set (match_operand:SI           0 "s_register_operand" "=r,r")
972	(minus:SI (match_operand:SI 1 "reg_or_int_operand" "rI,?n")
973		  (match_operand:SI 2 "s_register_operand" "r,r")))]
974  "TARGET_ARM"
975  "@
976   rsb%?\\t%0, %2, %1
977   #"
978  "TARGET_ARM
979   && GET_CODE (operands[1]) == CONST_INT
980   && !const_ok_for_arm (INTVAL (operands[1]))"
981  [(clobber (const_int 0))]
982  "
983  arm_split_constant (MINUS, SImode, curr_insn,
984                      INTVAL (operands[1]), operands[0], operands[2], 0);
985  DONE;
986  "
987  [(set_attr "length" "4,16")
988   (set_attr "predicable" "yes")]
989)
990
991(define_peephole2
992  [(match_scratch:SI 3 "r")
993   (set (match_operand:SI 0 "arm_general_register_operand" "")
994	(minus:SI (match_operand:SI 1 "const_int_operand" "")
995		  (match_operand:SI 2 "arm_general_register_operand" "")))]
996  "TARGET_ARM
997   && !const_ok_for_arm (INTVAL (operands[1]))
998   && const_ok_for_arm (~INTVAL (operands[1]))"
999  [(set (match_dup 3) (match_dup 1))
1000   (set (match_dup 0) (minus:SI (match_dup 3) (match_dup 2)))]
1001  ""
1002)
1003
1004(define_insn "*subsi3_compare0"
1005  [(set (reg:CC_NOOV CC_REGNUM)
1006	(compare:CC_NOOV
1007	 (minus:SI (match_operand:SI 1 "arm_rhs_operand" "r,I")
1008		   (match_operand:SI 2 "arm_rhs_operand" "rI,r"))
1009	 (const_int 0)))
1010   (set (match_operand:SI 0 "s_register_operand" "=r,r")
1011	(minus:SI (match_dup 1) (match_dup 2)))]
1012  "TARGET_ARM"
1013  "@
1014   sub%?s\\t%0, %1, %2
1015   rsb%?s\\t%0, %2, %1"
1016  [(set_attr "conds" "set")]
1017)
1018
1019(define_insn "decscc"
1020  [(set (match_operand:SI            0 "s_register_operand" "=r,r")
1021        (minus:SI (match_operand:SI  1 "s_register_operand" "0,?r")
1022		  (match_operator:SI 2 "arm_comparison_operator"
1023                   [(match_operand   3 "cc_register" "") (const_int 0)])))]
1024  "TARGET_ARM"
1025  "@
1026   sub%d2\\t%0, %1, #1
1027   mov%D2\\t%0, %1\;sub%d2\\t%0, %1, #1"
1028  [(set_attr "conds" "use")
1029   (set_attr "length" "*,8")]
1030)
1031
1032(define_expand "subsf3"
1033  [(set (match_operand:SF           0 "s_register_operand" "")
1034	(minus:SF (match_operand:SF 1 "arm_float_rhs_operand" "")
1035		  (match_operand:SF 2 "arm_float_rhs_operand" "")))]
1036  "TARGET_ARM && TARGET_HARD_FLOAT"
1037  "
1038  if (TARGET_MAVERICK)
1039    {
1040      if (!cirrus_fp_register (operands[1], SFmode))
1041        operands[1] = force_reg (SFmode, operands[1]);
1042      if (!cirrus_fp_register (operands[2], SFmode))
1043        operands[2] = force_reg (SFmode, operands[2]);
1044    }
1045")
1046
1047(define_expand "subdf3"
1048  [(set (match_operand:DF           0 "s_register_operand" "")
1049	(minus:DF (match_operand:DF 1 "arm_float_rhs_operand" "")
1050		  (match_operand:DF 2 "arm_float_rhs_operand" "")))]
1051  "TARGET_ARM && TARGET_HARD_FLOAT"
1052  "
1053  if (TARGET_MAVERICK)
1054    {
1055       if (!cirrus_fp_register (operands[1], DFmode))
1056         operands[1] = force_reg (DFmode, operands[1]);
1057       if (!cirrus_fp_register (operands[2], DFmode))
1058         operands[2] = force_reg (DFmode, operands[2]);
1059    }
1060")
1061
1062
1063;; Multiplication insns
1064
1065(define_expand "mulsi3"
1066  [(set (match_operand:SI          0 "s_register_operand" "")
1067	(mult:SI (match_operand:SI 2 "s_register_operand" "")
1068		 (match_operand:SI 1 "s_register_operand" "")))]
1069  "TARGET_EITHER"
1070  ""
1071)
1072
1073;; Use `&' and then `0' to prevent the operands 0 and 1 being the same
1074(define_insn "*arm_mulsi3"
1075  [(set (match_operand:SI          0 "s_register_operand" "=&r,&r")
1076	(mult:SI (match_operand:SI 2 "s_register_operand" "r,r")
1077		 (match_operand:SI 1 "s_register_operand" "%?r,0")))]
1078  "TARGET_ARM"
1079  "mul%?\\t%0, %2, %1"
1080  [(set_attr "insn" "mul")
1081   (set_attr "predicable" "yes")]
1082)
1083
1084; Unfortunately with the Thumb the '&'/'0' trick can fails when operands 
1085; 1 and 2; are the same, because reload will make operand 0 match 
1086; operand 1 without realizing that this conflicts with operand 2.  We fix 
1087; this by adding another alternative to match this case, and then `reload' 
1088; it ourselves.  This alternative must come first.
1089(define_insn "*thumb_mulsi3"
1090  [(set (match_operand:SI          0 "register_operand" "=&l,&l,&l")
1091	(mult:SI (match_operand:SI 1 "register_operand" "%l,*h,0")
1092		 (match_operand:SI 2 "register_operand" "l,l,l")))]
1093  "TARGET_THUMB"
1094  "*
1095  if (which_alternative < 2)
1096    return \"mov\\t%0, %1\;mul\\t%0, %2\";
1097  else
1098    return \"mul\\t%0, %2\";
1099  "
1100  [(set_attr "length" "4,4,2")
1101   (set_attr "insn" "mul")]
1102)
1103
1104(define_insn "*mulsi3_compare0"
1105  [(set (reg:CC_NOOV CC_REGNUM)
1106	(compare:CC_NOOV (mult:SI
1107			  (match_operand:SI 2 "s_register_operand" "r,r")
1108			  (match_operand:SI 1 "s_register_operand" "%?r,0"))
1109			 (const_int 0)))
1110   (set (match_operand:SI 0 "s_register_operand" "=&r,&r")
1111	(mult:SI (match_dup 2) (match_dup 1)))]
1112  "TARGET_ARM"
1113  "mul%?s\\t%0, %2, %1"
1114  [(set_attr "conds" "set")
1115   (set_attr "insn" "muls")]
1116)
1117
1118(define_insn "*mulsi_compare0_scratch"
1119  [(set (reg:CC_NOOV CC_REGNUM)
1120	(compare:CC_NOOV (mult:SI
1121			  (match_operand:SI 2 "s_register_operand" "r,r")
1122			  (match_operand:SI 1 "s_register_operand" "%?r,0"))
1123			 (const_int 0)))
1124   (clobber (match_scratch:SI 0 "=&r,&r"))]
1125  "TARGET_ARM"
1126  "mul%?s\\t%0, %2, %1"
1127  [(set_attr "conds" "set")
1128   (set_attr "insn" "muls")]
1129)
1130
1131;; Unnamed templates to match MLA instruction.
1132
1133(define_insn "*mulsi3addsi"
1134  [(set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r,&r")
1135	(plus:SI
1136	  (mult:SI (match_operand:SI 2 "s_register_operand" "r,r,r,r")
1137		   (match_operand:SI 1 "s_register_operand" "%r,0,r,0"))
1138	  (match_operand:SI 3 "s_register_operand" "?r,r,0,0")))]
1139  "TARGET_ARM"
1140  "mla%?\\t%0, %2, %1, %3"
1141  [(set_attr "insn" "mla")
1142   (set_attr "predicable" "yes")]
1143)
1144
1145(define_insn "*mulsi3addsi_compare0"
1146  [(set (reg:CC_NOOV CC_REGNUM)
1147	(compare:CC_NOOV
1148	 (plus:SI (mult:SI
1149		   (match_operand:SI 2 "s_register_operand" "r,r,r,r")
1150		   (match_operand:SI 1 "s_register_operand" "%r,0,r,0"))
1151		  (match_operand:SI 3 "s_register_operand" "?r,r,0,0"))
1152	 (const_int 0)))
1153   (set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r,&r")
1154	(plus:SI (mult:SI (match_dup 2) (match_dup 1))
1155		 (match_dup 3)))]
1156  "TARGET_ARM"
1157  "mla%?s\\t%0, %2, %1, %3"
1158  [(set_attr "conds" "set")
1159   (set_attr "insn" "mlas")]
1160)
1161
1162(define_insn "*mulsi3addsi_compare0_scratch"
1163  [(set (reg:CC_NOOV CC_REGNUM)
1164	(compare:CC_NOOV
1165	 (plus:SI (mult:SI
1166		   (match_operand:SI 2 "s_register_operand" "r,r,r,r")
1167		   (match_operand:SI 1 "s_register_operand" "%r,0,r,0"))
1168		  (match_operand:SI 3 "s_register_operand" "?r,r,0,0"))
1169	 (const_int 0)))
1170   (clobber (match_scratch:SI 0 "=&r,&r,&r,&r"))]
1171  "TARGET_ARM"
1172  "mla%?s\\t%0, %2, %1, %3"
1173  [(set_attr "conds" "set")
1174   (set_attr "insn" "mlas")]
1175)
1176
1177;; Unnamed template to match long long multiply-accumulate (smlal)
1178
1179(define_insn "*mulsidi3adddi"
1180  [(set (match_operand:DI 0 "s_register_operand" "=&r")
1181	(plus:DI
1182	 (mult:DI
1183	  (sign_extend:DI (match_operand:SI 2 "s_register_operand" "%r"))
1184	  (sign_extend:DI (match_operand:SI 3 "s_register_operand" "r")))
1185	 (match_operand:DI 1 "s_register_operand" "0")))]
1186  "TARGET_ARM && arm_arch3m"
1187  "smlal%?\\t%Q0, %R0, %3, %2"
1188  [(set_attr "insn" "smlal")
1189   (set_attr "predicable" "yes")]
1190)
1191
1192(define_insn "mulsidi3"
1193  [(set (match_operand:DI 0 "s_register_operand" "=&r")
1194	(mult:DI
1195	 (sign_extend:DI (match_operand:SI 1 "s_register_operand" "%r"))
1196	 (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r"))))]
1197  "TARGET_ARM && arm_arch3m"
1198  "smull%?\\t%Q0, %R0, %1, %2"
1199  [(set_attr "insn" "smull")
1200   (set_attr "predicable" "yes")]
1201)
1202
1203(define_insn "umulsidi3"
1204  [(set (match_operand:DI 0 "s_register_operand" "=&r")
1205	(mult:DI
1206	 (zero_extend:DI (match_operand:SI 1 "s_register_operand" "%r"))
1207	 (zero_extend:DI (match_operand:SI 2 "s_register_operand" "r"))))]
1208  "TARGET_ARM && arm_arch3m"
1209  "umull%?\\t%Q0, %R0, %1, %2"
1210  [(set_attr "insn" "umull")
1211   (set_attr "predicable" "yes")]
1212)
1213
1214;; Unnamed template to match long long unsigned multiply-accumulate (umlal)
1215
1216(define_insn "*umulsidi3adddi"
1217  [(set (match_operand:DI 0 "s_register_operand" "=&r")
1218	(plus:DI
1219	 (mult:DI
1220	  (zero_extend:DI (match_operand:SI 2 "s_register_operand" "%r"))
1221	  (zero_extend:DI (match_operand:SI 3 "s_register_operand" "r")))
1222	 (match_operand:DI 1 "s_register_operand" "0")))]
1223  "TARGET_ARM && arm_arch3m"
1224  "umlal%?\\t%Q0, %R0, %3, %2"
1225  [(set_attr "insn" "umlal")
1226   (set_attr "predicable" "yes")]
1227)
1228
1229(define_insn "smulsi3_highpart"
1230  [(set (match_operand:SI 0 "s_register_operand" "=&r,&r")
1231	(truncate:SI
1232	 (lshiftrt:DI
1233	  (mult:DI
1234	   (sign_extend:DI (match_operand:SI 1 "s_register_operand" "%r,0"))
1235	   (sign_extend:DI (match_operand:SI 2 "s_register_operand" "r,r")))
1236	  (const_int 32))))
1237   (clobber (match_scratch:SI 3 "=&r,&r"))]
1238  "TARGET_ARM && arm_arch3m"
1239  "smull%?\\t%3, %0, %2, %1"
1240  [(set_attr "insn" "smull")
1241   (set_attr "predicable" "yes")]
1242)
1243
1244(define_insn "umulsi3_highpart"
1245  [(set (match_operand:SI 0 "s_register_operand" "=&r,&r")
1246	(truncate:SI
1247	 (lshiftrt:DI
1248	  (mult:DI
1249	   (zero_extend:DI (match_operand:SI 1 "s_register_operand" "%r,0"))
1250	   (zero_extend:DI (match_operand:SI 2 "s_register_operand" "r,r")))
1251	  (const_int 32))))
1252   (clobber (match_scratch:SI 3 "=&r,&r"))]
1253  "TARGET_ARM && arm_arch3m"
1254  "umull%?\\t%3, %0, %2, %1"
1255  [(set_attr "insn" "umull")
1256   (set_attr "predicable" "yes")]
1257)
1258
1259(define_insn "mulhisi3"
1260  [(set (match_operand:SI 0 "s_register_operand" "=r")
1261	(mult:SI (sign_extend:SI
1262		  (match_operand:HI 1 "s_register_operand" "%r"))
1263		 (sign_extend:SI
1264		  (match_operand:HI 2 "s_register_operand" "r"))))]
1265  "TARGET_ARM && arm_arch5e"
1266  "smulbb%?\\t%0, %1, %2"
1267  [(set_attr "insn" "smulxy")
1268   (set_attr "predicable" "yes")]
1269)
1270
1271(define_insn "*mulhisi3tb"
1272  [(set (match_operand:SI 0 "s_register_operand" "=r")
1273	(mult:SI (ashiftrt:SI
1274		  (match_operand:SI 1 "s_register_operand" "r")
1275		  (const_int 16))
1276		 (sign_extend:SI
1277		  (match_operand:HI 2 "s_register_operand" "r"))))]
1278  "TARGET_ARM && arm_arch5e"
1279  "smultb%?\\t%0, %1, %2"
1280  [(set_attr "insn" "smulxy")
1281   (set_attr "predicable" "yes")]
1282)
1283
1284(define_insn "*mulhisi3bt"
1285  [(set (match_operand:SI 0 "s_register_operand" "=r")
1286	(mult:SI (sign_extend:SI
1287		  (match_operand:HI 1 "s_register_operand" "r"))
1288		 (ashiftrt:SI
1289		  (match_operand:SI 2 "s_register_operand" "r")
1290		  (const_int 16))))]
1291  "TARGET_ARM && arm_arch5e"
1292  "smulbt%?\\t%0, %1, %2"
1293  [(set_attr "insn" "smulxy")
1294   (set_attr "predicable" "yes")]
1295)
1296
1297(define_insn "*mulhisi3tt"
1298  [(set (match_operand:SI 0 "s_register_operand" "=r")
1299	(mult:SI (ashiftrt:SI
1300		  (match_operand:SI 1 "s_register_operand" "r")
1301		  (const_int 16))
1302		 (ashiftrt:SI
1303		  (match_operand:SI 2 "s_register_operand" "r")
1304		  (const_int 16))))]
1305  "TARGET_ARM && arm_arch5e"
1306  "smultt%?\\t%0, %1, %2"
1307  [(set_attr "insn" "smulxy")
1308   (set_attr "predicable" "yes")]
1309)
1310
1311(define_insn "*mulhisi3addsi"
1312  [(set (match_operand:SI 0 "s_register_operand" "=r")
1313	(plus:SI (match_operand:SI 1 "s_register_operand" "r")
1314		 (mult:SI (sign_extend:SI
1315			   (match_operand:HI 2 "s_register_operand" "%r"))
1316			  (sign_extend:SI
1317			   (match_operand:HI 3 "s_register_operand" "r")))))]
1318  "TARGET_ARM && arm_arch5e"
1319  "smlabb%?\\t%0, %2, %3, %1"
1320  [(set_attr "insn" "smlaxy")
1321   (set_attr "predicable" "yes")]
1322)
1323
1324(define_insn "*mulhidi3adddi"
1325  [(set (match_operand:DI 0 "s_register_operand" "=r")
1326	(plus:DI
1327	  (match_operand:DI 1 "s_register_operand" "0")
1328	  (mult:DI (sign_extend:DI
1329	 	    (match_operand:HI 2 "s_register_operand" "%r"))
1330		   (sign_extend:DI
1331		    (match_operand:HI 3 "s_register_operand" "r")))))]
1332  "TARGET_ARM && arm_arch5e"
1333  "smlalbb%?\\t%Q0, %R0, %2, %3"
1334  [(set_attr "insn" "smlalxy")
1335   (set_attr "predicable" "yes")])
1336
1337(define_expand "mulsf3"
1338  [(set (match_operand:SF          0 "s_register_operand" "")
1339	(mult:SF (match_operand:SF 1 "s_register_operand" "")
1340		 (match_operand:SF 2 "arm_float_rhs_operand" "")))]
1341  "TARGET_ARM && TARGET_HARD_FLOAT"
1342  "
1343  if (TARGET_MAVERICK
1344      && !cirrus_fp_register (operands[2], SFmode))
1345    operands[2] = force_reg (SFmode, operands[2]);
1346")
1347
1348(define_expand "muldf3"
1349  [(set (match_operand:DF          0 "s_register_operand" "")
1350	(mult:DF (match_operand:DF 1 "s_register_operand" "")
1351		 (match_operand:DF 2 "arm_float_rhs_operand" "")))]
1352  "TARGET_ARM && TARGET_HARD_FLOAT"
1353  "
1354  if (TARGET_MAVERICK
1355      && !cirrus_fp_register (operands[2], DFmode))
1356    operands[2] = force_reg (DFmode, operands[2]);
1357")
1358
1359;; Division insns
1360
1361(define_expand "divsf3"
1362  [(set (match_operand:SF 0 "s_register_operand" "")
1363	(div:SF (match_operand:SF 1 "arm_float_rhs_operand" "")
1364		(match_operand:SF 2 "arm_float_rhs_operand" "")))]
1365  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
1366  "")
1367
1368(define_expand "divdf3"
1369  [(set (match_operand:DF 0 "s_register_operand" "")
1370	(div:DF (match_operand:DF 1 "arm_float_rhs_operand" "")
1371		(match_operand:DF 2 "arm_float_rhs_operand" "")))]
1372  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
1373  "")
1374
1375;; Modulo insns
1376
1377(define_expand "modsf3"
1378  [(set (match_operand:SF 0 "s_register_operand" "")
1379	(mod:SF (match_operand:SF 1 "s_register_operand" "")
1380		(match_operand:SF 2 "arm_float_rhs_operand" "")))]
1381  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_FPA"
1382  "")
1383
1384(define_expand "moddf3"
1385  [(set (match_operand:DF 0 "s_register_operand" "")
1386	(mod:DF (match_operand:DF 1 "s_register_operand" "")
1387		(match_operand:DF 2 "arm_float_rhs_operand" "")))]
1388  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_FPA"
1389  "")
1390
1391;; Boolean and,ior,xor insns
1392
1393;; Split up double word logical operations
1394
1395;; Split up simple DImode logical operations.  Simply perform the logical
1396;; operation on the upper and lower halves of the registers.
1397(define_split
1398  [(set (match_operand:DI 0 "s_register_operand" "")
1399	(match_operator:DI 6 "logical_binary_operator"
1400	  [(match_operand:DI 1 "s_register_operand" "")
1401	   (match_operand:DI 2 "s_register_operand" "")]))]
1402  "TARGET_ARM && reload_completed && ! IS_IWMMXT_REGNUM (REGNO (operands[0]))"
1403  [(set (match_dup 0) (match_op_dup:SI 6 [(match_dup 1) (match_dup 2)]))
1404   (set (match_dup 3) (match_op_dup:SI 6 [(match_dup 4) (match_dup 5)]))]
1405  "
1406  {
1407    operands[3] = gen_highpart (SImode, operands[0]);
1408    operands[0] = gen_lowpart (SImode, operands[0]);
1409    operands[4] = gen_highpart (SImode, operands[1]);
1410    operands[1] = gen_lowpart (SImode, operands[1]);
1411    operands[5] = gen_highpart (SImode, operands[2]);
1412    operands[2] = gen_lowpart (SImode, operands[2]);
1413  }"
1414)
1415
1416(define_split
1417  [(set (match_operand:DI 0 "s_register_operand" "")
1418	(match_operator:DI 6 "logical_binary_operator"
1419	  [(sign_extend:DI (match_operand:SI 2 "s_register_operand" ""))
1420	   (match_operand:DI 1 "s_register_operand" "")]))]
1421  "TARGET_ARM && reload_completed"
1422  [(set (match_dup 0) (match_op_dup:SI 6 [(match_dup 1) (match_dup 2)]))
1423   (set (match_dup 3) (match_op_dup:SI 6
1424			[(ashiftrt:SI (match_dup 2) (const_int 31))
1425			 (match_dup 4)]))]
1426  "
1427  {
1428    operands[3] = gen_highpart (SImode, operands[0]);
1429    operands[0] = gen_lowpart (SImode, operands[0]);
1430    operands[4] = gen_highpart (SImode, operands[1]);
1431    operands[1] = gen_lowpart (SImode, operands[1]);
1432    operands[5] = gen_highpart (SImode, operands[2]);
1433    operands[2] = gen_lowpart (SImode, operands[2]);
1434  }"
1435)
1436
1437;; The zero extend of operand 2 means we can just copy the high part of
1438;; operand1 into operand0.
1439(define_split
1440  [(set (match_operand:DI 0 "s_register_operand" "")
1441	(ior:DI
1442	  (zero_extend:DI (match_operand:SI 2 "s_register_operand" ""))
1443	  (match_operand:DI 1 "s_register_operand" "")))]
1444  "TARGET_ARM && operands[0] != operands[1] && reload_completed"
1445  [(set (match_dup 0) (ior:SI (match_dup 1) (match_dup 2)))
1446   (set (match_dup 3) (match_dup 4))]
1447  "
1448  {
1449    operands[4] = gen_highpart (SImode, operands[1]);
1450    operands[3] = gen_highpart (SImode, operands[0]);
1451    operands[0] = gen_lowpart (SImode, operands[0]);
1452    operands[1] = gen_lowpart (SImode, operands[1]);
1453  }"
1454)
1455
1456;; The zero extend of operand 2 means we can just copy the high part of
1457;; operand1 into operand0.
1458(define_split
1459  [(set (match_operand:DI 0 "s_register_operand" "")
1460	(xor:DI
1461	  (zero_extend:DI (match_operand:SI 2 "s_register_operand" ""))
1462	  (match_operand:DI 1 "s_register_operand" "")))]
1463  "TARGET_ARM && operands[0] != operands[1] && reload_completed"
1464  [(set (match_dup 0) (xor:SI (match_dup 1) (match_dup 2)))
1465   (set (match_dup 3) (match_dup 4))]
1466  "
1467  {
1468    operands[4] = gen_highpart (SImode, operands[1]);
1469    operands[3] = gen_highpart (SImode, operands[0]);
1470    operands[0] = gen_lowpart (SImode, operands[0]);
1471    operands[1] = gen_lowpart (SImode, operands[1]);
1472  }"
1473)
1474
1475(define_insn "anddi3"
1476  [(set (match_operand:DI         0 "s_register_operand" "=&r,&r")
1477	(and:DI (match_operand:DI 1 "s_register_operand"  "%0,r")
1478		(match_operand:DI 2 "s_register_operand"   "r,r")))]
1479  "TARGET_ARM && ! TARGET_IWMMXT"
1480  "#"
1481  [(set_attr "length" "8")]
1482)
1483
1484(define_insn_and_split "*anddi_zesidi_di"
1485  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
1486	(and:DI (zero_extend:DI
1487		 (match_operand:SI 2 "s_register_operand" "r,r"))
1488		(match_operand:DI 1 "s_register_operand" "?r,0")))]
1489  "TARGET_ARM"
1490  "#"
1491  "TARGET_ARM && reload_completed"
1492  ; The zero extend of operand 2 clears the high word of the output
1493  ; operand.
1494  [(set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))
1495   (set (match_dup 3) (const_int 0))]
1496  "
1497  {
1498    operands[3] = gen_highpart (SImode, operands[0]);
1499    operands[0] = gen_lowpart (SImode, operands[0]);
1500    operands[1] = gen_lowpart (SImode, operands[1]);
1501  }"
1502  [(set_attr "length" "8")]
1503)
1504
1505(define_insn "*anddi_sesdi_di"
1506  [(set (match_operand:DI          0 "s_register_operand" "=&r,&r")
1507	(and:DI (sign_extend:DI
1508		 (match_operand:SI 2 "s_register_operand" "r,r"))
1509		(match_operand:DI  1 "s_register_operand" "?r,0")))]
1510  "TARGET_ARM"
1511  "#"
1512  [(set_attr "length" "8")]
1513)
1514
1515(define_expand "andsi3"
1516  [(set (match_operand:SI         0 "s_register_operand" "")
1517	(and:SI (match_operand:SI 1 "s_register_operand" "")
1518		(match_operand:SI 2 "reg_or_int_operand" "")))]
1519  "TARGET_EITHER"
1520  "
1521  if (TARGET_ARM)
1522    {
1523      if (GET_CODE (operands[2]) == CONST_INT)
1524        {
1525          arm_split_constant (AND, SImode, NULL_RTX,
1526	                      INTVAL (operands[2]), operands[0],
1527			      operands[1], optimize && !no_new_pseudos);
1528
1529          DONE;
1530        }
1531    }
1532  else /* TARGET_THUMB */
1533    {
1534      if (GET_CODE (operands[2]) != CONST_INT)
1535        operands[2] = force_reg (SImode, operands[2]);
1536      else
1537        {
1538          int i;
1539	  
1540          if (((unsigned HOST_WIDE_INT) ~INTVAL (operands[2])) < 256)
1541  	    {
1542	      operands[2] = force_reg (SImode,
1543				       GEN_INT (~INTVAL (operands[2])));
1544	      
1545	      emit_insn (gen_bicsi3 (operands[0], operands[2], operands[1]));
1546	      
1547	      DONE;
1548	    }
1549
1550          for (i = 9; i <= 31; i++)
1551	    {
1552	      if ((((HOST_WIDE_INT) 1) << i) - 1 == INTVAL (operands[2]))
1553	        {
1554	          emit_insn (gen_extzv (operands[0], operands[1], GEN_INT (i),
1555			 	        const0_rtx));
1556	          DONE;
1557	        }
1558	      else if ((((HOST_WIDE_INT) 1) << i) - 1
1559		       == ~INTVAL (operands[2]))
1560	        {
1561	          rtx shift = GEN_INT (i);
1562	          rtx reg = gen_reg_rtx (SImode);
1563		
1564	          emit_insn (gen_lshrsi3 (reg, operands[1], shift));
1565	          emit_insn (gen_ashlsi3 (operands[0], reg, shift));
1566		  
1567	          DONE;
1568	        }
1569	    }
1570
1571          operands[2] = force_reg (SImode, operands[2]);
1572        }
1573    }
1574  "
1575)
1576
1577(define_insn_and_split "*arm_andsi3_insn"
1578  [(set (match_operand:SI         0 "s_register_operand" "=r,r,r")
1579	(and:SI (match_operand:SI 1 "s_register_operand" "r,r,r")
1580		(match_operand:SI 2 "reg_or_int_operand" "rI,K,?n")))]
1581  "TARGET_ARM"
1582  "@
1583   and%?\\t%0, %1, %2
1584   bic%?\\t%0, %1, #%B2
1585   #"
1586  "TARGET_ARM
1587   && GET_CODE (operands[2]) == CONST_INT
1588   && !(const_ok_for_arm (INTVAL (operands[2]))
1589	|| const_ok_for_arm (~INTVAL (operands[2])))"
1590  [(clobber (const_int 0))]
1591  "
1592  arm_split_constant  (AND, SImode, curr_insn, 
1593	               INTVAL (operands[2]), operands[0], operands[1], 0);
1594  DONE;
1595  "
1596  [(set_attr "length" "4,4,16")
1597   (set_attr "predicable" "yes")]
1598)
1599
1600(define_insn "*thumb_andsi3_insn"
1601  [(set (match_operand:SI         0 "register_operand" "=l")
1602	(and:SI (match_operand:SI 1 "register_operand" "%0")
1603		(match_operand:SI 2 "register_operand" "l")))]
1604  "TARGET_THUMB"
1605  "and\\t%0, %0, %2"
1606  [(set_attr "length" "2")]
1607)
1608
1609(define_insn "*andsi3_compare0"
1610  [(set (reg:CC_NOOV CC_REGNUM)
1611	(compare:CC_NOOV
1612	 (and:SI (match_operand:SI 1 "s_register_operand" "r,r")
1613		 (match_operand:SI 2 "arm_not_operand" "rI,K"))
1614	 (const_int 0)))
1615   (set (match_operand:SI          0 "s_register_operand" "=r,r")
1616	(and:SI (match_dup 1) (match_dup 2)))]
1617  "TARGET_ARM"
1618  "@
1619   and%?s\\t%0, %1, %2
1620   bic%?s\\t%0, %1, #%B2"
1621  [(set_attr "conds" "set")]
1622)
1623
1624(define_insn "*andsi3_compare0_scratch"
1625  [(set (reg:CC_NOOV CC_REGNUM)
1626	(compare:CC_NOOV
1627	 (and:SI (match_operand:SI 0 "s_register_operand" "r,r")
1628		 (match_operand:SI 1 "arm_not_operand" "rI,K"))
1629	 (const_int 0)))
1630   (clobber (match_scratch:SI 2 "=X,r"))]
1631  "TARGET_ARM"
1632  "@
1633   tst%?\\t%0, %1
1634   bic%?s\\t%2, %0, #%B1"
1635  [(set_attr "conds" "set")]
1636)
1637
1638(define_insn "*zeroextractsi_compare0_scratch"
1639  [(set (reg:CC_NOOV CC_REGNUM)
1640	(compare:CC_NOOV (zero_extract:SI
1641			  (match_operand:SI 0 "s_register_operand" "r")
1642		 	  (match_operand 1 "const_int_operand" "n")
1643			  (match_operand 2 "const_int_operand" "n"))
1644			 (const_int 0)))]
1645  "TARGET_ARM
1646  && (INTVAL (operands[2]) >= 0 && INTVAL (operands[2]) < 32
1647      && INTVAL (operands[1]) > 0 
1648      && INTVAL (operands[1]) + (INTVAL (operands[2]) & 1) <= 8
1649      && INTVAL (operands[1]) + INTVAL (operands[2]) <= 32)"
1650  "*
1651  operands[1] = GEN_INT (((1 << INTVAL (operands[1])) - 1)
1652			 << INTVAL (operands[2]));
1653  output_asm_insn (\"tst%?\\t%0, %1\", operands);
1654  return \"\";
1655  "
1656  [(set_attr "conds" "set")]
1657)
1658
1659(define_insn_and_split "*ne_zeroextractsi"
1660  [(set (match_operand:SI 0 "s_register_operand" "=r")
1661	(ne:SI (zero_extract:SI
1662		(match_operand:SI 1 "s_register_operand" "r")
1663		(match_operand:SI 2 "const_int_operand" "n")
1664		(match_operand:SI 3 "const_int_operand" "n"))
1665	       (const_int 0)))
1666   (clobber (reg:CC CC_REGNUM))]
1667  "TARGET_ARM
1668   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
1669       && INTVAL (operands[2]) > 0 
1670       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
1671       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)"
1672  "#"
1673  "TARGET_ARM
1674   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
1675       && INTVAL (operands[2]) > 0 
1676       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
1677       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)"
1678  [(parallel [(set (reg:CC_NOOV CC_REGNUM)
1679		   (compare:CC_NOOV (and:SI (match_dup 1) (match_dup 2))
1680				    (const_int 0)))
1681	      (set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))])
1682   (set (match_dup 0)
1683	(if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
1684			 (match_dup 0) (const_int 1)))]
1685  "
1686  operands[2] = GEN_INT (((1 << INTVAL (operands[2])) - 1)
1687			 << INTVAL (operands[3])); 
1688  "
1689  [(set_attr "conds" "clob")
1690   (set_attr "length" "8")]
1691)
1692
1693(define_insn_and_split "*ne_zeroextractsi_shifted"
1694  [(set (match_operand:SI 0 "s_register_operand" "=r")
1695	(ne:SI (zero_extract:SI
1696		(match_operand:SI 1 "s_register_operand" "r")
1697		(match_operand:SI 2 "const_int_operand" "n")
1698		(const_int 0))
1699	       (const_int 0)))
1700   (clobber (reg:CC CC_REGNUM))]
1701  "TARGET_ARM"
1702  "#"
1703  "TARGET_ARM"
1704  [(parallel [(set (reg:CC_NOOV CC_REGNUM)
1705		   (compare:CC_NOOV (ashift:SI (match_dup 1) (match_dup 2))
1706				    (const_int 0)))
1707	      (set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))])
1708   (set (match_dup 0)
1709	(if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
1710			 (match_dup 0) (const_int 1)))]
1711  "
1712  operands[2] = GEN_INT (32 - INTVAL (operands[2]));
1713  "
1714  [(set_attr "conds" "clob")
1715   (set_attr "length" "8")]
1716)
1717
1718(define_insn_and_split "*ite_ne_zeroextractsi"
1719  [(set (match_operand:SI 0 "s_register_operand" "=r")
1720	(if_then_else:SI (ne (zero_extract:SI
1721			      (match_operand:SI 1 "s_register_operand" "r")
1722			      (match_operand:SI 2 "const_int_operand" "n")
1723			      (match_operand:SI 3 "const_int_operand" "n"))
1724			     (const_int 0))
1725			 (match_operand:SI 4 "arm_not_operand" "rIK")
1726			 (const_int 0)))
1727   (clobber (reg:CC CC_REGNUM))]
1728  "TARGET_ARM
1729   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
1730       && INTVAL (operands[2]) > 0 
1731       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
1732       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)
1733   && !reg_overlap_mentioned_p (operands[0], operands[4])"
1734  "#"
1735  "TARGET_ARM
1736   && (INTVAL (operands[3]) >= 0 && INTVAL (operands[3]) < 32
1737       && INTVAL (operands[2]) > 0 
1738       && INTVAL (operands[2]) + (INTVAL (operands[3]) & 1) <= 8
1739       && INTVAL (operands[2]) + INTVAL (operands[3]) <= 32)
1740   && !reg_overlap_mentioned_p (operands[0], operands[4])"
1741  [(parallel [(set (reg:CC_NOOV CC_REGNUM)
1742		   (compare:CC_NOOV (and:SI (match_dup 1) (match_dup 2))
1743				    (const_int 0)))
1744	      (set (match_dup 0) (and:SI (match_dup 1) (match_dup 2)))])
1745   (set (match_dup 0)
1746	(if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
1747			 (match_dup 0) (match_dup 4)))]
1748  "
1749  operands[2] = GEN_INT (((1 << INTVAL (operands[2])) - 1)
1750			 << INTVAL (operands[3])); 
1751  "
1752  [(set_attr "conds" "clob")
1753   (set_attr "length" "8")]
1754)
1755
1756(define_insn_and_split "*ite_ne_zeroextractsi_shifted"
1757  [(set (match_operand:SI 0 "s_register_operand" "=r")
1758	(if_then_else:SI (ne (zero_extract:SI
1759			      (match_operand:SI 1 "s_register_operand" "r")
1760			      (match_operand:SI 2 "const_int_operand" "n")
1761			      (const_int 0))
1762			     (const_int 0))
1763			 (match_operand:SI 3 "arm_not_operand" "rIK")
1764			 (const_int 0)))
1765   (clobber (reg:CC CC_REGNUM))]
1766  "TARGET_ARM && !reg_overlap_mentioned_p (operands[0], operands[3])"
1767  "#"
1768  "TARGET_ARM && !reg_overlap_mentioned_p (operands[0], operands[3])"
1769  [(parallel [(set (reg:CC_NOOV CC_REGNUM)
1770		   (compare:CC_NOOV (ashift:SI (match_dup 1) (match_dup 2))
1771				    (const_int 0)))
1772	      (set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))])
1773   (set (match_dup 0)
1774	(if_then_else:SI (eq (reg:CC_NOOV CC_REGNUM) (const_int 0))
1775			 (match_dup 0) (match_dup 3)))]
1776  "
1777  operands[2] = GEN_INT (32 - INTVAL (operands[2]));
1778  "
1779  [(set_attr "conds" "clob")
1780   (set_attr "length" "8")]
1781)
1782
1783(define_split
1784  [(set (match_operand:SI 0 "s_register_operand" "")
1785	(zero_extract:SI (match_operand:SI 1 "s_register_operand" "")
1786			 (match_operand:SI 2 "const_int_operand" "")
1787			 (match_operand:SI 3 "const_int_operand" "")))
1788   (clobber (match_operand:SI 4 "s_register_operand" ""))]
1789  "TARGET_THUMB"
1790  [(set (match_dup 4) (ashift:SI (match_dup 1) (match_dup 2)))
1791   (set (match_dup 0) (lshiftrt:SI (match_dup 4) (match_dup 3)))]
1792  "{
1793     HOST_WIDE_INT temp = INTVAL (operands[2]);
1794
1795     operands[2] = GEN_INT (32 - temp - INTVAL (operands[3]));
1796     operands[3] = GEN_INT (32 - temp);
1797   }"
1798)
1799
1800(define_split
1801  [(set (match_operand:SI 0 "s_register_operand" "")
1802	(match_operator:SI 1 "shiftable_operator"
1803	 [(zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
1804			   (match_operand:SI 3 "const_int_operand" "")
1805			   (match_operand:SI 4 "const_int_operand" ""))
1806	  (match_operand:SI 5 "s_register_operand" "")]))
1807   (clobber (match_operand:SI 6 "s_register_operand" ""))]
1808  "TARGET_ARM"
1809  [(set (match_dup 6) (ashift:SI (match_dup 2) (match_dup 3)))
1810   (set (match_dup 0)
1811	(match_op_dup 1
1812	 [(lshiftrt:SI (match_dup 6) (match_dup 4))
1813	  (match_dup 5)]))]
1814  "{
1815     HOST_WIDE_INT temp = INTVAL (operands[3]);
1816
1817     operands[3] = GEN_INT (32 - temp - INTVAL (operands[4]));
1818     operands[4] = GEN_INT (32 - temp);
1819   }"
1820)
1821  
1822(define_split
1823  [(set (match_operand:SI 0 "s_register_operand" "")
1824	(sign_extract:SI (match_operand:SI 1 "s_register_operand" "")
1825			 (match_operand:SI 2 "const_int_operand" "")
1826			 (match_operand:SI 3 "const_int_operand" "")))]
1827  "TARGET_THUMB"
1828  [(set (match_dup 0) (ashift:SI (match_dup 1) (match_dup 2)))
1829   (set (match_dup 0) (ashiftrt:SI (match_dup 0) (match_dup 3)))]
1830  "{
1831     HOST_WIDE_INT temp = INTVAL (operands[2]);
1832
1833     operands[2] = GEN_INT (32 - temp - INTVAL (operands[3]));
1834     operands[3] = GEN_INT (32 - temp);
1835   }"
1836)
1837
1838(define_split
1839  [(set (match_operand:SI 0 "s_register_operand" "")
1840	(match_operator:SI 1 "shiftable_operator"
1841	 [(sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
1842			   (match_operand:SI 3 "const_int_operand" "")
1843			   (match_operand:SI 4 "const_int_operand" ""))
1844	  (match_operand:SI 5 "s_register_operand" "")]))
1845   (clobber (match_operand:SI 6 "s_register_operand" ""))]
1846  "TARGET_ARM"
1847  [(set (match_dup 6) (ashift:SI (match_dup 2) (match_dup 3)))
1848   (set (match_dup 0)
1849	(match_op_dup 1
1850	 [(ashiftrt:SI (match_dup 6) (match_dup 4))
1851	  (match_dup 5)]))]
1852  "{
1853     HOST_WIDE_INT temp = INTVAL (operands[3]);
1854
1855     operands[3] = GEN_INT (32 - temp - INTVAL (operands[4]));
1856     operands[4] = GEN_INT (32 - temp);
1857   }"
1858)
1859  
1860;;; ??? This pattern is bogus.  If operand3 has bits outside the range
1861;;; represented by the bitfield, then this will produce incorrect results.
1862;;; Somewhere, the value needs to be truncated.  On targets like the m68k,
1863;;; which have a real bit-field insert instruction, the truncation happens
1864;;; in the bit-field insert instruction itself.  Since arm does not have a
1865;;; bit-field insert instruction, we would have to emit code here to truncate
1866;;; the value before we insert.  This loses some of the advantage of having
1867;;; this insv pattern, so this pattern needs to be reevalutated.
1868
1869(define_expand "insv"
1870  [(set (zero_extract:SI (match_operand:SI 0 "s_register_operand" "")
1871                         (match_operand:SI 1 "general_operand" "")
1872                         (match_operand:SI 2 "general_operand" ""))
1873        (match_operand:SI 3 "reg_or_int_operand" ""))]
1874  "TARGET_ARM"
1875  "
1876  {
1877    int start_bit = INTVAL (operands[2]);
1878    int width = INTVAL (operands[1]);
1879    HOST_WIDE_INT mask = (((HOST_WIDE_INT)1) << width) - 1;
1880    rtx target, subtarget;
1881
1882    target = operands[0];
1883    /* Avoid using a subreg as a subtarget, and avoid writing a paradoxical 
1884       subreg as the final target.  */
1885    if (GET_CODE (target) == SUBREG)
1886      {
1887	subtarget = gen_reg_rtx (SImode);
1888	if (GET_MODE_SIZE (GET_MODE (SUBREG_REG (target)))
1889	    < GET_MODE_SIZE (SImode))
1890	  target = SUBREG_REG (target);
1891      }
1892    else
1893      subtarget = target;    
1894
1895    if (GET_CODE (operands[3]) == CONST_INT)
1896      {
1897	/* Since we are inserting a known constant, we may be able to
1898	   reduce the number of bits that we have to clear so that
1899	   the mask becomes simple.  */
1900	/* ??? This code does not check to see if the new mask is actually
1901	   simpler.  It may not be.  */
1902	rtx op1 = gen_reg_rtx (SImode);
1903	/* ??? Truncate operand3 to fit in the bitfield.  See comment before
1904	   start of this pattern.  */
1905	HOST_WIDE_INT op3_value = mask & INTVAL (operands[3]);
1906	HOST_WIDE_INT mask2 = ((mask & ~op3_value) << start_bit);
1907
1908	emit_insn (gen_andsi3 (op1, operands[0],
1909			       gen_int_mode (~mask2, SImode)));
1910	emit_insn (gen_iorsi3 (subtarget, op1,
1911			       gen_int_mode (op3_value << start_bit, SImode)));
1912      }
1913    else if (start_bit == 0
1914	     && !(const_ok_for_arm (mask)
1915		  || const_ok_for_arm (~mask)))
1916      {
1917	/* A Trick, since we are setting the bottom bits in the word,
1918	   we can shift operand[3] up, operand[0] down, OR them together
1919	   and rotate the result back again.  This takes 3 insns, and
1920	   the third might be mergeable into another op.  */
1921	/* The shift up copes with the possibility that operand[3] is
1922           wider than the bitfield.  */
1923	rtx op0 = gen_reg_rtx (SImode);
1924	rtx op1 = gen_reg_rtx (SImode);
1925
1926	emit_insn (gen_ashlsi3 (op0, operands[3], GEN_INT (32 - width)));
1927	emit_insn (gen_lshrsi3 (op1, operands[0], operands[1]));
1928	emit_insn (gen_iorsi3  (op1, op1, op0));
1929	emit_insn (gen_rotlsi3 (subtarget, op1, operands[1]));
1930      }
1931    else if ((width + start_bit == 32)
1932	     && !(const_ok_for_arm (mask)
1933		  || const_ok_for_arm (~mask)))
1934      {
1935	/* Similar trick, but slightly less efficient.  */
1936
1937	rtx op0 = gen_reg_rtx (SImode);
1938	rtx op1 = gen_reg_rtx (SImode);
1939
1940	emit_insn (gen_ashlsi3 (op0, operands[3], GEN_INT (32 - width)));
1941	emit_insn (gen_ashlsi3 (op1, operands[0], operands[1]));
1942	emit_insn (gen_lshrsi3 (op1, op1, operands[1]));
1943	emit_insn (gen_iorsi3 (subtarget, op1, op0));
1944      }
1945    else
1946      {
1947	rtx op0 = gen_int_mode (mask, SImode);
1948	rtx op1 = gen_reg_rtx (SImode);
1949	rtx op2 = gen_reg_rtx (SImode);
1950
1951	if (!(const_ok_for_arm (mask) || const_ok_for_arm (~mask)))
1952	  {
1953	    rtx tmp = gen_reg_rtx (SImode);
1954
1955	    emit_insn (gen_movsi (tmp, op0));
1956	    op0 = tmp;
1957	  }
1958
1959	/* Mask out any bits in operand[3] that are not needed.  */
1960	   emit_insn (gen_andsi3 (op1, operands[3], op0));
1961
1962	if (GET_CODE (op0) == CONST_INT
1963	    && (const_ok_for_arm (mask << start_bit)
1964		|| const_ok_for_arm (~(mask << start_bit))))
1965	  {
1966	    op0 = gen_int_mode (~(mask << start_bit), SImode);
1967	    emit_insn (gen_andsi3 (op2, operands[0], op0));
1968	  }
1969	else
1970	  {
1971	    if (GET_CODE (op0) == CONST_INT)
1972	      {
1973		rtx tmp = gen_reg_rtx (SImode);
1974
1975		emit_insn (gen_movsi (tmp, op0));
1976		op0 = tmp;
1977	      }
1978
1979	    if (start_bit != 0)
1980	      emit_insn (gen_ashlsi3 (op0, op0, operands[2]));
1981	    
1982	    emit_insn (gen_andsi_notsi_si (op2, operands[0], op0));
1983	  }
1984
1985	if (start_bit != 0)
1986          emit_insn (gen_ashlsi3 (op1, op1, operands[2]));
1987
1988	emit_insn (gen_iorsi3 (subtarget, op1, op2));
1989      }
1990
1991    if (subtarget != target)
1992      {
1993	/* If TARGET is still a SUBREG, then it must be wider than a word,
1994	   so we must be careful only to set the subword we were asked to.  */
1995	if (GET_CODE (target) == SUBREG)
1996	  emit_move_insn (target, subtarget);
1997	else
1998	  emit_move_insn (target, gen_lowpart (GET_MODE (target), subtarget));
1999      }
2000
2001    DONE;
2002  }"
2003)
2004
2005; constants for op 2 will never be given to these patterns.
2006(define_insn_and_split "*anddi_notdi_di"
2007  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2008	(and:DI (not:DI (match_operand:DI 1 "s_register_operand" "r,0"))
2009		(match_operand:DI 2 "s_register_operand" "0,r")))]
2010  "TARGET_ARM"
2011  "#"
2012  "TARGET_ARM && reload_completed && ! IS_IWMMXT_REGNUM (REGNO (operands[0]))"
2013  [(set (match_dup 0) (and:SI (not:SI (match_dup 1)) (match_dup 2)))
2014   (set (match_dup 3) (and:SI (not:SI (match_dup 4)) (match_dup 5)))]
2015  "
2016  {
2017    operands[3] = gen_highpart (SImode, operands[0]);
2018    operands[0] = gen_lowpart (SImode, operands[0]);
2019    operands[4] = gen_highpart (SImode, operands[1]);
2020    operands[1] = gen_lowpart (SImode, operands[1]);
2021    operands[5] = gen_highpart (SImode, operands[2]);
2022    operands[2] = gen_lowpart (SImode, operands[2]);
2023  }"
2024  [(set_attr "length" "8")
2025   (set_attr "predicable" "yes")]
2026)
2027  
2028(define_insn_and_split "*anddi_notzesidi_di"
2029  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2030	(and:DI (not:DI (zero_extend:DI
2031			 (match_operand:SI 2 "s_register_operand" "r,r")))
2032		(match_operand:DI 1 "s_register_operand" "0,?r")))]
2033  "TARGET_ARM"
2034  "@
2035   bic%?\\t%Q0, %Q1, %2
2036   #"
2037  ; (not (zero_extend ...)) allows us to just copy the high word from
2038  ; operand1 to operand0.
2039  "TARGET_ARM
2040   && reload_completed
2041   && operands[0] != operands[1]"
2042  [(set (match_dup 0) (and:SI (not:SI (match_dup 2)) (match_dup 1)))
2043   (set (match_dup 3) (match_dup 4))]
2044  "
2045  {
2046    operands[3] = gen_highpart (SImode, operands[0]);
2047    operands[0] = gen_lowpart (SImode, operands[0]);
2048    operands[4] = gen_highpart (SImode, operands[1]);
2049    operands[1] = gen_lowpart (SImode, operands[1]);
2050  }"
2051  [(set_attr "length" "4,8")
2052   (set_attr "predicable" "yes")]
2053)
2054  
2055(define_insn_and_split "*anddi_notsesidi_di"
2056  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2057	(and:DI (not:DI (sign_extend:DI
2058			 (match_operand:SI 2 "s_register_operand" "r,r")))
2059		(match_operand:DI 1 "s_register_operand" "0,r")))]
2060  "TARGET_ARM"
2061  "#"
2062  "TARGET_ARM && reload_completed"
2063  [(set (match_dup 0) (and:SI (not:SI (match_dup 2)) (match_dup 1)))
2064   (set (match_dup 3) (and:SI (not:SI
2065				(ashiftrt:SI (match_dup 2) (const_int 31)))
2066			       (match_dup 4)))]
2067  "
2068  {
2069    operands[3] = gen_highpart (SImode, operands[0]);
2070    operands[0] = gen_lowpart (SImode, operands[0]);
2071    operands[4] = gen_highpart (SImode, operands[1]);
2072    operands[1] = gen_lowpart (SImode, operands[1]);
2073  }"
2074  [(set_attr "length" "8")
2075   (set_attr "predicable" "yes")]
2076)
2077  
2078(define_insn "andsi_notsi_si"
2079  [(set (match_operand:SI 0 "s_register_operand" "=r")
2080	(and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2081		(match_operand:SI 1 "s_register_operand" "r")))]
2082  "TARGET_ARM"
2083  "bic%?\\t%0, %1, %2"
2084  [(set_attr "predicable" "yes")]
2085)
2086
2087(define_insn "bicsi3"
2088  [(set (match_operand:SI                 0 "register_operand" "=l")
2089	(and:SI (not:SI (match_operand:SI 1 "register_operand" "l"))
2090		(match_operand:SI         2 "register_operand" "0")))]
2091  "TARGET_THUMB"
2092  "bic\\t%0, %0, %1"
2093  [(set_attr "length" "2")]
2094)
2095
2096(define_insn "andsi_not_shiftsi_si"
2097  [(set (match_operand:SI 0 "s_register_operand" "=r")
2098	(and:SI (not:SI (match_operator:SI 4 "shift_operator"
2099			 [(match_operand:SI 2 "s_register_operand" "r")
2100			  (match_operand:SI 3 "arm_rhs_operand" "rM")]))
2101		(match_operand:SI 1 "s_register_operand" "r")))]
2102  "TARGET_ARM"
2103  "bic%?\\t%0, %1, %2%S4"
2104  [(set_attr "predicable" "yes")
2105   (set_attr "shift" "2")
2106   (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
2107		      (const_string "alu_shift")
2108		      (const_string "alu_shift_reg")))]
2109)
2110
2111(define_insn "*andsi_notsi_si_compare0"
2112  [(set (reg:CC_NOOV CC_REGNUM)
2113	(compare:CC_NOOV
2114	 (and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2115		 (match_operand:SI 1 "s_register_operand" "r"))
2116	 (const_int 0)))
2117   (set (match_operand:SI 0 "s_register_operand" "=r")
2118	(and:SI (not:SI (match_dup 2)) (match_dup 1)))]
2119  "TARGET_ARM"
2120  "bic%?s\\t%0, %1, %2"
2121  [(set_attr "conds" "set")]
2122)
2123
2124(define_insn "*andsi_notsi_si_compare0_scratch"
2125  [(set (reg:CC_NOOV CC_REGNUM)
2126	(compare:CC_NOOV
2127	 (and:SI (not:SI (match_operand:SI 2 "s_register_operand" "r"))
2128		 (match_operand:SI 1 "s_register_operand" "r"))
2129	 (const_int 0)))
2130   (clobber (match_scratch:SI 0 "=r"))]
2131  "TARGET_ARM"
2132  "bic%?s\\t%0, %1, %2"
2133  [(set_attr "conds" "set")]
2134)
2135
2136(define_insn "iordi3"
2137  [(set (match_operand:DI         0 "s_register_operand" "=&r,&r")
2138	(ior:DI (match_operand:DI 1 "s_register_operand"  "%0,r")
2139		(match_operand:DI 2 "s_register_operand"   "r,r")))]
2140  "TARGET_ARM && ! TARGET_IWMMXT"
2141  "#"
2142  [(set_attr "length" "8")
2143   (set_attr "predicable" "yes")]
2144)
2145
2146(define_insn "*iordi_zesidi_di"
2147  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2148	(ior:DI (zero_extend:DI
2149		 (match_operand:SI 2 "s_register_operand" "r,r"))
2150		(match_operand:DI 1 "s_register_operand" "0,?r")))]
2151  "TARGET_ARM"
2152  "@
2153   orr%?\\t%Q0, %Q1, %2
2154   #"
2155  [(set_attr "length" "4,8")
2156   (set_attr "predicable" "yes")]
2157)
2158
2159(define_insn "*iordi_sesidi_di"
2160  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2161	(ior:DI (sign_extend:DI
2162		 (match_operand:SI 2 "s_register_operand" "r,r"))
2163		(match_operand:DI 1 "s_register_operand" "?r,0")))]
2164  "TARGET_ARM"
2165  "#"
2166  [(set_attr "length" "8")
2167   (set_attr "predicable" "yes")]
2168)
2169
2170(define_expand "iorsi3"
2171  [(set (match_operand:SI         0 "s_register_operand" "")
2172	(ior:SI (match_operand:SI 1 "s_register_operand" "")
2173		(match_operand:SI 2 "reg_or_int_operand" "")))]
2174  "TARGET_EITHER"
2175  "
2176  if (GET_CODE (operands[2]) == CONST_INT)
2177    {
2178      if (TARGET_ARM)
2179        {
2180          arm_split_constant (IOR, SImode, NULL_RTX,
2181	                      INTVAL (operands[2]), operands[0], operands[1],
2182			      optimize && !no_new_pseudos);
2183          DONE;
2184	}
2185      else /* TARGET_THUMB */
2186	operands [2] = force_reg (SImode, operands [2]);
2187    }
2188  "
2189)
2190
2191(define_insn_and_split "*arm_iorsi3"
2192  [(set (match_operand:SI         0 "s_register_operand" "=r,r")
2193	(ior:SI (match_operand:SI 1 "s_register_operand" "r,r")
2194		(match_operand:SI 2 "reg_or_int_operand" "rI,?n")))]
2195  "TARGET_ARM"
2196  "@
2197   orr%?\\t%0, %1, %2
2198   #"
2199  "TARGET_ARM
2200   && GET_CODE (operands[2]) == CONST_INT
2201   && !const_ok_for_arm (INTVAL (operands[2]))"
2202  [(clobber (const_int 0))]
2203  "
2204  arm_split_constant (IOR, SImode, curr_insn, 
2205                      INTVAL (operands[2]), operands[0], operands[1], 0);
2206  DONE;
2207  "
2208  [(set_attr "length" "4,16")
2209   (set_attr "predicable" "yes")]
2210)
2211
2212(define_insn "*thumb_iorsi3"
2213  [(set (match_operand:SI         0 "register_operand" "=l")
2214	(ior:SI (match_operand:SI 1 "register_operand" "%0")
2215		(match_operand:SI 2 "register_operand" "l")))]
2216  "TARGET_THUMB"
2217  "orr\\t%0, %0, %2"
2218  [(set_attr "length" "2")]
2219)
2220
2221(define_peephole2
2222  [(match_scratch:SI 3 "r")
2223   (set (match_operand:SI 0 "arm_general_register_operand" "")
2224	(ior:SI (match_operand:SI 1 "arm_general_register_operand" "")
2225		(match_operand:SI 2 "const_int_operand" "")))]
2226  "TARGET_ARM
2227   && !const_ok_for_arm (INTVAL (operands[2]))
2228   && const_ok_for_arm (~INTVAL (operands[2]))"
2229  [(set (match_dup 3) (match_dup 2))
2230   (set (match_dup 0) (ior:SI (match_dup 1) (match_dup 3)))]
2231  ""
2232)
2233
2234(define_insn "*iorsi3_compare0"
2235  [(set (reg:CC_NOOV CC_REGNUM)
2236	(compare:CC_NOOV (ior:SI (match_operand:SI 1 "s_register_operand" "%r")
2237				 (match_operand:SI 2 "arm_rhs_operand" "rI"))
2238			 (const_int 0)))
2239   (set (match_operand:SI 0 "s_register_operand" "=r")
2240	(ior:SI (match_dup 1) (match_dup 2)))]
2241  "TARGET_ARM"
2242  "orr%?s\\t%0, %1, %2"
2243  [(set_attr "conds" "set")]
2244)
2245
2246(define_insn "*iorsi3_compare0_scratch"
2247  [(set (reg:CC_NOOV CC_REGNUM)
2248	(compare:CC_NOOV (ior:SI (match_operand:SI 1 "s_register_operand" "%r")
2249				 (match_operand:SI 2 "arm_rhs_operand" "rI"))
2250			 (const_int 0)))
2251   (clobber (match_scratch:SI 0 "=r"))]
2252  "TARGET_ARM"
2253  "orr%?s\\t%0, %1, %2"
2254  [(set_attr "conds" "set")]
2255)
2256
2257(define_insn "xordi3"
2258  [(set (match_operand:DI         0 "s_register_operand" "=&r,&r")
2259	(xor:DI (match_operand:DI 1 "s_register_operand"  "%0,r")
2260		(match_operand:DI 2 "s_register_operand"   "r,r")))]
2261  "TARGET_ARM && !TARGET_IWMMXT"
2262  "#"
2263  [(set_attr "length" "8")
2264   (set_attr "predicable" "yes")]
2265)
2266
2267(define_insn "*xordi_zesidi_di"
2268  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2269	(xor:DI (zero_extend:DI
2270		 (match_operand:SI 2 "s_register_operand" "r,r"))
2271		(match_operand:DI 1 "s_register_operand" "0,?r")))]
2272  "TARGET_ARM"
2273  "@
2274   eor%?\\t%Q0, %Q1, %2
2275   #"
2276  [(set_attr "length" "4,8")
2277   (set_attr "predicable" "yes")]
2278)
2279
2280(define_insn "*xordi_sesidi_di"
2281  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
2282	(xor:DI (sign_extend:DI
2283		 (match_operand:SI 2 "s_register_operand" "r,r"))
2284		(match_operand:DI 1 "s_register_operand" "?r,0")))]
2285  "TARGET_ARM"
2286  "#"
2287  [(set_attr "length" "8")
2288   (set_attr "predicable" "yes")]
2289)
2290
2291(define_expand "xorsi3"
2292  [(set (match_operand:SI         0 "s_register_operand" "")
2293	(xor:SI (match_operand:SI 1 "s_register_operand" "")
2294		(match_operand:SI 2 "arm_rhs_operand"  "")))]
2295  "TARGET_EITHER"
2296  "if (TARGET_THUMB)
2297     if (GET_CODE (operands[2]) == CONST_INT)
2298       operands[2] = force_reg (SImode, operands[2]);
2299  "
2300)
2301
2302(define_insn "*arm_xorsi3"
2303  [(set (match_operand:SI         0 "s_register_operand" "=r")
2304	(xor:SI (match_operand:SI 1 "s_register_operand" "r")
2305		(match_operand:SI 2 "arm_rhs_operand" "rI")))]
2306  "TARGET_ARM"
2307  "eor%?\\t%0, %1, %2"
2308  [(set_attr "predicable" "yes")]
2309)
2310
2311(define_insn "*thumb_xorsi3"
2312  [(set (match_operand:SI         0 "register_operand" "=l")
2313	(xor:SI (match_operand:SI 1 "register_operand" "%0")
2314		(match_operand:SI 2 "register_operand" "l")))]
2315  "TARGET_THUMB"
2316  "eor\\t%0, %0, %2"
2317  [(set_attr "length" "2")]
2318)
2319
2320(define_insn "*xorsi3_compare0"
2321  [(set (reg:CC_NOOV CC_REGNUM)
2322	(compare:CC_NOOV (xor:SI (match_operand:SI 1 "s_register_operand" "r")
2323				 (match_operand:SI 2 "arm_rhs_operand" "rI"))
2324			 (const_int 0)))
2325   (set (match_operand:SI 0 "s_register_operand" "=r")
2326	(xor:SI (match_dup 1) (match_dup 2)))]
2327  "TARGET_ARM"
2328  "eor%?s\\t%0, %1, %2"
2329  [(set_attr "conds" "set")]
2330)
2331
2332(define_insn "*xorsi3_compare0_scratch"
2333  [(set (reg:CC_NOOV CC_REGNUM)
2334	(compare:CC_NOOV (xor:SI (match_operand:SI 0 "s_register_operand" "r")
2335				 (match_operand:SI 1 "arm_rhs_operand" "rI"))
2336			 (const_int 0)))]
2337  "TARGET_ARM"
2338  "teq%?\\t%0, %1"
2339  [(set_attr "conds" "set")]
2340)
2341
2342; By splitting (IOR (AND (NOT A) (NOT B)) C) as D = AND (IOR A B) (NOT C), 
2343; (NOT D) we can sometimes merge the final NOT into one of the following
2344; insns.
2345
2346(define_split
2347  [(set (match_operand:SI 0 "s_register_operand" "")
2348	(ior:SI (and:SI (not:SI (match_operand:SI 1 "s_register_operand" ""))
2349			(not:SI (match_operand:SI 2 "arm_rhs_operand" "")))
2350		(match_operand:SI 3 "arm_rhs_operand" "")))
2351   (clobber (match_operand:SI 4 "s_register_operand" ""))]
2352  "TARGET_ARM"
2353  [(set (match_dup 4) (and:SI (ior:SI (match_dup 1) (match_dup 2))
2354			      (not:SI (match_dup 3))))
2355   (set (match_dup 0) (not:SI (match_dup 4)))]
2356  ""
2357)
2358
2359(define_insn "*andsi_iorsi3_notsi"
2360  [(set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r")
2361	(and:SI (ior:SI (match_operand:SI 1 "s_register_operand" "r,r,0")
2362			(match_operand:SI 2 "arm_rhs_operand" "rI,0,rI"))
2363		(not:SI (match_operand:SI 3 "arm_rhs_operand" "rI,rI,rI"))))]
2364  "TARGET_ARM"
2365  "orr%?\\t%0, %1, %2\;bic%?\\t%0, %0, %3"
2366  [(set_attr "length" "8")
2367   (set_attr "predicable" "yes")]
2368)
2369
2370(define_split
2371  [(set (match_operand:SI 0 "s_register_operand" "")
2372	(match_operator:SI 1 "logical_binary_operator"
2373	 [(zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
2374			   (match_operand:SI 3 "const_int_operand" "")
2375			   (match_operand:SI 4 "const_int_operand" ""))
2376	  (match_operator:SI 9 "logical_binary_operator"
2377	   [(lshiftrt:SI (match_operand:SI 5 "s_register_operand" "")
2378			 (match_operand:SI 6 "const_int_operand" ""))
2379	    (match_operand:SI 7 "s_register_operand" "")])]))
2380   (clobber (match_operand:SI 8 "s_register_operand" ""))]
2381  "TARGET_ARM
2382   && GET_CODE (operands[1]) == GET_CODE (operands[9])
2383   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
2384  [(set (match_dup 8)
2385	(match_op_dup 1
2386	 [(ashift:SI (match_dup 2) (match_dup 4))
2387	  (match_dup 5)]))
2388   (set (match_dup 0)
2389	(match_op_dup 1
2390	 [(lshiftrt:SI (match_dup 8) (match_dup 6))
2391	  (match_dup 7)]))]
2392  "
2393  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
2394")
2395
2396(define_split
2397  [(set (match_operand:SI 0 "s_register_operand" "")
2398	(match_operator:SI 1 "logical_binary_operator"
2399	 [(match_operator:SI 9 "logical_binary_operator"
2400	   [(lshiftrt:SI (match_operand:SI 5 "s_register_operand" "")
2401			 (match_operand:SI 6 "const_int_operand" ""))
2402	    (match_operand:SI 7 "s_register_operand" "")])
2403	  (zero_extract:SI (match_operand:SI 2 "s_register_operand" "")
2404			   (match_operand:SI 3 "const_int_operand" "")
2405			   (match_operand:SI 4 "const_int_operand" ""))]))
2406   (clobber (match_operand:SI 8 "s_register_operand" ""))]
2407  "TARGET_ARM
2408   && GET_CODE (operands[1]) == GET_CODE (operands[9])
2409   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
2410  [(set (match_dup 8)
2411	(match_op_dup 1
2412	 [(ashift:SI (match_dup 2) (match_dup 4))
2413	  (match_dup 5)]))
2414   (set (match_dup 0)
2415	(match_op_dup 1
2416	 [(lshiftrt:SI (match_dup 8) (match_dup 6))
2417	  (match_dup 7)]))]
2418  "
2419  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
2420")
2421
2422(define_split
2423  [(set (match_operand:SI 0 "s_register_operand" "")
2424	(match_operator:SI 1 "logical_binary_operator"
2425	 [(sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
2426			   (match_operand:SI 3 "const_int_operand" "")
2427			   (match_operand:SI 4 "const_int_operand" ""))
2428	  (match_operator:SI 9 "logical_binary_operator"
2429	   [(ashiftrt:SI (match_operand:SI 5 "s_register_operand" "")
2430			 (match_operand:SI 6 "const_int_operand" ""))
2431	    (match_operand:SI 7 "s_register_operand" "")])]))
2432   (clobber (match_operand:SI 8 "s_register_operand" ""))]
2433  "TARGET_ARM
2434   && GET_CODE (operands[1]) == GET_CODE (operands[9])
2435   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
2436  [(set (match_dup 8)
2437	(match_op_dup 1
2438	 [(ashift:SI (match_dup 2) (match_dup 4))
2439	  (match_dup 5)]))
2440   (set (match_dup 0)
2441	(match_op_dup 1
2442	 [(ashiftrt:SI (match_dup 8) (match_dup 6))
2443	  (match_dup 7)]))]
2444  "
2445  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
2446")
2447
2448(define_split
2449  [(set (match_operand:SI 0 "s_register_operand" "")
2450	(match_operator:SI 1 "logical_binary_operator"
2451	 [(match_operator:SI 9 "logical_binary_operator"
2452	   [(ashiftrt:SI (match_operand:SI 5 "s_register_operand" "")
2453			 (match_operand:SI 6 "const_int_operand" ""))
2454	    (match_operand:SI 7 "s_register_operand" "")])
2455	  (sign_extract:SI (match_operand:SI 2 "s_register_operand" "")
2456			   (match_operand:SI 3 "const_int_operand" "")
2457			   (match_operand:SI 4 "const_int_operand" ""))]))
2458   (clobber (match_operand:SI 8 "s_register_operand" ""))]
2459  "TARGET_ARM
2460   && GET_CODE (operands[1]) == GET_CODE (operands[9])
2461   && INTVAL (operands[3]) == 32 - INTVAL (operands[6])"
2462  [(set (match_dup 8)
2463	(match_op_dup 1
2464	 [(ashift:SI (match_dup 2) (match_dup 4))
2465	  (match_dup 5)]))
2466   (set (match_dup 0)
2467	(match_op_dup 1
2468	 [(ashiftrt:SI (match_dup 8) (match_dup 6))
2469	  (match_dup 7)]))]
2470  "
2471  operands[4] = GEN_INT (32 - (INTVAL (operands[3]) + INTVAL (operands[4])));
2472")
2473
2474
2475;; Minimum and maximum insns
2476
2477(define_expand "smaxsi3"
2478  [(parallel [
2479    (set (match_operand:SI 0 "s_register_operand" "")
2480	 (smax:SI (match_operand:SI 1 "s_register_operand" "")
2481		  (match_operand:SI 2 "arm_rhs_operand" "")))
2482    (clobber (reg:CC CC_REGNUM))])]
2483  "TARGET_ARM"
2484  "
2485  if (operands[2] == const0_rtx || operands[2] == constm1_rtx)
2486    {
2487      /* No need for a clobber of the condition code register here.  */
2488      emit_insn (gen_rtx_SET (VOIDmode, operands[0],
2489			      gen_rtx_SMAX (SImode, operands[1],
2490					    operands[2])));
2491      DONE;
2492    }
2493")
2494
2495(define_insn "*smax_0"
2496  [(set (match_operand:SI 0 "s_register_operand" "=r")
2497	(smax:SI (match_operand:SI 1 "s_register_operand" "r")
2498		 (const_int 0)))]
2499  "TARGET_ARM"
2500  "bic%?\\t%0, %1, %1, asr #31"
2501  [(set_attr "predicable" "yes")]
2502)
2503
2504(define_insn "*smax_m1"
2505  [(set (match_operand:SI 0 "s_register_operand" "=r")
2506	(smax:SI (match_operand:SI 1 "s_register_operand" "r")
2507		 (const_int -1)))]
2508  "TARGET_ARM"
2509  "orr%?\\t%0, %1, %1, asr #31"
2510  [(set_attr "predicable" "yes")]
2511)
2512
2513(define_insn "*smax_insn"
2514  [(set (match_operand:SI          0 "s_register_operand" "=r,r")
2515	(smax:SI (match_operand:SI 1 "s_register_operand"  "%0,?r")
2516		 (match_operand:SI 2 "arm_rhs_operand"    "rI,rI")))
2517   (clobber (reg:CC CC_REGNUM))]
2518  "TARGET_ARM"
2519  "@
2520   cmp\\t%1, %2\;movlt\\t%0, %2
2521   cmp\\t%1, %2\;movge\\t%0, %1\;movlt\\t%0, %2"
2522  [(set_attr "conds" "clob")
2523   (set_attr "length" "8,12")]
2524)
2525
2526(define_expand "sminsi3"
2527  [(parallel [
2528    (set (match_operand:SI 0 "s_register_operand" "")
2529	 (smin:SI (match_operand:SI 1 "s_register_operand" "")
2530		  (match_operand:SI 2 "arm_rhs_operand" "")))
2531    (clobber (reg:CC CC_REGNUM))])]
2532  "TARGET_ARM"
2533  "
2534  if (operands[2] == const0_rtx)
2535    {
2536      /* No need for a clobber of the condition code register here.  */
2537      emit_insn (gen_rtx_SET (VOIDmode, operands[0],
2538			      gen_rtx_SMIN (SImode, operands[1],
2539					    operands[2])));
2540      DONE;
2541    }
2542")
2543
2544(define_insn "*smin_0"
2545  [(set (match_operand:SI 0 "s_register_operand" "=r")
2546	(smin:SI (match_operand:SI 1 "s_register_operand" "r")
2547		 (const_int 0)))]
2548  "TARGET_ARM"
2549  "and%?\\t%0, %1, %1, asr #31"
2550  [(set_attr "predicable" "yes")]
2551)
2552
2553(define_insn "*smin_insn"
2554  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
2555	(smin:SI (match_operand:SI 1 "s_register_operand" "%0,?r")
2556		 (match_operand:SI 2 "arm_rhs_operand" "rI,rI")))
2557   (clobber (reg:CC CC_REGNUM))]
2558  "TARGET_ARM"
2559  "@
2560   cmp\\t%1, %2\;movge\\t%0, %2
2561   cmp\\t%1, %2\;movlt\\t%0, %1\;movge\\t%0, %2"
2562  [(set_attr "conds" "clob")
2563   (set_attr "length" "8,12")]
2564)
2565
2566(define_insn "umaxsi3"
2567  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
2568	(umax:SI (match_operand:SI 1 "s_register_operand" "0,r,?r")
2569		 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
2570   (clobber (reg:CC CC_REGNUM))]
2571  "TARGET_ARM"
2572  "@
2573   cmp\\t%1, %2\;movcc\\t%0, %2
2574   cmp\\t%1, %2\;movcs\\t%0, %1
2575   cmp\\t%1, %2\;movcs\\t%0, %1\;movcc\\t%0, %2"
2576  [(set_attr "conds" "clob")
2577   (set_attr "length" "8,8,12")]
2578)
2579
2580(define_insn "uminsi3"
2581  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
2582	(umin:SI (match_operand:SI 1 "s_register_operand" "0,r,?r")
2583		 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
2584   (clobber (reg:CC CC_REGNUM))]
2585  "TARGET_ARM"
2586  "@
2587   cmp\\t%1, %2\;movcs\\t%0, %2
2588   cmp\\t%1, %2\;movcc\\t%0, %1
2589   cmp\\t%1, %2\;movcc\\t%0, %1\;movcs\\t%0, %2"
2590  [(set_attr "conds" "clob")
2591   (set_attr "length" "8,8,12")]
2592)
2593
2594(define_insn "*store_minmaxsi"
2595  [(set (match_operand:SI 0 "memory_operand" "=m")
2596	(match_operator:SI 3 "minmax_operator"
2597	 [(match_operand:SI 1 "s_register_operand" "r")
2598	  (match_operand:SI 2 "s_register_operand" "r")]))
2599   (clobber (reg:CC CC_REGNUM))]
2600  "TARGET_ARM"
2601  "*
2602  operands[3] = gen_rtx_fmt_ee (minmax_code (operands[3]), SImode,
2603				operands[1], operands[2]);
2604  output_asm_insn (\"cmp\\t%1, %2\", operands);
2605  output_asm_insn (\"str%d3\\t%1, %0\", operands);
2606  output_asm_insn (\"str%D3\\t%2, %0\", operands);
2607  return \"\";
2608  "
2609  [(set_attr "conds" "clob")
2610   (set_attr "length" "12")
2611   (set_attr "type" "store1")]
2612)
2613
2614; Reject the frame pointer in operand[1], since reloading this after
2615; it has been eliminated can cause carnage.
2616(define_insn "*minmax_arithsi"
2617  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
2618	(match_operator:SI 4 "shiftable_operator"
2619	 [(match_operator:SI 5 "minmax_operator"
2620	   [(match_operand:SI 2 "s_register_operand" "r,r")
2621	    (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
2622	  (match_operand:SI 1 "s_register_operand" "0,?r")]))
2623   (clobber (reg:CC CC_REGNUM))]
2624  "TARGET_ARM && !arm_eliminable_register (operands[1])"
2625  "*
2626  {
2627    enum rtx_code code = GET_CODE (operands[4]);
2628
2629    operands[5] = gen_rtx_fmt_ee (minmax_code (operands[5]), SImode,
2630				  operands[2], operands[3]);
2631    output_asm_insn (\"cmp\\t%2, %3\", operands);
2632    output_asm_insn (\"%i4%d5\\t%0, %1, %2\", operands);
2633    if (which_alternative != 0 || operands[3] != const0_rtx
2634        || (code != PLUS && code != MINUS && code != IOR && code != XOR))
2635      output_asm_insn (\"%i4%D5\\t%0, %1, %3\", operands);
2636    return \"\";
2637  }"
2638  [(set_attr "conds" "clob")
2639   (set_attr "length" "12")]
2640)
2641
2642
2643;; Shift and rotation insns
2644
2645(define_expand "ashldi3"
2646  [(set (match_operand:DI            0 "s_register_operand" "")
2647        (ashift:DI (match_operand:DI 1 "s_register_operand" "")
2648                   (match_operand:SI 2 "reg_or_int_operand" "")))]
2649  "TARGET_ARM"
2650  "
2651  if (GET_CODE (operands[2]) == CONST_INT)
2652    {
2653      if ((HOST_WIDE_INT) INTVAL (operands[2]) == 1)
2654        {
2655          emit_insn (gen_arm_ashldi3_1bit (operands[0], operands[1]));
2656          DONE;
2657        }
2658        /* Ideally we shouldn't fail here if we could know that operands[1] 
2659           ends up already living in an iwmmxt register. Otherwise it's
2660           cheaper to have the alternate code being generated than moving
2661           values to iwmmxt regs and back.  */
2662        FAIL;
2663    }
2664  else if (!TARGET_REALLY_IWMMXT && !(TARGET_HARD_FLOAT && TARGET_MAVERICK))
2665    FAIL;
2666  "
2667)
2668
2669(define_insn "arm_ashldi3_1bit"
2670  [(set (match_operand:DI            0 "s_register_operand" "=&r,r")
2671        (ashift:DI (match_operand:DI 1 "s_register_operand" "?r,0")
2672                   (const_int 1)))
2673   (clobber (reg:CC CC_REGNUM))]
2674  "TARGET_ARM"
2675  "movs\\t%Q0, %Q1, asl #1\;adc\\t%R0, %R1, %R1"
2676  [(set_attr "conds" "clob")
2677   (set_attr "length" "8")]
2678)
2679
2680(define_expand "ashlsi3"
2681  [(set (match_operand:SI            0 "s_register_operand" "")
2682	(ashift:SI (match_operand:SI 1 "s_register_operand" "")
2683		   (match_operand:SI 2 "arm_rhs_operand" "")))]
2684  "TARGET_EITHER"
2685  "
2686  if (GET_CODE (operands[2]) == CONST_INT
2687      && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
2688    {
2689      emit_insn (gen_movsi (operands[0], const0_rtx));
2690      DONE;
2691    }
2692  "
2693)
2694
2695(define_insn "*thumb_ashlsi3"
2696  [(set (match_operand:SI            0 "register_operand" "=l,l")
2697	(ashift:SI (match_operand:SI 1 "register_operand" "l,0")
2698		   (match_operand:SI 2 "nonmemory_operand" "N,l")))]
2699  "TARGET_THUMB"
2700  "lsl\\t%0, %1, %2"
2701  [(set_attr "length" "2")]
2702)
2703
2704(define_expand "ashrdi3"
2705  [(set (match_operand:DI              0 "s_register_operand" "")
2706        (ashiftrt:DI (match_operand:DI 1 "s_register_operand" "")
2707                     (match_operand:SI 2 "reg_or_int_operand" "")))]
2708  "TARGET_ARM"
2709  "
2710  if (GET_CODE (operands[2]) == CONST_INT)
2711    {
2712      if ((HOST_WIDE_INT) INTVAL (operands[2]) == 1)
2713        {
2714          emit_insn (gen_arm_ashrdi3_1bit (operands[0], operands[1]));
2715          DONE;
2716        }
2717        /* Ideally we shouldn't fail here if we could know that operands[1] 
2718           ends up already living in an iwmmxt register. Otherwise it's
2719           cheaper to have the alternate code being generated than moving
2720           values to iwmmxt regs and back.  */
2721        FAIL;
2722    }
2723  else if (!TARGET_REALLY_IWMMXT)
2724    FAIL;
2725  "
2726)
2727
2728(define_insn "arm_ashrdi3_1bit"
2729  [(set (match_operand:DI              0 "s_register_operand" "=&r,r")
2730        (ashiftrt:DI (match_operand:DI 1 "s_register_operand" "?r,0")
2731                     (const_int 1)))
2732   (clobber (reg:CC CC_REGNUM))]
2733  "TARGET_ARM"
2734  "movs\\t%R0, %R1, asr #1\;mov\\t%Q0, %Q1, rrx"
2735  [(set_attr "conds" "clob")
2736   (set_attr "length" "8")]
2737)
2738
2739(define_expand "ashrsi3"
2740  [(set (match_operand:SI              0 "s_register_operand" "")
2741	(ashiftrt:SI (match_operand:SI 1 "s_register_operand" "")
2742		     (match_operand:SI 2 "arm_rhs_operand" "")))]
2743  "TARGET_EITHER"
2744  "
2745  if (GET_CODE (operands[2]) == CONST_INT
2746      && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
2747    operands[2] = GEN_INT (31);
2748  "
2749)
2750
2751(define_insn "*thumb_ashrsi3"
2752  [(set (match_operand:SI              0 "register_operand" "=l,l")
2753	(ashiftrt:SI (match_operand:SI 1 "register_operand" "l,0")
2754		     (match_operand:SI 2 "nonmemory_operand" "N,l")))]
2755  "TARGET_THUMB"
2756  "asr\\t%0, %1, %2"
2757  [(set_attr "length" "2")]
2758)
2759
2760(define_expand "lshrdi3"
2761  [(set (match_operand:DI              0 "s_register_operand" "")
2762        (lshiftrt:DI (match_operand:DI 1 "s_register_operand" "")
2763                     (match_operand:SI 2 "reg_or_int_operand" "")))]
2764  "TARGET_ARM"
2765  "
2766  if (GET_CODE (operands[2]) == CONST_INT)
2767    {
2768      if ((HOST_WIDE_INT) INTVAL (operands[2]) == 1)
2769        {
2770          emit_insn (gen_arm_lshrdi3_1bit (operands[0], operands[1]));
2771          DONE;
2772        }
2773        /* Ideally we shouldn't fail here if we could know that operands[1] 
2774           ends up already living in an iwmmxt register. Otherwise it's
2775           cheaper to have the alternate code being generated than moving
2776           values to iwmmxt regs and back.  */
2777        FAIL;
2778    }
2779  else if (!TARGET_REALLY_IWMMXT)
2780    FAIL;
2781  "
2782)
2783
2784(define_insn "arm_lshrdi3_1bit"
2785  [(set (match_operand:DI              0 "s_register_operand" "=&r,r")
2786        (lshiftrt:DI (match_operand:DI 1 "s_register_operand" "?r,0")
2787                     (const_int 1)))
2788   (clobber (reg:CC CC_REGNUM))]
2789  "TARGET_ARM"
2790  "movs\\t%R0, %R1, lsr #1\;mov\\t%Q0, %Q1, rrx"
2791  [(set_attr "conds" "clob")
2792   (set_attr "length" "8")]
2793)
2794
2795(define_expand "lshrsi3"
2796  [(set (match_operand:SI              0 "s_register_operand" "")
2797	(lshiftrt:SI (match_operand:SI 1 "s_register_operand" "")
2798		     (match_operand:SI 2 "arm_rhs_operand" "")))]
2799  "TARGET_EITHER"
2800  "
2801  if (GET_CODE (operands[2]) == CONST_INT
2802      && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
2803    {
2804      emit_insn (gen_movsi (operands[0], const0_rtx));
2805      DONE;
2806    }
2807  "
2808)
2809
2810(define_insn "*thumb_lshrsi3"
2811  [(set (match_operand:SI              0 "register_operand" "=l,l")
2812	(lshiftrt:SI (match_operand:SI 1 "register_operand" "l,0")
2813		     (match_operand:SI 2 "nonmemory_operand" "N,l")))]
2814  "TARGET_THUMB"
2815  "lsr\\t%0, %1, %2"
2816  [(set_attr "length" "2")]
2817)
2818
2819(define_expand "rotlsi3"
2820  [(set (match_operand:SI              0 "s_register_operand" "")
2821	(rotatert:SI (match_operand:SI 1 "s_register_operand" "")
2822		     (match_operand:SI 2 "reg_or_int_operand" "")))]
2823  "TARGET_ARM"
2824  "
2825  if (GET_CODE (operands[2]) == CONST_INT)
2826    operands[2] = GEN_INT ((32 - INTVAL (operands[2])) % 32);
2827  else
2828    {
2829      rtx reg = gen_reg_rtx (SImode);
2830      emit_insn (gen_subsi3 (reg, GEN_INT (32), operands[2]));
2831      operands[2] = reg;
2832    }
2833  "
2834)
2835
2836(define_expand "rotrsi3"
2837  [(set (match_operand:SI              0 "s_register_operand" "")
2838	(rotatert:SI (match_operand:SI 1 "s_register_operand" "")
2839		     (match_operand:SI 2 "arm_rhs_operand" "")))]
2840  "TARGET_EITHER"
2841  "
2842  if (TARGET_ARM)
2843    {
2844      if (GET_CODE (operands[2]) == CONST_INT
2845          && ((unsigned HOST_WIDE_INT) INTVAL (operands[2])) > 31)
2846        operands[2] = GEN_INT (INTVAL (operands[2]) % 32);
2847    }
2848  else /* TARGET_THUMB */
2849    {
2850      if (GET_CODE (operands [2]) == CONST_INT)
2851        operands [2] = force_reg (SImode, operands[2]);
2852    }
2853  "
2854)
2855
2856(define_insn "*thumb_rotrsi3"
2857  [(set (match_operand:SI              0 "register_operand" "=l")
2858	(rotatert:SI (match_operand:SI 1 "register_operand" "0")
2859		     (match_operand:SI 2 "register_operand" "l")))]
2860  "TARGET_THUMB"
2861  "ror\\t%0, %0, %2"
2862  [(set_attr "length" "2")]
2863)
2864
2865(define_insn "*arm_shiftsi3"
2866  [(set (match_operand:SI   0 "s_register_operand" "=r")
2867	(match_operator:SI  3 "shift_operator"
2868	 [(match_operand:SI 1 "s_register_operand"  "r")
2869	  (match_operand:SI 2 "reg_or_int_operand" "rM")]))]
2870  "TARGET_ARM"
2871  "mov%?\\t%0, %1%S3"
2872  [(set_attr "predicable" "yes")
2873   (set_attr "shift" "1")
2874   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
2875		      (const_string "alu_shift")
2876		      (const_string "alu_shift_reg")))]
2877)
2878
2879(define_insn "*shiftsi3_compare0"
2880  [(set (reg:CC_NOOV CC_REGNUM)
2881	(compare:CC_NOOV (match_operator:SI 3 "shift_operator"
2882			  [(match_operand:SI 1 "s_register_operand" "r")
2883			   (match_operand:SI 2 "arm_rhs_operand" "rM")])
2884			 (const_int 0)))
2885   (set (match_operand:SI 0 "s_register_operand" "=r")
2886	(match_op_dup 3 [(match_dup 1) (match_dup 2)]))]
2887  "TARGET_ARM"
2888  "mov%?s\\t%0, %1%S3"
2889  [(set_attr "conds" "set")
2890   (set_attr "shift" "1")
2891   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
2892		      (const_string "alu_shift")
2893		      (const_string "alu_shift_reg")))]
2894)
2895
2896(define_insn "*shiftsi3_compare0_scratch"
2897  [(set (reg:CC_NOOV CC_REGNUM)
2898	(compare:CC_NOOV (match_operator:SI 3 "shift_operator"
2899			  [(match_operand:SI 1 "s_register_operand" "r")
2900			   (match_operand:SI 2 "arm_rhs_operand" "rM")])
2901			 (const_int 0)))
2902   (clobber (match_scratch:SI 0 "=r"))]
2903  "TARGET_ARM"
2904  "mov%?s\\t%0, %1%S3"
2905  [(set_attr "conds" "set")
2906   (set_attr "shift" "1")]
2907)
2908
2909(define_insn "*notsi_shiftsi"
2910  [(set (match_operand:SI 0 "s_register_operand" "=r")
2911	(not:SI (match_operator:SI 3 "shift_operator"
2912		 [(match_operand:SI 1 "s_register_operand" "r")
2913		  (match_operand:SI 2 "arm_rhs_operand" "rM")])))]
2914  "TARGET_ARM"
2915  "mvn%?\\t%0, %1%S3"
2916  [(set_attr "predicable" "yes")
2917   (set_attr "shift" "1")
2918   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
2919		      (const_string "alu_shift")
2920		      (const_string "alu_shift_reg")))]
2921)
2922
2923(define_insn "*notsi_shiftsi_compare0"
2924  [(set (reg:CC_NOOV CC_REGNUM)
2925	(compare:CC_NOOV (not:SI (match_operator:SI 3 "shift_operator"
2926			  [(match_operand:SI 1 "s_register_operand" "r")
2927			   (match_operand:SI 2 "arm_rhs_operand" "rM")]))
2928			 (const_int 0)))
2929   (set (match_operand:SI 0 "s_register_operand" "=r")
2930	(not:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])))]
2931  "TARGET_ARM"
2932  "mvn%?s\\t%0, %1%S3"
2933  [(set_attr "conds" "set")
2934   (set_attr "shift" "1")
2935   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
2936		      (const_string "alu_shift")
2937		      (const_string "alu_shift_reg")))]
2938)
2939
2940(define_insn "*not_shiftsi_compare0_scratch"
2941  [(set (reg:CC_NOOV CC_REGNUM)
2942	(compare:CC_NOOV (not:SI (match_operator:SI 3 "shift_operator"
2943			  [(match_operand:SI 1 "s_register_operand" "r")
2944			   (match_operand:SI 2 "arm_rhs_operand" "rM")]))
2945			 (const_int 0)))
2946   (clobber (match_scratch:SI 0 "=r"))]
2947  "TARGET_ARM"
2948  "mvn%?s\\t%0, %1%S3"
2949  [(set_attr "conds" "set")
2950   (set_attr "shift" "1")
2951   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
2952		      (const_string "alu_shift")
2953		      (const_string "alu_shift_reg")))]
2954)
2955
2956;; We don't really have extzv, but defining this using shifts helps
2957;; to reduce register pressure later on.
2958
2959(define_expand "extzv"
2960  [(set (match_dup 4)
2961	(ashift:SI (match_operand:SI   1 "register_operand" "")
2962		   (match_operand:SI   2 "const_int_operand" "")))
2963   (set (match_operand:SI              0 "register_operand" "")
2964	(lshiftrt:SI (match_dup 4)
2965		     (match_operand:SI 3 "const_int_operand" "")))]
2966  "TARGET_THUMB"
2967  "
2968  {
2969    HOST_WIDE_INT lshift = 32 - INTVAL (operands[2]) - INTVAL (operands[3]);
2970    HOST_WIDE_INT rshift = 32 - INTVAL (operands[2]);
2971    
2972    operands[3] = GEN_INT (rshift);
2973    
2974    if (lshift == 0)
2975      {
2976        emit_insn (gen_lshrsi3 (operands[0], operands[1], operands[3]));
2977        DONE;
2978      }
2979      
2980    operands[2] = GEN_INT (lshift);
2981    operands[4] = gen_reg_rtx (SImode);
2982  }"
2983)
2984
2985
2986;; Unary arithmetic insns
2987
2988(define_expand "negdi2"
2989 [(parallel
2990   [(set (match_operand:DI          0 "s_register_operand" "")
2991	  (neg:DI (match_operand:DI 1 "s_register_operand" "")))
2992    (clobber (reg:CC CC_REGNUM))])]
2993  "TARGET_EITHER"
2994  "
2995  if (TARGET_THUMB)
2996    {
2997      if (GET_CODE (operands[1]) != REG)
2998        operands[1] = force_reg (SImode, operands[1]);
2999     }
3000  "
3001)
3002
3003;; The constraints here are to prevent a *partial* overlap (where %Q0 == %R1).
3004;; The second alternative is to allow the common case of a *full* overlap.
3005(define_insn "*arm_negdi2"
3006  [(set (match_operand:DI         0 "s_register_operand" "=&r,r")
3007	(neg:DI (match_operand:DI 1 "s_register_operand"  "?r,0")))
3008   (clobber (reg:CC CC_REGNUM))]
3009  "TARGET_ARM"
3010  "rsbs\\t%Q0, %Q1, #0\;rsc\\t%R0, %R1, #0"
3011  [(set_attr "conds" "clob")
3012   (set_attr "length" "8")]
3013)
3014
3015(define_insn "*thumb_negdi2"
3016  [(set (match_operand:DI         0 "register_operand" "=&l")
3017	(neg:DI (match_operand:DI 1 "register_operand"   "l")))
3018   (clobber (reg:CC CC_REGNUM))]
3019  "TARGET_THUMB"
3020  "mov\\t%R0, #0\;neg\\t%Q0, %Q1\;sbc\\t%R0, %R1"
3021  [(set_attr "length" "6")]
3022)
3023
3024(define_expand "negsi2"
3025  [(set (match_operand:SI         0 "s_register_operand" "")
3026	(neg:SI (match_operand:SI 1 "s_register_operand" "")))]
3027  "TARGET_EITHER"
3028  ""
3029)
3030
3031(define_insn "*arm_negsi2"
3032  [(set (match_operand:SI         0 "s_register_operand" "=r")
3033	(neg:SI (match_operand:SI 1 "s_register_operand" "r")))]
3034  "TARGET_ARM"
3035  "rsb%?\\t%0, %1, #0"
3036  [(set_attr "predicable" "yes")]
3037)
3038
3039(define_insn "*thumb_negsi2"
3040  [(set (match_operand:SI         0 "register_operand" "=l")
3041	(neg:SI (match_operand:SI 1 "register_operand" "l")))]
3042  "TARGET_THUMB"
3043  "neg\\t%0, %1"
3044  [(set_attr "length" "2")]
3045)
3046
3047(define_expand "negsf2"
3048  [(set (match_operand:SF         0 "s_register_operand" "")
3049	(neg:SF (match_operand:SF 1 "s_register_operand" "")))]
3050  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
3051  ""
3052)
3053
3054(define_expand "negdf2"
3055  [(set (match_operand:DF         0 "s_register_operand" "")
3056	(neg:DF (match_operand:DF 1 "s_register_operand" "")))]
3057  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
3058  "")
3059
3060;; abssi2 doesn't really clobber the condition codes if a different register
3061;; is being set.  To keep things simple, assume during rtl manipulations that
3062;; it does, but tell the final scan operator the truth.  Similarly for
3063;; (neg (abs...))
3064
3065(define_expand "abssi2"
3066  [(parallel
3067    [(set (match_operand:SI         0 "s_register_operand" "")
3068	  (abs:SI (match_operand:SI 1 "s_register_operand" "")))
3069     (clobber (reg:CC CC_REGNUM))])]
3070  "TARGET_ARM"
3071  "")
3072
3073(define_insn "*arm_abssi2"
3074  [(set (match_operand:SI         0 "s_register_operand" "=r,&r")
3075	(abs:SI (match_operand:SI 1 "s_register_operand" "0,r")))
3076   (clobber (reg:CC CC_REGNUM))]
3077  "TARGET_ARM"
3078  "@
3079   cmp\\t%0, #0\;rsblt\\t%0, %0, #0
3080   eor%?\\t%0, %1, %1, asr #31\;sub%?\\t%0, %0, %1, asr #31"
3081  [(set_attr "conds" "clob,*")
3082   (set_attr "shift" "1")
3083   ;; predicable can't be set based on the variant, so left as no
3084   (set_attr "length" "8")]
3085)
3086
3087(define_insn "*neg_abssi2"
3088  [(set (match_operand:SI 0 "s_register_operand" "=r,&r")
3089	(neg:SI (abs:SI (match_operand:SI 1 "s_register_operand" "0,r"))))
3090   (clobber (reg:CC CC_REGNUM))]
3091  "TARGET_ARM"
3092  "@
3093   cmp\\t%0, #0\;rsbgt\\t%0, %0, #0
3094   eor%?\\t%0, %1, %1, asr #31\;rsb%?\\t%0, %0, %1, asr #31"
3095  [(set_attr "conds" "clob,*")
3096   (set_attr "shift" "1")
3097   ;; predicable can't be set based on the variant, so left as no
3098   (set_attr "length" "8")]
3099)
3100
3101(define_expand "abssf2"
3102  [(set (match_operand:SF         0 "s_register_operand" "")
3103	(abs:SF (match_operand:SF 1 "s_register_operand" "")))]
3104  "TARGET_ARM && TARGET_HARD_FLOAT"
3105  "")
3106
3107(define_expand "absdf2"
3108  [(set (match_operand:DF         0 "s_register_operand" "")
3109	(abs:DF (match_operand:DF 1 "s_register_operand" "")))]
3110  "TARGET_ARM && TARGET_HARD_FLOAT"
3111  "")
3112
3113(define_expand "sqrtsf2"
3114  [(set (match_operand:SF 0 "s_register_operand" "")
3115	(sqrt:SF (match_operand:SF 1 "s_register_operand" "")))]
3116  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
3117  "")
3118
3119(define_expand "sqrtdf2"
3120  [(set (match_operand:DF 0 "s_register_operand" "")
3121	(sqrt:DF (match_operand:DF 1 "s_register_operand" "")))]
3122  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
3123  "")
3124
3125(define_insn_and_split "one_cmpldi2"
3126  [(set (match_operand:DI 0 "s_register_operand" "=&r,&r")
3127	(not:DI (match_operand:DI 1 "s_register_operand" "?r,0")))]
3128  "TARGET_ARM"
3129  "#"
3130  "TARGET_ARM && reload_completed"
3131  [(set (match_dup 0) (not:SI (match_dup 1)))
3132   (set (match_dup 2) (not:SI (match_dup 3)))]
3133  "
3134  {
3135    operands[2] = gen_highpart (SImode, operands[0]);
3136    operands[0] = gen_lowpart (SImode, operands[0]);
3137    operands[3] = gen_highpart (SImode, operands[1]);
3138    operands[1] = gen_lowpart (SImode, operands[1]);
3139  }"
3140  [(set_attr "length" "8")
3141   (set_attr "predicable" "yes")]
3142)
3143
3144(define_expand "one_cmplsi2"
3145  [(set (match_operand:SI         0 "s_register_operand" "")
3146	(not:SI (match_operand:SI 1 "s_register_operand" "")))]
3147  "TARGET_EITHER"
3148  ""
3149)
3150
3151(define_insn "*arm_one_cmplsi2"
3152  [(set (match_operand:SI         0 "s_register_operand" "=r")
3153	(not:SI (match_operand:SI 1 "s_register_operand"  "r")))]
3154  "TARGET_ARM"
3155  "mvn%?\\t%0, %1"
3156  [(set_attr "predicable" "yes")]
3157)
3158
3159(define_insn "*thumb_one_cmplsi2"
3160  [(set (match_operand:SI         0 "register_operand" "=l")
3161	(not:SI (match_operand:SI 1 "register_operand"  "l")))]
3162  "TARGET_THUMB"
3163  "mvn\\t%0, %1"
3164  [(set_attr "length" "2")]
3165)
3166
3167(define_insn "*notsi_compare0"
3168  [(set (reg:CC_NOOV CC_REGNUM)
3169	(compare:CC_NOOV (not:SI (match_operand:SI 1 "s_register_operand" "r"))
3170			 (const_int 0)))
3171   (set (match_operand:SI 0 "s_register_operand" "=r")
3172	(not:SI (match_dup 1)))]
3173  "TARGET_ARM"
3174  "mvn%?s\\t%0, %1"
3175  [(set_attr "conds" "set")]
3176)
3177
3178(define_insn "*notsi_compare0_scratch"
3179  [(set (reg:CC_NOOV CC_REGNUM)
3180	(compare:CC_NOOV (not:SI (match_operand:SI 1 "s_register_operand" "r"))
3181			 (const_int 0)))
3182   (clobber (match_scratch:SI 0 "=r"))]
3183  "TARGET_ARM"
3184  "mvn%?s\\t%0, %1"
3185  [(set_attr "conds" "set")]
3186)
3187
3188;; Fixed <--> Floating conversion insns
3189
3190(define_expand "floatsisf2"
3191  [(set (match_operand:SF           0 "s_register_operand" "")
3192	(float:SF (match_operand:SI 1 "s_register_operand" "")))]
3193  "TARGET_ARM && TARGET_HARD_FLOAT"
3194  "
3195  if (TARGET_MAVERICK)
3196    {
3197      emit_insn (gen_cirrus_floatsisf2 (operands[0], operands[1]));
3198      DONE;
3199    }
3200")
3201
3202(define_expand "floatsidf2"
3203  [(set (match_operand:DF           0 "s_register_operand" "")
3204	(float:DF (match_operand:SI 1 "s_register_operand" "")))]
3205  "TARGET_ARM && TARGET_HARD_FLOAT"
3206  "
3207  if (TARGET_MAVERICK)
3208    {
3209      emit_insn (gen_cirrus_floatsidf2 (operands[0], operands[1]));
3210      DONE;
3211    }
3212")
3213
3214(define_expand "fix_truncsfsi2"
3215  [(set (match_operand:SI         0 "s_register_operand" "")
3216	(fix:SI (fix:SF (match_operand:SF 1 "s_register_operand"  ""))))]
3217  "TARGET_ARM && TARGET_HARD_FLOAT"
3218  "
3219  if (TARGET_MAVERICK)
3220    {
3221      if (!cirrus_fp_register (operands[0], SImode))
3222        operands[0] = force_reg (SImode, operands[0]);
3223      if (!cirrus_fp_register (operands[1], SFmode))
3224        operands[1] = force_reg (SFmode, operands[0]);
3225      emit_insn (gen_cirrus_truncsfsi2 (operands[0], operands[1]));
3226      DONE;
3227    }
3228")
3229
3230(define_expand "fix_truncdfsi2"
3231  [(set (match_operand:SI         0 "s_register_operand" "")
3232	(fix:SI (fix:DF (match_operand:DF 1 "s_register_operand"  ""))))]
3233  "TARGET_ARM && TARGET_HARD_FLOAT"
3234  "
3235  if (TARGET_MAVERICK)
3236    {
3237      if (!cirrus_fp_register (operands[1], DFmode))
3238        operands[1] = force_reg (DFmode, operands[0]);
3239      emit_insn (gen_cirrus_truncdfsi2 (operands[0], operands[1]));
3240      DONE;
3241    }
3242")
3243
3244;; Truncation insns
3245
3246(define_expand "truncdfsf2"
3247  [(set (match_operand:SF  0 "s_register_operand" "")
3248	(float_truncate:SF
3249 	 (match_operand:DF 1 "s_register_operand" "")))]
3250  "TARGET_ARM && TARGET_HARD_FLOAT"
3251  ""
3252)
3253
3254;; Zero and sign extension instructions.
3255
3256(define_insn "zero_extendsidi2"
3257  [(set (match_operand:DI 0 "s_register_operand" "=r")
3258        (zero_extend:DI (match_operand:SI 1 "s_register_operand" "r")))]
3259  "TARGET_ARM"
3260  "*
3261    if (REGNO (operands[1])
3262        != REGNO (operands[0]) + (WORDS_BIG_ENDIAN ? 1 : 0))
3263      output_asm_insn (\"mov%?\\t%Q0, %1\", operands);
3264    return \"mov%?\\t%R0, #0\";
3265  "
3266  [(set_attr "length" "8")
3267   (set_attr "predicable" "yes")]
3268)
3269
3270(define_insn "zero_extendqidi2"
3271  [(set (match_operand:DI                 0 "s_register_operand"  "=r,r")
3272	(zero_extend:DI (match_operand:QI 1 "nonimmediate_operand" "r,m")))]
3273  "TARGET_ARM"
3274  "@
3275   and%?\\t%Q0, %1, #255\;mov%?\\t%R0, #0
3276   ldr%?b\\t%Q0, %1\;mov%?\\t%R0, #0"
3277  [(set_attr "length" "8")
3278   (set_attr "predicable" "yes")
3279   (set_attr "type" "*,load_byte")
3280   (set_attr "pool_range" "*,4092")
3281   (set_attr "neg_pool_range" "*,4084")]
3282)
3283
3284(define_insn "extendsidi2"
3285  [(set (match_operand:DI 0 "s_register_operand" "=r")
3286        (sign_extend:DI (match_operand:SI 1 "s_register_operand" "r")))]
3287  "TARGET_ARM"
3288  "*
3289    if (REGNO (operands[1])
3290        != REGNO (operands[0]) + (WORDS_BIG_ENDIAN ? 1 : 0))
3291      output_asm_insn (\"mov%?\\t%Q0, %1\", operands);
3292    return \"mov%?\\t%R0, %Q0, asr #31\";
3293  "
3294  [(set_attr "length" "8")
3295   (set_attr "shift" "1")
3296   (set_attr "predicable" "yes")]
3297)
3298
3299(define_expand "zero_extendhisi2"
3300  [(set (match_dup 2)
3301	(ashift:SI (match_operand:HI 1 "nonimmediate_operand" "")
3302		   (const_int 16)))
3303   (set (match_operand:SI 0 "s_register_operand" "")
3304	(lshiftrt:SI (match_dup 2) (const_int 16)))]
3305  "TARGET_EITHER"
3306  "
3307  {
3308    if ((TARGET_THUMB || arm_arch4) && GET_CODE (operands[1]) == MEM)
3309      {
3310	emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3311				gen_rtx_ZERO_EXTEND (SImode, operands[1])));
3312	DONE;
3313      }
3314
3315    if (TARGET_ARM && GET_CODE (operands[1]) == MEM)
3316      {
3317	emit_insn (gen_movhi_bytes (operands[0], operands[1]));
3318	DONE;
3319      }
3320
3321    if (!s_register_operand (operands[1], HImode))
3322      operands[1] = copy_to_mode_reg (HImode, operands[1]);
3323
3324    if (arm_arch6)
3325      {
3326	emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3327				gen_rtx_ZERO_EXTEND (SImode, operands[1])));
3328	DONE;
3329      }
3330
3331    operands[1] = gen_lowpart (SImode, operands[1]);
3332    operands[2] = gen_reg_rtx (SImode);
3333  }"
3334)
3335
3336(define_insn "*thumb_zero_extendhisi2"
3337  [(set (match_operand:SI 0 "register_operand" "=l")
3338	(zero_extend:SI (match_operand:HI 1 "memory_operand" "m")))]
3339  "TARGET_THUMB && !arm_arch6"
3340  "*
3341  rtx mem = XEXP (operands[1], 0);
3342
3343  if (GET_CODE (mem) == CONST)
3344    mem = XEXP (mem, 0);
3345    
3346  if (GET_CODE (mem) == LABEL_REF)
3347    return \"ldr\\t%0, %1\";
3348    
3349  if (GET_CODE (mem) == PLUS)
3350    {
3351      rtx a = XEXP (mem, 0);
3352      rtx b = XEXP (mem, 1);
3353
3354      /* This can happen due to bugs in reload.  */
3355      if (GET_CODE (a) == REG && REGNO (a) == SP_REGNUM)
3356        {
3357          rtx ops[2];
3358          ops[0] = operands[0];
3359          ops[1] = a;
3360      
3361          output_asm_insn (\"mov	%0, %1\", ops);
3362
3363          XEXP (mem, 0) = operands[0];
3364       }
3365
3366      else if (   GET_CODE (a) == LABEL_REF
3367	       && GET_CODE (b) == CONST_INT)
3368        return \"ldr\\t%0, %1\";
3369    }
3370    
3371  return \"ldrh\\t%0, %1\";
3372  "
3373  [(set_attr "length" "4")
3374   (set_attr "type" "load_byte")
3375   (set_attr "pool_range" "60")]
3376)
3377
3378(define_insn "*thumb_zero_extendhisi2_v6"
3379  [(set (match_operand:SI 0 "register_operand" "=l,l")
3380	(zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "l,m")))]
3381  "TARGET_THUMB && arm_arch6"
3382  "*
3383  rtx mem;
3384
3385  if (which_alternative == 0)
3386    return \"uxth\\t%0, %1\";
3387
3388  mem = XEXP (operands[1], 0);
3389
3390  if (GET_CODE (mem) == CONST)
3391    mem = XEXP (mem, 0);
3392    
3393  if (GET_CODE (mem) == LABEL_REF)
3394    return \"ldr\\t%0, %1\";
3395    
3396  if (GET_CODE (mem) == PLUS)
3397    {
3398      rtx a = XEXP (mem, 0);
3399      rtx b = XEXP (mem, 1);
3400
3401      /* This can happen due to bugs in reload.  */
3402      if (GET_CODE (a) == REG && REGNO (a) == SP_REGNUM)
3403        {
3404          rtx ops[2];
3405          ops[0] = operands[0];
3406          ops[1] = a;
3407      
3408          output_asm_insn (\"mov	%0, %1\", ops);
3409
3410          XEXP (mem, 0) = operands[0];
3411       }
3412
3413      else if (   GET_CODE (a) == LABEL_REF
3414	       && GET_CODE (b) == CONST_INT)
3415        return \"ldr\\t%0, %1\";
3416    }
3417    
3418  return \"ldrh\\t%0, %1\";
3419  "
3420  [(set_attr "length" "2,4")
3421   (set_attr "type" "alu_shift,load_byte")
3422   (set_attr "pool_range" "*,60")]
3423)
3424
3425(define_insn "*arm_zero_extendhisi2"
3426  [(set (match_operand:SI 0 "s_register_operand" "=r")
3427	(zero_extend:SI (match_operand:HI 1 "memory_operand" "m")))]
3428  "TARGET_ARM && arm_arch4 && !arm_arch6"
3429  "ldr%?h\\t%0, %1"
3430  [(set_attr "type" "load_byte")
3431   (set_attr "predicable" "yes")
3432   (set_attr "pool_range" "256")
3433   (set_attr "neg_pool_range" "244")]
3434)
3435
3436(define_insn "*arm_zero_extendhisi2_v6"
3437  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3438	(zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,m")))]
3439  "TARGET_ARM && arm_arch6"
3440  "@
3441   uxth%?\\t%0, %1
3442   ldr%?h\\t%0, %1"
3443  [(set_attr "type" "alu_shift,load_byte")
3444   (set_attr "predicable" "yes")
3445   (set_attr "pool_range" "*,256")
3446   (set_attr "neg_pool_range" "*,244")]
3447)
3448
3449(define_insn "*arm_zero_extendhisi2addsi"
3450  [(set (match_operand:SI 0 "s_register_operand" "=r")
3451	(plus:SI (zero_extend:SI (match_operand:HI 1 "s_register_operand" "r"))
3452		 (match_operand:SI 2 "s_register_operand" "r")))]
3453  "TARGET_ARM && arm_arch6"
3454  "uxtah%?\\t%0, %2, %1"
3455  [(set_attr "type" "alu_shift")
3456   (set_attr "predicable" "yes")]
3457)
3458
3459(define_expand "zero_extendqisi2"
3460  [(set (match_operand:SI 0 "s_register_operand" "")
3461	(zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "")))]
3462  "TARGET_EITHER"
3463  "
3464  if (!arm_arch6 && GET_CODE (operands[1]) != MEM)
3465    {
3466      if (TARGET_ARM)
3467        {
3468          emit_insn (gen_andsi3 (operands[0],
3469				 gen_lowpart (SImode, operands[1]),
3470			         GEN_INT (255)));
3471        }
3472      else /* TARGET_THUMB */
3473        {
3474          rtx temp = gen_reg_rtx (SImode);
3475	  rtx ops[3];
3476	  
3477          operands[1] = copy_to_mode_reg (QImode, operands[1]);
3478          operands[1] = gen_lowpart (SImode, operands[1]);
3479
3480	  ops[0] = temp;
3481	  ops[1] = operands[1];
3482	  ops[2] = GEN_INT (24);
3483
3484	  emit_insn (gen_rtx_SET (VOIDmode, ops[0],
3485				  gen_rtx_ASHIFT (SImode, ops[1], ops[2])));
3486	  
3487          ops[0] = operands[0];
3488	  ops[1] = temp;
3489	  ops[2] = GEN_INT (24);
3490
3491	  emit_insn (gen_rtx_SET (VOIDmode, ops[0],
3492				  gen_rtx_LSHIFTRT (SImode, ops[1], ops[2])));
3493	}
3494      DONE;
3495    }
3496  "
3497)
3498
3499(define_insn "*thumb_zero_extendqisi2"
3500  [(set (match_operand:SI 0 "register_operand" "=l")
3501	(zero_extend:SI (match_operand:QI 1 "memory_operand" "m")))]
3502  "TARGET_THUMB && !arm_arch6"
3503  "ldrb\\t%0, %1"
3504  [(set_attr "length" "2")
3505   (set_attr "type" "load_byte")
3506   (set_attr "pool_range" "32")]
3507)
3508
3509(define_insn "*thumb_zero_extendqisi2_v6"
3510  [(set (match_operand:SI 0 "register_operand" "=l,l")
3511	(zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "l,m")))]
3512  "TARGET_THUMB && arm_arch6"
3513  "@
3514   uxtb\\t%0, %1
3515   ldrb\\t%0, %1"
3516  [(set_attr "length" "2,2")
3517   (set_attr "type" "alu_shift,load_byte")
3518   (set_attr "pool_range" "*,32")]
3519)
3520
3521(define_insn "*arm_zero_extendqisi2"
3522  [(set (match_operand:SI 0 "s_register_operand" "=r")
3523	(zero_extend:SI (match_operand:QI 1 "memory_operand" "m")))]
3524  "TARGET_ARM && !arm_arch6"
3525  "ldr%?b\\t%0, %1\\t%@ zero_extendqisi2"
3526  [(set_attr "type" "load_byte")
3527   (set_attr "predicable" "yes")
3528   (set_attr "pool_range" "4096")
3529   (set_attr "neg_pool_range" "4084")]
3530)
3531
3532(define_insn "*arm_zero_extendqisi2_v6"
3533  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3534	(zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "r,m")))]
3535  "TARGET_ARM && arm_arch6"
3536  "@
3537   uxtb%?\\t%0, %1
3538   ldr%?b\\t%0, %1\\t%@ zero_extendqisi2"
3539  [(set_attr "type" "alu_shift,load_byte")
3540   (set_attr "predicable" "yes")
3541   (set_attr "pool_range" "*,4096")
3542   (set_attr "neg_pool_range" "*,4084")]
3543)
3544
3545(define_insn "*arm_zero_extendqisi2addsi"
3546  [(set (match_operand:SI 0 "s_register_operand" "=r")
3547	(plus:SI (zero_extend:SI (match_operand:QI 1 "s_register_operand" "r"))
3548		 (match_operand:SI 2 "s_register_operand" "r")))]
3549  "TARGET_ARM && arm_arch6"
3550  "uxtab%?\\t%0, %2, %1"
3551  [(set_attr "predicable" "yes")
3552   (set_attr "type" "alu_shift")]
3553)
3554
3555(define_split
3556  [(set (match_operand:SI 0 "s_register_operand" "")
3557	(zero_extend:SI (subreg:QI (match_operand:SI 1 "" "") 0)))
3558   (clobber (match_operand:SI 2 "s_register_operand" ""))]
3559  "TARGET_ARM && (GET_CODE (operands[1]) != MEM) && ! BYTES_BIG_ENDIAN"
3560  [(set (match_dup 2) (match_dup 1))
3561   (set (match_dup 0) (and:SI (match_dup 2) (const_int 255)))]
3562  ""
3563)
3564
3565(define_split
3566  [(set (match_operand:SI 0 "s_register_operand" "")
3567	(zero_extend:SI (subreg:QI (match_operand:SI 1 "" "") 3)))
3568   (clobber (match_operand:SI 2 "s_register_operand" ""))]
3569  "TARGET_ARM && (GET_CODE (operands[1]) != MEM) && BYTES_BIG_ENDIAN"
3570  [(set (match_dup 2) (match_dup 1))
3571   (set (match_dup 0) (and:SI (match_dup 2) (const_int 255)))]
3572  ""
3573)
3574
3575(define_insn "*compareqi_eq0"
3576  [(set (reg:CC_Z CC_REGNUM)
3577	(compare:CC_Z (match_operand:QI 0 "s_register_operand" "r")
3578			 (const_int 0)))]
3579  "TARGET_ARM"
3580  "tst\\t%0, #255"
3581  [(set_attr "conds" "set")]
3582)
3583
3584(define_expand "extendhisi2"
3585  [(set (match_dup 2)
3586	(ashift:SI (match_operand:HI 1 "nonimmediate_operand" "")
3587		   (const_int 16)))
3588   (set (match_operand:SI 0 "s_register_operand" "")
3589	(ashiftrt:SI (match_dup 2)
3590		     (const_int 16)))]
3591  "TARGET_EITHER"
3592  "
3593  {
3594    if (GET_CODE (operands[1]) == MEM)
3595      {
3596	if (TARGET_THUMB)
3597	  {
3598	    emit_insn (gen_thumb_extendhisi2 (operands[0], operands[1]));
3599	    DONE;
3600          }
3601	else if (arm_arch4)
3602	  {
3603	    emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3604		       gen_rtx_SIGN_EXTEND (SImode, operands[1])));
3605	    DONE;
3606	  }
3607      }
3608
3609    if (TARGET_ARM && GET_CODE (operands[1]) == MEM)
3610      {
3611        emit_insn (gen_extendhisi2_mem (operands[0], operands[1]));
3612        DONE;
3613      }
3614
3615    if (!s_register_operand (operands[1], HImode))
3616      operands[1] = copy_to_mode_reg (HImode, operands[1]);
3617
3618    if (arm_arch6)
3619      {
3620	if (TARGET_THUMB)
3621	  emit_insn (gen_thumb_extendhisi2 (operands[0], operands[1]));
3622	else
3623	  emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3624		     gen_rtx_SIGN_EXTEND (SImode, operands[1])));
3625
3626	DONE;
3627      }
3628
3629    operands[1] = gen_lowpart (SImode, operands[1]);
3630    operands[2] = gen_reg_rtx (SImode);
3631  }"
3632)
3633
3634(define_insn "thumb_extendhisi2"
3635  [(set (match_operand:SI 0 "register_operand" "=l")
3636	(sign_extend:SI (match_operand:HI 1 "memory_operand" "m")))
3637   (clobber (match_scratch:SI 2 "=&l"))]
3638  "TARGET_THUMB && !arm_arch6"
3639  "*
3640  {
3641    rtx ops[4];
3642    rtx mem = XEXP (operands[1], 0);
3643
3644    /* This code used to try to use 'V', and fix the address only if it was
3645       offsettable, but this fails for e.g. REG+48 because 48 is outside the
3646       range of QImode offsets, and offsettable_address_p does a QImode
3647       address check.  */
3648       
3649    if (GET_CODE (mem) == CONST)
3650      mem = XEXP (mem, 0);
3651    
3652    if (GET_CODE (mem) == LABEL_REF)
3653      return \"ldr\\t%0, %1\";
3654    
3655    if (GET_CODE (mem) == PLUS)
3656      {
3657        rtx a = XEXP (mem, 0);
3658        rtx b = XEXP (mem, 1);
3659
3660        if (GET_CODE (a) == LABEL_REF
3661	    && GET_CODE (b) == CONST_INT)
3662          return \"ldr\\t%0, %1\";
3663
3664        if (GET_CODE (b) == REG)
3665          return \"ldrsh\\t%0, %1\";
3666	  
3667        ops[1] = a;
3668        ops[2] = b;
3669      }
3670    else
3671      {
3672        ops[1] = mem;
3673        ops[2] = const0_rtx;
3674      }
3675
3676    gcc_assert (GET_CODE (ops[1]) == REG);
3677
3678    ops[0] = operands[0];
3679    ops[3] = operands[2];
3680    output_asm_insn (\"mov\\t%3, %2\;ldrsh\\t%0, [%1, %3]\", ops);
3681    return \"\";
3682  }"
3683  [(set_attr "length" "4")
3684   (set_attr "type" "load_byte")
3685   (set_attr "pool_range" "1020")]
3686)
3687
3688;; We used to have an early-clobber on the scratch register here.
3689;; However, there's a bug somewhere in reload which means that this
3690;; can be partially ignored during spill allocation if the memory
3691;; address also needs reloading; this causes us to die later on when
3692;; we try to verify the operands.  Fortunately, we don't really need
3693;; the early-clobber: we can always use operand 0 if operand 2
3694;; overlaps the address.
3695(define_insn "*thumb_extendhisi2_insn_v6"
3696  [(set (match_operand:SI 0 "register_operand" "=l,l")
3697	(sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "l,m")))
3698   (clobber (match_scratch:SI 2 "=X,l"))]
3699  "TARGET_THUMB && arm_arch6"
3700  "*
3701  {
3702    rtx ops[4];
3703    rtx mem;
3704
3705    if (which_alternative == 0)
3706      return \"sxth\\t%0, %1\";
3707
3708    mem = XEXP (operands[1], 0);
3709
3710    /* This code used to try to use 'V', and fix the address only if it was
3711       offsettable, but this fails for e.g. REG+48 because 48 is outside the
3712       range of QImode offsets, and offsettable_address_p does a QImode
3713       address check.  */
3714       
3715    if (GET_CODE (mem) == CONST)
3716      mem = XEXP (mem, 0);
3717    
3718    if (GET_CODE (mem) == LABEL_REF)
3719      return \"ldr\\t%0, %1\";
3720    
3721    if (GET_CODE (mem) == PLUS)
3722      {
3723        rtx a = XEXP (mem, 0);
3724        rtx b = XEXP (mem, 1);
3725
3726        if (GET_CODE (a) == LABEL_REF
3727	    && GET_CODE (b) == CONST_INT)
3728          return \"ldr\\t%0, %1\";
3729
3730        if (GET_CODE (b) == REG)
3731          return \"ldrsh\\t%0, %1\";
3732	  
3733        ops[1] = a;
3734        ops[2] = b;
3735      }
3736    else
3737      {
3738        ops[1] = mem;
3739        ops[2] = const0_rtx;
3740      }
3741      
3742    gcc_assert (GET_CODE (ops[1]) == REG);
3743
3744    ops[0] = operands[0];
3745    if (reg_mentioned_p (operands[2], ops[1]))
3746      ops[3] = ops[0];
3747    else
3748      ops[3] = operands[2];
3749    output_asm_insn (\"mov\\t%3, %2\;ldrsh\\t%0, [%1, %3]\", ops);
3750    return \"\";
3751  }"
3752  [(set_attr "length" "2,4")
3753   (set_attr "type" "alu_shift,load_byte")
3754   (set_attr "pool_range" "*,1020")]
3755)
3756
3757(define_expand "extendhisi2_mem"
3758  [(set (match_dup 2) (zero_extend:SI (match_operand:HI 1 "" "")))
3759   (set (match_dup 3)
3760	(zero_extend:SI (match_dup 7)))
3761   (set (match_dup 6) (ashift:SI (match_dup 4) (const_int 24)))
3762   (set (match_operand:SI 0 "" "")
3763	(ior:SI (ashiftrt:SI (match_dup 6) (const_int 16)) (match_dup 5)))]
3764  "TARGET_ARM"
3765  "
3766  {
3767    rtx mem1, mem2;
3768    rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
3769
3770    mem1 = change_address (operands[1], QImode, addr);
3771    mem2 = change_address (operands[1], QImode, plus_constant (addr, 1));
3772    operands[0] = gen_lowpart (SImode, operands[0]);
3773    operands[1] = mem1;
3774    operands[2] = gen_reg_rtx (SImode);
3775    operands[3] = gen_reg_rtx (SImode);
3776    operands[6] = gen_reg_rtx (SImode);
3777    operands[7] = mem2;
3778
3779    if (BYTES_BIG_ENDIAN)
3780      {
3781	operands[4] = operands[2];
3782	operands[5] = operands[3];
3783      }
3784    else
3785      {
3786	operands[4] = operands[3];
3787	operands[5] = operands[2];
3788      }
3789  }"
3790)
3791
3792(define_insn "*arm_extendhisi2"
3793  [(set (match_operand:SI 0 "s_register_operand" "=r")
3794	(sign_extend:SI (match_operand:HI 1 "memory_operand" "m")))]
3795  "TARGET_ARM && arm_arch4 && !arm_arch6"
3796  "ldr%?sh\\t%0, %1"
3797  [(set_attr "type" "load_byte")
3798   (set_attr "predicable" "yes")
3799   (set_attr "pool_range" "256")
3800   (set_attr "neg_pool_range" "244")]
3801)
3802
3803(define_insn "*arm_extendhisi2_v6"
3804  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3805	(sign_extend:SI (match_operand:HI 1 "nonimmediate_operand" "r,m")))]
3806  "TARGET_ARM && arm_arch6"
3807  "@
3808   sxth%?\\t%0, %1
3809   ldr%?sh\\t%0, %1"
3810  [(set_attr "type" "alu_shift,load_byte")
3811   (set_attr "predicable" "yes")
3812   (set_attr "pool_range" "*,256")
3813   (set_attr "neg_pool_range" "*,244")]
3814)
3815
3816(define_insn "*arm_extendhisi2addsi"
3817  [(set (match_operand:SI 0 "s_register_operand" "=r")
3818	(plus:SI (sign_extend:SI (match_operand:HI 1 "s_register_operand" "r"))
3819		 (match_operand:SI 2 "s_register_operand" "r")))]
3820  "TARGET_ARM && arm_arch6"
3821  "sxtah%?\\t%0, %2, %1"
3822)
3823
3824(define_expand "extendqihi2"
3825  [(set (match_dup 2)
3826	(ashift:SI (match_operand:QI 1 "general_operand" "")
3827		   (const_int 24)))
3828   (set (match_operand:HI 0 "s_register_operand" "")
3829	(ashiftrt:SI (match_dup 2)
3830		     (const_int 24)))]
3831  "TARGET_ARM"
3832  "
3833  {
3834    if (arm_arch4 && GET_CODE (operands[1]) == MEM)
3835      {
3836	emit_insn (gen_rtx_SET (VOIDmode,
3837				operands[0],
3838				gen_rtx_SIGN_EXTEND (HImode, operands[1])));
3839	DONE;
3840      }
3841    if (!s_register_operand (operands[1], QImode))
3842      operands[1] = copy_to_mode_reg (QImode, operands[1]);
3843    operands[0] = gen_lowpart (SImode, operands[0]);
3844    operands[1] = gen_lowpart (SImode, operands[1]);
3845    operands[2] = gen_reg_rtx (SImode);
3846  }"
3847)
3848
3849(define_insn "*extendqihi_insn"
3850  [(set (match_operand:HI 0 "s_register_operand" "=r")
3851	(sign_extend:HI (match_operand:QI 1 "memory_operand" "Uq")))]
3852  "TARGET_ARM && arm_arch4"
3853  "ldr%?sb\\t%0, %1"
3854  [(set_attr "type" "load_byte")
3855   (set_attr "predicable" "yes")
3856   (set_attr "pool_range" "256")
3857   (set_attr "neg_pool_range" "244")]
3858)
3859
3860(define_expand "extendqisi2"
3861  [(set (match_dup 2)
3862	(ashift:SI (match_operand:QI 1 "general_operand" "")
3863		   (const_int 24)))
3864   (set (match_operand:SI 0 "s_register_operand" "")
3865	(ashiftrt:SI (match_dup 2)
3866		     (const_int 24)))]
3867  "TARGET_EITHER"
3868  "
3869  {
3870    if ((TARGET_THUMB || arm_arch4) && GET_CODE (operands[1]) == MEM)
3871      {
3872        emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3873			        gen_rtx_SIGN_EXTEND (SImode, operands[1])));
3874        DONE;
3875      }
3876
3877    if (!s_register_operand (operands[1], QImode))
3878      operands[1] = copy_to_mode_reg (QImode, operands[1]);
3879
3880    if (arm_arch6)
3881      {
3882        emit_insn (gen_rtx_SET (VOIDmode, operands[0],
3883			        gen_rtx_SIGN_EXTEND (SImode, operands[1])));
3884        DONE;
3885      }
3886
3887    operands[1] = gen_lowpart (SImode, operands[1]);
3888    operands[2] = gen_reg_rtx (SImode);
3889  }"
3890)
3891
3892(define_insn "*arm_extendqisi"
3893  [(set (match_operand:SI 0 "s_register_operand" "=r")
3894	(sign_extend:SI (match_operand:QI 1 "memory_operand" "Uq")))]
3895  "TARGET_ARM && arm_arch4 && !arm_arch6"
3896  "ldr%?sb\\t%0, %1"
3897  [(set_attr "type" "load_byte")
3898   (set_attr "predicable" "yes")
3899   (set_attr "pool_range" "256")
3900   (set_attr "neg_pool_range" "244")]
3901)
3902
3903(define_insn "*arm_extendqisi_v6"
3904  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
3905	(sign_extend:SI (match_operand:QI 1 "nonimmediate_operand" "r,Uq")))]
3906  "TARGET_ARM && arm_arch6"
3907  "@
3908   sxtb%?\\t%0, %1
3909   ldr%?sb\\t%0, %1"
3910  [(set_attr "type" "alu_shift,load_byte")
3911   (set_attr "predicable" "yes")
3912   (set_attr "pool_range" "*,256")
3913   (set_attr "neg_pool_range" "*,244")]
3914)
3915
3916(define_insn "*arm_extendqisi2addsi"
3917  [(set (match_operand:SI 0 "s_register_operand" "=r")
3918	(plus:SI (sign_extend:SI (match_operand:QI 1 "s_register_operand" "r"))
3919		 (match_operand:SI 2 "s_register_operand" "r")))]
3920  "TARGET_ARM && arm_arch6"
3921  "sxtab%?\\t%0, %2, %1"
3922  [(set_attr "type" "alu_shift")
3923   (set_attr "predicable" "yes")]
3924)
3925
3926(define_insn "*thumb_extendqisi2"
3927  [(set (match_operand:SI 0 "register_operand" "=l,l")
3928	(sign_extend:SI (match_operand:QI 1 "memory_operand" "V,m")))]
3929  "TARGET_THUMB && !arm_arch6"
3930  "*
3931  {
3932    rtx ops[3];
3933    rtx mem = XEXP (operands[1], 0);
3934    
3935    if (GET_CODE (mem) == CONST)
3936      mem = XEXP (mem, 0);
3937    
3938    if (GET_CODE (mem) == LABEL_REF)
3939      return \"ldr\\t%0, %1\";
3940
3941    if (GET_CODE (mem) == PLUS
3942        && GET_CODE (XEXP (mem, 0)) == LABEL_REF)
3943      return \"ldr\\t%0, %1\";
3944      
3945    if (which_alternative == 0)
3946      return \"ldrsb\\t%0, %1\";
3947      
3948    ops[0] = operands[0];
3949    
3950    if (GET_CODE (mem) == PLUS)
3951      {
3952        rtx a = XEXP (mem, 0);
3953	rtx b = XEXP (mem, 1);
3954	
3955        ops[1] = a;
3956        ops[2] = b;
3957
3958        if (GET_CODE (a) == REG)
3959	  {
3960	    if (GET_CODE (b) == REG)
3961              output_asm_insn (\"ldrsb\\t%0, [%1, %2]\", ops);
3962            else if (REGNO (a) == REGNO (ops[0]))
3963	      {
3964                output_asm_insn (\"ldrb\\t%0, [%1, %2]\", ops);
3965		output_asm_insn (\"lsl\\t%0, %0, #24\", ops);
3966		output_asm_insn (\"asr\\t%0, %0, #24\", ops);
3967	      }
3968	    else
3969              output_asm_insn (\"mov\\t%0, %2\;ldrsb\\t%0, [%1, %0]\", ops);
3970	  }
3971	else
3972          {
3973	    gcc_assert (GET_CODE (b) == REG);
3974            if (REGNO (b) == REGNO (ops[0]))
3975	      {
3976                output_asm_insn (\"ldrb\\t%0, [%2, %1]\", ops);
3977		output_asm_insn (\"lsl\\t%0, %0, #24\", ops);
3978		output_asm_insn (\"asr\\t%0, %0, #24\", ops);
3979	      }
3980	    else
3981              output_asm_insn (\"mov\\t%0, %2\;ldrsb\\t%0, [%1, %0]\", ops);
3982          }
3983      }
3984    else if (GET_CODE (mem) == REG && REGNO (ops[0]) == REGNO (mem))
3985      {
3986        output_asm_insn (\"ldrb\\t%0, [%0, #0]\", ops);
3987	output_asm_insn (\"lsl\\t%0, %0, #24\", ops);
3988	output_asm_insn (\"asr\\t%0, %0, #24\", ops);
3989      }
3990    else
3991      {
3992        ops[1] = mem;
3993        ops[2] = const0_rtx;
3994	
3995        output_asm_insn (\"mov\\t%0, %2\;ldrsb\\t%0, [%1, %0]\", ops);
3996      }
3997    return \"\";
3998  }"
3999  [(set_attr "length" "2,6")
4000   (set_attr "type" "load_byte,load_byte")
4001   (set_attr "pool_range" "32,32")]
4002)
4003
4004(define_insn "*thumb_extendqisi2_v6"
4005  [(set (match_operand:SI 0 "register_operand" "=l,l,l")
4006	(sign_extend:SI (match_operand:QI 1 "nonimmediate_operand" "l,V,m")))]
4007  "TARGET_THUMB && arm_arch6"
4008  "*
4009  {
4010    rtx ops[3];
4011    rtx mem;
4012
4013    if (which_alternative == 0)
4014      return \"sxtb\\t%0, %1\";
4015
4016    mem = XEXP (operands[1], 0);
4017    
4018    if (GET_CODE (mem) == CONST)
4019      mem = XEXP (mem, 0);
4020    
4021    if (GET_CODE (mem) == LABEL_REF)
4022      return \"ldr\\t%0, %1\";
4023
4024    if (GET_CODE (mem) == PLUS
4025        && GET_CODE (XEXP (mem, 0)) == LABEL_REF)
4026      return \"ldr\\t%0, %1\";
4027      
4028    if (which_alternative == 0)
4029      return \"ldrsb\\t%0, %1\";
4030      
4031    ops[0] = operands[0];
4032    
4033    if (GET_CODE (mem) == PLUS)
4034      {
4035        rtx a = XEXP (mem, 0);
4036	rtx b = XEXP (mem, 1);
4037	
4038        ops[1] = a;
4039        ops[2] = b;
4040
4041        if (GET_CODE (a) == REG)
4042	  {
4043	    if (GET_CODE (b) == REG)
4044              output_asm_insn (\"ldrsb\\t%0, [%1, %2]\", ops);
4045            else if (REGNO (a) == REGNO (ops[0]))
4046	      {
4047                output_asm_insn (\"ldrb\\t%0, [%1, %2]\", ops);
4048		output_asm_insn (\"sxtb\\t%0, %0\", ops);
4049	      }
4050	    else
4051              output_asm_insn (\"mov\\t%0, %2\;ldrsb\\t%0, [%1, %0]\", ops);
4052	  }
4053	else
4054          {
4055	    gcc_assert (GET_CODE (b) == REG);
4056            if (REGNO (b) == REGNO (ops[0]))
4057	      {
4058                output_asm_insn (\"ldrb\\t%0, [%2, %1]\", ops);
4059		output_asm_insn (\"sxtb\\t%0, %0\", ops);
4060	      }
4061	    else
4062              output_asm_insn (\"mov\\t%0, %2\;ldrsb\\t%0, [%1, %0]\", ops);
4063          }
4064      }
4065    else if (GET_CODE (mem) == REG && REGNO (ops[0]) == REGNO (mem))
4066      {
4067        output_asm_insn (\"ldrb\\t%0, [%0, #0]\", ops);
4068	output_asm_insn (\"sxtb\\t%0, %0\", ops);
4069      }
4070    else
4071      {
4072        ops[1] = mem;
4073        ops[2] = const0_rtx;
4074	
4075        output_asm_insn (\"mov\\t%0, %2\;ldrsb\\t%0, [%1, %0]\", ops);
4076      }
4077    return \"\";
4078  }"
4079  [(set_attr "length" "2,2,4")
4080   (set_attr "type" "alu_shift,load_byte,load_byte")
4081   (set_attr "pool_range" "*,32,32")]
4082)
4083
4084(define_expand "extendsfdf2"
4085  [(set (match_operand:DF                  0 "s_register_operand" "")
4086	(float_extend:DF (match_operand:SF 1 "s_register_operand"  "")))]
4087  "TARGET_ARM && TARGET_HARD_FLOAT"
4088  ""
4089)
4090
4091;; Move insns (including loads and stores)
4092
4093;; XXX Just some ideas about movti.
4094;; I don't think these are a good idea on the arm, there just aren't enough
4095;; registers
4096;;(define_expand "loadti"
4097;;  [(set (match_operand:TI 0 "s_register_operand" "")
4098;;	(mem:TI (match_operand:SI 1 "address_operand" "")))]
4099;;  "" "")
4100
4101;;(define_expand "storeti"
4102;;  [(set (mem:TI (match_operand:TI 0 "address_operand" ""))
4103;;	(match_operand:TI 1 "s_register_operand" ""))]
4104;;  "" "")
4105
4106;;(define_expand "movti"
4107;;  [(set (match_operand:TI 0 "general_operand" "")
4108;;	(match_operand:TI 1 "general_operand" ""))]
4109;;  ""
4110;;  "
4111;;{
4112;;  rtx insn;
4113;;
4114;;  if (GET_CODE (operands[0]) == MEM && GET_CODE (operands[1]) == MEM)
4115;;    operands[1] = copy_to_reg (operands[1]);
4116;;  if (GET_CODE (operands[0]) == MEM)
4117;;    insn = gen_storeti (XEXP (operands[0], 0), operands[1]);
4118;;  else if (GET_CODE (operands[1]) == MEM)
4119;;    insn = gen_loadti (operands[0], XEXP (operands[1], 0));
4120;;  else
4121;;    FAIL;
4122;;
4123;;  emit_insn (insn);
4124;;  DONE;
4125;;}")
4126
4127;; Recognize garbage generated above.
4128
4129;;(define_insn ""
4130;;  [(set (match_operand:TI 0 "general_operand" "=r,r,r,<,>,m")
4131;;	(match_operand:TI 1 "general_operand" "<,>,m,r,r,r"))]
4132;;  ""
4133;;  "*
4134;;  {
4135;;    register mem = (which_alternative < 3);
4136;;    register const char *template;
4137;;
4138;;    operands[mem] = XEXP (operands[mem], 0);
4139;;    switch (which_alternative)
4140;;      {
4141;;      case 0: template = \"ldmdb\\t%1!, %M0\"; break;
4142;;      case 1: template = \"ldmia\\t%1!, %M0\"; break;
4143;;      case 2: template = \"ldmia\\t%1, %M0\"; break;
4144;;      case 3: template = \"stmdb\\t%0!, %M1\"; break;
4145;;      case 4: template = \"stmia\\t%0!, %M1\"; break;
4146;;      case 5: template = \"stmia\\t%0, %M1\"; break;
4147;;      }
4148;;    output_asm_insn (template, operands);
4149;;    return \"\";
4150;;  }")
4151
4152(define_expand "movdi"
4153  [(set (match_operand:DI 0 "general_operand" "")
4154	(match_operand:DI 1 "general_operand" ""))]
4155  "TARGET_EITHER"
4156  "
4157  if (!no_new_pseudos)
4158    {
4159      if (GET_CODE (operands[0]) != REG)
4160	operands[1] = force_reg (DImode, operands[1]);
4161    }
4162  "
4163)
4164
4165(define_insn "*arm_movdi"
4166  [(set (match_operand:DI 0 "nonimmediate_di_operand" "=r, r, r, r, m")
4167	(match_operand:DI 1 "di_operand"              "rDa,Db,Dc,mi,r"))]
4168  "TARGET_ARM
4169   && !(TARGET_HARD_FLOAT && (TARGET_MAVERICK || TARGET_VFP))
4170   && !TARGET_IWMMXT
4171   && (   register_operand (operands[0], DImode)
4172       || register_operand (operands[1], DImode))"
4173  "*
4174  switch (which_alternative)
4175    {
4176    case 0:
4177    case 1:
4178    case 2:
4179      return \"#\";
4180    default:
4181      return output_move_double (operands);
4182    }
4183  "
4184  [(set_attr "length" "8,12,16,8,8")
4185   (set_attr "type" "*,*,*,load2,store2")
4186   (set_attr "pool_range" "*,*,*,1020,*")
4187   (set_attr "neg_pool_range" "*,*,*,1008,*")]
4188)
4189
4190(define_split
4191  [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
4192	(match_operand:ANY64 1 "const_double_operand" ""))]
4193  "TARGET_ARM
4194   && reload_completed
4195   && (arm_const_double_inline_cost (operands[1])
4196       <= ((optimize_size || arm_ld_sched) ? 3 : 4))"
4197  [(const_int 0)]
4198  "
4199  arm_split_constant (SET, SImode, curr_insn,
4200		      INTVAL (gen_lowpart (SImode, operands[1])),
4201		      gen_lowpart (SImode, operands[0]), NULL_RTX, 0);
4202  arm_split_constant (SET, SImode, curr_insn,
4203		      INTVAL (gen_highpart_mode (SImode,
4204						 GET_MODE (operands[0]),
4205						 operands[1])),
4206		      gen_highpart (SImode, operands[0]), NULL_RTX, 0);
4207  DONE;
4208  "
4209)
4210
4211; If optimizing for size, or if we have load delay slots, then 
4212; we want to split the constant into two separate operations. 
4213; In both cases this may split a trivial part into a single data op
4214; leaving a single complex constant to load.  We can also get longer
4215; offsets in a LDR which means we get better chances of sharing the pool
4216; entries.  Finally, we can normally do a better job of scheduling
4217; LDR instructions than we can with LDM.
4218; This pattern will only match if the one above did not.
4219(define_split
4220  [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
4221	(match_operand:ANY64 1 "const_double_operand" ""))]
4222  "TARGET_ARM && reload_completed
4223   && arm_const_double_by_parts (operands[1])"
4224  [(set (match_dup 0) (match_dup 1))
4225   (set (match_dup 2) (match_dup 3))]
4226  "
4227  operands[2] = gen_highpart (SImode, operands[0]);
4228  operands[3] = gen_highpart_mode (SImode, GET_MODE (operands[0]),
4229				   operands[1]);
4230  operands[0] = gen_lowpart (SImode, operands[0]);
4231  operands[1] = gen_lowpart (SImode, operands[1]);
4232  "
4233)
4234
4235(define_split
4236  [(set (match_operand:ANY64 0 "arm_general_register_operand" "")
4237	(match_operand:ANY64 1 "arm_general_register_operand" ""))]
4238  "TARGET_EITHER && reload_completed"
4239  [(set (match_dup 0) (match_dup 1))
4240   (set (match_dup 2) (match_dup 3))]
4241  "
4242  operands[2] = gen_highpart (SImode, operands[0]);
4243  operands[3] = gen_highpart (SImode, operands[1]);
4244  operands[0] = gen_lowpart (SImode, operands[0]);
4245  operands[1] = gen_lowpart (SImode, operands[1]);
4246
4247  /* Handle a partial overlap.  */
4248  if (rtx_equal_p (operands[0], operands[3]))
4249    {
4250      rtx tmp0 = operands[0];
4251      rtx tmp1 = operands[1];
4252
4253      operands[0] = operands[2];
4254      operands[1] = operands[3];
4255      operands[2] = tmp0;
4256      operands[3] = tmp1;
4257    }
4258  "
4259)
4260
4261;; We can't actually do base+index doubleword loads if the index and
4262;; destination overlap.  Split here so that we at least have chance to
4263;; schedule.
4264(define_split
4265  [(set (match_operand:DI 0 "s_register_operand" "")
4266	(mem:DI (plus:SI (match_operand:SI 1 "s_register_operand" "")
4267			 (match_operand:SI 2 "s_register_operand" ""))))]
4268  "TARGET_LDRD
4269  && reg_overlap_mentioned_p (operands[0], operands[1])
4270  && reg_overlap_mentioned_p (operands[0], operands[2])"
4271  [(set (match_dup 4)
4272	(plus:SI (match_dup 1)
4273		 (match_dup 2)))
4274   (set (match_dup 0)
4275	(mem:DI (match_dup 4)))]
4276  "
4277  operands[4] = gen_rtx_REG (SImode, REGNO(operands[0]));
4278  "
4279)
4280
4281;;; ??? This should have alternatives for constants.
4282;;; ??? This was originally identical to the movdf_insn pattern.
4283;;; ??? The 'i' constraint looks funny, but it should always be replaced by
4284;;; thumb_reorg with a memory reference.
4285(define_insn "*thumb_movdi_insn"
4286  [(set (match_operand:DI 0 "nonimmediate_operand" "=l,l,l,l,>,l, m,*r")
4287	(match_operand:DI 1 "general_operand"      "l, I,J,>,l,mi,l,*r"))]
4288  "TARGET_THUMB
4289   && !(TARGET_HARD_FLOAT && TARGET_MAVERICK)
4290   && (   register_operand (operands[0], DImode)
4291       || register_operand (operands[1], DImode))"
4292  "*
4293  {
4294  switch (which_alternative)
4295    {
4296    default:
4297    case 0:
4298      if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
4299	return \"add\\t%0,  %1,  #0\;add\\t%H0, %H1, #0\";
4300      return   \"add\\t%H0, %H1, #0\;add\\t%0,  %1,  #0\";
4301    case 1:
4302      return \"mov\\t%Q0, %1\;mov\\t%R0, #0\";
4303    case 2:
4304      operands[1] = GEN_INT (- INTVAL (operands[1]));
4305      return \"mov\\t%Q0, %1\;neg\\t%Q0, %Q0\;asr\\t%R0, %Q0, #31\";
4306    case 3:
4307      return \"ldmia\\t%1, {%0, %H0}\";
4308    case 4:
4309      return \"stmia\\t%0, {%1, %H1}\";
4310    case 5:
4311      return thumb_load_double_from_address (operands);
4312    case 6:
4313      operands[2] = gen_rtx_MEM (SImode,
4314			     plus_constant (XEXP (operands[0], 0), 4));
4315      output_asm_insn (\"str\\t%1, %0\;str\\t%H1, %2\", operands);
4316      return \"\";
4317    case 7:
4318      if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
4319	return \"mov\\t%0, %1\;mov\\t%H0, %H1\";
4320      return \"mov\\t%H0, %H1\;mov\\t%0, %1\";
4321    }
4322  }"
4323  [(set_attr "length" "4,4,6,2,2,6,4,4")
4324   (set_attr "type" "*,*,*,load2,store2,load2,store2,*")
4325   (set_attr "pool_range" "*,*,*,*,*,1020,*,*")]
4326)
4327
4328(define_expand "movsi"
4329  [(set (match_operand:SI 0 "general_operand" "")
4330        (match_operand:SI 1 "general_operand" ""))]
4331  "TARGET_EITHER"
4332  "
4333  if (TARGET_ARM)
4334    {
4335      /* Everything except mem = const or mem = mem can be done easily.  */
4336      if (GET_CODE (operands[0]) == MEM)
4337        operands[1] = force_reg (SImode, operands[1]);
4338      if (arm_general_register_operand (operands[0], SImode)
4339	  && GET_CODE (operands[1]) == CONST_INT
4340          && !(const_ok_for_arm (INTVAL (operands[1]))
4341               || const_ok_for_arm (~INTVAL (operands[1]))))
4342        {
4343           arm_split_constant (SET, SImode, NULL_RTX,
4344	                       INTVAL (operands[1]), operands[0], NULL_RTX,
4345			       optimize && !no_new_pseudos);
4346          DONE;
4347        }
4348    }
4349  else /* TARGET_THUMB....  */
4350    {
4351      if (!no_new_pseudos)
4352        {
4353          if (GET_CODE (operands[0]) != REG)
4354	    operands[1] = force_reg (SImode, operands[1]);
4355        }
4356    }
4357
4358  /* Recognize the case where operand[1] is a reference to thread-local
4359     data and load its address to a register.  */
4360  if (arm_tls_referenced_p (operands[1]))
4361    {
4362      rtx tmp = operands[1];
4363      rtx addend = NULL;
4364
4365      if (GET_CODE (tmp) == CONST && GET_CODE (XEXP (tmp, 0)) == PLUS)
4366        {
4367          addend = XEXP (XEXP (tmp, 0), 1);
4368          tmp = XEXP (XEXP (tmp, 0), 0);
4369        }
4370
4371      gcc_assert (GET_CODE (tmp) == SYMBOL_REF);
4372      gcc_assert (SYMBOL_REF_TLS_MODEL (tmp) != 0);
4373
4374      tmp = legitimize_tls_address (tmp, no_new_pseudos ? operands[0] : 0);
4375      if (addend)
4376        {
4377          tmp = gen_rtx_PLUS (SImode, tmp, addend);
4378          tmp = force_operand (tmp, operands[0]);
4379        }
4380      operands[1] = tmp;
4381    }
4382  else if (flag_pic
4383	   && (CONSTANT_P (operands[1])
4384	       || symbol_mentioned_p (operands[1])
4385	       || label_mentioned_p (operands[1])))
4386      operands[1] = legitimize_pic_address (operands[1], SImode,
4387					    (no_new_pseudos ? operands[0] : 0));
4388  "
4389)
4390
4391(define_insn "*arm_movsi_insn"
4392  [(set (match_operand:SI 0 "nonimmediate_operand" "=r,r,r, m")
4393	(match_operand:SI 1 "general_operand"      "rI,K,mi,r"))]
4394  "TARGET_ARM && ! TARGET_IWMMXT
4395   && !(TARGET_HARD_FLOAT && TARGET_VFP)
4396   && (   register_operand (operands[0], SImode)
4397       || register_operand (operands[1], SImode))"
4398  "@
4399   mov%?\\t%0, %1
4400   mvn%?\\t%0, #%B1
4401   ldr%?\\t%0, %1
4402   str%?\\t%1, %0"
4403  [(set_attr "type" "*,*,load1,store1")
4404   (set_attr "predicable" "yes")
4405   (set_attr "pool_range" "*,*,4096,*")
4406   (set_attr "neg_pool_range" "*,*,4084,*")]
4407)
4408
4409(define_split
4410  [(set (match_operand:SI 0 "arm_general_register_operand" "")
4411	(match_operand:SI 1 "const_int_operand" ""))]
4412  "TARGET_ARM
4413  && (!(const_ok_for_arm (INTVAL (operands[1]))
4414        || const_ok_for_arm (~INTVAL (operands[1]))))"
4415  [(clobber (const_int 0))]
4416  "
4417  arm_split_constant (SET, SImode, NULL_RTX, 
4418                      INTVAL (operands[1]), operands[0], NULL_RTX, 0);
4419  DONE;
4420  "
4421)
4422
4423(define_insn "*thumb_movsi_insn"
4424  [(set (match_operand:SI 0 "nonimmediate_operand" "=l,l,l,l,l,>,l, m,*lh")
4425	(match_operand:SI 1 "general_operand"      "l, I,J,K,>,l,mi,l,*lh"))]
4426  "TARGET_THUMB
4427   && (   register_operand (operands[0], SImode) 
4428       || register_operand (operands[1], SImode))"
4429  "@
4430   mov	%0, %1
4431   mov	%0, %1
4432   #
4433   #
4434   ldmia\\t%1, {%0}
4435   stmia\\t%0, {%1}
4436   ldr\\t%0, %1
4437   str\\t%1, %0
4438   mov\\t%0, %1"
4439  [(set_attr "length" "2,2,4,4,2,2,2,2,2")
4440   (set_attr "type" "*,*,*,*,load1,store1,load1,store1,*")
4441   (set_attr "pool_range" "*,*,*,*,*,*,1020,*,*")]
4442)
4443
4444(define_split 
4445  [(set (match_operand:SI 0 "register_operand" "")
4446	(match_operand:SI 1 "const_int_operand" ""))]
4447  "TARGET_THUMB && satisfies_constraint_J (operands[1])"
4448  [(set (match_dup 0) (match_dup 1))
4449   (set (match_dup 0) (neg:SI (match_dup 0)))]
4450  "operands[1] = GEN_INT (- INTVAL (operands[1]));"
4451)
4452
4453(define_split 
4454  [(set (match_operand:SI 0 "register_operand" "")
4455	(match_operand:SI 1 "const_int_operand" ""))]
4456  "TARGET_THUMB && satisfies_constraint_K (operands[1])"
4457  [(set (match_dup 0) (match_dup 1))
4458   (set (match_dup 0) (ashift:SI (match_dup 0) (match_dup 2)))]
4459  "
4460  {
4461    unsigned HOST_WIDE_INT val = INTVAL (operands[1]);
4462    unsigned HOST_WIDE_INT mask = 0xff;
4463    int i;
4464    
4465    for (i = 0; i < 25; i++)
4466      if ((val & (mask << i)) == val)
4467        break;
4468
4469    /* Shouldn't happen, but we don't want to split if the shift is zero.  */
4470    if (i == 0)
4471      FAIL;
4472
4473    operands[1] = GEN_INT (val >> i);
4474    operands[2] = GEN_INT (i);
4475  }"
4476)
4477
4478;; When generating pic, we need to load the symbol offset into a register.
4479;; So that the optimizer does not confuse this with a normal symbol load
4480;; we use an unspec.  The offset will be loaded from a constant pool entry,
4481;; since that is the only type of relocation we can use.
4482
4483;; The rather odd constraints on the following are to force reload to leave
4484;; the insn alone, and to force the minipool generation pass to then move
4485;; the GOT symbol to memory.
4486
4487(define_insn "pic_load_addr_arm"
4488  [(set (match_operand:SI 0 "s_register_operand" "=r")
4489	(unspec:SI [(match_operand:SI 1 "" "mX")] UNSPEC_PIC_SYM))]
4490  "TARGET_ARM && flag_pic"
4491  "ldr%?\\t%0, %1"
4492  [(set_attr "type" "load1")
4493   (set (attr "pool_range")     (const_int 4096))
4494   (set (attr "neg_pool_range") (const_int 4084))]
4495)
4496
4497(define_insn "pic_load_addr_thumb"
4498  [(set (match_operand:SI 0 "s_register_operand" "=l")
4499	(unspec:SI [(match_operand:SI 1 "" "mX")] UNSPEC_PIC_SYM))]
4500  "TARGET_THUMB && flag_pic"
4501  "ldr\\t%0, %1"
4502  [(set_attr "type" "load1")
4503   (set (attr "pool_range") (const_int 1024))]
4504)
4505
4506;; This variant is used for AOF assembly, since it needs to mention the
4507;; pic register in the rtl.
4508(define_expand "pic_load_addr_based"
4509  [(set (match_operand:SI 0 "s_register_operand" "")
4510	(unspec:SI [(match_operand 1 "" "") (match_dup 2)] UNSPEC_PIC_SYM))]
4511  "TARGET_ARM && flag_pic"
4512  "operands[2] = cfun->machine->pic_reg;"
4513)
4514
4515(define_insn "*pic_load_addr_based_insn"
4516  [(set (match_operand:SI 0 "s_register_operand" "=r")
4517	(unspec:SI [(match_operand 1 "" "")
4518		    (match_operand 2 "s_register_operand" "r")]
4519		   UNSPEC_PIC_SYM))]
4520  "TARGET_EITHER && flag_pic && operands[2] == cfun->machine->pic_reg"
4521  "*
4522#ifdef AOF_ASSEMBLER
4523  operands[1] = aof_pic_entry (operands[1]);
4524#endif
4525  output_asm_insn (\"ldr%?\\t%0, %a1\", operands);
4526  return \"\";
4527  "
4528  [(set_attr "type" "load1")
4529   (set (attr "pool_range")
4530	(if_then_else (eq_attr "is_thumb" "yes")
4531		      (const_int 1024)
4532		      (const_int 4096)))
4533   (set (attr "neg_pool_range")
4534	(if_then_else (eq_attr "is_thumb" "yes")
4535		      (const_int 0)
4536		      (const_int 4084)))]
4537)
4538
4539(define_insn "pic_add_dot_plus_four"
4540  [(set (match_operand:SI 0 "register_operand" "=r")
4541	(unspec:SI [(plus:SI (match_operand:SI 1 "register_operand" "0")
4542			     (const (plus:SI (pc) (const_int 4))))]
4543		   UNSPEC_PIC_BASE))
4544   (use (match_operand 2 "" ""))]
4545  "TARGET_THUMB"
4546  "*
4547  (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
4548				     INTVAL (operands[2]));
4549  return \"add\\t%0, %|pc\";
4550  "
4551  [(set_attr "length" "2")]
4552)
4553
4554(define_insn "pic_add_dot_plus_eight"
4555  [(set (match_operand:SI 0 "register_operand" "=r")
4556	(unspec:SI [(plus:SI (match_operand:SI 1 "register_operand" "r")
4557			     (const (plus:SI (pc) (const_int 8))))]
4558		   UNSPEC_PIC_BASE))
4559   (use (match_operand 2 "" ""))]
4560  "TARGET_ARM"
4561  "*
4562    (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
4563				       INTVAL (operands[2]));
4564    return \"add%?\\t%0, %|pc, %1\";
4565  "
4566  [(set_attr "predicable" "yes")]
4567)
4568
4569(define_insn "tls_load_dot_plus_eight"
4570  [(set (match_operand:SI 0 "register_operand" "+r")
4571	(mem:SI (unspec:SI [(plus:SI (match_operand:SI 1 "register_operand" "r")
4572				     (const (plus:SI (pc) (const_int 8))))]
4573			   UNSPEC_PIC_BASE)))
4574   (use (match_operand 2 "" ""))]
4575  "TARGET_ARM"
4576  "*
4577    (*targetm.asm_out.internal_label) (asm_out_file, \"LPIC\",
4578				       INTVAL (operands[2]));
4579    return \"ldr%?\\t%0, [%|pc, %1]\t\t@ tls_load_dot_plus_eight\";
4580  "
4581  [(set_attr "predicable" "yes")]
4582)
4583
4584;; PIC references to local variables can generate pic_add_dot_plus_eight
4585;; followed by a load.  These sequences can be crunched down to
4586;; tls_load_dot_plus_eight by a peephole.
4587
4588(define_peephole2
4589  [(parallel [(set (match_operand:SI 0 "register_operand" "")
4590		   (unspec:SI [(plus:SI (match_operand:SI 3 "register_operand" "")
4591			     	 	(const (plus:SI (pc) (const_int 8))))]
4592			      UNSPEC_PIC_BASE))
4593   	      (use (label_ref (match_operand 1 "" "")))])
4594   (set (match_operand:SI 2 "register_operand" "") (mem:SI (match_dup 0)))]
4595  "TARGET_ARM && peep2_reg_dead_p (2, operands[0])"
4596  [(parallel [(set (match_dup 2)
4597		   (mem:SI (unspec:SI [(plus:SI (match_dup 3)
4598						(const (plus:SI (pc) (const_int 8))))]
4599				      UNSPEC_PIC_BASE)))
4600   	      (use (label_ref (match_dup 1)))])]
4601  ""
4602)
4603
4604(define_expand "builtin_setjmp_receiver"
4605  [(label_ref (match_operand 0 "" ""))]
4606  "flag_pic"
4607  "
4608{
4609  /* r3 is clobbered by set/longjmp, so we can use it as a scratch
4610     register.  */
4611  if (arm_pic_register != INVALID_REGNUM)
4612    arm_load_pic_register (1UL << 3);
4613  DONE;
4614}")
4615
4616;; If copying one reg to another we can set the condition codes according to
4617;; its value.  Such a move is common after a return from subroutine and the
4618;; result is being tested against zero.
4619
4620(define_insn "*movsi_compare0"
4621  [(set (reg:CC CC_REGNUM)
4622	(compare:CC (match_operand:SI 1 "s_register_operand" "0,r")
4623		    (const_int 0)))
4624   (set (match_operand:SI 0 "s_register_operand" "=r,r")
4625	(match_dup 1))]
4626  "TARGET_ARM"
4627  "@
4628   cmp%?\\t%0, #0
4629   sub%?s\\t%0, %1, #0"
4630  [(set_attr "conds" "set")]
4631)
4632
4633;; Subroutine to store a half word from a register into memory.
4634;; Operand 0 is the source register (HImode)
4635;; Operand 1 is the destination address in a register (SImode)
4636
4637;; In both this routine and the next, we must be careful not to spill
4638;; a memory address of reg+large_const into a separate PLUS insn, since this
4639;; can generate unrecognizable rtl.
4640
4641(define_expand "storehi"
4642  [;; store the low byte
4643   (set (match_operand 1 "" "") (match_dup 3))
4644   ;; extract the high byte
4645   (set (match_dup 2)
4646	(ashiftrt:SI (match_operand 0 "" "") (const_int 8)))
4647   ;; store the high byte
4648   (set (match_dup 4) (match_dup 5))]
4649  "TARGET_ARM"
4650  "
4651  {
4652    rtx op1 = operands[1];
4653    rtx addr = XEXP (op1, 0);
4654    enum rtx_code code = GET_CODE (addr);
4655
4656    if ((code == PLUS && GET_CODE (XEXP (addr, 1)) != CONST_INT)
4657	|| code == MINUS)
4658      op1 = replace_equiv_address (operands[1], force_reg (SImode, addr));
4659
4660    operands[4] = adjust_address (op1, QImode, 1);
4661    operands[1] = adjust_address (operands[1], QImode, 0);
4662    operands[3] = gen_lowpart (QImode, operands[0]);
4663    operands[0] = gen_lowpart (SImode, operands[0]);
4664    operands[2] = gen_reg_rtx (SImode);
4665    operands[5] = gen_lowpart (QImode, operands[2]);
4666  }"
4667)
4668
4669(define_expand "storehi_bigend"
4670  [(set (match_dup 4) (match_dup 3))
4671   (set (match_dup 2)
4672	(ashiftrt:SI (match_operand 0 "" "") (const_int 8)))
4673   (set (match_operand 1 "" "")	(match_dup 5))]
4674  "TARGET_ARM"
4675  "
4676  {
4677    rtx op1 = operands[1];
4678    rtx addr = XEXP (op1, 0);
4679    enum rtx_code code = GET_CODE (addr);
4680
4681    if ((code == PLUS && GET_CODE (XEXP (addr, 1)) != CONST_INT)
4682	|| code == MINUS)
4683      op1 = replace_equiv_address (op1, force_reg (SImode, addr));
4684
4685    operands[4] = adjust_address (op1, QImode, 1);
4686    operands[1] = adjust_address (operands[1], QImode, 0);
4687    operands[3] = gen_lowpart (QImode, operands[0]);
4688    operands[0] = gen_lowpart (SImode, operands[0]);
4689    operands[2] = gen_reg_rtx (SImode);
4690    operands[5] = gen_lowpart (QImode, operands[2]);
4691  }"
4692)
4693
4694;; Subroutine to store a half word integer constant into memory.
4695(define_expand "storeinthi"
4696  [(set (match_operand 0 "" "")
4697	(match_operand 1 "" ""))
4698   (set (match_dup 3) (match_dup 2))]
4699  "TARGET_ARM"
4700  "
4701  {
4702    HOST_WIDE_INT value = INTVAL (operands[1]);
4703    rtx addr = XEXP (operands[0], 0);
4704    rtx op0 = operands[0];
4705    enum rtx_code code = GET_CODE (addr);
4706
4707    if ((code == PLUS && GET_CODE (XEXP (addr, 1)) != CONST_INT)
4708	|| code == MINUS)
4709      op0 = replace_equiv_address (op0, force_reg (SImode, addr));
4710
4711    operands[1] = gen_reg_rtx (SImode);
4712    if (BYTES_BIG_ENDIAN)
4713      {
4714	emit_insn (gen_movsi (operands[1], GEN_INT ((value >> 8) & 255)));
4715	if ((value & 255) == ((value >> 8) & 255))
4716	  operands[2] = operands[1];
4717	else
4718	  {
4719	    operands[2] = gen_reg_rtx (SImode);
4720	    emit_insn (gen_movsi (operands[2], GEN_INT (value & 255)));
4721	  }
4722      }
4723    else
4724      {
4725	emit_insn (gen_movsi (operands[1], GEN_INT (value & 255)));
4726	if ((value & 255) == ((value >> 8) & 255))
4727	  operands[2] = operands[1];
4728	else
4729	  {
4730	    operands[2] = gen_reg_rtx (SImode);
4731	    emit_insn (gen_movsi (operands[2], GEN_INT ((value >> 8) & 255)));
4732	  }
4733      }
4734
4735    operands[3] = adjust_address (op0, QImode, 1);
4736    operands[0] = adjust_address (operands[0], QImode, 0);
4737    operands[2] = gen_lowpart (QImode, operands[2]);
4738    operands[1] = gen_lowpart (QImode, operands[1]);
4739  }"
4740)
4741
4742(define_expand "storehi_single_op"
4743  [(set (match_operand:HI 0 "memory_operand" "")
4744	(match_operand:HI 1 "general_operand" ""))]
4745  "TARGET_ARM && arm_arch4"
4746  "
4747  if (!s_register_operand (operands[1], HImode))
4748    operands[1] = copy_to_mode_reg (HImode, operands[1]);
4749  "
4750)
4751
4752(define_expand "movhi"
4753  [(set (match_operand:HI 0 "general_operand" "")
4754	(match_operand:HI 1 "general_operand" ""))]
4755  "TARGET_EITHER"
4756  "
4757  if (TARGET_ARM)
4758    {
4759      if (!no_new_pseudos)
4760        {
4761          if (GET_CODE (operands[0]) == MEM)
4762	    {
4763	      if (arm_arch4)
4764	        {
4765	          emit_insn (gen_storehi_single_op (operands[0], operands[1]));
4766	          DONE;
4767	        }
4768	      if (GET_CODE (operands[1]) == CONST_INT)
4769	        emit_insn (gen_storeinthi (operands[0], operands[1]));
4770	      else
4771	        {
4772	          if (GET_CODE (operands[1]) == MEM)
4773		    operands[1] = force_reg (HImode, operands[1]);
4774	          if (BYTES_BIG_ENDIAN)
4775		    emit_insn (gen_storehi_bigend (operands[1], operands[0]));
4776	          else
4777		   emit_insn (gen_storehi (operands[1], operands[0]));
4778	        }
4779	      DONE;
4780	    }
4781          /* Sign extend a constant, and keep it in an SImode reg.  */
4782          else if (GET_CODE (operands[1]) == CONST_INT)
4783	    {
4784	      rtx reg = gen_reg_rtx (SImode);
4785	      HOST_WIDE_INT val = INTVAL (operands[1]) & 0xffff;
4786
4787	      /* If the constant is already valid, leave it alone.  */
4788	      if (!const_ok_for_arm (val))
4789	        {
4790	          /* If setting all the top bits will make the constant 
4791		     loadable in a single instruction, then set them.  
4792		     Otherwise, sign extend the number.  */
4793
4794	          if (const_ok_for_arm (~(val | ~0xffff)))
4795		    val |= ~0xffff;
4796	          else if (val & 0x8000)
4797		    val |= ~0xffff;
4798	        }
4799
4800	      emit_insn (gen_movsi (reg, GEN_INT (val)));
4801	      operands[1] = gen_lowpart (HImode, reg);
4802	    }
4803	  else if (arm_arch4 && optimize && !no_new_pseudos
4804		   && GET_CODE (operands[1]) == MEM)
4805	    {
4806	      rtx reg = gen_reg_rtx (SImode);
4807
4808	      emit_insn (gen_zero_extendhisi2 (reg, operands[1]));
4809	      operands[1] = gen_lowpart (HImode, reg);
4810	    }
4811          else if (!arm_arch4)
4812	    {
4813	      if (GET_CODE (operands[1]) == MEM)
4814	        {
4815		  rtx base;
4816		  rtx offset = const0_rtx;
4817		  rtx reg = gen_reg_rtx (SImode);
4818
4819		  if ((GET_CODE (base = XEXP (operands[1], 0)) == REG
4820		       || (GET_CODE (base) == PLUS
4821			   && (GET_CODE (offset = XEXP (base, 1))
4822			       == CONST_INT)
4823                           && ((INTVAL(offset) & 1) != 1)
4824			   && GET_CODE (base = XEXP (base, 0)) == REG))
4825		      && REGNO_POINTER_ALIGN (REGNO (base)) >= 32)
4826		    {
4827		      rtx new;
4828
4829		      new = widen_memory_access (operands[1], SImode,
4830						 ((INTVAL (offset) & ~3)
4831						  - INTVAL (offset)));
4832		      emit_insn (gen_movsi (reg, new));
4833		      if (((INTVAL (offset) & 2) != 0)
4834			  ^ (BYTES_BIG_ENDIAN ? 1 : 0))
4835			{
4836			  rtx reg2 = gen_reg_rtx (SImode);
4837
4838			  emit_insn (gen_lshrsi3 (reg2, reg, GEN_INT (16)));
4839			  reg = reg2;
4840			}
4841		    }
4842		  else
4843		    emit_insn (gen_movhi_bytes (reg, operands[1]));
4844
4845		  operands[1] = gen_lowpart (HImode, reg);
4846	       }
4847	   }
4848        }
4849      /* Handle loading a large integer during reload.  */
4850      else if (GET_CODE (operands[1]) == CONST_INT
4851	       && !const_ok_for_arm (INTVAL (operands[1]))
4852	       && !const_ok_for_arm (~INTVAL (operands[1])))
4853        {
4854          /* Writing a constant to memory needs a scratch, which should
4855	     be handled with SECONDARY_RELOADs.  */
4856          gcc_assert (GET_CODE (operands[0]) == REG);
4857
4858          operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
4859          emit_insn (gen_movsi (operands[0], operands[1]));
4860          DONE;
4861       }
4862    }
4863  else /* TARGET_THUMB */
4864    {
4865      if (!no_new_pseudos)
4866        {
4867	  if (GET_CODE (operands[1]) == CONST_INT)
4868	    {
4869	      rtx reg = gen_reg_rtx (SImode);
4870
4871	      emit_insn (gen_movsi (reg, operands[1]));
4872	      operands[1] = gen_lowpart (HImode, reg);
4873	    }
4874
4875          /* ??? We shouldn't really get invalid addresses here, but this can
4876	     happen if we are passed a SP (never OK for HImode/QImode) or 
4877	     virtual register (rejected by GO_IF_LEGITIMATE_ADDRESS for 
4878	     HImode/QImode) relative address.  */
4879          /* ??? This should perhaps be fixed elsewhere, for instance, in
4880	     fixup_stack_1, by checking for other kinds of invalid addresses,
4881	     e.g. a bare reference to a virtual register.  This may confuse the
4882	     alpha though, which must handle this case differently.  */
4883          if (GET_CODE (operands[0]) == MEM
4884	      && !memory_address_p (GET_MODE (operands[0]),
4885				    XEXP (operands[0], 0)))
4886	    operands[0]
4887	      = replace_equiv_address (operands[0],
4888				       copy_to_reg (XEXP (operands[0], 0)));
4889   
4890          if (GET_CODE (operands[1]) == MEM
4891	      && !memory_address_p (GET_MODE (operands[1]),
4892				    XEXP (operands[1], 0)))
4893	    operands[1]
4894	      = replace_equiv_address (operands[1],
4895				       copy_to_reg (XEXP (operands[1], 0)));
4896
4897	  if (GET_CODE (operands[1]) == MEM && optimize > 0)
4898	    {
4899	      rtx reg = gen_reg_rtx (SImode);
4900
4901	      emit_insn (gen_zero_extendhisi2 (reg, operands[1]));
4902	      operands[1] = gen_lowpart (HImode, reg);
4903	    }
4904
4905          if (GET_CODE (operands[0]) == MEM)
4906	    operands[1] = force_reg (HImode, operands[1]);
4907        }
4908      else if (GET_CODE (operands[1]) == CONST_INT
4909	        && !satisfies_constraint_I (operands[1]))
4910        {
4911	  /* Handle loading a large integer during reload.  */
4912
4913          /* Writing a constant to memory needs a scratch, which should
4914	     be handled with SECONDARY_RELOADs.  */
4915          gcc_assert (GET_CODE (operands[0]) == REG);
4916
4917          operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
4918          emit_insn (gen_movsi (operands[0], operands[1]));
4919          DONE;
4920        }
4921    }
4922  "
4923)
4924
4925(define_insn "*thumb_movhi_insn"
4926  [(set (match_operand:HI 0 "nonimmediate_operand" "=l,l,m,*r,*h,l")
4927	(match_operand:HI 1 "general_operand"       "l,m,l,*h,*r,I"))]
4928  "TARGET_THUMB
4929   && (   register_operand (operands[0], HImode)
4930       || register_operand (operands[1], HImode))"
4931  "*
4932  switch (which_alternative)
4933    {
4934    case 0: return \"add	%0, %1, #0\";
4935    case 2: return \"strh	%1, %0\";
4936    case 3: return \"mov	%0, %1\";
4937    case 4: return \"mov	%0, %1\";
4938    case 5: return \"mov	%0, %1\";
4939    default: gcc_unreachable ();
4940    case 1:
4941      /* The stack pointer can end up being taken as an index register.
4942          Catch this case here and deal with it.  */
4943      if (GET_CODE (XEXP (operands[1], 0)) == PLUS
4944	  && GET_CODE (XEXP (XEXP (operands[1], 0), 0)) == REG
4945	  && REGNO    (XEXP (XEXP (operands[1], 0), 0)) == SP_REGNUM)
4946        {
4947	  rtx ops[2];
4948          ops[0] = operands[0];
4949          ops[1] = XEXP (XEXP (operands[1], 0), 0);
4950      
4951          output_asm_insn (\"mov	%0, %1\", ops);
4952
4953          XEXP (XEXP (operands[1], 0), 0) = operands[0];
4954    
4955	}
4956      return \"ldrh	%0, %1\";
4957    }"
4958  [(set_attr "length" "2,4,2,2,2,2")
4959   (set_attr "type" "*,load1,store1,*,*,*")]
4960)
4961
4962
4963(define_expand "movhi_bytes"
4964  [(set (match_dup 2) (zero_extend:SI (match_operand:HI 1 "" "")))
4965   (set (match_dup 3)
4966	(zero_extend:SI (match_dup 6)))
4967   (set (match_operand:SI 0 "" "")
4968	 (ior:SI (ashift:SI (match_dup 4) (const_int 8)) (match_dup 5)))]
4969  "TARGET_ARM"
4970  "
4971  {
4972    rtx mem1, mem2;
4973    rtx addr = copy_to_mode_reg (SImode, XEXP (operands[1], 0));
4974
4975    mem1 = change_address (operands[1], QImode, addr);
4976    mem2 = change_address (operands[1], QImode, plus_constant (addr, 1));
4977    operands[0] = gen_lowpart (SImode, operands[0]);
4978    operands[1] = mem1;
4979    operands[2] = gen_reg_rtx (SImode);
4980    operands[3] = gen_reg_rtx (SImode);
4981    operands[6] = mem2;
4982
4983    if (BYTES_BIG_ENDIAN)
4984      {
4985	operands[4] = operands[2];
4986	operands[5] = operands[3];
4987      }
4988    else
4989      {
4990	operands[4] = operands[3];
4991	operands[5] = operands[2];
4992      }
4993  }"
4994)
4995
4996(define_expand "movhi_bigend"
4997  [(set (match_dup 2)
4998	(rotate:SI (subreg:SI (match_operand:HI 1 "memory_operand" "") 0)
4999		   (const_int 16)))
5000   (set (match_dup 3)
5001	(ashiftrt:SI (match_dup 2) (const_int 16)))
5002   (set (match_operand:HI 0 "s_register_operand" "")
5003	(match_dup 4))]
5004  "TARGET_ARM"
5005  "
5006  operands[2] = gen_reg_rtx (SImode);
5007  operands[3] = gen_reg_rtx (SImode);
5008  operands[4] = gen_lowpart (HImode, operands[3]);
5009  "
5010)
5011
5012;; Pattern to recognize insn generated default case above
5013(define_insn "*movhi_insn_arch4"
5014  [(set (match_operand:HI 0 "nonimmediate_operand" "=r,r,m,r")    
5015	(match_operand:HI 1 "general_operand"      "rI,K,r,m"))]
5016  "TARGET_ARM
5017   && arm_arch4
5018   && (GET_CODE (operands[1]) != CONST_INT
5019       || const_ok_for_arm (INTVAL (operands[1]))
5020       || const_ok_for_arm (~INTVAL (operands[1])))"
5021  "@
5022   mov%?\\t%0, %1\\t%@ movhi
5023   mvn%?\\t%0, #%B1\\t%@ movhi
5024   str%?h\\t%1, %0\\t%@ movhi
5025   ldr%?h\\t%0, %1\\t%@ movhi"
5026  [(set_attr "type" "*,*,store1,load1")
5027   (set_attr "predicable" "yes")
5028   (set_attr "pool_range" "*,*,*,256")
5029   (set_attr "neg_pool_range" "*,*,*,244")]
5030)
5031
5032(define_insn "*movhi_bytes"
5033  [(set (match_operand:HI 0 "s_register_operand" "=r,r")
5034	(match_operand:HI 1 "arm_rhs_operand"  "rI,K"))]
5035  "TARGET_ARM"
5036  "@
5037   mov%?\\t%0, %1\\t%@ movhi
5038   mvn%?\\t%0, #%B1\\t%@ movhi"
5039  [(set_attr "predicable" "yes")]
5040)
5041
5042(define_expand "thumb_movhi_clobber"
5043  [(set (match_operand:HI     0 "memory_operand"   "")
5044	(match_operand:HI     1 "register_operand" ""))
5045   (clobber (match_operand:DI 2 "register_operand" ""))]
5046  "TARGET_THUMB"
5047  "
5048  if (strict_memory_address_p (HImode, XEXP (operands[0], 0))
5049      && REGNO (operands[1]) <= LAST_LO_REGNUM)
5050    {
5051      emit_insn (gen_movhi (operands[0], operands[1]));
5052      DONE;
5053    }
5054  /* XXX Fixme, need to handle other cases here as well.  */
5055  gcc_unreachable ();
5056  "
5057)
5058	
5059;; We use a DImode scratch because we may occasionally need an additional
5060;; temporary if the address isn't offsettable -- push_reload doesn't seem
5061;; to take any notice of the "o" constraints on reload_memory_operand operand.
5062(define_expand "reload_outhi"
5063  [(parallel [(match_operand:HI 0 "arm_reload_memory_operand" "=o")
5064	      (match_operand:HI 1 "s_register_operand"        "r")
5065	      (match_operand:DI 2 "s_register_operand"        "=&l")])]
5066  "TARGET_EITHER"
5067  "if (TARGET_ARM)
5068     arm_reload_out_hi (operands);
5069   else
5070     thumb_reload_out_hi (operands);
5071  DONE;
5072  "
5073)
5074
5075(define_expand "reload_inhi"
5076  [(parallel [(match_operand:HI 0 "s_register_operand" "=r")
5077	      (match_operand:HI 1 "arm_reload_memory_operand" "o")
5078	      (match_operand:DI 2 "s_register_operand" "=&r")])]
5079  "TARGET_EITHER"
5080  "
5081  if (TARGET_ARM)
5082    arm_reload_in_hi (operands);
5083  else
5084    thumb_reload_out_hi (operands);
5085  DONE;
5086")
5087
5088(define_expand "movqi"
5089  [(set (match_operand:QI 0 "general_operand" "")
5090        (match_operand:QI 1 "general_operand" ""))]
5091  "TARGET_EITHER"
5092  "
5093  /* Everything except mem = const or mem = mem can be done easily */
5094
5095  if (!no_new_pseudos)
5096    {
5097      if (GET_CODE (operands[1]) == CONST_INT)
5098	{
5099	  rtx reg = gen_reg_rtx (SImode);
5100
5101	  emit_insn (gen_movsi (reg, operands[1]));
5102	  operands[1] = gen_lowpart (QImode, reg);
5103	}
5104
5105      if (TARGET_THUMB)
5106	{
5107          /* ??? We shouldn't really get invalid addresses here, but this can
5108	     happen if we are passed a SP (never OK for HImode/QImode) or
5109	     virtual register (rejected by GO_IF_LEGITIMATE_ADDRESS for
5110	     HImode/QImode) relative address.  */
5111          /* ??? This should perhaps be fixed elsewhere, for instance, in
5112	     fixup_stack_1, by checking for other kinds of invalid addresses,
5113	     e.g. a bare reference to a virtual register.  This may confuse the
5114	     alpha though, which must handle this case differently.  */
5115          if (GET_CODE (operands[0]) == MEM
5116	      && !memory_address_p (GET_MODE (operands[0]),
5117		  		     XEXP (operands[0], 0)))
5118	    operands[0]
5119	      = replace_equiv_address (operands[0],
5120				       copy_to_reg (XEXP (operands[0], 0)));
5121          if (GET_CODE (operands[1]) == MEM
5122	      && !memory_address_p (GET_MODE (operands[1]),
5123				    XEXP (operands[1], 0)))
5124	     operands[1]
5125	       = replace_equiv_address (operands[1],
5126					copy_to_reg (XEXP (operands[1], 0)));
5127	}
5128
5129      if (GET_CODE (operands[1]) == MEM && optimize > 0)
5130	{
5131	  rtx reg = gen_reg_rtx (SImode);
5132
5133	  emit_insn (gen_zero_extendqisi2 (reg, operands[1]));
5134	  operands[1] = gen_lowpart (QImode, reg);
5135	}
5136
5137      if (GET_CODE (operands[0]) == MEM)
5138	operands[1] = force_reg (QImode, operands[1]);
5139    }
5140  else if (TARGET_THUMB
5141	   && GET_CODE (operands[1]) == CONST_INT
5142	   && !satisfies_constraint_I (operands[1]))
5143    {
5144      /* Handle loading a large integer during reload.  */
5145
5146      /* Writing a constant to memory needs a scratch, which should
5147	 be handled with SECONDARY_RELOADs.  */
5148      gcc_assert (GET_CODE (operands[0]) == REG);
5149
5150      operands[0] = gen_rtx_SUBREG (SImode, operands[0], 0);
5151      emit_insn (gen_movsi (operands[0], operands[1]));
5152      DONE;
5153    }
5154  "
5155)
5156
5157
5158(define_insn "*arm_movqi_insn"
5159  [(set (match_operand:QI 0 "nonimmediate_operand" "=r,r,r,m")
5160	(match_operand:QI 1 "general_operand" "rI,K,m,r"))]
5161  "TARGET_ARM
5162   && (   register_operand (operands[0], QImode)
5163       || register_operand (operands[1], QImode))"
5164  "@
5165   mov%?\\t%0, %1
5166   mvn%?\\t%0, #%B1
5167   ldr%?b\\t%0, %1
5168   str%?b\\t%1, %0"
5169  [(set_attr "type" "*,*,load1,store1")
5170   (set_attr "predicable" "yes")]
5171)
5172
5173(define_insn "*thumb_movqi_insn"
5174  [(set (match_operand:QI 0 "nonimmediate_operand" "=l,l,m,*r,*h,l")
5175	(match_operand:QI 1 "general_operand"      "l, m,l,*h,*r,I"))]
5176  "TARGET_THUMB
5177   && (   register_operand (operands[0], QImode)
5178       || register_operand (operands[1], QImode))"
5179  "@
5180   add\\t%0, %1, #0
5181   ldrb\\t%0, %1
5182   strb\\t%1, %0
5183   mov\\t%0, %1
5184   mov\\t%0, %1
5185   mov\\t%0, %1"
5186  [(set_attr "length" "2")
5187   (set_attr "type" "*,load1,store1,*,*,*")
5188   (set_attr "pool_range" "*,32,*,*,*,*")]
5189)
5190
5191(define_expand "movsf"
5192  [(set (match_operand:SF 0 "general_operand" "")
5193	(match_operand:SF 1 "general_operand" ""))]
5194  "TARGET_EITHER"
5195  "
5196  if (TARGET_ARM)
5197    {
5198      if (GET_CODE (operands[0]) == MEM)
5199        operands[1] = force_reg (SFmode, operands[1]);
5200    }
5201  else /* TARGET_THUMB */
5202    {
5203      if (!no_new_pseudos)
5204        {
5205           if (GET_CODE (operands[0]) != REG)
5206	     operands[1] = force_reg (SFmode, operands[1]);
5207        }
5208    }
5209  "
5210)
5211
5212;; Transform a floating-point move of a constant into a core register into
5213;; an SImode operation.
5214(define_split
5215  [(set (match_operand:SF 0 "arm_general_register_operand" "")
5216	(match_operand:SF 1 "immediate_operand" ""))]
5217  "TARGET_ARM
5218   && reload_completed
5219   && GET_CODE (operands[1]) == CONST_DOUBLE"
5220  [(set (match_dup 2) (match_dup 3))]
5221  "
5222  operands[2] = gen_lowpart (SImode, operands[0]);
5223  operands[3] = gen_lowpart (SImode, operands[1]);
5224  if (operands[2] == 0 || operands[3] == 0)
5225    FAIL;
5226  "
5227)
5228
5229(define_insn "*arm_movsf_soft_insn"
5230  [(set (match_operand:SF 0 "nonimmediate_operand" "=r,r,m")
5231	(match_operand:SF 1 "general_operand"  "r,mE,r"))]
5232  "TARGET_ARM
5233   && TARGET_SOFT_FLOAT
5234   && (GET_CODE (operands[0]) != MEM
5235       || register_operand (operands[1], SFmode))"
5236  "@
5237   mov%?\\t%0, %1
5238   ldr%?\\t%0, %1\\t%@ float
5239   str%?\\t%1, %0\\t%@ float"
5240  [(set_attr "length" "4,4,4")
5241   (set_attr "predicable" "yes")
5242   (set_attr "type" "*,load1,store1")
5243   (set_attr "pool_range" "*,4096,*")
5244   (set_attr "neg_pool_range" "*,4084,*")]
5245)
5246
5247;;; ??? This should have alternatives for constants.
5248(define_insn "*thumb_movsf_insn"
5249  [(set (match_operand:SF     0 "nonimmediate_operand" "=l,l,>,l, m,*r,*h")
5250	(match_operand:SF     1 "general_operand"      "l, >,l,mF,l,*h,*r"))]
5251  "TARGET_THUMB
5252   && (   register_operand (operands[0], SFmode) 
5253       || register_operand (operands[1], SFmode))"
5254  "@
5255   add\\t%0, %1, #0
5256   ldmia\\t%1, {%0}
5257   stmia\\t%0, {%1}
5258   ldr\\t%0, %1
5259   str\\t%1, %0
5260   mov\\t%0, %1
5261   mov\\t%0, %1"
5262  [(set_attr "length" "2")
5263   (set_attr "type" "*,load1,store1,load1,store1,*,*")
5264   (set_attr "pool_range" "*,*,*,1020,*,*,*")]
5265)
5266
5267(define_expand "movdf"
5268  [(set (match_operand:DF 0 "general_operand" "")
5269	(match_operand:DF 1 "general_operand" ""))]
5270  "TARGET_EITHER"
5271  "
5272  if (TARGET_ARM)
5273    {
5274      if (GET_CODE (operands[0]) == MEM)
5275        operands[1] = force_reg (DFmode, operands[1]);
5276    }
5277  else /* TARGET_THUMB */
5278    {
5279      if (!no_new_pseudos)
5280        {
5281          if (GET_CODE (operands[0]) != REG)
5282	    operands[1] = force_reg (DFmode, operands[1]);
5283        }
5284    }
5285  "
5286)
5287
5288;; Reloading a df mode value stored in integer regs to memory can require a
5289;; scratch reg.
5290(define_expand "reload_outdf"
5291  [(match_operand:DF 0 "arm_reload_memory_operand" "=o")
5292   (match_operand:DF 1 "s_register_operand" "r")
5293   (match_operand:SI 2 "s_register_operand" "=&r")]
5294  "TARGET_ARM"
5295  "
5296  {
5297    enum rtx_code code = GET_CODE (XEXP (operands[0], 0));
5298
5299    if (code == REG)
5300      operands[2] = XEXP (operands[0], 0);
5301    else if (code == POST_INC || code == PRE_DEC)
5302      {
5303	operands[0] = gen_rtx_SUBREG (DImode, operands[0], 0);
5304	operands[1] = gen_rtx_SUBREG (DImode, operands[1], 0);
5305	emit_insn (gen_movdi (operands[0], operands[1]));
5306	DONE;
5307      }
5308    else if (code == PRE_INC)
5309      {
5310	rtx reg = XEXP (XEXP (operands[0], 0), 0);
5311
5312	emit_insn (gen_addsi3 (reg, reg, GEN_INT (8)));
5313	operands[2] = reg;
5314      }
5315    else if (code == POST_DEC)
5316      operands[2] = XEXP (XEXP (operands[0], 0), 0);
5317    else
5318      emit_insn (gen_addsi3 (operands[2], XEXP (XEXP (operands[0], 0), 0),
5319			     XEXP (XEXP (operands[0], 0), 1)));
5320
5321    emit_insn (gen_rtx_SET (VOIDmode,
5322			    replace_equiv_address (operands[0], operands[2]),
5323			    operands[1]));
5324
5325    if (code == POST_DEC)
5326      emit_insn (gen_addsi3 (operands[2], operands[2], GEN_INT (-8)));
5327
5328    DONE;
5329  }"
5330)
5331
5332(define_insn "*movdf_soft_insn"
5333  [(set (match_operand:DF 0 "nonimmediate_soft_df_operand" "=r,r,r,r,m")
5334	(match_operand:DF 1 "soft_df_operand" "rDa,Db,Dc,mF,r"))]
5335  "TARGET_ARM && TARGET_SOFT_FLOAT
5336   && (   register_operand (operands[0], DFmode)
5337       || register_operand (operands[1], DFmode))"
5338  "*
5339  switch (which_alternative)
5340    {
5341    case 0:
5342    case 1:
5343    case 2:
5344      return \"#\";
5345    default:
5346      return output_move_double (operands);
5347    }
5348  "
5349  [(set_attr "length" "8,12,16,8,8")
5350   (set_attr "type" "*,*,*,load2,store2")
5351   (set_attr "pool_range" "1020")
5352   (set_attr "neg_pool_range" "1008")]
5353)
5354
5355;;; ??? This should have alternatives for constants.
5356;;; ??? This was originally identical to the movdi_insn pattern.
5357;;; ??? The 'F' constraint looks funny, but it should always be replaced by
5358;;; thumb_reorg with a memory reference.
5359(define_insn "*thumb_movdf_insn"
5360  [(set (match_operand:DF 0 "nonimmediate_operand" "=l,l,>,l, m,*r")
5361	(match_operand:DF 1 "general_operand"      "l, >,l,mF,l,*r"))]
5362  "TARGET_THUMB
5363   && (   register_operand (operands[0], DFmode)
5364       || register_operand (operands[1], DFmode))"
5365  "*
5366  switch (which_alternative)
5367    {
5368    default:
5369    case 0:
5370      if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
5371	return \"add\\t%0, %1, #0\;add\\t%H0, %H1, #0\";
5372      return \"add\\t%H0, %H1, #0\;add\\t%0, %1, #0\";
5373    case 1:
5374      return \"ldmia\\t%1, {%0, %H0}\";
5375    case 2:
5376      return \"stmia\\t%0, {%1, %H1}\";
5377    case 3:
5378      return thumb_load_double_from_address (operands);
5379    case 4:
5380      operands[2] = gen_rtx_MEM (SImode,
5381				 plus_constant (XEXP (operands[0], 0), 4));
5382      output_asm_insn (\"str\\t%1, %0\;str\\t%H1, %2\", operands);
5383      return \"\";
5384    case 5:
5385      if (REGNO (operands[1]) == REGNO (operands[0]) + 1)
5386	return \"mov\\t%0, %1\;mov\\t%H0, %H1\";
5387      return \"mov\\t%H0, %H1\;mov\\t%0, %1\";
5388    }
5389  "
5390  [(set_attr "length" "4,2,2,6,4,4")
5391   (set_attr "type" "*,load2,store2,load2,store2,*")
5392   (set_attr "pool_range" "*,*,*,1020,*,*")]
5393)
5394
5395(define_expand "movxf"
5396  [(set (match_operand:XF 0 "general_operand" "")
5397	(match_operand:XF 1 "general_operand" ""))]
5398  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_FPA"
5399  "
5400  if (GET_CODE (operands[0]) == MEM)
5401    operands[1] = force_reg (XFmode, operands[1]);
5402  "
5403)
5404
5405;; Vector Moves
5406(define_expand "movv2si"
5407  [(set (match_operand:V2SI 0 "nonimmediate_operand" "")
5408	(match_operand:V2SI 1 "general_operand" ""))]
5409  "TARGET_REALLY_IWMMXT"
5410{
5411})
5412
5413(define_expand "movv4hi"
5414  [(set (match_operand:V4HI 0 "nonimmediate_operand" "")
5415	(match_operand:V4HI 1 "general_operand" ""))]
5416  "TARGET_REALLY_IWMMXT"
5417{
5418})
5419
5420(define_expand "movv8qi"
5421  [(set (match_operand:V8QI 0 "nonimmediate_operand" "")
5422	(match_operand:V8QI 1 "general_operand" ""))]
5423  "TARGET_REALLY_IWMMXT"
5424{
5425})
5426
5427
5428;; load- and store-multiple insns
5429;; The arm can load/store any set of registers, provided that they are in
5430;; ascending order; but that is beyond GCC so stick with what it knows.
5431
5432(define_expand "load_multiple"
5433  [(match_par_dup 3 [(set (match_operand:SI 0 "" "")
5434                          (match_operand:SI 1 "" ""))
5435                     (use (match_operand:SI 2 "" ""))])]
5436  "TARGET_ARM"
5437{
5438  HOST_WIDE_INT offset = 0;
5439
5440  /* Support only fixed point registers.  */
5441  if (GET_CODE (operands[2]) != CONST_INT
5442      || INTVAL (operands[2]) > 14
5443      || INTVAL (operands[2]) < 2
5444      || GET_CODE (operands[1]) != MEM
5445      || GET_CODE (operands[0]) != REG
5446      || REGNO (operands[0]) > (LAST_ARM_REGNUM - 1)
5447      || REGNO (operands[0]) + INTVAL (operands[2]) > LAST_ARM_REGNUM)
5448    FAIL;
5449
5450  operands[3]
5451    = arm_gen_load_multiple (REGNO (operands[0]), INTVAL (operands[2]),
5452			     force_reg (SImode, XEXP (operands[1], 0)),
5453			     TRUE, FALSE, operands[1], &offset);
5454})
5455
5456;; Load multiple with write-back
5457
5458(define_insn "*ldmsi_postinc4"
5459  [(match_parallel 0 "load_multiple_operation"
5460    [(set (match_operand:SI 1 "s_register_operand" "=r")
5461	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5462		   (const_int 16)))
5463     (set (match_operand:SI 3 "arm_hard_register_operand" "")
5464	  (mem:SI (match_dup 2)))
5465     (set (match_operand:SI 4 "arm_hard_register_operand" "")
5466	  (mem:SI (plus:SI (match_dup 2) (const_int 4))))
5467     (set (match_operand:SI 5 "arm_hard_register_operand" "")
5468	  (mem:SI (plus:SI (match_dup 2) (const_int 8))))
5469     (set (match_operand:SI 6 "arm_hard_register_operand" "")
5470	  (mem:SI (plus:SI (match_dup 2) (const_int 12))))])]
5471  "TARGET_ARM && XVECLEN (operands[0], 0) == 5"
5472  "ldm%?ia\\t%1!, {%3, %4, %5, %6}"
5473  [(set_attr "type" "load4")
5474   (set_attr "predicable" "yes")]
5475)
5476
5477(define_insn "*ldmsi_postinc4_thumb"
5478  [(match_parallel 0 "load_multiple_operation"
5479    [(set (match_operand:SI 1 "s_register_operand" "=l")
5480	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5481		   (const_int 16)))
5482     (set (match_operand:SI 3 "arm_hard_register_operand" "")
5483	  (mem:SI (match_dup 2)))
5484     (set (match_operand:SI 4 "arm_hard_register_operand" "")
5485	  (mem:SI (plus:SI (match_dup 2) (const_int 4))))
5486     (set (match_operand:SI 5 "arm_hard_register_operand" "")
5487	  (mem:SI (plus:SI (match_dup 2) (const_int 8))))
5488     (set (match_operand:SI 6 "arm_hard_register_operand" "")
5489	  (mem:SI (plus:SI (match_dup 2) (const_int 12))))])]
5490  "TARGET_THUMB && XVECLEN (operands[0], 0) == 5"
5491  "ldmia\\t%1!, {%3, %4, %5, %6}"
5492  [(set_attr "type" "load4")]
5493)
5494
5495(define_insn "*ldmsi_postinc3"
5496  [(match_parallel 0 "load_multiple_operation"
5497    [(set (match_operand:SI 1 "s_register_operand" "=r")
5498	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5499		   (const_int 12)))
5500     (set (match_operand:SI 3 "arm_hard_register_operand" "")
5501	  (mem:SI (match_dup 2)))
5502     (set (match_operand:SI 4 "arm_hard_register_operand" "")
5503	  (mem:SI (plus:SI (match_dup 2) (const_int 4))))
5504     (set (match_operand:SI 5 "arm_hard_register_operand" "")
5505	  (mem:SI (plus:SI (match_dup 2) (const_int 8))))])]
5506  "TARGET_ARM && XVECLEN (operands[0], 0) == 4"
5507  "ldm%?ia\\t%1!, {%3, %4, %5}"
5508  [(set_attr "type" "load3")
5509   (set_attr "predicable" "yes")]
5510)
5511
5512(define_insn "*ldmsi_postinc2"
5513  [(match_parallel 0 "load_multiple_operation"
5514    [(set (match_operand:SI 1 "s_register_operand" "=r")
5515	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5516		   (const_int 8)))
5517     (set (match_operand:SI 3 "arm_hard_register_operand" "")
5518	  (mem:SI (match_dup 2)))
5519     (set (match_operand:SI 4 "arm_hard_register_operand" "")
5520	  (mem:SI (plus:SI (match_dup 2) (const_int 4))))])]
5521  "TARGET_ARM && XVECLEN (operands[0], 0) == 3"
5522  "ldm%?ia\\t%1!, {%3, %4}"
5523  [(set_attr "type" "load2")
5524   (set_attr "predicable" "yes")]
5525)
5526
5527;; Ordinary load multiple
5528
5529(define_insn "*ldmsi4"
5530  [(match_parallel 0 "load_multiple_operation"
5531    [(set (match_operand:SI 2 "arm_hard_register_operand" "")
5532	  (mem:SI (match_operand:SI 1 "s_register_operand" "r")))
5533     (set (match_operand:SI 3 "arm_hard_register_operand" "")
5534	  (mem:SI (plus:SI (match_dup 1) (const_int 4))))
5535     (set (match_operand:SI 4 "arm_hard_register_operand" "")
5536	  (mem:SI (plus:SI (match_dup 1) (const_int 8))))
5537     (set (match_operand:SI 5 "arm_hard_register_operand" "")
5538	  (mem:SI (plus:SI (match_dup 1) (const_int 12))))])]
5539  "TARGET_ARM && XVECLEN (operands[0], 0) == 4"
5540  "ldm%?ia\\t%1, {%2, %3, %4, %5}"
5541  [(set_attr "type" "load4")
5542   (set_attr "predicable" "yes")]
5543)
5544
5545(define_insn "*ldmsi3"
5546  [(match_parallel 0 "load_multiple_operation"
5547    [(set (match_operand:SI 2 "arm_hard_register_operand" "")
5548	  (mem:SI (match_operand:SI 1 "s_register_operand" "r")))
5549     (set (match_operand:SI 3 "arm_hard_register_operand" "")
5550	  (mem:SI (plus:SI (match_dup 1) (const_int 4))))
5551     (set (match_operand:SI 4 "arm_hard_register_operand" "")
5552	  (mem:SI (plus:SI (match_dup 1) (const_int 8))))])]
5553  "TARGET_ARM && XVECLEN (operands[0], 0) == 3"
5554  "ldm%?ia\\t%1, {%2, %3, %4}"
5555  [(set_attr "type" "load3")
5556   (set_attr "predicable" "yes")]
5557)
5558
5559(define_insn "*ldmsi2"
5560  [(match_parallel 0 "load_multiple_operation"
5561    [(set (match_operand:SI 2 "arm_hard_register_operand" "")
5562	  (mem:SI (match_operand:SI 1 "s_register_operand" "r")))
5563     (set (match_operand:SI 3 "arm_hard_register_operand" "")
5564	  (mem:SI (plus:SI (match_dup 1) (const_int 4))))])]
5565  "TARGET_ARM && XVECLEN (operands[0], 0) == 2"
5566  "ldm%?ia\\t%1, {%2, %3}"
5567  [(set_attr "type" "load2")
5568   (set_attr "predicable" "yes")]
5569)
5570
5571(define_expand "store_multiple"
5572  [(match_par_dup 3 [(set (match_operand:SI 0 "" "")
5573                          (match_operand:SI 1 "" ""))
5574                     (use (match_operand:SI 2 "" ""))])]
5575  "TARGET_ARM"
5576{
5577  HOST_WIDE_INT offset = 0;
5578
5579  /* Support only fixed point registers.  */
5580  if (GET_CODE (operands[2]) != CONST_INT
5581      || INTVAL (operands[2]) > 14
5582      || INTVAL (operands[2]) < 2
5583      || GET_CODE (operands[1]) != REG
5584      || GET_CODE (operands[0]) != MEM
5585      || REGNO (operands[1]) > (LAST_ARM_REGNUM - 1)
5586      || REGNO (operands[1]) + INTVAL (operands[2]) > LAST_ARM_REGNUM)
5587    FAIL;
5588
5589  operands[3]
5590    = arm_gen_store_multiple (REGNO (operands[1]), INTVAL (operands[2]),
5591			      force_reg (SImode, XEXP (operands[0], 0)),
5592			      TRUE, FALSE, operands[0], &offset);
5593})
5594
5595;; Store multiple with write-back
5596
5597(define_insn "*stmsi_postinc4"
5598  [(match_parallel 0 "store_multiple_operation"
5599    [(set (match_operand:SI 1 "s_register_operand" "=r")
5600	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5601		   (const_int 16)))
5602     (set (mem:SI (match_dup 2))
5603	  (match_operand:SI 3 "arm_hard_register_operand" ""))
5604     (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
5605	  (match_operand:SI 4 "arm_hard_register_operand" ""))
5606     (set (mem:SI (plus:SI (match_dup 2) (const_int 8)))
5607	  (match_operand:SI 5 "arm_hard_register_operand" ""))
5608     (set (mem:SI (plus:SI (match_dup 2) (const_int 12)))
5609	  (match_operand:SI 6 "arm_hard_register_operand" ""))])]
5610  "TARGET_ARM && XVECLEN (operands[0], 0) == 5"
5611  "stm%?ia\\t%1!, {%3, %4, %5, %6}"
5612  [(set_attr "predicable" "yes")
5613   (set_attr "type" "store4")]
5614)
5615
5616(define_insn "*stmsi_postinc4_thumb"
5617  [(match_parallel 0 "store_multiple_operation"
5618    [(set (match_operand:SI 1 "s_register_operand" "=l")
5619	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5620		   (const_int 16)))
5621     (set (mem:SI (match_dup 2))
5622	  (match_operand:SI 3 "arm_hard_register_operand" ""))
5623     (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
5624	  (match_operand:SI 4 "arm_hard_register_operand" ""))
5625     (set (mem:SI (plus:SI (match_dup 2) (const_int 8)))
5626	  (match_operand:SI 5 "arm_hard_register_operand" ""))
5627     (set (mem:SI (plus:SI (match_dup 2) (const_int 12)))
5628	  (match_operand:SI 6 "arm_hard_register_operand" ""))])]
5629  "TARGET_THUMB && XVECLEN (operands[0], 0) == 5"
5630  "stmia\\t%1!, {%3, %4, %5, %6}"
5631  [(set_attr "type" "store4")]
5632)
5633
5634(define_insn "*stmsi_postinc3"
5635  [(match_parallel 0 "store_multiple_operation"
5636    [(set (match_operand:SI 1 "s_register_operand" "=r")
5637	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5638		   (const_int 12)))
5639     (set (mem:SI (match_dup 2))
5640	  (match_operand:SI 3 "arm_hard_register_operand" ""))
5641     (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
5642	  (match_operand:SI 4 "arm_hard_register_operand" ""))
5643     (set (mem:SI (plus:SI (match_dup 2) (const_int 8)))
5644	  (match_operand:SI 5 "arm_hard_register_operand" ""))])]
5645  "TARGET_ARM && XVECLEN (operands[0], 0) == 4"
5646  "stm%?ia\\t%1!, {%3, %4, %5}"
5647  [(set_attr "predicable" "yes")
5648   (set_attr "type" "store3")]
5649)
5650
5651(define_insn "*stmsi_postinc2"
5652  [(match_parallel 0 "store_multiple_operation"
5653    [(set (match_operand:SI 1 "s_register_operand" "=r")
5654	  (plus:SI (match_operand:SI 2 "s_register_operand" "1")
5655		   (const_int 8)))
5656     (set (mem:SI (match_dup 2))
5657	  (match_operand:SI 3 "arm_hard_register_operand" ""))
5658     (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
5659	  (match_operand:SI 4 "arm_hard_register_operand" ""))])]
5660  "TARGET_ARM && XVECLEN (operands[0], 0) == 3"
5661  "stm%?ia\\t%1!, {%3, %4}"
5662  [(set_attr "predicable" "yes")
5663   (set_attr "type" "store2")]
5664)
5665
5666;; Ordinary store multiple
5667
5668(define_insn "*stmsi4"
5669  [(match_parallel 0 "store_multiple_operation"
5670    [(set (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
5671	  (match_operand:SI 2 "arm_hard_register_operand" ""))
5672     (set (mem:SI (plus:SI (match_dup 1) (const_int 4)))
5673	  (match_operand:SI 3 "arm_hard_register_operand" ""))
5674     (set (mem:SI (plus:SI (match_dup 1) (const_int 8)))
5675	  (match_operand:SI 4 "arm_hard_register_operand" ""))
5676     (set (mem:SI (plus:SI (match_dup 1) (const_int 12)))
5677	  (match_operand:SI 5 "arm_hard_register_operand" ""))])]
5678  "TARGET_ARM && XVECLEN (operands[0], 0) == 4"
5679  "stm%?ia\\t%1, {%2, %3, %4, %5}"
5680  [(set_attr "predicable" "yes")
5681   (set_attr "type" "store4")]
5682)
5683
5684(define_insn "*stmsi3"
5685  [(match_parallel 0 "store_multiple_operation"
5686    [(set (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
5687	  (match_operand:SI 2 "arm_hard_register_operand" ""))
5688     (set (mem:SI (plus:SI (match_dup 1) (const_int 4)))
5689	  (match_operand:SI 3 "arm_hard_register_operand" ""))
5690     (set (mem:SI (plus:SI (match_dup 1) (const_int 8)))
5691	  (match_operand:SI 4 "arm_hard_register_operand" ""))])]
5692  "TARGET_ARM && XVECLEN (operands[0], 0) == 3"
5693  "stm%?ia\\t%1, {%2, %3, %4}"
5694  [(set_attr "predicable" "yes")
5695   (set_attr "type" "store3")]
5696)
5697
5698(define_insn "*stmsi2"
5699  [(match_parallel 0 "store_multiple_operation"
5700    [(set (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
5701	  (match_operand:SI 2 "arm_hard_register_operand" ""))
5702     (set (mem:SI (plus:SI (match_dup 1) (const_int 4)))
5703	  (match_operand:SI 3 "arm_hard_register_operand" ""))])]
5704  "TARGET_ARM && XVECLEN (operands[0], 0) == 2"
5705  "stm%?ia\\t%1, {%2, %3}"
5706  [(set_attr "predicable" "yes")
5707   (set_attr "type" "store2")]
5708)
5709
5710;; Move a block of memory if it is word aligned and MORE than 2 words long.
5711;; We could let this apply for blocks of less than this, but it clobbers so
5712;; many registers that there is then probably a better way.
5713
5714(define_expand "movmemqi"
5715  [(match_operand:BLK 0 "general_operand" "")
5716   (match_operand:BLK 1 "general_operand" "")
5717   (match_operand:SI 2 "const_int_operand" "")
5718   (match_operand:SI 3 "const_int_operand" "")]
5719  "TARGET_EITHER"
5720  "
5721  if (TARGET_ARM)
5722    {
5723      if (arm_gen_movmemqi (operands))
5724        DONE;
5725      FAIL;
5726    }
5727  else /* TARGET_THUMB */
5728    {
5729      if (   INTVAL (operands[3]) != 4
5730          || INTVAL (operands[2]) > 48)
5731        FAIL;
5732
5733      thumb_expand_movmemqi (operands);
5734      DONE;
5735    }
5736  "
5737)
5738
5739;; Thumb block-move insns
5740
5741(define_insn "movmem12b"
5742  [(set (mem:SI (match_operand:SI 2 "register_operand" "0"))
5743	(mem:SI (match_operand:SI 3 "register_operand" "1")))
5744   (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
5745	(mem:SI (plus:SI (match_dup 3) (const_int 4))))
5746   (set (mem:SI (plus:SI (match_dup 2) (const_int 8)))
5747	(mem:SI (plus:SI (match_dup 3) (const_int 8))))
5748   (set (match_operand:SI 0 "register_operand" "=l")
5749	(plus:SI (match_dup 2) (const_int 12)))
5750   (set (match_operand:SI 1 "register_operand" "=l")
5751	(plus:SI (match_dup 3) (const_int 12)))
5752   (clobber (match_scratch:SI 4 "=&l"))
5753   (clobber (match_scratch:SI 5 "=&l"))
5754   (clobber (match_scratch:SI 6 "=&l"))]
5755  "TARGET_THUMB"
5756  "* return thumb_output_move_mem_multiple (3, operands);"
5757  [(set_attr "length" "4")
5758   ; This isn't entirely accurate...  It loads as well, but in terms of
5759   ; scheduling the following insn it is better to consider it as a store
5760   (set_attr "type" "store3")]
5761)
5762
5763(define_insn "movmem8b"
5764  [(set (mem:SI (match_operand:SI 2 "register_operand" "0"))
5765	(mem:SI (match_operand:SI 3 "register_operand" "1")))
5766   (set (mem:SI (plus:SI (match_dup 2) (const_int 4)))
5767	(mem:SI (plus:SI (match_dup 3) (const_int 4))))
5768   (set (match_operand:SI 0 "register_operand" "=l")
5769	(plus:SI (match_dup 2) (const_int 8)))
5770   (set (match_operand:SI 1 "register_operand" "=l")
5771	(plus:SI (match_dup 3) (const_int 8)))
5772   (clobber (match_scratch:SI 4 "=&l"))
5773   (clobber (match_scratch:SI 5 "=&l"))]
5774  "TARGET_THUMB"
5775  "* return thumb_output_move_mem_multiple (2, operands);"
5776  [(set_attr "length" "4")
5777   ; This isn't entirely accurate...  It loads as well, but in terms of
5778   ; scheduling the following insn it is better to consider it as a store
5779   (set_attr "type" "store2")]
5780)
5781
5782
5783
5784;; Compare & branch insns
5785;; The range calculations are based as follows:
5786;; For forward branches, the address calculation returns the address of
5787;; the next instruction.  This is 2 beyond the branch instruction.
5788;; For backward branches, the address calculation returns the address of
5789;; the first instruction in this pattern (cmp).  This is 2 before the branch
5790;; instruction for the shortest sequence, and 4 before the branch instruction
5791;; if we have to jump around an unconditional branch.
5792;; To the basic branch range the PC offset must be added (this is +4).
5793;; So for forward branches we have 
5794;;   (pos_range - pos_base_offs + pc_offs) = (pos_range - 2 + 4).
5795;; And for backward branches we have 
5796;;   (neg_range - neg_base_offs + pc_offs) = (neg_range - (-2 or -4) + 4).
5797;;
5798;; For a 'b'       pos_range = 2046, neg_range = -2048 giving (-2040->2048).
5799;; For a 'b<cond>' pos_range = 254,  neg_range = -256  giving (-250 ->256).
5800
5801(define_expand "cbranchsi4"
5802  [(set (pc) (if_then_else
5803	      (match_operator 0 "arm_comparison_operator"
5804	       [(match_operand:SI 1 "s_register_operand" "")
5805	        (match_operand:SI 2 "nonmemory_operand" "")])
5806	      (label_ref (match_operand 3 "" ""))
5807	      (pc)))]
5808  "TARGET_THUMB"
5809  "
5810  if (thumb_cmpneg_operand (operands[2], SImode))
5811    {
5812      emit_jump_insn (gen_cbranchsi4_scratch (NULL, operands[1], operands[2],
5813					      operands[3], operands[0]));
5814      DONE;
5815    }
5816  if (!thumb_cmp_operand (operands[2], SImode))
5817    operands[2] = force_reg (SImode, operands[2]);
5818  ")
5819
5820(define_insn "*cbranchsi4_insn"
5821  [(set (pc) (if_then_else
5822	      (match_operator 0 "arm_comparison_operator"
5823	       [(match_operand:SI 1 "s_register_operand" "l,*h")
5824	        (match_operand:SI 2 "thumb_cmp_operand" "lI*h,*r")])
5825	      (label_ref (match_operand 3 "" ""))
5826	      (pc)))]
5827  "TARGET_THUMB"
5828  "*
5829  output_asm_insn (\"cmp\\t%1, %2\", operands);
5830
5831  switch (get_attr_length (insn))
5832    {
5833    case 4:  return \"b%d0\\t%l3\";
5834    case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
5835    default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
5836    }
5837  "
5838  [(set (attr "far_jump")
5839        (if_then_else
5840	    (eq_attr "length" "8")
5841	    (const_string "yes")
5842            (const_string "no")))
5843   (set (attr "length") 
5844        (if_then_else
5845	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
5846	         (le (minus (match_dup 3) (pc)) (const_int 256)))
5847	    (const_int 4)
5848	    (if_then_else
5849	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
5850		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
5851		(const_int 6)
5852		(const_int 8))))]
5853)
5854
5855(define_insn "cbranchsi4_scratch"
5856  [(set (pc) (if_then_else
5857	      (match_operator 4 "arm_comparison_operator"
5858	       [(match_operand:SI 1 "s_register_operand" "l,0")
5859	        (match_operand:SI 2 "thumb_cmpneg_operand" "L,J")])
5860	      (label_ref (match_operand 3 "" ""))
5861	      (pc)))
5862   (clobber (match_scratch:SI 0 "=l,l"))]
5863  "TARGET_THUMB"
5864  "*
5865  output_asm_insn (\"add\\t%0, %1, #%n2\", operands);
5866
5867  switch (get_attr_length (insn))
5868    {
5869    case 4:  return \"b%d4\\t%l3\";
5870    case 6:  return \"b%D4\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
5871    default: return \"b%D4\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
5872    }
5873  "
5874  [(set (attr "far_jump")
5875        (if_then_else
5876	    (eq_attr "length" "8")
5877	    (const_string "yes")
5878            (const_string "no")))
5879   (set (attr "length") 
5880        (if_then_else
5881	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
5882	         (le (minus (match_dup 3) (pc)) (const_int 256)))
5883	    (const_int 4)
5884	    (if_then_else
5885	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
5886		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
5887		(const_int 6)
5888		(const_int 8))))]
5889)
5890(define_insn "*movsi_cbranchsi4"
5891  [(set (pc)
5892	(if_then_else
5893	 (match_operator 3 "arm_comparison_operator"
5894	  [(match_operand:SI 1 "s_register_operand" "0,l,l,l")
5895	   (const_int 0)])
5896	 (label_ref (match_operand 2 "" ""))
5897	 (pc)))
5898   (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,l,*h,*m")
5899	(match_dup 1))]
5900  "TARGET_THUMB"
5901  "*{
5902  if (which_alternative == 0)
5903    output_asm_insn (\"cmp\t%0, #0\", operands);
5904  else if (which_alternative == 1)
5905    output_asm_insn (\"sub\t%0, %1, #0\", operands);
5906  else
5907    {
5908      output_asm_insn (\"cmp\t%1, #0\", operands);
5909      if (which_alternative == 2)
5910	output_asm_insn (\"mov\t%0, %1\", operands);
5911      else
5912	output_asm_insn (\"str\t%1, %0\", operands);
5913    }
5914  switch (get_attr_length (insn) - ((which_alternative > 1) ? 2 : 0))
5915    {
5916    case 4:  return \"b%d3\\t%l2\";
5917    case 6:  return \"b%D3\\t.LCB%=\;b\\t%l2\\t%@long jump\\n.LCB%=:\";
5918    default: return \"b%D3\\t.LCB%=\;bl\\t%l2\\t%@far jump\\n.LCB%=:\";
5919    }
5920  }"
5921  [(set (attr "far_jump")
5922        (if_then_else
5923	    (ior (and (gt (symbol_ref ("which_alternative"))
5924	                  (const_int 1))
5925		      (eq_attr "length" "8"))
5926		 (eq_attr "length" "10"))
5927	    (const_string "yes")
5928            (const_string "no")))
5929   (set (attr "length")
5930     (if_then_else
5931       (le (symbol_ref ("which_alternative"))
5932		       (const_int 1))
5933       (if_then_else
5934	 (and (ge (minus (match_dup 2) (pc)) (const_int -250))
5935	      (le (minus (match_dup 2) (pc)) (const_int 256)))
5936	 (const_int 4)
5937	 (if_then_else
5938	   (and (ge (minus (match_dup 2) (pc)) (const_int -2040))
5939		(le (minus (match_dup 2) (pc)) (const_int 2048)))
5940	   (const_int 6)
5941	   (const_int 8)))
5942       (if_then_else
5943	 (and (ge (minus (match_dup 2) (pc)) (const_int -248))
5944	      (le (minus (match_dup 2) (pc)) (const_int 256)))
5945	 (const_int 6)
5946	 (if_then_else
5947	   (and (ge (minus (match_dup 2) (pc)) (const_int -2038))
5948		(le (minus (match_dup 2) (pc)) (const_int 2048)))
5949	   (const_int 8)
5950	   (const_int 10)))))]
5951)
5952
5953(define_insn "*negated_cbranchsi4"
5954  [(set (pc)
5955	(if_then_else
5956	 (match_operator 0 "equality_operator"
5957	  [(match_operand:SI 1 "s_register_operand" "l")
5958	   (neg:SI (match_operand:SI 2 "s_register_operand" "l"))])
5959	 (label_ref (match_operand 3 "" ""))
5960	 (pc)))]
5961  "TARGET_THUMB"
5962  "*
5963  output_asm_insn (\"cmn\\t%1, %2\", operands);
5964  switch (get_attr_length (insn))
5965    {
5966    case 4:  return \"b%d0\\t%l3\";
5967    case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
5968    default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
5969    }
5970  "
5971  [(set (attr "far_jump")
5972        (if_then_else
5973	    (eq_attr "length" "8")
5974	    (const_string "yes")
5975            (const_string "no")))
5976   (set (attr "length") 
5977        (if_then_else
5978	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
5979	         (le (minus (match_dup 3) (pc)) (const_int 256)))
5980	    (const_int 4)
5981	    (if_then_else
5982	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
5983		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
5984		(const_int 6)
5985		(const_int 8))))]
5986)
5987
5988(define_insn "*tbit_cbranch"
5989  [(set (pc)
5990	(if_then_else
5991	 (match_operator 0 "equality_operator"
5992	  [(zero_extract:SI (match_operand:SI 1 "s_register_operand" "l")
5993			    (const_int 1)
5994			    (match_operand:SI 2 "const_int_operand" "i"))
5995	   (const_int 0)])
5996	 (label_ref (match_operand 3 "" ""))
5997	 (pc)))
5998   (clobber (match_scratch:SI 4 "=l"))]
5999  "TARGET_THUMB"
6000  "*
6001  {
6002  rtx op[3];
6003  op[0] = operands[4];
6004  op[1] = operands[1];
6005  op[2] = GEN_INT (32 - 1 - INTVAL (operands[2]));
6006
6007  output_asm_insn (\"lsl\\t%0, %1, %2\", op);
6008  switch (get_attr_length (insn))
6009    {
6010    case 4:  return \"b%d0\\t%l3\";
6011    case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
6012    default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
6013    }
6014  }"
6015  [(set (attr "far_jump")
6016        (if_then_else
6017	    (eq_attr "length" "8")
6018	    (const_string "yes")
6019            (const_string "no")))
6020   (set (attr "length") 
6021        (if_then_else
6022	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
6023	         (le (minus (match_dup 3) (pc)) (const_int 256)))
6024	    (const_int 4)
6025	    (if_then_else
6026	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
6027		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
6028		(const_int 6)
6029		(const_int 8))))]
6030)
6031  
6032(define_insn "*tlobits_cbranch"
6033  [(set (pc)
6034	(if_then_else
6035	 (match_operator 0 "equality_operator"
6036	  [(zero_extract:SI (match_operand:SI 1 "s_register_operand" "l")
6037			    (match_operand:SI 2 "const_int_operand" "i")
6038			    (const_int 0))
6039	   (const_int 0)])
6040	 (label_ref (match_operand 3 "" ""))
6041	 (pc)))
6042   (clobber (match_scratch:SI 4 "=l"))]
6043  "TARGET_THUMB"
6044  "*
6045  {
6046  rtx op[3];
6047  op[0] = operands[4];
6048  op[1] = operands[1];
6049  op[2] = GEN_INT (32 - INTVAL (operands[2]));
6050
6051  output_asm_insn (\"lsl\\t%0, %1, %2\", op);
6052  switch (get_attr_length (insn))
6053    {
6054    case 4:  return \"b%d0\\t%l3\";
6055    case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
6056    default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
6057    }
6058  }"
6059  [(set (attr "far_jump")
6060        (if_then_else
6061	    (eq_attr "length" "8")
6062	    (const_string "yes")
6063            (const_string "no")))
6064   (set (attr "length") 
6065        (if_then_else
6066	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
6067	         (le (minus (match_dup 3) (pc)) (const_int 256)))
6068	    (const_int 4)
6069	    (if_then_else
6070	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
6071		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
6072		(const_int 6)
6073		(const_int 8))))]
6074)
6075  
6076(define_insn "*tstsi3_cbranch"
6077  [(set (pc)
6078	(if_then_else
6079	 (match_operator 3 "equality_operator"
6080	  [(and:SI (match_operand:SI 0 "s_register_operand" "%l")
6081		   (match_operand:SI 1 "s_register_operand" "l"))
6082	   (const_int 0)])
6083	 (label_ref (match_operand 2 "" ""))
6084	 (pc)))]
6085  "TARGET_THUMB"
6086  "*
6087  {
6088  output_asm_insn (\"tst\\t%0, %1\", operands);
6089  switch (get_attr_length (insn))
6090    {
6091    case 4:  return \"b%d3\\t%l2\";
6092    case 6:  return \"b%D3\\t.LCB%=\;b\\t%l2\\t%@long jump\\n.LCB%=:\";
6093    default: return \"b%D3\\t.LCB%=\;bl\\t%l2\\t%@far jump\\n.LCB%=:\";
6094    }
6095  }"
6096  [(set (attr "far_jump")
6097        (if_then_else
6098	    (eq_attr "length" "8")
6099	    (const_string "yes")
6100            (const_string "no")))
6101   (set (attr "length") 
6102        (if_then_else
6103	    (and (ge (minus (match_dup 2) (pc)) (const_int -250))
6104	         (le (minus (match_dup 2) (pc)) (const_int 256)))
6105	    (const_int 4)
6106	    (if_then_else
6107	        (and (ge (minus (match_dup 2) (pc)) (const_int -2040))
6108		     (le (minus (match_dup 2) (pc)) (const_int 2048)))
6109		(const_int 6)
6110		(const_int 8))))]
6111)
6112  
6113(define_insn "*andsi3_cbranch"
6114  [(set (pc)
6115	(if_then_else
6116	 (match_operator 5 "equality_operator"
6117	  [(and:SI (match_operand:SI 2 "s_register_operand" "%0,1,1,1")
6118		   (match_operand:SI 3 "s_register_operand" "l,l,l,l"))
6119	   (const_int 0)])
6120	 (label_ref (match_operand 4 "" ""))
6121	 (pc)))
6122   (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,*?h,*?m,*?m")
6123	(and:SI (match_dup 2) (match_dup 3)))
6124   (clobber (match_scratch:SI 1 "=X,l,&l,&l"))]
6125  "TARGET_THUMB"
6126  "*
6127  {
6128  if (which_alternative == 0)
6129    output_asm_insn (\"and\\t%0, %3\", operands);
6130  else if (which_alternative == 1)
6131    {
6132      output_asm_insn (\"and\\t%1, %3\", operands);
6133      output_asm_insn (\"mov\\t%0, %1\", operands);
6134    }
6135  else
6136    {
6137      output_asm_insn (\"and\\t%1, %3\", operands);
6138      output_asm_insn (\"str\\t%1, %0\", operands);
6139    }
6140
6141  switch (get_attr_length (insn) - (which_alternative ? 2 : 0))
6142    {
6143    case 4:  return \"b%d5\\t%l4\";
6144    case 6:  return \"b%D5\\t.LCB%=\;b\\t%l4\\t%@long jump\\n.LCB%=:\";
6145    default: return \"b%D5\\t.LCB%=\;bl\\t%l4\\t%@far jump\\n.LCB%=:\";
6146    }
6147  }"
6148  [(set (attr "far_jump")
6149        (if_then_else
6150	    (ior (and (eq (symbol_ref ("which_alternative"))
6151	                  (const_int 0))
6152		      (eq_attr "length" "8"))
6153		 (eq_attr "length" "10"))
6154	    (const_string "yes")
6155            (const_string "no")))
6156   (set (attr "length")
6157     (if_then_else
6158       (eq (symbol_ref ("which_alternative"))
6159		       (const_int 0))
6160       (if_then_else
6161	 (and (ge (minus (match_dup 4) (pc)) (const_int -250))
6162	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6163	 (const_int 4)
6164	 (if_then_else
6165	   (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
6166		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6167	   (const_int 6)
6168	   (const_int 8)))
6169       (if_then_else
6170	 (and (ge (minus (match_dup 4) (pc)) (const_int -248))
6171	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6172	 (const_int 6)
6173	 (if_then_else
6174	   (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
6175		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6176	   (const_int 8)
6177	   (const_int 10)))))]
6178)
6179
6180(define_insn "*orrsi3_cbranch_scratch"
6181  [(set (pc)
6182	(if_then_else
6183	 (match_operator 4 "equality_operator"
6184	  [(ior:SI (match_operand:SI 1 "s_register_operand" "%0")
6185		   (match_operand:SI 2 "s_register_operand" "l"))
6186	   (const_int 0)])
6187	 (label_ref (match_operand 3 "" ""))
6188	 (pc)))
6189   (clobber (match_scratch:SI 0 "=l"))]
6190  "TARGET_THUMB"
6191  "*
6192  {
6193  output_asm_insn (\"orr\\t%0, %2\", operands);
6194  switch (get_attr_length (insn))
6195    {
6196    case 4:  return \"b%d4\\t%l3\";
6197    case 6:  return \"b%D4\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
6198    default: return \"b%D4\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
6199    }
6200  }"
6201  [(set (attr "far_jump")
6202        (if_then_else
6203	    (eq_attr "length" "8")
6204	    (const_string "yes")
6205            (const_string "no")))
6206   (set (attr "length") 
6207        (if_then_else
6208	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
6209	         (le (minus (match_dup 3) (pc)) (const_int 256)))
6210	    (const_int 4)
6211	    (if_then_else
6212	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
6213		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
6214		(const_int 6)
6215		(const_int 8))))]
6216)
6217  
6218(define_insn "*orrsi3_cbranch"
6219  [(set (pc)
6220	(if_then_else
6221	 (match_operator 5 "equality_operator"
6222	  [(ior:SI (match_operand:SI 2 "s_register_operand" "%0,1,1,1")
6223		   (match_operand:SI 3 "s_register_operand" "l,l,l,l"))
6224	   (const_int 0)])
6225	 (label_ref (match_operand 4 "" ""))
6226	 (pc)))
6227   (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,*?h,*?m,*?m")
6228	(ior:SI (match_dup 2) (match_dup 3)))
6229   (clobber (match_scratch:SI 1 "=X,l,&l,&l"))]
6230  "TARGET_THUMB"
6231  "*
6232  {
6233  if (which_alternative == 0)
6234    output_asm_insn (\"orr\\t%0, %3\", operands);
6235  else if (which_alternative == 1)
6236    {
6237      output_asm_insn (\"orr\\t%1, %3\", operands);
6238      output_asm_insn (\"mov\\t%0, %1\", operands);
6239    }
6240  else
6241    {
6242      output_asm_insn (\"orr\\t%1, %3\", operands);
6243      output_asm_insn (\"str\\t%1, %0\", operands);
6244    }
6245
6246  switch (get_attr_length (insn) - (which_alternative ? 2 : 0))
6247    {
6248    case 4:  return \"b%d5\\t%l4\";
6249    case 6:  return \"b%D5\\t.LCB%=\;b\\t%l4\\t%@long jump\\n.LCB%=:\";
6250    default: return \"b%D5\\t.LCB%=\;bl\\t%l4\\t%@far jump\\n.LCB%=:\";
6251    }
6252  }"
6253  [(set (attr "far_jump")
6254        (if_then_else
6255	    (ior (and (eq (symbol_ref ("which_alternative"))
6256	                  (const_int 0))
6257		      (eq_attr "length" "8"))
6258		 (eq_attr "length" "10"))
6259	    (const_string "yes")
6260            (const_string "no")))
6261   (set (attr "length")
6262     (if_then_else
6263       (eq (symbol_ref ("which_alternative"))
6264		       (const_int 0))
6265       (if_then_else
6266	 (and (ge (minus (match_dup 4) (pc)) (const_int -250))
6267	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6268	 (const_int 4)
6269	 (if_then_else
6270	   (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
6271		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6272	   (const_int 6)
6273	   (const_int 8)))
6274       (if_then_else
6275	 (and (ge (minus (match_dup 4) (pc)) (const_int -248))
6276	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6277	 (const_int 6)
6278	 (if_then_else
6279	   (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
6280		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6281	   (const_int 8)
6282	   (const_int 10)))))]
6283)
6284
6285(define_insn "*xorsi3_cbranch_scratch"
6286  [(set (pc)
6287	(if_then_else
6288	 (match_operator 4 "equality_operator"
6289	  [(xor:SI (match_operand:SI 1 "s_register_operand" "%0")
6290		   (match_operand:SI 2 "s_register_operand" "l"))
6291	   (const_int 0)])
6292	 (label_ref (match_operand 3 "" ""))
6293	 (pc)))
6294   (clobber (match_scratch:SI 0 "=l"))]
6295  "TARGET_THUMB"
6296  "*
6297  {
6298  output_asm_insn (\"eor\\t%0, %2\", operands);
6299  switch (get_attr_length (insn))
6300    {
6301    case 4:  return \"b%d4\\t%l3\";
6302    case 6:  return \"b%D4\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
6303    default: return \"b%D4\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
6304    }
6305  }"
6306  [(set (attr "far_jump")
6307        (if_then_else
6308	    (eq_attr "length" "8")
6309	    (const_string "yes")
6310            (const_string "no")))
6311   (set (attr "length") 
6312        (if_then_else
6313	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
6314	         (le (minus (match_dup 3) (pc)) (const_int 256)))
6315	    (const_int 4)
6316	    (if_then_else
6317	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
6318		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
6319		(const_int 6)
6320		(const_int 8))))]
6321)
6322  
6323(define_insn "*xorsi3_cbranch"
6324  [(set (pc)
6325	(if_then_else
6326	 (match_operator 5 "equality_operator"
6327	  [(xor:SI (match_operand:SI 2 "s_register_operand" "%0,1,1,1")
6328		   (match_operand:SI 3 "s_register_operand" "l,l,l,l"))
6329	   (const_int 0)])
6330	 (label_ref (match_operand 4 "" ""))
6331	 (pc)))
6332   (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,*?h,*?m,*?m")
6333	(xor:SI (match_dup 2) (match_dup 3)))
6334   (clobber (match_scratch:SI 1 "=X,l,&l,&l"))]
6335  "TARGET_THUMB"
6336  "*
6337  {
6338  if (which_alternative == 0)
6339    output_asm_insn (\"eor\\t%0, %3\", operands);
6340  else if (which_alternative == 1)
6341    {
6342      output_asm_insn (\"eor\\t%1, %3\", operands);
6343      output_asm_insn (\"mov\\t%0, %1\", operands);
6344    }
6345  else
6346    {
6347      output_asm_insn (\"eor\\t%1, %3\", operands);
6348      output_asm_insn (\"str\\t%1, %0\", operands);
6349    }
6350
6351  switch (get_attr_length (insn) - (which_alternative ? 2 : 0))
6352    {
6353    case 4:  return \"b%d5\\t%l4\";
6354    case 6:  return \"b%D5\\t.LCB%=\;b\\t%l4\\t%@long jump\\n.LCB%=:\";
6355    default: return \"b%D5\\t.LCB%=\;bl\\t%l4\\t%@far jump\\n.LCB%=:\";
6356    }
6357  }"
6358  [(set (attr "far_jump")
6359        (if_then_else
6360	    (ior (and (eq (symbol_ref ("which_alternative"))
6361	                  (const_int 0))
6362		      (eq_attr "length" "8"))
6363		 (eq_attr "length" "10"))
6364	    (const_string "yes")
6365            (const_string "no")))
6366   (set (attr "length")
6367     (if_then_else
6368       (eq (symbol_ref ("which_alternative"))
6369		       (const_int 0))
6370       (if_then_else
6371	 (and (ge (minus (match_dup 4) (pc)) (const_int -250))
6372	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6373	 (const_int 4)
6374	 (if_then_else
6375	   (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
6376		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6377	   (const_int 6)
6378	   (const_int 8)))
6379       (if_then_else
6380	 (and (ge (minus (match_dup 4) (pc)) (const_int -248))
6381	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6382	 (const_int 6)
6383	 (if_then_else
6384	   (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
6385		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6386	   (const_int 8)
6387	   (const_int 10)))))]
6388)
6389
6390(define_insn "*bicsi3_cbranch_scratch"
6391  [(set (pc)
6392	(if_then_else
6393	 (match_operator 4 "equality_operator"
6394	  [(and:SI (not:SI (match_operand:SI 2 "s_register_operand" "l"))
6395		   (match_operand:SI 1 "s_register_operand" "0"))
6396	   (const_int 0)])
6397	 (label_ref (match_operand 3 "" ""))
6398	 (pc)))
6399   (clobber (match_scratch:SI 0 "=l"))]
6400  "TARGET_THUMB"
6401  "*
6402  {
6403  output_asm_insn (\"bic\\t%0, %2\", operands);
6404  switch (get_attr_length (insn))
6405    {
6406    case 4:  return \"b%d4\\t%l3\";
6407    case 6:  return \"b%D4\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
6408    default: return \"b%D4\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
6409    }
6410  }"
6411  [(set (attr "far_jump")
6412        (if_then_else
6413	    (eq_attr "length" "8")
6414	    (const_string "yes")
6415            (const_string "no")))
6416   (set (attr "length") 
6417        (if_then_else
6418	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
6419	         (le (minus (match_dup 3) (pc)) (const_int 256)))
6420	    (const_int 4)
6421	    (if_then_else
6422	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
6423		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
6424		(const_int 6)
6425		(const_int 8))))]
6426)
6427  
6428(define_insn "*bicsi3_cbranch"
6429  [(set (pc)
6430	(if_then_else
6431	 (match_operator 5 "equality_operator"
6432	  [(and:SI (not:SI (match_operand:SI 3 "s_register_operand" "l,l,l,l,l"))
6433		   (match_operand:SI 2 "s_register_operand" "0,1,1,1,1"))
6434	   (const_int 0)])
6435	 (label_ref (match_operand 4 "" ""))
6436	 (pc)))
6437   (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=!l,l,*?h,*?m,*?m")
6438	(and:SI (not:SI (match_dup 3)) (match_dup 2)))
6439   (clobber (match_scratch:SI 1 "=X,l,l,&l,&l"))]
6440  "TARGET_THUMB"
6441  "*
6442  {
6443  if (which_alternative == 0)
6444    output_asm_insn (\"bic\\t%0, %3\", operands);
6445  else if (which_alternative <= 2)
6446    {
6447      output_asm_insn (\"bic\\t%1, %3\", operands);
6448      /* It's ok if OP0 is a lo-reg, even though the mov will set the
6449	 conditions again, since we're only testing for equality.  */
6450      output_asm_insn (\"mov\\t%0, %1\", operands);
6451    }
6452  else
6453    {
6454      output_asm_insn (\"bic\\t%1, %3\", operands);
6455      output_asm_insn (\"str\\t%1, %0\", operands);
6456    }
6457
6458  switch (get_attr_length (insn) - (which_alternative ? 2 : 0))
6459    {
6460    case 4:  return \"b%d5\\t%l4\";
6461    case 6:  return \"b%D5\\t.LCB%=\;b\\t%l4\\t%@long jump\\n.LCB%=:\";
6462    default: return \"b%D5\\t.LCB%=\;bl\\t%l4\\t%@far jump\\n.LCB%=:\";
6463    }
6464  }"
6465  [(set (attr "far_jump")
6466        (if_then_else
6467	    (ior (and (eq (symbol_ref ("which_alternative"))
6468	                  (const_int 0))
6469		      (eq_attr "length" "8"))
6470		 (eq_attr "length" "10"))
6471	    (const_string "yes")
6472            (const_string "no")))
6473   (set (attr "length")
6474     (if_then_else
6475       (eq (symbol_ref ("which_alternative"))
6476		       (const_int 0))
6477       (if_then_else
6478	 (and (ge (minus (match_dup 4) (pc)) (const_int -250))
6479	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6480	 (const_int 4)
6481	 (if_then_else
6482	   (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
6483		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6484	   (const_int 6)
6485	   (const_int 8)))
6486       (if_then_else
6487	 (and (ge (minus (match_dup 4) (pc)) (const_int -248))
6488	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6489	 (const_int 6)
6490	 (if_then_else
6491	   (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
6492		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6493	   (const_int 8)
6494	   (const_int 10)))))]
6495)
6496
6497(define_insn "*cbranchne_decr1"
6498  [(set (pc)
6499	(if_then_else (match_operator 3 "equality_operator"
6500		       [(match_operand:SI 2 "s_register_operand" "l,l,1,l")
6501		        (const_int 0)])
6502		      (label_ref (match_operand 4 "" ""))
6503		      (pc)))
6504   (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,*?h,*?m,*?m")
6505	(plus:SI (match_dup 2) (const_int -1)))
6506   (clobber (match_scratch:SI 1 "=X,l,&l,&l"))]
6507  "TARGET_THUMB"
6508  "*
6509   {
6510     rtx cond[2];
6511     cond[0] = gen_rtx_fmt_ee ((GET_CODE (operands[3]) == NE
6512				? GEU : LTU),
6513			       VOIDmode, operands[2], const1_rtx);
6514     cond[1] = operands[4];
6515
6516     if (which_alternative == 0)
6517       output_asm_insn (\"sub\\t%0, %2, #1\", operands);
6518     else if (which_alternative == 1)
6519       {
6520	 /* We must provide an alternative for a hi reg because reload 
6521	    cannot handle output reloads on a jump instruction, but we
6522	    can't subtract into that.  Fortunately a mov from lo to hi
6523	    does not clobber the condition codes.  */
6524	 output_asm_insn (\"sub\\t%1, %2, #1\", operands);
6525	 output_asm_insn (\"mov\\t%0, %1\", operands);
6526       }
6527     else
6528       {
6529	 /* Similarly, but the target is memory.  */
6530	 output_asm_insn (\"sub\\t%1, %2, #1\", operands);
6531	 output_asm_insn (\"str\\t%1, %0\", operands);
6532       }
6533
6534     switch (get_attr_length (insn) - (which_alternative ? 2 : 0))
6535       {
6536	 case 4:
6537	   output_asm_insn (\"b%d0\\t%l1\", cond);
6538	   return \"\";
6539	 case 6:
6540	   output_asm_insn (\"b%D0\\t.LCB%=\", cond);
6541	   return \"b\\t%l4\\t%@long jump\\n.LCB%=:\";
6542	 default:
6543	   output_asm_insn (\"b%D0\\t.LCB%=\", cond);
6544	   return \"bl\\t%l4\\t%@far jump\\n.LCB%=:\";
6545       }
6546   }
6547  "
6548  [(set (attr "far_jump")
6549        (if_then_else
6550	    (ior (and (eq (symbol_ref ("which_alternative"))
6551	                  (const_int 0))
6552		      (eq_attr "length" "8"))
6553		 (eq_attr "length" "10"))
6554	    (const_string "yes")
6555            (const_string "no")))
6556   (set_attr_alternative "length"
6557      [
6558       ;; Alternative 0
6559       (if_then_else
6560	 (and (ge (minus (match_dup 4) (pc)) (const_int -250))
6561	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6562	 (const_int 4)
6563	 (if_then_else
6564	   (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
6565		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6566	   (const_int 6)
6567	   (const_int 8)))
6568       ;; Alternative 1
6569       (if_then_else
6570	 (and (ge (minus (match_dup 4) (pc)) (const_int -248))
6571	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6572	 (const_int 6)
6573	 (if_then_else
6574	   (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
6575		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6576	   (const_int 8)
6577	   (const_int 10)))
6578       ;; Alternative 2
6579       (if_then_else
6580	 (and (ge (minus (match_dup 4) (pc)) (const_int -248))
6581	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6582	 (const_int 6)
6583	 (if_then_else
6584	   (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
6585		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6586	   (const_int 8)
6587	   (const_int 10)))
6588       ;; Alternative 3
6589       (if_then_else
6590	 (and (ge (minus (match_dup 4) (pc)) (const_int -248))
6591	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6592	 (const_int 6)
6593	 (if_then_else
6594	   (and (ge (minus (match_dup 4) (pc)) (const_int -2038))
6595		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6596	   (const_int 8)
6597	   (const_int 10)))])]
6598)
6599
6600(define_insn "*addsi3_cbranch"
6601  [(set (pc)
6602	(if_then_else
6603	 (match_operator 4 "comparison_operator"
6604	  [(plus:SI
6605	    (match_operand:SI 2 "s_register_operand" "%l,0,*0,1,1,1")
6606	    (match_operand:SI 3 "reg_or_int_operand" "lL,IJ,*r,lIJ,lIJ,lIJ"))
6607	   (const_int 0)])
6608	 (label_ref (match_operand 5 "" ""))
6609	 (pc)))
6610   (set
6611    (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,l,*!h,*?h,*?m,*?m")
6612    (plus:SI (match_dup 2) (match_dup 3)))
6613   (clobber (match_scratch:SI 1 "=X,X,X,l,&l,&l"))]
6614  "TARGET_THUMB
6615   && (GET_CODE (operands[4]) == EQ
6616       || GET_CODE (operands[4]) == NE
6617       || GET_CODE (operands[4]) == GE
6618       || GET_CODE (operands[4]) == LT)"
6619  "*
6620   {
6621     rtx cond[3];
6622
6623     
6624     cond[0] = (which_alternative < 3) ? operands[0] : operands[1];
6625     cond[1] = operands[2];
6626     cond[2] = operands[3];
6627
6628     if (GET_CODE (cond[2]) == CONST_INT && INTVAL (cond[2]) < 0)
6629       output_asm_insn (\"sub\\t%0, %1, #%n2\", cond);
6630     else
6631       output_asm_insn (\"add\\t%0, %1, %2\", cond);
6632
6633     if (which_alternative >= 3
6634	 && which_alternative < 4)
6635       output_asm_insn (\"mov\\t%0, %1\", operands);
6636     else if (which_alternative >= 4)
6637       output_asm_insn (\"str\\t%1, %0\", operands);
6638
6639     switch (get_attr_length (insn) - ((which_alternative >= 3) ? 2 : 0))
6640       {
6641	 case 4:
6642	   return \"b%d4\\t%l5\";
6643	 case 6:
6644	   return \"b%D4\\t.LCB%=\;b\\t%l5\\t%@long jump\\n.LCB%=:\";
6645	 default:
6646	   return \"b%D4\\t.LCB%=\;bl\\t%l5\\t%@far jump\\n.LCB%=:\";
6647       }
6648   }
6649  "
6650  [(set (attr "far_jump")
6651        (if_then_else
6652	    (ior (and (lt (symbol_ref ("which_alternative"))
6653	                  (const_int 3))
6654		      (eq_attr "length" "8"))
6655		 (eq_attr "length" "10"))
6656	    (const_string "yes")
6657            (const_string "no")))
6658   (set (attr "length")
6659     (if_then_else
6660       (lt (symbol_ref ("which_alternative"))
6661		       (const_int 3))
6662       (if_then_else
6663	 (and (ge (minus (match_dup 5) (pc)) (const_int -250))
6664	      (le (minus (match_dup 5) (pc)) (const_int 256)))
6665	 (const_int 4)
6666	 (if_then_else
6667	   (and (ge (minus (match_dup 5) (pc)) (const_int -2040))
6668		(le (minus (match_dup 5) (pc)) (const_int 2048)))
6669	   (const_int 6)
6670	   (const_int 8)))
6671       (if_then_else
6672	 (and (ge (minus (match_dup 5) (pc)) (const_int -248))
6673	      (le (minus (match_dup 5) (pc)) (const_int 256)))
6674	 (const_int 6)
6675	 (if_then_else
6676	   (and (ge (minus (match_dup 5) (pc)) (const_int -2038))
6677		(le (minus (match_dup 5) (pc)) (const_int 2048)))
6678	   (const_int 8)
6679	   (const_int 10)))))]
6680)
6681
6682(define_insn "*addsi3_cbranch_scratch"
6683  [(set (pc)
6684	(if_then_else
6685	 (match_operator 3 "comparison_operator"
6686	  [(plus:SI
6687	    (match_operand:SI 1 "s_register_operand" "%l,l,l,0")
6688	    (match_operand:SI 2 "reg_or_int_operand" "J,l,L,IJ"))
6689	   (const_int 0)])
6690	 (label_ref (match_operand 4 "" ""))
6691	 (pc)))
6692   (clobber (match_scratch:SI 0 "=X,X,l,l"))]
6693  "TARGET_THUMB
6694   && (GET_CODE (operands[3]) == EQ
6695       || GET_CODE (operands[3]) == NE
6696       || GET_CODE (operands[3]) == GE
6697       || GET_CODE (operands[3]) == LT)"
6698  "*
6699   {
6700     switch (which_alternative)
6701       {
6702       case 0:
6703	 output_asm_insn (\"cmp\t%1, #%n2\", operands);
6704	 break;
6705       case 1:
6706	 output_asm_insn (\"cmn\t%1, %2\", operands);
6707	 break;
6708       case 2:
6709	 if (INTVAL (operands[2]) < 0)
6710	   output_asm_insn (\"sub\t%0, %1, %2\", operands);
6711	 else
6712	   output_asm_insn (\"add\t%0, %1, %2\", operands);
6713	 break;
6714       case 3:
6715	 if (INTVAL (operands[2]) < 0)
6716	   output_asm_insn (\"sub\t%0, %0, %2\", operands);
6717	 else
6718	   output_asm_insn (\"add\t%0, %0, %2\", operands);
6719	 break;
6720       }
6721
6722     switch (get_attr_length (insn))
6723       {
6724	 case 4:
6725	   return \"b%d3\\t%l4\";
6726	 case 6:
6727	   return \"b%D3\\t.LCB%=\;b\\t%l4\\t%@long jump\\n.LCB%=:\";
6728	 default:
6729	   return \"b%D3\\t.LCB%=\;bl\\t%l4\\t%@far jump\\n.LCB%=:\";
6730       }
6731   }
6732  "
6733  [(set (attr "far_jump")
6734        (if_then_else
6735	    (eq_attr "length" "8")
6736	    (const_string "yes")
6737            (const_string "no")))
6738   (set (attr "length")
6739       (if_then_else
6740	 (and (ge (minus (match_dup 4) (pc)) (const_int -250))
6741	      (le (minus (match_dup 4) (pc)) (const_int 256)))
6742	 (const_int 4)
6743	 (if_then_else
6744	   (and (ge (minus (match_dup 4) (pc)) (const_int -2040))
6745		(le (minus (match_dup 4) (pc)) (const_int 2048)))
6746	   (const_int 6)
6747	   (const_int 8))))]
6748)
6749
6750(define_insn "*subsi3_cbranch"
6751  [(set (pc)
6752	(if_then_else
6753	 (match_operator 4 "comparison_operator"
6754	  [(minus:SI
6755	    (match_operand:SI 2 "s_register_operand" "l,l,1,l")
6756	    (match_operand:SI 3 "s_register_operand" "l,l,l,l"))
6757	   (const_int 0)])
6758	 (label_ref (match_operand 5 "" ""))
6759	 (pc)))
6760   (set (match_operand:SI 0 "thumb_cbrch_target_operand" "=l,*?h,*?m,*?m")
6761	(minus:SI (match_dup 2) (match_dup 3)))
6762   (clobber (match_scratch:SI 1 "=X,l,&l,&l"))]
6763  "TARGET_THUMB
6764   && (GET_CODE (operands[4]) == EQ
6765       || GET_CODE (operands[4]) == NE
6766       || GET_CODE (operands[4]) == GE
6767       || GET_CODE (operands[4]) == LT)"
6768  "*
6769   {
6770     if (which_alternative == 0)
6771       output_asm_insn (\"sub\\t%0, %2, %3\", operands);
6772     else if (which_alternative == 1)
6773       {
6774	 /* We must provide an alternative for a hi reg because reload 
6775	    cannot handle output reloads on a jump instruction, but we
6776	    can't subtract into that.  Fortunately a mov from lo to hi
6777	    does not clobber the condition codes.  */
6778	 output_asm_insn (\"sub\\t%1, %2, %3\", operands);
6779	 output_asm_insn (\"mov\\t%0, %1\", operands);
6780       }
6781     else
6782       {
6783	 /* Similarly, but the target is memory.  */
6784	 output_asm_insn (\"sub\\t%1, %2, %3\", operands);
6785	 output_asm_insn (\"str\\t%1, %0\", operands);
6786       }
6787
6788     switch (get_attr_length (insn) - ((which_alternative != 0) ? 2 : 0))
6789       {
6790	 case 4:
6791	   return \"b%d4\\t%l5\";
6792	 case 6:
6793	   return \"b%D4\\t.LCB%=\;b\\t%l5\\t%@long jump\\n.LCB%=:\";
6794	 default:
6795	   return \"b%D4\\t.LCB%=\;bl\\t%l5\\t%@far jump\\n.LCB%=:\";
6796       }
6797   }
6798  "
6799  [(set (attr "far_jump")
6800        (if_then_else
6801	    (ior (and (eq (symbol_ref ("which_alternative"))
6802	                  (const_int 0))
6803		      (eq_attr "length" "8"))
6804		 (eq_attr "length" "10"))
6805	    (const_string "yes")
6806            (const_string "no")))
6807   (set (attr "length")
6808     (if_then_else
6809       (eq (symbol_ref ("which_alternative"))
6810		       (const_int 0))
6811       (if_then_else
6812	 (and (ge (minus (match_dup 5) (pc)) (const_int -250))
6813	      (le (minus (match_dup 5) (pc)) (const_int 256)))
6814	 (const_int 4)
6815	 (if_then_else
6816	   (and (ge (minus (match_dup 5) (pc)) (const_int -2040))
6817		(le (minus (match_dup 5) (pc)) (const_int 2048)))
6818	   (const_int 6)
6819	   (const_int 8)))
6820       (if_then_else
6821	 (and (ge (minus (match_dup 5) (pc)) (const_int -248))
6822	      (le (minus (match_dup 5) (pc)) (const_int 256)))
6823	 (const_int 6)
6824	 (if_then_else
6825	   (and (ge (minus (match_dup 5) (pc)) (const_int -2038))
6826		(le (minus (match_dup 5) (pc)) (const_int 2048)))
6827	   (const_int 8)
6828	   (const_int 10)))))]
6829)
6830
6831(define_insn "*subsi3_cbranch_scratch"
6832  [(set (pc)
6833	(if_then_else
6834	 (match_operator 0 "arm_comparison_operator"
6835	  [(minus:SI (match_operand:SI 1 "register_operand" "l")
6836		     (match_operand:SI 2 "nonmemory_operand" "l"))
6837	   (const_int 0)])
6838	 (label_ref (match_operand 3 "" ""))
6839	 (pc)))]
6840  "TARGET_THUMB
6841   && (GET_CODE (operands[0]) == EQ
6842       || GET_CODE (operands[0]) == NE
6843       || GET_CODE (operands[0]) == GE
6844       || GET_CODE (operands[0]) == LT)"
6845  "*
6846  output_asm_insn (\"cmp\\t%1, %2\", operands);
6847  switch (get_attr_length (insn))
6848    {
6849    case 4:  return \"b%d0\\t%l3\";
6850    case 6:  return \"b%D0\\t.LCB%=\;b\\t%l3\\t%@long jump\\n.LCB%=:\";
6851    default: return \"b%D0\\t.LCB%=\;bl\\t%l3\\t%@far jump\\n.LCB%=:\";
6852    }
6853  "
6854  [(set (attr "far_jump")
6855        (if_then_else
6856	    (eq_attr "length" "8")
6857	    (const_string "yes")
6858            (const_string "no")))
6859   (set (attr "length") 
6860        (if_then_else
6861	    (and (ge (minus (match_dup 3) (pc)) (const_int -250))
6862	         (le (minus (match_dup 3) (pc)) (const_int 256)))
6863	    (const_int 4)
6864	    (if_then_else
6865	        (and (ge (minus (match_dup 3) (pc)) (const_int -2040))
6866		     (le (minus (match_dup 3) (pc)) (const_int 2048)))
6867		(const_int 6)
6868		(const_int 8))))]
6869)
6870
6871;; Comparison and test insns
6872
6873(define_expand "cmpsi"
6874  [(match_operand:SI 0 "s_register_operand" "")
6875   (match_operand:SI 1 "arm_add_operand" "")]
6876  "TARGET_ARM"
6877  "{
6878    arm_compare_op0 = operands[0];
6879    arm_compare_op1 = operands[1];
6880    DONE;
6881  }"
6882)
6883
6884(define_expand "cmpsf"
6885  [(match_operand:SF 0 "s_register_operand" "")
6886   (match_operand:SF 1 "arm_float_compare_operand" "")]
6887  "TARGET_ARM && TARGET_HARD_FLOAT"
6888  "
6889  arm_compare_op0 = operands[0];
6890  arm_compare_op1 = operands[1];
6891  DONE;
6892  "
6893)
6894
6895(define_expand "cmpdf"
6896  [(match_operand:DF 0 "s_register_operand" "")
6897   (match_operand:DF 1 "arm_float_compare_operand" "")]
6898  "TARGET_ARM && TARGET_HARD_FLOAT"
6899  "
6900  arm_compare_op0 = operands[0];
6901  arm_compare_op1 = operands[1];
6902  DONE;
6903  "
6904)
6905
6906(define_insn "*arm_cmpsi_insn"
6907  [(set (reg:CC CC_REGNUM)
6908	(compare:CC (match_operand:SI 0 "s_register_operand" "r,r")
6909		    (match_operand:SI 1 "arm_add_operand"    "rI,L")))]
6910  "TARGET_ARM"
6911  "@
6912   cmp%?\\t%0, %1
6913   cmn%?\\t%0, #%n1"
6914  [(set_attr "conds" "set")]
6915)
6916
6917(define_insn "*cmpsi_shiftsi"
6918  [(set (reg:CC CC_REGNUM)
6919	(compare:CC (match_operand:SI   0 "s_register_operand" "r")
6920		    (match_operator:SI  3 "shift_operator"
6921		     [(match_operand:SI 1 "s_register_operand" "r")
6922		      (match_operand:SI 2 "arm_rhs_operand"    "rM")])))]
6923  "TARGET_ARM"
6924  "cmp%?\\t%0, %1%S3"
6925  [(set_attr "conds" "set")
6926   (set_attr "shift" "1")
6927   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
6928		      (const_string "alu_shift")
6929		      (const_string "alu_shift_reg")))]
6930)
6931
6932(define_insn "*cmpsi_shiftsi_swp"
6933  [(set (reg:CC_SWP CC_REGNUM)
6934	(compare:CC_SWP (match_operator:SI 3 "shift_operator"
6935			 [(match_operand:SI 1 "s_register_operand" "r")
6936			  (match_operand:SI 2 "reg_or_int_operand" "rM")])
6937			(match_operand:SI 0 "s_register_operand" "r")))]
6938  "TARGET_ARM"
6939  "cmp%?\\t%0, %1%S3"
6940  [(set_attr "conds" "set")
6941   (set_attr "shift" "1")
6942   (set (attr "type") (if_then_else (match_operand 2 "const_int_operand" "")
6943		      (const_string "alu_shift")
6944		      (const_string "alu_shift_reg")))]
6945)
6946
6947(define_insn "*cmpsi_negshiftsi_si"
6948  [(set (reg:CC_Z CC_REGNUM)
6949	(compare:CC_Z
6950	 (neg:SI (match_operator:SI 1 "shift_operator"
6951		    [(match_operand:SI 2 "s_register_operand" "r")
6952		     (match_operand:SI 3 "reg_or_int_operand" "rM")]))
6953	 (match_operand:SI 0 "s_register_operand" "r")))]
6954  "TARGET_ARM"
6955  "cmn%?\\t%0, %2%S1"
6956  [(set_attr "conds" "set")
6957   (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
6958				    (const_string "alu_shift")
6959				    (const_string "alu_shift_reg")))]
6960)
6961
6962;; Cirrus SF compare instruction
6963(define_insn "*cirrus_cmpsf"
6964  [(set (reg:CCFP CC_REGNUM)
6965	(compare:CCFP (match_operand:SF 0 "cirrus_fp_register" "v")
6966		      (match_operand:SF 1 "cirrus_fp_register" "v")))]
6967  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_MAVERICK"
6968  "cfcmps%?\\tr15, %V0, %V1"
6969  [(set_attr "type"   "mav_farith")
6970   (set_attr "cirrus" "compare")]
6971)
6972
6973;; Cirrus DF compare instruction
6974(define_insn "*cirrus_cmpdf"
6975  [(set (reg:CCFP CC_REGNUM)
6976	(compare:CCFP (match_operand:DF 0 "cirrus_fp_register" "v")
6977		      (match_operand:DF 1 "cirrus_fp_register" "v")))]
6978  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_MAVERICK"
6979  "cfcmpd%?\\tr15, %V0, %V1"
6980  [(set_attr "type"   "mav_farith")
6981   (set_attr "cirrus" "compare")]
6982)
6983
6984;; Cirrus DI compare instruction
6985(define_expand "cmpdi"
6986  [(match_operand:DI 0 "cirrus_fp_register" "")
6987   (match_operand:DI 1 "cirrus_fp_register" "")]
6988  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_MAVERICK"
6989  "{
6990     arm_compare_op0 = operands[0];
6991     arm_compare_op1 = operands[1];
6992     DONE;
6993   }")
6994
6995(define_insn "*cirrus_cmpdi"
6996  [(set (reg:CC CC_REGNUM)
6997	(compare:CC (match_operand:DI 0 "cirrus_fp_register" "v")
6998		    (match_operand:DI 1 "cirrus_fp_register" "v")))]
6999  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_MAVERICK"
7000  "cfcmp64%?\\tr15, %V0, %V1"
7001  [(set_attr "type"   "mav_farith")
7002   (set_attr "cirrus" "compare")]
7003)
7004
7005; This insn allows redundant compares to be removed by cse, nothing should
7006; ever appear in the output file since (set (reg x) (reg x)) is a no-op that
7007; is deleted later on. The match_dup will match the mode here, so that
7008; mode changes of the condition codes aren't lost by this even though we don't
7009; specify what they are.
7010
7011(define_insn "*deleted_compare"
7012  [(set (match_operand 0 "cc_register" "") (match_dup 0))]
7013  "TARGET_ARM"
7014  "\\t%@ deleted compare"
7015  [(set_attr "conds" "set")
7016   (set_attr "length" "0")]
7017)
7018
7019
7020;; Conditional branch insns
7021
7022(define_expand "beq"
7023  [(set (pc)
7024	(if_then_else (eq (match_dup 1) (const_int 0))
7025		      (label_ref (match_operand 0 "" ""))
7026		      (pc)))]
7027  "TARGET_ARM"
7028  "operands[1] = arm_gen_compare_reg (EQ, arm_compare_op0, arm_compare_op1);"
7029)
7030
7031(define_expand "bne"
7032  [(set (pc)
7033	(if_then_else (ne (match_dup 1) (const_int 0))
7034		      (label_ref (match_operand 0 "" ""))
7035		      (pc)))]
7036  "TARGET_ARM"
7037  "operands[1] = arm_gen_compare_reg (NE, arm_compare_op0, arm_compare_op1);"
7038)
7039
7040(define_expand "bgt"
7041  [(set (pc)
7042	(if_then_else (gt (match_dup 1) (const_int 0))
7043		      (label_ref (match_operand 0 "" ""))
7044		      (pc)))]
7045  "TARGET_ARM"
7046  "operands[1] = arm_gen_compare_reg (GT, arm_compare_op0, arm_compare_op1);"
7047)
7048
7049(define_expand "ble"
7050  [(set (pc)
7051	(if_then_else (le (match_dup 1) (const_int 0))
7052		      (label_ref (match_operand 0 "" ""))
7053		      (pc)))]
7054  "TARGET_ARM"
7055  "operands[1] = arm_gen_compare_reg (LE, arm_compare_op0, arm_compare_op1);"
7056)
7057
7058(define_expand "bge"
7059  [(set (pc)
7060	(if_then_else (ge (match_dup 1) (const_int 0))
7061		      (label_ref (match_operand 0 "" ""))
7062		      (pc)))]
7063  "TARGET_ARM"
7064  "operands[1] = arm_gen_compare_reg (GE, arm_compare_op0, arm_compare_op1);"
7065)
7066
7067(define_expand "blt"
7068  [(set (pc)
7069	(if_then_else (lt (match_dup 1) (const_int 0))
7070		      (label_ref (match_operand 0 "" ""))
7071		      (pc)))]
7072  "TARGET_ARM"
7073  "operands[1] = arm_gen_compare_reg (LT, arm_compare_op0, arm_compare_op1);"
7074)
7075
7076(define_expand "bgtu"
7077  [(set (pc)
7078	(if_then_else (gtu (match_dup 1) (const_int 0))
7079		      (label_ref (match_operand 0 "" ""))
7080		      (pc)))]
7081  "TARGET_ARM"
7082  "operands[1] = arm_gen_compare_reg (GTU, arm_compare_op0, arm_compare_op1);"
7083)
7084
7085(define_expand "bleu"
7086  [(set (pc)
7087	(if_then_else (leu (match_dup 1) (const_int 0))
7088		      (label_ref (match_operand 0 "" ""))
7089		      (pc)))]
7090  "TARGET_ARM"
7091  "operands[1] = arm_gen_compare_reg (LEU, arm_compare_op0, arm_compare_op1);"
7092)
7093
7094(define_expand "bgeu"
7095  [(set (pc)
7096	(if_then_else (geu (match_dup 1) (const_int 0))
7097		      (label_ref (match_operand 0 "" ""))
7098		      (pc)))]
7099  "TARGET_ARM"
7100  "operands[1] = arm_gen_compare_reg (GEU, arm_compare_op0, arm_compare_op1);"
7101)
7102
7103(define_expand "bltu"
7104  [(set (pc)
7105	(if_then_else (ltu (match_dup 1) (const_int 0))
7106		      (label_ref (match_operand 0 "" ""))
7107		      (pc)))]
7108  "TARGET_ARM"
7109  "operands[1] = arm_gen_compare_reg (LTU, arm_compare_op0, arm_compare_op1);"
7110)
7111
7112(define_expand "bunordered"
7113  [(set (pc)
7114	(if_then_else (unordered (match_dup 1) (const_int 0))
7115		      (label_ref (match_operand 0 "" ""))
7116		      (pc)))]
7117  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7118  "operands[1] = arm_gen_compare_reg (UNORDERED, arm_compare_op0,
7119				      arm_compare_op1);"
7120)
7121
7122(define_expand "bordered"
7123  [(set (pc)
7124	(if_then_else (ordered (match_dup 1) (const_int 0))
7125		      (label_ref (match_operand 0 "" ""))
7126		      (pc)))]
7127  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7128  "operands[1] = arm_gen_compare_reg (ORDERED, arm_compare_op0,
7129				      arm_compare_op1);"
7130)
7131
7132(define_expand "bungt"
7133  [(set (pc)
7134	(if_then_else (ungt (match_dup 1) (const_int 0))
7135		      (label_ref (match_operand 0 "" ""))
7136		      (pc)))]
7137  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7138  "operands[1] = arm_gen_compare_reg (UNGT, arm_compare_op0, arm_compare_op1);"
7139)
7140
7141(define_expand "bunlt"
7142  [(set (pc)
7143	(if_then_else (unlt (match_dup 1) (const_int 0))
7144		      (label_ref (match_operand 0 "" ""))
7145		      (pc)))]
7146  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7147  "operands[1] = arm_gen_compare_reg (UNLT, arm_compare_op0, arm_compare_op1);"
7148)
7149
7150(define_expand "bunge"
7151  [(set (pc)
7152	(if_then_else (unge (match_dup 1) (const_int 0))
7153		      (label_ref (match_operand 0 "" ""))
7154		      (pc)))]
7155  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7156  "operands[1] = arm_gen_compare_reg (UNGE, arm_compare_op0, arm_compare_op1);"
7157)
7158
7159(define_expand "bunle"
7160  [(set (pc)
7161	(if_then_else (unle (match_dup 1) (const_int 0))
7162		      (label_ref (match_operand 0 "" ""))
7163		      (pc)))]
7164  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7165  "operands[1] = arm_gen_compare_reg (UNLE, arm_compare_op0, arm_compare_op1);"
7166)
7167
7168;; The following two patterns need two branch instructions, since there is
7169;; no single instruction that will handle all cases.
7170(define_expand "buneq"
7171  [(set (pc)
7172	(if_then_else (uneq (match_dup 1) (const_int 0))
7173		      (label_ref (match_operand 0 "" ""))
7174		      (pc)))]
7175  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7176  "operands[1] = arm_gen_compare_reg (UNEQ, arm_compare_op0, arm_compare_op1);"
7177)
7178
7179(define_expand "bltgt"
7180  [(set (pc)
7181	(if_then_else (ltgt (match_dup 1) (const_int 0))
7182		      (label_ref (match_operand 0 "" ""))
7183		      (pc)))]
7184  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7185  "operands[1] = arm_gen_compare_reg (LTGT, arm_compare_op0, arm_compare_op1);"
7186)
7187
7188;;
7189;; Patterns to match conditional branch insns.
7190;;
7191
7192; Special pattern to match UNEQ.
7193(define_insn "*arm_buneq"
7194  [(set (pc)
7195	(if_then_else (uneq (match_operand 1 "cc_register" "") (const_int 0))
7196		      (label_ref (match_operand 0 "" ""))
7197		      (pc)))]
7198  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7199  "*
7200  gcc_assert (!arm_ccfsm_state);
7201
7202  return \"bvs\\t%l0\;beq\\t%l0\";
7203  "
7204  [(set_attr "conds" "jump_clob")
7205   (set_attr "length" "8")]
7206)
7207
7208; Special pattern to match LTGT.
7209(define_insn "*arm_bltgt"
7210  [(set (pc)
7211	(if_then_else (ltgt (match_operand 1 "cc_register" "") (const_int 0))
7212		      (label_ref (match_operand 0 "" ""))
7213		      (pc)))]
7214  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7215  "*
7216  gcc_assert (!arm_ccfsm_state);
7217
7218  return \"bmi\\t%l0\;bgt\\t%l0\";
7219  "
7220  [(set_attr "conds" "jump_clob")
7221   (set_attr "length" "8")]
7222)
7223
7224(define_insn "*arm_cond_branch"
7225  [(set (pc)
7226	(if_then_else (match_operator 1 "arm_comparison_operator"
7227		       [(match_operand 2 "cc_register" "") (const_int 0)])
7228		      (label_ref (match_operand 0 "" ""))
7229		      (pc)))]
7230  "TARGET_ARM"
7231  "*
7232  if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
7233    {
7234      arm_ccfsm_state += 2;
7235      return \"\";
7236    }
7237  return \"b%d1\\t%l0\";
7238  "
7239  [(set_attr "conds" "use")
7240   (set_attr "type" "branch")]
7241)
7242
7243; Special pattern to match reversed UNEQ.
7244(define_insn "*arm_buneq_reversed"
7245  [(set (pc)
7246	(if_then_else (uneq (match_operand 1 "cc_register" "") (const_int 0))
7247		      (pc)
7248		      (label_ref (match_operand 0 "" ""))))]
7249  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7250  "*
7251  gcc_assert (!arm_ccfsm_state);
7252
7253  return \"bmi\\t%l0\;bgt\\t%l0\";
7254  "
7255  [(set_attr "conds" "jump_clob")
7256   (set_attr "length" "8")]
7257)
7258
7259; Special pattern to match reversed LTGT.
7260(define_insn "*arm_bltgt_reversed"
7261  [(set (pc)
7262	(if_then_else (ltgt (match_operand 1 "cc_register" "") (const_int 0))
7263		      (pc)
7264		      (label_ref (match_operand 0 "" ""))))]
7265  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7266  "*
7267  gcc_assert (!arm_ccfsm_state);
7268
7269  return \"bvs\\t%l0\;beq\\t%l0\";
7270  "
7271  [(set_attr "conds" "jump_clob")
7272   (set_attr "length" "8")]
7273)
7274
7275(define_insn "*arm_cond_branch_reversed"
7276  [(set (pc)
7277	(if_then_else (match_operator 1 "arm_comparison_operator"
7278		       [(match_operand 2 "cc_register" "") (const_int 0)])
7279		      (pc)
7280		      (label_ref (match_operand 0 "" ""))))]
7281  "TARGET_ARM"
7282  "*
7283  if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
7284    {
7285      arm_ccfsm_state += 2;
7286      return \"\";
7287    }
7288  return \"b%D1\\t%l0\";
7289  "
7290  [(set_attr "conds" "use")
7291   (set_attr "type" "branch")]
7292)
7293
7294
7295
7296; scc insns
7297
7298(define_expand "seq"
7299  [(set (match_operand:SI 0 "s_register_operand" "")
7300	(eq:SI (match_dup 1) (const_int 0)))]
7301  "TARGET_ARM"
7302  "operands[1] = arm_gen_compare_reg (EQ, arm_compare_op0, arm_compare_op1);"
7303)
7304
7305(define_expand "sne"
7306  [(set (match_operand:SI 0 "s_register_operand" "")
7307	(ne:SI (match_dup 1) (const_int 0)))]
7308  "TARGET_ARM"
7309  "operands[1] = arm_gen_compare_reg (NE, arm_compare_op0, arm_compare_op1);"
7310)
7311
7312(define_expand "sgt"
7313  [(set (match_operand:SI 0 "s_register_operand" "")
7314	(gt:SI (match_dup 1) (const_int 0)))]
7315  "TARGET_ARM"
7316  "operands[1] = arm_gen_compare_reg (GT, arm_compare_op0, arm_compare_op1);"
7317)
7318
7319(define_expand "sle"
7320  [(set (match_operand:SI 0 "s_register_operand" "")
7321	(le:SI (match_dup 1) (const_int 0)))]
7322  "TARGET_ARM"
7323  "operands[1] = arm_gen_compare_reg (LE, arm_compare_op0, arm_compare_op1);"
7324)
7325
7326(define_expand "sge"
7327  [(set (match_operand:SI 0 "s_register_operand" "")
7328	(ge:SI (match_dup 1) (const_int 0)))]
7329  "TARGET_ARM"
7330  "operands[1] = arm_gen_compare_reg (GE, arm_compare_op0, arm_compare_op1);"
7331)
7332
7333(define_expand "slt"
7334  [(set (match_operand:SI 0 "s_register_operand" "")
7335	(lt:SI (match_dup 1) (const_int 0)))]
7336  "TARGET_ARM"
7337  "operands[1] = arm_gen_compare_reg (LT, arm_compare_op0, arm_compare_op1);"
7338)
7339
7340(define_expand "sgtu"
7341  [(set (match_operand:SI 0 "s_register_operand" "")
7342	(gtu:SI (match_dup 1) (const_int 0)))]
7343  "TARGET_ARM"
7344  "operands[1] = arm_gen_compare_reg (GTU, arm_compare_op0, arm_compare_op1);"
7345)
7346
7347(define_expand "sleu"
7348  [(set (match_operand:SI 0 "s_register_operand" "")
7349	(leu:SI (match_dup 1) (const_int 0)))]
7350  "TARGET_ARM"
7351  "operands[1] = arm_gen_compare_reg (LEU, arm_compare_op0, arm_compare_op1);"
7352)
7353
7354(define_expand "sgeu"
7355  [(set (match_operand:SI 0 "s_register_operand" "")
7356	(geu:SI (match_dup 1) (const_int 0)))]
7357  "TARGET_ARM"
7358  "operands[1] = arm_gen_compare_reg (GEU, arm_compare_op0, arm_compare_op1);"
7359)
7360
7361(define_expand "sltu"
7362  [(set (match_operand:SI 0 "s_register_operand" "")
7363	(ltu:SI (match_dup 1) (const_int 0)))]
7364  "TARGET_ARM"
7365  "operands[1] = arm_gen_compare_reg (LTU, arm_compare_op0, arm_compare_op1);"
7366)
7367
7368(define_expand "sunordered"
7369  [(set (match_operand:SI 0 "s_register_operand" "")
7370	(unordered:SI (match_dup 1) (const_int 0)))]
7371  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7372  "operands[1] = arm_gen_compare_reg (UNORDERED, arm_compare_op0,
7373				      arm_compare_op1);"
7374)
7375
7376(define_expand "sordered"
7377  [(set (match_operand:SI 0 "s_register_operand" "")
7378	(ordered:SI (match_dup 1) (const_int 0)))]
7379  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7380  "operands[1] = arm_gen_compare_reg (ORDERED, arm_compare_op0,
7381				      arm_compare_op1);"
7382)
7383
7384(define_expand "sungt"
7385  [(set (match_operand:SI 0 "s_register_operand" "")
7386	(ungt:SI (match_dup 1) (const_int 0)))]
7387  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7388  "operands[1] = arm_gen_compare_reg (UNGT, arm_compare_op0,
7389				      arm_compare_op1);"
7390)
7391
7392(define_expand "sunge"
7393  [(set (match_operand:SI 0 "s_register_operand" "")
7394	(unge:SI (match_dup 1) (const_int 0)))]
7395  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7396  "operands[1] = arm_gen_compare_reg (UNGE, arm_compare_op0,
7397				      arm_compare_op1);"
7398)
7399
7400(define_expand "sunlt"
7401  [(set (match_operand:SI 0 "s_register_operand" "")
7402	(unlt:SI (match_dup 1) (const_int 0)))]
7403  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7404  "operands[1] = arm_gen_compare_reg (UNLT, arm_compare_op0,
7405				      arm_compare_op1);"
7406)
7407
7408(define_expand "sunle"
7409  [(set (match_operand:SI 0 "s_register_operand" "")
7410	(unle:SI (match_dup 1) (const_int 0)))]
7411  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7412  "operands[1] = arm_gen_compare_reg (UNLE, arm_compare_op0,
7413				      arm_compare_op1);"
7414)
7415
7416;;; DO NOT add patterns for SUNEQ or SLTGT, these can't be represented with
7417;;; simple ARM instructions. 
7418;
7419; (define_expand "suneq"
7420;   [(set (match_operand:SI 0 "s_register_operand" "")
7421; 	(uneq:SI (match_dup 1) (const_int 0)))]
7422;   "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7423;   "gcc_unreachable ();"
7424; )
7425;
7426; (define_expand "sltgt"
7427;   [(set (match_operand:SI 0 "s_register_operand" "")
7428; 	(ltgt:SI (match_dup 1) (const_int 0)))]
7429;   "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7430;   "gcc_unreachable ();"
7431; )
7432
7433(define_insn "*mov_scc"
7434  [(set (match_operand:SI 0 "s_register_operand" "=r")
7435	(match_operator:SI 1 "arm_comparison_operator"
7436	 [(match_operand 2 "cc_register" "") (const_int 0)]))]
7437  "TARGET_ARM"
7438  "mov%D1\\t%0, #0\;mov%d1\\t%0, #1"
7439  [(set_attr "conds" "use")
7440   (set_attr "length" "8")]
7441)
7442
7443(define_insn "*mov_negscc"
7444  [(set (match_operand:SI 0 "s_register_operand" "=r")
7445	(neg:SI (match_operator:SI 1 "arm_comparison_operator"
7446		 [(match_operand 2 "cc_register" "") (const_int 0)])))]
7447  "TARGET_ARM"
7448  "mov%D1\\t%0, #0\;mvn%d1\\t%0, #0"
7449  [(set_attr "conds" "use")
7450   (set_attr "length" "8")]
7451)
7452
7453(define_insn "*mov_notscc"
7454  [(set (match_operand:SI 0 "s_register_operand" "=r")
7455	(not:SI (match_operator:SI 1 "arm_comparison_operator"
7456		 [(match_operand 2 "cc_register" "") (const_int 0)])))]
7457  "TARGET_ARM"
7458  "mov%D1\\t%0, #0\;mvn%d1\\t%0, #1"
7459  [(set_attr "conds" "use")
7460   (set_attr "length" "8")]
7461)
7462
7463
7464;; Conditional move insns
7465
7466(define_expand "movsicc"
7467  [(set (match_operand:SI 0 "s_register_operand" "")
7468	(if_then_else:SI (match_operand 1 "arm_comparison_operator" "")
7469			 (match_operand:SI 2 "arm_not_operand" "")
7470			 (match_operand:SI 3 "arm_not_operand" "")))]
7471  "TARGET_ARM"
7472  "
7473  {
7474    enum rtx_code code = GET_CODE (operands[1]);
7475    rtx ccreg;
7476
7477    if (code == UNEQ || code == LTGT)
7478      FAIL;
7479
7480    ccreg = arm_gen_compare_reg (code, arm_compare_op0, arm_compare_op1);
7481    operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
7482  }"
7483)
7484
7485(define_expand "movsfcc"
7486  [(set (match_operand:SF 0 "s_register_operand" "")
7487	(if_then_else:SF (match_operand 1 "arm_comparison_operator" "")
7488			 (match_operand:SF 2 "s_register_operand" "")
7489			 (match_operand:SF 3 "nonmemory_operand" "")))]
7490  "TARGET_ARM"
7491  "
7492  {
7493    enum rtx_code code = GET_CODE (operands[1]);
7494    rtx ccreg;
7495
7496    if (code == UNEQ || code == LTGT)
7497      FAIL;
7498
7499    /* When compiling for SOFT_FLOAT, ensure both arms are in registers. 
7500       Otherwise, ensure it is a valid FP add operand */
7501    if ((!(TARGET_HARD_FLOAT && TARGET_FPA))
7502        || (!arm_float_add_operand (operands[3], SFmode)))
7503      operands[3] = force_reg (SFmode, operands[3]);
7504
7505    ccreg = arm_gen_compare_reg (code, arm_compare_op0, arm_compare_op1);
7506    operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
7507  }"
7508)
7509
7510(define_expand "movdfcc"
7511  [(set (match_operand:DF 0 "s_register_operand" "")
7512	(if_then_else:DF (match_operand 1 "arm_comparison_operator" "")
7513			 (match_operand:DF 2 "s_register_operand" "")
7514			 (match_operand:DF 3 "arm_float_add_operand" "")))]
7515  "TARGET_ARM && TARGET_HARD_FLOAT && (TARGET_FPA || TARGET_VFP)"
7516  "
7517  {
7518    enum rtx_code code = GET_CODE (operands[1]);
7519    rtx ccreg;
7520
7521    if (code == UNEQ || code == LTGT)
7522      FAIL;
7523
7524    ccreg = arm_gen_compare_reg (code, arm_compare_op0, arm_compare_op1);
7525    operands[1] = gen_rtx_fmt_ee (code, VOIDmode, ccreg, const0_rtx);
7526  }"
7527)
7528
7529(define_insn "*movsicc_insn"
7530  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r,r,r,r,r")
7531	(if_then_else:SI
7532	 (match_operator 3 "arm_comparison_operator"
7533	  [(match_operand 4 "cc_register" "") (const_int 0)])
7534	 (match_operand:SI 1 "arm_not_operand" "0,0,rI,K,rI,rI,K,K")
7535	 (match_operand:SI 2 "arm_not_operand" "rI,K,0,0,rI,K,rI,K")))]
7536  "TARGET_ARM"
7537  "@
7538   mov%D3\\t%0, %2
7539   mvn%D3\\t%0, #%B2
7540   mov%d3\\t%0, %1
7541   mvn%d3\\t%0, #%B1
7542   mov%d3\\t%0, %1\;mov%D3\\t%0, %2
7543   mov%d3\\t%0, %1\;mvn%D3\\t%0, #%B2
7544   mvn%d3\\t%0, #%B1\;mov%D3\\t%0, %2
7545   mvn%d3\\t%0, #%B1\;mvn%D3\\t%0, #%B2"
7546  [(set_attr "length" "4,4,4,4,8,8,8,8")
7547   (set_attr "conds" "use")]
7548)
7549
7550(define_insn "*movsfcc_soft_insn"
7551  [(set (match_operand:SF 0 "s_register_operand" "=r,r")
7552	(if_then_else:SF (match_operator 3 "arm_comparison_operator"
7553			  [(match_operand 4 "cc_register" "") (const_int 0)])
7554			 (match_operand:SF 1 "s_register_operand" "0,r")
7555			 (match_operand:SF 2 "s_register_operand" "r,0")))]
7556  "TARGET_ARM && TARGET_SOFT_FLOAT"
7557  "@
7558   mov%D3\\t%0, %2
7559   mov%d3\\t%0, %1"
7560  [(set_attr "conds" "use")]
7561)
7562
7563
7564;; Jump and linkage insns
7565
7566(define_expand "jump"
7567  [(set (pc)
7568	(label_ref (match_operand 0 "" "")))]
7569  "TARGET_EITHER"
7570  ""
7571)
7572
7573(define_insn "*arm_jump"
7574  [(set (pc)
7575	(label_ref (match_operand 0 "" "")))]
7576  "TARGET_ARM"
7577  "*
7578  {
7579    if (arm_ccfsm_state == 1 || arm_ccfsm_state == 2)
7580      {
7581        arm_ccfsm_state += 2;
7582        return \"\";
7583      }
7584    return \"b%?\\t%l0\";
7585  }
7586  "
7587  [(set_attr "predicable" "yes")]
7588)
7589
7590(define_insn "*thumb_jump"
7591  [(set (pc)
7592	(label_ref (match_operand 0 "" "")))]
7593  "TARGET_THUMB"
7594  "*
7595  if (get_attr_length (insn) == 2)
7596    return \"b\\t%l0\";
7597  return \"bl\\t%l0\\t%@ far jump\";
7598  "
7599  [(set (attr "far_jump")
7600        (if_then_else
7601	    (eq_attr "length" "4")
7602	    (const_string "yes")
7603	    (const_string "no")))
7604   (set (attr "length") 
7605        (if_then_else
7606	    (and (ge (minus (match_dup 0) (pc)) (const_int -2044))
7607		 (le (minus (match_dup 0) (pc)) (const_int 2048)))
7608  	    (const_int 2)
7609	    (const_int 4)))]
7610)
7611
7612(define_expand "call"
7613  [(parallel [(call (match_operand 0 "memory_operand" "")
7614	            (match_operand 1 "general_operand" ""))
7615	      (use (match_operand 2 "" ""))
7616	      (clobber (reg:SI LR_REGNUM))])]
7617  "TARGET_EITHER"
7618  "
7619  {
7620    rtx callee;
7621    
7622    /* In an untyped call, we can get NULL for operand 2.  */
7623    if (operands[2] == NULL_RTX)
7624      operands[2] = const0_rtx;
7625      
7626    /* This is to decide if we should generate indirect calls by loading the
7627       32 bit address of the callee into a register before performing the
7628       branch and link.  operand[2] encodes the long_call/short_call
7629       attribute of the function being called.  This attribute is set whenever
7630       __attribute__((long_call/short_call)) or #pragma long_call/no_long_call
7631       is used, and the short_call attribute can also be set if function is
7632       declared as static or if it has already been defined in the current
7633       compilation unit.  See arm.c and arm.h for info about this.  The third
7634       parameter to arm_is_longcall_p is used to tell it which pattern
7635       invoked it.  */
7636    callee  = XEXP (operands[0], 0);
7637    
7638    if ((GET_CODE (callee) == SYMBOL_REF
7639	 && arm_is_longcall_p (operands[0], INTVAL (operands[2]), 0))
7640	|| (GET_CODE (callee) != SYMBOL_REF
7641	    && GET_CODE (callee) != REG))
7642      XEXP (operands[0], 0) = force_reg (Pmode, callee);
7643  }"
7644)
7645
7646(define_insn "*call_reg_armv5"
7647  [(call (mem:SI (match_operand:SI 0 "s_register_operand" "r"))
7648         (match_operand 1 "" ""))
7649   (use (match_operand 2 "" ""))
7650   (clobber (reg:SI LR_REGNUM))]
7651  "TARGET_ARM && arm_arch5"
7652  "blx%?\\t%0"
7653  [(set_attr "type" "call")]
7654)
7655
7656(define_insn "*call_reg_arm"
7657  [(call (mem:SI (match_operand:SI 0 "s_register_operand" "r"))
7658         (match_operand 1 "" ""))
7659   (use (match_operand 2 "" ""))
7660   (clobber (reg:SI LR_REGNUM))]
7661  "TARGET_ARM && !arm_arch5"
7662  "*
7663  return output_call (operands);
7664  "
7665  ;; length is worst case, normally it is only two
7666  [(set_attr "length" "12")
7667   (set_attr "type" "call")]
7668)
7669
7670(define_insn "*call_mem"
7671  [(call (mem:SI (match_operand:SI 0 "call_memory_operand" "m"))
7672	 (match_operand 1 "" ""))
7673   (use (match_operand 2 "" ""))
7674   (clobber (reg:SI LR_REGNUM))]
7675  "TARGET_ARM"
7676  "*
7677  return output_call_mem (operands);
7678  "
7679  [(set_attr "length" "12")
7680   (set_attr "type" "call")]
7681)
7682
7683(define_insn "*call_reg_thumb_v5"
7684  [(call (mem:SI (match_operand:SI 0 "register_operand" "l*r"))
7685	 (match_operand 1 "" ""))
7686   (use (match_operand 2 "" ""))
7687   (clobber (reg:SI LR_REGNUM))]
7688  "TARGET_THUMB && arm_arch5"
7689  "blx\\t%0"
7690  [(set_attr "length" "2")
7691   (set_attr "type" "call")]
7692)
7693
7694(define_insn "*call_reg_thumb"
7695  [(call (mem:SI (match_operand:SI 0 "register_operand" "l*r"))
7696	 (match_operand 1 "" ""))
7697   (use (match_operand 2 "" ""))
7698   (clobber (reg:SI LR_REGNUM))]
7699  "TARGET_THUMB && !arm_arch5"
7700  "*
7701  {
7702    if (!TARGET_CALLER_INTERWORKING)
7703      return thumb_call_via_reg (operands[0]);
7704    else if (operands[1] == const0_rtx)
7705      return \"bl\\t%__interwork_call_via_%0\";
7706    else if (frame_pointer_needed)
7707      return \"bl\\t%__interwork_r7_call_via_%0\";
7708    else
7709      return \"bl\\t%__interwork_r11_call_via_%0\";
7710  }"
7711  [(set_attr "type" "call")]
7712)
7713
7714(define_expand "call_value"
7715  [(parallel [(set (match_operand       0 "" "")
7716	           (call (match_operand 1 "memory_operand" "")
7717		         (match_operand 2 "general_operand" "")))
7718	      (use (match_operand 3 "" ""))
7719	      (clobber (reg:SI LR_REGNUM))])]
7720  "TARGET_EITHER"
7721  "
7722  {
7723    rtx callee = XEXP (operands[1], 0);
7724    
7725    /* In an untyped call, we can get NULL for operand 2.  */
7726    if (operands[3] == 0)
7727      operands[3] = const0_rtx;
7728      
7729    /* See the comment in define_expand \"call\".  */
7730    if ((GET_CODE (callee) == SYMBOL_REF
7731	 && arm_is_longcall_p (operands[1], INTVAL (operands[3]), 0))
7732	|| (GET_CODE (callee) != SYMBOL_REF
7733	    && GET_CODE (callee) != REG))
7734      XEXP (operands[1], 0) = force_reg (Pmode, callee);
7735  }"
7736)
7737
7738(define_insn "*call_value_reg_armv5"
7739  [(set (match_operand 0 "" "")
7740        (call (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
7741	      (match_operand 2 "" "")))
7742   (use (match_operand 3 "" ""))
7743   (clobber (reg:SI LR_REGNUM))]
7744  "TARGET_ARM && arm_arch5"
7745  "blx%?\\t%1"
7746  [(set_attr "type" "call")]
7747)
7748
7749(define_insn "*call_value_reg_arm"
7750  [(set (match_operand 0 "" "")
7751        (call (mem:SI (match_operand:SI 1 "s_register_operand" "r"))
7752	      (match_operand 2 "" "")))
7753   (use (match_operand 3 "" ""))
7754   (clobber (reg:SI LR_REGNUM))]
7755  "TARGET_ARM && !arm_arch5"
7756  "*
7757  return output_call (&operands[1]);
7758  "
7759  [(set_attr "length" "12")
7760   (set_attr "type" "call")]
7761)
7762
7763(define_insn "*call_value_mem"
7764  [(set (match_operand 0 "" "")
7765	(call (mem:SI (match_operand:SI 1 "call_memory_operand" "m"))
7766	      (match_operand 2 "" "")))
7767   (use (match_operand 3 "" ""))
7768   (clobber (reg:SI LR_REGNUM))]
7769  "TARGET_ARM && (!CONSTANT_ADDRESS_P (XEXP (operands[1], 0)))"
7770  "*
7771  return output_call_mem (&operands[1]);
7772  "
7773  [(set_attr "length" "12")
7774   (set_attr "type" "call")]
7775)
7776
7777(define_insn "*call_value_reg_thumb_v5"
7778  [(set (match_operand 0 "" "")
7779	(call (mem:SI (match_operand:SI 1 "register_operand" "l*r"))
7780	      (match_operand 2 "" "")))
7781   (use (match_operand 3 "" ""))
7782   (clobber (reg:SI LR_REGNUM))]
7783  "TARGET_THUMB && arm_arch5"
7784  "blx\\t%1"
7785  [(set_attr "length" "2")
7786   (set_attr "type" "call")]
7787)
7788
7789(define_insn "*call_value_reg_thumb"
7790  [(set (match_operand 0 "" "")
7791	(call (mem:SI (match_operand:SI 1 "register_operand" "l*r"))
7792	      (match_operand 2 "" "")))
7793   (use (match_operand 3 "" ""))
7794   (clobber (reg:SI LR_REGNUM))]
7795  "TARGET_THUMB && !arm_arch5"
7796  "*
7797  {
7798    if (!TARGET_CALLER_INTERWORKING)
7799      return thumb_call_via_reg (operands[1]);
7800    else if (operands[2] == const0_rtx)
7801      return \"bl\\t%__interwork_call_via_%1\";
7802    else if (frame_pointer_needed)
7803      return \"bl\\t%__interwork_r7_call_via_%1\";
7804    else
7805      return \"bl\\t%__interwork_r11_call_via_%1\";
7806  }"
7807  [(set_attr "type" "call")]
7808)
7809
7810;; Allow calls to SYMBOL_REFs specially as they are not valid general addresses
7811;; The 'a' causes the operand to be treated as an address, i.e. no '#' output.
7812
7813(define_insn "*call_symbol"
7814  [(call (mem:SI (match_operand:SI 0 "" ""))
7815	 (match_operand 1 "" ""))
7816   (use (match_operand 2 "" ""))
7817   (clobber (reg:SI LR_REGNUM))]
7818  "TARGET_ARM
7819   && (GET_CODE (operands[0]) == SYMBOL_REF)
7820   && !arm_is_longcall_p (operands[0], INTVAL (operands[2]), 1)"
7821  "*
7822  {
7823    return NEED_PLT_RELOC ? \"bl%?\\t%a0(PLT)\" : \"bl%?\\t%a0\";
7824  }"
7825  [(set_attr "type" "call")]
7826)
7827
7828(define_insn "*call_value_symbol"
7829  [(set (match_operand 0 "" "")
7830	(call (mem:SI (match_operand:SI 1 "" ""))
7831	(match_operand:SI 2 "" "")))
7832   (use (match_operand 3 "" ""))
7833   (clobber (reg:SI LR_REGNUM))]
7834  "TARGET_ARM
7835   && (GET_CODE (operands[1]) == SYMBOL_REF)
7836   && !arm_is_longcall_p (operands[1], INTVAL (operands[3]), 1)"
7837  "*
7838  {
7839    return NEED_PLT_RELOC ? \"bl%?\\t%a1(PLT)\" : \"bl%?\\t%a1\";
7840  }"
7841  [(set_attr "type" "call")]
7842)
7843
7844(define_insn "*call_insn"
7845  [(call (mem:SI (match_operand:SI 0 "" ""))
7846	 (match_operand:SI 1 "" ""))
7847   (use (match_operand 2 "" ""))
7848   (clobber (reg:SI LR_REGNUM))]
7849  "TARGET_THUMB
7850   && GET_CODE (operands[0]) == SYMBOL_REF
7851   && !arm_is_longcall_p (operands[0], INTVAL (operands[2]), 1)"
7852  "bl\\t%a0"
7853  [(set_attr "length" "4")
7854   (set_attr "type" "call")]
7855)
7856
7857(define_insn "*call_value_insn"
7858  [(set (match_operand 0 "" "")
7859	(call (mem:SI (match_operand 1 "" ""))
7860	      (match_operand 2 "" "")))
7861   (use (match_operand 3 "" ""))
7862   (clobber (reg:SI LR_REGNUM))]
7863  "TARGET_THUMB
7864   && GET_CODE (operands[1]) == SYMBOL_REF
7865   && !arm_is_longcall_p (operands[1], INTVAL (operands[3]), 1)"
7866  "bl\\t%a1"
7867  [(set_attr "length" "4")
7868   (set_attr "type" "call")]
7869)
7870
7871;; We may also be able to do sibcalls for Thumb, but it's much harder...
7872(define_expand "sibcall"
7873  [(parallel [(call (match_operand 0 "memory_operand" "")
7874		    (match_operand 1 "general_operand" ""))
7875	      (return)
7876	      (use (match_operand 2 "" ""))])]
7877  "TARGET_ARM"
7878  "
7879  {
7880    if (operands[2] == NULL_RTX)
7881      operands[2] = const0_rtx;
7882  }"
7883)
7884
7885(define_expand "sibcall_value"
7886  [(parallel [(set (match_operand 0 "" "")
7887		   (call (match_operand 1 "memory_operand" "")
7888			 (match_operand 2 "general_operand" "")))
7889	      (return)
7890	      (use (match_operand 3 "" ""))])]
7891  "TARGET_ARM"
7892  "
7893  {
7894    if (operands[3] == NULL_RTX)
7895      operands[3] = const0_rtx;
7896  }"
7897)
7898
7899(define_insn "*sibcall_insn"
7900 [(call (mem:SI (match_operand:SI 0 "" "X"))
7901	(match_operand 1 "" ""))
7902  (return)
7903  (use (match_operand 2 "" ""))]
7904  "TARGET_ARM && GET_CODE (operands[0]) == SYMBOL_REF"
7905  "*
7906  return NEED_PLT_RELOC ? \"b%?\\t%a0(PLT)\" : \"b%?\\t%a0\";
7907  "
7908  [(set_attr "type" "call")]
7909)
7910
7911(define_insn "*sibcall_value_insn"
7912 [(set (match_operand 0 "" "")
7913       (call (mem:SI (match_operand:SI 1 "" "X"))
7914	     (match_operand 2 "" "")))
7915  (return)
7916  (use (match_operand 3 "" ""))]
7917  "TARGET_ARM && GET_CODE (operands[1]) == SYMBOL_REF"
7918  "*
7919  return NEED_PLT_RELOC ? \"b%?\\t%a1(PLT)\" : \"b%?\\t%a1\";
7920  "
7921  [(set_attr "type" "call")]
7922)
7923
7924;; Often the return insn will be the same as loading from memory, so set attr
7925(define_insn "return"
7926  [(return)]
7927  "TARGET_ARM && USE_RETURN_INSN (FALSE)"
7928  "*
7929  {
7930    if (arm_ccfsm_state == 2)
7931      {
7932        arm_ccfsm_state += 2;
7933        return \"\";
7934      }
7935    return output_return_instruction (const_true_rtx, TRUE, FALSE);
7936  }"
7937  [(set_attr "type" "load1")
7938   (set_attr "length" "12")
7939   (set_attr "predicable" "yes")]
7940)
7941
7942(define_insn "*cond_return"
7943  [(set (pc)
7944        (if_then_else (match_operator 0 "arm_comparison_operator"
7945		       [(match_operand 1 "cc_register" "") (const_int 0)])
7946                      (return)
7947                      (pc)))]
7948  "TARGET_ARM && USE_RETURN_INSN (TRUE)"
7949  "*
7950  {
7951    if (arm_ccfsm_state == 2)
7952      {
7953        arm_ccfsm_state += 2;
7954        return \"\";
7955      }
7956    return output_return_instruction (operands[0], TRUE, FALSE);
7957  }"
7958  [(set_attr "conds" "use")
7959   (set_attr "length" "12")
7960   (set_attr "type" "load1")]
7961)
7962
7963(define_insn "*cond_return_inverted"
7964  [(set (pc)
7965        (if_then_else (match_operator 0 "arm_comparison_operator"
7966		       [(match_operand 1 "cc_register" "") (const_int 0)])
7967                      (pc)
7968		      (return)))]
7969  "TARGET_ARM && USE_RETURN_INSN (TRUE)"
7970  "*
7971  {
7972    if (arm_ccfsm_state == 2)
7973      {
7974        arm_ccfsm_state += 2;
7975        return \"\";
7976      }
7977    return output_return_instruction (operands[0], TRUE, TRUE);
7978  }"
7979  [(set_attr "conds" "use")
7980   (set_attr "length" "12")
7981   (set_attr "type" "load1")]
7982)
7983
7984;; Generate a sequence of instructions to determine if the processor is
7985;; in 26-bit or 32-bit mode, and return the appropriate return address
7986;; mask.
7987
7988(define_expand "return_addr_mask"
7989  [(set (match_dup 1)
7990      (compare:CC_NOOV (unspec [(const_int 0)] UNSPEC_CHECK_ARCH)
7991		       (const_int 0)))
7992   (set (match_operand:SI 0 "s_register_operand" "")
7993      (if_then_else:SI (eq (match_dup 1) (const_int 0))
7994		       (const_int -1)
7995		       (const_int 67108860)))] ; 0x03fffffc
7996  "TARGET_ARM"
7997  "
7998  operands[1] = gen_rtx_REG (CC_NOOVmode, CC_REGNUM);
7999  ")
8000
8001(define_insn "*check_arch2"
8002  [(set (match_operand:CC_NOOV 0 "cc_register" "")
8003      (compare:CC_NOOV (unspec [(const_int 0)] UNSPEC_CHECK_ARCH)
8004		       (const_int 0)))]
8005  "TARGET_ARM"
8006  "teq\\t%|r0, %|r0\;teq\\t%|pc, %|pc"
8007  [(set_attr "length" "8")
8008   (set_attr "conds" "set")]
8009)
8010
8011;; Call subroutine returning any type.
8012
8013(define_expand "untyped_call"
8014  [(parallel [(call (match_operand 0 "" "")
8015		    (const_int 0))
8016	      (match_operand 1 "" "")
8017	      (match_operand 2 "" "")])]
8018  "TARGET_EITHER"
8019  "
8020  {
8021    int i;
8022    rtx par = gen_rtx_PARALLEL (VOIDmode,
8023				rtvec_alloc (XVECLEN (operands[2], 0)));
8024    rtx addr = gen_reg_rtx (Pmode);
8025    rtx mem;
8026    int size = 0;
8027
8028    emit_move_insn (addr, XEXP (operands[1], 0));
8029    mem = change_address (operands[1], BLKmode, addr);
8030
8031    for (i = 0; i < XVECLEN (operands[2], 0); i++)
8032      {
8033	rtx src = SET_SRC (XVECEXP (operands[2], 0, i));
8034
8035	/* Default code only uses r0 as a return value, but we could
8036	   be using anything up to 4 registers.  */
8037	if (REGNO (src) == R0_REGNUM)
8038	  src = gen_rtx_REG (TImode, R0_REGNUM);
8039
8040        XVECEXP (par, 0, i) = gen_rtx_EXPR_LIST (VOIDmode, src,
8041						 GEN_INT (size));
8042        size += GET_MODE_SIZE (GET_MODE (src));
8043      }
8044
8045    emit_call_insn (GEN_CALL_VALUE (par, operands[0], const0_rtx, NULL,
8046				    const0_rtx));
8047
8048    size = 0;
8049
8050    for (i = 0; i < XVECLEN (par, 0); i++)
8051      {
8052	HOST_WIDE_INT offset = 0;
8053	rtx reg = XEXP (XVECEXP (par, 0, i), 0);
8054
8055	if (size != 0)
8056	  emit_move_insn (addr, plus_constant (addr, size));
8057
8058	mem = change_address (mem, GET_MODE (reg), NULL);
8059	if (REGNO (reg) == R0_REGNUM)
8060	  {
8061	    /* On thumb we have to use a write-back instruction.  */
8062	    emit_insn (arm_gen_store_multiple (R0_REGNUM, 4, addr, TRUE,
8063			TARGET_THUMB ? TRUE : FALSE, mem, &offset));
8064	    size = TARGET_ARM ? 16 : 0;
8065	  }
8066	else
8067	  {
8068	    emit_move_insn (mem, reg);
8069	    size = GET_MODE_SIZE (GET_MODE (reg));
8070	  }
8071      }
8072
8073    /* The optimizer does not know that the call sets the function value
8074       registers we stored in the result block.  We avoid problems by
8075       claiming that all hard registers are used and clobbered at this
8076       point.  */
8077    emit_insn (gen_blockage ());
8078
8079    DONE;
8080  }"
8081)
8082
8083(define_expand "untyped_return"
8084  [(match_operand:BLK 0 "memory_operand" "")
8085   (match_operand 1 "" "")]
8086  "TARGET_EITHER"
8087  "
8088  {
8089    int i;
8090    rtx addr = gen_reg_rtx (Pmode);
8091    rtx mem;
8092    int size = 0;
8093
8094    emit_move_insn (addr, XEXP (operands[0], 0));
8095    mem = change_address (operands[0], BLKmode, addr);
8096
8097    for (i = 0; i < XVECLEN (operands[1], 0); i++)
8098      {
8099	HOST_WIDE_INT offset = 0;
8100	rtx reg = SET_DEST (XVECEXP (operands[1], 0, i));
8101
8102	if (size != 0)
8103	  emit_move_insn (addr, plus_constant (addr, size));
8104
8105	mem = change_address (mem, GET_MODE (reg), NULL);
8106	if (REGNO (reg) == R0_REGNUM)
8107	  {
8108	    /* On thumb we have to use a write-back instruction.  */
8109	    emit_insn (arm_gen_load_multiple (R0_REGNUM, 4, addr, TRUE,
8110			TARGET_THUMB ? TRUE : FALSE, mem, &offset));
8111	    size = TARGET_ARM ? 16 : 0;
8112	  }
8113	else
8114	  {
8115	    emit_move_insn (reg, mem);
8116	    size = GET_MODE_SIZE (GET_MODE (reg));
8117	  }
8118      }
8119
8120    /* Emit USE insns before the return.  */
8121    for (i = 0; i < XVECLEN (operands[1], 0); i++)
8122      emit_insn (gen_rtx_USE (VOIDmode,
8123			      SET_DEST (XVECEXP (operands[1], 0, i))));
8124
8125    /* Construct the return.  */
8126    expand_naked_return ();
8127
8128    DONE;
8129  }"
8130)
8131
8132;; UNSPEC_VOLATILE is considered to use and clobber all hard registers and
8133;; all of memory.  This blocks insns from being moved across this point.
8134
8135(define_insn "blockage"
8136  [(unspec_volatile [(const_int 0)] VUNSPEC_BLOCKAGE)]
8137  "TARGET_EITHER"
8138  ""
8139  [(set_attr "length" "0")
8140   (set_attr "type" "block")]
8141)
8142
8143(define_expand "casesi"
8144  [(match_operand:SI 0 "s_register_operand" "")	; index to jump on
8145   (match_operand:SI 1 "const_int_operand" "")	; lower bound
8146   (match_operand:SI 2 "const_int_operand" "")	; total range
8147   (match_operand:SI 3 "" "")			; table label
8148   (match_operand:SI 4 "" "")]			; Out of range label
8149  "TARGET_ARM"
8150  "
8151  {
8152    rtx reg;
8153    if (operands[1] != const0_rtx)
8154      {
8155	reg = gen_reg_rtx (SImode);
8156
8157	emit_insn (gen_addsi3 (reg, operands[0],
8158			       GEN_INT (-INTVAL (operands[1]))));
8159	operands[0] = reg;
8160      }
8161
8162    if (!const_ok_for_arm (INTVAL (operands[2])))
8163      operands[2] = force_reg (SImode, operands[2]);
8164
8165    emit_jump_insn (gen_casesi_internal (operands[0], operands[2], operands[3],
8166					 operands[4]));
8167    DONE;
8168  }"
8169)
8170
8171;; The USE in this pattern is needed to tell flow analysis that this is
8172;; a CASESI insn.  It has no other purpose.
8173(define_insn "casesi_internal"
8174  [(parallel [(set (pc)
8175	       (if_then_else
8176		(leu (match_operand:SI 0 "s_register_operand" "r")
8177		     (match_operand:SI 1 "arm_rhs_operand" "rI"))
8178		(mem:SI (plus:SI (mult:SI (match_dup 0) (const_int 4))
8179				 (label_ref (match_operand 2 "" ""))))
8180		(label_ref (match_operand 3 "" ""))))
8181	      (clobber (reg:CC CC_REGNUM))
8182	      (use (label_ref (match_dup 2)))])]
8183  "TARGET_ARM"
8184  "*
8185    if (flag_pic)
8186      return \"cmp\\t%0, %1\;addls\\t%|pc, %|pc, %0, asl #2\;b\\t%l3\";
8187    return   \"cmp\\t%0, %1\;ldrls\\t%|pc, [%|pc, %0, asl #2]\;b\\t%l3\";
8188  "
8189  [(set_attr "conds" "clob")
8190   (set_attr "length" "12")]
8191)
8192
8193(define_expand "indirect_jump"
8194  [(set (pc)
8195	(match_operand:SI 0 "s_register_operand" ""))]
8196  "TARGET_EITHER"
8197  ""
8198)
8199
8200;; NB Never uses BX.
8201(define_insn "*arm_indirect_jump"
8202  [(set (pc)
8203	(match_operand:SI 0 "s_register_operand" "r"))]
8204  "TARGET_ARM"
8205  "mov%?\\t%|pc, %0\\t%@ indirect register jump"
8206  [(set_attr "predicable" "yes")]
8207)
8208
8209(define_insn "*load_indirect_jump"
8210  [(set (pc)
8211	(match_operand:SI 0 "memory_operand" "m"))]
8212  "TARGET_ARM"
8213  "ldr%?\\t%|pc, %0\\t%@ indirect memory jump"
8214  [(set_attr "type" "load1")
8215   (set_attr "pool_range" "4096")
8216   (set_attr "neg_pool_range" "4084")
8217   (set_attr "predicable" "yes")]
8218)
8219
8220;; NB Never uses BX.
8221(define_insn "*thumb_indirect_jump"
8222  [(set (pc)
8223	(match_operand:SI 0 "register_operand" "l*r"))]
8224  "TARGET_THUMB"
8225  "mov\\tpc, %0"
8226  [(set_attr "conds" "clob")
8227   (set_attr "length" "2")]
8228)
8229
8230
8231;; Misc insns
8232
8233(define_insn "nop"
8234  [(const_int 0)]
8235  "TARGET_EITHER"
8236  "*
8237  if (TARGET_ARM)
8238    return \"mov%?\\t%|r0, %|r0\\t%@ nop\";
8239  return  \"mov\\tr8, r8\";
8240  "
8241  [(set (attr "length")
8242	(if_then_else (eq_attr "is_thumb" "yes")
8243		      (const_int 2)
8244		      (const_int 4)))]
8245)
8246
8247
8248;; Patterns to allow combination of arithmetic, cond code and shifts
8249
8250(define_insn "*arith_shiftsi"
8251  [(set (match_operand:SI 0 "s_register_operand" "=r")
8252        (match_operator:SI 1 "shiftable_operator"
8253          [(match_operator:SI 3 "shift_operator"
8254             [(match_operand:SI 4 "s_register_operand" "r")
8255              (match_operand:SI 5 "reg_or_int_operand" "rI")])
8256           (match_operand:SI 2 "s_register_operand" "r")]))]
8257  "TARGET_ARM"
8258  "%i1%?\\t%0, %2, %4%S3"
8259  [(set_attr "predicable" "yes")
8260   (set_attr "shift" "4")
8261   (set (attr "type") (if_then_else (match_operand 5 "const_int_operand" "")
8262		      (const_string "alu_shift")
8263		      (const_string "alu_shift_reg")))]
8264)
8265
8266(define_split
8267  [(set (match_operand:SI 0 "s_register_operand" "")
8268	(match_operator:SI 1 "shiftable_operator"
8269	 [(match_operator:SI 2 "shiftable_operator"
8270	   [(match_operator:SI 3 "shift_operator"
8271	     [(match_operand:SI 4 "s_register_operand" "")
8272	      (match_operand:SI 5 "reg_or_int_operand" "")])
8273	    (match_operand:SI 6 "s_register_operand" "")])
8274	  (match_operand:SI 7 "arm_rhs_operand" "")]))
8275   (clobber (match_operand:SI 8 "s_register_operand" ""))]
8276  "TARGET_ARM"
8277  [(set (match_dup 8)
8278	(match_op_dup 2 [(match_op_dup 3 [(match_dup 4) (match_dup 5)])
8279			 (match_dup 6)]))
8280   (set (match_dup 0)
8281	(match_op_dup 1 [(match_dup 8) (match_dup 7)]))]
8282  "")
8283
8284(define_insn "*arith_shiftsi_compare0"
8285  [(set (reg:CC_NOOV CC_REGNUM)
8286        (compare:CC_NOOV (match_operator:SI 1 "shiftable_operator"
8287		          [(match_operator:SI 3 "shift_operator"
8288		            [(match_operand:SI 4 "s_register_operand" "r")
8289		             (match_operand:SI 5 "reg_or_int_operand" "rI")])
8290		           (match_operand:SI 2 "s_register_operand" "r")])
8291			 (const_int 0)))
8292   (set (match_operand:SI 0 "s_register_operand" "=r")
8293	(match_op_dup 1 [(match_op_dup 3 [(match_dup 4) (match_dup 5)])
8294			 (match_dup 2)]))]
8295  "TARGET_ARM"
8296  "%i1%?s\\t%0, %2, %4%S3"
8297  [(set_attr "conds" "set")
8298   (set_attr "shift" "4")
8299   (set (attr "type") (if_then_else (match_operand 5 "const_int_operand" "")
8300		      (const_string "alu_shift")
8301		      (const_string "alu_shift_reg")))]
8302)
8303
8304(define_insn "*arith_shiftsi_compare0_scratch"
8305  [(set (reg:CC_NOOV CC_REGNUM)
8306        (compare:CC_NOOV (match_operator:SI 1 "shiftable_operator"
8307		          [(match_operator:SI 3 "shift_operator"
8308		            [(match_operand:SI 4 "s_register_operand" "r")
8309		             (match_operand:SI 5 "reg_or_int_operand" "rI")])
8310		           (match_operand:SI 2 "s_register_operand" "r")])
8311			 (const_int 0)))
8312   (clobber (match_scratch:SI 0 "=r"))]
8313  "TARGET_ARM"
8314  "%i1%?s\\t%0, %2, %4%S3"
8315  [(set_attr "conds" "set")
8316   (set_attr "shift" "4")
8317   (set (attr "type") (if_then_else (match_operand 5 "const_int_operand" "")
8318		      (const_string "alu_shift")
8319		      (const_string "alu_shift_reg")))]
8320)
8321
8322(define_insn "*sub_shiftsi"
8323  [(set (match_operand:SI 0 "s_register_operand" "=r")
8324	(minus:SI (match_operand:SI 1 "s_register_operand" "r")
8325		  (match_operator:SI 2 "shift_operator"
8326		   [(match_operand:SI 3 "s_register_operand" "r")
8327		    (match_operand:SI 4 "reg_or_int_operand" "rM")])))]
8328  "TARGET_ARM"
8329  "sub%?\\t%0, %1, %3%S2"
8330  [(set_attr "predicable" "yes")
8331   (set_attr "shift" "3")
8332   (set (attr "type") (if_then_else (match_operand 4 "const_int_operand" "")
8333		      (const_string "alu_shift")
8334		      (const_string "alu_shift_reg")))]
8335)
8336
8337(define_insn "*sub_shiftsi_compare0"
8338  [(set (reg:CC_NOOV CC_REGNUM)
8339	(compare:CC_NOOV
8340	 (minus:SI (match_operand:SI 1 "s_register_operand" "r")
8341		   (match_operator:SI 2 "shift_operator"
8342		    [(match_operand:SI 3 "s_register_operand" "r")
8343		     (match_operand:SI 4 "reg_or_int_operand" "rM")]))
8344	 (const_int 0)))
8345   (set (match_operand:SI 0 "s_register_operand" "=r")
8346	(minus:SI (match_dup 1) (match_op_dup 2 [(match_dup 3)
8347						 (match_dup 4)])))]
8348  "TARGET_ARM"
8349  "sub%?s\\t%0, %1, %3%S2"
8350  [(set_attr "conds" "set")
8351   (set_attr "shift" "3")
8352   (set (attr "type") (if_then_else (match_operand 4 "const_int_operand" "")
8353		      (const_string "alu_shift")
8354		      (const_string "alu_shift_reg")))]
8355)
8356
8357(define_insn "*sub_shiftsi_compare0_scratch"
8358  [(set (reg:CC_NOOV CC_REGNUM)
8359	(compare:CC_NOOV
8360	 (minus:SI (match_operand:SI 1 "s_register_operand" "r")
8361		   (match_operator:SI 2 "shift_operator"
8362		    [(match_operand:SI 3 "s_register_operand" "r")
8363		     (match_operand:SI 4 "reg_or_int_operand" "rM")]))
8364	 (const_int 0)))
8365   (clobber (match_scratch:SI 0 "=r"))]
8366  "TARGET_ARM"
8367  "sub%?s\\t%0, %1, %3%S2"
8368  [(set_attr "conds" "set")
8369   (set_attr "shift" "3")
8370   (set (attr "type") (if_then_else (match_operand 4 "const_int_operand" "")
8371		      (const_string "alu_shift")
8372		      (const_string "alu_shift_reg")))]
8373)
8374
8375
8376
8377(define_insn "*and_scc"
8378  [(set (match_operand:SI 0 "s_register_operand" "=r")
8379	(and:SI (match_operator:SI 1 "arm_comparison_operator"
8380		 [(match_operand 3 "cc_register" "") (const_int 0)])
8381		(match_operand:SI 2 "s_register_operand" "r")))]
8382  "TARGET_ARM"
8383  "mov%D1\\t%0, #0\;and%d1\\t%0, %2, #1"
8384  [(set_attr "conds" "use")
8385   (set_attr "length" "8")]
8386)
8387
8388(define_insn "*ior_scc"
8389  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
8390	(ior:SI (match_operator:SI 2 "arm_comparison_operator"
8391		 [(match_operand 3 "cc_register" "") (const_int 0)])
8392		(match_operand:SI 1 "s_register_operand" "0,?r")))]
8393  "TARGET_ARM"
8394  "@
8395   orr%d2\\t%0, %1, #1
8396   mov%D2\\t%0, %1\;orr%d2\\t%0, %1, #1"
8397  [(set_attr "conds" "use")
8398   (set_attr "length" "4,8")]
8399)
8400
8401(define_insn "*compare_scc"
8402  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
8403	(match_operator:SI 1 "arm_comparison_operator"
8404	 [(match_operand:SI 2 "s_register_operand" "r,r")
8405	  (match_operand:SI 3 "arm_add_operand" "rI,L")]))
8406   (clobber (reg:CC CC_REGNUM))]
8407  "TARGET_ARM"
8408  "*
8409    if (operands[3] == const0_rtx)
8410      {
8411	if (GET_CODE (operands[1]) == LT)
8412	  return \"mov\\t%0, %2, lsr #31\";
8413
8414	if (GET_CODE (operands[1]) == GE)
8415	  return \"mvn\\t%0, %2\;mov\\t%0, %0, lsr #31\";
8416
8417	if (GET_CODE (operands[1]) == EQ)
8418	  return \"rsbs\\t%0, %2, #1\;movcc\\t%0, #0\";
8419      }
8420
8421    if (GET_CODE (operands[1]) == NE)
8422      {
8423        if (which_alternative == 1)
8424	  return \"adds\\t%0, %2, #%n3\;movne\\t%0, #1\";
8425        return \"subs\\t%0, %2, %3\;movne\\t%0, #1\";
8426      }
8427    if (which_alternative == 1)
8428      output_asm_insn (\"cmn\\t%2, #%n3\", operands);
8429    else
8430      output_asm_insn (\"cmp\\t%2, %3\", operands);
8431    return \"mov%D1\\t%0, #0\;mov%d1\\t%0, #1\";
8432  "
8433  [(set_attr "conds" "clob")
8434   (set_attr "length" "12")]
8435)
8436
8437(define_insn "*cond_move"
8438  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
8439	(if_then_else:SI (match_operator 3 "equality_operator"
8440			  [(match_operator 4 "arm_comparison_operator"
8441			    [(match_operand 5 "cc_register" "") (const_int 0)])
8442			   (const_int 0)])
8443			 (match_operand:SI 1 "arm_rhs_operand" "0,rI,?rI")
8444			 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))]
8445  "TARGET_ARM"
8446  "*
8447    if (GET_CODE (operands[3]) == NE)
8448      {
8449        if (which_alternative != 1)
8450	  output_asm_insn (\"mov%D4\\t%0, %2\", operands);
8451        if (which_alternative != 0)
8452	  output_asm_insn (\"mov%d4\\t%0, %1\", operands);
8453        return \"\";
8454      }
8455    if (which_alternative != 0)
8456      output_asm_insn (\"mov%D4\\t%0, %1\", operands);
8457    if (which_alternative != 1)
8458      output_asm_insn (\"mov%d4\\t%0, %2\", operands);
8459    return \"\";
8460  "
8461  [(set_attr "conds" "use")
8462   (set_attr "length" "4,4,8")]
8463)
8464
8465(define_insn "*cond_arith"
8466  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
8467        (match_operator:SI 5 "shiftable_operator" 
8468	 [(match_operator:SI 4 "arm_comparison_operator"
8469           [(match_operand:SI 2 "s_register_operand" "r,r")
8470	    (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
8471          (match_operand:SI 1 "s_register_operand" "0,?r")]))
8472   (clobber (reg:CC CC_REGNUM))]
8473  "TARGET_ARM"
8474  "*
8475    if (GET_CODE (operands[4]) == LT && operands[3] == const0_rtx)
8476      return \"%i5\\t%0, %1, %2, lsr #31\";
8477
8478    output_asm_insn (\"cmp\\t%2, %3\", operands);
8479    if (GET_CODE (operands[5]) == AND)
8480      output_asm_insn (\"mov%D4\\t%0, #0\", operands);
8481    else if (GET_CODE (operands[5]) == MINUS)
8482      output_asm_insn (\"rsb%D4\\t%0, %1, #0\", operands);
8483    else if (which_alternative != 0)
8484      output_asm_insn (\"mov%D4\\t%0, %1\", operands);
8485    return \"%i5%d4\\t%0, %1, #1\";
8486  "
8487  [(set_attr "conds" "clob")
8488   (set_attr "length" "12")]
8489)
8490
8491(define_insn "*cond_sub"
8492  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
8493        (minus:SI (match_operand:SI 1 "s_register_operand" "0,?r")
8494		  (match_operator:SI 4 "arm_comparison_operator"
8495                   [(match_operand:SI 2 "s_register_operand" "r,r")
8496		    (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))
8497   (clobber (reg:CC CC_REGNUM))]
8498  "TARGET_ARM"
8499  "*
8500    output_asm_insn (\"cmp\\t%2, %3\", operands);
8501    if (which_alternative != 0)
8502      output_asm_insn (\"mov%D4\\t%0, %1\", operands);
8503    return \"sub%d4\\t%0, %1, #1\";
8504  "
8505  [(set_attr "conds" "clob")
8506   (set_attr "length" "8,12")]
8507)
8508
8509(define_insn "*cmp_ite0"
8510  [(set (match_operand 6 "dominant_cc_register" "")
8511	(compare
8512	 (if_then_else:SI
8513	  (match_operator 4 "arm_comparison_operator"
8514	   [(match_operand:SI 0 "s_register_operand" "r,r,r,r")
8515	    (match_operand:SI 1 "arm_add_operand" "rI,L,rI,L")])
8516	  (match_operator:SI 5 "arm_comparison_operator"
8517	   [(match_operand:SI 2 "s_register_operand" "r,r,r,r")
8518	    (match_operand:SI 3 "arm_add_operand" "rI,rI,L,L")])
8519	  (const_int 0))
8520	 (const_int 0)))]
8521  "TARGET_ARM"
8522  "*
8523  {
8524    static const char * const opcodes[4][2] =
8525    {
8526      {\"cmp\\t%2, %3\;cmp%d5\\t%0, %1\",
8527       \"cmp\\t%0, %1\;cmp%d4\\t%2, %3\"},
8528      {\"cmp\\t%2, %3\;cmn%d5\\t%0, #%n1\",
8529       \"cmn\\t%0, #%n1\;cmp%d4\\t%2, %3\"},
8530      {\"cmn\\t%2, #%n3\;cmp%d5\\t%0, %1\",
8531       \"cmp\\t%0, %1\;cmn%d4\\t%2, #%n3\"},
8532      {\"cmn\\t%2, #%n3\;cmn%d5\\t%0, #%n1\",
8533       \"cmn\\t%0, #%n1\;cmn%d4\\t%2, #%n3\"}
8534    };
8535    int swap =
8536      comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
8537
8538    return opcodes[which_alternative][swap];
8539  }"
8540  [(set_attr "conds" "set")
8541   (set_attr "length" "8")]
8542)
8543
8544(define_insn "*cmp_ite1"
8545  [(set (match_operand 6 "dominant_cc_register" "")
8546	(compare
8547	 (if_then_else:SI
8548	  (match_operator 4 "arm_comparison_operator"
8549	   [(match_operand:SI 0 "s_register_operand" "r,r,r,r")
8550	    (match_operand:SI 1 "arm_add_operand" "rI,L,rI,L")])
8551	  (match_operator:SI 5 "arm_comparison_operator"
8552	   [(match_operand:SI 2 "s_register_operand" "r,r,r,r")
8553	    (match_operand:SI 3 "arm_add_operand" "rI,rI,L,L")])
8554	  (const_int 1))
8555	 (const_int 0)))]
8556  "TARGET_ARM"
8557  "*
8558  {
8559    static const char * const opcodes[4][2] =
8560    {
8561      {\"cmp\\t%0, %1\;cmp%d4\\t%2, %3\",
8562       \"cmp\\t%2, %3\;cmp%D5\\t%0, %1\"},
8563      {\"cmn\\t%0, #%n1\;cmp%d4\\t%2, %3\",
8564       \"cmp\\t%2, %3\;cmn%D5\\t%0, #%n1\"},
8565      {\"cmp\\t%0, %1\;cmn%d4\\t%2, #%n3\",
8566       \"cmn\\t%2, #%n3\;cmp%D5\\t%0, %1\"},
8567      {\"cmn\\t%0, #%n1\;cmn%d4\\t%2, #%n3\",
8568       \"cmn\\t%2, #%n3\;cmn%D5\\t%0, #%n1\"}
8569    };
8570    int swap =
8571      comparison_dominates_p (GET_CODE (operands[5]),
8572			      reverse_condition (GET_CODE (operands[4])));
8573
8574    return opcodes[which_alternative][swap];
8575  }"
8576  [(set_attr "conds" "set")
8577   (set_attr "length" "8")]
8578)
8579
8580(define_insn "*cmp_and"
8581  [(set (match_operand 6 "dominant_cc_register" "")
8582	(compare
8583	 (and:SI
8584	  (match_operator 4 "arm_comparison_operator"
8585	   [(match_operand:SI 0 "s_register_operand" "r,r,r,r")
8586	    (match_operand:SI 1 "arm_add_operand" "rI,L,rI,L")])
8587	  (match_operator:SI 5 "arm_comparison_operator"
8588	   [(match_operand:SI 2 "s_register_operand" "r,r,r,r")
8589	    (match_operand:SI 3 "arm_add_operand" "rI,rI,L,L")]))
8590	 (const_int 0)))]
8591  "TARGET_ARM"
8592  "*
8593  {
8594    static const char *const opcodes[4][2] =
8595    {
8596      {\"cmp\\t%2, %3\;cmp%d5\\t%0, %1\",
8597       \"cmp\\t%0, %1\;cmp%d4\\t%2, %3\"},
8598      {\"cmp\\t%2, %3\;cmn%d5\\t%0, #%n1\",
8599       \"cmn\\t%0, #%n1\;cmp%d4\\t%2, %3\"},
8600      {\"cmn\\t%2, #%n3\;cmp%d5\\t%0, %1\",
8601       \"cmp\\t%0, %1\;cmn%d4\\t%2, #%n3\"},
8602      {\"cmn\\t%2, #%n3\;cmn%d5\\t%0, #%n1\",
8603       \"cmn\\t%0, #%n1\;cmn%d4\\t%2, #%n3\"}
8604    };
8605    int swap =
8606      comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
8607
8608    return opcodes[which_alternative][swap];
8609  }"
8610  [(set_attr "conds" "set")
8611   (set_attr "predicable" "no")
8612   (set_attr "length" "8")]
8613)
8614
8615(define_insn "*cmp_ior"
8616  [(set (match_operand 6 "dominant_cc_register" "")
8617	(compare
8618	 (ior:SI
8619	  (match_operator 4 "arm_comparison_operator"
8620	   [(match_operand:SI 0 "s_register_operand" "r,r,r,r")
8621	    (match_operand:SI 1 "arm_add_operand" "rI,L,rI,L")])
8622	  (match_operator:SI 5 "arm_comparison_operator"
8623	   [(match_operand:SI 2 "s_register_operand" "r,r,r,r")
8624	    (match_operand:SI 3 "arm_add_operand" "rI,rI,L,L")]))
8625	 (const_int 0)))]
8626  "TARGET_ARM"
8627  "*
8628{
8629  static const char *const opcodes[4][2] =
8630  {
8631    {\"cmp\\t%0, %1\;cmp%D4\\t%2, %3\",
8632     \"cmp\\t%2, %3\;cmp%D5\\t%0, %1\"},
8633    {\"cmn\\t%0, #%n1\;cmp%D4\\t%2, %3\",
8634     \"cmp\\t%2, %3\;cmn%D5\\t%0, #%n1\"},
8635    {\"cmp\\t%0, %1\;cmn%D4\\t%2, #%n3\",
8636     \"cmn\\t%2, #%n3\;cmp%D5\\t%0, %1\"},
8637    {\"cmn\\t%0, #%n1\;cmn%D4\\t%2, #%n3\",
8638     \"cmn\\t%2, #%n3\;cmn%D5\\t%0, #%n1\"}
8639  };
8640  int swap =
8641    comparison_dominates_p (GET_CODE (operands[5]), GET_CODE (operands[4]));
8642
8643  return opcodes[which_alternative][swap];
8644}
8645"
8646  [(set_attr "conds" "set")
8647   (set_attr "length" "8")]
8648)
8649
8650(define_insn_and_split "*ior_scc_scc"
8651  [(set (match_operand:SI 0 "s_register_operand" "=r")
8652	(ior:SI (match_operator:SI 3 "arm_comparison_operator"
8653		 [(match_operand:SI 1 "s_register_operand" "r")
8654		  (match_operand:SI 2 "arm_add_operand" "rIL")])
8655		(match_operator:SI 6 "arm_comparison_operator"
8656		 [(match_operand:SI 4 "s_register_operand" "r")
8657		  (match_operand:SI 5 "arm_add_operand" "rIL")])))
8658   (clobber (reg:CC CC_REGNUM))]
8659  "TARGET_ARM
8660   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_OR_Y)
8661       != CCmode)"
8662  "#"
8663  "TARGET_ARM && reload_completed"
8664  [(set (match_dup 7)
8665	(compare
8666	 (ior:SI
8667	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
8668	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
8669	 (const_int 0)))
8670   (set (match_dup 0) (ne:SI (match_dup 7) (const_int 0)))]
8671  "operands[7]
8672     = gen_rtx_REG (arm_select_dominance_cc_mode (operands[3], operands[6],
8673						  DOM_CC_X_OR_Y),
8674		    CC_REGNUM);"
8675  [(set_attr "conds" "clob")
8676   (set_attr "length" "16")])
8677
8678; If the above pattern is followed by a CMP insn, then the compare is 
8679; redundant, since we can rework the conditional instruction that follows.
8680(define_insn_and_split "*ior_scc_scc_cmp"
8681  [(set (match_operand 0 "dominant_cc_register" "")
8682	(compare (ior:SI (match_operator:SI 3 "arm_comparison_operator"
8683			  [(match_operand:SI 1 "s_register_operand" "r")
8684			   (match_operand:SI 2 "arm_add_operand" "rIL")])
8685			 (match_operator:SI 6 "arm_comparison_operator"
8686			  [(match_operand:SI 4 "s_register_operand" "r")
8687			   (match_operand:SI 5 "arm_add_operand" "rIL")]))
8688		 (const_int 0)))
8689   (set (match_operand:SI 7 "s_register_operand" "=r")
8690	(ior:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])
8691		(match_op_dup 6 [(match_dup 4) (match_dup 5)])))]
8692  "TARGET_ARM"
8693  "#"
8694  "TARGET_ARM && reload_completed"
8695  [(set (match_dup 0)
8696	(compare
8697	 (ior:SI
8698	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
8699	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
8700	 (const_int 0)))
8701   (set (match_dup 7) (ne:SI (match_dup 0) (const_int 0)))]
8702  ""
8703  [(set_attr "conds" "set")
8704   (set_attr "length" "16")])
8705
8706(define_insn_and_split "*and_scc_scc"
8707  [(set (match_operand:SI 0 "s_register_operand" "=r")
8708	(and:SI (match_operator:SI 3 "arm_comparison_operator"
8709		 [(match_operand:SI 1 "s_register_operand" "r")
8710		  (match_operand:SI 2 "arm_add_operand" "rIL")])
8711		(match_operator:SI 6 "arm_comparison_operator"
8712		 [(match_operand:SI 4 "s_register_operand" "r")
8713		  (match_operand:SI 5 "arm_add_operand" "rIL")])))
8714   (clobber (reg:CC CC_REGNUM))]
8715  "TARGET_ARM
8716   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
8717       != CCmode)"
8718  "#"
8719  "TARGET_ARM && reload_completed
8720   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
8721       != CCmode)"
8722  [(set (match_dup 7)
8723	(compare
8724	 (and:SI
8725	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
8726	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
8727	 (const_int 0)))
8728   (set (match_dup 0) (ne:SI (match_dup 7) (const_int 0)))]
8729  "operands[7]
8730     = gen_rtx_REG (arm_select_dominance_cc_mode (operands[3], operands[6],
8731						  DOM_CC_X_AND_Y),
8732		    CC_REGNUM);"
8733  [(set_attr "conds" "clob")
8734   (set_attr "length" "16")])
8735
8736; If the above pattern is followed by a CMP insn, then the compare is 
8737; redundant, since we can rework the conditional instruction that follows.
8738(define_insn_and_split "*and_scc_scc_cmp"
8739  [(set (match_operand 0 "dominant_cc_register" "")
8740	(compare (and:SI (match_operator:SI 3 "arm_comparison_operator"
8741			  [(match_operand:SI 1 "s_register_operand" "r")
8742			   (match_operand:SI 2 "arm_add_operand" "rIL")])
8743			 (match_operator:SI 6 "arm_comparison_operator"
8744			  [(match_operand:SI 4 "s_register_operand" "r")
8745			   (match_operand:SI 5 "arm_add_operand" "rIL")]))
8746		 (const_int 0)))
8747   (set (match_operand:SI 7 "s_register_operand" "=r")
8748	(and:SI (match_op_dup 3 [(match_dup 1) (match_dup 2)])
8749		(match_op_dup 6 [(match_dup 4) (match_dup 5)])))]
8750  "TARGET_ARM"
8751  "#"
8752  "TARGET_ARM && reload_completed"
8753  [(set (match_dup 0)
8754	(compare
8755	 (and:SI
8756	  (match_op_dup 3 [(match_dup 1) (match_dup 2)])
8757	  (match_op_dup 6 [(match_dup 4) (match_dup 5)]))
8758	 (const_int 0)))
8759   (set (match_dup 7) (ne:SI (match_dup 0) (const_int 0)))]
8760  ""
8761  [(set_attr "conds" "set")
8762   (set_attr "length" "16")])
8763
8764;; If there is no dominance in the comparison, then we can still save an
8765;; instruction in the AND case, since we can know that the second compare
8766;; need only zero the value if false (if true, then the value is already
8767;; correct).
8768(define_insn_and_split "*and_scc_scc_nodom"
8769  [(set (match_operand:SI 0 "s_register_operand" "=&r,&r,&r")
8770	(and:SI (match_operator:SI 3 "arm_comparison_operator"
8771		 [(match_operand:SI 1 "s_register_operand" "r,r,0")
8772		  (match_operand:SI 2 "arm_add_operand" "rIL,0,rIL")])
8773		(match_operator:SI 6 "arm_comparison_operator"
8774		 [(match_operand:SI 4 "s_register_operand" "r,r,r")
8775		  (match_operand:SI 5 "arm_add_operand" "rIL,rIL,rIL")])))
8776   (clobber (reg:CC CC_REGNUM))]
8777  "TARGET_ARM
8778   && (arm_select_dominance_cc_mode (operands[3], operands[6], DOM_CC_X_AND_Y)
8779       == CCmode)"
8780  "#"
8781  "TARGET_ARM && reload_completed"
8782  [(parallel [(set (match_dup 0)
8783		   (match_op_dup 3 [(match_dup 1) (match_dup 2)]))
8784	      (clobber (reg:CC CC_REGNUM))])
8785   (set (match_dup 7) (match_op_dup 8 [(match_dup 4) (match_dup 5)]))
8786   (set (match_dup 0)
8787	(if_then_else:SI (match_op_dup 6 [(match_dup 7) (const_int 0)])
8788			 (match_dup 0)
8789			 (const_int 0)))]
8790  "operands[7] = gen_rtx_REG (SELECT_CC_MODE (GET_CODE (operands[6]),
8791					      operands[4], operands[5]),
8792			      CC_REGNUM);
8793   operands[8] = gen_rtx_COMPARE (GET_MODE (operands[7]), operands[4],
8794				  operands[5]);"
8795  [(set_attr "conds" "clob")
8796   (set_attr "length" "20")])
8797
8798(define_split
8799  [(set (reg:CC_NOOV CC_REGNUM)
8800	(compare:CC_NOOV (ior:SI
8801			  (and:SI (match_operand:SI 0 "s_register_operand" "")
8802				  (const_int 1))
8803			  (match_operator:SI 1 "comparison_operator"
8804			   [(match_operand:SI 2 "s_register_operand" "")
8805			    (match_operand:SI 3 "arm_add_operand" "")]))
8806			 (const_int 0)))
8807   (clobber (match_operand:SI 4 "s_register_operand" ""))]
8808  "TARGET_ARM"
8809  [(set (match_dup 4)
8810	(ior:SI (match_op_dup 1 [(match_dup 2) (match_dup 3)])
8811		(match_dup 0)))
8812   (set (reg:CC_NOOV CC_REGNUM)
8813	(compare:CC_NOOV (and:SI (match_dup 4) (const_int 1))
8814			 (const_int 0)))]
8815  "")
8816
8817(define_split
8818  [(set (reg:CC_NOOV CC_REGNUM)
8819	(compare:CC_NOOV (ior:SI
8820			  (match_operator:SI 1 "comparison_operator"
8821			   [(match_operand:SI 2 "s_register_operand" "")
8822			    (match_operand:SI 3 "arm_add_operand" "")])
8823			  (and:SI (match_operand:SI 0 "s_register_operand" "")
8824				  (const_int 1)))
8825			 (const_int 0)))
8826   (clobber (match_operand:SI 4 "s_register_operand" ""))]
8827  "TARGET_ARM"
8828  [(set (match_dup 4)
8829	(ior:SI (match_op_dup 1 [(match_dup 2) (match_dup 3)])
8830		(match_dup 0)))
8831   (set (reg:CC_NOOV CC_REGNUM)
8832	(compare:CC_NOOV (and:SI (match_dup 4) (const_int 1))
8833			 (const_int 0)))]
8834  "")
8835
8836(define_insn "*negscc"
8837  [(set (match_operand:SI 0 "s_register_operand" "=r")
8838	(neg:SI (match_operator 3 "arm_comparison_operator"
8839		 [(match_operand:SI 1 "s_register_operand" "r")
8840		  (match_operand:SI 2 "arm_rhs_operand" "rI")])))
8841   (clobber (reg:CC CC_REGNUM))]
8842  "TARGET_ARM"
8843  "*
8844  if (GET_CODE (operands[3]) == LT && operands[2] == const0_rtx)
8845    return \"mov\\t%0, %1, asr #31\";
8846
8847  if (GET_CODE (operands[3]) == NE)
8848    return \"subs\\t%0, %1, %2\;mvnne\\t%0, #0\";
8849
8850  output_asm_insn (\"cmp\\t%1, %2\", operands);
8851  output_asm_insn (\"mov%D3\\t%0, #0\", operands);
8852  return \"mvn%d3\\t%0, #0\";
8853  "
8854  [(set_attr "conds" "clob")
8855   (set_attr "length" "12")]
8856)
8857
8858(define_insn "movcond"
8859  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
8860	(if_then_else:SI
8861	 (match_operator 5 "arm_comparison_operator"
8862	  [(match_operand:SI 3 "s_register_operand" "r,r,r")
8863	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL,rIL")])
8864	 (match_operand:SI 1 "arm_rhs_operand" "0,rI,?rI")
8865	 (match_operand:SI 2 "arm_rhs_operand" "rI,0,rI")))
8866   (clobber (reg:CC CC_REGNUM))]
8867  "TARGET_ARM"
8868  "*
8869  if (GET_CODE (operands[5]) == LT
8870      && (operands[4] == const0_rtx))
8871    {
8872      if (which_alternative != 1 && GET_CODE (operands[1]) == REG)
8873	{
8874	  if (operands[2] == const0_rtx)
8875	    return \"and\\t%0, %1, %3, asr #31\";
8876	  return \"ands\\t%0, %1, %3, asr #32\;movcc\\t%0, %2\";
8877	}
8878      else if (which_alternative != 0 && GET_CODE (operands[2]) == REG)
8879	{
8880	  if (operands[1] == const0_rtx)
8881	    return \"bic\\t%0, %2, %3, asr #31\";
8882	  return \"bics\\t%0, %2, %3, asr #32\;movcs\\t%0, %1\";
8883	}
8884      /* The only case that falls through to here is when both ops 1 & 2
8885	 are constants.  */
8886    }
8887
8888  if (GET_CODE (operands[5]) == GE
8889      && (operands[4] == const0_rtx))
8890    {
8891      if (which_alternative != 1 && GET_CODE (operands[1]) == REG)
8892	{
8893	  if (operands[2] == const0_rtx)
8894	    return \"bic\\t%0, %1, %3, asr #31\";
8895	  return \"bics\\t%0, %1, %3, asr #32\;movcs\\t%0, %2\";
8896	}
8897      else if (which_alternative != 0 && GET_CODE (operands[2]) == REG)
8898	{
8899	  if (operands[1] == const0_rtx)
8900	    return \"and\\t%0, %2, %3, asr #31\";
8901	  return \"ands\\t%0, %2, %3, asr #32\;movcc\\t%0, %1\";
8902	}
8903      /* The only case that falls through to here is when both ops 1 & 2
8904	 are constants.  */
8905    }
8906  if (GET_CODE (operands[4]) == CONST_INT
8907      && !const_ok_for_arm (INTVAL (operands[4])))
8908    output_asm_insn (\"cmn\\t%3, #%n4\", operands);
8909  else
8910    output_asm_insn (\"cmp\\t%3, %4\", operands);
8911  if (which_alternative != 0)
8912    output_asm_insn (\"mov%d5\\t%0, %1\", operands);
8913  if (which_alternative != 1)
8914    output_asm_insn (\"mov%D5\\t%0, %2\", operands);
8915  return \"\";
8916  "
8917  [(set_attr "conds" "clob")
8918   (set_attr "length" "8,8,12")]
8919)
8920
8921(define_insn "*ifcompare_plus_move"
8922  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
8923	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
8924			  [(match_operand:SI 4 "s_register_operand" "r,r")
8925			   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
8926			 (plus:SI
8927			  (match_operand:SI 2 "s_register_operand" "r,r")
8928			  (match_operand:SI 3 "arm_add_operand" "rIL,rIL"))
8929			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))
8930   (clobber (reg:CC CC_REGNUM))]
8931  "TARGET_ARM"
8932  "#"
8933  [(set_attr "conds" "clob")
8934   (set_attr "length" "8,12")]
8935)
8936
8937(define_insn "*if_plus_move"
8938  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r")
8939	(if_then_else:SI
8940	 (match_operator 4 "arm_comparison_operator"
8941	  [(match_operand 5 "cc_register" "") (const_int 0)])
8942	 (plus:SI
8943	  (match_operand:SI 2 "s_register_operand" "r,r,r,r")
8944	  (match_operand:SI 3 "arm_add_operand" "rI,L,rI,L"))
8945	 (match_operand:SI 1 "arm_rhs_operand" "0,0,?rI,?rI")))]
8946  "TARGET_ARM"
8947  "@
8948   add%d4\\t%0, %2, %3
8949   sub%d4\\t%0, %2, #%n3
8950   add%d4\\t%0, %2, %3\;mov%D4\\t%0, %1
8951   sub%d4\\t%0, %2, #%n3\;mov%D4\\t%0, %1"
8952  [(set_attr "conds" "use")
8953   (set_attr "length" "4,4,8,8")
8954   (set_attr "type" "*,*,*,*")]
8955)
8956
8957(define_insn "*ifcompare_move_plus"
8958  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
8959	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
8960			  [(match_operand:SI 4 "s_register_operand" "r,r")
8961			   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
8962			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
8963			 (plus:SI
8964			  (match_operand:SI 2 "s_register_operand" "r,r")
8965			  (match_operand:SI 3 "arm_add_operand" "rIL,rIL"))))
8966   (clobber (reg:CC CC_REGNUM))]
8967  "TARGET_ARM"
8968  "#"
8969  [(set_attr "conds" "clob")
8970   (set_attr "length" "8,12")]
8971)
8972
8973(define_insn "*if_move_plus"
8974  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r,r")
8975	(if_then_else:SI
8976	 (match_operator 4 "arm_comparison_operator"
8977	  [(match_operand 5 "cc_register" "") (const_int 0)])
8978	 (match_operand:SI 1 "arm_rhs_operand" "0,0,?rI,?rI")
8979	 (plus:SI
8980	  (match_operand:SI 2 "s_register_operand" "r,r,r,r")
8981	  (match_operand:SI 3 "arm_add_operand" "rI,L,rI,L"))))]
8982  "TARGET_ARM"
8983  "@
8984   add%D4\\t%0, %2, %3
8985   sub%D4\\t%0, %2, #%n3
8986   add%D4\\t%0, %2, %3\;mov%d4\\t%0, %1
8987   sub%D4\\t%0, %2, #%n3\;mov%d4\\t%0, %1"
8988  [(set_attr "conds" "use")
8989   (set_attr "length" "4,4,8,8")
8990   (set_attr "type" "*,*,*,*")]
8991)
8992
8993(define_insn "*ifcompare_arith_arith"
8994  [(set (match_operand:SI 0 "s_register_operand" "=r")
8995	(if_then_else:SI (match_operator 9 "arm_comparison_operator"
8996			  [(match_operand:SI 5 "s_register_operand" "r")
8997			   (match_operand:SI 6 "arm_add_operand" "rIL")])
8998			 (match_operator:SI 8 "shiftable_operator"
8999			  [(match_operand:SI 1 "s_register_operand" "r")
9000			   (match_operand:SI 2 "arm_rhs_operand" "rI")])
9001			 (match_operator:SI 7 "shiftable_operator"
9002			  [(match_operand:SI 3 "s_register_operand" "r")
9003			   (match_operand:SI 4 "arm_rhs_operand" "rI")])))
9004   (clobber (reg:CC CC_REGNUM))]
9005  "TARGET_ARM"
9006  "#"
9007  [(set_attr "conds" "clob")
9008   (set_attr "length" "12")]
9009)
9010
9011(define_insn "*if_arith_arith"
9012  [(set (match_operand:SI 0 "s_register_operand" "=r")
9013	(if_then_else:SI (match_operator 5 "arm_comparison_operator"
9014			  [(match_operand 8 "cc_register" "") (const_int 0)])
9015			 (match_operator:SI 6 "shiftable_operator"
9016			  [(match_operand:SI 1 "s_register_operand" "r")
9017			   (match_operand:SI 2 "arm_rhs_operand" "rI")])
9018			 (match_operator:SI 7 "shiftable_operator"
9019			  [(match_operand:SI 3 "s_register_operand" "r")
9020			   (match_operand:SI 4 "arm_rhs_operand" "rI")])))]
9021  "TARGET_ARM"
9022  "%I6%d5\\t%0, %1, %2\;%I7%D5\\t%0, %3, %4"
9023  [(set_attr "conds" "use")
9024   (set_attr "length" "8")]
9025)
9026
9027(define_insn "*ifcompare_arith_move"
9028  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9029	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
9030			  [(match_operand:SI 2 "s_register_operand" "r,r")
9031			   (match_operand:SI 3 "arm_add_operand" "rIL,rIL")])
9032			 (match_operator:SI 7 "shiftable_operator"
9033			  [(match_operand:SI 4 "s_register_operand" "r,r")
9034			   (match_operand:SI 5 "arm_rhs_operand" "rI,rI")])
9035			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))
9036   (clobber (reg:CC CC_REGNUM))]
9037  "TARGET_ARM"
9038  "*
9039  /* If we have an operation where (op x 0) is the identity operation and
9040     the conditional operator is LT or GE and we are comparing against zero and
9041     everything is in registers then we can do this in two instructions.  */
9042  if (operands[3] == const0_rtx
9043      && GET_CODE (operands[7]) != AND
9044      && GET_CODE (operands[5]) == REG
9045      && GET_CODE (operands[1]) == REG 
9046      && REGNO (operands[1]) == REGNO (operands[4])
9047      && REGNO (operands[4]) != REGNO (operands[0]))
9048    {
9049      if (GET_CODE (operands[6]) == LT)
9050	return \"and\\t%0, %5, %2, asr #31\;%I7\\t%0, %4, %0\";
9051      else if (GET_CODE (operands[6]) == GE)
9052	return \"bic\\t%0, %5, %2, asr #31\;%I7\\t%0, %4, %0\";
9053    }
9054  if (GET_CODE (operands[3]) == CONST_INT
9055      && !const_ok_for_arm (INTVAL (operands[3])))
9056    output_asm_insn (\"cmn\\t%2, #%n3\", operands);
9057  else
9058    output_asm_insn (\"cmp\\t%2, %3\", operands);
9059  output_asm_insn (\"%I7%d6\\t%0, %4, %5\", operands);
9060  if (which_alternative != 0)
9061    return \"mov%D6\\t%0, %1\";
9062  return \"\";
9063  "
9064  [(set_attr "conds" "clob")
9065   (set_attr "length" "8,12")]
9066)
9067
9068(define_insn "*if_arith_move"
9069  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9070	(if_then_else:SI (match_operator 4 "arm_comparison_operator"
9071			  [(match_operand 6 "cc_register" "") (const_int 0)])
9072			 (match_operator:SI 5 "shiftable_operator"
9073			  [(match_operand:SI 2 "s_register_operand" "r,r")
9074			   (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])
9075			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")))]
9076  "TARGET_ARM"
9077  "@
9078   %I5%d4\\t%0, %2, %3
9079   %I5%d4\\t%0, %2, %3\;mov%D4\\t%0, %1"
9080  [(set_attr "conds" "use")
9081   (set_attr "length" "4,8")
9082   (set_attr "type" "*,*")]
9083)
9084
9085(define_insn "*ifcompare_move_arith"
9086  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9087	(if_then_else:SI (match_operator 6 "arm_comparison_operator"
9088			  [(match_operand:SI 4 "s_register_operand" "r,r")
9089			   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
9090			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
9091			 (match_operator:SI 7 "shiftable_operator"
9092			  [(match_operand:SI 2 "s_register_operand" "r,r")
9093			   (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))
9094   (clobber (reg:CC CC_REGNUM))]
9095  "TARGET_ARM"
9096  "*
9097  /* If we have an operation where (op x 0) is the identity operation and
9098     the conditional operator is LT or GE and we are comparing against zero and
9099     everything is in registers then we can do this in two instructions */
9100  if (operands[5] == const0_rtx
9101      && GET_CODE (operands[7]) != AND
9102      && GET_CODE (operands[3]) == REG
9103      && GET_CODE (operands[1]) == REG 
9104      && REGNO (operands[1]) == REGNO (operands[2])
9105      && REGNO (operands[2]) != REGNO (operands[0]))
9106    {
9107      if (GET_CODE (operands[6]) == GE)
9108	return \"and\\t%0, %3, %4, asr #31\;%I7\\t%0, %2, %0\";
9109      else if (GET_CODE (operands[6]) == LT)
9110	return \"bic\\t%0, %3, %4, asr #31\;%I7\\t%0, %2, %0\";
9111    }
9112
9113  if (GET_CODE (operands[5]) == CONST_INT
9114      && !const_ok_for_arm (INTVAL (operands[5])))
9115    output_asm_insn (\"cmn\\t%4, #%n5\", operands);
9116  else
9117    output_asm_insn (\"cmp\\t%4, %5\", operands);
9118
9119  if (which_alternative != 0)
9120    output_asm_insn (\"mov%d6\\t%0, %1\", operands);
9121  return \"%I7%D6\\t%0, %2, %3\";
9122  "
9123  [(set_attr "conds" "clob")
9124   (set_attr "length" "8,12")]
9125)
9126
9127(define_insn "*if_move_arith"
9128  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9129	(if_then_else:SI
9130	 (match_operator 4 "arm_comparison_operator"
9131	  [(match_operand 6 "cc_register" "") (const_int 0)])
9132	 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
9133	 (match_operator:SI 5 "shiftable_operator"
9134	  [(match_operand:SI 2 "s_register_operand" "r,r")
9135	   (match_operand:SI 3 "arm_rhs_operand" "rI,rI")])))]
9136  "TARGET_ARM"
9137  "@
9138   %I5%D4\\t%0, %2, %3
9139   %I5%D4\\t%0, %2, %3\;mov%d4\\t%0, %1"
9140  [(set_attr "conds" "use")
9141   (set_attr "length" "4,8")
9142   (set_attr "type" "*,*")]
9143)
9144
9145(define_insn "*ifcompare_move_not"
9146  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9147	(if_then_else:SI
9148	 (match_operator 5 "arm_comparison_operator"
9149	  [(match_operand:SI 3 "s_register_operand" "r,r")
9150	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
9151	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")
9152	 (not:SI
9153	  (match_operand:SI 2 "s_register_operand" "r,r"))))
9154   (clobber (reg:CC CC_REGNUM))]
9155  "TARGET_ARM"
9156  "#"
9157  [(set_attr "conds" "clob")
9158   (set_attr "length" "8,12")]
9159)
9160
9161(define_insn "*if_move_not"
9162  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9163	(if_then_else:SI
9164	 (match_operator 4 "arm_comparison_operator"
9165	  [(match_operand 3 "cc_register" "") (const_int 0)])
9166	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
9167	 (not:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))))]
9168  "TARGET_ARM"
9169  "@
9170   mvn%D4\\t%0, %2
9171   mov%d4\\t%0, %1\;mvn%D4\\t%0, %2
9172   mvn%d4\\t%0, #%B1\;mvn%D4\\t%0, %2"
9173  [(set_attr "conds" "use")
9174   (set_attr "length" "4,8,8")]
9175)
9176
9177(define_insn "*ifcompare_not_move"
9178  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9179	(if_then_else:SI 
9180	 (match_operator 5 "arm_comparison_operator"
9181	  [(match_operand:SI 3 "s_register_operand" "r,r")
9182	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
9183	 (not:SI
9184	  (match_operand:SI 2 "s_register_operand" "r,r"))
9185	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
9186   (clobber (reg:CC CC_REGNUM))]
9187  "TARGET_ARM"
9188  "#"
9189  [(set_attr "conds" "clob")
9190   (set_attr "length" "8,12")]
9191)
9192
9193(define_insn "*if_not_move"
9194  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9195	(if_then_else:SI
9196	 (match_operator 4 "arm_comparison_operator"
9197	  [(match_operand 3 "cc_register" "") (const_int 0)])
9198	 (not:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))
9199	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
9200  "TARGET_ARM"
9201  "@
9202   mvn%d4\\t%0, %2
9203   mov%D4\\t%0, %1\;mvn%d4\\t%0, %2
9204   mvn%D4\\t%0, #%B1\;mvn%d4\\t%0, %2"
9205  [(set_attr "conds" "use")
9206   (set_attr "length" "4,8,8")]
9207)
9208
9209(define_insn "*ifcompare_shift_move"
9210  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9211	(if_then_else:SI
9212	 (match_operator 6 "arm_comparison_operator"
9213	  [(match_operand:SI 4 "s_register_operand" "r,r")
9214	   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
9215	 (match_operator:SI 7 "shift_operator"
9216	  [(match_operand:SI 2 "s_register_operand" "r,r")
9217	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM")])
9218	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
9219   (clobber (reg:CC CC_REGNUM))]
9220  "TARGET_ARM"
9221  "#"
9222  [(set_attr "conds" "clob")
9223   (set_attr "length" "8,12")]
9224)
9225
9226(define_insn "*if_shift_move"
9227  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9228	(if_then_else:SI
9229	 (match_operator 5 "arm_comparison_operator"
9230	  [(match_operand 6 "cc_register" "") (const_int 0)])
9231	 (match_operator:SI 4 "shift_operator"
9232	  [(match_operand:SI 2 "s_register_operand" "r,r,r")
9233	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM,rM")])
9234	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
9235  "TARGET_ARM"
9236  "@
9237   mov%d5\\t%0, %2%S4
9238   mov%D5\\t%0, %1\;mov%d5\\t%0, %2%S4
9239   mvn%D5\\t%0, #%B1\;mov%d5\\t%0, %2%S4"
9240  [(set_attr "conds" "use")
9241   (set_attr "shift" "2")
9242   (set_attr "length" "4,8,8")
9243   (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
9244		      (const_string "alu_shift")
9245		      (const_string "alu_shift_reg")))]
9246)
9247
9248(define_insn "*ifcompare_move_shift"
9249  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9250	(if_then_else:SI
9251	 (match_operator 6 "arm_comparison_operator"
9252	  [(match_operand:SI 4 "s_register_operand" "r,r")
9253	   (match_operand:SI 5 "arm_add_operand" "rIL,rIL")])
9254	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")
9255	 (match_operator:SI 7 "shift_operator"
9256	  [(match_operand:SI 2 "s_register_operand" "r,r")
9257	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM")])))
9258   (clobber (reg:CC CC_REGNUM))]
9259  "TARGET_ARM"
9260  "#"
9261  [(set_attr "conds" "clob")
9262   (set_attr "length" "8,12")]
9263)
9264
9265(define_insn "*if_move_shift"
9266  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9267	(if_then_else:SI
9268	 (match_operator 5 "arm_comparison_operator"
9269	  [(match_operand 6 "cc_register" "") (const_int 0)])
9270	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
9271	 (match_operator:SI 4 "shift_operator"
9272	  [(match_operand:SI 2 "s_register_operand" "r,r,r")
9273	   (match_operand:SI 3 "arm_rhs_operand" "rM,rM,rM")])))]
9274  "TARGET_ARM"
9275  "@
9276   mov%D5\\t%0, %2%S4
9277   mov%d5\\t%0, %1\;mov%D5\\t%0, %2%S4
9278   mvn%d5\\t%0, #%B1\;mov%D5\\t%0, %2%S4"
9279  [(set_attr "conds" "use")
9280   (set_attr "shift" "2")
9281   (set_attr "length" "4,8,8")
9282   (set (attr "type") (if_then_else (match_operand 3 "const_int_operand" "")
9283		      (const_string "alu_shift")
9284		      (const_string "alu_shift_reg")))]
9285)
9286
9287(define_insn "*ifcompare_shift_shift"
9288  [(set (match_operand:SI 0 "s_register_operand" "=r")
9289	(if_then_else:SI
9290	 (match_operator 7 "arm_comparison_operator"
9291	  [(match_operand:SI 5 "s_register_operand" "r")
9292	   (match_operand:SI 6 "arm_add_operand" "rIL")])
9293	 (match_operator:SI 8 "shift_operator"
9294	  [(match_operand:SI 1 "s_register_operand" "r")
9295	   (match_operand:SI 2 "arm_rhs_operand" "rM")])
9296	 (match_operator:SI 9 "shift_operator"
9297	  [(match_operand:SI 3 "s_register_operand" "r")
9298	   (match_operand:SI 4 "arm_rhs_operand" "rM")])))
9299   (clobber (reg:CC CC_REGNUM))]
9300  "TARGET_ARM"
9301  "#"
9302  [(set_attr "conds" "clob")
9303   (set_attr "length" "12")]
9304)
9305
9306(define_insn "*if_shift_shift"
9307  [(set (match_operand:SI 0 "s_register_operand" "=r")
9308	(if_then_else:SI
9309	 (match_operator 5 "arm_comparison_operator"
9310	  [(match_operand 8 "cc_register" "") (const_int 0)])
9311	 (match_operator:SI 6 "shift_operator"
9312	  [(match_operand:SI 1 "s_register_operand" "r")
9313	   (match_operand:SI 2 "arm_rhs_operand" "rM")])
9314	 (match_operator:SI 7 "shift_operator"
9315	  [(match_operand:SI 3 "s_register_operand" "r")
9316	   (match_operand:SI 4 "arm_rhs_operand" "rM")])))]
9317  "TARGET_ARM"
9318  "mov%d5\\t%0, %1%S6\;mov%D5\\t%0, %3%S7"
9319  [(set_attr "conds" "use")
9320   (set_attr "shift" "1")
9321   (set_attr "length" "8")
9322   (set (attr "type") (if_then_else
9323		        (and (match_operand 2 "const_int_operand" "")
9324                             (match_operand 4 "const_int_operand" ""))
9325		      (const_string "alu_shift")
9326		      (const_string "alu_shift_reg")))]
9327)
9328
9329(define_insn "*ifcompare_not_arith"
9330  [(set (match_operand:SI 0 "s_register_operand" "=r")
9331	(if_then_else:SI
9332	 (match_operator 6 "arm_comparison_operator"
9333	  [(match_operand:SI 4 "s_register_operand" "r")
9334	   (match_operand:SI 5 "arm_add_operand" "rIL")])
9335	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))
9336	 (match_operator:SI 7 "shiftable_operator"
9337	  [(match_operand:SI 2 "s_register_operand" "r")
9338	   (match_operand:SI 3 "arm_rhs_operand" "rI")])))
9339   (clobber (reg:CC CC_REGNUM))]
9340  "TARGET_ARM"
9341  "#"
9342  [(set_attr "conds" "clob")
9343   (set_attr "length" "12")]
9344)
9345
9346(define_insn "*if_not_arith"
9347  [(set (match_operand:SI 0 "s_register_operand" "=r")
9348	(if_then_else:SI
9349	 (match_operator 5 "arm_comparison_operator"
9350	  [(match_operand 4 "cc_register" "") (const_int 0)])
9351	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))
9352	 (match_operator:SI 6 "shiftable_operator"
9353	  [(match_operand:SI 2 "s_register_operand" "r")
9354	   (match_operand:SI 3 "arm_rhs_operand" "rI")])))]
9355  "TARGET_ARM"
9356  "mvn%d5\\t%0, %1\;%I6%D5\\t%0, %2, %3"
9357  [(set_attr "conds" "use")
9358   (set_attr "length" "8")]
9359)
9360
9361(define_insn "*ifcompare_arith_not"
9362  [(set (match_operand:SI 0 "s_register_operand" "=r")
9363	(if_then_else:SI
9364	 (match_operator 6 "arm_comparison_operator"
9365	  [(match_operand:SI 4 "s_register_operand" "r")
9366	   (match_operand:SI 5 "arm_add_operand" "rIL")])
9367	 (match_operator:SI 7 "shiftable_operator"
9368	  [(match_operand:SI 2 "s_register_operand" "r")
9369	   (match_operand:SI 3 "arm_rhs_operand" "rI")])
9370	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))))
9371   (clobber (reg:CC CC_REGNUM))]
9372  "TARGET_ARM"
9373  "#"
9374  [(set_attr "conds" "clob")
9375   (set_attr "length" "12")]
9376)
9377
9378(define_insn "*if_arith_not"
9379  [(set (match_operand:SI 0 "s_register_operand" "=r")
9380	(if_then_else:SI
9381	 (match_operator 5 "arm_comparison_operator"
9382	  [(match_operand 4 "cc_register" "") (const_int 0)])
9383	 (match_operator:SI 6 "shiftable_operator"
9384	  [(match_operand:SI 2 "s_register_operand" "r")
9385	   (match_operand:SI 3 "arm_rhs_operand" "rI")])
9386	 (not:SI (match_operand:SI 1 "s_register_operand" "r"))))]
9387  "TARGET_ARM"
9388  "mvn%D5\\t%0, %1\;%I6%d5\\t%0, %2, %3"
9389  [(set_attr "conds" "use")
9390   (set_attr "length" "8")]
9391)
9392
9393(define_insn "*ifcompare_neg_move"
9394  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9395	(if_then_else:SI
9396	 (match_operator 5 "arm_comparison_operator"
9397	  [(match_operand:SI 3 "s_register_operand" "r,r")
9398	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
9399	 (neg:SI (match_operand:SI 2 "s_register_operand" "r,r"))
9400	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")))
9401   (clobber (reg:CC CC_REGNUM))]
9402  "TARGET_ARM"
9403  "#"
9404  [(set_attr "conds" "clob")
9405   (set_attr "length" "8,12")]
9406)
9407
9408(define_insn "*if_neg_move"
9409  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9410	(if_then_else:SI
9411	 (match_operator 4 "arm_comparison_operator"
9412	  [(match_operand 3 "cc_register" "") (const_int 0)])
9413	 (neg:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))
9414	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")))]
9415  "TARGET_ARM"
9416  "@
9417   rsb%d4\\t%0, %2, #0
9418   mov%D4\\t%0, %1\;rsb%d4\\t%0, %2, #0
9419   mvn%D4\\t%0, #%B1\;rsb%d4\\t%0, %2, #0"
9420  [(set_attr "conds" "use")
9421   (set_attr "length" "4,8,8")]
9422)
9423
9424(define_insn "*ifcompare_move_neg"
9425  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9426	(if_then_else:SI
9427	 (match_operator 5 "arm_comparison_operator"
9428	  [(match_operand:SI 3 "s_register_operand" "r,r")
9429	   (match_operand:SI 4 "arm_add_operand" "rIL,rIL")])
9430	 (match_operand:SI 1 "arm_not_operand" "0,?rIK")
9431	 (neg:SI (match_operand:SI 2 "s_register_operand" "r,r"))))
9432   (clobber (reg:CC CC_REGNUM))]
9433  "TARGET_ARM"
9434  "#"
9435  [(set_attr "conds" "clob")
9436   (set_attr "length" "8,12")]
9437)
9438
9439(define_insn "*if_move_neg"
9440  [(set (match_operand:SI 0 "s_register_operand" "=r,r,r")
9441	(if_then_else:SI
9442	 (match_operator 4 "arm_comparison_operator"
9443	  [(match_operand 3 "cc_register" "") (const_int 0)])
9444	 (match_operand:SI 1 "arm_not_operand" "0,?rI,K")
9445	 (neg:SI (match_operand:SI 2 "s_register_operand" "r,r,r"))))]
9446  "TARGET_ARM"
9447  "@
9448   rsb%D4\\t%0, %2, #0
9449   mov%d4\\t%0, %1\;rsb%D4\\t%0, %2, #0
9450   mvn%d4\\t%0, #%B1\;rsb%D4\\t%0, %2, #0"
9451  [(set_attr "conds" "use")
9452   (set_attr "length" "4,8,8")]
9453)
9454
9455(define_insn "*arith_adjacentmem"
9456  [(set (match_operand:SI 0 "s_register_operand" "=r")
9457	(match_operator:SI 1 "shiftable_operator"
9458	 [(match_operand:SI 2 "memory_operand" "m")
9459	  (match_operand:SI 3 "memory_operand" "m")]))
9460   (clobber (match_scratch:SI 4 "=r"))]
9461  "TARGET_ARM && adjacent_mem_locations (operands[2], operands[3])"
9462  "*
9463  {
9464    rtx ldm[3];
9465    rtx arith[4];
9466    rtx base_reg;
9467    HOST_WIDE_INT val1 = 0, val2 = 0;
9468
9469    if (REGNO (operands[0]) > REGNO (operands[4]))
9470      {
9471	ldm[1] = operands[4];
9472	ldm[2] = operands[0];
9473      }
9474    else
9475      {
9476	ldm[1] = operands[0];
9477	ldm[2] = operands[4];
9478      }
9479
9480    base_reg = XEXP (operands[2], 0);
9481
9482    if (!REG_P (base_reg))
9483      {
9484	val1 = INTVAL (XEXP (base_reg, 1));
9485	base_reg = XEXP (base_reg, 0);
9486      }
9487
9488    if (!REG_P (XEXP (operands[3], 0)))
9489      val2 = INTVAL (XEXP (XEXP (operands[3], 0), 1));
9490
9491    arith[0] = operands[0];
9492    arith[3] = operands[1];
9493
9494    if (val1 < val2)
9495      {
9496	arith[1] = ldm[1];
9497	arith[2] = ldm[2];
9498      }
9499    else
9500      {
9501	arith[1] = ldm[2];
9502	arith[2] = ldm[1];
9503      }
9504
9505    ldm[0] = base_reg;
9506    if (val1 !=0 && val2 != 0)
9507      {
9508	rtx ops[3];
9509
9510	if (val1 == 4 || val2 == 4)
9511	  /* Other val must be 8, since we know they are adjacent and neither
9512	     is zero.  */
9513	  output_asm_insn (\"ldm%?ib\\t%0, {%1, %2}\", ldm);
9514	else if (const_ok_for_arm (val1) || const_ok_for_arm (-val1))
9515	  {
9516	    ldm[0] = ops[0] = operands[4];
9517	    ops[1] = base_reg;
9518	    ops[2] = GEN_INT (val1);
9519	    output_add_immediate (ops);
9520	    if (val1 < val2)
9521	      output_asm_insn (\"ldm%?ia\\t%0, {%1, %2}\", ldm);
9522	    else
9523	      output_asm_insn (\"ldm%?da\\t%0, {%1, %2}\", ldm);
9524	  }
9525	else
9526	  {
9527	    /* Offset is out of range for a single add, so use two ldr.  */
9528	    ops[0] = ldm[1];
9529	    ops[1] = base_reg;
9530	    ops[2] = GEN_INT (val1);
9531	    output_asm_insn (\"ldr%?\\t%0, [%1, %2]\", ops);
9532	    ops[0] = ldm[2];
9533	    ops[2] = GEN_INT (val2);
9534	    output_asm_insn (\"ldr%?\\t%0, [%1, %2]\", ops);
9535	  }
9536      }
9537    else if (val1 != 0)
9538      {
9539	if (val1 < val2)
9540	  output_asm_insn (\"ldm%?da\\t%0, {%1, %2}\", ldm);
9541	else
9542	  output_asm_insn (\"ldm%?ia\\t%0, {%1, %2}\", ldm);
9543      }
9544    else
9545      {
9546	if (val1 < val2)
9547	  output_asm_insn (\"ldm%?ia\\t%0, {%1, %2}\", ldm);
9548	else
9549	  output_asm_insn (\"ldm%?da\\t%0, {%1, %2}\", ldm);
9550      }
9551    output_asm_insn (\"%I3%?\\t%0, %1, %2\", arith);
9552    return \"\";
9553  }"
9554  [(set_attr "length" "12")
9555   (set_attr "predicable" "yes")
9556   (set_attr "type" "load1")]
9557)
9558
9559; This pattern is never tried by combine, so do it as a peephole
9560
9561(define_peephole2
9562  [(set (match_operand:SI 0 "arm_general_register_operand" "")
9563	(match_operand:SI 1 "arm_general_register_operand" ""))
9564   (set (reg:CC CC_REGNUM)
9565	(compare:CC (match_dup 1) (const_int 0)))]
9566  "TARGET_ARM"
9567  [(parallel [(set (reg:CC CC_REGNUM) (compare:CC (match_dup 1) (const_int 0)))
9568	      (set (match_dup 0) (match_dup 1))])]
9569  ""
9570)
9571
9572; Peepholes to spot possible load- and store-multiples, if the ordering is
9573; reversed, check that the memory references aren't volatile.
9574
9575(define_peephole
9576  [(set (match_operand:SI 0 "s_register_operand" "=r")
9577        (match_operand:SI 4 "memory_operand" "m"))
9578   (set (match_operand:SI 1 "s_register_operand" "=r")
9579        (match_operand:SI 5 "memory_operand" "m"))
9580   (set (match_operand:SI 2 "s_register_operand" "=r")
9581        (match_operand:SI 6 "memory_operand" "m"))
9582   (set (match_operand:SI 3 "s_register_operand" "=r")
9583        (match_operand:SI 7 "memory_operand" "m"))]
9584  "TARGET_ARM && load_multiple_sequence (operands, 4, NULL, NULL, NULL)"
9585  "*
9586  return emit_ldm_seq (operands, 4);
9587  "
9588)
9589
9590(define_peephole
9591  [(set (match_operand:SI 0 "s_register_operand" "=r")
9592        (match_operand:SI 3 "memory_operand" "m"))
9593   (set (match_operand:SI 1 "s_register_operand" "=r")
9594        (match_operand:SI 4 "memory_operand" "m"))
9595   (set (match_operand:SI 2 "s_register_operand" "=r")
9596        (match_operand:SI 5 "memory_operand" "m"))]
9597  "TARGET_ARM && load_multiple_sequence (operands, 3, NULL, NULL, NULL)"
9598  "*
9599  return emit_ldm_seq (operands, 3);
9600  "
9601)
9602
9603(define_peephole
9604  [(set (match_operand:SI 0 "s_register_operand" "=r")
9605        (match_operand:SI 2 "memory_operand" "m"))
9606   (set (match_operand:SI 1 "s_register_operand" "=r")
9607        (match_operand:SI 3 "memory_operand" "m"))]
9608  "TARGET_ARM && load_multiple_sequence (operands, 2, NULL, NULL, NULL)"
9609  "*
9610  return emit_ldm_seq (operands, 2);
9611  "
9612)
9613
9614(define_peephole
9615  [(set (match_operand:SI 4 "memory_operand" "=m")
9616        (match_operand:SI 0 "s_register_operand" "r"))
9617   (set (match_operand:SI 5 "memory_operand" "=m")
9618        (match_operand:SI 1 "s_register_operand" "r"))
9619   (set (match_operand:SI 6 "memory_operand" "=m")
9620        (match_operand:SI 2 "s_register_operand" "r"))
9621   (set (match_operand:SI 7 "memory_operand" "=m")
9622        (match_operand:SI 3 "s_register_operand" "r"))]
9623  "TARGET_ARM && store_multiple_sequence (operands, 4, NULL, NULL, NULL)"
9624  "*
9625  return emit_stm_seq (operands, 4);
9626  "
9627)
9628
9629(define_peephole
9630  [(set (match_operand:SI 3 "memory_operand" "=m")
9631        (match_operand:SI 0 "s_register_operand" "r"))
9632   (set (match_operand:SI 4 "memory_operand" "=m")
9633        (match_operand:SI 1 "s_register_operand" "r"))
9634   (set (match_operand:SI 5 "memory_operand" "=m")
9635        (match_operand:SI 2 "s_register_operand" "r"))]
9636  "TARGET_ARM && store_multiple_sequence (operands, 3, NULL, NULL, NULL)"
9637  "*
9638  return emit_stm_seq (operands, 3);
9639  "
9640)
9641
9642(define_peephole
9643  [(set (match_operand:SI 2 "memory_operand" "=m")
9644        (match_operand:SI 0 "s_register_operand" "r"))
9645   (set (match_operand:SI 3 "memory_operand" "=m")
9646        (match_operand:SI 1 "s_register_operand" "r"))]
9647  "TARGET_ARM && store_multiple_sequence (operands, 2, NULL, NULL, NULL)"
9648  "*
9649  return emit_stm_seq (operands, 2);
9650  "
9651)
9652
9653(define_split
9654  [(set (match_operand:SI 0 "s_register_operand" "")
9655	(and:SI (ge:SI (match_operand:SI 1 "s_register_operand" "")
9656		       (const_int 0))
9657		(neg:SI (match_operator:SI 2 "arm_comparison_operator"
9658			 [(match_operand:SI 3 "s_register_operand" "")
9659			  (match_operand:SI 4 "arm_rhs_operand" "")]))))
9660   (clobber (match_operand:SI 5 "s_register_operand" ""))]
9661  "TARGET_ARM"
9662  [(set (match_dup 5) (not:SI (ashiftrt:SI (match_dup 1) (const_int 31))))
9663   (set (match_dup 0) (and:SI (match_op_dup 2 [(match_dup 3) (match_dup 4)])
9664			      (match_dup 5)))]
9665  ""
9666)
9667
9668;; This split can be used because CC_Z mode implies that the following
9669;; branch will be an equality, or an unsigned inequality, so the sign
9670;; extension is not needed.
9671
9672(define_split
9673  [(set (reg:CC_Z CC_REGNUM)
9674	(compare:CC_Z
9675	 (ashift:SI (subreg:SI (match_operand:QI 0 "memory_operand" "") 0)
9676		    (const_int 24))
9677	 (match_operand 1 "const_int_operand" "")))
9678   (clobber (match_scratch:SI 2 ""))]
9679  "TARGET_ARM
9680   && (((unsigned HOST_WIDE_INT) INTVAL (operands[1]))
9681       == (((unsigned HOST_WIDE_INT) INTVAL (operands[1])) >> 24) << 24)"
9682  [(set (match_dup 2) (zero_extend:SI (match_dup 0)))
9683   (set (reg:CC CC_REGNUM) (compare:CC (match_dup 2) (match_dup 1)))]
9684  "
9685  operands[1] = GEN_INT (((unsigned long) INTVAL (operands[1])) >> 24);
9686  "
9687)
9688
9689(define_expand "prologue"
9690  [(clobber (const_int 0))]
9691  "TARGET_EITHER"
9692  "if (TARGET_ARM)
9693     arm_expand_prologue ();
9694   else
9695     thumb_expand_prologue ();
9696  DONE;
9697  "
9698)
9699
9700(define_expand "epilogue"
9701  [(clobber (const_int 0))]
9702  "TARGET_EITHER"
9703  "
9704  if (current_function_calls_eh_return)
9705    emit_insn (gen_prologue_use (gen_rtx_REG (Pmode, 2)));
9706  if (TARGET_THUMB)
9707    thumb_expand_epilogue ();
9708  else if (USE_RETURN_INSN (FALSE))
9709    {
9710      emit_jump_insn (gen_return ());
9711      DONE;
9712    }
9713  emit_jump_insn (gen_rtx_UNSPEC_VOLATILE (VOIDmode,
9714	gen_rtvec (1,
9715		gen_rtx_RETURN (VOIDmode)),
9716	VUNSPEC_EPILOGUE));
9717  DONE;
9718  "
9719)
9720
9721;; Note - although unspec_volatile's USE all hard registers,
9722;; USEs are ignored after relaod has completed.  Thus we need
9723;; to add an unspec of the link register to ensure that flow
9724;; does not think that it is unused by the sibcall branch that
9725;; will replace the standard function epilogue.
9726(define_insn "sibcall_epilogue"
9727  [(parallel [(unspec:SI [(reg:SI LR_REGNUM)] UNSPEC_PROLOGUE_USE)
9728              (unspec_volatile [(return)] VUNSPEC_EPILOGUE)])]
9729  "TARGET_ARM"
9730  "*
9731  if (use_return_insn (FALSE, next_nonnote_insn (insn)))
9732    return output_return_instruction (const_true_rtx, FALSE, FALSE);
9733  return arm_output_epilogue (next_nonnote_insn (insn));
9734  "
9735;; Length is absolute worst case
9736  [(set_attr "length" "44")
9737   (set_attr "type" "block")
9738   ;; We don't clobber the conditions, but the potential length of this
9739   ;; operation is sufficient to make conditionalizing the sequence 
9740   ;; unlikely to be profitable.
9741   (set_attr "conds" "clob")]
9742)
9743
9744(define_insn "*epilogue_insns"
9745  [(unspec_volatile [(return)] VUNSPEC_EPILOGUE)]
9746  "TARGET_EITHER"
9747  "*
9748  if (TARGET_ARM)
9749    return arm_output_epilogue (NULL);
9750  else /* TARGET_THUMB */
9751    return thumb_unexpanded_epilogue ();
9752  "
9753  ; Length is absolute worst case
9754  [(set_attr "length" "44")
9755   (set_attr "type" "block")
9756   ;; We don't clobber the conditions, but the potential length of this
9757   ;; operation is sufficient to make conditionalizing the sequence 
9758   ;; unlikely to be profitable.
9759   (set_attr "conds" "clob")]
9760)
9761
9762(define_expand "eh_epilogue"
9763  [(use (match_operand:SI 0 "register_operand" ""))
9764   (use (match_operand:SI 1 "register_operand" ""))
9765   (use (match_operand:SI 2 "register_operand" ""))]
9766  "TARGET_EITHER"
9767  "
9768  {
9769    cfun->machine->eh_epilogue_sp_ofs = operands[1];
9770    if (GET_CODE (operands[2]) != REG || REGNO (operands[2]) != 2)
9771      {
9772	rtx ra = gen_rtx_REG (Pmode, 2);
9773
9774	emit_move_insn (ra, operands[2]);
9775	operands[2] = ra;
9776      }
9777    /* This is a hack -- we may have crystalized the function type too
9778       early.  */
9779    cfun->machine->func_type = 0;
9780  }"
9781)
9782
9783;; This split is only used during output to reduce the number of patterns
9784;; that need assembler instructions adding to them.  We allowed the setting
9785;; of the conditions to be implicit during rtl generation so that
9786;; the conditional compare patterns would work.  However this conflicts to
9787;; some extent with the conditional data operations, so we have to split them
9788;; up again here.
9789
9790(define_split
9791  [(set (match_operand:SI 0 "s_register_operand" "")
9792	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
9793			  [(match_operand 2 "" "") (match_operand 3 "" "")])
9794			 (match_dup 0)
9795			 (match_operand 4 "" "")))
9796   (clobber (reg:CC CC_REGNUM))]
9797  "TARGET_ARM && reload_completed"
9798  [(set (match_dup 5) (match_dup 6))
9799   (cond_exec (match_dup 7)
9800	      (set (match_dup 0) (match_dup 4)))]
9801  "
9802  {
9803    enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
9804					     operands[2], operands[3]);
9805    enum rtx_code rc = GET_CODE (operands[1]);
9806
9807    operands[5] = gen_rtx_REG (mode, CC_REGNUM);
9808    operands[6] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
9809    if (mode == CCFPmode || mode == CCFPEmode)
9810      rc = reverse_condition_maybe_unordered (rc);
9811    else
9812      rc = reverse_condition (rc);
9813
9814    operands[7] = gen_rtx_fmt_ee (rc, VOIDmode, operands[5], const0_rtx);
9815  }"
9816)
9817
9818(define_split
9819  [(set (match_operand:SI 0 "s_register_operand" "")
9820	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
9821			  [(match_operand 2 "" "") (match_operand 3 "" "")])
9822			 (match_operand 4 "" "")
9823			 (match_dup 0)))
9824   (clobber (reg:CC CC_REGNUM))]
9825  "TARGET_ARM && reload_completed"
9826  [(set (match_dup 5) (match_dup 6))
9827   (cond_exec (match_op_dup 1 [(match_dup 5) (const_int 0)])
9828	      (set (match_dup 0) (match_dup 4)))]
9829  "
9830  {
9831    enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
9832					     operands[2], operands[3]);
9833
9834    operands[5] = gen_rtx_REG (mode, CC_REGNUM);
9835    operands[6] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
9836  }"
9837)
9838
9839(define_split
9840  [(set (match_operand:SI 0 "s_register_operand" "")
9841	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
9842			  [(match_operand 2 "" "") (match_operand 3 "" "")])
9843			 (match_operand 4 "" "")
9844			 (match_operand 5 "" "")))
9845   (clobber (reg:CC CC_REGNUM))]
9846  "TARGET_ARM && reload_completed"
9847  [(set (match_dup 6) (match_dup 7))
9848   (cond_exec (match_op_dup 1 [(match_dup 6) (const_int 0)])
9849	      (set (match_dup 0) (match_dup 4)))
9850   (cond_exec (match_dup 8)
9851	      (set (match_dup 0) (match_dup 5)))]
9852  "
9853  {
9854    enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
9855					     operands[2], operands[3]);
9856    enum rtx_code rc = GET_CODE (operands[1]);
9857
9858    operands[6] = gen_rtx_REG (mode, CC_REGNUM);
9859    operands[7] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
9860    if (mode == CCFPmode || mode == CCFPEmode)
9861      rc = reverse_condition_maybe_unordered (rc);
9862    else
9863      rc = reverse_condition (rc);
9864
9865    operands[8] = gen_rtx_fmt_ee (rc, VOIDmode, operands[6], const0_rtx);
9866  }"
9867)
9868
9869(define_split
9870  [(set (match_operand:SI 0 "s_register_operand" "")
9871	(if_then_else:SI (match_operator 1 "arm_comparison_operator"
9872			  [(match_operand:SI 2 "s_register_operand" "")
9873			   (match_operand:SI 3 "arm_add_operand" "")])
9874			 (match_operand:SI 4 "arm_rhs_operand" "")
9875			 (not:SI
9876			  (match_operand:SI 5 "s_register_operand" ""))))
9877   (clobber (reg:CC CC_REGNUM))]
9878  "TARGET_ARM && reload_completed"
9879  [(set (match_dup 6) (match_dup 7))
9880   (cond_exec (match_op_dup 1 [(match_dup 6) (const_int 0)])
9881	      (set (match_dup 0) (match_dup 4)))
9882   (cond_exec (match_dup 8)
9883	      (set (match_dup 0) (not:SI (match_dup 5))))]
9884  "
9885  {
9886    enum machine_mode mode = SELECT_CC_MODE (GET_CODE (operands[1]),
9887					     operands[2], operands[3]);
9888    enum rtx_code rc = GET_CODE (operands[1]);
9889
9890    operands[6] = gen_rtx_REG (mode, CC_REGNUM);
9891    operands[7] = gen_rtx_COMPARE (mode, operands[2], operands[3]);
9892    if (mode == CCFPmode || mode == CCFPEmode)
9893      rc = reverse_condition_maybe_unordered (rc);
9894    else
9895      rc = reverse_condition (rc);
9896
9897    operands[8] = gen_rtx_fmt_ee (rc, VOIDmode, operands[6], const0_rtx);
9898  }"
9899)
9900
9901(define_insn "*cond_move_not"
9902  [(set (match_operand:SI 0 "s_register_operand" "=r,r")
9903	(if_then_else:SI (match_operator 4 "arm_comparison_operator"
9904			  [(match_operand 3 "cc_register" "") (const_int 0)])
9905			 (match_operand:SI 1 "arm_rhs_operand" "0,?rI")
9906			 (not:SI
9907			  (match_operand:SI 2 "s_register_operand" "r,r"))))]
9908  "TARGET_ARM"
9909  "@
9910   mvn%D4\\t%0, %2
9911   mov%d4\\t%0, %1\;mvn%D4\\t%0, %2"
9912  [(set_attr "conds" "use")
9913   (set_attr "length" "4,8")]
9914)
9915
9916;; The next two patterns occur when an AND operation is followed by a
9917;; scc insn sequence 
9918
9919(define_insn "*sign_extract_onebit"
9920  [(set (match_operand:SI 0 "s_register_operand" "=r")
9921	(sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
9922			 (const_int 1)
9923			 (match_operand:SI 2 "const_int_operand" "n")))
9924    (clobber (reg:CC CC_REGNUM))]
9925  "TARGET_ARM"
9926  "*
9927    operands[2] = GEN_INT (1 << INTVAL (operands[2]));
9928    output_asm_insn (\"ands\\t%0, %1, %2\", operands);
9929    return \"mvnne\\t%0, #0\";
9930  "
9931  [(set_attr "conds" "clob")
9932   (set_attr "length" "8")]
9933)
9934
9935(define_insn "*not_signextract_onebit"
9936  [(set (match_operand:SI 0 "s_register_operand" "=r")
9937	(not:SI
9938	 (sign_extract:SI (match_operand:SI 1 "s_register_operand" "r")
9939			  (const_int 1)
9940			  (match_operand:SI 2 "const_int_operand" "n"))))
9941   (clobber (reg:CC CC_REGNUM))]
9942  "TARGET_ARM"
9943  "*
9944    operands[2] = GEN_INT (1 << INTVAL (operands[2]));
9945    output_asm_insn (\"tst\\t%1, %2\", operands);
9946    output_asm_insn (\"mvneq\\t%0, #0\", operands);
9947    return \"movne\\t%0, #0\";
9948  "
9949  [(set_attr "conds" "clob")
9950   (set_attr "length" "12")]
9951)
9952
9953;; Push multiple registers to the stack.  Registers are in parallel (use ...)
9954;; expressions.  For simplicity, the first register is also in the unspec
9955;; part.
9956(define_insn "*push_multi"
9957  [(match_parallel 2 "multi_register_push"
9958    [(set (match_operand:BLK 0 "memory_operand" "=m")
9959	  (unspec:BLK [(match_operand:SI 1 "s_register_operand" "r")]
9960		      UNSPEC_PUSH_MULT))])]
9961  "TARGET_ARM"
9962  "*
9963  {
9964    int num_saves = XVECLEN (operands[2], 0);
9965     
9966    /* For the StrongARM at least it is faster to
9967       use STR to store only a single register.  */
9968    if (num_saves == 1)
9969      output_asm_insn (\"str\\t%1, [%m0, #-4]!\", operands);
9970    else
9971      {
9972	int i;
9973	char pattern[100];
9974
9975	strcpy (pattern, \"stmfd\\t%m0!, {%1\");
9976
9977	for (i = 1; i < num_saves; i++)
9978	  {
9979	    strcat (pattern, \", %|\");
9980	    strcat (pattern,
9981		    reg_names[REGNO (XEXP (XVECEXP (operands[2], 0, i), 0))]);
9982	  }
9983
9984	strcat (pattern, \"}\");
9985	output_asm_insn (pattern, operands);
9986      }
9987
9988    return \"\";
9989  }"
9990  [(set_attr "type" "store4")]
9991)
9992
9993(define_insn "stack_tie"
9994  [(set (mem:BLK (scratch))
9995	(unspec:BLK [(match_operand:SI 0 "s_register_operand" "r")
9996		     (match_operand:SI 1 "s_register_operand" "r")]
9997		    UNSPEC_PRLG_STK))]
9998  ""
9999  ""
10000  [(set_attr "length" "0")]
10001)
10002
10003;; Similarly for the floating point registers
10004(define_insn "*push_fp_multi"
10005  [(match_parallel 2 "multi_register_push"
10006    [(set (match_operand:BLK 0 "memory_operand" "=m")
10007	  (unspec:BLK [(match_operand:XF 1 "f_register_operand" "f")]
10008		      UNSPEC_PUSH_MULT))])]
10009  "TARGET_ARM && TARGET_HARD_FLOAT && TARGET_FPA"
10010  "*
10011  {
10012    char pattern[100];
10013
10014    sprintf (pattern, \"sfmfd\\t%%1, %d, [%%m0]!\", XVECLEN (operands[2], 0));
10015    output_asm_insn (pattern, operands);
10016    return \"\";
10017  }"
10018  [(set_attr "type" "f_store")]
10019)
10020
10021;; Special patterns for dealing with the constant pool
10022
10023(define_insn "align_4"
10024  [(unspec_volatile [(const_int 0)] VUNSPEC_ALIGN)]
10025  "TARGET_EITHER"
10026  "*
10027  assemble_align (32);
10028  return \"\";
10029  "
10030)
10031
10032(define_insn "align_8"
10033  [(unspec_volatile [(const_int 0)] VUNSPEC_ALIGN8)]
10034  "TARGET_EITHER"
10035  "*
10036  assemble_align (64);
10037  return \"\";
10038  "
10039)
10040
10041(define_insn "consttable_end"
10042  [(unspec_volatile [(const_int 0)] VUNSPEC_POOL_END)]
10043  "TARGET_EITHER"
10044  "*
10045  making_const_table = FALSE;
10046  return \"\";
10047  "
10048)
10049
10050(define_insn "consttable_1"
10051  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_1)]
10052  "TARGET_THUMB"
10053  "*
10054  making_const_table = TRUE;
10055  assemble_integer (operands[0], 1, BITS_PER_WORD, 1);
10056  assemble_zeros (3);
10057  return \"\";
10058  "
10059  [(set_attr "length" "4")]
10060)
10061
10062(define_insn "consttable_2"
10063  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_2)]
10064  "TARGET_THUMB"
10065  "*
10066  making_const_table = TRUE;
10067  assemble_integer (operands[0], 2, BITS_PER_WORD, 1);
10068  assemble_zeros (2);
10069  return \"\";
10070  "
10071  [(set_attr "length" "4")]
10072)
10073
10074(define_insn "consttable_4"
10075  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_4)]
10076  "TARGET_EITHER"
10077  "*
10078  {
10079    making_const_table = TRUE;
10080    switch (GET_MODE_CLASS (GET_MODE (operands[0])))
10081      {
10082      case MODE_FLOAT:
10083      {
10084        REAL_VALUE_TYPE r;
10085        REAL_VALUE_FROM_CONST_DOUBLE (r, operands[0]);
10086        assemble_real (r, GET_MODE (operands[0]), BITS_PER_WORD);
10087        break;
10088      }
10089      default:
10090        assemble_integer (operands[0], 4, BITS_PER_WORD, 1);
10091        break;
10092      }
10093    return \"\";
10094  }"
10095  [(set_attr "length" "4")]
10096)
10097
10098(define_insn "consttable_8"
10099  [(unspec_volatile [(match_operand 0 "" "")] VUNSPEC_POOL_8)]
10100  "TARGET_EITHER"
10101  "*
10102  {
10103    making_const_table = TRUE;
10104    switch (GET_MODE_CLASS (GET_MODE (operands[0])))
10105      {
10106       case MODE_FLOAT:
10107        {
10108          REAL_VALUE_TYPE r;
10109          REAL_VALUE_FROM_CONST_DOUBLE (r, operands[0]);
10110          assemble_real (r, GET_MODE (operands[0]), BITS_PER_WORD);
10111          break;
10112        }
10113      default:
10114        assemble_integer (operands[0], 8, BITS_PER_WORD, 1);
10115        break;
10116      }
10117    return \"\";
10118  }"
10119  [(set_attr "length" "8")]
10120)
10121
10122;; Miscellaneous Thumb patterns
10123
10124(define_expand "tablejump"
10125  [(parallel [(set (pc) (match_operand:SI 0 "register_operand" ""))
10126	      (use (label_ref (match_operand 1 "" "")))])]
10127  "TARGET_THUMB"
10128  "
10129  if (flag_pic)
10130    {
10131      /* Hopefully, CSE will eliminate this copy.  */
10132      rtx reg1 = copy_addr_to_reg (gen_rtx_LABEL_REF (Pmode, operands[1]));
10133      rtx reg2 = gen_reg_rtx (SImode);
10134
10135      emit_insn (gen_addsi3 (reg2, operands[0], reg1));
10136      operands[0] = reg2;
10137    }
10138  "
10139)
10140
10141;; NB never uses BX.
10142(define_insn "*thumb_tablejump"
10143  [(set (pc) (match_operand:SI 0 "register_operand" "l*r"))
10144   (use (label_ref (match_operand 1 "" "")))]
10145  "TARGET_THUMB"
10146  "mov\\t%|pc, %0"
10147  [(set_attr "length" "2")]
10148)
10149
10150;; V5 Instructions,
10151
10152(define_insn "clzsi2"
10153  [(set (match_operand:SI 0 "s_register_operand" "=r")
10154	(clz:SI (match_operand:SI 1 "s_register_operand" "r")))]
10155  "TARGET_ARM && arm_arch5"
10156  "clz%?\\t%0, %1"
10157  [(set_attr "predicable" "yes")])
10158
10159(define_expand "ffssi2"
10160  [(set (match_operand:SI 0 "s_register_operand" "")
10161	(ffs:SI (match_operand:SI 1 "s_register_operand" "")))]
10162  "TARGET_ARM && arm_arch5"
10163  "
10164  {
10165    rtx t1, t2, t3;
10166
10167    t1 = gen_reg_rtx (SImode);
10168    t2 = gen_reg_rtx (SImode);
10169    t3 = gen_reg_rtx (SImode);
10170
10171    emit_insn (gen_negsi2 (t1, operands[1]));
10172    emit_insn (gen_andsi3 (t2, operands[1], t1));
10173    emit_insn (gen_clzsi2 (t3, t2));
10174    emit_insn (gen_subsi3 (operands[0], GEN_INT (32), t3));
10175    DONE;
10176  }"
10177)
10178
10179(define_expand "ctzsi2"
10180  [(set (match_operand:SI 0 "s_register_operand" "")
10181	(ctz:SI (match_operand:SI 1 "s_register_operand" "")))]
10182  "TARGET_ARM && arm_arch5"
10183  "
10184  {
10185    rtx t1, t2, t3;
10186
10187    t1 = gen_reg_rtx (SImode);
10188    t2 = gen_reg_rtx (SImode);
10189    t3 = gen_reg_rtx (SImode);
10190
10191    emit_insn (gen_negsi2 (t1, operands[1]));
10192    emit_insn (gen_andsi3 (t2, operands[1], t1));
10193    emit_insn (gen_clzsi2 (t3, t2));
10194    emit_insn (gen_subsi3 (operands[0], GEN_INT (31), t3));
10195    DONE;
10196  }"
10197)
10198
10199;; V5E instructions.
10200
10201(define_insn "prefetch"
10202  [(prefetch (match_operand:SI 0 "address_operand" "p")
10203	     (match_operand:SI 1 "" "")
10204	     (match_operand:SI 2 "" ""))]
10205  "TARGET_ARM && arm_arch5e"
10206  "pld\\t%a0")
10207
10208;; General predication pattern
10209
10210(define_cond_exec
10211  [(match_operator 0 "arm_comparison_operator"
10212    [(match_operand 1 "cc_register" "")
10213     (const_int 0)])]
10214  "TARGET_ARM"
10215  ""
10216)
10217
10218(define_insn "prologue_use"
10219  [(unspec:SI [(match_operand:SI 0 "register_operand" "")] UNSPEC_PROLOGUE_USE)]
10220  ""
10221  "%@ %0 needed for prologue"
10222)
10223
10224
10225;; Patterns for exception handling
10226
10227(define_expand "eh_return"
10228  [(use (match_operand 0 "general_operand" ""))]
10229  "TARGET_EITHER"
10230  "
10231  {
10232    if (TARGET_ARM)
10233      emit_insn (gen_arm_eh_return (operands[0]));
10234    else
10235      emit_insn (gen_thumb_eh_return (operands[0]));
10236    DONE;
10237  }"
10238)
10239				   
10240;; We can't expand this before we know where the link register is stored.
10241(define_insn_and_split "arm_eh_return"
10242  [(unspec_volatile [(match_operand:SI 0 "s_register_operand" "r")]
10243		    VUNSPEC_EH_RETURN)
10244   (clobber (match_scratch:SI 1 "=&r"))]
10245  "TARGET_ARM"
10246  "#"
10247  "&& reload_completed"
10248  [(const_int 0)]
10249  "
10250  {
10251    arm_set_return_address (operands[0], operands[1]);
10252    DONE;
10253  }"
10254)
10255
10256(define_insn_and_split "thumb_eh_return"
10257  [(unspec_volatile [(match_operand:SI 0 "s_register_operand" "l")]
10258		    VUNSPEC_EH_RETURN)
10259   (clobber (match_scratch:SI 1 "=&l"))]
10260  "TARGET_THUMB"
10261  "#"
10262  "&& reload_completed"
10263  [(const_int 0)]
10264  "
10265  {
10266    thumb_set_return_address (operands[0], operands[1]);
10267    DONE;
10268  }"
10269)
10270
10271
10272;; TLS support
10273
10274(define_insn "load_tp_hard"
10275  [(set (match_operand:SI 0 "register_operand" "=r")
10276	(unspec:SI [(const_int 0)] UNSPEC_TLS))]
10277  "TARGET_HARD_TP"
10278  "mrc%?\\tp15, 0, %0, c13, c0, 3\\t@ load_tp_hard"
10279  [(set_attr "predicable" "yes")]
10280)
10281
10282;; Doesn't clobber R1-R3.  Must use r0 for the first operand.
10283(define_insn "load_tp_soft"
10284  [(set (reg:SI 0) (unspec:SI [(const_int 0)] UNSPEC_TLS))
10285   (clobber (reg:SI LR_REGNUM))
10286   (clobber (reg:SI IP_REGNUM))
10287   (clobber (reg:CC CC_REGNUM))]
10288  "TARGET_SOFT_TP"
10289  "bl\\t__aeabi_read_tp\\t@ load_tp_soft"
10290  [(set_attr "conds" "clob")]
10291)
10292
10293;; Load the FPA co-processor patterns
10294(include "fpa.md")
10295;; Load the Maverick co-processor patterns
10296(include "cirrus.md")
10297;; Load the Intel Wireless Multimedia Extension patterns
10298(include "iwmmxt.md")
10299;; Load the VFP co-processor patterns
10300(include "vfp.md")
10301
10302