OSDN Git Service

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