OSDN Git Service

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