OSDN Git Service

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