OSDN Git Service

* config/c4x/c4x-c.c, config/c4x/c4x-modes.def,
[pf3gnuchains/gcc-fork.git] / gcc / config / c4x / c4x.md
1 ;; Machine description for the TMS320C[34]x for GCC
2 ;; Copyright (C) 1994, 1995, 1996, 1997, 1998,
3 ;; 1999, 2000, 2002 Free Software Foundation, Inc.
4
5 ;; Contributed by Michael Hayes (m.hayes@elec.canterbury.ac.nz)
6 ;;            and Herman Ten Brugge (Haj.Ten.Brugge@net.HCC.nl)
7
8 ;; This file is part of GCC.
9
10 ;; GCC is free software; you can redistribute it and/or modify
11 ;; it under the terms of the GNU General Public License as published by
12 ;; the Free Software Foundation; either version 2, or (at your option)
13 ;; any later version.
14
15 ;; GCC is distributed in the hope that it will be useful,
16 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
17 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18 ;; GNU General Public License for more details.
19
20 ;; You should have received a copy of the GNU General Public License
21 ;; along with GCC; see the file COPYING.  If not, write to
22 ;; the Free Software Foundation, 59 Temple Place - Suite 330,
23 ;; Boston, MA 02111-1307, USA.
24
25 ;
26 ; TODO :
27 ;        Try using PQImode again for addresses since C30 only uses
28 ;        24-bit addresses.   Ideally GCC would emit different insns
29 ;        for QImode and Pmode, whether Pmode was QImode or PQImode.
30 ;        For addresses we wouldn't have to have a clobber of the CC
31 ;        associated with each insn and we could use MPYI in address
32 ;        calculations without having to synthesize a proper 32 bit multiply.
33
34 ; Additional C30/C40 instructions not coded:
35 ; CALLcond, IACK, IDLE, LDE, LDFI, LDII, LDM, NORM, RETIcond
36 ; ROLC, RORC, SIGI, STFI, STII, SUBC, SWI
37
38 ; Additional C40 instructions not coded:
39 ; LDEP, LDPE, LWRct, LAJcond, RETIcondD
40
41 ;
42 ; C4x MODES
43 ;
44 ; QImode                char, short, int, long (32-bits)
45 ; HImode                long long              (64-bits)
46 ; QFmode                float, double          (32-bits)
47 ; HFmode                long double            (40-bits)
48 ; CCmode                
49 ; CC_NOOVmode           
50
51 ;
52 ; C4x PREDICATES:
53 ;
54 ; comparison_operator   LT, GT, LE, GE, LTU, GTU, LEU, GEU, EQ, NE
55 ; memory_operand        memory                                     [m]
56 ; immediate_operand     immediate constant                         [IKN]
57 ; register_operand      register                                   [rf]
58 ; general_operand       register, memory, constant                 [rfmI]
59
60 ; addr_reg_operand      AR0-AR7, pseudo reg                        [a]
61 ; sp_reg_operand        SP                                         [b]
62 ; std_reg_operand       AR0-AR7, IR0-IR1, RC, RS, RE, SP, pseudo   [c]
63 ; ext_reg_operand       R0-R11, pseudo reg                         [f]
64 ; ext_low_reg_operand   R0-R7, pseudo reg                          [q]
65 ; index_reg_operand     IR0-IR1, pseudo reg                        [x]
66 ; st_reg_operand        ST                                         [y]
67 ; dp_reg_operand        DP                                         [z]
68 ; stik_const_operand    5-bit const                                [K]
69 ; src_operand           general operand                            [rfHmI]
70 ; par_ind_operand       indirect S mode (ARx + 0, 1, IRx)          [S<>]
71 ; parallel_operand      par_ind_operand or ext_low_reg_operand
72 ; symbolic_address_operand
73 ; call_address_operand
74
75 ; ADDI src2, src1, dst  three operand op
76 ; ADDI src, dst         two operand op
77
78 ;  Note that the predicates are only used when selecting a pattern
79 ;  to determine if an operand is valid.
80
81 ;  The constraints then select which of the possible valid operands
82 ;  is present (and guide register selection). The actual assembly
83 ;  instruction is then selected on the basis of the constraints.
84
85 ;  The extra constraint (valid_operands) is used to determine if
86 ;  the combination of operands is legitimate for the pattern.
87
88 ;
89 ; C4x CONSTRAINTS:
90 ;
91 ; a   address reg          AR0-AR7
92 ; b   stack pointer        SP
93 ; c   other int reg        AR0-AR7, IR0-IR1, RC, RS, RE
94 ; d   fp reg               R0-R11 (sets CC when dst) 
95 ; e
96 ; f   fp reg               R0-R11 (sets CC when dst)
97 ; g   general reg, memory, constant
98 ; h   fp reg (HFmode)      R0-R11 (sets CC when dst) 
99 ; i   immediate int constant
100 ; j
101 ; k   block count          BK
102 ; l
103 ; m   memory
104 ; n   immediate int constant with known numeric value
105 ; o   offsettable memory
106 ; p   memory address
107 ; q   low fp reg           R0-R7  (sets CC when dst)
108 ; r   general reg          R0-R11, AR0-AR7, IR0-IR1, RC, RS, RE
109 ; s   immediate int constant (value not explicit)
110 ; t                        R0-R1
111 ; u                        R2-R3
112 ; v   repeat count reg     RC
113 ; w
114 ; x   index reg            IR0-IR1
115 ; y   status (CC) reg      ST
116 ; z   data pointer         DP
117
118 ; G   fp zero
119 ; H   fp 16-bit constant
120 ; I   signed 16-bit
121 ; J   signed 8-bit    (C4x only)
122 ; K   signed 5-bit    (C4x only)
123 ; L   unsigned 16-bit
124 ; M   unsigned 8-bit  (C4x only)
125 ; N   ones complement of unsigned 16-bit
126 ; O   16 bit high constant
127 ; Q   ARx + 9-bit signed disp
128 ; R   ARx + 5-bit unsigned disp  (C4x only)
129 ; S   ARx + 0, 1, IRx disp
130 ; T   direct memory operand
131 ; V   non offsettable memory
132 ; X   any operand
133 ; <   memory operand with autodecrement addressing
134 ; >   memory operand with autoincrement addressing
135 ; {   memory operand with pre-modify addressing
136 ; }   memory operand with post-modify addressing
137
138 ;  Note that the 'd', 'f', and 'h' constraints are equivalent.
139 ;  The m constraint is equivalent to 'QT<>{}'
140
141 ;  Note we cannot use the 'g' constraint with Pmode (i.e, QImode)
142 ;  operations since LEGITIMATE_CONSTANT_P accepts SYMBOL_REF.
143 ;  So instead we use 'rIm' for signed operands or 'rLm' for unsigned operands.
144
145 ;  Note that the constraints are used to select the operands
146 ;  for a chosen pattern.  The constraint that requires the fewest
147 ;  instructions to load an operand is chosen.
148
149 ;  Note that the 'r' constraint is mostly only used for src integer register 
150 ;  operands,  while 'c' and 'd' constraints are generally only used for dst
151 ;  integer register operands (the 'r' constraint is the union of the 'c' and
152 ;  'd' constraints).  When a register satisfying the 'd' constraint
153 ;  is used as a dst operand, the CC gets clobbered (except for LDIcond)---but 
154 ;  not for 'c'.
155
156 ;  The 'f' constraint is only for float register operands---when 
157 ;  a register satisying the 'f' constraint is used as a dst operand,
158 ;  the CC gets clobbered (except for LDFcond).
159
160 ;  The ! in front of the 'b' constaint says to GCC to disparage the
161 ;  use of this constraint.  The 'b' constraint applies only to the SP.
162
163 ;  Note that we deal with the condition code CC like some of the RISC
164 ;  architectures (arm, sh, sparc) where it is stored in a general register,
165 ;  in this case the hard register ST (21).  Unlike these other architectures
166 ;  that do not set the CC with many instructions, the C[34]x architectures
167 ;  sets the CC for many instructions when the destination register is
168 ;  an extended precision register.  While it would have been easier
169 ;  to use the generic cc0 register to store the CC, as with most of
170 ;  the other ported architectures, this constrains the setting and testing
171 ;  of the CC to be consecutive insns.  Thus we would reduce the benefit
172 ;  of scheduling instructions to avoid pipeline conflicts and filling of
173 ;  delayed branch slots.
174
175 ;  Since the C[34]x has many instructions that set the CC, we pay the
176 ;  price of having to explicity define which insns clobber the CC
177 ;  (rather than using the macro NOTICE_UPDATE_CC). 
178
179 ;  Note that many patterns say that the CC is clobbered when in fact
180 ;  that it may not be (depending on the destination register).
181 ;  We have to cover ourselves if an extended precision register
182 ;  is allocated to the destination register.
183 ;  Unfortunately, it is not easy to tell GCC that the clobbering of CC
184 ;  is register dependent.  If we could tolerate the ST register being
185 ;  copied about, then we could store the CC in a pseudo register and
186 ;  use constructs such as (clobber (match_scratch:CC N "&y,X")) to
187 ;  indicate that the 'y' class (ST register) is clobbered for the
188 ;  first combination of operands, but not with the second.
189 ;  I tried this approach for a while but reload got unhappy since I
190 ;  didn't allow it to move the CC around.
191
192 ;  Note that fundamental operations, such as moves, must not clobber the
193 ;  CC.  Thus movqi choses a move instruction that doesn't clobber the CC.
194 ;  If GCC wants to combine a move with a compare, it is smart enough to
195 ;  chose the move instruction that sets the CC.
196
197 ;  Unfortunately, the C[34]x instruction set does not have arithmetic or
198 ;  logical operations that never touch the CC.  We thus have to assume
199 ;  that the CC may be clobbered at all times.  If we define patterns
200 ;  such as addqi without the clobber of CC, then GCC will be forced
201 ;  to use registers such as the auxiliary registers which can cause
202 ;  horrible pipeline conflicts.  The tradeoff is that GCC can't now
203 ;  sneak in an add instruction between setting and testing of the CC.
204
205 ;  Most of the C[34]x instructions require operands of the following formats,
206 ;  where imm represents an immediate constant, dir a direct memory reference,
207 ;  ind an indirect memory reference, and reg a register:
208
209 ;        src2 (op2)             src1 (op1)      dst (op0)
210 ; imm  dir  ind  reg  |  imm  dir  ind  reg  |  reg      Notes
211 ;---------------------+----------------------+------
212 ; ILH   T   Q<>   r   |   -    -    -    0   |   r       2 operand
213 ;  -    -   S<>   r   |   -    -   S<>   r   |   r       
214 ;  J    -    R    -   |   -    -    R    r   |   r       C4x
215
216 ;  Arithmetic operations use the I, J constraints for immediate constants,
217 ;  while logical operations use the L, J constraints.  Floating point
218 ;  operations use the H constraint for immediate constants.
219
220 ;  With most instructions the src2 and src1 operands are commutative
221 ;  (except for SUB, SUBR, ANDN).  The assembler considers
222 ;  ADDI 10, R0, R1 and ADDI R0, 10, R1 to be equivalent.
223 ;  We thus match src2 and src1 with the src_operand predicate and
224 ;  use valid_operands as the extra constraint to reject invalid
225 ;  operand combinations.  For example, ADDI @foo, @bar, R0.
226
227 ;  Note that we use the ? modifier so that reload doesn't preferentially
228 ;  try the alternative where three registers are acceptable as
229 ;  operands (whenever an operand requires reloading).  Instead it will try
230 ;  the 2 operand form which will produce better code since it won't require
231 ;  a new spill register.
232
233 ;  Note that the floating point representation of 0.0 on the C4x
234 ;  is 0x80000000 (-2147483648).  This value produces a warning
235 ;  message on 32-bit machines about the decimal constant being so large
236 ;  that it is unsigned.
237
238 ;  With two operand instructions patterns having two sets,
239 ;  the compare set must come first to keep the combiner happy.
240 ;  While the combiner seems to cope most of the time with the
241 ;  compare set coming second, it's best to have it first.
242
243 ;
244 ; C4x CONSTANT attributes
245 ;
246 (define_attr "cpu" "c4x,c3x"
247  (const
248   (cond [(symbol_ref "TARGET_C3X") (const_string "c3x")]
249          (const_string "c4x"))))
250
251 ;
252 ; C4x INSN ATTRIBUTES:
253 ;
254 ; lda           load address, non-clobber CC
255 ; store         memory store, non-clobber CC
256 ; load_load     parallel memory loads, non-clobber CC
257 ; load_store    parallel memory load and store, non-clobber CC
258 ; store_load    parallel memory store and load, non-clobber CC
259 ; store_store   parallel memory stores, non-clobber CC
260 ; unary         two operand arithmetic, non-clobber CC
261 ; unarycc       two operand arithmetic, clobber CC
262 ; binary        three operand arithmetic, non-clobber CC
263 ; binarycc      three operand arithmetic, clobber CC
264 ; compare       compare, clobber CC
265 ; call          function call
266 ; rets          return from subroutine
267 ; jump          unconditional branch
268 ; jmpc          conditional branch
269 ; db            decrement and branch (unconditional)
270 ; dbc           decrement and branch (conditional)
271 ; ldp           load DP
272 ; push          stack push
273 ; pop           stack pop
274 ; repeat        block repeat
275 ; repeat_top    block repeat top
276 ; laj           link and jump
277 ; multi         multiple instruction
278 ; misc          nop             (default)
279
280 ;  The only real instructions that affect things are the ones that modify
281 ;  address registers and ones that call or jump.  Note that the number
282 ;  of operands refers to the RTL insn pattern, not the number of explicit
283 ;  operands in the machine instruction.
284 ;
285 (define_attr "type" "lda,store,unary,unarycc,binary,binarycc,compare,call,rets,jump,jmpc,db,dbc,misc,ldp,repeat,repeat_top,laj,load_load,load_store,store_load,store_store,push,pop,multi"
286              (const_string "misc"))
287
288
289 ; Some instructions operate on unsigned data constants, some on signed data
290 ; constants, or the ones complement of unsigned constants.
291 ; This differentiates them.  Default to signed.  This attribute
292 ; is used by the macro SMALL_CONST () (defined in c4x.h) to determine
293 ; whether an immediate integer constant will fit within the instruction,
294 ; or will have to be loaded using direct addressing from memory.
295 ; Note that logical operations assume unsigned integers whereas
296 ; arithmetic operations assume signed integers.  Note that the C4x
297 ; small immediate constant (J) used as src2 in three operand instructions
298 ; is always signed.  not_uint16 refers to a number that fits into 16-bits
299 ; when one's complemented.
300 ;
301 (define_attr "data" "int16,uint16,high_16,not_uint16" (const_string "int16"))
302
303 (define_asm_attributes
304   [(set_attr "type" "multi")])
305
306 ;
307 ; C4x DELAY SLOTS
308 ;
309 ; Define delay slot scheduling for branch and call instructions.
310 ; The C[34]x has three delay slots. Note that none of the three instructions
311 ; that follow a delayed branch can be a Bcond, BcondD, BR, BRD, DBcond,
312 ; DBcondD, CALL, CALLcond, TRAPcond, RETIcond, RETScond, RPTB, RPTS, or IDLE.
313 ;
314 ; Annulled branches are a bit difficult because the next instructions
315 ; are preprocessed.
316 ; The table below shows what phase of the c4x is executed.
317 ;        BccA[TF] label
318 ;        op1             fetch, decode and read executed
319 ;        op2             fetch and decode executed
320 ;        op3             fetch executed
321 ; This means that we can allow any instruction in the last delay slot
322 ; and only instructions which modify registers in the first two. 
323 ; lda can not be executed in the first delay slot 
324 ; and ldpk can not be executed in the first two delay slots.
325
326 (define_attr "onlyreg" "false,true"
327        (cond [(eq_attr "type" "unary,unarycc")
328                        (if_then_else (and (match_operand 0 "reg_imm_operand" "")
329                                           (match_operand 1 "reg_imm_operand" ""))
330                                      (const_string "true") (const_string "false"))
331               (eq_attr "type" "binary,binarycc")
332                        (if_then_else (and (match_operand 0 "reg_imm_operand" "")
333                                           (and (match_operand 1 "reg_imm_operand" "")
334                                                (match_operand 2 "reg_imm_operand" "")))
335                                      (const_string "true") (const_string "false"))]
336              (const_string "false")))
337
338 (define_attr "onlyreg_nomod" "false,true"
339        (cond [(eq_attr "type" "unary,unarycc,compare,lda,store")
340                        (if_then_else (and (match_operand 0 "not_modify_reg" "")
341                                           (match_operand 1 "not_modify_reg" ""))
342                                      (const_string "true") (const_string "false"))
343               (eq_attr "type" "binary,binarycc")
344                        (if_then_else (and (match_operand 0 "not_modify_reg" "")
345                                           (and (match_operand 1 "not_modify_reg" "")
346                                                (match_operand 2 "not_modify_reg" "")))
347                                      (const_string "true") (const_string "false"))]
348              (const_string "false")))
349
350 (define_attr "not_repeat_reg" "false,true"
351        (cond [(eq_attr "type" "unary,unarycc,compare,lda,ldp,store")
352                        (if_then_else (and (match_operand 0 "not_rc_reg" "")
353                                           (match_operand 1 "not_rc_reg" ""))
354                                      (const_string "true") (const_string "false"))
355               (eq_attr "type" "binary,binarycc")
356                        (if_then_else (and (match_operand 0 "not_rc_reg" "")
357                                           (and (match_operand 1 "not_rc_reg" "")
358                                                (match_operand 2 "not_rc_reg" "")))
359                                      (const_string "true") (const_string "false"))]
360              (const_string "false")))
361
362 /* Disable compare because the c4x contains a bug. The cmpi insn sets the CC
363    in the read phase of the pipeline instead of the execution phase when
364    two registers are compared.  */
365 (define_attr "in_annul_slot_1" "false,true"
366   (if_then_else (and (and (eq_attr "cpu" "c4x")
367                           (eq_attr "type" "!jump,call,rets,jmpc,compare,db,dbc,repeat,repeat_top,laj,push,pop,lda,ldp,multi"))
368                      (eq_attr "onlyreg" "true"))
369                 (const_string "true")
370                 (const_string "false")))
371
372 (define_attr "in_annul_slot_2" "false,true"
373   (if_then_else (and (and (eq_attr "cpu" "c4x")
374                           (eq_attr "type" "!jump,call,rets,jmpc,db,dbc,repeat,repeat_top,laj,push,pop,ldp,multi"))
375                      (eq_attr "onlyreg_nomod" "true"))
376                 (const_string "true")
377                 (const_string "false")))
378
379 /* Disable ldp because the c4x contains a bug. The ldp insn modifies
380    the dp register when the insn is anulled or not.
381    Also disable autoincrement insns because of a silicon bug.  */
382 (define_attr "in_annul_slot_3" "false,true"
383   (if_then_else (and (and (eq_attr "cpu" "c4x")
384                           (eq_attr "type" "!jump,call,rets,jmpc,db,dbc,repeat,repeat_top,laj,push,pop,ldp,multi"))
385                      (eq_attr "onlyreg_nomod" "true"))
386                 (const_string "true")
387                 (const_string "false")))
388
389 (define_attr "in_delay_slot" "false,true"
390   (if_then_else (eq_attr "type" "!jump,call,rets,jmpc,db,dbc,repeat,repeat_top,laj,multi")
391                 (const_string "true")
392                 (const_string "false")))
393
394 (define_attr "in_repeat_slot" "false,true"
395   (if_then_else (and (eq_attr "cpu" "c4x")
396                      (and (eq_attr "type" "!jump,call,rets,jmpc,db,dbc,repeat,repeat_top,laj,multi")
397                           (eq_attr "not_repeat_reg" "true")))
398                 (const_string "true")
399                 (const_string "false")))
400
401 (define_attr "in_dbc_slot" "false,true"
402   (if_then_else (eq_attr "type" "!jump,call,rets,jmpc,unarycc,binarycc,compare,db,dbc,repeat,repeat_top,laj,multi")
403                 (const_string "true")
404                 (const_string "false")))
405
406 (define_delay (eq_attr "type" "jmpc")
407               [(eq_attr "in_delay_slot" "true")
408                (eq_attr "in_annul_slot_1" "true")
409                (eq_attr "in_annul_slot_1" "true")
410
411                (eq_attr "in_delay_slot" "true")
412                (eq_attr "in_annul_slot_2" "true")
413                (eq_attr "in_annul_slot_2" "true")
414
415                (eq_attr "in_delay_slot" "true")
416                (eq_attr "in_annul_slot_3" "true")
417                (eq_attr "in_annul_slot_3" "true") ])
418
419
420 (define_delay (eq_attr "type" "repeat_top")
421               [(eq_attr "in_repeat_slot" "true") (nil) (nil)
422                (eq_attr "in_repeat_slot" "true") (nil) (nil)
423                (eq_attr "in_repeat_slot" "true") (nil) (nil)])
424
425 (define_delay (eq_attr "type" "jump,db")
426               [(eq_attr "in_delay_slot" "true") (nil) (nil)
427                (eq_attr "in_delay_slot" "true") (nil) (nil)
428                (eq_attr "in_delay_slot" "true") (nil) (nil)])
429
430
431 ; Decrement and branch conditional instructions cannot modify the
432 ; condition codes for the cycles in the delay slots.
433 ;
434 (define_delay (eq_attr "type" "dbc")
435               [(eq_attr "in_dbc_slot" "true") (nil) (nil)
436                (eq_attr "in_dbc_slot" "true") (nil) (nil)
437                (eq_attr "in_dbc_slot" "true") (nil) (nil)])
438
439 ; The LAJ instruction has three delay slots but the last slot is
440 ; used for pushing the return address.  Thus we can only use two slots.
441 ;
442 (define_delay (eq_attr "type" "laj")
443               [(eq_attr "in_delay_slot" "true") (nil) (nil)
444                (eq_attr "in_delay_slot" "true") (nil) (nil)])
445
446 ;
447 ; C4x UNSPEC NUMBERS
448 ;
449 (define_constants
450   [
451    (UNSPEC_BU                   1)
452    (UNSPEC_RPTS                 2)
453    (UNSPEC_LSH                  3)
454    (UNSPEC_CMPHI                4)
455    (UNSPEC_RCPF                 5)
456    (UNSPEC_RND                  6)
457    (UNSPEC_RPTB_FILL            7)
458    (UNSPEC_LOADHF_INT           8)
459    (UNSPEC_STOREHF_INT          9)
460    (UNSPEC_RSQRF                10)
461    (UNSPEC_LOADQF_INT           11)
462    (UNSPEC_STOREQF_INT          12)
463    (UNSPEC_LDIV                 13)
464    (UNSPEC_PUSH_ST              14)
465    (UNSPEC_POP_ST               15)
466    (UNSPEC_PUSH_DP              16)
467    (UNSPEC_POP_DP               17)
468    (UNSPEC_POPQI                18)
469    (UNSPEC_POPQF                19)
470    (UNSPEC_ANDN_ST              20)
471    (UNSPEC_RPTB_INIT            22)
472    (UNSPEC_TOIEEE               23)
473    (UNSPEC_FRIEEE               24)
474   ])
475
476 ;
477 ; C4x FUNCTIONAL UNITS
478 ;
479 ; Define functional units for instruction scheduling to minimise
480 ; pipeline conflicts.
481 ;
482 ; With the C3x, an external memory write (with no wait states) takes
483 ; two cycles and an external memory read (with no wait states) takes
484 ; one cycle.  However, an external read following an external write
485 ; takes two cycles.  With internal memory, reads and writes take
486 ; half a cycle.
487 ;
488 ; When a C4x address register is loaded it will not be available for
489 ; an extra machine cycle.  Calculating with a C4x address register
490 ; makes it unavailable for 2 machine cycles.  To notify GCC of these
491 ; pipeline delays, each of the auxiliary and index registers are declared
492 ; as separate functional units.
493 ;
494 ; (define_function_unit NAME MULTIPLICITY SIMULTANEITY
495 ;                       TEST READY-DELAY ISSUE-DELAY [CONFLICT-LIST])
496 ;
497 ; MULTIPLICITY 1 (C4x has no independent identical function units)
498 ; SIMULTANEITY 0 (C4x is pipelined)
499 ; READY_DELAY  1 (Results usually ready after every cyle)
500 ; ISSUE_DELAY  1 (Can issue insns every cycle)
501
502 ; Just some dummy definitions. The real work is done in c4x_adjust_cost.
503 ; These are needed so the min/max READY_DELAY is known.
504
505 (define_function_unit "dummy" 1 0 (const_int 0) 1 1)
506 (define_function_unit "dummy" 1 0 (const_int 0) 2 1)
507 (define_function_unit "dummy" 1 0 (const_int 0) 3 1)
508
509 ; The attribute setar0 is set to 1 for insns where ar0 is a dst operand.
510 ; Note that the attributes unarycc and binarycc do not apply
511 ; if ar0 is a dst operand (only loading an ext. prec. reg. sets CC)
512 (define_attr "setar0" ""
513        (cond [(eq_attr "type" "unary,binary")
514                        (if_then_else (match_operand 0 "ar0_reg_operand" "")
515                                      (const_int 1) (const_int 0))]
516              (const_int 0)))
517
518 (define_attr "setlda_ar0" ""
519        (cond [(eq_attr "type" "lda")
520                        (if_then_else (match_operand 0 "ar0_reg_operand" "")
521                                      (const_int 1) (const_int 0))]
522              (const_int 0)))
523
524 ; The attribute usear0 is set to 1 for insns where ar0 is used
525 ; for addressing, as a src operand, or as a dst operand.
526 (define_attr "usear0" ""
527        (cond [(eq_attr "type" "compare,store")
528                        (if_then_else (match_operand 0 "ar0_mem_operand" "")
529                                      (const_int 1) (const_int 0))
530               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
531                        (if_then_else (match_operand 1 "ar0_mem_operand" "")
532                                      (const_int 1) (const_int 0))
533               (eq_attr "type" "binary,binarycc")
534                        (if_then_else (match_operand 2 "ar0_mem_operand" "")
535                                      (const_int 1) (const_int 0))
536               (eq_attr "type" "db,dbc")
537                        (if_then_else (match_operand 0 "ar0_reg_operand" "")
538                                      (const_int 1) (const_int 0))]
539              (const_int 0)))
540
541 ; The attribute readar0 is set to 1 for insns where ar0 is a src operand.
542 (define_attr "readar0" ""
543        (cond [(eq_attr "type" "compare")
544                        (if_then_else (match_operand 0 "ar0_reg_operand" "")
545                                      (const_int 1) (const_int 0))
546               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
547                        (if_then_else (match_operand 1 "ar0_reg_operand" "")
548                                      (const_int 1) (const_int 0))
549               (eq_attr "type" "binary,binarycc")
550                        (if_then_else (match_operand 2 "ar0_reg_operand" "")
551                                      (const_int 1) (const_int 0))]
552              (const_int 0)))
553
554 (define_attr "setar1" ""
555        (cond [(eq_attr "type" "unary,binary")
556                        (if_then_else (match_operand 0 "ar1_reg_operand" "")
557                                      (const_int 1) (const_int 0))]
558              (const_int 0)))
559
560 (define_attr "setlda_ar1" ""
561        (cond [(eq_attr "type" "lda")
562                        (if_then_else (match_operand 0 "ar1_reg_operand" "")
563                                      (const_int 1) (const_int 0))]
564              (const_int 0)))
565
566 (define_attr "usear1" ""
567        (cond [(eq_attr "type" "compare,store")
568                        (if_then_else (match_operand 0 "ar1_mem_operand" "")
569                                      (const_int 1) (const_int 0))
570               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
571                        (if_then_else (match_operand 1 "ar1_mem_operand" "")
572                                      (const_int 1) (const_int 0))
573               (eq_attr "type" "binary,binarycc")
574                        (if_then_else (match_operand 2 "ar1_mem_operand" "")
575                                      (const_int 1) (const_int 0))
576               (eq_attr "type" "db,dbc")
577                        (if_then_else (match_operand 0 "ar1_reg_operand" "")
578                                      (const_int 1) (const_int 0))]
579              (const_int 0)))
580
581 (define_attr "readar1" ""
582        (cond [(eq_attr "type" "compare")
583                        (if_then_else (match_operand 0 "ar1_reg_operand" "")
584                                      (const_int 1) (const_int 0))
585               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
586                        (if_then_else (match_operand 1 "ar1_reg_operand" "")
587                                      (const_int 1) (const_int 0))
588               (eq_attr "type" "binary,binarycc")
589                        (if_then_else (match_operand 2 "ar1_reg_operand" "")
590                                      (const_int 1) (const_int 0))]
591              (const_int 0)))
592
593 (define_attr "setar2" ""
594        (cond [(eq_attr "type" "unary,binary")
595                        (if_then_else (match_operand 0 "ar2_reg_operand" "")
596                                      (const_int 1) (const_int 0))]
597              (const_int 0)))
598
599 (define_attr "setlda_ar2" ""
600        (cond [(eq_attr "type" "lda")
601                        (if_then_else (match_operand 0 "ar2_reg_operand" "")
602                                      (const_int 1) (const_int 0))]
603              (const_int 0)))
604
605 (define_attr "usear2" ""
606        (cond [(eq_attr "type" "compare,store")
607                        (if_then_else (match_operand 0 "ar2_mem_operand" "")
608                                      (const_int 1) (const_int 0))
609               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
610                        (if_then_else (match_operand 1 "ar2_mem_operand" "")
611                                      (const_int 1) (const_int 0))
612               (eq_attr "type" "binary,binarycc")
613                        (if_then_else (match_operand 2 "ar2_mem_operand" "")
614                                      (const_int 1) (const_int 0))
615               (eq_attr "type" "db,dbc")
616                        (if_then_else (match_operand 0 "ar2_reg_operand" "")
617                                      (const_int 1) (const_int 0))]
618              (const_int 0)))
619
620 (define_attr "readar2" ""
621        (cond [(eq_attr "type" "compare")
622                        (if_then_else (match_operand 0 "ar2_reg_operand" "")
623                                      (const_int 1) (const_int 0))
624               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
625                        (if_then_else (match_operand 1 "ar2_reg_operand" "")
626                                      (const_int 1) (const_int 0))
627               (eq_attr "type" "binary,binarycc")
628                        (if_then_else (match_operand 2 "ar2_reg_operand" "")
629                                      (const_int 1) (const_int 0))]
630              (const_int 0)))
631
632 (define_attr "setar3" ""
633        (cond [(eq_attr "type" "unary,binary")
634                        (if_then_else (match_operand 0 "ar3_reg_operand" "")
635                                      (const_int 1) (const_int 0))]
636              (const_int 0)))
637
638 (define_attr "setlda_ar3" ""
639        (cond [(eq_attr "type" "lda")
640                        (if_then_else (match_operand 0 "ar3_reg_operand" "")
641                                      (const_int 1) (const_int 0))]
642              (const_int 0)))
643
644 (define_attr "usear3" ""
645        (cond [(eq_attr "type" "compare,store")
646                        (if_then_else (match_operand 0 "ar3_mem_operand" "")
647                                      (const_int 1) (const_int 0))
648               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
649                        (if_then_else (match_operand 1 "ar3_mem_operand" "")
650                                      (const_int 1) (const_int 0))
651               (eq_attr "type" "binary,binarycc")
652                        (if_then_else (match_operand 2 "ar3_mem_operand" "")
653                                      (const_int 1) (const_int 0))
654               (eq_attr "type" "db,dbc")
655                        (if_then_else (match_operand 0 "ar3_reg_operand" "")
656                                      (const_int 1) (const_int 0))]
657              (const_int 0)))
658
659 (define_attr "readar3" ""
660        (cond [(eq_attr "type" "compare")
661                        (if_then_else (match_operand 0 "ar3_reg_operand" "")
662                                      (const_int 1) (const_int 0))
663               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
664                        (if_then_else (match_operand 1 "ar3_reg_operand" "")
665                                      (const_int 1) (const_int 0))
666               (eq_attr "type" "binary,binarycc")
667                        (if_then_else (match_operand 2 "ar3_reg_operand" "")
668                                      (const_int 1) (const_int 0))]
669              (const_int 0)))
670
671 (define_attr "setar4" ""
672        (cond [(eq_attr "type" "unary,binary")
673                        (if_then_else (match_operand 0 "ar4_reg_operand" "")
674                                      (const_int 1) (const_int 0))]
675              (const_int 0)))
676
677 (define_attr "setlda_ar4" ""
678        (cond [(eq_attr "type" "lda")
679                        (if_then_else (match_operand 0 "ar4_reg_operand" "")
680                                      (const_int 1) (const_int 0))]
681              (const_int 0)))
682
683 (define_attr "usear4" ""
684        (cond [(eq_attr "type" "compare,store")
685                        (if_then_else (match_operand 0 "ar4_mem_operand" "")
686                                      (const_int 1) (const_int 0))
687               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
688                        (if_then_else (match_operand 1 "ar4_mem_operand" "")
689                                      (const_int 1) (const_int 0))
690               (eq_attr "type" "binary,binarycc")
691                        (if_then_else (match_operand 2 "ar4_mem_operand" "")
692                                      (const_int 1) (const_int 0))
693               (eq_attr "type" "db,dbc")
694                        (if_then_else (match_operand 0 "ar4_reg_operand" "")
695                                      (const_int 1) (const_int 0))]
696              (const_int 0)))
697
698 (define_attr "readar4" ""
699        (cond [(eq_attr "type" "compare")
700                        (if_then_else (match_operand 0 "ar4_reg_operand" "")
701                                      (const_int 1) (const_int 0))
702               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
703                        (if_then_else (match_operand 1 "ar4_reg_operand" "")
704                                      (const_int 1) (const_int 0))
705               (eq_attr "type" "binary,binarycc")
706                        (if_then_else (match_operand 2 "ar4_reg_operand" "")
707                                      (const_int 1) (const_int 0))]
708              (const_int 0)))
709
710 (define_attr "setar5" ""
711        (cond [(eq_attr "type" "unary,binary")
712                        (if_then_else (match_operand 0 "ar5_reg_operand" "")
713                                      (const_int 1) (const_int 0))]
714              (const_int 0)))
715
716 (define_attr "setlda_ar5" ""
717        (cond [(eq_attr "type" "lda")
718                        (if_then_else (match_operand 0 "ar5_reg_operand" "")
719                                      (const_int 1) (const_int 0))]
720              (const_int 0)))
721
722 (define_attr "usear5" ""
723        (cond [(eq_attr "type" "compare,store")
724                        (if_then_else (match_operand 0 "ar5_mem_operand" "")
725                                      (const_int 1) (const_int 0))
726               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
727                        (if_then_else (match_operand 1 "ar5_mem_operand" "")
728                                      (const_int 1) (const_int 0))
729               (eq_attr "type" "binary,binarycc")
730                        (if_then_else (match_operand 2 "ar5_mem_operand" "")
731                                      (const_int 1) (const_int 0))
732               (eq_attr "type" "db,dbc")
733                        (if_then_else (match_operand 0 "ar5_reg_operand" "")
734                                      (const_int 1) (const_int 0))]
735              (const_int 0)))
736
737 (define_attr "readar5" ""
738        (cond [(eq_attr "type" "compare")
739                        (if_then_else (match_operand 0 "ar5_reg_operand" "")
740                                      (const_int 1) (const_int 0))
741               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
742                        (if_then_else (match_operand 1 "ar5_reg_operand" "")
743                                      (const_int 1) (const_int 0))
744               (eq_attr "type" "binary,binarycc")
745                        (if_then_else (match_operand 2 "ar5_reg_operand" "")
746                                      (const_int 1) (const_int 0))]
747              (const_int 0)))
748
749 (define_attr "setar6" ""
750        (cond [(eq_attr "type" "unary,binary")
751                        (if_then_else (match_operand 0 "ar6_reg_operand" "")
752                                      (const_int 1) (const_int 0))]
753              (const_int 0)))
754
755 (define_attr "setlda_ar6" ""
756        (cond [(eq_attr "type" "lda")
757                        (if_then_else (match_operand 0 "ar6_reg_operand" "")
758                                      (const_int 1) (const_int 0))]
759              (const_int 0)))
760
761 (define_attr "usear6" ""
762        (cond [(eq_attr "type" "compare,store")
763                        (if_then_else (match_operand 0 "ar6_mem_operand" "")
764                                      (const_int 1) (const_int 0))
765               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
766                        (if_then_else (match_operand 1 "ar6_mem_operand" "")
767                                      (const_int 1) (const_int 0))
768               (eq_attr "type" "binary,binarycc")
769                        (if_then_else (match_operand 2 "ar6_mem_operand" "")
770                                      (const_int 1) (const_int 0))
771               (eq_attr "type" "db,dbc")
772                        (if_then_else (match_operand 0 "ar6_reg_operand" "")
773                                      (const_int 1) (const_int 0))]
774              (const_int 0)))
775
776 (define_attr "readar6" ""
777        (cond [(eq_attr "type" "compare")
778                        (if_then_else (match_operand 0 "ar6_reg_operand" "")
779                                      (const_int 1) (const_int 0))
780               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
781                        (if_then_else (match_operand 1 "ar6_reg_operand" "")
782                                      (const_int 1) (const_int 0))
783               (eq_attr "type" "binary,binarycc")
784                        (if_then_else (match_operand 2 "ar6_reg_operand" "")
785                                      (const_int 1) (const_int 0))]
786              (const_int 0)))
787
788 (define_attr "setar7" ""
789        (cond [(eq_attr "type" "unary,binary")
790                        (if_then_else (match_operand 0 "ar7_reg_operand" "")
791                                      (const_int 1) (const_int 0))]
792              (const_int 0)))
793
794 (define_attr "setlda_ar7" ""
795        (cond [(eq_attr "type" "lda")
796                        (if_then_else (match_operand 0 "ar7_reg_operand" "")
797                                      (const_int 1) (const_int 0))]
798              (const_int 0)))
799
800 (define_attr "usear7" ""
801        (cond [(eq_attr "type" "compare,store")
802                        (if_then_else (match_operand 0 "ar7_mem_operand" "")
803                                      (const_int 1) (const_int 0))
804               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
805                        (if_then_else (match_operand 1 "ar7_mem_operand" "")
806                                      (const_int 1) (const_int 0))
807               (eq_attr "type" "binary,binarycc")
808                        (if_then_else (match_operand 2 "ar7_mem_operand" "")
809                                      (const_int 1) (const_int 0))
810               (eq_attr "type" "db,dbc")
811                        (if_then_else (match_operand 0 "ar7_reg_operand" "")
812                                      (const_int 1) (const_int 0))]
813              (const_int 0)))
814
815 (define_attr "readar7" ""
816        (cond [(eq_attr "type" "compare")
817                        (if_then_else (match_operand 0 "ar7_reg_operand" "")
818                                      (const_int 1) (const_int 0))
819               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
820                        (if_then_else (match_operand 1 "ar7_reg_operand" "")
821                                      (const_int 1) (const_int 0))
822               (eq_attr "type" "binary,binarycc")
823                        (if_then_else (match_operand 2 "ar7_reg_operand" "")
824                                      (const_int 1) (const_int 0))]
825              (const_int 0)))
826
827 (define_attr "setir0" ""
828        (cond [(eq_attr "type" "unary,binary")
829                        (if_then_else (match_operand 0 "ir0_reg_operand" "")
830                                      (const_int 1) (const_int 0))]
831              (const_int 0)))
832
833 (define_attr "setlda_ir0" ""
834        (cond [(eq_attr "type" "lda")
835                        (if_then_else (match_operand 0 "ir0_reg_operand" "")
836                                      (const_int 1) (const_int 0))]
837              (const_int 0)))
838
839 (define_attr "useir0" ""
840        (cond [(eq_attr "type" "compare,store")
841                        (if_then_else (match_operand 0 "ir0_mem_operand" "")
842                                      (const_int 1) (const_int 0))
843               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
844                        (if_then_else (match_operand 1 "ir0_mem_operand" "")
845                                      (const_int 1) (const_int 0))
846               (eq_attr "type" "binary,binarycc")
847                        (if_then_else (match_operand 2 "ir0_mem_operand" "")
848                                      (const_int 1) (const_int 0))]
849              (const_int 0)))
850
851 (define_attr "setir1" ""
852        (cond [(eq_attr "type" "unary,binary")
853                        (if_then_else (match_operand 0 "ir1_reg_operand" "")
854                                      (const_int 1) (const_int 0))]
855              (const_int 0)))
856
857 (define_attr "setlda_ir1" ""
858        (cond [(eq_attr "type" "lda")
859                        (if_then_else (match_operand 0 "ir1_reg_operand" "")
860                                      (const_int 1) (const_int 0))]
861              (const_int 0)))
862
863 (define_attr "useir1" ""
864        (cond [(eq_attr "type" "compare,store")
865                        (if_then_else (match_operand 0 "ir1_mem_operand" "")
866                                      (const_int 1) (const_int 0))
867               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc")
868                        (if_then_else (match_operand 1 "ir1_mem_operand" "")
869                                      (const_int 1) (const_int 0))
870               (eq_attr "type" "binary,binarycc")
871                        (if_then_else (match_operand 2 "ir1_mem_operand" "")
872                                      (const_int 1) (const_int 0))]
873              (const_int 0)))
874
875 ; With the C3x, things are simpler, but slower, i.e. more pipeline conflicts :(
876 ; There are three functional groups:
877 ; (1) AR0-AR7, IR0-IR1, BK
878 ; (2) DP
879 ; (3) SP
880 ;
881 ; When a register in one of these functional groups is loaded,
882 ; the contents of that or any other register in its group
883 ; will not be available to the next instruction for 2 machine cycles.
884 ; Similarly, when a register in one of the functional groups is read
885 ; excepting (IR0-IR1, BK, DP) the contents of that or any other register
886 ; in its group will not be available to the next instruction for
887 ; 1 machine cycle.
888 ;
889 ; Let's ignore functional groups 2 and 3 for now, since they are not
890 ; so important.
891
892 (define_attr "setgroup1" ""
893        (cond [(eq_attr "type" "lda,unary,binary")
894                   (if_then_else (match_operand 0 "group1_reg_operand" "")
895                                 (const_int 1) (const_int 0))]
896              (const_int 0)))
897
898 (define_attr "usegroup1" ""
899        (cond [(eq_attr "type" "compare,store,store_store,store_load")
900               (if_then_else (match_operand 0 "group1_mem_operand" "")
901                             (const_int 1) (const_int 0))
902               (eq_attr "type" "compare,lda,unary,unarycc,binary,binarycc,load_load,load_store")
903               (if_then_else (match_operand 1 "group1_mem_operand" "")
904                             (const_int 1) (const_int 0))
905               (eq_attr "type" "store_store,load_store")
906               (if_then_else (match_operand 2 "group1_mem_operand" "")
907                             (const_int 1) (const_int 0))
908               (eq_attr "type" "load_load,store_load")
909               (if_then_else (match_operand 3 "group1_mem_operand" "")
910                             (const_int 1) (const_int 0))]
911              (const_int 0)))
912
913 (define_attr "readarx" ""
914        (cond [(eq_attr "type" "compare")
915               (if_then_else (match_operand 0 "arx_reg_operand" "")
916                             (const_int 1) (const_int 0))
917               (eq_attr "type" "compare,store,lda,unary,unarycc,binary,binarycc")
918               (if_then_else (match_operand 1 "arx_reg_operand" "")
919                             (const_int 1) (const_int 0))
920               (eq_attr "type" "binary,binarycc")
921               (if_then_else (match_operand 2 "arx_reg_operand" "")
922                             (const_int 1) (const_int 0))]
923              (const_int 0)))
924
925
926 ;
927 ; C4x INSN PATTERNS:
928 ;
929 ; Note that the movMM and addP patterns can be called during reload
930 ; so we need to take special care with theses patterns since
931 ; we cannot blindly clobber CC or generate new pseudo registers.
932
933 ;
934 ; TWO OPERAND INTEGER INSTRUCTIONS
935 ;
936
937 ;
938 ; LDP/LDPK
939 ;
940 (define_insn "set_ldp"
941   [(set (match_operand:QI 0 "dp_reg_operand" "=z")
942         (high:QI (match_operand:QI 1 "" "")))]
943   "! TARGET_SMALL"
944   "* return (TARGET_C3X) ? \"ldp\\t%A1\" : \"ldpk\\t%A1\";"
945   [(set_attr "type" "ldp")])
946
947 (define_insn "set_ldp_prologue"
948   [(set (match_operand:QI 0 "dp_reg_operand" "=z")
949         (high:QI (match_operand:QI 1 "" "")))]
950   "TARGET_SMALL && TARGET_PARANOID"
951   "* return (TARGET_C3X) ? \"ldp\\t@data_sec\" : \"ldpk\\t@data_sec\";"
952   [(set_attr "type" "ldp")])
953
954 (define_insn "set_high"
955   [(set (match_operand:QI 0 "std_reg_operand" "=c")
956         (high:QI (match_operand:QI 1 "symbolic_address_operand" "")))]
957   "! TARGET_C3X && ! TARGET_TI"
958   "ldhi\\t^%H1,%0"
959   [(set_attr "type" "unary")])
960
961 (define_insn "set_lo_sum"
962   [(set (match_operand:QI 0 "std_reg_operand" "+c")
963         (lo_sum:QI (match_dup 0)
964                    (match_operand:QI 1 "symbolic_address_operand" "")))]
965   "! TARGET_TI"
966   "or\\t#%H1,%0"
967   [(set_attr "type" "unary")])
968
969 (define_split
970   [(set (match_operand:QI 0 "std_reg_operand" "")
971         (match_operand:QI 1 "symbolic_address_operand" ""))]
972   "reload_completed && ! TARGET_C3X && ! TARGET_TI"
973   [(set (match_dup 0) (high:QI (match_dup 1)))
974    (set (match_dup 0) (lo_sum:QI (match_dup 0) (match_dup 1)))]
975   "")
976
977 (define_split
978   [(set (match_operand:QI 0 "reg_operand" "")
979         (match_operand:QI 1 "const_int_operand" ""))
980    (clobber (reg:QI 16))]
981   "! TARGET_C3X
982    && ! IS_INT16_CONST (INTVAL (operands[1]))
983    && ! IS_HIGH_CONST (INTVAL (operands[1]))
984    && reload_completed
985    && std_reg_operand (operands[0], QImode)"
986   [(set (match_dup 0) (match_dup 2))
987    (set (match_dup 0) (ior:QI (match_dup 0) (match_dup 3)))]
988   "
989 {
990    operands[2] = GEN_INT (INTVAL (operands[1]) & ~0xffff);
991    operands[3] = GEN_INT (INTVAL (operands[1]) & 0xffff);
992 }")
993
994 (define_split
995   [(set (match_operand:QI 0 "reg_operand" "")
996         (match_operand:QI 1 "const_int_operand" ""))]
997   "! TARGET_C3X
998    && ! IS_INT16_CONST (INTVAL (operands[1]))
999    && ! IS_HIGH_CONST (INTVAL (operands[1]))
1000    && reload_completed
1001    && std_reg_operand (operands[0], QImode)"
1002   [(set (match_dup 0) (match_dup 2))
1003    (set (match_dup 0) (ior:QI (match_dup 0) (match_dup 3)))]
1004   "
1005 {
1006    operands[2] = GEN_INT (INTVAL (operands[1]) & ~0xffff);
1007    operands[3] = GEN_INT (INTVAL (operands[1]) & 0xffff);
1008 }")
1009
1010 (define_split
1011   [(set (match_operand:QI 0 "reg_operand" "")
1012         (match_operand:QI 1 "const_int_operand" ""))
1013    (clobber (reg:QI 16))]
1014   "TARGET_C3X && ! TARGET_SMALL
1015    && ! IS_INT16_CONST (INTVAL (operands[1]))
1016    && reload_completed
1017    && std_reg_operand (operands[0], QImode)
1018    && c4x_shiftable_constant (operands[1]) < 0"
1019   [(set (match_dup 0) (match_dup 2))
1020    (set (match_dup 0) (ashift:QI (match_dup 0) (match_dup 4)))
1021    (set (match_dup 0) (ior:QI (match_dup 0) (match_dup 3)))]
1022   "
1023 {
1024    /* Generate two's complement value of 16 MSBs.  */
1025    operands[2] = gen_rtx (CONST_INT, VOIDmode,
1026                           (((INTVAL (operands[1]) >> 16) & 0xffff)
1027                            - 0x8000) ^ ~0x7fff);
1028    operands[3] = GEN_INT (INTVAL (operands[1]) & 0xffff);
1029    operands[4] = GEN_INT (16);
1030 }")
1031
1032 (define_split
1033   [(set (match_operand:QI 0 "reg_operand" "")
1034         (match_operand:QI 1 "const_int_operand" ""))]
1035   "TARGET_C3X && ! TARGET_SMALL
1036    && ! IS_INT16_CONST (INTVAL (operands[1]))
1037    && reload_completed
1038    && std_reg_operand (operands[0], QImode)
1039    && c4x_shiftable_constant (operands[1]) < 0"
1040   [(set (match_dup 0) (match_dup 2))
1041    (set (match_dup 0) (ashift:QI (match_dup 0) (match_dup 4)))
1042    (set (match_dup 0) (ior:QI (match_dup 0) (match_dup 3)))]
1043   "
1044 {
1045    /* Generate two's complement value of 16 MSBs.  */
1046    operands[2] = gen_rtx (CONST_INT, VOIDmode,
1047                           (((INTVAL (operands[1]) >> 16) & 0xffff)
1048                            - 0x8000) ^ ~0x7fff);
1049    operands[3] = GEN_INT (INTVAL (operands[1]) & 0xffff);
1050    operands[4] = GEN_INT (16);
1051 }")
1052
1053 (define_split
1054   [(set (match_operand:QI 0 "reg_operand" "")
1055         (match_operand:QI 1 "const_int_operand" ""))
1056    (clobber (reg:QI 16))]
1057   "TARGET_C3X
1058    && ! IS_INT16_CONST (INTVAL (operands[1]))
1059    && reload_completed
1060    && std_reg_operand (operands[0], QImode)
1061    && c4x_shiftable_constant (operands[1]) >= 0"
1062   [(set (match_dup 0) (match_dup 2))
1063    (set (match_dup 0) (ashift:QI (match_dup 0) (match_dup 3)))]
1064   "
1065 {
1066    /* Generate two's complement value of MSBs.  */
1067    int shift = c4x_shiftable_constant (operands[1]);
1068
1069    operands[2] = GEN_INT ((((INTVAL (operands[1]) >> shift) & 0xffff)
1070                            - 0x8000) ^ ~0x7fff);
1071    operands[3] = GEN_INT (shift);
1072 }")
1073
1074 (define_split
1075   [(set (match_operand:QI 0 "reg_operand" "")
1076         (match_operand:QI 1 "const_int_operand" ""))]
1077   "TARGET_C3X
1078    && ! IS_INT16_CONST (INTVAL (operands[1]))
1079    && reload_completed
1080    && std_reg_operand (operands[0], QImode)
1081    && c4x_shiftable_constant (operands[1]) >= 0"
1082   [(set (match_dup 0) (match_dup 2))
1083    (set (match_dup 0) (ashift:QI (match_dup 0) (match_dup 3)))]
1084   "
1085 {
1086    /* Generate two's complement value of MSBs.  */
1087    int shift = c4x_shiftable_constant (operands[1]);
1088
1089    operands[2] = GEN_INT ((((INTVAL (operands[1]) >> shift) & 0xffff)
1090                             - 0x8000) ^ ~0x7fff);
1091    operands[3] = GEN_INT (shift);
1092 }")
1093
1094 (define_split
1095   [(set (match_operand:QI 0 "reg_operand" "")
1096         (match_operand:QI 1 "const_int_operand" ""))
1097    (clobber (reg:QI 16))]
1098   "! TARGET_SMALL
1099    && ! IS_INT16_CONST (INTVAL (operands[1]))
1100    && ! IS_HIGH_CONST (INTVAL (operands[1]))
1101    && reload_completed
1102    && ! std_reg_operand (operands[0], QImode)"
1103   [(set (match_dup 2) (high:QI (match_dup 3)))
1104    (set (match_dup 0) (match_dup 4))
1105    (use (match_dup 1))]
1106   "
1107 {
1108    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1109    operands[2] = dp_reg;
1110    operands[3] = force_const_mem (Pmode, operands[1]);
1111    operands[4] = change_address (operands[3], QImode,
1112                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1113                                                  XEXP (operands[3], 0)));
1114    operands[3] = XEXP (operands[3], 0);
1115 }")
1116
1117 (define_split
1118   [(set (match_operand:QI 0 "reg_operand" "")
1119         (match_operand:QI 1 "const_int_operand" ""))]
1120   "! TARGET_SMALL
1121    && ! IS_INT16_CONST (INTVAL (operands[1]))
1122    && ! IS_HIGH_CONST (INTVAL (operands[1]))
1123    && reload_completed
1124    && ! std_reg_operand (operands[0], QImode)"
1125   [(set (match_dup 2) (high:QI (match_dup 3)))
1126    (set (match_dup 0) (match_dup 4))
1127    (use (match_dup 1))]
1128   "
1129 {
1130    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1131    operands[2] = dp_reg;
1132    operands[3] = force_const_mem (Pmode, operands[1]);
1133    operands[4] = change_address (operands[3], QImode,
1134                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1135                                                  XEXP (operands[3], 0)));
1136    operands[3] = XEXP (operands[3], 0);
1137 }")
1138
1139 (define_split
1140   [(set (match_operand:QI 0 "reg_operand" "")
1141         (match_operand:QI 1 "const_int_operand" ""))
1142    (clobber (reg:QI 16))]
1143   "TARGET_SMALL
1144    && ! IS_INT16_CONST (INTVAL (operands[1]))
1145    && ! IS_HIGH_CONST (INTVAL (operands[1]))
1146    && reload_completed
1147    && ((TARGET_C3X && c4x_shiftable_constant (operands[1]) < 0)
1148        || ! std_reg_operand (operands[0], QImode))"
1149   [(set (match_dup 0) (match_dup 2))
1150    (use (match_dup 1))]
1151   "
1152 {
1153    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1154    operands[2] = force_const_mem (Pmode, operands[1]);
1155    operands[2] = change_address (operands[2], QImode,
1156                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1157                                                  XEXP (operands[2], 0)));
1158 }")
1159
1160 (define_split
1161   [(set (match_operand:QI 0 "reg_operand" "")
1162         (match_operand:QI 1 "const_int_operand" ""))]
1163   "TARGET_SMALL
1164    && ! IS_INT16_CONST (INTVAL (operands[1]))
1165    && ! IS_HIGH_CONST (INTVAL (operands[1]))
1166    && reload_completed
1167    && ((TARGET_C3X && c4x_shiftable_constant (operands[1]) < 0)
1168        || ! std_reg_operand (operands[0], QImode))"
1169   [(set (match_dup 0) (match_dup 2))
1170    (use (match_dup 1))]
1171   "
1172 {
1173    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1174    operands[2] = force_const_mem (Pmode, operands[1]);
1175    operands[2] = change_address (operands[2], QImode,
1176                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1177                                                  XEXP (operands[2], 0)));
1178 }")
1179
1180 (define_split
1181   [(set (match_operand:HI 0 "reg_operand" "")
1182         (match_operand:HI 1 "const_int_operand" ""))
1183    (clobber (reg:QI 16))]
1184   "reload_completed"
1185   [(set (match_dup 2) (match_dup 4))
1186    (set (match_dup 3) (match_dup 5))]
1187   "
1188 {
1189    operands[2] = c4x_operand_subword (operands[0], 0, 1, HImode);
1190    operands[3] = c4x_operand_subword (operands[0], 1, 1, HImode);
1191    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
1192    operands[5] = c4x_operand_subword (operands[1], 1, 1, HImode);
1193 }")
1194
1195
1196 ; We need to clobber the DP reg to be safe in case we
1197 ; need to load this address from memory
1198 (define_insn "load_immed_address"
1199   [(set (match_operand:QI 0 "reg_operand" "=a?x?c*r")
1200         (match_operand:QI 1 "symbolic_address_operand" ""))
1201    (clobber (reg:QI 16))]
1202   "TARGET_LOAD_ADDRESS"
1203   "#"
1204   [(set_attr "type" "multi")])
1205
1206
1207 (define_split
1208   [(set (match_operand:QI 0 "std_reg_operand" "")
1209         (match_operand:QI 1 "symbolic_address_operand" ""))
1210    (clobber (reg:QI 16))]
1211   "reload_completed && ! TARGET_C3X && ! TARGET_TI"
1212   [(set (match_dup 0) (high:QI (match_dup 1)))
1213    (set (match_dup 0) (lo_sum:QI (match_dup 0) (match_dup 1)))]
1214   "")
1215
1216 ; CC has been selected to load a symbolic address.  We force the address
1217 ; into memory and then generate LDP and LDIU insns.
1218 ; This is also required for the C30 if we pretend that we can 
1219 ; easily load symbolic addresses into a register.
1220 (define_split
1221   [(set (match_operand:QI 0 "reg_operand" "")
1222         (match_operand:QI 1 "symbolic_address_operand" ""))
1223    (clobber (reg:QI 16))]
1224   "reload_completed
1225    && ! TARGET_SMALL 
1226    && (TARGET_C3X || TARGET_TI || ! std_reg_operand (operands[0], QImode))"
1227   [(set (match_dup 2) (high:QI (match_dup 3)))
1228    (set (match_dup 0) (match_dup 4))
1229    (use (match_dup 1))]
1230   "
1231 {
1232    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1233    operands[2] = dp_reg;
1234    operands[3] = force_const_mem (Pmode, operands[1]);
1235    operands[4] = change_address (operands[3], QImode,
1236                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1237                                                  XEXP (operands[3], 0)));
1238    operands[3] = XEXP (operands[3], 0);
1239 }")
1240
1241 ; This pattern is similar to the above but does not emit a LDP
1242 ; for the small memory model.
1243 (define_split
1244   [(set (match_operand:QI 0 "reg_operand" "")
1245         (match_operand:QI 1 "symbolic_address_operand" ""))
1246    (clobber (reg:QI 16))]
1247   "reload_completed
1248    && TARGET_SMALL
1249    && (TARGET_C3X || TARGET_TI || ! std_reg_operand (operands[0], QImode))"
1250   [(set (match_dup 0) (match_dup 2))
1251    (use (match_dup 1))]
1252   "
1253 {  
1254    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1255    operands[2] = force_const_mem (Pmode, operands[1]);
1256    operands[2] = change_address (operands[2], QImode,
1257                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1258                                                  XEXP (operands[2], 0)));
1259 }")
1260
1261 (define_insn "loadhi_big_constant"
1262   [(set (match_operand:HI 0 "reg_operand" "=c*d")
1263         (match_operand:HI 1 "const_int_operand" ""))
1264    (clobber (reg:QI 16))]
1265   ""
1266   "#"
1267   [(set_attr "type" "multi")])
1268
1269 ;
1270 ; LDIU/LDA/STI/STIK
1271 ;
1272 ; The following moves will not set the condition codes register.
1273 ;
1274
1275 ; This must come before the general case
1276 (define_insn "*movqi_stik"
1277   [(set (match_operand:QI 0 "memory_operand" "=m")
1278         (match_operand:QI 1 "stik_const_operand" "K"))]
1279   "! TARGET_C3X"
1280   "stik\\t%1,%0"
1281   [(set_attr "type" "store")])
1282
1283 (define_insn "loadqi_big_constant"
1284   [(set (match_operand:QI 0 "reg_operand" "=c*d")
1285         (match_operand:QI 1 "const_int_operand" ""))
1286    (clobber (reg:QI 16))]
1287   "! IS_INT16_CONST (INTVAL (operands[1]))
1288    && ! IS_HIGH_CONST (INTVAL (operands[1]))"
1289   "#"
1290   [(set_attr "type" "multi")])
1291
1292 ; We must provide an alternative to store to memory in case we have to
1293 ; spill a register.
1294 (define_insn "movqi_noclobber"
1295   [(set (match_operand:QI 0 "dst_operand" "=d,*c,m,r")
1296         (match_operand:QI 1 "src_hi_operand" "rIm,rIm,r,O"))]
1297   "(REG_P (operands[0]) || REG_P (operands[1])
1298     || GET_CODE (operands[0]) == SUBREG
1299     || GET_CODE (operands[1]) == SUBREG)
1300     && ! symbolic_address_operand (operands[1], QImode)"
1301   "*
1302    if (which_alternative == 2)
1303      return \"sti\\t%1,%0\";
1304
1305    if (! TARGET_C3X && which_alternative == 3)
1306      {
1307        operands[1] = GEN_INT ((INTVAL (operands[1]) >> 16) & 0xffff);
1308        return \"ldhi\\t%1,%0\";
1309      }
1310
1311    /* The lda instruction cannot use the same register as source
1312       and destination.  */
1313    if (! TARGET_C3X && which_alternative == 1
1314        && (   IS_ADDR_REG (operands[0])
1315            || IS_INDEX_REG (operands[0])
1316            || IS_SP_REG (operands[0]))
1317        && (REGNO (operands[0]) != REGNO (operands[1])))
1318       return \"lda\\t%1,%0\";
1319    return \"ldiu\\t%1,%0\";
1320   "
1321   [(set_attr "type" "unary,lda,store,unary")
1322    (set_attr "data" "int16,int16,int16,high_16")])
1323
1324 ;
1325 ; LDI
1326 ;
1327
1328 ; We shouldn't need these peepholes, but the combiner seems to miss them...
1329 (define_peephole
1330   [(set (match_operand:QI 0 "ext_reg_operand" "=d")
1331         (match_operand:QI 1 "src_operand" "rIm"))
1332    (set (reg:CC 21)
1333         (compare:CC (match_dup 0) (const_int 0)))]
1334   ""
1335   "ldi\\t%1,%0"
1336   [(set_attr "type" "unarycc")
1337    (set_attr "data" "int16")])
1338
1339 (define_insn "*movqi_set"
1340   [(set (reg:CC 21)
1341         (compare:CC (match_operand:QI 1 "src_operand" "rIm") 
1342                     (const_int 0)))
1343    (set (match_operand:QI 0 "ext_reg_operand" "=d")
1344         (match_dup 1))]
1345   ""
1346   "ldi\\t%1,%0"
1347   [(set_attr "type" "unarycc")
1348    (set_attr "data" "int16")])
1349
1350 ; This pattern probably gets in the way and requires a scratch register
1351 ; when a simple compare with zero will suffice.
1352 ;(define_insn "*movqi_test"
1353 ; [(set (reg:CC 21)
1354 ;       (compare:CC (match_operand:QI 1 "src_operand" "rIm") 
1355 ;                   (const_int 0)))
1356 ;  (clobber (match_scratch:QI 0 "=d"))]
1357 ; ""
1358 ; "@
1359 ;  ldi\\t%1,%0"
1360 ;  [(set_attr "type" "unarycc")
1361 ;   (set_attr "data" "int16")])
1362
1363 ;  If one of the operands is not a register, then we should
1364 ;  emit two insns, using a scratch register.  This will produce
1365 ;  better code in loops if the source operand is invariant, since
1366 ;  the source reload can be optimized out.  During reload we cannot
1367 ;  use change_address or force_reg which will allocate new pseudo regs.
1368
1369 ;  Unlike most other insns, the move insns can't be split with
1370 ;  different predicates, because register spilling and other parts of
1371 ;  the compiler, have memoized the insn number already.
1372
1373 (define_expand "movqi"
1374   [(set (match_operand:QI 0 "general_operand" "")
1375         (match_operand:QI 1 "general_operand" ""))]
1376   ""
1377   "
1378 {
1379   if (c4x_emit_move_sequence (operands, QImode))
1380     DONE;
1381 }")
1382
1383
1384 ; As far as GCC is concerned, the moves are performed in parallel
1385 ; thus it must be convinced that there is no aliasing.
1386 ; It also assumes that the input operands are simultaneously loaded
1387 ; and then the output operands are simultaneously stored.
1388 ; With the C4x, if there are parallel stores to the same address
1389 ; both stores are executed.
1390 ; If there is a parallel load and store to the same address,
1391 ; the load is performed first.
1392 ; The problem with this pattern is that reload can spoil
1393 ; the show when it eliminates a reference to the frame pointer.
1394 ; This can invalidate the memory addressing mode, i.e., when
1395 ; the displacement is greater than 1.
1396 (define_insn "movqi_parallel"
1397   [(set (match_operand:QI 0 "parallel_operand" "=q,S<>!V,q,S<>!V")
1398         (match_operand:QI 1 "parallel_operand" "S<>!V,q,S<>!V,q"))
1399    (set (match_operand:QI 2 "parallel_operand" "=q,S<>!V,S<>!V,q")
1400         (match_operand:QI 3 "parallel_operand" "S<>!V,q,q,S<>!V"))]
1401   "TARGET_PARALLEL && valid_parallel_load_store (operands, QImode)"
1402   "@
1403    ldi1\\t%1,%0\\n||\\tldi2\\t%3,%2
1404    sti1\\t%1,%0\\n||\\tsti2\\t%3,%2
1405    ldi\\t%1,%0\\n||\\tsti\\t%3,%2
1406    ldi\\t%3,%2\\n||\\tsti\\t%1,%0"
1407   [(set_attr "type" "load_load,store_store,load_store,store_load")])
1408
1409 ;
1410 ; PUSH/POP
1411 ;
1412 (define_insn "pushqi"
1413   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
1414         (match_operand:QI 0 "reg_operand" "r"))]
1415   ""
1416   "push\\t%0"
1417   [(set_attr "type" "push")])
1418
1419 (define_insn "push_st"
1420   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
1421         (unspec:QI [(reg:QI 21)] UNSPEC_PUSH_ST))
1422    (use (reg:QI 21))]
1423   ""
1424   "push\\tst"
1425   [(set_attr "type" "push")])
1426
1427 (define_insn "push_dp"
1428   [(set (mem:QI (pre_inc:QI (reg:QI 20))) 
1429         (unspec:QI [(reg:QI 16)] UNSPEC_PUSH_DP))
1430    (use (reg:QI 16))]
1431   ""
1432   "push\\tdp"
1433   [(set_attr "type" "push")])
1434
1435 (define_insn "popqi"
1436   [(set (match_operand:QI 0 "reg_operand" "=r")
1437         (mem:QI (post_dec:QI (reg:QI 20))))
1438    (clobber (reg:CC 21))]
1439   ""
1440   "pop\\t%0"
1441   [(set_attr "type" "pop")])
1442
1443 (define_insn "pop_st"
1444   [(set (unspec:QI [(reg:QI 21)] UNSPEC_POP_ST) 
1445         (mem:QI (post_dec:QI (reg:QI 20))))
1446    (clobber (reg:CC 21))]
1447   ""
1448   "pop\\tst"
1449   [(set_attr "type" "pop")])
1450
1451 (define_insn "pop_dp"
1452   [(set (unspec:QI [(reg:QI 16)] UNSPEC_POP_DP)
1453         (mem:QI (post_dec:QI (reg:QI 20))))
1454    (clobber (reg:CC 16))]
1455   ""
1456   "pop\\tdp"
1457   [(set_attr "type" "pop")])
1458
1459 (define_insn "popqi_unspec"
1460   [(set (unspec:QI [(match_operand:QI 0 "reg_operand" "=r")] UNSPEC_POPQI)
1461         (mem:QI (post_dec:QI (reg:QI 20))))
1462    (clobber (match_dup 0))
1463    (clobber (reg:CC 21))]
1464   ""
1465   "pop\\t%0"
1466   [(set_attr "type" "pop")])
1467
1468 ;
1469 ; ABSI
1470 ;
1471 (define_expand "absqi2"
1472   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1473                    (abs:QI (match_operand:QI 1 "src_operand" "")))
1474               (clobber (reg:CC_NOOV 21))])]
1475   ""
1476   "")
1477
1478 (define_insn "*absqi2_clobber"
1479   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1480         (abs:QI (match_operand:QI 1 "src_operand" "rIm,rIm")))
1481    (clobber (reg:CC_NOOV 21))]
1482   ""
1483   "absi\\t%1,%0"
1484   [(set_attr "type" "unarycc,unary")
1485    (set_attr "data" "int16,int16")])
1486
1487 (define_insn "*absqi2_noclobber"
1488   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1489         (abs:QI (match_operand:QI 1 "src_operand" "rIm")))]
1490   ""
1491   "absi\\t%1,%0"
1492   [(set_attr "type" "unary")
1493    (set_attr "data" "int16")])
1494
1495 (define_split
1496   [(set (match_operand:QI 0 "std_reg_operand" "")
1497         (abs:QI (match_operand:QI 1 "src_operand" "")))
1498    (clobber (reg:CC_NOOV 21))]
1499   "reload_completed"
1500   [(set (match_dup 0)
1501         (abs:QI (match_dup 1)))]
1502   "")
1503
1504 (define_insn "*absqi2_test"
1505   [(set (reg:CC_NOOV 21)
1506         (compare:CC_NOOV (abs:QI (match_operand:QI 1 "src_operand" "rIm"))
1507                          (const_int 0)))
1508    (clobber (match_scratch:QI 0 "=d"))]
1509   ""
1510   "absi\\t%1,%0"
1511   [(set_attr "type" "unarycc")
1512    (set_attr "data" "int16")])
1513
1514 (define_insn "*absqi2_set"
1515   [(set (reg:CC_NOOV 21)
1516         (compare:CC_NOOV (abs:QI (match_operand:QI 1 "src_operand" "rIm"))
1517                          (const_int 0)))
1518    (set (match_operand:QI 0 "ext_reg_operand" "=d")
1519         (abs:QI (match_dup 1)))]
1520   ""
1521   "absi\\t%1,%0"
1522   [(set_attr "type" "unarycc")
1523    (set_attr "data" "int16")])        
1524
1525 ;
1526 ; NEGI
1527 ;
1528 (define_expand "negqi2"
1529   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1530                    (neg:QI (match_operand:QI 1 "src_operand" "")))
1531               (clobber (reg:CC_NOOV 21))])]
1532 ""
1533 "")
1534
1535 (define_insn "*negqi2_clobber"
1536   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1537         (neg:QI (match_operand:QI 1 "src_operand" "rIm,rIm")))
1538    (clobber (reg:CC_NOOV 21))]
1539   ""
1540   "negi\\t%1,%0"
1541   [(set_attr "type" "unarycc,unary")
1542    (set_attr "data" "int16,int16")])
1543
1544 (define_insn "*negqi2_noclobber"
1545   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1546         (neg:QI (match_operand:QI 1 "src_operand" "rIm")))]
1547   ""
1548   "negi\\t%1,%0"
1549   [(set_attr "type" "unary")
1550    (set_attr "data" "int16")])
1551
1552 (define_split
1553   [(set (match_operand:QI 0 "std_reg_operand" "")
1554         (neg:QI (match_operand:QI 1 "src_operand" "")))
1555    (clobber (reg:CC_NOOV 21))]
1556   "reload_completed"
1557   [(set (match_dup 0)
1558         (neg:QI (match_dup 1)))]
1559   "")
1560
1561 (define_insn "*negqi2_test"
1562   [(set (reg:CC_NOOV 21)
1563         (compare:CC_NOOV (neg:QI (match_operand:QI 1 "src_operand" "rIm"))
1564                          (const_int 0)))
1565    (clobber (match_scratch:QI 0 "=d"))]
1566   ""
1567   "negi\\t%1,%0"
1568   [(set_attr "type" "unarycc")
1569    (set_attr "data" "int16")])
1570
1571 (define_insn "*negqi2_set"
1572   [(set (reg:CC_NOOV 21)
1573         (compare:CC_NOOV (neg:QI (match_operand:QI 1 "src_operand" "rIm"))
1574                          (const_int 0)))
1575    (set (match_operand:QI 0 "ext_reg_operand" "=d")
1576         (neg:QI (match_dup 1)))]
1577   ""
1578   "negi\\t%1,%0"
1579   [(set_attr "type" "unarycc")
1580    (set_attr "data" "int16")])        
1581
1582 (define_insn "*negbqi2_clobber"
1583   [(set (match_operand:QI 0 "ext_reg_operand" "=d")
1584         (neg:QI (match_operand:QI 1 "src_operand" "rIm")))
1585    (use (reg:CC_NOOV 21))
1586    (clobber (reg:CC_NOOV 21))]
1587   ""
1588   "negb\\t%1,%0"
1589   [(set_attr "type" "unarycc")
1590    (set_attr "data" "int16")])        
1591
1592 ;
1593 ; NOT
1594 ;
1595 (define_expand "one_cmplqi2"
1596   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1597                    (not:QI (match_operand:QI 1 "lsrc_operand" "")))
1598               (clobber (reg:CC 21))])]
1599   ""
1600   "")
1601
1602 (define_insn "*one_cmplqi2_clobber"
1603   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1604         (not:QI (match_operand:QI 1 "lsrc_operand" "rLm,rLm")))
1605    (clobber (reg:CC 21))]
1606   ""
1607   "not\\t%1,%0"
1608   [(set_attr "type" "unarycc,unary")
1609    (set_attr "data" "uint16,uint16")])
1610
1611 (define_insn "*one_cmplqi2_noclobber"
1612   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1613         (not:QI (match_operand:QI 1 "lsrc_operand" "rLm")))]
1614   ""
1615   "not\\t%1,%0"
1616   [(set_attr "type" "unary")
1617    (set_attr "data" "uint16")])
1618
1619 (define_split
1620   [(set (match_operand:QI 0 "std_reg_operand" "")
1621         (not:QI (match_operand:QI 1 "lsrc_operand" "")))
1622    (clobber (reg:CC 21))]
1623   "reload_completed"
1624   [(set (match_dup 0)
1625         (not:QI (match_dup 1)))]
1626   "")
1627
1628 (define_insn "*one_cmplqi2_test"
1629   [(set (reg:CC 21)
1630         (compare:CC (not:QI (match_operand:QI 1 "lsrc_operand" "rLm"))
1631                     (const_int 0)))
1632    (clobber (match_scratch:QI 0 "=d"))]
1633   ""
1634   "not\\t%1,%0"
1635   [(set_attr "type" "unarycc")
1636    (set_attr "data" "uint16")])
1637
1638 (define_insn "*one_cmplqi2_set"
1639   [(set (reg:CC 21)
1640         (compare:CC (not:QI (match_operand:QI 1 "lsrc_operand" "rLm"))
1641                     (const_int 0)))
1642    (set (match_operand:QI 0 "ext_reg_operand" "=d")        
1643         (not:QI (match_dup 1)))]
1644   ""
1645   "not\\t%1,%0"
1646   [(set_attr "type" "unarycc")
1647    (set_attr "data" "uint16")])        
1648
1649 (define_insn "*one_cmplqi2_const_clobber"
1650   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1651         (match_operand:QI 1 "not_const_operand" "N,N"))
1652    (clobber (reg:CC 21))]
1653   ""
1654   "@
1655    not\\t%N1,%0
1656    not\\t%N1,%0"
1657    [(set_attr "type" "unarycc,unary")
1658     (set_attr "data" "not_uint16,not_uint16")])
1659
1660 ; movqi can use this for loading an integer that can't normally
1661 ; fit into a 16-bit signed integer.  The drawback is that it cannot
1662 ; go into R0-R11 since that will clobber the CC and movqi shouldn't
1663 ; do that.  This can cause additional reloading but in most cases
1664 ; this will cause only an additional register move.  With the large
1665 ; memory model we require an extra instruction to load DP anyway,
1666 ; if we're loading the constant from memory.  The big advantage of
1667 ; allowing constants that satisfy not_const_operand in movqi, is that
1668 ; it allows andn to be generated more often.
1669 ; However, there is a problem if GCC has decided that it wants
1670 ; to use R0-R11, since we won't have a matching pattern...
1671 ; In interim, we prevent immed_const allowing `N' constants.
1672 (define_insn "*one_cmplqi2_const_noclobber"
1673   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1674         (match_operand:QI 1 "not_const_operand" "N"))]
1675   ""
1676   "not\\t%N1,%0"
1677   [(set_attr "type" "unary")
1678    (set_attr "data" "not_uint16")])
1679
1680 ;
1681 ; ROL
1682 ;
1683 (define_expand "rotlqi3"
1684   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1685                    (rotate:QI (match_operand:QI 1 "reg_operand" "")
1686                               (match_operand:QI 2 "const_int_operand" "")))
1687               (clobber (reg:CC 21))])]
1688   ""
1689   "if (INTVAL (operands[2]) > 4)
1690      FAIL; /* Open code as two shifts and an or */
1691    if (INTVAL (operands[2]) > 1)
1692      {
1693         int i;
1694         rtx tmp;
1695
1696         /* If we have 4 or fewer shifts, then it is probably faster
1697            to emit separate ROL instructions.  A C3x requires
1698            at least 4 instructions (a C4x requires at least 3), to
1699            perform a rotation by shifts.  */
1700
1701         tmp = operands[1];
1702         for (i = 0; i < INTVAL (operands[2]) - 1; i++)
1703           {
1704             tmp = gen_reg_rtx (QImode);
1705             emit_insn (gen_rotl_1_clobber (tmp, operands[1]));
1706             operands[1] = tmp;
1707           }
1708         emit_insn (gen_rotl_1_clobber (operands[0], tmp));
1709         DONE;
1710      }")
1711
1712 (define_insn "rotl_1_clobber"
1713   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1714         (rotate:QI (match_operand:QI 1 "reg_operand" "0,0")
1715                    (const_int 1)))
1716    (clobber (reg:CC 21))]
1717   ""
1718   "rol\\t%0"
1719   [(set_attr "type" "unarycc,unary")])
1720 ; Default to int16 data attr.
1721
1722 ;
1723 ; ROR
1724 ;
1725 (define_expand "rotrqi3"
1726   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1727                    (rotatert:QI (match_operand:QI 1 "reg_operand" "")
1728                                 (match_operand:QI 2 "const_int_operand" "")))
1729               (clobber (reg:CC 21))])]
1730   ""
1731   "if (INTVAL (operands[2]) > 4)
1732      FAIL; /* Open code as two shifts and an or */
1733    if (INTVAL (operands[2]) > 1)
1734      {
1735         int i;
1736         rtx tmp;
1737  
1738         /* If we have 4 or fewer shifts, then it is probably faster
1739            to emit separate ROL instructions.  A C3x requires
1740            at least 4 instructions (a C4x requires at least 3), to
1741            perform a rotation by shifts.  */
1742  
1743         tmp = operands[1];
1744         for (i = 0; i < INTVAL (operands[2]) - 1; i++)
1745           {
1746             tmp = gen_reg_rtx (QImode);
1747             emit_insn (gen_rotr_1_clobber (tmp, operands[1]));
1748             operands[1] = tmp;
1749           }
1750         emit_insn (gen_rotr_1_clobber (operands[0], tmp));
1751         DONE;
1752      }")
1753
1754 (define_insn "rotr_1_clobber"
1755   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1756         (rotatert:QI (match_operand:QI 1 "reg_operand" "0,0")
1757                      (const_int 1)))
1758    (clobber (reg:CC 21))]
1759   ""
1760   "ror\\t%0"
1761   [(set_attr "type" "unarycc,unary")])
1762 ; Default to int16 data attr.
1763
1764
1765 ;
1766 ; THREE OPERAND INTEGER INSTRUCTIONS
1767 ;
1768
1769 ;
1770 ; ADDI
1771 ;
1772 ; This is used by reload when it calls gen_add2_insn for address arithmetic
1773 ; so we must emit the pattern that doesn't clobber CC.
1774 ;
1775 (define_expand "addqi3"
1776   [(parallel [(set (match_operand:QI 0 "std_or_reg_operand" "")
1777                    (plus:QI (match_operand:QI 1 "src_operand" "")
1778                             (match_operand:QI 2 "src_operand" "")))
1779               (clobber (reg:CC_NOOV 21))])]
1780   ""
1781   "legitimize_operands (PLUS, operands, QImode);
1782    if (reload_in_progress
1783        || (! IS_PSEUDO_REG (operands[0]) 
1784            && ! IS_EXT_REG (operands[0])))
1785    {
1786       emit_insn (gen_addqi3_noclobber (operands[0], operands[1], operands[2]));
1787       DONE;
1788    }")
1789
1790 (define_insn "*addqi3_clobber"
1791   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
1792         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
1793                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
1794    (clobber (reg:CC_NOOV 21))]
1795   "valid_operands (PLUS, operands, QImode)"
1796   "@
1797    addi\\t%2,%0
1798    addi3\\t%2,%1,%0
1799    addi3\\t%2,%1,%0
1800    addi\\t%2,%0
1801    addi3\\t%2,%1,%0
1802    addi3\\t%2,%1,%0"
1803   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
1804 ; Default to int16 data attr.
1805
1806 (define_split
1807   [(set (match_operand:QI 0 "std_reg_operand" "")
1808         (plus:QI (match_operand:QI 1 "src_operand" "")
1809                  (match_operand:QI 2 "src_operand" "")))
1810    (clobber (reg:CC_NOOV 21))]
1811   "reload_completed"
1812   [(set (match_dup 0)
1813         (plus:QI (match_dup 1)
1814                  (match_dup 2)))]
1815   "")
1816
1817 (define_insn "*addqi3_test"
1818   [(set (reg:CC_NOOV 21)
1819         (compare:CC_NOOV (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1820                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
1821                          (const_int 0)))
1822    (clobber (match_scratch:QI 0 "=d,d,d"))]
1823   "valid_operands (PLUS, operands, QImode)"
1824   "@
1825    addi\\t%2,%0
1826    addi3\\t%2,%1,%0
1827    addi3\\t%2,%1,%0"
1828   [(set_attr "type" "binarycc,binarycc,binarycc")])
1829 ; Default to int16 data attr.
1830
1831 ; gcc does this in combine.c we just reverse it here
1832 (define_insn "*cmp_neg"
1833   [(set (reg:CC_NOOV 21)
1834         (compare:CC_NOOV (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1835                          (neg: QI (match_operand:QI 2 "src_operand" "g,JR,rS<>"))))
1836    (clobber (match_scratch:QI 0 "=d,d,d"))]
1837   "valid_operands (PLUS, operands, QImode)"
1838   "@
1839    addi\\t%2,%0
1840    addi3\\t%2,%1,%0
1841    addi3\\t%2,%1,%0"
1842   [(set_attr "type" "binarycc,binarycc,binarycc")])
1843   
1844 (define_peephole
1845   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
1846                    (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1847                             (match_operand:QI 2 "src_operand" "g,JR,rS<>")))
1848               (clobber (reg:CC_NOOV 21))])
1849    (set (reg:CC_NOOV 21)
1850         (compare:CC_NOOV (match_dup 0) (const_int 0)))]
1851   "valid_operands (PLUS, operands, QImode)"
1852   "@
1853    addi\\t%2,%0
1854    addi3\\t%2,%1,%0
1855    addi3\\t%2,%1,%0"
1856   [(set_attr "type" "binarycc,binarycc,binarycc")])
1857
1858 (define_insn "*addqi3_set"
1859   [(set (reg:CC_NOOV 21)
1860         (compare:CC_NOOV (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1861                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
1862                          (const_int 0)))
1863    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
1864         (plus:QI (match_dup 1) (match_dup 2)))]
1865   "valid_operands (PLUS, operands, QImode)"
1866   "@
1867    addi\\t%2,%0
1868    addi3\\t%2,%1,%0
1869    addi3\\t%2,%1,%0"
1870   [(set_attr "type" "binarycc,binarycc,binarycc")])
1871 ; Default to int16 data attr.
1872
1873 ; This pattern is required primarily for manipulating the stack pointer
1874 ; where GCC doesn't expect CC to be clobbered or for calculating
1875 ; addresses during reload.
1876 (define_insn "addqi3_noclobber"
1877   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c")
1878         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1879                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))]
1880   "valid_operands (PLUS, operands, QImode)"
1881   "@
1882    addi\\t%2,%0
1883    addi3\\t%2,%1,%0
1884    addi3\\t%2,%1,%0"
1885   [(set_attr "type" "binary,binary,binary")])
1886 ; Default to int16 data attr.
1887
1888
1889 ; This pattern is required during reload when eliminate_regs_in_insn
1890 ; effectively converts a move insn into an add insn when the src
1891 ; operand is the frame pointer plus a constant.  Without this
1892 ; pattern, gen_addqi3 can be called with a register for operand0
1893 ; that can clobber CC.
1894 ; For example, we may have (set (mem (reg ar0)) (reg 99))
1895 ; with (set (reg 99) (plus (reg ar3) (const_int 8)))
1896 ; Now since ar3, the frame pointer, is unchanging within the function,
1897 ; (plus (reg ar3) (const_int 8)) is considered a constant.
1898 ; eliminate_regs_in_insn substitutes this constant to give
1899 ; (set (mem (reg ar0)) (plus (reg ar3) (const_int 8))).
1900 ; This is an invalid C4x insn but if we don't provide a pattern
1901 ; for it, it will be considered to be a move insn for reloading.
1902 (define_insn "*addqi3_noclobber_reload"
1903   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c")
1904         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1905                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))]
1906   "reload_in_progress"
1907   "@
1908    addi\\t%2,%0
1909    addi3\\t%2,%1,%0
1910    addi3\\t%2,%1,%0"
1911   [(set_attr "type" "binary,binary,binary")])
1912 ; Default to int16 data attr.
1913
1914
1915 (define_insn "*addqi3_carry_clobber"
1916   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
1917         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
1918                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
1919    (use (reg:CC_NOOV 21))
1920    (clobber (reg:CC_NOOV 21))]
1921   "valid_operands (PLUS, operands, QImode)"
1922   "@
1923    addc\\t%2,%0
1924    addc3\\t%2,%1,%0
1925    addc3\\t%2,%1,%0
1926    addc\\t%2,%0
1927    addc3\\t%2,%1,%0
1928    addc3\\t%2,%1,%0"
1929   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
1930 ; Default to int16 data attr.
1931
1932
1933 ;
1934 ; SUBI/SUBRI
1935 ;
1936 (define_expand "subqi3"
1937   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1938                    (minus:QI (match_operand:QI 1 "src_operand" "")
1939                              (match_operand:QI 2 "src_operand" "")))
1940               (clobber (reg:CC_NOOV 21))])]
1941   ""
1942   "legitimize_operands (MINUS, operands, QImode);")
1943
1944 (define_insn "*subqi3_clobber"
1945   [(set (match_operand:QI 0 "reg_operand" "=d,d,d,?d,c,c,c,?c")
1946         (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>,0,rIm,rR,rS<>")
1947                   (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>,rIm,0,JR,rS<>")))
1948    (clobber (reg:CC_NOOV 21))]
1949   "valid_operands (MINUS, operands, QImode)"
1950   "@
1951    subi\\t%2,%0
1952    subri\\t%1,%0
1953    subi3\\t%2,%1,%0
1954    subi3\\t%2,%1,%0
1955    subi\\t%2,%0
1956    subri\\t%1,%0
1957    subi3\\t%2,%1,%0
1958    subi3\\t%2,%1,%0"
1959   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc,binary,binary,binary,binary")])
1960 ; Default to int16 data attr.
1961
1962 (define_split
1963   [(set (match_operand:QI 0 "std_reg_operand" "")
1964         (minus:QI (match_operand:QI 1 "src_operand" "")
1965                   (match_operand:QI 2 "src_operand" "")))
1966    (clobber (reg:CC_NOOV 21))]
1967   "reload_completed"
1968   [(set (match_dup 0)
1969         (minus:QI (match_dup 1)
1970                  (match_dup 2)))]
1971   "")
1972
1973 (define_insn "*subqi3_test"
1974   [(set (reg:CC_NOOV 21)
1975         (compare:CC_NOOV (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
1976                                    (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>"))
1977                          (const_int 0)))
1978    (clobber (match_scratch:QI 0 "=d,d,d,?d"))]
1979   "valid_operands (MINUS, operands, QImode)"
1980   "@
1981    subi\\t%2,%0
1982    subri\\t%1,%0
1983    subi3\\t%2,%1,%0
1984    subi3\\t%2,%1,%0"
1985   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
1986 ; Default to int16 data attr.
1987
1988 (define_peephole
1989   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
1990                    (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
1991                              (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>")))
1992               (clobber (reg:CC_NOOV 21))])
1993    (set (reg:CC_NOOV 21)
1994         (compare:CC_NOOV (match_dup 0) (const_int 0)))]
1995   "valid_operands (MINUS, operands, QImode)"
1996   "@
1997    subi\\t%2,%0
1998    subri\\t%1,%0
1999    subi3\\t%2,%1,%0
2000    subi3\\t%2,%1,%0"
2001   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
2002   
2003 (define_insn "*subqi3_set"
2004   [(set (reg:CC_NOOV 21)
2005         (compare:CC_NOOV (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
2006                                    (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>"))
2007                          (const_int 0)))
2008    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2009         (minus:QI (match_dup 1)
2010                   (match_dup 2)))]
2011   "valid_operands (MINUS, operands, QImode)"
2012   "@
2013    subi\\t%2,%0
2014    subri\\t%1,%0
2015    subi3\\t%2,%1,%0
2016    subi3\\t%2,%1,%0"
2017   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
2018 ; Default to int16 data attr.
2019
2020 (define_insn "*subqi3_noclobber"
2021   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c,?c")
2022         (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
2023                   (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>")))]
2024   "valid_operands (MINUS, operands, QImode)"
2025   "@
2026    subi\\t%2,%0
2027    subri\\t%1,%0
2028    subi3\\t%2,%1,%0
2029    subi3\\t%2,%1,%0"
2030   [(set_attr "type" "binary,binary,binary,binary")])
2031 ; Default to int16 data attr.
2032
2033 (define_insn "*subqi3_carry_clobber"
2034   [(set (match_operand:QI 0 "reg_operand" "=d,d,d,?d,c,c,c,?c")
2035         (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>,0,rIm,rR,rS<>")
2036                   (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>,rIm,0,JR,rS<>")))
2037    (use (reg:CC_NOOV 21))
2038    (clobber (reg:CC_NOOV 21))]
2039   "valid_operands (MINUS, operands, QImode)"
2040   "@
2041    subb\\t%2,%0
2042    subrb\\t%1,%0
2043    subb3\\t%2,%1,%0
2044    subb3\\t%2,%1,%0
2045    subb\\t%2,%0
2046    subrb\\t%1,%0
2047    subb3\\t%2,%1,%0
2048    subb3\\t%2,%1,%0"
2049   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc,binary,binary,binary,binary")])
2050 ; Default to int16 data attr.
2051
2052 (define_insn "*subqi3_carry_set"
2053   [(set (reg:CC_NOOV 21)
2054         (compare:CC_NOOV (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
2055                                    (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>"))
2056                          (const_int 0)))
2057    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2058         (minus:QI (match_dup 1)
2059                   (match_dup 2)))
2060    (use (reg:CC_NOOV 21))]
2061   "valid_operands (MINUS, operands, QImode)"
2062   "@
2063    subb\\t%2,%0
2064    subrb\\t%1,%0
2065    subb3\\t%2,%1,%0
2066    subb3\\t%2,%1,%0"
2067   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
2068 ; Default to int16 data attr.
2069
2070 ;
2071 ; MPYI
2072 ;
2073 (define_expand "mulqi3"
2074   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2075                    (mult:QI (match_operand:QI 1 "src_operand" "")
2076                             (match_operand:QI 2 "src_operand" "")))
2077               (clobber (reg:CC_NOOV 21))])]
2078   ""
2079   "if (TARGET_MPYI || (GET_CODE (operands[2]) == CONST_INT
2080        && exact_log2 (INTVAL (operands[2])) >= 0))
2081      legitimize_operands (MULT, operands, QImode);
2082    else
2083      {        
2084        if (GET_CODE (operands[2]) == CONST_INT)
2085          {
2086           /* Let GCC try to synthesize the multiplication using shifts
2087              and adds.  In most cases this will be more profitable than
2088              using the C3x MPYI.  */
2089             FAIL;
2090          }
2091        if (operands[1] == operands[2])
2092          {
2093             /* Do the squaring operation in-line.  */
2094             emit_insn (gen_sqrqi2_inline (operands[0], operands[1]));
2095             DONE;
2096          }
2097        if (TARGET_INLINE)
2098          {
2099             emit_insn (gen_mulqi3_inline (operands[0], operands[1],
2100                                           operands[2]));
2101             DONE;
2102          }
2103        c4x_emit_libcall3 (smul_optab->handlers[(int) QImode].libfunc,
2104                           MULT, QImode, operands);
2105        DONE;
2106      }
2107   ")
2108
2109 (define_insn "*mulqi3_clobber"
2110   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2111         (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2112                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2113    (clobber (reg:CC_NOOV 21))]
2114   "valid_operands (MULT, operands, QImode)"
2115   "*
2116   if (which_alternative == 0 || which_alternative == 3)
2117     {
2118       if (TARGET_C3X
2119           && GET_CODE (operands[2]) == CONST_INT
2120           && exact_log2 (INTVAL (operands[2])) >= 0)
2121         return \"ash\\t%L2,%0\";
2122       else
2123         return \"mpyi\\t%2,%0\";
2124     }
2125   else
2126       return \"mpyi3\\t%2,%1,%0\";"
2127   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2128 ; Default to int16 data attr.
2129
2130 (define_insn "*mulqi3_test"
2131   [(set (reg:CC_NOOV 21)
2132         (compare:CC_NOOV (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2133                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2134                          (const_int 0)))
2135    (clobber (match_scratch:QI 0 "=d,d,d"))]
2136   "valid_operands (MULT, operands, QImode)"
2137   "*
2138   if (which_alternative == 0)
2139     {
2140       if (TARGET_C3X 
2141           && GET_CODE (operands[2]) == CONST_INT
2142           && exact_log2 (INTVAL (operands[2])) >= 0)
2143         return \"ash\\t%L2,%0\";
2144       else
2145         return \"mpyi\\t%2,%0\";
2146     } 
2147   else
2148       return \"mpyi3\\t%2,%1,%0\";"
2149   [(set_attr "type" "binarycc,binarycc,binarycc")])
2150 ; Default to int16 data attr.
2151
2152 (define_insn "*mulqi3_set"
2153   [(set (reg:CC_NOOV 21)
2154         (compare:CC_NOOV (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2155                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2156                          (const_int 0)))
2157    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2158         (mult:QI (match_dup 1)
2159                  (match_dup 2)))]
2160   "valid_operands (MULT, operands, QImode)"
2161   "*
2162   if (which_alternative == 0)
2163     {
2164       if (TARGET_C3X 
2165           && GET_CODE (operands[2]) == CONST_INT
2166           && exact_log2 (INTVAL (operands[2])) >= 0)
2167         return \"ash\\t%L2,%0\";
2168       else
2169         return \"mpyi\\t%2,%0\";
2170     }
2171     else
2172         return \"mpyi3\\t%2,%1,%0\";"
2173   [(set_attr "type" "binarycc,binarycc,binarycc")])
2174 ; Default to int16 data attr.
2175
2176 ; The C3x multiply instruction assumes 24-bit signed integer operands
2177 ; and the 48-bit result is truncated to 32-bits.
2178 (define_insn "mulqi3_24_clobber"
2179   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2180         (mult:QI
2181          (sign_extend:QI
2182           (and:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2183                   (const_int 16777215)))
2184          (sign_extend:QI
2185           (and:QI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")
2186                   (const_int 16777215)))))
2187    (clobber (reg:CC_NOOV 21))]
2188   "TARGET_C3X && valid_operands (MULT, operands, QImode)"
2189   "@
2190    mpyi\\t%2,%0
2191    mpyi3\\t%2,%1,%0
2192    mpyi3\\t%2,%1,%0
2193    mpyi\\t%2,%0
2194    mpyi3\\t%2,%1,%0
2195    mpyi3\\t%2,%1,%0"
2196   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2197 ; Default to int16 data attr.
2198
2199
2200 ; Fast square function for C3x where TARGET_MPYI not asserted
2201 (define_expand "sqrqi2_inline"
2202   [(set (match_dup 7) (match_operand:QI 1 "src_operand" ""))
2203    (parallel [(set (match_dup 3)
2204                    (lshiftrt:QI (match_dup 7) (const_int 16)))
2205               (clobber (reg:CC 21))])
2206    (parallel [(set (match_dup 2)
2207                    (and:QI (match_dup 7) (const_int 65535)))
2208               (clobber (reg:CC 21))])
2209    (parallel [(set (match_dup 4)
2210                    (mult:QI (sign_extend:QI (and:QI (match_dup 2) 
2211                                                     (const_int 16777215)))
2212                             (sign_extend:QI (and:QI (match_dup 2) 
2213                                                     (const_int 16777215)))))
2214               (clobber (reg:CC_NOOV 21))])
2215    (parallel [(set (match_dup 5)
2216                    (mult:QI (sign_extend:QI (and:QI (match_dup 2) 
2217                                                     (const_int 16777215)))
2218                             (sign_extend:QI (and:QI (match_dup 3) 
2219                                                     (const_int 16777215)))))
2220               (clobber (reg:CC_NOOV 21))])
2221    (parallel [(set (match_dup 6)
2222                    (ashift:QI (match_dup 5) (const_int 17)))
2223               (clobber (reg:CC 21))])
2224    (parallel [(set (match_operand:QI 0 "reg_operand" "")
2225                    (plus:QI (match_dup 4) (match_dup 6)))
2226               (clobber (reg:CC_NOOV 21))])]
2227   ""
2228   "
2229   operands[2] = gen_reg_rtx (QImode); /* a = val & 0xffff */
2230   operands[3] = gen_reg_rtx (QImode); /* b = val >> 16 */
2231   operands[4] = gen_reg_rtx (QImode); /* a * a */
2232   operands[5] = gen_reg_rtx (QImode); /* a * b */
2233   operands[6] = gen_reg_rtx (QImode); /* (a * b) << 17 */
2234   operands[7] = gen_reg_rtx (QImode); /* val */
2235   ")
2236
2237 ; Inlined integer multiply for C3x
2238 (define_expand "mulqi3_inline"
2239   [(set (match_dup 12) (const_int -16))
2240    (set (match_dup 13) (match_operand:QI 1 "src_operand" ""))
2241    (set (match_dup 14) (match_operand:QI 2 "src_operand" ""))
2242    (parallel [(set (match_dup 4)
2243                    (lshiftrt:QI (match_dup 13) (neg:QI (match_dup 12))))
2244               (clobber (reg:CC 21))])
2245    (parallel [(set (match_dup 6)
2246                    (lshiftrt:QI (match_dup 14) (neg:QI (match_dup 12))))
2247               (clobber (reg:CC 21))])
2248    (parallel [(set (match_dup 3)
2249                    (and:QI (match_dup 13)
2250                            (const_int 65535)))
2251               (clobber (reg:CC 21))])
2252    (parallel [(set (match_dup 5)
2253                    (and:QI (match_dup 14) 
2254                            (const_int 65535)))
2255               (clobber (reg:CC 21))])
2256    (parallel [(set (match_dup 7)
2257                    (mult:QI (sign_extend:QI (and:QI (match_dup 4) 
2258                                                     (const_int 16777215)))
2259                             (sign_extend:QI (and:QI (match_dup 5) 
2260                                                     (const_int 16777215)))))
2261               (clobber (reg:CC_NOOV 21))])
2262    (parallel [(set (match_dup 8)
2263                    (mult:QI (sign_extend:QI (and:QI (match_dup 3) 
2264                                                     (const_int 16777215)))
2265                             (sign_extend:QI (and:QI (match_dup 5) 
2266                                                     (const_int 16777215)))))
2267               (clobber (reg:CC_NOOV 21))])
2268    (parallel [(set (match_dup 9)
2269                    (mult:QI (sign_extend:QI (and:QI (match_dup 3) 
2270                                                     (const_int 16777215)))
2271                             (sign_extend:QI (and:QI (match_dup 6) 
2272                                                     (const_int 16777215)))))
2273               (clobber (reg:CC_NOOV 21))])
2274    (parallel [(set (match_dup 10)
2275                    (plus:QI (match_dup 7) (match_dup 9)))
2276               (clobber (reg:CC_NOOV 21))])
2277    (parallel [(set (match_dup 11)
2278                    (ashift:QI (match_dup 10) (const_int 16)))
2279               (clobber (reg:CC 21))])
2280    (parallel [(set (match_operand:QI 0 "reg_operand" "")
2281                    (plus:QI (match_dup 8) (match_dup 11)))
2282               (clobber (reg:CC_NOOV 21))])]
2283   "TARGET_C3X"
2284   "
2285   operands[3] = gen_reg_rtx (QImode); /* a = arg1 & 0xffff */
2286   operands[4] = gen_reg_rtx (QImode); /* b = arg1 >> 16 */
2287   operands[5] = gen_reg_rtx (QImode); /* a = arg2 & 0xffff */
2288   operands[6] = gen_reg_rtx (QImode); /* b = arg2 >> 16 */
2289   operands[7] = gen_reg_rtx (QImode); /* b * c */
2290   operands[8] = gen_reg_rtx (QImode); /* a * c */
2291   operands[9] = gen_reg_rtx (QImode); /* a * d */
2292   operands[10] = gen_reg_rtx (QImode); /* b * c + a * d */
2293   operands[11] = gen_reg_rtx (QImode); /* (b *c + a * d) << 16 */
2294   operands[12] = gen_reg_rtx (QImode); /* -16 */
2295   operands[13] = gen_reg_rtx (QImode); /* arg1 */
2296   operands[14] = gen_reg_rtx (QImode); /* arg2 */
2297   ")
2298
2299 ;
2300 ; MPYSHI (C4x only)
2301 ;
2302 (define_expand "smulqi3_highpart"
2303   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2304                    (truncate:QI
2305                     (lshiftrt:HI
2306                      (mult:HI
2307                       (sign_extend:HI (match_operand:QI 1 "src_operand" ""))
2308                       (sign_extend:HI (match_operand:QI 2 "src_operand" "")))
2309                  (const_int 32))))
2310               (clobber (reg:CC_NOOV 21))])]
2311  ""
2312  "legitimize_operands (MULT, operands, QImode);
2313   if (TARGET_C3X)
2314     {
2315        c4x_emit_libcall_mulhi (smulhi3_libfunc, SIGN_EXTEND, QImode, operands);
2316        DONE;
2317     }
2318  ")
2319
2320 (define_insn "*smulqi3_highpart_clobber"
2321   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2322         (truncate:QI 
2323          (lshiftrt:HI
2324           (mult:HI
2325            (sign_extend:HI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>"))
2326            (sign_extend:HI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2327       (const_int 32))))
2328    (clobber (reg:CC_NOOV 21))]
2329   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2330   "@
2331    mpyshi\\t%2,%0
2332    mpyshi3\\t%2,%1,%0
2333    mpyshi3\\t%2,%1,%0
2334    mpyshi\\t%2,%0
2335    mpyshi3\\t%2,%1,%0
2336    mpyshi3\\t%2,%1,%0"
2337   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2338    (set_attr "data" "int16,int16,int16,int16,int16,int16")])
2339
2340 (define_insn "*smulqi3_highpart_noclobber"
2341   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2342         (truncate:QI 
2343          (lshiftrt:HI
2344           (mult:HI
2345            (sign_extend:HI (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2346            (sign_extend:HI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))
2347       (const_int 32))))]
2348   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2349   "@
2350    mpyshi\\t%2,%0
2351    mpyshi3\\t%2,%1,%0
2352    mpyshi3\\t%2,%1,%0"
2353   [(set_attr "type" "binary,binary,binary")
2354    (set_attr "data" "int16,int16,int16")])
2355
2356 ;
2357 ; MPYUHI (C4x only)
2358 ;
2359 (define_expand "umulqi3_highpart"
2360   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2361                (truncate:QI
2362                 (lshiftrt:HI
2363                  (mult:HI
2364                   (zero_extend:HI (match_operand:QI 1
2365                                    "nonimmediate_src_operand" ""))
2366                   (zero_extend:HI (match_operand:QI 2
2367                                    "nonimmediate_lsrc_operand" "")))
2368                  (const_int 32))))
2369               (clobber (reg:CC_NOOV 21))])]
2370  ""
2371  "legitimize_operands (MULT, operands, QImode);
2372   if (TARGET_C3X) 
2373     {
2374       c4x_emit_libcall_mulhi (umulhi3_libfunc, ZERO_EXTEND, QImode, operands);
2375       DONE;
2376     }
2377  ")
2378
2379 (define_insn "*umulqi3_highpart_clobber"
2380   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2381         (truncate:QI
2382          (lshiftrt:HI
2383           (mult:HI 
2384            (zero_extend:HI (match_operand:QI 1
2385                             "nonimmediate_src_operand" "%0,rR,rS<>,0,rR,rS<>"))
2386            (zero_extend:HI (match_operand:QI 2
2387                             "nonimmediate_lsrc_operand" "rm,R,rS<>,rm,R,rS<>")))
2388           (const_int 32))))
2389    (clobber (reg:CC_NOOV 21))]
2390   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2391   "@
2392    mpyuhi\\t%2,%0
2393    mpyuhi3\\t%2,%1,%0
2394    mpyuhi3\\t%2,%1,%0
2395    mpyuhi\\t%2,%0
2396    mpyuhi3\\t%2,%1,%0
2397    mpyuhi3\\t%2,%1,%0"
2398   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2399    (set_attr "data" "uint16,uint16,uint16,uint16,uint16,uint16")])
2400
2401 (define_insn "*umulqi3_highpart_noclobber"
2402   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2403         (truncate:QI
2404          (lshiftrt:HI
2405           (mult:HI 
2406            (zero_extend:HI (match_operand:QI 1
2407                             "nonimmediate_src_operand" "0,rR,rS<>"))
2408            (zero_extend:HI (match_operand:QI 2
2409                             "nonimmediate_lsrc_operand" "rm,R,rS<>")))
2410           (const_int 32))))]
2411   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2412   "@
2413    mpyuhi\\t%2,%0
2414    mpyuhi3\\t%2,%1,%0
2415    mpyuhi3\\t%2,%1,%0"
2416   [(set_attr "type" "binary,binary,binary")
2417    (set_attr "data" "uint16,uint16,uint16")])
2418
2419 ;
2420 ; AND
2421 ;
2422 (define_expand "andqi3"
2423   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2424                    (and:QI (match_operand:QI 1 "src_operand" "")
2425                            (match_operand:QI 2 "tsrc_operand" "")))
2426               (clobber (reg:CC 21))])]
2427  ""
2428  "legitimize_operands (AND, operands, QImode);")
2429
2430
2431 (define_insn "*andqi3_255_clobber"
2432   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2433         (and:QI (match_operand:QI 1 "src_operand" "mr,mr")
2434                 (const_int 255)))
2435    (clobber (reg:CC 21))]
2436  "! TARGET_C3X"
2437  "lbu0\\t%1,%0"
2438   [(set_attr "type" "unarycc,unary")])
2439
2440 (define_insn "*andqi3_255_noclobber"
2441   [(set (match_operand:QI 0 "reg_operand" "=c")
2442         (and:QI (match_operand:QI 1 "src_operand" "mr")
2443                 (const_int 255)))]
2444  "! TARGET_C3X"
2445  "lbu0\\t%1,%0"
2446   [(set_attr "type" "unary")])
2447
2448
2449 (define_insn "*andqi3_65535_clobber"
2450   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2451         (and:QI (match_operand:QI 1 "src_operand" "mr,mr")
2452                 (const_int 65535)))
2453    (clobber (reg:CC 21))]
2454  "! TARGET_C3X"
2455  "lhu0\\t%1,%0"
2456   [(set_attr "type" "unarycc,unary")])
2457
2458 (define_insn "*andqi3_65535_noclobber"
2459   [(set (match_operand:QI 0 "reg_operand" "=c")
2460         (and:QI (match_operand:QI 1 "src_operand" "mr")
2461                 (const_int 65535)))]
2462  "! TARGET_C3X"
2463  "lhu0\\t%1,%0"
2464   [(set_attr "type" "unary")])
2465
2466 (define_insn "*andqi3_clobber"
2467   [(set (match_operand:QI 0 "reg_operand" "=d,d,d,?d,c,c,c,?c")
2468         (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>,0,0,rR,rS<>")
2469                 (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>,N,rLm,JR,rS<>")))
2470    (clobber (reg:CC 21))]
2471   "valid_operands (AND, operands, QImode)"
2472   "@
2473    andn\\t%N2,%0
2474    and\\t%2,%0
2475    and3\\t%2,%1,%0
2476    and3\\t%2,%1,%0
2477    andn\\t%N2,%0
2478    and\\t%2,%0
2479    and3\\t%2,%1,%0
2480    and3\\t%2,%1,%0"
2481   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc,binary,binary,binary,binary")
2482    (set_attr "data" "not_uint16,uint16,int16,uint16,not_uint16,uint16,int16,uint16")])
2483
2484 (define_insn "*andqi3_noclobber"
2485   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c,?c")
2486         (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2487                 (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>")))]
2488   "valid_operands (AND, operands, QImode)"
2489   "@
2490    andn\\t%N2,%0
2491    and\\t%2,%0
2492    and3\\t%2,%1,%0
2493    and3\\t%2,%1,%0"
2494   [(set_attr "type" "binary,binary,binary,binary")
2495    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2496
2497 (define_insn "andn_st"
2498   [(set (unspec:QI [(reg:QI 21)] 20)
2499         (and:QI (unspec:QI [(reg:QI 21)] UNSPEC_ANDN_ST)
2500                 (match_operand:QI 0 "" "N")))
2501    (use (match_dup 0))
2502    (use (reg:CC 21))
2503    (clobber (reg:CC 21))]
2504   ""
2505   "andn\\t%N0,st"
2506   [(set_attr "type" "misc")
2507    (set_attr "data" "not_uint16")])
2508
2509 (define_split
2510   [(set (match_operand:QI 0 "std_reg_operand" "")
2511         (and:QI (match_operand:QI 1 "src_operand" "")
2512                 (match_operand:QI 2 "tsrc_operand" "")))
2513    (clobber (reg:CC 21))]
2514   "reload_completed"
2515   [(set (match_dup 0)
2516         (and:QI (match_dup 1)
2517                 (match_dup 2)))]
2518   "")
2519
2520 (define_insn "*andqi3_test"
2521   [(set (reg:CC 21)
2522         (compare:CC (and:QI (match_operand:QI 1 "src_operand" "%0,r,rR,rS<>")
2523                             (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>"))
2524                     (const_int 0)))
2525    (clobber (match_scratch:QI 0 "=d,X,X,?X"))]
2526   "valid_operands (AND, operands, QImode)"
2527   "@
2528    andn\\t%N2,%0
2529    tstb\\t%2,%1
2530    tstb3\\t%2,%1
2531    tstb3\\t%2,%1"
2532   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2533    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2534
2535 (define_peephole
2536   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2537                    (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2538                            (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>")))
2539               (clobber (reg:CC 21))])
2540    (set (reg:CC 21)
2541         (compare:CC (match_dup 0) (const_int 0)))]
2542   "valid_operands (AND, operands, QImode)"
2543   "@
2544    andn\\t%N2,%0
2545    and\\t%2,%0
2546    and3\\t%2,%1,%0
2547    and3\\t%2,%1,%0"
2548   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2549    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2550   
2551 (define_insn "*andqi3_set"
2552   [(set (reg:CC 21)
2553         (compare:CC (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2554                             (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>"))
2555                     (const_int 0)))
2556    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2557         (and:QI (match_dup 1)
2558                 (match_dup 2)))]
2559   "valid_operands (AND, operands, QImode)"
2560   "@
2561    andn\\t%N2,%0
2562    and\\t%2,%0
2563    and3\\t%2,%1,%0
2564    and3\\t%2,%1,%0"
2565   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2566    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2567
2568 ;
2569 ; ANDN
2570 ;
2571 ; NB, this insn doesn't have commutative operands, but valid_operands
2572 ; assumes that the code AND does.  We might have to kludge this if
2573 ; we make valid_operands stricter.
2574 (define_insn "*andnqi3_clobber"
2575   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2576         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>"))
2577                 (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")))
2578    (clobber (reg:CC 21))]
2579   "valid_operands (AND, operands, QImode)"
2580   "@
2581    andn\\t%2,%0
2582    andn3\\t%2,%1,%0
2583    andn3\\t%2,%1,%0
2584    andn\\t%2,%0
2585    andn3\\t%2,%1,%0
2586    andn3\\t%2,%1,%0"
2587   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2588    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2589
2590 (define_insn "*andnqi3_noclobber"
2591   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2592         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2593                 (match_operand:QI 1 "src_operand" "0,rR,rS<>")))]
2594   "valid_operands (AND, operands, QImode)"
2595   "@
2596    andn\\t%2,%0
2597    andn3\\t%2,%1,%0
2598    andn3\\t%2,%1,%0"
2599   [(set_attr "type" "binary,binary,binary")
2600    (set_attr "data" "uint16,int16,uint16")])
2601
2602 (define_split
2603   [(set (match_operand:QI 0 "std_reg_operand" "")
2604         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" ""))
2605                 (match_operand:QI 1 "src_operand" "")))
2606    (clobber (reg:CC 21))]
2607   "reload_completed"
2608   [(set (match_dup 0)
2609         (and:QI (not:QI (match_dup 2))
2610                 (match_dup 1)))]
2611   "")
2612
2613 (define_insn "*andnqi3_test"
2614   [(set (reg:CC 21)
2615         (compare:CC (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2616                             (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2617                     (const_int 0)))
2618    (clobber (match_scratch:QI 0 "=d,d,d"))]
2619   "valid_operands (AND, operands, QImode)"
2620   "@
2621    andn\\t%2,%0
2622    andn3\\t%2,%1,%0
2623    andn3\\t%2,%1,%0"
2624   [(set_attr "type" "binarycc,binarycc,binarycc")
2625    (set_attr "data" "uint16,int16,uint16")])
2626
2627 (define_insn "*andnqi3_set"
2628   [(set (reg:CC 21)
2629         (compare:CC (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2630                             (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2631                     (const_int 0)))
2632    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2633         (and:QI (not:QI (match_dup 2))
2634                 (match_dup 1)))]
2635   "valid_operands (AND, operands, QImode)"
2636   "@
2637    andn\\t%2,%0
2638    andn3\\t%2,%1,%0
2639    andn3\\t%2,%1,%0"
2640   [(set_attr "type" "binarycc,binarycc,binarycc")
2641    (set_attr "data" "uint16,int16,uint16")])
2642
2643 ;
2644 ; OR
2645 ;
2646 (define_expand "iorqi3"
2647   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2648                    (ior:QI (match_operand:QI 1 "src_operand" "")
2649                            (match_operand:QI 2 "lsrc_operand" "")))
2650               (clobber (reg:CC 21))])]
2651  ""
2652  "legitimize_operands (IOR, operands, QImode);")
2653
2654 (define_insn "*iorqi3_clobber"
2655   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2656         (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2657                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2658    (clobber (reg:CC 21))]
2659   "valid_operands (IOR, operands, QImode)"
2660   "@
2661    or\\t%2,%0
2662    or3\\t%2,%1,%0
2663    or3\\t%2,%1,%0
2664    or\\t%2,%0
2665    or3\\t%2,%1,%0
2666    or3\\t%2,%1,%0"
2667   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2668    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2669
2670 (define_split
2671   [(set (match_operand:QI 0 "std_reg_operand" "")
2672         (ior:QI (match_operand:QI 1 "src_operand" "")
2673                 (match_operand:QI 2 "lsrc_operand" "")))
2674    (clobber (reg:CC 21))]
2675   "reload_completed"
2676   [(set (match_dup 0)
2677         (ior:QI (match_dup 1)
2678                 (match_dup 2)))]
2679   "")
2680
2681 (define_insn "*iorqi3_test"
2682   [(set (reg:CC 21)
2683         (compare:CC (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2684                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2685                     (const_int 0)))
2686    (clobber (match_scratch:QI 0 "=d,d,d"))]
2687   "valid_operands (IOR, operands, QImode)"
2688   "@
2689    or\\t%2,%0
2690    or3\\t%2,%1,%0
2691    or3\\t%2,%1,%0"
2692   [(set_attr "type" "binarycc,binarycc,binarycc")
2693    (set_attr "data" "uint16,int16,uint16")])
2694
2695 (define_peephole
2696   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2697                    (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2698                            (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))
2699               (clobber (reg:CC 21))])
2700    (set (reg:CC 21)
2701         (compare:CC (match_dup 0) (const_int 0)))]
2702   "valid_operands (IOR, operands, QImode)"
2703   "@
2704    or\\t%2,%0
2705    or3\\t%2,%1,%0
2706    or3\\t%2,%1,%0"
2707   [(set_attr "type" "binarycc,binarycc,binarycc")
2708    (set_attr "data" "uint16,int16,uint16")])
2709   
2710 (define_insn "*iorqi3_set"
2711   [(set (reg:CC 21)
2712         (compare:CC (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2713                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2714                     (const_int 0)))
2715    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2716         (ior:QI (match_dup 1)
2717                 (match_dup 2)))]
2718   "valid_operands (IOR, operands, QImode)"
2719   "@
2720    or\\t%2,%0
2721    or3\\t%2,%1,%0
2722    or3\\t%2,%1,%0"
2723   [(set_attr "type" "binarycc,binarycc,binarycc")
2724    (set_attr "data" "uint16,int16,uint16")])
2725
2726 ; This pattern is used for loading symbol references in several parts. 
2727 (define_insn "iorqi3_noclobber"
2728   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c")
2729         (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2730                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))]
2731   "valid_operands (IOR, operands, QImode)"
2732   "@
2733    or\\t%2,%0
2734    or3\\t%2,%1,%0
2735    or3\\t%2,%1,%0"
2736   [(set_attr "type" "binary,binary,binary")
2737    (set_attr "data" "uint16,int16,uint16")])
2738
2739 ;
2740 ; XOR
2741 ;
2742 (define_expand "xorqi3"
2743   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2744                    (xor:QI (match_operand:QI 1 "src_operand" "")
2745                            (match_operand:QI 2 "lsrc_operand" "")))
2746               (clobber (reg:CC 21))])]
2747  ""
2748  "legitimize_operands (XOR, operands, QImode);")
2749
2750 (define_insn "*xorqi3_clobber"
2751   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2752         (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2753                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2754    (clobber (reg:CC 21))]
2755   "valid_operands (XOR, operands, QImode)"
2756   "@
2757    xor\\t%2,%0
2758    xor3\\t%2,%1,%0
2759    xor3\\t%2,%1,%0
2760    xor\\t%2,%0
2761    xor3\\t%2,%1,%0
2762    xor3\\t%2,%1,%0"
2763   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2764    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2765
2766 (define_insn "*xorqi3_noclobber"
2767   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2768         (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2769                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))]
2770   "valid_operands (XOR, operands, QImode)"
2771   "@
2772    xor\\t%2,%0
2773    xor3\\t%2,%1,%0
2774    xor3\\t%2,%1,%0"
2775   [(set_attr "type" "binary,binary,binary")
2776    (set_attr "data" "uint16,int16,uint16")])
2777
2778 (define_split
2779   [(set (match_operand:QI 0 "std_reg_operand" "")
2780         (xor:QI (match_operand:QI 1 "src_operand" "")
2781                 (match_operand:QI 2 "lsrc_operand" "")))
2782    (clobber (reg:CC 21))]
2783   "reload_completed"
2784   [(set (match_dup 0)
2785         (xor:QI (match_dup 1)
2786                 (match_dup 2)))]
2787   "")
2788
2789 (define_insn "*xorqi3_test"
2790   [(set (reg:CC 21)
2791         (compare:CC (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2792                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2793                     (const_int 0)))
2794    (clobber (match_scratch:QI 0 "=d,d,d"))]
2795   "valid_operands (XOR, operands, QImode)"
2796   "@
2797    xor\\t%2,%0
2798    xor3\\t%2,%1,%0
2799    xor3\\t%2,%1,%0"
2800   [(set_attr "type" "binarycc,binarycc,binarycc")
2801    (set_attr "data" "uint16,int16,uint16")])
2802
2803 (define_insn "*xorqi3_set"
2804   [(set (reg:CC 21)
2805         (compare:CC (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2806                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2807                     (const_int 0)))
2808    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2809         (xor:QI (match_dup 1)
2810                 (match_dup 2)))]
2811   "valid_operands (XOR, operands, QImode)"
2812   "@
2813    xor\\t%2,%0
2814    xor3\\t%2,%1,%0
2815    xor3\\t%2,%1,%0"
2816   [(set_attr "type" "binarycc,binarycc,binarycc")
2817    (set_attr "data" "uint16,int16,uint16")])
2818
2819 ;
2820 ; LSH/ASH (left)
2821 ;
2822 ; The C3x and C4x have two shift instructions ASH and LSH
2823 ; If the shift count is positive, a left shift is performed
2824 ; otherwise a right shift is performed.  The number of bits
2825 ; shifted is determined by the seven LSBs of the shift count.
2826 ; If the absolute value of the count is 32 or greater, the result
2827 ; using the LSH instruction is zero; with the ASH insn the result
2828 ; is zero or negative 1.   Note that the ISO C standard allows 
2829 ; the result to be machine dependent whenever the shift count
2830 ; exceeds the size of the object.
2831 (define_expand "ashlqi3"
2832   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2833                    (ashift:QI (match_operand:QI 1 "src_operand" "")
2834                               (match_operand:QI 2 "src_operand" "")))
2835               (clobber (reg:CC 21))])]
2836  ""
2837  "legitimize_operands (ASHIFT, operands, QImode);")
2838
2839 (define_insn "*ashlqi3_clobber"
2840   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2841         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2842                    (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2843    (clobber (reg:CC 21))]
2844   "valid_operands (ASHIFT, operands, QImode)"
2845   "@
2846    ash\\t%2,%0
2847    ash3\\t%2,%1,%0
2848    ash3\\t%2,%1,%0
2849    ash\\t%2,%0
2850    ash3\\t%2,%1,%0
2851    ash3\\t%2,%1,%0"
2852   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2853 ; Default to int16 data attr.
2854
2855 (define_insn "*ashlqi3_set"
2856   [(set (reg:CC 21)
2857         (compare:CC
2858           (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2859                      (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2860           (const_int 0)))
2861    (set (match_operand:QI 0 "reg_operand" "=d,d,d")
2862         (ashift:QI (match_dup 1)
2863                    (match_dup 2)))]
2864   "valid_operands (ASHIFT, operands, QImode)"
2865   "@
2866    ash\\t%2,%0
2867    ash3\\t%2,%1,%0
2868    ash3\\t%2,%1,%0"
2869   [(set_attr "type" "binarycc,binarycc,binarycc")])
2870 ; Default to int16 data attr.
2871
2872 (define_insn "ashlqi3_noclobber"
2873   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2874         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2875                    (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))]
2876   "valid_operands (ASHIFT, operands, QImode)"
2877   "@
2878    ash\\t%2,%0
2879    ash3\\t%2,%1,%0
2880    ash3\\t%2,%1,%0"
2881   [(set_attr "type" "binary,binary,binary")])
2882 ; Default to int16 data attr.
2883
2884 (define_split
2885   [(set (match_operand:QI 0 "std_reg_operand" "")
2886         (ashift:QI (match_operand:QI 1 "src_operand" "")
2887                    (match_operand:QI 2 "src_operand" "")))
2888    (clobber (reg:CC 21))]
2889   "reload_completed"
2890   [(set (match_dup 0)
2891         (ashift:QI (match_dup 1)
2892                    (match_dup 2)))]
2893   "")
2894
2895 ; This is only used by lshrhi3_reg where we need a LSH insn that will
2896 ; shift both ways.
2897 (define_insn "*lshlqi3_clobber"
2898   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2899         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2900                    (unspec:QI [(match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")] UNSPEC_LSH)))
2901    (clobber (reg:CC 21))]
2902   "valid_operands (ASHIFT, operands, QImode)"
2903   "@
2904    lsh\\t%2,%0
2905    lsh3\\t%2,%1,%0
2906    lsh3\\t%2,%1,%0
2907    lsh\\t%2,%0
2908    lsh3\\t%2,%1,%0
2909    lsh3\\t%2,%1,%0"
2910   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2911 ; Default to int16 data attr.
2912
2913 ;
2914 ; LSH (right)
2915 ;
2916 ; Logical right shift on the C[34]x works by negating the shift count,
2917 ; then emitting a right shift with the shift count negated.  This means
2918 ; that all actual shift counts in the RTL will be positive.
2919 ;
2920 (define_expand "lshrqi3"
2921   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2922                    (lshiftrt:QI (match_operand:QI 1 "src_operand" "")
2923                                 (match_operand:QI 2 "src_operand" "")))
2924               (clobber (reg:CC 21))])]
2925   ""
2926   "legitimize_operands (LSHIFTRT, operands, QImode);")
2927
2928
2929 (define_insn "*lshrqi3_24_clobber"
2930   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2931         (lshiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2932                      (const_int 24)))
2933    (clobber (reg:CC 21))]
2934   "! TARGET_C3X"
2935   "lbu3\\t%1,%0"
2936   [(set_attr "type" "unarycc")])
2937
2938
2939 (define_insn "*ashrqi3_24_clobber"
2940   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2941         (ashiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2942                      (const_int 24)))
2943    (clobber (reg:CC 21))]
2944   "! TARGET_C3X"
2945   "lb3\\t%1,%0"
2946   [(set_attr "type" "unarycc")])
2947
2948
2949 (define_insn "lshrqi3_16_clobber"
2950   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2951         (lshiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2952                      (const_int 16)))
2953    (clobber (reg:CC 21))]
2954   "! TARGET_C3X"
2955   "lhu1\\t%1,%0"
2956   [(set_attr "type" "unarycc")])
2957
2958
2959 (define_insn "*ashrqi3_16_clobber"
2960   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2961         (ashiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2962                      (const_int 16)))
2963    (clobber (reg:CC 21))]
2964   "! TARGET_C3X"
2965   "lh1\\t%1,%0"
2966   [(set_attr "type" "unarycc")])
2967
2968
2969 ; When the shift count is greater than the size of the word
2970 ; the result can be implementation specific
2971 (define_insn "*lshrqi3_const_clobber"
2972   [(set (match_operand:QI 0 "reg_operand" "=d,c,?d,?c")
2973         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,0,r,r")
2974                      (match_operand:QI 2 "const_int_operand" "n,n,J,J")))
2975    (clobber (reg:CC 21))]
2976   "valid_operands (LSHIFTRT, operands, QImode)"
2977   "@
2978    lsh\\t%n2,%0
2979    lsh\\t%n2,%0
2980    lsh3\\t%n2,%1,%0
2981    lsh3\\t%n2,%1,%0"
2982   [(set_attr "type" "binarycc,binary,binarycc,binary")])
2983
2984 (define_insn "*lshrqi3_const_noclobber"
2985   [(set (match_operand:QI 0 "std_reg_operand" "=c,?c")
2986         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
2987                      (match_operand:QI 2 "const_int_operand" "n,J")))]
2988   "valid_operands (LSHIFTRT, operands, QImode)"
2989   "@
2990    lsh\\t%n2,%0
2991    lsh3\\t%n2,%1,%0"
2992   [(set_attr "type" "binary,binary")])
2993
2994 ; When the shift count is greater than the size of the word
2995 ; the result can be implementation specific
2996 (define_insn "*lshrqi3_const_set"
2997   [(set (reg:CC 21)
2998         (compare:CC
2999           (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
3000                        (match_operand:QI 2 "const_int_operand" "n,J"))
3001           (const_int 0)))
3002    (set (match_operand:QI 0 "reg_operand" "=?d,d")
3003         (lshiftrt:QI (match_dup 1)
3004                      (match_dup 2)))]
3005   "valid_operands (LSHIFTRT, operands, QImode)"
3006   "@
3007    lsh\\t%n2,%0
3008    lsh3\\t%n2,%1,%0"
3009   [(set_attr "type" "binarycc,binarycc")])
3010
3011 (define_insn "*lshrqi3_nonconst_clobber"
3012   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
3013         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
3014                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>,rm,R,rS<>"))))
3015    (clobber (reg:CC 21))]
3016   "valid_operands (LSHIFTRT, operands, QImode)"
3017   "@
3018    lsh\\t%2,%0
3019    lsh3\\t%2,%1,%0
3020    lsh3\\t%2,%1,%0
3021    lsh\\t%2,%0
3022    lsh3\\t%2,%1,%0
3023    lsh3\\t%2,%1,%0"
3024   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
3025 ; Default to int16 data attr.
3026
3027 (define_insn "*lshrqi3_nonconst_noclobber"
3028   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
3029         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
3030                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>"))))]
3031   "valid_operands (LSHIFTRT, operands, QImode)"
3032   "@
3033    lsh\\t%2,%0
3034    lsh3\\t%2,%1,%0
3035    lsh3\\t%2,%1,%0"
3036   [(set_attr "type" "binary,binary,binary")])
3037 ; Default to int16 data attr.
3038
3039 ;
3040 ; ASH (right)
3041 ;
3042 ; Arithmetic right shift on the C[34]x works by negating the shift count,
3043 ; then emitting a right shift with the shift count negated.  This means
3044 ; that all actual shift counts in the RTL will be positive.
3045
3046 (define_expand "ashrqi3"
3047   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3048                    (ashiftrt:QI (match_operand:QI 1 "src_operand" "")
3049                                 (match_operand:QI 2 "src_operand" "")))
3050               (clobber (reg:CC 21))])]
3051   ""
3052   "legitimize_operands (ASHIFTRT, operands, QImode);")
3053
3054 ; When the shift count is greater than the size of the word
3055 ; the result can be implementation specific
3056 (define_insn "*ashrqi3_const_clobber"
3057   [(set (match_operand:QI 0 "reg_operand" "=d,c,?d,?c")
3058         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,0,r,r")
3059                      (match_operand:QI 2 "const_int_operand" "n,n,J,J")))
3060    (clobber (reg:CC 21))]
3061   "valid_operands (ASHIFTRT, operands, QImode)"
3062   "@
3063    ash\\t%n2,%0
3064    ash\\t%n2,%0
3065    ash3\\t%n2,%1,%0
3066    ash3\\t%n2,%1,%0"
3067   [(set_attr "type" "binarycc,binary,binarycc,binary")])
3068
3069 (define_insn "*ashrqi3_const_noclobber"
3070   [(set (match_operand:QI 0 "std_reg_operand" "=c,?c")
3071         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
3072                      (match_operand:QI 2 "const_int_operand" "n,J")))]
3073   "valid_operands (ASHIFTRT, operands, QImode)"
3074   "@
3075    ash\\t%n2,%0
3076    ash3\\t%n2,%1,%0"
3077   [(set_attr "type" "binarycc,binarycc")])
3078
3079 ; When the shift count is greater than the size of the word
3080 ; the result can be implementation specific
3081 (define_insn "*ashrqi3_const_set"
3082   [(set (reg:CC 21)
3083         (compare:CC
3084           (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
3085                        (match_operand:QI 2 "const_int_operand" "n,J"))
3086           (const_int 0)))
3087    (set (match_operand:QI 0 "reg_operand" "=?d,d")
3088         (ashiftrt:QI (match_dup 1)
3089                      (match_dup 2)))]
3090   "valid_operands (ASHIFTRT, operands, QImode)"
3091   "@
3092    ash\\t%n2,%0
3093    ash3\\t%n2,%1,%0"
3094   [(set_attr "type" "binarycc,binarycc")])
3095
3096 (define_insn "*ashrqi3_nonconst_clobber"
3097   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
3098         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
3099                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>,rm,R,rS<>"))))
3100    (clobber (reg:CC 21))]
3101   "valid_operands (ASHIFTRT, operands, QImode)"
3102   "@
3103    ash\\t%2,%0
3104    ash3\\t%2,%1,%0
3105    ash3\\t%2,%1,%0
3106    ash\\t%2,%0
3107    ash3\\t%2,%1,%0
3108    ash3\\t%2,%1,%0"
3109   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
3110 ; Default to int16 data attr.
3111
3112 (define_insn "*ashrqi3_nonconst_noclobber"
3113   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
3114         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
3115                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>"))))]
3116   "valid_operands (ASHIFTRT, operands, QImode)"
3117   "@
3118    ash\\t%2,%0
3119    ash3\\t%2,%1,%0
3120    ash3\\t%2,%1,%0"
3121   [(set_attr "type" "binary,binary,binary")])
3122 ; Default to int16 data attr.
3123
3124 ;
3125 ; CMPI
3126 ;
3127 ; Unfortunately the C40 doesn't allow cmpi3 7, *ar0++ so the next best
3128 ; thing would be to get the small constant loaded into a register (say r0)
3129 ; so that it could be hoisted out of the loop so that we only
3130 ; would need to do cmpi3 *ar0++, r0.  Now the loop optimisation pass
3131 ; comes before the flow pass (which finds autoincrements) so we're stuck.
3132 ; Ideally, GCC requires another loop optimisation pass (preferably after
3133 ; reload) so that it can hoist invariants out of loops.
3134 ; The current solution modifies legitimize_operands () so that small
3135 ; constants are forced into a pseudo register.
3136
3137 (define_expand "cmpqi"
3138   [(set (reg:CC 21)
3139         (compare:CC (match_operand:QI 0 "src_operand" "")
3140                     (match_operand:QI 1 "src_operand" "")))]
3141   ""
3142   "legitimize_operands (COMPARE, operands, QImode);
3143    c4x_compare_op0 = operands[0];
3144    c4x_compare_op1 = operands[1];
3145    DONE;")
3146
3147 (define_insn "*cmpqi_test"
3148   [(set (reg:CC 21)
3149         (compare:CC (match_operand:QI 0 "src_operand" "r,rR,rS<>")
3150                     (match_operand:QI 1 "src_operand" "rIm,JR,rS<>")))]
3151   "valid_operands (COMPARE, operands, QImode)"
3152   "@
3153    cmpi\\t%1,%0
3154    cmpi3\\t%1,%0
3155    cmpi3\\t%1,%0"
3156   [(set_attr "type" "compare,compare,compare")])
3157
3158 (define_insn "*cmpqi_test_noov"
3159   [(set (reg:CC_NOOV 21)
3160         (compare:CC_NOOV (match_operand:QI 0 "src_operand" "r,rR,rS<>")
3161                          (match_operand:QI 1 "src_operand" "rIm,JR,rS<>")))]
3162   "valid_operands (COMPARE, operands, QImode)"
3163   "@
3164    cmpi\\t%1,%0
3165    cmpi3\\t%1,%0
3166    cmpi3\\t%1,%0"
3167   [(set_attr "type" "compare,compare,compare")])
3168
3169
3170 ;
3171 ; BIT-FIELD INSTRUCTIONS
3172 ;
3173
3174 ;
3175 ; LBx/LHw (C4x only)
3176 ;
3177 (define_expand "extv"
3178   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3179                    (sign_extract:QI (match_operand:QI 1 "src_operand" "")
3180                                     (match_operand:QI 2 "const_int_operand" "")
3181                                     (match_operand:QI 3 "const_int_operand" "")))
3182               (clobber (reg:CC 21))])]
3183  "! TARGET_C3X"
3184  "if ((INTVAL (operands[2]) != 8 && INTVAL (operands[2]) != 16)
3185       || (INTVAL (operands[3]) % INTVAL (operands[2]) != 0))
3186         FAIL;
3187  ")
3188
3189 (define_insn "*extv_clobber"
3190   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3191         (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm,rLm")
3192                          (match_operand:QI 2 "const_int_operand" "n,n")
3193                          (match_operand:QI 3 "const_int_operand" "n,n")))
3194    (clobber (reg:CC 21))]
3195   "! TARGET_C3X
3196    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3197    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3198   "*
3199    if (INTVAL (operands[2]) == 8)
3200      {
3201        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3202        return \"lb%3\\t%1,%0\";
3203      }
3204    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3205    return \"lh%3\\t%1,%0\";
3206   "
3207   [(set_attr "type" "binarycc,binary")
3208    (set_attr "data" "int16,int16")])
3209
3210 (define_insn "*extv_clobber_test"
3211   [(set (reg:CC 21)
3212         (compare:CC (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3213                                      (match_operand:QI 2 "const_int_operand" "n")
3214                                      (match_operand:QI 3 "const_int_operand" "n"))
3215                     (const_int 0)))
3216    (clobber (match_scratch:QI 0 "=d"))]
3217   "! TARGET_C3X
3218    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3219    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3220   "*
3221    if (INTVAL (operands[2]) == 8)
3222      {
3223        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3224        return \"lb%3\\t%1,%0\";
3225      }
3226    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3227    return \"lh%3\\t%1,%0\";
3228   "
3229   [(set_attr "type" "binarycc")
3230    (set_attr "data" "int16")])
3231
3232 (define_insn "*extv_clobber_set"
3233   [(set (reg:CC 21)
3234         (compare:CC (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3235                                      (match_operand:QI 2 "const_int_operand" "n")
3236                                      (match_operand:QI 3 "const_int_operand" "n"))
3237                     (const_int 0)))
3238    (set (match_operand:QI 0 "reg_operand" "=d")
3239         (sign_extract:QI (match_dup 1)
3240                          (match_dup 2)
3241                          (match_dup 3)))]
3242   "! TARGET_C3X
3243    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3244    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3245   "*
3246    if (INTVAL (operands[2]) == 8)
3247      {
3248        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3249        return \"lb%3\\t%1,%0\";
3250      }
3251    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3252    return \"lh%3\\t%1,%0\";
3253   "
3254   [(set_attr "type" "binarycc")
3255    (set_attr "data" "int16")])
3256
3257 ;
3258 ; LBUx/LHUw (C4x only)
3259 ;
3260 (define_expand "extzv"
3261   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3262                    (zero_extract:QI (match_operand:QI 1 "src_operand" "")
3263                                     (match_operand:QI 2 "const_int_operand" "")
3264                                     (match_operand:QI 3 "const_int_operand" "")))
3265               (clobber (reg:CC 21))])]
3266  "! TARGET_C3X"
3267  "if ((INTVAL (operands[2]) != 8 && INTVAL (operands[2]) != 16)
3268       || (INTVAL (operands[3]) % INTVAL (operands[2]) != 0))
3269         FAIL;
3270  ")
3271
3272 (define_insn "*extzv_clobber"
3273   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3274         (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm,rLm")
3275                          (match_operand:QI 2 "const_int_operand" "n,n")
3276                          (match_operand:QI 3 "const_int_operand" "n,n")))
3277    (clobber (reg:CC 21))]
3278   "! TARGET_C3X
3279    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3280    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3281   "*
3282    if (INTVAL (operands[2]) == 8)
3283      {
3284        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3285        return \"lbu%3\\t%1,%0\";
3286      }
3287    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3288    return \"lhu%3\\t%1,%0\";
3289   "
3290   [(set_attr "type" "binarycc,binary")
3291    (set_attr "data" "uint16,uint16")])
3292
3293 (define_insn "*extzv_test"
3294   [(set (reg:CC 21)
3295         (compare:CC (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3296                                      (match_operand:QI 2 "const_int_operand" "n")
3297                                      (match_operand:QI 3 "const_int_operand" "n"))
3298                     (const_int 0)))
3299    (clobber (match_scratch:QI 0 "=d"))]
3300   "! TARGET_C3X
3301    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3302    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3303   "*
3304    if (INTVAL (operands[2]) == 8)
3305      {
3306        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3307        return \"lbu%3\\t%1,%0\";
3308      }
3309    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3310    return \"lhu%3\\t%1,%0\";
3311   "
3312   [(set_attr "type" "binarycc")
3313    (set_attr "data" "uint16")])
3314
3315 (define_insn "*extzv_set"
3316   [(set (reg:CC 21)
3317         (compare:CC (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3318                                      (match_operand:QI 2 "const_int_operand" "n")
3319                                      (match_operand:QI 3 "const_int_operand" "n"))
3320                     (const_int 0)))
3321    (set (match_operand:QI 0 "ext_reg_operand" "=d")
3322         (zero_extract:QI (match_dup 1)
3323                          (match_dup 2)
3324                          (match_dup 3)))]
3325   "! TARGET_C3X
3326    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3327    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3328   "*
3329    if (INTVAL (operands[2]) == 8)
3330      {
3331         /* 8 bit extract.  */
3332        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3333        return \"lbu%3\\t%1,%0\";
3334      }
3335    /* 16 bit extract.  */
3336    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3337    return \"lhu%3\\t%1,%0\";
3338   "
3339   [(set_attr "type" "binarycc")
3340    (set_attr "data" "uint16")])
3341
3342 ;
3343 ; MBx/MHw (C4x only)
3344 ;
3345 (define_expand "insv"
3346   [(parallel [(set (zero_extract:QI (match_operand:QI 0 "reg_operand" "")
3347                                     (match_operand:QI 1 "const_int_operand" "")
3348                                     (match_operand:QI 2 "const_int_operand" ""))
3349                    (match_operand:QI 3 "src_operand" ""))
3350               (clobber (reg:CC 21))])]
3351  "! TARGET_C3X"
3352  "if (! (((INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3353          && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0))
3354         || (INTVAL (operands[1]) == 24 && INTVAL (operands[2]) == 8)))
3355     FAIL;
3356  ")
3357
3358 (define_insn "*insv_clobber"
3359   [(set (zero_extract:QI (match_operand:QI 0 "reg_operand" "+d,c")
3360                          (match_operand:QI 1 "const_int_operand" "n,n")
3361                          (match_operand:QI 2 "const_int_operand" "n,n"))
3362         (match_operand:QI 3 "src_operand" "rLm,rLm"))
3363    (clobber (reg:CC 21))]
3364   "! TARGET_C3X
3365    && (((INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3366         && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0))
3367        || (INTVAL (operands[1]) == 24 && INTVAL (operands[2]) == 8))"
3368   "*
3369    if (INTVAL (operands[1]) == 8)
3370      {
3371        /* 8 bit insert.  */
3372        operands[2] = GEN_INT (INTVAL (operands[2]) / 8);
3373        return \"mb%2\\t%3,%0\";
3374      }
3375    else if (INTVAL (operands[1]) == 16)
3376      {
3377        /* 16 bit insert.  */
3378        operands[2] = GEN_INT (INTVAL (operands[2]) / 16);
3379        return \"mh%2\\t%3,%0\";
3380      }
3381    /* 24 bit insert.  */
3382    return \"lwl1\\t%3,%0\";
3383   "
3384   [(set_attr "type" "binarycc,binary")
3385    (set_attr "data" "uint16,uint16")])
3386
3387 (define_peephole
3388   [(parallel [(set (zero_extract:QI (match_operand:QI 0 "ext_reg_operand" "+d")
3389                                     (match_operand:QI 1 "const_int_operand" "n")
3390                                     (match_operand:QI 2 "const_int_operand" "n"))
3391                    (match_operand:QI 3 "src_operand" "rLm"))
3392               (clobber (reg:CC 21))])
3393    (set (reg:CC 21)
3394         (compare:CC (match_dup 0) (const_int 0)))]
3395   "! TARGET_C3X
3396    && (INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3397    && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0)"
3398   "*
3399    if (INTVAL (operands[1]) == 8)
3400      {
3401        operands[2] = GEN_INT (INTVAL (operands[2]) / 8);
3402        return \"mb%2\\t%3,%0\";
3403      }
3404    operands[2] = GEN_INT (INTVAL (operands[2]) / 16);
3405    return \"mh%2\\t%3,%0\";
3406   "
3407   [(set_attr "type" "binarycc")
3408    (set_attr "data" "uint16")])
3409
3410
3411 ; TWO OPERAND FLOAT INSTRUCTIONS
3412 ;
3413
3414 ;
3415 ; LDF/STF
3416 ;
3417 ;  If one of the operands is not a register, then we should
3418 ;  emit two insns, using a scratch register.  This will produce
3419 ;  better code in loops if the source operand is invariant, since
3420 ;  the source reload can be optimized out.  During reload we cannot
3421 ;  use change_address or force_reg.
3422 (define_expand "movqf"
3423   [(set (match_operand:QF 0 "src_operand" "")
3424         (match_operand:QF 1 "src_operand" ""))]
3425  ""
3426  "
3427 {
3428   if (c4x_emit_move_sequence (operands, QFmode))
3429     DONE;
3430 }")
3431
3432 ; This can generate invalid stack slot displacements
3433 (define_split
3434  [(set (match_operand:QI 0 "reg_operand" "")
3435        (unspec:QI [(match_operand:QF 1 "reg_operand" "")] UNSPEC_STOREQF_INT))]
3436   "reload_completed"
3437   [(set (match_dup 3) (match_dup 1))
3438    (set (match_dup 0) (match_dup 2))]
3439   "operands[2] = assign_stack_temp (QImode, GET_MODE_SIZE (QImode), 0);
3440    operands[3] = copy_rtx (operands[2]);
3441    PUT_MODE (operands[3], QFmode);")
3442
3443
3444 (define_insn "storeqf_int"
3445  [(set (match_operand:QI 0 "reg_operand" "=r")
3446        (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] UNSPEC_STOREQF_INT))]
3447  ""
3448  "#"
3449   [(set_attr "type" "multi")])
3450
3451 (define_split
3452  [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3453                   (unspec:QI [(match_operand:QF 1 "reg_operand" "")] UNSPEC_STOREQF_INT))
3454              (clobber (reg:CC 21))])]
3455   "reload_completed"
3456   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
3457         (match_dup 1))
3458    (parallel [(set (match_dup 0)
3459                    (mem:QI (post_dec:QI (reg:QI 20))))
3460               (clobber (reg:CC 21))])]
3461   "")
3462
3463
3464 ; We need accurate death notes for this...
3465 ;(define_peephole
3466 ;  [(set (match_operand:QF 0 "reg_operand" "=f")
3467 ;        (match_operand:QF 1 "memory_operand" "m"))
3468 ;   (set (mem:QF (pre_inc:QI (reg:QI 20)))
3469 ;        (match_dup 0))
3470 ;   (parallel [(set (match_operand:QI 2 "reg_operand" "r")
3471 ;                   (mem:QI (post_dec:QI (reg:QI 20))))
3472 ;              (clobber (reg:CC 21))])]
3473 ;  ""
3474 ;  "ldiu\\t%1,%0")
3475
3476 (define_insn "storeqf_int_clobber"
3477  [(parallel [(set (match_operand:QI 0 "reg_operand" "=r")
3478                   (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] UNSPEC_STOREQF_INT))
3479              (clobber (reg:CC 21))])]
3480  ""
3481  "#"
3482   [(set_attr "type" "multi")])
3483
3484
3485 ; This can generate invalid stack slot displacements
3486 (define_split
3487  [(set (match_operand:QF 0 "reg_operand" "")
3488        (unspec:QF [(match_operand:QI 1 "reg_operand" "")] UNSPEC_LOADQF_INT))]
3489   "reload_completed"
3490   [(set (match_dup 2) (match_dup 1))
3491    (set (match_dup 0) (match_dup 3))]
3492   "operands[2] = assign_stack_temp (QImode, GET_MODE_SIZE (QImode), 0);
3493    operands[3] = copy_rtx (operands[2]);
3494    PUT_MODE (operands[3], QFmode);")
3495
3496
3497 (define_insn "loadqf_int"
3498  [(set (match_operand:QF 0 "reg_operand" "=f")
3499        (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] UNSPEC_LOADQF_INT))]
3500  ""
3501  "#"
3502   [(set_attr "type" "multi")])
3503
3504 (define_split
3505  [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3506                   (unspec:QF [(match_operand:QI 1 "reg_operand" "")] UNSPEC_LOADQF_INT))
3507              (clobber (reg:CC 21))])]
3508   "reload_completed"
3509   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
3510         (match_dup 1))
3511    (parallel [(set (match_dup 0)
3512                    (mem:QF (post_dec:QI (reg:QI 20))))
3513               (clobber (reg:CC 21))])]
3514   "")
3515
3516 (define_insn "loadqf_int_clobber"
3517  [(parallel [(set (match_operand:QF 0 "reg_operand" "=f")
3518                   (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] UNSPEC_LOADQF_INT))
3519              (clobber (reg:CC 21))])]
3520  ""
3521  "#"
3522   [(set_attr "type" "multi")])
3523
3524 ; We must provide an alternative to store to memory in case we have to
3525 ; spill a register.
3526 (define_insn "movqf_noclobber"
3527  [(set (match_operand:QF 0 "dst_operand" "=f,m")
3528        (match_operand:QF 1 "src_operand" "fHm,f"))]
3529  "REG_P (operands[0]) || REG_P (operands[1])"
3530  "@
3531   ldfu\\t%1,%0
3532   stf\\t%1,%0"
3533   [(set_attr "type" "unary,store")])
3534
3535 ;(define_insn "*movqf_clobber"
3536 ;  [(set (match_operand:QF 0 "reg_operand" "=f")
3537 ;        (match_operand:QF 1 "src_operand" "fHm"))
3538 ;   (clobber (reg:CC 21))]
3539 ; "0"
3540 ; "ldf\\t%1,%0"
3541 ;  [(set_attr "type" "unarycc")])
3542
3543 (define_insn "*movqf_test"
3544   [(set (reg:CC 21)
3545         (compare:CC (match_operand:QF 1 "src_operand" "fHm")
3546                     (const_int 0)))
3547    (clobber (match_scratch:QF 0 "=f"))]
3548  ""
3549  "ldf\\t%1,%0"
3550   [(set_attr "type" "unarycc")])
3551
3552 (define_insn "*movqf_set"
3553   [(set (reg:CC 21)
3554         (compare:CC (match_operand:QF 1 "src_operand" "fHm")
3555                     (match_operand:QF 2 "fp_zero_operand" "G")))
3556     (set (match_operand:QF 0 "reg_operand" "=f")
3557          (match_dup 1))]
3558  ""
3559  "ldf\\t%1,%0"
3560   [(set_attr "type" "unarycc")])
3561
3562
3563 (define_insn "*movqf_parallel"
3564  [(set (match_operand:QF 0 "parallel_operand" "=q,S<>!V,q,S<>!V")
3565        (match_operand:QF 1 "parallel_operand" "S<>!V,q,S<>!V,q"))
3566   (set (match_operand:QF 2 "parallel_operand" "=q,S<>!V,S<>!V,q")
3567        (match_operand:QF 3 "parallel_operand" "S<>!V,q,q,S<>!V"))]
3568  "TARGET_PARALLEL && valid_parallel_load_store (operands, QFmode)"
3569  "@
3570   ldf1\\t%1,%0\\n||\\tldf2\\t%3,%2
3571   stf1\\t%1,%0\\n||\\tstf2\\t%3,%2
3572   ldf\\t%1,%0\\n||\\tstf\\t%3,%2
3573   ldf\\t%3,%2\\n||\\tstf\\t%1,%0"
3574   [(set_attr "type" "load_load,store_store,load_store,store_load")])
3575
3576
3577 ;
3578 ; PUSH/POP
3579 ;
3580 (define_insn "pushqf"
3581   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
3582         (match_operand:QF 0 "reg_operand" "f"))]
3583  ""
3584  "pushf\\t%0"
3585  [(set_attr "type" "push")])
3586
3587 (define_insn "popqf"
3588   [(set (match_operand:QF 0 "reg_operand" "=f")
3589         (mem:QF (post_dec:QI (reg:QI 20))))
3590    (clobber (reg:CC 21))]
3591  ""
3592  "popf\\t%0"
3593  [(set_attr "type" "pop")])
3594
3595 (define_insn "popqf_unspec"
3596   [(set (unspec:QF [(match_operand:QF 0 "reg_operand" "=f")] UNSPEC_POPQF)
3597         (mem:QF (post_dec:QI (reg:QI 20))))
3598    (clobber (match_dup 0))
3599    (clobber (reg:CC 21))]
3600  ""
3601  "popf\\t%0"
3602  [(set_attr "type" "pop")])
3603
3604 ;
3605 ; ABSF
3606 ;
3607 (define_expand "absqf2"
3608   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3609                    (abs:QF (match_operand:QF 1 "src_operand" "")))
3610               (clobber (reg:CC_NOOV 21))])]
3611 ""
3612 "")
3613
3614 (define_insn "*absqf2_clobber"
3615   [(set (match_operand:QF 0 "reg_operand" "=f")
3616         (abs:QF (match_operand:QF 1 "src_operand" "fHm")))
3617    (clobber (reg:CC_NOOV 21))]
3618   ""
3619   "absf\\t%1,%0"
3620   [(set_attr "type" "unarycc")])
3621
3622 (define_insn "*absqf2_test"
3623   [(set (reg:CC_NOOV 21)
3624         (compare:CC_NOOV (abs:QF (match_operand:QF 1 "src_operand" "fHm"))
3625                          (match_operand:QF 2 "fp_zero_operand" "G")))
3626    (clobber (match_scratch:QF 0 "=f"))]
3627   ""
3628   "absf\\t%1,%0"
3629   [(set_attr "type" "unarycc")])
3630
3631 (define_insn "*absqf2_set"
3632   [(set (reg:CC_NOOV 21)
3633         (compare:CC_NOOV (abs:QF (match_operand:QF 1 "src_operand" "fHm"))
3634                          (match_operand:QF 2 "fp_zero_operand" "G")))
3635    (set (match_operand:QF 0 "reg_operand" "=f")
3636         (abs:QF (match_dup 1)))]
3637
3638   ""
3639   "absf\\t%1,%0"
3640   [(set_attr "type" "unarycc")])
3641
3642 ;
3643 ; NEGF
3644 ;
3645 (define_expand "negqf2"
3646   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3647                    (neg:QF (match_operand:QF 1 "src_operand" "")))
3648               (clobber (reg:CC_NOOV 21))])]
3649 ""
3650 "")
3651
3652 (define_insn "*negqf2_clobber"
3653   [(set (match_operand:QF 0 "reg_operand" "=f")
3654         (neg:QF (match_operand:QF 1 "src_operand" "fHm")))
3655    (clobber (reg:CC_NOOV 21))]
3656   ""
3657   "negf\\t%1,%0"
3658   [(set_attr "type" "unarycc")])
3659
3660 (define_insn "*negqf2_test"
3661   [(set (reg:CC_NOOV 21)
3662         (compare:CC_NOOV (neg:QF (match_operand:QF 1 "src_operand" "fHm"))
3663                          (match_operand:QF 2 "fp_zero_operand" "G")))
3664    (clobber (match_scratch:QF 0 "=f"))]
3665   ""
3666   "negf\\t%1,%0"
3667   [(set_attr "type" "unarycc")])
3668
3669 (define_insn "*negqf2_set"
3670   [(set (reg:CC_NOOV 21)
3671         (compare:CC_NOOV (neg:QF (match_operand:QF 1 "src_operand" "fHm"))
3672                          (match_operand:QF 2 "fp_zero_operand" "G")))
3673    (set (match_operand:QF 0 "reg_operand" "=f")
3674         (neg:QF (match_dup 1)))]
3675   ""
3676   "negf\\t%1,%0"
3677   [(set_attr "type" "unarycc")])
3678
3679 ;
3680 ; FLOAT
3681 ;
3682 (define_insn "floatqiqf2"
3683   [(set (match_operand:QF 0 "reg_operand" "=f")
3684         (float:QF (match_operand:QI 1 "src_operand" "rIm")))
3685    (clobber (reg:CC 21))]
3686  ""
3687  "float\\t%1,%0"
3688   [(set_attr "type" "unarycc")])
3689
3690 (define_insn "*floatqiqf2_set"
3691   [(set (reg:CC 21)
3692         (compare:CC (float:QF (match_operand:QI 1 "src_operand" "rIm"))
3693                     (match_operand:QF 2 "fp_zero_operand" "G")))
3694    (set (match_operand:QF 0 "reg_operand" "=f")
3695         (float:QF (match_dup 1)))]
3696  ""
3697  "float\\t%1,%0"
3698   [(set_attr "type" "unarycc")])
3699
3700 ; Unsigned conversions are a little tricky because we need to
3701 ; add the value for the high bit if necessary.
3702
3703 ;
3704 (define_expand "floatunsqiqf2"
3705  [(set (match_dup 2) (match_dup 3))
3706   (parallel [(set (reg:CC 21)
3707                   (compare:CC (float:QF (match_operand:QI 1 "src_operand" ""))
3708                               (match_dup 3)))
3709              (set (match_dup 4)
3710                   (float:QF (match_dup 1)))])
3711   (set (match_dup 6)
3712        (if_then_else:QF (lt (reg:CC 21) (const_int 0))
3713                         (match_dup 5)
3714                         (match_dup 2)))
3715   (parallel [(set (match_operand:QF 0 "reg_operand" "")
3716                   (plus:QF (match_dup 6) (match_dup 4)))
3717              (clobber (reg:CC_NOOV 21))])]
3718  ""
3719  "operands[2] = gen_reg_rtx (QFmode);
3720   operands[3] = CONST0_RTX (QFmode); 
3721   operands[4] = gen_reg_rtx (QFmode);
3722   operands[5] = gen_reg_rtx (QFmode);
3723   operands[6] = gen_reg_rtx (QFmode);
3724   emit_move_insn (operands[5], CONST_DOUBLE_ATOF (\"4294967296.0\", QFmode));")
3725
3726 (define_expand "floatunsqihf2"
3727  [(set (match_dup 2) (match_dup 3))
3728   (parallel [(set (reg:CC 21)
3729                   (compare:CC (float:HF (match_operand:QI 1 "src_operand" ""))
3730                               (match_dup 3)))
3731              (set (match_dup 4)
3732                   (float:HF (match_dup 1)))])
3733   (set (match_dup 6)
3734        (if_then_else:HF (lt (reg:CC 21) (const_int 0))
3735                         (match_dup 5)
3736                         (match_dup 2)))
3737   (parallel [(set (match_operand:HF 0 "reg_operand" "")
3738                   (plus:HF (match_dup 6) (match_dup 4)))
3739              (clobber (reg:CC_NOOV 21))])]
3740  ""
3741  "operands[2] = gen_reg_rtx (HFmode);
3742   operands[3] = CONST0_RTX (HFmode); 
3743   operands[4] = gen_reg_rtx (HFmode);
3744   operands[5] = gen_reg_rtx (HFmode);
3745   operands[6] = gen_reg_rtx (HFmode);
3746   emit_move_insn (operands[5], CONST_DOUBLE_ATOF (\"4294967296.0\", HFmode));")
3747
3748 (define_insn "floatqihf2"
3749   [(set (match_operand:HF 0 "reg_operand" "=h")
3750         (float:HF (match_operand:QI 1 "src_operand" "rIm")))
3751    (clobber (reg:CC 21))]
3752  ""
3753  "float\\t%1,%0"
3754   [(set_attr "type" "unarycc")])
3755
3756 (define_insn "*floatqihf2_set"
3757   [(set (reg:CC 21)
3758         (compare:CC (float:HF (match_operand:QI 1 "src_operand" "rIm"))
3759                     (match_operand:QF 2 "fp_zero_operand" "G")))
3760    (set (match_operand:HF 0 "reg_operand" "=h")
3761         (float:HF (match_dup 1)))]
3762  ""
3763  "float\\t%1,%0"
3764   [(set_attr "type" "unarycc")])
3765
3766 ;
3767 ; FIX
3768 ;
3769 (define_insn "fixqfqi_clobber"
3770   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3771         (fix:QI (match_operand:QF 1 "src_operand" "fHm,fHm")))
3772    (clobber (reg:CC 21))]
3773  ""
3774  "fix\\t%1,%0"
3775   [(set_attr "type" "unarycc")])
3776
3777 (define_insn "*fixqfqi_set"
3778   [(set (reg:CC 21)
3779         (compare:CC (fix:QI (match_operand:QF 1 "src_operand" "fHm"))
3780                     (const_int 0)))
3781    (set (match_operand:QI 0 "ext_reg_operand" "=d")
3782         (fix:QI (match_dup 1)))]
3783  ""
3784  "fix\\t%1,%0"
3785   [(set_attr "type" "unarycc")])
3786
3787 (define_insn "*fixhfqi_set"
3788   [(set (reg:CC 21)
3789         (compare:CC (fix:QI (match_operand:HF 1 "src_operand" "fH"))
3790                     (const_int 0)))
3791    (set (match_operand:QI 0 "ext_reg_operand" "=d")
3792         (fix:QI (match_dup 1)))]
3793  ""
3794  "fix\\t%1,%0"
3795   [(set_attr "type" "unarycc")])
3796
3797 ;
3798 ; The C[34]x fix instruction implements a floor, not a straight trunc,
3799 ; so we have to invert the number, fix it, and reinvert it if negative
3800 ;
3801 (define_expand "fix_truncqfqi2"
3802   [(parallel [(set (match_dup 2)
3803                    (fix:QI (match_operand:QF 1 "src_operand" "")))
3804               (clobber (reg:CC 21))])
3805    (parallel [(set (match_dup 3) (neg:QF (match_dup 1)))
3806               (clobber (reg:CC_NOOV 21))])
3807    (parallel [(set (match_dup 4) (fix:QI (match_dup 3)))
3808               (clobber (reg:CC 21))])
3809    (parallel [(set (reg:CC_NOOV 21)
3810                    (compare:CC_NOOV (neg:QI (match_dup 4)) (const_int 0)))
3811               (set (match_dup 5) (neg:QI (match_dup 4)))])
3812    (set (match_dup 2)
3813         (if_then_else:QI (le (reg:CC 21) (const_int 0))
3814                          (match_dup 5)
3815                          (match_dup 2)))
3816    (set (match_operand:QI 0 "reg_operand" "=r") (match_dup 2))]
3817  ""
3818  "if (TARGET_FAST_FIX)
3819     {
3820        emit_insn (gen_fixqfqi_clobber (operands[0], operands[1]));
3821        DONE;
3822     }
3823   operands[2] = gen_reg_rtx (QImode);
3824   operands[3] = gen_reg_rtx (QFmode);
3825   operands[4] = gen_reg_rtx (QImode);
3826   operands[5] = gen_reg_rtx (QImode);
3827  ")
3828
3829 (define_expand "fix_trunchfqi2"
3830   [(parallel [(set (match_dup 2)
3831                    (fix:QI (match_operand:HF 1 "src_operand" "")))
3832               (clobber (reg:CC 21))])
3833    (parallel [(set (match_dup 3) (neg:HF (match_dup 1)))
3834               (clobber (reg:CC_NOOV 21))])
3835    (parallel [(set (match_dup 4) (fix:QI (match_dup 3)))
3836               (clobber (reg:CC 21))])
3837    (parallel [(set (reg:CC_NOOV 21)
3838                    (compare:CC_NOOV (neg:QI (match_dup 4)) (const_int 0)))
3839               (set (match_dup 5) (neg:QI (match_dup 4)))])
3840    (set (match_dup 2)
3841         (if_then_else:QI (le (reg:CC 21) (const_int 0))
3842                          (match_dup 5)
3843                          (match_dup 2)))
3844    (set (match_operand:QI 0 "reg_operand" "=r") (match_dup 2))]
3845  ""
3846  "if (TARGET_FAST_FIX)
3847     {
3848        emit_insn (gen_fixhfqi_clobber (operands[0], operands[1]));
3849        DONE;
3850     }
3851   operands[2] = gen_reg_rtx (QImode);
3852   operands[3] = gen_reg_rtx (HFmode);
3853   operands[4] = gen_reg_rtx (QImode);
3854   operands[5] = gen_reg_rtx (QImode);
3855  ")
3856
3857 (define_expand "fix_truncqfhi2"
3858   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
3859                    (fix:HI (match_operand:QF 1 "src_operand" "")))
3860               (clobber (reg:CC 21))])]
3861   ""
3862   "c4x_emit_libcall (fix_truncqfhi2_libfunc, FIX, HImode, QFmode, 2, operands);
3863    DONE;")
3864
3865 (define_expand "fixuns_truncqfqi2"
3866  [(parallel [(set (match_dup 2)
3867                   (fix:QI (match_operand:QF 1 "src_operand" "fHm")))
3868              (clobber (reg:CC 21))])
3869   (parallel [(set (match_dup 3)
3870                   (minus:QF (match_dup 1) (match_dup 5)))
3871              (clobber (reg:CC_NOOV 21))])
3872   (parallel [(set (reg:CC 21)
3873                   (compare:CC (fix:QI (match_dup 3))
3874                               (const_int 0)))
3875              (set (match_dup 4)
3876                   (fix:QI (match_dup 3)))])
3877   (parallel [(set (match_dup 4) (unspec:QI [(match_dup 2)] UNSPEC_LDIV))
3878              (use (reg:CC 21))])
3879   (set (match_operand:QI 0 "reg_operand" "=r") (match_dup 4))]
3880  ""
3881  "operands[2] = gen_reg_rtx (QImode);
3882   operands[3] = gen_reg_rtx (QFmode);
3883   operands[4] = gen_reg_rtx (QImode);
3884   operands[5] = gen_reg_rtx (QFmode);
3885   emit_move_insn (operands[5], CONST_DOUBLE_ATOF (\"4294967296.0\", QFmode));")
3886
3887 (define_expand "fixuns_trunchfqi2"
3888  [(parallel [(set (match_dup 2)
3889                   (fix:QI (match_operand:HF 1 "src_operand" "hH")))
3890              (clobber (reg:CC 21))])
3891   (parallel [(set (match_dup 3)
3892                   (minus:HF (match_dup 1) (match_dup 5)))
3893              (clobber (reg:CC_NOOV 21))])
3894   (parallel [(set (reg:CC 21)
3895                   (compare:CC (fix:QI (match_dup 3))
3896                               (const_int 0)))
3897              (set (match_dup 4)
3898                   (fix:QI (match_dup 3)))])
3899   (parallel [(set (match_dup 4) (unspec:QI [(match_dup 2)] UNSPEC_LDIV))
3900              (use (reg:CC 21))])
3901   (set (match_operand:QI 0 "reg_operand" "=r") (match_dup 4))]
3902  ""
3903  "operands[2] = gen_reg_rtx (QImode);
3904   operands[3] = gen_reg_rtx (HFmode);
3905   operands[4] = gen_reg_rtx (QImode);
3906   operands[5] = gen_reg_rtx (HFmode);
3907   emit_move_insn (operands[5], CONST_DOUBLE_ATOF (\"4294967296.0\", HFmode));")
3908
3909 (define_expand "fixuns_truncqfhi2"
3910   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
3911                    (unsigned_fix:HI (match_operand:QF 1 "src_operand" "")))
3912               (clobber (reg:CC 21))])]
3913   ""
3914   "c4x_emit_libcall (fixuns_truncqfhi2_libfunc, UNSIGNED_FIX, 
3915                      HImode, QFmode, 2, operands);
3916    DONE;")
3917
3918 ;
3919 ; RCPF
3920 ;
3921 (define_insn "rcpfqf_clobber"
3922   [(set (match_operand:QF 0 "reg_operand" "=f")
3923         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] UNSPEC_RCPF))
3924    (clobber (reg:CC_NOOV 21))]
3925   "! TARGET_C3X"
3926   "rcpf\\t%1,%0"
3927   [(set_attr "type" "unarycc")])
3928
3929 ;
3930 ; RSQRF
3931 ;
3932 (define_insn "*rsqrfqf_clobber"
3933   [(set (match_operand:QF 0 "reg_operand" "=f")
3934         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] UNSPEC_RSQRF))
3935    (clobber (reg:CC_NOOV 21))]
3936   "! TARGET_C3X"
3937   "rsqrf\\t%1,%0"
3938   [(set_attr "type" "unarycc")])
3939
3940 ;
3941 ; RNDF
3942 ;
3943 (define_insn "*rndqf_clobber"
3944   [(set (match_operand:QF 0 "reg_operand" "=f")
3945         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] UNSPEC_RND))
3946    (clobber (reg:CC_NOOV 21))]
3947   "! TARGET_C3X"
3948   "rnd\\t%1,%0"
3949   [(set_attr "type" "unarycc")])
3950
3951
3952 ; Inlined float square root for C4x
3953 (define_expand "sqrtqf2_inline"
3954   [(parallel [(set (match_dup 2)
3955                    (unspec:QF [(match_operand:QF 1 "src_operand" "")] UNSPEC_RSQRF))
3956               (clobber (reg:CC_NOOV 21))])
3957    (parallel [(set (match_dup 3) (mult:QF (match_dup 5) (match_dup 1)))
3958               (clobber (reg:CC_NOOV 21))])
3959    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
3960               (clobber (reg:CC_NOOV 21))])
3961    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 4)))
3962               (clobber (reg:CC_NOOV 21))])
3963    (parallel [(set (match_dup 4) (minus:QF (match_dup 6) (match_dup 4)))
3964               (clobber (reg:CC_NOOV 21))])
3965    (parallel [(set (match_dup 2) (mult:QF (match_dup 2) (match_dup 4)))
3966               (clobber (reg:CC_NOOV 21))])
3967    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
3968               (clobber (reg:CC_NOOV 21))])
3969    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 4)))
3970               (clobber (reg:CC_NOOV 21))])
3971    (parallel [(set (match_dup 4) (minus:QF (match_dup 6) (match_dup 4)))
3972               (clobber (reg:CC_NOOV 21))])
3973    (parallel [(set (match_dup 2) (mult:QF (match_dup 2) (match_dup 4)))
3974               (clobber (reg:CC_NOOV 21))])
3975    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 1)))
3976               (clobber (reg:CC_NOOV 21))])
3977    (parallel [(set (match_operand:QF 0 "reg_operand" "")
3978                    (unspec:QF [(match_dup 4)] UNSPEC_RND))
3979               (clobber (reg:CC_NOOV 21))])]
3980   "! TARGET_C3X"
3981   "if (! reload_in_progress
3982        && ! reg_operand (operands[1], QFmode))
3983      operands[1] = force_reg (QFmode, operands[1]);
3984    operands[2] = gen_reg_rtx (QFmode);
3985    operands[3] = gen_reg_rtx (QFmode);
3986    operands[4] = gen_reg_rtx (QFmode);
3987    operands[5] = CONST_DOUBLE_ATOF (\"0.5\", QFmode);
3988    operands[6] = CONST_DOUBLE_ATOF (\"1.5\", QFmode);")
3989
3990 (define_expand "sqrtqf2"
3991   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3992                    (sqrt:QF (match_operand:QF 1 "src_operand" "")))
3993               (clobber (reg:CC 21))])]
3994   "! TARGET_C3X && TARGET_INLINE"
3995   "emit_insn (gen_sqrtqf2_inline (operands[0], operands[1]));
3996    DONE;")
3997
3998 ;
3999 ; TOIEEE / FRIEEE
4000 ;
4001 (define_insn "toieee"
4002   [(set (match_operand:QF 0 "reg_operand" "=f")
4003         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] UNSPEC_TOIEEE))
4004    (clobber (reg:CC 21))]
4005  ""
4006  "toieee\\t%1,%0")
4007
4008 (define_insn "frieee"
4009   [(set (match_operand:QF 0 "reg_operand" "=f")
4010         (unspec:QF [(match_operand:QF 1 "memory_operand" "m")] UNSPEC_FRIEEE))
4011    (clobber (reg:CC 21))]
4012  ""
4013  "frieee\\t%1,%0")
4014
4015 ;
4016 ; THREE OPERAND FLOAT INSTRUCTIONS
4017 ;
4018
4019 ;
4020 ; ADDF
4021 ;
4022 (define_expand "addqf3"
4023   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
4024                    (plus:QF (match_operand:QF 1 "src_operand" "")
4025                             (match_operand:QF 2 "src_operand" "")))
4026               (clobber (reg:CC_NOOV 21))])]
4027   ""
4028   "legitimize_operands (PLUS, operands, QFmode);")
4029
4030 (define_insn "*addqf3_clobber"
4031   [(set (match_operand:QF 0 "reg_operand" "=f,f,?f")
4032         (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4033                  (match_operand:QF 2 "src_operand" "fHm,R,fS<>")))
4034    (clobber (reg:CC_NOOV 21))]
4035   "valid_operands (PLUS, operands, QFmode)"
4036   "@
4037    addf\\t%2,%0
4038    addf3\\t%2,%1,%0
4039    addf3\\t%2,%1,%0"
4040   [(set_attr "type" "binarycc,binarycc,binarycc")])
4041
4042 (define_insn "*addqf3_test"
4043   [(set (reg:CC_NOOV 21)
4044         (compare:CC_NOOV (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4045                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
4046                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
4047    (clobber (match_scratch:QF 0 "=f,f,?f"))]
4048   "valid_operands (PLUS, operands, QFmode)"
4049   "@
4050    addf\\t%2,%0
4051    addf3\\t%2,%1,%0
4052    addf3\\t%2,%1,%0"
4053   [(set_attr "type" "binarycc,binarycc,binarycc")])
4054
4055 (define_insn "*addqf3_set"
4056   [(set (reg:CC_NOOV 21)
4057         (compare:CC_NOOV (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4058                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
4059                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
4060    (set (match_operand:QF 0 "reg_operand" "=f,f,?f")
4061         (plus:QF (match_dup 1)
4062                  (match_dup 2)))]
4063   "valid_operands (PLUS, operands, QFmode)"
4064   "@
4065    addf\\t%2,%0
4066    addf3\\t%2,%1,%0
4067    addf3\\t%2,%1,%0"
4068   [(set_attr "type" "binarycc,binarycc,binarycc")])
4069
4070 ;
4071 ; SUBF/SUBRF
4072 ;
4073 (define_expand "subqf3"
4074   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
4075                    (minus:QF (match_operand:QF 1 "src_operand" "")
4076                              (match_operand:QF 2 "src_operand" "")))
4077               (clobber (reg:CC_NOOV 21))])]
4078   ""
4079   "legitimize_operands (MINUS, operands, QFmode);")
4080
4081 (define_insn "*subqf3_clobber"
4082    [(set (match_operand:QF 0 "reg_operand" "=f,f,f,?f")
4083          (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
4084                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>")))
4085    (clobber (reg:CC_NOOV 21))]
4086   "valid_operands (MINUS, operands, QFmode)"
4087   "@
4088    subf\\t%2,%0
4089    subrf\\t%1,%0
4090    subf3\\t%2,%1,%0
4091    subf3\\t%2,%1,%0"
4092   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4093
4094 (define_insn "*subqf3_test"
4095   [(set (reg:CC_NOOV 21)
4096         (compare:CC_NOOV (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
4097                                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>"))
4098                          (match_operand:QF 3 "fp_zero_operand" "G,G,G,G")))
4099    (clobber (match_scratch:QF 0 "=f,f,f,?f"))]
4100   "valid_operands (MINUS, operands, QFmode)"
4101   "@
4102    subf\\t%2,%0
4103    subrf\\t%1,%0
4104    subf3\\t%2,%1,%0
4105    subf3\\t%2,%1,%0"
4106   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4107
4108 (define_insn "*subqf3_set"
4109   [(set (reg:CC_NOOV 21)
4110         (compare:CC_NOOV (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
4111                                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>"))
4112                          (match_operand:QF 3 "fp_zero_operand" "G,G,G,G")))
4113    (set (match_operand:QF 0 "reg_operand" "=f,f,f,?f")
4114         (minus:QF (match_dup 1)
4115                   (match_dup 2)))]
4116   "valid_operands (MINUS, operands, QFmode)"
4117   "@
4118    subf\\t%2,%0
4119    subrf\\t%1,%0
4120    subf3\\t%2,%1,%0
4121    subf3\\t%2,%1,%0"
4122   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4123
4124 ;
4125 ; MPYF
4126 ;
4127 (define_expand "mulqf3"
4128   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
4129                    (mult:QF (match_operand:QF 1 "src_operand" "")
4130                             (match_operand:QF 2 "src_operand" "")))
4131               (clobber (reg:CC_NOOV 21))])]
4132   ""
4133   "legitimize_operands (MULT, operands, QFmode);")
4134
4135 (define_insn "*mulqf3_clobber"
4136   [(set (match_operand:QF 0 "reg_operand" "=f,f,?f")
4137         (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4138                  (match_operand:QF 2 "src_operand" "fHm,R,fS<>")))
4139    (clobber (reg:CC_NOOV 21))]
4140   "valid_operands (MULT, operands, QFmode)"
4141   "@
4142    mpyf\\t%2,%0
4143    mpyf3\\t%2,%1,%0
4144    mpyf3\\t%2,%1,%0"
4145   [(set_attr "type" "binarycc,binarycc,binarycc")])
4146
4147 (define_insn "*mulqf3_test"
4148   [(set (reg:CC_NOOV 21)
4149         (compare:CC_NOOV (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4150                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
4151                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
4152    (clobber (match_scratch:QF 0 "=f,f,?f"))]
4153   "valid_operands (MULT, operands, QFmode)"
4154   "@
4155    mpyf\\t%2,%0
4156    mpyf3\\t%2,%1,%0
4157    mpyf3\\t%2,%1,%0"
4158   [(set_attr "type" "binarycc,binarycc,binarycc")])
4159
4160 (define_insn "*mulqf3_set"
4161   [(set (reg:CC_NOOV 21)
4162         (compare:CC_NOOV (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4163                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
4164                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
4165    (set (match_operand:QF 0 "reg_operand" "=f,f,?f")
4166         (mult:QF (match_dup 1)
4167                  (match_dup 2)))]
4168   "valid_operands (MULT, operands, QFmode)"
4169   "@
4170    mpyf\\t%2,%0
4171    mpyf3\\t%2,%1,%0
4172    mpyf3\\t%2,%1,%0"
4173   [(set_attr "type" "binarycc,binarycc,binarycc")])
4174
4175 ;
4176 ; CMPF
4177 ;
4178 (define_expand "cmpqf"
4179   [(set (reg:CC 21)
4180         (compare:CC (match_operand:QF 0 "src_operand" "")
4181                     (match_operand:QF 1 "src_operand" "")))]
4182   ""
4183   "legitimize_operands (COMPARE, operands, QFmode);
4184    c4x_compare_op0 = operands[0];
4185    c4x_compare_op1 = operands[1];
4186    DONE;")
4187
4188 (define_insn "*cmpqf"
4189   [(set (reg:CC 21)
4190         (compare:CC (match_operand:QF 0 "src_operand" "f,fR,fS<>")
4191                     (match_operand:QF 1 "src_operand" "fHm,R,fS<>")))]
4192   "valid_operands (COMPARE, operands, QFmode)"
4193   "@
4194    cmpf\\t%1,%0
4195    cmpf3\\t%1,%0
4196    cmpf3\\t%1,%0"
4197   [(set_attr "type" "compare,compare,compare")])
4198
4199 (define_insn "*cmpqf_noov"
4200   [(set (reg:CC_NOOV 21)
4201         (compare:CC_NOOV (match_operand:QF 0 "src_operand" "f,fR,fS<>")
4202                          (match_operand:QF 1 "src_operand" "fHm,R,fS<>")))]
4203   "valid_operands (COMPARE, operands, QFmode)"
4204   "@
4205    cmpf\\t%1,%0
4206    cmpf3\\t%1,%0
4207    cmpf3\\t%1,%0"
4208   [(set_attr "type" "compare,compare,compare")])
4209
4210 ; Inlined float divide for C4x
4211 (define_expand "divqf3_inline"
4212   [(parallel [(set (match_dup 3)
4213                    (unspec:QF [(match_operand:QF 2 "src_operand" "")] UNSPEC_RCPF))
4214               (clobber (reg:CC_NOOV 21))])
4215    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
4216               (clobber (reg:CC_NOOV 21))])
4217    (parallel [(set (match_dup 4) (minus:QF (match_dup 5) (match_dup 4)))
4218               (clobber (reg:CC_NOOV 21))])
4219    (parallel [(set (match_dup 3) (mult:QF (match_dup 3) (match_dup 4)))
4220               (clobber (reg:CC_NOOV 21))])
4221    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
4222               (clobber (reg:CC_NOOV 21))])
4223    (parallel [(set (match_dup 4) (minus:QF (match_dup 5) (match_dup 4)))
4224               (clobber (reg:CC_NOOV 21))])
4225    (parallel [(set (match_dup 3) (mult:QF (match_dup 3) (match_dup 4)))
4226               (clobber (reg:CC_NOOV 21))])
4227    (parallel [(set (match_dup 3)
4228                    (mult:QF (match_operand:QF 1 "src_operand" "")
4229                             (match_dup 3)))
4230               (clobber (reg:CC_NOOV 21))])
4231    (parallel [(set (match_operand:QF 0 "reg_operand" "")
4232                    (unspec:QF [(match_dup 3)] UNSPEC_RND))
4233               (clobber (reg:CC_NOOV 21))])]
4234   "! TARGET_C3X"
4235   "if (! reload_in_progress
4236       && ! reg_operand (operands[2], QFmode))
4237      operands[2] = force_reg (QFmode, operands[2]);
4238    operands[3] = gen_reg_rtx (QFmode);
4239    operands[4] = gen_reg_rtx (QFmode);
4240    operands[5] = CONST2_RTX (QFmode);")
4241
4242 (define_expand "divqf3"
4243   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
4244                    (div:QF (match_operand:QF 1 "src_operand" "")
4245                             (match_operand:QF 2 "src_operand" "")))
4246               (clobber (reg:CC 21))])]
4247   "! TARGET_C3X && TARGET_INLINE"
4248   "emit_insn (gen_divqf3_inline (operands[0], operands[1], operands[2]));
4249    DONE;")
4250
4251 ;
4252 ; CONDITIONAL MOVES
4253 ;
4254
4255 ; ???  We should make these pattern fail if the src operand combination
4256 ; is not valid.  Although reload will fix things up, it will introduce
4257 ; extra load instructions that won't be hoisted out of a loop.
4258
4259 (define_insn "*ldi_conditional"
4260   [(set (match_operand:QI 0 "reg_operand" "=r,r")
4261         (if_then_else:QI (match_operator 1 "comparison_operator"
4262                           [(reg:CC 21) (const_int 0)])
4263                          (match_operand:QI 2 "src_operand" "rIm,0")
4264                          (match_operand:QI 3 "src_operand" "0,rIm")))]
4265  ""
4266  "@
4267   ldi%1\\t%2,%0
4268   ldi%I1\\t%3,%0"
4269  [(set_attr "type" "binary")])
4270
4271 (define_insn "*ldi_conditional_noov"
4272   [(set (match_operand:QI 0 "reg_operand" "=r,r")
4273         (if_then_else:QI (match_operator 1 "comparison_operator"
4274                           [(reg:CC_NOOV 21) (const_int 0)])
4275                          (match_operand:QI 2 "src_operand" "rIm,0")
4276                          (match_operand:QI 3 "src_operand" "0,rIm")))]
4277  "GET_CODE (operands[1]) != LE
4278   && GET_CODE (operands[1]) != GE
4279   && GET_CODE (operands[1]) != LT
4280   && GET_CODE (operands[1]) != GT"
4281  "@
4282   ldi%1\\t%2,%0
4283   ldi%I1\\t%3,%0"
4284  [(set_attr "type" "binary")])
4285
4286 (define_insn "*ldi_on_overflow"
4287   [(set (match_operand:QI 0 "reg_operand" "=r")
4288         (unspec:QI [(match_operand:QI 1 "src_operand" "rIm")] UNSPEC_LDIV))
4289    (use (reg:CC 21))]
4290   ""
4291   "ldiv\\t%1,%0"
4292   [(set_attr "type" "unary")])
4293
4294 ; Move operand 2 to operand 0 if condition (operand 1) is true
4295 ; else move operand 3 to operand 0.
4296 ; The temporary register is required below because some of the operands
4297 ; might be identical (namely 0 and 2). 
4298 ;
4299 (define_expand "movqicc"
4300   [(set (match_operand:QI 0 "reg_operand" "")
4301         (if_then_else:QI (match_operand 1 "comparison_operator" "")
4302                          (match_operand:QI 2 "src_operand" "")
4303                          (match_operand:QI 3 "src_operand" "")))]
4304  ""
4305  "{ 
4306     enum rtx_code code = GET_CODE (operands[1]);
4307     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
4308     if (ccreg == NULL_RTX) FAIL;
4309     emit_insn (gen_rtx_SET (QImode, operands[0],
4310                             gen_rtx_IF_THEN_ELSE (QImode,
4311                                  gen_rtx (code, VOIDmode, ccreg, const0_rtx),
4312                                           operands[2], operands[3])));
4313     DONE;}")
4314                       
4315 (define_insn "*ldf_conditional"
4316   [(set (match_operand:QF 0 "reg_operand" "=f,f")
4317         (if_then_else:QF (match_operator 1 "comparison_operator"
4318                           [(reg:CC 21) (const_int 0)])
4319                          (match_operand:QF 2 "src_operand" "fHm,0")
4320                          (match_operand:QF 3 "src_operand" "0,fHm")))]
4321  ""
4322  "@
4323   ldf%1\\t%2,%0
4324   ldf%I1\\t%3,%0"
4325  [(set_attr "type" "binary")])
4326
4327 (define_insn "*ldf_conditional_noov"
4328   [(set (match_operand:QF 0 "reg_operand" "=f,f")
4329         (if_then_else:QF (match_operator 1 "comparison_operator"
4330                           [(reg:CC_NOOV 21) (const_int 0)])
4331                          (match_operand:QF 2 "src_operand" "fHm,0")
4332                          (match_operand:QF 3 "src_operand" "0,fHm")))]
4333  "GET_CODE (operands[1]) != LE
4334   && GET_CODE (operands[1]) != GE
4335   && GET_CODE (operands[1]) != LT
4336   && GET_CODE (operands[1]) != GT"
4337  "@
4338   ldf%1\\t%2,%0
4339   ldf%I1\\t%3,%0"
4340  [(set_attr "type" "binary")])
4341
4342 (define_expand "movqfcc"
4343   [(set (match_operand:QF 0 "reg_operand" "")
4344         (if_then_else:QF (match_operand 1 "comparison_operator" "")
4345                          (match_operand:QF 2 "src_operand" "")
4346                          (match_operand:QF 3 "src_operand" "")))]
4347  ""
4348  "{ 
4349     enum rtx_code code = GET_CODE (operands[1]);
4350     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
4351     if (ccreg == NULL_RTX) FAIL;
4352     emit_insn (gen_rtx_SET (QFmode, operands[0],
4353                             gen_rtx_IF_THEN_ELSE (QFmode,
4354                                  gen_rtx (code, VOIDmode, ccreg, const0_rtx),
4355                                           operands[2], operands[3])));
4356     DONE;}")
4357
4358 (define_insn "*ldhf_conditional"
4359   [(set (match_operand:HF 0 "reg_operand" "=h,h")
4360         (if_then_else:HF (match_operator 1 "comparison_operator"
4361                           [(reg:CC 21) (const_int 0)])
4362                          (match_operand:HF 2 "src_operand" "hH,0")
4363                          (match_operand:HF 3 "src_operand" "0,hH")))]
4364  ""
4365  "@
4366   ldf%1\\t%2,%0
4367   ldf%I1\\t%3,%0"
4368  [(set_attr "type" "binary")])
4369
4370 (define_insn "*ldhf_conditional_noov"
4371   [(set (match_operand:HF 0 "reg_operand" "=h,h")
4372         (if_then_else:HF (match_operator 1 "comparison_operator"
4373                           [(reg:CC_NOOV 21) (const_int 0)])
4374                          (match_operand:HF 2 "src_operand" "hH,0")
4375                          (match_operand:HF 3 "src_operand" "0,hH")))]
4376  "GET_CODE (operands[1]) != LE
4377   && GET_CODE (operands[1]) != GE
4378   && GET_CODE (operands[1]) != LT
4379   && GET_CODE (operands[1]) != GT"
4380  "@
4381   ldf%1\\t%2,%0
4382   ldf%I1\\t%3,%0"
4383  [(set_attr "type" "binary")])
4384
4385 (define_expand "movhfcc"
4386   [(set (match_operand:HF 0 "reg_operand" "")
4387         (if_then_else:HF (match_operand 1 "comparison_operator" "")
4388                          (match_operand:HF 2 "src_operand" "")
4389                          (match_operand:HF 3 "src_operand" "")))]
4390  ""
4391  "{ 
4392     enum rtx_code code = GET_CODE (operands[1]);
4393     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
4394     if (ccreg == NULL_RTX) FAIL;
4395     emit_insn (gen_rtx_SET (HFmode, operands[0],
4396                             gen_rtx_IF_THEN_ELSE (HFmode,
4397                                  gen_rtx (code, VOIDmode, ccreg, const0_rtx),
4398                                           operands[2], operands[3])));
4399     DONE;}")
4400
4401 (define_expand "seq"
4402  [(set (match_operand:QI 0 "reg_operand" "")
4403        (const_int 0))
4404   (set (match_dup 0)
4405        (if_then_else:QI (eq (match_dup 1) (const_int 0))
4406                         (const_int 1)
4407                         (match_dup 0)))]
4408  ""
4409  "operands[1] = c4x_gen_compare_reg (EQ, c4x_compare_op0, c4x_compare_op1);")
4410
4411 (define_expand "sne"
4412  [(set (match_operand:QI 0 "reg_operand" "")
4413        (const_int 0))
4414   (set (match_dup 0)
4415        (if_then_else:QI (ne (match_dup 1) (const_int 0))
4416                         (const_int 1)
4417                         (match_dup 0)))]
4418  ""
4419  "operands[1] = c4x_gen_compare_reg (NE, c4x_compare_op0, c4x_compare_op1);")
4420
4421 (define_expand "slt"
4422   [(set (match_operand:QI 0 "reg_operand" "")
4423         (const_int 0))
4424    (set (match_dup 0)
4425         (if_then_else:QI (lt (match_dup 1) (const_int 0))
4426                         (const_int 1)
4427                          (match_dup 0)))]
4428   ""
4429   "operands[1] = c4x_gen_compare_reg (LT, c4x_compare_op0, c4x_compare_op1);
4430    if (operands[1] == NULL_RTX) FAIL;")
4431
4432 (define_expand "sltu"
4433   [(set (match_operand:QI 0 "reg_operand" "")
4434         (const_int 0))
4435    (set (match_dup 0)
4436         (if_then_else:QI (ltu (match_dup 1) (const_int 0))
4437                         (const_int 1)
4438                          (match_dup 0)))]
4439   ""
4440   "operands[1] = c4x_gen_compare_reg (LTU, c4x_compare_op0, c4x_compare_op1);")
4441
4442 (define_expand "sgt"
4443   [(set (match_operand:QI 0 "reg_operand" "")
4444         (const_int 0))
4445    (set (match_dup 0)
4446         (if_then_else:QI (gt (match_dup 1) (const_int 0))
4447                         (const_int 1)
4448                          (match_dup 0)))]
4449   "" 
4450   "operands[1] = c4x_gen_compare_reg (GT, c4x_compare_op0, c4x_compare_op1);
4451    if (operands[1] == NULL_RTX) FAIL;")
4452
4453 (define_expand "sgtu"
4454   [(set (match_operand:QI 0 "reg_operand" "")
4455         (const_int 0))
4456    (set (match_dup 0)
4457         (if_then_else:QI (gtu (match_dup 1) (const_int 0))
4458                         (const_int 1)
4459                          (match_dup 0)))]
4460   ""
4461   "operands[1] = c4x_gen_compare_reg (GTU, c4x_compare_op0, c4x_compare_op1);")
4462
4463 (define_expand "sle"
4464   [(set (match_operand:QI 0 "reg_operand" "")
4465         (const_int 0))
4466    (set (match_dup 0)
4467         (if_then_else:QI (le (match_dup 1) (const_int 0))
4468                          (const_int 1)
4469                          (match_dup 0)))]
4470   ""
4471   "operands[1] = c4x_gen_compare_reg (LE, c4x_compare_op0, c4x_compare_op1);
4472    if (operands[1] == NULL_RTX) FAIL;")
4473
4474 (define_expand "sleu"
4475   [(set (match_operand:QI 0 "reg_operand" "")
4476         (const_int 0))
4477    (set (match_dup 0)
4478         (if_then_else:QI (leu (match_dup 1) (const_int 0))
4479                          (const_int 1)
4480                          (match_dup 0)))]
4481   ""
4482   "operands[1] = c4x_gen_compare_reg (LEU, c4x_compare_op0, c4x_compare_op1);")
4483
4484 (define_expand "sge"
4485   [(set (match_operand:QI 0 "reg_operand" "")
4486         (const_int 0))
4487    (set (match_dup 0)
4488         (if_then_else:QI (ge (match_dup 1) (const_int 0))
4489                          (const_int 1)
4490                          (match_dup 0)))]
4491   ""
4492   "operands[1] = c4x_gen_compare_reg (GE, c4x_compare_op0, c4x_compare_op1);
4493    if (operands[1] == NULL_RTX) FAIL;")
4494
4495 (define_expand "sgeu"
4496   [(set (match_operand:QI 0 "reg_operand" "")
4497         (const_int 0))
4498    (set (match_dup 0)
4499         (if_then_else:QI (geu (match_dup 1) (const_int 0))
4500                          (const_int 1)
4501                          (match_dup 0)))]
4502   ""
4503   "operands[1] = c4x_gen_compare_reg (GEU, c4x_compare_op0, c4x_compare_op1);")
4504
4505 (define_split
4506   [(set (match_operand:QI 0 "reg_operand" "")
4507         (match_operator:QI 1 "comparison_operator" [(reg:CC 21) (const_int 0)]))]
4508   "reload_completed"
4509   [(set (match_dup 0) (const_int 0))
4510    (set (match_dup 0)
4511         (if_then_else:QI (match_op_dup 1 [(reg:CC 21) (const_int 0)])
4512                         (const_int 1)
4513                          (match_dup 0)))]
4514   "")
4515
4516 (define_split
4517   [(set (match_operand:QI 0 "reg_operand" "")
4518         (match_operator:QI 1 "comparison_operator" [(reg:CC_NOOV 21) (const_int 0)]))]
4519   "reload_completed"
4520   [(set (match_dup 0) (const_int 0))
4521    (set (match_dup 0)
4522         (if_then_else:QI (match_op_dup 1 [(reg:CC_NOOV 21) (const_int 0)])
4523                          (const_int 1)
4524                          (match_dup 0)))]
4525   "")
4526
4527 (define_insn "*bu"
4528   [(set (pc)
4529         (unspec [(match_operand:QI 0 "reg_operand" "r")] UNSPEC_BU))]
4530   ""
4531   "bu%#\\t%0"
4532   [(set_attr "type" "jump")])
4533
4534 (define_expand "caseqi"
4535   [(parallel [(set (match_dup 5)
4536                    (minus:QI (match_operand:QI 0 "reg_operand" "")
4537                              (match_operand:QI 1 "src_operand" "")))
4538               (clobber (reg:CC_NOOV 21))])
4539    (set (reg:CC 21)
4540         (compare:CC (match_dup 5)
4541                     (match_operand:QI 2 "src_operand" "")))
4542    (set (pc)
4543         (if_then_else (gtu (reg:CC 21)
4544                            (const_int 0))
4545                       (label_ref (match_operand 4 "" ""))
4546                       (pc)))
4547    (parallel [(set (match_dup 6)
4548                    (plus:QI (match_dup 5)
4549                             (label_ref:QI (match_operand 3 "" ""))))
4550               (clobber (reg:CC_NOOV 21))])
4551    (set (match_dup 7)
4552         (mem:QI (match_dup 6)))
4553    (set (pc) (match_dup 7))]
4554   ""
4555   "operands[5] = gen_reg_rtx (QImode);
4556    operands[6] = gen_reg_rtx (QImode);
4557    operands[7] = gen_reg_rtx (QImode);")
4558                 
4559 ;
4560 ; PARALLEL FLOAT INSTRUCTIONS
4561 ;
4562 ; This patterns are under development
4563
4564 ;
4565 ; ABSF/STF
4566 ;
4567
4568 (define_insn "*absqf2_movqf_clobber"
4569   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4570         (abs:QF (match_operand:QF 1 "par_ind_operand" "S<>")))
4571    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4572         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4573    (clobber (reg:CC_NOOV 21))]
4574   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4575   "absf\\t%1,%0\\n||\\tstf\\t%3,%2"
4576   [(set_attr "type" "binarycc")])
4577
4578 ;
4579 ; ADDF/STF
4580 ;
4581
4582 (define_insn "*addqf3_movqf_clobber"
4583   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q,q")
4584         (plus:QF (match_operand:QF 1 "parallel_operand" "%q,S<>")
4585                  (match_operand:QF 2 "parallel_operand" "S<>,q")))
4586    (set (match_operand:QF 3 "par_ind_operand" "=S<>,S<>")
4587         (match_operand:QF 4 "ext_low_reg_operand" "q,q"))
4588    (clobber (reg:CC 21))]
4589   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4590   "addf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4591   [(set_attr "type" "binarycc,binarycc")])
4592
4593 ;
4594 ; FLOAT/STF
4595 ;
4596
4597 (define_insn "*floatqiqf2_movqf_clobber"
4598   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4599         (float:QF (match_operand:QI 1 "par_ind_operand" "S<>")))
4600    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4601         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4602    (clobber (reg:CC 21))]
4603   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4604   "float\\t%1,%0\\n||\\tstf\\t%3,%2"
4605   [(set_attr "type" "binarycc")])
4606
4607 ;
4608 ; MPYF/ADDF
4609 ;
4610
4611 (define_insn "*mulqf3_addqf3_clobber"
4612   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t,t,t,t")
4613         (mult:QF (match_operand:QF 1 "parallel_operand" "%S<>!V,q,S<>!V,q")
4614                  (match_operand:QF 2 "parallel_operand" "q,S<>!V,S<>!V,q")))
4615    (set (match_operand:QF 3 "r2r3_reg_operand" "=u,u,u,u")
4616         (plus:QF (match_operand:QF 4 "parallel_operand" "%S<>!V,q,q,S<>!V")
4617                  (match_operand:QF 5 "parallel_operand" "q,S<>!V,q,S<>!V")))
4618    (clobber (reg:CC_NOOV 21))]
4619   "TARGET_PARALLEL_MPY && valid_parallel_operands_6 (operands, QFmode)"
4620   "mpyf3\\t%2,%1,%0\\n||\\taddf3\\t%5,%4,%3"
4621   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4622
4623
4624 ;
4625 ; MPYF/STF
4626 ;
4627
4628 (define_insn "*mulqf3_movqf_clobber"
4629   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q,q")
4630         (mult:QF (match_operand:QF 1 "parallel_operand" "%q,S<>")
4631                  (match_operand:QF 2 "parallel_operand" "S<>,q")))
4632    (set (match_operand:QF 3 "par_ind_operand" "=S<>,S<>")
4633         (match_operand:QF 4 "ext_low_reg_operand" "q,q"))
4634    (clobber (reg:CC 21))]
4635   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4636   "mpyf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4637   [(set_attr "type" "binarycc,binarycc")])
4638
4639 ;
4640 ; MPYF/SUBF
4641 ;
4642
4643 (define_insn "*mulqf3_subqf3_clobber"
4644   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t,t")
4645         (mult:QF (match_operand:QF 1 "parallel_operand" "S<>,q")
4646                  (match_operand:QF 2 "parallel_operand" "q,S<>")))
4647    (set (match_operand:QF 3 "r2r3_reg_operand" "=u,u")
4648         (minus:QF (match_operand:QF 4 "parallel_operand" "S<>,q")
4649                   (match_operand:QF 5 "parallel_operand" "q,S<>")))
4650    (clobber (reg:CC 21))]
4651   "TARGET_PARALLEL_MPY && valid_parallel_operands_6 (operands, QFmode)"
4652   "mpyf3\\t%2,%1,%0\\n||\\tsubf3\\t%5,%4,%3"
4653   [(set_attr "type" "binarycc,binarycc")])
4654
4655 ;
4656 ; MPYF/LDF 0
4657 ;
4658
4659 (define_insn "*mulqf3_clrqf_clobber"
4660   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t")
4661         (mult:QF (match_operand:QF 1 "par_ind_operand" "%S<>")
4662                  (match_operand:QF 2 "par_ind_operand" "S<>")))
4663    (set (match_operand:QF 3 "r2r3_reg_operand" "=u")
4664         (match_operand:QF 4 "fp_zero_operand" "G"))
4665    (clobber (reg:CC 21))]
4666   "TARGET_PARALLEL_MPY"
4667   "mpyf3\\t%2,%1,%0\\n||\\tsubf3\\t%3,%3,%3"
4668   [(set_attr "type" "binarycc")])
4669
4670 ;
4671 ; NEGF/STF
4672 ;
4673
4674 (define_insn "*negqf2_movqf_clobber"
4675   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4676         (neg:QF (match_operand:QF 1 "par_ind_operand" "S<>")))
4677    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4678         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4679    (clobber (reg:CC 21))]
4680   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4681   "negf\\t%1,%0\\n||\\tstf\\t%3,%2"
4682   [(set_attr "type" "binarycc")])
4683
4684 ;
4685 ; SUBF/STF
4686 ;
4687
4688 (define_insn "*subqf3_movqf_clobber"
4689   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4690         (minus:QF (match_operand:QF 1 "ext_low_reg_operand" "q")
4691                   (match_operand:QF 2 "par_ind_operand" "S<>")))
4692    (set (match_operand:QF 3 "par_ind_operand" "=S<>")
4693         (match_operand:QF 4 "ext_low_reg_operand" "q"))
4694    (clobber (reg:CC 21))]
4695   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4696   "subf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4697   [(set_attr "type" "binarycc")])
4698
4699 ;
4700 ; TOIEEE/STF
4701 ;
4702
4703 (define_insn "*toieee_movqf_clobber"
4704   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4705         (unspec:QF [(match_operand:QF 1 "par_ind_operand" "S<>")] UNSPEC_TOIEEE))
4706    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4707         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4708    (clobber (reg:CC 21))]
4709   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4710   "toieee\\t%1,%0\\n||\\tstf\\t%3,%2"
4711   [(set_attr "type" "binarycc")])
4712
4713 ;
4714 ; FRIEEE/STF
4715 ;
4716
4717 (define_insn "*frieee_movqf_clobber"
4718   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4719         (unspec:QF [(match_operand:QF 1 "par_ind_operand" "S<>")] UNSPEC_FRIEEE))
4720    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4721         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4722    (clobber (reg:CC 21))]
4723   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4724   "frieee\\t%1,%0\\n||\\tstf\\t%3,%2"
4725   [(set_attr "type" "binarycc")])
4726
4727 ;
4728 ; PARALLEL INTEGER INSTRUCTIONS
4729 ;
4730
4731 ;
4732 ; ABSI/STI
4733 ;
4734
4735 (define_insn "*absqi2_movqi_clobber"
4736   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4737         (abs:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4738    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4739         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4740    (clobber (reg:CC_NOOV 21))]
4741   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4742   "absi\\t%1,%0\\n||\\tsti\\t%3,%2"
4743   [(set_attr "type" "binarycc")])
4744
4745 ;
4746 ; ADDI/STI
4747 ;
4748
4749 (define_insn "*addqi3_movqi_clobber"
4750   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4751         (plus:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4752                  (match_operand:QI 2 "parallel_operand" "S<>,q")))
4753    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4754         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4755    (clobber (reg:CC 21))]
4756   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4757   "addi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4758   [(set_attr "type" "binarycc,binarycc")])
4759
4760 ;
4761 ; AND/STI
4762 ;
4763
4764 (define_insn "*andqi3_movqi_clobber"
4765   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4766         (and:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4767                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4768    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4769         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4770    (clobber (reg:CC 21))]
4771   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4772   "and3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4773   [(set_attr "type" "binarycc,binarycc")])
4774
4775 ;
4776 ; ASH(left)/STI 
4777 ;
4778
4779 (define_insn "*ashlqi3_movqi_clobber"
4780   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4781         (ashift:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4782                    (match_operand:QI 2 "ext_low_reg_operand" "q")))
4783    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4784         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4785    (clobber (reg:CC 21))]
4786   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4787   "ash3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4788   [(set_attr "type" "binarycc")])
4789
4790 ;
4791 ; ASH(right)/STI 
4792 ;
4793
4794 (define_insn "*ashrqi3_movqi_clobber"
4795   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4796         (ashiftrt:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4797                      (neg:QI (match_operand:QI 2 "ext_low_reg_operand" "q"))))
4798    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4799         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4800    (clobber (reg:CC 21))]
4801   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4802   "ash3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4803   [(set_attr "type" "binarycc")])
4804
4805 ;
4806 ; FIX/STI
4807 ;
4808
4809 (define_insn "*fixqfqi2_movqi_clobber"
4810   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4811         (fix:QI (match_operand:QF 1 "par_ind_operand" "S<>")))
4812    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4813         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4814    (clobber (reg:CC 21))]
4815   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4816   "fix\\t%1,%0\\n||\\tsti\\t%3,%2"
4817   [(set_attr "type" "binarycc")])
4818
4819 ;
4820 ; LSH(right)/STI 
4821 ;
4822
4823 (define_insn "*lshrqi3_movqi_clobber"
4824   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4825         (lshiftrt:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4826                      (neg:QI (match_operand:QI 2 "ext_low_reg_operand" "q"))))
4827    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4828         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4829    (clobber (reg:CC 21))]
4830   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4831   "lsh3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4832   [(set_attr "type" "binarycc")])
4833
4834 ;
4835 ; MPYI/ADDI
4836 ;
4837
4838 (define_insn "*mulqi3_addqi3_clobber"
4839   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t,t,t,t")
4840         (mult:QI (match_operand:QI 1 "parallel_operand" "%S<>!V,q,S<>!V,q")
4841                  (match_operand:QI 2 "parallel_operand" "q,S<>!V,S<>!V,q")))
4842    (set (match_operand:QI 3 "r2r3_reg_operand" "=u,u,u,u")
4843         (plus:QI (match_operand:QI 4 "parallel_operand" "%S<>!V,q,q,S<>!V")
4844                  (match_operand:QI 5 "parallel_operand" "q,S<>!V,q,S<>!V")))
4845    (clobber (reg:CC 21))]
4846   "TARGET_PARALLEL_MPY && TARGET_MPYI 
4847    && valid_parallel_operands_6 (operands, QImode)"
4848   "mpyi3\\t%2,%1,%0\\n||\\taddi3\\t%5,%4,%3"
4849   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4850
4851
4852 ;
4853 ; MPYI/STI
4854 ;
4855
4856 (define_insn "*mulqi3_movqi_clobber"
4857   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4858         (mult:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4859                  (match_operand:QI 2 "parallel_operand" "S<>,q")))
4860    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4861         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4862    (clobber (reg:CC 21))]
4863   "TARGET_PARALLEL && TARGET_MPYI
4864    && valid_parallel_operands_5 (operands, QImode)"
4865   "mpyi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4866   [(set_attr "type" "binarycc,binarycc")])
4867
4868 ;
4869 ; MPYI/SUBI
4870 ;
4871
4872 (define_insn "*mulqi3_subqi3_clobber"
4873   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t,t")
4874         (mult:QI (match_operand:QI 1 "parallel_operand" "S<>,q")
4875                  (match_operand:QI 2 "parallel_operand" "q,S<>")))
4876    (set (match_operand:QI 3 "r2r3_reg_operand" "=u,u")
4877         (minus:QI (match_operand:QI 4 "parallel_operand" "S<>,q")
4878                   (match_operand:QI 5 "parallel_operand" "q,S<>")))
4879    (clobber (reg:CC 21))]
4880   "TARGET_PARALLEL_MPY && TARGET_MPYI
4881    && valid_parallel_operands_6 (operands, QImode)"
4882   "mpyi3\\t%2,%1,%0\\n||\\tsubi3\\t%5,%4,%3"
4883   [(set_attr "type" "binarycc,binarycc")])
4884
4885 ;
4886 ; MPYI/LDI 0
4887 ;
4888
4889 (define_insn "*mulqi3_clrqi_clobber"
4890   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t")
4891         (mult:QI (match_operand:QI 1 "par_ind_operand" "%S<>")
4892                  (match_operand:QI 2 "par_ind_operand" "S<>")))
4893    (set (match_operand:QI 3 "r2r3_reg_operand" "=u")
4894         (const_int 0))
4895    (clobber (reg:CC 21))]
4896   "TARGET_PARALLEL_MPY && TARGET_MPYI"
4897   "mpyi3\\t%2,%1,%0\\n||\\tsubi3\\t%3,%3,%3"
4898   [(set_attr "type" "binarycc")])
4899
4900 ;
4901 ; NEGI/STI
4902 ;
4903
4904 (define_insn "*negqi2_movqi_clobber"
4905   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4906         (neg:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4907    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4908         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4909    (clobber (reg:CC 21))]
4910   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4911   "negi\\t%1,%0\\n||\\tsti\\t%3,%2"
4912   [(set_attr "type" "binarycc")])
4913
4914 ;
4915 ; NOT/STI
4916 ;
4917
4918 (define_insn "*notqi2_movqi_clobber"
4919   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4920         (not:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4921    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4922         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4923    (clobber (reg:CC 21))]
4924   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4925   "not\\t%1,%0\\n||\\tsti\\t%3,%2"
4926   [(set_attr "type" "binarycc")])
4927
4928 ;
4929 ; OR/STI
4930 ;
4931
4932 (define_insn "*iorqi3_movqi_clobber"
4933   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4934         (ior:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4935                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4936    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4937         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4938    (clobber (reg:CC 21))]
4939   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4940   "or3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4941   [(set_attr "type" "binarycc,binarycc")])
4942
4943 ;
4944 ; SUBI/STI
4945 ;
4946
4947 (define_insn "*subqi3_movqi_clobber"
4948   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4949         (minus:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4950                   (match_operand:QI 2 "ext_low_reg_operand" "q")))
4951    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4952         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4953    (clobber (reg:CC 21))]
4954   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4955   "subi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4956   [(set_attr "type" "binarycc")])
4957
4958 ;
4959 ; XOR/STI
4960 ;
4961
4962 (define_insn "*xorqi3_movqi_clobber"
4963   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4964         (xor:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4965                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4966    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4967         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4968    (clobber (reg:CC 21))]
4969   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4970   "xor3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4971   [(set_attr "type" "binarycc,binarycc")])
4972
4973 ;
4974 ; BRANCH/CALL INSTRUCTIONS
4975 ;
4976
4977 ;
4978 ; Branch instructions
4979 ;
4980 (define_insn "*b"
4981   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4982                            [(reg:CC 21) (const_int 0)])
4983                            (label_ref (match_operand 1 "" ""))
4984                            (pc)))]
4985   ""
4986   "*
4987    return c4x_output_cbranch (\"b%0\", insn);"
4988   [(set_attr "type" "jmpc")])
4989
4990 (define_insn "*b_rev"
4991   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4992                            [(reg:CC 21) (const_int 0)])
4993                            (pc)
4994                            (label_ref (match_operand 1 "" ""))))]
4995   ""
4996   "*
4997    return c4x_output_cbranch (\"b%I0\", insn);"
4998   [(set_attr "type" "jmpc")])
4999
5000 (define_insn "*b_noov"
5001   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
5002                            [(reg:CC_NOOV 21) (const_int 0)])
5003                            (label_ref (match_operand 1 "" ""))
5004                            (pc)))]
5005  "GET_CODE (operands[0]) != LE
5006   && GET_CODE (operands[0]) != GE
5007   && GET_CODE (operands[0]) != LT
5008   && GET_CODE (operands[0]) != GT"
5009   "*
5010    return c4x_output_cbranch (\"b%0\", insn);"
5011   [(set_attr "type" "jmpc")])
5012
5013 (define_insn "*b_noov_rev"
5014   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
5015                            [(reg:CC_NOOV 21) (const_int 0)])
5016                            (pc)
5017                            (label_ref (match_operand 1 "" ""))))]
5018  "GET_CODE (operands[0]) != LE
5019   && GET_CODE (operands[0]) != GE
5020   && GET_CODE (operands[0]) != LT
5021   && GET_CODE (operands[0]) != GT"
5022   "*
5023    return c4x_output_cbranch (\"b%I0\", insn);"
5024   [(set_attr "type" "jmpc")])
5025
5026 (define_expand "beq"
5027   [(set (pc) (if_then_else (eq (match_dup 1) (const_int 0))
5028                            (label_ref (match_operand 0 "" ""))
5029                            (pc)))]
5030   ""
5031   "operands[1] = c4x_gen_compare_reg (EQ, c4x_compare_op0, c4x_compare_op1);")
5032
5033 (define_expand "bne"
5034   [(set (pc) (if_then_else (ne (match_dup 1) (const_int 0))
5035                            (label_ref (match_operand 0 "" ""))
5036                            (pc)))]
5037   ""
5038   "operands[1] = c4x_gen_compare_reg (NE, c4x_compare_op0, c4x_compare_op1);")
5039
5040 (define_expand "blt"
5041   [(set (pc) (if_then_else (lt (match_dup 1) (const_int 0))
5042                            (label_ref (match_operand 0 "" ""))
5043                            (pc)))]
5044   ""
5045   "operands[1] = c4x_gen_compare_reg (LT, c4x_compare_op0, c4x_compare_op1);
5046    if (operands[1] == NULL_RTX) FAIL;")
5047
5048 (define_expand "bltu"
5049   [(set (pc) (if_then_else (ltu (match_dup 1) (const_int 0))
5050                            (label_ref (match_operand 0 "" ""))
5051                            (pc)))]
5052   ""
5053   "operands[1] = c4x_gen_compare_reg (LTU, c4x_compare_op0, c4x_compare_op1);")
5054
5055 (define_expand "bgt"
5056   [(set (pc) (if_then_else (gt (match_dup 1) (const_int 0))
5057                            (label_ref (match_operand 0 "" ""))
5058                            (pc)))]
5059   ""
5060   "operands[1] = c4x_gen_compare_reg (GT, c4x_compare_op0, c4x_compare_op1);
5061    if (operands[1] == NULL_RTX) FAIL;")
5062
5063 (define_expand "bgtu"
5064   [(set (pc) (if_then_else (gtu (match_dup 1) (const_int 0))
5065                            (label_ref (match_operand 0 "" ""))
5066                            (pc)))]
5067   ""
5068   "operands[1] = c4x_gen_compare_reg (GTU, c4x_compare_op0, c4x_compare_op1);")
5069
5070 (define_expand "ble"
5071   [(set (pc) (if_then_else (le (match_dup 1) (const_int 0))
5072                            (label_ref (match_operand 0 "" ""))
5073                            (pc)))]
5074   ""
5075   "operands[1] = c4x_gen_compare_reg (LE, c4x_compare_op0, c4x_compare_op1);
5076    if (operands[1] == NULL_RTX) FAIL;")
5077
5078 (define_expand "bleu"
5079   [(set (pc) (if_then_else (leu (match_dup 1) (const_int 0))
5080                            (label_ref (match_operand 0 "" ""))
5081                            (pc)))]
5082   ""
5083   "operands[1] = c4x_gen_compare_reg (LEU, c4x_compare_op0, c4x_compare_op1);")
5084
5085 (define_expand "bge"
5086   [(set (pc) (if_then_else (ge (match_dup 1) (const_int 0))
5087                            (label_ref (match_operand 0 "" ""))
5088                            (pc)))]
5089   ""
5090   "operands[1] = c4x_gen_compare_reg (GE, c4x_compare_op0, c4x_compare_op1);
5091    if (operands[1] == NULL_RTX) FAIL;")
5092
5093 (define_expand "bgeu"
5094   [(set (pc) (if_then_else (geu (match_dup 1) (const_int 0))
5095                            (label_ref (match_operand 0 "" ""))
5096                            (pc)))]
5097   ""
5098   "operands[1] = c4x_gen_compare_reg (GEU, c4x_compare_op0, c4x_compare_op1);")
5099
5100 (define_insn "*b_reg"
5101  [(set (pc) (match_operand:QI 0 "reg_operand" "r"))]
5102  ""
5103  "bu%#\\t%0"
5104   [(set_attr "type" "jump")])
5105
5106 (define_expand "indirect_jump"
5107  [(set (pc) (match_operand:QI 0 "reg_operand" ""))]
5108  ""
5109  "")
5110
5111 (define_insn "tablejump"
5112   [(set (pc) (match_operand:QI 0 "src_operand" "r"))
5113    (use (label_ref (match_operand 1 "" "")))]
5114   ""
5115   "bu%#\\t%0"
5116   [(set_attr "type" "jump")])
5117
5118 ;
5119 ; CALL
5120 ;
5121 (define_insn "*call_c3x"
5122  [(call (mem:QI (match_operand:QI 0 "call_address_operand" "Ur"))
5123         (match_operand:QI 1 "general_operand" ""))
5124   (clobber (reg:QI 31))]
5125   ;; Operand 1 not really used on the C4x.  The C30 doesn't have reg 31.
5126
5127   "TARGET_C3X"
5128   "call%U0\\t%C0"
5129   [(set_attr "type" "call")])
5130
5131 ; LAJ requires R11 (31) for the return address
5132 (define_insn "*laj"
5133  [(call (mem:QI (match_operand:QI 0 "call_address_operand" "Ur"))
5134         (match_operand:QI 1 "general_operand" ""))
5135   (clobber (reg:QI 31))]
5136   ;; Operand 1 not really used on the C4x.
5137
5138   "! TARGET_C3X"
5139   "*
5140    if (final_sequence)
5141      return c4x_check_laj_p (insn)
5142          ? \"nop\\n\\tlaj%U0\\t%C0\" : \"laj%U0\\t%C0\";
5143    else
5144      return \"call%U0\\t%C0\";"
5145   [(set_attr "type" "laj")])
5146
5147 (define_expand "call"
5148  [(parallel [(call (match_operand:QI 0 "" "")
5149                    (match_operand:QI 1 "general_operand" ""))
5150              (clobber (reg:QI 31))])]
5151  ""
5152  "
5153 {
5154   if (GET_CODE (operands[0]) == MEM
5155       && ! call_address_operand (XEXP (operands[0], 0), Pmode))
5156     operands[0] = gen_rtx_MEM (GET_MODE (operands[0]),
5157                                force_reg (Pmode, XEXP (operands[0], 0)));
5158 }")
5159
5160 (define_insn "nodb_call"
5161  [(call (mem:QI (match_operand:QI 0 "call_address_operand" "Ur"))
5162         (const_int 0))]
5163   ""
5164   "call%U0\\t%C0"
5165   [(set_attr "type" "call")])
5166
5167 (define_insn "*callv_c3x"
5168  [(set (match_operand 0 "" "=r")
5169        (call (mem:QI (match_operand:QI 1 "call_address_operand" "Ur"))
5170              (match_operand:QI 2 "general_operand" "")))
5171   (clobber (reg:QI 31))]
5172   ;; Operand 0 and 2 not really used for the C4x. 
5173   ;; The C30 doesn't have reg 31.
5174
5175   "TARGET_C3X"
5176   "call%U1\\t%C1"
5177   [(set_attr "type" "call")])
5178
5179 ; LAJ requires R11 (31) for the return address
5180 (define_insn "*lajv"
5181  [(set (match_operand 0 "" "=r")
5182        (call (mem:QI (match_operand:QI 1 "call_address_operand" "Ur"))
5183              (match_operand:QI 2 "general_operand" "")))
5184   (clobber (reg:QI 31))]
5185   ;; Operand 0 and 2 not really used in the C30 instruction.
5186
5187   "! TARGET_C3X"
5188   "*
5189    if (final_sequence)
5190      return c4x_check_laj_p (insn)
5191          ? \"nop\\n\\tlaj%U1\\t%C1\" : \"laj%U1\\t%C1\";
5192    else
5193      return \"call%U1\\t%C1\";"
5194   [(set_attr "type" "laj")])
5195
5196 (define_expand "call_value"
5197  [(parallel [(set (match_operand 0 "" "")
5198                   (call (match_operand:QI 1 "" "")
5199                         (match_operand:QI 2 "general_operand" "")))
5200              (clobber (reg:QI 31))])]
5201  ""
5202  "
5203 {
5204   if (GET_CODE (operands[0]) == MEM
5205       && ! call_address_operand (XEXP (operands[1], 0), Pmode))
5206     operands[0] = gen_rtx_MEM (GET_MODE (operands[1]),
5207                                force_reg (Pmode, XEXP (operands[1], 0)));
5208 }")
5209
5210 (define_insn "return"
5211   [(return)]
5212   "! c4x_null_epilogue_p ()"
5213   "rets"
5214   [(set_attr "type" "rets")])
5215
5216 (define_insn "return_from_epilogue"
5217   [(return)]
5218   "reload_completed && ! c4x_interrupt_function_p ()"
5219   "rets"
5220   [(set_attr "type" "rets")])
5221
5222 (define_insn "return_from_interrupt_epilogue"
5223   [(return)]
5224   "reload_completed && c4x_interrupt_function_p ()"
5225   "reti"
5226   [(set_attr "type" "rets")])
5227
5228 (define_insn "*return_cc"
5229   [(set (pc)
5230         (if_then_else (match_operator 0 "comparison_operator"
5231                       [(reg:CC 21) (const_int 0)])
5232                       (return)
5233                        (pc)))]
5234   "! c4x_null_epilogue_p ()"
5235   "rets%0"
5236   [(set_attr "type" "rets")])
5237
5238 (define_insn "*return_cc_noov"
5239   [(set (pc)
5240         (if_then_else (match_operator 0 "comparison_operator"
5241                       [(reg:CC_NOOV 21) (const_int 0)])
5242                       (return)
5243                        (pc)))]
5244   "GET_CODE (operands[0]) != LE
5245    && GET_CODE (operands[0]) != GE
5246    && GET_CODE (operands[0]) != LT
5247    && GET_CODE (operands[0]) != GT
5248    && ! c4x_null_epilogue_p ()"
5249   "rets%0"
5250   [(set_attr "type" "rets")])
5251
5252 (define_insn "*return_cc_inverse"
5253   [(set (pc)
5254         (if_then_else (match_operator 0 "comparison_operator"
5255                       [(reg:CC 21) (const_int 0)])
5256                        (pc)
5257                       (return)))]
5258   "! c4x_null_epilogue_p ()"
5259   "rets%I0"
5260   [(set_attr "type" "rets")])
5261
5262 (define_insn "*return_cc_noov_inverse"
5263   [(set (pc)
5264         (if_then_else (match_operator 0 "comparison_operator"
5265                       [(reg:CC_NOOV 21) (const_int 0)])
5266                        (pc)
5267                       (return)))]
5268   "GET_CODE (operands[0]) != LE
5269    && GET_CODE (operands[0]) != GE
5270    && GET_CODE (operands[0]) != LT
5271    && GET_CODE (operands[0]) != GT
5272    && ! c4x_null_epilogue_p ()"
5273   "rets%I0"
5274   [(set_attr "type" "rets")])
5275
5276 (define_insn "jump"
5277   [(set (pc) (label_ref (match_operand 0 "" "")))]
5278   ""
5279   "br%#\\t%l0"
5280   [(set_attr "type" "jump")])
5281
5282 (define_insn "trap"
5283   [(trap_if (const_int 1) (const_int 31))]
5284   ""
5285   "trapu\\t31"
5286   [(set_attr "type" "call")])
5287
5288 (define_expand "conditional_trap"
5289  [(trap_if (match_operand 0 "comparison_operator" "")
5290            (match_operand 1 "const_int_operand" ""))]
5291  ""
5292  "{
5293     enum rtx_code code = GET_CODE (operands[1]);
5294     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
5295     if (ccreg == NULL_RTX) FAIL;
5296     if (GET_MODE (ccreg) == CCmode)
5297       emit_insn (gen_cond_trap_cc (operands[0], operands[1]));
5298     else 
5299       emit_insn (gen_cond_trap_cc_noov (operands[0], operands[1]));
5300     DONE;}")
5301
5302 (define_insn "cond_trap_cc"
5303   [(trap_if (match_operator 0 "comparison_operator"
5304             [(reg:CC 21) (const_int 0)])
5305             (match_operand 1 "const_int_operand" ""))]
5306   ""
5307   "trap%0\\t31"
5308   [(set_attr "type" "call")])
5309
5310 (define_insn "cond_trap_cc_noov"
5311   [(trap_if (match_operator 0 "comparison_operator"
5312             [(reg:CC_NOOV 21) (const_int 0)])
5313             (match_operand 1 "const_int_operand" ""))]
5314   "GET_CODE (operands[0]) != LE
5315    && GET_CODE (operands[0]) != GE
5316    && GET_CODE (operands[0]) != LT
5317    && GET_CODE (operands[0]) != GT"
5318   "trap%0\\t31"
5319   [(set_attr "type" "call")])
5320
5321 ;
5322 ; DBcond
5323 ;
5324 ; Note we have to emit a dbu instruction if there are no delay slots
5325 ; to fill.
5326 ; Also note that GCC will try to reverse a loop to see if it can
5327 ; utilize this instruction.  However, if there are more than one
5328 ; memory reference in the loop, it cannot guarantee that reversing
5329 ; the loop will work :(  (see check_dbra_loop() in loop.c)
5330 ; Note that the C3x only decrements the 24 LSBs of the address register
5331 ; and the 8 MSBs are untouched.  The C4x uses all 32-bits.  We thus
5332 ; have an option to disable this instruction.
5333 (define_insn "*db"
5334   [(set (pc)
5335         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
5336                           (const_int 0))
5337                       (label_ref (match_operand 1 "" ""))
5338                       (pc)))
5339    (set (match_dup 0)
5340         (plus:QI (match_dup 0)
5341                  (const_int -1)))
5342    (use (reg:QI 20))
5343    (clobber (reg:CC_NOOV 21))]
5344   "TARGET_DB && TARGET_LOOP_UNSIGNED"
5345   "*
5346   if (which_alternative == 0)
5347     return \"dbu%#\\t%0,%l1\";
5348   else if (which_alternative == 1)
5349     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5350   else if (which_alternative == 2)
5351     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5352   else
5353     return c4x_output_cbranch (\"push\\tr0\\n\\tldi\\t%0,r0\\n\\tsubi\\t1,r0\\n\\tsti\\tr0,%0\\n\\tpop\\tr0\\n\\tbhs\", insn);
5354   "
5355   [(set_attr "type" "db,jmpc,jmpc,jmpc")])
5356
5357 (define_insn "*db_noclobber"
5358   [(set (pc)
5359         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "+a")
5360                           (const_int 0))
5361                       (label_ref (match_operand 1 "" ""))
5362                       (pc)))
5363    (set (match_dup 0)
5364         (plus:QI (match_dup 0)
5365                  (const_int -1)))]
5366   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5367   "dbu%#\\t%0,%l1"
5368   [(set_attr "type" "db")])
5369
5370 (define_split
5371   [(set (pc)
5372         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "")
5373                           (const_int 0))
5374                       (label_ref (match_operand 1 "" ""))
5375                       (pc)))
5376    (set (match_dup 0)
5377         (plus:QI (match_dup 0)
5378                  (const_int -1)))
5379    (use (reg:QI 20))
5380    (clobber (reg:CC_NOOV 21))]
5381   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5382   [(parallel [(set (pc)
5383                    (if_then_else (ne (match_dup 0)
5384                                      (const_int 0))
5385                                  (label_ref (match_dup 1))
5386                                  (pc)))
5387               (set (match_dup 0)
5388                    (plus:QI (match_dup 0)
5389                             (const_int -1)))])]
5390   "")
5391   
5392
5393 ; This insn is used for some loop tests, typically loops reversed when
5394 ; strength reduction is used.  It is actually created when the instruction
5395 ; combination phase combines the special loop test.  Since this insn
5396 ; is both a jump insn and has an output, it must deal with its own
5397 ; reloads, hence the `m' constraints. 
5398
5399 ; The C4x does the decrement and then compares the result against zero.
5400 ; It branches if the result was greater than or equal to zero.
5401 ; In the RTL the comparison and decrement are assumed to happen
5402 ; at the same time so we bias the iteration counter with by -1
5403 ; when we make the test.
5404 (define_insn "decrement_and_branch_until_zero"
5405   [(set (pc)
5406         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
5407                                    (const_int -1))
5408                           (const_int 0))
5409                       (label_ref (match_operand 1 "" ""))
5410                       (pc)))
5411    (set (match_dup 0)
5412         (plus:QI (match_dup 0)
5413                  (const_int -1)))
5414    (use (reg:QI 20))
5415    (clobber (reg:CC_NOOV 21))]
5416   "TARGET_DB && (find_reg_note (insn, REG_NONNEG, 0) || TARGET_LOOP_UNSIGNED)"
5417   "*
5418   if (which_alternative == 0)
5419     return \"dbu%#\\t%0,%l1\";
5420   else if (which_alternative == 1)
5421     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5422   else if (which_alternative == 2)
5423     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5424   else
5425     return c4x_output_cbranch (\"push\\tr0\\n\\tldi\\t%0,r0\\n\\tsubi\\t1,r0\\n\\tsti\\tr0,%0\\n\\tpop\\tr0\\n\\tbhs\", insn);
5426   "
5427   [(set_attr "type" "db,jmpc,jmpc,jmpc")])
5428
5429 (define_insn "*decrement_and_branch_until_zero_noclobber"
5430   [(set (pc)
5431         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a")
5432                                    (const_int -1))
5433                           (const_int 0))
5434                       (label_ref (match_operand 1 "" ""))
5435                       (pc)))
5436    (set (match_dup 0)
5437         (plus:QI (match_dup 0)
5438                  (const_int -1)))]
5439   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5440   "dbu%#\\t%0,%l1"
5441   [(set_attr "type" "db")])
5442
5443 (define_split
5444   [(set (pc)
5445         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "")
5446                                    (const_int -1))
5447                           (const_int 0))
5448                       (label_ref (match_operand 1 "" ""))
5449                       (pc)))
5450    (set (match_dup 0)
5451         (plus:QI (match_dup 0)
5452                  (const_int -1)))
5453    (use (reg:QI 20))
5454    (clobber (reg:CC_NOOV 21))]
5455   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5456   [(parallel [(set (pc)
5457                    (if_then_else (ge (plus:QI (match_dup 0)
5458                                               (const_int -1))
5459                                      (const_int 0))
5460                                  (label_ref (match_dup 1))
5461                                  (pc)))
5462               (set (match_dup 0)
5463                    (plus:QI (match_dup 0)
5464                             (const_int -1)))])]
5465   "")
5466
5467 ;
5468 ; MISC INSTRUCTIONS
5469 ;
5470
5471 ;
5472 ; NOP
5473 ;
5474 (define_insn "nop"
5475   [(const_int 0)]
5476   ""
5477   "nop")
5478 ; Default to misc type attr.
5479
5480 (define_insn "return_indirect_internal"
5481   [(return)
5482    (use (match_operand:QI 0 "reg_operand" ""))]
5483   "reload_completed"                           
5484   "bu%#\\t%0"
5485   [(set_attr "type" "jump")])
5486
5487 (define_expand "prologue"
5488   [(const_int 1)]
5489   ""                           
5490   "c4x_expand_prologue (); DONE;")
5491
5492 (define_expand "epilogue"
5493   [(const_int 1)]
5494   ""
5495   "c4x_expand_epilogue (); DONE;")
5496
5497 ;
5498 ; RPTB
5499 ;
5500 (define_insn "rptb_top"
5501   [(use (label_ref (match_operand 0 "" "")))
5502    (use (label_ref (match_operand 1 "" "")))
5503    (clobber (reg:QI 25))
5504    (clobber (reg:QI 26))]
5505   ""
5506   "*
5507    return ! final_sequence && c4x_rptb_rpts_p (insn, operands[0])
5508          ? \"rpts\\trc\" : \"rptb%#\\t%l1-1\";
5509   "
5510   [(set_attr "type" "repeat_top")])
5511
5512 (define_insn "rpts_top"
5513   [(unspec [(use (label_ref (match_operand 0 "" "")))
5514             (use (label_ref (match_operand 1 "" "")))] UNSPEC_RPTS)
5515    (clobber (reg:QI 25))
5516    (clobber (reg:QI 26))]
5517   ""
5518   "*
5519    return ! final_sequence && c4x_rptb_rpts_p (insn, operands[0])
5520          ? \"rpts\\trc\" : \"rptb%#\\t%l1-1\";
5521   "
5522   [(set_attr "type" "repeat")])
5523
5524 ; This pattern needs to be emitted at the start of the loop to
5525 ; say that RS and RE are loaded.
5526 (define_insn "rptb_init"
5527   [(unspec [(match_operand:QI 0 "register_operand" "va")] UNSPEC_RPTB_INIT)
5528    (clobber (reg:QI 25))
5529    (clobber (reg:QI 26))]
5530   ""
5531   ""
5532   [(set_attr "type" "repeat")])
5533
5534
5535 ; operand 0 is the loop count pseudo register
5536 ; operand 1 is the number of loop iterations or 0 if it is unknown
5537 ; operand 2 is the maximum number of loop iterations
5538 ; operand 3 is the number of levels of enclosed loops
5539 (define_expand "doloop_begin"
5540   [(use (match_operand 0 "register_operand" ""))
5541    (use (match_operand:QI 1 "const_int_operand" ""))
5542    (use (match_operand:QI 2 "const_int_operand" ""))
5543    (use (match_operand:QI 3 "const_int_operand" ""))]
5544   ""
5545   "if (INTVAL (operands[3]) > 1 || ! TARGET_RPTB)
5546      FAIL;
5547    emit_insn (gen_rptb_init (operands[0]));
5548    DONE;
5549   ")
5550
5551
5552 ; The RS (25) and RE (26) registers must be unviolate from the top of the loop
5553 ; to here.
5554 (define_insn "rptb_end"
5555   [(set (pc)
5556         (if_then_else (ge (match_operand:QI 0 "register_operand" "+v,?a,!*d,!*x*k,!m")
5557                           (const_int 0))
5558                       (label_ref (match_operand 1 "" ""))
5559                       (pc)))
5560    (set (match_dup 0)
5561         (plus:QI (match_dup 0)
5562                  (const_int -1)))
5563    (use (reg:QI 25))
5564    (use (reg:QI 26))
5565    (use (reg:QI 20))
5566    (clobber (reg:CC_NOOV 21))]
5567   ""
5568   "*
5569    if (which_alternative == 0)
5570      return c4x_rptb_nop_p (insn) ? \"nop\" : \"\";
5571    else if (which_alternative == 1 && TARGET_DB)
5572      return \"dbu%#\\t%0,%l1\";
5573    else if (which_alternative == 2)
5574      return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5575    else if (which_alternative == 3 || (which_alternative == 1 && ! TARGET_DB))
5576      return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5577    else
5578      return c4x_output_cbranch (\"push\\tr0\\n\\tldi\\t%0,r0\\n\\tsubi\\t1,r0\\n\\tsti\\tr0,%0\\n\\tpop\\tr0\\n\\tbhs\", insn);
5579   "
5580   [(set_attr "type" "repeat,db,jmpc,jmpc,jmpc")])
5581
5582 (define_split
5583    [(set (pc)
5584         (if_then_else (ge (match_operand:QI 0 "addr_reg_operand" "")
5585                           (const_int 0))
5586                       (label_ref (match_operand 1 "" ""))
5587                       (pc)))
5588    (set (match_dup 0)
5589         (plus:QI (match_dup 0)
5590                  (const_int -1)))
5591    (use (match_operand:QI 2 "const_int_operand" ""))
5592    (use (match_operand:QI 3 "const_int_operand" ""))
5593    (use (match_operand:QI 4 "const_int_operand" ""))
5594    (use (reg:QI 25))
5595    (use (reg:QI 26))
5596    (use (reg:QI 20))
5597    (clobber (reg:CC_NOOV 21))]
5598   "reload_completed"
5599   [(parallel [(set (pc)
5600                    (if_then_else (ge (match_dup 0)
5601                                      (const_int 0))
5602                                  (label_ref (match_dup 1))
5603                                  (pc)))
5604               (set (match_dup 0)
5605                    (plus:QI (match_dup 0)
5606                             (const_int -1)))])]
5607   "")
5608
5609 ; operand 0 is the loop count pseudo register
5610 ; operand 1 is the number of loop iterations or 0 if it is unknown
5611 ; operand 2 is the maximum number of loop iterations
5612 ; operand 3 is the number of levels of enclosed loops
5613 ; operand 4 is the label to jump to at the top of the loop
5614 (define_expand "doloop_end"
5615   [(use (match_operand 0 "register_operand" ""))
5616    (use (match_operand:QI 1 "const_int_operand" ""))
5617    (use (match_operand:QI 2 "const_int_operand" ""))
5618    (use (match_operand:QI 3 "const_int_operand" ""))
5619    (use (label_ref (match_operand 4 "" "")))]
5620   ""
5621   "if (! TARGET_LOOP_UNSIGNED 
5622        && (unsigned HOST_WIDE_INT) INTVAL (operands[2]) > ((unsigned) 1 << 31))
5623      FAIL;
5624    if (INTVAL (operands[3]) > 1 || ! TARGET_RPTB)
5625      {
5626         /* The C30 maximum iteration count for DB is 2^24.  */
5627         if (! TARGET_DB)
5628           FAIL;
5629         emit_jump_insn (gen_decrement_and_branch_until_zero (operands[0],
5630                                                              operands[4]));
5631         DONE;
5632      }
5633     emit_jump_insn (gen_rptb_end (operands[0], operands[4]));
5634     DONE;
5635   ")
5636
5637 ; The current low overhead looping code is naff and is not failsafe
5638 ; If you want RTPB instructions to be generated, apply the patches
5639 ; from www.elec.canterbury.ac.nz/c4x.  This will utilize the
5640 ; doloop_begin and doloop_end patterns in this MD.
5641 (define_expand "decrement_and_branch_on_count"
5642   [(parallel [(set (pc)
5643                    (if_then_else (ge (match_operand:QI 0 "register_operand" "")
5644                                      (const_int 0))
5645                                  (label_ref (match_operand 1 "" ""))
5646                                  (pc)))
5647               (set (match_dup 0)
5648                    (plus:QI (match_dup 0)
5649                             (const_int -1)))
5650               (use (reg:QI 25))
5651               (use (reg:QI 26))
5652               (clobber (reg:CC_NOOV 21))])]
5653   "0"
5654   "")
5655
5656 (define_expand "movstrqi_small2"
5657   [(parallel [(set (mem:BLK (match_operand:BLK 0 "src_operand" ""))
5658                    (mem:BLK (match_operand:BLK 1 "src_operand" "")))
5659               (use (match_operand:QI 2 "immediate_operand" ""))
5660               (use (match_operand:QI 3 "immediate_operand" ""))
5661               (clobber (match_operand:QI 4 "ext_low_reg_operand" ""))])]
5662   ""
5663   "
5664  {
5665     rtx src, dst, tmp;
5666     rtx src_mem, dst_mem;    
5667     int len;
5668     int i;
5669
5670     dst = operands[0];
5671     src = operands[1];
5672     len = INTVAL (operands[2]);
5673     tmp = operands[4];
5674
5675     src_mem = gen_rtx_MEM (QImode, src);
5676     dst_mem = gen_rtx_MEM (QImode, dst);
5677
5678     if (TARGET_PARALLEL)
5679       {
5680         emit_insn (gen_movqi (tmp, src_mem));   
5681         emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));        
5682         for (i = 1; i < len; i++)
5683           {
5684             emit_insn (gen_movqi_parallel (tmp, src_mem, dst_mem, tmp));
5685             emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));    
5686             emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));    
5687           }
5688         emit_insn (gen_movqi (dst_mem, tmp));   
5689         emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));        
5690       }
5691     else
5692       {
5693         for (i = 0; i < len; i++)
5694           {
5695             emit_insn (gen_movqi (tmp, src_mem));       
5696             emit_insn (gen_movqi (dst_mem, tmp));       
5697             emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));    
5698             emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));    
5699           }
5700       }
5701     DONE;
5702   }
5703   ")
5704
5705
5706 ;
5707 ; BLOCK MOVE
5708 ; We should probably get RC loaded when using RPTB automagically...
5709 ; There's probably no need to call _memcpy() if we don't get
5710 ; an immediate operand for the size.  We could do a better job here
5711 ; than most memcpy() implementations.
5712 ; operand 2 is the number of bytes
5713 ; operand 3 is the shared alignment
5714 ; operand 4 is a scratch register
5715
5716 (define_insn "movstrqi_small"
5717   [(set (mem:BLK (match_operand:QI 0 "addr_reg_operand" "+a"))
5718         (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a")))
5719    (use (match_operand:QI 2 "immediate_operand" "i"))
5720    (use (match_operand:QI 3 "immediate_operand" ""))
5721    (clobber (match_operand:QI 4 "ext_low_reg_operand" "=&q"))
5722    (clobber (match_dup 0))
5723    (clobber (match_dup 1))]
5724   ""
5725   "*
5726  {
5727    int i;
5728    int len = INTVAL (operands[2]);
5729    int first = 1;
5730
5731    for (i = 0; i < len; i++)
5732     {
5733       if (first)
5734         output_asm_insn (\"ldiu\\t*%1++,%4\", operands);
5735       else
5736         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5737       output_asm_insn (\"sti\\t%4,*%0++\", operands);
5738       first = 0;
5739     } 
5740   return \"\";
5741   }
5742   "
5743   [(set_attr "type" "multi")])
5744
5745 (define_insn "movstrqi_large"
5746   [(set (mem:BLK (match_operand:QI 0 "addr_reg_operand" "+a"))
5747         (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a")))
5748    (use (match_operand:QI 2 "immediate_operand" "i"))
5749    (use (match_operand:QI 3 "immediate_operand" ""))
5750    (clobber (match_operand:QI 4 "ext_low_reg_operand" "=&q"))
5751    (clobber (match_dup 0))
5752    (clobber (match_dup 1))
5753    (clobber (reg:QI 25))
5754    (clobber (reg:QI 26))
5755    (clobber (reg:QI 27))]
5756   ""
5757   "*
5758  {
5759    int len = INTVAL (operands[2]);
5760
5761    output_asm_insn (\"ldiu\\t*%1++,%4\", operands);
5762    if (TARGET_RPTS_CYCLES (len))
5763      {
5764         output_asm_insn (\"rpts\\t%2-2\", operands);  
5765         output_asm_insn (\"sti\\t%4,*%0++\", operands);
5766         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5767         return \"sti\\t%4,*%0++\";
5768      }
5769    else
5770      {
5771         output_asm_insn (\"ldiu\\t%2-2,rc\", operands);
5772         output_asm_insn (\"rptb\\t$+1\", operands);  
5773         output_asm_insn (\"sti\\t%4,*%0++\", operands);
5774         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5775
5776         return \"sti\\t%4,*%0++\";
5777      }
5778   }
5779   "
5780   [(set_attr "type" "multi")])
5781
5782 ; Operand 2 is the count, operand 3 is the alignment.
5783 (define_expand "movstrqi"
5784   [(parallel [(set (mem:BLK (match_operand:BLK 0 "src_operand" ""))
5785                    (mem:BLK (match_operand:BLK 1 "src_operand" "")))
5786               (use (match_operand:QI 2 "immediate_operand" ""))
5787               (use (match_operand:QI 3 "immediate_operand" ""))])]
5788   ""
5789   "
5790  {
5791    rtx tmp;
5792    if (GET_CODE (operands[2]) != CONST_INT 
5793        || INTVAL (operands[2]) > 32767 
5794        || INTVAL (operands[2]) <= 0)
5795      {
5796         FAIL;  /* Try to call _memcpy */
5797      }
5798
5799    operands[0] = copy_to_mode_reg (Pmode, XEXP (operands[0], 0));
5800    operands[1] = copy_to_mode_reg (Pmode, XEXP (operands[1], 0));
5801    tmp = gen_reg_rtx (QImode);
5802    if (INTVAL (operands[2]) < 8)
5803      emit_insn (gen_movstrqi_small2 (operands[0], operands[1], operands[2],
5804                                     operands[3], tmp));
5805    else
5806      {
5807       emit_insn (gen_movstrqi_large (operands[0], operands[1], operands[2],
5808                                      operands[3], tmp));
5809      }
5810    DONE;
5811  }")
5812
5813
5814 (define_insn "*cmpstrqi"
5815   [(set (match_operand:QI 0 "ext_reg_operand" "=d")
5816         (compare:QI (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a"))
5817                     (mem:BLK (match_operand:QI 2 "addr_reg_operand" "+a"))))
5818    (use (match_operand:QI 3 "immediate_operand" "i"))
5819    (use (match_operand:QI 4 "immediate_operand" ""))
5820    (clobber (match_operand:QI 5 "std_reg_operand" "=&c"))
5821    (clobber (reg:QI 21))]
5822   ""
5823   "*
5824  {
5825     output_asm_insn (\"ldi\\t%3-1,%5\", operands);
5826     output_asm_insn (\"$1:\tsubi3\\t*%1++,*%2++,%0\", operands);
5827     output_asm_insn (\"dbeq\\t%5,$1\", operands);
5828     return \"\";
5829  }")
5830
5831 (define_expand "cmpstrqi"
5832   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
5833                    (compare:QI (match_operand:BLK 1 "general_operand" "")
5834                                (match_operand:BLK 2 "general_operand" "")))
5835               (use (match_operand:QI 3 "immediate_operand" ""))
5836               (use (match_operand:QI 4 "immediate_operand" ""))
5837               (clobber (match_dup 5))
5838               (clobber (reg:QI 21))])]
5839   ""
5840   "
5841 {
5842    if (GET_CODE (operands[3]) != CONST_INT
5843        || INTVAL (operands[3]) > 32767 
5844        || INTVAL (operands[3]) <= 0)
5845      {
5846         FAIL;
5847      }
5848    operands[1] = copy_to_mode_reg (Pmode, XEXP (operands[1], 0));
5849    operands[2] = copy_to_mode_reg (Pmode, XEXP (operands[2], 0));
5850    operands[5] = gen_reg_rtx (QImode);
5851 }")
5852
5853 ;
5854 ; TWO OPERAND LONG DOUBLE INSTRUCTIONS
5855 ;
5856
5857 (define_expand "movhf"
5858   [(set (match_operand:HF 0 "src_operand" "")
5859         (match_operand:HF 1 "src_operand" ""))]
5860  ""
5861  "if (c4x_emit_move_sequence (operands, HFmode))
5862     DONE;")
5863
5864 (define_insn "*movhf_noclobber_reg"
5865   [(set (match_operand:HF 0 "reg_operand" "=h")
5866         (match_operand:HF 1 "src_operand" "Hh"))]
5867  "GET_CODE (operands[1]) != MEM"
5868  "ldfu\\t%1,%0"
5869   [(set_attr "type" "unary")])
5870
5871 (define_insn "*movhf_noclobber"
5872  [(set (match_operand:HF 0 "dst_operand" "=h,m")
5873        (match_operand:HF 1 "src_operand" "Hm,h"))]
5874  "reg_operand (operands[0], HFmode) ^ reg_operand (operands[1], HFmode)"
5875  "#"
5876  [(set_attr "type" "multi,multi")])
5877
5878 (define_insn "*movhf_test"
5879   [(set (reg:CC 21)
5880         (compare:CC (match_operand:HF 1 "reg_operand" "h")
5881                     (const_int 0)))
5882    (clobber (match_scratch:HF 0 "=h"))]
5883  ""
5884  "ldf\\t%1,%0"
5885   [(set_attr "type" "unarycc")])
5886
5887 (define_insn "*movhf_set"
5888   [(set (reg:CC 21)
5889         (compare:CC (match_operand:HF 1 "reg_operand" "h")
5890                     (match_operand:HF 2 "fp_zero_operand" "G")))
5891     (set (match_operand:HF 0 "reg_operand" "=h")
5892          (match_dup 1))]
5893  ""
5894  "ldf\\t%1,%0"
5895   [(set_attr "type" "unarycc")])
5896
5897 (define_split
5898  [(set (match_operand:HF 0 "reg_operand" "")
5899        (match_operand:HF 1 "memory_operand" ""))]
5900  "reload_completed"
5901  [(set (match_dup 0) (float_extend:HF (match_dup 2)))
5902   (set (match_dup 0) (unspec:HF [(subreg:QI (match_dup 0) 0)
5903                                             (match_dup 3)] UNSPEC_LOADHF_INT))]
5904  "operands[2] = c4x_operand_subword (operands[1], 0, 1, HFmode);
5905   operands[3] = c4x_operand_subword (operands[1], 1, 1, HFmode);
5906   PUT_MODE (operands[2], QFmode);
5907   PUT_MODE (operands[3], QImode);")
5908
5909 (define_split
5910  [(set (match_operand:HF 0 "reg_operand" "")
5911        (match_operand:HF 1 "const_operand" ""))]
5912  "reload_completed && 0"
5913  [(set (match_dup 0) (float_extend:HF (match_dup 2)))
5914   (set (match_dup 0) (unspec:HF [(subreg:QI (match_dup 0) 0)
5915                                             (match_dup 3)] UNSPEC_LOADHF_INT))]
5916  "operands[2] = c4x_operand_subword (operands[1], 0, 1, HFmode);
5917   operands[3] = c4x_operand_subword (operands[1], 1, 1, HFmode);
5918   PUT_MODE (operands[2], QFmode);
5919   PUT_MODE (operands[3], QImode);")
5920
5921 (define_split
5922  [(set (match_operand:HF 0 "memory_operand" "")
5923        (match_operand:HF 1 "reg_operand" ""))]
5924   "reload_completed"
5925   [(set (match_dup 2) (float_truncate:QF (match_dup 1)))
5926    (set (match_dup 3) (unspec:QI [(match_dup 1)] UNSPEC_STOREHF_INT))]
5927  "operands[2] = c4x_operand_subword (operands[0], 0, 1, HFmode);
5928   operands[3] = c4x_operand_subword (operands[0], 1, 1, HFmode);
5929   PUT_MODE (operands[2], QFmode);
5930   PUT_MODE (operands[3], QImode);")
5931
5932 (define_insn "*loadhf_float"
5933  [(set (match_operand:HF 0 "reg_operand" "=h")
5934        (float_extend:HF (match_operand:QF 1 "src_operand" "fHm")))]
5935  ""
5936  "ldfu\\t%1,%0"
5937   [(set_attr "type" "unary")])
5938
5939 (define_insn "*loadhf_int"
5940  [(set (match_operand:HF 0 "reg_operand" "+h")
5941        (unspec:HF [(subreg:QI (match_dup 0) 0)
5942                    (match_operand:QI 1 "src_operand" "rIm")] UNSPEC_LOADHF_INT))]
5943  ""
5944  "ldiu\\t%1,%0"
5945   [(set_attr "type" "unary")])
5946
5947 (define_insn "*storehf_float"
5948   [(set (match_operand:QF 0 "memory_operand" "=m")
5949         (float_truncate:QF (match_operand:HF 1 "reg_operand" "h")))]
5950   ""
5951   "stf\\t%1,%0"
5952   [(set_attr "type" "store")])
5953
5954 (define_insn "*storehf_int"
5955  [(set (match_operand:QI 0 "memory_operand" "=m")
5956        (unspec:QI [(match_operand:HF 1 "reg_operand" "h")] UNSPEC_STOREHF_INT))]
5957  ""
5958  "sti\\t%1,%0"
5959   [(set_attr "type" "store")])
5960
5961 (define_insn "extendqfhf2"
5962   [(set (match_operand:HF 0 "reg_operand" "=h")
5963         (float_extend:HF (match_operand:QF 1 "reg_operand" "h")))]
5964   ""
5965   "ldfu\\t%1,%0"
5966   [(set_attr "type" "unarycc")])
5967
5968 (define_insn "trunchfqf2"
5969   [(set (match_operand:QF 0 "reg_operand" "=h")
5970         (float_truncate:QF (match_operand:HF 1 "reg_operand" "0")))
5971    (clobber (reg:CC 21))]
5972   ""
5973   "andn\\t0ffh,%0"
5974   [(set_attr "type" "unarycc")])
5975
5976 ;
5977 ; PUSH/POP
5978 ;
5979 (define_insn "pushhf"
5980   [(set (mem:HF (pre_inc:QI (reg:QI 20)))
5981         (match_operand:HF 0 "reg_operand" "h"))]
5982  ""
5983  "#"
5984  [(set_attr "type" "multi")])
5985
5986 (define_split
5987  [(set (mem:HF (pre_inc:QI (reg:QI 20)))
5988         (match_operand:HF 0 "reg_operand" ""))]
5989   "reload_completed"
5990   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
5991         (float_truncate:QF (match_dup 0)))
5992    (set (mem:QI (pre_inc:QI (reg:QI 20)))
5993         (unspec:QI [(match_dup 0)] UNSPEC_STOREHF_INT))]
5994  "")
5995
5996 (define_insn "pushhf_trunc"
5997   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
5998         (float_truncate:QF (match_operand:HF 0 "reg_operand" "h")))]
5999  ""
6000  "pushf\\t%0"
6001  [(set_attr "type" "push")])
6002
6003 (define_insn "pushhf_int"
6004   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
6005         (unspec:QI [(match_operand:HF 0 "reg_operand" "h")] UNSPEC_STOREHF_INT))]
6006  ""
6007  "push\\t%0"
6008  [(set_attr "type" "push")])
6009
6010 ; we can not use this because the popf will destroy the low 8 bits
6011 ;(define_insn "pophf"
6012 ;  [(set (match_operand:HF 0 "reg_operand" "=h")
6013 ;        (mem:HF (post_dec:QI (reg:QI 20))))
6014 ;   (clobber (reg:CC 21))]
6015 ; ""
6016 ; "#"
6017 ; [(set_attr "type" "multi")])
6018
6019 (define_split
6020  [(set (match_operand:HF 0 "reg_operand" "")
6021        (mem:HF (post_dec:QI (reg:QI 20))))
6022    (clobber (reg:CC 21))]
6023   "reload_completed"
6024   [(parallel [(set (match_operand:HF 0 "reg_operand" "=h")
6025                    (float_extend:HF (mem:QF (post_dec:QI (reg:QI 20)))))
6026               (clobber (reg:CC 21))])
6027    (parallel [(set (match_dup 0)
6028                    (unspec:HF [(subreg:QI (match_dup 0) 0)
6029                    (mem:QI (post_dec:QI (reg:QI 20)))] UNSPEC_LOADHF_INT))
6030               (clobber (reg:CC 21))])]
6031  "")
6032
6033 (define_insn "*pophf_int"
6034  [(set (match_operand:HF 0 "reg_operand" "+h")
6035        (unspec:HF [(subreg:QI (match_dup 0) 0)
6036                    (mem:QI (post_dec:QI (reg:QI 20)))] UNSPEC_LOADHF_INT))
6037   (clobber (reg:CC 21))]
6038  ""
6039  "pop\\t%0"
6040   [(set_attr "type" "pop")])
6041
6042 (define_insn "*pophf_float"
6043  [(set (match_operand:HF 0 "reg_operand" "=h")
6044        (float_extend:HF (mem:QF (post_dec:QI (reg:QI 20)))))
6045   (clobber (reg:CC 21))]
6046  ""
6047  "popf\\t%0"
6048   [(set_attr "type" "pop")])
6049
6050 ;
6051 ; FIX
6052 ;
6053 (define_insn "fixhfqi_clobber"
6054   [(set (match_operand:QI 0 "reg_operand" "=dc")
6055         (fix:QI (match_operand:HF 1 "reg_or_const_operand" "hH")))
6056    (clobber (reg:CC 21))]
6057  ""
6058  "fix\\t%1,%0"
6059   [(set_attr "type" "unarycc")])
6060
6061 ;
6062 ; ABSF
6063 ;
6064 (define_expand "abshf2"
6065   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6066                    (abs:HF (match_operand:HF 1 "reg_or_const_operand" "")))
6067               (clobber (reg:CC_NOOV 21))])]
6068 ""
6069 "")
6070
6071 (define_insn "*abshf2_clobber"
6072   [(set (match_operand:HF 0 "reg_operand" "=h")
6073         (abs:HF (match_operand:HF 1 "reg_or_const_operand" "hH")))
6074    (clobber (reg:CC_NOOV 21))]
6075   ""
6076   "absf\\t%1,%0"
6077   [(set_attr "type" "unarycc")])
6078
6079 (define_insn "*abshf2_test"
6080   [(set (reg:CC_NOOV 21)
6081         (compare:CC_NOOV (abs:HF (match_operand:HF 1 "reg_operand" "h"))
6082                          (match_operand:HF 2 "fp_zero_operand" "G")))
6083    (clobber (match_scratch:HF 0 "=h"))]
6084   ""
6085   "absf\\t%1,%0"
6086   [(set_attr "type" "unarycc")])
6087
6088 (define_insn "*abshf2_set"
6089   [(set (reg:CC_NOOV 21)
6090         (compare:CC_NOOV (abs:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
6091                          (match_operand:HF 2 "fp_zero_operand" "G")))
6092    (set (match_operand:HF 0 "reg_operand" "=h")
6093         (abs:HF (match_dup 1)))]
6094
6095   ""
6096   "absf\\t%1,%0"
6097   [(set_attr "type" "unarycc")])
6098
6099 ;
6100 ; NEGF
6101 ;
6102 (define_expand "neghf2"
6103   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6104                    (neg:HF (match_operand:HF 1 "reg_or_const_operand" "")))
6105               (clobber (reg:CC_NOOV 21))])]
6106 ""
6107 "")
6108
6109 (define_insn "*neghf2_clobber"
6110   [(set (match_operand:HF 0 "reg_operand" "=h")
6111         (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH")))
6112    (clobber (reg:CC_NOOV 21))]
6113   ""
6114   "negf\\t%1,%0"
6115   [(set_attr "type" "unarycc")])
6116
6117 (define_insn "*neghf2_test"
6118   [(set (reg:CC_NOOV 21)
6119         (compare:CC_NOOV (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
6120                          (match_operand:HF 2 "fp_zero_operand" "G")))
6121    (clobber (match_scratch:HF 0 "=h"))]
6122   ""
6123   "negf\\t%1,%0"
6124   [(set_attr "type" "unarycc")])
6125
6126 (define_insn "*neghf2_set"
6127   [(set (reg:CC_NOOV 21)
6128         (compare:CC_NOOV (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
6129                          (match_operand:HF 2 "fp_zero_operand" "G")))
6130    (set (match_operand:HF 0 "reg_operand" "=h")
6131         (neg:HF (match_dup 1)))]
6132   ""
6133   "negf\\t%1,%0"
6134   [(set_attr "type" "unarycc")])
6135
6136 ;
6137 ; RCPF
6138 ;
6139 (define_insn "*rcpfhf_clobber"
6140   [(set (match_operand:HF 0 "reg_operand" "=h")
6141         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] UNSPEC_RCPF))
6142    (clobber (reg:CC_NOOV 21))]
6143   "! TARGET_C3X"
6144   "rcpf\\t%1,%0"
6145   [(set_attr "type" "unarycc")])
6146
6147 ;
6148 ; RSQRF
6149 ;
6150 (define_insn "*rsqrfhf_clobber"
6151   [(set (match_operand:HF 0 "reg_operand" "=h")
6152         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] UNSPEC_RSQRF))
6153    (clobber (reg:CC_NOOV 21))]
6154   "! TARGET_C3X"
6155   "rsqrf\\t%1,%0"
6156   [(set_attr "type" "unarycc")])
6157
6158 ;
6159 ; RNDF
6160 ;
6161 (define_insn "*rndhf_clobber"
6162   [(set (match_operand:HF 0 "reg_operand" "=h")
6163         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] UNSPEC_RND))
6164    (clobber (reg:CC_NOOV 21))]
6165   "! TARGET_C3X"
6166   "rnd\\t%1,%0"
6167   [(set_attr "type" "unarycc")])
6168
6169
6170 ; Inlined float square root for C4x
6171 (define_expand "sqrthf2_inline"
6172   [(parallel [(set (match_dup 2)
6173                    (unspec:HF [(match_operand:HF 1 "reg_operand" "")] UNSPEC_RSQRF))
6174               (clobber (reg:CC_NOOV 21))])
6175    (parallel [(set (match_dup 3) (mult:HF (match_dup 5) (match_dup 1)))
6176               (clobber (reg:CC_NOOV 21))])
6177    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6178               (clobber (reg:CC_NOOV 21))])
6179    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 4)))
6180               (clobber (reg:CC_NOOV 21))])
6181    (parallel [(set (match_dup 4) (minus:HF (match_dup 6) (match_dup 4)))
6182               (clobber (reg:CC_NOOV 21))])
6183    (parallel [(set (match_dup 2) (mult:HF (match_dup 2) (match_dup 4)))
6184               (clobber (reg:CC_NOOV 21))])
6185    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6186               (clobber (reg:CC_NOOV 21))])
6187    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 4)))
6188               (clobber (reg:CC_NOOV 21))])
6189    (parallel [(set (match_dup 4) (minus:HF (match_dup 6) (match_dup 4)))
6190               (clobber (reg:CC_NOOV 21))])
6191    (parallel [(set (match_dup 2) (mult:HF (match_dup 2) (match_dup 4)))
6192               (clobber (reg:CC_NOOV 21))])
6193    (parallel [(set (match_operand:HF 0 "reg_operand" "")
6194                    (mult:HF (match_dup 2) (match_dup 1)))
6195               (clobber (reg:CC_NOOV 21))])]
6196   "! TARGET_C3X"
6197   "
6198   operands[2] = gen_reg_rtx (HFmode);
6199   operands[3] = gen_reg_rtx (HFmode);
6200   operands[4] = gen_reg_rtx (HFmode);
6201   operands[5] = CONST_DOUBLE_ATOF (\"0.5\", HFmode);
6202   operands[6] = CONST_DOUBLE_ATOF (\"1.5\", HFmode);
6203   ")
6204
6205
6206 (define_expand "sqrthf2"
6207   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6208                    (sqrt:HF (match_operand:HF 1 "reg_operand" "")))
6209               (clobber (reg:CC 21))])]
6210   "! TARGET_C3X && TARGET_INLINE"
6211   "emit_insn (gen_sqrthf2_inline (operands[0], operands[1]));
6212    DONE;")
6213
6214
6215 (define_expand "fix_trunchfhi2"
6216   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6217                    (fix:HI (match_operand:HF 1 "reg_operand" "")))
6218               (clobber (reg:CC 21))])]
6219   ""
6220   "c4x_emit_libcall (fix_trunchfhi2_libfunc, FIX, HImode, HFmode, 2, operands);
6221    DONE;")
6222
6223 (define_expand "fixuns_trunchfhi2"
6224   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6225                    (unsigned_fix:HI (match_operand:HF 1 "reg_operand" "")))
6226               (clobber (reg:CC 21))])]
6227   ""
6228   "c4x_emit_libcall (fixuns_trunchfhi2_libfunc, UNSIGNED_FIX, 
6229                      HImode, HFmode, 2, operands);
6230    DONE;")
6231
6232 ;
6233 ; THREE OPERAND LONG DOUBLE INSTRUCTIONS
6234 ;
6235
6236 ;
6237 ; ADDF
6238 ;
6239 (define_insn "addhf3"
6240   [(set (match_operand:HF 0 "reg_operand" "=h,?h")
6241         (plus:HF (match_operand:HF 1 "reg_operand" "%0,h")
6242                  (match_operand:HF 2 "reg_or_const_operand" "H,h")))
6243    (clobber (reg:CC_NOOV 21))]
6244   ""
6245   "@
6246    addf\\t%2,%0
6247    addf3\\t%2,%1,%0"
6248   [(set_attr "type" "binarycc,binarycc")])
6249
6250 ;
6251 ; SUBF
6252 ;
6253 (define_insn "subhf3"
6254   [(set (match_operand:HF 0 "reg_operand" "=h,h,?h")
6255         (minus:HF (match_operand:HF 1 "reg_or_const_operand" "0,H,h")
6256                   (match_operand:HF 2 "reg_or_const_operand" "H,0,h")))
6257    (clobber (reg:CC_NOOV 21))]
6258   ""
6259   "@
6260    subf\\t%2,%0
6261    subrf\\t%1,%0
6262    subf3\\t%2,%1,%0"
6263   [(set_attr "type" "binarycc,binarycc,binarycc")])
6264
6265 ;
6266 ; MULF
6267 ;
6268 ; The C3x MPYF only uses 24 bit precision while the C4x uses 32 bit precison.
6269 ;
6270 (define_expand "mulhf3"
6271   [(parallel [(set (match_operand:HF 0 "reg_operand" "=h")
6272                    (mult:HF (match_operand:HF 1 "reg_operand" "h")
6273                             (match_operand:HF 2 "reg_operand" "h")))
6274               (clobber (reg:CC_NOOV 21))])]
6275   "! TARGET_C3X"
6276   "")
6277
6278 (define_insn "*mulhf3_c40"
6279   [(set (match_operand:HF 0 "reg_operand" "=h,?h")
6280         (mult:HF (match_operand:HF 1 "reg_operand" "%0,h")
6281                  (match_operand:HF 2 "reg_or_const_operand" "hH,h")))
6282    (clobber (reg:CC_NOOV 21))]
6283   ""
6284   "@
6285    mpyf\\t%2,%0
6286    mpyf3\\t%2,%1,%0"
6287   [(set_attr "type" "binarycc,binarycc")])
6288
6289 ;
6290 ; CMPF
6291 ;
6292 (define_expand "cmphf"
6293   [(set (reg:CC 21)
6294         (compare:CC (match_operand:HF 0 "reg_operand" "")
6295                     (match_operand:HF 1 "reg_or_const_operand" "")))]
6296   ""
6297   "c4x_compare_op0 = operands[0];
6298    c4x_compare_op1 = operands[1];
6299    DONE;")
6300
6301 (define_insn "*cmphf"
6302   [(set (reg:CC 21)
6303         (compare:CC (match_operand:HF 0 "reg_operand" "h")
6304                     (match_operand:HF 1 "reg_or_const_operand" "hH")))]
6305   ""
6306   "cmpf\\t%1,%0"
6307   [(set_attr "type" "compare")])
6308
6309 (define_insn "*cmphf_noov"
6310   [(set (reg:CC_NOOV 21)
6311         (compare:CC_NOOV (match_operand:HF 0 "reg_operand" "h")
6312                          (match_operand:HF 1 "reg_or_const_operand" "hH")))]
6313   ""
6314   "cmpf\\t%1,%0"
6315   [(set_attr "type" "compare")])
6316
6317 ; Inlined float divide for C4x
6318 (define_expand "divhf3_inline"
6319   [(parallel [(set (match_dup 3)
6320                    (unspec:HF [(match_operand:HF 2 "reg_operand" "")] UNSPEC_RCPF))
6321               (clobber (reg:CC_NOOV 21))])
6322    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6323               (clobber (reg:CC_NOOV 21))])
6324    (parallel [(set (match_dup 4) (minus:HF (match_dup 5) (match_dup 4)))
6325               (clobber (reg:CC_NOOV 21))])
6326    (parallel [(set (match_dup 3) (mult:HF (match_dup 3) (match_dup 4)))
6327               (clobber (reg:CC_NOOV 21))])
6328    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6329               (clobber (reg:CC_NOOV 21))])
6330    (parallel [(set (match_dup 4) (minus:HF (match_dup 5) (match_dup 4)))
6331               (clobber (reg:CC_NOOV 21))])
6332    (parallel [(set (match_dup 3) (mult:HF (match_dup 3) (match_dup 4)))
6333               (clobber (reg:CC_NOOV 21))])
6334    (parallel [(set (match_operand:HF 0 "reg_operand" "")
6335                    (mult:HF (match_operand:HF 1 "reg_operand" "")
6336                             (match_dup 3)))
6337               (clobber (reg:CC_NOOV 21))])]
6338   "! TARGET_C3X"
6339   "
6340   operands[3] = gen_reg_rtx (HFmode);
6341   operands[4] = gen_reg_rtx (HFmode);
6342   operands[5] = CONST2_RTX (HFmode);
6343   ")
6344
6345 (define_expand "divhf3"
6346   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6347                    (div:HF (match_operand:HF 1 "reg_operand" "")
6348                            (match_operand:HF 2 "reg_operand" "")))
6349               (clobber (reg:CC 21))])]
6350   "! TARGET_C3X && TARGET_INLINE"
6351   "emit_insn (gen_divhf3_inline (operands[0], operands[1], operands[2]));
6352    DONE;")
6353
6354
6355 ;
6356 ; TWO OPERAND LONG LONG INSTRUCTIONS
6357 ;
6358
6359 (define_insn "*movhi_stik"
6360   [(set (match_operand:HI 0 "memory_operand" "=m")
6361         (match_operand:HI 1 "stik_const_operand" "K"))]
6362   "! TARGET_C3X"
6363   "#"
6364   [(set_attr "type" "multi")])
6365
6366 ; We could load some constants using define_splits for the C30
6367 ; in the large memory model---these would emit shift and or insns.
6368 (define_expand "movhi"
6369   [(set (match_operand:HI 0 "src_operand" "")
6370         (match_operand:HI 1 "src_operand" ""))]
6371  ""
6372  "if (c4x_emit_move_sequence (operands, HImode))
6373     DONE;")
6374
6375 ; The constraints for movhi must include 'r' if we don't
6376 ; restrict HImode regnos to start on an even number, since
6377 ; we can get RC, R8 allocated as a pair.  We want more
6378 ; votes for FP_REGS so we use dr as the constraints.
6379 (define_insn "*movhi_noclobber"
6380   [(set (match_operand:HI 0 "dst_operand" "=dr,m")
6381         (match_operand:HI 1 "src_operand" "drIm,r"))]
6382   "reg_operand (operands[0], HImode)
6383    || reg_operand (operands[1], HImode)"
6384   "#"
6385   [(set_attr "type" "multi,multi")])
6386
6387 ; This will fail miserably if the destination register is used in the 
6388 ; source memory address.
6389 ; The usual strategy in this case is to swap the order of insns we emit,
6390 ; however, this will fail if we have an autoincrement memory address.
6391 ; For example:
6392 ; ldi *ar0++, ar0
6393 ; ldi *ar0++, ar1
6394 ;
6395 ; We could convert this to
6396 ; ldi *ar0(1), ar1
6397 ; ldi *ar0, ar0
6398 ;
6399 ; However, things are likely to be very screwed up if we get this.
6400
6401 (define_split
6402   [(set (match_operand:HI 0 "dst_operand" "")
6403         (match_operand:HI 1 "src_operand" ""))]
6404   "reload_completed
6405    && (reg_operand (operands[0], HImode)
6406        || reg_operand (operands[1], HImode)
6407        || stik_const_operand (operands[1], HImode))"
6408   [(set (match_dup 2) (match_dup 4))
6409    (set (match_dup 3) (match_dup 5))]
6410   "operands[2] = c4x_operand_subword (operands[0], 0, 1, HImode);
6411    operands[3] = c4x_operand_subword (operands[0], 1, 1, HImode);
6412    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6413    operands[5] = c4x_operand_subword (operands[1], 1, 1, HImode);
6414    if (reg_overlap_mentioned_p (operands[2], operands[5]))
6415      {
6416         /* Swap order of move insns.  */
6417         rtx tmp;
6418         tmp = operands[2];
6419         operands[2] =operands[3];
6420         operands[3] = tmp;
6421         tmp = operands[4];
6422         operands[4] =operands[5];
6423         operands[5] = tmp;        
6424      }")
6425
6426
6427 (define_insn "extendqihi2"
6428   [(set (match_operand:HI 0 "reg_operand" "=dc")
6429         (sign_extend:HI (match_operand:QI 1 "src_operand" "rIm")))
6430    (clobber (reg:CC 21))]
6431   ""
6432   "#"
6433   [(set_attr "type" "multi")])
6434
6435 (define_split
6436   [(set (match_operand:HI 0 "reg_operand" "")
6437         (sign_extend:HI (match_operand:QI 1 "src_operand" "")))
6438    (clobber (reg:CC 21))]
6439   "reload_completed && TARGET_C3X"
6440   [(set (match_dup 2) (match_dup 1))
6441    (set (match_dup 3) (match_dup 2))
6442    (parallel [(set (match_dup 3) (ashiftrt:QI (match_dup 3) (const_int 31)))
6443               (clobber (reg:CC 21))])]
6444   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6445    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6446
6447 (define_split
6448   [(set (match_operand:HI 0 "reg_operand" "")
6449         (sign_extend:HI (match_operand:QI 1 "src_operand" "")))
6450    (clobber (reg:CC 21))]
6451   "reload_completed && ! TARGET_C3X"
6452   [(set (match_dup 2) (match_dup 1))
6453    (parallel [(set (match_dup 3) (ashiftrt:QI (match_dup 2) (const_int 31)))
6454               (clobber (reg:CC 21))])]
6455   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6456    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6457
6458 (define_insn "zero_extendqihi2"
6459   [(set (match_operand:HI 0 "reg_operand" "=?dc")
6460         (zero_extend:HI (match_operand:QI 1 "nonimmediate_src_operand" "rm")))
6461    (clobber (reg:CC 21))]
6462   ""
6463   "#"
6464   [(set_attr "type" "multi")])
6465
6466 ; If operand0 and operand1 are the same register we don't need
6467 ; the first set.
6468 (define_split
6469   [(set (match_operand:HI 0 "reg_operand" "")
6470         (zero_extend:HI (match_operand:QI 1 "nonimmediate_src_operand" "")))
6471    (clobber (reg:CC 21))]
6472   "reload_completed"
6473   [(set (match_dup 2) (match_dup 1))
6474    (set (match_dup 3) (const_int 0))]
6475   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6476    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6477
6478 ;
6479 ; PUSH/POP
6480 ;
6481 (define_insn "*pushhi"
6482   [(set (mem:HI (pre_inc:QI (reg:QI 20)))
6483         (match_operand:HI 0 "reg_operand" "r"))]
6484   ""
6485   "#"
6486   [(set_attr "type" "multi")])
6487
6488 (define_split
6489   [(set (mem:HI (pre_inc:QI (reg:QI 20)))
6490         (match_operand:HI 0 "reg_operand" ""))]
6491   "reload_completed"
6492   [(set (mem:QI (pre_inc:QI (reg:QI 20))) (match_dup 2))
6493    (set (mem:QI (pre_inc:QI (reg:QI 20))) (match_dup 3))]
6494   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6495    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6496
6497 (define_insn "*pophi"
6498   [(set (match_operand:HI 0 "reg_operand" "=r")
6499         (mem:HI (post_dec:QI (reg:QI 20))))
6500    (clobber (reg:CC 21))]
6501   ""
6502   "#"
6503   [(set_attr "type" "multi")])
6504
6505 (define_split
6506   [(set (match_operand:HI 0 "reg_operand" "")
6507        (mem:HI (pre_inc:QI (reg:QI 20))))]
6508   "reload_completed"
6509   [(set (match_dup 2) (mem:QI (pre_inc:QI (reg:QI 20))))
6510    (set (match_dup 3) (mem:QI (pre_inc:QI (reg:QI 20))))]
6511   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6512    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6513
6514 ;
6515 ; NEG
6516 ;
6517 (define_insn "neghi2"
6518   [(set (match_operand:HI 0 "ext_reg_operand" "=d")
6519         (neg:HI (match_operand:HI 1 "src_operand" "rm")))
6520    (clobber (reg:CC_NOOV 21))]
6521   ""
6522   "#"
6523   [(set_attr "type" "multi")])
6524
6525 (define_split
6526   [(set (match_operand:HI 0 "ext_reg_operand" "")
6527         (neg:HI (match_operand:HI 1 "src_operand" "")))
6528    (clobber (reg:CC_NOOV 21))]
6529   "reload_completed"
6530    [(parallel [(set (reg:CC_NOOV 21)
6531                     (compare:CC_NOOV (neg:QI (match_dup 3))
6532                                      (const_int 0)))
6533                (set (match_dup 2) (neg:QI (match_dup 3)))])
6534    (parallel [(set (match_dup 4) (neg:QI (match_dup 5)))
6535               (use (reg:CC_NOOV 21))
6536               (clobber (reg:CC_NOOV 21))])]
6537   "operands[2] = c4x_operand_subword (operands[0], 0, 1, HImode);
6538    operands[3] = c4x_operand_subword (operands[1], 0, 1, HImode);
6539    operands[4] = c4x_operand_subword (operands[0], 1, 1, HImode);
6540    operands[5] = c4x_operand_subword (operands[1], 1, 1, HImode);")
6541
6542 (define_insn "one_cmplhi2"
6543   [(set (match_operand:HI 0 "reg_operand" "=r")
6544         (not:HI (match_operand:HI 1 "src_operand" "rm")))
6545    (clobber (reg:CC 21))]
6546   ""
6547   "#"
6548   [(set_attr "type" "multi")])
6549
6550 (define_split
6551   [(set (match_operand:HI 0 "reg_operand" "")
6552         (not:HI (match_operand:HI 1 "src_operand" "")))
6553    (clobber (reg:CC 21))]
6554   "reload_completed"
6555    [(parallel [(set (match_dup 2) (not:QI (match_dup 3)))
6556                (clobber (reg:CC 21))])
6557     (parallel [(set (match_dup 4) (not:QI (match_dup 5)))
6558                (clobber (reg:CC 21))])]
6559   "operands[2] = c4x_operand_subword (operands[0], 0, 1, HImode);
6560    operands[3] = c4x_operand_subword (operands[1], 0, 1, HImode);
6561    operands[4] = c4x_operand_subword (operands[0], 1, 1, HImode);
6562    operands[5] = c4x_operand_subword (operands[1], 1, 1, HImode);")
6563
6564 (define_expand "floathiqf2"
6565   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
6566                    (float:QF (match_operand:HI 1 "src_operand" "")))
6567               (clobber (reg:CC 21))])]
6568   ""
6569   "c4x_emit_libcall (floathiqf2_libfunc, FLOAT, QFmode, HImode, 2, operands);
6570    DONE;")
6571
6572 (define_expand "floatunshiqf2"
6573   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
6574                    (unsigned_float:QF (match_operand:HI 1 "src_operand" "")))
6575               (clobber (reg:CC 21))])]
6576   ""
6577   "c4x_emit_libcall (floatunshiqf2_libfunc, UNSIGNED_FLOAT,
6578                      QFmode, HImode, 2, operands);
6579    DONE;")
6580
6581 (define_expand "floathihf2"
6582   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6583                    (float:HF (match_operand:HI 1 "src_operand" "")))
6584               (clobber (reg:CC 21))])]
6585   ""
6586   "c4x_emit_libcall (floathihf2_libfunc, FLOAT, HFmode, HImode, 2, operands);
6587    DONE;")
6588
6589 (define_expand "floatunshihf2"
6590   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6591                    (unsigned_float:HF (match_operand:HI 1 "src_operand" "")))
6592               (clobber (reg:CC 21))])]
6593   ""
6594   "c4x_emit_libcall (floatunshihf2_libfunc, UNSIGNED_FLOAT,
6595                      HFmode, HImode, 2, operands);
6596    DONE;")
6597
6598
6599 ;
6600 ; THREE OPERAND LONG LONG INSTRUCTIONS
6601 ;
6602
6603 (define_expand "addhi3"
6604   [(parallel [(set (match_operand:HI 0 "ext_reg_operand" "")
6605                    (plus:HI (match_operand:HI 1 "src_operand" "")
6606                             (match_operand:HI 2 "src_operand" "")))
6607               (clobber (reg:CC_NOOV 21))])]
6608   ""
6609   "legitimize_operands (PLUS, operands, HImode);")
6610
6611 (define_insn "*addhi3_clobber"
6612   [(set (match_operand:HI 0 "ext_reg_operand" "=d,d,?d")
6613         (plus:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6614                  (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6615    (clobber (reg:CC_NOOV 21))]
6616   "valid_operands (PLUS, operands, HImode)"
6617   "#"
6618   [(set_attr "type" "multi,multi,multi")])
6619
6620 (define_split
6621  [(set (match_operand:HI 0 "ext_reg_operand" "")
6622        (plus:HI (match_operand:HI 1 "src_operand" "")
6623                 (match_operand:HI 2 "src_operand" "")))
6624   (clobber (reg:CC_NOOV 21))]
6625  "reload_completed"
6626   [(parallel [(set (reg:CC_NOOV 21)
6627                    (compare:CC_NOOV (plus:QI (match_dup 4) (match_dup 5))
6628                                     (const_int 0)))
6629               (set (match_dup 3) (plus:QI (match_dup 4) (match_dup 5)))])
6630    (parallel [(set (match_dup 6) (plus:QI (match_dup 7) (match_dup 8)))
6631               (use (reg:CC_NOOV 21))
6632               (clobber (reg:CC_NOOV 21))])]
6633   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6634    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6635    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6636    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6637    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6638    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6639
6640 (define_expand "subhi3"
6641   [(parallel [(set (match_operand:HI 0 "ext_reg_operand" "")
6642                    (minus:HI (match_operand:HI 1 "src_operand" "")
6643                              (match_operand:HI 2 "src_operand" "")))
6644               (clobber (reg:CC_NOOV 21))])]
6645   ""
6646   "legitimize_operands (MINUS, operands, HImode);")
6647
6648
6649 (define_insn "*subhi3_clobber"
6650   [(set (match_operand:HI 0 "ext_reg_operand" "=d,d,?d")
6651         (minus:HI (match_operand:HI 1 "src_operand" "0,rR,rS<>")
6652                   (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6653    (clobber (reg:CC_NOOV 21))]
6654   "valid_operands (MINUS, operands, HImode)"
6655   "#"
6656   [(set_attr "type" "multi,multi,multi")])
6657
6658 (define_split
6659  [(set (match_operand:HI 0 "ext_reg_operand" "")
6660        (minus:HI (match_operand:HI 1 "src_operand" "")
6661                  (match_operand:HI 2 "src_operand" "")))
6662   (clobber (reg:CC_NOOV 21))]
6663  "reload_completed"
6664   [(parallel [(set (reg:CC_NOOV 21)
6665                    (compare:CC_NOOV (minus:QI (match_dup 4) (match_dup 5))
6666                                     (const_int 0)))
6667               (set (match_dup 3) (minus:QI (match_dup 4) (match_dup 5)))])
6668    (parallel [(set (match_dup 6) (minus:QI (match_dup 7) (match_dup 8)))
6669               (use (reg:CC_NOOV 21))
6670               (clobber (reg:CC_NOOV 21))])]
6671   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6672    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6673    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6674    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6675    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6676    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6677
6678 (define_expand "iorhi3"
6679   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6680                    (ior:HI (match_operand:HI 1 "src_operand" "")
6681                            (match_operand:HI 2 "src_operand" "")))
6682               (clobber (reg:CC 21))])]
6683   ""
6684   "legitimize_operands (IOR, operands, HImode);")
6685
6686 (define_insn "*iorhi3_clobber"
6687   [(set (match_operand:HI 0 "reg_operand" "=d,d,?d")
6688         (ior:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6689                 (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6690    (clobber (reg:CC 21))]
6691   "valid_operands (IOR, operands, HImode)"
6692   "#"
6693   [(set_attr "type" "multi,multi,multi")])
6694
6695 (define_split
6696  [(set (match_operand:HI 0 "reg_operand" "")
6697        (ior:HI (match_operand:HI 1 "src_operand" "")
6698                (match_operand:HI 2 "src_operand" "")))
6699   (clobber (reg:CC 21))]
6700  "reload_completed"
6701   [(parallel [(set (match_dup 3) (ior:QI (match_dup 4) (match_dup 5)))
6702               (clobber (reg:CC 21))])
6703    (parallel [(set (match_dup 6) (ior:QI (match_dup 7) (match_dup 8)))
6704               (clobber (reg:CC 21))])]
6705   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6706    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6707    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6708    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6709    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6710    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6711
6712 (define_expand "andhi3"
6713   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6714                    (and:HI (match_operand:HI 1 "src_operand" "")
6715                            (match_operand:HI 2 "src_operand" "")))
6716               (clobber (reg:CC 21))])]
6717   ""
6718   "legitimize_operands (AND, operands, HImode);")
6719
6720 (define_insn "*andhi3_clobber"
6721   [(set (match_operand:HI 0 "reg_operand" "=d,d,?d")
6722         (and:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6723                 (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6724    (clobber (reg:CC 21))]
6725   "valid_operands (AND, operands, HImode)"
6726   "#"
6727   [(set_attr "type" "multi,multi,multi")])
6728
6729 (define_split
6730  [(set (match_operand:HI 0 "reg_operand" "")
6731        (and:HI (match_operand:HI 1 "src_operand" "")
6732                 (match_operand:HI 2 "src_operand" "")))
6733   (clobber (reg:CC 21))]
6734  "reload_completed"
6735   [(parallel [(set (match_dup 3) (and:QI (match_dup 4) (match_dup 5)))
6736               (clobber (reg:CC 21))])
6737    (parallel [(set (match_dup 6) (and:QI (match_dup 7) (match_dup 8)))
6738               (clobber (reg:CC 21))])]
6739   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6740    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6741    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6742    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6743    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6744    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6745
6746 (define_expand "xorhi3"
6747   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6748                    (xor:HI (match_operand:HI 1 "src_operand" "")
6749                            (match_operand:HI 2 "src_operand" "")))
6750               (clobber (reg:CC 21))])]
6751   ""
6752   "legitimize_operands (XOR, operands, HImode);")
6753
6754
6755 (define_insn "*xorhi3_clobber"
6756   [(set (match_operand:HI 0 "reg_operand" "=d,d,?d")
6757         (xor:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6758                 (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6759    (clobber (reg:CC 21))]
6760   "valid_operands (XOR, operands, HImode)"
6761   "#"
6762   [(set_attr "type" "multi,multi,multi")])
6763
6764 (define_split
6765  [(set (match_operand:HI 0 "reg_operand" "")
6766        (xor:HI (match_operand:HI 1 "src_operand" "")
6767                (match_operand:HI 2 "src_operand" "")))
6768   (clobber (reg:CC 21))]
6769  "reload_completed"
6770   [(parallel [(set (match_dup 3) (xor:QI (match_dup 4) (match_dup 5)))
6771               (clobber (reg:CC 21))])
6772    (parallel [(set (match_dup 6) (xor:QI (match_dup 7) (match_dup 8)))
6773               (clobber (reg:CC 21))])]
6774   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6775    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6776    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6777    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6778    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6779    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6780
6781 (define_expand "ashlhi3"
6782  [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6783              (ashift:HI (match_operand:HI 1 "src_operand" "")
6784                         (match_operand:QI 2 "src_operand" "")))
6785              (clobber (reg:CC 21))])]
6786  ""
6787  "if (GET_CODE (operands[2]) == CONST_INT && INTVAL (operands[2]) >= 32)
6788     {
6789        rtx op0hi = operand_subword (operands[0], 1, 0, HImode);
6790        rtx op0lo = operand_subword (operands[0], 0, 0, HImode);
6791        rtx op1lo = operand_subword (operands[1], 0, 0, HImode);
6792        rtx count = GEN_INT ((INTVAL (operands[2]) - 32));
6793
6794        if (INTVAL (count))
6795          emit_insn (gen_ashlqi3 (op0hi, op1lo, count));
6796        else
6797          emit_insn (gen_movqi (op0hi, op1lo));
6798        emit_insn (gen_movqi (op0lo, const0_rtx));
6799        DONE;
6800     }
6801   if (! REG_P (operands[1]))
6802     operands[1] = force_reg (HImode, operands[1]);
6803   emit_insn (gen_ashlhi3_reg (operands[0], operands[1], operands[2]));
6804   DONE;
6805  ")
6806
6807 ; %0.lo = %1.lo << %2
6808 ; %0.hi = (%1.hi << %2 ) | (%1.lo >> (32 - %2))
6809 ; This algorithm should work for shift counts greater than 32
6810 (define_expand "ashlhi3_reg" 
6811  [(use (match_operand:HI 1 "reg_operand" ""))
6812   (use (match_operand:HI 0 "reg_operand" ""))
6813   /* If the shift count is greater than 32 this will give zero.  */
6814   (parallel [(set (match_dup 7)
6815                   (ashift:QI (match_dup 3)
6816                              (match_operand:QI 2 "reg_operand" "")))
6817              (clobber (reg:CC 21))])
6818   /* If the shift count is greater than 32 this will give zero.  */
6819   (parallel [(set (match_dup 8)
6820                   (ashift:QI (match_dup 4) (match_dup 2)))
6821              (clobber (reg:CC 21))])
6822   (parallel [(set (match_dup 10)
6823                   (plus:QI (match_dup 2) (const_int -32)))
6824              (clobber (reg:CC_NOOV 21))])
6825   /* If the shift count is greater than 32 this will do a left shift.  */
6826   (parallel [(set (match_dup 9)
6827                   (lshiftrt:QI (match_dup 3) (neg:QI (match_dup 10))))
6828              (clobber (reg:CC 21))])
6829   (set (match_dup 5) (match_dup 7))
6830   (parallel [(set (match_dup 6)
6831                   (ior:QI (match_dup 8) (match_dup 9)))
6832              (clobber (reg:CC 21))])]
6833  ""
6834  " 
6835   operands[3] = operand_subword (operands[1], 0, 1, HImode); /* lo */
6836   operands[4] = operand_subword (operands[1], 1, 1, HImode); /* hi */
6837   operands[5] = operand_subword (operands[0], 0, 1, HImode); /* lo */
6838   operands[6] = operand_subword (operands[0], 1, 1, HImode); /* hi */
6839   operands[7] = gen_reg_rtx (QImode); /* lo << count */
6840   operands[8] = gen_reg_rtx (QImode); /* hi << count */
6841   operands[9] = gen_reg_rtx (QImode); /* lo >> (32 - count) */
6842   operands[10] = gen_reg_rtx (QImode); /* 32 - count */
6843  ")
6844
6845 ; This should do all the dirty work with define_split
6846 (define_expand "lshrhi3"
6847  [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6848              (lshiftrt:HI (match_operand:HI 1 "src_operand" "")
6849                           (match_operand:QI 2 "src_operand" "")))
6850              (clobber (reg:CC 21))])]
6851  ""
6852  "if (GET_CODE (operands[2]) == CONST_INT && INTVAL (operands[2]) >= 32)
6853     {
6854        rtx op0hi = operand_subword (operands[0], 1, 0, HImode);
6855        rtx op0lo = operand_subword (operands[0], 0, 0, HImode);
6856        rtx op1hi = operand_subword (operands[1], 1, 0, HImode);
6857        rtx count = GEN_INT ((INTVAL (operands[2]) - 32));
6858
6859        if (INTVAL (count))
6860          emit_insn (gen_lshrqi3 (op0lo, op1hi, count));
6861        else
6862          emit_insn (gen_movqi (op0lo, op1hi));
6863        emit_insn (gen_movqi (op0hi, const0_rtx));
6864        DONE;
6865     }
6866   if (! REG_P (operands[1]))
6867     operands[1] = force_reg (HImode, operands[1]);
6868   emit_insn (gen_lshrhi3_reg (operands[0], operands[1], operands[2]));
6869   DONE;")
6870
6871 ; %0.hi = %1.hi >> %2
6872 ; %0.lo = (%1.lo >> %2 ) | (%1.hi << (32 - %2))
6873 ; This algorithm should work for shift counts greater than 32
6874 (define_expand "lshrhi3_reg" 
6875  [(use (match_operand:HI 1 "reg_operand" ""))
6876   (use (match_operand:HI 0 "reg_operand" ""))
6877   (parallel [(set (match_dup 11)
6878                   (neg:QI (match_operand:QI 2 "reg_operand" "")))
6879              (clobber (reg:CC_NOOV 21))])
6880   /* If the shift count is greater than 32 this will give zero.  */
6881   (parallel [(set (match_dup 7)
6882                   (lshiftrt:QI (match_dup 3)
6883                                (neg:QI (match_dup 11))))
6884              (clobber (reg:CC 21))])
6885   /* If the shift count is greater than 32 this will give zero.  */
6886   (parallel [(set (match_dup 8)
6887                   (lshiftrt:QI (match_dup 4) 
6888                                (neg:QI (match_dup 11))))
6889              (clobber (reg:CC 21))])
6890   (parallel [(set (match_dup 10)
6891                   (plus:QI (match_dup 11) (const_int 32)))
6892              (clobber (reg:CC_NOOV 21))])
6893   /* If the shift count is greater than 32 this will do an arithmetic
6894      right shift.  However, we need a logical right shift.  */
6895   (parallel [(set (match_dup 9)
6896                   (ashift:QI (match_dup 4) (unspec:QI [(match_dup 10)] UNSPEC_LSH)))
6897              (clobber (reg:CC 21))])
6898   (set (match_dup 6) (match_dup 8))
6899   (parallel [(set (match_dup 5)
6900                   (ior:QI (match_dup 7) (match_dup 9)))
6901              (clobber (reg:CC 21))])]
6902  ""
6903  " 
6904   operands[3] = operand_subword (operands[1], 0, 1, HImode); /* lo */
6905   operands[4] = operand_subword (operands[1], 1, 1, HImode); /* hi */
6906   operands[5] = operand_subword (operands[0], 0, 1, HImode); /* lo */
6907   operands[6] = operand_subword (operands[0], 1, 1, HImode); /* hi */
6908   operands[7] = gen_reg_rtx (QImode); /* lo >> count */
6909   operands[8] = gen_reg_rtx (QImode); /* hi >> count */
6910   operands[9] = gen_reg_rtx (QImode); /* hi << (32 - count) */
6911   operands[10] = gen_reg_rtx (QImode); /* 32 - count */
6912   operands[11] = gen_reg_rtx (QImode); /* -count */
6913  ")
6914
6915 ; This should do all the dirty work with define_split
6916 (define_expand "ashrhi3"
6917   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6918               (ashiftrt:HI (match_operand:HI 1 "src_operand" "")
6919                            (match_operand:QI 2 "src_operand" "")))
6920               (clobber (reg:CC 21))])]
6921  ""
6922  "if (GET_CODE (operands[2]) == CONST_INT && INTVAL (operands[2]) >= 32)
6923     {
6924        rtx op0hi = operand_subword (operands[0], 1, 0, HImode);
6925        rtx op0lo = operand_subword (operands[0], 0, 0, HImode);
6926        rtx op1hi = operand_subword (operands[1], 1, 0, HImode);
6927        rtx count = GEN_INT ((INTVAL (operands[2]) - 32));
6928
6929        if (INTVAL (count))
6930          emit_insn (gen_ashrqi3 (op0lo, op1hi, count));
6931        else
6932          emit_insn (gen_movqi (op0lo, op1hi));
6933        emit_insn (gen_ashrqi3 (op0hi, op1hi, GEN_INT (31)));
6934        DONE;
6935     }
6936   if (! REG_P (operands[1]))
6937     operands[1] = force_reg (HImode, operands[1]);
6938   emit_insn (gen_ashrhi3_reg (operands[0], operands[1], operands[2]));
6939   DONE;")
6940
6941 ; %0.hi = %1.hi >> %2
6942 ; %0.lo = (%1.lo >> %2 ) | (%1.hi << (32 - %2))
6943 ; This algorithm should work for shift counts greater than 32
6944 (define_expand "ashrhi3_reg" 
6945  [(use (match_operand:HI 1 "reg_operand" ""))
6946   (use (match_operand:HI 0 "reg_operand" ""))
6947   (parallel [(set (match_dup 11)
6948                   (neg:QI (match_operand:QI 2 "reg_operand" "")))
6949              (clobber (reg:CC_NOOV 21))])
6950   /* If the shift count is greater than 32 this will give zero.  */
6951   (parallel [(set (match_dup 7)
6952                   (lshiftrt:QI (match_dup 3)
6953                                (neg:QI (match_dup 11))))
6954              (clobber (reg:CC 21))])
6955   /* If the shift count is greater than 32 this will give zero.  */
6956   (parallel [(set (match_dup 8)
6957                   (ashiftrt:QI (match_dup 4) 
6958                                (neg:QI (match_dup 11))))
6959              (clobber (reg:CC 21))])
6960   (parallel [(set (match_dup 10)
6961                   (plus:QI (match_dup 11) (const_int 32)))
6962              (clobber (reg:CC_NOOV 21))])
6963   /* If the shift count is greater than 32 this will do an arithmetic
6964      right shift.  */
6965   (parallel [(set (match_dup 9)
6966                   (ashift:QI (match_dup 4) (match_dup 10)))
6967              (clobber (reg:CC 21))])
6968   (set (match_dup 6) (match_dup 8))
6969   (parallel [(set (match_dup 5)
6970                   (ior:QI (match_dup 7) (match_dup 9)))
6971              (clobber (reg:CC 21))])]
6972  ""
6973  " 
6974   operands[3] = operand_subword (operands[1], 0, 1, HImode); /* lo */
6975   operands[4] = operand_subword (operands[1], 1, 1, HImode); /* hi */
6976   operands[5] = operand_subword (operands[0], 0, 1, HImode); /* lo */
6977   operands[6] = operand_subword (operands[0], 1, 1, HImode); /* hi */
6978   operands[7] = gen_reg_rtx (QImode); /* lo >> count */
6979   operands[8] = gen_reg_rtx (QImode); /* hi >> count */
6980   operands[9] = gen_reg_rtx (QImode); /* hi << (32 - count) */
6981   operands[10] = gen_reg_rtx (QImode); /* 32 - count */
6982   operands[11] = gen_reg_rtx (QImode); /* -count */
6983  ")
6984
6985 (define_expand "cmphi"
6986   [(set (reg:CC 21)
6987         (compare:CC (match_operand:HI 0 "src_operand" "")
6988                     (match_operand:HI 1 "src_operand" "")))]
6989   ""
6990   "legitimize_operands (COMPARE, operands, HImode);
6991    c4x_compare_op0 = operands[0];
6992    c4x_compare_op1 = operands[1];
6993    DONE;")
6994
6995 (define_insn "*cmphi_cc"
6996   [(set (reg:CC 21)
6997         (compare:CC (match_operand:HI 0 "src_operand" "rR,rS<>")
6998                     (match_operand:HI 1 "src_operand" "R,rS<>")))]
6999   "valid_operands (COMPARE, operands, HImode)"
7000   "#"
7001   [(set_attr "type" "multi")])
7002
7003 (define_insn "*cmphi_cc_noov"
7004   [(set (reg:CC_NOOV 21)
7005         (compare:CC_NOOV (match_operand:HI 0 "src_operand" "rR,rS<>")
7006                          (match_operand:HI 1 "src_operand" "R,rS<>")))]
7007   "valid_operands (COMPARE, operands, HImode)"
7008   "#"
7009   [(set_attr "type" "multi")])
7010
7011 ; This works only before reload because we need 2 extra registers.
7012 ; Use unspec to avoid recursive split.
7013 (define_split
7014   [(set (reg:CC 21)
7015         (compare:CC (match_operand:HI 0 "src_operand" "")
7016                     (match_operand:HI 1 "src_operand" "")))]
7017   "! reload_completed"
7018   [(parallel [(set (reg:CC 21)
7019                    (unspec:CC [(compare:CC (match_dup 0)
7020                                            (match_dup 1))] UNSPEC_CMPHI))
7021               (clobber (match_scratch:QI 2 ""))
7022               (clobber (match_scratch:QI 3 ""))])]
7023   "")
7024
7025 (define_split
7026   [(set (reg:CC_NOOV 21)
7027         (compare:CC_NOOV (match_operand:HI 0 "src_operand" "")
7028                          (match_operand:HI 1 "src_operand" "")))]
7029   "! reload_completed"
7030   [(parallel [(set (reg:CC_NOOV 21)
7031                    (unspec:CC_NOOV [(compare:CC_NOOV (match_dup 0)
7032                                                      (match_dup 1))] UNSPEC_CMPHI))
7033               (clobber (match_scratch:QI 2 ""))
7034               (clobber (match_scratch:QI 3 ""))])]
7035   "")
7036
7037 ; This is normally not used. The define splits above are used first.
7038 (define_split
7039   [(set (reg:CC 21)
7040         (compare:CC (match_operand:HI 0 "src_operand" "")
7041                     (match_operand:HI 1 "src_operand" "")))]
7042   "reload_completed"
7043   [(parallel [(set (reg:CC 21)
7044                    (compare:CC (match_dup 0) (match_dup 1)))
7045               (use (reg:QI 20))])]
7046   "")
7047
7048 (define_split
7049   [(set (reg:CC_NOOV 21)
7050         (compare:CC_NOOV (match_operand:HI 0 "src_operand" "")
7051                          (match_operand:HI 1 "src_operand" "")))]
7052   "reload_completed"
7053   [(parallel [(set (reg:CC_NOOV 21)
7054                    (compare:CC_NOOV (match_dup 0) (match_dup 1)))
7055               (use (reg:QI 20))])]
7056   "")
7057
7058 (define_insn "*cmphi"
7059   [(set (reg:CC 21)
7060         (compare:CC (match_operand:HI 0 "src_operand" "rR,rS<>")
7061                     (match_operand:HI 1 "src_operand" "R,rS<>")))
7062    (use (reg:QI 20))]
7063   "valid_operands (COMPARE, operands, HImode)"
7064   "*
7065    {
7066      int use_ir1 = (reg_operand (operands[0], HImode)
7067                     && REG_P (operands[0])
7068                     && REGNO (operands[0]) == IR1_REGNO)
7069                     || (reg_operand (operands[1], HImode)
7070                         && REG_P (operands[1])
7071                         && REGNO (operands[1]) == IR1_REGNO);
7072
7073      if (use_ir1)
7074        output_asm_insn (\"push\\tir1\", operands);
7075      else
7076        output_asm_insn (\"push\\tbk\", operands);
7077      output_asm_insn (\"push\\tr0\", operands);
7078      output_asm_insn (\"subi3\\t%1,%0,r0\", operands);
7079      if (use_ir1)
7080        {
7081          output_asm_insn (\"ldiu\\tst,ir1\", operands);
7082          output_asm_insn (\"or\\t07bh,ir1\", operands);
7083        }
7084      else
7085        {
7086          output_asm_insn (\"ldiu\\tst,bk\", operands);
7087          output_asm_insn (\"or\\t07bh,bk\", operands);
7088        }
7089      output_asm_insn (\"subb3\\t%O1,%O0,r0\", operands);
7090      if (use_ir1)
7091        output_asm_insn (\"and3\\tir1,st,ir1\", operands);
7092      else
7093        output_asm_insn (\"and3\\tbk,st,bk\", operands);
7094      output_asm_insn (\"pop\\tr0\", operands);
7095      if (use_ir1)
7096        {
7097          output_asm_insn (\"ldiu\\tir1,st\", operands);
7098          output_asm_insn (\"pop\\tir1\", operands);
7099        }
7100      else
7101        {
7102          output_asm_insn (\"ldiu\\tbk,st\", operands);
7103          output_asm_insn (\"pop\\tbk\", operands);
7104        }
7105      return \"\";
7106    }"
7107   [(set_attr "type" "multi")])
7108  
7109 (define_insn "*cmphi_noov"
7110   [(set (reg:CC_NOOV 21)
7111         (compare:CC_NOOV (match_operand:HI 0 "src_operand" "rR,rS<>")
7112                          (match_operand:HI 1 "src_operand" "R,rS<>")))
7113    (use (reg:QI 20))]
7114   "valid_operands (COMPARE, operands, HImode)"
7115   "*
7116    {
7117      int use_ir1 = (reg_operand (operands[0], HImode)
7118                     && REG_P (operands[0])
7119                     && REGNO (operands[0]) == IR1_REGNO)
7120                     || (reg_operand (operands[1], HImode)
7121                         && REG_P (operands[1])
7122                         && REGNO (operands[1]) == IR1_REGNO);
7123
7124      if (use_ir1)
7125        output_asm_insn (\"push\\tir1\", operands);
7126      else
7127        output_asm_insn (\"push\\tbk\", operands);
7128      output_asm_insn (\"push\\tr0\", operands);
7129      output_asm_insn (\"subi3\\t%1,%0,r0\", operands);
7130      if (use_ir1)
7131        {
7132          output_asm_insn (\"ldiu\\tst,ir1\", operands);
7133          output_asm_insn (\"or\\t07bh,ir1\", operands);
7134        }
7135      else
7136        {
7137          output_asm_insn (\"ldiu\\tst,bk\", operands);
7138          output_asm_insn (\"or\\t07bh,bk\", operands);
7139        }
7140      output_asm_insn (\"subb3\\t%O1,%O0,r0\", operands);
7141      if (use_ir1)
7142        output_asm_insn (\"and3\\tir1,st,ir1\", operands);
7143      else
7144        output_asm_insn (\"and3\\tbk,st,bk\", operands);
7145      output_asm_insn (\"pop\\tr0\", operands);
7146      if (use_ir1)
7147        {
7148          output_asm_insn (\"ldiu\\tir1,st\", operands);
7149          output_asm_insn (\"pop\\tir1\", operands);
7150        }
7151      else
7152        {
7153          output_asm_insn (\"ldiu\\tbk,st\", operands);
7154          output_asm_insn (\"pop\\tbk\", operands);
7155        }
7156      return \"\";
7157    }"
7158   [(set_attr "type" "multi")])
7159
7160  
7161 (define_insn "cmphi_cc"
7162   [(set (reg:CC 21)
7163         (unspec:CC [(compare:CC (match_operand:HI 0 "src_operand" "rR,rS<>")
7164                                 (match_operand:HI 1 "src_operand" "R,rS<>"))] UNSPEC_CMPHI))
7165    (clobber (match_scratch:QI 2 "=&d,&d"))
7166    (clobber (match_scratch:QI 3 "=&c,&c"))]
7167   "valid_operands (COMPARE, operands, HImode)"
7168   "*
7169    output_asm_insn (\"subi3\\t%1,%0,%2\", operands);
7170    output_asm_insn (\"ldiu\\tst,%3\", operands);
7171    output_asm_insn (\"or\\t07bh,%3\", operands);
7172    output_asm_insn (\"subb3\\t%O1,%O0,%2\", operands);
7173    output_asm_insn (\"and\\t%3,st\", operands);
7174    return \"\";"
7175   [(set_attr "type" "multi")])
7176
7177 (define_insn "cmphi_cc_noov"
7178   [(set (reg:CC_NOOV 21)
7179         (unspec:CC_NOOV [(compare:CC_NOOV (match_operand:HI 0 "src_operand" "rR,rS<>")
7180                                      (match_operand:HI 1 "src_operand" "R,rS<>"))] UNSPEC_CMPHI))
7181    (clobber (match_scratch:QI 2 "=&d,&d"))
7182    (clobber (match_scratch:QI 3 "=&c,&c"))]
7183   "valid_operands (COMPARE, operands, HImode)"
7184   "*
7185    output_asm_insn (\"subi3\\t%1,%0,%2\", operands);
7186    output_asm_insn (\"ldiu\\tst,%3\", operands);
7187    output_asm_insn (\"or\\t07bh,%3\", operands);
7188    output_asm_insn (\"subb3\\t%O1,%O0,%2\", operands);
7189    output_asm_insn (\"and\\t%3,st\", operands);
7190    return \"\";"
7191   [(set_attr "type" "multi")])
7192
7193 (define_expand "mulhi3"
7194   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
7195                    (mult:HI (match_operand:HI 1 "src_operand" "")
7196                             (match_operand:HI 2 "src_operand" "")))
7197               (clobber (reg:CC 21))])]
7198   ""
7199   "c4x_emit_libcall3 (smul_optab->handlers[(int) HImode].libfunc,
7200                       MULT, HImode, operands);
7201    DONE;")
7202
7203
7204 ;
7205 ; PEEPHOLES
7206 ;
7207
7208 ; dbCC peepholes
7209 ;
7210 ; Turns
7211 ;   loop:
7212 ;           [ ... ]
7213 ;           bCC label           ; abnormal loop termination
7214 ;           dbu aN, loop        ; normal loop termination
7215 ;
7216 ; Into
7217 ;   loop:
7218 ;           [ ... ]
7219 ;           dbCC aN, loop
7220 ;           bCC label
7221 ;
7222 ; Which moves the bCC condition outside the inner loop for free.
7223 ;
7224 (define_peephole
7225   [(set (pc) (if_then_else (match_operator 3 "comparison_operator"
7226                            [(reg:CC 21) (const_int 0)])
7227                            (label_ref (match_operand 2 "" ""))
7228                            (pc)))
7229    (parallel
7230     [(set (pc)
7231           (if_then_else
7232             (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a")
7233                          (const_int -1))
7234                 (const_int 0))
7235             (label_ref (match_operand 1 "" ""))
7236             (pc)))
7237      (set (match_dup 0)
7238           (plus:QI (match_dup 0)
7239                    (const_int -1)))
7240      (use (reg:QI 20))
7241      (clobber (reg:CC_NOOV 21))])]
7242   "! c4x_label_conflict (insn, operands[2], operands[1])"
7243   "db%I3\\t%0,%l1\\n\\tb%3\\t%l2"
7244   [(set_attr "type" "multi")])
7245
7246 (define_peephole
7247   [(set (pc) (if_then_else (match_operator 3 "comparison_operator"
7248                            [(reg:CC 21) (const_int 0)])
7249                            (label_ref (match_operand 2 "" ""))
7250                            (pc)))
7251    (parallel
7252     [(set (pc)
7253           (if_then_else
7254             (ne (match_operand:QI 0 "addr_reg_operand" "+a")
7255                 (const_int 0))
7256             (label_ref (match_operand 1 "" ""))
7257             (pc)))
7258      (set (match_dup 0)
7259           (plus:QI (match_dup 0)
7260                    (const_int -1)))])]
7261   "! c4x_label_conflict (insn, operands[2], operands[1])"
7262   "db%I3\\t%0,%l1\\n\\tb%3\\t%l2"
7263   [(set_attr "type" "multi")])
7264
7265 ;
7266 ; Peepholes to convert 'call label; rets' into jump label
7267 ;
7268
7269 (define_peephole
7270   [(parallel [(call (mem:QI (match_operand:QI 0 "call_address_operand" ""))
7271                     (match_operand:QI 1 "general_operand" ""))
7272               (clobber (reg:QI 31))])
7273    (return)]
7274   "! c4x_null_epilogue_p ()"
7275   "*
7276    if (REG_P (operands[0]))
7277      return \"bu%#\\t%C0\";
7278    else
7279      return \"br%#\\t%C0\";"
7280   [(set_attr "type" "jump")])
7281
7282 (define_peephole
7283   [(parallel [(set (match_operand 0 "" "")
7284                    (call (mem:QI (match_operand:QI 1 "call_address_operand" ""))
7285                          (match_operand:QI 2 "general_operand" "")))
7286               (clobber (reg:QI 31))])
7287    (return)]
7288   "! c4x_null_epilogue_p ()"
7289   "*
7290    if (REG_P (operands[1]))
7291      return \"bu%#\\t%C1\";
7292    else
7293      return \"br%#\\t%C1\";"
7294   [(set_attr "type" "jump")])
7295
7296
7297 ; This peephole should be unnecessary with my patches to flow.c
7298 ; for better autoincrement detection
7299 (define_peephole
7300  [(set (match_operand:QF 0 "ext_low_reg_operand" "")
7301        (mem:QF (match_operand:QI 1 "addr_reg_operand" "")))
7302   (set (match_operand:QF 2 "ext_low_reg_operand" "")
7303        (mem:QF (plus:QI (match_dup 1) (const_int 1))))
7304   (parallel [(set (match_dup 1) (plus:QI (match_dup 1) (const_int 2)))
7305              (clobber (reg:CC_NOOV 21))])]
7306  ""
7307  "ldf\\t*%1++,%0\\n\\tldf\\t*%1++,%2")
7308
7309
7310 ; This peephole should be unnecessary with my patches to flow.c
7311 ; for better autoincrement detection
7312 (define_peephole
7313  [(set (mem:QF (match_operand:QI 0 "addr_reg_operand" ""))
7314        (match_operand:QF 1 "ext_low_reg_operand" ""))
7315   (set (mem:QF (plus:QI (match_dup 0) (const_int 1)))
7316        (match_operand:QF 2 "ext_low_reg_operand" ""))
7317   (parallel [(set (match_dup 0) (plus:QI (match_dup 0) (const_int 2)))
7318              (clobber (reg:CC_NOOV 21))])]
7319  ""
7320  "stf\\t%1,*%0++\\n\\tstf\\t%2,*%0++")
7321
7322
7323 ; The following two peepholes remove an unecessary load
7324 ; often found at the end of a function.  These peepholes
7325 ; could be generalized to other binary operators.  They shouldn't
7326 ; be required if we run a post reload mop-up pass.
7327 (define_peephole
7328  [(parallel [(set (match_operand:QF 0 "ext_reg_operand" "")
7329                   (plus:QF (match_operand:QF 1 "ext_reg_operand" "")
7330                            (match_operand:QF 2 "ext_reg_operand" "")))
7331              (clobber (reg:CC_NOOV 21))])
7332   (set (match_operand:QF 3 "ext_reg_operand" "")
7333        (match_dup 0))]
7334  "dead_or_set_p (insn, operands[0])"
7335  "addf3\\t%2,%1,%3")
7336
7337 (define_peephole
7338  [(parallel [(set (match_operand:QI 0 "reg_operand" "")
7339                   (plus:QI (match_operand:QI 1 "reg_operand" "")
7340                            (match_operand:QI 2 "reg_operand" "")))
7341              (clobber (reg:CC_NOOV 21))])
7342   (set (match_operand:QI 3 "reg_operand" "")
7343        (match_dup 0))]
7344  "dead_or_set_p (insn, operands[0])"
7345  "addi3\\t%2,%1,%3")