Fortran: Unlimited polymorphic intrinsic function arguments [PR84006]
[official-gcc.git] / gcc / config / alpha / alpha.md
blob79f12c53c1688f145f0f51ae1a41409f2fa23ef2
1 ;; Machine description for DEC Alpha for GNU C compiler
2 ;; Copyright (C) 1992-2024 Free Software Foundation, Inc.
3 ;; Contributed by Richard Kenner (kenner@vlsi1.ultra.nyu.edu)
4 ;;
5 ;; This file is part of GCC.
6 ;;
7 ;; GCC is free software; you can redistribute it and/or modify
8 ;; it under the terms of the GNU General Public License as published by
9 ;; the Free Software Foundation; either version 3, or (at your option)
10 ;; any later version.
12 ;; GCC is distributed in the hope that it will be useful,
13 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
14 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 ;; GNU General Public License for more details.
17 ;; You should have received a copy of the GNU General Public License
18 ;; along with GCC; see the file COPYING3.  If not see
19 ;; <http://www.gnu.org/licenses/>.
21 ;;- See file "rtl.def" for documentation on define_insn, match_*, et. al.
23 ;; Uses of UNSPEC in this file:
25 (define_c_enum "unspec" [
26   UNSPEC_XFLT_COMPARE
27   UNSPEC_ARG_HOME
28   UNSPEC_LDGP1
29   UNSPEC_INSXH
30   UNSPEC_MSKXH
31   UNSPEC_CVTQL
32   UNSPEC_CVTLQ
33   UNSPEC_LDGP2
34   UNSPEC_LITERAL
35   UNSPEC_LITUSE
36   UNSPEC_SIBCALL
37   UNSPEC_SYMBOL
39   ;; TLS Support
40   UNSPEC_TLSGD_CALL
41   UNSPEC_TLSLDM_CALL
42   UNSPEC_TLSGD
43   UNSPEC_TLSLDM
44   UNSPEC_DTPREL
45   UNSPEC_TPREL
46   UNSPEC_TP
48   ;; Builtins
49   UNSPEC_CMPBGE
50   UNSPEC_ZAP
51   UNSPEC_AMASK
52   UNSPEC_IMPLVER
53   UNSPEC_PERR
54   UNSPEC_COPYSIGN
56   ;; Atomic operations
57   UNSPEC_MB
58   UNSPEC_ATOMIC
59   UNSPEC_CMPXCHG
60   UNSPEC_XCHG
63 ;; UNSPEC_VOLATILE:
65 (define_c_enum "unspecv" [
66   UNSPECV_IMB
67   UNSPECV_BLOCKAGE
68   UNSPECV_SETJMPR       ; builtin_setjmp_receiver
69   UNSPECV_LONGJMP       ; builtin_longjmp
70   UNSPECV_TRAPB
71   UNSPECV_PSPL          ; prologue_stack_probe_loop
72   UNSPECV_REALIGN
73   UNSPECV_EHR           ; exception_receiver
74   UNSPECV_MCOUNT
75   UNSPECV_FORCE_MOV
76   UNSPECV_LDGP1
77   UNSPECV_PLDGP2        ; prologue ldgp
78   UNSPECV_SET_TP
79   UNSPECV_RPCC
80   UNSPECV_SETJMPR_ER    ; builtin_setjmp_receiver fragment
81   UNSPECV_LL            ; load-locked
82   UNSPECV_SC            ; store-conditional
83   UNSPECV_CMPXCHG
86 ;; On non-BWX targets, CQImode must be handled the similarly to HImode
87 ;; when generating reloads.
88 (define_mode_iterator RELOAD12 [QI HI CQI])
89 (define_mode_attr reloadmode [(QI "qi") (HI "hi") (CQI "hi")])
91 ;; Other mode iterators
92 (define_mode_iterator IMODE [QI HI SI DI])
93 (define_mode_iterator I12MODE [QI HI])
94 (define_mode_iterator I124MODE [QI HI SI])
95 (define_mode_iterator I24MODE [HI SI])
96 (define_mode_iterator I248MODE [HI SI DI])
97 (define_mode_iterator I48MODE [SI DI])
99 (define_mode_attr DWI [(SI "DI") (DI "TI")])
100 (define_mode_attr modesuffix [(QI "b") (HI "w") (SI "l") (DI "q")
101                               (V8QI "b8") (V4HI "w4")
102                               (SF "%,") (DF "%-")])
103 (define_mode_attr vecmodesuffix [(QI "b8") (HI "w4")])
105 (define_code_iterator any_maxmin [smax smin umax umin])
107 (define_code_attr maxmin [(smax "maxs") (smin "mins")
108                           (umax "maxu") (umin "minu")])
110 ;; Where necessary, the suffixes _le and _be are used to distinguish between
111 ;; little-endian and big-endian patterns.
113 ;; Note that the Unicos/Mk assembler does not support the following
114 ;; opcodes: mov, fmov, nop, fnop, unop.
116 ;; Processor type -- this attribute must exactly match the processor_type
117 ;; enumeration in alpha.h.
119 (define_attr "tune" "ev4,ev5,ev6"
120   (const (symbol_ref "((enum attr_tune) alpha_tune)")))
122 ;; Define an insn type attribute.  This is used in function unit delay
123 ;; computations, among other purposes.  For the most part, we use the names
124 ;; defined in the EV4 documentation, but add a few that we have to know about
125 ;; separately.
127 (define_attr "type"
128   "ild,fld,ldsym,ist,fst,ibr,callpal,fbr,jsr,iadd,ilog,shift,icmov,fcmov,
129    icmp,imul,fadd,fmul,fcpys,fdiv,fsqrt,misc,mvi,ftoi,itof,mb,ld_l,st_c,
130    multi,none"
131   (const_string "iadd"))
133 ;; Describe a user's asm statement.
134 (define_asm_attributes
135   [(set_attr "type" "multi")])
137 ;; Define the operand size an insn operates on.  Used primarily by mul
138 ;; and div operations that have size dependent timings.
140 (define_attr "opsize" "si,di,udi"
141   (const_string "di"))
143 ;; The TRAP attribute marks instructions that may generate traps
144 ;; (which are imprecise and may need a trapb if software completion
145 ;; is desired).
147 (define_attr "trap" "no,yes"
148   (const_string "no"))
150 ;; The ROUND_SUFFIX attribute marks which instructions require a
151 ;; rounding-mode suffix.  The value NONE indicates no suffix,
152 ;; the value NORMAL indicates a suffix controlled by alpha_fprm.
154 (define_attr "round_suffix" "none,normal,c"
155   (const_string "none"))
157 ;; The TRAP_SUFFIX attribute marks instructions requiring a trap-mode suffix:
158 ;;   NONE       no suffix
159 ;;   SU         accepts only /su (cmpt et al)
160 ;;   SUI        accepts only /sui (cvtqt and cvtqs)
161 ;;   V_SV       accepts /v and /sv (cvtql only)
162 ;;   V_SV_SVI   accepts /v, /sv and /svi (cvttq only)
163 ;;   U_SU_SUI   accepts /u, /su and /sui (most fp instructions)
165 ;; The actual suffix emitted is controlled by alpha_fptm.
167 (define_attr "trap_suffix" "none,su,sui,v_sv,v_sv_svi,u_su_sui"
168   (const_string "none"))
170 ;; The length of an instruction sequence in bytes.
172 (define_attr "length" ""
173   (const_int 4))
175 ;; The USEGP attribute marks instructions that have relocations that use
176 ;; the GP.
178 (define_attr "usegp" "no,yes"
179   (cond [(eq_attr "type" "ldsym,jsr")
180            (const_string "yes")
181          (eq_attr "type" "ild,fld,ist,fst")
182            (symbol_ref "((enum attr_usegp) alpha_find_lo_sum_using_gp (insn))")
183         ]
184         (const_string "no")))
186 ;; The CANNOT_COPY attribute marks instructions with relocations that
187 ;; cannot easily be duplicated.  This includes insns with gpdisp relocs
188 ;; since they have to stay in 1-1 correspondence with one another.  This
189 ;; also includes jsr insns, since they must stay in correspondence with
190 ;; the immediately following gpdisp instructions.
192 (define_attr "cannot_copy" "false,true"
193   (const_string "false"))
195 ;; Used to control the "enabled" attribute on a per-instruction basis.
196 ;; For convenience, conflate ABI issues re loading of addresses with
197 ;; an "isa".
198 (define_attr "isa" "base,bwx,max,fix,cix,vms,ner,er"
199   (const_string "base"))
201 (define_attr "enabled" ""
202   (cond [(eq_attr "isa" "bwx")  (symbol_ref "TARGET_BWX")
203          (eq_attr "isa" "max")  (symbol_ref "TARGET_MAX")
204          (eq_attr "isa" "fix")  (symbol_ref "TARGET_FIX")
205          (eq_attr "isa" "cix")  (symbol_ref "TARGET_CIX")
206          (eq_attr "isa" "vms")  (symbol_ref "TARGET_ABI_OPEN_VMS")
207          (eq_attr "isa" "ner")  (symbol_ref "!TARGET_EXPLICIT_RELOCS")
208          (eq_attr "isa" "er")   (symbol_ref "TARGET_EXPLICIT_RELOCS")
209         ]
210         (const_int 1)))
212 ;; Include scheduling descriptions.
213   
214 (include "ev4.md")
215 (include "ev5.md")
216 (include "ev6.md")
219 ;; Operand and operator predicates and constraints
221 (include "predicates.md")
222 (include "constraints.md")
225 ;; First define the arithmetic insns.  Note that the 32-bit forms also
226 ;; sign-extend.
228 ;; Handle 32-64 bit extension from memory to a floating point register
229 ;; specially, since this occurs frequently in int->double conversions.
231 ;; Note that while we must retain the =f case in the insn for reload's
232 ;; benefit, it should be eliminated after reload, so we should never emit
233 ;; code for that case.  But we don't reject the possibility.
235 (define_expand "extendsidi2"
236   [(set (match_operand:DI 0 "register_operand")
237         (sign_extend:DI (match_operand:SI 1 "nonimmediate_operand")))])
239 (define_insn "*cvtlq"
240   [(set (match_operand:DI 0 "register_operand" "=f")
241         (unspec:DI [(match_operand:SF 1 "reg_or_0_operand" "fG")]
242                    UNSPEC_CVTLQ))]
243   ""
244   "cvtlq %1,%0"
245   [(set_attr "type" "fadd")])
247 (define_insn "*extendsidi2_1"
248   [(set (match_operand:DI 0 "register_operand" "=r,r,!*f")
249         (sign_extend:DI
250           (match_operand:SI 1 "nonimmediate_operand" "r,m,m")))]
251   ""
252   "@
253    addl $31,%1,%0
254    ldl %0,%1
255    lds %0,%1\;cvtlq %0,%0"
256   [(set_attr "type" "iadd,ild,fld")
257    (set_attr "length" "*,*,8")])
259 (define_split
260   [(set (match_operand:DI 0 "hard_fp_register_operand")
261         (sign_extend:DI (match_operand:SI 1 "memory_operand")))]
262   "reload_completed"
263   [(set (match_dup 2) (match_dup 1))
264    (set (match_dup 0) (unspec:DI [(match_dup 2)] UNSPEC_CVTLQ))]
266   operands[1] = adjust_address (operands[1], SFmode, 0);
267   operands[2] = gen_rtx_REG (SFmode, REGNO (operands[0]));
270 ;; Optimize sign-extension of SImode loads.  This shows up in the wake of
271 ;; reload when converting fp->int.
273 (define_peephole2
274   [(set (match_operand:SI 0 "hard_int_register_operand")
275         (match_operand:SI 1 "memory_operand"))
276    (set (match_operand:DI 2 "hard_int_register_operand")
277         (sign_extend:DI (match_dup 0)))]
278   "true_regnum (operands[0]) == true_regnum (operands[2])
279    || peep2_reg_dead_p (2, operands[0])"
280   [(set (match_dup 2)
281         (sign_extend:DI (match_dup 1)))])
283 (define_insn "addsi3"
284   [(set (match_operand:SI 0 "register_operand" "=r,r,r,r")
285         (plus:SI (match_operand:SI 1 "reg_or_0_operand" "%rJ,rJ,rJ,rJ")
286                  (match_operand:SI 2 "add_operand" "rI,O,K,L")))]
287   ""
288   "@
289    addl %r1,%2,%0
290    subl %r1,%n2,%0
291    lda %0,%2(%r1)
292    ldah %0,%h2(%r1)")
294 (define_split
295   [(set (match_operand:SI 0 "register_operand")
296         (plus:SI (match_operand:SI 1 "register_operand")
297                  (match_operand:SI 2 "const_int_operand")))]
298   "! add_operand (operands[2], SImode)"
299   [(set (match_dup 0) (plus:SI (match_dup 1) (match_dup 3)))
300    (set (match_dup 0) (plus:SI (match_dup 0) (match_dup 4)))]
302   HOST_WIDE_INT val = INTVAL (operands[2]);
303   HOST_WIDE_INT low = (val & 0xffff) - 2 * (val & 0x8000);
304   HOST_WIDE_INT rest = val - low;
306   operands[3] = GEN_INT (rest);
307   operands[4] = GEN_INT (low);
310 (define_insn "*addsi_se"
311   [(set (match_operand:DI 0 "register_operand" "=r,r")
312         (sign_extend:DI
313          (plus:SI (match_operand:SI 1 "reg_or_0_operand" "%rJ,rJ")
314                   (match_operand:SI 2 "sext_add_operand" "rI,O"))))]
315   ""
316   "@
317    addl %r1,%2,%0
318    subl %r1,%n2,%0")
320 (define_insn "*addsi_se2"
321   [(set (match_operand:DI 0 "register_operand" "=r,r")
322         (sign_extend:DI
323          (subreg:SI (plus:DI (match_operand:DI 1 "reg_or_0_operand" "%rJ,rJ")
324                              (match_operand:DI 2 "sext_add_operand" "rI,O"))
325                     0)))]
326   ""
327   "@
328    addl %r1,%2,%0
329    subl %r1,%n2,%0")
331 (define_split
332   [(set (match_operand:DI 0 "register_operand")
333         (sign_extend:DI
334          (plus:SI (match_operand:SI 1 "reg_not_elim_operand")
335                   (match_operand:SI 2 "const_int_operand"))))
336    (clobber (match_operand:SI 3 "reg_not_elim_operand"))]
337   "! sext_add_operand (operands[2], SImode) && INTVAL (operands[2]) > 0
338    && INTVAL (operands[2]) % 4 == 0"
339   [(set (match_dup 3) (match_dup 4))
340    (set (match_dup 0) (sign_extend:DI (plus:SI (ashift:SI (match_dup 3)
341                                                           (match_dup 5))
342                                                (match_dup 1))))]
344   HOST_WIDE_INT val = INTVAL (operands[2]) / 4;
345   int mult = 4;
347   if (val % 2 == 0)
348     val /= 2, mult = 8;
350   operands[4] = GEN_INT (val);
351   operands[5] = GEN_INT (exact_log2 (mult));
354 (define_split
355   [(set (match_operand:DI 0 "register_operand")
356         (sign_extend:DI
357          (plus:SI (match_operator:SI 1 "comparison_operator"
358                                      [(match_operand 2)
359                                       (match_operand 3)])
360                   (match_operand:SI 4 "add_operand"))))
361    (clobber (match_operand:DI 5 "register_operand"))]
362   ""
363   [(set (match_dup 5) (match_dup 6))
364    (set (match_dup 0) (sign_extend:DI (plus:SI (match_dup 7) (match_dup 4))))]
366   operands[6] = gen_rtx_fmt_ee (GET_CODE (operands[1]), DImode,
367                                 operands[2], operands[3]);
368   operands[7] = gen_lowpart (SImode, operands[5]);
371 (define_expand "adddi3"
372   [(set (match_operand:DI 0 "register_operand")
373         (plus:DI (match_operand:DI 1 "register_operand")
374                  (match_operand:DI 2 "add_operand")))])
376 (define_insn "*adddi_er_lo16_dtp"
377   [(set (match_operand:DI 0 "register_operand" "=r")
378         (lo_sum:DI (match_operand:DI 1 "register_operand" "r")
379                    (match_operand:DI 2 "dtp16_symbolic_operand")))]
380   "HAVE_AS_TLS"
381   "lda %0,%2(%1)\t\t!dtprel")
383 (define_insn "*adddi_er_hi32_dtp"
384   [(set (match_operand:DI 0 "register_operand" "=r")
385         (plus:DI (match_operand:DI 1 "register_operand" "r")
386                  (high:DI (match_operand:DI 2 "dtp32_symbolic_operand"))))]
387   "HAVE_AS_TLS"
388   "ldah %0,%2(%1)\t\t!dtprelhi")
390 (define_insn "*adddi_er_lo32_dtp"
391   [(set (match_operand:DI 0 "register_operand" "=r")
392         (lo_sum:DI (match_operand:DI 1 "register_operand" "r")
393                    (match_operand:DI 2 "dtp32_symbolic_operand")))]
394   "HAVE_AS_TLS"
395   "lda %0,%2(%1)\t\t!dtprello")
397 (define_insn "*adddi_er_lo16_tp"
398   [(set (match_operand:DI 0 "register_operand" "=r")
399         (lo_sum:DI (match_operand:DI 1 "register_operand" "r")
400                    (match_operand:DI 2 "tp16_symbolic_operand")))]
401   "HAVE_AS_TLS"
402   "lda %0,%2(%1)\t\t!tprel")
404 (define_insn "*adddi_er_hi32_tp"
405   [(set (match_operand:DI 0 "register_operand" "=r")
406         (plus:DI (match_operand:DI 1 "register_operand" "r")
407                  (high:DI (match_operand:DI 2 "tp32_symbolic_operand"))))]
408   "HAVE_AS_TLS"
409   "ldah %0,%2(%1)\t\t!tprelhi")
411 (define_insn "*adddi_er_lo32_tp"
412   [(set (match_operand:DI 0 "register_operand" "=r")
413         (lo_sum:DI (match_operand:DI 1 "register_operand" "r")
414                    (match_operand:DI 2 "tp32_symbolic_operand")))]
415   "HAVE_AS_TLS"
416   "lda %0,%2(%1)\t\t!tprello")
418 (define_insn "*adddi_er_high_l"
419   [(set (match_operand:DI 0 "register_operand" "=r")
420         (plus:DI (match_operand:DI 1 "register_operand" "r")
421                  (high:DI (match_operand:DI 2 "local_symbolic_operand"))))]
422   "TARGET_EXPLICIT_RELOCS && reload_completed"
423   "ldah %0,%2(%1)\t\t!gprelhigh"
424   [(set_attr "usegp" "yes")])
426 (define_split
427   [(set (match_operand:DI 0 "register_operand")
428         (high:DI (match_operand:DI 1 "local_symbolic_operand")))]
429   "TARGET_EXPLICIT_RELOCS && reload_completed"
430   [(set (match_dup 0)
431         (plus:DI (match_dup 2) (high:DI (match_dup 1))))]
432   "operands[2] = pic_offset_table_rtx;")
434 ;; We used to expend quite a lot of effort choosing addq/subq/lda.
435 ;; With complications like
437 ;;   The NT stack unwind code can't handle a subq to adjust the stack
438 ;;   (that's a bug, but not one we can do anything about).  As of NT4.0 SP3,
439 ;;   the exception handling code will loop if a subq is used and an
440 ;;   exception occurs.
442 ;;   The 19980616 change to emit prologues as RTL also confused some
443 ;;   versions of GDB, which also interprets prologues.  This has been
444 ;;   fixed as of GDB 4.18, but it does not harm to unconditionally
445 ;;   use lda here.
447 ;; and the fact that the three insns schedule exactly the same, it's
448 ;; just not worth the effort.
450 (define_insn "*adddi_internal"
451   [(set (match_operand:DI 0 "register_operand" "=r,r,r")
452         (plus:DI (match_operand:DI 1 "register_operand" "%r,r,r")
453                  (match_operand:DI 2 "add_operand" "r,K,L")))]
454   ""
455   "@
456    addq %1,%2,%0
457    lda %0,%2(%1)
458    ldah %0,%h2(%1)")
460 ;; ??? Allow large constants when basing off the frame pointer or some
461 ;; virtual register that may eliminate to the frame pointer.  This is
462 ;; done because register elimination offsets will change the hi/lo split,
463 ;; and if we split before reload, we will require additional instructions.
465 (define_insn "*adddi_fp_hack"
466   [(set (match_operand:DI 0 "register_operand" "=r,r,r")
467         (plus:DI (match_operand:DI 1 "reg_no_subreg_operand" "r,r,r")
468                  (match_operand:DI 2 "const_int_operand" "K,L,n")))]
469   "NONSTRICT_REG_OK_FP_BASE_P (operands[1])
470    && INTVAL (operands[2]) >= 0
471    /* This is the largest constant an lda+ldah pair can add, minus
472       an upper bound on the displacement between SP and AP during
473       register elimination.  See INITIAL_ELIMINATION_OFFSET.  */
474    && INTVAL (operands[2])
475         < (0x7fff8000
476            - FIRST_PSEUDO_REGISTER * UNITS_PER_WORD
477            - ALPHA_ROUND(crtl->outgoing_args_size)
478            - (ALPHA_ROUND (get_frame_size ()
479                            + max_reg_num () * UNITS_PER_WORD
480                            + crtl->args.pretend_args_size)
481               - crtl->args.pretend_args_size))"
482   "@
483    lda %0,%2(%1)
484    ldah %0,%h2(%1)
485    #")
487 ;; Don't do this if we are adjusting SP since we don't want to do it
488 ;; in two steps.  Don't split FP sources for the reason listed above.
489 (define_split
490   [(set (match_operand:DI 0 "register_operand")
491         (plus:DI (match_operand:DI 1 "register_operand")
492                  (match_operand:DI 2 "const_int_operand")))]
493   "! add_operand (operands[2], DImode)
494    && operands[0] != stack_pointer_rtx
495    && operands[1] != frame_pointer_rtx
496    && operands[1] != arg_pointer_rtx"
497   [(set (match_dup 0) (plus:DI (match_dup 1) (match_dup 3)))
498    (set (match_dup 0) (plus:DI (match_dup 0) (match_dup 4)))]
500   HOST_WIDE_INT val = INTVAL (operands[2]);
501   HOST_WIDE_INT low = (val & 0xffff) - 2 * (val & 0x8000);
502   HOST_WIDE_INT rest = val - low;
503   rtx rest_rtx = GEN_INT (rest);
505   operands[4] = GEN_INT (low);
506   if (satisfies_constraint_L (rest_rtx))
507     operands[3] = rest_rtx;
508   else if (can_create_pseudo_p ())
509     {
510       operands[3] = gen_reg_rtx (DImode);
511       emit_move_insn (operands[3], operands[2]);
512       emit_insn (gen_adddi3 (operands[0], operands[1], operands[3]));
513       DONE;
514     }
515   else
516     FAIL;
519 (define_insn "*sadd<modesuffix>"
520   [(set (match_operand:I48MODE 0 "register_operand" "=r,r")
521         (plus:I48MODE
522          (ashift:I48MODE (match_operand:I48MODE 1 "reg_not_elim_operand" "r,r")
523                          (match_operand:I48MODE 2 "const23_operand" "I,I"))
524          (match_operand:I48MODE 3 "sext_add_operand" "rI,O")))]
525   ""
526   "@
527    s%P2add<modesuffix> %1,%3,%0
528    s%P2sub<modesuffix> %1,%n3,%0")
530 (define_insn "*saddl_se"
531   [(set (match_operand:DI 0 "register_operand" "=r,r")
532         (sign_extend:DI
533          (plus:SI
534           (ashift:SI (match_operand:SI 1 "reg_not_elim_operand" "r,r")
535                      (match_operand:SI 2 "const23_operand" "I,I"))
536          (match_operand:SI 3 "sext_add_operand" "rI,O"))))]
537   ""
538   "@
539    s%P2addl %1,%3,%0
540    s%P2subl %1,%n3,%0")
542 (define_split
543   [(set (match_operand:DI 0 "register_operand")
544         (sign_extend:DI
545          (plus:SI (ashift:SI (match_operator:SI 1 "comparison_operator"
546                                               [(match_operand 2)
547                                                (match_operand 3)])
548                            (match_operand:SI 4 "const23_operand"))
549                   (match_operand:SI 5 "sext_add_operand"))))
550    (clobber (match_operand:DI 6 "reg_not_elim_operand"))]
551   ""
552   [(set (match_dup 6) (match_dup 7))
553    (set (match_dup 0)
554         (sign_extend:DI (plus:SI (ashift:SI (match_dup 8) (match_dup 4))
555                                  (match_dup 5))))]
557   operands[7] = gen_rtx_fmt_ee (GET_CODE (operands[1]), DImode,
558                                 operands[2], operands[3]);
559   operands[8] = gen_lowpart (SImode, operands[6]);
562 (define_insn "addv<mode>3"
563   [(set (match_operand:I48MODE 0 "register_operand" "=r,r")
564         (plus:I48MODE (match_operand:I48MODE 1 "reg_or_0_operand" "%rJ,rJ")
565                       (match_operand:I48MODE 2 "sext_add_operand" "rI,O")))
566    (trap_if (ne (plus:<DWI> (sign_extend:<DWI> (match_dup 1))
567                             (sign_extend:<DWI> (match_dup 2)))
568                 (sign_extend:<DWI> (plus:I48MODE (match_dup 1)
569                                                  (match_dup 2))))
570             (const_int 0))]
571   ""
572   "@
573    add<modesuffix>v %r1,%2,%0
574    sub<modesuffix>v %r1,%n2,%0")
576 (define_insn "neg<mode>2"
577   [(set (match_operand:I48MODE 0 "register_operand" "=r")
578         (neg:I48MODE (match_operand:I48MODE 1 "reg_or_8bit_operand" "rI")))]
579   ""
580   "sub<modesuffix> $31,%1,%0")
582 (define_insn "*negsi_se"
583   [(set (match_operand:DI 0 "register_operand" "=r")
584         (sign_extend:DI (neg:SI
585                          (match_operand:SI 1 "reg_or_8bit_operand" "rI"))))]
586   ""
587   "subl $31,%1,%0")
589 (define_insn "negv<mode>2"
590   [(set (match_operand:I48MODE 0 "register_operand" "=r")
591         (neg:I48MODE (match_operand:I48MODE 1 "register_operand" "r")))
592    (trap_if (ne (neg:<DWI> (sign_extend:<DWI> (match_dup 1)))
593                 (sign_extend:<DWI> (neg:I48MODE (match_dup 1))))
594             (const_int 0))]
595   ""
596   "sub<modesuffix>v $31,%1,%0")
598 (define_insn "sub<mode>3"
599   [(set (match_operand:I48MODE 0 "register_operand" "=r")
600         (minus:I48MODE (match_operand:I48MODE 1 "reg_or_0_operand" "rJ")
601                        (match_operand:I48MODE 2 "reg_or_8bit_operand" "rI")))]
602   ""
603   "sub<modesuffix> %r1,%2,%0")
605 (define_insn "*subsi_se"
606   [(set (match_operand:DI 0 "register_operand" "=r")
607         (sign_extend:DI
608          (minus:SI (match_operand:SI 1 "reg_or_0_operand" "rJ")
609                    (match_operand:SI 2 "reg_or_8bit_operand" "rI"))))]
610   ""
611   "subl %r1,%2,%0")
613 (define_insn "*subsi_se2"
614   [(set (match_operand:DI 0 "register_operand" "=r")
615         (sign_extend:DI
616          (subreg:SI (minus:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
617                               (match_operand:DI 2 "reg_or_8bit_operand" "rI"))
618                     0)))]
619   ""
620   "subl %r1,%2,%0")
622 (define_insn "*ssub<modesuffix>"
623   [(set (match_operand:I48MODE 0 "register_operand" "=r")
624         (minus:I48MODE
625          (ashift:I48MODE (match_operand:I48MODE 1 "reg_not_elim_operand" "r")
626                          (match_operand:I48MODE 2 "const23_operand" "I"))
627                   (match_operand:I48MODE 3 "reg_or_8bit_operand" "rI")))]
628   ""
629   "s%P2sub<modesuffix> %1,%3,%0")
631 (define_insn "*ssubl_se"
632   [(set (match_operand:DI 0 "register_operand" "=r")
633         (sign_extend:DI
634          (minus:SI
635           (ashift:SI (match_operand:SI 1 "reg_not_elim_operand" "r")
636                      (match_operand:SI 2 "const23_operand" "I"))
637          (match_operand:SI 3 "reg_or_8bit_operand" "rI"))))]
638   ""
639   "s%P2subl %1,%3,%0")
641 (define_insn "subv<mode>3"
642   [(set (match_operand:I48MODE 0 "register_operand" "=r")
643         (minus:I48MODE (match_operand:I48MODE 1 "reg_or_0_operand" "rJ")
644                        (match_operand:I48MODE 2 "reg_or_8bit_operand" "rI")))
645    (trap_if (ne (minus:<DWI> (sign_extend:<DWI> (match_dup 1))
646                              (sign_extend:<DWI> (match_dup 2)))
647                 (sign_extend:<DWI> (minus:I48MODE (match_dup 1)
648                                                   (match_dup 2))))
649             (const_int 0))]
650   ""
651   "sub<modesuffix>v %r1,%2,%0")
653 (define_insn "mul<mode>3"
654   [(set (match_operand:I48MODE 0 "register_operand" "=r")
655         (mult:I48MODE (match_operand:I48MODE 1 "reg_or_0_operand" "%rJ")
656                       (match_operand:I48MODE 2 "reg_or_8bit_operand" "rI")))]
657   ""
658   "mul<modesuffix> %r1,%2,%0"
659   [(set_attr "type" "imul")
660    (set_attr "opsize" "<mode>")])
662 (define_insn "*mulsi_se"
663   [(set (match_operand:DI 0 "register_operand" "=r")
664         (sign_extend:DI
665           (mult:SI (match_operand:SI 1 "reg_or_0_operand" "%rJ")
666                    (match_operand:SI 2 "reg_or_8bit_operand" "rI"))))]
667   ""
668   "mull %r1,%2,%0"
669   [(set_attr "type" "imul")
670    (set_attr "opsize" "si")])
672 (define_insn "mulv<mode>3"
673   [(set (match_operand:I48MODE 0 "register_operand" "=r")
674         (mult:I48MODE (match_operand:I48MODE 1 "reg_or_0_operand" "%rJ")
675                       (match_operand:I48MODE 2 "reg_or_8bit_operand" "rI")))
676    (trap_if (ne (mult:<DWI> (sign_extend:<DWI> (match_dup 1))
677                             (sign_extend:<DWI> (match_dup 2)))
678                 (sign_extend:<DWI> (mult:I48MODE (match_dup 1)
679                                                  (match_dup 2))))
680             (const_int 0))]
681   ""
682   "mul<modesuffix>v %r1,%2,%0"
683   [(set_attr "type" "imul")
684    (set_attr "opsize" "<mode>")])
686 (define_insn "umuldi3_highpart"
687   [(set (match_operand:DI 0 "register_operand" "=r")
688         (umul_highpart:DI (match_operand:DI 1 "reg_or_0_operand" "%rJ")
689                           (match_operand:DI 2 "reg_or_8bit_operand" "rI")))]
690   ""
691   "umulh %1,%2,%0"
692   [(set_attr "type" "imul")
693    (set_attr "opsize" "udi")])
695 (define_expand "umulditi3"
696   [(set (match_operand:TI 0 "register_operand")
697        (mult:TI
698          (zero_extend:TI (match_operand:DI 1 "reg_no_subreg_operand"))
699          (zero_extend:TI (match_operand:DI 2 "reg_no_subreg_operand"))))]
700   ""
702   rtx l = gen_reg_rtx (DImode), h = gen_reg_rtx (DImode);
703   emit_insn (gen_muldi3 (l, operands[1], operands[2]));
704   emit_insn (gen_umuldi3_highpart (h, operands[1], operands[2]));
705   emit_move_insn (gen_lowpart (DImode, operands[0]), l);
706   emit_move_insn (gen_highpart (DImode, operands[0]), h);
707   DONE;
710 ;; The divide and remainder operations take their inputs from r24 and
711 ;; r25, put their output in r27, and clobber r23 and r28 on all systems.
713 ;; ??? Force sign-extension here because some versions of OSF/1 and
714 ;; Interix/NT don't do the right thing if the inputs are not properly
715 ;; sign-extended.  But Linux, for instance, does not have this
716 ;; problem.  Is it worth the complication here to eliminate the sign
717 ;; extension?
719 (define_code_iterator any_divmod [div mod udiv umod])
721 (define_expand "<code>si3"
722   [(set (match_dup 3)
723         (sign_extend:DI (match_operand:SI 1 "nonimmediate_operand")))
724    (set (match_dup 4)
725         (sign_extend:DI (match_operand:SI 2 "nonimmediate_operand")))
726    (parallel [(set (match_dup 5)
727                    (sign_extend:DI
728                     (any_divmod:SI (match_dup 3) (match_dup 4))))
729               (clobber (reg:DI 23))
730               (clobber (reg:DI 28))])
731    (set (match_operand:SI 0 "nonimmediate_operand")
732         (subreg:SI (match_dup 5) 0))]
733   "TARGET_ABI_OSF"
735   operands[3] = gen_reg_rtx (DImode);
736   operands[4] = gen_reg_rtx (DImode);
737   operands[5] = gen_reg_rtx (DImode);
740 (define_expand "<code>di3"
741   [(parallel [(set (match_operand:DI 0 "register_operand")
742                    (any_divmod:DI
743                     (match_operand:DI 1 "register_operand")
744                     (match_operand:DI 2 "register_operand")))
745               (clobber (reg:DI 23))
746               (clobber (reg:DI 28))])]
747   "TARGET_ABI_OSF")
749 ;; Lengths of 8 for ldq $t12,__divq($gp); jsr $t9,($t12),__divq as
750 ;; expanded by the assembler.
752 (define_insn_and_split "*divmodsi_internal_er"
753   [(set (match_operand:DI 0 "register_operand" "=c")
754         (sign_extend:DI (match_operator:SI 3 "divmod_operator"
755                         [(match_operand:DI 1 "register_operand" "a")
756                          (match_operand:DI 2 "register_operand" "b")])))
757    (clobber (reg:DI 23))
758    (clobber (reg:DI 28))]
759   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
760   "#"
761   "&& reload_completed"
762   [(parallel [(set (match_dup 0)
763                    (sign_extend:DI (match_dup 3)))
764               (use (match_dup 0))
765               (use (match_dup 4))
766               (clobber (reg:DI 23))
767               (clobber (reg:DI 28))])]
769   const char *str;
770   switch (GET_CODE (operands[3]))
771     {
772     case DIV: 
773       str = "__divl";
774       break; 
775     case UDIV:
776       str = "__divlu";
777       break;
778     case MOD:
779       str = "__reml";
780       break;
781     case UMOD:
782       str = "__remlu";
783       break;
784     default:
785       gcc_unreachable ();
786     }
787   operands[4] = GEN_INT (alpha_next_sequence_number++);
788   emit_insn (gen_movdi_er_high_g (operands[0], pic_offset_table_rtx,
789                                   gen_rtx_SYMBOL_REF (DImode, str),
790                                   operands[4]));
792   [(set_attr "type" "jsr")
793    (set_attr "length" "8")])
795 (define_insn "*divmodsi_internal_er_1"
796   [(set (match_operand:DI 0 "register_operand" "=c")
797         (sign_extend:DI (match_operator:SI 3 "divmod_operator"
798                         [(match_operand:DI 1 "register_operand" "a")
799                          (match_operand:DI 2 "register_operand" "b")])))
800    (use (match_operand:DI 4 "register_operand" "c"))
801    (use (match_operand 5 "const_int_operand"))
802    (clobber (reg:DI 23))
803    (clobber (reg:DI 28))]
804   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
805   "jsr $23,($27),__%E3%j5"
806   [(set_attr "type" "jsr")
807    (set_attr "length" "4")])
809 (define_insn "*divmodsi_internal"
810   [(set (match_operand:DI 0 "register_operand" "=c")
811         (sign_extend:DI (match_operator:SI 3 "divmod_operator"
812                         [(match_operand:DI 1 "register_operand" "a")
813                          (match_operand:DI 2 "register_operand" "b")])))
814    (clobber (reg:DI 23))
815    (clobber (reg:DI 28))]
816   "TARGET_ABI_OSF"
817   "%E3 %1,%2,%0"
818   [(set_attr "type" "jsr")
819    (set_attr "length" "8")])
821 (define_insn_and_split "*divmoddi_internal_er"
822   [(set (match_operand:DI 0 "register_operand" "=c")
823         (match_operator:DI 3 "divmod_operator"
824                         [(match_operand:DI 1 "register_operand" "a")
825                          (match_operand:DI 2 "register_operand" "b")]))
826    (clobber (reg:DI 23))
827    (clobber (reg:DI 28))]
828   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
829   "#"
830   "&& reload_completed"
831   [(parallel [(set (match_dup 0) (match_dup 3))
832               (use (match_dup 0))
833               (use (match_dup 4))
834               (clobber (reg:DI 23))
835               (clobber (reg:DI 28))])]
837   const char *str;
838   switch (GET_CODE (operands[3]))
839     {
840     case DIV: 
841       str = "__divq";
842       break; 
843     case UDIV:
844       str = "__divqu";
845       break;
846     case MOD:
847       str = "__remq";
848       break;
849     case UMOD:
850       str = "__remqu";
851       break;
852     default:
853       gcc_unreachable ();
854     }
855   operands[4] = GEN_INT (alpha_next_sequence_number++);
856   emit_insn (gen_movdi_er_high_g (operands[0], pic_offset_table_rtx,
857                                   gen_rtx_SYMBOL_REF (DImode, str),
858                                   operands[4]));
860   [(set_attr "type" "jsr")
861    (set_attr "length" "8")])
863 (define_insn "*divmoddi_internal_er_1"
864   [(set (match_operand:DI 0 "register_operand" "=c")
865         (match_operator:DI 3 "divmod_operator"
866                         [(match_operand:DI 1 "register_operand" "a")
867                          (match_operand:DI 2 "register_operand" "b")]))
868    (use (match_operand:DI 4 "register_operand" "c"))
869    (use (match_operand 5 "const_int_operand"))
870    (clobber (reg:DI 23))
871    (clobber (reg:DI 28))]
872   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
873   "jsr $23,($27),__%E3%j5"
874   [(set_attr "type" "jsr")
875    (set_attr "length" "4")])
877 (define_insn "*divmoddi_internal"
878   [(set (match_operand:DI 0 "register_operand" "=c")
879         (match_operator:DI 3 "divmod_operator"
880                         [(match_operand:DI 1 "register_operand" "a")
881                          (match_operand:DI 2 "register_operand" "b")]))
882    (clobber (reg:DI 23))
883    (clobber (reg:DI 28))]
884   "TARGET_ABI_OSF"
885   "%E3 %1,%2,%0"
886   [(set_attr "type" "jsr")
887    (set_attr "length" "8")])
889 ;; Next are the basic logical operations.  We only expose the DImode operations
890 ;; to the rtl expanders, but SImode versions exist for combine as well as for
891 ;; the atomic operation splitters.
893 (define_insn "*andsi_internal"
894   [(set (match_operand:SI 0 "register_operand" "=r,r,r")
895         (and:SI (match_operand:SI 1 "reg_or_0_operand" "%rJ,rJ,rJ")
896                 (match_operand:SI 2 "and_operand" "rI,N,M")))]
897   ""
898   "@
899    and %r1,%2,%0
900    bic %r1,%N2,%0
901    zapnot %r1,%m2,%0"
902   [(set_attr "type" "ilog,ilog,shift")])
904 (define_insn "anddi3"
905   [(set (match_operand:DI 0 "register_operand" "=r,r,r")
906         (and:DI (match_operand:DI 1 "reg_or_0_operand" "%rJ,rJ,rJ")
907                 (match_operand:DI 2 "and_operand" "rI,N,M")))]
908   ""
909   "@
910    and %r1,%2,%0
911    bic %r1,%N2,%0
912    zapnot %r1,%m2,%0"
913   [(set_attr "type" "ilog,ilog,shift")])
915 ;; There are times when we can split an AND into two AND insns.  This occurs
916 ;; when we can first clear any bytes and then clear anything else.  For
917 ;; example "I & 0xffff07" is "(I & 0xffffff) & 0xffffffffffffff07".
918 ;; Only do this when running on 64-bit host since the computations are
919 ;; too messy otherwise.
921 (define_split
922   [(set (match_operand:DI 0 "register_operand")
923         (and:DI (match_operand:DI 1 "register_operand")
924                 (match_operand:DI 2 "const_int_operand")))]
925   "! and_operand (operands[2], DImode)"
926   [(set (match_dup 0) (and:DI (match_dup 1) (match_dup 3)))
927    (set (match_dup 0) (and:DI (match_dup 0) (match_dup 4)))]
929   unsigned HOST_WIDE_INT mask1 = INTVAL (operands[2]);
930   unsigned HOST_WIDE_INT mask2 = mask1;
931   int i;
933   /* For each byte that isn't all zeros, make it all ones.  */
934   for (i = 0; i < 64; i += 8)
935     if ((mask1 & ((HOST_WIDE_INT) 0xff << i)) != 0)
936       mask1 |= (HOST_WIDE_INT) 0xff << i;
938   /* Now turn on any bits we've just turned off.  */
939   mask2 |= ~ mask1;
941   operands[3] = GEN_INT (mask1);
942   operands[4] = GEN_INT (mask2);
945 (define_insn "zero_extendqi<mode>2"
946   [(set (match_operand:I248MODE 0 "register_operand" "=r,r")
947         (zero_extend:I248MODE
948           (match_operand:QI 1 "reg_or_bwx_memory_operand" "r,m")))]
949   ""
950   "@
951    and %1,0xff,%0
952    ldbu %0,%1"
953   [(set_attr "type" "ilog,ild")
954    (set_attr "isa" "*,bwx")])
956 (define_insn "zero_extendhi<mode>2"
957   [(set (match_operand:I48MODE 0 "register_operand" "=r,r")
958         (zero_extend:I48MODE
959           (match_operand:HI 1 "reg_or_bwx_memory_operand" "r,m")))]
960   ""
961   "@
962    zapnot %1,3,%0
963    ldwu %0,%1"
964   [(set_attr "type" "shift,ild")
965    (set_attr "isa" "*,bwx")])
967 (define_insn "zero_extendsidi2"
968   [(set (match_operand:DI 0 "register_operand" "=r")
969         (zero_extend:DI (match_operand:SI 1 "register_operand" "r")))]
970   ""
971   "zapnot %1,15,%0"
972   [(set_attr "type" "shift")])
974 (define_insn "andnot<mode>3"
975   [(set (match_operand:I48MODE 0 "register_operand" "=r")
976         (and:I48MODE
977          (not:I48MODE (match_operand:I48MODE 1 "reg_or_8bit_operand" "rI"))
978          (match_operand:I48MODE 2 "reg_or_0_operand" "rJ")))]
979   ""
980   "bic %r2,%1,%0"
981   [(set_attr "type" "ilog")])
983 (define_insn "*iorsi_internal"
984   [(set (match_operand:SI 0 "register_operand" "=r,r")
985         (ior:SI (match_operand:SI 1 "reg_or_0_operand" "%rJ,rJ")
986                 (match_operand:SI 2 "or_operand" "rI,N")))]
987   ""
988   "@
989    bis %r1,%2,%0
990    ornot %r1,%N2,%0"
991   [(set_attr "type" "ilog")])
993 (define_insn "iordi3"
994   [(set (match_operand:DI 0 "register_operand" "=r,r")
995         (ior:DI (match_operand:DI 1 "reg_or_0_operand" "%rJ,rJ")
996                 (match_operand:DI 2 "or_operand" "rI,N")))]
997   ""
998   "@
999    bis %r1,%2,%0
1000    ornot %r1,%N2,%0"
1001   [(set_attr "type" "ilog")])
1003 (define_insn "*one_cmplsi_internal"
1004   [(set (match_operand:SI 0 "register_operand" "=r")
1005         (not:SI (match_operand:SI 1 "reg_or_8bit_operand" "rI")))]
1006   ""
1007   "ornot $31,%1,%0"
1008   [(set_attr "type" "ilog")])
1010 (define_insn "one_cmpldi2"
1011   [(set (match_operand:DI 0 "register_operand" "=r")
1012         (not:DI (match_operand:DI 1 "reg_or_8bit_operand" "rI")))]
1013   ""
1014   "ornot $31,%1,%0"
1015   [(set_attr "type" "ilog")])
1017 (define_insn "*iornot<mode>3"
1018   [(set (match_operand:I48MODE 0 "register_operand" "=r")
1019         (ior:I48MODE
1020          (not:I48MODE (match_operand:I48MODE 1 "reg_or_8bit_operand" "rI"))
1021          (match_operand:I48MODE 2 "reg_or_0_operand" "rJ")))]
1022   ""
1023   "ornot %r2,%1,%0"
1024   [(set_attr "type" "ilog")])
1026 (define_insn "*xorsi_internal"
1027   [(set (match_operand:SI 0 "register_operand" "=r,r")
1028         (xor:SI (match_operand:SI 1 "reg_or_0_operand" "%rJ,rJ")
1029                 (match_operand:SI 2 "or_operand" "rI,N")))]
1030   ""
1031   "@
1032    xor %r1,%2,%0
1033    eqv %r1,%N2,%0"
1034   [(set_attr "type" "ilog")])
1036 (define_insn "xordi3"
1037   [(set (match_operand:DI 0 "register_operand" "=r,r")
1038         (xor:DI (match_operand:DI 1 "reg_or_0_operand" "%rJ,rJ")
1039                 (match_operand:DI 2 "or_operand" "rI,N")))]
1040   ""
1041   "@
1042    xor %r1,%2,%0
1043    eqv %r1,%N2,%0"
1044   [(set_attr "type" "ilog")])
1046 (define_insn "*xornot<mode>3"
1047   [(set (match_operand:I48MODE 0 "register_operand" "=r")
1048         (not:I48MODE (xor:I48MODE
1049                       (match_operand:I48MODE 1 "register_operand" "%rJ")
1050                       (match_operand:I48MODE 2 "register_operand" "rI"))))]
1051   ""
1052   "eqv %r1,%2,%0"
1053   [(set_attr "type" "ilog")])
1055 ;; Handle FFS and related insns iff we support CIX.
1057 (define_expand "ffsdi2"
1058   [(set (match_dup 2)
1059         (ctz:DI (match_operand:DI 1 "register_operand")))
1060    (set (match_dup 3)
1061         (plus:DI (match_dup 2) (const_int 1)))
1062    (set (match_operand:DI 0 "register_operand")
1063         (if_then_else:DI (eq (match_dup 1) (const_int 0))
1064                          (const_int 0) (match_dup 3)))]
1065   "TARGET_CIX"
1067   operands[2] = gen_reg_rtx (DImode);
1068   operands[3] = gen_reg_rtx (DImode);
1071 (define_insn "clzdi2"
1072   [(set (match_operand:DI 0 "register_operand" "=r")
1073         (clz:DI (match_operand:DI 1 "register_operand" "r")))]
1074   "TARGET_CIX"
1075   "ctlz %1,%0"
1076   [(set_attr "type" "mvi")])
1078 (define_insn "ctzdi2"
1079   [(set (match_operand:DI 0 "register_operand" "=r")
1080         (ctz:DI (match_operand:DI 1 "register_operand" "r")))]
1081   "TARGET_CIX"
1082   "cttz %1,%0"
1083   [(set_attr "type" "mvi")])
1085 (define_insn "popcountdi2"
1086   [(set (match_operand:DI 0 "register_operand" "=r")
1087         (popcount:DI (match_operand:DI 1 "register_operand" "r")))]
1088   "TARGET_CIX"
1089   "ctpop %1,%0"
1090   [(set_attr "type" "mvi")])
1092 (define_expand "bswapsi2"
1093   [(set (match_operand:SI 0 "register_operand")
1094         (bswap:SI (match_operand:SI 1 "register_operand")))]
1095   "!optimize_size"
1097   rtx t0, t1;
1099   t0 = gen_reg_rtx (DImode);
1100   t1 = gen_reg_rtx (DImode);
1102   emit_insn (gen_inslh (t0, gen_lowpart (DImode, operands[1]), GEN_INT (7)));
1103   emit_insn (gen_inswl_const (t1, gen_lowpart (HImode, operands[1]),
1104                               GEN_INT (24)));
1105   emit_insn (gen_iordi3 (t1, t0, t1));
1106   emit_insn (gen_lshrdi3 (t0, t1, GEN_INT (16)));
1107   emit_insn (gen_anddi3 (t1, t1, alpha_expand_zap_mask (0x5)));
1108   emit_insn (gen_anddi3 (t0, t0, alpha_expand_zap_mask (0xa)));
1109   emit_insn (gen_addsi3 (operands[0], gen_lowpart (SImode, t0),
1110                          gen_lowpart (SImode, t1)));
1111   DONE;
1114 (define_expand "bswapdi2"
1115   [(set (match_operand:DI 0 "register_operand")
1116         (bswap:DI (match_operand:DI 1 "register_operand")))]
1117   "!optimize_size"
1119   rtx t0, t1;
1121   t0 = gen_reg_rtx (DImode);
1122   t1 = gen_reg_rtx (DImode);
1124   /* This method of shifting and masking is not specific to Alpha, but
1125      is only profitable on Alpha because of our handy byte zap insn.  */
1127   emit_insn (gen_lshrdi3 (t0, operands[1], GEN_INT (32)));
1128   emit_insn (gen_ashldi3 (t1, operands[1], GEN_INT (32)));
1129   emit_insn (gen_iordi3 (t1, t0, t1));
1131   emit_insn (gen_lshrdi3 (t0, t1, GEN_INT (16)));
1132   emit_insn (gen_ashldi3 (t1, t1, GEN_INT (16)));
1133   emit_insn (gen_anddi3 (t0, t0, alpha_expand_zap_mask (0xcc)));
1134   emit_insn (gen_anddi3 (t1, t1, alpha_expand_zap_mask (0x33)));
1135   emit_insn (gen_iordi3 (t1, t0, t1));
1137   emit_insn (gen_lshrdi3 (t0, t1, GEN_INT (8)));
1138   emit_insn (gen_ashldi3 (t1, t1, GEN_INT (8)));
1139   emit_insn (gen_anddi3 (t0, t0, alpha_expand_zap_mask (0xaa)));
1140   emit_insn (gen_anddi3 (t1, t1, alpha_expand_zap_mask (0x55)));
1141   emit_insn (gen_iordi3 (operands[0], t0, t1));
1142   DONE;
1145 ;; Next come the shifts and the various extract and insert operations.
1147 (define_insn "ashldi3"
1148   [(set (match_operand:DI 0 "register_operand" "=r,r")
1149         (ashift:DI (match_operand:DI 1 "reg_or_0_operand" "rJ,rJ")
1150                    (match_operand:DI 2 "reg_or_6bit_operand" "P,rS")))]
1151   ""
1153   switch (which_alternative)
1154     {
1155     case 0:
1156       if (operands[2] == const1_rtx)
1157         return "addq %r1,%r1,%0";
1158       else
1159         return "s%P2addq %r1,0,%0";
1160     case 1:
1161       return "sll %r1,%2,%0";
1162     default:
1163       gcc_unreachable ();
1164     }
1166   [(set_attr "type" "iadd,shift")])
1168 (define_insn "ashlsi3"
1169   [(set (match_operand:SI 0 "register_operand" "=r")
1170         (ashift:SI (match_operand:SI 1 "reg_or_0_operand" "rJ")
1171                    (match_operand:SI 2 "const123_operand" "P")))]
1172   ""
1174   if (operands[2] == const1_rtx)
1175     return "addl %r1,%r1,%0";
1176   else
1177     return "s%P2addl %r1,0,%0";
1179   [(set_attr "type" "iadd")])
1181 (define_insn "*ashlsi_se"
1182   [(set (match_operand:DI 0 "register_operand" "=r")
1183         (sign_extend:DI
1184          (ashift:SI (match_operand:SI 1 "reg_or_0_operand" "rJ")
1185                     (match_operand:SI 2 "const123_operand" "P"))))]
1186   ""
1188   if (operands[2] == const1_rtx)
1189     return "addl %r1,%r1,%0";
1190   else
1191     return "s%P2addl %r1,0,%0";
1193   [(set_attr "type" "iadd")])
1195 (define_insn "lshrdi3"
1196   [(set (match_operand:DI 0 "register_operand" "=r")
1197         (lshiftrt:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1198                      (match_operand:DI 2 "reg_or_6bit_operand" "rS")))]
1199   ""
1200   "srl %r1,%2,%0"
1201   [(set_attr "type" "shift")])
1203 (define_insn "ashrdi3"
1204   [(set (match_operand:DI 0 "register_operand" "=r")
1205         (ashiftrt:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1206                      (match_operand:DI 2 "reg_or_6bit_operand" "rS")))]
1207   ""
1208   "sra %r1,%2,%0"
1209   [(set_attr "type" "shift")])
1211 (define_insn "extendqi<mode>2"
1212   [(set (match_operand:I24MODE 0 "register_operand" "=r")
1213         (sign_extend:I24MODE
1214          (match_operand:QI 1 "register_operand" "r")))]
1215   "TARGET_BWX"
1216   "sextb %1,%0"
1217   [(set_attr "type" "shift")])
1219 (define_expand "extendqidi2"
1220   [(set (match_operand:DI 0 "register_operand")
1221         (sign_extend:DI (match_operand:QI 1 "general_operand")))]
1222   ""
1224   if (TARGET_BWX)
1225     operands[1] = force_reg (QImode, operands[1]);
1226   else
1227     {
1228       rtx x, t1, t2, i56;
1230       if (unaligned_memory_operand (operands[1], QImode))
1231         {
1232           x = gen_unaligned_extendqidi (operands[0], XEXP (operands[1], 0));
1233           alpha_set_memflags (x, operands[1]);
1234           emit_insn (x);
1235           DONE;
1236         }
1238       t1 = gen_reg_rtx (DImode);
1239       t2 = gen_reg_rtx (DImode);
1240       i56 = GEN_INT (56);
1242       x = gen_lowpart (DImode, force_reg (QImode, operands[1]));
1243       emit_move_insn (t1, x);
1244       emit_insn (gen_ashldi3 (t2, t1, i56));
1245       emit_insn (gen_ashrdi3 (operands[0], t2, i56));
1246       DONE;
1247     }
1250 (define_insn "*extendqidi2_bwx"
1251   [(set (match_operand:DI 0 "register_operand" "=r")
1252         (sign_extend:DI (match_operand:QI 1 "register_operand" "r")))]
1253   "TARGET_BWX"
1254   "sextb %1,%0"
1255   [(set_attr "type" "shift")])
1257 (define_insn "extendhisi2"
1258   [(set (match_operand:SI 0 "register_operand" "=r")
1259         (sign_extend:SI (match_operand:HI 1 "register_operand" "r")))]
1260   "TARGET_BWX"
1261   "sextw %1,%0"
1262   [(set_attr "type" "shift")])
1264 (define_expand "extendhidi2"
1265   [(set (match_operand:DI 0 "register_operand")
1266         (sign_extend:DI (match_operand:HI 1 "general_operand")))]
1267   ""
1269   if (TARGET_BWX)
1270     operands[1] = force_reg (HImode, operands[1]);
1271   else
1272     {
1273       rtx x, t1, t2, i48;
1275       if (unaligned_memory_operand (operands[1], HImode))
1276         {
1277           x = gen_unaligned_extendhidi (operands[0], XEXP (operands[1], 0));
1278           alpha_set_memflags (x, operands[1]);
1279           emit_insn (x);
1280           DONE;
1281         }
1283       t1 = gen_reg_rtx (DImode);
1284       t2 = gen_reg_rtx (DImode);
1285       i48 = GEN_INT (48);
1287       x = gen_lowpart (DImode, force_reg (HImode, operands[1]));
1288       emit_move_insn (t1, x);
1289       emit_insn (gen_ashldi3 (t2, t1, i48));
1290       emit_insn (gen_ashrdi3 (operands[0], t2, i48));
1291       DONE;
1292     }
1295 (define_insn "*extendhidi2_bwx"
1296   [(set (match_operand:DI 0 "register_operand" "=r")
1297         (sign_extend:DI (match_operand:HI 1 "register_operand" "r")))]
1298   "TARGET_BWX"
1299   "sextw %1,%0"
1300   [(set_attr "type" "shift")])
1302 ;; Here's how we sign extend an unaligned byte and halfword.  Doing this
1303 ;; as a pattern saves one instruction.  The code is similar to that for
1304 ;; the unaligned loads (see below).
1306 ;; Operand 1 is the address, operand 0 is the result.
1308 (define_expand "unaligned_extendqidi"
1309   [(set (match_dup 3)
1310         (mem:DI (and:DI (match_operand:DI 1 "address_operand") (const_int -8))))
1311    (set (match_dup 4)
1312         (ashift:DI (match_dup 3)
1313                    (minus:DI (const_int 64)
1314                              (ashift:DI
1315                               (and:DI (match_dup 2) (const_int 7))
1316                               (const_int 3)))))
1317    (set (match_operand:QI 0 "register_operand")
1318         (ashiftrt:DI (match_dup 4) (const_int 56)))]
1319   ""
1321   operands[0] = gen_lowpart (DImode, operands[0]);
1322   operands[2] = get_unaligned_offset (operands[1], 1);
1323   operands[3] = gen_reg_rtx (DImode);
1324   operands[4] = gen_reg_rtx (DImode);
1327 (define_expand "unaligned_extendhidi"
1328   [(set (match_dup 3)
1329         (mem:DI (and:DI (match_operand:DI 1 "address_operand") (const_int -8))))
1330    (set (match_dup 4)
1331         (ashift:DI (match_dup 3)
1332                    (minus:DI (const_int 64)
1333                              (ashift:DI
1334                               (and:DI (match_dup 2) (const_int 7))
1335                               (const_int 3)))))
1336    (set (match_operand:HI 0 "register_operand")
1337         (ashiftrt:DI (match_dup 4) (const_int 48)))]
1338   ""
1340   operands[0] = gen_lowpart (DImode, operands[0]);
1341   operands[2] = get_unaligned_offset (operands[1], 2);
1342   operands[3] = gen_reg_rtx (DImode);
1343   operands[4] = gen_reg_rtx (DImode);
1346 (define_insn "*extxl_const"
1347   [(set (match_operand:DI 0 "register_operand" "=r")
1348         (zero_extract:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1349                          (match_operand:DI 2 "mode_width_operand" "n")
1350                          (match_operand:DI 3 "mul8_operand" "I")))]
1351   ""
1352   "ext%M2l %r1,%s3,%0"
1353   [(set_attr "type" "shift")])
1355 (define_insn "extxl"
1356   [(set (match_operand:DI 0 "register_operand" "=r")
1357         (zero_extract:DI
1358           (match_operand:DI 1 "reg_or_0_operand" "rJ")
1359           (match_operand:DI 2 "mode_width_operand" "n")
1360           (ashift:DI (match_operand:DI 3 "reg_or_8bit_operand" "rI")
1361                      (const_int 3))))]
1362   ""
1363   "ext%M2l %r1,%3,%0"
1364   [(set_attr "type" "shift")])
1366 ;; Combine has some strange notion of preserving existing undefined behavior
1367 ;; in shifts larger than a word size.  So capture these patterns that it
1368 ;; should have turned into zero_extracts.
1370 (define_insn "*extxl_1"
1371   [(set (match_operand:DI 0 "register_operand" "=r")
1372         (and:DI (lshiftrt:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1373                   (ashift:DI (match_operand:DI 2 "reg_or_8bit_operand" "rI")
1374                              (const_int 3)))
1375              (match_operand:DI 3 "mode_mask_operand" "n")))]
1376   ""
1377   "ext%U3l %1,%2,%0"
1378   [(set_attr "type" "shift")])
1380 (define_insn "*extql_2"
1381   [(set (match_operand:DI 0 "register_operand" "=r")
1382         (lshiftrt:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1383           (ashift:DI (match_operand:DI 2 "reg_or_8bit_operand" "rI")
1384                      (const_int 3))))]
1385   ""
1386   "extql %1,%2,%0"
1387   [(set_attr "type" "shift")])
1389 (define_insn "extqh"
1390   [(set (match_operand:DI 0 "register_operand" "=r")
1391         (ashift:DI
1392          (match_operand:DI 1 "reg_or_0_operand" "rJ")
1393           (minus:DI (const_int 64)
1394                     (ashift:DI
1395                      (and:DI
1396                       (match_operand:DI 2 "reg_or_8bit_operand" "rI")
1397                       (const_int 7))
1398                      (const_int 3)))))]
1399   ""
1400   "extqh %r1,%2,%0"
1401   [(set_attr "type" "shift")])
1403 (define_insn "extwh"
1404   [(set (match_operand:DI 0 "register_operand" "=r")
1405         (ashift:DI
1406          (and:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1407                  (const_int 65535))
1408          (minus:DI (const_int 64)
1409                     (ashift:DI
1410                      (and:DI
1411                       (match_operand:DI 2 "reg_or_8bit_operand" "rI")
1412                       (const_int 7))
1413                      (const_int 3)))))]
1414   ""
1415   "extwh %r1,%2,%0"
1416   [(set_attr "type" "shift")])
1418 (define_insn "extlh"
1419   [(set (match_operand:DI 0 "register_operand" "=r")
1420         (ashift:DI
1421          (and:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1422                  (const_int 2147483647))
1423          (minus:DI (const_int 64)
1424                     (ashift:DI
1425                      (and:DI
1426                       (match_operand:DI 2 "reg_or_8bit_operand" "rI")
1427                       (const_int 7))
1428                      (const_int 3)))))]
1429   ""
1430   "extlh %r1,%2,%0"
1431   [(set_attr "type" "shift")])
1433 ;; This converts an extXl into an extXh with an appropriate adjustment
1434 ;; to the address calculation.
1436 ;;(define_split
1437 ;;  [(set (match_operand:DI 0 "register_operand")
1438 ;;      (ashift:DI (zero_extract:DI (match_operand:DI 1 "register_operand")
1439 ;;                                  (match_operand:DI 2 "mode_width_operand")
1440 ;;                                  (ashift:DI (match_operand:DI 3)
1441 ;;                                             (const_int 3)))
1442 ;;                 (match_operand:DI 4 "const_int_operand")))
1443 ;;   (clobber (match_operand:DI 5 "register_operand"))]
1444 ;;  "INTVAL (operands[4]) == 64 - INTVAL (operands[2])"
1445 ;;  [(set (match_dup 5) (match_dup 6))
1446 ;;   (set (match_dup 0)
1447 ;;      (ashift:DI (zero_extract:DI (match_dup 1) (match_dup 2)
1448 ;;                                  (ashift:DI (plus:DI (match_dup 5)
1449 ;;                                                      (match_dup 7))
1450 ;;                                             (const_int 3)))
1451 ;;                 (match_dup 4)))]
1452 ;;  "
1454 ;;  operands[6] = plus_constant (DImode, operands[3],
1455 ;;                             INTVAL (operands[2]) / BITS_PER_UNIT);
1456 ;;  operands[7] = GEN_INT (- INTVAL (operands[2]) / BITS_PER_UNIT);
1457 ;;}")
1459 (define_insn "ins<modesuffix>l_const"
1460   [(set (match_operand:DI 0 "register_operand" "=r")
1461         (ashift:DI (zero_extend:DI
1462                     (match_operand:I124MODE 1 "register_operand" "r"))
1463                    (match_operand:DI 2 "mul8_operand" "I")))]
1464   ""
1465   "ins<modesuffix>l %1,%s2,%0"
1466   [(set_attr "type" "shift")])
1468 (define_insn "ins<modesuffix>l"
1469   [(set (match_operand:DI 0 "register_operand" "=r")
1470         (ashift:DI (zero_extend:DI
1471                     (match_operand:I124MODE 1 "register_operand" "r"))
1472                    (ashift:DI (match_operand:DI 2 "reg_or_8bit_operand" "rI")
1473                               (const_int 3))))]
1474   ""
1475   "ins<modesuffix>l %1,%2,%0"
1476   [(set_attr "type" "shift")])
1478 (define_insn "insql"
1479   [(set (match_operand:DI 0 "register_operand" "=r")
1480         (ashift:DI (match_operand:DI 1 "register_operand" "r")
1481                    (ashift:DI (match_operand:DI 2 "reg_or_8bit_operand" "rI")
1482                               (const_int 3))))]
1483   ""
1484   "insql %1,%2,%0"
1485   [(set_attr "type" "shift")])
1487 ;; Combine has this sometimes habit of moving the and outside of the
1488 ;; shift, making life more interesting.
1490 (define_insn "*insxl"
1491   [(set (match_operand:DI 0 "register_operand" "=r")
1492         (and:DI (ashift:DI (match_operand:DI 1 "register_operand" "r")
1493                            (match_operand:DI 2 "mul8_operand" "I"))
1494                 (match_operand:DI 3 "const_int_operand" "i")))]
1495   "((unsigned HOST_WIDE_INT) 0xff << INTVAL (operands[2])
1496     == (unsigned HOST_WIDE_INT) INTVAL (operands[3]))
1497     || ((unsigned HOST_WIDE_INT) 0xffff << INTVAL (operands[2])
1498         == (unsigned HOST_WIDE_INT) INTVAL (operands[3]))
1499     || ((unsigned HOST_WIDE_INT) 0xffffffff << INTVAL (operands[2])
1500         == (unsigned HOST_WIDE_INT) INTVAL (operands[3]))"
1502   if ((unsigned HOST_WIDE_INT) 0xff << INTVAL (operands[2])
1503       == (unsigned HOST_WIDE_INT) INTVAL (operands[3]))
1504     return "insbl %1,%s2,%0";
1505   if ((unsigned HOST_WIDE_INT) 0xffff << INTVAL (operands[2])
1506       == (unsigned HOST_WIDE_INT) INTVAL (operands[3]))
1507     return "inswl %1,%s2,%0";
1508   if ((unsigned HOST_WIDE_INT) 0xffffffff << INTVAL (operands[2])
1509       == (unsigned HOST_WIDE_INT) INTVAL (operands[3]))
1510     return "insll %1,%s2,%0";
1512   gcc_unreachable ();
1514   [(set_attr "type" "shift")])
1516 ;; We do not include the insXh insns because they are complex to express
1517 ;; and it does not appear that we would ever want to generate them.
1519 ;; Since we need them for block moves, though, cop out and use unspec.
1521 (define_insn "insxh"
1522   [(set (match_operand:DI 0 "register_operand" "=r")
1523         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
1524                     (match_operand:DI 2 "mode_width_operand" "n")
1525                     (match_operand:DI 3 "reg_or_8bit_operand" "rI")]
1526                    UNSPEC_INSXH))]
1527   ""
1528   "ins%M2h %1,%3,%0"
1529   [(set_attr "type" "shift")])
1531 (define_insn "mskxl"
1532   [(set (match_operand:DI 0 "register_operand" "=r")
1533         (and:DI (not:DI (ashift:DI
1534                          (match_operand:DI 2 "mode_mask_operand" "n")
1535                          (ashift:DI
1536                           (match_operand:DI 3 "reg_or_8bit_operand" "rI")
1537                           (const_int 3))))
1538                 (match_operand:DI 1 "reg_or_0_operand" "rJ")))]
1539   ""
1540   "msk%U2l %r1,%3,%0"
1541   [(set_attr "type" "shift")])
1543 ;; We do not include the mskXh insns because it does not appear we would
1544 ;; ever generate one.
1546 ;; Again, we do for block moves and we use unspec again.
1548 (define_insn "mskxh"
1549   [(set (match_operand:DI 0 "register_operand" "=r")
1550         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
1551                     (match_operand:DI 2 "mode_width_operand" "n")
1552                     (match_operand:DI 3 "reg_or_8bit_operand" "rI")]
1553                    UNSPEC_MSKXH))]
1554   ""
1555   "msk%M2h %1,%3,%0"
1556   [(set_attr "type" "shift")])
1558 ;; Prefer AND + NE over LSHIFTRT + AND.
1560 (define_insn_and_split "*ze_and_ne"
1561   [(set (match_operand:DI 0 "register_operand" "=r")
1562         (zero_extract:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
1563                          (const_int 1)
1564                          (match_operand 2 "const_int_operand" "I")))]
1565   "(unsigned HOST_WIDE_INT) INTVAL (operands[2]) < 8"
1566   "#"
1567   "(unsigned HOST_WIDE_INT) INTVAL (operands[2]) < 8"
1568   [(set (match_dup 0)
1569         (and:DI (match_dup 1) (match_dup 3)))
1570    (set (match_dup 0)
1571         (ne:DI (match_dup 0) (const_int 0)))]
1572   "operands[3] = GEN_INT (1 << INTVAL (operands[2]));")
1574 ;; Floating-point operations.  All the double-precision insns can extend
1575 ;; from single, so indicate that.  The exception are the ones that simply
1576 ;; play with the sign bits; it's not clear what to do there.
1578 (define_mode_iterator FMODE [SF DF])
1580 (define_mode_attr opmode [(SF "si") (DF "di")])
1582 (define_insn "abs<mode>2"
1583   [(set (match_operand:FMODE 0 "register_operand" "=f")
1584         (abs:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "fG")))]
1585   "TARGET_FP"
1586   "cpys $f31,%R1,%0"
1587   [(set_attr "type" "fcpys")])
1589 (define_insn "*nabs<mode>2"
1590   [(set (match_operand:FMODE 0 "register_operand" "=f")
1591         (neg:FMODE
1592          (abs:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "fG"))))]
1593   "TARGET_FP"
1594   "cpysn $f31,%R1,%0"
1595   [(set_attr "type" "fadd")])
1597 (define_expand "abstf2"
1598   [(parallel [(set (match_operand:TF 0 "register_operand")
1599                    (abs:TF (match_operand:TF 1 "reg_or_0_operand")))
1600               (use (match_dup 2))])]
1601   "TARGET_HAS_XFLOATING_LIBS"
1602   "operands[2] = force_reg (DImode, GEN_INT (HOST_WIDE_INT_1U << 63));")
1604 (define_insn_and_split "*abstf_internal"
1605   [(set (match_operand:TF 0 "register_operand" "=r")
1606         (abs:TF (match_operand:TF 1 "reg_or_0_operand" "rG")))
1607    (use (match_operand:DI 2 "register_operand" "r"))]
1608   "TARGET_HAS_XFLOATING_LIBS"
1609   "#"
1610   "&& reload_completed"
1611   [(const_int 0)]
1612   "alpha_split_tfmode_frobsign (operands, gen_andnotdi3); DONE;")
1614 (define_insn "neg<mode>2"
1615   [(set (match_operand:FMODE 0 "register_operand" "=f")
1616         (neg:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "fG")))]
1617   "TARGET_FP"
1618   "cpysn %R1,%R1,%0"
1619   [(set_attr "type" "fadd")])
1621 (define_expand "negtf2"
1622   [(parallel [(set (match_operand:TF 0 "register_operand")
1623                    (neg:TF (match_operand:TF 1 "reg_or_0_operand")))
1624               (use (match_dup 2))])]
1625   "TARGET_HAS_XFLOATING_LIBS"
1626   "operands[2] = force_reg (DImode, GEN_INT (HOST_WIDE_INT_1U << 63));")
1628 (define_insn_and_split "*negtf_internal"
1629   [(set (match_operand:TF 0 "register_operand" "=r")
1630         (neg:TF (match_operand:TF 1 "reg_or_0_operand" "rG")))
1631    (use (match_operand:DI 2 "register_operand" "r"))]
1632   "TARGET_HAS_XFLOATING_LIBS"
1633   "#"
1634   "&& reload_completed"
1635   [(const_int 0)]
1636   "alpha_split_tfmode_frobsign (operands, gen_xordi3); DONE;")
1638 (define_insn "copysign<mode>3"
1639   [(set (match_operand:FMODE 0 "register_operand" "=f")
1640         (unspec:FMODE [(match_operand:FMODE 1 "reg_or_0_operand" "fG")
1641                        (match_operand:FMODE 2 "reg_or_0_operand" "fG")]
1642                       UNSPEC_COPYSIGN))]
1643   "TARGET_FP"
1644   "cpys %R2,%R1,%0"
1645   [(set_attr "type" "fadd")])
1647 (define_insn "*ncopysign<mode>3"
1648   [(set (match_operand:FMODE 0 "register_operand" "=f")
1649         (neg:FMODE
1650          (unspec:FMODE [(match_operand:FMODE 1 "reg_or_0_operand" "fG")
1651                         (match_operand:FMODE 2 "reg_or_0_operand" "fG")]
1652                        UNSPEC_COPYSIGN)))]
1653   "TARGET_FP"
1654   "cpysn %R2,%R1,%0"
1655   [(set_attr "type" "fadd")])
1657 (define_insn "add<mode>3"
1658   [(set (match_operand:FMODE 0 "register_operand" "=f,&f")
1659         (plus:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "%fG,fG")
1660                     (match_operand:FMODE 2 "reg_or_0_operand" "fG,fG")))]
1661   "TARGET_FP"
1662   "add<modesuffix>%/ %R1,%R2,%0"
1663   [(set_attr "type" "fadd")
1664    (set_attr "trap" "yes")
1665    (set_attr "round_suffix" "normal")
1666    (set_attr "trap_suffix" "u_su_sui")
1667    (set (attr "enabled")
1668      (cond [(eq_attr "alternative" "0")
1669               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
1670            ]
1671            (symbol_ref "true")))])
1673 (define_insn "*adddf_ext1"
1674   [(set (match_operand:DF 0 "register_operand" "=f")
1675         (plus:DF (float_extend:DF
1676                   (match_operand:SF 1 "reg_or_0_operand" "fG"))
1677                  (match_operand:DF 2 "reg_or_0_operand" "fG")))]
1678   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1679   "add%-%/ %R1,%R2,%0"
1680   [(set_attr "type" "fadd")
1681    (set_attr "trap" "yes")
1682    (set_attr "round_suffix" "normal")
1683    (set_attr "trap_suffix" "u_su_sui")])
1685 (define_insn "*adddf_ext2"
1686   [(set (match_operand:DF 0 "register_operand" "=f")
1687         (plus:DF (float_extend:DF
1688                   (match_operand:SF 1 "reg_or_0_operand" "%fG"))
1689                  (float_extend:DF
1690                   (match_operand:SF 2 "reg_or_0_operand" "fG"))))]
1691   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1692   "add%-%/ %R1,%R2,%0"
1693   [(set_attr "type" "fadd")
1694    (set_attr "trap" "yes")
1695    (set_attr "round_suffix" "normal")
1696    (set_attr "trap_suffix" "u_su_sui")])
1698 (define_expand "addtf3"
1699   [(use (match_operand:TF 0 "register_operand"))
1700    (use (match_operand:TF 1 "general_operand"))
1701    (use (match_operand:TF 2 "general_operand"))]
1702   "TARGET_HAS_XFLOATING_LIBS"
1703   "alpha_emit_xfloating_arith (PLUS, operands); DONE;")
1705 (define_insn "sub<mode>3"
1706   [(set (match_operand:FMODE 0 "register_operand" "=f,&f")
1707         (minus:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "fG,fG")
1708                      (match_operand:FMODE 2 "reg_or_0_operand" "fG,fG")))]
1709   "TARGET_FP"
1710   "sub<modesuffix>%/ %R1,%R2,%0"
1711   [(set_attr "type" "fadd")
1712    (set_attr "trap" "yes")
1713    (set_attr "round_suffix" "normal")
1714    (set_attr "trap_suffix" "u_su_sui")
1715    (set (attr "enabled")
1716      (cond [(eq_attr "alternative" "0")
1717               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
1718            ]
1719            (symbol_ref "true")))])
1721 (define_insn "*subdf_ext1"
1722   [(set (match_operand:DF 0 "register_operand" "=f")
1723         (minus:DF (float_extend:DF
1724                    (match_operand:SF 1 "reg_or_0_operand" "fG"))
1725                   (match_operand:DF 2 "reg_or_0_operand" "fG")))]
1726   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1727   "sub%-%/ %R1,%R2,%0"
1728   [(set_attr "type" "fadd")
1729    (set_attr "trap" "yes")
1730    (set_attr "round_suffix" "normal")
1731    (set_attr "trap_suffix" "u_su_sui")])
1733 (define_insn "*subdf_ext2"
1734   [(set (match_operand:DF 0 "register_operand" "=f")
1735         (minus:DF (match_operand:DF 1 "reg_or_0_operand" "fG")
1736                   (float_extend:DF
1737                    (match_operand:SF 2 "reg_or_0_operand" "fG"))))]
1738   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1739   "sub%-%/ %R1,%R2,%0"
1740   [(set_attr "type" "fadd")
1741    (set_attr "trap" "yes")
1742    (set_attr "round_suffix" "normal")
1743    (set_attr "trap_suffix" "u_su_sui")])
1745 (define_insn "*subdf_ext3"
1746   [(set (match_operand:DF 0 "register_operand" "=f")
1747         (minus:DF (float_extend:DF
1748                    (match_operand:SF 1 "reg_or_0_operand" "fG"))
1749                   (float_extend:DF
1750                    (match_operand:SF 2 "reg_or_0_operand" "fG"))))]
1751   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1752   "sub%-%/ %R1,%R2,%0"
1753   [(set_attr "type" "fadd")
1754    (set_attr "trap" "yes")
1755    (set_attr "round_suffix" "normal")
1756    (set_attr "trap_suffix" "u_su_sui")])
1758 (define_expand "subtf3"
1759   [(use (match_operand:TF 0 "register_operand"))
1760    (use (match_operand:TF 1 "general_operand"))
1761    (use (match_operand:TF 2 "general_operand"))]
1762   "TARGET_HAS_XFLOATING_LIBS"
1763   "alpha_emit_xfloating_arith (MINUS, operands); DONE;")
1765 (define_insn "mul<mode>3"
1766   [(set (match_operand:FMODE 0 "register_operand" "=f,&f")
1767         (mult:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "%fG,fG")
1768                     (match_operand:FMODE 2 "reg_or_0_operand" "fG,fG")))]
1769   "TARGET_FP"
1770   "mul<modesuffix>%/ %R1,%R2,%0"
1771   [(set_attr "type" "fmul")
1772    (set_attr "trap" "yes")
1773    (set_attr "round_suffix" "normal")
1774    (set_attr "trap_suffix" "u_su_sui")
1775    (set (attr "enabled")
1776      (cond [(eq_attr "alternative" "0")
1777               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
1778            ]
1779            (symbol_ref "true")))])
1781 (define_insn "*muldf_ext1"
1782   [(set (match_operand:DF 0 "register_operand" "=f")
1783         (mult:DF (float_extend:DF
1784                   (match_operand:SF 1 "reg_or_0_operand" "fG"))
1785                  (match_operand:DF 2 "reg_or_0_operand" "fG")))]
1786   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1787   "mul%-%/ %R1,%R2,%0"
1788   [(set_attr "type" "fmul")
1789    (set_attr "trap" "yes")
1790    (set_attr "round_suffix" "normal")
1791    (set_attr "trap_suffix" "u_su_sui")])
1793 (define_insn "*muldf_ext2"
1794   [(set (match_operand:DF 0 "register_operand" "=f")
1795         (mult:DF (float_extend:DF
1796                   (match_operand:SF 1 "reg_or_0_operand" "%fG"))
1797                  (float_extend:DF
1798                   (match_operand:SF 2 "reg_or_0_operand" "fG"))))]
1799   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1800   "mul%-%/ %R1,%R2,%0"
1801   [(set_attr "type" "fmul")
1802    (set_attr "trap" "yes")
1803    (set_attr "round_suffix" "normal")
1804    (set_attr "trap_suffix" "u_su_sui")])
1806 (define_expand "multf3"
1807   [(use (match_operand:TF 0 "register_operand"))
1808    (use (match_operand:TF 1 "general_operand"))
1809    (use (match_operand:TF 2 "general_operand"))]
1810   "TARGET_HAS_XFLOATING_LIBS"
1811   "alpha_emit_xfloating_arith (MULT, operands); DONE;")
1813 (define_insn "div<mode>3"
1814   [(set (match_operand:FMODE 0 "register_operand" "=f,&f")
1815         (div:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "fG,fG")
1816                    (match_operand:FMODE 2 "reg_or_0_operand" "fG,fG")))]
1817   "TARGET_FP"
1818   "div<modesuffix>%/ %R1,%R2,%0"
1819   [(set_attr "type" "fdiv")
1820    (set_attr "opsize" "<opmode>")
1821    (set_attr "trap" "yes")
1822    (set_attr "round_suffix" "normal")
1823    (set_attr "trap_suffix" "u_su_sui")
1824    (set (attr "enabled")
1825      (cond [(eq_attr "alternative" "0")
1826               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
1827            ]
1828            (symbol_ref "true")))])
1830 (define_insn "*divdf_ext1"
1831   [(set (match_operand:DF 0 "register_operand" "=f")
1832         (div:DF (float_extend:DF (match_operand:SF 1 "reg_or_0_operand" "fG"))
1833                 (match_operand:DF 2 "reg_or_0_operand" "fG")))]
1834   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1835   "div%-%/ %R1,%R2,%0"
1836   [(set_attr "type" "fdiv")
1837    (set_attr "trap" "yes")
1838    (set_attr "round_suffix" "normal")
1839    (set_attr "trap_suffix" "u_su_sui")])
1841 (define_insn "*divdf_ext2"
1842   [(set (match_operand:DF 0 "register_operand" "=f")
1843         (div:DF (match_operand:DF 1 "reg_or_0_operand" "fG")
1844                 (float_extend:DF
1845                  (match_operand:SF 2 "reg_or_0_operand" "fG"))))]
1846   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1847   "div%-%/ %R1,%R2,%0"
1848   [(set_attr "type" "fdiv")
1849    (set_attr "trap" "yes")
1850    (set_attr "round_suffix" "normal")
1851    (set_attr "trap_suffix" "u_su_sui")])
1853 (define_insn "*divdf_ext3"
1854   [(set (match_operand:DF 0 "register_operand" "=f")
1855         (div:DF (float_extend:DF
1856                  (match_operand:SF 1 "reg_or_0_operand" "fG"))
1857                 (float_extend:DF
1858                  (match_operand:SF 2 "reg_or_0_operand" "fG"))))]
1859   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1860   "div%-%/ %R1,%R2,%0"
1861   [(set_attr "type" "fdiv")
1862    (set_attr "trap" "yes")
1863    (set_attr "round_suffix" "normal")
1864    (set_attr "trap_suffix" "u_su_sui")])
1866 (define_expand "divtf3"
1867   [(use (match_operand:TF 0 "register_operand"))
1868    (use (match_operand:TF 1 "general_operand"))
1869    (use (match_operand:TF 2 "general_operand"))]
1870   "TARGET_HAS_XFLOATING_LIBS"
1871   "alpha_emit_xfloating_arith (DIV, operands); DONE;")
1873 (define_insn "sqrt<mode>2"
1874   [(set (match_operand:FMODE 0 "register_operand" "=f,&f")
1875         (sqrt:FMODE (match_operand:FMODE 1 "reg_or_0_operand" "fG,fG")))]
1876   "TARGET_FP && TARGET_FIX"
1877   "sqrt<modesuffix>%/ %R1,%0"
1878   [(set_attr "type" "fsqrt")
1879    (set_attr "opsize" "<opmode>")
1880    (set_attr "trap" "yes")
1881    (set_attr "round_suffix" "normal")
1882    (set_attr "trap_suffix" "u_su_sui")
1883    (set (attr "enabled")
1884      (cond [(eq_attr "alternative" "0")
1885               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
1886            ]
1887            (symbol_ref "true")))])
1889 ;; Define conversion operators between DFmode and SImode, using the cvtql
1890 ;; instruction.  To allow combine et al to do useful things, we keep the
1891 ;; operation as a unit until after reload, at which point we split the
1892 ;; instructions.
1894 ;; Note that we (attempt to) only consider this optimization when the
1895 ;; ultimate destination is memory.  If we will be doing further integer
1896 ;; processing, it is cheaper to do the truncation in the int regs.
1898 (define_insn "*cvtql"
1899   [(set (match_operand:SF 0 "register_operand" "=f")
1900         (unspec:SF [(match_operand:DI 1 "reg_or_0_operand" "fG")]
1901                    UNSPEC_CVTQL))]
1902   "TARGET_FP"
1903   "cvtql%/ %R1,%0"
1904   [(set_attr "type" "fadd")
1905    (set_attr "trap" "yes")
1906    (set_attr "trap_suffix" "v_sv")])
1908 (define_insn_and_split "*fix_truncdfsi_ieee"
1909   [(set (match_operand:SI 0 "memory_operand" "=m")
1910         (subreg:SI
1911           (match_operator:DI 4 "fix_operator" 
1912             [(match_operand:DF 1 "reg_or_0_operand" "fG")]) 0))
1913    (clobber (match_scratch:DI 2 "=&f"))
1914    (clobber (match_scratch:SF 3 "=&f"))]
1915   "TARGET_FP && alpha_fptm >= ALPHA_FPTM_SU"
1916   "#"
1917   "&& reload_completed"
1918   [(set (match_dup 2) (match_op_dup 4 [(match_dup 1)]))
1919    (set (match_dup 3) (unspec:SF [(match_dup 2)] UNSPEC_CVTQL))
1920    (set (match_dup 5) (match_dup 3))]
1922   operands[5] = adjust_address (operands[0], SFmode, 0);
1924   [(set_attr "type" "fadd")
1925    (set_attr "trap" "yes")])
1927 (define_insn_and_split "*fix_truncdfsi_internal"
1928   [(set (match_operand:SI 0 "memory_operand" "=m")
1929         (subreg:SI
1930           (match_operator:DI 3 "fix_operator" 
1931             [(match_operand:DF 1 "reg_or_0_operand" "fG")]) 0))
1932    (clobber (match_scratch:DI 2 "=f"))]
1933   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
1934   "#"
1935   "&& reload_completed"
1936   [(set (match_dup 2) (match_op_dup 3 [(match_dup 1)]))
1937    (set (match_dup 4) (unspec:SF [(match_dup 2)] UNSPEC_CVTQL))
1938    (set (match_dup 5) (match_dup 4))]
1940   operands[4] = gen_rtx_REG (SFmode, REGNO (operands[2]));
1941   operands[5] = adjust_address (operands[0], SFmode, 0);
1943   [(set_attr "type" "fadd")
1944    (set_attr "trap" "yes")])
1946 (define_insn "*fix_truncdfdi2"
1947   [(set (match_operand:DI 0 "reg_no_subreg_operand" "=f,&f")
1948         (match_operator:DI 2 "fix_operator" 
1949           [(match_operand:DF 1 "reg_or_0_operand" "fG,fG")]))]
1950   "TARGET_FP"
1951   "cvt%-q%/ %R1,%0"
1952   [(set_attr "type" "fadd")
1953    (set_attr "trap" "yes")
1954    (set_attr "round_suffix" "c")
1955    (set_attr "trap_suffix" "v_sv_svi")
1956    (set (attr "enabled")
1957      (cond [(eq_attr "alternative" "0")
1958               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
1959            ]
1960            (symbol_ref "true")))])
1962 (define_expand "fix_truncdfdi2"
1963   [(set (match_operand:DI 0 "reg_no_subreg_operand")
1964         (fix:DI (match_operand:DF 1 "reg_or_0_operand")))]
1965   "TARGET_FP")
1967 (define_expand "fixuns_truncdfdi2"
1968   [(set (match_operand:DI 0 "reg_no_subreg_operand")
1969         (unsigned_fix:DI (match_operand:DF 1 "reg_or_0_operand")))]
1970   "TARGET_FP")
1972 ;; Likewise between SFmode and SImode.
1974 (define_insn_and_split "*fix_truncsfsi_ieee"
1975   [(set (match_operand:SI 0 "memory_operand" "=m")
1976         (subreg:SI
1977           (match_operator:DI 4 "fix_operator" 
1978             [(float_extend:DF
1979                (match_operand:SF 1 "reg_or_0_operand" "fG"))]) 0))
1980    (clobber (match_scratch:DI 2 "=&f"))
1981    (clobber (match_scratch:SF 3 "=&f"))]
1982   "TARGET_FP && alpha_fptm >= ALPHA_FPTM_SU"
1983   "#"
1984   "&& reload_completed"
1985   [(set (match_dup 2) (match_op_dup 4 [(float_extend:DF (match_dup 1))]))
1986    (set (match_dup 3) (unspec:SF [(match_dup 2)] UNSPEC_CVTQL))
1987    (set (match_dup 5) (match_dup 3))]
1988   "operands[5] = adjust_address (operands[0], SFmode, 0);"
1989   [(set_attr "type" "fadd")
1990    (set_attr "trap" "yes")])
1992 (define_insn_and_split "*fix_truncsfsi_internal"
1993   [(set (match_operand:SI 0 "memory_operand" "=m")
1994         (subreg:SI
1995           (match_operator:DI 3 "fix_operator" 
1996             [(float_extend:DF
1997                (match_operand:SF 1 "reg_or_0_operand" "fG"))]) 0))
1998    (clobber (match_scratch:DI 2 "=f"))]
1999   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2000   "#"
2001   "&& reload_completed"
2002   [(set (match_dup 2) (match_op_dup 3 [(float_extend:DF (match_dup 1))]))
2003    (set (match_dup 4) (unspec:SF [(match_dup 2)] UNSPEC_CVTQL))
2004    (set (match_dup 5) (match_dup 4))]
2006   operands[4] = gen_rtx_REG (SFmode, REGNO (operands[2]));
2007   operands[5] = adjust_address (operands[0], SFmode, 0);
2009   [(set_attr "type" "fadd")
2010    (set_attr "trap" "yes")])
2012 (define_insn "*fix_truncsfdi2"
2013   [(set (match_operand:DI 0 "reg_no_subreg_operand" "=f,&f")
2014         (match_operator:DI 2 "fix_operator" 
2015           [(float_extend:DF (match_operand:SF 1 "reg_or_0_operand" "fG,fG"))]))]
2016   "TARGET_FP"
2017   "cvt%-q%/ %R1,%0"
2018   [(set_attr "type" "fadd")
2019    (set_attr "trap" "yes")
2020    (set_attr "round_suffix" "c")
2021    (set_attr "trap_suffix" "v_sv_svi")
2022    (set (attr "enabled")
2023      (cond [(eq_attr "alternative" "0")
2024               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
2025            ]
2026            (symbol_ref "true")))])
2028 (define_expand "fix_truncsfdi2"
2029   [(set (match_operand:DI 0 "reg_no_subreg_operand")
2030         (fix:DI (float_extend:DF (match_operand:SF 1 "reg_or_0_operand"))))]
2031   "TARGET_FP")
2033 (define_expand "fixuns_truncsfdi2"
2034   [(set (match_operand:DI 0 "reg_no_subreg_operand")
2035         (unsigned_fix:DI
2036           (float_extend:DF (match_operand:SF 1 "reg_or_0_operand"))))]
2037   "TARGET_FP")
2039 (define_expand "fix_trunctfdi2"
2040   [(use (match_operand:DI 0 "register_operand"))
2041    (use (match_operand:TF 1 "general_operand"))]
2042   "TARGET_HAS_XFLOATING_LIBS"
2043   "alpha_emit_xfloating_cvt (FIX, operands); DONE;")
2045 (define_expand "fixuns_trunctfdi2"
2046   [(use (match_operand:DI 0 "register_operand"))
2047    (use (match_operand:TF 1 "general_operand"))]
2048   "TARGET_HAS_XFLOATING_LIBS"
2049   "alpha_emit_xfloating_cvt (UNSIGNED_FIX, operands); DONE;")
2051 (define_insn "floatdisf2"
2052   [(set (match_operand:SF 0 "register_operand" "=f,&f")
2053         (float:SF (match_operand:DI 1 "reg_no_subreg_operand" "f,f")))]
2054   "TARGET_FP"
2055   "cvtq%,%/ %1,%0"
2056   [(set_attr "type" "fadd")
2057    (set_attr "trap" "yes")
2058    (set_attr "round_suffix" "normal")
2059    (set_attr "trap_suffix" "sui")
2060    (set (attr "enabled")
2061      (cond [(eq_attr "alternative" "0")
2062               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
2063            ]
2064            (symbol_ref "true")))])
2066 (define_insn_and_split "*floatsisf2_ieee"
2067   [(set (match_operand:SF 0 "register_operand" "=&f")
2068         (float:SF (match_operand:SI 1 "memory_operand" "m")))
2069    (clobber (match_scratch:DI 2 "=&f"))
2070    (clobber (match_scratch:SF 3 "=&f"))]
2071   "TARGET_FP && alpha_fptm >= ALPHA_FPTM_SU"
2072   "#"
2073   "&& reload_completed"
2074   [(set (match_dup 3) (match_dup 1))
2075    (set (match_dup 2) (unspec:DI [(match_dup 3)] UNSPEC_CVTLQ))
2076    (set (match_dup 0) (float:SF (match_dup 2)))]
2077   "operands[1] = adjust_address (operands[1], SFmode, 0);")
2079 (define_insn_and_split "*floatsisf2"
2080   [(set (match_operand:SF 0 "register_operand" "=f")
2081         (float:SF (match_operand:SI 1 "memory_operand" "m")))]
2082   "TARGET_FP"
2083   "#"
2084   "&& reload_completed"
2085   [(set (match_dup 0) (match_dup 1))
2086    (set (match_dup 2) (unspec:DI [(match_dup 0)] UNSPEC_CVTLQ))
2087    (set (match_dup 0) (float:SF (match_dup 2)))]
2089   operands[1] = adjust_address (operands[1], SFmode, 0);
2090   operands[2] = gen_rtx_REG (DImode, REGNO (operands[0]));
2093 (define_insn "floatdidf2"
2094   [(set (match_operand:DF 0 "register_operand" "=f,&f")
2095         (float:DF (match_operand:DI 1 "reg_no_subreg_operand" "f,f")))]
2096   "TARGET_FP"
2097   "cvtq%-%/ %1,%0"
2098   [(set_attr "type" "fadd")
2099    (set_attr "trap" "yes")
2100    (set_attr "round_suffix" "normal")
2101    (set_attr "trap_suffix" "sui")
2102    (set (attr "enabled")
2103      (cond [(eq_attr "alternative" "0")
2104               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
2105            ]
2106            (symbol_ref "true")))])
2108 (define_insn_and_split "*floatsidf2_ieee"
2109   [(set (match_operand:DF 0 "register_operand" "=&f")
2110         (float:DF (match_operand:SI 1 "memory_operand" "m")))
2111    (clobber (match_scratch:DI 2 "=&f"))
2112    (clobber (match_scratch:SF 3 "=&f"))]
2113   "TARGET_FP && alpha_fptm >= ALPHA_FPTM_SU"
2114   "#"
2115   "&& reload_completed"
2116   [(set (match_dup 3) (match_dup 1))
2117    (set (match_dup 2) (unspec:DI [(match_dup 3)] UNSPEC_CVTLQ))
2118    (set (match_dup 0) (float:DF (match_dup 2)))]
2119   "operands[1] = adjust_address (operands[1], SFmode, 0);")
2121 (define_insn_and_split "*floatsidf2"
2122   [(set (match_operand:DF 0 "register_operand" "=f")
2123         (float:DF (match_operand:SI 1 "memory_operand" "m")))]
2124   "TARGET_FP"
2125   "#"
2126   "&& reload_completed"
2127   [(set (match_dup 3) (match_dup 1))
2128    (set (match_dup 2) (unspec:DI [(match_dup 3)] UNSPEC_CVTLQ))
2129    (set (match_dup 0) (float:DF (match_dup 2)))]
2131   operands[1] = adjust_address (operands[1], SFmode, 0);
2132   operands[2] = gen_rtx_REG (DImode, REGNO (operands[0]));
2133   operands[3] = gen_rtx_REG (SFmode, REGNO (operands[0]));
2136 (define_expand "floatditf2"
2137   [(use (match_operand:TF 0 "register_operand"))
2138    (use (match_operand:DI 1 "general_operand"))]
2139   "TARGET_HAS_XFLOATING_LIBS"
2140   "alpha_emit_xfloating_cvt (FLOAT, operands); DONE;")
2142 (define_expand "floatunsdisf2"
2143   [(use (match_operand:SF 0 "register_operand"))
2144    (use (match_operand:DI 1 "register_operand"))]
2145   "TARGET_FP"
2146   "alpha_emit_floatuns (operands); DONE;")
2148 (define_expand "floatunsdidf2"
2149   [(use (match_operand:DF 0 "register_operand"))
2150    (use (match_operand:DI 1 "register_operand"))]
2151   "TARGET_FP"
2152   "alpha_emit_floatuns (operands); DONE;")
2154 (define_expand "floatunsditf2"
2155   [(use (match_operand:TF 0 "register_operand"))
2156    (use (match_operand:DI 1 "general_operand"))]
2157   "TARGET_HAS_XFLOATING_LIBS"
2158   "alpha_emit_xfloating_cvt (UNSIGNED_FLOAT, operands); DONE;")
2160 (define_expand "extendsfdf2"
2161   [(set (match_operand:DF 0 "register_operand")
2162         (float_extend:DF (match_operand:SF 1 "nonimmediate_operand")))]
2163   "TARGET_FP"
2165   if (alpha_fptm >= ALPHA_FPTM_SU)
2166     operands[1] = force_reg (SFmode, operands[1]);
2169 ;; The Unicos/Mk assembler doesn't support cvtst, but we've already
2170 ;; asserted that alpha_fptm == ALPHA_FPTM_N.
2172 (define_insn "*extendsfdf2_ieee"
2173   [(set (match_operand:DF 0 "register_operand" "=&f")
2174         (float_extend:DF (match_operand:SF 1 "register_operand" "f")))]
2175   "TARGET_FP && alpha_fptm >= ALPHA_FPTM_SU"
2176   "cvtsts %1,%0"
2177   [(set_attr "type" "fadd")
2178    (set_attr "trap" "yes")])
2180 (define_insn "*extendsfdf2_internal"
2181   [(set (match_operand:DF 0 "register_operand" "=f,f,m")
2182         (float_extend:DF (match_operand:SF 1 "nonimmediate_operand" "f,m,f")))]
2183   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2184   "@
2185    cpys %1,%1,%0
2186    ld%, %0,%1
2187    st%- %1,%0"
2188   [(set_attr "type" "fcpys,fld,fst")])
2190 ;; Use register_operand for operand 1 to prevent compress_float_constant
2191 ;; from doing something silly.  When optimizing we'll put things back 
2192 ;; together anyway.
2193 (define_expand "extendsftf2"
2194   [(use (match_operand:TF 0 "register_operand"))
2195    (use (match_operand:SF 1 "register_operand"))]
2196   "TARGET_HAS_XFLOATING_LIBS"
2198   rtx tmp = gen_reg_rtx (DFmode);
2199   emit_insn (gen_extendsfdf2 (tmp, operands[1]));
2200   emit_insn (gen_extenddftf2 (operands[0], tmp));
2201   DONE;
2204 (define_expand "extenddftf2"
2205   [(use (match_operand:TF 0 "register_operand"))
2206    (use (match_operand:DF 1 "register_operand"))]
2207   "TARGET_HAS_XFLOATING_LIBS"
2208   "alpha_emit_xfloating_cvt (FLOAT_EXTEND, operands); DONE;")
2210 (define_insn "truncdfsf2"
2211   [(set (match_operand:SF 0 "register_operand" "=f,&f")
2212         (float_truncate:SF (match_operand:DF 1 "reg_or_0_operand" "fG,fG")))]
2213   "TARGET_FP"
2214   "cvt%-%,%/ %R1,%0"
2215   [(set_attr "type" "fadd")
2216    (set_attr "trap" "yes")
2217    (set_attr "round_suffix" "normal")
2218    (set_attr "trap_suffix" "u_su_sui")
2219    (set (attr "enabled")
2220      (cond [(eq_attr "alternative" "0")
2221               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
2222            ]
2223            (symbol_ref "true")))])
2225 (define_expand "trunctfdf2"
2226   [(use (match_operand:DF 0 "register_operand"))
2227    (use (match_operand:TF 1 "general_operand"))]
2228   "TARGET_HAS_XFLOATING_LIBS"
2229   "alpha_emit_xfloating_cvt (FLOAT_TRUNCATE, operands); DONE;")
2231 (define_expand "trunctfsf2"
2232   [(use (match_operand:SF 0 "register_operand"))
2233    (use (match_operand:TF 1 "general_operand"))]
2234   "TARGET_FP && TARGET_HAS_XFLOATING_LIBS"
2236   rtx tmpf, sticky, arg, lo, hi;
2238   tmpf = gen_reg_rtx (DFmode);
2239   sticky = gen_reg_rtx (DImode);
2240   arg = copy_to_mode_reg (TFmode, operands[1]);
2241   lo = gen_lowpart (DImode, arg);
2242   hi = gen_highpart (DImode, arg);
2244   /* Convert the low word of the TFmode value into a sticky rounding bit,
2245      then or it into the low bit of the high word.  This leaves the sticky
2246      bit at bit 48 of the fraction, which is representable in DFmode,
2247      which prevents rounding error in the final conversion to SFmode.  */
2249   emit_insn (gen_rtx_SET (sticky, gen_rtx_NE (DImode, lo, const0_rtx)));
2250   emit_insn (gen_iordi3 (hi, hi, sticky));
2251   emit_insn (gen_trunctfdf2 (tmpf, arg));
2252   emit_insn (gen_truncdfsf2 (operands[0], tmpf));
2253   DONE;
2256 ;; Next are all the integer comparisons, and conditional moves and branches
2257 ;; and some of the related define_expand's and define_split's.
2259 (define_insn "*setcc_internal"
2260   [(set (match_operand 0 "register_operand" "=r")
2261         (match_operator 1 "alpha_comparison_operator"
2262                            [(match_operand:DI 2 "register_operand" "r")
2263                             (match_operand:DI 3 "reg_or_8bit_operand" "rI")]))]
2264   "GET_MODE_CLASS (GET_MODE (operands[0])) == MODE_INT
2265    && GET_MODE_SIZE (GET_MODE (operands[0])) <= 8
2266    && GET_MODE (operands[0]) == GET_MODE (operands[1])"
2267   "cmp%C1 %2,%3,%0"
2268   [(set_attr "type" "icmp")])
2270 ;; Yes, we can technically support reg_or_8bit_operand in operand 2,
2271 ;; but that's non-canonical rtl and allowing that causes inefficiencies
2272 ;; from cse on.
2273 (define_insn "*setcc_swapped_internal"
2274   [(set (match_operand 0 "register_operand" "=r")
2275         (match_operator 1 "alpha_swapped_comparison_operator"
2276                            [(match_operand:DI 2 "register_operand" "r")
2277                             (match_operand:DI 3 "reg_or_0_operand" "rJ")]))]
2278   "GET_MODE_CLASS (GET_MODE (operands[0])) == MODE_INT
2279    && GET_MODE_SIZE (GET_MODE (operands[0])) <= 8
2280    && GET_MODE (operands[0]) == GET_MODE (operands[1])"
2281   "cmp%c1 %r3,%2,%0"
2282   [(set_attr "type" "icmp")])
2284 ;; Use match_operator rather than ne directly so that we can match
2285 ;; multiple integer modes.
2286 (define_insn "*setne_internal"
2287   [(set (match_operand 0 "register_operand" "=r")
2288         (match_operator 1 "signed_comparison_operator"
2289                           [(match_operand:DI 2 "register_operand" "r")
2290                            (const_int 0)]))]
2291   "GET_MODE_CLASS (GET_MODE (operands[0])) == MODE_INT
2292    && GET_MODE_SIZE (GET_MODE (operands[0])) <= 8
2293    && GET_CODE (operands[1]) == NE
2294    && GET_MODE (operands[0]) == GET_MODE (operands[1])"
2295   "cmpult $31,%2,%0"
2296   [(set_attr "type" "icmp")])
2298 ;; The mode folding trick can't be used with const_int operands, since
2299 ;; reload needs to know the proper mode.
2301 ;; Use add_operand instead of the more seemingly natural reg_or_8bit_operand
2302 ;; in order to create more pairs of constants.  As long as we're allowing
2303 ;; two constants at the same time, and will have to reload one of them...
2305 (define_insn "*mov<mode>cc_internal"
2306   [(set (match_operand:IMODE 0 "register_operand" "=r,r,r,r")
2307         (if_then_else:IMODE
2308          (match_operator 2 "signed_comparison_operator"
2309                          [(match_operand:DI 3 "reg_or_0_operand" "rJ,rJ,J,J")
2310                           (match_operand:DI 4 "reg_or_0_operand" "J,J,rJ,rJ")])
2311          (match_operand:IMODE 1 "add_operand" "rI,0,rI,0")
2312          (match_operand:IMODE 5 "add_operand" "0,rI,0,rI")))]
2313   "(operands[3] == const0_rtx) ^ (operands[4] == const0_rtx)"
2314   "@
2315    cmov%C2 %r3,%1,%0
2316    cmov%D2 %r3,%5,%0
2317    cmov%c2 %r4,%1,%0
2318    cmov%d2 %r4,%5,%0"
2319   [(set_attr "type" "icmov")])
2321 (define_insn "*mov<mode>cc_lbc"
2322   [(set (match_operand:IMODE 0 "register_operand" "=r,r")
2323         (if_then_else:IMODE
2324          (eq (zero_extract:DI (match_operand:DI 2 "reg_or_0_operand" "rJ,rJ")
2325                               (const_int 1)
2326                               (const_int 0))
2327              (const_int 0))
2328          (match_operand:IMODE 1 "reg_or_8bit_operand" "rI,0")
2329          (match_operand:IMODE 3 "reg_or_8bit_operand" "0,rI")))]
2330   ""
2331   "@
2332    cmovlbc %r2,%1,%0
2333    cmovlbs %r2,%3,%0"
2334   [(set_attr "type" "icmov")])
2336 (define_insn "*mov<mode>cc_lbs"
2337   [(set (match_operand:IMODE 0 "register_operand" "=r,r")
2338         (if_then_else:IMODE
2339          (ne (zero_extract:DI (match_operand:DI 2 "reg_or_0_operand" "rJ,rJ")
2340                               (const_int 1)
2341                               (const_int 0))
2342              (const_int 0))
2343          (match_operand:IMODE 1 "reg_or_8bit_operand" "rI,0")
2344          (match_operand:IMODE 3 "reg_or_8bit_operand" "0,rI")))]
2345   ""
2346   "@
2347    cmovlbs %r2,%1,%0
2348    cmovlbc %r2,%3,%0"
2349   [(set_attr "type" "icmov")])
2351 ;; For ABS, we have two choices, depending on whether the input and output
2352 ;; registers are the same or not.
2353 (define_expand "absdi2"
2354   [(set (match_operand:DI 0 "register_operand")
2355         (abs:DI (match_operand:DI 1 "register_operand")))]
2356   ""
2358   if (rtx_equal_p (operands[0], operands[1]))
2359     emit_insn (gen_absdi2_same (operands[0], gen_reg_rtx (DImode)));
2360   else
2361     emit_insn (gen_absdi2_diff (operands[0], operands[1]));
2362   DONE;
2365 (define_expand "absdi2_same"
2366   [(set (match_operand:DI 1 "register_operand")
2367         (neg:DI (match_operand:DI 0 "register_operand")))
2368    (set (match_dup 0)
2369         (if_then_else:DI (ge (match_dup 0) (const_int 0))
2370                          (match_dup 0)
2371                          (match_dup 1)))])
2373 (define_expand "absdi2_diff"
2374   [(set (match_operand:DI 0 "register_operand")
2375         (neg:DI (match_operand:DI 1 "register_operand")))
2376    (set (match_dup 0)
2377         (if_then_else:DI (lt (match_dup 1) (const_int 0))
2378                          (match_dup 0)
2379                          (match_dup 1)))])
2381 (define_split
2382   [(set (match_operand:DI 0 "register_operand")
2383         (abs:DI (match_dup 0)))
2384    (clobber (match_operand:DI 1 "register_operand"))]
2385   ""
2386   [(set (match_dup 1) (neg:DI (match_dup 0)))
2387    (set (match_dup 0) (if_then_else:DI (ge (match_dup 0) (const_int 0))
2388                                        (match_dup 0) (match_dup 1)))])
2390 (define_split
2391   [(set (match_operand:DI 0 "register_operand")
2392         (abs:DI (match_operand:DI 1 "register_operand")))]
2393   "! rtx_equal_p (operands[0], operands[1])"
2394   [(set (match_dup 0) (neg:DI (match_dup 1)))
2395    (set (match_dup 0) (if_then_else:DI (lt (match_dup 1) (const_int 0))
2396                                        (match_dup 0) (match_dup 1)))])
2398 (define_split
2399   [(set (match_operand:DI 0 "register_operand")
2400         (neg:DI (abs:DI (match_dup 0))))
2401    (clobber (match_operand:DI 1 "register_operand"))]
2402   ""
2403   [(set (match_dup 1) (neg:DI (match_dup 0)))
2404    (set (match_dup 0) (if_then_else:DI (le (match_dup 0) (const_int 0))
2405                                        (match_dup 0) (match_dup 1)))])
2407 (define_split
2408   [(set (match_operand:DI 0 "register_operand")
2409         (neg:DI (abs:DI (match_operand:DI 1 "register_operand"))))]
2410   "! rtx_equal_p (operands[0], operands[1])"
2411   [(set (match_dup 0) (neg:DI (match_dup 1)))
2412    (set (match_dup 0) (if_then_else:DI (gt (match_dup 1) (const_int 0))
2413                                        (match_dup 0) (match_dup 1)))])
2415 (define_insn "<code><mode>3"
2416   [(set (match_operand:I12MODE 0 "register_operand" "=r")
2417         (any_maxmin:I12MODE
2418          (match_operand:I12MODE 1 "reg_or_0_operand" "%rJ")
2419          (match_operand:I12MODE 2 "reg_or_8bit_operand" "rI")))]
2420   "TARGET_MAX"
2421   "<maxmin><vecmodesuffix> %r1,%2,%0"
2422   [(set_attr "type" "mvi")])
2424 (define_expand "smaxdi3"
2425   [(set (match_dup 3)
2426         (le:DI (match_operand:DI 1 "reg_or_0_operand")
2427                (match_operand:DI 2 "reg_or_8bit_operand")))
2428    (set (match_operand:DI 0 "register_operand")
2429         (if_then_else:DI (eq (match_dup 3) (const_int 0))
2430                          (match_dup 1) (match_dup 2)))]
2431   ""
2432   "operands[3] = gen_reg_rtx (DImode);")
2434 (define_split
2435   [(set (match_operand:DI 0 "register_operand")
2436         (smax:DI (match_operand:DI 1 "reg_or_0_operand")
2437                  (match_operand:DI 2 "reg_or_8bit_operand")))
2438    (clobber (match_operand:DI 3 "register_operand"))]
2439   "operands[2] != const0_rtx"
2440   [(set (match_dup 3) (le:DI (match_dup 1) (match_dup 2)))
2441    (set (match_dup 0) (if_then_else:DI (eq (match_dup 3) (const_int 0))
2442                                        (match_dup 1) (match_dup 2)))])
2444 (define_insn "*smax_const0"
2445   [(set (match_operand:DI 0 "register_operand" "=r")
2446         (smax:DI (match_operand:DI 1 "register_operand" "0")
2447                  (const_int 0)))]
2448   ""
2449   "cmovlt %0,0,%0"
2450   [(set_attr "type" "icmov")])
2452 (define_expand "smindi3"
2453   [(set (match_dup 3)
2454         (lt:DI (match_operand:DI 1 "reg_or_0_operand")
2455                (match_operand:DI 2 "reg_or_8bit_operand")))
2456    (set (match_operand:DI 0 "register_operand")
2457         (if_then_else:DI (ne (match_dup 3) (const_int 0))
2458                          (match_dup 1) (match_dup 2)))]
2459   ""
2460   "operands[3] = gen_reg_rtx (DImode);")
2462 (define_split
2463   [(set (match_operand:DI 0 "register_operand")
2464         (smin:DI (match_operand:DI 1 "reg_or_0_operand")
2465                  (match_operand:DI 2 "reg_or_8bit_operand")))
2466    (clobber (match_operand:DI 3 "register_operand"))]
2467   "operands[2] != const0_rtx"
2468   [(set (match_dup 3) (lt:DI (match_dup 1) (match_dup 2)))
2469    (set (match_dup 0) (if_then_else:DI (ne (match_dup 3) (const_int 0))
2470                                        (match_dup 1) (match_dup 2)))])
2472 (define_insn "*smin_const0"
2473   [(set (match_operand:DI 0 "register_operand" "=r")
2474         (smin:DI (match_operand:DI 1 "register_operand" "0")
2475                  (const_int 0)))]
2476   ""
2477   "cmovgt %0,0,%0"
2478   [(set_attr "type" "icmov")])
2480 (define_expand "umaxdi3"
2481   [(set (match_dup 3)
2482         (leu:DI (match_operand:DI 1 "reg_or_0_operand")
2483                 (match_operand:DI 2 "reg_or_8bit_operand")))
2484    (set (match_operand:DI 0 "register_operand")
2485         (if_then_else:DI (eq (match_dup 3) (const_int 0))
2486                          (match_dup 1) (match_dup 2)))]
2487   ""
2488   "operands[3] = gen_reg_rtx (DImode);")
2490 (define_split
2491   [(set (match_operand:DI 0 "register_operand")
2492         (umax:DI (match_operand:DI 1 "reg_or_0_operand")
2493                  (match_operand:DI 2 "reg_or_8bit_operand")))
2494    (clobber (match_operand:DI 3 "register_operand"))]
2495   "operands[2] != const0_rtx"
2496   [(set (match_dup 3) (leu:DI (match_dup 1) (match_dup 2)))
2497    (set (match_dup 0) (if_then_else:DI (eq (match_dup 3) (const_int 0))
2498                                        (match_dup 1) (match_dup 2)))])
2500 (define_expand "umindi3"
2501   [(set (match_dup 3)
2502         (ltu:DI (match_operand:DI 1 "reg_or_0_operand")
2503                 (match_operand:DI 2 "reg_or_8bit_operand")))
2504    (set (match_operand:DI 0 "register_operand")
2505         (if_then_else:DI (ne (match_dup 3) (const_int 0))
2506                          (match_dup 1) (match_dup 2)))]
2507   ""
2508   "operands[3] = gen_reg_rtx (DImode);")
2510 (define_split
2511   [(set (match_operand:DI 0 "register_operand")
2512         (umin:DI (match_operand:DI 1 "reg_or_0_operand")
2513                  (match_operand:DI 2 "reg_or_8bit_operand")))
2514    (clobber (match_operand:DI 3 "register_operand"))]
2515   "operands[2] != const0_rtx"
2516   [(set (match_dup 3) (ltu:DI (match_dup 1) (match_dup 2)))
2517    (set (match_dup 0) (if_then_else:DI (ne (match_dup 3) (const_int 0))
2518                                        (match_dup 1) (match_dup 2)))])
2520 (define_insn "*bcc_normal"
2521   [(set (pc)
2522         (if_then_else
2523          (match_operator 1 "signed_comparison_operator"
2524                          [(match_operand:DI 2 "reg_or_0_operand" "rJ")
2525                           (const_int 0)])
2526          (label_ref (match_operand 0))
2527          (pc)))]
2528   ""
2529   "b%C1 %r2,%0"
2530   [(set_attr "type" "ibr")])
2532 (define_insn "*bcc_reverse"
2533   [(set (pc)
2534         (if_then_else
2535          (match_operator 1 "signed_comparison_operator"
2536                          [(match_operand:DI 2 "register_operand" "r")
2537                           (const_int 0)])
2539          (pc)
2540          (label_ref (match_operand 0))))]
2541   ""
2542   "b%c1 %2,%0"
2543   [(set_attr "type" "ibr")])
2545 (define_insn "*blbs_normal"
2546   [(set (pc)
2547         (if_then_else
2548          (ne (zero_extract:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
2549                               (const_int 1)
2550                               (const_int 0))
2551              (const_int 0))
2552          (label_ref (match_operand 0))
2553          (pc)))]
2554   ""
2555   "blbs %r1,%0"
2556   [(set_attr "type" "ibr")])
2558 (define_insn "*blbc_normal"
2559   [(set (pc)
2560         (if_then_else
2561          (eq (zero_extract:DI (match_operand:DI 1 "reg_or_0_operand" "rJ")
2562                               (const_int 1)
2563                               (const_int 0))
2564              (const_int 0))
2565          (label_ref (match_operand 0))
2566          (pc)))]
2567   ""
2568   "blbc %r1,%0"
2569   [(set_attr "type" "ibr")])
2571 (define_split
2572   [(parallel
2573     [(set (pc)
2574           (if_then_else
2575            (match_operator 1 "comparison_operator"
2576              [(zero_extract:DI (match_operand:DI 2 "register_operand")
2577                                (const_int 1)
2578                                (match_operand:DI 3 "const_int_operand"))
2579               (const_int 0)])
2580            (label_ref (match_operand 0))
2581            (pc)))
2582      (clobber (match_operand:DI 4 "register_operand"))])]
2583   "INTVAL (operands[3]) != 0"
2584   [(set (match_dup 4)
2585         (lshiftrt:DI (match_dup 2) (match_dup 3)))
2586    (set (pc)
2587         (if_then_else (match_op_dup 1
2588                                     [(zero_extract:DI (match_dup 4)
2589                                                       (const_int 1)
2590                                                       (const_int 0))
2591                                      (const_int 0)])
2592                       (label_ref (match_dup 0))
2593                       (pc)))]
2596 ;; The following are the corresponding floating-point insns.  Recall
2597 ;; we need to have variants that expand the arguments from SFmode
2598 ;; to DFmode.
2600 (define_insn "*cmpdf_internal"
2601   [(set (match_operand:DF 0 "register_operand" "=f,&f")
2602         (match_operator:DF 1 "alpha_fp_comparison_operator"
2603                            [(match_operand:DF 2 "reg_or_0_operand" "fG,fG")
2604                             (match_operand:DF 3 "reg_or_0_operand" "fG,fG")]))]
2605   "TARGET_FP"
2606   "cmp%-%C1%/ %R2,%R3,%0"
2607   [(set_attr "type" "fadd")
2608    (set_attr "trap" "yes")
2609    (set_attr "trap_suffix" "su")
2610    (set (attr "enabled")
2611      (cond [(eq_attr "alternative" "0")
2612               (symbol_ref "alpha_fptm < ALPHA_FPTM_SU")
2613            ]
2614            (symbol_ref "true")))])
2616 (define_insn "*cmpdf_ext1"
2617   [(set (match_operand:DF 0 "register_operand" "=f")
2618         (match_operator:DF 1 "alpha_fp_comparison_operator"
2619                            [(float_extend:DF
2620                              (match_operand:SF 2 "reg_or_0_operand" "fG"))
2621                             (match_operand:DF 3 "reg_or_0_operand" "fG")]))]
2622   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2623   "cmp%-%C1%/ %R2,%R3,%0"
2624   [(set_attr "type" "fadd")
2625    (set_attr "trap" "yes")
2626    (set_attr "trap_suffix" "su")])
2628 (define_insn "*cmpdf_ext2"
2629   [(set (match_operand:DF 0 "register_operand" "=f")
2630         (match_operator:DF 1 "alpha_fp_comparison_operator"
2631                            [(match_operand:DF 2 "reg_or_0_operand" "fG")
2632                             (float_extend:DF
2633                              (match_operand:SF 3 "reg_or_0_operand" "fG"))]))]
2634   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2635   "cmp%-%C1%/ %R2,%R3,%0"
2636   [(set_attr "type" "fadd")
2637    (set_attr "trap" "yes")
2638    (set_attr "trap_suffix" "su")])
2640 (define_insn "*cmpdf_ext3"
2641   [(set (match_operand:DF 0 "register_operand" "=f")
2642         (match_operator:DF 1 "alpha_fp_comparison_operator"
2643                            [(float_extend:DF
2644                              (match_operand:SF 2 "reg_or_0_operand" "fG"))
2645                             (float_extend:DF
2646                              (match_operand:SF 3 "reg_or_0_operand" "fG"))]))]
2647   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2648   "cmp%-%C1%/ %R2,%R3,%0"
2649   [(set_attr "type" "fadd")
2650    (set_attr "trap" "yes")
2651    (set_attr "trap_suffix" "su")])
2653 (define_insn "*mov<mode>cc_internal"
2654   [(set (match_operand:FMODE 0 "register_operand" "=f,f")
2655         (if_then_else:FMODE
2656          (match_operator 3 "signed_comparison_operator"
2657                          [(match_operand:DF 4 "reg_or_0_operand" "fG,fG")
2658                           (match_operand:DF 2 "const0_operand" "G,G")])
2659          (match_operand:FMODE 1 "reg_or_0_operand" "fG,0")
2660          (match_operand:FMODE 5 "reg_or_0_operand" "0,fG")))]
2661   "TARGET_FP"
2662   "@
2663    fcmov%C3 %R4,%R1,%0
2664    fcmov%D3 %R4,%R5,%0"
2665   [(set_attr "type" "fcmov")])
2667 (define_insn "*movdfcc_ext1"
2668   [(set (match_operand:DF 0 "register_operand" "=f,f")
2669         (if_then_else:DF
2670          (match_operator 3 "signed_comparison_operator"
2671                          [(match_operand:DF 4 "reg_or_0_operand" "fG,fG")
2672                           (match_operand:DF 2 "const0_operand" "G,G")])
2673          (float_extend:DF (match_operand:SF 1 "reg_or_0_operand" "fG,0"))
2674          (match_operand:DF 5 "reg_or_0_operand" "0,fG")))]
2675   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2676   "@
2677    fcmov%C3 %R4,%R1,%0
2678    fcmov%D3 %R4,%R5,%0"
2679   [(set_attr "type" "fcmov")])
2681 (define_insn "*movdfcc_ext2"
2682   [(set (match_operand:DF 0 "register_operand" "=f,f")
2683         (if_then_else:DF
2684          (match_operator 3 "signed_comparison_operator"
2685                          [(float_extend:DF
2686                            (match_operand:SF 4 "reg_or_0_operand" "fG,fG"))
2687                           (match_operand:DF 2 "const0_operand" "G,G")])
2688          (match_operand:DF 1 "reg_or_0_operand" "fG,0")
2689          (match_operand:DF 5 "reg_or_0_operand" "0,fG")))]
2690   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2691   "@
2692    fcmov%C3 %R4,%R1,%0
2693    fcmov%D3 %R4,%R5,%0"
2694   [(set_attr "type" "fcmov")])
2696 (define_insn "*movdfcc_ext3"
2697   [(set (match_operand:SF 0 "register_operand" "=f,f")
2698         (if_then_else:SF
2699          (match_operator 3 "signed_comparison_operator"
2700                          [(float_extend:DF
2701                            (match_operand:SF 4 "reg_or_0_operand" "fG,fG"))
2702                           (match_operand:DF 2 "const0_operand" "G,G")])
2703          (match_operand:SF 1 "reg_or_0_operand" "fG,0")
2704          (match_operand:SF 5 "reg_or_0_operand" "0,fG")))]
2705   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2706   "@
2707    fcmov%C3 %R4,%R1,%0
2708    fcmov%D3 %R4,%R5,%0"
2709   [(set_attr "type" "fcmov")])
2711 (define_insn "*movdfcc_ext4"
2712   [(set (match_operand:DF 0 "register_operand" "=f,f")
2713         (if_then_else:DF
2714          (match_operator 3 "signed_comparison_operator"
2715                          [(float_extend:DF
2716                            (match_operand:SF 4 "reg_or_0_operand" "fG,fG"))
2717                           (match_operand:DF 2 "const0_operand" "G,G")])
2718          (float_extend:DF (match_operand:SF 1 "reg_or_0_operand" "fG,0"))
2719          (match_operand:DF 5 "reg_or_0_operand" "0,fG")))]
2720   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2721   "@
2722    fcmov%C3 %R4,%R1,%0
2723    fcmov%D3 %R4,%R5,%0"
2724   [(set_attr "type" "fcmov")])
2726 (define_expand "smaxdf3"
2727   [(set (match_dup 3)
2728         (le:DF (match_operand:DF 1 "reg_or_0_operand")
2729                (match_operand:DF 2 "reg_or_0_operand")))
2730    (set (match_operand:DF 0 "register_operand")
2731         (if_then_else:DF (eq (match_dup 3) (match_dup 4))
2732                          (match_dup 1) (match_dup 2)))]
2733   "TARGET_FP"
2735   operands[3] = gen_reg_rtx (DFmode);
2736   operands[4] = CONST0_RTX (DFmode);
2739 (define_expand "smindf3"
2740   [(set (match_dup 3)
2741         (lt:DF (match_operand:DF 1 "reg_or_0_operand")
2742                (match_operand:DF 2 "reg_or_0_operand")))
2743    (set (match_operand:DF 0 "register_operand")
2744         (if_then_else:DF (ne (match_dup 3) (match_dup 4))
2745                          (match_dup 1) (match_dup 2)))]
2746   "TARGET_FP"
2748   operands[3] = gen_reg_rtx (DFmode);
2749   operands[4] = CONST0_RTX (DFmode);
2752 (define_expand "smaxsf3"
2753   [(set (match_dup 3)
2754         (le:DF (float_extend:DF (match_operand:SF 1 "reg_or_0_operand"))
2755                (float_extend:DF (match_operand:SF 2 "reg_or_0_operand"))))
2756    (set (match_operand:SF 0 "register_operand")
2757         (if_then_else:SF (eq (match_dup 3) (match_dup 4))
2758                          (match_dup 1) (match_dup 2)))]
2759   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2761   operands[3] = gen_reg_rtx (DFmode);
2762   operands[4] = CONST0_RTX (DFmode);
2765 (define_expand "sminsf3"
2766   [(set (match_dup 3)
2767         (lt:DF (float_extend:DF (match_operand:SF 1 "reg_or_0_operand"))
2768                (float_extend:DF (match_operand:SF 2 "reg_or_0_operand"))))
2769    (set (match_operand:SF 0 "register_operand")
2770         (if_then_else:SF (ne (match_dup 3) (match_dup 4))
2771                       (match_dup 1) (match_dup 2)))]
2772   "TARGET_FP && alpha_fptm < ALPHA_FPTM_SU"
2774   operands[3] = gen_reg_rtx (DFmode);
2775   operands[4] = CONST0_RTX (DFmode);
2778 (define_insn "*fbcc_normal"
2779   [(set (pc)
2780         (if_then_else
2781          (match_operator 1 "signed_comparison_operator"
2782                          [(match_operand:DF 2 "reg_or_0_operand" "fG")
2783                           (match_operand:DF 3 "const0_operand" "G")])
2784          (label_ref (match_operand 0))
2785          (pc)))]
2786   "TARGET_FP"
2787   "fb%C1 %R2,%0"
2788   [(set_attr "type" "fbr")])
2790 (define_insn "*fbcc_ext_normal"
2791   [(set (pc)
2792         (if_then_else
2793          (match_operator 1 "signed_comparison_operator"
2794                          [(float_extend:DF
2795                            (match_operand:SF 2 "reg_or_0_operand" "fG"))
2796                           (match_operand:DF 3 "const0_operand" "G")])
2797          (label_ref (match_operand 0))
2798          (pc)))]
2799   "TARGET_FP"
2800   "fb%C1 %R2,%0"
2801   [(set_attr "type" "fbr")])
2803 ;; These are the main define_expand's used to make conditional branches
2804 ;; and compares.
2806 (define_expand "cbranchdf4"
2807   [(use (match_operator 0 "alpha_cbranch_operator"
2808          [(match_operand:DF 1 "reg_or_0_operand")
2809           (match_operand:DF 2 "reg_or_0_operand")]))
2810    (use (match_operand 3))]
2811   "TARGET_FP"
2812   "alpha_emit_conditional_branch (operands, DFmode); DONE;")
2814 (define_expand "cbranchtf4"
2815   [(use (match_operator 0 "alpha_cbranch_operator"
2816          [(match_operand:TF 1 "general_operand")
2817           (match_operand:TF 2 "general_operand")]))
2818    (use (match_operand 3))]
2819   "TARGET_HAS_XFLOATING_LIBS"
2820   "alpha_emit_conditional_branch (operands, TFmode); DONE;")
2822 (define_expand "cbranchdi4"
2823   [(use (match_operator 0 "alpha_cbranch_operator"
2824          [(match_operand:DI 1 "general_operand")
2825           (match_operand:DI 2 "general_operand")]))
2826    (use (match_operand 3))]
2827   ""
2828   "alpha_emit_conditional_branch (operands, DImode); DONE;")
2830 (define_expand "cstoredf4"
2831   [(use (match_operator:DI 1 "alpha_cbranch_operator"
2832          [(match_operand:DF 2 "reg_or_0_operand")
2833           (match_operand:DF 3 "reg_or_0_operand")]))
2834    (clobber (match_operand:DI 0 "register_operand"))]
2835   "TARGET_FP"
2837   if (alpha_emit_setcc (operands, DFmode))
2838     DONE;
2839   else
2840     FAIL;
2843 (define_expand "cstoretf4"
2844   [(use (match_operator:DI 1 "alpha_cbranch_operator"
2845          [(match_operand:TF 2 "general_operand")
2846           (match_operand:TF 3 "general_operand")]))
2847    (clobber (match_operand:DI 0 "register_operand"))]
2848   "TARGET_HAS_XFLOATING_LIBS"
2850   if (alpha_emit_setcc (operands, TFmode))
2851     DONE;
2852   else
2853     FAIL;
2856 (define_expand "cstoredi4"
2857   [(use (match_operator:DI 1 "alpha_cbranch_operator"
2858          [(match_operand:DI 2 "general_operand")
2859           (match_operand:DI 3 "general_operand")]))
2860    (clobber (match_operand:DI 0 "register_operand"))]
2861   ""
2863   if (alpha_emit_setcc (operands, DImode))
2864     DONE;
2865   else
2866     FAIL;
2869 ;; These are the main define_expand's used to make conditional moves.
2871 (define_expand "mov<mode>cc"
2872   [(set (match_operand:I48MODE 0 "register_operand")
2873         (if_then_else:I48MODE
2874           (match_operand 1 "comparison_operator")
2875           (match_operand:I48MODE 2 "reg_or_8bit_operand")
2876           (match_operand:I48MODE 3 "reg_or_8bit_operand")))]
2877   ""
2879   operands[1] = alpha_emit_conditional_move (operands[1], <MODE>mode);
2880   if (operands[1] == 0)
2881     FAIL;
2884 (define_expand "mov<mode>cc"
2885   [(set (match_operand:FMODE 0 "register_operand")
2886         (if_then_else:FMODE
2887           (match_operand 1 "comparison_operator")
2888           (match_operand:FMODE 2 "reg_or_8bit_operand")
2889           (match_operand:FMODE 3 "reg_or_8bit_operand")))]
2890   ""
2892   operands[1] = alpha_emit_conditional_move (operands[1], <MODE>mode);
2893   if (operands[1] == 0)
2894     FAIL;
2897 ;; These define_split definitions are used in cases when comparisons have
2898 ;; not be stated in the correct way and we need to reverse the second
2899 ;; comparison.  For example, x >= 7 has to be done as x < 6 with the
2900 ;; comparison that tests the result being reversed.  We have one define_split
2901 ;; for each use of a comparison.  They do not match valid insns and need
2902 ;; not generate valid insns.
2904 ;; We can also handle equality comparisons (and inequality comparisons in
2905 ;; cases where the resulting add cannot overflow) by doing an add followed by
2906 ;; a comparison with zero.  This is faster since the addition takes one
2907 ;; less cycle than a compare when feeding into a conditional move.
2908 ;; For this case, we also have an SImode pattern since we can merge the add
2909 ;; and sign extend and the order doesn't matter.
2911 ;; We do not do this for floating-point, since it isn't clear how the "wrong"
2912 ;; operation could have been generated.
2914 (define_split
2915   [(set (match_operand:DI 0 "register_operand")
2916         (if_then_else:DI
2917          (match_operator 1 "comparison_operator"
2918                          [(match_operand:DI 2 "reg_or_0_operand")
2919                           (match_operand:DI 3 "reg_or_cint_operand")])
2920          (match_operand:DI 4 "reg_or_cint_operand")
2921          (match_operand:DI 5 "reg_or_cint_operand")))
2922    (clobber (match_operand:DI 6 "register_operand"))]
2923   "operands[3] != const0_rtx"
2924   [(set (match_dup 6) (match_dup 7))
2925    (set (match_dup 0)
2926         (if_then_else:DI (match_dup 8) (match_dup 4) (match_dup 5)))]
2928   enum rtx_code code = GET_CODE (operands[1]);
2929   int unsignedp = (code == GEU || code == LEU || code == GTU || code == LTU);
2931   /* If we are comparing for equality with a constant and that constant
2932      appears in the arm when the register equals the constant, use the
2933      register since that is more likely to match (and to produce better code
2934      if both would).  */
2936   if (code == EQ && CONST_INT_P (operands[3])
2937       && rtx_equal_p (operands[4], operands[3]))
2938     operands[4] = operands[2];
2940   else if (code == NE && CONST_INT_P (operands[3])
2941            && rtx_equal_p (operands[5], operands[3]))
2942     operands[5] = operands[2];
2944   if (code == NE || code == EQ
2945       || (extended_count (operands[2], DImode, unsignedp) >= 1
2946           && extended_count (operands[3], DImode, unsignedp) >= 1))
2947     {
2948       if (CONST_INT_P (operands[3]))
2949         operands[7] = gen_rtx_PLUS (DImode, operands[2],
2950                                     GEN_INT (- INTVAL (operands[3])));
2951       else
2952         operands[7] = gen_rtx_MINUS (DImode, operands[2], operands[3]);
2954       operands[8] = gen_rtx_fmt_ee (code, VOIDmode, operands[6], const0_rtx);
2955     }
2957   else if (code == EQ || code == LE || code == LT
2958            || code == LEU || code == LTU)
2959     {
2960       operands[7] = gen_rtx_fmt_ee (code, DImode, operands[2], operands[3]);
2961       operands[8] = gen_rtx_NE (VOIDmode, operands[6], const0_rtx);
2962     }
2963   else
2964     {
2965       operands[7] = gen_rtx_fmt_ee (reverse_condition (code), DImode,
2966                                     operands[2], operands[3]);
2967       operands[8] = gen_rtx_EQ (VOIDmode, operands[6], const0_rtx);
2968     }
2971 (define_split
2972   [(set (match_operand:DI 0 "register_operand")
2973         (if_then_else:DI
2974          (match_operator 1 "comparison_operator"
2975                          [(match_operand:SI 2 "reg_or_0_operand")
2976                           (match_operand:SI 3 "reg_or_cint_operand")])
2977          (match_operand:DI 4 "reg_or_8bit_operand")
2978          (match_operand:DI 5 "reg_or_8bit_operand")))
2979    (clobber (match_operand:DI 6 "register_operand"))]
2980   "operands[3] != const0_rtx
2981    && (GET_CODE (operands[1]) == EQ || GET_CODE (operands[1]) == NE)"
2982   [(set (match_dup 6) (match_dup 7))
2983    (set (match_dup 0)
2984         (if_then_else:DI (match_dup 8) (match_dup 4) (match_dup 5)))]
2986   enum rtx_code code = GET_CODE (operands[1]);
2987   int unsignedp = (code == GEU || code == LEU || code == GTU || code == LTU);
2988   rtx tem;
2990   if ((code != NE && code != EQ
2991        && ! (extended_count (operands[2], DImode, unsignedp) >= 1
2992              && extended_count (operands[3], DImode, unsignedp) >= 1)))
2993     FAIL;
2995   if (CONST_INT_P (operands[3]))
2996     tem = gen_rtx_PLUS (SImode, operands[2],
2997                         GEN_INT (- INTVAL (operands[3])));
2998   else
2999     tem = gen_rtx_MINUS (SImode, operands[2], operands[3]);
3001   operands[7] = gen_rtx_SIGN_EXTEND (DImode, tem);
3002   operands[8] = gen_rtx_fmt_ee (GET_CODE (operands[1]), VOIDmode,
3003                                 operands[6], const0_rtx);
3006 ;; Prefer to use cmp and arithmetic when possible instead of a cmove.
3008 (define_split
3009   [(set (match_operand 0 "register_operand")
3010         (if_then_else (match_operator 1 "signed_comparison_operator"
3011                            [(match_operand:DI 2 "reg_or_0_operand")
3012                             (const_int 0)])
3013           (match_operand 3 "const_int_operand")
3014           (match_operand 4 "const_int_operand")))]
3015   ""
3016   [(const_int 0)]
3018   if (alpha_split_conditional_move (GET_CODE (operands[1]), operands[0],
3019                                     operands[2], operands[3], operands[4]))
3020     DONE;
3021   else
3022     FAIL;
3025 ;; ??? Why combine is allowed to create such non-canonical rtl, I don't know.
3026 ;; Oh well, we match it in movcc, so it must be partially our fault.
3027 (define_split
3028   [(set (match_operand 0 "register_operand")
3029         (if_then_else (match_operator 1 "signed_comparison_operator"
3030                            [(const_int 0)
3031                             (match_operand:DI 2 "reg_or_0_operand")])
3032           (match_operand 3 "const_int_operand")
3033           (match_operand 4 "const_int_operand")))]
3034   ""
3035   [(const_int 0)]
3037   if (alpha_split_conditional_move (swap_condition (GET_CODE (operands[1])),
3038                                     operands[0], operands[2], operands[3],
3039                                     operands[4]))
3040     DONE;
3041   else
3042     FAIL;
3045 (define_insn_and_split "*cmp_sadd_di"
3046   [(set (match_operand:DI 0 "register_operand" "=r")
3047         (plus:DI (if_then_else:DI
3048                    (match_operator 1 "alpha_zero_comparison_operator"
3049                      [(match_operand:DI 2 "reg_or_0_operand" "rJ")
3050                       (const_int 0)])
3051                    (match_operand:DI 3 "const48_operand" "I")
3052                    (const_int 0))
3053                  (match_operand:DI 4 "sext_add_operand" "rIO")))
3054    (clobber (match_scratch:DI 5 "=r"))]
3055   ""
3056   "#"
3057   ""
3058   [(set (match_dup 5)
3059         (match_op_dup:DI 1 [(match_dup 2) (const_int 0)]))
3060    (set (match_dup 0)
3061         (plus:DI (ashift:DI (match_dup 5) (match_dup 3))
3062                  (match_dup 4)))]
3064   operands[3] = GEN_INT (exact_log2 (INTVAL (operands [3])));
3065   if (can_create_pseudo_p ())
3066     operands[5] = gen_reg_rtx (DImode);
3067   else if (reg_overlap_mentioned_p (operands[5], operands[4]))
3068     operands[5] = operands[0];
3071 (define_insn_and_split "*cmp_sadd_si"
3072   [(set (match_operand:SI 0 "register_operand" "=r")
3073         (plus:SI (if_then_else:SI
3074                    (match_operator 1 "alpha_zero_comparison_operator"
3075                      [(match_operand:DI 2 "reg_or_0_operand" "rJ")
3076                       (const_int 0)])
3077                    (match_operand:SI 3 "const48_operand" "I")
3078                    (const_int 0))
3079                  (match_operand:SI 4 "sext_add_operand" "rIO")))
3080    (clobber (match_scratch:DI 5 "=r"))]
3081   ""
3082   "#"
3083   ""
3084   [(set (match_dup 5)
3085         (match_op_dup:DI 1 [(match_dup 2) (const_int 0)]))
3086    (set (match_dup 0)
3087         (plus:SI (ashift:SI (match_dup 6) (match_dup 3))
3088                  (match_dup 4)))]
3090   operands[3] = GEN_INT (exact_log2 (INTVAL (operands [3])));
3091   if (can_create_pseudo_p ())
3092     operands[5] = gen_reg_rtx (DImode);
3093   else if (reg_overlap_mentioned_p (operands[5], operands[4]))
3094     operands[5] = gen_lowpart (DImode, operands[0]);
3096   operands[6] = gen_lowpart (SImode, operands[5]);
3099 (define_insn_and_split "*cmp_sadd_sidi"
3100   [(set (match_operand:DI 0 "register_operand" "=r")
3101         (sign_extend:DI
3102           (plus:SI (if_then_else:SI
3103                      (match_operator 1 "alpha_zero_comparison_operator"
3104                        [(match_operand:DI 2 "reg_or_0_operand" "rJ")
3105                         (const_int 0)])
3106                      (match_operand:SI 3 "const48_operand" "I")
3107                      (const_int 0))
3108                    (match_operand:SI 4 "sext_add_operand" "rIO"))))
3109    (clobber (match_scratch:DI 5 "=r"))]
3110   ""
3111   "#"
3112   ""
3113   [(set (match_dup 5)
3114         (match_op_dup:DI 1 [(match_dup 2) (const_int 0)]))
3115    (set (match_dup 0)
3116         (sign_extend:DI (plus:SI (ashift:SI (match_dup 6) (match_dup 3))
3117                                  (match_dup 4))))]
3119   operands[3] = GEN_INT (exact_log2 (INTVAL (operands [3])));
3120   if (can_create_pseudo_p ())
3121     operands[5] = gen_reg_rtx (DImode);
3122   else if (reg_overlap_mentioned_p (operands[5], operands[4]))
3123     operands[5] = operands[0];
3125   operands[6] = gen_lowpart (SImode, operands[5]);
3128 (define_insn_and_split "*cmp_ssub_di"
3129   [(set (match_operand:DI 0 "register_operand" "=r")
3130         (minus:DI (if_then_else:DI
3131                     (match_operator 1 "alpha_zero_comparison_operator"
3132                       [(match_operand:DI 2 "reg_or_0_operand" "rJ")
3133                        (const_int 0)])
3134                     (match_operand:DI 3 "const48_operand" "I")
3135                     (const_int 0))
3136                   (match_operand:DI 4 "reg_or_8bit_operand" "rI")))
3137    (clobber (match_scratch:DI 5 "=r"))]
3138   ""
3139   "#"
3140   ""
3141   [(set (match_dup 5)
3142         (match_op_dup:DI 1 [(match_dup 2) (const_int 0)]))
3143    (set (match_dup 0)
3144         (minus:DI (ashift:DI (match_dup 5) (match_dup 3))
3145                   (match_dup 4)))]
3147   operands[3] = GEN_INT (exact_log2 (INTVAL (operands [3])));
3148   if (can_create_pseudo_p ())
3149     operands[5] = gen_reg_rtx (DImode);
3150   else if (reg_overlap_mentioned_p (operands[5], operands[4]))
3151     operands[5] = operands[0];
3154 (define_insn_and_split "*cmp_ssub_si"
3155   [(set (match_operand:SI 0 "register_operand" "=r")
3156         (minus:SI (if_then_else:SI
3157                     (match_operator 1 "alpha_zero_comparison_operator"
3158                       [(match_operand:DI 2 "reg_or_0_operand" "rJ")
3159                        (const_int 0)])
3160                     (match_operand:SI 3 "const48_operand" "I")
3161                     (const_int 0))
3162                   (match_operand:SI 4 "reg_or_8bit_operand" "rI")))
3163    (clobber (match_scratch:DI 5 "=r"))]
3164   ""
3165   "#"
3166   ""
3167   [(set (match_dup 5)
3168         (match_op_dup:DI 1 [(match_dup 2) (const_int 0)]))
3169    (set (match_dup 0)
3170         (minus:SI (ashift:SI (match_dup 6) (match_dup 3))
3171                  (match_dup 4)))]
3173   operands[3] = GEN_INT (exact_log2 (INTVAL (operands [3])));
3174   if (can_create_pseudo_p ())
3175     operands[5] = gen_reg_rtx (DImode);
3176   else if (reg_overlap_mentioned_p (operands[5], operands[4]))
3177     operands[5] = gen_lowpart (DImode, operands[0]);
3179   operands[6] = gen_lowpart (SImode, operands[5]);
3182 (define_insn_and_split "*cmp_ssub_sidi"
3183   [(set (match_operand:DI 0 "register_operand" "=r")
3184         (sign_extend:DI
3185           (minus:SI (if_then_else:SI
3186                       (match_operator 1 "alpha_zero_comparison_operator"
3187                         [(match_operand:DI 2 "reg_or_0_operand" "rJ")
3188                          (const_int 0)])
3189                       (match_operand:SI 3 "const48_operand" "I")
3190                       (const_int 0))
3191                     (match_operand:SI 4 "reg_or_8bit_operand" "rI"))))
3192    (clobber (match_scratch:DI 5 "=r"))]
3193   ""
3194   "#"
3195   ""
3196   [(set (match_dup 5)
3197         (match_op_dup:DI 1 [(match_dup 2) (const_int 0)]))
3198    (set (match_dup 0)
3199         (sign_extend:DI (minus:SI (ashift:SI (match_dup 6) (match_dup 3))
3200                                   (match_dup 4))))]
3202   operands[3] = GEN_INT (exact_log2 (INTVAL (operands [3])));
3203   if (can_create_pseudo_p ())
3204     operands[5] = gen_reg_rtx (DImode);
3205   else if (reg_overlap_mentioned_p (operands[5], operands[4]))
3206     operands[5] = operands[0];
3208   operands[6] = gen_lowpart (SImode, operands[5]);
3211 ;; Here are the CALL and unconditional branch insns.  Calls on NT and OSF
3212 ;; work differently, so we have different patterns for each.
3214 (define_expand "call"
3215   [(use (match_operand:DI 0))
3216    (use (match_operand 1))
3217    (use (match_operand 2))
3218    (use (match_operand 3))]
3219   ""
3221   if (TARGET_ABI_OPEN_VMS)
3222     emit_call_insn (gen_call_vms (operands[0], operands[2]));
3223   else
3224     emit_call_insn (gen_call_osf (operands[0], operands[1]));
3225   DONE;
3228 (define_expand "sibcall"
3229   [(parallel [(call (mem:DI (match_operand 0))
3230                             (match_operand 1))
3231               (unspec [(reg:DI 29)] UNSPEC_SIBCALL)])]
3232   "TARGET_ABI_OSF"
3234   gcc_assert (MEM_P (operands[0]));
3235   operands[0] = XEXP (operands[0], 0);
3238 (define_expand "call_osf"
3239   [(parallel [(call (mem:DI (match_operand 0))
3240                     (match_operand 1))
3241               (use (reg:DI 29))
3242               (clobber (reg:DI 26))])]
3243   ""
3245   gcc_assert (MEM_P (operands[0]));
3247   operands[0] = XEXP (operands[0], 0);
3248   if (! call_operand (operands[0], Pmode))
3249     operands[0] = copy_to_mode_reg (Pmode, operands[0]);
3253 ;; call openvms/alpha
3254 ;; op 0: symbol ref for called function
3255 ;; op 1: next_arg_reg (argument information value for R25)
3257 (define_expand "call_vms"
3258   [(parallel [(call (mem:DI (match_operand 0))
3259                     (match_operand 1))
3260               (use (match_dup 2))
3261               (use (reg:DI 25))
3262               (use (reg:DI 26))
3263               (clobber (reg:DI 27))])]
3264   ""
3266   gcc_assert (MEM_P (operands[0]));
3268   operands[0] = XEXP (operands[0], 0);
3270   /* Always load AI with argument information, then handle symbolic and
3271      indirect call differently.  Load RA and set operands[2] to PV in
3272      both cases.  */
3274   emit_move_insn (gen_rtx_REG (DImode, 25), operands[1]);
3275   if (GET_CODE (operands[0]) == SYMBOL_REF)
3276     {
3277       operands[2] = const0_rtx;
3278     }
3279   else
3280     {
3281       emit_move_insn (gen_rtx_REG (Pmode, 26),
3282                       gen_rtx_MEM (Pmode, plus_constant (Pmode,
3283                                                          operands[0], 8)));
3284       operands[2] = operands[0];
3285     }
3288 (define_expand "call_value"
3289   [(use (match_operand 0))
3290    (use (match_operand:DI 1))
3291    (use (match_operand 2))
3292    (use (match_operand 3))
3293    (use (match_operand 4))]
3294   ""
3296   if (TARGET_ABI_OPEN_VMS)
3297     emit_call_insn (gen_call_value_vms (operands[0], operands[1],
3298                                         operands[3]));
3299   else
3300     emit_call_insn (gen_call_value_osf (operands[0], operands[1],
3301                                         operands[2]));
3302   DONE;
3305 (define_expand "sibcall_value"
3306   [(parallel [(set (match_operand 0)
3307                    (call (mem:DI (match_operand 1))
3308                          (match_operand 2)))
3309               (unspec [(reg:DI 29)] UNSPEC_SIBCALL)])]
3310   "TARGET_ABI_OSF"
3312   gcc_assert (MEM_P (operands[1]));
3313   operands[1] = XEXP (operands[1], 0);
3316 (define_expand "call_value_osf"
3317   [(parallel [(set (match_operand 0)
3318                    (call (mem:DI (match_operand 1))
3319                          (match_operand 2)))
3320               (use (reg:DI 29))
3321               (clobber (reg:DI 26))])]
3322   ""
3324   gcc_assert (MEM_P (operands[1]));
3326   operands[1] = XEXP (operands[1], 0);
3327   if (! call_operand (operands[1], Pmode))
3328     operands[1] = copy_to_mode_reg (Pmode, operands[1]);
3331 (define_expand "call_value_vms"
3332   [(parallel [(set (match_operand 0)
3333                    (call (mem:DI (match_operand:DI 1))
3334                          (match_operand 2)))
3335               (use (match_dup 3))
3336               (use (reg:DI 25))
3337               (use (reg:DI 26))
3338               (clobber (reg:DI 27))])]
3339   ""
3341   gcc_assert (MEM_P (operands[1]));
3343   operands[1] = XEXP (operands[1], 0);
3345   /* Always load AI with argument information, then handle symbolic and
3346      indirect call differently.  Load RA and set operands[3] to PV in
3347      both cases.  */
3349   emit_move_insn (gen_rtx_REG (DImode, 25), operands[2]);
3350   if (GET_CODE (operands[1]) == SYMBOL_REF)
3351     {
3352       operands[3] = const0_rtx;
3353     }
3354   else
3355     {
3356       emit_move_insn (gen_rtx_REG (Pmode, 26),
3357                       gen_rtx_MEM (Pmode, plus_constant (Pmode,
3358                                                          operands[1], 8)));
3359       operands[3] = operands[1];
3360     }
3363 (define_insn "*call_osf_1_er_noreturn"
3364   [(call (mem:DI (match_operand:DI 0 "call_operand" "c,R,s"))
3365          (match_operand 1))
3366    (use (reg:DI 29))
3367    (clobber (reg:DI 26))]
3368   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF
3369    && find_reg_note (insn, REG_NORETURN, NULL_RTX)"
3370   "@
3371    jsr $26,($27),0
3372    bsr $26,%0\t\t!samegp
3373    ldq $27,%0($29)\t\t!literal!%#\;jsr $26,($27),%0\t\t!lituse_jsr!%#"
3374   [(set_attr "type" "jsr")
3375    (set_attr "length" "*,*,8")])
3377 (define_insn "*call_osf_1_er"
3378   [(call (mem:DI (match_operand:DI 0 "call_operand" "c,R,s"))
3379          (match_operand 1))
3380    (use (reg:DI 29))
3381    (clobber (reg:DI 26))]
3382   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
3383   "@
3384    jsr $26,(%0),0\;ldah $29,0($26)\t\t!gpdisp!%*\;lda $29,0($29)\t\t!gpdisp!%*
3385    bsr $26,%0\t\t!samegp
3386    ldq $27,%0($29)\t\t!literal!%#\;jsr $26,($27),%0\t\t!lituse_jsr!%#\;ldah $29,0($26)\t\t!gpdisp!%*\;lda $29,0($29)\t\t!gpdisp!%*"
3387   [(set_attr "type" "jsr")
3388    (set_attr "length" "12,*,16")])
3390 ;; We must use peep2 instead of a split because we need accurate life
3391 ;; information for $gp.  Consider the case of { bar(); while (1); }.
3392 (define_peephole2
3393   [(parallel [(call (mem:DI (match_operand:DI 0 "call_operand"))
3394                     (match_operand 1))
3395               (use (reg:DI 29))
3396               (clobber (reg:DI 26))])]
3397   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF && reload_completed
3398    && ! samegp_function_operand (operands[0], Pmode)
3399    && (peep2_regno_dead_p (1, 29)
3400        || find_reg_note (insn, REG_NORETURN, NULL_RTX))"
3401   [(parallel [(call (mem:DI (match_dup 2))
3402                     (match_dup 1))
3403               (use (reg:DI 29))
3404               (use (match_dup 0))
3405               (use (match_dup 3))
3406               (clobber (reg:DI 26))])]
3408   if (CONSTANT_P (operands[0]))
3409     {
3410       operands[2] = gen_rtx_REG (Pmode, 27);
3411       operands[3] = GEN_INT (alpha_next_sequence_number++);
3412       emit_insn (gen_movdi_er_high_g (operands[2], pic_offset_table_rtx,
3413                                       operands[0], operands[3]));
3414     }
3415   else
3416     {
3417       operands[2] = operands[0];
3418       operands[0] = const0_rtx;
3419       operands[3] = const0_rtx;
3420     }
3423 (define_peephole2
3424   [(parallel [(call (mem:DI (match_operand:DI 0 "call_operand"))
3425                     (match_operand 1))
3426               (use (reg:DI 29))
3427               (clobber (reg:DI 26))])]
3428   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF && reload_completed
3429    && ! samegp_function_operand (operands[0], Pmode)
3430    && ! (peep2_regno_dead_p (1, 29)
3431          || find_reg_note (insn, REG_NORETURN, NULL_RTX))"
3432   [(parallel [(call (mem:DI (match_dup 2))
3433                     (match_dup 1))
3434               (set (match_dup 5)
3435                    (unspec:DI [(match_dup 5) (match_dup 3)] UNSPEC_LDGP1))
3436               (use (match_dup 0))
3437               (use (match_dup 4))
3438               (clobber (reg:DI 26))])
3439    (set (match_dup 5)
3440         (unspec:DI [(match_dup 5) (match_dup 3)] UNSPEC_LDGP2))]
3442   if (CONSTANT_P (operands[0]))
3443     {
3444       operands[2] = gen_rtx_REG (Pmode, 27);
3445       operands[4] = GEN_INT (alpha_next_sequence_number++);
3446       emit_insn (gen_movdi_er_high_g (operands[2], pic_offset_table_rtx,
3447                                       operands[0], operands[4]));
3448     }
3449   else
3450     {
3451       operands[2] = operands[0];
3452       operands[0] = const0_rtx;
3453       operands[4] = const0_rtx;
3454     }
3455   operands[3] = GEN_INT (alpha_next_sequence_number++);
3456   operands[5] = pic_offset_table_rtx;
3459 (define_insn "*call_osf_2_er_nogp"
3460   [(call (mem:DI (match_operand:DI 0 "register_operand" "c"))
3461          (match_operand 1))
3462    (use (reg:DI 29))
3463    (use (match_operand 2))
3464    (use (match_operand 3 "const_int_operand"))
3465    (clobber (reg:DI 26))]
3466   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
3467   "jsr $26,(%0),%2%J3"
3468   [(set_attr "type" "jsr")])
3470 (define_insn "*call_osf_2_er"
3471   [(call (mem:DI (match_operand:DI 0 "register_operand" "c"))
3472          (match_operand 1))
3473    (set (reg:DI 29)
3474         (unspec:DI [(reg:DI 29) (match_operand 4 "const_int_operand")]
3475                    UNSPEC_LDGP1))
3476    (use (match_operand 2))
3477    (use (match_operand 3 "const_int_operand"))
3478    (clobber (reg:DI 26))]
3479   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
3480   "jsr $26,(%0),%2%J3\;ldah $29,0($26)\t\t!gpdisp!%4"
3481   [(set_attr "type" "jsr")
3482    (set_attr "cannot_copy" "true")
3483    (set_attr "length" "8")])
3485 (define_insn "*call_osf_1_noreturn"
3486   [(call (mem:DI (match_operand:DI 0 "call_operand" "c,R,s"))
3487          (match_operand 1))
3488    (use (reg:DI 29))
3489    (clobber (reg:DI 26))]
3490   "! TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF
3491    && find_reg_note (insn, REG_NORETURN, NULL_RTX)"
3492   "@
3493    jsr $26,($27),0
3494    bsr $26,$%0..ng
3495    jsr $26,%0"
3496   [(set_attr "type" "jsr")
3497    (set_attr "length" "*,*,8")])
3499 (define_insn "*call_osf_1"
3500   [(call (mem:DI (match_operand:DI 0 "call_operand" "c,R,s"))
3501          (match_operand 1))
3502    (use (reg:DI 29))
3503    (clobber (reg:DI 26))]
3504   "! TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
3505   "@
3506    jsr $26,($27),0\;ldgp $29,0($26)
3507    bsr $26,$%0..ng
3508    jsr $26,%0\;ldgp $29,0($26)"
3509   [(set_attr "type" "jsr")
3510    (set_attr "length" "12,*,16")])
3512 (define_insn "*sibcall_osf_1_er"
3513   [(call (mem:DI (match_operand:DI 0 "symbolic_operand" "R,s"))
3514          (match_operand 1))
3515    (unspec [(reg:DI 29)] UNSPEC_SIBCALL)]
3516   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
3517   "@
3518    br $31,%0\t\t!samegp
3519    ldq $27,%0($29)\t\t!literal!%#\;jmp $31,($27),%0\t\t!lituse_jsr!%#"
3520   [(set_attr "type" "jsr")
3521    (set_attr "length" "*,8")])
3523 ;; Note that the DEC assembler expands "jmp foo" with $at, which
3524 ;; doesn't do what we want.
3525 (define_insn "*sibcall_osf_1"
3526   [(call (mem:DI (match_operand:DI 0 "symbolic_operand" "R,s"))
3527          (match_operand 1))
3528    (unspec [(reg:DI 29)] UNSPEC_SIBCALL)]
3529   "! TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
3530   "@
3531    br $31,$%0..ng
3532    lda $27,%0\;jmp $31,($27),%0"
3533   [(set_attr "type" "jsr")
3534    (set_attr "length" "*,8")])
3536 ; GAS relies on the order and position of instructions output below in order
3537 ; to generate relocs for VMS link to potentially optimize the call.
3538 ; Please do not molest.
3539 (define_insn "*call_vms_1"
3540   [(call (mem:DI (match_operand:DI 0 "call_operand" "r,s"))
3541          (match_operand 1))
3542    (use (match_operand:DI 2 "nonmemory_operand" "r,n"))
3543    (use (reg:DI 25))
3544    (use (reg:DI 26))
3545    (clobber (reg:DI 27))]
3546   "TARGET_ABI_OPEN_VMS"
3548   switch (which_alternative)
3549     {
3550     case 0:
3551         return "mov %2,$27\;jsr $26,0\;ldq $27,0($29)";
3552     case 1:
3553         operands [2] = alpha_use_linkage (operands [0], true, false);
3554         operands [3] = alpha_use_linkage (operands [0], false, false);
3555         return "ldq $26,%3\;ldq $27,%2\;jsr $26,%0\;ldq $27,0($29)";
3556     default:
3557       gcc_unreachable ();
3558     }
3560   [(set_attr "type" "jsr")
3561    (set_attr "length" "12,16")])
3563 ;; Call subroutine returning any type.
3565 (define_expand "untyped_call"
3566   [(parallel [(call (match_operand 0)
3567                     (const_int 0))
3568               (match_operand 1)
3569               (match_operand 2)])]
3570   ""
3572   int i;
3574   emit_call_insn (gen_call (operands[0], const0_rtx, NULL, const0_rtx));
3576   for (i = 0; i < XVECLEN (operands[2], 0); i++)
3577     {
3578       rtx set = XVECEXP (operands[2], 0, i);
3579       emit_move_insn (SET_DEST (set), SET_SRC (set));
3580     }
3582   /* The optimizer does not know that the call sets the function value
3583      registers we stored in the result block.  We avoid problems by
3584      claiming that all hard registers are used and clobbered at this
3585      point.  */
3586   emit_insn (gen_blockage ());
3588   DONE;
3591 ;; UNSPEC_VOLATILE is considered to use and clobber all hard registers and
3592 ;; all of memory.  This blocks insns from being moved across this point.
3594 (define_insn "blockage"
3595   [(unspec_volatile [(const_int 0)] UNSPECV_BLOCKAGE)]
3596   ""
3597   ""
3598   [(set_attr "length" "0")
3599    (set_attr "type" "none")])
3601 (define_insn "jump"
3602   [(set (pc)
3603         (label_ref (match_operand 0)))]
3604   ""
3605   "br $31,%l0"
3606   [(set_attr "type" "ibr")])
3608 (define_expand "return"
3609   [(return)]
3610   "direct_return ()")
3612 (define_insn "*return_internal"
3613   [(return)]
3614   "reload_completed"
3615   "ret $31,($26),1"
3616   [(set_attr "type" "ibr")])
3618 (define_insn "indirect_jump"
3619   [(set (pc) (match_operand:DI 0 "register_operand" "r"))]
3620   ""
3621   "jmp $31,(%0),0"
3622   [(set_attr "type" "ibr")])
3624 (define_expand "tablejump"
3625   [(parallel [(set (pc)
3626                    (match_operand 0 "register_operand"))
3627               (use (label_ref:DI (match_operand 1)))])]
3628   ""
3630   if (TARGET_ABI_OSF)
3631     {
3632       rtx dest = gen_reg_rtx (DImode);
3633       emit_insn (gen_extendsidi2 (dest, operands[0]));
3634       emit_insn (gen_adddi3 (dest, pic_offset_table_rtx, dest));        
3635       operands[0] = dest;
3636     }
3639 (define_insn "*tablejump_internal"
3640   [(set (pc)
3641         (match_operand:DI 0 "register_operand" "r"))
3642    (use (label_ref (match_operand 1)))]
3643   ""
3644   "jmp $31,(%0),0"
3645   [(set_attr "type" "ibr")])
3647 ;; Cache flush.  Used by alpha_trampoline_init.  0x86 is PAL_imb, but we don't
3648 ;; want to have to include pal.h in our .s file.
3649 (define_insn "imb"
3650   [(unspec_volatile [(const_int 0)] UNSPECV_IMB)]
3651   ""
3652   "call_pal 0x86"
3653   [(set_attr "type" "callpal")])
3655 (define_expand "clear_cache"
3656   [(match_operand:DI 0)         ; region start
3657    (match_operand:DI 1)]                ; region end
3658   ""
3660   emit_insn (gen_imb ());
3661   DONE;
3664 ;; BUGCHK is documented common to OSF/1 and VMS PALcode.
3665 (define_insn "trap"
3666   [(trap_if (const_int 1) (const_int 0))
3667    (use (reg:DI 29))]
3668   ""
3669   "call_pal 0x81"
3670   [(set_attr "type" "callpal")])
3672 ;; For userland, we load the thread pointer from the TCB.
3673 ;; For the kernel, we load the per-cpu private value.
3675 (define_insn "get_thread_pointerdi"
3676   [(set (match_operand:DI 0 "register_operand" "=v")
3677         (unspec:DI [(const_int 0)] UNSPEC_TP))]
3678   "TARGET_ABI_OSF"
3680   if (TARGET_TLS_KERNEL)
3681     return "call_pal 0x32";
3682   else
3683     return "call_pal 0x9e";
3685   [(set_attr "type" "callpal")])
3687 ;; For completeness, and possibly a __builtin function, here's how to
3688 ;; set the thread pointer.  Since we don't describe enough of this
3689 ;; quantity for CSE, we have to use a volatile unspec, and then there's
3690 ;; not much point in creating an R16_REG register class.
3692 (define_expand "set_thread_pointerdi"
3693   [(set (reg:DI 16) (match_operand:DI 0 "input_operand"))
3694    (unspec_volatile [(reg:DI 16)] UNSPECV_SET_TP)]
3695   "TARGET_ABI_OSF")
3697 (define_insn "*set_tp"
3698   [(unspec_volatile [(reg:DI 16)] UNSPECV_SET_TP)]
3699   "TARGET_ABI_OSF"
3701   if (TARGET_TLS_KERNEL)
3702     return "call_pal 0x31";
3703   else
3704     return "call_pal 0x9f";
3706   [(set_attr "type" "callpal")])
3708 ;; Special builtins for establishing and reverting VMS condition handlers.
3710 (define_expand "builtin_establish_vms_condition_handler"
3711   [(set (reg:DI 0) (match_operand:DI 0 "register_operand"))
3712    (use (match_operand:DI 1 "address_operand"))]
3713   "TARGET_ABI_OPEN_VMS"
3715   alpha_expand_builtin_establish_vms_condition_handler (operands[0],
3716                                                         operands[1]);
3719 (define_expand "builtin_revert_vms_condition_handler"
3720   [(set (reg:DI 0) (match_operand:DI 0 "register_operand"))]
3721   "TARGET_ABI_OPEN_VMS"
3722   "alpha_expand_builtin_revert_vms_condition_handler (operands[0]);")
3724 ;; Finally, we have the basic data motion insns.  The byte and word insns
3725 ;; are done via define_expand.  Start with the floating-point insns, since
3726 ;; they are simpler.
3728 (define_expand "movsf"
3729   [(set (match_operand:SF 0 "nonimmediate_operand")
3730         (match_operand:SF 1 "general_operand"))]
3731   ""
3733   if (MEM_P (operands[0])
3734       && ! reg_or_0_operand (operands[1], SFmode))
3735     operands[1] = force_reg (SFmode, operands[1]);
3738 (define_insn "*movsf"
3739   [(set (match_operand:SF 0 "nonimmediate_operand" "=f,f,*r,*r,m,m,f,*r")
3740         (match_operand:SF 1 "input_operand" "fG,m,*rG,m,fG,*r,*r,f"))]
3741   "register_operand (operands[0], SFmode)
3742    || reg_or_0_operand (operands[1], SFmode)"
3743   "@
3744    cpys %R1,%R1,%0
3745    ld%, %0,%1
3746    bis $31,%r1,%0
3747    ldl %0,%1
3748    st%, %R1,%0
3749    stl %r1,%0
3750    itofs %1,%0
3751    ftois %1,%0"
3752   [(set_attr "type" "fcpys,fld,ilog,ild,fst,ist,itof,ftoi")
3753    (set_attr "isa" "*,*,*,*,*,*,fix,fix")])
3755 (define_expand "movdf"
3756   [(set (match_operand:DF 0 "nonimmediate_operand")
3757         (match_operand:DF 1 "general_operand"))]
3758   ""
3760   if (MEM_P (operands[0])
3761       && ! reg_or_0_operand (operands[1], DFmode))
3762     operands[1] = force_reg (DFmode, operands[1]);
3765 (define_insn "*movdf"
3766   [(set (match_operand:DF 0 "nonimmediate_operand" "=f,f,*r,*r,m,m,f,*r")
3767         (match_operand:DF 1 "input_operand" "fG,m,*rG,m,fG,*r,*r,f"))]
3768   "register_operand (operands[0], DFmode)
3769    || reg_or_0_operand (operands[1], DFmode)"
3770   "@
3771    cpys %R1,%R1,%0
3772    ld%- %0,%1
3773    bis $31,%r1,%0
3774    ldq %0,%1
3775    st%- %R1,%0
3776    stq %r1,%0
3777    itoft %1,%0
3778    ftoit %1,%0"
3779   [(set_attr "type" "fcpys,fld,ilog,ild,fst,ist,itof,ftoi")
3780    (set_attr "isa" "*,*,*,*,*,*,fix,fix")])
3782 ;; Subregs suck for register allocation.  Pretend we can move TFmode
3783 ;; data between general registers until after reload.
3784 ;; ??? Is this still true now that we have the lower-subreg pass?
3786 (define_expand "movtf"
3787   [(set (match_operand:TF 0 "nonimmediate_operand")
3788         (match_operand:TF 1 "general_operand"))]
3789   ""
3791   if (MEM_P (operands[0])
3792       && ! reg_or_0_operand (operands[1], TFmode))
3793     operands[1] = force_reg (TFmode, operands[1]);
3796 (define_insn_and_split "*movtf_internal"
3797   [(set (match_operand:TF 0 "nonimmediate_operand" "=r,o")
3798         (match_operand:TF 1 "input_operand" "roG,rG"))]
3799   "register_operand (operands[0], TFmode)
3800    || reg_or_0_operand (operands[1], TFmode)"
3801   "#"
3802   "reload_completed"
3803   [(set (match_dup 0) (match_dup 2))
3804    (set (match_dup 1) (match_dup 3))]
3805   "alpha_split_tmode_pair (operands, TFmode, true);")
3807 ;; We do two major things here: handle mem->mem and construct long
3808 ;; constants.
3810 (define_expand "movsi"
3811   [(set (match_operand:SI 0 "nonimmediate_operand")
3812         (match_operand:SI 1 "general_operand"))]
3813   ""
3815   if (alpha_expand_mov (SImode, operands))
3816     DONE;
3819 (define_insn "*movsi"
3820   [(set (match_operand:SI 0 "nonimmediate_operand" "=r,r,r,r,r,m,r")
3821         (match_operand:SI 1 "input_operand" "rJ,K,L,n,m,rJ,s"))]
3822   "register_operand (operands[0], SImode)
3823    || reg_or_0_operand (operands[1], SImode)"
3824   "@
3825    bis $31,%r1,%0
3826    lda %0,%1($31)
3827    ldah %0,%h1($31)
3828    #
3829    ldl %0,%1
3830    stl %r1,%0
3831    lda %0,%1"
3832   [(set_attr "type" "ilog,iadd,iadd,multi,ild,ist,ldsym")
3833    (set_attr "isa" "*,*,*,*,*,*,vms")])
3835 ;; Split a load of a large constant into the appropriate two-insn
3836 ;; sequence.
3838 (define_split
3839   [(set (match_operand:SI 0 "register_operand")
3840         (match_operand:SI 1 "non_add_const_operand"))]
3841   ""
3842   [(const_int 0)]
3844   if (alpha_split_const_mov (SImode, operands))
3845     DONE;
3846   else
3847     FAIL;
3850 (define_insn "*movdi_er_low_l"
3851   [(set (match_operand:DI 0 "register_operand" "=r")
3852         (lo_sum:DI (match_operand:DI 1 "register_operand" "r")
3853                    (match_operand:DI 2 "local_symbolic_operand")))]
3854   "TARGET_EXPLICIT_RELOCS"
3856   if (true_regnum (operands[1]) == 29)
3857     return "lda %0,%2(%1)\t\t!gprel";
3858   else
3859     return "lda %0,%2(%1)\t\t!gprellow";
3861   [(set_attr "usegp" "yes")])
3863 (define_split
3864   [(set (match_operand:DI 0 "register_operand")
3865         (match_operand:DI 1 "small_symbolic_operand"))]
3866   "TARGET_EXPLICIT_RELOCS && reload_completed"
3867   [(set (match_dup 0)
3868         (lo_sum:DI (match_dup 2) (match_dup 1)))]
3869   "operands[2] = pic_offset_table_rtx;")
3871 (define_split
3872   [(set (match_operand:DI 0 "register_operand")
3873         (match_operand:DI 1 "local_symbolic_operand"))]
3874   "TARGET_EXPLICIT_RELOCS && reload_completed"
3875   [(set (match_dup 0)
3876         (plus:DI (match_dup 2) (high:DI (match_dup 1))))
3877    (set (match_dup 0)
3878         (lo_sum:DI (match_dup 0) (match_dup 1)))]
3879   "operands[2] = pic_offset_table_rtx;")
3881 (define_split
3882   [(match_operand 0 "some_small_symbolic_operand")]
3883   ""
3884   [(match_dup 0)]
3885   "operands[0] = split_small_symbolic_operand (operands[0]);")
3887 ;; Accepts any symbolic, not just global, since function calls that
3888 ;; don't go via bsr still use !literal in hopes of linker relaxation.
3889 (define_insn "movdi_er_high_g"
3890   [(set (match_operand:DI 0 "register_operand" "=r")
3891         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
3892                     (match_operand:DI 2 "symbolic_operand")
3893                     (match_operand 3 "const_int_operand")]
3894                    UNSPEC_LITERAL))]
3895   "TARGET_EXPLICIT_RELOCS"
3897   if (INTVAL (operands[3]) == 0)
3898     return "ldq %0,%2(%1)\t\t!literal";
3899   else
3900     return "ldq %0,%2(%1)\t\t!literal!%3";
3902   [(set_attr "type" "ldsym")])
3904 (define_split
3905   [(set (match_operand:DI 0 "register_operand")
3906         (match_operand:DI 1 "global_symbolic_operand"))]
3907   "TARGET_EXPLICIT_RELOCS && reload_completed"
3908   [(set (match_dup 0)
3909         (unspec:DI [(match_dup 2)
3910                     (match_dup 1)
3911                     (const_int 0)] UNSPEC_LITERAL))]
3912   "operands[2] = pic_offset_table_rtx;")
3914 (define_insn "movdi_er_tlsgd"
3915   [(set (match_operand:DI 0 "register_operand" "=r")
3916         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
3917                     (match_operand:DI 2 "symbolic_operand")
3918                     (match_operand 3 "const_int_operand")]
3919                    UNSPEC_TLSGD))]
3920   "HAVE_AS_TLS"
3922   if (INTVAL (operands[3]) == 0)
3923     return "lda %0,%2(%1)\t\t!tlsgd";
3924   else
3925     return "lda %0,%2(%1)\t\t!tlsgd!%3";
3928 (define_insn "movdi_er_tlsldm"
3929   [(set (match_operand:DI 0 "register_operand" "=r")
3930         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
3931                     (match_operand 2 "const_int_operand")]
3932                    UNSPEC_TLSLDM))]
3933   "HAVE_AS_TLS"
3935   if (INTVAL (operands[2]) == 0)
3936     return "lda %0,%&(%1)\t\t!tlsldm";
3937   else
3938     return "lda %0,%&(%1)\t\t!tlsldm!%2";
3941 (define_insn "*movdi_er_gotdtp"
3942   [(set (match_operand:DI 0 "register_operand" "=r")
3943         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
3944                     (match_operand:DI 2 "symbolic_operand")]
3945                    UNSPEC_DTPREL))]
3946   "HAVE_AS_TLS"
3947   "ldq %0,%2(%1)\t\t!gotdtprel"
3948   [(set_attr "type" "ild")
3949    (set_attr "usegp" "yes")])
3951 (define_split
3952   [(set (match_operand:DI 0 "register_operand")
3953         (match_operand:DI 1 "gotdtp_symbolic_operand"))]
3954   "HAVE_AS_TLS && reload_completed"
3955   [(set (match_dup 0)
3956         (unspec:DI [(match_dup 2)
3957                     (match_dup 1)] UNSPEC_DTPREL))]
3959   operands[1] = XVECEXP (XEXP (operands[1], 0), 0, 0);
3960   operands[2] = pic_offset_table_rtx;
3963 (define_insn "*movdi_er_gottp"
3964   [(set (match_operand:DI 0 "register_operand" "=r")
3965         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
3966                     (match_operand:DI 2 "symbolic_operand")]
3967                    UNSPEC_TPREL))]
3968   "HAVE_AS_TLS"
3969   "ldq %0,%2(%1)\t\t!gottprel"
3970   [(set_attr "type" "ild")
3971    (set_attr "usegp" "yes")])
3973 (define_split
3974   [(set (match_operand:DI 0 "register_operand")
3975         (match_operand:DI 1 "gottp_symbolic_operand"))]
3976   "HAVE_AS_TLS && reload_completed"
3977   [(set (match_dup 0)
3978         (unspec:DI [(match_dup 2)
3979                     (match_dup 1)] UNSPEC_TPREL))]
3981   operands[1] = XVECEXP (XEXP (operands[1], 0), 0, 0);
3982   operands[2] = pic_offset_table_rtx;
3985 (define_insn "*movdi"
3986   [(set (match_operand:DI 0 "nonimmediate_operand"
3987                                 "=r,r,r,r,r,r,r,r, m, *f,*f, Q, r,*f")
3988         (match_operand:DI 1 "input_operand"
3989                                 "rJ,K,L,T,s,n,s,m,rJ,*fJ, Q,*f,*f, r"))]
3990   "register_operand (operands[0], DImode)
3991    || reg_or_0_operand (operands[1], DImode)"
3992   "@
3993    mov %r1,%0
3994    lda %0,%1($31)
3995    ldah %0,%h1($31)
3996    #
3997    #
3998    #
3999    lda %0,%1
4000    ldq%A1 %0,%1
4001    stq%A0 %r1,%0
4002    fmov %R1,%0
4003    ldt %0,%1
4004    stt %R1,%0
4005    ftoit %1,%0
4006    itoft %1,%0"
4007   [(set_attr "type" "ilog,iadd,iadd,iadd,ldsym,multi,ldsym,ild,ist,fcpys,fld,fst,ftoi,itof")
4008    (set_attr "isa" "*,*,*,er,er,*,ner,*,*,*,*,*,fix,fix")
4009    (set_attr "usegp" "*,*,*,yes,*,*,*,*,*,*,*,*,*,*")])
4011 ;; VMS needs to set up "vms_base_regno" for unwinding.  This move
4012 ;; often appears dead to the life analysis code, at which point we
4013 ;; die for emitting dead prologue instructions.  Force this live.
4015 (define_insn "force_movdi"
4016   [(set (match_operand:DI 0 "register_operand" "=r")
4017         (unspec_volatile:DI [(match_operand:DI 1 "register_operand" "r")]
4018                             UNSPECV_FORCE_MOV))]
4019   ""
4020   "mov %1,%0"
4021   [(set_attr "type" "ilog")])
4023 ;; We do three major things here: handle mem->mem, put 64-bit constants in
4024 ;; memory, and construct long 32-bit constants.
4026 (define_expand "movdi"
4027   [(set (match_operand:DI 0 "nonimmediate_operand")
4028         (match_operand:DI 1 "general_operand"))]
4029   ""
4031   if (alpha_expand_mov (DImode, operands))
4032     DONE;
4035 ;; Split a load of a large constant into the appropriate two-insn
4036 ;; sequence.
4038 (define_split
4039   [(set (match_operand:DI 0 "register_operand")
4040         (match_operand:DI 1 "non_add_const_operand"))]
4041   ""
4042   [(const_int 0)]
4044   if (alpha_split_const_mov (DImode, operands))
4045     DONE;
4046   else
4047     FAIL;
4050 ;; We need to prevent reload from splitting TImode moves, because it
4051 ;; might decide to overwrite a pointer with the value it points to.
4052 ;; In that case we have to do the loads in the appropriate order so
4053 ;; that the pointer is not destroyed too early.
4055 (define_insn_and_split "*movti_internal"
4056   [(set (match_operand:TI 0 "nonimmediate_operand" "=r,o")
4057         (match_operand:TI 1 "input_operand" "roJ,rJ"))]
4058   "(register_operand (operands[0], TImode)
4059     /* Prevent rematerialization of constants.  */
4060     && ! CONSTANT_P (operands[1]))
4061    || reg_or_0_operand (operands[1], TImode)"
4062   "#"
4063   "reload_completed"
4064   [(set (match_dup 0) (match_dup 2))
4065    (set (match_dup 1) (match_dup 3))]
4066   "alpha_split_tmode_pair (operands, TImode, true);")
4068 (define_expand "movti"
4069   [(set (match_operand:TI 0 "nonimmediate_operand")
4070         (match_operand:TI 1 "general_operand"))]
4071   ""
4073   if (MEM_P (operands[0])
4074       && ! reg_or_0_operand (operands[1], TImode))
4075     operands[1] = force_reg (TImode, operands[1]);
4077   if (operands[1] == const0_rtx)
4078     ;
4079   /* We must put 64-bit constants in memory.  We could keep the
4080      32-bit constants in TImode and rely on the splitter, but
4081      this doesn't seem to be worth the pain.  */
4082   else if (CONST_SCALAR_INT_P (operands[1]))
4083     {
4084       rtx in[2], out[2], target;
4086       gcc_assert (can_create_pseudo_p ());
4088       split_double (operands[1], &in[0], &in[1]);
4090       if (in[0] == const0_rtx)
4091         out[0] = const0_rtx;
4092       else
4093         {
4094           out[0] = gen_reg_rtx (DImode);
4095           emit_insn (gen_movdi (out[0], in[0]));
4096         }
4098       if (in[1] == const0_rtx)
4099         out[1] = const0_rtx;
4100       else
4101         {
4102           out[1] = gen_reg_rtx (DImode);
4103           emit_insn (gen_movdi (out[1], in[1]));
4104         }
4106       if (!REG_P (operands[0]))
4107         target = gen_reg_rtx (TImode);
4108       else
4109         target = operands[0];
4111       emit_insn (gen_movdi (operand_subword (target, 0, 0, TImode), out[0]));
4112       emit_insn (gen_movdi (operand_subword (target, 1, 0, TImode), out[1]));
4114       if (target != operands[0])
4115         emit_insn (gen_rtx_SET (operands[0], target));
4117       DONE;
4118     }
4121 ;; These are the partial-word cases.
4123 ;; First we have the code to load an aligned word.  Operand 0 is the register
4124 ;; in which to place the result.  It's mode is QImode or HImode.  Operand 1
4125 ;; is an SImode MEM at the low-order byte of the proper word.  Operand 2 is the
4126 ;; number of bits within the word that the value is.  Operand 3 is an SImode
4127 ;; scratch register.  If operand 0 is a hard register, operand 3 may be the
4128 ;; same register.  It is allowed to conflict with operand 1 as well.
4130 (define_expand "aligned_loadqi"
4131   [(set (match_operand:SI 3 "register_operand")
4132         (match_operand:SI 1 "memory_operand"))
4133    (set (match_operand:DI 0 "register_operand")
4134         (zero_extract:DI (subreg:DI (match_dup 3) 0)
4135                          (const_int 8)
4136                          (match_operand:DI 2 "const_int_operand")))])
4138 (define_expand "aligned_loadhi"
4139   [(set (match_operand:SI 3 "register_operand")
4140         (match_operand:SI 1 "memory_operand"))
4141    (set (match_operand:DI 0 "register_operand")
4142         (zero_extract:DI (subreg:DI (match_dup 3) 0)
4143                          (const_int 16)
4144                          (match_operand:DI 2 "const_int_operand")))])
4146 ;; Similar for unaligned loads, where we use the sequence from the
4147 ;; Alpha Architecture manual. We have to distinguish between little-endian
4148 ;; and big-endian systems as the sequences are different.
4150 ;; Operand 1 is the address.  Operands 2 and 3 are temporaries, where
4151 ;; operand 3 can overlap the input and output registers.
4153 (define_expand "unaligned_loadqi"
4154   [(set (match_operand:DI 2 "register_operand")
4155         (mem:DI (and:DI (match_operand:DI 1 "address_operand")
4156                         (const_int -8))))
4157    (set (match_operand:DI 3 "register_operand")
4158         (match_dup 1))
4159    (set (match_operand:DI 0 "register_operand")
4160         (zero_extract:DI (match_dup 2)
4161                          (const_int 8)
4162                          (ashift:DI (match_dup 3) (const_int 3))))])
4164 (define_expand "unaligned_loadhi"
4165   [(set (match_operand:DI 2 "register_operand")
4166         (mem:DI (and:DI (match_operand:DI 1 "address_operand")
4167                         (const_int -8))))
4168    (set (match_operand:DI 3 "register_operand")
4169         (match_dup 1))
4170    (set (match_operand:DI 0 "register_operand")
4171         (zero_extract:DI (match_dup 2)
4172                          (const_int 16)
4173                          (ashift:DI (match_dup 3) (const_int 3))))])
4175 ;; Storing an aligned byte or word requires two temporaries.  Operand 0 is the
4176 ;; aligned SImode MEM.  Operand 1 is the register containing the
4177 ;; byte or word to store.  Operand 2 is the number of bits within the word that
4178 ;; the value should be placed.  Operands 3 and 4 are SImode temporaries.
4180 (define_expand "aligned_store"
4181   [(set (match_operand:SI 3 "register_operand")
4182         (match_operand:SI 0 "memory_operand"))
4183    (set (subreg:DI (match_dup 3) 0)
4184         (and:DI (subreg:DI (match_dup 3) 0) (match_dup 5)))
4185    (set (subreg:DI (match_operand:SI 4 "register_operand") 0)
4186         (ashift:DI (zero_extend:DI (match_operand 1 "register_operand"))
4187                    (match_operand:DI 2 "const_int_operand")))
4188    (set (subreg:DI (match_dup 4) 0)
4189         (ior:DI (subreg:DI (match_dup 4) 0) (subreg:DI (match_dup 3) 0)))
4190    (set (match_dup 0) (match_dup 4))]
4191   ""
4193   operands[5] = GEN_INT (~ (GET_MODE_MASK (GET_MODE (operands[1]))
4194                             << INTVAL (operands[2])));
4197 ;; For the unaligned byte and halfword cases, we use code similar to that
4198 ;; in the ;; Architecture book, but reordered to lower the number of registers
4199 ;; required.  Operand 0 is the address.  Operand 1 is the data to store.
4200 ;; Operands 2, 3, and 4 are DImode temporaries, where operands 2 and 4 may
4201 ;; be the same temporary, if desired.  If the address is in a register,
4202 ;; operand 2 can be that register.
4204 (define_expand "@unaligned_store<mode>"
4205   [(set (match_operand:DI 3 "register_operand")
4206         (mem:DI (and:DI (match_operand:DI 0 "address_operand")
4207                         (const_int -8))))
4208    (set (match_operand:DI 2 "register_operand")
4209         (match_dup 0))
4210    (set (match_dup 3)
4211         (and:DI (not:DI (ashift:DI (match_dup 5)
4212                                    (ashift:DI (match_dup 2) (const_int 3))))
4213                 (match_dup 3)))
4214    (set (match_operand:DI 4 "register_operand")
4215         (ashift:DI (zero_extend:DI
4216                      (match_operand:I12MODE 1 "register_operand"))
4217                    (ashift:DI (match_dup 2) (const_int 3))))
4218    (set (match_dup 4) (ior:DI (match_dup 4) (match_dup 3)))
4219    (set (mem:DI (and:DI (match_dup 0) (const_int -8)))
4220         (match_dup 4))]
4221   ""
4222   "operands[5] = GEN_INT (GET_MODE_MASK (<MODE>mode));")
4224 ;; Here are the define_expand's for QI and HI moves that use the above
4225 ;; patterns.  We have the normal sets, plus the ones that need scratch
4226 ;; registers for reload.
4228 (define_expand "mov<mode>"
4229   [(set (match_operand:I12MODE 0 "nonimmediate_operand")
4230         (match_operand:I12MODE 1 "general_operand"))]
4231   ""
4233   if (TARGET_BWX
4234       ? alpha_expand_mov (<MODE>mode, operands)
4235       : alpha_expand_mov_nobwx (<MODE>mode, operands))
4236     DONE;
4239 (define_insn "*movqi"
4240   [(set (match_operand:QI 0 "nonimmediate_operand" "=r,r,r,m")
4241         (match_operand:QI 1 "input_operand" "rJ,n,m,rJ"))]
4242   "register_operand (operands[0], QImode)
4243    || reg_or_0_operand (operands[1], QImode)"
4244   "@
4245    bis $31,%r1,%0
4246    lda %0,%L1($31)
4247    ldbu %0,%1
4248    stb %r1,%0"
4249   [(set_attr "type" "ilog,iadd,ild,ist")
4250    (set_attr "isa" "*,*,bwx,bwx")])
4252 (define_insn "*movhi"
4253   [(set (match_operand:HI 0 "nonimmediate_operand" "=r,r,r,m")
4254         (match_operand:HI 1 "input_operand" "rJ,n,m,rJ"))]
4255   "register_operand (operands[0], HImode)
4256    || reg_or_0_operand (operands[1], HImode)"
4257   "@
4258    bis $31,%r1,%0
4259    lda %0,%L1($31)
4260    ldwu %0,%1
4261    stw %r1,%0"
4262   [(set_attr "type" "ilog,iadd,ild,ist")
4263    (set_attr "isa" "*,*,bwx,bwx")])
4265 ;; We need to hook into the extra support that we have for HImode 
4266 ;; reloads when BWX insns are not available.
4267 (define_expand "movcqi"
4268   [(set (match_operand:CQI 0 "nonimmediate_operand")
4269         (match_operand:CQI 1 "general_operand"))]
4270   "!TARGET_BWX"
4272   if (GET_CODE (operands[0]) == CONCAT || GET_CODE (operands[1]) == CONCAT)
4273     ;
4274   else if (!any_memory_operand (operands[0], CQImode))
4275     {
4276       if (!any_memory_operand (operands[1], CQImode))
4277         {
4278           emit_move_insn (gen_lowpart (HImode, operands[0]),
4279                           gen_lowpart (HImode, operands[1]));
4280           DONE;
4281         }
4282       if (aligned_memory_operand (operands[1], CQImode))
4283         {
4284           bool done;
4285         do_aligned1:
4286           operands[1] = gen_lowpart (HImode, operands[1]);
4287         do_aligned2:
4288           operands[0] = gen_lowpart (HImode, operands[0]);
4289           done = alpha_expand_mov_nobwx (HImode, operands);
4290           gcc_assert (done);
4291           DONE;
4292         }
4293     }
4294   else if (aligned_memory_operand (operands[0], CQImode))
4295     {
4296       if (MEM_P (operands[1]))
4297         {
4298           rtx x = gen_reg_rtx (HImode);
4299           emit_move_insn (gen_lowpart (CQImode, x), operands[1]);
4300           operands[1] = x;
4301           goto do_aligned2;
4302         }
4303       goto do_aligned1;
4304     }
4306   gcc_assert (!reload_in_progress);
4307   emit_move_complex_parts (operands[0], operands[1]);
4308   DONE;
4311 ;; Here are the versions for reload.
4312 ;; 
4313 ;; The aligned input case is recognized early in alpha_secondary_reload
4314 ;; in order to avoid allocating an unnecessary scratch register.
4315 ;; 
4316 ;; Note that in the unaligned cases we know that the operand must not be
4317 ;; a pseudo-register because stack slots are always aligned references.
4319 (define_expand "reload_in<mode>"
4320   [(parallel [(match_operand:RELOAD12 0 "register_operand" "=r")
4321               (match_operand:RELOAD12 1 "any_memory_operand" "m")
4322               (match_operand:TI 2 "register_operand" "=&r")])]
4323   "!TARGET_BWX"
4325   rtx scratch, seq, addr;
4326   unsigned regno = REGNO (operands[2]);
4328   /* It is possible that one of the registers we got for operands[2]
4329      might coincide with that of operands[0] (which is why we made
4330      it TImode).  Pick the other one to use as our scratch.  */
4331   if (regno == REGNO (operands[0]))
4332     regno++;
4333   scratch = gen_rtx_REG (DImode, regno);
4335   addr = get_unaligned_address (operands[1]);
4336   operands[0] = gen_rtx_REG (DImode, REGNO (operands[0]));
4337   seq = gen_unaligned_load<reloadmode> (operands[0], addr,
4338                                         scratch, operands[0]);
4339   alpha_set_memflags (seq, operands[1]);
4341   emit_insn (seq);
4342   DONE;
4345 (define_expand "reload_out<mode>"
4346   [(parallel [(match_operand:RELOAD12 0 "any_memory_operand" "=m")
4347               (match_operand:RELOAD12 1 "register_operand" "r")
4348               (match_operand:TI 2 "register_operand" "=&r")])]
4349   "!TARGET_BWX"
4351   unsigned regno = REGNO (operands[2]);
4353   if (<MODE>mode == CQImode)
4354     {
4355       operands[0] = gen_lowpart (HImode, operands[0]);
4356       operands[1] = gen_lowpart (HImode, operands[1]);
4357     }
4359   if (aligned_memory_operand (operands[0], <MODE>mode))
4360     {
4361       emit_insn (gen_reload_out<reloadmode>_aligned
4362                  (operands[0], operands[1],
4363                   gen_rtx_REG (SImode, regno),
4364                   gen_rtx_REG (SImode, regno + 1)));
4365     }
4366   else
4367     {
4368       rtx addr = get_unaligned_address (operands[0]);
4369       rtx scratch1 = gen_rtx_REG (DImode, regno);
4370       rtx scratch2 = gen_rtx_REG (DImode, regno + 1);
4371       rtx scratch3 = scratch1;
4372       rtx seq;
4374       if (REG_P (addr))
4375         scratch1 = addr;
4377       seq = gen_unaligned_store<reloadmode> (addr, operands[1], scratch1,
4378                                              scratch2, scratch3);
4379       alpha_set_memflags (seq, operands[0]);
4380       emit_insn (seq);
4381     }
4382   DONE;
4385 ;; Helpers for the above.  The way reload is structured, we can't
4386 ;; always get a proper address for a stack slot during reload_foo
4387 ;; expansion, so we must delay our address manipulations until after.
4389 (define_insn_and_split "@reload_in<mode>_aligned"
4390   [(set (match_operand:I12MODE 0 "register_operand" "=r")
4391         (match_operand:I12MODE 1 "memory_operand" "m"))]
4392   "!TARGET_BWX && (reload_in_progress || reload_completed)"
4393   "#"
4394   "!TARGET_BWX && reload_completed"
4395   [(const_int 0)]
4397   rtx aligned_mem, bitnum;
4398   get_aligned_mem (operands[1], &aligned_mem, &bitnum);
4399   emit_insn (gen_aligned_load<reloadmode>
4400              (gen_lowpart (DImode, operands[0]), aligned_mem, bitnum,
4401               gen_rtx_REG (SImode, REGNO (operands[0]))));
4402   DONE;
4405 (define_insn_and_split "reload_out<mode>_aligned"
4406   [(set (match_operand:I12MODE 0 "memory_operand" "=m")
4407         (match_operand:I12MODE 1 "register_operand" "r"))
4408    (clobber (match_operand:SI 2 "register_operand" "=&r"))
4409    (clobber (match_operand:SI 3 "register_operand" "=&r"))]
4410   "!TARGET_BWX && (reload_in_progress || reload_completed)"
4411   "#"
4412   "!TARGET_BWX && reload_completed"
4413   [(const_int 0)]
4415   rtx aligned_mem, bitnum;
4416   get_aligned_mem (operands[0], &aligned_mem, &bitnum);
4417   emit_insn (gen_aligned_store (aligned_mem, operands[1], bitnum,
4418                                 operands[2], operands[3]));
4419   DONE;
4422 ;; Vector operations
4424 (define_mode_iterator VEC [V8QI V4HI V2SI])
4425 (define_mode_iterator VEC12 [V8QI V4HI])
4427 (define_expand "mov<mode>"
4428   [(set (match_operand:VEC 0 "nonimmediate_operand")
4429         (match_operand:VEC 1 "general_operand"))]
4430   ""
4432   if (alpha_expand_mov (<MODE>mode, operands))
4433     DONE;
4436 (define_split
4437   [(set (match_operand:VEC 0 "register_operand")
4438         (match_operand:VEC 1 "non_zero_const_operand"))]
4439   ""
4440   [(const_int 0)]
4442   if (alpha_split_const_mov (<MODE>mode, operands))
4443     DONE;
4444   else
4445     FAIL;
4449 (define_expand "movmisalign<mode>"
4450   [(set (match_operand:VEC 0 "nonimmediate_operand")
4451         (match_operand:VEC 1 "general_operand"))]
4452   ""
4454   alpha_expand_movmisalign (<MODE>mode, operands);
4455   DONE;
4458 (define_insn "*mov<mode>_fix"
4459   [(set (match_operand:VEC 0 "nonimmediate_operand" "=r,r,r,m,*f,*f,m,r,*f")
4460         (match_operand:VEC 1 "input_operand" "rW,i,m,rW,*fW,m,*f,*f,r"))]
4461   "register_operand (operands[0], <MODE>mode)
4462    || reg_or_0_operand (operands[1], <MODE>mode)"
4463   "@
4464    bis $31,%r1,%0
4465    #
4466    ldq %0,%1
4467    stq %r1,%0
4468    cpys %R1,%R1,%0
4469    ldt %0,%1
4470    stt %R1,%0
4471    ftoit %1,%0
4472    itoft %1,%0"
4473   [(set_attr "type" "ilog,multi,ild,ist,fcpys,fld,fst,ftoi,itof")
4474    (set_attr "isa" "*,*,*,*,*,*,*,fix,fix")])
4476 (define_insn "<code><mode>3"
4477   [(set (match_operand:VEC12 0 "register_operand" "=r")
4478         (any_maxmin:VEC12
4479          (match_operand:VEC12 1 "reg_or_0_operand" "rW")
4480          (match_operand:VEC12 2 "reg_or_0_operand" "rW")))]
4481   "TARGET_MAX"
4482   "<maxmin><modesuffix> %r1,%r2,%0"
4483   [(set_attr "type" "mvi")])
4485 (define_insn "one_cmpl<mode>2"
4486   [(set (match_operand:VEC 0 "register_operand" "=r")
4487         (not:VEC (match_operand:VEC 1 "register_operand" "r")))]
4488   ""
4489   "ornot $31,%1,%0"
4490   [(set_attr "type" "ilog")])
4492 (define_insn "and<mode>3"
4493   [(set (match_operand:VEC 0 "register_operand" "=r")
4494         (and:VEC (match_operand:VEC 1 "register_operand" "r")
4495                  (match_operand:VEC 2 "register_operand" "r")))]
4496   ""
4497   "and %1,%2,%0"
4498   [(set_attr "type" "ilog")])
4500 (define_insn "*andnot<mode>3"
4501   [(set (match_operand:VEC 0 "register_operand" "=r")
4502         (and:VEC (not:VEC (match_operand:VEC 1 "register_operand" "r"))
4503                  (match_operand:VEC 2 "register_operand" "r")))]
4504   ""
4505   "bic %2,%1,%0"
4506   [(set_attr "type" "ilog")])
4508 (define_insn "ior<mode>3"
4509   [(set (match_operand:VEC 0 "register_operand" "=r")
4510         (ior:VEC (match_operand:VEC 1 "register_operand" "r")
4511                  (match_operand:VEC 2 "register_operand" "r")))]
4512   ""
4513   "bis %1,%2,%0"
4514   [(set_attr "type" "ilog")])
4516 (define_insn "*iornot<mode>3"
4517   [(set (match_operand:VEC 0 "register_operand" "=r")
4518         (ior:VEC (not:DI (match_operand:VEC 1 "register_operand" "r"))
4519                  (match_operand:VEC 2 "register_operand" "r")))]
4520   ""
4521   "ornot %2,%1,%0"
4522   [(set_attr "type" "ilog")])
4524 (define_insn "xor<mode>3"
4525   [(set (match_operand:VEC 0 "register_operand" "=r")
4526         (xor:VEC (match_operand:VEC 1 "register_operand" "r")
4527                  (match_operand:VEC 2 "register_operand" "r")))]
4528   ""
4529   "xor %1,%2,%0"
4530   [(set_attr "type" "ilog")])
4532 (define_insn "*xornot<mode>3"
4533   [(set (match_operand:VEC 0 "register_operand" "=r")
4534         (not:VEC (xor:VEC (match_operand:VEC 1 "register_operand" "r")
4535                           (match_operand:VEC 2 "register_operand" "r"))))]
4536   ""
4537   "eqv %1,%2,%0"
4538   [(set_attr "type" "ilog")])
4540 (define_expand "vec_shl_<mode>"
4541   [(set (match_operand:VEC 0 "register_operand")
4542         (ashift:DI (match_operand:VEC 1 "register_operand")
4543                    (match_operand:DI 2 "reg_or_6bit_operand")))]
4544   ""
4546   operands[0] = gen_lowpart (DImode, operands[0]);
4547   operands[1] = gen_lowpart (DImode, operands[1]);
4550 (define_expand "vec_shr_<mode>"
4551   [(set (match_operand:VEC 0 "register_operand")
4552         (lshiftrt:DI (match_operand:VEC 1 "register_operand")
4553                      (match_operand:DI 2 "reg_or_6bit_operand")))]
4554   ""
4556   operands[0] = gen_lowpart (DImode, operands[0]);
4557   operands[1] = gen_lowpart (DImode, operands[1]);
4560 ;; Bit field extract patterns which use ext[wlq][lh]
4562 (define_expand "extvmisaligndi"
4563   [(set (match_operand:DI 0 "register_operand")
4564         (sign_extract:DI (match_operand:BLK 1 "memory_operand")
4565                          (match_operand:DI 2 "const_int_operand")
4566                          (match_operand:DI 3 "const_int_operand")))]
4567   ""
4569   /* We can do 16, 32 and 64 bit fields, if aligned on byte boundaries.  */
4570   if (INTVAL (operands[3]) % 8 != 0
4571       || (INTVAL (operands[2]) != 16
4572           && INTVAL (operands[2]) != 32
4573           && INTVAL (operands[2]) != 64))
4574     FAIL;
4576   alpha_expand_unaligned_load (operands[0], operands[1],
4577                                INTVAL (operands[2]) / 8,
4578                                INTVAL (operands[3]) / 8, 1);
4579   DONE;
4582 (define_expand "extzvdi"
4583   [(set (match_operand:DI 0 "register_operand")
4584         (zero_extract:DI (match_operand:DI 1 "register_operand")
4585                          (match_operand:DI 2 "const_int_operand")
4586                          (match_operand:DI 3 "const_int_operand")))]
4587   ""
4589   /* We can do 8, 16, 32 and 64 bit fields, if aligned on byte boundaries.  */
4590   if (INTVAL (operands[3]) % 8 != 0
4591       || (INTVAL (operands[2]) != 8
4592           && INTVAL (operands[2]) != 16
4593           && INTVAL (operands[2]) != 32
4594           && INTVAL (operands[2]) != 64))
4595     FAIL;
4598 (define_expand "extzvmisaligndi"
4599   [(set (match_operand:DI 0 "register_operand")
4600         (zero_extract:DI (match_operand:BLK 1 "memory_operand")
4601                          (match_operand:DI 2 "const_int_operand")
4602                          (match_operand:DI 3 "const_int_operand")))]
4603   ""
4605   /* We can do 16, 32 and 64 bit fields, if aligned on byte boundaries.
4606      We fail 8-bit fields, falling back on a simple byte load.  */
4607   if (INTVAL (operands[3]) % 8 != 0
4608       || (INTVAL (operands[2]) != 16
4609           && INTVAL (operands[2]) != 32
4610           && INTVAL (operands[2]) != 64))
4611     FAIL;
4613   alpha_expand_unaligned_load (operands[0], operands[1],
4614                                INTVAL (operands[2]) / 8,
4615                                INTVAL (operands[3]) / 8, 0);
4616   DONE;
4619 (define_expand "insvmisaligndi"
4620   [(set (zero_extract:DI (match_operand:BLK 0 "memory_operand")
4621                          (match_operand:DI 1 "const_int_operand")
4622                          (match_operand:DI 2 "const_int_operand"))
4623         (match_operand:DI 3 "register_operand"))]
4624   ""
4626   /* We can do 16, 32 and 64 bit fields, if aligned on byte boundaries.  */
4627   if (INTVAL (operands[2]) % 8 != 0
4628       || (INTVAL (operands[1]) != 16
4629           && INTVAL (operands[1]) != 32
4630           && INTVAL (operands[1]) != 64))
4631     FAIL;
4633   alpha_expand_unaligned_store (operands[0], operands[3],
4634                                 INTVAL (operands[1]) / 8,
4635                                 INTVAL (operands[2]) / 8);
4636   DONE;
4639 ;; Block move/clear, see alpha.cc for more details.
4640 ;; Argument 0 is the destination
4641 ;; Argument 1 is the source
4642 ;; Argument 2 is the length
4643 ;; Argument 3 is the alignment
4645 (define_expand "cpymemqi"
4646   [(parallel [(set (match_operand:BLK 0 "memory_operand")
4647                    (match_operand:BLK 1 "memory_operand"))
4648               (use (match_operand:DI 2 "immediate_operand"))
4649               (use (match_operand:DI 3 "immediate_operand"))])]
4650   ""
4652   if (alpha_expand_block_move (operands))
4653     DONE;
4654   else
4655     FAIL;
4658 (define_expand "cpymemdi"
4659   [(parallel [(set (match_operand:BLK 0 "memory_operand")
4660                    (match_operand:BLK 1 "memory_operand"))
4661               (use (match_operand:DI 2 "immediate_operand"))
4662               (use (match_operand:DI 3 "immediate_operand"))
4663               (use (match_dup 4))
4664               (clobber (reg:DI 25))
4665               (clobber (reg:DI 16))
4666               (clobber (reg:DI 17))
4667               (clobber (reg:DI 18))
4668               (clobber (reg:DI 19))
4669               (clobber (reg:DI 20))
4670               (clobber (reg:DI 26))
4671               (clobber (reg:DI 27))])]
4672   "TARGET_ABI_OPEN_VMS"
4673   "operands[4] = gen_rtx_SYMBOL_REF (Pmode, \"OTS$MOVE\");")
4675 (define_insn "*cpymemdi_1"
4676   [(set (match_operand:BLK 0 "memory_operand" "=m,m")
4677         (match_operand:BLK 1 "memory_operand" "m,m"))
4678    (use (match_operand:DI 2 "nonmemory_operand" "r,i"))
4679    (use (match_operand:DI 3 "immediate_operand"))
4680    (use (match_operand:DI 4 "call_operand" "i,i"))
4681    (clobber (reg:DI 25))
4682    (clobber (reg:DI 16))
4683    (clobber (reg:DI 17))
4684    (clobber (reg:DI 18))
4685    (clobber (reg:DI 19))
4686    (clobber (reg:DI 20))
4687    (clobber (reg:DI 26))
4688    (clobber (reg:DI 27))]
4689   "TARGET_ABI_OPEN_VMS"
4691   operands [5] = alpha_use_linkage (operands [4], false, true);
4692   switch (which_alternative)
4693     {
4694     case 0:
4695         return "lda $16,%0\;bis $31,%2,$17\;lda $18,%1\;ldq $26,%5\;lda $25,3($31)\;jsr $26,%4\;ldq $27,0($29)";
4696     case 1:
4697         return "lda $16,%0\;lda $17,%2($31)\;lda $18,%1\;ldq $26,%5\;lda $25,3($31)\;jsr $26,%4\;ldq $27,0($29)";
4698     default:
4699       gcc_unreachable ();
4700     }
4702   [(set_attr "type" "multi")
4703    (set_attr "length" "28")])
4705 (define_expand "setmemqi"
4706   [(parallel [(set (match_operand:BLK 0 "memory_operand")
4707                    (match_operand 2 "const_int_operand"))
4708               (use (match_operand:DI 1 "immediate_operand"))
4709               (use (match_operand:DI 3 "immediate_operand"))])]
4710   ""
4712   /* If value to set is not zero, use the library routine.  */
4713   if (operands[2] != const0_rtx)
4714     FAIL;
4716   if (alpha_expand_block_clear (operands))
4717     DONE;
4718   else
4719     FAIL;
4722 (define_expand "setmemdi"
4723   [(parallel [(set (match_operand:BLK 0 "memory_operand")
4724                    (match_operand 2 "const_int_operand"))
4725               (use (match_operand:DI 1 "immediate_operand"))
4726               (use (match_operand:DI 3 "immediate_operand"))
4727               (use (match_dup 4))
4728               (clobber (reg:DI 25))
4729               (clobber (reg:DI 16))
4730               (clobber (reg:DI 17))
4731               (clobber (reg:DI 26))
4732               (clobber (reg:DI 27))])]
4733   "TARGET_ABI_OPEN_VMS"
4735   /* If value to set is not zero, use the library routine.  */
4736   if (operands[2] != const0_rtx)
4737     FAIL;
4739   operands[4] = gen_rtx_SYMBOL_REF (Pmode, "OTS$ZERO");
4742 (define_insn "*clrmemdi_1"
4743   [(set (match_operand:BLK 0 "memory_operand" "=m,m")
4744                    (const_int 0))
4745    (use (match_operand:DI 1 "nonmemory_operand" "r,i"))
4746    (use (match_operand:DI 2 "immediate_operand"))
4747    (use (match_operand:DI 3 "call_operand" "i,i"))
4748    (clobber (reg:DI 25))
4749    (clobber (reg:DI 16))
4750    (clobber (reg:DI 17))
4751    (clobber (reg:DI 26))
4752    (clobber (reg:DI 27))]
4753   "TARGET_ABI_OPEN_VMS"
4755   operands [4] = alpha_use_linkage (operands [3], false, true);
4756   switch (which_alternative)
4757     {
4758     case 0:
4759         return "lda $16,%0\;bis $31,%1,$17\;ldq $26,%4\;lda $25,2($31)\;jsr $26,%3\;ldq $27,0($29)";
4760     case 1:
4761         return "lda $16,%0\;lda $17,%1($31)\;ldq $26,%4\;lda $25,2($31)\;jsr $26,%3\;ldq $27,0($29)";
4762     default:
4763       gcc_unreachable ();
4764     }
4766   [(set_attr "type" "multi")
4767    (set_attr "length" "24")])
4770 ;; Subroutine of stack space allocation.  Perform a stack probe.
4771 (define_expand "stack_probe_internal"
4772   [(set (match_dup 1) (match_operand:DI 0 "const_int_operand"))]
4773   ""
4775   operands[1] = gen_rtx_MEM (DImode, plus_constant (Pmode, stack_pointer_rtx,
4776                                                     INTVAL (operands[0])));
4777   MEM_VOLATILE_P (operands[1]) = 1;
4779   operands[0] = const0_rtx;
4782 ;; This is how we allocate stack space.  If we are allocating a
4783 ;; constant amount of space and we know it is less than 4096
4784 ;; bytes, we need do nothing.
4786 ;; If it is more than 4096 bytes, we need to probe the stack
4787 ;; periodically.
4788 (define_expand "allocate_stack"
4789   [(set (reg:DI 30)
4790         (plus:DI (reg:DI 30)
4791                  (match_operand:DI 1 "reg_or_cint_operand")))
4792    (set (match_operand:DI 0 "register_operand" "=r")
4793         (match_dup 2))]
4794   ""
4796   if (CONST_INT_P (operands[1])
4797       && INTVAL (operands[1]) < 32768)
4798     {
4799       if (INTVAL (operands[1]) >= 4096)
4800         {
4801           /* We do this the same way as in the prologue and generate explicit
4802              probes.  Then we update the stack by the constant.  */
4804           int probed = 4096;
4806           emit_insn (gen_stack_probe_internal (GEN_INT (- probed)));
4807           while (probed + 8192 < INTVAL (operands[1]))
4808             emit_insn (gen_stack_probe_internal
4809                        (GEN_INT (- (probed += 8192))));
4811           if (probed + 4096 < INTVAL (operands[1]))
4812             emit_insn (gen_stack_probe_internal
4813                        (GEN_INT (- INTVAL(operands[1]))));
4814         }
4816       operands[1] = GEN_INT (- INTVAL (operands[1]));
4817       operands[2] = virtual_stack_dynamic_rtx;
4818     }
4819   else
4820     {
4821       rtx_code_label *out_label = 0;
4822       rtx_code_label *loop_label = gen_label_rtx ();
4823       rtx want = gen_reg_rtx (Pmode);
4824       rtx tmp = gen_reg_rtx (Pmode);
4825       rtx memref, test;
4827       emit_insn (gen_subdi3 (want, stack_pointer_rtx,
4828                              force_reg (Pmode, operands[1])));
4830       if (!CONST_INT_P (operands[1]))
4831         {
4832           rtx limit = GEN_INT (4096);
4833           out_label = gen_label_rtx ();
4834           test = gen_rtx_LTU (VOIDmode, operands[1], limit);
4835           emit_jump_insn
4836             (gen_cbranchdi4 (test, operands[1], limit, out_label));
4837         }
4839       emit_insn (gen_adddi3 (tmp, stack_pointer_rtx, GEN_INT (-4096)));
4840       emit_label (loop_label);
4841       memref = gen_rtx_MEM (DImode, tmp);
4842       MEM_VOLATILE_P (memref) = 1;
4843       emit_move_insn (memref, const0_rtx);
4844       emit_insn (gen_adddi3 (tmp, tmp, GEN_INT(-8192)));
4845       test = gen_rtx_GTU (VOIDmode, tmp, want);
4846       emit_jump_insn (gen_cbranchdi4 (test, tmp, want, loop_label));
4848       memref = gen_rtx_MEM (DImode, want);
4849       MEM_VOLATILE_P (memref) = 1;
4850       emit_move_insn (memref, const0_rtx);
4852       if (out_label)
4853         emit_label (out_label);
4855       emit_move_insn (stack_pointer_rtx, want);
4856       emit_move_insn (operands[0], virtual_stack_dynamic_rtx);
4857       DONE;
4858     }
4861 ;; This is used by alpha_expand_prolog to do the same thing as above,
4862 ;; except we cannot at that time generate new basic blocks, so we hide
4863 ;; the loop in this one insn.
4865 (define_insn "prologue_stack_probe_loop"
4866   [(unspec_volatile [(match_operand:DI 0 "register_operand" "r")
4867                      (match_operand:DI 1 "register_operand" "r")]
4868                     UNSPECV_PSPL)]
4869   ""
4871   operands[2] = gen_label_rtx ();
4872   (*targetm.asm_out.internal_label) (asm_out_file, "L",
4873                              CODE_LABEL_NUMBER (operands[2]));
4875   return "stq $31,-8192(%1)\;subq %0,1,%0\;lda %1,-8192(%1)\;bne %0,%l2";
4877   [(set_attr "length" "16")
4878    (set_attr "type" "multi")])
4880 (define_expand "prologue"
4881   [(const_int 0)]
4882   ""
4884   alpha_expand_prologue ();
4885   DONE;
4888 ;; These take care of emitting the ldgp insn in the prologue. This will be
4889 ;; an lda/ldah pair and we want to align them properly.  So we have two
4890 ;; unspec_volatile insns, the first of which emits the ldgp assembler macro
4891 ;; and the second of which emits nothing.  However, both are marked as type
4892 ;; IADD (the default) so the alignment code in alpha.cc does the right thing
4893 ;; with them.
4895 (define_expand "prologue_ldgp"
4896   [(set (match_dup 0)
4897         (unspec_volatile:DI [(match_dup 1) (match_dup 2)] UNSPECV_LDGP1))
4898    (set (match_dup 0)
4899         (unspec_volatile:DI [(match_dup 0) (match_dup 2)] UNSPECV_PLDGP2))]
4900   ""
4902   operands[0] = pic_offset_table_rtx;
4903   operands[1] = gen_rtx_REG (Pmode, 27);
4904   operands[2] = (TARGET_EXPLICIT_RELOCS
4905                  ? GEN_INT (alpha_next_sequence_number++)
4906                  : const0_rtx);
4909 (define_insn "*ldgp_er_1"
4910   [(set (match_operand:DI 0 "register_operand" "=r")
4911         (unspec_volatile:DI [(match_operand:DI 1 "register_operand" "r")
4912                              (match_operand 2 "const_int_operand")]
4913                             UNSPECV_LDGP1))]
4914   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
4915   "ldah %0,0(%1)\t\t!gpdisp!%2"
4916   [(set_attr "cannot_copy" "true")])
4918 (define_insn "*ldgp_er_2"
4919   [(set (match_operand:DI 0 "register_operand" "=r")
4920         (unspec:DI [(match_operand:DI 1 "register_operand" "r")
4921                     (match_operand 2 "const_int_operand")]
4922                    UNSPEC_LDGP2))]
4923   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
4924   "lda %0,0(%1)\t\t!gpdisp!%2"
4925   [(set_attr "cannot_copy" "true")])
4927 (define_insn "*prologue_ldgp_er_2"
4928   [(set (match_operand:DI 0 "register_operand" "=r")
4929         (unspec_volatile:DI [(match_operand:DI 1 "register_operand" "r")
4930                              (match_operand 2 "const_int_operand")]
4931                             UNSPECV_PLDGP2))]
4932   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
4933   "lda %0,0(%1)\t\t!gpdisp!%2\n$%~..ng:"
4934   [(set_attr "cannot_copy" "true")])
4936 (define_insn "*prologue_ldgp_1"
4937   [(set (match_operand:DI 0 "register_operand" "=r")
4938         (unspec_volatile:DI [(match_operand:DI 1 "register_operand" "r")
4939                              (match_operand 2 "const_int_operand")]
4940                             UNSPECV_LDGP1))]
4941   ""
4942   "ldgp %0,0(%1)\n$%~..ng:"
4943   [(set_attr "cannot_copy" "true")])
4945 (define_insn "*prologue_ldgp_2"
4946   [(set (match_operand:DI 0 "register_operand" "=r")
4947         (unspec_volatile:DI [(match_operand:DI 1 "register_operand" "r")
4948                              (match_operand 2 "const_int_operand")]
4949                             UNSPECV_PLDGP2))]
4950   ""
4953 ;; The _mcount profiling hook has special calling conventions, and
4954 ;; does not clobber all the registers that a normal call would.  So
4955 ;; hide the fact this is a call at all.
4957 (define_insn "prologue_mcount"
4958   [(unspec_volatile [(const_int 0)] UNSPECV_MCOUNT)]
4959   ""
4961   if (TARGET_EXPLICIT_RELOCS)
4962     /* Note that we cannot use a lituse_jsr reloc, since _mcount
4963        cannot be called via the PLT.  */
4964     return "ldq $28,_mcount($29)\t\t!literal\;jsr $28,($28),_mcount";
4965   else
4966     return "lda $28,_mcount\;jsr $28,($28),_mcount";
4968   [(set_attr "type" "multi")
4969    (set_attr "length" "8")])
4971 (define_insn "init_fp"
4972   [(set (match_operand:DI 0 "register_operand" "=r")
4973         (match_operand:DI 1 "register_operand" "r"))
4974    (clobber (mem:BLK (match_operand:DI 2 "register_operand" "=r")))]
4975   ""
4976   "bis $31,%1,%0")
4978 (define_expand "epilogue"
4979   [(return)]
4980   ""
4981   "alpha_expand_epilogue ();")
4983 (define_expand "sibcall_epilogue"
4984   [(return)]
4985   "TARGET_ABI_OSF"
4987   alpha_expand_epilogue ();
4988   DONE;
4991 (define_expand "builtin_longjmp"
4992   [(use (match_operand:DI 0 "register_operand" "r"))]
4993   "TARGET_ABI_OSF"
4995   /* The elements of the buffer are, in order:  */
4996   rtx fp = gen_rtx_MEM (Pmode, operands[0]);
4997   rtx lab = gen_rtx_MEM (Pmode, plus_constant (Pmode, operands[0], 8));
4998   rtx stack = gen_rtx_MEM (Pmode, plus_constant (Pmode, operands[0], 16));
4999   rtx pv = gen_rtx_REG (Pmode, 27);
5001   /* This bit is the same as expand_builtin_longjmp.  */
5002   emit_move_insn (hard_frame_pointer_rtx, fp);
5003   emit_move_insn (pv, lab);
5004   emit_stack_restore (SAVE_NONLOCAL, stack);
5005   emit_use (hard_frame_pointer_rtx);
5006   emit_use (stack_pointer_rtx);
5008   /* Load the label we are jumping through into $27 so that we know
5009      where to look for it when we get back to setjmp's function for
5010      restoring the gp.  */
5011   emit_jump_insn (gen_builtin_longjmp_internal (pv));
5012   emit_barrier ();
5013   DONE;
5016 ;; This is effectively a copy of indirect_jump, but constrained such
5017 ;; that register renaming cannot foil our cunning plan with $27.
5018 (define_insn "builtin_longjmp_internal"
5019   [(set (pc)
5020         (unspec_volatile [(match_operand:DI 0 "register_operand" "c")]
5021                          UNSPECV_LONGJMP))]
5022   ""
5023   "jmp $31,(%0),0"
5024   [(set_attr "type" "ibr")])
5026 (define_expand "builtin_setjmp_receiver"
5027   [(unspec_volatile [(label_ref (match_operand 0))] UNSPECV_SETJMPR)]
5028   "TARGET_ABI_OSF")
5030 (define_insn_and_split "*builtin_setjmp_receiver_1"
5031   [(unspec_volatile [(match_operand 0)] UNSPECV_SETJMPR)]
5032   "TARGET_ABI_OSF"
5034   if (TARGET_EXPLICIT_RELOCS)
5035     return "#";
5036   else
5037     return "br $27,$LSJ%=\n$LSJ%=:\;ldgp $29,0($27)";
5039   "&& TARGET_EXPLICIT_RELOCS && reload_completed"
5040   [(set (match_dup 1)
5041         (unspec_volatile:DI [(match_dup 2) (match_dup 3)] UNSPECV_LDGP1))
5042    (set (match_dup 1)
5043         (unspec:DI [(match_dup 1) (match_dup 3)] UNSPEC_LDGP2))]
5045   if (prev_nonnote_insn (curr_insn) != XEXP (operands[0], 0))
5046     emit_insn (gen_rtx_UNSPEC_VOLATILE (VOIDmode, gen_rtvec (1, operands[0]),
5047                                         UNSPECV_SETJMPR_ER));
5048   operands[1] = pic_offset_table_rtx;
5049   operands[2] = gen_rtx_REG (Pmode, 27);
5050   operands[3] = GEN_INT (alpha_next_sequence_number++);
5052   [(set_attr "length" "12")
5053    (set_attr "type" "multi")])
5055 (define_insn "*builtin_setjmp_receiver_er_sl_1"
5056   [(unspec_volatile [(match_operand 0)] UNSPECV_SETJMPR_ER)]
5057   "TARGET_ABI_OSF && TARGET_EXPLICIT_RELOCS"
5058   "lda $27,$LSJ%=-%l0($27)\n$LSJ%=:")
5059   
5060 ;; When flag_reorder_blocks_and_partition is in effect, compiler puts
5061 ;; exception landing pads in a cold section.  To prevent inter-section offset
5062 ;; calculation, a jump to original landing pad is emitted in the place of the
5063 ;; original landing pad.  Since landing pad is moved, RA-relative GP
5064 ;; calculation in the prologue of landing pad breaks.  To solve this problem,
5065 ;; we use alternative GP load approach.
5067 (define_expand "exception_receiver"
5068   [(unspec_volatile [(match_dup 0)] UNSPECV_EHR)]
5069   "TARGET_ABI_OSF"
5071   if (flag_reorder_blocks_and_partition)
5072     operands[0] = copy_rtx (alpha_gp_save_rtx ());
5073   else
5074     operands[0] = const0_rtx;
5077 (define_insn "*exception_receiver_2"
5078   [(unspec_volatile [(match_operand:DI 0 "memory_operand" "m")] UNSPECV_EHR)]
5079   "TARGET_ABI_OSF && flag_reorder_blocks_and_partition"
5080   "ldq $29,%0"
5081   [(set_attr "type" "ild")])
5083 (define_insn_and_split "*exception_receiver_1"
5084   [(unspec_volatile [(const_int 0)] UNSPECV_EHR)]
5085   "TARGET_ABI_OSF"
5087   if (TARGET_EXPLICIT_RELOCS)
5088     return "#";
5089   else
5090     return "ldgp $29,0($26)";
5092   "&& TARGET_EXPLICIT_RELOCS && reload_completed"
5093   [(set (match_dup 0)
5094         (unspec_volatile:DI [(match_dup 1) (match_dup 2)] UNSPECV_LDGP1))
5095    (set (match_dup 0)
5096         (unspec:DI [(match_dup 0) (match_dup 2)] UNSPEC_LDGP2))]
5098   operands[0] = pic_offset_table_rtx;
5099   operands[1] = gen_rtx_REG (Pmode, 26);
5100   operands[2] = GEN_INT (alpha_next_sequence_number++);
5102   [(set_attr "length" "8")
5103    (set_attr "type" "multi")])
5105 (define_expand "nonlocal_goto_receiver"
5106   [(unspec_volatile [(const_int 0)] UNSPECV_BLOCKAGE)
5107    (set (reg:DI 27) (mem:DI (reg:DI 29)))
5108    (unspec_volatile [(const_int 0)] UNSPECV_BLOCKAGE)
5109    (use (reg:DI 27))]
5110   "TARGET_ABI_OPEN_VMS")
5112 (define_insn "arg_home"
5113   [(unspec [(const_int 0)] UNSPEC_ARG_HOME)
5114    (use (reg:DI 1))
5115    (use (reg:DI 25))
5116    (use (reg:DI 16))
5117    (use (reg:DI 17))
5118    (use (reg:DI 18))
5119    (use (reg:DI 19))
5120    (use (reg:DI 20))
5121    (use (reg:DI 21))
5122    (use (reg:DI 48))
5123    (use (reg:DI 49))
5124    (use (reg:DI 50))
5125    (use (reg:DI 51))
5126    (use (reg:DI 52))
5127    (use (reg:DI 53))
5128    (clobber (mem:BLK (const_int 0)))
5129    (clobber (reg:DI 24))
5130    (clobber (reg:DI 25))
5131    (clobber (reg:DI 0))]
5132   "TARGET_ABI_OPEN_VMS"
5133   "lda $0,OTS$HOME_ARGS\;ldq $0,8($0)\;jsr $0,OTS$HOME_ARGS"
5134   [(set_attr "length" "16")
5135    (set_attr "type" "multi")])
5137 ;; Prefetch data.  
5139 ;; On EV4, these instructions are nops -- no load occurs.
5141 ;; On EV5, these instructions act as a normal load, and thus can trap
5142 ;; if the address is invalid.  The OS may (or may not) handle this in
5143 ;; the entMM fault handler and suppress the fault.  If so, then this
5144 ;; has the effect of a read prefetch instruction.
5146 ;; On EV6, these become official prefetch instructions.
5148 (define_insn "prefetch"
5149   [(prefetch (match_operand:DI 0 "address_operand" "p")
5150              (match_operand:DI 1 "const_int_operand" "n")
5151              (match_operand:DI 2 "const_int_operand" "n"))]
5152   "TARGET_FIXUP_EV5_PREFETCH || alpha_cpu == PROCESSOR_EV6"
5154   /* Interpret "no temporal locality" as this data should be evicted once
5155      it is used.  The "evict next" alternatives load the data into the cache
5156      and leave the LRU eviction counter pointing to that block.  */
5157   static const char * const alt[2][2] = {
5158     { 
5159       "ldq $31,%a0",            /* read, evict next */
5160       "ldl $31,%a0",            /* read, evict last */
5161     },
5162     {
5163       "ldt $f31,%a0",           /* write, evict next */
5164       "lds $f31,%a0",           /* write, evict last */
5165     }
5166   };
5168   bool write = INTVAL (operands[1]) != 0;
5169   bool lru = INTVAL (operands[2]) != 0;
5171   return alt[write][lru];
5173   [(set_attr "type" "ild")])
5175 ;; Close the trap shadow of preceding instructions.  This is generated
5176 ;; by alpha_reorg.
5178 (define_insn "trapb"
5179   [(unspec_volatile [(const_int 0)] UNSPECV_TRAPB)]
5180   ""
5181   "trapb"
5182   [(set_attr "type" "misc")])
5184 ;; No-op instructions used by machine-dependent reorg to preserve
5185 ;; alignment for instruction issue.
5186 ;; The Unicos/Mk assembler does not support these opcodes.
5188 (define_insn "nop"
5189   [(const_int 0)]
5190   ""
5191   "bis $31,$31,$31"
5192   [(set_attr "type" "ilog")])
5194 (define_insn "fnop"
5195   [(const_int 1)]
5196   "TARGET_FP"
5197   "cpys $f31,$f31,$f31"
5198   [(set_attr "type" "fcpys")])
5200 (define_insn "unop"
5201   [(const_int 2)]
5202   ""
5203   "ldq_u $31,0($30)")
5205 (define_insn "realign"
5206   [(unspec_volatile [(match_operand 0 "immediate_operand" "i")]
5207                     UNSPECV_REALIGN)]
5208   ""
5209   ".align %0 #realign")
5211 ;; Instructions to be emitted from __builtins.
5213 (define_insn "builtin_cmpbge"
5214   [(set (match_operand:DI 0 "register_operand" "=r")
5215         (unspec:DI [(match_operand:DI 1 "reg_or_0_operand" "rJ")
5216                     (match_operand:DI 2 "reg_or_8bit_operand" "rI")]
5217                    UNSPEC_CMPBGE))]
5218   ""
5219   "cmpbge %r1,%2,%0"
5220   ;; The EV6 data sheets list this as ILOG.  OTOH, EV6 doesn't 
5221   ;; actually differentiate between ILOG and ICMP in the schedule.
5222   [(set_attr "type" "icmp")])
5224 (define_expand "extbl"
5225   [(match_operand:DI 0 "register_operand")
5226    (match_operand:DI 1 "reg_or_0_operand")
5227    (match_operand:DI 2 "reg_or_8bit_operand")]
5228   ""
5230   emit_insn (gen_extxl (operands[0], operands[1], GEN_INT (8), operands[2]));
5231   DONE;
5234 (define_expand "extwl"
5235   [(match_operand:DI 0 "register_operand")
5236    (match_operand:DI 1 "reg_or_0_operand")
5237    (match_operand:DI 2 "reg_or_8bit_operand")]
5238   ""
5240   emit_insn (gen_extxl (operands[0], operands[1], GEN_INT (16), operands[2]));
5241   DONE;
5244 (define_expand "extll"
5245   [(match_operand:DI 0 "register_operand")
5246    (match_operand:DI 1 "reg_or_0_operand")
5247    (match_operand:DI 2 "reg_or_8bit_operand")]
5248   ""
5250   emit_insn (gen_extxl (operands[0], operands[1], GEN_INT (32), operands[2]));
5251   DONE;
5254 (define_expand "extql"
5255   [(match_operand:DI 0 "register_operand")
5256    (match_operand:DI 1 "reg_or_0_operand")
5257    (match_operand:DI 2 "reg_or_8bit_operand")]
5258   ""
5260   emit_insn (gen_extxl (operands[0], operands[1], GEN_INT (64), operands[2]));
5261   DONE;
5264 (define_expand "builtin_insbl"
5265   [(match_operand:DI 0 "register_operand")
5266    (match_operand:DI 1 "register_operand")
5267    (match_operand:DI 2 "reg_or_8bit_operand")]
5268   ""
5270   operands[1] = gen_lowpart (QImode, operands[1]);
5271   emit_insn (gen_insbl (operands[0], operands[1], operands[2]));
5272   DONE;
5275 (define_expand "builtin_inswl"
5276   [(match_operand:DI 0 "register_operand")
5277    (match_operand:DI 1 "register_operand")
5278    (match_operand:DI 2 "reg_or_8bit_operand")]
5279   ""
5281   operands[1] = gen_lowpart (HImode, operands[1]);
5282   emit_insn (gen_inswl (operands[0], operands[1], operands[2]));
5283   DONE;
5286 (define_expand "builtin_insll"
5287   [(match_operand:DI 0 "register_operand")
5288    (match_operand:DI 1 "register_operand")
5289    (match_operand:DI 2 "reg_or_8bit_operand")]
5290   ""
5292   operands[1] = gen_lowpart (SImode, operands[1]);
5293   emit_insn (gen_insll (operands[0], operands[1], operands[2]));
5294   DONE;
5297 (define_expand "inswh"
5298   [(match_operand:DI 0 "register_operand")
5299    (match_operand:DI 1 "register_operand")
5300    (match_operand:DI 2 "reg_or_8bit_operand")]
5301   ""
5303   emit_insn (gen_insxh (operands[0], operands[1], GEN_INT (16), operands[2]));
5304   DONE;
5307 (define_expand "inslh"
5308   [(match_operand:DI 0 "register_operand")
5309    (match_operand:DI 1 "register_operand")
5310    (match_operand:DI 2 "reg_or_8bit_operand")]
5311   ""
5313   emit_insn (gen_insxh (operands[0], operands[1], GEN_INT (32), operands[2]));
5314   DONE;
5317 (define_expand "insqh"
5318   [(match_operand:DI 0 "register_operand")
5319    (match_operand:DI 1 "register_operand")
5320    (match_operand:DI 2 "reg_or_8bit_operand")]
5321   ""
5323   emit_insn (gen_insxh (operands[0], operands[1], GEN_INT (64), operands[2]));
5324   DONE;
5327 (define_expand "mskbl"
5328   [(match_operand:DI 0 "register_operand")
5329    (match_operand:DI 1 "reg_or_0_operand")
5330    (match_operand:DI 2 "reg_or_8bit_operand")]
5331   ""
5333   rtx mask = GEN_INT (0xff);
5334   emit_insn (gen_mskxl (operands[0], operands[1], mask, operands[2]));
5335   DONE;
5338 (define_expand "mskwl"
5339   [(match_operand:DI 0 "register_operand")
5340    (match_operand:DI 1 "reg_or_0_operand")
5341    (match_operand:DI 2 "reg_or_8bit_operand")]
5342   ""
5344   rtx mask = GEN_INT (0xffff);
5345   emit_insn (gen_mskxl (operands[0], operands[1], mask, operands[2]));
5346   DONE;
5349 (define_expand "mskll"
5350   [(match_operand:DI 0 "register_operand")
5351    (match_operand:DI 1 "reg_or_0_operand")
5352    (match_operand:DI 2 "reg_or_8bit_operand")]
5353   ""
5355   rtx mask = gen_int_mode (0xffffffff, DImode);
5356   emit_insn (gen_mskxl (operands[0], operands[1], mask, operands[2]));
5357   DONE;
5360 (define_expand "mskql"
5361   [(match_operand:DI 0 "register_operand")
5362    (match_operand:DI 1 "reg_or_0_operand")
5363    (match_operand:DI 2 "reg_or_8bit_operand")]
5364   ""
5366   rtx mask = constm1_rtx;
5367   emit_insn (gen_mskxl (operands[0], operands[1], mask, operands[2]));
5368   DONE;
5371 (define_expand "mskwh"
5372   [(match_operand:DI 0 "register_operand")
5373    (match_operand:DI 1 "register_operand")
5374    (match_operand:DI 2 "reg_or_8bit_operand")]
5375   ""
5377   emit_insn (gen_mskxh (operands[0], operands[1], GEN_INT (16), operands[2]));
5378   DONE;
5381 (define_expand "msklh"
5382   [(match_operand:DI 0 "register_operand")
5383    (match_operand:DI 1 "register_operand")
5384    (match_operand:DI 2 "reg_or_8bit_operand")]
5385   ""
5387   emit_insn (gen_mskxh (operands[0], operands[1], GEN_INT (32), operands[2]));
5388   DONE;
5391 (define_expand "mskqh"
5392   [(match_operand:DI 0 "register_operand")
5393    (match_operand:DI 1 "register_operand")
5394    (match_operand:DI 2 "reg_or_8bit_operand")]
5395   ""
5397   emit_insn (gen_mskxh (operands[0], operands[1], GEN_INT (64), operands[2]));
5398   DONE;
5401 (define_expand "builtin_zap"
5402   [(set (match_operand:DI 0 "register_operand")
5403         (and:DI (unspec:DI
5404                   [(match_operand:DI 2 "reg_or_cint_operand")]
5405                   UNSPEC_ZAP)
5406                 (match_operand:DI 1 "reg_or_cint_operand")))]
5407   ""
5409   if (CONST_INT_P (operands[2]))
5410     {
5411       rtx mask = alpha_expand_zap_mask (INTVAL (operands[2]));
5413       if (mask == const0_rtx)
5414         {
5415           emit_move_insn (operands[0], const0_rtx);
5416           DONE;
5417         }
5418       if (mask == constm1_rtx)
5419         {
5420           emit_move_insn (operands[0], operands[1]);
5421           DONE;
5422         }
5424       operands[1] = force_reg (DImode, operands[1]);
5425       emit_insn (gen_anddi3 (operands[0], operands[1], mask));
5426       DONE;
5427     }
5429   operands[1] = force_reg (DImode, operands[1]);
5430   operands[2] = gen_lowpart (QImode, operands[2]);
5433 (define_insn "*builtin_zap_1"
5434   [(set (match_operand:DI 0 "register_operand" "=r,r,r,r")
5435         (and:DI (unspec:DI
5436                   [(match_operand:QI 2 "reg_or_cint_operand" "n,n,r,r")]
5437                   UNSPEC_ZAP)
5438                 (match_operand:DI 1 "reg_or_cint_operand" "n,r,J,r")))]
5439   ""
5440   "@
5441    #
5442    #
5443    bis $31,$31,%0
5444    zap %r1,%2,%0"
5445   [(set_attr "type" "shift,shift,ilog,shift")])
5447 (define_split
5448   [(set (match_operand:DI 0 "register_operand")
5449         (and:DI (unspec:DI
5450                   [(match_operand:QI 2 "const_int_operand")]
5451                   UNSPEC_ZAP)
5452                 (match_operand:DI 1 "const_int_operand")))]
5453   ""
5454   [(const_int 0)]
5456   rtx mask = alpha_expand_zap_mask (INTVAL (operands[2]));
5458   operands[1] = gen_int_mode (INTVAL (operands[1]) & INTVAL (mask), DImode);
5459   emit_move_insn (operands[0], operands[1]);
5460   DONE;
5463 (define_split
5464   [(set (match_operand:DI 0 "register_operand")
5465         (and:DI (unspec:DI
5466                   [(match_operand:QI 2 "const_int_operand")]
5467                   UNSPEC_ZAP)
5468                 (match_operand:DI 1 "register_operand")))]
5469   ""
5470   [(set (match_dup 0)
5471         (and:DI (match_dup 1) (match_dup 2)))]
5473   operands[2] = alpha_expand_zap_mask (INTVAL (operands[2]));
5474   if (operands[2] == const0_rtx)
5475     {
5476       emit_move_insn (operands[0], const0_rtx);
5477       DONE;
5478     }
5479   if (operands[2] == constm1_rtx)
5480     {
5481       emit_move_insn (operands[0], operands[1]);
5482       DONE;
5483     }
5486 (define_expand "builtin_zapnot"
5487   [(set (match_operand:DI 0 "register_operand")
5488         (and:DI (unspec:DI
5489                   [(not:QI (match_operand:DI 2 "reg_or_cint_operand"))]
5490                   UNSPEC_ZAP)
5491                 (match_operand:DI 1 "reg_or_cint_operand")))]
5492   ""
5494   if (CONST_INT_P (operands[2]))
5495     {
5496       rtx mask = alpha_expand_zap_mask (~ INTVAL (operands[2]));
5498       if (mask == const0_rtx)
5499         {
5500           emit_move_insn (operands[0], const0_rtx);
5501           DONE;
5502         }
5503       if (mask == constm1_rtx)
5504         {
5505           emit_move_insn (operands[0], operands[1]);
5506           DONE;
5507         }
5509       operands[1] = force_reg (DImode, operands[1]);
5510       emit_insn (gen_anddi3 (operands[0], operands[1], mask));
5511       DONE;
5512     }
5514   operands[1] = force_reg (DImode, operands[1]);
5515   operands[2] = gen_lowpart (QImode, operands[2]);
5518 (define_insn "*builtin_zapnot_1"
5519   [(set (match_operand:DI 0 "register_operand" "=r")
5520         (and:DI (unspec:DI
5521                   [(not:QI (match_operand:QI 2 "register_operand" "r"))]
5522                   UNSPEC_ZAP)
5523                 (match_operand:DI 1 "reg_or_0_operand" "rJ")))]
5524   ""
5525   "zapnot %r1,%2,%0"
5526   [(set_attr "type" "shift")])
5528 (define_insn "builtin_amask"
5529   [(set (match_operand:DI 0 "register_operand" "=r")
5530         (unspec:DI [(match_operand:DI 1 "reg_or_8bit_operand" "rI")]
5531                    UNSPEC_AMASK))]
5532   ""
5533   "amask %1,%0"
5534   [(set_attr "type" "ilog")])
5536 (define_insn "builtin_implver"
5537   [(set (match_operand:DI 0 "register_operand" "=r")
5538         (unspec:DI [(const_int 0)] UNSPEC_IMPLVER))]
5539   ""
5540   "implver %0"
5541   [(set_attr "type" "ilog")])
5543 (define_insn "builtin_rpcc"
5544   [(set (match_operand:DI 0 "register_operand" "=r")
5545         (unspec_volatile:DI [(const_int 0)] UNSPECV_RPCC))]
5546   ""
5547   "rpcc %0"
5548   [(set_attr "type" "ilog")])
5550 (define_expand "builtin_minub8"
5551   [(match_operand:DI 0 "register_operand")
5552    (match_operand:DI 1 "reg_or_0_operand")
5553    (match_operand:DI 2 "reg_or_0_operand")]
5554   "TARGET_MAX"
5556   alpha_expand_builtin_vector_binop (gen_uminv8qi3, V8QImode, operands[0],
5557                                      operands[1], operands[2]);
5558   DONE;
5561 (define_expand "builtin_minsb8"
5562   [(match_operand:DI 0 "register_operand")
5563    (match_operand:DI 1 "reg_or_0_operand")
5564    (match_operand:DI 2 "reg_or_0_operand")]
5565   "TARGET_MAX"
5567   alpha_expand_builtin_vector_binop (gen_sminv8qi3, V8QImode, operands[0],
5568                                      operands[1], operands[2]);
5569   DONE;
5572 (define_expand "builtin_minuw4"
5573   [(match_operand:DI 0 "register_operand")
5574    (match_operand:DI 1 "reg_or_0_operand")
5575    (match_operand:DI 2 "reg_or_0_operand")]
5576   "TARGET_MAX"
5578   alpha_expand_builtin_vector_binop (gen_uminv4hi3, V4HImode, operands[0],
5579                                      operands[1], operands[2]);
5580   DONE;
5583 (define_expand "builtin_minsw4"
5584   [(match_operand:DI 0 "register_operand")
5585    (match_operand:DI 1 "reg_or_0_operand")
5586    (match_operand:DI 2 "reg_or_0_operand")]
5587   "TARGET_MAX"
5589   alpha_expand_builtin_vector_binop (gen_sminv4hi3, V4HImode, operands[0],
5590                                      operands[1], operands[2]);
5591   DONE;
5594 (define_expand "builtin_maxub8"
5595   [(match_operand:DI 0 "register_operand")
5596    (match_operand:DI 1 "reg_or_0_operand")
5597    (match_operand:DI 2 "reg_or_0_operand")]
5598   "TARGET_MAX"
5600   alpha_expand_builtin_vector_binop (gen_umaxv8qi3, V8QImode, operands[0],
5601                                      operands[1], operands[2]);
5602   DONE;
5605 (define_expand "builtin_maxsb8"
5606   [(match_operand:DI 0 "register_operand")
5607    (match_operand:DI 1 "reg_or_0_operand")
5608    (match_operand:DI 2 "reg_or_0_operand")]
5609   "TARGET_MAX"
5611   alpha_expand_builtin_vector_binop (gen_smaxv8qi3, V8QImode, operands[0],
5612                                      operands[1], operands[2]);
5613   DONE;
5616 (define_expand "builtin_maxuw4"
5617   [(match_operand:DI 0 "register_operand")
5618    (match_operand:DI 1 "reg_or_0_operand")
5619    (match_operand:DI 2 "reg_or_0_operand")]
5620   "TARGET_MAX"
5622   alpha_expand_builtin_vector_binop (gen_umaxv4hi3, V4HImode, operands[0],
5623                                      operands[1], operands[2]);
5624   DONE;
5627 (define_expand "builtin_maxsw4"
5628   [(match_operand:DI 0 "register_operand")
5629    (match_operand:DI 1 "reg_or_0_operand")
5630    (match_operand:DI 2 "reg_or_0_operand")]
5631   "TARGET_MAX"
5633   alpha_expand_builtin_vector_binop (gen_smaxv4hi3, V4HImode, operands[0],
5634                                      operands[1], operands[2]);
5635   DONE;
5638 (define_insn "builtin_perr"
5639   [(set (match_operand:DI 0 "register_operand" "=r")
5640         (unspec:DI [(match_operand:DI 1 "reg_or_0_operand" "%rJ")
5641                     (match_operand:DI 2 "reg_or_8bit_operand" "rJ")]
5642                    UNSPEC_PERR))]
5643   "TARGET_MAX"
5644   "perr %r1,%r2,%0"
5645   [(set_attr "type" "mvi")])
5647 (define_expand "builtin_pklb"
5648   [(set (match_operand:DI 0 "register_operand")
5649         (vec_concat:V8QI
5650           (vec_concat:V4QI
5651             (truncate:V2QI (match_operand:DI 1 "register_operand"))
5652             (match_dup 2))
5653           (match_dup 3)))]
5654   "TARGET_MAX"
5656   operands[0] = gen_lowpart (V8QImode, operands[0]);
5657   operands[1] = gen_lowpart (V2SImode, operands[1]);
5658   operands[2] = CONST0_RTX (V2QImode);
5659   operands[3] = CONST0_RTX (V4QImode);
5662 (define_insn "*pklb"
5663   [(set (match_operand:V8QI 0 "register_operand" "=r")
5664         (vec_concat:V8QI
5665           (vec_concat:V4QI
5666             (truncate:V2QI (match_operand:V2SI 1 "register_operand" "r"))
5667             (match_operand:V2QI 2 "const0_operand"))
5668           (match_operand:V4QI 3 "const0_operand")))]
5669   "TARGET_MAX"
5670   "pklb %r1,%0"
5671   [(set_attr "type" "mvi")])
5673 (define_expand "builtin_pkwb"
5674   [(set (match_operand:DI 0 "register_operand")
5675         (vec_concat:V8QI
5676           (truncate:V4QI (match_operand:DI 1 "register_operand"))
5677           (match_dup 2)))]
5678   "TARGET_MAX"
5680   operands[0] = gen_lowpart (V8QImode, operands[0]);
5681   operands[1] = gen_lowpart (V4HImode, operands[1]);
5682   operands[2] = CONST0_RTX (V4QImode);
5685 (define_insn "*pkwb"
5686   [(set (match_operand:V8QI 0 "register_operand" "=r")
5687         (vec_concat:V8QI
5688           (truncate:V4QI (match_operand:V4HI 1 "register_operand" "r"))
5689           (match_operand:V4QI 2 "const0_operand")))]
5690   "TARGET_MAX"
5691   "pkwb %r1,%0"
5692   [(set_attr "type" "mvi")])
5694 (define_expand "builtin_unpkbl"
5695   [(set (match_operand:DI 0 "register_operand")
5696         (zero_extend:V2SI
5697           (vec_select:V2QI (match_operand:DI 1 "register_operand")
5698                            (parallel [(const_int 0) (const_int 1)]))))]
5699   "TARGET_MAX"
5701   operands[0] = gen_lowpart (V2SImode, operands[0]);
5702   operands[1] = gen_lowpart (V8QImode, operands[1]);
5705 (define_insn "*unpkbl"
5706   [(set (match_operand:V2SI 0 "register_operand" "=r")
5707         (zero_extend:V2SI
5708           (vec_select:V2QI (match_operand:V8QI 1 "reg_or_0_operand" "rW")
5709                            (parallel [(const_int 0) (const_int 1)]))))]
5710   "TARGET_MAX"
5711   "unpkbl %r1,%0"
5712   [(set_attr "type" "mvi")])
5714 (define_expand "builtin_unpkbw"
5715   [(set (match_operand:DI 0 "register_operand")
5716         (zero_extend:V4HI
5717           (vec_select:V4QI (match_operand:DI 1 "register_operand")
5718                            (parallel [(const_int 0)
5719                                       (const_int 1)
5720                                       (const_int 2)
5721                                       (const_int 3)]))))]
5722   "TARGET_MAX"
5724   operands[0] = gen_lowpart (V4HImode, operands[0]);
5725   operands[1] = gen_lowpart (V8QImode, operands[1]);
5728 (define_insn "*unpkbw"
5729   [(set (match_operand:V4HI 0 "register_operand" "=r")
5730         (zero_extend:V4HI
5731           (vec_select:V4QI (match_operand:V8QI 1 "reg_or_0_operand" "rW")
5732                            (parallel [(const_int 0)
5733                                       (const_int 1)
5734                                       (const_int 2)
5735                                       (const_int 3)]))))]
5736   "TARGET_MAX"
5737   "unpkbw %r1,%0"
5738   [(set_attr "type" "mvi")])
5740 (include "sync.md")
5742 ;; The call patterns are at the end of the file because their
5743 ;; wildcard operand0 interferes with nice recognition.
5745 (define_insn "*call_value_osf_1_er_noreturn"
5746   [(set (match_operand 0)
5747         (call (mem:DI (match_operand:DI 1 "call_operand" "c,R,s"))
5748               (match_operand 2)))
5749    (use (reg:DI 29))
5750    (clobber (reg:DI 26))]
5751   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF
5752    && find_reg_note (insn, REG_NORETURN, NULL_RTX)"
5753   "@
5754    jsr $26,($27),0
5755    bsr $26,%1\t\t!samegp
5756    ldq $27,%1($29)\t\t!literal!%#\;jsr $26,($27),%1\t\t!lituse_jsr!%#"
5757   [(set_attr "type" "jsr")
5758    (set_attr "length" "*,*,8")])
5760 (define_insn "*call_value_osf_1_er"
5761   [(set (match_operand 0)
5762         (call (mem:DI (match_operand:DI 1 "call_operand" "c,R,s"))
5763               (match_operand 2)))
5764    (use (reg:DI 29))
5765    (clobber (reg:DI 26))]
5766   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
5767   "@
5768    jsr $26,(%1),0\;ldah $29,0($26)\t\t!gpdisp!%*\;lda $29,0($29)\t\t!gpdisp!%*
5769    bsr $26,%1\t\t!samegp
5770    ldq $27,%1($29)\t\t!literal!%#\;jsr $26,($27),0\t\t!lituse_jsr!%#\;ldah $29,0($26)\t\t!gpdisp!%*\;lda $29,0($29)\t\t!gpdisp!%*"
5771   [(set_attr "type" "jsr")
5772    (set_attr "length" "12,*,16")])
5774 ;; We must use peep2 instead of a split because we need accurate life
5775 ;; information for $gp.  Consider the case of { bar(); while (1); }.
5776 (define_peephole2
5777   [(parallel [(set (match_operand 0)
5778                    (call (mem:DI (match_operand:DI 1 "call_operand"))
5779                          (match_operand 2)))
5780               (use (reg:DI 29))
5781               (clobber (reg:DI 26))])]
5782   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF && reload_completed
5783    && ! samegp_function_operand (operands[1], Pmode)
5784    && (peep2_regno_dead_p (1, 29)
5785        || find_reg_note (insn, REG_NORETURN, NULL_RTX))"
5786   [(parallel [(set (match_dup 0)
5787                    (call (mem:DI (match_dup 3))
5788                          (match_dup 2)))
5789               (use (reg:DI 29))
5790               (use (match_dup 1))
5791               (use (match_dup 4))
5792               (clobber (reg:DI 26))])]
5794   if (CONSTANT_P (operands[1]))
5795     {
5796       operands[3] = gen_rtx_REG (Pmode, 27);
5797       operands[4] = GEN_INT (alpha_next_sequence_number++);
5798       emit_insn (gen_movdi_er_high_g (operands[3], pic_offset_table_rtx,
5799                                       operands[1], operands[4]));
5800     }
5801   else
5802     {
5803       operands[3] = operands[1];
5804       operands[1] = const0_rtx;
5805       operands[4] = const0_rtx;
5806     }
5809 (define_peephole2
5810   [(parallel [(set (match_operand 0)
5811                    (call (mem:DI (match_operand:DI 1 "call_operand"))
5812                          (match_operand 2)))
5813               (use (reg:DI 29))
5814               (clobber (reg:DI 26))])]
5815   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF && reload_completed
5816    && ! samegp_function_operand (operands[1], Pmode)
5817    && ! (peep2_regno_dead_p (1, 29)
5818          || find_reg_note (insn, REG_NORETURN, NULL_RTX))"
5819   [(parallel [(set (match_dup 0)
5820                    (call (mem:DI (match_dup 3))
5821                          (match_dup 2)))
5822               (set (match_dup 6)
5823                    (unspec:DI [(match_dup 6) (match_dup 4)] UNSPEC_LDGP1))
5824               (use (match_dup 1))
5825               (use (match_dup 5))
5826               (clobber (reg:DI 26))])
5827    (set (match_dup 6)
5828         (unspec:DI [(match_dup 6) (match_dup 4)] UNSPEC_LDGP2))]
5830   if (CONSTANT_P (operands[1]))
5831     {
5832       operands[3] = gen_rtx_REG (Pmode, 27);
5833       operands[5] = GEN_INT (alpha_next_sequence_number++);
5834       emit_insn (gen_movdi_er_high_g (operands[3], pic_offset_table_rtx,
5835                                       operands[1], operands[5]));
5836     }
5837   else
5838     {
5839       operands[3] = operands[1];
5840       operands[1] = const0_rtx;
5841       operands[5] = const0_rtx;
5842     }
5843   operands[4] = GEN_INT (alpha_next_sequence_number++);
5844   operands[6] = pic_offset_table_rtx;
5847 (define_insn "*call_value_osf_2_er_nogp"
5848   [(set (match_operand 0)
5849         (call (mem:DI (match_operand:DI 1 "register_operand" "c"))
5850               (match_operand 2)))
5851    (use (reg:DI 29))
5852    (use (match_operand 3))
5853    (use (match_operand 4))
5854    (clobber (reg:DI 26))]
5855   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
5856   "jsr $26,(%1),%3%J4"
5857   [(set_attr "type" "jsr")])
5859 (define_insn "*call_value_osf_2_er"
5860   [(set (match_operand 0)
5861         (call (mem:DI (match_operand:DI 1 "register_operand" "c"))
5862               (match_operand 2)))
5863    (set (reg:DI 29)
5864         (unspec:DI [(reg:DI 29) (match_operand 5 "const_int_operand")]
5865                    UNSPEC_LDGP1))
5866    (use (match_operand 3))
5867    (use (match_operand 4))
5868    (clobber (reg:DI 26))]
5869   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
5870   "jsr $26,(%1),%3%J4\;ldah $29,0($26)\t\t!gpdisp!%5"
5871   [(set_attr "type" "jsr")
5872    (set_attr "cannot_copy" "true")
5873    (set_attr "length" "8")])
5875 (define_insn "*call_value_osf_1_noreturn"
5876   [(set (match_operand 0)
5877         (call (mem:DI (match_operand:DI 1 "call_operand" "c,R,s"))
5878               (match_operand 2)))
5879    (use (reg:DI 29))
5880    (clobber (reg:DI 26))]
5881   "! TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF
5882    && find_reg_note (insn, REG_NORETURN, NULL_RTX)"
5883   "@
5884    jsr $26,($27),0
5885    bsr $26,$%1..ng
5886    jsr $26,%1"
5887   [(set_attr "type" "jsr")
5888    (set_attr "length" "*,*,8")])
5890 (define_int_iterator TLS_CALL
5891         [UNSPEC_TLSGD_CALL
5892          UNSPEC_TLSLDM_CALL])
5894 (define_int_attr tls
5895         [(UNSPEC_TLSGD_CALL "tlsgd")
5896          (UNSPEC_TLSLDM_CALL "tlsldm")])
5898 (define_insn "call_value_osf_<tls>"
5899   [(set (match_operand 0)
5900         (call (mem:DI (match_operand:DI 1 "symbolic_operand"))
5901               (const_int 0)))
5902    (unspec [(match_operand:DI 2 "const_int_operand")] TLS_CALL)
5903    (use (reg:DI 29))
5904    (clobber (reg:DI 26))]
5905   "HAVE_AS_TLS"
5906   "ldq $27,%1($29)\t\t!literal!%2\;jsr $26,($27),%1\t\t!lituse_<tls>!%2\;ldah $29,0($26)\t\t!gpdisp!%*\;lda $29,0($29)\t\t!gpdisp!%*"
5907   [(set_attr "type" "jsr")
5908    (set_attr "length" "16")])
5910 ;; We must use peep2 instead of a split because we need accurate life
5911 ;; information for $gp.
5912 (define_peephole2
5913   [(parallel
5914     [(set (match_operand 0)
5915           (call (mem:DI (match_operand:DI 1 "symbolic_operand"))
5916                 (const_int 0)))
5917      (unspec [(match_operand:DI 2 "const_int_operand")] TLS_CALL)
5918      (use (reg:DI 29))
5919      (clobber (reg:DI 26))])]
5920   "HAVE_AS_TLS && reload_completed
5921    && peep2_regno_dead_p (1, 29)"
5922   [(set (match_dup 3)
5923         (unspec:DI [(match_dup 5)
5924                     (match_dup 1)
5925                     (match_dup 2)] UNSPEC_LITERAL))
5926    (parallel [(set (match_dup 0)
5927                    (call (mem:DI (match_dup 3))
5928                          (const_int 0)))
5929               (use (match_dup 5))
5930               (use (match_dup 1))
5931               (use (unspec [(match_dup 2)] TLS_CALL))
5932               (clobber (reg:DI 26))])
5933    (set (match_dup 5)
5934         (unspec:DI [(match_dup 5) (match_dup 4)] UNSPEC_LDGP2))]
5936   operands[3] = gen_rtx_REG (Pmode, 27);
5937   operands[4] = GEN_INT (alpha_next_sequence_number++);
5938   operands[5] = pic_offset_table_rtx;
5941 (define_peephole2
5942   [(parallel
5943     [(set (match_operand 0)
5944           (call (mem:DI (match_operand:DI 1 "symbolic_operand"))
5945                 (const_int 0)))
5946      (unspec [(match_operand:DI 2 "const_int_operand")] TLS_CALL)
5947      (use (reg:DI 29))
5948      (clobber (reg:DI 26))])]
5949   "HAVE_AS_TLS && reload_completed
5950    && !peep2_regno_dead_p (1, 29)"
5951   [(set (match_dup 3)
5952         (unspec:DI [(match_dup 5)
5953                     (match_dup 1)
5954                     (match_dup 2)] UNSPEC_LITERAL))
5955    (parallel [(set (match_dup 0)
5956                    (call (mem:DI (match_dup 3))
5957                          (const_int 0)))
5958               (set (match_dup 5)
5959                    (unspec:DI [(match_dup 5) (match_dup 4)] UNSPEC_LDGP1))
5960               (use (match_dup 1))
5961               (use (unspec [(match_dup 2)] TLS_CALL))
5962               (clobber (reg:DI 26))])
5963    (set (match_dup 5)
5964         (unspec:DI [(match_dup 5) (match_dup 4)] UNSPEC_LDGP2))]
5966   operands[3] = gen_rtx_REG (Pmode, 27);
5967   operands[4] = GEN_INT (alpha_next_sequence_number++);
5968   operands[5] = pic_offset_table_rtx;
5971 (define_insn "*call_value_osf_1"
5972   [(set (match_operand 0)
5973         (call (mem:DI (match_operand:DI 1 "call_operand" "c,R,s"))
5974               (match_operand 2)))
5975    (use (reg:DI 29))
5976    (clobber (reg:DI 26))]
5977   "! TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
5978   "@
5979    jsr $26,($27),0\;ldgp $29,0($26)
5980    bsr $26,$%1..ng
5981    jsr $26,%1\;ldgp $29,0($26)"
5982   [(set_attr "type" "jsr")
5983    (set_attr "length" "12,*,16")])
5985 (define_insn "*sibcall_value_osf_1_er"
5986   [(set (match_operand 0)
5987         (call (mem:DI (match_operand:DI 1 "symbolic_operand" "R,s"))
5988               (match_operand 2)))
5989    (unspec [(reg:DI 29)] UNSPEC_SIBCALL)]
5990   "TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
5991   "@
5992    br $31,%1\t\t!samegp
5993    ldq $27,%1($29)\t\t!literal!%#\;jmp $31,($27),%1\t\t!lituse_jsr!%#"
5994   [(set_attr "type" "jsr")
5995    (set_attr "length" "*,8")])
5997 (define_insn "*sibcall_value_osf_1"
5998   [(set (match_operand 0)
5999         (call (mem:DI (match_operand:DI 1 "symbolic_operand" "R,s"))
6000               (match_operand 2)))
6001    (unspec [(reg:DI 29)] UNSPEC_SIBCALL)]
6002   "! TARGET_EXPLICIT_RELOCS && TARGET_ABI_OSF"
6003   "@
6004    br $31,$%1..ng
6005    lda $27,%1\;jmp $31,($27),%1"
6006   [(set_attr "type" "jsr")
6007    (set_attr "length" "*,8")])
6009 ; GAS relies on the order and position of instructions output below in order
6010 ; to generate relocs for VMS link to potentially optimize the call.
6011 ; Please do not molest.
6012 (define_insn "*call_value_vms_1"
6013   [(set (match_operand 0)
6014         (call (mem:DI (match_operand:DI 1 "call_operand" "r,s"))
6015               (match_operand 2)))
6016    (use (match_operand:DI 3 "nonmemory_operand" "r,n"))
6017    (use (reg:DI 25))
6018    (use (reg:DI 26))
6019    (clobber (reg:DI 27))]
6020   "TARGET_ABI_OPEN_VMS"
6022   switch (which_alternative)
6023     {
6024     case 0:
6025         return "mov %3,$27\;jsr $26,0\;ldq $27,0($29)";
6026     case 1:
6027         operands [3] = alpha_use_linkage (operands [1], true, false);
6028         operands [4] = alpha_use_linkage (operands [1], false, false);
6029         return "ldq $26,%4\;ldq $27,%3\;jsr $26,%1\;ldq $27,0($29)";
6030     default:
6031       gcc_unreachable ();
6032     }
6034   [(set_attr "type" "jsr")
6035    (set_attr "length" "12,16")])