OSDN Git Service

2000-02-05 Michael Hayes <m.hayes@elec.canterbury.ac.nz>
[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 && ! TARGET_TI"
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   "! TARGET_TI"
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 && ! TARGET_TI"
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 || TARGET_TI
1255        || (reload_completed
1256            && ! std_reg_operand (operands[0], QImode)))"
1257   [(set (match_dup 2) (high:QI (match_dup 3)))
1258    (set (match_dup 0) (match_dup 4))
1259    (use (match_dup 1))]
1260   "
1261 {
1262    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1263    operands[2] = dp_reg;
1264    operands[3] = force_const_mem (Pmode, operands[1]);
1265    operands[4] = change_address (operands[3], QImode,
1266                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1267                                                  XEXP (operands[3], 0)));
1268    operands[3] = XEXP (operands[3], 0);
1269 }")
1270
1271 ; This pattern is similar to the above but does not emit a LDP
1272 ; for the small memory model.
1273 (define_split
1274   [(set (match_operand:QI 0 "reg_operand" "")
1275         (match_operand:QI 1 "symbolic_address_operand" ""))]
1276   "TARGET_SMALL
1277    && (TARGET_C3X || TARGET_TI
1278        || (reload_completed
1279            && ! std_reg_operand (operands[0], QImode)))"
1280   [(set (match_dup 0) (match_dup 2))
1281    (use (match_dup 1))]
1282   "
1283 {  
1284    rtx dp_reg = gen_rtx_REG (Pmode, DP_REGNO);
1285    operands[2] = force_const_mem (Pmode, operands[1]);
1286    operands[2] = change_address (operands[2], QImode,
1287                                  gen_rtx_LO_SUM (Pmode, dp_reg,
1288                                                  XEXP (operands[2], 0)));
1289 }")
1290
1291 (define_insn "load_immed_address"
1292   [(set (match_operand:QI 0 "reg_operand" "=a?x?c*r")
1293         (match_operand:QI 1 "symbolic_address_operand" ""))]
1294   "TARGET_LOAD_ADDRESS"
1295   "#"
1296   [(set_attr "type" "multi")])
1297
1298 (define_insn "loadhi_big_constant"
1299   [(set (match_operand:HI 0 "reg_operand" "=c*d")
1300         (match_operand:HI 1 "const_int_operand" ""))]
1301   ""
1302   "#"
1303   [(set_attr "type" "multi")])
1304
1305 ;
1306 ; LDIU/LDA/STI/STIK
1307 ;
1308 ; The following moves will not set the condition codes register.
1309 ;
1310
1311 ; This must come before the general case
1312 (define_insn "*movqi_stik"
1313   [(set (match_operand:QI 0 "memory_operand" "=m")
1314         (match_operand:QI 1 "stik_const_operand" "K"))]
1315   "! TARGET_C3X"
1316   "stik\\t%1,%0"
1317   [(set_attr "type" "store")])
1318
1319 (define_insn "loadqi_big_constant"
1320   [(set (match_operand:QI 0 "reg_operand" "=c*d")
1321         (match_operand:QI 1 "const_int_operand" ""))]
1322   "! IS_INT16_CONST (INTVAL (operands[1]))
1323    && ! IS_HIGH_CONST (INTVAL (operands[1]))"
1324   "#"
1325   [(set_attr "type" "multi")])
1326
1327 ; We must provide an alternative to store to memory in case we have to
1328 ; spill a register.
1329 (define_insn "movqi_noclobber"
1330   [(set (match_operand:QI 0 "dst_operand" "=d,*c,m,r")
1331         (match_operand:QI 1 "src_hi_operand" "rIm,rIm,r,O"))]
1332   "(REG_P (operands[0]) || REG_P (operands[1])
1333     || GET_CODE (operands[0]) == SUBREG
1334     || GET_CODE (operands[1]) == SUBREG)
1335     && ! symbolic_address_operand (operands[1], QImode)"
1336   "*
1337    if (which_alternative == 2)
1338      return \"sti\\t%1,%0\";
1339
1340    if (! TARGET_C3X && which_alternative == 3)
1341      {
1342        operands[1] = GEN_INT ((INTVAL (operands[1]) >> 16) & 0xffff);
1343        return \"ldhi\\t%1,%0\";
1344      }
1345
1346    /* The lda instruction cannot use the same register as source
1347       and destination.  */
1348    if (! TARGET_C3X && which_alternative == 1
1349        && (   IS_ADDR_REG (operands[0])
1350            || IS_INDEX_REG (operands[0])
1351            || IS_SP_REG (operands[0]))
1352        && (REGNO (operands[0]) != REGNO (operands[1])))
1353       return \"lda\\t%1,%0\";
1354    return \"ldiu\\t%1,%0\";
1355   "
1356   [(set_attr "type" "unary,lda,store,unary")
1357    (set_attr "data" "int16,int16,int16,high_16")])
1358
1359 ;
1360 ; LDI
1361 ;
1362
1363 ; We shouldn't need these peepholes, but the combiner seems to miss them...
1364 (define_peephole
1365   [(set (match_operand:QI 0 "ext_reg_operand" "=d")
1366         (match_operand:QI 1 "src_operand" "rIm"))
1367    (set (reg:CC 21)
1368         (compare:CC (match_dup 0) (const_int 0)))]
1369   ""
1370   "@
1371   ldi\\t%1,%0"
1372   [(set_attr "type" "unarycc")
1373    (set_attr "data" "int16")])
1374
1375 (define_insn "*movqi_set"
1376   [(set (reg:CC 21)
1377         (compare:CC (match_operand:QI 1 "src_operand" "rIm") 
1378                     (const_int 0)))
1379    (set (match_operand:QI 0 "ext_reg_operand" "=d")
1380         (match_dup 1))]
1381   ""
1382   "@
1383   ldi\\t%1,%0"
1384   [(set_attr "type" "unarycc")
1385    (set_attr "data" "int16")])
1386
1387 ; This pattern probably gets in the way and requires a scratch register
1388 ; when a simple compare with zero will suffice.
1389 ;(define_insn "*movqi_test"
1390 ; [(set (reg:CC 21)
1391 ;       (compare:CC (match_operand:QI 1 "src_operand" "rIm") 
1392 ;                   (const_int 0)))
1393 ;  (clobber (match_scratch:QI 0 "=d"))]
1394 ; ""
1395 ; "@
1396 ;  ldi\\t%1,%0"
1397 ;  [(set_attr "type" "unarycc")
1398 ;   (set_attr "data" "int16")])
1399
1400 ;  If one of the operands is not a register, then we should
1401 ;  emit two insns, using a scratch register.  This will produce
1402 ;  better code in loops if the source operand is invariant, since
1403 ;  the source reload can be optimised out.  During reload we cannot
1404 ;  use change_address or force_reg which will allocate new pseudo regs.
1405
1406 ;  Unlike most other insns, the move insns can't be split with
1407 ;  different predicates, because register spilling and other parts of
1408 ;  the compiler, have memoized the insn number already.
1409
1410 (define_expand "movqi"
1411   [(set (match_operand:QI 0 "general_operand" "")
1412         (match_operand:QI 1 "general_operand" ""))]
1413   ""
1414   "
1415 {
1416   if (c4x_emit_move_sequence (operands, QImode))
1417     DONE;
1418 }")
1419
1420
1421 (define_insn "movqi_parallel"
1422   [(set (match_operand:QI 0 "parallel_operand" "=q,S<>!V,q,S<>!V")
1423         (match_operand:QI 1 "parallel_operand" "S<>!V,q,S<>!V,q"))
1424    (set (match_operand:QI 2 "parallel_operand" "=q,S<>!V,S<>!V,q")
1425         (match_operand:QI 3 "parallel_operand" "S<>!V,q,q,S<>!V"))]
1426   "TARGET_PARALLEL && valid_parallel_load_store (operands, QImode)"
1427   "@
1428    ldi1\\t%1,%0\\n||\\tldi2\\t%3,%2
1429    sti1\\t%1,%0\\n||\\tsti2\\t%3,%2
1430    ldi\\t%1,%0\\n||\\tsti\\t%3,%2
1431    ldi\\t%3,%2\\n||\\tsti\\t%1,%0"
1432   [(set_attr "type" "load_load,store_store,load_store,store_load")])
1433
1434 ;
1435 ; PUSH/POP
1436 ;
1437 (define_insn "*pushqi"
1438   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
1439         (match_operand:QI 0 "reg_operand" "r"))]
1440   ""
1441   "push\\t%0"
1442   [(set_attr "type" "push")])
1443
1444 (define_insn "*popqi"
1445   [(set (match_operand:QI 0 "reg_operand" "=r")
1446         (mem:QI (post_dec:QI (reg:QI 20))))
1447    (clobber (reg:CC 21))]
1448   ""
1449   "pop\\t%0"
1450   [(set_attr "type" "pop")])
1451
1452 ;
1453 ; ABSI
1454 ;
1455 (define_expand "absqi2"
1456   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1457                    (abs:QI (match_operand:QI 1 "src_operand" "")))
1458               (clobber (reg:CC_NOOV 21))])]
1459   ""
1460   "")
1461
1462 (define_insn "*absqi2_clobber"
1463   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1464         (abs:QI (match_operand:QI 1 "src_operand" "rIm,rIm")))
1465    (clobber (reg:CC_NOOV 21))]
1466   ""
1467   "absi\\t%1,%0"
1468   [(set_attr "type" "unarycc,unary")
1469    (set_attr "data" "int16,int16")])
1470
1471 (define_insn "*absqi2_noclobber"
1472   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1473         (abs:QI (match_operand:QI 1 "src_operand" "rIm")))]
1474   ""
1475   "absi\\t%1,%0"
1476   [(set_attr "type" "unary")
1477    (set_attr "data" "int16")])
1478
1479 (define_split
1480   [(set (match_operand:QI 0 "std_reg_operand" "")
1481         (abs:QI (match_operand:QI 1 "src_operand" "")))
1482    (clobber (reg:CC_NOOV 21))]
1483   "reload_completed"
1484   [(set (match_dup 0)
1485         (abs:QI (match_dup 1)))]
1486   "")
1487
1488 (define_insn "*absqi2_test"
1489   [(set (reg:CC_NOOV 21)
1490         (compare:CC_NOOV (abs:QI (match_operand:QI 1 "src_operand" "rIm"))
1491                          (const_int 0)))
1492    (clobber (match_scratch:QI 0 "=d"))]
1493   ""
1494   "absi\\t%1,%0"
1495   [(set_attr "type" "unarycc")
1496    (set_attr "data" "int16")])
1497
1498 (define_insn "*absqi2_set"
1499   [(set (reg:CC_NOOV 21)
1500         (compare:CC_NOOV (abs:QI (match_operand:QI 1 "src_operand" "rIm"))
1501                          (const_int 0)))
1502    (set (match_operand:QI 0 "ext_reg_operand" "=d")
1503         (abs:QI (match_dup 1)))]
1504   ""
1505   "absi\\t%1,%0"
1506   [(set_attr "type" "unarycc")
1507    (set_attr "data" "int16")])        
1508
1509 ;
1510 ; NEGI
1511 ;
1512 (define_expand "negqi2"
1513   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1514                    (neg:QI (match_operand:QI 1 "src_operand" "")))
1515               (clobber (reg:CC_NOOV 21))])]
1516 ""
1517 "")
1518
1519 (define_insn "*negqi2_clobber"
1520   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1521         (neg:QI (match_operand:QI 1 "src_operand" "rIm,rIm")))
1522    (clobber (reg:CC_NOOV 21))]
1523   ""
1524   "negi\\t%1,%0"
1525   [(set_attr "type" "unarycc,unary")
1526    (set_attr "data" "int16,int16")])
1527
1528 (define_insn "*negqi2_noclobber"
1529   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1530         (neg:QI (match_operand:QI 1 "src_operand" "rIm")))]
1531   ""
1532   "negi\\t%1,%0"
1533   [(set_attr "type" "unary")
1534    (set_attr "data" "int16")])
1535
1536 (define_split
1537   [(set (match_operand:QI 0 "std_reg_operand" "")
1538         (neg:QI (match_operand:QI 1 "src_operand" "")))
1539    (clobber (reg:CC_NOOV 21))]
1540   "reload_completed"
1541   [(set (match_dup 0)
1542         (neg:QI (match_dup 1)))]
1543   "")
1544
1545 (define_insn "*negqi2_test"
1546   [(set (reg:CC_NOOV 21)
1547         (compare:CC_NOOV (neg:QI (match_operand:QI 1 "src_operand" "rIm"))
1548                          (const_int 0)))
1549    (clobber (match_scratch:QI 0 "=d"))]
1550   ""
1551   "negi\\t%1,%0"
1552   [(set_attr "type" "unarycc")
1553    (set_attr "data" "int16")])
1554
1555 (define_insn "*negqi2_set"
1556   [(set (reg:CC_NOOV 21)
1557         (compare:CC_NOOV (neg:QI (match_operand:QI 1 "src_operand" "rIm"))
1558                          (const_int 0)))
1559    (set (match_operand:QI 0 "ext_reg_operand" "=d")
1560         (neg:QI (match_dup 1)))]
1561   ""
1562   "negi\\t%1,%0"
1563   [(set_attr "type" "unarycc")
1564    (set_attr "data" "int16")])        
1565
1566 (define_insn "*negbqi2_clobber"
1567   [(set (match_operand:QI 0 "ext_reg_operand" "=d")
1568         (neg:QI (match_operand:QI 1 "src_operand" "rIm")))
1569    (use (reg:CC_NOOV 21))
1570    (clobber (reg:CC_NOOV 21))]
1571   ""
1572   "negb\\t%1,%0"
1573   [(set_attr "type" "unarycc")
1574    (set_attr "data" "int16")])        
1575
1576 ;
1577 ; NOT
1578 ;
1579 (define_expand "one_cmplqi2"
1580   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1581                    (not:QI (match_operand:QI 1 "lsrc_operand" "")))
1582               (clobber (reg:CC 21))])]
1583   ""
1584   "")
1585
1586 (define_insn "*one_cmplqi2_clobber"
1587   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1588         (not:QI (match_operand:QI 1 "lsrc_operand" "rLm,rLm")))
1589    (clobber (reg:CC 21))]
1590   ""
1591   "not\\t%1,%0"
1592   [(set_attr "type" "unarycc,unary")
1593    (set_attr "data" "uint16,uint16")])
1594
1595 (define_insn "*one_cmplqi2_noclobber"
1596   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1597         (not:QI (match_operand:QI 1 "lsrc_operand" "rLm")))]
1598   ""
1599   "not\\t%1,%0"
1600   [(set_attr "type" "unary")
1601    (set_attr "data" "uint16")])
1602
1603 (define_split
1604   [(set (match_operand:QI 0 "std_reg_operand" "")
1605         (not:QI (match_operand:QI 1 "lsrc_operand" "")))
1606    (clobber (reg:CC 21))]
1607   "reload_completed"
1608   [(set (match_dup 0)
1609         (not:QI (match_dup 1)))]
1610   "")
1611
1612 (define_insn "*one_cmplqi2_test"
1613   [(set (reg:CC 21)
1614         (compare:CC (not:QI (match_operand:QI 1 "lsrc_operand" "rLm"))
1615                     (const_int 0)))
1616    (clobber (match_scratch:QI 0 "=d"))]
1617   ""
1618   "not\\t%1,%0"
1619   [(set_attr "type" "unarycc")
1620    (set_attr "data" "uint16")])
1621
1622 (define_insn "*one_cmplqi2_set"
1623   [(set (reg:CC 21)
1624         (compare:CC (not:QI (match_operand:QI 1 "lsrc_operand" "rLm"))
1625                     (const_int 0)))
1626    (set (match_operand:QI 0 "ext_reg_operand" "=d")        
1627         (not:QI (match_dup 1)))]
1628   ""
1629   "not\\t%1,%0"
1630   [(set_attr "type" "unarycc")
1631    (set_attr "data" "uint16")])        
1632
1633 (define_insn "*one_cmplqi2_const_clobber"
1634   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1635         (match_operand:QI 1 "not_const_operand" "N,N"))
1636    (clobber (reg:CC 21))]
1637   ""
1638   "@
1639    not\\t%N1,%0
1640    not\\t%N1,%0"
1641    [(set_attr "type" "unarycc,unary")
1642     (set_attr "data" "not_uint16,not_uint16")])
1643
1644 ; movqi can use this for loading an integer that can't normally
1645 ; fit into a 16-bit signed integer.  The drawback is that it cannot
1646 ; go into R0-R11 since that will clobber the CC and movqi shouldn't
1647 ; do that.  This can cause additional reloading but in most cases
1648 ; this will cause only an additional register move.  With the large
1649 ; memory model we require an extra instruction to load DP anyway,
1650 ; if we're loading the constant from memory.  The big advantage of
1651 ; allowing constants that satisfy not_const_operand in movqi, is that
1652 ; it allows andn to be generated more often.
1653 ; However, there is a problem if GCC has decided that it wants
1654 ; to use R0-R11, since we won't have a matching pattern...
1655 ; In interim, we prevent immed_const allowing `N' constants.
1656 (define_insn "*one_cmplqi2_const_noclobber"
1657   [(set (match_operand:QI 0 "std_reg_operand" "=c")
1658         (match_operand:QI 1 "not_const_operand" "N"))]
1659   ""
1660   "not\\t%N1,%0"
1661   [(set_attr "type" "unary")
1662    (set_attr "data" "not_uint16")])
1663
1664 ;
1665 ; ROL
1666 ;
1667 (define_expand "rotlqi3"
1668   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1669                    (rotate:QI (match_operand:QI 1 "reg_operand" "")
1670                               (match_operand:QI 2 "const_int_operand" "")))
1671               (clobber (reg:CC 21))])]
1672   ""
1673   "if (INTVAL (operands[2]) > 4)
1674      FAIL; /* Open code as two shifts and an or */
1675    if (INTVAL (operands[2]) > 1)
1676      {
1677         int i;
1678         rtx tmp;
1679
1680         /* If we have 4 or fewer shifts, then it is probably faster
1681            to emit separate ROL instructions.  A C3x requires
1682            at least 4 instructions (a C4x requires at least 3), to
1683            perform a rotation by shifts.  */
1684
1685         tmp = operands[1];
1686         for (i = 0; i < INTVAL (operands[2]) - 1; i++)
1687           {
1688             tmp = gen_reg_rtx (QImode);
1689             emit_insn (gen_rotl_1_clobber (tmp, operands[1]));
1690             operands[1] = tmp;
1691           }
1692         emit_insn (gen_rotl_1_clobber (operands[0], tmp));
1693         DONE;
1694      }")
1695
1696 (define_insn "rotl_1_clobber"
1697   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1698         (rotate:QI (match_operand:QI 1 "reg_operand" "0,0")
1699                    (const_int 1)))
1700    (clobber (reg:CC 21))]
1701   ""
1702   "rol\\t%0"
1703   [(set_attr "type" "unarycc,unary")])
1704 ; Default to int16 data attr.
1705
1706 ;
1707 ; ROR
1708 ;
1709 (define_expand "rotrqi3"
1710   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1711                    (rotatert:QI (match_operand:QI 1 "reg_operand" "")
1712                                 (match_operand:QI 2 "const_int_operand" "")))
1713               (clobber (reg:CC 21))])]
1714   ""
1715   "if (INTVAL (operands[2]) > 4)
1716      FAIL; /* Open code as two shifts and an or */
1717    if (INTVAL (operands[2]) > 1)
1718      {
1719         int i;
1720         rtx tmp;
1721  
1722         /* If we have 4 or fewer shifts, then it is probably faster
1723            to emit separate ROL instructions.  A C3x requires
1724            at least 4 instructions (a C4x requires at least 3), to
1725            perform a rotation by shifts.  */
1726  
1727         tmp = operands[1];
1728         for (i = 0; i < INTVAL (operands[2]) - 1; i++)
1729           {
1730             tmp = gen_reg_rtx (QImode);
1731             emit_insn (gen_rotr_1_clobber (tmp, operands[1]));
1732             operands[1] = tmp;
1733           }
1734         emit_insn (gen_rotr_1_clobber (operands[0], tmp));
1735         DONE;
1736      }")
1737
1738 (define_insn "rotr_1_clobber"
1739   [(set (match_operand:QI 0 "reg_operand" "=d,c")
1740         (rotatert:QI (match_operand:QI 1 "reg_operand" "0,0")
1741                      (const_int 1)))
1742    (clobber (reg:CC 21))]
1743   ""
1744   "ror\\t%0"
1745   [(set_attr "type" "unarycc,unary")])
1746 ; Default to int16 data attr.
1747
1748
1749 ;
1750 ; THREE OPERAND INTEGER INSTRUCTIONS
1751 ;
1752
1753 ;
1754 ; ADDI
1755 ;
1756 ; This is used by reload when it calls gen_add2_insn for address arithmetic
1757 ; so we must emit the pattern that doesn't clobber CC.
1758 ;
1759 (define_expand "addqi3"
1760   [(parallel [(set (match_operand:QI 0 "std_or_reg_operand" "")
1761                    (plus:QI (match_operand:QI 1 "src_operand" "")
1762                             (match_operand:QI 2 "src_operand" "")))
1763               (clobber (reg:CC_NOOV 21))])]
1764   ""
1765   "legitimize_operands (PLUS, operands, QImode);
1766    if (reload_in_progress
1767        || (! IS_PSEUDO_REG (operands[0]) 
1768            && ! IS_EXT_REG (operands[0])))
1769    {
1770       emit_insn (gen_addqi3_noclobber (operands[0], operands[1], operands[2]));
1771       DONE;
1772    }")
1773
1774 (define_insn "*addqi3_clobber"
1775   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
1776         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
1777                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
1778    (clobber (reg:CC_NOOV 21))]
1779   "valid_operands (PLUS, operands, QImode)"
1780   "@
1781    addi\\t%2,%0
1782    addi3\\t%2,%1,%0
1783    addi3\\t%2,%1,%0
1784    addi\\t%2,%0
1785    addi3\\t%2,%1,%0
1786    addi3\\t%2,%1,%0"
1787   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
1788 ; Default to int16 data attr.
1789
1790 (define_split
1791   [(set (match_operand:QI 0 "std_reg_operand" "")
1792         (plus:QI (match_operand:QI 1 "src_operand" "")
1793                  (match_operand:QI 2 "src_operand" "")))
1794    (clobber (reg:CC_NOOV 21))]
1795   "reload_completed"
1796   [(set (match_dup 0)
1797         (plus:QI (match_dup 1)
1798                  (match_dup 2)))]
1799   "")
1800
1801 (define_insn "*addqi3_test"
1802   [(set (reg:CC_NOOV 21)
1803         (compare:CC_NOOV (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1804                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
1805                          (const_int 0)))
1806    (clobber (match_scratch:QI 0 "=d,d,d"))]
1807   "valid_operands (PLUS, operands, QImode)"
1808   "@
1809    addi\\t%2,%0
1810    addi3\\t%2,%1,%0
1811    addi3\\t%2,%1,%0"
1812   [(set_attr "type" "binarycc,binarycc,binarycc")])
1813 ; Default to int16 data attr.
1814
1815 ; gcc does this in combine.c we just reverse it here
1816 (define_insn "*cmp_neg"
1817   [(set (reg:CC_NOOV 21)
1818         (compare:CC_NOOV (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1819                          (neg: QI (match_operand:QI 2 "src_operand" "g,JR,rS<>"))))
1820    (clobber (match_scratch:QI 0 "=d,d,d"))]
1821   "valid_operands (PLUS, operands, QImode)"
1822   "@
1823    addi\\t%2,%0
1824    addi3\\t%2,%1,%0
1825    addi3\\t%2,%1,%0"
1826   [(set_attr "type" "binarycc,binarycc,binarycc")])
1827   
1828 (define_peephole
1829   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
1830                    (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1831                             (match_operand:QI 2 "src_operand" "g,JR,rS<>")))
1832               (clobber (reg:CC_NOOV 21))])
1833    (set (reg:CC_NOOV 21)
1834         (compare:CC_NOOV (match_dup 0) (const_int 0)))]
1835   "valid_operands (PLUS, operands, QImode)"
1836   "@
1837    addi\\t%2,%0
1838    addi3\\t%2,%1,%0
1839    addi3\\t%2,%1,%0"
1840   [(set_attr "type" "binarycc,binarycc,binarycc")])
1841
1842 (define_insn "*addqi3_set"
1843   [(set (reg:CC_NOOV 21)
1844         (compare:CC_NOOV (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1845                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
1846                          (const_int 0)))
1847    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
1848         (plus:QI (match_dup 1) (match_dup 2)))]
1849   "valid_operands (PLUS, operands, QImode)"
1850   "@
1851    addi\\t%2,%0
1852    addi3\\t%2,%1,%0
1853    addi3\\t%2,%1,%0"
1854   [(set_attr "type" "binarycc,binarycc,binarycc")])
1855 ; Default to int16 data attr.
1856
1857 ; This pattern is required primarily for manipulating the stack pointer
1858 ; where GCC doesn't expect CC to be clobbered or for calculating
1859 ; addresses during reload.
1860 (define_insn "addqi3_noclobber"
1861   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c")
1862         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1863                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))]
1864   "valid_operands (PLUS, operands, QImode)"
1865   "@
1866    addi\\t%2,%0
1867    addi3\\t%2,%1,%0
1868    addi3\\t%2,%1,%0"
1869   [(set_attr "type" "binary,binary,binary")])
1870 ; Default to int16 data attr.
1871
1872
1873 ; This pattern is required during reload when eliminate_regs_in_insn
1874 ; effectively converts a move insn into an add insn when the src
1875 ; operand is the frame pointer plus a constant.  Without this
1876 ; pattern, gen_addqi3 can be called with a register for operand0
1877 ; that can clobber CC.
1878 ; For example, we may have (set (mem (reg ar0)) (reg 99))
1879 ; with (set (reg 99) (plus (reg ar3) (const_int 8)))
1880 ; Now since ar3, the frame pointer, is unchanging within the function,
1881 ; (plus (reg ar3) (const_int 8)) is considered a constant.
1882 ; eliminate_regs_in_insn substitutes this constant to give
1883 ; (set (mem (reg ar0)) (plus (reg ar3) (const_int 8))).
1884 ; This is an invalid C4x insn but if we don't provide a pattern
1885 ; for it, it will be considered to be a move insn for reloading.
1886 (define_insn "*addqi3_noclobber_reload"
1887   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c")
1888         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
1889                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))]
1890   "reload_in_progress"
1891   "@
1892    addi\\t%2,%0
1893    addi3\\t%2,%1,%0
1894    addi3\\t%2,%1,%0"
1895   [(set_attr "type" "binary,binary,binary")])
1896 ; Default to int16 data attr.
1897
1898
1899 (define_insn "*addqi3_carry_clobber"
1900   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
1901         (plus:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
1902                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
1903    (use (reg:CC_NOOV 21))
1904    (clobber (reg:CC_NOOV 21))]
1905   "valid_operands (PLUS, operands, QImode)"
1906   "@
1907    addc\\t%2,%0
1908    addc3\\t%2,%1,%0
1909    addc3\\t%2,%1,%0
1910    addc\\t%2,%0
1911    addc3\\t%2,%1,%0
1912    addc3\\t%2,%1,%0"
1913   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
1914 ; Default to int16 data attr.
1915
1916
1917 ;
1918 ; SUBI/SUBRI
1919 ;
1920 (define_expand "subqi3"
1921   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
1922                    (minus:QI (match_operand:QI 1 "src_operand" "")
1923                              (match_operand:QI 2 "src_operand" "")))
1924               (clobber (reg:CC_NOOV 21))])]
1925   ""
1926   "legitimize_operands (MINUS, operands, QImode);")
1927
1928 (define_insn "*subqi3_clobber"
1929   [(set (match_operand:QI 0 "reg_operand" "=d,d,d,?d,c,c,c,?c")
1930         (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>,0,rIm,rR,rS<>")
1931                   (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>,rIm,0,JR,rS<>")))
1932    (clobber (reg:CC_NOOV 21))]
1933   "valid_operands (MINUS, operands, QImode)"
1934   "@
1935    subi\\t%2,%0
1936    subri\\t%1,%0
1937    subi3\\t%2,%1,%0
1938    subi3\\t%2,%1,%0
1939    subi\\t%2,%0
1940    subri\\t%1,%0
1941    subi3\\t%2,%1,%0
1942    subi3\\t%2,%1,%0"
1943   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc,binary,binary,binary,binary")])
1944 ; Default to int16 data attr.
1945
1946 (define_split
1947   [(set (match_operand:QI 0 "std_reg_operand" "")
1948         (minus:QI (match_operand:QI 1 "src_operand" "")
1949                   (match_operand:QI 2 "src_operand" "")))
1950    (clobber (reg:CC_NOOV 21))]
1951   "reload_completed"
1952   [(set (match_dup 0)
1953         (minus:QI (match_dup 1)
1954                  (match_dup 2)))]
1955   "")
1956
1957 (define_insn "*subqi3_test"
1958   [(set (reg:CC_NOOV 21)
1959         (compare:CC_NOOV (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
1960                                    (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>"))
1961                          (const_int 0)))
1962    (clobber (match_scratch:QI 0 "=d,d,d,?d"))]
1963   "valid_operands (MINUS, operands, QImode)"
1964   "@
1965    subi\\t%2,%0
1966    subri\\t%1,%0
1967    subi3\\t%2,%1,%0
1968    subi3\\t%2,%1,%0"
1969   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
1970 ; Default to int16 data attr.
1971
1972 (define_peephole
1973   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
1974                    (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
1975                              (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>")))
1976               (clobber (reg:CC_NOOV 21))])
1977    (set (reg:CC_NOOV 21)
1978         (compare:CC_NOOV (match_dup 0) (const_int 0)))]
1979   "valid_operands (MINUS, operands, QImode)"
1980   "@
1981    subi\\t%2,%0
1982    subri\\t%1,%0
1983    subi3\\t%2,%1,%0
1984    subi3\\t%2,%1,%0"
1985   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
1986   
1987 (define_insn "*subqi3_set"
1988   [(set (reg:CC_NOOV 21)
1989         (compare:CC_NOOV (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
1990                                    (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>"))
1991                          (const_int 0)))
1992    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
1993         (minus:QI (match_dup 1)
1994                   (match_dup 2)))]
1995   "valid_operands (MINUS, operands, QImode)"
1996   "@
1997    subi\\t%2,%0
1998    subri\\t%1,%0
1999    subi3\\t%2,%1,%0
2000    subi3\\t%2,%1,%0"
2001   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
2002 ; Default to int16 data attr.
2003
2004 (define_insn "*subqi3_noclobber"
2005   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c,?c")
2006         (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
2007                   (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>")))]
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" "binary,binary,binary,binary")])
2015 ; Default to int16 data attr.
2016
2017 (define_insn "*subqi3_carry_clobber"
2018   [(set (match_operand:QI 0 "reg_operand" "=d,d,d,?d,c,c,c,?c")
2019         (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>,0,rIm,rR,rS<>")
2020                   (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>,rIm,0,JR,rS<>")))
2021    (use (reg:CC_NOOV 21))
2022    (clobber (reg:CC_NOOV 21))]
2023   "valid_operands (MINUS, operands, QImode)"
2024   "@
2025    subb\\t%2,%0
2026    subrb\\t%1,%0
2027    subb3\\t%2,%1,%0
2028    subb3\\t%2,%1,%0
2029    subb\\t%2,%0
2030    subrb\\t%1,%0
2031    subb3\\t%2,%1,%0
2032    subb3\\t%2,%1,%0"
2033   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc,binary,binary,binary,binary")])
2034 ; Default to int16 data attr.
2035
2036 (define_insn "*subqi3_carry_set"
2037   [(set (reg:CC_NOOV 21)
2038         (compare:CC_NOOV (minus:QI (match_operand:QI 1 "src_operand" "0,rIm,rR,rS<>")
2039                                    (match_operand:QI 2 "src_operand" "rIm,0,JR,rS<>"))
2040                          (const_int 0)))
2041    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2042         (minus:QI (match_dup 1)
2043                   (match_dup 2)))
2044    (use (reg:CC_NOOV 21))]
2045   "valid_operands (MINUS, operands, QImode)"
2046   "@
2047    subb\\t%2,%0
2048    subrb\\t%1,%0
2049    subb3\\t%2,%1,%0
2050    subb3\\t%2,%1,%0"
2051   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
2052 ; Default to int16 data attr.
2053
2054 ;
2055 ; MPYI
2056 ;
2057 (define_expand "mulqi3"
2058   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2059                    (mult:QI (match_operand:QI 1 "src_operand" "")
2060                             (match_operand:QI 2 "src_operand" "")))
2061               (clobber (reg:CC_NOOV 21))])]
2062   ""
2063   "if (TARGET_MPYI || (GET_CODE (operands[2]) == CONST_INT
2064        && exact_log2 (INTVAL (operands[2])) >= 0))
2065      legitimize_operands (MULT, operands, QImode);
2066    else
2067      {        
2068        if (GET_CODE (operands[2]) == CONST_INT)
2069          {
2070           /* Let GCC try to synthesise the multiplication using shifts
2071              and adds.  In most cases this will be more profitable than
2072              using the C3x MPYI.  */
2073             FAIL;
2074          }
2075        if (operands[1] == operands[2])
2076          {
2077             /* Do the squaring operation in-line.  */
2078             emit_insn (gen_sqrqi2_inline (operands[0], operands[1]));
2079             DONE;
2080          }
2081        if (TARGET_INLINE)
2082          {
2083             emit_insn (gen_mulqi3_inline (operands[0], operands[1],
2084                                           operands[2]));
2085             DONE;
2086          }
2087        c4x_emit_libcall3 (smul_optab->handlers[(int) QImode].libfunc,
2088                           MULT, QImode, operands);
2089        DONE;
2090      }
2091   ")
2092
2093 (define_insn "*mulqi3_clobber"
2094   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2095         (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2096                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2097    (clobber (reg:CC_NOOV 21))]
2098   "valid_operands (MULT, operands, QImode)"
2099   "*
2100   if (which_alternative == 0 || which_alternative == 3)
2101     {
2102       if (TARGET_C3X
2103           && GET_CODE (operands[2]) == CONST_INT
2104           && exact_log2 (INTVAL (operands[2])) >= 0)
2105         return \"ash\\t%L2,%0\";
2106       else
2107         return \"mpyi\\t%2,%0\";
2108     }
2109   else
2110       return \"mpyi3\\t%2,%1,%0\";"
2111   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2112 ; Default to int16 data attr.
2113
2114 (define_insn "*mulqi3_test"
2115   [(set (reg:CC_NOOV 21)
2116         (compare:CC_NOOV (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2117                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2118                          (const_int 0)))
2119    (clobber (match_scratch:QI 0 "=d,d,d"))]
2120   "valid_operands (MULT, operands, QImode)"
2121   "*
2122   if (which_alternative == 0)
2123     {
2124       if (TARGET_C3X 
2125           && GET_CODE (operands[2]) == CONST_INT
2126           && exact_log2 (INTVAL (operands[2])) >= 0)
2127         return \"ash\\t%L2,%0\";
2128       else
2129         return \"mpyi\\t%2,%0\";
2130     } 
2131   else
2132       return \"mpyi3\\t%2,%1,%0\";"
2133   [(set_attr "type" "binarycc,binarycc,binarycc")])
2134 ; Default to int16 data attr.
2135
2136 (define_insn "*mulqi3_set"
2137   [(set (reg:CC_NOOV 21)
2138         (compare:CC_NOOV (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2139                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2140                          (const_int 0)))
2141    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2142         (mult:QI (match_dup 1)
2143                  (match_dup 2)))]
2144   "valid_operands (MULT, operands, QImode)"
2145   "*
2146   if (which_alternative == 0)
2147     {
2148       if (TARGET_C3X 
2149           && GET_CODE (operands[2]) == CONST_INT
2150           && exact_log2 (INTVAL (operands[2])) >= 0)
2151         return \"ash\\t%L2,%0\";
2152       else
2153         return \"mpyi\\t%2,%0\";
2154     }
2155     else
2156         return \"mpyi3\\t%2,%1,%0\";"
2157   [(set_attr "type" "binarycc,binarycc,binarycc")])
2158 ; Default to int16 data attr.
2159
2160 ; The C3x multiply instruction assumes 24-bit signed integer operands
2161 ; and the 48-bit result is truncated to 32-bits.
2162 (define_insn "*mulqi3_24_clobber"
2163   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2164         (mult:QI
2165          (sign_extend:QI
2166           (and:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2167                   (const_int 16777215)))
2168          (sign_extend:QI
2169           (and:QI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")
2170                   (const_int 16777215)))))
2171    (clobber (reg:CC_NOOV 21))]
2172   "TARGET_C3X && valid_operands (MULT, operands, QImode)"
2173   "@
2174    mpyi\\t%2,%0
2175    mpyi3\\t%2,%1,%0
2176    mpyi3\\t%2,%1,%0
2177    mpyi\\t%2,%0
2178    mpyi3\\t%2,%1,%0
2179    mpyi3\\t%2,%1,%0"
2180   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2181 ; Default to int16 data attr.
2182
2183
2184 ; Fast square function for C3x where TARGET_MPYI not asserted
2185 (define_expand "sqrqi2_inline"
2186   [(set (match_dup 7) (match_operand:QI 1 "src_operand" ""))
2187    (parallel [(set (match_dup 3)
2188                    (lshiftrt:QI (match_dup 7) (const_int 16)))
2189               (clobber (reg:CC 21))])
2190    (parallel [(set (match_dup 2)
2191                    (and:QI (match_dup 7) (const_int 65535)))
2192               (clobber (reg:CC 21))])
2193    (parallel [(set (match_dup 4)
2194                    (mult:QI (sign_extend:QI (and:QI (match_dup 2) 
2195                                                     (const_int 16777215)))
2196                             (sign_extend:QI (and:QI (match_dup 2) 
2197                                                     (const_int 16777215)))))
2198               (clobber (reg:CC_NOOV 21))])
2199    (parallel [(set (match_dup 5)
2200                    (mult:QI (sign_extend:QI (and:QI (match_dup 2) 
2201                                                     (const_int 16777215)))
2202                             (sign_extend:QI (and:QI (match_dup 3) 
2203                                                     (const_int 16777215)))))
2204               (clobber (reg:CC_NOOV 21))])
2205    (parallel [(set (match_dup 6)
2206                    (ashift:QI (match_dup 5) (const_int 17)))
2207               (clobber (reg:CC 21))])
2208    (parallel [(set (match_operand:QI 0 "reg_operand" "")
2209                    (plus:QI (match_dup 4) (match_dup 6)))
2210               (clobber (reg:CC_NOOV 21))])]
2211   ""
2212   "
2213   operands[2] = gen_reg_rtx (QImode); /* a = val & 0xffff */
2214   operands[3] = gen_reg_rtx (QImode); /* b = val >> 16 */
2215   operands[4] = gen_reg_rtx (QImode); /* a * a */
2216   operands[5] = gen_reg_rtx (QImode); /* a * b */
2217   operands[6] = gen_reg_rtx (QImode); /* (a * b) << 17 */
2218   operands[7] = gen_reg_rtx (QImode); /* val */
2219   ")
2220
2221 ; Inlined integer multiply for C3x
2222 (define_expand "mulqi3_inline"
2223   [(set (match_dup 12) (const_int -16))
2224    (set (match_dup 13) (match_operand:QI 1 "src_operand" ""))
2225    (set (match_dup 14) (match_operand:QI 2 "src_operand" ""))
2226    (parallel [(set (match_dup 4)
2227                    (lshiftrt:QI (match_dup 13) (neg:QI (match_dup 12))))
2228               (clobber (reg:CC 21))])
2229    (parallel [(set (match_dup 6)
2230                    (lshiftrt:QI (match_dup 14) (neg:QI (match_dup 12))))
2231               (clobber (reg:CC 21))])
2232    (parallel [(set (match_dup 3)
2233                    (and:QI (match_dup 13)
2234                            (const_int 65535)))
2235               (clobber (reg:CC 21))])
2236    (parallel [(set (match_dup 5)
2237                    (and:QI (match_dup 14) 
2238                            (const_int 65535)))
2239               (clobber (reg:CC 21))])
2240    (parallel [(set (match_dup 7)
2241                    (mult:QI (sign_extend:QI (and:QI (match_dup 4) 
2242                                                     (const_int 16777215)))
2243                             (sign_extend:QI (and:QI (match_dup 5) 
2244                                                     (const_int 16777215)))))
2245               (clobber (reg:CC_NOOV 21))])
2246    (parallel [(set (match_dup 8)
2247                    (mult:QI (sign_extend:QI (and:QI (match_dup 3) 
2248                                                     (const_int 16777215)))
2249                             (sign_extend:QI (and:QI (match_dup 5) 
2250                                                     (const_int 16777215)))))
2251               (clobber (reg:CC_NOOV 21))])
2252    (parallel [(set (match_dup 9)
2253                    (mult:QI (sign_extend:QI (and:QI (match_dup 3) 
2254                                                     (const_int 16777215)))
2255                             (sign_extend:QI (and:QI (match_dup 6) 
2256                                                     (const_int 16777215)))))
2257               (clobber (reg:CC_NOOV 21))])
2258    (parallel [(set (match_dup 10)
2259                    (plus:QI (match_dup 7) (match_dup 9)))
2260               (clobber (reg:CC_NOOV 21))])
2261    (parallel [(set (match_dup 11)
2262                    (ashift:QI (match_dup 10) (const_int 16)))
2263               (clobber (reg:CC 21))])
2264    (parallel [(set (match_operand:QI 0 "reg_operand" "")
2265                    (plus:QI (match_dup 8) (match_dup 11)))
2266               (clobber (reg:CC_NOOV 21))])]
2267   "TARGET_C3X"
2268   "
2269   operands[3] = gen_reg_rtx (QImode); /* a = arg1 & 0xffff */
2270   operands[4] = gen_reg_rtx (QImode); /* b = arg1 >> 16 */
2271   operands[5] = gen_reg_rtx (QImode); /* a = arg2 & 0xffff */
2272   operands[6] = gen_reg_rtx (QImode); /* b = arg2 >> 16 */
2273   operands[7] = gen_reg_rtx (QImode); /* b * c */
2274   operands[8] = gen_reg_rtx (QImode); /* a * c */
2275   operands[9] = gen_reg_rtx (QImode); /* a * d */
2276   operands[10] = gen_reg_rtx (QImode); /* b * c + a * d */
2277   operands[11] = gen_reg_rtx (QImode); /* (b *c + a * d) << 16 */
2278   operands[12] = gen_reg_rtx (QImode); /* -16 */
2279   operands[13] = gen_reg_rtx (QImode); /* arg1 */
2280   operands[14] = gen_reg_rtx (QImode); /* arg2 */
2281   ")
2282
2283 ;
2284 ; MPYSHI (C4x only)
2285 ;
2286 (define_expand "smulqi3_highpart"
2287   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2288                    (truncate:QI
2289                     (lshiftrt:HI
2290                      (mult:HI
2291                       (sign_extend:HI (match_operand:QI 1 "src_operand" ""))
2292                       (sign_extend:HI (match_operand:QI 2 "src_operand" "")))
2293                  (const_int 32))))
2294               (clobber (reg:CC_NOOV 21))])]
2295  ""
2296  "legitimize_operands (MULT, operands, QImode);
2297   if (TARGET_C3X)
2298     {
2299        c4x_emit_libcall_mulhi (smulhi3_libfunc, SIGN_EXTEND, QImode, operands);
2300        DONE;
2301     }
2302  ")
2303
2304 (define_insn "*smulqi3_highpart_clobber"
2305   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2306         (truncate:QI 
2307          (lshiftrt:HI
2308           (mult:HI
2309            (sign_extend:HI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>"))
2310            (sign_extend:HI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2311       (const_int 32))))
2312    (clobber (reg:CC_NOOV 21))]
2313   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2314   "@
2315    mpyshi\\t%2,%0
2316    mpyshi3\\t%2,%1,%0
2317    mpyshi3\\t%2,%1,%0
2318    mpyshi\\t%2,%0
2319    mpyshi3\\t%2,%1,%0
2320    mpyshi3\\t%2,%1,%0"
2321   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2322    (set_attr "data" "int16,int16,int16,int16,int16,int16")])
2323
2324 (define_insn "*smulqi3_highpart_noclobber"
2325   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2326         (truncate:QI 
2327          (lshiftrt:HI
2328           (mult:HI
2329            (sign_extend:HI (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2330            (sign_extend:HI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))
2331       (const_int 32))))]
2332   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2333   "@
2334    mpyshi\\t%2,%0
2335    mpyshi3\\t%2,%1,%0
2336    mpyshi3\\t%2,%1,%0"
2337   [(set_attr "type" "binary,binary,binary")
2338    (set_attr "data" "int16,int16,int16")])
2339
2340 ;
2341 ; MPYUHI (C4x only)
2342 ;
2343 (define_expand "umulqi3_highpart"
2344   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2345                (truncate:QI
2346                 (lshiftrt:HI
2347                  (mult:HI
2348                   (zero_extend:HI (match_operand:QI 1 "src_operand" ""))
2349                   (zero_extend:HI (match_operand:QI 2 "lsrc_operand" "")))
2350                  (const_int 32))))
2351               (clobber (reg:CC_NOOV 21))])]
2352  ""
2353  "legitimize_operands (MULT, operands, QImode);
2354   if (TARGET_C3X) 
2355     {
2356       c4x_emit_libcall_mulhi (umulhi3_libfunc, ZERO_EXTEND, QImode, operands);
2357       DONE;
2358     }
2359  ")
2360
2361 (define_insn "*umulqi3_highpart_clobber"
2362   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2363         (truncate:QI
2364          (lshiftrt:HI
2365           (mult:HI 
2366            (zero_extend:HI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>"))
2367            (zero_extend:HI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2368           (const_int 32))))
2369    (clobber (reg:CC_NOOV 21))]
2370   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2371   "@
2372    mpyuhi\\t%2,%0
2373    mpyuhi3\\t%2,%1,%0
2374    mpyuhi3\\t%2,%1,%0
2375    mpyuhi\\t%2,%0
2376    mpyuhi3\\t%2,%1,%0
2377    mpyuhi3\\t%2,%1,%0"
2378   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2379    (set_attr "data" "uint16,uint16,uint16,uint16,uint16,uint16")])
2380
2381 (define_insn "*umulqi3_highpart_noclobber"
2382   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2383         (truncate:QI
2384          (lshiftrt:HI
2385           (mult:HI 
2386            (zero_extend:HI (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2387            (zero_extend:HI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))
2388           (const_int 32))))]
2389   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2390   "@
2391    mpyuhi\\t%2,%0
2392    mpyuhi3\\t%2,%1,%0
2393    mpyuhi3\\t%2,%1,%0"
2394   [(set_attr "type" "binary,binary,binary")
2395    (set_attr "data" "uint16,uint16,uint16")])
2396
2397 ;
2398 ; AND
2399 ;
2400 (define_expand "andqi3"
2401   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2402                    (and:QI (match_operand:QI 1 "src_operand" "")
2403                            (match_operand:QI 2 "tsrc_operand" "")))
2404               (clobber (reg:CC 21))])]
2405  ""
2406  "legitimize_operands (AND, operands, QImode);")
2407
2408
2409 (define_insn "*andqi3_255_clobber"
2410   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2411         (and:QI (match_operand:QI 1 "src_operand" "mr,mr")
2412                 (const_int 255)))
2413    (clobber (reg:CC 21))]
2414  "! TARGET_C3X"
2415  "lbu0\\t%1,%0"
2416   [(set_attr "type" "unarycc,unary")])
2417
2418 (define_insn "*andqi3_255_noclobber"
2419   [(set (match_operand:QI 0 "reg_operand" "=c")
2420         (and:QI (match_operand:QI 1 "src_operand" "mr")
2421                 (const_int 255)))]
2422  "! TARGET_C3X"
2423  "lbu0\\t%1,%0"
2424   [(set_attr "type" "unary")])
2425
2426
2427 (define_insn "*andqi3_65535_clobber"
2428   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2429         (and:QI (match_operand:QI 1 "src_operand" "mr,mr")
2430                 (const_int 65535)))
2431    (clobber (reg:CC 21))]
2432  "! TARGET_C3X"
2433  "lhu0\\t%1,%0"
2434   [(set_attr "type" "unarycc,unary")])
2435
2436 (define_insn "*andqi3_65535_noclobber"
2437   [(set (match_operand:QI 0 "reg_operand" "=c")
2438         (and:QI (match_operand:QI 1 "src_operand" "mr")
2439                 (const_int 65535)))]
2440  "! TARGET_C3X"
2441  "lhu0\\t%1,%0"
2442   [(set_attr "type" "unary")])
2443
2444 (define_insn "*andqi3_clobber"
2445   [(set (match_operand:QI 0 "reg_operand" "=d,d,d,?d,c,c,c,?c")
2446         (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>,0,0,rR,rS<>")
2447                 (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>,N,rLm,JR,rS<>")))
2448    (clobber (reg:CC 21))]
2449   "valid_operands (AND, operands, QImode)"
2450   "@
2451    andn\\t%N2,%0
2452    and\\t%2,%0
2453    and3\\t%2,%1,%0
2454    and3\\t%2,%1,%0
2455    andn\\t%N2,%0
2456    and\\t%2,%0
2457    and3\\t%2,%1,%0
2458    and3\\t%2,%1,%0"
2459   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc,binary,binary,binary,binary")
2460    (set_attr "data" "not_uint16,uint16,int16,uint16,not_uint16,uint16,int16,uint16")])
2461
2462 (define_insn "*andqi3_noclobber"
2463   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c,?c")
2464         (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2465                 (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>")))]
2466   "valid_operands (AND, operands, QImode)"
2467   "@
2468    andn\\t%N2,%0
2469    and\\t%2,%0
2470    and3\\t%2,%1,%0
2471    and3\\t%2,%1,%0"
2472   [(set_attr "type" "binary,binary,binary,binary")
2473    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2474
2475 (define_split
2476   [(set (match_operand:QI 0 "std_reg_operand" "")
2477         (and:QI (match_operand:QI 1 "src_operand" "")
2478                 (match_operand:QI 2 "tsrc_operand" "")))
2479    (clobber (reg:CC 21))]
2480   "reload_completed"
2481   [(set (match_dup 0)
2482         (and:QI (match_dup 1)
2483                 (match_dup 2)))]
2484   "")
2485
2486 (define_insn "*andqi3_test"
2487   [(set (reg:CC 21)
2488         (compare:CC (and:QI (match_operand:QI 1 "src_operand" "%0,r,rR,rS<>")
2489                             (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>"))
2490                     (const_int 0)))
2491    (clobber (match_scratch:QI 0 "=d,X,X,?X"))]
2492   "valid_operands (AND, operands, QImode)"
2493   "@
2494    andn\\t%N2,%0
2495    tstb\\t%2,%1
2496    tstb3\\t%2,%1
2497    tstb3\\t%2,%1"
2498   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2499    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2500
2501 (define_peephole
2502   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2503                    (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2504                            (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>")))
2505               (clobber (reg:CC 21))])
2506    (set (reg:CC 21)
2507         (compare:CC (match_dup 0) (const_int 0)))]
2508   "valid_operands (AND, operands, QImode)"
2509   "@
2510    andn\\t%N2,%0
2511    and\\t%2,%0
2512    and3\\t%2,%1,%0
2513    and3\\t%2,%1,%0"
2514   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2515    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2516   
2517 (define_insn "*andqi3_set"
2518   [(set (reg:CC 21)
2519         (compare:CC (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2520                             (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>"))
2521                     (const_int 0)))
2522    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2523         (and:QI (match_dup 1)
2524                 (match_dup 2)))]
2525   "valid_operands (AND, operands, QImode)"
2526   "@
2527    andn\\t%N2,%0
2528    and\\t%2,%0
2529    and3\\t%2,%1,%0
2530    and3\\t%2,%1,%0"
2531   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2532    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2533
2534 ;
2535 ; ANDN
2536 ;
2537 ; NB, this insn doesn't have commutative operands, but valid_operands
2538 ; assumes that the code AND does.  We might have to kludge this if
2539 ; we make valid_operands stricter.
2540 (define_insn "*andnqi3_clobber"
2541   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2542         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>"))
2543                 (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")))
2544    (clobber (reg:CC 21))]
2545   "valid_operands (AND, operands, QImode)"
2546   "@
2547    andn\\t%2,%0
2548    andn3\\t%2,%1,%0
2549    andn3\\t%2,%1,%0
2550    andn\\t%2,%0
2551    andn3\\t%2,%1,%0
2552    andn3\\t%2,%1,%0"
2553   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2554    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2555
2556 (define_insn "*andnqi3_noclobber"
2557   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2558         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2559                 (match_operand:QI 1 "src_operand" "0,rR,rS<>")))]
2560   "valid_operands (AND, operands, QImode)"
2561   "@
2562    andn\\t%2,%0
2563    andn3\\t%2,%1,%0
2564    andn3\\t%2,%1,%0"
2565   [(set_attr "type" "binary,binary,binary")
2566    (set_attr "data" "uint16,int16,uint16")])
2567
2568 (define_split
2569   [(set (match_operand:QI 0 "std_reg_operand" "")
2570         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" ""))
2571                 (match_operand:QI 1 "src_operand" "")))
2572    (clobber (reg:CC 21))]
2573   "reload_completed"
2574   [(set (match_dup 0)
2575         (and:QI (not:QI (match_dup 2))
2576                 (match_dup 1)))]
2577   "")
2578
2579 (define_insn "*andnqi3_test"
2580   [(set (reg:CC 21)
2581         (compare:CC (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2582                             (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2583                     (const_int 0)))
2584    (clobber (match_scratch:QI 0 "=d,d,d"))]
2585   "valid_operands (AND, operands, QImode)"
2586   "@
2587    andn\\t%2,%0
2588    andn3\\t%2,%1,%0
2589    andn3\\t%2,%1,%0"
2590   [(set_attr "type" "binarycc,binarycc,binarycc")
2591    (set_attr "data" "uint16,int16,uint16")])
2592
2593 (define_insn "*andnqi3_set"
2594   [(set (reg:CC 21)
2595         (compare:CC (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2596                             (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2597                     (const_int 0)))
2598    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2599         (and:QI (not:QI (match_dup 2))
2600                 (match_dup 1)))]
2601   "valid_operands (AND, operands, QImode)"
2602   "@
2603    andn\\t%2,%0
2604    andn3\\t%2,%1,%0
2605    andn3\\t%2,%1,%0"
2606   [(set_attr "type" "binarycc,binarycc,binarycc")
2607    (set_attr "data" "uint16,int16,uint16")])
2608
2609 ;
2610 ; OR
2611 ;
2612 (define_expand "iorqi3"
2613   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2614                    (ior:QI (match_operand:QI 1 "src_operand" "")
2615                            (match_operand:QI 2 "lsrc_operand" "")))
2616               (clobber (reg:CC 21))])]
2617  ""
2618  "legitimize_operands (IOR, operands, QImode);")
2619
2620 (define_insn "*iorqi3_clobber"
2621   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2622         (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2623                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2624    (clobber (reg:CC 21))]
2625   "valid_operands (IOR, operands, QImode)"
2626   "@
2627    or\\t%2,%0
2628    or3\\t%2,%1,%0
2629    or3\\t%2,%1,%0
2630    or\\t%2,%0
2631    or3\\t%2,%1,%0
2632    or3\\t%2,%1,%0"
2633   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2634    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2635
2636 (define_split
2637   [(set (match_operand:QI 0 "std_reg_operand" "")
2638         (ior:QI (match_operand:QI 1 "src_operand" "")
2639                 (match_operand:QI 2 "lsrc_operand" "")))
2640    (clobber (reg:CC 21))]
2641   "reload_completed"
2642   [(set (match_dup 0)
2643         (ior:QI (match_dup 1)
2644                 (match_dup 2)))]
2645   "")
2646
2647 (define_insn "*iorqi3_test"
2648   [(set (reg:CC 21)
2649         (compare:CC (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2650                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2651                     (const_int 0)))
2652    (clobber (match_scratch:QI 0 "=d,d,d"))]
2653   "valid_operands (IOR, operands, QImode)"
2654   "@
2655    or\\t%2,%0
2656    or3\\t%2,%1,%0
2657    or3\\t%2,%1,%0"
2658   [(set_attr "type" "binarycc,binarycc,binarycc")
2659    (set_attr "data" "uint16,int16,uint16")])
2660
2661 (define_peephole
2662   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2663                    (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2664                            (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))
2665               (clobber (reg:CC 21))])
2666    (set (reg:CC 21)
2667         (compare:CC (match_dup 0) (const_int 0)))]
2668   "valid_operands (IOR, operands, QImode)"
2669   "@
2670    or\\t%2,%0
2671    or3\\t%2,%1,%0
2672    or3\\t%2,%1,%0"
2673   [(set_attr "type" "binarycc,binarycc,binarycc")
2674    (set_attr "data" "uint16,int16,uint16")])
2675   
2676 (define_insn "*iorqi3_set"
2677   [(set (reg:CC 21)
2678         (compare:CC (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2679                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2680                     (const_int 0)))
2681    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2682         (ior:QI (match_dup 1)
2683                 (match_dup 2)))]
2684   "valid_operands (IOR, operands, QImode)"
2685   "@
2686    or\\t%2,%0
2687    or3\\t%2,%1,%0
2688    or3\\t%2,%1,%0"
2689   [(set_attr "type" "binarycc,binarycc,binarycc")
2690    (set_attr "data" "uint16,int16,uint16")])
2691
2692 ; This pattern is used for loading symbol references in several parts. 
2693 (define_insn "iorqi3_noclobber"
2694   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c")
2695         (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2696                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))]
2697   "valid_operands (IOR, operands, QImode)"
2698   "@
2699    or\\t%2,%0
2700    or3\\t%2,%1,%0
2701    or3\\t%2,%1,%0"
2702   [(set_attr "type" "binary,binary,binary")
2703    (set_attr "data" "uint16,int16,uint16")])
2704
2705 ;
2706 ; XOR
2707 ;
2708 (define_expand "xorqi3"
2709   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2710                    (xor:QI (match_operand:QI 1 "src_operand" "")
2711                            (match_operand:QI 2 "lsrc_operand" "")))
2712               (clobber (reg:CC 21))])]
2713  ""
2714  "legitimize_operands (XOR, operands, QImode);")
2715
2716 (define_insn "*xorqi3_clobber"
2717   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2718         (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2719                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2720    (clobber (reg:CC 21))]
2721   "valid_operands (XOR, operands, QImode)"
2722   "@
2723    xor\\t%2,%0
2724    xor3\\t%2,%1,%0
2725    xor3\\t%2,%1,%0
2726    xor\\t%2,%0
2727    xor3\\t%2,%1,%0
2728    xor3\\t%2,%1,%0"
2729   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2730    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2731
2732 (define_insn "*xorqi3_noclobber"
2733   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2734         (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2735                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))]
2736   "valid_operands (XOR, operands, QImode)"
2737   "@
2738    xor\\t%2,%0
2739    xor3\\t%2,%1,%0
2740    xor3\\t%2,%1,%0"
2741   [(set_attr "type" "binary,binary,binary")
2742    (set_attr "data" "uint16,int16,uint16")])
2743
2744 (define_split
2745   [(set (match_operand:QI 0 "std_reg_operand" "")
2746         (xor:QI (match_operand:QI 1 "src_operand" "")
2747                 (match_operand:QI 2 "lsrc_operand" "")))
2748    (clobber (reg:CC 21))]
2749   "reload_completed"
2750   [(set (match_dup 0)
2751         (xor:QI (match_dup 1)
2752                 (match_dup 2)))]
2753   "")
2754
2755 (define_insn "*xorqi3_test"
2756   [(set (reg:CC 21)
2757         (compare:CC (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2758                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2759                     (const_int 0)))
2760    (clobber (match_scratch:QI 0 "=d,d,d"))]
2761   "valid_operands (XOR, operands, QImode)"
2762   "@
2763    xor\\t%2,%0
2764    xor3\\t%2,%1,%0
2765    xor3\\t%2,%1,%0"
2766   [(set_attr "type" "binarycc,binarycc,binarycc")
2767    (set_attr "data" "uint16,int16,uint16")])
2768
2769 (define_insn "*xorqi3_set"
2770   [(set (reg:CC 21)
2771         (compare:CC (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2772                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2773                     (const_int 0)))
2774    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2775         (xor:QI (match_dup 1)
2776                 (match_dup 2)))]
2777   "valid_operands (XOR, operands, QImode)"
2778   "@
2779    xor\\t%2,%0
2780    xor3\\t%2,%1,%0
2781    xor3\\t%2,%1,%0"
2782   [(set_attr "type" "binarycc,binarycc,binarycc")
2783    (set_attr "data" "uint16,int16,uint16")])
2784
2785 ;
2786 ; LSH/ASH (left)
2787 ;
2788 ; The C3x and C4x have two shift instructions ASH and LSH
2789 ; If the shift count is positive, a left shift is performed
2790 ; otherwise a right shift is performed.  The number of bits
2791 ; shifted is determined by the seven LSBs of the shift count.
2792 ; If the absolute value of the count is 32 or greater, the result
2793 ; using the LSH instruction is zero; with the ASH insn the result
2794 ; is zero or negative 1.   Note that the ISO C standard allows 
2795 ; the result to be machine dependent whenever the shift count
2796 ; exceeds the size of the object.
2797 (define_expand "ashlqi3"
2798   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2799                    (ashift:QI (match_operand:QI 1 "src_operand" "")
2800                               (match_operand:QI 2 "src_operand" "")))
2801               (clobber (reg:CC 21))])]
2802  ""
2803  "legitimize_operands (ASHIFT, operands, QImode);")
2804
2805 (define_insn "*ashlqi3_clobber"
2806   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2807         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2808                    (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2809    (clobber (reg:CC 21))]
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    ash\\t%2,%0
2816    ash3\\t%2,%1,%0
2817    ash3\\t%2,%1,%0"
2818   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2819 ; Default to int16 data attr.
2820
2821 (define_insn "*ashlqi3_set"
2822   [(set (reg:CC 21)
2823         (compare:CC
2824           (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2825                      (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2826           (const_int 0)))
2827    (set (match_operand:QI 0 "reg_operand" "=d,d,d")
2828         (ashift:QI (match_dup 1)
2829                    (match_dup 2)))]
2830   "valid_operands (ASHIFT, operands, QImode)"
2831   "@
2832    ash\\t%2,%0
2833    ash3\\t%2,%1,%0
2834    ash3\\t%2,%1,%0"
2835   [(set_attr "type" "binarycc,binarycc,binarycc")])
2836 ; Default to int16 data attr.
2837
2838 (define_insn "ashlqi3_noclobber"
2839   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2840         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2841                    (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))]
2842   "valid_operands (ASHIFT, operands, QImode)"
2843   "@
2844    ash\\t%2,%0
2845    ash3\\t%2,%1,%0
2846    ash3\\t%2,%1,%0"
2847   [(set_attr "type" "binary,binary,binary")])
2848 ; Default to int16 data attr.
2849
2850 (define_split
2851   [(set (match_operand:QI 0 "std_reg_operand" "")
2852         (ashift:QI (match_operand:QI 1 "src_operand" "")
2853                    (match_operand:QI 2 "src_operand" "")))
2854    (clobber (reg:CC 21))]
2855   "reload_completed"
2856   [(set (match_dup 0)
2857         (ashift:QI (match_dup 1)
2858                    (match_dup 2)))]
2859   "")
2860
2861 ; This is only used by lshrhi3_reg where we need a LSH insn that will
2862 ; shift both ways.
2863 (define_insn "*lshlqi3_clobber"
2864   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2865         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2866                    (unspec:QI [(match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")] 3)))
2867    (clobber (reg:CC 21))]
2868   "valid_operands (ASHIFT, operands, QImode)"
2869   "@
2870    lsh\\t%2,%0
2871    lsh3\\t%2,%1,%0
2872    lsh3\\t%2,%1,%0
2873    lsh\\t%2,%0
2874    lsh3\\t%2,%1,%0
2875    lsh3\\t%2,%1,%0"
2876   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2877 ; Default to int16 data attr.
2878
2879 ;
2880 ; LSH (right)
2881 ;
2882 ; Logical right shift on the C[34]x works by negating the shift count,
2883 ; then emitting a right shift with the shift count negated.  This means
2884 ; that all actual shift counts in the RTL will be positive.
2885 ;
2886 (define_expand "lshrqi3"
2887   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2888                    (lshiftrt:QI (match_operand:QI 1 "src_operand" "")
2889                                 (match_operand:QI 2 "src_operand" "")))
2890               (clobber (reg:CC 21))])]
2891   ""
2892   "legitimize_operands (LSHIFTRT, operands, QImode);")
2893
2894
2895 (define_insn "*lshrqi3_24_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 24)))
2899    (clobber (reg:CC 21))]
2900   "! TARGET_C3X"
2901   "lbu3\\t%1,%0"
2902   [(set_attr "type" "unarycc")])
2903
2904
2905 (define_insn "*ashrqi3_24_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 24)))
2909    (clobber (reg:CC 21))]
2910   "! TARGET_C3X"
2911   "lb3\\t%1,%0"
2912   [(set_attr "type" "unarycc")])
2913
2914
2915 (define_insn "lshrqi3_16_clobber"
2916   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2917         (lshiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2918                      (const_int 16)))
2919    (clobber (reg:CC 21))]
2920   "! TARGET_C3X"
2921   "lhu1\\t%1,%0"
2922   [(set_attr "type" "unarycc")])
2923
2924
2925 (define_insn "*ashrqi3_16_clobber"
2926   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2927         (ashiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2928                      (const_int 16)))
2929    (clobber (reg:CC 21))]
2930   "! TARGET_C3X"
2931   "lh1\\t%1,%0"
2932   [(set_attr "type" "unarycc")])
2933
2934
2935 ; When the shift count is greater than the size of the word
2936 ; the result can be implementation specific
2937 (define_insn "*lshrqi3_const_clobber"
2938   [(set (match_operand:QI 0 "reg_operand" "=d,c,?d,?c")
2939         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,0,r,r")
2940                      (match_operand:QI 2 "const_int_operand" "n,n,J,J")))
2941    (clobber (reg:CC 21))]
2942   "valid_operands (LSHIFTRT, operands, QImode)"
2943   "@
2944    lsh\\t%n2,%0
2945    lsh\\t%n2,%0
2946    lsh3\\t%n2,%1,%0
2947    lsh3\\t%n2,%1,%0"
2948   [(set_attr "type" "binarycc,binary,binarycc,binary")])
2949
2950 (define_insn "*lshrqi3_const_noclobber"
2951   [(set (match_operand:QI 0 "std_reg_operand" "=c,?c")
2952         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
2953                      (match_operand:QI 2 "const_int_operand" "n,J")))]
2954   "valid_operands (LSHIFTRT, operands, QImode)"
2955   "@
2956    lsh\\t%n2,%0
2957    lsh3\\t%n2,%1,%0"
2958   [(set_attr "type" "binary,binary")])
2959
2960 ; When the shift count is greater than the size of the word
2961 ; the result can be implementation specific
2962 (define_insn "*lshrqi3_const_set"
2963   [(set (reg:CC 21)
2964         (compare:CC
2965           (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
2966                        (match_operand:QI 2 "const_int_operand" "n,J"))
2967           (const_int 0)))
2968    (set (match_operand:QI 0 "reg_operand" "=?d,d")
2969         (lshiftrt:QI (match_dup 1)
2970                      (match_dup 2)))]
2971   "valid_operands (LSHIFTRT, operands, QImode)"
2972   "@
2973    lsh\\t%n2,%0
2974    lsh3\\t%n2,%1,%0"
2975   [(set_attr "type" "binarycc,binarycc")])
2976
2977 (define_insn "*lshrqi3_nonconst_clobber"
2978   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2979         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2980                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>,rm,R,rS<>"))))
2981    (clobber (reg:CC 21))]
2982   "valid_operands (LSHIFTRT, operands, QImode)"
2983   "@
2984    lsh\\t%2,%0
2985    lsh3\\t%2,%1,%0
2986    lsh3\\t%2,%1,%0
2987    lsh\\t%2,%0
2988    lsh3\\t%2,%1,%0
2989    lsh3\\t%2,%1,%0"
2990   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2991 ; Default to int16 data attr.
2992
2993 (define_insn "*lshrqi3_nonconst_noclobber"
2994   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2995         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2996                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>"))))]
2997   "valid_operands (LSHIFTRT, operands, QImode)"
2998   "@
2999    lsh\\t%2,%0
3000    lsh3\\t%2,%1,%0
3001    lsh3\\t%2,%1,%0"
3002   [(set_attr "type" "binary,binary,binary")])
3003 ; Default to int16 data attr.
3004
3005 ;
3006 ; ASH (right)
3007 ;
3008 ; Arithmetic right shift on the C[34]x works by negating the shift count,
3009 ; then emitting a right shift with the shift count negated.  This means
3010 ; that all actual shift counts in the RTL will be positive.
3011
3012 (define_expand "ashrqi3"
3013   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3014                    (ashiftrt:QI (match_operand:QI 1 "src_operand" "")
3015                                 (match_operand:QI 2 "src_operand" "")))
3016               (clobber (reg:CC 21))])]
3017   ""
3018   "legitimize_operands (ASHIFTRT, operands, QImode);")
3019
3020 ; When the shift count is greater than the size of the word
3021 ; the result can be implementation specific
3022 (define_insn "*ashrqi3_const_clobber"
3023   [(set (match_operand:QI 0 "reg_operand" "=d,c,?d,?c")
3024         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,0,r,r")
3025                      (match_operand:QI 2 "const_int_operand" "n,n,J,J")))
3026    (clobber (reg:CC 21))]
3027   "valid_operands (ASHIFTRT, operands, QImode)"
3028   "@
3029    ash\\t%n2,%0
3030    ash\\t%n2,%0
3031    ash3\\t%n2,%1,%0
3032    ash3\\t%n2,%1,%0"
3033   [(set_attr "type" "binarycc,binary,binarycc,binary")])
3034
3035 (define_insn "*ashrqi3_const_noclobber"
3036   [(set (match_operand:QI 0 "std_reg_operand" "=c,?c")
3037         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
3038                      (match_operand:QI 2 "const_int_operand" "n,J")))]
3039   "valid_operands (ASHIFTRT, operands, QImode)"
3040   "@
3041    ash\\t%n2,%0
3042    ash3\\t%n2,%1,%0"
3043   [(set_attr "type" "binarycc,binarycc")])
3044
3045 ; When the shift count is greater than the size of the word
3046 ; the result can be implementation specific
3047 (define_insn "*ashrqi3_const_set"
3048   [(set (reg:CC 21)
3049         (compare:CC
3050           (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
3051                        (match_operand:QI 2 "const_int_operand" "n,J"))
3052           (const_int 0)))
3053    (set (match_operand:QI 0 "reg_operand" "=?d,d")
3054         (ashiftrt:QI (match_dup 1)
3055                      (match_dup 2)))]
3056   "valid_operands (ASHIFTRT, operands, QImode)"
3057   "@
3058    ash\\t%n2,%0
3059    ash3\\t%n2,%1,%0"
3060   [(set_attr "type" "binarycc,binarycc")])
3061
3062 (define_insn "*ashrqi3_nonconst_clobber"
3063   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
3064         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
3065                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>,rm,R,rS<>"))))
3066    (clobber (reg:CC 21))]
3067   "valid_operands (ASHIFTRT, operands, QImode)"
3068   "@
3069    ash\\t%2,%0
3070    ash3\\t%2,%1,%0
3071    ash3\\t%2,%1,%0
3072    ash\\t%2,%0
3073    ash3\\t%2,%1,%0
3074    ash3\\t%2,%1,%0"
3075   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
3076 ; Default to int16 data attr.
3077
3078 (define_insn "*ashrqi3_nonconst_noclobber"
3079   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
3080         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
3081                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>"))))]
3082   "valid_operands (ASHIFTRT, operands, QImode)"
3083   "@
3084    ash\\t%2,%0
3085    ash3\\t%2,%1,%0
3086    ash3\\t%2,%1,%0"
3087   [(set_attr "type" "binary,binary,binary")])
3088 ; Default to int16 data attr.
3089
3090 ;
3091 ; CMPI
3092 ;
3093 ; Unfortunately the C40 doesn't allow cmpi3 7, *ar0++ so the next best
3094 ; thing would be to get the small constant loaded into a register (say r0)
3095 ; so that it could be hoisted out of the loop so that we only
3096 ; would need to do cmpi3 *ar0++, r0.  Now the loop optimisation pass
3097 ; comes before the flow pass (which finds autoincrements) so we're stuck.
3098 ; Ideally, GCC requires another loop optimisation pass (preferably after
3099 ; reload) so that it can hoist invariants out of loops.
3100 ; The current solution modifies legitimize_operands () so that small
3101 ; constants are forced into a pseudo register.
3102
3103 (define_expand "cmpqi"
3104   [(set (reg:CC 21)
3105         (compare:CC (match_operand:QI 0 "src_operand" "")
3106                     (match_operand:QI 1 "src_operand" "")))]
3107   ""
3108   "legitimize_operands (COMPARE, operands, QImode);
3109    c4x_compare_op0 = operands[0];
3110    c4x_compare_op1 = operands[1];
3111    DONE;")
3112
3113 (define_insn "*cmpqi_test"
3114   [(set (reg:CC 21)
3115         (compare:CC (match_operand:QI 0 "src_operand" "r,rR,rS<>")
3116                     (match_operand:QI 1 "src_operand" "rIm,JR,rS<>")))]
3117   "valid_operands (COMPARE, operands, QImode)"
3118   "@
3119    cmpi\\t%1,%0
3120    cmpi3\\t%1,%0
3121    cmpi3\\t%1,%0"
3122   [(set_attr "type" "compare,compare,compare")])
3123
3124 (define_insn "*cmpqi_test_noov"
3125   [(set (reg:CC_NOOV 21)
3126         (compare:CC_NOOV (match_operand:QI 0 "src_operand" "r,rR,rS<>")
3127                          (match_operand:QI 1 "src_operand" "rIm,JR,rS<>")))]
3128   "valid_operands (COMPARE, operands, QImode)"
3129   "@
3130    cmpi\\t%1,%0
3131    cmpi3\\t%1,%0
3132    cmpi3\\t%1,%0"
3133   [(set_attr "type" "compare,compare,compare")])
3134
3135
3136 ;
3137 ; BIT-FIELD INSTRUCTIONS
3138 ;
3139
3140 ;
3141 ; LBx/LHw (C4x only)
3142 ;
3143 (define_expand "extv"
3144   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3145                    (sign_extract:QI (match_operand:QI 1 "src_operand" "")
3146                                     (match_operand:QI 2 "const_int_operand" "")
3147                                     (match_operand:QI 3 "const_int_operand" "")))
3148               (clobber (reg:CC 21))])]
3149  "! TARGET_C3X"
3150  "if ((INTVAL (operands[2]) != 8 && INTVAL (operands[2]) != 16)
3151       || (INTVAL (operands[3]) % INTVAL (operands[2]) != 0))
3152         FAIL;
3153  ")
3154
3155 (define_insn "*extv_clobber"
3156   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3157         (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm,rLm")
3158                          (match_operand:QI 2 "const_int_operand" "n,n")
3159                          (match_operand:QI 3 "const_int_operand" "n,n")))
3160    (clobber (reg:CC 21))]
3161   "! TARGET_C3X
3162    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3163    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3164   "*
3165    if (INTVAL (operands[2]) == 8)
3166      {
3167        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3168        return \"lb%3\\t%1,%0\";
3169      }
3170    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3171    return \"lh%3\\t%1,%0\";
3172   "
3173   [(set_attr "type" "binarycc,binary")
3174    (set_attr "data" "int16,int16")])
3175
3176 (define_insn "*extv_clobber_test"
3177   [(set (reg:CC 21)
3178         (compare:CC (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3179                                      (match_operand:QI 2 "const_int_operand" "n")
3180                                      (match_operand:QI 3 "const_int_operand" "n"))
3181                     (const_int 0)))
3182    (clobber (match_scratch:QI 0 "=d"))]
3183   "! TARGET_C3X
3184    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3185    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3186   "*
3187    if (INTVAL (operands[2]) == 8)
3188      {
3189        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3190        return \"lb%3\\t%1,%0\";
3191      }
3192    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3193    return \"lh%3\\t%1,%0\";
3194   "
3195   [(set_attr "type" "binarycc")
3196    (set_attr "data" "int16")])
3197
3198 (define_insn "*extv_clobber_set"
3199   [(set (reg:CC 21)
3200         (compare:CC (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3201                                      (match_operand:QI 2 "const_int_operand" "n")
3202                                      (match_operand:QI 3 "const_int_operand" "n"))
3203                     (const_int 0)))
3204    (set (match_operand:QI 0 "reg_operand" "=d")
3205         (sign_extract:QI (match_dup 1)
3206                          (match_dup 2)
3207                          (match_dup 3)))]
3208   "! TARGET_C3X
3209    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3210    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3211   "*
3212    if (INTVAL (operands[2]) == 8)
3213      {
3214        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3215        return \"lb%3\\t%1,%0\";
3216      }
3217    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3218    return \"lh%3\\t%1,%0\";
3219   "
3220   [(set_attr "type" "binarycc")
3221    (set_attr "data" "int16")])
3222
3223 ;
3224 ; LBUx/LHUw (C4x only)
3225 ;
3226 (define_expand "extzv"
3227   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3228                    (zero_extract:QI (match_operand:QI 1 "src_operand" "")
3229                                     (match_operand:QI 2 "const_int_operand" "")
3230                                     (match_operand:QI 3 "const_int_operand" "")))
3231               (clobber (reg:CC 21))])]
3232  "! TARGET_C3X"
3233  "if ((INTVAL (operands[2]) != 8 && INTVAL (operands[2]) != 16)
3234       || (INTVAL (operands[3]) % INTVAL (operands[2]) != 0))
3235         FAIL;
3236  ")
3237
3238 (define_insn "*extzv_clobber"
3239   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3240         (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm,rLm")
3241                          (match_operand:QI 2 "const_int_operand" "n,n")
3242                          (match_operand:QI 3 "const_int_operand" "n,n")))
3243    (clobber (reg:CC 21))]
3244   "! TARGET_C3X
3245    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3246    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3247   "*
3248    if (INTVAL (operands[2]) == 8)
3249      {
3250        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3251        return \"lbu%3\\t%1,%0\";
3252      }
3253    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3254    return \"lhu%3\\t%1,%0\";
3255   "
3256   [(set_attr "type" "binarycc,binary")
3257    (set_attr "data" "uint16,uint16")])
3258
3259 (define_insn "*extzv_test"
3260   [(set (reg:CC 21)
3261         (compare:CC (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3262                                      (match_operand:QI 2 "const_int_operand" "n")
3263                                      (match_operand:QI 3 "const_int_operand" "n"))
3264                     (const_int 0)))
3265    (clobber (match_scratch:QI 0 "=d"))]
3266   "! TARGET_C3X
3267    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3268    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3269   "*
3270    if (INTVAL (operands[2]) == 8)
3271      {
3272        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3273        return \"lbu%3\\t%1,%0\";
3274      }
3275    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3276    return \"lhu%3\\t%1,%0\";
3277   "
3278   [(set_attr "type" "binarycc")
3279    (set_attr "data" "uint16")])
3280
3281 (define_insn "*extzv_set"
3282   [(set (reg:CC 21)
3283         (compare:CC (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3284                                      (match_operand:QI 2 "const_int_operand" "n")
3285                                      (match_operand:QI 3 "const_int_operand" "n"))
3286                     (const_int 0)))
3287    (set (match_operand:QI 0 "ext_reg_operand" "=d")
3288         (zero_extract:QI (match_dup 1)
3289                          (match_dup 2)
3290                          (match_dup 3)))]
3291   "! TARGET_C3X
3292    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3293    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3294   "*
3295    if (INTVAL (operands[2]) == 8)
3296      {
3297         /* 8 bit extract.  */
3298        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3299        return \"lbu%3\\t%1,%0\";
3300      }
3301    /* 16 bit extract.  */
3302    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3303    return \"lhu%3\\t%1,%0\";
3304   "
3305   [(set_attr "type" "binarycc")
3306    (set_attr "data" "uint16")])
3307
3308 ;
3309 ; MBx/MHw (C4x only)
3310 ;
3311 (define_expand "insv"
3312   [(parallel [(set (zero_extract:QI (match_operand:QI 0 "reg_operand" "")
3313                                     (match_operand:QI 1 "const_int_operand" "")
3314                                     (match_operand:QI 2 "const_int_operand" ""))
3315                    (match_operand:QI 3 "src_operand" ""))
3316               (clobber (reg:CC 21))])]
3317  "! TARGET_C3X"
3318  "if (! (((INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3319          && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0))
3320         || (INTVAL (operands[1]) == 24 && INTVAL (operands[2]) == 8)))
3321     FAIL;
3322  ")
3323
3324 (define_insn "*insv_clobber"
3325   [(set (zero_extract:QI (match_operand:QI 0 "reg_operand" "=d,c")
3326                          (match_operand:QI 1 "const_int_operand" "n,n")
3327                          (match_operand:QI 2 "const_int_operand" "n,n"))
3328         (match_operand:QI 3 "src_operand" "rLm,rLm"))
3329    (clobber (reg:CC 21))]
3330   "! TARGET_C3X
3331    && (((INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3332         && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0))
3333        || (INTVAL (operands[1]) == 24 && INTVAL (operands[2]) == 8))"
3334   "*
3335    if (INTVAL (operands[1]) == 8)
3336      {
3337        /* 8 bit insert.  */
3338        operands[2] = GEN_INT (INTVAL (operands[2]) / 8);
3339        return \"mb%2\\t%3,%0\";
3340      }
3341    else if (INTVAL (operands[1]) == 16)
3342      {
3343        /* 16 bit insert.  */
3344        operands[2] = GEN_INT (INTVAL (operands[2]) / 16);
3345        return \"mh%2\\t%3,%0\";
3346      }
3347    /* 24 bit insert.  */
3348    return \"lwl1\\t%3,%0\";
3349   "
3350   [(set_attr "type" "binarycc,binary")
3351    (set_attr "data" "uint16,uint16")])
3352
3353 (define_peephole
3354   [(parallel [(set (zero_extract:QI (match_operand:QI 0 "ext_reg_operand" "=d")
3355                                     (match_operand:QI 1 "const_int_operand" "n")
3356                                     (match_operand:QI 2 "const_int_operand" "n"))
3357                    (match_operand:QI 3 "src_operand" "rLm"))
3358               (clobber (reg:CC 21))])
3359    (set (reg:CC 21)
3360         (compare:CC (match_dup 0) (const_int 0)))]
3361   "! TARGET_C3X
3362    && (INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3363    && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0)"
3364   "*
3365    if (INTVAL (operands[1]) == 8)
3366      {
3367        operands[2] = GEN_INT (INTVAL (operands[2]) / 8);
3368        return \"mb%2\\t%3,%0\";
3369      }
3370    operands[2] = GEN_INT (INTVAL (operands[2]) / 16);
3371    return \"mh%2\\t%3,%0\";
3372   "
3373   [(set_attr "type" "binarycc")
3374    (set_attr "data" "uint16")])
3375
3376
3377 ; TWO OPERAND FLOAT INSTRUCTIONS
3378 ;
3379
3380 ;
3381 ; LDF/STF
3382 ;
3383 ;  If one of the operands is not a register, then we should
3384 ;  emit two insns, using a scratch register.  This will produce
3385 ;  better code in loops if the source operand is invariant, since
3386 ;  the source reload can be optimised out.  During reload we cannot
3387 ;  use change_address or force_reg.
3388 (define_expand "movqf"
3389   [(set (match_operand:QF 0 "src_operand" "")
3390         (match_operand:QF 1 "src_operand" ""))]
3391  ""
3392  "
3393 {
3394   if (c4x_emit_move_sequence (operands, QFmode))
3395     DONE;
3396 }")
3397
3398 ; This can generate invalid stack slot displacements
3399 (define_split
3400  [(set (match_operand:QI 0 "reg_operand" "=r")
3401        (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))]
3402   "reload_completed"
3403   [(set (match_dup 3) (match_dup 1))
3404    (set (match_dup 0) (match_dup 2))]
3405   "operands[2] = assign_stack_temp (QImode, GET_MODE_SIZE (QImode), 0);
3406    operands[3] = copy_rtx (operands[2]);
3407    PUT_MODE (operands[3], QFmode);")
3408
3409
3410 (define_insn "storeqf_int"
3411  [(set (match_operand:QI 0 "reg_operand" "=r")
3412        (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))]
3413  ""
3414  "#"
3415   [(set_attr "type" "multi")])
3416
3417 (define_split
3418  [(parallel [(set (match_operand:QI 0 "reg_operand" "=r")
3419                   (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))
3420              (clobber (reg:CC 21))])]
3421   "reload_completed"
3422   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
3423         (match_dup 1))
3424    (parallel [(set (match_dup 0)
3425                    (mem:QI (post_dec:QI (reg:QI 20))))
3426               (clobber (reg:CC 21))])]
3427   "")
3428
3429
3430 ; We need accurate death notes for this...
3431 ;(define_peephole
3432 ;  [(set (match_operand:QF 0 "reg_operand" "=f")
3433 ;        (match_operand:QF 1 "memory_operand" "m"))
3434 ;   (set (mem:QF (pre_inc:QI (reg:QI 20)))
3435 ;        (match_dup 0))
3436 ;   (parallel [(set (match_operand:QI 2 "reg_operand" "r")
3437 ;                   (mem:QI (post_dec:QI (reg:QI 20))))
3438 ;              (clobber (reg:CC 21))])]
3439 ;  ""
3440 ;  "ldiu\\t%1,%0")
3441
3442 (define_insn "storeqf_int_clobber"
3443  [(parallel [(set (match_operand:QI 0 "reg_operand" "=r")
3444                   (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))
3445              (clobber (reg:CC 21))])]
3446  ""
3447  "#"
3448   [(set_attr "type" "multi")])
3449
3450
3451 ; This can generate invalid stack slot displacements
3452 (define_split
3453  [(set (match_operand:QF 0 "reg_operand" "=f")
3454        (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))]
3455   "reload_completed"
3456   [(set (match_dup 2) (match_dup 1))
3457    (set (match_dup 0) (match_dup 3))]
3458   "operands[2] = assign_stack_temp (QImode, GET_MODE_SIZE (QImode), 0);
3459    operands[3] = copy_rtx (operands[2]);
3460    PUT_MODE (operands[3], QFmode);")
3461
3462
3463 (define_insn "loadqf_int"
3464  [(set (match_operand:QF 0 "reg_operand" "=f")
3465        (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))]
3466  ""
3467  "#"
3468   [(set_attr "type" "multi")])
3469
3470 (define_split
3471  [(parallel [(set (match_operand:QF 0 "reg_operand" "=f")
3472                   (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))
3473              (clobber (reg:CC 21))])]
3474   "reload_completed"
3475   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
3476         (match_dup 1))
3477    (parallel [(set (match_dup 0)
3478                    (mem:QF (post_dec:QI (reg:QI 20))))
3479               (clobber (reg:CC 21))])]
3480   "")
3481
3482 (define_insn "loadqf_int_clobber"
3483  [(parallel [(set (match_operand:QF 0 "reg_operand" "=f")
3484                   (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))
3485              (clobber (reg:CC 21))])]
3486  ""
3487  "#"
3488   [(set_attr "type" "multi")])
3489
3490 ; We must provide an alternative to store to memory in case we have to
3491 ; spill a register.
3492 (define_insn "movqf_noclobber"
3493  [(set (match_operand:QF 0 "dst_operand" "=f,m")
3494        (match_operand:QF 1 "src_operand" "fHm,f"))]
3495  "REG_P (operands[0]) || REG_P (operands[1])"
3496  "@
3497   ldfu\\t%1,%0
3498   stf\\t%1,%0"
3499   [(set_attr "type" "unary,store")])
3500
3501 ;(define_insn "*movqf_clobber"
3502 ;  [(set (match_operand:QF 0 "reg_operand" "=f")
3503 ;        (match_operand:QF 1 "src_operand" "fHm"))
3504 ;   (clobber (reg:CC 21))]
3505 ; "0"
3506 ; "ldf\\t%1,%0"
3507 ;  [(set_attr "type" "unarycc")])
3508
3509 (define_insn "*movqf_test"
3510   [(set (reg:CC 21)
3511         (compare:CC (match_operand:QF 1 "src_operand" "fHm")
3512                     (const_int 0)))
3513    (clobber (match_scratch:QF 0 "=f"))]
3514  ""
3515  "ldf\\t%1,%0"
3516   [(set_attr "type" "unarycc")])
3517
3518 (define_insn "*movqf_set"
3519   [(set (reg:CC 21)
3520         (compare:CC (match_operand:QF 1 "src_operand" "fHm")
3521                     (match_operand:QF 2 "fp_zero_operand" "G")))
3522     (set (match_operand:QF 0 "reg_operand" "=f")
3523          (match_dup 1))]
3524  ""
3525  "ldf\\t%1,%0"
3526   [(set_attr "type" "unarycc")])
3527
3528
3529 (define_insn "*movqf_parallel"
3530  [(set (match_operand:QF 0 "parallel_operand" "=q,S<>!V,q,S<>!V")
3531        (match_operand:QF 1 "parallel_operand" "S<>!V,q,S<>!V,q"))
3532   (set (match_operand:QF 2 "parallel_operand" "=q,S<>!V,S<>!V,q")
3533        (match_operand:QF 3 "parallel_operand" "S<>!V,q,q,S<>!V"))]
3534  "TARGET_PARALLEL && valid_parallel_load_store (operands, QFmode)"
3535  "@
3536   ldf1\\t%1,%0\\n||\\tldf2\\t%3,%2
3537   stf1\\t%1,%0\\n||\\tstf2\\t%3,%2
3538   ldf\\t%1,%0\\n||\\tstf\\t%3,%2
3539   ldf\\t%3,%2\\n||\\tstf\\t%1,%0"
3540   [(set_attr "type" "load_load,store_store,load_store,store_load")])
3541
3542
3543 ;
3544 ; PUSH/POP
3545 ;
3546 (define_insn "*pushqf"
3547   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
3548         (match_operand:QF 0 "reg_operand" "f"))]
3549  ""
3550  "pushf\\t%0"
3551  [(set_attr "type" "push")])
3552
3553 (define_insn "*popqf"
3554   [(set (match_operand:QF 0 "reg_operand" "=f")
3555         (mem:QF (post_dec:QI (reg:QI 20))))
3556    (clobber (reg:CC 21))]
3557  ""
3558  "popf\\t%0"
3559  [(set_attr "type" "pop")])
3560
3561
3562 ;
3563 ; ABSF
3564 ;
3565 (define_expand "absqf2"
3566   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3567                    (abs:QF (match_operand:QF 1 "src_operand" "")))
3568               (clobber (reg:CC_NOOV 21))])]
3569 ""
3570 "")
3571
3572 (define_insn "*absqf2_clobber"
3573   [(set (match_operand:QF 0 "reg_operand" "=f")
3574         (abs:QF (match_operand:QF 1 "src_operand" "fHm")))
3575    (clobber (reg:CC_NOOV 21))]
3576   ""
3577   "absf\\t%1,%0"
3578   [(set_attr "type" "unarycc")])
3579
3580 (define_insn "*absqf2_test"
3581   [(set (reg:CC_NOOV 21)
3582         (compare:CC_NOOV (abs:QF (match_operand:QF 1 "src_operand" "fHm"))
3583                          (match_operand:QF 2 "fp_zero_operand" "G")))
3584    (clobber (match_scratch:QF 0 "=f"))]
3585   ""
3586   "absf\\t%1,%0"
3587   [(set_attr "type" "unarycc")])
3588
3589 (define_insn "*absqf2_set"
3590   [(set (reg:CC_NOOV 21)
3591         (compare:CC_NOOV (abs:QF (match_operand:QF 1 "src_operand" "fHm"))
3592                          (match_operand:QF 2 "fp_zero_operand" "G")))
3593    (set (match_operand:QF 0 "reg_operand" "=f")
3594         (abs:QF (match_dup 1)))]
3595
3596   ""
3597   "absf\\t%1,%0"
3598   [(set_attr "type" "unarycc")])
3599
3600 ;
3601 ; NEGF
3602 ;
3603 (define_expand "negqf2"
3604   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3605                    (neg:QF (match_operand:QF 1 "src_operand" "")))
3606               (clobber (reg:CC_NOOV 21))])]
3607 ""
3608 "")
3609
3610 (define_insn "*negqf2_clobber"
3611   [(set (match_operand:QF 0 "reg_operand" "=f")
3612         (neg:QF (match_operand:QF 1 "src_operand" "fHm")))
3613    (clobber (reg:CC_NOOV 21))]
3614   ""
3615   "negf\\t%1,%0"
3616   [(set_attr "type" "unarycc")])
3617
3618 (define_insn "*negqf2_test"
3619   [(set (reg:CC_NOOV 21)
3620         (compare:CC_NOOV (neg:QF (match_operand:QF 1 "src_operand" "fHm"))
3621                          (match_operand:QF 2 "fp_zero_operand" "G")))
3622    (clobber (match_scratch:QF 0 "=f"))]
3623   ""
3624   "negf\\t%1,%0"
3625   [(set_attr "type" "unarycc")])
3626
3627 (define_insn "*negqf2_set"
3628   [(set (reg:CC_NOOV 21)
3629         (compare:CC_NOOV (neg:QF (match_operand:QF 1 "src_operand" "fHm"))
3630                          (match_operand:QF 2 "fp_zero_operand" "G")))
3631    (set (match_operand:QF 0 "reg_operand" "=f")
3632         (neg:QF (match_dup 1)))]
3633   ""
3634   "negf\\t%1,%0"
3635   [(set_attr "type" "unarycc")])
3636
3637 ;
3638 ; FLOAT
3639 ;
3640 (define_insn "floatqiqf2"
3641   [(set (match_operand:QF 0 "reg_operand" "=f")
3642         (float:QF (match_operand:QI 1 "src_operand" "rIm")))
3643    (clobber (reg:CC 21))]
3644  ""
3645  "float\\t%1,%0"
3646   [(set_attr "type" "unarycc")])
3647
3648 (define_insn "*floatqiqf2_set"
3649   [(set (reg:CC 21)
3650         (compare:CC (float:QF (match_operand:QI 1 "src_operand" "rIm"))
3651                     (match_operand:QF 2 "fp_zero_operand" "G")))
3652    (set (match_operand:QF 0 "reg_operand" "=f")
3653         (float:QF (match_dup 1)))]
3654  ""
3655  "float\\t%1,%0"
3656   [(set_attr "type" "unarycc")])
3657
3658 ; Unsigned conversions are a little tricky because we need to
3659 ; add the value for the high bit if necessary.
3660
3661 ;
3662 (define_expand "floatunsqiqf2"
3663  [(set (match_dup 2) (match_dup 3))
3664   (parallel [(set (reg:CC 21)
3665                   (compare:CC (float:QF (match_operand:QI 1 "src_operand" ""))
3666                               (match_dup 3)))
3667              (set (match_dup 4)
3668                   (float:QF (match_dup 1)))])
3669   (set (match_dup 6)
3670        (if_then_else:QF (lt (reg:CC 21) (const_int 0))
3671                         (match_dup 5)
3672                         (match_dup 2)))
3673   (parallel [(set (match_operand:QF 0 "reg_operand" "")
3674                   (plus:QF (match_dup 6) (match_dup 4)))
3675              (clobber (reg:CC_NOOV 21))])]
3676  ""
3677  "operands[2] = gen_reg_rtx (QFmode);
3678   operands[3] = CONST0_RTX (QFmode); 
3679   operands[4] = gen_reg_rtx (QFmode);
3680   operands[5] = gen_reg_rtx (QFmode);
3681   operands[6] = gen_reg_rtx (QFmode);
3682   emit_move_insn (operands[5], 
3683    immed_real_const_1 (REAL_VALUE_ATOF (\"4294967296.0\", QFmode), QFmode));")
3684
3685 (define_insn "floatqihf2"
3686   [(set (match_operand:HF 0 "reg_operand" "=h")
3687         (float:HF (match_operand:QI 1 "src_operand" "rIm")))
3688    (clobber (reg:CC 21))]
3689  ""
3690  "float\\t%1,%0"
3691   [(set_attr "type" "unarycc")])
3692
3693 ;
3694 ; FIX
3695 ;
3696 (define_insn "fixqfqi_clobber"
3697   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3698         (fix:QI (match_operand:QF 1 "src_operand" "fHm,fHm")))
3699    (clobber (reg:CC 21))]
3700  ""
3701  "fix\\t%1,%0"
3702   [(set_attr "type" "unarycc")])
3703
3704 (define_insn "*fixqfqi_set"
3705   [(set (reg:CC 21)
3706         (compare:CC (fix:QI (match_operand:QF 1 "src_operand" "fHm"))
3707                     (const_int 0)))
3708    (set (match_operand:QI 0 "ext_reg_operand" "=d")
3709         (fix:QI (match_dup 1)))]
3710  ""
3711  "fix\\t%1,%0"
3712   [(set_attr "type" "unarycc")])
3713
3714 ;
3715 ; The C[34]x fix instruction implements a floor, not a straight trunc,
3716 ; so we have to invert the number, fix it, and reinvert it if negative
3717 ;
3718 (define_expand "fix_truncqfqi2"
3719   [(parallel [(set (match_dup 2)
3720                    (fix:QI (match_operand:QF 1 "src_operand" "")))
3721               (clobber (reg:CC 21))])
3722    (parallel [(set (match_dup 3) (neg:QF (match_dup 1)))
3723               (clobber (reg:CC_NOOV 21))])
3724    (parallel [(set (match_dup 4) (fix:QI (match_dup 3)))
3725               (clobber (reg:CC 21))])
3726    (parallel [(set (reg:CC_NOOV 21)
3727                    (compare:CC_NOOV (neg:QI (match_dup 4)) (const_int 0)))
3728               (set (match_dup 5) (neg:QI (match_dup 4)))])
3729    (set (match_dup 2)
3730         (if_then_else:QI (le (reg:CC 21) (const_int 0))
3731                          (match_dup 5)
3732                          (match_dup 2)))
3733    (set (match_operand:QI 0 "reg_operand" "=r") (match_dup 2))]
3734  ""
3735  "if (TARGET_FAST_FIX)
3736     {
3737        emit_insn (gen_fixqfqi_clobber (operands[0], operands[1]));
3738        DONE;
3739     }
3740   operands[2] = gen_reg_rtx (QImode);
3741   operands[3] = gen_reg_rtx (QFmode);
3742   operands[4] = gen_reg_rtx (QImode);
3743   operands[5] = gen_reg_rtx (QImode);
3744  ")
3745
3746 (define_expand "fix_truncqfhi2"
3747   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
3748                    (fix:HI (match_operand:QF 1 "src_operand" "")))
3749               (clobber (reg:CC 21))])]
3750   ""
3751   "c4x_emit_libcall (fix_truncqfhi2_libfunc, FIX, HImode, QFmode, 2, operands);
3752    DONE;")
3753
3754 (define_expand "fixuns_truncqfqi2"
3755  [(set (match_dup 2) (match_dup 5))
3756   (set (reg:CC 21)
3757        (compare:CC (match_operand:QF 1 "src_operand" "fHm")
3758                    (match_dup 2)))
3759   (set (match_dup 2)
3760        (if_then_else:QF (lt (reg:CC 21) (const_int 0))
3761                         (match_dup 4)
3762                         (match_dup 2)))
3763   (parallel [(set (match_dup 2)
3764                   (plus:QF (match_dup 2) (match_dup 2)))
3765              (clobber (reg:CC_NOOV 21))])
3766   (parallel [(set (match_dup 2)
3767                   (minus:QF (match_dup 1) (match_dup 2)))
3768              (clobber (reg:CC_NOOV 21))])
3769   (parallel [(set (match_operand:QI 0 "reg_operand" "=r")
3770                   (fix:QI (match_dup 2)))
3771              (clobber (reg:CC 21))])]
3772  ""
3773  "operands[2] = gen_reg_rtx (QFmode);
3774   operands[3] = gen_reg_rtx (QFmode);
3775   operands[4] = gen_reg_rtx (QFmode);
3776   operands[5] = gen_reg_rtx (QFmode);
3777   emit_move_insn (operands[4],
3778    immed_real_const_1 (REAL_VALUE_ATOF (\"0.0\", QFmode), QFmode));
3779   emit_move_insn (operands[5],
3780    immed_real_const_1 (REAL_VALUE_ATOF (\"2147483648.0\", QFmode), QFmode));")
3781
3782 (define_expand "fixuns_truncqfhi2"
3783   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
3784                    (unsigned_fix:HI (match_operand:QF 1 "src_operand" "")))
3785               (clobber (reg:CC 21))])]
3786   ""
3787   "c4x_emit_libcall (fixuns_truncqfhi2_libfunc, UNSIGNED_FIX, 
3788                      HImode, QFmode, 2, operands);
3789    DONE;")
3790
3791 ;
3792 ; RCPF
3793 ;
3794 (define_insn "*rcpfqf_clobber"
3795   [(set (match_operand:QF 0 "reg_operand" "=f")
3796         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] 5))
3797    (clobber (reg:CC_NOOV 21))]
3798   "! TARGET_C3X"
3799   "rcpf\\t%1,%0"
3800   [(set_attr "type" "unarycc")])
3801
3802 ;
3803 ; RSQRF
3804 ;
3805 (define_insn "*rsqrfqf_clobber"
3806   [(set (match_operand:QF 0 "reg_operand" "=f")
3807         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] 10))
3808    (clobber (reg:CC_NOOV 21))]
3809   "! TARGET_C3X"
3810   "rsqrf\\t%1,%0"
3811   [(set_attr "type" "unarycc")])
3812
3813 ;
3814 ; RNDF
3815 ;
3816 (define_insn "*rndqf_clobber"
3817   [(set (match_operand:QF 0 "reg_operand" "=f")
3818         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] 6))
3819    (clobber (reg:CC_NOOV 21))]
3820   "! TARGET_C3X"
3821   "rnd\\t%1,%0"
3822   [(set_attr "type" "unarycc")])
3823
3824
3825 ; Inlined float square root for C4x
3826 (define_expand "sqrtqf2_inline"
3827   [(parallel [(set (match_dup 2)
3828                    (unspec:QF [(match_operand:QF 1 "src_operand" "")] 10))
3829               (clobber (reg:CC_NOOV 21))])
3830    (parallel [(set (match_dup 3) (mult:QF (match_dup 5) (match_dup 1)))
3831               (clobber (reg:CC_NOOV 21))])
3832    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
3833               (clobber (reg:CC_NOOV 21))])
3834    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 4)))
3835               (clobber (reg:CC_NOOV 21))])
3836    (parallel [(set (match_dup 4) (minus:QF (match_dup 6) (match_dup 4)))
3837               (clobber (reg:CC_NOOV 21))])
3838    (parallel [(set (match_dup 2) (mult:QF (match_dup 2) (match_dup 4)))
3839               (clobber (reg:CC_NOOV 21))])
3840    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
3841               (clobber (reg:CC_NOOV 21))])
3842    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 4)))
3843               (clobber (reg:CC_NOOV 21))])
3844    (parallel [(set (match_dup 4) (minus:QF (match_dup 6) (match_dup 4)))
3845               (clobber (reg:CC_NOOV 21))])
3846    (parallel [(set (match_dup 2) (mult:QF (match_dup 2) (match_dup 4)))
3847               (clobber (reg:CC_NOOV 21))])
3848    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 1)))
3849               (clobber (reg:CC_NOOV 21))])
3850    (parallel [(set (match_operand:QF 0 "reg_operand" "")
3851                    (unspec:QF [(match_dup 4)] 6))
3852               (clobber (reg:CC_NOOV 21))])]
3853   "! TARGET_C3X"
3854   "if (! reload_in_progress
3855        && ! reg_operand (operands[1], QFmode))
3856      operands[1] = force_reg (QFmode, operands[1]);
3857    operands[2] = gen_reg_rtx (QFmode);
3858    operands[3] = gen_reg_rtx (QFmode);
3859    operands[4] = gen_reg_rtx (QFmode);
3860    operands[5] = immed_real_const_1 (REAL_VALUE_ATOF (\"0.5\", QFmode),
3861                                      QFmode);
3862    operands[6] = immed_real_const_1 (REAL_VALUE_ATOF (\"1.5\", QFmode),
3863                                      QFmode);")
3864
3865 (define_expand "sqrtqf2"
3866   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3867                    (sqrt:QF (match_operand:QF 1 "src_operand" "")))
3868               (clobber (reg:CC 21))])]
3869   "! TARGET_C3X && TARGET_INLINE"
3870   "emit_insn (gen_sqrtqf2_inline (operands[0], operands[1]));
3871    DONE;")
3872
3873 ;
3874 ; THREE OPERAND FLOAT INSTRUCTIONS
3875 ;
3876
3877 ;
3878 ; ADDF
3879 ;
3880 (define_expand "addqf3"
3881   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3882                    (plus:QF (match_operand:QF 1 "src_operand" "")
3883                             (match_operand:QF 2 "src_operand" "")))
3884               (clobber (reg:CC_NOOV 21))])]
3885   ""
3886   "legitimize_operands (PLUS, operands, QFmode);")
3887
3888 (define_insn "*addqf3_clobber"
3889   [(set (match_operand:QF 0 "reg_operand" "=f,f,?f")
3890         (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3891                  (match_operand:QF 2 "src_operand" "fHm,R,fS<>")))
3892    (clobber (reg:CC_NOOV 21))]
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 (define_insn "*addqf3_test"
3901   [(set (reg:CC_NOOV 21)
3902         (compare:CC_NOOV (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3903                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
3904                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
3905    (clobber (match_scratch:QF 0 "=f,f,?f"))]
3906   "valid_operands (PLUS, operands, QFmode)"
3907   "@
3908    addf\\t%2,%0
3909    addf3\\t%2,%1,%0
3910    addf3\\t%2,%1,%0"
3911   [(set_attr "type" "binarycc,binarycc,binarycc")])
3912
3913 (define_insn "*addqf3_set"
3914   [(set (reg:CC_NOOV 21)
3915         (compare:CC_NOOV (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3916                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
3917                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
3918    (set (match_operand:QF 0 "reg_operand" "=f,f,?f")
3919         (plus:QF (match_dup 1)
3920                  (match_dup 2)))]
3921   "valid_operands (PLUS, operands, QFmode)"
3922   "@
3923    addf\\t%2,%0
3924    addf3\\t%2,%1,%0
3925    addf3\\t%2,%1,%0"
3926   [(set_attr "type" "binarycc,binarycc,binarycc")])
3927
3928 ;
3929 ; SUBF/SUBRF
3930 ;
3931 (define_expand "subqf3"
3932   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3933                    (minus:QF (match_operand:QF 1 "src_operand" "")
3934                              (match_operand:QF 2 "src_operand" "")))
3935               (clobber (reg:CC_NOOV 21))])]
3936   ""
3937   "legitimize_operands (MINUS, operands, QFmode);")
3938
3939 (define_insn "*subqf3_clobber"
3940    [(set (match_operand:QF 0 "reg_operand" "=f,f,f,?f")
3941          (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
3942                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>")))
3943    (clobber (reg:CC_NOOV 21))]
3944   "valid_operands (MINUS, operands, QFmode)"
3945   "@
3946    subf\\t%2,%0
3947    subrf\\t%1,%0
3948    subf3\\t%2,%1,%0
3949    subf3\\t%2,%1,%0"
3950   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
3951
3952 (define_insn "*subqf3_test"
3953   [(set (reg:CC_NOOV 21)
3954         (compare:CC_NOOV (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
3955                                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>"))
3956                          (match_operand:QF 3 "fp_zero_operand" "G,G,G,G")))
3957    (clobber (match_scratch:QF 0 "=f,f,f,?f"))]
3958   "valid_operands (MINUS, operands, QFmode)"
3959   "@
3960    subf\\t%2,%0
3961    subrf\\t%1,%0
3962    subf3\\t%2,%1,%0
3963    subf3\\t%2,%1,%0"
3964   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
3965
3966 (define_insn "*subqf3_set"
3967   [(set (reg:CC_NOOV 21)
3968         (compare:CC_NOOV (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
3969                                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>"))
3970                          (match_operand:QF 3 "fp_zero_operand" "G,G,G,G")))
3971    (set (match_operand:QF 0 "reg_operand" "=f,f,f,?f")
3972         (minus:QF (match_dup 1)
3973                   (match_dup 2)))]
3974   "valid_operands (MINUS, operands, QFmode)"
3975   "@
3976    subf\\t%2,%0
3977    subrf\\t%1,%0
3978    subf3\\t%2,%1,%0
3979    subf3\\t%2,%1,%0"
3980   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
3981
3982 ;
3983 ; MPYF
3984 ;
3985 (define_expand "mulqf3"
3986   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3987                    (mult:QF (match_operand:QF 1 "src_operand" "")
3988                             (match_operand:QF 2 "src_operand" "")))
3989               (clobber (reg:CC_NOOV 21))])]
3990   ""
3991   "legitimize_operands (MULT, operands, QFmode);")
3992
3993 (define_insn "*mulqf3_clobber"
3994   [(set (match_operand:QF 0 "reg_operand" "=f,f,?f")
3995         (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3996                  (match_operand:QF 2 "src_operand" "fHm,R,fS<>")))
3997    (clobber (reg:CC_NOOV 21))]
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 (define_insn "*mulqf3_test"
4006   [(set (reg:CC_NOOV 21)
4007         (compare:CC_NOOV (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4008                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
4009                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
4010    (clobber (match_scratch:QF 0 "=f,f,?f"))]
4011   "valid_operands (MULT, operands, QFmode)"
4012   "@
4013    mpyf\\t%2,%0
4014    mpyf3\\t%2,%1,%0
4015    mpyf3\\t%2,%1,%0"
4016   [(set_attr "type" "binarycc,binarycc,binarycc")])
4017
4018 (define_insn "*mulqf3_set"
4019   [(set (reg:CC_NOOV 21)
4020         (compare:CC_NOOV (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4021                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
4022                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
4023    (set (match_operand:QF 0 "reg_operand" "=f,f,?f")
4024         (mult:QF (match_dup 1)
4025                  (match_dup 2)))]
4026   "valid_operands (MULT, operands, QFmode)"
4027   "@
4028    mpyf\\t%2,%0
4029    mpyf3\\t%2,%1,%0
4030    mpyf3\\t%2,%1,%0"
4031   [(set_attr "type" "binarycc,binarycc,binarycc")])
4032
4033 ;
4034 ; CMPF
4035 ;
4036 (define_expand "cmpqf"
4037   [(set (reg:CC 21)
4038         (compare:CC (match_operand:QF 0 "src_operand" "")
4039                     (match_operand:QF 1 "src_operand" "")))]
4040   ""
4041   "legitimize_operands (COMPARE, operands, QFmode);
4042    c4x_compare_op0 = operands[0];
4043    c4x_compare_op1 = operands[1];
4044    DONE;")
4045
4046 (define_insn "*cmpqf"
4047   [(set (reg:CC 21)
4048         (compare:CC (match_operand:QF 0 "src_operand" "f,fR,fS<>")
4049                     (match_operand:QF 1 "src_operand" "fHm,R,fS<>")))]
4050   "valid_operands (COMPARE, operands, QFmode)"
4051   "@
4052    cmpf\\t%1,%0
4053    cmpf3\\t%1,%0
4054    cmpf3\\t%1,%0"
4055   [(set_attr "type" "compare,compare,compare")])
4056
4057 (define_insn "*cmpqf_noov"
4058   [(set (reg:CC_NOOV 21)
4059         (compare:CC_NOOV (match_operand:QF 0 "src_operand" "f,fR,fS<>")
4060                          (match_operand:QF 1 "src_operand" "fHm,R,fS<>")))]
4061   "valid_operands (COMPARE, operands, QFmode)"
4062   "@
4063    cmpf\\t%1,%0
4064    cmpf3\\t%1,%0
4065    cmpf3\\t%1,%0"
4066   [(set_attr "type" "compare,compare,compare")])
4067
4068 ; Inlined float divide for C4x
4069 (define_expand "divqf3_inline"
4070   [(parallel [(set (match_dup 3)
4071                    (unspec:QF [(match_operand:QF 2 "src_operand" "")] 5))
4072               (clobber (reg:CC_NOOV 21))])
4073    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
4074               (clobber (reg:CC_NOOV 21))])
4075    (parallel [(set (match_dup 4) (minus:QF (match_dup 5) (match_dup 4)))
4076               (clobber (reg:CC_NOOV 21))])
4077    (parallel [(set (match_dup 3) (mult:QF (match_dup 3) (match_dup 4)))
4078               (clobber (reg:CC_NOOV 21))])
4079    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
4080               (clobber (reg:CC_NOOV 21))])
4081    (parallel [(set (match_dup 4) (minus:QF (match_dup 5) (match_dup 4)))
4082               (clobber (reg:CC_NOOV 21))])
4083    (parallel [(set (match_dup 3) (mult:QF (match_dup 3) (match_dup 4)))
4084               (clobber (reg:CC_NOOV 21))])
4085    (parallel [(set (match_dup 3)
4086                    (mult:QF (match_operand:QF 1 "src_operand" "")
4087                             (match_dup 3)))
4088               (clobber (reg:CC_NOOV 21))])
4089    (parallel [(set (match_operand:QF 0 "reg_operand" "")
4090                    (unspec:QF [(match_dup 3)] 6))
4091               (clobber (reg:CC_NOOV 21))])]
4092   "! TARGET_C3X"
4093   "if (! reload_in_progress
4094       && ! reg_operand (operands[2], QFmode))
4095      operands[2] = force_reg (QFmode, operands[2]);
4096    operands[3] = gen_reg_rtx (QFmode);
4097    operands[4] = gen_reg_rtx (QFmode);
4098    operands[5] = CONST2_RTX (QFmode);")
4099
4100 (define_expand "divqf3"
4101   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
4102                    (div:QF (match_operand:QF 1 "src_operand" "")
4103                             (match_operand:QF 2 "src_operand" "")))
4104               (clobber (reg:CC 21))])]
4105   "! TARGET_C3X && TARGET_INLINE"
4106   "emit_insn (gen_divqf3_inline (operands[0], operands[1], operands[2]));
4107    DONE;")
4108
4109 ;
4110 ; CONDITIONAL MOVES
4111 ;
4112
4113 ; ???  We should make these pattern fail if the src operand combination
4114 ; is not valid.  Although reload will fix things up, it will introduce
4115 ; extra load instructions that won't be hoisted out of a loop.
4116
4117 (define_insn "*ldi_conditional"
4118   [(set (match_operand:QI 0 "reg_operand" "=r,r")
4119         (if_then_else:QI (match_operator 1 "comparison_operator"
4120                           [(reg:CC 21) (const_int 0)])
4121                          (match_operand:QI 2 "src_operand" "rIm,0")
4122                          (match_operand:QI 3 "src_operand" "0,rIm")))]
4123  ""
4124  "@
4125   ldi%1\\t%2,%0
4126   ldi%I1\\t%3,%0"
4127  [(set_attr "type" "binary")])
4128
4129 (define_insn "*ldi_conditional_noov"
4130   [(set (match_operand:QI 0 "reg_operand" "=r,r")
4131         (if_then_else:QI (match_operator 1 "comparison_operator"
4132                           [(reg:CC_NOOV 21) (const_int 0)])
4133                          (match_operand:QI 2 "src_operand" "rIm,0")
4134                          (match_operand:QI 3 "src_operand" "0,rIm")))]
4135  "GET_CODE (operands[1]) != LE
4136   && GET_CODE (operands[1]) != GE
4137   && GET_CODE (operands[1]) != LT
4138   && GET_CODE (operands[1]) != GT"
4139  "@
4140   ldi%1\\t%2,%0
4141   ldi%I1\\t%3,%0"
4142  [(set_attr "type" "binary")])
4143
4144 ; Move operand 2 to operand 0 if condition (operand 1) is true
4145 ; else move operand 3 to operand 0.
4146 ; The temporary register is required below because some of the operands
4147 ; might be identical (namely 0 and 2). 
4148 ;
4149 (define_expand "movqicc"
4150   [(set (match_operand:QI 0 "reg_operand" "")
4151         (if_then_else:QI (match_operand 1 "comparison_operator" "")
4152                          (match_operand:QI 2 "src_operand" "")
4153                          (match_operand:QI 3 "src_operand" "")))]
4154  ""
4155  "{ 
4156     enum rtx_code code = GET_CODE (operands[1]);
4157     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
4158     if (ccreg == NULL_RTX) FAIL;
4159     emit_insn (gen_rtx_SET (QImode, operands[0],
4160                             gen_rtx_IF_THEN_ELSE (QImode,
4161                                  gen_rtx (code, VOIDmode, ccreg, const0_rtx),
4162                                           operands[2], operands[3])));
4163     DONE;}")
4164                       
4165 (define_insn "*ldf_conditional"
4166   [(set (match_operand:QF 0 "reg_operand" "=f,f")
4167         (if_then_else:QF (match_operator 1 "comparison_operator"
4168                           [(reg:CC 21) (const_int 0)])
4169                          (match_operand:QF 2 "src_operand" "fHm,0")
4170                          (match_operand:QF 3 "src_operand" "0,fHm")))]
4171  ""
4172  "@
4173   ldf%1\\t%2,%0
4174   ldf%I1\\t%3,%0"
4175  [(set_attr "type" "binary")])
4176
4177 (define_insn "*ldf_conditional_noov"
4178   [(set (match_operand:QF 0 "reg_operand" "=f,f")
4179         (if_then_else:QF (match_operator 1 "comparison_operator"
4180                           [(reg:CC_NOOV 21) (const_int 0)])
4181                          (match_operand:QF 2 "src_operand" "fHm,0")
4182                          (match_operand:QF 3 "src_operand" "0,fHm")))]
4183  "GET_CODE (operands[1]) != LE
4184   && GET_CODE (operands[1]) != GE
4185   && GET_CODE (operands[1]) != LT
4186   && GET_CODE (operands[1]) != GT"
4187  "@
4188   ldf%1\\t%2,%0
4189   ldf%I1\\t%3,%0"
4190  [(set_attr "type" "binary")])
4191
4192 (define_expand "movqfcc"
4193   [(set (match_operand:QF 0 "reg_operand" "")
4194         (if_then_else:QF (match_operand 1 "comparison_operator" "")
4195                          (match_operand:QF 2 "src_operand" "")
4196                          (match_operand:QF 3 "src_operand" "")))]
4197  ""
4198  "{ 
4199     enum rtx_code code = GET_CODE (operands[1]);
4200     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
4201     if (ccreg == NULL_RTX) FAIL;
4202     emit_insn (gen_rtx_SET (QFmode, operands[0],
4203                             gen_rtx_IF_THEN_ELSE (QFmode,
4204                                  gen_rtx (code, VOIDmode, ccreg, const0_rtx),
4205                                           operands[2], operands[3])));
4206     DONE;}")
4207
4208 (define_expand "seq"
4209  [(set (match_operand:QI 0 "reg_operand" "")
4210        (const_int 0))
4211   (set (match_dup 0)
4212        (if_then_else:QI (eq (match_dup 1) (const_int 0))
4213                         (const_int 1)
4214                         (match_dup 0)))]
4215  ""
4216  "operands[1] = c4x_gen_compare_reg (EQ, c4x_compare_op0, c4x_compare_op1);")
4217
4218 (define_expand "sne"
4219  [(set (match_operand:QI 0 "reg_operand" "")
4220        (const_int 0))
4221   (set (match_dup 0)
4222        (if_then_else:QI (ne (match_dup 1) (const_int 0))
4223                         (const_int 1)
4224                         (match_dup 0)))]
4225  ""
4226  "operands[1] = c4x_gen_compare_reg (NE, c4x_compare_op0, c4x_compare_op1);")
4227
4228 (define_expand "slt"
4229   [(set (match_operand:QI 0 "reg_operand" "")
4230         (const_int 0))
4231    (set (match_dup 0)
4232         (if_then_else:QI (lt (match_dup 1) (const_int 0))
4233                         (const_int 1)
4234                          (match_dup 0)))]
4235   ""
4236   "operands[1] = c4x_gen_compare_reg (LT, c4x_compare_op0, c4x_compare_op1);
4237    if (operands[1] == NULL_RTX) FAIL;")
4238
4239 (define_expand "sltu"
4240   [(set (match_operand:QI 0 "reg_operand" "")
4241         (const_int 0))
4242    (set (match_dup 0)
4243         (if_then_else:QI (ltu (match_dup 1) (const_int 0))
4244                         (const_int 1)
4245                          (match_dup 0)))]
4246   ""
4247   "operands[1] = c4x_gen_compare_reg (LTU, c4x_compare_op0, c4x_compare_op1);")
4248
4249 (define_expand "sgt"
4250   [(set (match_operand:QI 0 "reg_operand" "")
4251         (const_int 0))
4252    (set (match_dup 0)
4253         (if_then_else:QI (gt (match_dup 1) (const_int 0))
4254                         (const_int 1)
4255                          (match_dup 0)))]
4256   "" 
4257   "operands[1] = c4x_gen_compare_reg (GT, c4x_compare_op0, c4x_compare_op1);
4258    if (operands[1] == NULL_RTX) FAIL;")
4259
4260 (define_expand "sgtu"
4261   [(set (match_operand:QI 0 "reg_operand" "")
4262         (const_int 0))
4263    (set (match_dup 0)
4264         (if_then_else:QI (gtu (match_dup 1) (const_int 0))
4265                         (const_int 1)
4266                          (match_dup 0)))]
4267   ""
4268   "operands[1] = c4x_gen_compare_reg (GTU, c4x_compare_op0, c4x_compare_op1);")
4269
4270 (define_expand "sle"
4271   [(set (match_operand:QI 0 "reg_operand" "")
4272         (const_int 0))
4273    (set (match_dup 0)
4274         (if_then_else:QI (le (match_dup 1) (const_int 0))
4275                          (const_int 1)
4276                          (match_dup 0)))]
4277   ""
4278   "operands[1] = c4x_gen_compare_reg (LE, c4x_compare_op0, c4x_compare_op1);
4279    if (operands[1] == NULL_RTX) FAIL;")
4280
4281 (define_expand "sleu"
4282   [(set (match_operand:QI 0 "reg_operand" "")
4283         (const_int 0))
4284    (set (match_dup 0)
4285         (if_then_else:QI (leu (match_dup 1) (const_int 0))
4286                          (const_int 1)
4287                          (match_dup 0)))]
4288   ""
4289   "operands[1] = c4x_gen_compare_reg (LEU, c4x_compare_op0, c4x_compare_op1);")
4290
4291 (define_expand "sge"
4292   [(set (match_operand:QI 0 "reg_operand" "")
4293         (const_int 0))
4294    (set (match_dup 0)
4295         (if_then_else:QI (ge (match_dup 1) (const_int 0))
4296                          (const_int 1)
4297                          (match_dup 0)))]
4298   ""
4299   "operands[1] = c4x_gen_compare_reg (GE, c4x_compare_op0, c4x_compare_op1);
4300    if (operands[1] == NULL_RTX) FAIL;")
4301
4302 (define_expand "sgeu"
4303   [(set (match_operand:QI 0 "reg_operand" "")
4304         (const_int 0))
4305    (set (match_dup 0)
4306         (if_then_else:QI (geu (match_dup 1) (const_int 0))
4307                          (const_int 1)
4308                          (match_dup 0)))]
4309   ""
4310   "operands[1] = c4x_gen_compare_reg (GEU, c4x_compare_op0, c4x_compare_op1);")
4311
4312 (define_split
4313   [(set (match_operand:QI 0 "reg_operand" "")
4314         (match_operator:QI 1 "comparison_operator" [(reg:CC 21) (const_int 0)]))]
4315   "reload_completed"
4316   [(set (match_dup 0) (const_int 0))
4317    (set (match_dup 0)
4318         (if_then_else:QI (match_op_dup 1 [(reg:CC 21) (const_int 0)])
4319                         (const_int 1)
4320                          (match_dup 0)))]
4321   "")
4322
4323 (define_split
4324   [(set (match_operand:QI 0 "reg_operand" "")
4325         (match_operator:QI 1 "comparison_operator" [(reg:CC_NOOV 21) (const_int 0)]))]
4326   "reload_completed"
4327   [(set (match_dup 0) (const_int 0))
4328    (set (match_dup 0)
4329         (if_then_else:QI (match_op_dup 1 [(reg:CC_NOOV 21) (const_int 0)])
4330                          (const_int 1)
4331                          (match_dup 0)))]
4332   "")
4333
4334 (define_insn "*bu"
4335   [(set (pc)
4336         (unspec [(match_operand:QI 0 "reg_operand" "r")] 1))]
4337   ""
4338   "bu%#\\t%0"
4339   [(set_attr "type" "jump")])
4340
4341 (define_expand "caseqi"
4342   [(parallel [(set (match_dup 5)
4343                    (minus:QI (match_operand:QI 0 "reg_operand" "")
4344                              (match_operand:QI 1 "src_operand" "")))
4345               (clobber (reg:CC_NOOV 21))])
4346    (set (reg:CC 21)
4347         (compare:CC (match_dup 5)
4348                     (match_operand:QI 2 "src_operand" "")))
4349    (set (pc)
4350         (if_then_else (gtu (reg:CC 21)
4351                            (const_int 0))
4352                       (label_ref (match_operand 4 "" ""))
4353                       (pc)))
4354    (parallel [(set (match_dup 6)
4355                    (plus:QI (match_dup 5)
4356                             (label_ref:QI (match_operand 3 "" ""))))
4357               (clobber (reg:CC_NOOV 21))])
4358    (set (match_dup 7)
4359         (mem:QI (match_dup 6)))
4360    (set (pc) (match_dup 7))]
4361   ""
4362   "operands[5] = gen_reg_rtx (QImode);
4363    operands[6] = gen_reg_rtx (QImode);
4364    operands[7] = gen_reg_rtx (QImode);")
4365                 
4366 ;
4367 ; PARALLEL FLOAT INSTRUCTIONS
4368 ;
4369 ; This patterns are under development
4370
4371 ;
4372 ; ABSF/STF
4373 ;
4374
4375 (define_insn "*absqf2_movqf_clobber"
4376   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4377         (abs:QF (match_operand:QF 1 "par_ind_operand" "S<>")))
4378    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4379         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4380    (clobber (reg:CC_NOOV 21))]
4381   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4382   "absf\\t%1,%0\\n||\\tstf\\t%3,%2"
4383   [(set_attr "type" "binarycc")])
4384
4385 ;
4386 ; ADDF/STF
4387 ;
4388
4389 (define_insn "*addqf3_movqf_clobber"
4390   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q,q")
4391         (plus:QF (match_operand:QF 1 "parallel_operand" "%q,S<>")
4392                  (match_operand:QF 2 "parallel_operand" "S<>,q")))
4393    (set (match_operand:QF 3 "par_ind_operand" "=S<>,S<>")
4394         (match_operand:QF 4 "ext_low_reg_operand" "q,q"))
4395    (clobber (reg:CC 21))]
4396   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4397   "addf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4398   [(set_attr "type" "binarycc,binarycc")])
4399
4400 ;
4401 ; FLOAT/STF
4402 ;
4403
4404 (define_insn "*floatqiqf2_movqf_clobber"
4405   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4406         (float:QF (match_operand:QI 1 "par_ind_operand" "S<>")))
4407    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4408         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4409    (clobber (reg:CC 21))]
4410   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4411   "float\\t%1,%0\\n||\\tstf\\t%3,%2"
4412   [(set_attr "type" "binarycc")])
4413
4414 ;
4415 ; MPYF/ADDF
4416 ;
4417
4418 (define_insn "*mulqf3_addqf3_clobber"
4419   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t,t,t,t")
4420         (mult:QF (match_operand:QF 1 "parallel_operand" "%S<>!V,q,S<>!V,q")
4421                  (match_operand:QF 2 "parallel_operand" "q,S<>!V,S<>!V,q")))
4422    (set (match_operand:QF 3 "r2r3_reg_operand" "=u,u,u,u")
4423         (plus:QF (match_operand:QF 4 "parallel_operand" "%S<>!V,q,q,S<>!V")
4424                  (match_operand:QF 5 "parallel_operand" "q,S<>!V,q,S<>!V")))
4425    (clobber (reg:CC_NOOV 21))]
4426   "TARGET_PARALLEL_MPY && valid_parallel_operands_6 (operands, QFmode)"
4427   "mpyf3\\t%2,%1,%0\\n||\\taddf3\\t%5,%4,%3"
4428   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4429
4430
4431 ;
4432 ; MPYF/STF
4433 ;
4434
4435 (define_insn "*mulqf3_movqf_clobber"
4436   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q,q")
4437         (mult:QF (match_operand:QF 1 "parallel_operand" "%q,S<>")
4438                  (match_operand:QF 2 "parallel_operand" "S<>,q")))
4439    (set (match_operand:QF 3 "par_ind_operand" "=S<>,S<>")
4440         (match_operand:QF 4 "ext_low_reg_operand" "q,q"))
4441    (clobber (reg:CC 21))]
4442   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4443   "mpyf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4444   [(set_attr "type" "binarycc,binarycc")])
4445
4446 ;
4447 ; MPYF/SUBF
4448 ;
4449
4450 (define_insn "*mulqf3_subqf3_clobber"
4451   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t,t")
4452         (mult:QF (match_operand:QF 1 "parallel_operand" "S<>,q")
4453                  (match_operand:QF 2 "parallel_operand" "q,S<>")))
4454    (set (match_operand:QF 3 "r2r3_reg_operand" "=u,u")
4455         (minus:QF (match_operand:QF 4 "parallel_operand" "S<>,q")
4456                   (match_operand:QF 5 "parallel_operand" "q,S<>")))
4457    (clobber (reg:CC 21))]
4458   "TARGET_PARALLEL_MPY && valid_parallel_operands_6 (operands, QFmode)"
4459   "mpyf3\\t%2,%1,%0\\n||\\tsubf3\\t%5,%4,%3"
4460   [(set_attr "type" "binarycc,binarycc")])
4461
4462 ;
4463 ; MPYF/LDF 0
4464 ;
4465
4466 (define_insn "*mulqf3_clrqf_clobber"
4467   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t")
4468         (mult:QF (match_operand:QF 1 "par_ind_operand" "%S<>")
4469                  (match_operand:QF 2 "par_ind_operand" "S<>")))
4470    (set (match_operand:QF 3 "r2r3_reg_operand" "=u")
4471         (match_operand:QF 4 "fp_zero_operand" "G"))
4472    (clobber (reg:CC 21))]
4473   "TARGET_PARALLEL_MPY"
4474   "mpyf3\\t%2,%1,%0\\n||\\tsubf3\\t%3,%3,%3"
4475   [(set_attr "type" "binarycc")])
4476
4477 ;
4478 ; NEGF/STF
4479 ;
4480
4481 (define_insn "*negqf2_movqf_clobber"
4482   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4483         (neg:QF (match_operand:QF 1 "par_ind_operand" "S<>")))
4484    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4485         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4486    (clobber (reg:CC 21))]
4487   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4488   "negf\\t%1,%0\\n||\\tstf\\t%3,%2"
4489   [(set_attr "type" "binarycc")])
4490
4491 ;
4492 ; SUBF/STF
4493 ;
4494
4495 (define_insn "*subqf3_movqf_clobber"
4496   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4497         (minus:QF (match_operand:QF 1 "ext_low_reg_operand" "q")
4498                   (match_operand:QF 2 "par_ind_operand" "S<>")))
4499    (set (match_operand:QF 3 "par_ind_operand" "=S<>")
4500         (match_operand:QF 4 "ext_low_reg_operand" "q"))
4501    (clobber (reg:CC 21))]
4502   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4503   "subf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4504   [(set_attr "type" "binarycc")])
4505
4506 ;
4507 ; PARALLEL INTEGER INSTRUCTIONS
4508 ;
4509
4510 ;
4511 ; ABSI/STI
4512 ;
4513
4514 (define_insn "*absqi2_movqi_clobber"
4515   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4516         (abs:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4517    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4518         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4519    (clobber (reg:CC_NOOV 21))]
4520   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4521   "absi\\t%1,%0\\n||\\tsti\\t%3,%2"
4522   [(set_attr "type" "binarycc")])
4523
4524 ;
4525 ; ADDI/STI
4526 ;
4527
4528 (define_insn "*addqi3_movqi_clobber"
4529   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4530         (plus:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4531                  (match_operand:QI 2 "parallel_operand" "S<>,q")))
4532    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4533         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4534    (clobber (reg:CC 21))]
4535   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4536   "addi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4537   [(set_attr "type" "binarycc,binarycc")])
4538
4539 ;
4540 ; AND/STI
4541 ;
4542
4543 (define_insn "*andqi3_movqi_clobber"
4544   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4545         (and:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4546                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4547    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4548         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4549    (clobber (reg:CC 21))]
4550   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4551   "and3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4552   [(set_attr "type" "binarycc,binarycc")])
4553
4554 ;
4555 ; ASH(left)/STI 
4556 ;
4557
4558 (define_insn "*ashlqi3_movqi_clobber"
4559   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4560         (ashift:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4561                    (match_operand:QI 2 "ext_low_reg_operand" "q")))
4562    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4563         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4564    (clobber (reg:CC 21))]
4565   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4566   "ash3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4567   [(set_attr "type" "binarycc")])
4568
4569 ;
4570 ; ASH(right)/STI 
4571 ;
4572
4573 (define_insn "*ashrqi3_movqi_clobber"
4574   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4575         (ashiftrt:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4576                      (neg:QI (match_operand:QI 2 "ext_low_reg_operand" "q"))))
4577    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4578         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4579    (clobber (reg:CC 21))]
4580   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4581   "ash3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4582   [(set_attr "type" "binarycc")])
4583
4584 ;
4585 ; FIX/STI
4586 ;
4587
4588 (define_insn "*fixqfqi2_movqi_clobber"
4589   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4590         (fix:QI (match_operand:QF 1 "par_ind_operand" "S<>")))
4591    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4592         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4593    (clobber (reg:CC 21))]
4594   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4595   "fix\\t%1,%0\\n||\\tsti\\t%3,%2"
4596   [(set_attr "type" "binarycc")])
4597
4598 ;
4599 ; LSH(right)/STI 
4600 ;
4601
4602 (define_insn "*lshrqi3_movqi_clobber"
4603   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4604         (lshiftrt:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4605                      (neg:QI (match_operand:QI 2 "ext_low_reg_operand" "q"))))
4606    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4607         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4608    (clobber (reg:CC 21))]
4609   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4610   "lsh3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4611   [(set_attr "type" "binarycc")])
4612
4613 ;
4614 ; MPYI/ADDI
4615 ;
4616
4617 (define_insn "*mulqi3_addqi3_clobber"
4618   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t,t,t,t")
4619         (mult:QI (match_operand:QI 1 "parallel_operand" "%S<>!V,q,S<>!V,q")
4620                  (match_operand:QI 2 "parallel_operand" "q,S<>!V,S<>!V,q")))
4621    (set (match_operand:QI 3 "r2r3_reg_operand" "=u,u,u,u")
4622         (plus:QI (match_operand:QI 4 "parallel_operand" "%S<>!V,q,q,S<>!V")
4623                  (match_operand:QI 5 "parallel_operand" "q,S<>!V,q,S<>!V")))
4624    (clobber (reg:CC 21))]
4625   "TARGET_PARALLEL_MPY && TARGET_MPYI 
4626    && valid_parallel_operands_6 (operands, QImode)"
4627   "mpyi3\\t%2,%1,%0\\n||\\taddi3\\t%5,%4,%3"
4628   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4629
4630
4631 ;
4632 ; MPYI/STI
4633 ;
4634
4635 (define_insn "*mulqi3_movqi_clobber"
4636   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4637         (mult:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4638                  (match_operand:QI 2 "parallel_operand" "S<>,q")))
4639    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4640         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4641    (clobber (reg:CC 21))]
4642   "TARGET_PARALLEL && TARGET_MPYI
4643    && valid_parallel_operands_5 (operands, QImode)"
4644   "mpyi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4645   [(set_attr "type" "binarycc,binarycc")])
4646
4647 ;
4648 ; MPYI/SUBI
4649 ;
4650
4651 (define_insn "*mulqi3_subqi3_clobber"
4652   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t,t")
4653         (mult:QI (match_operand:QI 1 "parallel_operand" "S<>,q")
4654                  (match_operand:QI 2 "parallel_operand" "q,S<>")))
4655    (set (match_operand:QI 3 "r2r3_reg_operand" "=u,u")
4656         (minus:QI (match_operand:QI 4 "parallel_operand" "S<>,q")
4657                   (match_operand:QI 5 "parallel_operand" "q,S<>")))
4658    (clobber (reg:CC 21))]
4659   "TARGET_PARALLEL_MPY && TARGET_MPYI
4660    && valid_parallel_operands_6 (operands, QImode)"
4661   "mpyi3\\t%2,%1,%0\\n||\\tsubi3\\t%5,%4,%3"
4662   [(set_attr "type" "binarycc,binarycc")])
4663
4664 ;
4665 ; MPYI/LDI 0
4666 ;
4667
4668 (define_insn "*mulqi3_clrqi_clobber"
4669   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t")
4670         (mult:QI (match_operand:QI 1 "par_ind_operand" "%S<>")
4671                  (match_operand:QI 2 "par_ind_operand" "S<>")))
4672    (set (match_operand:QI 3 "r2r3_reg_operand" "=u")
4673         (const_int 0))
4674    (clobber (reg:CC 21))]
4675   "TARGET_PARALLEL_MPY && TARGET_MPYI"
4676   "mpyi3\\t%2,%1,%0\\n||\\tsubi3\\t%3,%3,%3"
4677   [(set_attr "type" "binarycc")])
4678
4679 ;
4680 ; NEGI/STI
4681 ;
4682
4683 (define_insn "*negqi2_movqi_clobber"
4684   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4685         (neg:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4686    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4687         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4688    (clobber (reg:CC 21))]
4689   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4690   "negi\\t%1,%0\\n||\\tsti\\t%3,%2"
4691   [(set_attr "type" "binarycc")])
4692
4693 ;
4694 ; NOT/STI
4695 ;
4696
4697 (define_insn "*notqi2_movqi_clobber"
4698   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4699         (not:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4700    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4701         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4702    (clobber (reg:CC 21))]
4703   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4704   "not\\t%1,%0\\n||\\tsti\\t%3,%2"
4705   [(set_attr "type" "binarycc")])
4706
4707 ;
4708 ; OR/STI
4709 ;
4710
4711 (define_insn "*iorqi3_movqi_clobber"
4712   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4713         (ior:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4714                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4715    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4716         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4717    (clobber (reg:CC 21))]
4718   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4719   "or3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4720   [(set_attr "type" "binarycc,binarycc")])
4721
4722 ;
4723 ; SUBI/STI
4724 ;
4725
4726 (define_insn "*subqi3_movqi_clobber"
4727   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4728         (minus:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4729                   (match_operand:QI 2 "ext_low_reg_operand" "q")))
4730    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4731         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4732    (clobber (reg:CC 21))]
4733   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4734   "subi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4735   [(set_attr "type" "binarycc")])
4736
4737 ;
4738 ; XOR/STI
4739 ;
4740
4741 (define_insn "*xorqi3_movqi_clobber"
4742   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4743         (xor:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4744                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4745    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4746         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4747    (clobber (reg:CC 21))]
4748   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4749   "xor3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4750   [(set_attr "type" "binarycc,binarycc")])
4751
4752 ;
4753 ; BRANCH/CALL INSTRUCTIONS
4754 ;
4755
4756 ;
4757 ; Branch instructions
4758 ;
4759 (define_insn "*b"
4760   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4761                            [(reg:CC 21) (const_int 0)])
4762                            (label_ref (match_operand 1 "" ""))
4763                            (pc)))]
4764   ""
4765   "*
4766    return c4x_output_cbranch (\"b%0\", insn);"
4767   [(set_attr "type" "jmpc")])
4768
4769 (define_insn "*b_rev"
4770   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4771                            [(reg:CC 21) (const_int 0)])
4772                            (pc)
4773                            (label_ref (match_operand 1 "" ""))))]
4774   ""
4775   "*
4776    return c4x_output_cbranch (\"b%I0\", insn);"
4777   [(set_attr "type" "jmpc")])
4778
4779 (define_insn "*b_noov"
4780   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4781                            [(reg:CC_NOOV 21) (const_int 0)])
4782                            (label_ref (match_operand 1 "" ""))
4783                            (pc)))]
4784  "GET_CODE (operands[0]) != LE
4785   && GET_CODE (operands[0]) != GE
4786   && GET_CODE (operands[0]) != LT
4787   && GET_CODE (operands[0]) != GT"
4788   "*
4789    return c4x_output_cbranch (\"b%0\", insn);"
4790   [(set_attr "type" "jmpc")])
4791
4792 (define_insn "*b_noov_rev"
4793   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4794                            [(reg:CC_NOOV 21) (const_int 0)])
4795                            (pc)
4796                            (label_ref (match_operand 1 "" ""))))]
4797  "GET_CODE (operands[0]) != LE
4798   && GET_CODE (operands[0]) != GE
4799   && GET_CODE (operands[0]) != LT
4800   && GET_CODE (operands[0]) != GT"
4801   "*
4802    return c4x_output_cbranch (\"b%I0\", insn);"
4803   [(set_attr "type" "jmpc")])
4804
4805 (define_expand "beq"
4806   [(set (pc) (if_then_else (eq (match_dup 1) (const_int 0))
4807                            (label_ref (match_operand 0 "" ""))
4808                            (pc)))]
4809   ""
4810   "operands[1] = c4x_gen_compare_reg (EQ, c4x_compare_op0, c4x_compare_op1);")
4811
4812 (define_expand "bne"
4813   [(set (pc) (if_then_else (ne (match_dup 1) (const_int 0))
4814                            (label_ref (match_operand 0 "" ""))
4815                            (pc)))]
4816   ""
4817   "operands[1] = c4x_gen_compare_reg (NE, c4x_compare_op0, c4x_compare_op1);")
4818
4819 (define_expand "blt"
4820   [(set (pc) (if_then_else (lt (match_dup 1) (const_int 0))
4821                            (label_ref (match_operand 0 "" ""))
4822                            (pc)))]
4823   ""
4824   "operands[1] = c4x_gen_compare_reg (LT, c4x_compare_op0, c4x_compare_op1);
4825    if (operands[1] == NULL_RTX) FAIL;")
4826
4827 (define_expand "bltu"
4828   [(set (pc) (if_then_else (ltu (match_dup 1) (const_int 0))
4829                            (label_ref (match_operand 0 "" ""))
4830                            (pc)))]
4831   ""
4832   "operands[1] = c4x_gen_compare_reg (LTU, c4x_compare_op0, c4x_compare_op1);")
4833
4834 (define_expand "bgt"
4835   [(set (pc) (if_then_else (gt (match_dup 1) (const_int 0))
4836                            (label_ref (match_operand 0 "" ""))
4837                            (pc)))]
4838   ""
4839   "operands[1] = c4x_gen_compare_reg (GT, c4x_compare_op0, c4x_compare_op1);
4840    if (operands[1] == NULL_RTX) FAIL;")
4841
4842 (define_expand "bgtu"
4843   [(set (pc) (if_then_else (gtu (match_dup 1) (const_int 0))
4844                            (label_ref (match_operand 0 "" ""))
4845                            (pc)))]
4846   ""
4847   "operands[1] = c4x_gen_compare_reg (GTU, c4x_compare_op0, c4x_compare_op1);")
4848
4849 (define_expand "ble"
4850   [(set (pc) (if_then_else (le (match_dup 1) (const_int 0))
4851                            (label_ref (match_operand 0 "" ""))
4852                            (pc)))]
4853   ""
4854   "operands[1] = c4x_gen_compare_reg (LE, c4x_compare_op0, c4x_compare_op1);
4855    if (operands[1] == NULL_RTX) FAIL;")
4856
4857 (define_expand "bleu"
4858   [(set (pc) (if_then_else (leu (match_dup 1) (const_int 0))
4859                            (label_ref (match_operand 0 "" ""))
4860                            (pc)))]
4861   ""
4862   "operands[1] = c4x_gen_compare_reg (LEU, c4x_compare_op0, c4x_compare_op1);")
4863
4864 (define_expand "bge"
4865   [(set (pc) (if_then_else (ge (match_dup 1) (const_int 0))
4866                            (label_ref (match_operand 0 "" ""))
4867                            (pc)))]
4868   ""
4869   "operands[1] = c4x_gen_compare_reg (GE, c4x_compare_op0, c4x_compare_op1);
4870    if (operands[1] == NULL_RTX) FAIL;")
4871
4872 (define_expand "bgeu"
4873   [(set (pc) (if_then_else (geu (match_dup 1) (const_int 0))
4874                            (label_ref (match_operand 0 "" ""))
4875                            (pc)))]
4876   ""
4877   "operands[1] = c4x_gen_compare_reg (GEU, c4x_compare_op0, c4x_compare_op1);")
4878
4879 (define_insn "*b_reg"
4880  [(set (pc) (match_operand:QI 0 "reg_operand" "r"))]
4881  ""
4882  "bu%#\\t%0"
4883   [(set_attr "type" "jump")])
4884
4885 (define_expand "indirect_jump"
4886  [(set (pc) (match_operand:QI 0 "reg_operand" ""))]
4887  ""
4888  "")
4889
4890 (define_insn "tablejump"
4891   [(set (pc) (match_operand:QI 0 "src_operand" "r"))
4892    (use (label_ref (match_operand 1 "" "")))]
4893   ""
4894   "bu%#\\t%0"
4895   [(set_attr "type" "jump")])
4896
4897 ;
4898 ; CALL
4899 ;
4900 (define_insn "*call_c3x"
4901  [(call (mem:QI (match_operand:QI 0 "call_address_operand" "Ur"))
4902         (match_operand:QI 1 "general_operand" ""))
4903   (clobber (reg:QI 31))]
4904   ;; Operand 1 not really used on the C4x.  The C30 doesn't have reg 31.
4905
4906   "TARGET_C3X"
4907   "call%U0\\t%C0"
4908   [(set_attr "type" "call")])
4909
4910 ; LAJ requires R11 (31) for the return address
4911 (define_insn "*laj"
4912  [(call (mem:QI (match_operand:QI 0 "call_address_operand" "Ur"))
4913         (match_operand:QI 1 "general_operand" ""))
4914   (clobber (reg:QI 31))]
4915   ;; Operand 1 not really used on the C4x.
4916
4917   "! TARGET_C3X"
4918   "*
4919    if (final_sequence)
4920      return \"laj%U0\\t%C0\";
4921    else
4922      return \"call%U0\\t%C0\";"
4923   [(set_attr "type" "laj")])
4924
4925 (define_expand "call"
4926  [(parallel [(call (match_operand:QI 0 "" "")
4927                    (match_operand:QI 1 "general_operand" ""))
4928              (clobber (reg:QI 31))])]
4929  ""
4930  "
4931 {
4932   if (GET_CODE (operands[0]) == MEM
4933       && ! call_address_operand (XEXP (operands[0], 0), Pmode))
4934     operands[0] = gen_rtx_MEM (GET_MODE (operands[0]),
4935                                force_reg (Pmode, XEXP (operands[0], 0)));
4936 }")
4937
4938 (define_insn "*callv_c3x"
4939  [(set (match_operand 0 "" "=r")
4940        (call (mem:QI (match_operand:QI 1 "call_address_operand" "Ur"))
4941              (match_operand:QI 2 "general_operand" "")))
4942   (clobber (reg:QI 31))]
4943   ;; Operand 0 and 2 not really used for the C4x. 
4944   ;; The C30 doesn't have reg 31.
4945
4946   "TARGET_C3X"
4947   "call%U1\\t%C1"
4948   [(set_attr "type" "call")])
4949
4950 ; LAJ requires R11 (31) for the return address
4951 (define_insn "*lajv"
4952  [(set (match_operand 0 "" "=r")
4953        (call (mem:QI (match_operand:QI 1 "call_address_operand" "Ur"))
4954              (match_operand:QI 2 "general_operand" "")))
4955   (clobber (reg:QI 31))]
4956   ;; Operand 0 and 2 not really used in the C30 instruction.
4957
4958   "! TARGET_C3X"
4959   "*
4960    if (final_sequence)
4961      return \"laj%U1\\t%C1\";
4962    else
4963      return \"call%U1\\t%C1\";"
4964   [(set_attr "type" "laj")])
4965
4966 (define_expand "call_value"
4967  [(parallel [(set (match_operand 0 "" "")
4968                   (call (match_operand:QI 1 "" "")
4969                         (match_operand:QI 2 "general_operand" "")))
4970              (clobber (reg:QI 31))])]
4971  ""
4972  "
4973 {
4974   if (GET_CODE (operands[0]) == MEM
4975       && ! call_address_operand (XEXP (operands[1], 0), Pmode))
4976     operands[0] = gen_rtx_MEM (GET_MODE (operands[1]),
4977                                force_reg (Pmode, XEXP (operands[1], 0)));
4978 }")
4979
4980 (define_insn "return"
4981   [(return)]
4982   "c4x_null_epilogue_p ()"
4983   "rets"
4984   [(set_attr "type" "rets")])
4985
4986 (define_insn "*return_cc"
4987   [(set (pc)
4988         (if_then_else (match_operator 0 "comparison_operator"
4989                       [(reg:CC 21) (const_int 0)])
4990                       (return)
4991                        (pc)))]
4992   "c4x_null_epilogue_p ()"
4993   "rets%0"
4994   [(set_attr "type" "rets")])
4995
4996 (define_insn "*return_cc_noov"
4997   [(set (pc)
4998         (if_then_else (match_operator 0 "comparison_operator"
4999                       [(reg:CC_NOOV 21) (const_int 0)])
5000                       (return)
5001                        (pc)))]
5002   "GET_CODE (operands[0]) != LE
5003    && GET_CODE (operands[0]) != GE
5004    && GET_CODE (operands[0]) != LT
5005    && GET_CODE (operands[0]) != GT
5006    && c4x_null_epilogue_p ()"
5007   "rets%0"
5008   [(set_attr "type" "rets")])
5009
5010 (define_insn "*return_cc_inverse"
5011   [(set (pc)
5012         (if_then_else (match_operator 0 "comparison_operator"
5013                       [(reg:CC 21) (const_int 0)])
5014                        (pc)
5015                       (return)))]
5016   "c4x_null_epilogue_p ()"
5017   "rets%I0"
5018   [(set_attr "type" "rets")])
5019
5020 (define_insn "*return_cc_noov_inverse"
5021   [(set (pc)
5022         (if_then_else (match_operator 0 "comparison_operator"
5023                       [(reg:CC_NOOV 21) (const_int 0)])
5024                        (pc)
5025                       (return)))]
5026   "GET_CODE (operands[0]) != LE
5027    && GET_CODE (operands[0]) != GE
5028    && GET_CODE (operands[0]) != LT
5029    && GET_CODE (operands[0]) != GT
5030    && c4x_null_epilogue_p ()"
5031   "rets%I0"
5032   [(set_attr "type" "rets")])
5033
5034 (define_insn "jump"
5035   [(set (pc) (label_ref (match_operand 0 "" "")))]
5036   ""
5037   "br%#\\t%l0"
5038   [(set_attr "type" "jump")])
5039
5040 ;
5041 ; DBcond
5042 ;
5043 ; Note we have to emit a dbu instruction if there are no delay slots
5044 ; to fill.
5045 ; Also note that GCC will try to reverse a loop to see if it can
5046 ; utilise this instruction.  However, if there are more than one
5047 ; memory reference in the loop, it cannot guarantee that reversing
5048 ; the loop will work :(  (see check_dbra_loop() in loop.c)
5049 ; Note that the C3x only decrements the 24 LSBs of the address register
5050 ; and the 8 MSBs are untouched.  The C4x uses all 32-bits.  We thus
5051 ; have an option to disable this instruction.
5052 (define_insn "*db"
5053   [(set (pc)
5054         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
5055                           (const_int 0))
5056                       (label_ref (match_operand 1 "" ""))
5057                       (pc)))
5058    (set (match_dup 0)
5059         (plus:QI (match_dup 0)
5060                  (const_int -1)))
5061    (clobber (reg:CC_NOOV 21))]
5062   "TARGET_DB && TARGET_LOOP_UNSIGNED"
5063   "*
5064   if (which_alternative == 0)
5065     return \"dbu%#\\t%0,%l1\";
5066   else if (which_alternative == 1)
5067     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5068   else if (which_alternative == 2)
5069     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5070   else
5071     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);
5072   "
5073   [(set_attr "type" "db,jmpc,jmpc,jmpc")])
5074
5075 (define_insn "*db_noclobber"
5076   [(set (pc)
5077         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "+a")
5078                           (const_int 0))
5079                       (label_ref (match_operand 1 "" ""))
5080                       (pc)))
5081    (set (match_dup 0)
5082         (plus:QI (match_dup 0)
5083                  (const_int -1)))]
5084   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5085   "dbu%#\\t%0,%l1"
5086   [(set_attr "type" "db")])
5087
5088 (define_split
5089   [(set (pc)
5090         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "")
5091                           (const_int 0))
5092                       (label_ref (match_operand 1 "" ""))
5093                       (pc)))
5094    (set (match_dup 0)
5095         (plus:QI (match_dup 0)
5096                  (const_int -1)))
5097    (clobber (reg:CC_NOOV 21))]
5098   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5099   [(parallel [(set (pc)
5100                    (if_then_else (ne (match_dup 0)
5101                                      (const_int 0))
5102                                  (label_ref (match_dup 1))
5103                                  (pc)))
5104               (set (match_dup 0)
5105                    (plus:QI (match_dup 0)
5106                             (const_int -1)))])]
5107   "")
5108   
5109
5110 ; This insn is used for some loop tests, typically loops reversed when
5111 ; strength reduction is used.  It is actually created when the instruction
5112 ; combination phase combines the special loop test.  Since this insn
5113 ; is both a jump insn and has an output, it must deal with its own
5114 ; reloads, hence the `m' constraints. 
5115
5116 ; The C4x does the decrement and then compares the result against zero.
5117 ; It branches if the result was greater than or equal to zero.
5118 ; In the RTL the comparison and decrement are assumed to happen
5119 ; at the same time so we bias the iteration counter with by -1
5120 ; when we make the test.
5121 (define_insn "decrement_and_branch_until_zero"
5122   [(set (pc)
5123         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
5124                                    (const_int -1))
5125                           (const_int 0))
5126                       (label_ref (match_operand 1 "" ""))
5127                       (pc)))
5128    (set (match_dup 0)
5129         (plus:QI (match_dup 0)
5130                  (const_int -1)))
5131    (clobber (reg:CC_NOOV 21))]
5132   "TARGET_DB && (find_reg_note (insn, REG_NONNEG, 0) || TARGET_LOOP_UNSIGNED)"
5133   "*
5134   if (which_alternative == 0)
5135     return \"dbu%#\\t%0,%l1\";
5136   else if (which_alternative == 1)
5137     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5138   else if (which_alternative == 2)
5139     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5140   else
5141     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);
5142   "
5143   [(set_attr "type" "db,jmpc,jmpc,jmpc")])
5144
5145 (define_insn "*decrement_and_branch_until_zero_noclobber"
5146   [(set (pc)
5147         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a")
5148                                    (const_int -1))
5149                           (const_int 0))
5150                       (label_ref (match_operand 1 "" ""))
5151                       (pc)))
5152    (set (match_dup 0)
5153         (plus:QI (match_dup 0)
5154                  (const_int -1)))]
5155   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5156   "dbu%#\\t%0,%l1"
5157   [(set_attr "type" "db")])
5158
5159 (define_split
5160   [(set (pc)
5161         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "")
5162                                    (const_int -1))
5163                           (const_int 0))
5164                       (label_ref (match_operand 1 "" ""))
5165                       (pc)))
5166    (set (match_dup 0)
5167         (plus:QI (match_dup 0)
5168                  (const_int -1)))
5169    (clobber (reg:CC_NOOV 21))]
5170   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5171   [(parallel [(set (pc)
5172                    (if_then_else (ge (plus:QI (match_dup 0)
5173                                               (const_int -1))
5174                                      (const_int 0))
5175                                  (label_ref (match_dup 1))
5176                                  (pc)))
5177               (set (match_dup 0)
5178                    (plus:QI (match_dup 0)
5179                             (const_int -1)))])]
5180   "")
5181
5182 ;
5183 ; MISC INSTRUCTIONS
5184 ;
5185
5186 ;
5187 ; NOP
5188 ;
5189 (define_insn "nop"
5190   [(const_int 0)]
5191   ""
5192   "nop")
5193 ; Default to misc type attr.
5194
5195
5196 ;
5197 ; RPTB
5198 ;
5199 (define_insn "rptb_top"
5200   [(use (label_ref (match_operand 0 "" "")))
5201    (use (label_ref (match_operand 1 "" "")))
5202    (clobber (reg:QI 25))
5203    (clobber (reg:QI 26))]
5204   ""
5205   "*
5206    return ! final_sequence && c4x_rptb_rpts_p (insn, operands[0])
5207          ? \"rpts\\trc\" : \"rptb%#\\t%l1-1\";
5208   "
5209   [(set_attr "type" "repeat_top")])
5210
5211 (define_insn "rpts_top"
5212   [(unspec [(use (label_ref (match_operand 0 "" "")))
5213             (use (label_ref (match_operand 1 "" "")))] 2)
5214    (clobber (reg:QI 25))
5215    (clobber (reg:QI 26))]
5216   ""
5217   "*
5218    return ! final_sequence && c4x_rptb_rpts_p (insn, operands[0])
5219          ? \"rpts\\trc\" : \"rptb%#\\t%l1-1\";
5220   "
5221   [(set_attr "type" "repeat")])
5222
5223 ; This pattern needs to be emitted at the start of the loop to
5224 ; say that RS and RE are loaded.
5225 (define_insn "rptb_init"
5226   [(unspec [(match_operand:QI 0 "register_operand" "va")] 22)
5227    (clobber (reg:QI 25))
5228    (clobber (reg:QI 26))]
5229   ""
5230   ""
5231   [(set_attr "type" "repeat")])
5232
5233
5234 ; operand 0 is the loop count pseudo register
5235 ; operand 1 is the number of loop iterations or 0 if it is unknown
5236 ; operand 2 is the maximum number of loop iterations
5237 ; operand 3 is the number of levels of enclosed loops
5238 (define_expand "doloop_begin"
5239   [(use (match_operand 0 "register_operand" ""))
5240    (use (match_operand:QI 1 "const_int_operand" ""))
5241    (use (match_operand:QI 2 "const_int_operand" ""))
5242    (use (match_operand:QI 3 "const_int_operand" ""))]
5243   ""
5244   "if (INTVAL (operands[3]) > 1 || ! TARGET_RPTB)
5245      FAIL;
5246    emit_insn (gen_rptb_init (operands[0]));
5247    DONE;
5248   ")
5249
5250
5251 ; The RS (25) and RE (26) registers must be unviolate from the top of the loop
5252 ; to here.
5253 (define_insn "rptb_end"
5254   [(set (pc)
5255         (if_then_else (ge (match_operand:QI 0 "register_operand" "+v,?a,!*d,!*x*k,!m")
5256                           (const_int 0))
5257                       (label_ref (match_operand 1 "" ""))
5258                       (pc)))
5259    (set (match_dup 0)
5260         (plus:QI (match_dup 0)
5261                  (const_int -1)))
5262    (use (reg:QI 25))
5263    (use (reg:QI 26))
5264    (clobber (reg:CC_NOOV 21))]
5265   ""
5266   "*
5267    if (which_alternative == 0)
5268      return c4x_rptb_nop_p (insn) ? \"nop\" : \"\";
5269    else if (which_alternative == 1 && TARGET_DB)
5270      return \"dbu%#\\t%0,%l1\";
5271    else if (which_alternative == 2)
5272      return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5273    else if (which_alternative == 3 || (which_alternative == 1 && ! TARGET_DB))
5274      return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5275    else
5276      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);
5277   "
5278   [(set_attr "type" "repeat,db,jmpc,jmpc,jmpc")])
5279
5280 (define_split
5281    [(set (pc)
5282         (if_then_else (ge (match_operand:QI 0 "addr_reg_operand" "")
5283                           (const_int 0))
5284                       (label_ref (match_operand 1 "" ""))
5285                       (pc)))
5286    (set (match_dup 0)
5287         (plus:QI (match_dup 0)
5288                  (const_int -1)))
5289    (use (match_operand:QI 2 "const_int_operand" ""))
5290    (use (match_operand:QI 3 "const_int_operand" ""))
5291    (use (match_operand:QI 4 "const_int_operand" ""))
5292    (use (reg:QI 25))
5293    (use (reg:QI 26))
5294    (clobber (reg:CC_NOOV 21))]
5295   "reload_completed"
5296   [(parallel [(set (pc)
5297                    (if_then_else (ge (match_dup 0)
5298                                      (const_int 0))
5299                                  (label_ref (match_dup 1))
5300                                  (pc)))
5301               (set (match_dup 0)
5302                    (plus:QI (match_dup 0)
5303                             (const_int -1)))])]
5304   "")
5305
5306 ; operand 0 is the loop count pseudo register
5307 ; operand 1 is the number of loop iterations or 0 if it is unknown
5308 ; operand 2 is the maximum number of loop iterations
5309 ; operand 3 is the number of levels of enclosed loops
5310 ; operand 4 is the label to jump to at the top of the loop
5311 (define_expand "doloop_end"
5312   [(use (match_operand 0 "register_operand" ""))
5313    (use (match_operand:QI 1 "const_int_operand" ""))
5314    (use (match_operand:QI 2 "const_int_operand" ""))
5315    (use (match_operand:QI 3 "const_int_operand" ""))
5316    (use (label_ref (match_operand 4 "" "")))]
5317   ""
5318   "if (! TARGET_LOOP_UNSIGNED 
5319        && (unsigned HOST_WIDE_INT) INTVAL (operands[2]) > (1U << 31))
5320      FAIL;
5321    if (INTVAL (operands[3]) > 1 || ! TARGET_RPTB)
5322      {
5323         /* The C30 maximum iteration count for DB is 2^24.  */
5324         if (! TARGET_DB)
5325           FAIL;
5326         emit_jump_insn (gen_decrement_and_branch_until_zero (operands[0],
5327                                                              operands[4]));
5328         DONE;
5329      }
5330     emit_jump_insn (gen_rptb_end (operands[0], operands[4]));
5331     DONE;
5332   ")
5333
5334 ; The current low overhead looping code is naff and is not failsafe
5335 ; If you want RTPB instructions to be generated, apply the patches
5336 ; from www.elec.canterbury.ac.nz/c4x.  This will utilise the
5337 ; doloop_begin and doloop_end patterns in this MD.
5338 (define_expand "decrement_and_branch_on_count"
5339   [(parallel [(set (pc)
5340                    (if_then_else (ge (match_operand:QI 0 "register_operand" "")
5341                                      (const_int 0))
5342                                  (label_ref (match_operand 1 "" ""))
5343                                  (pc)))
5344               (set (match_dup 0)
5345                    (plus:QI (match_dup 0)
5346                             (const_int -1)))
5347               (use (reg:QI 25))
5348               (use (reg:QI 26))
5349               (clobber (reg:CC_NOOV 21))])]
5350   "0"
5351   "")
5352
5353 (define_expand "movstrqi_small2"
5354   [(parallel [(set (mem:BLK (match_operand:BLK 0 "src_operand" ""))
5355                    (mem:BLK (match_operand:BLK 1 "src_operand" "")))
5356               (use (match_operand:QI 2 "immediate_operand" ""))
5357               (use (match_operand:QI 3 "immediate_operand" ""))
5358               (clobber (match_operand:QI 4 "ext_low_reg_operand" ""))])]
5359   ""
5360   "
5361  {
5362     rtx src, dst, tmp;
5363     rtx src_mem, dst_mem;    
5364     int len;
5365     int i;
5366
5367     dst = operands[0];
5368     src = operands[1];
5369     len = INTVAL (operands[2]);
5370     tmp = operands[4];
5371
5372     src_mem = gen_rtx_MEM (QImode, src);
5373     dst_mem = gen_rtx_MEM (QImode, dst);
5374
5375     if (TARGET_PARALLEL)
5376       {
5377         emit_insn (gen_movqi (tmp, src_mem));   
5378         emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));        
5379         for (i = 1; i < len; i++)
5380           {
5381             emit_insn (gen_movqi_parallel (tmp, src_mem, dst_mem, tmp));
5382             emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));    
5383             emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));    
5384           }
5385         emit_insn (gen_movqi (dst_mem, tmp));   
5386         emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));        
5387       }
5388     else
5389       {
5390         for (i = 0; i < len; i++)
5391           {
5392             emit_insn (gen_movqi (tmp, src_mem));       
5393             emit_insn (gen_movqi (dst_mem, tmp));       
5394             emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));    
5395             emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));    
5396           }
5397       }
5398     DONE;
5399   }
5400   ")
5401
5402
5403 ;
5404 ; BLOCK MOVE
5405 ; We should probably get RC loaded when using RPTB automagically...
5406 ; There's probably no need to call _memcpy() if we don't get
5407 ; a immediate operand for the size.  We could do a better job here
5408 ; than most memcpy() implementations.
5409 ; operand 2 is the number of bytes
5410 ; operand 3 is the shared alignment
5411 ; operand 4 is a scratch register
5412
5413 (define_insn "movstrqi_small"
5414   [(set (mem:BLK (match_operand:QI 0 "addr_reg_operand" "+a"))
5415         (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a")))
5416    (use (match_operand:QI 2 "immediate_operand" "i"))
5417    (use (match_operand:QI 3 "immediate_operand" ""))
5418    (clobber (match_operand:QI 4 "ext_low_reg_operand" "=&q"))
5419    (clobber (match_dup 0))
5420    (clobber (match_dup 1))]
5421   ""
5422   "*
5423  {
5424    int i;
5425    int len = INTVAL (operands[2]);
5426    int first = 1;
5427
5428    for (i = 0; i < len; i++)
5429     {
5430       if (first)
5431         output_asm_insn (\"ldiu\\t*%1++,%4\", operands);
5432       else
5433         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5434       output_asm_insn (\"sti\\t%4,*%0++\", operands);
5435       first = 0;
5436     } 
5437   return \"\";
5438   }
5439   "
5440   [(set_attr "type" "multi")])
5441
5442 (define_insn "movstrqi_large"
5443   [(set (mem:BLK (match_operand:QI 0 "addr_reg_operand" "+a"))
5444         (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a")))
5445    (use (match_operand:QI 2 "immediate_operand" "i"))
5446    (use (match_operand:QI 3 "immediate_operand" ""))
5447    (clobber (match_operand:QI 4 "ext_low_reg_operand" "=&q"))
5448    (clobber (match_dup 0))
5449    (clobber (match_dup 1))
5450    (clobber (reg:QI 25))
5451    (clobber (reg:QI 26))
5452    (clobber (reg:QI 27))]
5453   ""
5454   "*
5455  {
5456    int len = INTVAL (operands[2]);
5457
5458    output_asm_insn (\"ldiu\\t*%1++,%4\", operands);
5459    if (TARGET_RPTS_CYCLES (len))
5460      {
5461         output_asm_insn (\"rpts\\t%2-2\", operands);  
5462         output_asm_insn (\"sti\\t%4,*%0++\", operands);
5463         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5464         return \"sti\\t%4,*%0++\";
5465      }
5466    else
5467      {
5468         output_asm_insn (\"ldiu\\t%2-2,rc\", operands);
5469         output_asm_insn (\"rptb\\t$+1\", operands);  
5470         output_asm_insn (\"sti\\t%4,*%0++\", operands);
5471         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5472
5473         return \"sti\\t%4,*%0++\";
5474      }
5475   }
5476   "
5477   [(set_attr "type" "multi")])
5478
5479 ; Operand 2 is the count, operand 3 is the alignment.
5480 (define_expand "movstrqi"
5481   [(parallel [(set (mem:BLK (match_operand:BLK 0 "src_operand" ""))
5482                    (mem:BLK (match_operand:BLK 1 "src_operand" "")))
5483               (use (match_operand:QI 2 "immediate_operand" ""))
5484               (use (match_operand:QI 3 "immediate_operand" ""))])]
5485   ""
5486   "
5487  {
5488    rtx tmp;
5489    if (GET_CODE (operands[2]) != CONST_INT 
5490        || INTVAL (operands[2]) > 32767 
5491        || INTVAL (operands[2]) <= 0)
5492      {
5493         FAIL;  /* Try to call _memcpy */
5494      }
5495
5496    operands[0] = copy_to_mode_reg (Pmode, XEXP (operands[0], 0));
5497    operands[1] = copy_to_mode_reg (Pmode, XEXP (operands[1], 0));
5498    tmp = gen_reg_rtx (QImode);
5499    if (INTVAL (operands[2]) < 8)
5500      emit_insn (gen_movstrqi_small2 (operands[0], operands[1], operands[2],
5501                                     operands[3], tmp));
5502    else
5503      {
5504       emit_insn (gen_movstrqi_large (operands[0], operands[1], operands[2],
5505                                      operands[3], tmp));
5506      }
5507    DONE;
5508  }")
5509
5510
5511 (define_insn "*cmpstrqi"
5512   [(set (match_operand:QI 0 "ext_reg_operand" "=d")
5513         (compare:QI (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a"))
5514                     (mem:BLK (match_operand:QI 2 "addr_reg_operand" "+a"))))
5515    (use (match_operand:QI 3 "immediate_operand" "i"))
5516    (use (match_operand:QI 4 "immediate_operand" ""))
5517    (clobber (match_operand:QI 5 "std_reg_operand" "=&c"))
5518    (clobber (reg:QI 21))]
5519   ""
5520   "*
5521  {
5522     output_asm_insn (\"ldi\\t%3-1,%5\", operands);
5523     output_asm_insn (\"$1:\tsubi3\\t*%1++,*%2++,%0\", operands);
5524     output_asm_insn (\"dbeq\\t%5,$1\", operands);
5525     return \"\";
5526  }")
5527
5528 (define_expand "cmpstrqi"
5529   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
5530                    (compare:QI (match_operand:BLK 1 "general_operand" "")
5531                                (match_operand:BLK 2 "general_operand" "")))
5532               (use (match_operand:QI 3 "immediate_operand" ""))
5533               (use (match_operand:QI 4 "immediate_operand" ""))
5534               (clobber (match_dup 5))
5535               (clobber (reg:QI 21))])]
5536   ""
5537   "
5538 {
5539    if (GET_CODE (operands[3]) != CONST_INT
5540        || INTVAL (operands[3]) > 32767 
5541        || INTVAL (operands[3]) <= 0)
5542      {
5543         FAIL;
5544      }
5545    operands[1] = copy_to_mode_reg (Pmode, XEXP (operands[1], 0));
5546    operands[2] = copy_to_mode_reg (Pmode, XEXP (operands[2], 0));
5547    operands[5] = gen_reg_rtx (QImode);
5548 }")
5549
5550 ;
5551 ; TWO OPERAND LONG DOUBLE INSTRUCTIONS
5552 ;
5553
5554 (define_expand "movhf"
5555   [(set (match_operand:HF 0 "src_operand" "")
5556         (match_operand:HF 1 "src_operand" ""))]
5557  ""
5558  "if (c4x_emit_move_sequence (operands, HFmode))
5559     DONE;")
5560
5561 (define_insn "*movhf_noclobber_reg"
5562   [(set (match_operand:HF 0 "reg_operand" "=h")
5563         (match_operand:HF 1 "src_operand" "Hh"))]
5564  "GET_CODE (operands[1]) != MEM"
5565  "ldfu\\t%1,%0"
5566   [(set_attr "type" "unary")])
5567
5568 (define_insn "*movhf_noclobber"
5569  [(set (match_operand:HF 0 "dst_operand" "=h,m")
5570        (match_operand:HF 1 "src_operand" "Hm,h"))]
5571  "reg_operand (operands[0], HFmode) ^ reg_operand (operands[1], HFmode)"
5572  "#"
5573  [(set_attr "type" "multi,multi")])
5574
5575 (define_insn "*movhf_test"
5576   [(set (reg:CC 21)
5577         (compare:CC (match_operand:HF 1 "reg_operand" "h")
5578                     (const_int 0)))
5579    (clobber (match_scratch:HF 0 "=h"))]
5580  ""
5581  "ldf\\t%1,%0"
5582   [(set_attr "type" "unarycc")])
5583
5584 (define_insn "*movhf_set"
5585   [(set (reg:CC 21)
5586         (compare:CC (match_operand:HF 1 "reg_operand" "h")
5587                     (match_operand:HF 2 "fp_zero_operand" "G")))
5588     (set (match_operand:HF 0 "reg_operand" "=h")
5589          (match_dup 1))]
5590  ""
5591  "ldf\\t%1,%0"
5592   [(set_attr "type" "unarycc")])
5593
5594 (define_split
5595  [(set (match_operand:HF 0 "reg_operand" "")
5596        (match_operand:HF 1 "memory_operand" ""))]
5597  "reload_completed"
5598  [(set (match_dup 0) (float_extend:HF (match_dup 2)))
5599   (set (match_dup 0) (unspec:HF [(subreg:QI (match_dup 0) 0)
5600                                             (match_dup 3)] 8))]
5601  "operands[2] = c4x_operand_subword (operands[1], 0, 1, HFmode);
5602   operands[3] = c4x_operand_subword (operands[1], 1, 1, HFmode);
5603   PUT_MODE (operands[2], QFmode);
5604   PUT_MODE (operands[3], QImode);")
5605
5606 (define_split
5607  [(set (match_operand:HF 0 "reg_operand" "")
5608        (match_operand:HF 1 "const_operand" ""))]
5609  "reload_completed && 0"
5610  [(set (match_dup 0) (float_extend:HF (match_dup 2)))
5611   (set (match_dup 0) (unspec:HF [(subreg:QI (match_dup 0) 0)
5612                                             (match_dup 3)] 8))]
5613  "operands[2] = c4x_operand_subword (operands[1], 0, 1, HFmode);
5614   operands[3] = c4x_operand_subword (operands[1], 1, 1, HFmode);
5615   PUT_MODE (operands[2], QFmode);
5616   PUT_MODE (operands[3], QImode);")
5617
5618 (define_split
5619  [(set (match_operand:HF 0 "memory_operand" "")
5620        (match_operand:HF 1 "reg_operand" ""))]
5621   "reload_completed"
5622   [(set (match_dup 2) (float_truncate:QF (match_dup 1)))
5623    (set (match_dup 3) (unspec:QI [(match_dup 1)] 9))]
5624  "operands[2] = c4x_operand_subword (operands[0], 0, 1, HFmode);
5625   operands[3] = c4x_operand_subword (operands[0], 1, 1, HFmode);
5626   PUT_MODE (operands[2], QFmode);
5627   PUT_MODE (operands[3], QImode);")
5628
5629 (define_insn "*loadhf_float"
5630  [(set (match_operand:HF 0 "reg_operand" "=h")
5631        (float_extend:HF (match_operand:QF 1 "src_operand" "fHm")))]
5632  ""
5633  "@
5634   ldfu\\t%1,%0"
5635   [(set_attr "type" "unary")])
5636
5637 (define_insn "*loadhf_int"
5638  [(set (match_operand:HF 0 "reg_operand" "=h")
5639        (unspec:HF [(subreg:QI (match_dup 0) 0)
5640                    (match_operand:QI 1 "src_operand" "rIm")] 8))]
5641  ""
5642  "@
5643   ldiu\\t%1,%0"
5644   [(set_attr "type" "unary")])
5645
5646 (define_insn "*storehf_float"
5647   [(set (match_operand:QF 0 "memory_operand" "=m")
5648         (float_truncate:QF (match_operand:HF 1 "reg_operand" "h")))]
5649   ""
5650   "stf\\t%1,%0"
5651   [(set_attr "type" "store")])
5652
5653 (define_insn "*storehf_int"
5654  [(set (match_operand:QI 0 "memory_operand" "=m")
5655        (unspec:QI [(match_operand:HF 1 "reg_operand" "h")] 9))]
5656  ""
5657  "@
5658   sti\\t%1,%0"
5659   [(set_attr "type" "store")])
5660
5661 (define_insn "extendqfhf2"
5662   [(set (match_operand:HF 0 "reg_operand" "=h")
5663         (float_extend:HF (match_operand:QF 1 "reg_operand" "h")))]
5664   ""
5665   "ldfu\\t%1,%0"
5666   [(set_attr "type" "unarycc")])
5667
5668 (define_insn "trunchfqf2"
5669   [(set (match_operand:QF 0 "reg_operand" "=h")
5670         (float_truncate:QF (match_operand:HF 1 "reg_operand" "0")))
5671    (clobber (reg:CC 21))]
5672   ""
5673   "andn\\t0ffh,%0"
5674   [(set_attr "type" "unarycc")])
5675
5676 ;
5677 ; PUSH/POP
5678 ;
5679 (define_insn "*pushhf"
5680   [(set (mem:HF (pre_inc:QI (reg:QI 20)))
5681         (match_operand:HF 0 "reg_operand" "h"))]
5682  ""
5683  "#"
5684  [(set_attr "type" "multi")])
5685
5686 (define_split
5687  [(set (mem:HF (pre_inc:QI (reg:QI 20)))
5688         (match_operand:HF 0 "reg_operand" ""))]
5689   "reload_completed"
5690   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
5691         (float_truncate:QF (match_dup 0)))
5692    (set (mem:QI (pre_inc:QI (reg:QI 20)))
5693         (unspec:QI [(match_dup 0)] 9))]
5694  "")
5695
5696 (define_insn "pushhf_trunc"
5697   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
5698         (float_truncate:QF (match_operand:HF 0 "reg_operand" "h")))]
5699  ""
5700  "pushf\\t%0"
5701  [(set_attr "type" "push")])
5702
5703 (define_insn "pushhf_int"
5704   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
5705         (unspec:QI [(match_operand:HF 0 "reg_operand" "h")] 9))]
5706  ""
5707  "push\\t%0"
5708  [(set_attr "type" "push")])
5709
5710 ; we can not use this because the popf will destroy the low 8 bits
5711 ;(define_insn "*pophf"
5712 ;  [(set (match_operand:HF 0 "reg_operand" "=h")
5713 ;        (mem:HF (post_dec:QI (reg:QI 20))))
5714 ;   (clobber (reg:CC 21))]
5715 ; ""
5716 ; "#"
5717 ; [(set_attr "type" "multi")])
5718
5719 (define_split
5720  [(set (match_operand:HF 0 "reg_operand" "")
5721        (mem:HF (post_dec:QI (reg:QI 20))))
5722    (clobber (reg:CC 21))]
5723   "reload_completed"
5724   [(parallel [(set (match_operand:HF 0 "reg_operand" "=h")
5725                    (float_extend:HF (mem:QF (post_dec:QI (reg:QI 20)))))
5726               (clobber (reg:CC 21))])
5727    (parallel [(set (match_dup 0)
5728                    (unspec:HF [(subreg:QI (match_dup 0) 0)
5729                    (mem:QI (post_dec:QI (reg:QI 20)))] 8))
5730               (clobber (reg:CC 21))])]
5731  "")
5732
5733 (define_insn "*pophf_int"
5734  [(set (match_operand:HF 0 "reg_operand" "=h")
5735        (unspec:HF [(subreg:QI (match_dup 0) 0)
5736                    (mem:QI (post_dec:QI (reg:QI 20)))] 8))
5737   (clobber (reg:CC 21))]
5738  ""
5739  "@
5740   pop\\t%0"
5741   [(set_attr "type" "pop")])
5742
5743 (define_insn "*pophf_float"
5744  [(set (match_operand:HF 0 "reg_operand" "=h")
5745        (float_extend:HF (mem:QF (post_dec:QI (reg:QI 20)))))
5746   (clobber (reg:CC 21))]
5747  ""
5748  "@
5749   popf\\t%0"
5750   [(set_attr "type" "unary")])
5751
5752 ;
5753 ; FIX
5754 ;
5755 (define_insn "fixhfqi_clobber"
5756   [(set (match_operand:QI 0 "reg_operand" "=dc")
5757         (fix:QI (match_operand:HF 1 "reg_or_const_operand" "hH")))
5758    (clobber (reg:CC 21))]
5759  ""
5760  "fix\\t%1,%0"
5761   [(set_attr "type" "unarycc")])
5762
5763 ;
5764 ; ABSF
5765 ;
5766 (define_expand "abshf2"
5767   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
5768                    (abs:HF (match_operand:HF 1 "reg_or_const_operand" "")))
5769               (clobber (reg:CC_NOOV 21))])]
5770 ""
5771 "")
5772
5773 (define_insn "*abshf2_clobber"
5774   [(set (match_operand:HF 0 "reg_operand" "=h")
5775         (abs:HF (match_operand:HF 1 "reg_or_const_operand" "hH")))
5776    (clobber (reg:CC_NOOV 21))]
5777   ""
5778   "absf\\t%1,%0"
5779   [(set_attr "type" "unarycc")])
5780
5781 (define_insn "*abshf2_test"
5782   [(set (reg:CC_NOOV 21)
5783         (compare:CC_NOOV (abs:HF (match_operand:HF 1 "reg_operand" "h"))
5784                          (match_operand:HF 2 "fp_zero_operand" "G")))
5785    (clobber (match_scratch:HF 0 "=h"))]
5786   ""
5787   "absf\\t%1,%0"
5788   [(set_attr "type" "unarycc")])
5789
5790 (define_insn "*abshf2_set"
5791   [(set (reg:CC_NOOV 21)
5792         (compare:CC_NOOV (abs:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
5793                          (match_operand:HF 2 "fp_zero_operand" "G")))
5794    (set (match_operand:HF 0 "reg_operand" "=h")
5795         (abs:HF (match_dup 1)))]
5796
5797   ""
5798   "absf\\t%1,%0"
5799   [(set_attr "type" "unarycc")])
5800
5801 ;
5802 ; NEGF
5803 ;
5804 (define_expand "neghf2"
5805   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
5806                    (neg:HF (match_operand:HF 1 "reg_or_const_operand" "")))
5807               (clobber (reg:CC 21))])]
5808 ""
5809 "")
5810
5811 (define_insn "*neghf2_clobber"
5812   [(set (match_operand:HF 0 "reg_operand" "=h")
5813         (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH")))
5814    (clobber (reg:CC 21))]
5815   ""
5816   "negf\\t%1,%0"
5817   [(set_attr "type" "unarycc")])
5818
5819 (define_insn "*neghf2_test"
5820   [(set (reg:CC 21)
5821         (compare:CC (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
5822                     (match_operand:HF 2 "fp_zero_operand" "G")))
5823    (clobber (match_scratch:HF 0 "=h"))]
5824   ""
5825   "negf\\t%1,%0"
5826   [(set_attr "type" "unarycc")])
5827
5828 (define_insn "*neghf2_set"
5829   [(set (reg:CC 21)
5830         (compare:CC (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
5831                     (match_operand:HF 2 "fp_zero_operand" "G")))
5832    (set (match_operand:HF 0 "reg_operand" "=h")
5833         (neg:HF (match_dup 1)))]
5834   ""
5835   "negf\\t%1,%0"
5836   [(set_attr "type" "unarycc")])
5837
5838 ;
5839 ; RCPF
5840 ;
5841 (define_insn "*rcpfhf_clobber"
5842   [(set (match_operand:HF 0 "reg_operand" "=h")
5843         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] 5))
5844    (clobber (reg:CC_NOOV 21))]
5845   "! TARGET_C3X"
5846   "rcpf\\t%1,%0"
5847   [(set_attr "type" "unarycc")])
5848
5849 ;
5850 ; RSQRF
5851 ;
5852 (define_insn "*rsqrfhf_clobber"
5853   [(set (match_operand:HF 0 "reg_operand" "=h")
5854         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] 10))
5855    (clobber (reg:CC_NOOV 21))]
5856   "! TARGET_C3X"
5857   "rsqrf\\t%1,%0"
5858   [(set_attr "type" "unarycc")])
5859
5860 ;
5861 ; RNDF
5862 ;
5863 (define_insn "*rndhf_clobber"
5864   [(set (match_operand:HF 0 "reg_operand" "=h")
5865         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] 6))
5866    (clobber (reg:CC_NOOV 21))]
5867   "! TARGET_C3X"
5868   "rnd\\t%1,%0"
5869   [(set_attr "type" "unarycc")])
5870
5871
5872 ; Inlined float square root for C4x
5873 (define_expand "sqrthf2_inline"
5874   [(parallel [(set (match_dup 2)
5875                    (unspec:HF [(match_operand:HF 1 "reg_operand" "")] 10))
5876               (clobber (reg:CC_NOOV 21))])
5877    (parallel [(set (match_dup 3) (mult:HF (match_dup 5) (match_dup 1)))
5878               (clobber (reg:CC_NOOV 21))])
5879    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
5880               (clobber (reg:CC_NOOV 21))])
5881    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 4)))
5882               (clobber (reg:CC_NOOV 21))])
5883    (parallel [(set (match_dup 4) (minus:HF (match_dup 6) (match_dup 4)))
5884               (clobber (reg:CC_NOOV 21))])
5885    (parallel [(set (match_dup 2) (mult:HF (match_dup 2) (match_dup 4)))
5886               (clobber (reg:CC_NOOV 21))])
5887    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
5888               (clobber (reg:CC_NOOV 21))])
5889    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 4)))
5890               (clobber (reg:CC_NOOV 21))])
5891    (parallel [(set (match_dup 4) (minus:HF (match_dup 6) (match_dup 4)))
5892               (clobber (reg:CC_NOOV 21))])
5893    (parallel [(set (match_dup 2) (mult:HF (match_dup 2) (match_dup 4)))
5894               (clobber (reg:CC_NOOV 21))])
5895    (parallel [(set (match_operand:HF 0 "reg_operand" "")
5896                    (mult:HF (match_dup 2) (match_dup 1)))
5897               (clobber (reg:CC_NOOV 21))])]
5898   "! TARGET_C3X"
5899   "
5900   operands[2] = gen_reg_rtx (HFmode);
5901   operands[3] = gen_reg_rtx (HFmode);
5902   operands[4] = gen_reg_rtx (HFmode);
5903   operands[5] = immed_real_const_1 (REAL_VALUE_ATOF (\"0.5\", HFmode), HFmode);
5904   operands[6] = immed_real_const_1 (REAL_VALUE_ATOF (\"1.5\", HFmode), HFmode);
5905   ")
5906
5907
5908 (define_expand "sqrthf2"
5909   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
5910                    (sqrt:HF (match_operand:HF 1 "reg_operand" "")))
5911               (clobber (reg:CC 21))])]
5912   "! TARGET_C3X && TARGET_INLINE"
5913   "emit_insn (gen_sqrthf2_inline (operands[0], operands[1]));
5914    DONE;")
5915
5916
5917 (define_expand "fix_trunchfhi2"
5918   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
5919                    (fix:HI (match_operand:HF 1 "reg_operand" "")))
5920               (clobber (reg:CC 21))])]
5921   ""
5922   "c4x_emit_libcall (fix_trunchfhi2_libfunc, FIX, HImode, HFmode, 2, operands);
5923    DONE;")
5924
5925 (define_expand "fixuns_trunchfhi2"
5926   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
5927                    (unsigned_fix:HI (match_operand:HF 1 "reg_operand" "")))
5928               (clobber (reg:CC 21))])]
5929   ""
5930   "c4x_emit_libcall (fixuns_trunchfhi2_libfunc, UNSIGNED_FIX, 
5931                      HImode, HFmode, 2, operands);
5932    DONE;")
5933
5934 ;
5935 ; THREE OPERAND LONG DOUBLE INSTRUCTIONS
5936 ;
5937
5938 ;
5939 ; ADDF
5940 ;
5941 (define_insn "addhf3"
5942   [(set (match_operand:HF 0 "reg_operand" "=h,?h")
5943         (plus:HF (match_operand:HF 1 "reg_operand" "%0,h")
5944                  (match_operand:HF 2 "reg_or_const_operand" "H,h")))
5945    (clobber (reg:CC_NOOV 21))]
5946   ""
5947   "@
5948    addf\\t%2,%0
5949    addf3\\t%2,%1,%0"
5950   [(set_attr "type" "binarycc,binarycc")])
5951
5952 ;
5953 ; SUBF
5954 ;
5955 (define_insn "subhf3"
5956   [(set (match_operand:HF 0 "reg_operand" "=h,h,?h")
5957         (minus:HF (match_operand:HF 1 "reg_or_const_operand" "0,H,h")
5958                   (match_operand:HF 2 "reg_or_const_operand" "H,0,h")))
5959    (clobber (reg:CC_NOOV 21))]
5960   ""
5961   "@
5962    subf\\t%2,%0
5963    subrf\\t%1,%0
5964    subf3\\t%2,%1,%0"
5965   [(set_attr "type" "binarycc,binarycc,binarycc")])
5966
5967 ;
5968 ; MULF
5969 ;
5970 ; The C3x MPYF only uses 24 bit precision while the C4x uses 32 bit precison.
5971 ;
5972 (define_expand "mulhf3"
5973   [(parallel [(set (match_operand:HF 0 "reg_operand" "=h")
5974                    (mult:HF (match_operand:HF 1 "reg_operand" "h")
5975                             (match_operand:HF 2 "reg_operand" "h")))
5976               (clobber (reg:CC_NOOV 21))])]
5977   "! TARGET_C3X"
5978   "")
5979
5980 (define_insn "*mulhf3_c40"
5981   [(set (match_operand:HF 0 "reg_operand" "=h,?h")
5982         (mult:HF (match_operand:HF 1 "reg_operand" "%0,h")
5983                  (match_operand:HF 2 "reg_or_const_operand" "hH,h")))
5984    (clobber (reg:CC_NOOV 21))]
5985   ""
5986   "@
5987    mpyf\\t%2,%0
5988    mpyf3\\t%2,%1,%0"
5989   [(set_attr "type" "binarycc,binarycc")])
5990
5991 ;
5992 ; CMPF
5993 ;
5994 (define_expand "cmphf"
5995   [(set (reg:CC 21)
5996         (compare:CC (match_operand:HF 0 "reg_operand" "")
5997                     (match_operand:HF 1 "reg_or_const_operand" "")))]
5998   ""
5999   "c4x_compare_op0 = operands[0];
6000    c4x_compare_op1 = operands[1];
6001    DONE;")
6002
6003 (define_insn "*cmphf"
6004   [(set (reg:CC 21)
6005         (compare:CC (match_operand:HF 0 "reg_operand" "h")
6006                     (match_operand:HF 1 "reg_or_const_operand" "hH")))]
6007   ""
6008   "cmpf\\t%1,%0"
6009   [(set_attr "type" "compare")])
6010
6011 (define_insn "*cmphf_noov"
6012   [(set (reg:CC_NOOV 21)
6013         (compare:CC_NOOV (match_operand:HF 0 "reg_operand" "h")
6014                          (match_operand:HF 1 "reg_or_const_operand" "hH")))]
6015   ""
6016   "cmpf\\t%1,%0"
6017   [(set_attr "type" "compare")])
6018
6019 ; Inlined float divide for C4x
6020 (define_expand "divhf3_inline"
6021   [(parallel [(set (match_dup 3)
6022                    (unspec:HF [(match_operand:HF 2 "reg_operand" "")] 5))
6023               (clobber (reg:CC_NOOV 21))])
6024    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6025               (clobber (reg:CC_NOOV 21))])
6026    (parallel [(set (match_dup 4) (minus:HF (match_dup 5) (match_dup 4)))
6027               (clobber (reg:CC_NOOV 21))])
6028    (parallel [(set (match_dup 3) (mult:HF (match_dup 3) (match_dup 4)))
6029               (clobber (reg:CC_NOOV 21))])
6030    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6031               (clobber (reg:CC_NOOV 21))])
6032    (parallel [(set (match_dup 4) (minus:HF (match_dup 5) (match_dup 4)))
6033               (clobber (reg:CC_NOOV 21))])
6034    (parallel [(set (match_dup 3) (mult:HF (match_dup 3) (match_dup 4)))
6035               (clobber (reg:CC_NOOV 21))])
6036    (parallel [(set (match_operand:HF 0 "reg_operand" "")
6037                    (mult:HF (match_operand:HF 1 "reg_operand" "")
6038                             (match_dup 3)))
6039               (clobber (reg:CC_NOOV 21))])]
6040   "! TARGET_C3X"
6041   "
6042   operands[3] = gen_reg_rtx (HFmode);
6043   operands[4] = gen_reg_rtx (HFmode);
6044   operands[5] = CONST2_RTX (HFmode);
6045   ")
6046
6047 (define_expand "divhf3"
6048   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6049                    (div:HF (match_operand:HF 1 "reg_operand" "")
6050                            (match_operand:HF 2 "reg_operand" "")))
6051               (clobber (reg:CC 21))])]
6052   "! TARGET_C3X && TARGET_INLINE"
6053   "emit_insn (gen_divhf3_inline (operands[0], operands[1], operands[2]));
6054    DONE;")
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_libfunc, 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_libfunc, 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_libfunc, 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_libfunc, 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 (smul_optab->handlers[(int) HImode].libfunc,
6864                       MULT, HImode, operands);
6865    DONE;")
6866
6867
6868 ;
6869 ; PEEPHOLES
6870 ;
6871
6872 ; dbCC peepholes
6873 ;
6874 ; Turns
6875 ;   loop:
6876 ;           [ ... ]
6877 ;           bCC label           ; abnormal loop termination
6878 ;           dbu aN, loop        ; normal loop termination
6879 ;
6880 ; Into
6881 ;   loop:
6882 ;           [ ... ]
6883 ;           dbCC aN, loop
6884 ;           bCC label
6885 ;
6886 ; Which moves the bCC condition outside the inner loop for free.
6887 ;
6888 (define_peephole
6889   [(set (pc) (if_then_else (match_operator 3 "comparison_operator"
6890                            [(reg:CC 21) (const_int 0)])
6891                            (label_ref (match_operand 2 "" ""))
6892                            (pc)))
6893    (parallel
6894     [(set (pc)
6895           (if_then_else
6896             (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a")
6897                          (const_int -1))
6898                 (const_int 0))
6899             (label_ref (match_operand 1 "" ""))
6900             (pc)))
6901      (set (match_dup 0)
6902           (plus:QI (match_dup 0)
6903                    (const_int -1)))
6904      (clobber (reg:CC_NOOV 21))])]
6905   "! c4x_label_conflict (insn, operands[2], operands[1])"
6906   "db%I3\\t%0,%l1\\n\\tb%3\\t%l2"
6907   [(set_attr "type" "multi")])
6908
6909 (define_peephole
6910   [(set (pc) (if_then_else (match_operator 3 "comparison_operator"
6911                            [(reg:CC 21) (const_int 0)])
6912                            (label_ref (match_operand 2 "" ""))
6913                            (pc)))
6914    (parallel
6915     [(set (pc)
6916           (if_then_else
6917             (ne (match_operand:QI 0 "addr_reg_operand" "+a")
6918                 (const_int 0))
6919             (label_ref (match_operand 1 "" ""))
6920             (pc)))
6921      (set (match_dup 0)
6922           (plus:QI (match_dup 0)
6923                    (const_int -1)))])]
6924   "! c4x_label_conflict (insn, operands[2], operands[1])"
6925   "db%I3\\t%0,%l1\\n\\tb%3\\t%l2"
6926   [(set_attr "type" "multi")])
6927
6928 ;
6929 ; Peepholes to convert 'call label; rets' into jump label
6930 ;
6931
6932 (define_peephole
6933   [(parallel [(call (mem:QI (match_operand:QI 0 "call_address_operand" ""))
6934                     (match_operand:QI 1 "general_operand" ""))
6935               (clobber (reg:QI 31))])
6936    (return)]
6937   "c4x_null_epilogue_p ()"
6938   "*
6939    if (REG_P (operands[0]))
6940      return \"bu%#\\t%C0\";
6941    else
6942      return \"br%#\\t%C0\";"
6943   [(set_attr "type" "jump")])
6944
6945 (define_peephole
6946   [(parallel [(set (match_operand 0 "" "")
6947                    (call (mem:QI (match_operand:QI 1 "call_address_operand" ""))
6948                          (match_operand:QI 2 "general_operand" "")))
6949               (clobber (reg:QI 31))])
6950    (return)]
6951   "c4x_null_epilogue_p ()"
6952   "*
6953    if (REG_P (operands[1]))
6954      return \"bu%#\\t%C1\";
6955    else
6956      return \"br%#\\t%C1\";"
6957   [(set_attr "type" "jump")])
6958
6959
6960 ; This peephole should be unnecessary with my patches to flow.c
6961 ; for better autoincrement detection
6962 (define_peephole
6963  [(set (match_operand:QF 0 "ext_low_reg_operand" "")
6964        (mem:QF (match_operand:QI 1 "addr_reg_operand" "")))
6965   (set (match_operand:QF 2 "ext_low_reg_operand" "")
6966        (mem:QF (plus:QI (match_dup 1) (const_int 1))))
6967   (parallel [(set (match_dup 1) (plus:QI (match_dup 1) (const_int 2)))
6968              (clobber (reg:CC_NOOV 21))])]
6969  ""
6970  "ldf\\t*%1++,%0\\n\\tldf\\t*%1++,%2")
6971
6972
6973 ; This peephole should be unnecessary with my patches to flow.c
6974 ; for better autoincrement detection
6975 (define_peephole
6976  [(set (mem:QF (match_operand:QI 0 "addr_reg_operand" ""))
6977        (match_operand:QF 1 "ext_low_reg_operand" ""))
6978   (set (mem:QF (plus:QI (match_dup 0) (const_int 1)))
6979        (match_operand:QF 2 "ext_low_reg_operand" ""))
6980   (parallel [(set (match_dup 0) (plus:QI (match_dup 0) (const_int 2)))
6981              (clobber (reg:CC_NOOV 21))])]
6982  ""
6983  "stf\\t%1,*%0++\\n\\tstf\\t%2,*%0++")
6984
6985
6986 ; The following two peepholes remove an unecessary load
6987 ; often found at the end of a function.  These peepholes
6988 ; could be generalised to other binary operators.  They shouldn't
6989 ; be required if we run a post reload mop-up pass.
6990 (define_peephole
6991  [(parallel [(set (match_operand:QF 0 "ext_reg_operand" "")
6992                   (plus:QF (match_operand:QF 1 "ext_reg_operand" "")
6993                            (match_operand:QF 2 "ext_reg_operand" "")))
6994              (clobber (reg:CC_NOOV 21))])
6995   (set (match_operand:QF 3 "ext_reg_operand" "")
6996        (match_dup 0))]
6997  "dead_or_set_p (insn, operands[0])"
6998  "addf3\\t%2,%1,%3")
6999
7000 (define_peephole
7001  [(parallel [(set (match_operand:QI 0 "reg_operand" "")
7002                   (plus:QI (match_operand:QI 1 "reg_operand" "")
7003                            (match_operand:QI 2 "reg_operand" "")))
7004              (clobber (reg:CC_NOOV 21))])
7005   (set (match_operand:QI 3 "reg_operand" "")
7006        (match_dup 0))]
7007  "dead_or_set_p (insn, operands[0])"
7008  "addi3\\t%2,%1,%3")