ia64.md revision 96263
10SN/A;; IA-64 Machine description template
22362SN/A;; Copyright (C) 1999, 2000, 2001 Free Software Foundation, Inc.
30SN/A;; Contributed by James E. Wilson <wilson@cygnus.com> and
40SN/A;;		  David Mosberger <davidm@hpl.hp.com>.
50SN/A
60SN/A;; This file is part of GNU CC.
72362SN/A
80SN/A;; GNU CC is free software; you can redistribute it and/or modify
92362SN/A;; it under the terms of the GNU General Public License as published by
100SN/A;; the Free Software Foundation; either version 2, or (at your option)
110SN/A;; any later version.
120SN/A
130SN/A;; GNU CC is distributed in the hope that it will be useful,
140SN/A;; but WITHOUT ANY WARRANTY; without even the implied warranty of
150SN/A;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
160SN/A;; GNU General Public License for more details.
170SN/A
180SN/A;; You should have received a copy of the GNU General Public License
190SN/A;; along with GNU CC; see the file COPYING.  If not, write to
200SN/A;; the Free Software Foundation, 59 Temple Place - Suite 330,
212362SN/A;; Boston, MA 02111-1307, USA.
222362SN/A
232362SN/A;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
240SN/A
250SN/A;; ??? register_operand accepts (subreg:DI (mem:SI X)) which forces later
260SN/A;; reload.  This will be fixed once scheduling support is turned on.
270SN/A
280SN/A;; ??? Optimize for post-increment addressing modes.
290SN/A
300SN/A;; ??? fselect is not supported, because there is no integer register
310SN/A;; equivalent.
320SN/A
330SN/A;; ??? fp abs/min/max instructions may also work for integer values.
340SN/A
350SN/A;; ??? Would a predicate_reg_operand predicate be useful?  The HP one is buggy,
360SN/A;; it assumes the operand is a register and takes REGNO of it without checking.
370SN/A
380SN/A;; ??? Would a branch_reg_operand predicate be useful?  The HP one is buggy,
390SN/A;; it assumes the operand is a register and takes REGNO of it without checking.
400SN/A
410SN/A;; ??? Go through list of documented named patterns and look for more to
420SN/A;; implement.
430SN/A
440SN/A;; ??? Go through instruction manual and look for more instructions that
450SN/A;; can be emitted.
460SN/A
470SN/A;; ??? Add function unit scheduling info for Itanium (TM) processor.
480SN/A
490SN/A;; ??? Need a better way to describe alternate fp status registers.
500SN/A
510SN/A;; Unspec usage:
520SN/A;;
530SN/A;; unspec:
540SN/A;;	1	gr_spill
550SN/A;;	2	gr_restore
560SN/A;;	3	fr_spill
570SN/A;;	4	fr_restore
580SN/A;;	5	recip_approx
590SN/A;;	7	pred_rel_mutex
600SN/A;;	8	popcnt
610SN/A;;	9	pic call
620SN/A;;	12	mf
630SN/A;;	13	cmpxchg_acq
640SN/A;;	19	fetchadd_acq
650SN/A;;	20	bsp_value
660SN/A;;	21	flushrs
670SN/A;;	22      bundle selector
680SN/A;;	23      cycle display
690SN/A;;      24      addp4
700SN/A;;	25	prologue_use
710SN/A;;
720SN/A;; unspec_volatile:
730SN/A;;	0	alloc
740SN/A;;	1	blockage
750SN/A;;	2	insn_group_barrier
760SN/A;;	3	break
770SN/A;;	5	set_bsp
780SN/A;;	8	pred.safe_across_calls all
790SN/A;;	9	pred.safe_across_calls normal
800SN/A
810SN/A;; ::::::::::::::::::::
82;; ::
83;; :: Attributes
84;; ::
85;; ::::::::::::::::::::
86
87;; Instruction type.  This primarily determines how instructions can be
88;; packed in bundles, and secondarily affects scheduling to function units.
89
90;; A alu, can go in I or M syllable of a bundle
91;; I integer
92;; M memory
93;; F floating-point
94;; B branch
95;; L long immediate, takes two syllables
96;; S stop bit
97
98;; ??? Should not have any pattern with type unknown.  Perhaps add code to
99;; check this in md_reorg?  Currently use unknown for patterns which emit
100;; multiple instructions, patterns which emit 0 instructions, and patterns
101;; which emit instruction that can go in any slot (e.g. nop).
102
103(define_attr "itanium_class" "unknown,ignore,stop_bit,br,fcmp,fcvtfx,fld,fmac,fmisc,frar_i,frar_m,frbr,frfr,frpr,ialu,icmp,ilog,ishf,ld,chk_s,long_i,mmmul,mmshf,mmshfi,rse_m,scall,sem,stf,st,syst_m0,syst_m,tbit,toar_i,toar_m,tobr,tofr,topr,xmpy,xtd,nop_b,nop_f,nop_i,nop_m,nop_x,lfetch"
104         (const_string "unknown"))
105
106;; chk_s has an I and an M form; use type A for convenience.
107(define_attr "type" "unknown,A,I,M,F,B,L,X,S"
108  (cond [(eq_attr "itanium_class" "ld,st,fld,stf,sem,nop_m") (const_string "M")
109	 (eq_attr "itanium_class" "rse_m,syst_m,syst_m0") (const_string "M")
110	 (eq_attr "itanium_class" "frar_m,toar_m,frfr,tofr") (const_string "M")
111	 (eq_attr "itanium_class" "lfetch") (const_string "M")
112	 (eq_attr "itanium_class" "chk_s,ialu,icmp,ilog") (const_string "A")
113	 (eq_attr "itanium_class" "fmisc,fmac,fcmp,xmpy") (const_string "F")
114	 (eq_attr "itanium_class" "fcvtfx,nop_f") (const_string "F")
115	 (eq_attr "itanium_class" "frar_i,toar_i,frbr,tobr") (const_string "I")
116	 (eq_attr "itanium_class" "frpr,topr,ishf,xtd,tbit") (const_string "I")
117	 (eq_attr "itanium_class" "mmmul,mmshf,mmshfi,nop_i") (const_string "I")
118	 (eq_attr "itanium_class" "br,scall,nop_b") (const_string "B")
119	 (eq_attr "itanium_class" "stop_bit") (const_string "S")
120	 (eq_attr "itanium_class" "nop_x") (const_string "X")
121	 (eq_attr "itanium_class" "long_i") (const_string "L")]
122	(const_string "unknown")))
123
124(define_attr "itanium_requires_unit0" "no,yes"
125  (cond [(eq_attr "itanium_class" "syst_m0,sem,frfr,rse_m") (const_string "yes")
126	 (eq_attr "itanium_class" "toar_m,frar_m") (const_string "yes")
127	 (eq_attr "itanium_class" "frbr,tobr,mmmul") (const_string "yes")
128	 (eq_attr "itanium_class" "tbit,ishf,topr,frpr") (const_string "yes")
129	 (eq_attr "itanium_class" "toar_i,frar_i") (const_string "yes")
130	 (eq_attr "itanium_class" "fmisc,fcmp") (const_string "yes")]
131	(const_string "no")))
132
133;; Predication.  True iff this instruction can be predicated.
134
135(define_attr "predicable" "no,yes" (const_string "yes"))
136
137
138;; ::::::::::::::::::::
139;; ::
140;; :: Function Units
141;; ::
142;; ::::::::::::::::::::
143
144;; We define 6 "dummy" functional units.  All the real work to decide which
145;; insn uses which unit is done by our MD_SCHED_REORDER hooks.  We only
146;; have to ensure here that there are enough copies of the dummy unit so
147;; that the scheduler doesn't get confused by MD_SCHED_REORDER.
148;; Other than the 6 dummies for normal insns, we also add a single dummy unit
149;; for stop bits.
150
151(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "br")     0 0)
152(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "scall")  0 0)
153(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "fcmp")   2 0)
154(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "fcvtfx") 7 0)
155(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "fld")    9 0)
156(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "fmac")   5 0)
157(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "fmisc")  5 0)
158
159;; There is only one insn `mov = ar.bsp' for frar_i:
160(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "frar_i") 13 0)
161;; There is only ony insn `mov = ar.unat' for frar_m:
162(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "frar_m") 6 0)
163(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "frbr")   2 0)
164(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "frfr")   2 0)
165(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "frpr")   2 0)
166
167(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "ialu")   1 0)
168(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "icmp")   1 0)
169(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "ilog")   1 0)
170(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "ishf")   1 0)
171(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "ld")     2 0)
172(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "long_i") 1 0)
173(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "mmmul")  2 0)
174(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "mmshf")  2 0)
175(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "mmshfi")  2 0)
176
177;; Now we have only one insn (flushrs) of such class.  We assume that flushrs
178;; is the 1st syllable of the bundle after stop bit.
179(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "rse_m")  0 0)
180(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "sem")   11 0)
181(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "stf")    1 0)
182(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "st")     1 0)
183(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "syst_m0") 1 0)
184;; Now we use only one insn `mf'.  Therfore latency time is set up to 0.
185(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "syst_m") 0 0)
186(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "tbit")   1 0)
187
188;; There is only one insn `mov ar.pfs =' for toar_i therefore we use
189;; latency time equal to 0:
190(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "toar_i") 0 0)
191;; There are only ony 2 insns `mov ar.ccv =' and `mov ar.unat =' for toar_m:
192(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "toar_m") 5 0)
193(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "tobr")   1 0)
194(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "tofr")   9 0)
195(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "topr")   1 0)
196(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "xmpy")   7 0)
197(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "xtd")    1 0)
198
199(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "nop_m")  0 0)
200(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "nop_i")  0 0)
201(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "nop_f")  0 0)
202(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "nop_b")  0 0)
203(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "nop_x")  0 0)
204
205(define_function_unit "stop_bit" 1 1 (eq_attr "itanium_class" "stop_bit") 0 0)
206(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "ignore") 0 0)
207(define_function_unit "dummy" 6 1 (eq_attr "itanium_class" "unknown") 0 0)
208
209;; ::::::::::::::::::::
210;; ::
211;; :: Moves
212;; ::
213;; ::::::::::::::::::::
214
215;; Set of a single predicate register.  This is only used to implement
216;; pr-to-pr move and complement.
217
218(define_insn "*movcci"
219  [(set (match_operand:CCI 0 "register_operand" "=c,c,c")
220	(match_operand:CCI 1 "nonmemory_operand" "O,n,c"))]
221  ""
222  "@
223   cmp.ne %0, p0 = r0, r0
224   cmp.eq %0, p0 = r0, r0
225   (%1) cmp.eq.unc %0, p0 = r0, r0"
226  [(set_attr "itanium_class" "icmp")
227   (set_attr "predicable" "no")])
228
229(define_insn "movbi"
230  [(set (match_operand:BI 0 "nonimmediate_operand" "=c,c,?c,?*r, c,*r,*r,*m,*r")
231	(match_operand:BI 1 "move_operand"         " O,n, c,  c,*r, n,*m,*r,*r"))]
232  ""
233  "@
234   cmp.ne %0, %I0 = r0, r0
235   cmp.eq %0, %I0 = r0, r0
236   #
237   #
238   tbit.nz %0, %I0 = %1, 0
239   adds %0 = %1, r0
240   ld1%O1 %0 = %1%P1
241   st1%Q0 %0 = %1%P0
242   mov %0 = %1"
243  [(set_attr "itanium_class" "icmp,icmp,unknown,unknown,tbit,ialu,ld,st,ialu")])
244
245(define_split
246  [(set (match_operand:BI 0 "register_operand" "")
247	(match_operand:BI 1 "register_operand" ""))]
248  "reload_completed
249   && GET_CODE (operands[0]) == REG && GR_REGNO_P (REGNO (operands[0]))
250   && GET_CODE (operands[1]) == REG && PR_REGNO_P (REGNO (operands[1]))"
251  [(cond_exec (ne (match_dup 1) (const_int 0))
252     (set (match_dup 0) (const_int 1)))
253   (cond_exec (eq (match_dup 1) (const_int 0))
254     (set (match_dup 0) (const_int 0)))]
255  "")
256
257(define_split
258  [(set (match_operand:BI 0 "register_operand" "")
259	(match_operand:BI 1 "register_operand" ""))]
260  "reload_completed
261   && GET_CODE (operands[0]) == REG && PR_REGNO_P (REGNO (operands[0]))
262   && GET_CODE (operands[1]) == REG && PR_REGNO_P (REGNO (operands[1]))"
263  [(set (match_dup 2) (match_dup 4))
264   (set (match_dup 3) (match_dup 5))
265   (set (match_dup 0) (unspec:BI [(match_dup 0)] 7))]
266  "operands[2] = gen_rtx_REG (CCImode, REGNO (operands[0]));
267   operands[3] = gen_rtx_REG (CCImode, REGNO (operands[0]) + 1);
268   operands[4] = gen_rtx_REG (CCImode, REGNO (operands[1]));
269   operands[5] = gen_rtx_REG (CCImode, REGNO (operands[1]) + 1);")
270
271(define_expand "movqi"
272  [(set (match_operand:QI 0 "general_operand" "")
273	(match_operand:QI 1 "general_operand" ""))]
274  ""
275  "
276{
277  if (! reload_in_progress && ! reload_completed
278      && ! ia64_move_ok (operands[0], operands[1]))
279    operands[1] = force_reg (QImode, operands[1]);
280}")
281
282(define_insn "*movqi_internal"
283  [(set (match_operand:QI 0 "destination_operand" "=r,r,r, m, r,*f,*f")
284	(match_operand:QI 1 "move_operand"        "rO,J,m,rO,*f,rO,*f"))]
285  "ia64_move_ok (operands[0], operands[1])"
286  "@
287   mov %0 = %r1
288   addl %0 = %1, r0
289   ld1%O1 %0 = %1%P1
290   st1%Q0 %0 = %r1%P0
291   getf.sig %0 = %1
292   setf.sig %0 = %r1
293   mov %0 = %1"
294  [(set_attr "itanium_class" "ialu,ialu,ld,st,frfr,tofr,fmisc")])
295
296(define_expand "movhi"
297  [(set (match_operand:HI 0 "general_operand" "")
298	(match_operand:HI 1 "general_operand" ""))]
299  ""
300  "
301{
302  if (! reload_in_progress && ! reload_completed
303      && ! ia64_move_ok (operands[0], operands[1]))
304    operands[1] = force_reg (HImode, operands[1]);
305}")
306
307(define_insn "*movhi_internal"
308  [(set (match_operand:HI 0 "destination_operand" "=r,r,r, m, r,*f,*f")
309	(match_operand:HI 1 "move_operand"        "rO,J,m,rO,*f,rO,*f"))]
310  "ia64_move_ok (operands[0], operands[1])"
311  "@
312   mov %0 = %r1
313   addl %0 = %1, r0
314   ld2%O1 %0 = %1%P1
315   st2%Q0 %0 = %r1%P0
316   getf.sig %0 = %1
317   setf.sig %0 = %r1
318   mov %0 = %1"
319  [(set_attr "itanium_class" "ialu,ialu,ld,st,frfr,tofr,fmisc")])
320
321(define_expand "movsi"
322  [(set (match_operand:SI 0 "general_operand" "")
323	(match_operand:SI 1 "general_operand" ""))]
324  ""
325  "
326{
327  if (! reload_in_progress && ! reload_completed
328      && ! ia64_move_ok (operands[0], operands[1]))
329    operands[1] = force_reg (SImode, operands[1]);
330}")
331
332(define_insn "*movsi_internal"
333  [(set (match_operand:SI 0 "destination_operand" "=r,r,r,r, m, r,*f,*f, r,*d")
334	(match_operand:SI 1 "move_operand"        "rO,J,i,m,rO,*f,rO,*f,*d,rK"))]
335  "ia64_move_ok (operands[0], operands[1])"
336  "@
337  mov %0 = %r1
338  addl %0 = %1, r0
339  movl %0 = %1
340  ld4%O1 %0 = %1%P1
341  st4%Q0 %0 = %r1%P0
342  getf.sig %0 = %1
343  setf.sig %0 = %r1
344  mov %0 = %1
345  mov %0 = %1
346  mov %0 = %r1"
347;; frar_m, toar_m ??? why not frar_i and toar_i
348  [(set_attr "itanium_class" "ialu,ialu,long_i,ld,st,frfr,tofr,fmisc,frar_m,toar_m")])
349
350(define_expand "movdi"
351  [(set (match_operand:DI 0 "general_operand" "")
352	(match_operand:DI 1 "general_operand" ""))]
353  ""
354  "
355{
356  if (! reload_in_progress && ! reload_completed
357      && ! ia64_move_ok (operands[0], operands[1]))
358    operands[1] = force_reg (DImode, operands[1]);
359  if (! TARGET_NO_PIC && symbolic_operand (operands[1], DImode))
360    {
361      /* Before optimization starts, delay committing to any particular
362	 type of PIC address load.  If this function gets deferred, we
363	 may acquire information that changes the value of the
364	 sdata_symbolic_operand predicate.  */
365      /* But don't delay for function pointers.  Loading a function address
366	 actually loads the address of the descriptor not the function.
367	 If we represent these as SYMBOL_REFs, then they get cse'd with
368	 calls, and we end up with calls to the descriptor address instead of
369	 calls to the function address.  Functions are not candidates for
370	 sdata anyways.  */
371      if (rtx_equal_function_value_matters
372	  && ! (GET_CODE (operands[1]) == SYMBOL_REF
373		&& SYMBOL_REF_FLAG (operands[1])))
374	emit_insn (gen_movdi_symbolic (operands[0], operands[1], gen_reg_rtx (DImode)));
375      else
376        ia64_expand_load_address (operands[0], operands[1], NULL_RTX);
377      DONE;
378    }
379}")
380
381;; This is used during early compilation to delay the decision on
382;; how to refer to a variable as long as possible.  This is especially
383;; important between initial rtl generation and optimization for
384;; deferred functions, since we may acquire additional information
385;; on the variables used in the meantime.
386
387;; ??? This causes us to lose REG_LABEL notes, because the insn splitter
388;; does not attempt to preserve any REG_NOTES on the input instruction.
389
390(define_insn_and_split "movdi_symbolic"
391  [(set (match_operand:DI 0 "register_operand" "=r")
392	(match_operand:DI 1 "symbolic_operand" "s"))
393   (clobber (match_operand:DI  2 "register_operand" "+r"))
394   (use (reg:DI 1))]
395  ""
396  "* abort ();"
397  ""
398  [(const_int 0)]
399  "ia64_expand_load_address (operands[0], operands[1], operands[2]); DONE;")
400
401(define_insn "*movdi_internal"
402  [(set (match_operand:DI 0 "destination_operand"
403		    "=r,r,r,r, m, r,*f,*f,*f, Q, r,*b, r,*e, r,*d, r,*c")
404	(match_operand:DI 1 "move_operand"
405		    "rO,J,i,m,rO,*f,rO,*f, Q,*f,*b,rO,*e,rK,*d,rK,*c,rO"))]
406  "ia64_move_ok (operands[0], operands[1])"
407  "*
408{
409  static const char * const alt[] = {
410    \"%,mov %0 = %r1\",
411    \"%,addl %0 = %1, r0\",
412    \"%,movl %0 = %1\",
413    \"%,ld8%O1 %0 = %1%P1\",
414    \"%,st8%Q0 %0 = %r1%P0\",
415    \"%,getf.sig %0 = %1\",
416    \"%,setf.sig %0 = %r1\",
417    \"%,mov %0 = %1\",
418    \"%,ldf8 %0 = %1%P1\",
419    \"%,stf8 %0 = %1%P0\",
420    \"%,mov %0 = %1\",
421    \"%,mov %0 = %r1\",
422    \"%,mov %0 = %1\",
423    \"%,mov %0 = %1\",
424    \"%,mov %0 = %1\",
425    \"%,mov %0 = %1\",
426    \"mov %0 = pr\",
427    \"mov pr = %1, -1\"
428  };
429
430  if (which_alternative == 2 && ! TARGET_NO_PIC
431      && symbolic_operand (operands[1], VOIDmode))
432    abort ();
433
434  return alt[which_alternative];
435}"
436  [(set_attr "itanium_class" "ialu,ialu,long_i,ld,st,frfr,tofr,fmisc,fld,stf,frbr,tobr,frar_i,toar_i,frar_m,toar_m,frpr,topr")])
437
438(define_split
439  [(set (match_operand:DI 0 "register_operand" "")
440	(match_operand:DI 1 "symbolic_operand" ""))]
441  "reload_completed && ! TARGET_NO_PIC"
442  [(const_int 0)]
443  "
444{
445  ia64_expand_load_address (operands[0], operands[1], NULL_RTX);
446  DONE;
447}")
448
449(define_expand "load_fptr"
450  [(set (match_dup 2)
451	(plus:DI (reg:DI 1) (match_operand:DI 1 "function_operand" "")))
452   (set (match_operand:DI 0 "register_operand" "") (match_dup 3))]
453  ""
454  "
455{
456  operands[2] = no_new_pseudos ? operands[0] : gen_reg_rtx (DImode);
457  operands[3] = gen_rtx_MEM (DImode, operands[2]);
458  RTX_UNCHANGING_P (operands[3]) = 1;
459}")
460
461(define_insn "*load_fptr_internal1"
462  [(set (match_operand:DI 0 "register_operand" "=r")
463	(plus:DI (reg:DI 1) (match_operand:DI 1 "function_operand" "s")))]
464  ""
465  "addl %0 = @ltoff(@fptr(%1)), gp"
466  [(set_attr "itanium_class" "ialu")])
467
468(define_insn "load_gprel"
469  [(set (match_operand:DI 0 "register_operand" "=r")
470	(plus:DI (reg:DI 1) (match_operand:DI 1 "sdata_symbolic_operand" "s")))]
471  ""
472  "addl %0 = @gprel(%1), gp"
473  [(set_attr "itanium_class" "ialu")])
474
475(define_insn "gprel64_offset"
476  [(set (match_operand:DI 0 "register_operand" "=r")
477	(minus:DI (match_operand:DI 1 "symbolic_operand" "") (reg:DI 1)))]
478  ""
479  "movl %0 = @gprel(%1)"
480  [(set_attr "itanium_class" "long_i")])
481
482(define_expand "load_gprel64"
483  [(set (match_dup 2)
484	(minus:DI (match_operand:DI 1 "symbolic_operand" "") (match_dup 3)))
485   (set (match_operand:DI 0 "register_operand" "")
486	(plus:DI (match_dup 3) (match_dup 2)))]
487  ""
488  "
489{
490  operands[2] = no_new_pseudos ? operands[0] : gen_reg_rtx (DImode);
491  operands[3] = pic_offset_table_rtx;
492}")
493
494(define_expand "load_symptr"
495  [(set (match_operand:DI 2 "register_operand" "")
496	(plus:DI (match_dup 4) (match_operand:DI 1 "got_symbolic_operand" "")))
497   (set (match_operand:DI 0 "register_operand" "") (match_dup 3))]
498  ""
499  "
500{
501  operands[3] = gen_rtx_MEM (DImode, operands[2]);
502  operands[4] = pic_offset_table_rtx;
503  RTX_UNCHANGING_P (operands[3]) = 1;
504}")
505
506(define_insn "*load_symptr_internal1"
507  [(set (match_operand:DI 0 "register_operand" "=r")
508	(plus:DI (reg:DI 1) (match_operand:DI 1 "got_symbolic_operand" "s")))]
509  ""
510  "addl %0 = @ltoff(%1), gp"
511  [(set_attr "itanium_class" "ialu")])
512
513;; With no offsettable memory references, we've got to have a scratch
514;; around to play with the second word.
515(define_expand "movti"
516  [(parallel [(set (match_operand:TI 0 "general_operand" "")
517		   (match_operand:TI 1 "general_operand" ""))
518	      (clobber (match_scratch:DI 2 ""))])]
519  ""
520  "
521{
522  if (! reload_in_progress && ! reload_completed
523      && ! ia64_move_ok (operands[0], operands[1]))
524    operands[1] = force_reg (TImode, operands[1]);
525}")
526
527(define_insn_and_split "*movti_internal"
528  [(set (match_operand:TI 0 "nonimmediate_operand" "=r,r,m")
529	(match_operand:TI 1 "general_operand"      "ri,m,r"))
530   (clobber (match_scratch:DI 2 "=X,&r,&r"))]
531  "ia64_move_ok (operands[0], operands[1])"
532  "#"
533  "reload_completed"
534  [(const_int 0)]
535  "
536{
537  rtx adj1, adj2, in[2], out[2], insn;
538  int first;
539
540  adj1 = ia64_split_timode (in, operands[1], operands[2]);
541  adj2 = ia64_split_timode (out, operands[0], operands[2]);
542
543  first = 0;
544  if (reg_overlap_mentioned_p (out[0], in[1]))
545    {
546      if (reg_overlap_mentioned_p (out[1], in[0]))
547	abort ();
548      first = 1;
549    }
550
551  if (adj1 && adj2)
552    abort ();
553  if (adj1)
554    emit_insn (adj1);
555  if (adj2)
556    emit_insn (adj2);
557  insn = emit_insn (gen_rtx_SET (VOIDmode, out[first], in[first]));
558  if (GET_CODE (out[first]) == MEM
559      && GET_CODE (XEXP (out[first], 0)) == POST_MODIFY)
560    REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_INC,
561					  XEXP (XEXP (out[first], 0), 0),
562					  REG_NOTES (insn));
563  insn = emit_insn (gen_rtx_SET (VOIDmode, out[!first], in[!first]));
564  if (GET_CODE (out[!first]) == MEM
565      && GET_CODE (XEXP (out[!first], 0)) == POST_MODIFY)
566    REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_INC,
567					  XEXP (XEXP (out[!first], 0), 0),
568					  REG_NOTES (insn));
569  DONE;
570}"
571  [(set_attr "itanium_class" "unknown")
572   (set_attr "predicable" "no")])
573
574;; ??? SSA creates these.  Can't allow memories since we don't have
575;; the scratch register.  Fortunately combine will know how to add
576;; the clobber and scratch.
577(define_insn_and_split "*movti_internal_reg"
578  [(set (match_operand:TI 0 "register_operand"  "=r")
579	(match_operand:TI 1 "nonmemory_operand" "ri"))]
580  ""
581  "#"
582  "reload_completed"
583  [(const_int 0)]
584  "
585{
586  rtx in[2], out[2];
587  int first;
588
589  ia64_split_timode (in, operands[1], NULL_RTX);
590  ia64_split_timode (out, operands[0], NULL_RTX);
591
592  first = 0;
593  if (reg_overlap_mentioned_p (out[0], in[1]))
594    {
595      if (reg_overlap_mentioned_p (out[1], in[0]))
596	abort ();
597      first = 1;
598    }
599
600  emit_insn (gen_rtx_SET (VOIDmode, out[first], in[first]));
601  emit_insn (gen_rtx_SET (VOIDmode, out[!first], in[!first]));
602  DONE;
603}"
604  [(set_attr "itanium_class" "unknown")
605   (set_attr "predicable" "no")])
606
607(define_expand "reload_inti"
608  [(parallel [(set (match_operand:TI 0 "register_operand" "=r")
609		   (match_operand:TI 1 "" "m"))
610	      (clobber (match_operand:TI 2 "register_operand" "=&r"))])]
611  ""
612  "
613{
614  unsigned int s_regno = REGNO (operands[2]);
615  if (s_regno == REGNO (operands[0]))
616    s_regno += 1;
617  operands[2] = gen_rtx_REG (DImode, s_regno);
618}")
619
620(define_expand "reload_outti"
621  [(parallel [(set (match_operand:TI 0 "" "=m")
622		   (match_operand:TI 1 "register_operand" "r"))
623	      (clobber (match_operand:TI 2 "register_operand" "=&r"))])]
624  ""
625  "
626{
627  unsigned int s_regno = REGNO (operands[2]);
628  if (s_regno == REGNO (operands[1]))
629    s_regno += 1;
630  operands[2] = gen_rtx_REG (DImode, s_regno);
631}")
632
633;; Floating Point Moves
634;;
635;; Note - Patterns for SF mode moves are compulsory, but
636;; patterns for DF are optional, as GCC can synthesise them.
637
638(define_expand "movsf"
639  [(set (match_operand:SF 0 "general_operand" "")
640	(match_operand:SF 1 "general_operand" ""))]
641  ""
642  "
643{
644  if (! reload_in_progress && ! reload_completed
645      && ! ia64_move_ok (operands[0], operands[1]))
646    operands[1] = force_reg (SFmode, operands[1]);
647}")
648
649(define_insn "*movsf_internal"
650  [(set (match_operand:SF 0 "destination_operand" "=f,f, Q,*r, f,*r,*r, m")
651	(match_operand:SF 1 "general_operand"     "fG,Q,fG,fG,*r,*r, m,*r"))]
652  "ia64_move_ok (operands[0], operands[1])"
653  "@
654  mov %0 = %F1
655  ldfs %0 = %1%P1
656  stfs %0 = %F1%P0
657  getf.s %0 = %F1
658  setf.s %0 = %1
659  mov %0 = %1
660  ld4%O1 %0 = %1%P1
661  st4%Q0 %0 = %1%P0"
662  [(set_attr "itanium_class" "fmisc,fld,stf,frfr,tofr,ialu,ld,st")])
663
664(define_expand "movdf"
665  [(set (match_operand:DF 0 "general_operand" "")
666	(match_operand:DF 1 "general_operand" ""))]
667  ""
668  "
669{
670  if (! reload_in_progress && ! reload_completed
671      && ! ia64_move_ok (operands[0], operands[1]))
672    operands[1] = force_reg (DFmode, operands[1]);
673}")
674
675(define_insn "*movdf_internal"
676  [(set (match_operand:DF 0 "destination_operand" "=f,f, Q,*r, f,*r,*r, m")
677	(match_operand:DF 1 "general_operand"     "fG,Q,fG,fG,*r,*r, m,*r"))]
678  "ia64_move_ok (operands[0], operands[1])"
679  "@
680  mov %0 = %F1
681  ldfd %0 = %1%P1
682  stfd %0 = %F1%P0
683  getf.d %0 = %F1
684  setf.d %0 = %1
685  mov %0 = %1
686  ld8%O1 %0 = %1%P1
687  st8%Q0 %0 = %1%P0"
688  [(set_attr "itanium_class" "fmisc,fld,stf,frfr,tofr,ialu,ld,st")])
689
690;; With no offsettable memory references, we've got to have a scratch
691;; around to play with the second word if the variable winds up in GRs.
692(define_expand "movtf"
693  [(set (match_operand:TF 0 "general_operand" "")
694	(match_operand:TF 1 "general_operand" ""))]
695  "INTEL_EXTENDED_IEEE_FORMAT"
696  "
697{
698  /* We must support TFmode loads into general registers for stdarg/vararg
699     and unprototyped calls.  We split them into DImode loads for convenience.
700     We don't need TFmode stores from general regs, because a stdarg/vararg
701     routine does a block store to memory of unnamed arguments.  */
702  if (GET_CODE (operands[0]) == REG
703      && GR_REGNO_P (REGNO (operands[0])))
704    {
705      /* We're hoping to transform everything that deals with TFmode
706	 quantities and GR registers early in the compiler.  */
707      if (no_new_pseudos)
708	abort ();
709
710      /* Struct to register can just use TImode instead.  */
711      if ((GET_CODE (operands[1]) == SUBREG
712	   && GET_MODE (SUBREG_REG (operands[1])) == TImode)
713	  || (GET_CODE (operands[1]) == REG
714	      && GR_REGNO_P (REGNO (operands[1]))))
715	{
716	  emit_move_insn (gen_rtx_REG (TImode, REGNO (operands[0])),
717			  SUBREG_REG (operands[1]));
718	  DONE;
719	}
720
721      if (GET_CODE (operands[1]) == CONST_DOUBLE)
722	{
723	  emit_move_insn (gen_rtx_REG (DImode, REGNO (operands[0])),
724			  operand_subword (operands[1], 0, 0, TFmode));
725	  emit_move_insn (gen_rtx_REG (DImode, REGNO (operands[0]) + 1),
726			  operand_subword (operands[1], 1, 0, TFmode));
727	  DONE;
728	}
729
730      /* If the quantity is in a register not known to be GR, spill it.  */
731      if (register_operand (operands[1], TFmode))
732	operands[1] = spill_tfmode_operand (operands[1], 1);
733
734      if (GET_CODE (operands[1]) == MEM)
735	{
736	  rtx out[2];
737
738	  out[WORDS_BIG_ENDIAN] = gen_rtx_REG (DImode, REGNO (operands[0]));
739	  out[!WORDS_BIG_ENDIAN] = gen_rtx_REG (DImode, REGNO (operands[0])+1);
740
741	  emit_move_insn (out[0], adjust_address (operands[1], DImode, 0));
742	  emit_move_insn (out[1], adjust_address (operands[1], DImode, 8));
743	  DONE;
744	}
745
746      abort ();
747    }
748
749  if (! reload_in_progress && ! reload_completed)
750    {
751      operands[0] = spill_tfmode_operand (operands[0], 0);
752      operands[1] = spill_tfmode_operand (operands[1], 0);
753
754      if (! ia64_move_ok (operands[0], operands[1]))
755	operands[1] = force_reg (TFmode, operands[1]);
756    }
757}")
758
759;; ??? There's no easy way to mind volatile acquire/release semantics.
760
761(define_insn "*movtf_internal"
762  [(set (match_operand:TF 0 "destination_tfmode_operand" "=f,f, m")
763	(match_operand:TF 1 "general_tfmode_operand"     "fG,m,fG"))]
764  "INTEL_EXTENDED_IEEE_FORMAT && ia64_move_ok (operands[0], operands[1])"
765  "@
766  mov %0 = %F1
767  ldfe %0 = %1%P1
768  stfe %0 = %F1%P0"
769  [(set_attr "itanium_class" "fmisc,fld,stf")])
770
771;; ::::::::::::::::::::
772;; ::
773;; :: Conversions
774;; ::
775;; ::::::::::::::::::::
776
777;; Signed conversions from a smaller integer to a larger integer
778
779(define_insn "extendqidi2"
780  [(set (match_operand:DI 0 "gr_register_operand" "=r")
781	(sign_extend:DI (match_operand:QI 1 "gr_register_operand" "r")))]
782  ""
783  "sxt1 %0 = %1"
784  [(set_attr "itanium_class" "xtd")])
785
786(define_insn "extendhidi2"
787  [(set (match_operand:DI 0 "gr_register_operand" "=r")
788	(sign_extend:DI (match_operand:HI 1 "gr_register_operand" "r")))]
789  ""
790  "sxt2 %0 = %1"
791  [(set_attr "itanium_class" "xtd")])
792
793(define_insn "extendsidi2"
794  [(set (match_operand:DI 0 "grfr_register_operand" "=r,?f")
795	(sign_extend:DI (match_operand:SI 1 "grfr_register_operand" "r,f")))]
796  ""
797  "@
798   sxt4 %0 = %1
799   fsxt.r %0 = %1, %1"
800  [(set_attr "itanium_class" "xtd,fmisc")])
801
802;; Unsigned conversions from a smaller integer to a larger integer
803
804(define_insn "zero_extendqidi2"
805  [(set (match_operand:DI 0 "gr_register_operand" "=r,r")
806	(zero_extend:DI (match_operand:QI 1 "gr_nonimmediate_operand" "r,m")))]
807  ""
808  "@
809   zxt1 %0 = %1
810   ld1%O1 %0 = %1%P1"
811  [(set_attr "itanium_class" "xtd,ld")])
812
813(define_insn "zero_extendhidi2"
814  [(set (match_operand:DI 0 "gr_register_operand" "=r,r")
815	(zero_extend:DI (match_operand:HI 1 "gr_nonimmediate_operand" "r,m")))]
816  ""
817  "@
818   zxt2 %0 = %1
819   ld2%O1 %0 = %1%P1"
820  [(set_attr "itanium_class" "xtd,ld")])
821
822(define_insn "zero_extendsidi2"
823  [(set (match_operand:DI 0 "grfr_register_operand" "=r,r,?f")
824	(zero_extend:DI
825	  (match_operand:SI 1 "grfr_nonimmediate_operand" "r,m,f")))]
826  ""
827  "@
828   zxt4 %0 = %1
829   ld4%O1 %0 = %1%P1
830   fmix.r %0 = f0, %1"
831  [(set_attr "itanium_class" "xtd,ld,fmisc")])
832
833;; Convert between floating point types of different sizes.
834
835;; At first glance, it would appear that emitting fnorm for an extending
836;; conversion is unnecessary.  However, the stf and getf instructions work
837;; correctly only if the input is properly rounded for its type.  In
838;; particular, we get the wrong result for getf.d/stfd if the input is a
839;; denorm single.  Since we don't know what the next instruction will be, we
840;; have to emit an fnorm.
841
842;; ??? Optimization opportunity here.  Get rid of the insn altogether
843;; when we can.  Should probably use a scheme like has been proposed
844;; for ia32 in dealing with operands that match unary operators.  This
845;; would let combine merge the thing into adjacent insns.  See also how the
846;; mips port handles SIGN_EXTEND as operands to integer arithmetic insns via
847;; se_register_operand.
848
849(define_insn "extendsfdf2"
850  [(set (match_operand:DF 0 "fr_register_operand" "=f")
851	(float_extend:DF (match_operand:SF 1 "fr_register_operand" "f")))]
852  ""
853  "fnorm.d %0 = %1"
854  [(set_attr "itanium_class" "fmac")])
855
856(define_insn "extendsftf2"
857  [(set (match_operand:TF 0 "fr_register_operand" "=f")
858	(float_extend:TF (match_operand:SF 1 "fr_register_operand" "f")))]
859  "INTEL_EXTENDED_IEEE_FORMAT"
860  "fnorm %0 = %1"
861  [(set_attr "itanium_class" "fmac")])
862
863(define_insn "extenddftf2"
864  [(set (match_operand:TF 0 "fr_register_operand" "=f")
865	(float_extend:TF (match_operand:DF 1 "fr_register_operand" "f")))]
866  "INTEL_EXTENDED_IEEE_FORMAT"
867  "fnorm %0 = %1"
868  [(set_attr "itanium_class" "fmac")])
869
870(define_insn "truncdfsf2"
871  [(set (match_operand:SF 0 "fr_register_operand" "=f")
872	(float_truncate:SF (match_operand:DF 1 "fr_register_operand" "f")))]
873  ""
874  "fnorm.s %0 = %1"
875  [(set_attr "itanium_class" "fmac")])
876
877(define_insn "trunctfsf2"
878  [(set (match_operand:SF 0 "fr_register_operand" "=f")
879	(float_truncate:SF (match_operand:TF 1 "fr_register_operand" "f")))]
880  "INTEL_EXTENDED_IEEE_FORMAT"
881  "fnorm.s %0 = %1"
882  [(set_attr "itanium_class" "fmac")])
883
884(define_insn "trunctfdf2"
885  [(set (match_operand:DF 0 "fr_register_operand" "=f")
886	(float_truncate:DF (match_operand:TF 1 "fr_register_operand" "f")))]
887  "INTEL_EXTENDED_IEEE_FORMAT"
888  "fnorm.d %0 = %1"
889  [(set_attr "itanium_class" "fmac")])
890
891;; Convert between signed integer types and floating point.
892
893(define_insn "floatditf2"
894  [(set (match_operand:TF 0 "fr_register_operand" "=f")
895	(float:TF (match_operand:DI 1 "fr_register_operand" "f")))]
896  "INTEL_EXTENDED_IEEE_FORMAT"
897  "fcvt.xf %0 = %1"
898  [(set_attr "itanium_class" "fcvtfx")])
899
900;; ??? Suboptimal.  This should be split somehow.
901(define_insn "floatdidf2"
902  [(set (match_operand:DF 0 "register_operand" "=f")
903        (float:DF (match_operand:DI 1 "register_operand" "f")))]
904  "!INTEL_EXTENDED_IEEE_FORMAT"
905  "fcvt.xf %0 = %1\;;;\;fnorm.d %0 = %0"
906  [(set_attr "itanium_class" "fcvtfx")])
907
908;; ??? Suboptimal.  This should be split somehow.
909(define_insn "floatdisf2"
910  [(set (match_operand:SF 0 "register_operand" "=f")
911        (float:SF (match_operand:DI 1 "register_operand" "f")))]
912  "!INTEL_EXTENDED_IEEE_FORMAT"
913  "fcvt.xf %0 = %1\;;;\;fnorm.s %0 = %0"
914  [(set_attr "itanium_class" "fcvtfx")])
915
916(define_insn "fix_truncsfdi2"
917  [(set (match_operand:DI 0 "fr_register_operand" "=f")
918	(fix:DI (match_operand:SF 1 "fr_register_operand" "f")))]
919  ""
920  "fcvt.fx.trunc %0 = %1"
921  [(set_attr "itanium_class" "fcvtfx")])
922
923(define_insn "fix_truncdfdi2"
924  [(set (match_operand:DI 0 "fr_register_operand" "=f")
925	(fix:DI (match_operand:DF 1 "fr_register_operand" "f")))]
926  ""
927  "fcvt.fx.trunc %0 = %1"
928  [(set_attr "itanium_class" "fcvtfx")])
929
930(define_insn "fix_trunctfdi2"
931  [(set (match_operand:DI 0 "fr_register_operand" "=f")
932	(fix:DI (match_operand:TF 1 "fr_register_operand" "f")))]
933  "INTEL_EXTENDED_IEEE_FORMAT"
934  "fcvt.fx.trunc %0 = %1"
935  [(set_attr "itanium_class" "fcvtfx")])
936
937(define_insn "fix_trunctfdi2_alts"
938  [(set (match_operand:DI 0 "fr_register_operand" "=f")
939	(fix:DI (match_operand:TF 1 "fr_register_operand" "f")))
940   (use (match_operand:SI 2 "const_int_operand" ""))]
941  "INTEL_EXTENDED_IEEE_FORMAT"
942  "fcvt.fx.trunc.s%2 %0 = %1"
943  [(set_attr "itanium_class" "fcvtfx")])
944
945;; Convert between unsigned integer types and floating point.
946
947(define_insn "floatunsdisf2"
948  [(set (match_operand:SF 0 "fr_register_operand" "=f")
949	(unsigned_float:SF (match_operand:DI 1 "fr_register_operand" "f")))]
950  ""
951  "fcvt.xuf.s %0 = %1"
952  [(set_attr "itanium_class" "fcvtfx")])
953
954(define_insn "floatunsdidf2"
955  [(set (match_operand:DF 0 "fr_register_operand" "=f")
956	(unsigned_float:DF (match_operand:DI 1 "fr_register_operand" "f")))]
957  ""
958  "fcvt.xuf.d %0 = %1"
959  [(set_attr "itanium_class" "fcvtfx")])
960
961(define_insn "floatunsditf2"
962  [(set (match_operand:TF 0 "fr_register_operand" "=f")
963	(unsigned_float:TF (match_operand:DI 1 "fr_register_operand" "f")))]
964  "INTEL_EXTENDED_IEEE_FORMAT"
965  "fcvt.xuf %0 = %1"
966  [(set_attr "itanium_class" "fcvtfx")])
967
968(define_insn "fixuns_truncsfdi2"
969  [(set (match_operand:DI 0 "fr_register_operand" "=f")
970	(unsigned_fix:DI (match_operand:SF 1 "fr_register_operand" "f")))]
971  ""
972  "fcvt.fxu.trunc %0 = %1"
973  [(set_attr "itanium_class" "fcvtfx")])
974
975(define_insn "fixuns_truncdfdi2"
976  [(set (match_operand:DI 0 "fr_register_operand" "=f")
977	(unsigned_fix:DI (match_operand:DF 1 "fr_register_operand" "f")))]
978  ""
979  "fcvt.fxu.trunc %0 = %1"
980  [(set_attr "itanium_class" "fcvtfx")])
981
982(define_insn "fixuns_trunctfdi2"
983  [(set (match_operand:DI 0 "fr_register_operand" "=f")
984	(unsigned_fix:DI (match_operand:TF 1 "fr_register_operand" "f")))]
985  "INTEL_EXTENDED_IEEE_FORMAT"
986  "fcvt.fxu.trunc %0 = %1"
987  [(set_attr "itanium_class" "fcvtfx")])
988
989(define_insn "fixuns_trunctfdi2_alts"
990  [(set (match_operand:DI 0 "fr_register_operand" "=f")
991	(unsigned_fix:DI (match_operand:TF 1 "fr_register_operand" "f")))
992   (use (match_operand:SI 2 "const_int_operand" ""))]
993  "INTEL_EXTENDED_IEEE_FORMAT"
994  "fcvt.fxu.trunc.s%2 %0 = %1"
995  [(set_attr "itanium_class" "fcvtfx")])
996
997;; ::::::::::::::::::::
998;; ::
999;; :: Bit field extraction
1000;; ::
1001;; ::::::::::::::::::::
1002
1003(define_insn "extv"
1004  [(set (match_operand:DI 0 "gr_register_operand" "=r")
1005	(sign_extract:DI (match_operand:DI 1 "gr_register_operand" "r")
1006			 (match_operand:DI 2 "const_int_operand" "n")
1007			 (match_operand:DI 3 "const_int_operand" "n")))]
1008  ""
1009  "extr %0 = %1, %3, %2"
1010  [(set_attr "itanium_class" "ishf")])
1011
1012(define_insn "extzv"
1013  [(set (match_operand:DI 0 "gr_register_operand" "=r")
1014	(zero_extract:DI (match_operand:DI 1 "gr_register_operand" "r")
1015			 (match_operand:DI 2 "const_int_operand" "n")
1016			 (match_operand:DI 3 "const_int_operand" "n")))]
1017  ""
1018  "extr.u %0 = %1, %3, %2"
1019  [(set_attr "itanium_class" "ishf")])
1020
1021;; Insert a bit field.
1022;; Can have 3 operands, source1 (inserter), source2 (insertee), dest.
1023;; Source1 can be 0 or -1.
1024;; Source2 can be 0.
1025
1026;; ??? Actual dep instruction is more powerful than what these insv
1027;; patterns support.  Unfortunately, combine is unable to create patterns
1028;; where source2 != dest.
1029
1030(define_expand "insv"
1031  [(set (zero_extract:DI (match_operand:DI 0 "gr_register_operand" "")
1032			 (match_operand:DI 1 "const_int_operand" "")
1033			 (match_operand:DI 2 "const_int_operand" ""))
1034	(match_operand:DI 3 "nonmemory_operand" ""))]
1035  ""
1036  "
1037{
1038  int width = INTVAL (operands[1]);
1039  int shift = INTVAL (operands[2]);
1040
1041  /* If operand[3] is a constant, and isn't 0 or -1, then load it into a
1042     pseudo.  */
1043  if (! register_operand (operands[3], DImode)
1044      && operands[3] != const0_rtx && operands[3] != constm1_rtx)
1045    operands[3] = force_reg (DImode, operands[3]);
1046
1047  /* If this is a single dep instruction, we have nothing to do.  */
1048  if (! ((register_operand (operands[3], DImode) && width <= 16)
1049	 || operands[3] == const0_rtx || operands[3] == constm1_rtx))
1050    {
1051      /* Check for cases that can be implemented with a mix instruction.  */
1052      if (width == 32 && shift == 0)
1053	{
1054	  /* Directly generating the mix4left instruction confuses
1055	     optimize_bit_field in function.c.  Since this is performing
1056	     a useful optimization, we defer generation of the complicated
1057	     mix4left RTL to the first splitting phase.  */
1058	  rtx tmp = gen_reg_rtx (DImode);
1059	  emit_insn (gen_shift_mix4left (operands[0], operands[3], tmp));
1060	  DONE;
1061	}
1062      else if (width == 32 && shift == 32)
1063	{
1064	  emit_insn (gen_mix4right (operands[0], operands[3]));
1065	  DONE;
1066	}
1067
1068      /* We could handle remaining cases by emitting multiple dep
1069	 instructions.
1070
1071	 If we need more than two dep instructions then we lose.  A 6
1072	 insn sequence mov mask1,mov mask2,shl;;and,and;;or is better than
1073	 mov;;dep,shr;;dep,shr;;dep.  The former can be executed in 3 cycles,
1074	 the latter is 6 cycles on an Itanium (TM) processor, because there is
1075	 only one function unit that can execute dep and shr immed.
1076
1077	 If we only need two dep instruction, then we still lose.
1078	 mov;;dep,shr;;dep is still 4 cycles.  Even if we optimize away
1079	 the unnecessary mov, this is still undesirable because it will be
1080	 hard to optimize, and it creates unnecessary pressure on the I0
1081	 function unit.  */
1082
1083      FAIL;
1084
1085#if 0
1086      /* This code may be useful for other IA-64 processors, so we leave it in
1087	 for now.  */
1088      while (width > 16)
1089	{
1090	  rtx tmp;
1091
1092	  emit_insn (gen_insv (operands[0], GEN_INT (16), GEN_INT (shift),
1093			       operands[3]));
1094	  shift += 16;
1095	  width -= 16;
1096	  tmp = gen_reg_rtx (DImode);
1097	  emit_insn (gen_lshrdi3 (tmp, operands[3], GEN_INT (16)));
1098	  operands[3] = tmp;
1099	}
1100      operands[1] = GEN_INT (width);
1101      operands[2] = GEN_INT (shift);
1102#endif
1103    }
1104}")
1105
1106(define_insn "*insv_internal"
1107  [(set (zero_extract:DI (match_operand:DI 0 "gr_register_operand" "+r")
1108			 (match_operand:DI 1 "const_int_operand" "n")
1109			 (match_operand:DI 2 "const_int_operand" "n"))
1110	(match_operand:DI 3 "nonmemory_operand" "rP"))]
1111  "(gr_register_operand (operands[3], DImode) && INTVAL (operands[1]) <= 16)
1112   || operands[3] == const0_rtx || operands[3] == constm1_rtx"
1113  "dep %0 = %3, %0, %2, %1"
1114  [(set_attr "itanium_class" "ishf")])
1115
1116;; Combine doesn't like to create bitfield insertions into zero.
1117(define_insn "*depz_internal"
1118  [(set (match_operand:DI 0 "gr_register_operand" "=r")
1119	(and:DI (ashift:DI (match_operand:DI 1 "gr_register_operand" "r")
1120			   (match_operand:DI 2 "const_int_operand" "n"))
1121		(match_operand:DI 3 "const_int_operand" "n")))]
1122  "CONST_OK_FOR_M (INTVAL (operands[2]))
1123   && ia64_depz_field_mask (operands[3], operands[2]) > 0"
1124  "*
1125{
1126  operands[3] = GEN_INT (ia64_depz_field_mask (operands[3], operands[2]));
1127  return \"%,dep.z %0 = %1, %2, %3\";
1128}"
1129  [(set_attr "itanium_class" "ishf")])
1130
1131(define_insn "shift_mix4left"
1132  [(set (zero_extract:DI (match_operand:DI 0 "gr_register_operand" "+r")
1133			 (const_int 32) (const_int 0))
1134	(match_operand:DI 1 "gr_register_operand" "r"))
1135   (clobber (match_operand:DI 2 "gr_register_operand" "=r"))]
1136  ""
1137  "#"
1138  [(set_attr "itanium_class" "unknown")])
1139
1140(define_split
1141  [(set (zero_extract:DI (match_operand:DI 0 "register_operand" "")
1142			 (const_int 32) (const_int 0))
1143	(match_operand:DI 1 "register_operand" ""))
1144   (clobber (match_operand:DI 2 "register_operand" ""))]
1145  "reload_completed"
1146  [(set (match_dup 3) (ashift:DI (match_dup 1) (const_int 32)))
1147   (set (zero_extract:DI (match_dup 0) (const_int 32) (const_int 0))
1148	(lshiftrt:DI (match_dup 3) (const_int 32)))]
1149  "operands[3] = operands[2];")
1150
1151(define_split
1152  [(set (zero_extract:DI (match_operand:DI 0 "register_operand" "")
1153			 (const_int 32) (const_int 0))
1154	(match_operand:DI 1 "register_operand" ""))
1155   (clobber (match_operand:DI 2 "register_operand" ""))]
1156  "! reload_completed"
1157  [(set (match_dup 3) (ashift:DI (match_dup 1) (const_int 32)))
1158   (set (zero_extract:DI (match_dup 0) (const_int 32) (const_int 0))
1159	(lshiftrt:DI (match_dup 3) (const_int 32)))]
1160  "operands[3] = operands[2];")
1161
1162(define_insn "*mix4left"
1163  [(set (zero_extract:DI (match_operand:DI 0 "gr_register_operand" "+r")
1164			 (const_int 32) (const_int 0))
1165	(lshiftrt:DI (match_operand:DI 1 "gr_register_operand" "r")
1166		     (const_int 32)))]
1167  ""
1168  "mix4.l %0 = %0, %r1"
1169  [(set_attr "itanium_class" "mmshf")])
1170
1171(define_insn "mix4right"
1172  [(set (zero_extract:DI (match_operand:DI 0 "gr_register_operand" "+r")
1173			 (const_int 32) (const_int 32))
1174	(match_operand:DI 1 "gr_reg_or_0_operand" "rO"))]
1175  ""
1176  "mix4.r %0 = %r1, %0"
1177  [(set_attr "itanium_class" "mmshf")])
1178
1179;; This is used by the rotrsi3 pattern.
1180
1181(define_insn "*mix4right_3op"
1182  [(set (match_operand:DI 0 "gr_register_operand" "=r")
1183	(ior:DI (zero_extend:DI (match_operand:SI 1 "gr_register_operand" "r"))
1184		(ashift:DI (zero_extend:DI
1185			     (match_operand:SI 2 "gr_register_operand" "r"))
1186			   (const_int 32))))]
1187  ""
1188  "mix4.r %0 = %2, %1"
1189  [(set_attr "itanium_class" "mmshf")])
1190
1191
1192;; ::::::::::::::::::::
1193;; ::
1194;; :: 1 bit Integer arithmetic
1195;; ::
1196;; ::::::::::::::::::::
1197
1198(define_insn_and_split "andbi3"
1199  [(set (match_operand:BI 0 "register_operand" "=c,c,r")
1200	(and:BI (match_operand:BI 1 "register_operand" "%0,0,r")
1201		(match_operand:BI 2 "register_operand" "c,r,r")))]
1202  ""
1203  "@
1204   #
1205   tbit.nz.and.orcm %0, %I0 = %2, 0
1206   and %0 = %2, %1"
1207  "reload_completed
1208   && GET_CODE (operands[0]) == REG && PR_REGNO_P (REGNO (operands[0]))
1209   && GET_CODE (operands[2]) == REG && PR_REGNO_P (REGNO (operands[2]))"
1210  [(cond_exec (eq (match_dup 2) (const_int 0))
1211     (set (match_dup 0) (and:BI (ne:BI (const_int 0) (const_int 0))
1212				(match_dup 0))))]
1213  ""
1214  [(set_attr "itanium_class" "unknown,tbit,ilog")])
1215
1216(define_insn_and_split "*andcmbi3"
1217  [(set (match_operand:BI 0 "register_operand" "=c,c,r")
1218	(and:BI (not:BI (match_operand:BI 1 "register_operand" "c,r,r"))
1219		(match_operand:BI 2 "register_operand" "0,0,r")))]
1220  ""
1221  "@
1222   #
1223   tbit.z.and.orcm %0, %I0 = %1, 0
1224   andcm %0 = %2, %1"
1225  "reload_completed
1226   && GET_CODE (operands[0]) == REG && PR_REGNO_P (REGNO (operands[0]))
1227   && GET_CODE (operands[1]) == REG && PR_REGNO_P (REGNO (operands[1]))"
1228  [(cond_exec (ne (match_dup 1) (const_int 0))
1229     (set (match_dup 0) (and:BI (ne:BI (const_int 0) (const_int 0))
1230				(match_dup 0))))]
1231  ""
1232  [(set_attr "itanium_class" "unknown,tbit,ilog")])
1233
1234(define_insn_and_split "iorbi3"
1235  [(set (match_operand:BI 0 "register_operand" "=c,c,r")
1236	(ior:BI (match_operand:BI 1 "register_operand" "%0,0,r")
1237		(match_operand:BI 2 "register_operand" "c,r,r")))]
1238  ""
1239  "@
1240   #
1241   tbit.nz.or.andcm %0, %I0 = %2, 0
1242   or %0 = %2, %1"
1243  "reload_completed
1244   && GET_CODE (operands[0]) == REG && PR_REGNO_P (REGNO (operands[0]))
1245   && GET_CODE (operands[2]) == REG && PR_REGNO_P (REGNO (operands[2]))"
1246  [(cond_exec (ne (match_dup 2) (const_int 0))
1247     (set (match_dup 0) (ior:BI (eq:BI (const_int 0) (const_int 0))
1248				(match_dup 0))))]
1249  ""
1250  [(set_attr "itanium_class" "unknown,tbit,ilog")])
1251
1252(define_insn_and_split "*iorcmbi3"
1253  [(set (match_operand:BI 0 "register_operand" "=c,c")
1254	(ior:BI (not:BI (match_operand:BI 1 "register_operand" "c,r"))
1255		(match_operand:BI 2 "register_operand" "0,0")))]
1256  ""
1257  "@
1258   #
1259   tbit.z.or.andcm %0, %I0 = %1, 0"
1260  "reload_completed
1261   && GET_CODE (operands[0]) == REG && PR_REGNO_P (REGNO (operands[0]))
1262   && GET_CODE (operands[1]) == REG && PR_REGNO_P (REGNO (operands[1]))"
1263  [(cond_exec (eq (match_dup 1) (const_int 0))
1264     (set (match_dup 0) (ior:BI (eq:BI (const_int 0) (const_int 0))
1265				(match_dup 0))))]
1266  ""
1267  [(set_attr "itanium_class" "unknown,tbit")])
1268
1269(define_insn "one_cmplbi2"
1270  [(set (match_operand:BI 0 "register_operand" "=c,r,c,&c")
1271	(not:BI (match_operand:BI 1 "register_operand" "r,r,0,c")))
1272   (clobber (match_scratch:BI 2 "=X,X,c,X"))]
1273  ""
1274  "@
1275   tbit.z %0, %I0 = %1, 0
1276   xor %0 = 1, %1
1277   #
1278   #"
1279  [(set_attr "itanium_class" "tbit,ilog,unknown,unknown")])
1280
1281(define_split
1282  [(set (match_operand:BI 0 "register_operand" "")
1283	(not:BI (match_operand:BI 1 "register_operand" "")))
1284   (clobber (match_scratch:BI 2 ""))]
1285  "reload_completed
1286   && GET_CODE (operands[0]) == REG && PR_REGNO_P (REGNO (operands[0]))
1287   && rtx_equal_p (operands[0], operands[1])"
1288  [(set (match_dup 4) (match_dup 3))
1289   (set (match_dup 0) (const_int 1))
1290   (cond_exec (ne (match_dup 2) (const_int 0))
1291     (set (match_dup 0) (const_int 0)))
1292   (set (match_dup 0) (unspec:BI [(match_dup 0)] 7))]
1293  "operands[3] = gen_rtx_REG (CCImode, REGNO (operands[1]));
1294   operands[4] = gen_rtx_REG (CCImode, REGNO (operands[2]));")
1295
1296(define_split
1297  [(set (match_operand:BI 0 "register_operand" "")
1298	(not:BI (match_operand:BI 1 "register_operand" "")))
1299   (clobber (match_scratch:BI 2 ""))]
1300  "reload_completed
1301   && GET_CODE (operands[0]) == REG && PR_REGNO_P (REGNO (operands[0]))
1302   && GET_CODE (operands[1]) == REG && PR_REGNO_P (REGNO (operands[1]))
1303   && ! rtx_equal_p (operands[0], operands[1])"
1304  [(cond_exec (ne (match_dup 1) (const_int 0))
1305     (set (match_dup 0) (const_int 0)))
1306   (cond_exec (eq (match_dup 1) (const_int 0))
1307     (set (match_dup 0) (const_int 1)))
1308   (set (match_dup 0) (unspec:BI [(match_dup 0)] 7))]
1309  "")
1310
1311(define_insn "*cmpsi_and_0"
1312  [(set (match_operand:BI 0 "register_operand" "=c")
1313	(and:BI (match_operator:BI 4 "predicate_operator"
1314		  [(match_operand:SI 2 "gr_reg_or_0_operand" "rO")
1315		   (match_operand:SI 3 "gr_reg_or_8bit_operand" "rK")])
1316		(match_operand:BI 1 "register_operand" "0")))]
1317  ""
1318  "cmp4.%C4.and.orcm %0, %I0 = %3, %r2"
1319  [(set_attr "itanium_class" "icmp")])
1320
1321(define_insn "*cmpsi_and_1"
1322  [(set (match_operand:BI 0 "register_operand" "=c")
1323	(and:BI (match_operator:BI 3 "signed_inequality_operator"
1324		  [(match_operand:SI 2 "gr_register_operand" "r")
1325		   (const_int 0)])
1326		(match_operand:BI 1 "register_operand" "0")))]
1327  ""
1328  "cmp4.%C3.and.orcm %0, %I0 = r0, %2"
1329  [(set_attr "itanium_class" "icmp")])
1330
1331(define_insn "*cmpsi_andnot_0"
1332  [(set (match_operand:BI 0 "register_operand" "=c")
1333	(and:BI (not:BI (match_operator:BI 4 "predicate_operator"
1334			 [(match_operand:SI 2 "gr_reg_or_0_operand" "rO")
1335			  (match_operand:SI 3 "gr_reg_or_8bit_operand" "rK")]))
1336		(match_operand:BI 1 "register_operand" "0")))]
1337  ""
1338  "cmp4.%C4.or.andcm %I0, %0 = %3, %r2"
1339  [(set_attr "itanium_class" "icmp")])
1340
1341(define_insn "*cmpsi_andnot_1"
1342  [(set (match_operand:BI 0 "register_operand" "=c")
1343	(and:BI (not:BI (match_operator:BI 3 "signed_inequality_operator"
1344			  [(match_operand:SI 2 "gr_register_operand" "r")
1345			   (const_int 0)]))
1346		(match_operand:BI 1 "register_operand" "0")))]
1347  ""
1348  "cmp4.%C3.or.andcm %I0, %0 = r0, %2"
1349  [(set_attr "itanium_class" "icmp")])
1350
1351(define_insn "*cmpdi_and_0"
1352  [(set (match_operand:BI 0 "register_operand" "=c")
1353	(and:BI (match_operator:BI 4 "predicate_operator"
1354		  [(match_operand:DI 2 "gr_register_operand" "r")
1355		   (match_operand:DI 3 "gr_reg_or_8bit_operand" "rK")])
1356		(match_operand:BI 1 "register_operand" "0")))]
1357  ""
1358  "cmp.%C4.and.orcm %0, %I0 = %3, %2"
1359  [(set_attr "itanium_class" "icmp")])
1360
1361(define_insn "*cmpdi_and_1"
1362  [(set (match_operand:BI 0 "register_operand" "=c")
1363	(and:BI (match_operator:BI 3 "signed_inequality_operator"
1364		  [(match_operand:DI 2 "gr_register_operand" "r")
1365		   (const_int 0)])
1366		(match_operand:BI 1 "register_operand" "0")))]
1367  ""
1368  "cmp.%C3.and.orcm %0, %I0 = r0, %2"
1369  [(set_attr "itanium_class" "icmp")])
1370
1371(define_insn "*cmpdi_andnot_0"
1372  [(set (match_operand:BI 0 "register_operand" "=c")
1373	(and:BI (not:BI (match_operator:BI 4 "predicate_operator"
1374			 [(match_operand:DI 2 "gr_register_operand" "r")
1375			  (match_operand:DI 3 "gr_reg_or_8bit_operand" "rK")]))
1376		(match_operand:BI 1 "register_operand" "0")))]
1377  ""
1378  "cmp.%C4.or.andcm %I0, %0 = %3, %2"
1379  [(set_attr "itanium_class" "icmp")])
1380
1381(define_insn "*cmpdi_andnot_1"
1382  [(set (match_operand:BI 0 "register_operand" "=c")
1383	(and:BI (not:BI (match_operator:BI 3 "signed_inequality_operator"
1384			  [(match_operand:DI 2 "gr_register_operand" "r")
1385			   (const_int 0)]))
1386		(match_operand:BI 1 "register_operand" "0")))]
1387  ""
1388  "cmp.%C3.or.andcm %I0, %0 = r0, %2"
1389  [(set_attr "itanium_class" "icmp")])
1390
1391(define_insn "*tbit_and_0"
1392  [(set (match_operand:BI 0 "register_operand" "=c")
1393	(and:BI (ne:BI (and:DI (match_operand:DI 1 "gr_register_operand" "r")
1394			       (const_int 1))
1395		       (const_int 0))
1396		(match_operand:BI 2 "register_operand" "0")))]
1397  ""
1398  "tbit.nz.and.orcm %0, %I0 = %1, 0"
1399  [(set_attr "itanium_class" "tbit")])
1400
1401(define_insn "*tbit_and_1"
1402  [(set (match_operand:BI 0 "register_operand" "=c")
1403	(and:BI (eq:BI (and:DI (match_operand:DI 1 "gr_register_operand" "r")
1404			       (const_int 1))
1405		       (const_int 0))
1406		(match_operand:BI 2 "register_operand" "0")))]
1407  ""
1408  "tbit.z.and.orcm %0, %I0 = %1, 0"
1409  [(set_attr "itanium_class" "tbit")])
1410
1411(define_insn "*tbit_and_2"
1412  [(set (match_operand:BI 0 "register_operand" "=c")
1413	(and:BI (ne:BI (zero_extract:DI
1414			 (match_operand:DI 1 "gr_register_operand" "r")
1415			 (const_int 1)
1416			 (match_operand:DI 2 "const_int_operand" "n"))
1417		       (const_int 0))
1418		(match_operand:BI 3 "register_operand" "0")))]
1419  ""
1420  "tbit.nz.and.orcm %0, %I0 = %1, %2"
1421  [(set_attr "itanium_class" "tbit")])
1422
1423(define_insn "*tbit_and_3"
1424  [(set (match_operand:BI 0 "register_operand" "=c")
1425	(and:BI (eq:BI (zero_extract:DI
1426			 (match_operand:DI 1 "gr_register_operand" "r")
1427			 (const_int 1)
1428			 (match_operand:DI 2 "const_int_operand" "n"))
1429		       (const_int 0))
1430		(match_operand:BI 3 "register_operand" "0")))]
1431  ""
1432  "tbit.z.and.orcm %0, %I0 = %1, %2"
1433  [(set_attr "itanium_class" "tbit")])
1434
1435(define_insn "*cmpsi_or_0"
1436  [(set (match_operand:BI 0 "register_operand" "=c")
1437	(ior:BI (match_operator:BI 4 "predicate_operator"
1438		  [(match_operand:SI 2 "gr_reg_or_0_operand" "rO")
1439		   (match_operand:SI 3 "gr_reg_or_8bit_operand" "rK")])
1440		(match_operand:BI 1 "register_operand" "0")))]
1441  ""
1442  "cmp4.%C4.or.andcm %0, %I0 = %3, %r2"
1443  [(set_attr "itanium_class" "icmp")])
1444
1445(define_insn "*cmpsi_or_1"
1446  [(set (match_operand:BI 0 "register_operand" "=c")
1447	(ior:BI (match_operator:BI 3 "signed_inequality_operator"
1448		  [(match_operand:SI 2 "gr_register_operand" "r")
1449		   (const_int 0)])
1450		(match_operand:BI 1 "register_operand" "0")))]
1451  ""
1452  "cmp4.%C3.or.andcm %0, %I0 = r0, %2"
1453  [(set_attr "itanium_class" "icmp")])
1454
1455(define_insn "*cmpsi_orcm_0"
1456  [(set (match_operand:BI 0 "register_operand" "=c")
1457	(ior:BI (not:BI (match_operator:BI 4 "predicate_operator"
1458			 [(match_operand:SI 2 "gr_reg_or_0_operand" "rO")
1459			  (match_operand:SI 3 "gr_reg_or_8bit_operand" "rK")]))
1460		(match_operand:BI 1 "register_operand" "0")))]
1461  ""
1462  "cmp4.%C4.and.orcm %I0, %0 = %3, %r2"
1463  [(set_attr "itanium_class" "icmp")])
1464
1465(define_insn "*cmpsi_orcm_1"
1466  [(set (match_operand:BI 0 "register_operand" "=c")
1467	(ior:BI (not:BI (match_operator:BI 3 "signed_inequality_operator"
1468			  [(match_operand:SI 2 "gr_register_operand" "r")
1469			   (const_int 0)]))
1470		(match_operand:BI 1 "register_operand" "0")))]
1471  ""
1472  "cmp4.%C3.and.orcm %I0, %0 = r0, %2"
1473  [(set_attr "itanium_class" "icmp")])
1474
1475(define_insn "*cmpdi_or_0"
1476  [(set (match_operand:BI 0 "register_operand" "=c")
1477	(ior:BI (match_operator:BI 4 "predicate_operator"
1478		  [(match_operand:DI 2 "gr_register_operand" "r")
1479		   (match_operand:DI 3 "gr_reg_or_8bit_operand" "rK")])
1480		(match_operand:BI 1 "register_operand" "0")))]
1481  ""
1482  "cmp.%C4.or.andcm %0, %I0 = %3, %2"
1483  [(set_attr "itanium_class" "icmp")])
1484
1485(define_insn "*cmpdi_or_1"
1486  [(set (match_operand:BI 0 "register_operand" "=c")
1487	(ior:BI (match_operator:BI 3 "signed_inequality_operator"
1488		  [(match_operand:DI 2 "gr_register_operand" "r")
1489		   (const_int 0)])
1490		(match_operand:BI 1 "register_operand" "0")))]
1491  ""
1492  "cmp.%C3.or.andcm %0, %I0 = r0, %2"
1493  [(set_attr "itanium_class" "icmp")])
1494
1495(define_insn "*cmpdi_orcm_0"
1496  [(set (match_operand:BI 0 "register_operand" "=c")
1497	(ior:BI (not:BI (match_operator:BI 4 "predicate_operator"
1498			 [(match_operand:DI 2 "gr_register_operand" "r")
1499			  (match_operand:DI 3 "gr_reg_or_8bit_operand" "rK")]))
1500		(match_operand:BI 1 "register_operand" "0")))]
1501  ""
1502  "cmp.%C4.and.orcm %I0, %0 = %3, %2"
1503  [(set_attr "itanium_class" "icmp")])
1504
1505(define_insn "*cmpdi_orcm_1"
1506  [(set (match_operand:BI 0 "register_operand" "=c")
1507	(ior:BI (not:BI (match_operator:BI 3 "signed_inequality_operator"
1508			  [(match_operand:DI 2 "gr_register_operand" "r")
1509			   (const_int 0)]))
1510		(match_operand:BI 1 "register_operand" "0")))]
1511  ""
1512  "cmp.%C3.and.orcm %I0, %0 = r0, %2"
1513  [(set_attr "itanium_class" "icmp")])
1514
1515(define_insn "*tbit_or_0"
1516  [(set (match_operand:BI 0 "register_operand" "=c")
1517	(ior:BI (ne:BI (and:DI (match_operand:DI 1 "gr_register_operand" "r")
1518			       (const_int 1))
1519		       (const_int 0))
1520		(match_operand:BI 2 "register_operand" "0")))]
1521  ""
1522  "tbit.nz.or.andcm %0, %I0 = %1, 0"
1523  [(set_attr "itanium_class" "tbit")])
1524
1525(define_insn "*tbit_or_1"
1526  [(set (match_operand:BI 0 "register_operand" "=c")
1527	(ior:BI (eq:BI (and:DI (match_operand:DI 1 "gr_register_operand" "r")
1528			       (const_int 1))
1529		       (const_int 0))
1530		(match_operand:BI 2 "register_operand" "0")))]
1531  ""
1532  "tbit.z.or.andcm %0, %I0 = %1, 0"
1533  [(set_attr "itanium_class" "tbit")])
1534
1535(define_insn "*tbit_or_2"
1536  [(set (match_operand:BI 0 "register_operand" "=c")
1537	(ior:BI (ne:BI (zero_extract:DI
1538			 (match_operand:DI 1 "gr_register_operand" "r")
1539			 (const_int 1)
1540			 (match_operand:DI 2 "const_int_operand" "n"))
1541		       (const_int 0))
1542		(match_operand:BI 3 "register_operand" "0")))]
1543  ""
1544  "tbit.nz.or.andcm %0, %I0 = %1, %2"
1545  [(set_attr "itanium_class" "tbit")])
1546
1547(define_insn "*tbit_or_3"
1548  [(set (match_operand:BI 0 "register_operand" "=c")
1549	(ior:BI (eq:BI (zero_extract:DI
1550			 (match_operand:DI 1 "gr_register_operand" "r")
1551			 (const_int 1)
1552			 (match_operand:DI 2 "const_int_operand" "n"))
1553		       (const_int 0))
1554		(match_operand:BI 3 "register_operand" "0")))]
1555  ""
1556  "tbit.z.or.andcm %0, %I0 = %1, %2"
1557  [(set_attr "itanium_class" "tbit")])
1558
1559;; Transform test of and/or of setcc into parallel comparisons.
1560
1561(define_split
1562  [(set (match_operand:BI 0 "register_operand" "")
1563	(ne:BI (and:DI (ne:DI (match_operand:BI 2 "register_operand" "")
1564			      (const_int 0))
1565		       (match_operand:DI 3 "register_operand" ""))
1566	       (const_int 0)))]
1567  ""
1568  [(set (match_dup 0)
1569	(and:BI (ne:BI (and:DI (match_dup 3) (const_int 1)) (const_int 0))
1570		(match_dup 2)))]
1571  "")
1572
1573(define_split
1574  [(set (match_operand:BI 0 "register_operand" "")
1575	(eq:BI (and:DI (ne:DI (match_operand:BI 2 "register_operand" "")
1576			      (const_int 0))
1577		       (match_operand:DI 3 "register_operand" ""))
1578	       (const_int 0)))]
1579  ""
1580  [(set (match_dup 0)
1581	(and:BI (ne:BI (and:DI (match_dup 3) (const_int 1)) (const_int 0))
1582		(match_dup 2)))
1583   (parallel [(set (match_dup 0) (not:BI (match_dup 0)))
1584	      (clobber (scratch))])]
1585  "")
1586
1587(define_split
1588  [(set (match_operand:BI 0 "register_operand" "")
1589	(ne:BI (ior:DI (ne:DI (match_operand:BI 2 "register_operand" "")
1590			      (const_int 0))
1591		       (match_operand:DI 3 "register_operand" ""))
1592	       (const_int 0)))]
1593  ""
1594  [(set (match_dup 0) 
1595	(ior:BI (ne:BI (match_dup 3) (const_int 0))
1596		(match_dup 2)))]
1597  "")
1598
1599(define_split
1600  [(set (match_operand:BI 0 "register_operand" "")
1601	(eq:BI (ior:DI (ne:DI (match_operand:BI 2 "register_operand" "")
1602			      (const_int 0))
1603		       (match_operand:DI 3 "register_operand" ""))
1604	       (const_int 0)))]
1605  ""
1606  [(set (match_dup 0) 
1607	(ior:BI (ne:BI (match_dup 3) (const_int 0))
1608		(match_dup 2)))
1609   (parallel [(set (match_dup 0) (not:BI (match_dup 0)))
1610	      (clobber (scratch))])]
1611  "")
1612
1613;; ??? Incredibly hackish.  Either need four proper patterns with all
1614;; the alternatives, or rely on sched1 to split the insn and hope that
1615;; nothing bad happens to the comparisons in the meantime.
1616;;
1617;; Alternately, adjust combine to allow 2->2 and 3->3 splits, assuming
1618;; that we're doing height reduction.
1619;
1620;(define_insn_and_split ""
1621;  [(set (match_operand:BI 0 "register_operand" "=c")
1622;	(and:BI (and:BI (match_operator:BI 1 "comparison_operator"
1623;			  [(match_operand 2 "" "")
1624;			   (match_operand 3 "" "")])
1625;			(match_operator:BI 4 "comparison_operator"
1626;			  [(match_operand 5 "" "")
1627;			   (match_operand 6 "" "")]))
1628;		(match_dup 0)))]
1629;  "flag_schedule_insns"
1630;  "#"
1631;  ""
1632;  [(set (match_dup 0) (and:BI (match_dup 1) (match_dup 0)))
1633;   (set (match_dup 0) (and:BI (match_dup 4) (match_dup 0)))]
1634;  "")
1635;
1636;(define_insn_and_split ""
1637;  [(set (match_operand:BI 0 "register_operand" "=c")
1638;	(ior:BI (ior:BI (match_operator:BI 1 "comparison_operator"
1639;			  [(match_operand 2 "" "")
1640;			   (match_operand 3 "" "")])
1641;			(match_operator:BI 4 "comparison_operator"
1642;			  [(match_operand 5 "" "")
1643;			   (match_operand 6 "" "")]))
1644;		(match_dup 0)))]
1645;  "flag_schedule_insns"
1646;  "#"
1647;  ""
1648;  [(set (match_dup 0) (ior:BI (match_dup 1) (match_dup 0)))
1649;   (set (match_dup 0) (ior:BI (match_dup 4) (match_dup 0)))]
1650;  "")
1651;
1652;(define_split
1653;  [(set (match_operand:BI 0 "register_operand" "")
1654;	(and:BI (and:BI (match_operator:BI 1 "comparison_operator"
1655;			  [(match_operand 2 "" "")
1656;			   (match_operand 3 "" "")])
1657;			(match_operand:BI 7 "register_operand" ""))
1658;		(and:BI (match_operator:BI 4 "comparison_operator"
1659;			  [(match_operand 5 "" "")
1660;			   (match_operand 6 "" "")])
1661;			(match_operand:BI 8 "register_operand" ""))))]
1662;  ""
1663;  [(set (match_dup 0) (and:BI (match_dup 7) (match_dup 8)))
1664;   (set (match_dup 0) (and:BI (and:BI (match_dup 1) (match_dup 4))
1665;			      (match_dup 0)))]
1666;  "")
1667;
1668;(define_split
1669;  [(set (match_operand:BI 0 "register_operand" "")
1670;	(ior:BI (ior:BI (match_operator:BI 1 "comparison_operator"
1671;			  [(match_operand 2 "" "")
1672;			   (match_operand 3 "" "")])
1673;			(match_operand:BI 7 "register_operand" ""))
1674;		(ior:BI (match_operator:BI 4 "comparison_operator"
1675;			  [(match_operand 5 "" "")
1676;			   (match_operand 6 "" "")])
1677;			(match_operand:BI 8 "register_operand" ""))))]
1678;  ""
1679;  [(set (match_dup 0) (ior:BI (match_dup 7) (match_dup 8)))
1680;   (set (match_dup 0) (ior:BI (ior:BI (match_dup 1) (match_dup 4))
1681;			      (match_dup 0)))]
1682;  "")
1683
1684;; Try harder to avoid predicate copies by duplicating compares.
1685;; Note that we'll have already split the predicate copy, which
1686;; is kind of a pain, but oh well.
1687
1688(define_peephole2
1689  [(set (match_operand:BI 0 "register_operand" "")
1690	(match_operand:BI 1 "comparison_operator" ""))
1691   (set (match_operand:CCI 2 "register_operand" "")
1692	(match_operand:CCI 3 "register_operand" ""))
1693   (set (match_operand:CCI 4 "register_operand" "")
1694	(match_operand:CCI 5 "register_operand" ""))
1695   (set (match_operand:BI 6 "register_operand" "")
1696	(unspec:BI [(match_dup 6)] 7))]
1697  "REGNO (operands[3]) == REGNO (operands[0])
1698   && REGNO (operands[4]) == REGNO (operands[0]) + 1
1699   && REGNO (operands[4]) == REGNO (operands[2]) + 1
1700   && REGNO (operands[6]) == REGNO (operands[2])"
1701  [(set (match_dup 0) (match_dup 1))
1702   (set (match_dup 6) (match_dup 7))]
1703  "operands[7] = copy_rtx (operands[1]);")
1704
1705;; ::::::::::::::::::::
1706;; ::
1707;; :: 16 bit Integer arithmetic
1708;; ::
1709;; ::::::::::::::::::::
1710
1711(define_insn "mulhi3"
1712  [(set (match_operand:HI 0 "gr_register_operand" "=r")
1713	(mult:HI (match_operand:HI 1 "gr_register_operand" "r")
1714		 (match_operand:HI 2 "gr_register_operand" "r")))]
1715  ""
1716  "pmpy2.r %0 = %1, %2"
1717  [(set_attr "itanium_class" "mmmul")])
1718
1719
1720;; ::::::::::::::::::::
1721;; ::
1722;; :: 32 bit Integer arithmetic
1723;; ::
1724;; ::::::::::::::::::::
1725
1726(define_insn "addsi3"
1727  [(set (match_operand:SI 0 "gr_register_operand" "=r,r,r")
1728	(plus:SI (match_operand:SI 1 "gr_register_operand" "%r,r,a")
1729		 (match_operand:SI 2 "gr_reg_or_22bit_operand" "r,I,J")))]
1730  ""
1731  "@
1732  add %0 = %1, %2
1733  adds %0 = %2, %1
1734  addl %0 = %2, %1"
1735  [(set_attr "itanium_class" "ialu")])
1736
1737(define_insn "*addsi3_plus1"
1738  [(set (match_operand:SI 0 "gr_register_operand" "=r")
1739	(plus:SI (plus:SI (match_operand:SI 1 "gr_register_operand" "r")
1740			  (match_operand:SI 2 "gr_register_operand" "r"))
1741		 (const_int 1)))]
1742  ""
1743  "add %0 = %1, %2, 1"
1744  [(set_attr "itanium_class" "ialu")])
1745
1746(define_insn "*addsi3_plus1_alt"
1747  [(set (match_operand:SI 0 "gr_register_operand" "=r")
1748	(plus:SI (mult:SI (match_operand:SI 1 "gr_register_operand" "r")
1749			  (const_int 2))
1750		 (const_int 1)))]
1751  ""
1752  "add %0 = %1, %1, 1"
1753  [(set_attr "itanium_class" "ialu")])
1754
1755(define_insn "*addsi3_shladd"
1756  [(set (match_operand:SI 0 "gr_register_operand" "=r")
1757	(plus:SI (mult:SI (match_operand:SI 1 "gr_register_operand" "r")
1758			  (match_operand:SI 2 "shladd_operand" "n"))
1759		 (match_operand:SI 3 "gr_register_operand" "r")))]
1760  ""
1761  "shladd %0 = %1, %S2, %3"
1762  [(set_attr "itanium_class" "ialu")])
1763
1764(define_insn "subsi3"
1765  [(set (match_operand:SI 0 "gr_register_operand" "=r")
1766	(minus:SI (match_operand:SI 1 "gr_reg_or_8bit_operand" "rK")
1767		  (match_operand:SI 2 "gr_register_operand" "r")))]
1768  ""
1769  "sub %0 = %1, %2"
1770  [(set_attr "itanium_class" "ialu")])
1771
1772(define_insn "*subsi3_minus1"
1773  [(set (match_operand:SI 0 "gr_register_operand" "=r")
1774	(plus:SI (not:SI (match_operand:SI 1 "gr_register_operand" "r"))
1775		 (match_operand:SI 2 "gr_register_operand" "r")))]
1776  ""
1777  "sub %0 = %2, %1, 1"
1778  [(set_attr "itanium_class" "ialu")])
1779
1780;; ??? Could add maddsi3 patterns patterned after the madddi3 patterns.
1781
1782(define_insn "mulsi3"
1783  [(set (match_operand:SI 0 "fr_register_operand" "=f")
1784	(mult:SI (match_operand:SI 1 "grfr_register_operand" "f")
1785		 (match_operand:SI 2 "grfr_register_operand" "f")))]
1786  ""
1787  "xmpy.l %0 = %1, %2"
1788  [(set_attr "itanium_class" "xmpy")])
1789
1790(define_insn "maddsi4"
1791  [(set (match_operand:SI 0 "fr_register_operand" "=f")
1792	(plus:SI (mult:SI (match_operand:SI 1 "grfr_register_operand" "f")
1793			  (match_operand:SI 2 "grfr_register_operand" "f"))
1794		 (match_operand:SI 3 "grfr_register_operand" "f")))]
1795  ""
1796  "xma.l %0 = %1, %2, %3"
1797  [(set_attr "itanium_class" "xmpy")])
1798
1799(define_insn "negsi2"
1800  [(set (match_operand:SI 0 "gr_register_operand" "=r")
1801	(neg:SI (match_operand:SI 1 "gr_register_operand" "r")))]
1802  ""
1803  "sub %0 = r0, %1"
1804  [(set_attr "itanium_class" "ialu")])
1805
1806(define_expand "abssi2"
1807  [(set (match_dup 2)
1808	(ge:BI (match_operand:SI 1 "gr_register_operand" "") (const_int 0)))
1809   (set (match_operand:SI 0 "gr_register_operand" "")
1810	(if_then_else:SI (eq (match_dup 2) (const_int 0))
1811			 (neg:SI (match_dup 1))
1812			 (match_dup 1)))]
1813  ""
1814  "
1815{
1816  operands[2] = gen_reg_rtx (BImode);
1817}")
1818
1819(define_expand "sminsi3"
1820  [(set (match_dup 3)
1821	(ge:BI (match_operand:SI 1 "gr_register_operand" "")
1822	       (match_operand:SI 2 "gr_register_operand" "")))
1823   (set (match_operand:SI 0 "gr_register_operand" "")
1824	(if_then_else:SI (ne (match_dup 3) (const_int 0))
1825			 (match_dup 2) (match_dup 1)))]
1826  ""
1827  "
1828{
1829  operands[3] = gen_reg_rtx (BImode);
1830}")
1831
1832(define_expand "smaxsi3"
1833  [(set (match_dup 3)
1834	(ge:BI (match_operand:SI 1 "gr_register_operand" "")
1835	       (match_operand:SI 2 "gr_register_operand" "")))
1836   (set (match_operand:SI 0 "gr_register_operand" "")
1837	(if_then_else:SI (ne (match_dup 3) (const_int 0))
1838			 (match_dup 1) (match_dup 2)))]
1839  ""
1840  "
1841{
1842  operands[3] = gen_reg_rtx (BImode);
1843}")
1844
1845(define_expand "uminsi3"
1846  [(set (match_dup 3)
1847	(geu:BI (match_operand:SI 1 "gr_register_operand" "")
1848		(match_operand:SI 2 "gr_register_operand" "")))
1849   (set (match_operand:SI 0 "gr_register_operand" "")
1850	(if_then_else:SI (ne (match_dup 3) (const_int 0))
1851			 (match_dup 2) (match_dup 1)))]
1852  ""
1853  "
1854{
1855  operands[3] = gen_reg_rtx (BImode);
1856}")
1857
1858(define_expand "umaxsi3"
1859  [(set (match_dup 3)
1860	(geu:BI (match_operand:SI 1 "gr_register_operand" "")
1861		(match_operand:SI 2 "gr_register_operand" "")))
1862   (set (match_operand:SI 0 "gr_register_operand" "")
1863	(if_then_else:SI (ne (match_dup 3) (const_int 0))
1864			 (match_dup 1) (match_dup 2)))]
1865  ""
1866  "
1867{
1868  operands[3] = gen_reg_rtx (BImode);
1869}")
1870
1871(define_expand "divsi3"
1872  [(set (match_operand:SI 0 "register_operand" "")
1873	(div:SI (match_operand:SI 1 "general_operand" "")
1874		(match_operand:SI 2 "general_operand" "")))]
1875  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
1876  "
1877{
1878  rtx op1_tf, op2_tf, op0_tf, op0_di, twon34;
1879
1880  op0_tf = gen_reg_rtx (TFmode);
1881  op0_di = gen_reg_rtx (DImode);
1882
1883  if (CONSTANT_P (operands[1]))
1884    operands[1] = force_reg (SImode, operands[1]);
1885  op1_tf = gen_reg_rtx (TFmode);
1886  expand_float (op1_tf, operands[1], 0);
1887
1888  if (CONSTANT_P (operands[2]))
1889    operands[2] = force_reg (SImode, operands[2]);
1890  op2_tf = gen_reg_rtx (TFmode);
1891  expand_float (op2_tf, operands[2], 0);
1892
1893  /* 2^-34 */
1894#if 0
1895  twon34 = (CONST_DOUBLE_FROM_REAL_VALUE
1896	    (REAL_VALUE_FROM_TARGET_SINGLE (0x2e800000), TFmode));
1897  twon34 = force_reg (TFmode, twon34);
1898#else
1899  twon34 = gen_reg_rtx (TFmode);
1900  convert_move (twon34, force_const_mem (SFmode, CONST_DOUBLE_FROM_REAL_VALUE (REAL_VALUE_FROM_TARGET_SINGLE (0x2e800000), SFmode)), 0);
1901#endif
1902
1903  emit_insn (gen_divsi3_internal (op0_tf, op1_tf, op2_tf, twon34));
1904
1905  emit_insn (gen_fix_trunctfdi2_alts (op0_di, op0_tf, const1_rtx));
1906  emit_move_insn (operands[0], gen_lowpart (SImode, op0_di));
1907  DONE;
1908}")
1909
1910(define_expand "modsi3"
1911  [(set (match_operand:SI 0 "register_operand" "")
1912	(mod:SI (match_operand:SI 1 "general_operand" "")
1913		(match_operand:SI 2 "general_operand" "")))]
1914  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
1915  "
1916{
1917  rtx op2_neg, op1_di, div;
1918
1919  div = gen_reg_rtx (SImode);
1920  emit_insn (gen_divsi3 (div, operands[1], operands[2]));
1921
1922  op2_neg = expand_unop (SImode, neg_optab, operands[2], NULL_RTX, 0);
1923
1924  /* This is a trick to get us to reuse the value that we're sure to
1925     have already copied to the FP regs.  */
1926  op1_di = gen_reg_rtx (DImode);
1927  convert_move (op1_di, operands[1], 0);
1928
1929  emit_insn (gen_maddsi4 (operands[0], div, op2_neg,
1930			  gen_lowpart (SImode, op1_di)));
1931  DONE;
1932}")
1933
1934(define_expand "udivsi3"
1935  [(set (match_operand:SI 0 "register_operand" "")
1936	(udiv:SI (match_operand:SI 1 "general_operand" "")
1937		 (match_operand:SI 2 "general_operand" "")))]
1938  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
1939  "
1940{
1941  rtx op1_tf, op2_tf, op0_tf, op0_di, twon34;
1942
1943  op0_tf = gen_reg_rtx (TFmode);
1944  op0_di = gen_reg_rtx (DImode);
1945
1946  if (CONSTANT_P (operands[1]))
1947    operands[1] = force_reg (SImode, operands[1]);
1948  op1_tf = gen_reg_rtx (TFmode);
1949  expand_float (op1_tf, operands[1], 1);
1950
1951  if (CONSTANT_P (operands[2]))
1952    operands[2] = force_reg (SImode, operands[2]);
1953  op2_tf = gen_reg_rtx (TFmode);
1954  expand_float (op2_tf, operands[2], 1);
1955
1956  /* 2^-34 */
1957#if 0
1958  twon34 = (CONST_DOUBLE_FROM_REAL_VALUE
1959	    (REAL_VALUE_FROM_TARGET_SINGLE (0x2e800000), TFmode));
1960  twon34 = force_reg (TFmode, twon34);
1961#else
1962  twon34 = gen_reg_rtx (TFmode);
1963  convert_move (twon34, force_const_mem (SFmode, CONST_DOUBLE_FROM_REAL_VALUE (REAL_VALUE_FROM_TARGET_SINGLE (0x2e800000), SFmode)), 0);
1964#endif
1965
1966  emit_insn (gen_divsi3_internal (op0_tf, op1_tf, op2_tf, twon34));
1967
1968  emit_insn (gen_fixuns_trunctfdi2_alts (op0_di, op0_tf, const1_rtx));
1969  emit_move_insn (operands[0], gen_lowpart (SImode, op0_di));
1970  DONE;
1971}")
1972
1973(define_expand "umodsi3"
1974  [(set (match_operand:SI 0 "register_operand" "")
1975	(umod:SI (match_operand:SI 1 "general_operand" "")
1976		 (match_operand:SI 2 "general_operand" "")))]
1977  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
1978  "
1979{
1980  rtx op2_neg, op1_di, div;
1981
1982  div = gen_reg_rtx (SImode);
1983  emit_insn (gen_udivsi3 (div, operands[1], operands[2]));
1984
1985  op2_neg = expand_unop (SImode, neg_optab, operands[2], NULL_RTX, 0);
1986
1987  /* This is a trick to get us to reuse the value that we're sure to
1988     have already copied to the FP regs.  */
1989  op1_di = gen_reg_rtx (DImode);
1990  convert_move (op1_di, operands[1], 1);
1991
1992  emit_insn (gen_maddsi4 (operands[0], div, op2_neg,
1993			  gen_lowpart (SImode, op1_di)));
1994  DONE;
1995}")
1996
1997(define_insn_and_split "divsi3_internal"
1998  [(set (match_operand:TF 0 "fr_register_operand" "=&f")
1999	(float:TF (div:SI (match_operand:TF 1 "fr_register_operand" "f")
2000			  (match_operand:TF 2 "fr_register_operand" "f"))))
2001   (clobber (match_scratch:TF 4 "=&f"))
2002   (clobber (match_scratch:TF 5 "=&f"))
2003   (clobber (match_scratch:BI 6 "=c"))
2004   (use (match_operand:TF 3 "fr_register_operand" "f"))]
2005  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
2006  "#"
2007  "&& reload_completed"
2008  [(parallel [(set (match_dup 0) (div:TF (const_int 1) (match_dup 2)))
2009	      (set (match_dup 6) (unspec:BI [(match_dup 1) (match_dup 2)] 5))
2010	      (use (const_int 1))])
2011   (cond_exec (ne (match_dup 6) (const_int 0))
2012     (parallel [(set (match_dup 4) (mult:TF (match_dup 1) (match_dup 0)))
2013		(use (const_int 1))]))
2014   (cond_exec (ne (match_dup 6) (const_int 0))
2015     (parallel [(set (match_dup 5)
2016		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 0)))
2017			      (match_dup 7)))
2018		(use (const_int 1))]))
2019   (cond_exec (ne (match_dup 6) (const_int 0))
2020     (parallel [(set (match_dup 4)
2021		     (plus:TF (mult:TF (match_dup 5) (match_dup 4))
2022			      (match_dup 4)))
2023		(use (const_int 1))]))
2024   (cond_exec (ne (match_dup 6) (const_int 0))
2025     (parallel [(set (match_dup 5)
2026		     (plus:TF (mult:TF (match_dup 5) (match_dup 5))
2027			      (match_dup 3)))
2028		(use (const_int 1))]))
2029   (cond_exec (ne (match_dup 6) (const_int 0))
2030     (parallel [(set (match_dup 0)
2031		     (plus:TF (mult:TF (match_dup 5) (match_dup 4))
2032			      (match_dup 4)))
2033		(use (const_int 1))]))
2034  ] 
2035  "operands[7] = CONST1_RTX (TFmode);"
2036  [(set_attr "predicable" "no")])
2037
2038;; ::::::::::::::::::::
2039;; ::
2040;; :: 64 bit Integer arithmetic
2041;; ::
2042;; ::::::::::::::::::::
2043
2044(define_insn "adddi3"
2045  [(set (match_operand:DI 0 "gr_register_operand" "=r,r,r")
2046	(plus:DI (match_operand:DI 1 "gr_register_operand" "%r,r,a")
2047		 (match_operand:DI 2 "gr_reg_or_22bit_operand" "r,I,J")))]
2048  ""
2049  "@
2050  add %0 = %1, %2
2051  adds %0 = %2, %1
2052  addl %0 = %2, %1"
2053  [(set_attr "itanium_class" "ialu")])
2054
2055(define_insn "*adddi3_plus1"
2056  [(set (match_operand:DI 0 "gr_register_operand" "=r")
2057	(plus:DI (plus:DI (match_operand:DI 1 "gr_register_operand" "r")
2058			  (match_operand:DI 2 "gr_register_operand" "r"))
2059		 (const_int 1)))]
2060  ""
2061  "add %0 = %1, %2, 1"
2062  [(set_attr "itanium_class" "ialu")])
2063
2064;; This has some of the same problems as shladd.  We let the shladd
2065;; eliminator hack handle it, which results in the 1 being forced into
2066;; a register, but not more ugliness here.
2067(define_insn "*adddi3_plus1_alt"
2068  [(set (match_operand:DI 0 "gr_register_operand" "=r")
2069	(plus:DI (mult:DI (match_operand:DI 1 "gr_register_operand" "r")
2070			  (const_int 2))
2071		 (const_int 1)))]
2072  ""
2073  "add %0 = %1, %1, 1"
2074  [(set_attr "itanium_class" "ialu")])
2075
2076(define_insn "subdi3"
2077  [(set (match_operand:DI 0 "gr_register_operand" "=r")
2078	(minus:DI (match_operand:DI 1 "gr_reg_or_8bit_operand" "rK")
2079		  (match_operand:DI 2 "gr_register_operand" "r")))]
2080  ""
2081  "sub %0 = %1, %2"
2082  [(set_attr "itanium_class" "ialu")])
2083
2084(define_insn "*subdi3_minus1"
2085  [(set (match_operand:DI 0 "gr_register_operand" "=r")
2086	(plus:DI (not:DI (match_operand:DI 1 "gr_register_operand" "r"))
2087		 (match_operand:DI 2 "gr_register_operand" "r")))]
2088  ""
2089  "sub %0 = %2, %1, 1"
2090  [(set_attr "itanium_class" "ialu")])
2091
2092;; ??? Use grfr instead of fr because of virtual register elimination
2093;; and silly test cases multiplying by the frame pointer.
2094(define_insn "muldi3"
2095  [(set (match_operand:DI 0 "fr_register_operand" "=f")
2096	(mult:DI (match_operand:DI 1 "grfr_register_operand" "f")
2097		 (match_operand:DI 2 "grfr_register_operand" "f")))]
2098  ""
2099  "xmpy.l %0 = %1, %2"
2100  [(set_attr "itanium_class" "xmpy")])
2101
2102;; ??? If operand 3 is an eliminable reg, then register elimination causes the
2103;; same problem that we have with shladd below.  Unfortunately, this case is
2104;; much harder to fix because the multiply puts the result in an FP register,
2105;; but the add needs inputs from a general register.  We add a spurious clobber
2106;; here so that it will be present just in case register elimination gives us
2107;; the funny result.
2108
2109;; ??? Maybe validate_changes should try adding match_scratch clobbers?
2110
2111;; ??? Maybe we should change how adds are canonicalized.
2112
2113(define_insn "madddi4"
2114  [(set (match_operand:DI 0 "fr_register_operand" "=f")
2115	(plus:DI (mult:DI (match_operand:DI 1 "grfr_register_operand" "f")
2116			  (match_operand:DI 2 "grfr_register_operand" "f"))
2117		 (match_operand:DI 3 "grfr_register_operand" "f")))
2118   (clobber (match_scratch:DI 4 "=X"))]
2119  ""
2120  "xma.l %0 = %1, %2, %3"
2121  [(set_attr "itanium_class" "xmpy")])
2122
2123;; This can be created by register elimination if operand3 of shladd is an
2124;; eliminable register or has reg_equiv_constant set.
2125
2126;; We have to use nonmemory_operand for operand 4, to ensure that the
2127;; validate_changes call inside eliminate_regs will always succeed.  If it
2128;; doesn't succeed, then this remain a madddi4 pattern, and will be reloaded
2129;; incorrectly.
2130
2131(define_insn "*madddi4_elim"
2132  [(set (match_operand:DI 0 "register_operand" "=&r")
2133	(plus:DI (plus:DI (mult:DI (match_operand:DI 1 "register_operand" "f")
2134				   (match_operand:DI 2 "register_operand" "f"))
2135			  (match_operand:DI 3 "register_operand" "f"))
2136		 (match_operand:DI 4 "nonmemory_operand" "rI")))
2137   (clobber (match_scratch:DI 5 "=f"))]
2138  "reload_in_progress"
2139  "#"
2140  [(set_attr "itanium_class" "unknown")])
2141
2142(define_split
2143  [(set (match_operand:DI 0 "register_operand" "")
2144	(plus:DI (plus:DI (mult:DI (match_operand:DI 1 "register_operand" "")
2145				   (match_operand:DI 2 "register_operand" ""))
2146			  (match_operand:DI 3 "register_operand" ""))
2147		 (match_operand:DI 4 "gr_reg_or_14bit_operand" "")))
2148   (clobber (match_scratch:DI 5 ""))]
2149  "reload_completed"
2150  [(parallel [(set (match_dup 5) (plus:DI (mult:DI (match_dup 1) (match_dup 2))
2151					  (match_dup 3)))
2152	      (clobber (match_dup 0))])
2153   (set (match_dup 0) (match_dup 5))
2154   (set (match_dup 0) (plus:DI (match_dup 0) (match_dup 4)))]
2155  "")
2156
2157;; ??? There are highpart multiply and add instructions, but we have no way
2158;; to generate them.
2159
2160(define_insn "smuldi3_highpart"
2161  [(set (match_operand:DI 0 "fr_register_operand" "=f")
2162	(truncate:DI
2163	 (lshiftrt:TI
2164	  (mult:TI (sign_extend:TI
2165		     (match_operand:DI 1 "fr_register_operand" "f"))
2166		   (sign_extend:TI
2167		     (match_operand:DI 2 "fr_register_operand" "f")))
2168	  (const_int 64))))]
2169  ""
2170  "xmpy.h %0 = %1, %2"
2171  [(set_attr "itanium_class" "xmpy")])
2172
2173(define_insn "umuldi3_highpart"
2174  [(set (match_operand:DI 0 "fr_register_operand" "=f")
2175	(truncate:DI
2176	 (lshiftrt:TI
2177	  (mult:TI (zero_extend:TI
2178		     (match_operand:DI 1 "fr_register_operand" "f"))
2179		   (zero_extend:TI
2180		     (match_operand:DI 2 "fr_register_operand" "f")))
2181	  (const_int 64))))]
2182  ""
2183  "xmpy.hu %0 = %1, %2"
2184  [(set_attr "itanium_class" "xmpy")])
2185
2186(define_insn "negdi2"
2187  [(set (match_operand:DI 0 "gr_register_operand" "=r")
2188	(neg:DI (match_operand:DI 1 "gr_register_operand" "r")))]
2189  ""
2190  "sub %0 = r0, %1"
2191  [(set_attr "itanium_class" "ialu")])
2192
2193(define_expand "absdi2"
2194  [(set (match_dup 2)
2195	(ge:BI (match_operand:DI 1 "gr_register_operand" "") (const_int 0)))
2196   (set (match_operand:DI 0 "gr_register_operand" "")
2197	(if_then_else:DI (eq (match_dup 2) (const_int 0))
2198			 (neg:DI (match_dup 1))
2199			 (match_dup 1)))]
2200  ""
2201  "
2202{
2203  operands[2] = gen_reg_rtx (BImode);
2204}")
2205
2206(define_expand "smindi3"
2207  [(set (match_dup 3)
2208	(ge:BI (match_operand:DI 1 "gr_register_operand" "")
2209	       (match_operand:DI 2 "gr_register_operand" "")))
2210   (set (match_operand:DI 0 "gr_register_operand" "")
2211	(if_then_else:DI (ne (match_dup 3) (const_int 0))
2212			 (match_dup 2) (match_dup 1)))]
2213  ""
2214  "
2215{
2216  operands[3] = gen_reg_rtx (BImode);
2217}")
2218
2219(define_expand "smaxdi3"
2220  [(set (match_dup 3)
2221	(ge:BI (match_operand:DI 1 "gr_register_operand" "")
2222	       (match_operand:DI 2 "gr_register_operand" "")))
2223   (set (match_operand:DI 0 "gr_register_operand" "")
2224	(if_then_else:DI (ne (match_dup 3) (const_int 0))
2225			 (match_dup 1) (match_dup 2)))]
2226  ""
2227  "
2228{
2229  operands[3] = gen_reg_rtx (BImode);
2230}")
2231
2232(define_expand "umindi3"
2233  [(set (match_dup 3)
2234	(geu:BI (match_operand:DI 1 "gr_register_operand" "")
2235		(match_operand:DI 2 "gr_register_operand" "")))
2236   (set (match_operand:DI 0 "gr_register_operand" "")
2237	(if_then_else:DI (ne (match_dup 3) (const_int 0))
2238			 (match_dup 2) (match_dup 1)))]
2239  ""
2240  "
2241{
2242  operands[3] = gen_reg_rtx (BImode);
2243}")
2244
2245(define_expand "umaxdi3"
2246  [(set (match_dup 3)
2247	(geu:BI (match_operand:DI 1 "gr_register_operand" "")
2248		(match_operand:DI 2 "gr_register_operand" "")))
2249   (set (match_operand:DI 0 "gr_register_operand" "")
2250	(if_then_else:DI (ne (match_dup 3) (const_int 0))
2251			 (match_dup 1) (match_dup 2)))]
2252  ""
2253  "
2254{
2255  operands[3] = gen_reg_rtx (BImode);
2256}")
2257
2258(define_expand "ffsdi2"
2259  [(set (match_dup 6)
2260	(eq:BI (match_operand:DI 1 "gr_register_operand" "") (const_int 0)))
2261   (set (match_dup 2) (plus:DI (match_dup 1) (const_int -1)))
2262   (set (match_dup 5) (const_int 0))
2263   (set (match_dup 3) (xor:DI (match_dup 1) (match_dup 2)))
2264   (set (match_dup 4) (unspec:DI [(match_dup 3)] 8))
2265   (set (match_operand:DI 0 "gr_register_operand" "")
2266	(if_then_else:DI (ne (match_dup 6) (const_int 0))
2267			 (match_dup 5) (match_dup 4)))]
2268  ""
2269  "
2270{
2271  operands[2] = gen_reg_rtx (DImode);
2272  operands[3] = gen_reg_rtx (DImode);
2273  operands[4] = gen_reg_rtx (DImode);
2274  operands[5] = gen_reg_rtx (DImode);
2275  operands[6] = gen_reg_rtx (BImode);
2276}")
2277
2278(define_insn "*popcnt"
2279  [(set (match_operand:DI 0 "gr_register_operand" "=r")
2280	(unspec:DI [(match_operand:DI 1 "gr_register_operand" "r")] 8))]
2281  ""
2282  "popcnt %0 = %1"
2283  [(set_attr "itanium_class" "mmmul")])
2284
2285(define_expand "divdi3"
2286  [(set (match_operand:DI 0 "register_operand" "")
2287	(div:DI (match_operand:DI 1 "general_operand" "")
2288		(match_operand:DI 2 "general_operand" "")))]
2289  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
2290  "
2291{
2292  rtx op1_tf, op2_tf, op0_tf;
2293
2294  op0_tf = gen_reg_rtx (TFmode);
2295
2296  if (CONSTANT_P (operands[1]))
2297    operands[1] = force_reg (DImode, operands[1]);
2298  op1_tf = gen_reg_rtx (TFmode);
2299  expand_float (op1_tf, operands[1], 0);
2300
2301  if (CONSTANT_P (operands[2]))
2302    operands[2] = force_reg (DImode, operands[2]);
2303  op2_tf = gen_reg_rtx (TFmode);
2304  expand_float (op2_tf, operands[2], 0);
2305
2306  if (TARGET_INLINE_DIV_LAT)
2307    emit_insn (gen_divdi3_internal_lat (op0_tf, op1_tf, op2_tf));
2308  else
2309    emit_insn (gen_divdi3_internal_thr (op0_tf, op1_tf, op2_tf));
2310
2311  emit_insn (gen_fix_trunctfdi2_alts (operands[0], op0_tf, const1_rtx));
2312  DONE;
2313}")
2314
2315(define_expand "moddi3"
2316  [(set (match_operand:DI 0 "register_operand" "")
2317	(mod:SI (match_operand:DI 1 "general_operand" "")
2318		(match_operand:DI 2 "general_operand" "")))]
2319  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
2320  "
2321{
2322  rtx op2_neg, div;
2323
2324  div = gen_reg_rtx (DImode);
2325  emit_insn (gen_divdi3 (div, operands[1], operands[2]));
2326
2327  op2_neg = expand_unop (DImode, neg_optab, operands[2], NULL_RTX, 0);
2328
2329  emit_insn (gen_madddi4 (operands[0], div, op2_neg, operands[1]));
2330  DONE;
2331}")
2332
2333(define_expand "udivdi3"
2334  [(set (match_operand:DI 0 "register_operand" "")
2335	(udiv:DI (match_operand:DI 1 "general_operand" "")
2336		 (match_operand:DI 2 "general_operand" "")))]
2337  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
2338  "
2339{
2340  rtx op1_tf, op2_tf, op0_tf;
2341
2342  op0_tf = gen_reg_rtx (TFmode);
2343
2344  if (CONSTANT_P (operands[1]))
2345    operands[1] = force_reg (DImode, operands[1]);
2346  op1_tf = gen_reg_rtx (TFmode);
2347  expand_float (op1_tf, operands[1], 1);
2348
2349  if (CONSTANT_P (operands[2]))
2350    operands[2] = force_reg (DImode, operands[2]);
2351  op2_tf = gen_reg_rtx (TFmode);
2352  expand_float (op2_tf, operands[2], 1);
2353
2354  if (TARGET_INLINE_DIV_LAT)
2355    emit_insn (gen_divdi3_internal_lat (op0_tf, op1_tf, op2_tf));
2356  else
2357    emit_insn (gen_divdi3_internal_thr (op0_tf, op1_tf, op2_tf));
2358
2359  emit_insn (gen_fixuns_trunctfdi2_alts (operands[0], op0_tf, const1_rtx));
2360  DONE;
2361}")
2362
2363(define_expand "umoddi3"
2364  [(set (match_operand:DI 0 "register_operand" "")
2365	(umod:DI (match_operand:DI 1 "general_operand" "")
2366		 (match_operand:DI 2 "general_operand" "")))]
2367  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
2368  "
2369{
2370  rtx op2_neg, div;
2371
2372  div = gen_reg_rtx (DImode);
2373  emit_insn (gen_udivdi3 (div, operands[1], operands[2]));
2374
2375  op2_neg = expand_unop (DImode, neg_optab, operands[2], NULL_RTX, 0);
2376
2377  emit_insn (gen_madddi4 (operands[0], div, op2_neg, operands[1]));
2378  DONE;
2379}")
2380
2381(define_insn_and_split "divdi3_internal_lat"
2382  [(set (match_operand:TF 0 "fr_register_operand" "=&f")
2383	(float:TF (div:SI (match_operand:TF 1 "fr_register_operand" "f")
2384			  (match_operand:TF 2 "fr_register_operand" "f"))))
2385   (clobber (match_scratch:TF 3 "=&f"))
2386   (clobber (match_scratch:TF 4 "=&f"))
2387   (clobber (match_scratch:TF 5 "=&f"))
2388   (clobber (match_scratch:BI 6 "=c"))]
2389  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_LAT"
2390  "#"
2391  "&& reload_completed"
2392  [(parallel [(set (match_dup 0) (div:TF (const_int 1) (match_dup 2)))
2393	      (set (match_dup 6) (unspec:BI [(match_dup 1) (match_dup 2)] 5))
2394	      (use (const_int 1))])
2395   (cond_exec (ne (match_dup 6) (const_int 0))
2396     (parallel [(set (match_dup 3)
2397		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 0)))
2398			      (match_dup 7)))
2399		(use (const_int 1))]))
2400   (cond_exec (ne (match_dup 6) (const_int 0))
2401     (parallel [(set (match_dup 4) (mult:TF (match_dup 1) (match_dup 0)))
2402		(use (const_int 1))]))
2403   (cond_exec (ne (match_dup 6) (const_int 0))
2404     (parallel [(set (match_dup 5) (mult:TF (match_dup 3) (match_dup 3)))
2405		(use (const_int 1))]))
2406   (cond_exec (ne (match_dup 6) (const_int 0))
2407     (parallel [(set (match_dup 4)
2408		     (plus:TF (mult:TF (match_dup 3) (match_dup 4))
2409			      (match_dup 4)))
2410		(use (const_int 1))]))
2411   (cond_exec (ne (match_dup 6) (const_int 0))
2412     (parallel [(set (match_dup 0)
2413		     (plus:TF (mult:TF (match_dup 3) (match_dup 0))
2414			      (match_dup 0)))
2415		(use (const_int 1))]))
2416   (cond_exec (ne (match_dup 6) (const_int 0))
2417     (parallel [(set (match_dup 3)
2418		     (plus:TF (mult:TF (match_dup 5) (match_dup 4))
2419			      (match_dup 4)))
2420		(use (const_int 1))]))
2421   (cond_exec (ne (match_dup 6) (const_int 0))
2422     (parallel [(set (match_dup 0)
2423		     (plus:TF (mult:TF (match_dup 5) (match_dup 0))
2424			      (match_dup 0)))
2425		(use (const_int 1))]))
2426   (cond_exec (ne (match_dup 6) (const_int 0))
2427     (parallel [(set (match_dup 4)
2428		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 3)))
2429			      (match_dup 1)))
2430		(use (const_int 1))]))
2431   (cond_exec (ne (match_dup 6) (const_int 0))
2432     (parallel [(set (match_dup 0)
2433		     (plus:TF (mult:TF (match_dup 4) (match_dup 0))
2434			      (match_dup 3)))
2435		(use (const_int 1))]))
2436  ] 
2437  "operands[7] = CONST1_RTX (TFmode);"
2438  [(set_attr "predicable" "no")])
2439
2440(define_insn_and_split "divdi3_internal_thr"
2441  [(set (match_operand:TF 0 "fr_register_operand" "=&f")
2442	(float:TF (div:SI (match_operand:TF 1 "fr_register_operand" "f")
2443			  (match_operand:TF 2 "fr_register_operand" "f"))))
2444   (clobber (match_scratch:TF 3 "=&f"))
2445   (clobber (match_scratch:TF 4 "=f"))
2446   (clobber (match_scratch:BI 5 "=c"))]
2447  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_THR"
2448  "#"
2449  "&& reload_completed"
2450  [(parallel [(set (match_dup 0) (div:TF (const_int 1) (match_dup 2)))
2451	      (set (match_dup 5) (unspec:BI [(match_dup 1) (match_dup 2)] 5))
2452	      (use (const_int 1))])
2453   (cond_exec (ne (match_dup 5) (const_int 0))
2454     (parallel [(set (match_dup 3)
2455		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 0)))
2456			      (match_dup 6)))
2457		(use (const_int 1))]))
2458   (cond_exec (ne (match_dup 5) (const_int 0))
2459     (parallel [(set (match_dup 0)
2460		     (plus:TF (mult:TF (match_dup 3) (match_dup 0))
2461			      (match_dup 0)))
2462		(use (const_int 1))]))
2463   (cond_exec (ne (match_dup 5) (const_int 0))
2464     (parallel [(set (match_dup 3) (mult:TF (match_dup 3) (match_dup 3)))
2465		(use (const_int 1))]))
2466   (cond_exec (ne (match_dup 5) (const_int 0))
2467     (parallel [(set (match_dup 0)
2468		     (plus:TF (mult:TF (match_dup 3) (match_dup 0))
2469			      (match_dup 0)))
2470		(use (const_int 1))]))
2471   (cond_exec (ne (match_dup 5) (const_int 0))
2472     (parallel [(set (match_dup 3) (mult:TF (match_dup 0) (match_dup 1)))
2473		(use (const_int 1))]))
2474   (cond_exec (ne (match_dup 5) (const_int 0))
2475     (parallel [(set (match_dup 4)
2476		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 3)))
2477			      (match_dup 1)))
2478		(use (const_int 1))]))
2479   (cond_exec (ne (match_dup 5) (const_int 0))
2480     (parallel [(set (match_dup 0)
2481		     (plus:TF (mult:TF (match_dup 4) (match_dup 0))
2482			      (match_dup 3)))
2483		(use (const_int 1))]))
2484  ] 
2485  "operands[6] = CONST1_RTX (TFmode);"
2486  [(set_attr "predicable" "no")])
2487
2488;; ::::::::::::::::::::
2489;; ::
2490;; :: 32 bit floating point arithmetic
2491;; ::
2492;; ::::::::::::::::::::
2493
2494(define_insn "addsf3"
2495  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2496	(plus:SF (match_operand:SF 1 "fr_register_operand" "%f")
2497		 (match_operand:SF 2 "fr_reg_or_fp01_operand" "fG")))]
2498  ""
2499  "fadd.s %0 = %1, %F2"
2500  [(set_attr "itanium_class" "fmac")])
2501
2502(define_insn "subsf3"
2503  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2504	(minus:SF (match_operand:SF 1 "fr_reg_or_fp01_operand" "fG")
2505		  (match_operand:SF 2 "fr_reg_or_fp01_operand" "fG")))]
2506  ""
2507  "fsub.s %0 = %F1, %F2"
2508  [(set_attr "itanium_class" "fmac")])
2509
2510(define_insn "mulsf3"
2511  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2512	(mult:SF (match_operand:SF 1 "fr_register_operand" "%f")
2513		 (match_operand:SF 2 "fr_register_operand" "f")))]
2514  ""
2515  "fmpy.s %0 = %1, %2"
2516  [(set_attr "itanium_class" "fmac")])
2517
2518(define_insn "abssf2"
2519  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2520	(abs:SF (match_operand:SF 1 "fr_register_operand" "f")))]
2521  ""
2522  "fabs %0 = %1"
2523  [(set_attr "itanium_class" "fmisc")])
2524
2525(define_insn "negsf2"
2526  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2527	(neg:SF (match_operand:SF 1 "fr_register_operand" "f")))]
2528  ""
2529  "fneg %0 = %1"
2530  [(set_attr "itanium_class" "fmisc")])
2531
2532(define_insn "*nabssf2"
2533  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2534	(neg:SF (abs:SF (match_operand:SF 1 "fr_register_operand" "f"))))]
2535  ""
2536  "fnegabs %0 = %1"
2537  [(set_attr "itanium_class" "fmisc")])
2538
2539(define_insn "minsf3"
2540  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2541	(smin:SF (match_operand:SF 1 "fr_register_operand" "f")
2542		 (match_operand:SF 2 "fr_reg_or_fp01_operand" "fG")))]
2543  ""
2544  "fmin %0 = %1, %F2"
2545  [(set_attr "itanium_class" "fmisc")])
2546
2547(define_insn "maxsf3"
2548  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2549	(smax:SF (match_operand:SF 1 "fr_register_operand" "f")
2550		 (match_operand:SF 2 "fr_reg_or_fp01_operand" "fG")))]
2551  ""
2552  "fmax %0 = %1, %F2"
2553  [(set_attr "itanium_class" "fmisc")])
2554
2555(define_insn "*maddsf4"
2556  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2557	(plus:SF (mult:SF (match_operand:SF 1 "fr_register_operand" "f")
2558			  (match_operand:SF 2 "fr_register_operand" "f"))
2559		 (match_operand:SF 3 "fr_reg_or_fp01_operand" "fG")))]
2560  ""
2561  "fma.s %0 = %1, %2, %F3"
2562  [(set_attr "itanium_class" "fmac")])
2563
2564(define_insn "*msubsf4"
2565  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2566	(minus:SF (mult:SF (match_operand:SF 1 "fr_register_operand" "f")
2567			   (match_operand:SF 2 "fr_register_operand" "f"))
2568		  (match_operand:SF 3 "fr_reg_or_fp01_operand" "fG")))]
2569  ""
2570  "fms.s %0 = %1, %2, %F3"
2571  [(set_attr "itanium_class" "fmac")])
2572
2573(define_insn "*nmulsf3"
2574  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2575	(neg:SF (mult:SF (match_operand:SF 1 "fr_register_operand" "f")
2576			 (match_operand:SF 2 "fr_register_operand" "f"))))]
2577  ""
2578  "fnmpy.s %0 = %1, %2"
2579  [(set_attr "itanium_class" "fmac")])
2580
2581;; ??? Is it possible to canonicalize this as (minus (reg) (mult))?
2582
2583(define_insn "*nmaddsf4"
2584  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2585	(plus:SF (neg:SF (mult:SF
2586			   (match_operand:SF 1 "fr_register_operand" "f")
2587			   (match_operand:SF 2 "fr_register_operand" "f")))
2588		 (match_operand:SF 3 "fr_reg_or_fp01_operand" "fG")))]
2589  ""
2590  "fnma.s %0 = %1, %2, %F3"
2591  [(set_attr "itanium_class" "fmac")])
2592
2593(define_expand "divsf3"
2594  [(set (match_operand:SF 0 "fr_register_operand" "")
2595	(div:SF (match_operand:SF 1 "fr_register_operand" "")
2596		(match_operand:SF 2 "fr_register_operand" "")))]
2597  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
2598  "
2599{
2600  rtx insn;
2601  if (TARGET_INLINE_DIV_LAT)
2602    insn = gen_divsf3_internal_lat (operands[0], operands[1], operands[2]);
2603  else
2604    insn = gen_divsf3_internal_thr (operands[0], operands[1], operands[2]);
2605  emit_insn (insn);
2606  DONE;
2607}")
2608
2609(define_insn_and_split "divsf3_internal_lat"
2610  [(set (match_operand:SF 0 "fr_register_operand" "=&f")
2611	(div:SF (match_operand:SF 1 "fr_register_operand" "f")
2612		(match_operand:SF 2 "fr_register_operand" "f")))
2613   (clobber (match_scratch:TF 3 "=&f"))
2614   (clobber (match_scratch:TF 4 "=f"))
2615   (clobber (match_scratch:BI 5 "=c"))]
2616  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_LAT"
2617  "#"
2618  "&& reload_completed"
2619  [(parallel [(set (match_dup 6) (div:TF (const_int 1) (match_dup 8)))
2620	      (set (match_dup 5) (unspec:BI [(match_dup 7) (match_dup 8)] 5))
2621	      (use (const_int 1))])
2622   (cond_exec (ne (match_dup 5) (const_int 0))
2623     (parallel [(set (match_dup 3) (mult:TF (match_dup 7) (match_dup 6)))
2624		(use (const_int 1))]))
2625   (cond_exec (ne (match_dup 5) (const_int 0))
2626     (parallel [(set (match_dup 4)
2627		     (plus:TF (neg:TF (mult:TF (match_dup 8) (match_dup 6)))
2628			      (match_dup 10)))
2629		(use (const_int 1))]))
2630   (cond_exec (ne (match_dup 5) (const_int 0))
2631     (parallel [(set (match_dup 3)
2632		     (plus:TF (mult:TF (match_dup 4) (match_dup 3))
2633			      (match_dup 3)))
2634		(use (const_int 1))]))
2635   (cond_exec (ne (match_dup 5) (const_int 0))
2636     (parallel [(set (match_dup 4) (mult:TF (match_dup 4) (match_dup 4)))
2637		(use (const_int 1))]))
2638   (cond_exec (ne (match_dup 5) (const_int 0))
2639     (parallel [(set (match_dup 3)
2640		     (plus:TF (mult:TF (match_dup 4) (match_dup 3))
2641			      (match_dup 3)))
2642		(use (const_int 1))]))
2643   (cond_exec (ne (match_dup 5) (const_int 0))
2644     (parallel [(set (match_dup 4) (mult:TF (match_dup 4) (match_dup 4)))
2645		(use (const_int 1))]))
2646   (cond_exec (ne (match_dup 5) (const_int 0))
2647     (parallel [(set (match_dup 9)
2648		     (float_truncate:DF
2649		       (plus:TF (mult:TF (match_dup 4) (match_dup 3))
2650			      (match_dup 3))))
2651		(use (const_int 1))]))
2652   (cond_exec (ne (match_dup 5) (const_int 0))
2653     (set (match_dup 0)
2654	  (float_truncate:SF (match_dup 6))))
2655  ] 
2656  "operands[6] = gen_rtx_REG (TFmode, REGNO (operands[0]));
2657   operands[7] = gen_rtx_REG (TFmode, REGNO (operands[1]));
2658   operands[8] = gen_rtx_REG (TFmode, REGNO (operands[2]));
2659   operands[9] = gen_rtx_REG (DFmode, REGNO (operands[0]));
2660   operands[10] = CONST1_RTX (TFmode);"
2661  [(set_attr "predicable" "no")])
2662
2663(define_insn_and_split "divsf3_internal_thr"
2664  [(set (match_operand:SF 0 "fr_register_operand" "=&f")
2665	(div:SF (match_operand:SF 1 "fr_register_operand" "f")
2666		(match_operand:SF 2 "fr_register_operand" "f")))
2667   (clobber (match_scratch:TF 3 "=&f"))
2668   (clobber (match_scratch:TF 4 "=f"))
2669   (clobber (match_scratch:BI 5 "=c"))]
2670  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_THR"
2671  "#"
2672  "&& reload_completed"
2673  [(parallel [(set (match_dup 6) (div:TF (const_int 1) (match_dup 8)))
2674	      (set (match_dup 5) (unspec:BI [(match_dup 7) (match_dup 8)] 5))
2675	      (use (const_int 1))])
2676   (cond_exec (ne (match_dup 5) (const_int 0))
2677     (parallel [(set (match_dup 3)
2678		     (plus:TF (neg:TF (mult:TF (match_dup 8) (match_dup 6)))
2679			      (match_dup 10)))
2680		(use (const_int 1))]))
2681   (cond_exec (ne (match_dup 5) (const_int 0))
2682     (parallel [(set (match_dup 3)
2683		     (plus:TF (mult:TF (match_dup 3) (match_dup 3))
2684			      (match_dup 3)))
2685		(use (const_int 1))]))
2686   (cond_exec (ne (match_dup 5) (const_int 0))
2687     (parallel [(set (match_dup 6)
2688		     (plus:TF (mult:TF (match_dup 3) (match_dup 6))
2689			      (match_dup 6)))
2690		(use (const_int 1))]))
2691   (cond_exec (ne (match_dup 5) (const_int 0))
2692     (parallel [(set (match_dup 9)
2693		     (float_truncate:SF
2694		       (mult:TF (match_dup 7) (match_dup 6))))
2695		(use (const_int 1))]))
2696   (cond_exec (ne (match_dup 5) (const_int 0))
2697     (parallel [(set (match_dup 4)
2698		     (plus:TF (neg:TF (mult:TF (match_dup 8) (match_dup 3)))
2699			      (match_dup 7)))
2700		(use (const_int 1))]))
2701   (cond_exec (ne (match_dup 5) (const_int 0))
2702     (set (match_dup 0)
2703	  (float_truncate:SF
2704	    (plus:TF (mult:TF (match_dup 4) (match_dup 6))
2705			      (match_dup 3)))))
2706  ] 
2707  "operands[6] = gen_rtx_REG (TFmode, REGNO (operands[0]));
2708   operands[7] = gen_rtx_REG (TFmode, REGNO (operands[1]));
2709   operands[8] = gen_rtx_REG (TFmode, REGNO (operands[2]));
2710   operands[9] = gen_rtx_REG (SFmode, REGNO (operands[3]));
2711   operands[10] = CONST1_RTX (TFmode);"
2712  [(set_attr "predicable" "no")])
2713
2714;; ::::::::::::::::::::
2715;; ::
2716;; :: 64 bit floating point arithmetic
2717;; ::
2718;; ::::::::::::::::::::
2719
2720(define_insn "adddf3"
2721  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2722	(plus:DF (match_operand:DF 1 "fr_register_operand" "%f")
2723		 (match_operand:DF 2 "fr_reg_or_fp01_operand" "fG")))]
2724  ""
2725  "fadd.d %0 = %1, %F2"
2726  [(set_attr "itanium_class" "fmac")])
2727
2728(define_insn "*adddf3_trunc"
2729  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2730	(float_truncate:SF
2731	  (plus:DF (match_operand:DF 1 "fr_register_operand" "%f")
2732		   (match_operand:DF 2 "fr_reg_or_fp01_operand" "fG"))))]
2733  ""
2734  "fadd.s %0 = %1, %F2"
2735  [(set_attr "itanium_class" "fmac")])
2736
2737(define_insn "subdf3"
2738  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2739	(minus:DF (match_operand:DF 1 "fr_reg_or_fp01_operand" "fG")
2740		  (match_operand:DF 2 "fr_reg_or_fp01_operand" "fG")))]
2741  ""
2742  "fsub.d %0 = %F1, %F2"
2743  [(set_attr "itanium_class" "fmac")])
2744
2745(define_insn "*subdf3_trunc"
2746  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2747	(float_truncate:SF
2748	  (minus:DF (match_operand:DF 1 "fr_reg_or_fp01_operand" "fG")
2749		    (match_operand:DF 2 "fr_reg_or_fp01_operand" "fG"))))]
2750  ""
2751  "fsub.s %0 = %F1, %F2"
2752  [(set_attr "itanium_class" "fmac")])
2753
2754(define_insn "muldf3"
2755  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2756	(mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2757		 (match_operand:DF 2 "fr_register_operand" "f")))]
2758  ""
2759  "fmpy.d %0 = %1, %2"
2760  [(set_attr "itanium_class" "fmac")])
2761
2762(define_insn "*muldf3_trunc"
2763  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2764	(float_truncate:SF
2765	  (mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2766		   (match_operand:DF 2 "fr_register_operand" "f"))))]
2767  ""
2768  "fmpy.s %0 = %1, %2"
2769  [(set_attr "itanium_class" "fmac")])
2770
2771(define_insn "absdf2"
2772  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2773	(abs:DF (match_operand:DF 1 "fr_register_operand" "f")))]
2774  ""
2775  "fabs %0 = %1"
2776  [(set_attr "itanium_class" "fmisc")])
2777
2778(define_insn "negdf2"
2779  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2780	(neg:DF (match_operand:DF 1 "fr_register_operand" "f")))]
2781  ""
2782  "fneg %0 = %1"
2783  [(set_attr "itanium_class" "fmisc")])
2784
2785(define_insn "*nabsdf2"
2786  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2787	(neg:DF (abs:DF (match_operand:DF 1 "fr_register_operand" "f"))))]
2788  ""
2789  "fnegabs %0 = %1"
2790  [(set_attr "itanium_class" "fmisc")])
2791
2792(define_insn "mindf3"
2793  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2794	(smin:DF (match_operand:DF 1 "fr_register_operand" "f")
2795		 (match_operand:DF 2 "fr_reg_or_fp01_operand" "fG")))]
2796  ""
2797  "fmin %0 = %1, %F2"
2798  [(set_attr "itanium_class" "fmisc")])
2799
2800(define_insn "maxdf3"
2801  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2802	(smax:DF (match_operand:DF 1 "fr_register_operand" "f")
2803		 (match_operand:DF 2 "fr_reg_or_fp01_operand" "fG")))]
2804  ""
2805  "fmax %0 = %1, %F2"
2806  [(set_attr "itanium_class" "fmisc")])
2807
2808(define_insn "*madddf4"
2809  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2810	(plus:DF (mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2811			  (match_operand:DF 2 "fr_register_operand" "f"))
2812		 (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG")))]
2813  ""
2814  "fma.d %0 = %1, %2, %F3"
2815  [(set_attr "itanium_class" "fmac")])
2816
2817(define_insn "*madddf4_trunc"
2818  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2819	(float_truncate:SF
2820	  (plus:DF (mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2821			    (match_operand:DF 2 "fr_register_operand" "f"))
2822		   (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG"))))]
2823  ""
2824  "fma.s %0 = %1, %2, %F3"
2825  [(set_attr "itanium_class" "fmac")])
2826
2827(define_insn "*msubdf4"
2828  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2829	(minus:DF (mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2830			   (match_operand:DF 2 "fr_register_operand" "f"))
2831		  (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG")))]
2832  ""
2833  "fms.d %0 = %1, %2, %F3"
2834  [(set_attr "itanium_class" "fmac")])
2835
2836(define_insn "*msubdf4_trunc"
2837  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2838	(float_truncate:SF
2839	  (minus:DF (mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2840			     (match_operand:DF 2 "fr_register_operand" "f"))
2841		    (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG"))))]
2842  ""
2843  "fms.s %0 = %1, %2, %F3"
2844  [(set_attr "itanium_class" "fmac")])
2845
2846(define_insn "*nmuldf3"
2847  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2848	(neg:DF (mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2849			 (match_operand:DF 2 "fr_register_operand" "f"))))]
2850  ""
2851  "fnmpy.d %0 = %1, %2"
2852  [(set_attr "itanium_class" "fmac")])
2853
2854(define_insn "*nmuldf3_trunc"
2855  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2856	(float_truncate:SF
2857	  (neg:DF (mult:DF (match_operand:DF 1 "fr_register_operand" "f")
2858			   (match_operand:DF 2 "fr_register_operand" "f")))))]
2859  ""
2860  "fnmpy.s %0 = %1, %2"
2861  [(set_attr "itanium_class" "fmac")])
2862
2863;; ??? Is it possible to canonicalize this as (minus (reg) (mult))?
2864
2865(define_insn "*nmadddf4"
2866  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2867	(plus:DF (neg:DF (mult:DF
2868			   (match_operand:DF 1 "fr_register_operand" "f")
2869			   (match_operand:DF 2 "fr_register_operand" "f")))
2870		 (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG")))]
2871  ""
2872  "fnma.d %0 = %1, %2, %F3"
2873  [(set_attr "itanium_class" "fmac")])
2874
2875(define_insn "*nmadddf4_alts"
2876  [(set (match_operand:DF 0 "fr_register_operand" "=f")
2877	(plus:DF (neg:DF (mult:DF
2878			   (match_operand:DF 1 "fr_register_operand" "f")
2879			   (match_operand:DF 2 "fr_register_operand" "f")))
2880		 (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG")))
2881   (use (match_operand:SI 4 "const_int_operand" ""))]
2882  ""
2883  "fnma.d.s%4 %0 = %1, %2, %F3"
2884  [(set_attr "itanium_class" "fmac")])
2885
2886(define_insn "*nmadddf4_trunc"
2887  [(set (match_operand:SF 0 "fr_register_operand" "=f")
2888	(float_truncate:SF
2889	  (plus:DF (neg:DF (mult:DF
2890			     (match_operand:DF 1 "fr_register_operand" "f")
2891			     (match_operand:DF 2 "fr_register_operand" "f")))
2892		   (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG"))))]
2893  ""
2894  "fnma.s %0 = %1, %2, %F3"
2895  [(set_attr "itanium_class" "fmac")])
2896
2897(define_expand "divdf3"
2898  [(set (match_operand:DF 0 "fr_register_operand" "")
2899	(div:DF (match_operand:DF 1 "fr_register_operand" "")
2900		(match_operand:DF 2 "fr_register_operand" "")))]
2901  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
2902  "
2903{
2904  rtx insn;
2905  if (TARGET_INLINE_DIV_LAT)
2906    insn = gen_divdf3_internal_lat (operands[0], operands[1], operands[2]);
2907  else
2908    insn = gen_divdf3_internal_thr (operands[0], operands[1], operands[2]);
2909  emit_insn (insn);
2910  DONE;
2911}")
2912
2913(define_insn_and_split "divdf3_internal_lat"
2914  [(set (match_operand:DF 0 "fr_register_operand" "=&f")
2915	(div:DF (match_operand:DF 1 "fr_register_operand" "f")
2916		(match_operand:DF 2 "fr_register_operand" "f")))
2917   (clobber (match_scratch:TF 3 "=&f"))
2918   (clobber (match_scratch:TF 4 "=&f"))
2919   (clobber (match_scratch:TF 5 "=&f"))
2920   (clobber (match_scratch:BI 6 "=c"))]
2921  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_LAT"
2922  "#"
2923  "&& reload_completed"
2924  [(parallel [(set (match_dup 7) (div:TF (const_int 1) (match_dup 9)))
2925	      (set (match_dup 6) (unspec:BI [(match_dup 8) (match_dup 9)] 5))
2926	      (use (const_int 1))])
2927   (cond_exec (ne (match_dup 6) (const_int 0))
2928     (parallel [(set (match_dup 3) (mult:TF (match_dup 8) (match_dup 7)))
2929		(use (const_int 1))]))
2930   (cond_exec (ne (match_dup 6) (const_int 0))
2931     (parallel [(set (match_dup 4)
2932		     (plus:TF (neg:TF (mult:TF (match_dup 9) (match_dup 7)))
2933			      (match_dup 12)))
2934		(use (const_int 1))]))
2935   (cond_exec (ne (match_dup 6) (const_int 0))
2936     (parallel [(set (match_dup 3)
2937		     (plus:TF (mult:TF (match_dup 4) (match_dup 3))
2938			      (match_dup 3)))
2939		(use (const_int 1))]))
2940   (cond_exec (ne (match_dup 6) (const_int 0))
2941     (parallel [(set (match_dup 5) (mult:TF (match_dup 4) (match_dup 4)))
2942		(use (const_int 1))]))
2943   (cond_exec (ne (match_dup 6) (const_int 0))
2944     (parallel [(set (match_dup 7)
2945		     (plus:TF (mult:TF (match_dup 4) (match_dup 7))
2946			      (match_dup 7)))
2947		(use (const_int 1))]))
2948   (cond_exec (ne (match_dup 6) (const_int 0))
2949     (parallel [(set (match_dup 3)
2950		     (plus:TF (mult:TF (match_dup 5) (match_dup 3))
2951			      (match_dup 3)))
2952		(use (const_int 1))]))
2953   (cond_exec (ne (match_dup 6) (const_int 0))
2954     (parallel [(set (match_dup 4) (mult:TF (match_dup 5) (match_dup 5)))
2955		(use (const_int 1))]))
2956   (cond_exec (ne (match_dup 6) (const_int 0))
2957     (parallel [(set (match_dup 7)
2958		     (plus:TF (mult:TF (match_dup 5) (match_dup 7))
2959			      (match_dup 7)))
2960		(use (const_int 1))]))
2961   (cond_exec (ne (match_dup 6) (const_int 0))
2962     (parallel [(set (match_dup 10)
2963		     (float_truncate:DF
2964		       (plus:TF (mult:TF (match_dup 4) (match_dup 3))
2965			      (match_dup 3))))
2966		(use (const_int 1))]))
2967   (cond_exec (ne (match_dup 6) (const_int 0))
2968     (parallel [(set (match_dup 7)
2969		     (plus:TF (mult:TF (match_dup 4) (match_dup 7))
2970			      (match_dup 7)))
2971		(use (const_int 1))]))
2972   (cond_exec (ne (match_dup 6) (const_int 0))
2973     (parallel [(set (match_dup 11)
2974		     (float_truncate:DF
2975		       (plus:TF (neg:TF (mult:TF (match_dup 9) (match_dup 3)))
2976			        (match_dup 8))))
2977		(use (const_int 1))]))
2978   (cond_exec (ne (match_dup 6) (const_int 0))
2979     (set (match_dup 0)
2980	  (float_truncate:DF (plus:TF (mult:TF (match_dup 5) (match_dup 7))
2981			      (match_dup 3)))))
2982  ] 
2983  "operands[7] = gen_rtx_REG (TFmode, REGNO (operands[0]));
2984   operands[8] = gen_rtx_REG (TFmode, REGNO (operands[1]));
2985   operands[9] = gen_rtx_REG (TFmode, REGNO (operands[2]));
2986   operands[10] = gen_rtx_REG (DFmode, REGNO (operands[3]));
2987   operands[11] = gen_rtx_REG (DFmode, REGNO (operands[5]));
2988   operands[12] = CONST1_RTX (TFmode);"
2989  [(set_attr "predicable" "no")])
2990
2991(define_insn_and_split "divdf3_internal_thr"
2992  [(set (match_operand:DF 0 "fr_register_operand" "=&f")
2993	(div:DF (match_operand:DF 1 "fr_register_operand" "f")
2994		(match_operand:DF 2 "fr_register_operand" "f")))
2995   (clobber (match_scratch:TF 3 "=&f"))
2996   (clobber (match_scratch:DF 4 "=f"))
2997   (clobber (match_scratch:BI 5 "=c"))]
2998  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_THR"
2999  "#"
3000  "&& reload_completed"
3001  [(parallel [(set (match_dup 6) (div:TF (const_int 1) (match_dup 8)))
3002	      (set (match_dup 5) (unspec:BI [(match_dup 7) (match_dup 8)] 5))
3003	      (use (const_int 1))])
3004   (cond_exec (ne (match_dup 5) (const_int 0))
3005     (parallel [(set (match_dup 3)
3006		     (plus:TF (neg:TF (mult:TF (match_dup 8) (match_dup 6)))
3007			      (match_dup 10)))
3008		(use (const_int 1))]))
3009   (cond_exec (ne (match_dup 5) (const_int 0))
3010     (parallel [(set (match_dup 6)
3011		     (plus:TF (mult:TF (match_dup 3) (match_dup 6))
3012			      (match_dup 6)))
3013		(use (const_int 1))]))
3014   (cond_exec (ne (match_dup 5) (const_int 0))
3015     (parallel [(set (match_dup 3)
3016		     (mult:TF (match_dup 3) (match_dup 3)))
3017		(use (const_int 1))]))
3018   (cond_exec (ne (match_dup 5) (const_int 0))
3019     (parallel [(set (match_dup 6)
3020		     (plus:TF (mult:TF (match_dup 3) (match_dup 6))
3021			      (match_dup 6)))
3022		(use (const_int 1))]))
3023   (cond_exec (ne (match_dup 5) (const_int 0))
3024     (parallel [(set (match_dup 3)
3025		     (mult:TF (match_dup 3) (match_dup 3)))
3026		(use (const_int 1))]))
3027   (cond_exec (ne (match_dup 5) (const_int 0))
3028     (parallel [(set (match_dup 6)
3029		     (plus:TF (mult:TF (match_dup 3) (match_dup 6))
3030			      (match_dup 6)))
3031		(use (const_int 1))]))
3032   (cond_exec (ne (match_dup 5) (const_int 0))
3033     (parallel [(set (match_dup 9)
3034		     (float_truncate:DF
3035		       (mult:TF (match_dup 7) (match_dup 3))))
3036		(use (const_int 1))]))
3037   (cond_exec (ne (match_dup 5) (const_int 0))
3038     (parallel [(set (match_dup 4)
3039		     (plus:DF (neg:DF (mult:DF (match_dup 2) (match_dup 9)))
3040			      (match_dup 1)))
3041		(use (const_int 1))]))
3042   (cond_exec (ne (match_dup 5) (const_int 0))
3043     (set (match_dup 0)
3044	  (plus:DF (mult:DF (match_dup 4) (match_dup 0))
3045			    (match_dup 9))))
3046  ] 
3047  "operands[6] = gen_rtx_REG (TFmode, REGNO (operands[0]));
3048   operands[7] = gen_rtx_REG (TFmode, REGNO (operands[1]));
3049   operands[8] = gen_rtx_REG (TFmode, REGNO (operands[2]));
3050   operands[9] = gen_rtx_REG (DFmode, REGNO (operands[3]));
3051   operands[10] = CONST1_RTX (TFmode);"
3052  [(set_attr "predicable" "no")])
3053
3054;; ::::::::::::::::::::
3055;; ::
3056;; :: 80 bit floating point arithmetic
3057;; ::
3058;; ::::::::::::::::::::
3059
3060(define_insn "addtf3"
3061  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3062	(plus:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3063		 (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))]
3064  "INTEL_EXTENDED_IEEE_FORMAT"
3065  "fadd %0 = %F1, %F2"
3066  [(set_attr "itanium_class" "fmac")])
3067
3068(define_insn "*addtf3_truncsf"
3069  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3070	(float_truncate:SF
3071	  (plus:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3072		   (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))]
3073  "INTEL_EXTENDED_IEEE_FORMAT"
3074  "fadd.s %0 = %F1, %F2"
3075  [(set_attr "itanium_class" "fmac")])
3076
3077(define_insn "*addtf3_truncdf"
3078  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3079	(float_truncate:DF
3080	  (plus:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3081		   (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))]
3082  "INTEL_EXTENDED_IEEE_FORMAT"
3083  "fadd.d %0 = %F1, %F2"
3084  [(set_attr "itanium_class" "fmac")])
3085
3086(define_insn "subtf3"
3087  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3088	(minus:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3089		  (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))]
3090  "INTEL_EXTENDED_IEEE_FORMAT"
3091  "fsub %0 = %F1, %F2"
3092  [(set_attr "itanium_class" "fmac")])
3093
3094(define_insn "*subtf3_truncsf"
3095  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3096	(float_truncate:SF
3097	  (minus:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3098		    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))]
3099  "INTEL_EXTENDED_IEEE_FORMAT"
3100  "fsub.s %0 = %F1, %F2"
3101  [(set_attr "itanium_class" "fmac")])
3102
3103(define_insn "*subtf3_truncdf"
3104  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3105	(float_truncate:DF
3106	  (minus:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3107		    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))]
3108  "INTEL_EXTENDED_IEEE_FORMAT"
3109  "fsub.d %0 = %F1, %F2"
3110  [(set_attr "itanium_class" "fmac")])
3111
3112(define_insn "multf3"
3113  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3114	(mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3115		 (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))]
3116  "INTEL_EXTENDED_IEEE_FORMAT"
3117  "fmpy %0 = %F1, %F2"
3118  [(set_attr "itanium_class" "fmac")])
3119
3120(define_insn "*multf3_truncsf"
3121  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3122	(float_truncate:SF
3123	  (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3124		   (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))]
3125  "INTEL_EXTENDED_IEEE_FORMAT"
3126  "fmpy.s %0 = %F1, %F2"
3127  [(set_attr "itanium_class" "fmac")])
3128
3129(define_insn "*multf3_truncdf"
3130  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3131	(float_truncate:DF
3132	  (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3133		   (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))]
3134  "INTEL_EXTENDED_IEEE_FORMAT"
3135  "fmpy.d %0 = %F1, %F2"
3136  [(set_attr "itanium_class" "fmac")])
3137
3138(define_insn "*multf3_alts"
3139  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3140	(mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3141		 (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))
3142   (use (match_operand:SI 3 "const_int_operand" ""))]
3143  "INTEL_EXTENDED_IEEE_FORMAT"
3144  "fmpy.s%3 %0 = %F1, %F2"
3145  [(set_attr "itanium_class" "fmac")])
3146
3147(define_insn "*multf3_truncsf_alts"
3148  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3149	(float_truncate:SF
3150	  (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3151		   (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))
3152   (use (match_operand:SI 3 "const_int_operand" ""))]
3153  "INTEL_EXTENDED_IEEE_FORMAT"
3154  "fmpy.s.s%3 %0 = %F1, %F2"
3155  [(set_attr "itanium_class" "fmac")])
3156
3157(define_insn "*multf3_truncdf_alts"
3158  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3159	(float_truncate:DF
3160	  (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3161		   (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))
3162   (use (match_operand:SI 3 "const_int_operand" ""))]
3163  "INTEL_EXTENDED_IEEE_FORMAT"
3164  "fmpy.d.s%3 %0 = %F1, %F2"
3165  [(set_attr "itanium_class" "fmac")])
3166
3167(define_insn "abstf2"
3168  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3169	(abs:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")))]
3170  "INTEL_EXTENDED_IEEE_FORMAT"
3171  "fabs %0 = %F1"
3172  [(set_attr "itanium_class" "fmisc")])
3173
3174(define_insn "negtf2"
3175  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3176	(neg:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")))]
3177  "INTEL_EXTENDED_IEEE_FORMAT"
3178  "fneg %0 = %F1"
3179  [(set_attr "itanium_class" "fmisc")])
3180
3181(define_insn "*nabstf2"
3182  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3183	(neg:TF (abs:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG"))))]
3184  "INTEL_EXTENDED_IEEE_FORMAT"
3185  "fnegabs %0 = %F1"
3186  [(set_attr "itanium_class" "fmisc")])
3187
3188(define_insn "mintf3"
3189  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3190	(smin:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3191		 (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))]
3192  "INTEL_EXTENDED_IEEE_FORMAT"
3193  "fmin %0 = %F1, %F2"
3194  [(set_attr "itanium_class" "fmisc")])
3195
3196(define_insn "maxtf3"
3197  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3198	(smax:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3199		 (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))]
3200  "INTEL_EXTENDED_IEEE_FORMAT"
3201  "fmax %0 = %F1, %F2"
3202  [(set_attr "itanium_class" "fmisc")])
3203
3204(define_insn "*maddtf4"
3205  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3206	(plus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3207			  (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3208		 (match_operand:TF 3 "tfreg_or_fp01_operand" "fG")))]
3209  "INTEL_EXTENDED_IEEE_FORMAT"
3210  "fma %0 = %F1, %F2, %F3"
3211  [(set_attr "itanium_class" "fmac")])
3212
3213(define_insn "*maddtf4_truncsf"
3214  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3215	(float_truncate:SF
3216	  (plus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3217			    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3218		   (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))]
3219  "INTEL_EXTENDED_IEEE_FORMAT"
3220  "fma.s %0 = %F1, %F2, %F3"
3221  [(set_attr "itanium_class" "fmac")])
3222
3223(define_insn "*maddtf4_truncdf"
3224  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3225	(float_truncate:DF
3226	  (plus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3227			    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3228		   (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))]
3229  "INTEL_EXTENDED_IEEE_FORMAT"
3230  "fma.d %0 = %F1, %F2, %F3"
3231  [(set_attr "itanium_class" "fmac")])
3232
3233(define_insn "*maddtf4_alts"
3234  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3235	(plus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3236			  (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3237		 (match_operand:TF 3 "tfreg_or_fp01_operand" "fG")))
3238   (use (match_operand:SI 4 "const_int_operand" ""))]
3239  "INTEL_EXTENDED_IEEE_FORMAT"
3240  "fma.s%4 %0 = %F1, %F2, %F3"
3241  [(set_attr "itanium_class" "fmac")])
3242
3243(define_insn "*maddtf4_alts_truncdf"
3244  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3245	(float_truncate:DF
3246	  (plus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3247			    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3248		   (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))
3249   (use (match_operand:SI 4 "const_int_operand" ""))]
3250  "INTEL_EXTENDED_IEEE_FORMAT"
3251  "fma.d.s%4 %0 = %F1, %F2, %F3"
3252  [(set_attr "itanium_class" "fmac")])
3253
3254(define_insn "*msubtf4"
3255  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3256	(minus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3257			   (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3258		  (match_operand:TF 3 "tfreg_or_fp01_operand" "fG")))]
3259  "INTEL_EXTENDED_IEEE_FORMAT"
3260  "fms %0 = %F1, %F2, %F3"
3261  [(set_attr "itanium_class" "fmac")])
3262
3263(define_insn "*msubtf4_truncsf"
3264  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3265	(float_truncate:SF
3266	  (minus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3267			     (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3268		    (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))]
3269  "INTEL_EXTENDED_IEEE_FORMAT"
3270  "fms.s %0 = %F1, %F2, %F3"
3271  [(set_attr "itanium_class" "fmac")])
3272
3273(define_insn "*msubtf4_truncdf"
3274  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3275	(float_truncate:DF
3276	  (minus:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3277			     (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))
3278		    (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))]
3279  "INTEL_EXTENDED_IEEE_FORMAT"
3280  "fms.d %0 = %F1, %F2, %F3"
3281  [(set_attr "itanium_class" "fmac")])
3282
3283(define_insn "*nmultf3"
3284  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3285	(neg:TF (mult:TF (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3286			 (match_operand:TF 2 "tfreg_or_fp01_operand" "fG"))))]
3287  "INTEL_EXTENDED_IEEE_FORMAT"
3288  "fnmpy %0 = %F1, %F2"
3289  [(set_attr "itanium_class" "fmac")])
3290
3291(define_insn "*nmultf3_truncsf"
3292  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3293	(float_truncate:SF
3294	  (neg:TF (mult:TF
3295		    (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3296		    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))))]
3297  "INTEL_EXTENDED_IEEE_FORMAT"
3298  "fnmpy.s %0 = %F1, %F2"
3299  [(set_attr "itanium_class" "fmac")])
3300
3301(define_insn "*nmultf3_truncdf"
3302  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3303	(float_truncate:DF
3304	  (neg:TF (mult:TF
3305		    (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3306		    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))))]
3307  "INTEL_EXTENDED_IEEE_FORMAT"
3308  "fnmpy.d %0 = %F1, %F2"
3309  [(set_attr "itanium_class" "fmac")])
3310
3311;; ??? Is it possible to canonicalize this as (minus (reg) (mult))?
3312
3313(define_insn "*nmaddtf4"
3314  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3315	(plus:TF (neg:TF (mult:TF
3316			  (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3317			  (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))
3318		 (match_operand:TF 3 "tfreg_or_fp01_operand" "fG")))]
3319  "INTEL_EXTENDED_IEEE_FORMAT"
3320  "fnma %0 = %F1, %F2, %F3"
3321  [(set_attr "itanium_class" "fmac")])
3322
3323(define_insn "*nmaddtf4_truncsf"
3324  [(set (match_operand:SF 0 "fr_register_operand" "=f")
3325	(float_truncate:SF
3326	  (plus:TF (neg:TF (mult:TF
3327			    (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3328			    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))
3329		   (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))]
3330  "INTEL_EXTENDED_IEEE_FORMAT"
3331  "fnma.s %0 = %F1, %F2, %F3"
3332  [(set_attr "itanium_class" "fmac")])
3333
3334(define_insn "*nmaddtf4_truncdf"
3335  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3336	(float_truncate:DF
3337	  (plus:TF (neg:TF (mult:TF
3338			    (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3339			    (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))
3340		   (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))]
3341  "INTEL_EXTENDED_IEEE_FORMAT"
3342  "fnma.d %0 = %F1, %F2, %F3"
3343  [(set_attr "itanium_class" "fmac")])
3344
3345(define_insn "*nmaddtf4_alts"
3346  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3347	(plus:TF (neg:TF (mult:TF
3348			  (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3349			  (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))
3350		 (match_operand:TF 3 "tfreg_or_fp01_operand" "fG")))
3351   (use (match_operand:SI 4 "const_int_operand" ""))]
3352  "INTEL_EXTENDED_IEEE_FORMAT"
3353  "fnma.s%4 %0 = %F1, %F2, %F3"
3354  [(set_attr "itanium_class" "fmac")])
3355
3356(define_insn "*nmaddtf4_truncdf_alts"
3357  [(set (match_operand:DF 0 "fr_register_operand" "=f")
3358	(float_truncate:DF
3359	  (plus:TF (neg:TF
3360		     (mult:TF
3361		       (match_operand:TF 1 "tfreg_or_fp01_operand" "fG")
3362		       (match_operand:TF 2 "tfreg_or_fp01_operand" "fG")))
3363		 (match_operand:TF 3 "tfreg_or_fp01_operand" "fG"))))
3364   (use (match_operand:SI 4 "const_int_operand" ""))]
3365  "INTEL_EXTENDED_IEEE_FORMAT"
3366  "fnma.d.s%4 %0 = %F1, %F2, %F3"
3367  [(set_attr "itanium_class" "fmac")])
3368
3369(define_expand "divtf3"
3370  [(set (match_operand:TF 0 "fr_register_operand" "")
3371	(div:TF (match_operand:TF 1 "fr_register_operand" "")
3372		(match_operand:TF 2 "fr_register_operand" "")))]
3373  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV"
3374  "
3375{
3376  rtx insn;
3377  if (TARGET_INLINE_DIV_LAT)
3378    insn = gen_divtf3_internal_lat (operands[0], operands[1], operands[2]);
3379  else
3380    insn = gen_divtf3_internal_thr (operands[0], operands[1], operands[2]);
3381  emit_insn (insn);
3382  DONE;
3383}")
3384
3385(define_insn_and_split "divtf3_internal_lat"
3386  [(set (match_operand:TF 0 "fr_register_operand" "=&f")
3387	(div:TF (match_operand:TF 1 "fr_register_operand" "f")
3388		(match_operand:TF 2 "fr_register_operand" "f")))
3389   (clobber (match_scratch:TF 3 "=&f"))
3390   (clobber (match_scratch:TF 4 "=&f"))
3391   (clobber (match_scratch:TF 5 "=&f"))
3392   (clobber (match_scratch:TF 6 "=&f"))
3393   (clobber (match_scratch:BI 7 "=c"))]
3394  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_LAT"
3395  "#"
3396  "&& reload_completed"
3397  [(parallel [(set (match_dup 0) (div:TF (const_int 1) (match_dup 2)))
3398	      (set (match_dup 7) (unspec:BI [(match_dup 1) (match_dup 2)] 5))
3399	      (use (const_int 1))])
3400   (cond_exec (ne (match_dup 7) (const_int 0))
3401     (parallel [(set (match_dup 3)
3402		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 0)))
3403			      (match_dup 8)))
3404		(use (const_int 1))]))
3405   (cond_exec (ne (match_dup 7) (const_int 0))
3406     (parallel [(set (match_dup 4) (mult:TF (match_dup 1) (match_dup 0)))
3407		(use (const_int 1))]))
3408   (cond_exec (ne (match_dup 7) (const_int 0))
3409     (parallel [(set (match_dup 5) (mult:TF (match_dup 3) (match_dup 3)))
3410		(use (const_int 1))]))
3411   (cond_exec (ne (match_dup 7) (const_int 0))
3412     (parallel [(set (match_dup 6)
3413		     (plus:TF (mult:TF (match_dup 3) (match_dup 3))
3414			      (match_dup 3)))
3415		(use (const_int 1))]))
3416   (cond_exec (ne (match_dup 7) (const_int 0))
3417     (parallel [(set (match_dup 3)
3418		     (plus:TF (mult:TF (match_dup 5) (match_dup 5))
3419			      (match_dup 3)))
3420		(use (const_int 1))]))
3421   (cond_exec (ne (match_dup 7) (const_int 0))
3422     (parallel [(set (match_dup 5)
3423		     (plus:TF (mult:TF (match_dup 6) (match_dup 0))
3424			      (match_dup 0)))
3425		(use (const_int 1))]))
3426   (cond_exec (ne (match_dup 7) (const_int 0))
3427     (parallel [(set (match_dup 0)
3428		     (plus:TF (mult:TF (match_dup 5) (match_dup 3))
3429			      (match_dup 0)))
3430		(use (const_int 1))]))
3431   (cond_exec (ne (match_dup 7) (const_int 0))
3432     (parallel [(set (match_dup 4)
3433		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 4)))
3434			      (match_dup 1)))
3435		(use (const_int 1))]))
3436   (cond_exec (ne (match_dup 7) (const_int 0))
3437     (parallel [(set (match_dup 3)
3438		     (plus:TF (mult:TF (match_dup 3) (match_dup 0))
3439			      (match_dup 4)))
3440		(use (const_int 1))]))
3441   (cond_exec (ne (match_dup 7) (const_int 0))
3442     (parallel [(set (match_dup 5)
3443		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 0)))
3444			      (match_dup 8)))
3445		(use (const_int 1))]))
3446   (cond_exec (ne (match_dup 7) (const_int 0))
3447     (parallel [(set (match_dup 0)
3448		     (plus:TF (mult:TF (match_dup 4) (match_dup 0))
3449			      (match_dup 0)))
3450		(use (const_int 1))]))
3451   (cond_exec (ne (match_dup 7) (const_int 0))
3452     (parallel [(set (match_dup 4)
3453		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 3)))
3454			      (match_dup 1)))
3455		(use (const_int 1))]))
3456   (cond_exec (ne (match_dup 7) (const_int 0))
3457     (set (match_dup 0)
3458	  (plus:TF (mult:TF (match_dup 4) (match_dup 0))
3459		   (match_dup 3))))
3460  ] 
3461  "operands[8] = CONST1_RTX (TFmode);"
3462  [(set_attr "predicable" "no")])
3463
3464(define_insn_and_split "divtf3_internal_thr"
3465  [(set (match_operand:TF 0 "fr_register_operand" "=&f")
3466	(div:TF (match_operand:TF 1 "fr_register_operand" "f")
3467		(match_operand:TF 2 "fr_register_operand" "f")))
3468   (clobber (match_scratch:TF 3 "=&f"))
3469   (clobber (match_scratch:TF 4 "=&f"))
3470   (clobber (match_scratch:BI 5 "=c"))]
3471  "INTEL_EXTENDED_IEEE_FORMAT && TARGET_INLINE_DIV_THR"
3472  "#"
3473  "&& reload_completed"
3474  [(parallel [(set (match_dup 0) (div:TF (const_int 1) (match_dup 2)))
3475	      (set (match_dup 5) (unspec:BI [(match_dup 1) (match_dup 2)] 5))
3476	      (use (const_int 1))])
3477   (cond_exec (ne (match_dup 5) (const_int 0))
3478     (parallel [(set (match_dup 3)
3479		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 0)))
3480			      (match_dup 6)))
3481		(use (const_int 1))]))
3482   (cond_exec (ne (match_dup 5) (const_int 0))
3483     (parallel [(set (match_dup 4)
3484		     (plus:TF (mult:TF (match_dup 3) (match_dup 0))
3485			      (match_dup 0)))
3486		(use (const_int 1))]))
3487   (cond_exec (ne (match_dup 5) (const_int 0))
3488     (parallel [(set (match_dup 3) (mult:TF (match_dup 3) (match_dup 3)))
3489		(use (const_int 1))]))
3490   (cond_exec (ne (match_dup 5) (const_int 0))
3491     (parallel [(set (match_dup 3)
3492		     (plus:TF (mult:TF (match_dup 3) (match_dup 4))
3493			      (match_dup 4)))
3494		(use (const_int 1))]))
3495   (cond_exec (ne (match_dup 5) (const_int 0))
3496     (parallel [(set (match_dup 4) (mult:TF (match_dup 1) (match_dup 0)))
3497		(use (const_int 1))]))
3498   (cond_exec (ne (match_dup 5) (const_int 0))
3499     (parallel [(set (match_dup 0)
3500		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 3)))
3501			      (match_dup 6)))
3502		(use (const_int 1))]))
3503   (cond_exec (ne (match_dup 5) (const_int 0))
3504     (parallel [(set (match_dup 0)
3505		     (plus:TF (mult:TF (match_dup 0) (match_dup 3))
3506			      (match_dup 3)))
3507		(use (const_int 1))]))
3508   (cond_exec (ne (match_dup 5) (const_int 0))
3509     (parallel [(set (match_dup 3)
3510		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 4)))
3511			      (match_dup 1)))
3512		(use (const_int 1))]))
3513   (cond_exec (ne (match_dup 5) (const_int 0))
3514     (parallel [(set (match_dup 3)
3515		     (plus:TF (mult:TF (match_dup 3) (match_dup 0))
3516			      (match_dup 4)))
3517		(use (const_int 1))]))
3518   (cond_exec (ne (match_dup 5) (const_int 0))
3519     (parallel [(set (match_dup 4)
3520		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 0)))
3521			      (match_dup 6)))
3522		(use (const_int 1))]))
3523   (cond_exec (ne (match_dup 5) (const_int 0))
3524     (parallel [(set (match_dup 0)
3525		     (plus:TF (mult:TF (match_dup 4) (match_dup 0))
3526			      (match_dup 0)))
3527		(use (const_int 1))]))
3528   (cond_exec (ne (match_dup 5) (const_int 0))
3529     (parallel [(set (match_dup 4)
3530		     (plus:TF (neg:TF (mult:TF (match_dup 2) (match_dup 3)))
3531			      (match_dup 1)))
3532		(use (const_int 1))]))
3533   (cond_exec (ne (match_dup 5) (const_int 0))
3534     (set (match_dup 0)
3535	  (plus:TF (mult:TF (match_dup 4) (match_dup 0))
3536		   (match_dup 3))))
3537  ] 
3538  "operands[6] = CONST1_RTX (TFmode);"
3539  [(set_attr "predicable" "no")])
3540
3541;; ??? frcpa works like cmp.foo.unc.
3542
3543(define_insn "*recip_approx"
3544  [(set (match_operand:TF 0 "fr_register_operand" "=f")
3545	(div:TF (const_int 1)
3546		(match_operand:TF 3 "fr_register_operand" "f")))
3547   (set (match_operand:BI 1 "register_operand" "=c")
3548	(unspec:BI [(match_operand:TF 2 "fr_register_operand" "f")
3549		    (match_dup 3)] 5))
3550   (use (match_operand:SI 4 "const_int_operand" ""))]
3551  "INTEL_EXTENDED_IEEE_FORMAT"
3552  "frcpa.s%4 %0, %1 = %2, %3"
3553  [(set_attr "itanium_class" "fmisc")
3554   (set_attr "predicable" "no")])
3555
3556;; ::::::::::::::::::::
3557;; ::
3558;; :: 32 bit Integer Shifts and Rotates
3559;; ::
3560;; ::::::::::::::::::::
3561
3562(define_expand "ashlsi3"
3563  [(set (match_operand:SI 0 "gr_register_operand" "")
3564	(ashift:SI (match_operand:SI 1 "gr_register_operand" "")
3565		   (match_operand:SI 2 "gr_reg_or_5bit_operand" "")))]
3566  ""
3567  "
3568{
3569  if (GET_CODE (operands[2]) != CONST_INT)
3570    {
3571      /* Why oh why didn't Intel arrange for SHIFT_COUNT_TRUNCATED?  Now
3572	 we've got to get rid of stray bits outside the SImode register.  */
3573      rtx subshift = gen_reg_rtx (DImode);
3574      emit_insn (gen_zero_extendsidi2 (subshift, operands[2]));
3575      operands[2] = subshift;
3576    }
3577}")
3578
3579(define_insn "*ashlsi3_internal"
3580  [(set (match_operand:SI 0 "gr_register_operand" "=r,r,r")
3581	(ashift:SI (match_operand:SI 1 "gr_register_operand" "r,r,r")
3582		   (match_operand:DI 2 "gr_reg_or_5bit_operand" "R,n,r")))]
3583  ""
3584  "@
3585   shladd %0 = %1, %2, r0
3586   dep.z %0 = %1, %2, %E2
3587   shl %0 = %1, %2"
3588  [(set_attr "itanium_class" "ialu,ishf,mmshf")])
3589
3590(define_expand "ashrsi3"
3591  [(set (match_operand:SI 0 "gr_register_operand" "")
3592	(ashiftrt:SI (match_operand:SI 1 "gr_register_operand" "")
3593		     (match_operand:SI 2 "gr_reg_or_5bit_operand" "")))]
3594  ""
3595  "
3596{
3597  rtx subtarget = gen_reg_rtx (DImode);
3598  if (GET_CODE (operands[2]) == CONST_INT)
3599    emit_insn (gen_extv (subtarget, gen_lowpart (DImode, operands[1]),
3600			 GEN_INT (32 - INTVAL (operands[2])), operands[2]));
3601  else
3602    {
3603      rtx subshift = gen_reg_rtx (DImode);
3604      emit_insn (gen_extendsidi2 (subtarget, operands[1]));
3605      emit_insn (gen_zero_extendsidi2 (subshift, operands[2]));
3606      emit_insn (gen_ashrdi3 (subtarget, subtarget, subshift));
3607    }
3608  emit_move_insn (gen_lowpart (DImode, operands[0]), subtarget);
3609  DONE;
3610}")
3611
3612(define_expand "lshrsi3"
3613  [(set (match_operand:SI 0 "gr_register_operand" "")
3614	(lshiftrt:SI (match_operand:SI 1 "gr_register_operand" "")
3615		     (match_operand:SI 2 "gr_reg_or_5bit_operand" "")))]
3616  ""
3617  "
3618{
3619  rtx subtarget = gen_reg_rtx (DImode);
3620  if (GET_CODE (operands[2]) == CONST_INT)
3621    emit_insn (gen_extzv (subtarget, gen_lowpart (DImode, operands[1]),
3622			  GEN_INT (32 - INTVAL (operands[2])), operands[2]));
3623  else
3624    {
3625      rtx subshift = gen_reg_rtx (DImode);
3626      emit_insn (gen_zero_extendsidi2 (subtarget, operands[1]));
3627      emit_insn (gen_zero_extendsidi2 (subshift, operands[2]));
3628      emit_insn (gen_lshrdi3 (subtarget, subtarget, subshift));
3629    }
3630  emit_move_insn (gen_lowpart (DImode, operands[0]), subtarget);
3631  DONE;
3632}")
3633
3634;; Use mix4.r/shr to implement rotrsi3.  We only get 32 bits of valid result
3635;; here, instead of 64 like the patterns above.  Keep the pattern together
3636;; until after combine; otherwise it won't get matched often.
3637
3638(define_expand "rotrsi3"
3639  [(set (match_operand:SI 0 "gr_register_operand" "")
3640	(rotatert:SI (match_operand:SI 1 "gr_register_operand" "")
3641		     (match_operand:SI 2 "gr_reg_or_5bit_operand" "")))]
3642  ""
3643  "
3644{
3645  if (GET_MODE (operands[2]) != VOIDmode)
3646    {
3647      rtx tmp = gen_reg_rtx (DImode);
3648      emit_insn (gen_zero_extendsidi2 (tmp, operands[2]));
3649      operands[2] = tmp;
3650    }
3651}")
3652
3653(define_insn_and_split "*rotrsi3_internal"
3654  [(set (match_operand:SI 0 "gr_register_operand" "=&r")
3655	(rotatert:SI (match_operand:SI 1 "gr_register_operand" "r")
3656		     (match_operand:DI 2 "gr_reg_or_5bit_operand" "rM")))]
3657  ""
3658  "#"
3659  "reload_completed"
3660  [(set (match_dup 3)
3661	(ior:DI (zero_extend:DI (match_dup 1))
3662		(ashift:DI (zero_extend:DI (match_dup 1)) (const_int 32))))
3663   (set (match_dup 3)
3664	(lshiftrt:DI (match_dup 3) (match_dup 2)))]
3665  "operands[3] = gen_rtx_REG (DImode, REGNO (operands[0]));")
3666
3667(define_expand "rotlsi3"
3668  [(set (match_operand:SI 0 "gr_register_operand" "")
3669	(rotate:SI (match_operand:SI 1 "gr_register_operand" "")
3670		   (match_operand:SI 2 "gr_reg_or_5bit_operand" "")))]
3671  ""
3672  "
3673{
3674  if (! shift_32bit_count_operand (operands[2], SImode))
3675    {
3676      rtx tmp = gen_reg_rtx (SImode);
3677      emit_insn (gen_subsi3 (tmp, GEN_INT (32), operands[2]));
3678      emit_insn (gen_rotrsi3 (operands[0], operands[1], tmp));
3679      DONE;
3680    }
3681}")
3682
3683(define_insn_and_split "*rotlsi3_internal"
3684  [(set (match_operand:SI 0 "gr_register_operand" "=r")
3685	(rotate:SI (match_operand:SI 1 "gr_register_operand" "r")
3686		   (match_operand:SI 2 "shift_32bit_count_operand" "n")))]
3687  ""
3688  "#"
3689  "reload_completed"
3690  [(set (match_dup 3)
3691	(ior:DI (zero_extend:DI (match_dup 1))
3692		(ashift:DI (zero_extend:DI (match_dup 1)) (const_int 32))))
3693   (set (match_dup 3)
3694	(lshiftrt:DI (match_dup 3) (match_dup 2)))]
3695  "operands[3] = gen_rtx_REG (DImode, REGNO (operands[0]));
3696   operands[2] = GEN_INT (32 - INTVAL (operands[2]));")
3697
3698;; ::::::::::::::::::::
3699;; ::
3700;; :: 64 bit Integer Shifts and Rotates
3701;; ::
3702;; ::::::::::::::::::::
3703
3704(define_insn "ashldi3"
3705  [(set (match_operand:DI 0 "gr_register_operand" "=r,r,r")
3706	(ashift:DI (match_operand:DI 1 "gr_register_operand" "r,r,r")
3707		   (match_operand:DI 2 "gr_reg_or_6bit_operand" "R,r,rM")))]
3708  ""
3709  "@
3710   shladd %0 = %1, %2, r0
3711   shl %0 = %1, %2
3712   shl %0 = %1, %2"
3713  [(set_attr "itanium_class" "ialu,mmshf,mmshfi")])
3714
3715;; ??? Maybe combine this with the multiply and add instruction?
3716
3717(define_insn "*shladd"
3718  [(set (match_operand:DI 0 "gr_register_operand" "=r")
3719	(plus:DI (mult:DI (match_operand:DI 1 "gr_register_operand" "r")
3720			  (match_operand:DI 2 "shladd_operand" "n"))
3721		 (match_operand:DI 3 "gr_register_operand" "r")))]
3722  ""
3723  "shladd %0 = %1, %S2, %3"
3724  [(set_attr "itanium_class" "ialu")])
3725
3726;; This can be created by register elimination if operand3 of shladd is an
3727;; eliminable register or has reg_equiv_constant set.
3728
3729;; We have to use nonmemory_operand for operand 4, to ensure that the
3730;; validate_changes call inside eliminate_regs will always succeed.  If it
3731;; doesn't succeed, then this remain a shladd pattern, and will be reloaded
3732;; incorrectly.
3733
3734(define_insn_and_split "*shladd_elim"
3735  [(set (match_operand:DI 0 "gr_register_operand" "=&r")
3736	(plus:DI (plus:DI (mult:DI (match_operand:DI 1 "gr_register_operand" "r")
3737				   (match_operand:DI 2 "shladd_operand" "n"))
3738			  (match_operand:DI 3 "nonmemory_operand" "r"))
3739		 (match_operand:DI 4 "nonmemory_operand" "rI")))]
3740  "reload_in_progress"
3741  "* abort ();"
3742  "reload_completed"
3743  [(set (match_dup 0) (plus:DI (mult:DI (match_dup 1) (match_dup 2))
3744			       (match_dup 3)))
3745   (set (match_dup 0) (plus:DI (match_dup 0) (match_dup 4)))]
3746  ""
3747  [(set_attr "itanium_class" "unknown")])
3748
3749(define_insn "ashrdi3"
3750  [(set (match_operand:DI 0 "gr_register_operand" "=r,r")
3751	(ashiftrt:DI (match_operand:DI 1 "gr_register_operand" "r,r")
3752		     (match_operand:DI 2 "gr_reg_or_6bit_operand" "r,rM")))]
3753  ""
3754  "@
3755   shr %0 = %1, %2
3756   shr %0 = %1, %2"
3757  [(set_attr "itanium_class" "mmshf,mmshfi")])
3758
3759(define_insn "lshrdi3"
3760  [(set (match_operand:DI 0 "gr_register_operand" "=r,r")
3761	(lshiftrt:DI (match_operand:DI 1 "gr_register_operand" "r,r")
3762		     (match_operand:DI 2 "gr_reg_or_6bit_operand" "r,rM")))]
3763  ""
3764  "@
3765   shr.u %0 = %1, %2
3766   shr.u %0 = %1, %2"
3767  [(set_attr "itanium_class" "mmshf,mmshfi")])
3768
3769;; Using a predicate that accepts only constants doesn't work, because optabs
3770;; will load the operand into a register and call the pattern if the predicate
3771;; did not accept it on the first try.  So we use nonmemory_operand and then
3772;; verify that we have an appropriate constant in the expander.
3773
3774(define_expand "rotrdi3"
3775  [(set (match_operand:DI 0 "gr_register_operand" "")
3776	(rotatert:DI (match_operand:DI 1 "gr_register_operand" "")
3777		     (match_operand:DI 2 "nonmemory_operand" "")))]
3778  ""
3779  "
3780{
3781  if (! shift_count_operand (operands[2], DImode))
3782    FAIL;
3783}")
3784
3785(define_insn "*rotrdi3_internal"
3786  [(set (match_operand:DI 0 "gr_register_operand" "=r")
3787	(rotatert:DI (match_operand:DI 1 "gr_register_operand" "r")
3788		     (match_operand:DI 2 "shift_count_operand" "M")))]
3789  ""
3790  "shrp %0 = %1, %1, %2"
3791  [(set_attr "itanium_class" "ishf")])
3792
3793(define_expand "rotldi3"
3794  [(set (match_operand:DI 0 "gr_register_operand" "")
3795	(rotate:DI (match_operand:DI 1 "gr_register_operand" "")
3796		   (match_operand:DI 2 "nonmemory_operand" "")))]
3797  ""
3798  "
3799{
3800  if (! shift_count_operand (operands[2], DImode))
3801    FAIL;
3802}")
3803
3804(define_insn "*rotldi3_internal"
3805  [(set (match_operand:DI 0 "gr_register_operand" "=r")
3806	(rotate:DI (match_operand:DI 1 "gr_register_operand" "r")
3807		   (match_operand:DI 2 "shift_count_operand" "M")))]
3808  ""
3809  "shrp %0 = %1, %1, %e2"
3810  [(set_attr "itanium_class" "ishf")])
3811
3812;; ::::::::::::::::::::
3813;; ::
3814;; :: 32 bit Integer Logical operations
3815;; ::
3816;; ::::::::::::::::::::
3817
3818;; We don't seem to need any other 32-bit logical operations, because gcc
3819;; generates zero-extend;zero-extend;DImode-op, which combine optimizes to
3820;; DImode-op;zero-extend, and then we can optimize away the zero-extend.
3821;; This doesn't work for unary logical operations, because we don't call
3822;; apply_distributive_law for them.
3823
3824;; ??? Likewise, this doesn't work for andnot, which isn't handled by
3825;; apply_distributive_law.  We get inefficient code for
3826;; int sub4 (int i, int j) { return i & ~j; }
3827;; We could convert (and (not (sign_extend A)) (sign_extend B)) to
3828;; (zero_extend (and (not A) B)) in combine.
3829;; Or maybe fix this by adding andsi3/iorsi3/xorsi3 patterns like the
3830;; one_cmplsi2 pattern.
3831
3832(define_insn "one_cmplsi2"
3833  [(set (match_operand:SI 0 "gr_register_operand" "=r")
3834	(not:SI (match_operand:SI 1 "gr_register_operand" "r")))]
3835  ""
3836  "andcm %0 = -1, %1"
3837  [(set_attr "itanium_class" "ilog")])
3838
3839;; ::::::::::::::::::::
3840;; ::
3841;; :: 64 bit Integer Logical operations
3842;; ::
3843;; ::::::::::::::::::::
3844
3845(define_insn "anddi3"
3846  [(set (match_operand:DI 0 "grfr_register_operand" "=r,*f")
3847	(and:DI (match_operand:DI 1 "grfr_register_operand" "%r,*f")
3848		(match_operand:DI 2 "grfr_reg_or_8bit_operand" "rK,*f")))]
3849  ""
3850  "@
3851   and %0 = %2, %1
3852   fand %0 = %2, %1"
3853  [(set_attr "itanium_class" "ilog,fmisc")])
3854
3855(define_insn "*andnot"
3856  [(set (match_operand:DI 0 "grfr_register_operand" "=r,*f")
3857	(and:DI (not:DI (match_operand:DI 1 "grfr_register_operand" "r,*f"))
3858		(match_operand:DI 2 "grfr_reg_or_8bit_operand" "rK,*f")))]
3859  ""
3860  "@
3861   andcm %0 = %2, %1
3862   fandcm %0 = %2, %1"
3863  [(set_attr "itanium_class" "ilog,fmisc")])
3864
3865(define_insn "iordi3"
3866  [(set (match_operand:DI 0 "grfr_register_operand" "=r,*f")
3867	(ior:DI (match_operand:DI 1 "grfr_register_operand" "%r,*f")
3868		(match_operand:DI 2 "grfr_reg_or_8bit_operand" "rK,*f")))]
3869  ""
3870  "@
3871   or %0 = %2, %1
3872   for %0 = %2, %1"
3873  [(set_attr "itanium_class" "ilog,fmisc")])
3874
3875(define_insn "xordi3"
3876  [(set (match_operand:DI 0 "grfr_register_operand" "=r,*f")
3877	(xor:DI (match_operand:DI 1 "grfr_register_operand" "%r,*f")
3878		(match_operand:DI 2 "grfr_reg_or_8bit_operand" "rK,*f")))]
3879  ""
3880  "@
3881   xor %0 = %2, %1
3882   fxor %0 = %2, %1"
3883  [(set_attr "itanium_class" "ilog,fmisc")])
3884
3885(define_insn "one_cmpldi2"
3886  [(set (match_operand:DI 0 "gr_register_operand" "=r")
3887	(not:DI (match_operand:DI 1 "gr_register_operand" "r")))]
3888  ""
3889  "andcm %0 = -1, %1"
3890  [(set_attr "itanium_class" "ilog")])
3891
3892;; ::::::::::::::::::::
3893;; ::
3894;; :: Comparisons
3895;; ::
3896;; ::::::::::::::::::::
3897
3898(define_expand "cmpbi"
3899  [(set (cc0)
3900        (compare (match_operand:BI 0 "register_operand" "")
3901  		 (match_operand:BI 1 "const_int_operand" "")))]
3902  ""
3903  "
3904{
3905  ia64_compare_op0 = operands[0];
3906  ia64_compare_op1 = operands[1];
3907  DONE;
3908}")
3909
3910(define_expand "cmpsi"
3911  [(set (cc0)
3912        (compare (match_operand:SI 0 "gr_register_operand" "")
3913  		 (match_operand:SI 1 "gr_reg_or_8bit_and_adjusted_operand" "")))]
3914  ""
3915  "
3916{
3917  ia64_compare_op0 = operands[0];
3918  ia64_compare_op1 = operands[1];
3919  DONE;
3920}")
3921
3922(define_expand "cmpdi"
3923  [(set (cc0)
3924        (compare (match_operand:DI 0 "gr_register_operand" "")
3925  		 (match_operand:DI 1 "gr_reg_or_8bit_and_adjusted_operand" "")))]
3926  ""
3927  "
3928{
3929  ia64_compare_op0 = operands[0];
3930  ia64_compare_op1 = operands[1];
3931  DONE;
3932}")
3933
3934(define_expand "cmpsf"
3935  [(set (cc0)
3936        (compare (match_operand:SF 0 "fr_reg_or_fp01_operand" "")
3937  		 (match_operand:SF 1 "fr_reg_or_fp01_operand" "")))]
3938  ""
3939  "
3940{
3941  ia64_compare_op0 = operands[0];
3942  ia64_compare_op1 = operands[1];
3943  DONE;
3944}")
3945
3946(define_expand "cmpdf"
3947  [(set (cc0)
3948        (compare (match_operand:DF 0 "fr_reg_or_fp01_operand" "")
3949  		 (match_operand:DF 1 "fr_reg_or_fp01_operand" "")))]
3950  ""
3951  "
3952{
3953  ia64_compare_op0 = operands[0];
3954  ia64_compare_op1 = operands[1];
3955  DONE;
3956}")
3957
3958(define_expand "cmptf"
3959  [(set (cc0)
3960        (compare (match_operand:TF 0 "tfreg_or_fp01_operand" "")
3961  		 (match_operand:TF 1 "tfreg_or_fp01_operand" "")))]
3962  "INTEL_EXTENDED_IEEE_FORMAT"
3963  "
3964{
3965  ia64_compare_op0 = operands[0];
3966  ia64_compare_op1 = operands[1];
3967  DONE;
3968}")
3969
3970(define_insn "*cmpsi_normal"
3971  [(set (match_operand:BI 0 "register_operand" "=c")
3972	(match_operator:BI 1 "normal_comparison_operator"
3973	   [(match_operand:SI 2 "gr_register_operand" "r")
3974	    (match_operand:SI 3 "gr_reg_or_8bit_operand" "rK")]))]
3975  ""
3976  "cmp4.%C1 %0, %I0 = %3, %2"
3977  [(set_attr "itanium_class" "icmp")])
3978
3979;; We use %r3 because it is possible for us to match a 0, and two of the
3980;; unsigned comparisons don't accept immediate operands of zero.
3981
3982(define_insn "*cmpsi_adjusted"
3983  [(set (match_operand:BI 0 "register_operand" "=c")
3984	(match_operator:BI 1 "adjusted_comparison_operator"
3985	   [(match_operand:SI 2 "gr_register_operand" "r")
3986	    (match_operand:SI 3 "gr_reg_or_8bit_adjusted_operand" "rL")]))]
3987  ""
3988  "cmp4.%C1 %0, %I0 = %r3, %2"
3989  [(set_attr "itanium_class" "icmp")])
3990
3991(define_insn "*cmpdi_normal"
3992  [(set (match_operand:BI 0 "register_operand" "=c")
3993	(match_operator:BI 1 "normal_comparison_operator"
3994	   [(match_operand:DI 2 "gr_reg_or_0_operand" "rO")
3995	    (match_operand:DI 3 "gr_reg_or_8bit_operand" "rK")]))]
3996  ""
3997  "cmp.%C1 %0, %I0 = %3, %r2"
3998  [(set_attr "itanium_class" "icmp")])
3999
4000;; We use %r3 because it is possible for us to match a 0, and two of the
4001;; unsigned comparisons don't accept immediate operands of zero.
4002
4003(define_insn "*cmpdi_adjusted"
4004  [(set (match_operand:BI 0 "register_operand" "=c")
4005	(match_operator:BI 1 "adjusted_comparison_operator"
4006	   [(match_operand:DI 2 "gr_register_operand" "r")
4007	    (match_operand:DI 3 "gr_reg_or_8bit_adjusted_operand" "rL")]))]
4008  ""
4009  "cmp.%C1 %0, %I0 = %r3, %2"
4010  [(set_attr "itanium_class" "icmp")])
4011
4012(define_insn "*cmpsf_internal"
4013  [(set (match_operand:BI 0 "register_operand" "=c")
4014	(match_operator:BI 1 "comparison_operator"
4015	   [(match_operand:SF 2 "fr_reg_or_fp01_operand" "fG")
4016	    (match_operand:SF 3 "fr_reg_or_fp01_operand" "fG")]))]
4017  ""
4018  "fcmp.%D1 %0, %I0 = %F2, %F3"
4019  [(set_attr "itanium_class" "fcmp")])
4020
4021(define_insn "*cmpdf_internal"
4022  [(set (match_operand:BI 0 "register_operand" "=c")
4023	(match_operator:BI 1 "comparison_operator"
4024	   [(match_operand:DF 2 "fr_reg_or_fp01_operand" "fG")
4025	    (match_operand:DF 3 "fr_reg_or_fp01_operand" "fG")]))]
4026  ""
4027  "fcmp.%D1 %0, %I0 = %F2, %F3"
4028  [(set_attr "itanium_class" "fcmp")])
4029
4030(define_insn "*cmptf_internal"
4031  [(set (match_operand:BI 0 "register_operand" "=c")
4032	(match_operator:BI 1 "comparison_operator"
4033		   [(match_operand:TF 2 "tfreg_or_fp01_operand" "fG")
4034		    (match_operand:TF 3 "tfreg_or_fp01_operand" "fG")]))]
4035  "INTEL_EXTENDED_IEEE_FORMAT"
4036  "fcmp.%D1 %0, %I0 = %F2, %F3"
4037  [(set_attr "itanium_class" "fcmp")])
4038
4039;; ??? Can this pattern be generated?
4040
4041(define_insn "*bit_zero"
4042  [(set (match_operand:BI 0 "register_operand" "=c")
4043	(eq:BI (zero_extract:DI (match_operand:DI 1 "gr_register_operand" "r")
4044				(const_int 1)
4045				(match_operand:DI 2 "immediate_operand" "n"))
4046	       (const_int 0)))]
4047  ""
4048  "tbit.z %0, %I0 = %1, %2"
4049  [(set_attr "itanium_class" "tbit")])
4050
4051(define_insn "*bit_one"
4052  [(set (match_operand:BI 0 "register_operand" "=c")
4053	(ne:BI (zero_extract:DI (match_operand:DI 1 "gr_register_operand" "r")
4054				(const_int 1)
4055				(match_operand:DI 2 "immediate_operand" "n"))
4056	       (const_int 0)))]
4057  ""
4058  "tbit.nz %0, %I0 = %1, %2"
4059  [(set_attr "itanium_class" "tbit")])
4060
4061;; ::::::::::::::::::::
4062;; ::
4063;; :: Branches
4064;; ::
4065;; ::::::::::::::::::::
4066
4067(define_expand "beq"
4068  [(set (pc)
4069	(if_then_else (match_dup 1)
4070		      (label_ref (match_operand 0 "" ""))
4071		      (pc)))]
4072  ""
4073  "operands[1] = ia64_expand_compare (EQ, VOIDmode);")
4074
4075(define_expand "bne"
4076  [(set (pc)
4077	(if_then_else (match_dup 1)
4078		      (label_ref (match_operand 0 "" ""))
4079		      (pc)))]
4080  ""
4081  "operands[1] = ia64_expand_compare (NE, VOIDmode);")
4082
4083(define_expand "blt"
4084  [(set (pc)
4085	(if_then_else (match_dup 1)
4086		      (label_ref (match_operand 0 "" ""))
4087		      (pc)))]
4088  ""
4089  "operands[1] = ia64_expand_compare (LT, VOIDmode);")
4090
4091(define_expand "ble"
4092  [(set (pc)
4093	(if_then_else (match_dup 1)
4094		      (label_ref (match_operand 0 "" ""))
4095		      (pc)))]
4096  ""
4097  "operands[1] = ia64_expand_compare (LE, VOIDmode);")
4098
4099(define_expand "bgt"
4100  [(set (pc)
4101	(if_then_else (match_dup 1)
4102		      (label_ref (match_operand 0 "" ""))
4103		      (pc)))]
4104  ""
4105  "operands[1] = ia64_expand_compare (GT, VOIDmode);")
4106
4107(define_expand "bge"
4108  [(set (pc)
4109	(if_then_else (match_dup 1)
4110		      (label_ref (match_operand 0 "" ""))
4111		      (pc)))]
4112  ""
4113  "operands[1] = ia64_expand_compare (GE, VOIDmode);")
4114
4115(define_expand "bltu"
4116  [(set (pc)
4117	(if_then_else (match_dup 1)
4118		      (label_ref (match_operand 0 "" ""))
4119		      (pc)))]
4120  ""
4121  "operands[1] = ia64_expand_compare (LTU, VOIDmode);")
4122
4123(define_expand "bleu"
4124  [(set (pc)
4125	(if_then_else (match_dup 1)
4126		      (label_ref (match_operand 0 "" ""))
4127		      (pc)))]
4128  ""
4129  "operands[1] = ia64_expand_compare (LEU, VOIDmode);")
4130
4131(define_expand "bgtu"
4132  [(set (pc)
4133	(if_then_else (match_dup 1)
4134		      (label_ref (match_operand 0 "" ""))
4135		      (pc)))]
4136  ""
4137  "operands[1] = ia64_expand_compare (GTU, VOIDmode);")
4138
4139(define_expand "bgeu"
4140  [(set (pc)
4141	(if_then_else (match_dup 1)
4142		      (label_ref (match_operand 0 "" ""))
4143		      (pc)))]
4144  ""
4145  "operands[1] = ia64_expand_compare (GEU, VOIDmode);")
4146
4147(define_expand "bunordered"
4148  [(set (pc)
4149	(if_then_else (match_dup 1)
4150		      (label_ref (match_operand 0 "" ""))
4151		      (pc)))]
4152  ""
4153  "operands[1] = ia64_expand_compare (UNORDERED, VOIDmode);")
4154
4155(define_expand "bordered"
4156  [(set (pc)
4157	(if_then_else (match_dup 1)
4158		      (label_ref (match_operand 0 "" ""))
4159		      (pc)))]
4160  ""
4161  "operands[1] = ia64_expand_compare (ORDERED, VOIDmode);")
4162
4163(define_insn "*br_true"
4164  [(set (pc)
4165	(if_then_else (match_operator 0 "predicate_operator"
4166			[(match_operand:BI 1 "register_operand" "c")
4167			 (const_int 0)])
4168		      (label_ref (match_operand 2 "" ""))
4169		      (pc)))]
4170  ""
4171  "(%J0) br.cond%+ %l2"
4172  [(set_attr "itanium_class" "br")
4173   (set_attr "predicable" "no")])
4174
4175(define_insn "*br_false"
4176  [(set (pc)
4177	(if_then_else (match_operator 0 "predicate_operator"
4178			[(match_operand:BI 1 "register_operand" "c")
4179			 (const_int 0)])
4180		      (pc)
4181		      (label_ref (match_operand 2 "" ""))))]
4182  ""
4183  "(%j0) br.cond%+ %l2"
4184  [(set_attr "itanium_class" "br")
4185   (set_attr "predicable" "no")])
4186
4187;; ::::::::::::::::::::
4188;; ::
4189;; :: Counted loop operations
4190;; ::
4191;; ::::::::::::::::::::
4192
4193(define_expand "doloop_end"
4194  [(use (match_operand 0 "" ""))	; loop pseudo
4195   (use (match_operand 1 "" ""))	; iterations; zero if unknown
4196   (use (match_operand 2 "" ""))	; max iterations
4197   (use (match_operand 3 "" ""))	; loop level
4198   (use (match_operand 4 "" ""))]	; label
4199  ""
4200  "
4201{
4202  /* Only use cloop on innermost loops.  */
4203  if (INTVAL (operands[3]) > 1)
4204    FAIL;
4205  emit_jump_insn (gen_doloop_end_internal (gen_rtx_REG (DImode, AR_LC_REGNUM),
4206					   operands[4]));
4207  DONE;
4208}")
4209
4210(define_insn "doloop_end_internal"
4211  [(set (pc) (if_then_else (ne (match_operand:DI 0 "ar_lc_reg_operand" "")
4212			       (const_int 0))
4213		(label_ref (match_operand 1 "" ""))
4214		(pc)))
4215   (set (match_dup 0) (if_then_else:DI (ne (match_dup 0) (const_int 0))
4216			 (match_dup 0)
4217			 (plus:DI (match_dup 0) (const_int -1))))]
4218  ""
4219  "br.cloop.sptk.few %l1"
4220  [(set_attr "itanium_class" "br")
4221   (set_attr "predicable" "no")])
4222
4223;; ::::::::::::::::::::
4224;; ::
4225;; :: Set flag operations
4226;; ::
4227;; ::::::::::::::::::::
4228
4229(define_expand "seq"
4230  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4231  ""
4232  "operands[1] = ia64_expand_compare (EQ, DImode);")
4233
4234(define_expand "sne"
4235  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4236  ""
4237  "operands[1] = ia64_expand_compare (NE, DImode);")
4238
4239(define_expand "slt"
4240  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4241  ""
4242  "operands[1] = ia64_expand_compare (LT, DImode);")
4243
4244(define_expand "sle"
4245  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4246  ""
4247  "operands[1] = ia64_expand_compare (LE, DImode);")
4248
4249(define_expand "sgt"
4250  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4251  ""
4252  "operands[1] = ia64_expand_compare (GT, DImode);")
4253
4254(define_expand "sge"
4255  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4256  ""
4257  "operands[1] = ia64_expand_compare (GE, DImode);")
4258
4259(define_expand "sltu"
4260  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4261  ""
4262  "operands[1] = ia64_expand_compare (LTU, DImode);")
4263
4264(define_expand "sleu"
4265  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4266  ""
4267  "operands[1] = ia64_expand_compare (LEU, DImode);")
4268
4269(define_expand "sgtu"
4270  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4271  ""
4272  "operands[1] = ia64_expand_compare (GTU, DImode);")
4273
4274(define_expand "sgeu"
4275  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4276  ""
4277  "operands[1] = ia64_expand_compare (GEU, DImode);")
4278
4279(define_expand "sunordered"
4280  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4281  ""
4282  "operands[1] = ia64_expand_compare (UNORDERED, DImode);")
4283
4284(define_expand "sordered"
4285  [(set (match_operand:DI 0 "gr_register_operand" "") (match_dup 1))]
4286  ""
4287  "operands[1] = ia64_expand_compare (ORDERED, DImode);")
4288
4289;; Don't allow memory as destination here, because cmov/cmov/st is more
4290;; efficient than mov/mov/cst/cst.
4291
4292(define_insn_and_split "*sne_internal"
4293  [(set (match_operand:DI 0 "gr_register_operand" "=r")
4294	(ne:DI (match_operand:BI 1 "register_operand" "c")
4295	       (const_int 0)))]
4296  ""
4297  "#"
4298  "reload_completed"
4299  [(cond_exec (ne (match_dup 1) (const_int 0))
4300     (set (match_dup 0) (const_int 1)))
4301   (cond_exec (eq (match_dup 1) (const_int 0))
4302     (set (match_dup 0) (const_int 0)))]
4303  ""
4304  [(set_attr "itanium_class" "unknown")])
4305
4306(define_insn_and_split "*seq_internal"
4307  [(set (match_operand:DI 0 "gr_register_operand" "=r")
4308	(eq:DI (match_operand:BI 1 "register_operand" "c")
4309	       (const_int 0)))]
4310  ""
4311  "#"
4312  "reload_completed"
4313  [(cond_exec (ne (match_dup 1) (const_int 0))
4314     (set (match_dup 0) (const_int 0)))
4315   (cond_exec (eq (match_dup 1) (const_int 0))
4316     (set (match_dup 0) (const_int 1)))]
4317  ""
4318  [(set_attr "itanium_class" "unknown")])
4319
4320;; ::::::::::::::::::::
4321;; ::
4322;; :: Conditional move instructions.
4323;; ::
4324;; ::::::::::::::::::::
4325
4326;; ??? Add movXXcc patterns?
4327
4328;;
4329;; DImode if_then_else patterns.
4330;;
4331
4332(define_insn "*cmovdi_internal"
4333  [(set (match_operand:DI 0 "destination_operand"
4334	   "= r,  r,  r,   r,  r,  r,   r, r, r,   r, m, Q, *f,*b,*d*e")
4335	(if_then_else:DI
4336	  (match_operator 4 "predicate_operator"
4337	    [(match_operand:BI 1 "register_operand"
4338		"c,c,c,c,c,c,c,c,c,c,c,c,c,c,c")
4339	     (const_int 0)])
4340	  (match_operand:DI 2 "move_operand"
4341	   "rim, *f, *b,*d*e,rim,rim, rim,*f,*b,*d*e,rO,*f,rOQ,rO,  rK")
4342	  (match_operand:DI 3 "move_operand"
4343	   "rim,rim,rim, rim, *f, *b,*d*e,*f,*b,*d*e,rO,*f,rOQ,rO,  rK")))]
4344  "ia64_move_ok (operands[0], operands[2])
4345   && ia64_move_ok (operands[0], operands[3])"
4346  "* abort ();"
4347  [(set_attr "predicable" "no")])
4348
4349(define_split
4350  [(set (match_operand 0 "destination_operand" "")
4351	(if_then_else
4352	  (match_operator 4 "predicate_operator"
4353	    [(match_operand:BI 1 "register_operand" "")
4354	     (const_int 0)])
4355	  (match_operand 2 "move_operand" "")
4356	  (match_operand 3 "move_operand" "")))]
4357  "reload_completed"
4358  [(const_int 0)]
4359  "
4360{
4361  rtx tmp;
4362  if (! rtx_equal_p (operands[0], operands[2]))
4363    {
4364      tmp = gen_rtx_SET (VOIDmode, operands[0], operands[2]);
4365      tmp = gen_rtx_COND_EXEC (VOIDmode, operands[4], tmp);
4366      emit_insn (tmp);
4367    }
4368  if (! rtx_equal_p (operands[0], operands[3]))
4369    {
4370      tmp = gen_rtx_fmt_ee (GET_CODE (operands[4]) == NE ? EQ : NE,
4371			    VOIDmode, operands[1], const0_rtx);
4372      tmp = gen_rtx_COND_EXEC (VOIDmode, tmp,
4373			       gen_rtx_SET (VOIDmode, operands[0],
4374					    operands[3]));
4375      emit_insn (tmp);
4376    }
4377  DONE;
4378}")
4379
4380;; Absolute value pattern.
4381
4382(define_insn "*absdi2_internal"
4383  [(set (match_operand:DI 0 "gr_register_operand" "=r,r")
4384	(if_then_else:DI
4385	  (match_operator 4 "predicate_operator"
4386	    [(match_operand:BI 1 "register_operand" "c,c")
4387	     (const_int 0)])
4388	  (neg:DI (match_operand:DI 2 "gr_reg_or_22bit_operand" "rI,rI"))
4389	  (match_operand:DI 3 "gr_reg_or_22bit_operand" "0,rI")))]
4390  ""
4391  "#"
4392  [(set_attr "itanium_class" "ialu,unknown")
4393   (set_attr "predicable" "no")])
4394
4395(define_split
4396  [(set (match_operand:DI 0 "register_operand" "")
4397	(if_then_else:DI
4398	  (match_operator 4 "predicate_operator"
4399	    [(match_operand:BI 1 "register_operand" "c,c")
4400	     (const_int 0)])
4401	  (neg:DI (match_operand:DI 2 "gr_reg_or_22bit_operand" ""))
4402	  (match_operand:DI 3 "gr_reg_or_22bit_operand" "")))]
4403  "reload_completed && rtx_equal_p (operands[0], operands[3])"
4404  [(cond_exec
4405     (match_dup 4)
4406     (set (match_dup 0)
4407	  (neg:DI (match_dup 2))))]
4408  "")
4409
4410(define_split
4411  [(set (match_operand:DI 0 "register_operand" "")
4412	(if_then_else:DI
4413	  (match_operator 4 "predicate_operator"
4414	    [(match_operand:BI 1 "register_operand" "c,c")
4415	     (const_int 0)])
4416	  (neg:DI (match_operand:DI 2 "gr_reg_or_22bit_operand" ""))
4417	  (match_operand:DI 3 "gr_reg_or_22bit_operand" "")))]
4418  "reload_completed"
4419  [(cond_exec
4420     (match_dup 4)
4421     (set (match_dup 0) (neg:DI (match_dup 2))))
4422   (cond_exec
4423     (match_dup 5)
4424     (set (match_dup 0) (match_dup 3)))]
4425  "
4426{
4427  operands[5] = gen_rtx_fmt_ee (GET_CODE (operands[4]) == NE ? EQ : NE,
4428				VOIDmode, operands[1], const0_rtx);
4429}")
4430
4431;;
4432;; SImode if_then_else patterns.
4433;;
4434
4435(define_insn "*cmovsi_internal"
4436  [(set (match_operand:SI 0 "destination_operand" "=r,m,*f,r,m,*f,r,m,*f")
4437	(if_then_else:SI
4438	  (match_operator 4 "predicate_operator"
4439	    [(match_operand:BI 1 "register_operand" "c,c,c,c,c,c,c,c,c")
4440	     (const_int 0)])
4441	  (match_operand:SI 2 "move_operand"
4442		    "0,0,0,rim*f,rO,rO,rim*f,rO,rO")
4443	  (match_operand:SI 3 "move_operand"
4444		    "rim*f,rO,rO,0,0,0,rim*f,rO,rO")))]
4445  "ia64_move_ok (operands[0], operands[2])
4446   && ia64_move_ok (operands[0], operands[3])"
4447  "* abort ();"
4448  [(set_attr "predicable" "no")])
4449
4450(define_insn "*abssi2_internal"
4451  [(set (match_operand:SI 0 "gr_register_operand" "=r,r")
4452	(if_then_else:SI
4453	  (match_operator 4 "predicate_operator"
4454	    [(match_operand:BI 1 "register_operand" "c,c")
4455	     (const_int 0)])
4456	  (neg:SI (match_operand:SI 3 "gr_reg_or_22bit_operand" "rI,rI"))
4457	  (match_operand:SI 2 "gr_reg_or_22bit_operand" "0,rI")))]
4458  ""
4459  "#"
4460  [(set_attr "itanium_class" "ialu,unknown")
4461   (set_attr "predicable" "no")])
4462
4463(define_split
4464  [(set (match_operand:SI 0 "register_operand" "")
4465	(if_then_else:SI
4466	  (match_operator 4 "predicate_operator"
4467	    [(match_operand:BI 1 "register_operand" "c,c")
4468	     (const_int 0)])
4469	  (neg:SI (match_operand:SI 2 "gr_reg_or_22bit_operand" ""))
4470	  (match_operand:SI 3 "gr_reg_or_22bit_operand" "")))]
4471  "reload_completed && rtx_equal_p (operands[0], operands[3])"
4472  [(cond_exec
4473     (match_dup 4)
4474     (set (match_dup 0)
4475	  (neg:SI (match_dup 2))))]
4476  "")
4477
4478(define_split
4479  [(set (match_operand:SI 0 "register_operand" "")
4480	(if_then_else:SI
4481	  (match_operator 4 "predicate_operator"
4482	    [(match_operand:BI 1 "register_operand" "c,c")
4483	     (const_int 0)])
4484	  (neg:SI (match_operand:SI 2 "gr_reg_or_22bit_operand" ""))
4485	  (match_operand:SI 3 "gr_reg_or_22bit_operand" "")))]
4486  "reload_completed"
4487  [(cond_exec
4488     (match_dup 4)
4489     (set (match_dup 0) (neg:SI (match_dup 2))))
4490   (cond_exec
4491     (match_dup 5)
4492     (set (match_dup 0) (match_dup 3)))]
4493  "
4494{
4495  operands[5] = gen_rtx_fmt_ee (GET_CODE (operands[4]) == NE ? EQ : NE,
4496				VOIDmode, operands[1], const0_rtx);
4497}")
4498
4499(define_insn_and_split "*cond_opsi2_internal"
4500  [(set (match_operand:SI 0 "gr_register_operand" "=r")
4501	(match_operator:SI 5 "condop_operator"
4502	  [(if_then_else:SI
4503	     (match_operator 6 "predicate_operator"
4504	       [(match_operand:BI 1 "register_operand" "c")
4505	        (const_int 0)])
4506	     (match_operand:SI 2 "gr_register_operand" "r")
4507	     (match_operand:SI 3 "gr_register_operand" "r"))
4508	   (match_operand:SI 4 "gr_register_operand" "r")]))]
4509  ""
4510  "#"
4511  "reload_completed"
4512  [(cond_exec
4513     (match_dup 6)
4514     (set (match_dup 0) (match_op_dup:SI 5 [(match_dup 2) (match_dup 4)])))
4515   (cond_exec
4516     (match_dup 7)
4517     (set (match_dup 0) (match_op_dup:SI 5 [(match_dup 3) (match_dup 4)])))]
4518  "
4519{
4520  operands[7] = gen_rtx_fmt_ee (GET_CODE (operands[6]) == NE ? EQ : NE,
4521				VOIDmode, operands[1], const0_rtx);
4522}"
4523  [(set_attr "itanium_class" "ialu")
4524   (set_attr "predicable" "no")])
4525
4526
4527(define_insn_and_split "*cond_opsi2_internal_b"
4528  [(set (match_operand:SI 0 "gr_register_operand" "=r")
4529	(match_operator:SI 5 "condop_operator"
4530	  [(match_operand:SI 4 "gr_register_operand" "r")
4531	   (if_then_else:SI
4532	     (match_operator 6 "predicate_operator"
4533	       [(match_operand:BI 1 "register_operand" "c")
4534	        (const_int 0)])
4535	     (match_operand:SI 2 "gr_register_operand" "r")
4536	     (match_operand:SI 3 "gr_register_operand" "r"))]))]
4537  ""
4538  "#"
4539  "reload_completed"
4540  [(cond_exec
4541     (match_dup 6)
4542     (set (match_dup 0) (match_op_dup:SI 5 [(match_dup 4) (match_dup 2)])))
4543   (cond_exec
4544     (match_dup 7)
4545     (set (match_dup 0) (match_op_dup:SI 5 [(match_dup 4) (match_dup 3)])))]
4546  "
4547{
4548  operands[7] = gen_rtx_fmt_ee (GET_CODE (operands[6]) == NE ? EQ : NE,
4549				VOIDmode, operands[1], const0_rtx);
4550}"
4551  [(set_attr "itanium_class" "ialu")
4552   (set_attr "predicable" "no")])
4553
4554
4555;; ::::::::::::::::::::
4556;; ::
4557;; :: Call and branch instructions
4558;; ::
4559;; ::::::::::::::::::::
4560
4561;; Subroutine call instruction returning no value.  Operand 0 is the function
4562;; to call; operand 1 is the number of bytes of arguments pushed (in mode
4563;; `SImode', except it is normally a `const_int'); operand 2 is the number of
4564;; registers used as operands.
4565
4566;; On most machines, operand 2 is not actually stored into the RTL pattern.  It
4567;; is supplied for the sake of some RISC machines which need to put this
4568;; information into the assembler code; they can put it in the RTL instead of
4569;; operand 1.
4570
4571(define_expand "call"
4572  [(use (match_operand:DI 0 "" ""))
4573   (use (match_operand 1 "" ""))
4574   (use (match_operand 2 "" ""))
4575   (use (match_operand 3 "" ""))]
4576  ""
4577  "
4578{
4579  ia64_expand_call (NULL_RTX, operands[0], operands[2], 0);
4580  DONE;
4581}")
4582
4583(define_expand "sibcall"
4584  [(use (match_operand:DI 0 "" ""))
4585   (use (match_operand 1 "" ""))
4586   (use (match_operand 2 "" ""))
4587   (use (match_operand 3 "" ""))]
4588  ""
4589  "
4590{
4591  ia64_expand_call (NULL_RTX, operands[0], operands[2], 1);
4592  DONE;
4593}")
4594
4595;; Subroutine call instruction returning a value.  Operand 0 is the hard
4596;; register in which the value is returned.  There are three more operands,
4597;; the same as the three operands of the `call' instruction (but with numbers
4598;; increased by one).
4599;;
4600;; Subroutines that return `BLKmode' objects use the `call' insn.
4601
4602(define_expand "call_value"
4603  [(use (match_operand 0 "" ""))
4604   (use (match_operand:DI 1 "" ""))
4605   (use (match_operand 2 "" ""))
4606   (use (match_operand 3 "" ""))
4607   (use (match_operand 4 "" ""))]
4608  ""
4609  "
4610{
4611  ia64_expand_call (operands[0], operands[1], operands[3], 0);
4612  DONE;
4613}")
4614
4615(define_expand "sibcall_value"
4616  [(use (match_operand 0 "" ""))
4617   (use (match_operand:DI 1 "" ""))
4618   (use (match_operand 2 "" ""))
4619   (use (match_operand 3 "" ""))
4620   (use (match_operand 4 "" ""))]
4621  ""
4622  "
4623{
4624  ia64_expand_call (operands[0], operands[1], operands[3], 1);
4625  DONE;
4626}")
4627
4628;; Call subroutine returning any type.
4629
4630(define_expand "untyped_call"
4631  [(parallel [(call (match_operand 0 "" "")
4632		    (const_int 0))
4633	      (match_operand 1 "" "")
4634	      (match_operand 2 "" "")])]
4635  ""
4636  "
4637{
4638  int i;
4639
4640  emit_call_insn (gen_call (operands[0], const0_rtx, NULL, const0_rtx));
4641
4642  for (i = 0; i < XVECLEN (operands[2], 0); i++)
4643    {
4644      rtx set = XVECEXP (operands[2], 0, i);
4645      emit_move_insn (SET_DEST (set), SET_SRC (set));
4646    }
4647
4648  /* The optimizer does not know that the call sets the function value
4649     registers we stored in the result block.  We avoid problems by
4650     claiming that all hard registers are used and clobbered at this
4651     point.  */
4652  emit_insn (gen_blockage ());
4653
4654  DONE;
4655}")
4656
4657(define_insn "call_nopic"
4658  [(call (mem:DI (match_operand:DI 0 "call_operand" "b,i"))
4659	 (match_operand 1 "" ""))
4660   (clobber (match_operand:DI 2 "register_operand" "=b,b"))]
4661  ""
4662  "br.call%+.many %2 = %0"
4663  [(set_attr "itanium_class" "br,scall")])
4664
4665(define_insn "call_value_nopic"
4666  [(set (match_operand 0 "" "")
4667	(call (mem:DI (match_operand:DI 1 "call_operand" "b,i"))
4668	      (match_operand 2 "" "")))
4669   (clobber (match_operand:DI 3 "register_operand" "=b,b"))]
4670  ""
4671  "br.call%+.many %3 = %1"
4672  [(set_attr "itanium_class" "br,scall")])
4673
4674(define_insn "sibcall_nopic"
4675  [(call (mem:DI (match_operand:DI 0 "call_operand" "b,i"))
4676	 (match_operand 1 "" ""))
4677   (use (match_operand:DI 2 "register_operand" "=b,b"))
4678   (use (match_operand:DI 3 "ar_pfs_reg_operand" ""))]
4679  ""
4680  "br%+.many %0"
4681  [(set_attr "itanium_class" "br,scall")])
4682
4683(define_insn "call_pic"
4684  [(call (mem:DI (match_operand:DI 0 "call_operand" "b,i"))
4685	 (match_operand 1 "" ""))
4686   (use (unspec [(reg:DI 1)] 9))
4687   (clobber (match_operand:DI 2 "register_operand" "=b,b"))]
4688  ""
4689  "br.call%+.many %2 = %0"
4690  [(set_attr "itanium_class" "br,scall")])
4691
4692(define_insn "call_value_pic"
4693  [(set (match_operand 0 "" "")
4694	(call (mem:DI (match_operand:DI 1 "call_operand" "b,i"))
4695	      (match_operand 2 "" "")))
4696   (use (unspec [(reg:DI 1)] 9))
4697   (clobber (match_operand:DI 3 "register_operand" "=b,b"))]
4698  ""
4699  "br.call%+.many %3 = %1"
4700  [(set_attr "itanium_class" "br,scall")])
4701
4702(define_insn "sibcall_pic"
4703  [(call (mem:DI (match_operand:DI 0 "call_operand" "bi"))
4704	 (match_operand 1 "" ""))
4705   (use (unspec [(reg:DI 1)] 9))
4706   (use (match_operand:DI 2 "register_operand" "=b"))
4707   (use (match_operand:DI 3 "ar_pfs_reg_operand" ""))]
4708  ""
4709  "br%+.many %0"
4710  [(set_attr "itanium_class" "br")])
4711
4712(define_insn "return_internal"
4713  [(return)
4714   (use (match_operand:DI 0 "register_operand" "b"))]
4715  ""
4716  "br.ret.sptk.many %0"
4717  [(set_attr "itanium_class" "br")])
4718
4719(define_insn "return"
4720  [(return)]
4721  "ia64_direct_return ()"
4722  "br.ret.sptk.many rp"
4723  [(set_attr "itanium_class" "br")])
4724
4725(define_insn "*return_true"
4726  [(set (pc)
4727	(if_then_else (match_operator 0 "predicate_operator"
4728			[(match_operand:BI 1 "register_operand" "c")
4729			 (const_int 0)])
4730		      (return)
4731		      (pc)))]
4732  "ia64_direct_return ()"
4733  "(%J0) br.ret%+.many rp"
4734  [(set_attr "itanium_class" "br")
4735   (set_attr "predicable" "no")])
4736
4737(define_insn "*return_false"
4738  [(set (pc)
4739	(if_then_else (match_operator 0 "predicate_operator"
4740			[(match_operand:BI 1 "register_operand" "c")
4741			 (const_int 0)])
4742		      (pc)
4743		      (return)))]
4744  "ia64_direct_return ()"
4745  "(%j0) br.ret%+.many rp"
4746  [(set_attr "itanium_class" "br")
4747   (set_attr "predicable" "no")])
4748
4749(define_insn "jump"
4750  [(set (pc) (label_ref (match_operand 0 "" "")))]
4751  ""
4752  "br %l0"
4753  [(set_attr "itanium_class" "br")])
4754
4755(define_insn "indirect_jump"
4756  [(set (pc) (match_operand:DI 0 "register_operand" "b"))]
4757  ""
4758  "br %0"
4759  [(set_attr "itanium_class" "br")])
4760
4761(define_expand "tablejump"
4762  [(parallel [(set (pc) (match_operand:DI 0 "memory_operand" ""))
4763	      (use (label_ref (match_operand 1 "" "")))])]
4764  ""
4765{
4766  rtx op0 = operands[0];
4767  rtx addr;
4768
4769  /* ??? Bother -- do_tablejump is "helpful" and pulls the table
4770     element into a register without bothering to see whether that
4771     is necessary given the operand predicate.  Check for MEM just
4772     in case someone fixes this.  */
4773  if (GET_CODE (op0) == MEM)
4774    addr = XEXP (op0, 0);
4775  else
4776    {
4777      /* Otherwise, cheat and guess that the previous insn in the
4778	 stream was the memory load.  Grab the address from that.
4779	 Note we have to momentarily pop out of the sequence started
4780	 by the insn-emit wrapper in order to grab the last insn.  */
4781      rtx last, set;
4782
4783      end_sequence ();
4784      last = get_last_insn ();
4785      start_sequence ();
4786      set = single_set (last);
4787
4788      if (! rtx_equal_p (SET_DEST (set), op0)
4789	  || GET_CODE (SET_SRC (set)) != MEM)
4790	abort ();
4791      addr = XEXP (SET_SRC (set), 0);
4792      if (rtx_equal_p (addr, op0))
4793	abort ();
4794    }
4795
4796  /* Jump table elements are stored pc-relative.  That is, a displacement
4797     from the entry to the label.  Thus to convert to an absolute address
4798     we add the address of the memory from which the value is loaded.  */
4799  operands[0] = expand_simple_binop (DImode, PLUS, op0, addr,
4800				     NULL_RTX, 1, OPTAB_DIRECT);
4801})
4802
4803(define_insn "*tablejump_internal"
4804  [(set (pc) (match_operand:DI 0 "register_operand" "b"))
4805   (use (label_ref (match_operand 1 "" "")))]
4806  ""
4807  "br %0"
4808  [(set_attr "itanium_class" "br")])
4809
4810
4811;; ::::::::::::::::::::
4812;; ::
4813;; :: Prologue and Epilogue instructions
4814;; ::
4815;; ::::::::::::::::::::
4816
4817(define_expand "prologue"
4818  [(const_int 1)]
4819  ""
4820  "
4821{
4822  ia64_expand_prologue ();
4823  DONE;
4824}")
4825
4826(define_expand "epilogue"
4827  [(return)]
4828  ""
4829  "
4830{
4831  ia64_expand_epilogue (0);
4832  DONE;
4833}")
4834
4835(define_expand "sibcall_epilogue"
4836  [(return)]
4837  ""
4838  "
4839{
4840  ia64_expand_epilogue (1);
4841  DONE;
4842}")
4843
4844;; This prevents the scheduler from moving the SP decrement past FP-relative
4845;; stack accesses.  This is the same as adddi3 plus the extra set.
4846
4847(define_insn "prologue_allocate_stack"
4848  [(set (match_operand:DI 0 "register_operand" "=r,r,r")
4849	(plus:DI (match_operand:DI 1 "register_operand" "%r,r,a")
4850		 (match_operand:DI 2 "gr_reg_or_22bit_operand" "r,I,J")))
4851   (set (match_operand:DI 3 "register_operand" "+r,r,r")
4852	(match_dup 3))]
4853  ""
4854  "@
4855  add %0 = %1, %2
4856  adds %0 = %2, %1
4857  addl %0 = %2, %1"
4858  [(set_attr "itanium_class" "ialu")])
4859
4860;; This prevents the scheduler from moving the SP restore past FP-relative
4861;; stack accesses.  This is similar to movdi plus the extra set.
4862
4863(define_insn "epilogue_deallocate_stack"
4864  [(set (match_operand:DI 0 "register_operand" "=r")
4865	(match_operand:DI 1 "register_operand" "+r"))
4866   (set (match_dup 1) (match_dup 1))]
4867  ""
4868  "mov %0 = %1"
4869  [(set_attr "itanium_class" "ialu")])
4870
4871;; Allocate a new register frame.
4872
4873(define_insn "alloc"
4874  [(set (match_operand:DI 0 "register_operand" "=r")
4875	(unspec_volatile:DI [(const_int 0)] 0))
4876   (use (match_operand:DI 1 "const_int_operand" "i"))
4877   (use (match_operand:DI 2 "const_int_operand" "i"))
4878   (use (match_operand:DI 3 "const_int_operand" "i"))
4879   (use (match_operand:DI 4 "const_int_operand" "i"))]
4880  ""
4881  "alloc %0 = ar.pfs, %1, %2, %3, %4"
4882  [(set_attr "itanium_class" "syst_m0")
4883   (set_attr "predicable" "no")])
4884
4885;; Modifies ar.unat
4886(define_expand "gr_spill"
4887  [(parallel [(set (match_operand:DI 0 "memory_operand" "=m")
4888		   (unspec:DI [(match_operand:DI 1 "register_operand" "r")
4889			       (match_operand:DI 2 "const_int_operand" "")] 1))
4890	      (clobber (match_dup 3))])]
4891  ""
4892  "operands[3] = gen_rtx_REG (DImode, AR_UNAT_REGNUM);")
4893
4894(define_insn "gr_spill_internal"
4895  [(set (match_operand:DI 0 "memory_operand" "=m")
4896	(unspec:DI [(match_operand:DI 1 "register_operand" "r")
4897		    (match_operand:DI 2 "const_int_operand" "")] 1))
4898   (clobber (match_operand:DI 3 "register_operand" ""))]
4899  ""
4900  "*
4901{
4902  return \".mem.offset %2, 0\;%,st8.spill %0 = %1%P0\";
4903}"
4904  [(set_attr "itanium_class" "st")])
4905
4906;; Reads ar.unat
4907(define_expand "gr_restore"
4908  [(parallel [(set (match_operand:DI 0 "register_operand" "=r")
4909		   (unspec:DI [(match_operand:DI 1 "memory_operand" "m")
4910			       (match_operand:DI 2 "const_int_operand" "")] 2))
4911	      (use (match_dup 3))])]
4912  ""
4913  "operands[3] = gen_rtx_REG (DImode, AR_UNAT_REGNUM);")
4914
4915(define_insn "gr_restore_internal"
4916  [(set (match_operand:DI 0 "register_operand" "=r")
4917	(unspec:DI [(match_operand:DI 1 "memory_operand" "m")
4918		    (match_operand:DI 2 "const_int_operand" "")] 2))
4919   (use (match_operand:DI 3 "register_operand" ""))]
4920  ""
4921  "*
4922{
4923  return \".mem.offset %2, 0\;%,ld8.fill %0 = %1%P1\";
4924}"
4925  [(set_attr "itanium_class" "ld")])
4926
4927(define_insn "fr_spill"
4928  [(set (match_operand:TF 0 "memory_operand" "=m")
4929	(unspec:TF [(match_operand:TF 1 "register_operand" "f")] 3))]
4930  ""
4931  "stf.spill %0 = %1%P0"
4932  [(set_attr "itanium_class" "stf")])
4933
4934(define_insn "fr_restore"
4935  [(set (match_operand:TF 0 "register_operand" "=f")
4936	(unspec:TF [(match_operand:TF 1 "memory_operand" "m")] 4))]
4937  ""
4938  "ldf.fill %0 = %1%P1"
4939  [(set_attr "itanium_class" "fld")])
4940
4941;; ??? The explicit stop is not ideal.  It would be better if
4942;; rtx_needs_barrier took care of this, but this is something that can be
4943;; fixed later.  This avoids an RSE DV.
4944
4945(define_insn "bsp_value"
4946  [(set (match_operand:DI 0 "register_operand" "=r")
4947	(unspec:DI [(const_int 0)] 20))]
4948  ""
4949  ";;\;mov %0 = ar.bsp"
4950  [(set_attr "itanium_class" "frar_i")])
4951
4952(define_insn "set_bsp"
4953  [(unspec_volatile [(match_operand:DI 0 "register_operand" "r")] 5)]
4954  ""
4955  "flushrs\;mov r19=ar.rsc\;;;\;and r19=0x1c,r19\;;;\;mov ar.rsc=r19\;;;\;mov ar.bspstore=%0\;;;\;or r19=0x3,r19\;;;\;loadrs\;invala\;;;\;mov ar.rsc=r19"
4956  [(set_attr "itanium_class" "unknown")
4957   (set_attr "predicable" "no")])
4958
4959;; ??? The explicit stops are not ideal.  It would be better if
4960;; rtx_needs_barrier took care of this, but this is something that can be
4961;; fixed later.  This avoids an RSE DV.
4962
4963(define_insn "flushrs"
4964  [(unspec [(const_int 0)] 21)]
4965  ""
4966  ";;\;flushrs\;;;"
4967  [(set_attr "itanium_class" "rse_m")])
4968
4969;; ::::::::::::::::::::
4970;; ::
4971;; :: Miscellaneous instructions
4972;; ::
4973;; ::::::::::::::::::::
4974
4975;; ??? Emiting a NOP instruction isn't very useful.  This should probably
4976;; be emitting ";;" to force a break in the instruction packing.
4977
4978;; No operation, needed in case the user uses -g but not -O.
4979(define_insn "nop"
4980  [(const_int 0)]
4981  ""
4982  "nop 0"
4983  [(set_attr "itanium_class" "unknown")])
4984
4985(define_insn "nop_m"
4986  [(const_int 1)]
4987  ""
4988  "nop.m 0"
4989  [(set_attr "itanium_class" "nop_m")])
4990
4991(define_insn "nop_i"
4992  [(const_int 2)]
4993  ""
4994  "nop.i 0"
4995  [(set_attr "itanium_class" "nop_i")])
4996
4997(define_insn "nop_f"
4998  [(const_int 3)]
4999  ""
5000  "nop.f 0"
5001  [(set_attr "itanium_class" "nop_f")])
5002
5003(define_insn "nop_b"
5004  [(const_int 4)]
5005  ""
5006  "nop.b 0"
5007  [(set_attr "itanium_class" "nop_b")])
5008
5009(define_insn "nop_x"
5010  [(const_int 5)]
5011  ""
5012  ""
5013  [(set_attr "itanium_class" "nop_x")])
5014
5015(define_insn "cycle_display"
5016  [(unspec [(match_operand 0 "const_int_operand" "")] 23)]
5017  ""
5018  "// cycle %0"
5019  [(set_attr "itanium_class" "ignore")
5020   (set_attr "predicable" "no")])
5021
5022(define_insn "bundle_selector"
5023  [(unspec [(match_operand 0 "const_int_operand" "")] 22)]
5024  ""
5025  "*
5026{
5027  return get_bundle_name (INTVAL (operands[0]));
5028}"
5029  [(set_attr "itanium_class" "ignore")
5030   (set_attr "predicable" "no")])
5031
5032;; Pseudo instruction that prevents the scheduler from moving code above this
5033;; point.
5034(define_insn "blockage"
5035  [(unspec_volatile [(const_int 0)] 1)]
5036  ""
5037  ""
5038  [(set_attr "itanium_class" "ignore")
5039   (set_attr "predicable" "no")])
5040
5041(define_insn "insn_group_barrier"
5042  [(unspec_volatile [(match_operand 0 "const_int_operand" "")] 2)]
5043  ""
5044  ";;"
5045  [(set_attr "itanium_class" "stop_bit")
5046   (set_attr "predicable" "no")])
5047
5048(define_expand "trap"
5049  [(trap_if (const_int 1) (const_int 0))]
5050  ""
5051  "")
5052
5053;; ??? We don't have a match-any slot type.  Setting the type to unknown
5054;; produces worse code that setting the slot type to A.
5055
5056(define_insn "*trap"
5057  [(trap_if (const_int 1) (match_operand 0 "const_int_operand" ""))]
5058  ""
5059  "break %0"
5060  [(set_attr "itanium_class" "chk_s")])
5061
5062(define_expand "conditional_trap"
5063  [(trap_if (match_operand 0 "" "") (match_operand 1 "" ""))]
5064  ""
5065{
5066  operands[0] = ia64_expand_compare (GET_CODE (operands[0]), VOIDmode);
5067})
5068
5069(define_insn "*conditional_trap"
5070  [(trap_if (match_operator 0 "predicate_operator"
5071	      [(match_operand:BI 1 "register_operand" "c")
5072	       (const_int 0)])  
5073	    (match_operand 2 "const_int_operand" ""))]
5074  ""
5075  "(%J0) break %2"
5076  [(set_attr "itanium_class" "chk_s")
5077   (set_attr "predicable" "no")])
5078
5079(define_insn "break_f"
5080  [(unspec_volatile [(const_int 0)] 3)]
5081  ""
5082  "break.f 0"
5083  [(set_attr "itanium_class" "nop_f")])
5084
5085(define_insn "prefetch"
5086  [(prefetch (match_operand:DI 0 "address_operand" "p")
5087	     (match_operand:DI 1 "const_int_operand" "n")
5088	     (match_operand:DI 2 "const_int_operand" "n"))]
5089  ""
5090{
5091  static const char * const alt[2][4] = {
5092    {
5093      "lfetch.nta [%0]",
5094      "lfetch.nt1 [%0]",
5095      "lfetch.nt2 [%0]",
5096      "lfetch [%0]"
5097    },
5098    {
5099      "lfetch.excl.nta [%0]",
5100      "lfetch.excl.nt1 [%0]",
5101      "lfetch.excl.nt2 [%0]",
5102      "lfetch.excl [%0]"
5103    }
5104  };
5105  int i = (INTVAL (operands[1]));
5106  int j = (INTVAL (operands[2]));
5107
5108  if (i != 0 && i != 1)
5109    abort ();
5110  if (j < 0 || j > 3)
5111    abort ();
5112  return alt[i][j];
5113}
5114  [(set_attr "itanium_class" "lfetch")])
5115
5116;; Non-local goto support.
5117
5118(define_expand "save_stack_nonlocal"
5119  [(use (match_operand:OI 0 "memory_operand" ""))
5120   (use (match_operand:DI 1 "register_operand" ""))]
5121  ""
5122  "
5123{
5124  emit_library_call (gen_rtx_SYMBOL_REF (Pmode,
5125					 \"__ia64_save_stack_nonlocal\"),
5126		     0, VOIDmode, 2, XEXP (operands[0], 0), Pmode,
5127		     operands[1], Pmode);
5128  DONE;
5129}")
5130
5131(define_expand "nonlocal_goto"
5132  [(use (match_operand 0 "general_operand" ""))
5133   (use (match_operand 1 "general_operand" ""))
5134   (use (match_operand 2 "general_operand" ""))
5135   (use (match_operand 3 "general_operand" ""))]
5136  ""
5137  "
5138{
5139  emit_library_call (gen_rtx_SYMBOL_REF (Pmode, \"__ia64_nonlocal_goto\"),
5140		     LCT_NORETURN, VOIDmode, 3,
5141		     operands[1], Pmode,
5142		     copy_to_reg (XEXP (operands[2], 0)), Pmode,
5143		     operands[3], Pmode);
5144  emit_barrier ();
5145  DONE;
5146}")
5147
5148;; The rest of the setjmp processing happens with the nonlocal_goto expander.
5149;; ??? This is not tested.
5150(define_expand "builtin_setjmp_setup"
5151  [(use (match_operand:DI 0 "" ""))]
5152  ""
5153  "
5154{
5155  emit_move_insn (ia64_gp_save_reg (0), gen_rtx_REG (DImode, GR_REG (1)));
5156  DONE;
5157}")
5158
5159(define_expand "builtin_setjmp_receiver"
5160  [(use (match_operand:DI 0 "" ""))]
5161  ""
5162  "
5163{
5164  emit_move_insn (gen_rtx_REG (DImode, GR_REG (1)), ia64_gp_save_reg (0));
5165  DONE;
5166}")
5167
5168(define_expand "eh_epilogue"
5169  [(use (match_operand:DI 0 "register_operand" "r"))
5170   (use (match_operand:DI 1 "register_operand" "r"))
5171   (use (match_operand:DI 2 "register_operand" "r"))]
5172  ""
5173  "
5174{
5175  rtx bsp = gen_rtx_REG (Pmode, 10);
5176  rtx sp = gen_rtx_REG (Pmode, 9);
5177
5178  if (GET_CODE (operands[0]) != REG || REGNO (operands[0]) != 10)
5179    {
5180      emit_move_insn (bsp, operands[0]);
5181      operands[0] = bsp;
5182    }
5183  if (GET_CODE (operands[2]) != REG || REGNO (operands[2]) != 9)
5184    {
5185      emit_move_insn (sp, operands[2]);
5186      operands[2] = sp;
5187    }
5188  emit_insn (gen_rtx_USE (VOIDmode, sp));
5189  emit_insn (gen_rtx_USE (VOIDmode, bsp));
5190
5191  cfun->machine->ia64_eh_epilogue_sp = sp;
5192  cfun->machine->ia64_eh_epilogue_bsp = bsp;
5193}")
5194
5195;; Builtin apply support.
5196
5197(define_expand "restore_stack_nonlocal"
5198  [(use (match_operand:DI 0 "register_operand" ""))
5199   (use (match_operand:OI 1 "memory_operand" ""))]
5200  ""
5201  "
5202{
5203  emit_library_call (gen_rtx_SYMBOL_REF (Pmode,
5204					 \"__ia64_restore_stack_nonlocal\"),
5205		     0, VOIDmode, 1,
5206		     copy_to_reg (XEXP (operands[1], 0)), Pmode);
5207  DONE;
5208}")
5209
5210
5211;;; Intrinsics support.
5212
5213(define_expand "mf"
5214  [(set (mem:BLK (match_dup 0))
5215	(unspec:BLK [(mem:BLK (match_dup 0))] 12))]
5216  ""
5217  "
5218{
5219  operands[0] = gen_rtx_MEM (BLKmode, gen_rtx_SCRATCH (DImode));
5220  MEM_VOLATILE_P (operands[0]) = 1;
5221}")
5222
5223(define_insn "*mf_internal"
5224  [(set (match_operand:BLK 0 "" "")
5225	(unspec:BLK [(match_operand:BLK 1 "" "")] 12))]
5226  ""
5227  "mf"
5228  [(set_attr "itanium_class" "syst_m")])
5229
5230(define_insn "fetchadd_acq_si"
5231  [(set (match_operand:SI 0 "gr_register_operand" "=r")
5232	(match_dup 1))
5233   (set (match_operand:SI 1 "not_postinc_memory_operand" "+S")
5234	(unspec:SI [(match_dup 1)
5235		    (match_operand:SI 2 "fetchadd_operand" "n")] 19))]
5236  ""
5237  "fetchadd4.acq %0 = %1, %2"
5238  [(set_attr "itanium_class" "sem")])
5239
5240(define_insn "fetchadd_acq_di"
5241  [(set (match_operand:DI 0 "gr_register_operand" "=r")
5242	(match_dup 1))
5243   (set (match_operand:DI 1 "not_postinc_memory_operand" "+S")
5244	(unspec:DI [(match_dup 1)
5245		    (match_operand:DI 2 "fetchadd_operand" "n")] 19))]
5246  ""
5247  "fetchadd8.acq %0 = %1, %2"
5248  [(set_attr "itanium_class" "sem")])
5249
5250(define_insn "cmpxchg_acq_si"
5251  [(set (match_operand:SI 0 "gr_register_operand" "=r")
5252	(match_dup 1))
5253   (set (match_operand:SI 1 "not_postinc_memory_operand" "+S")
5254        (unspec:SI [(match_dup 1)
5255                    (match_operand:SI 2 "gr_register_operand" "r")
5256		    (match_operand:SI 3 "ar_ccv_reg_operand" "")] 13))]
5257  ""
5258  "cmpxchg4.acq %0 = %1, %2, %3"
5259  [(set_attr "itanium_class" "sem")])
5260
5261(define_insn "cmpxchg_acq_di"
5262  [(set (match_operand:DI 0 "gr_register_operand" "=r")
5263	(match_dup 1))
5264   (set (match_operand:DI 1 "not_postinc_memory_operand" "+S")
5265        (unspec:DI [(match_dup 1)
5266                    (match_operand:DI 2 "gr_register_operand" "r")
5267		    (match_operand:DI 3 "ar_ccv_reg_operand" "")] 13))]
5268  ""
5269  "cmpxchg8.acq %0 = %1, %2, %3"
5270  [(set_attr "itanium_class" "sem")])
5271
5272(define_insn "xchgsi"
5273  [(set (match_operand:SI 0 "gr_register_operand" "=r")
5274        (match_operand:SI 1 "not_postinc_memory_operand" "+S"))
5275   (set (match_dup 1)
5276        (match_operand:SI 2 "gr_register_operand" "r"))]
5277  ""
5278  "xchg4 %0 = %1, %2"
5279  [(set_attr "itanium_class" "sem")])
5280
5281(define_insn "xchgdi"
5282  [(set (match_operand:DI 0 "gr_register_operand" "=r")
5283        (match_operand:DI 1 "not_postinc_memory_operand" "+S"))
5284   (set (match_dup 1)
5285        (match_operand:DI 2 "gr_register_operand" "r"))]
5286  ""
5287  "xchg8 %0 = %1, %2"
5288  [(set_attr "itanium_class" "sem")])
5289
5290;; Predication.
5291
5292(define_cond_exec
5293  [(match_operator 0 "predicate_operator"
5294     [(match_operand:BI 1 "register_operand" "c")
5295      (const_int 0)])]
5296  ""
5297  "(%J0)")
5298
5299(define_insn "pred_rel_mutex"
5300  [(set (match_operand:BI 0 "register_operand" "+c")
5301       (unspec:BI [(match_dup 0)] 7))]
5302  ""
5303  ".pred.rel.mutex %0, %I0"
5304  [(set_attr "itanium_class" "ignore")
5305   (set_attr "predicable" "no")])
5306
5307(define_insn "safe_across_calls_all"
5308  [(unspec_volatile [(const_int 0)] 8)]
5309  ""
5310  ".pred.safe_across_calls p1-p63"
5311  [(set_attr "itanium_class" "ignore")
5312   (set_attr "predicable" "no")])
5313
5314(define_insn "safe_across_calls_normal"
5315  [(unspec_volatile [(const_int 0)] 9)]
5316  ""
5317  "*
5318{
5319  emit_safe_across_calls (asm_out_file);
5320  return \"\";
5321}"
5322  [(set_attr "itanium_class" "ignore")
5323   (set_attr "predicable" "no")])
5324
5325;;
5326;;
5327;; UNSPEC instruction definition to "swizzle" 32 bit pointer into 64 bit
5328;; pointer.  This is used by the HP-UX 32 bit mode.
5329
5330(define_insn "ptr_extend"
5331  [(set (match_operand:DI 0 "gr_register_operand" "=r")
5332        (unspec:DI [(match_operand:SI 1 "gr_register_operand" "r")] 24))]
5333  ""
5334  "addp4 %0 = 0,%1"
5335  [(set_attr "itanium_class" "ialu")])
5336
5337;;
5338;; As USE insns aren't meaningful after reload, this is used instead
5339;; to prevent deleting instructions setting registers for EH handling
5340(define_insn "prologue_use"
5341  [(unspec:DI [(match_operand:DI 0 "register_operand" "")] 25)]
5342  ""
5343  "// %0 needed for EH"
5344  [(set_attr "itanium_class" "ignore")
5345   (set_attr "predicable" "no")])
5346