OSDN Git Service

2000-01-29 Herman A.J. ten Brugge <Haj.Ten.Brugge@net.HCC.nl>
[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 (MULQI3_LIBCALL, MULT, QImode, operands);
2088        DONE;
2089      }
2090   ")
2091
2092 (define_insn "*mulqi3_clobber"
2093   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2094         (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2095                  (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2096    (clobber (reg:CC_NOOV 21))]
2097   "valid_operands (MULT, operands, QImode)"
2098   "*
2099   if (which_alternative == 0 || which_alternative == 3)
2100     {
2101       if (TARGET_C3X
2102           && GET_CODE (operands[2]) == CONST_INT
2103           && exact_log2 (INTVAL (operands[2])) >= 0)
2104         return \"ash\\t%L2,%0\";
2105       else
2106         return \"mpyi\\t%2,%0\";
2107     }
2108   else
2109       return \"mpyi3\\t%2,%1,%0\";"
2110   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2111 ; Default to int16 data attr.
2112
2113 (define_insn "*mulqi3_test"
2114   [(set (reg:CC_NOOV 21)
2115         (compare:CC_NOOV (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2116                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2117                          (const_int 0)))
2118    (clobber (match_scratch:QI 0 "=d,d,d"))]
2119   "valid_operands (MULT, operands, QImode)"
2120   "*
2121   if (which_alternative == 0)
2122     {
2123       if (TARGET_C3X 
2124           && GET_CODE (operands[2]) == CONST_INT
2125           && exact_log2 (INTVAL (operands[2])) >= 0)
2126         return \"ash\\t%L2,%0\";
2127       else
2128         return \"mpyi\\t%2,%0\";
2129     } 
2130   else
2131       return \"mpyi3\\t%2,%1,%0\";"
2132   [(set_attr "type" "binarycc,binarycc,binarycc")])
2133 ; Default to int16 data attr.
2134
2135 (define_insn "*mulqi3_set"
2136   [(set (reg:CC_NOOV 21)
2137         (compare:CC_NOOV (mult:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2138                                   (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2139                          (const_int 0)))
2140    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2141         (mult:QI (match_dup 1)
2142                  (match_dup 2)))]
2143   "valid_operands (MULT, operands, QImode)"
2144   "*
2145   if (which_alternative == 0)
2146     {
2147       if (TARGET_C3X 
2148           && GET_CODE (operands[2]) == CONST_INT
2149           && exact_log2 (INTVAL (operands[2])) >= 0)
2150         return \"ash\\t%L2,%0\";
2151       else
2152         return \"mpyi\\t%2,%0\";
2153     }
2154     else
2155         return \"mpyi3\\t%2,%1,%0\";"
2156   [(set_attr "type" "binarycc,binarycc,binarycc")])
2157 ; Default to int16 data attr.
2158
2159 ; The C3x multiply instruction assumes 24-bit signed integer operands
2160 ; and the 48-bit result is truncated to 32-bits.
2161 (define_insn "*mulqi3_24_clobber"
2162   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2163         (mult:QI
2164          (sign_extend:QI
2165           (and:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2166                   (const_int 16777215)))
2167          (sign_extend:QI
2168           (and:QI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")
2169                   (const_int 16777215)))))
2170    (clobber (reg:CC_NOOV 21))]
2171   "TARGET_C3X && valid_operands (MULT, operands, QImode)"
2172   "@
2173    mpyi\\t%2,%0
2174    mpyi3\\t%2,%1,%0
2175    mpyi3\\t%2,%1,%0
2176    mpyi\\t%2,%0
2177    mpyi3\\t%2,%1,%0
2178    mpyi3\\t%2,%1,%0"
2179   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2180 ; Default to int16 data attr.
2181
2182
2183 ; Fast square function for C3x where TARGET_MPYI not asserted
2184 (define_expand "sqrqi2_inline"
2185   [(set (match_dup 7) (match_operand:QI 1 "src_operand" ""))
2186    (parallel [(set (match_dup 3)
2187                    (lshiftrt:QI (match_dup 7) (const_int 16)))
2188               (clobber (reg:CC 21))])
2189    (parallel [(set (match_dup 2)
2190                    (and:QI (match_dup 7) (const_int 65535)))
2191               (clobber (reg:CC 21))])
2192    (parallel [(set (match_dup 4)
2193                    (mult:QI (sign_extend:QI (and:QI (match_dup 2) 
2194                                                     (const_int 16777215)))
2195                             (sign_extend:QI (and:QI (match_dup 2) 
2196                                                     (const_int 16777215)))))
2197               (clobber (reg:CC_NOOV 21))])
2198    (parallel [(set (match_dup 5)
2199                    (mult:QI (sign_extend:QI (and:QI (match_dup 2) 
2200                                                     (const_int 16777215)))
2201                             (sign_extend:QI (and:QI (match_dup 3) 
2202                                                     (const_int 16777215)))))
2203               (clobber (reg:CC_NOOV 21))])
2204    (parallel [(set (match_dup 6)
2205                    (ashift:QI (match_dup 5) (const_int 17)))
2206               (clobber (reg:CC 21))])
2207    (parallel [(set (match_operand:QI 0 "reg_operand" "")
2208                    (plus:QI (match_dup 4) (match_dup 6)))
2209               (clobber (reg:CC_NOOV 21))])]
2210   ""
2211   "
2212   operands[2] = gen_reg_rtx (QImode); /* a = val & 0xffff */
2213   operands[3] = gen_reg_rtx (QImode); /* b = val >> 16 */
2214   operands[4] = gen_reg_rtx (QImode); /* a * a */
2215   operands[5] = gen_reg_rtx (QImode); /* a * b */
2216   operands[6] = gen_reg_rtx (QImode); /* (a * b) << 17 */
2217   operands[7] = gen_reg_rtx (QImode); /* val */
2218   ")
2219
2220 ; Inlined integer multiply for C3x
2221 (define_expand "mulqi3_inline"
2222   [(set (match_dup 12) (const_int -16))
2223    (set (match_dup 13) (match_operand:QI 1 "src_operand" ""))
2224    (set (match_dup 14) (match_operand:QI 2 "src_operand" ""))
2225    (parallel [(set (match_dup 4)
2226                    (lshiftrt:QI (match_dup 13) (neg:QI (match_dup 12))))
2227               (clobber (reg:CC 21))])
2228    (parallel [(set (match_dup 6)
2229                    (lshiftrt:QI (match_dup 14) (neg:QI (match_dup 12))))
2230               (clobber (reg:CC 21))])
2231    (parallel [(set (match_dup 3)
2232                    (and:QI (match_dup 13)
2233                            (const_int 65535)))
2234               (clobber (reg:CC 21))])
2235    (parallel [(set (match_dup 5)
2236                    (and:QI (match_dup 14) 
2237                            (const_int 65535)))
2238               (clobber (reg:CC 21))])
2239    (parallel [(set (match_dup 7)
2240                    (mult:QI (sign_extend:QI (and:QI (match_dup 4) 
2241                                                     (const_int 16777215)))
2242                             (sign_extend:QI (and:QI (match_dup 5) 
2243                                                     (const_int 16777215)))))
2244               (clobber (reg:CC_NOOV 21))])
2245    (parallel [(set (match_dup 8)
2246                    (mult:QI (sign_extend:QI (and:QI (match_dup 3) 
2247                                                     (const_int 16777215)))
2248                             (sign_extend:QI (and:QI (match_dup 5) 
2249                                                     (const_int 16777215)))))
2250               (clobber (reg:CC_NOOV 21))])
2251    (parallel [(set (match_dup 9)
2252                    (mult:QI (sign_extend:QI (and:QI (match_dup 3) 
2253                                                     (const_int 16777215)))
2254                             (sign_extend:QI (and:QI (match_dup 6) 
2255                                                     (const_int 16777215)))))
2256               (clobber (reg:CC_NOOV 21))])
2257    (parallel [(set (match_dup 10)
2258                    (plus:QI (match_dup 7) (match_dup 9)))
2259               (clobber (reg:CC_NOOV 21))])
2260    (parallel [(set (match_dup 11)
2261                    (ashift:QI (match_dup 10) (const_int 16)))
2262               (clobber (reg:CC 21))])
2263    (parallel [(set (match_operand:QI 0 "reg_operand" "")
2264                    (plus:QI (match_dup 8) (match_dup 11)))
2265               (clobber (reg:CC_NOOV 21))])]
2266   "TARGET_C3X"
2267   "
2268   operands[3] = gen_reg_rtx (QImode); /* a = arg1 & 0xffff */
2269   operands[4] = gen_reg_rtx (QImode); /* b = arg1 >> 16 */
2270   operands[5] = gen_reg_rtx (QImode); /* a = arg2 & 0xffff */
2271   operands[6] = gen_reg_rtx (QImode); /* b = arg2 >> 16 */
2272   operands[7] = gen_reg_rtx (QImode); /* b * c */
2273   operands[8] = gen_reg_rtx (QImode); /* a * c */
2274   operands[9] = gen_reg_rtx (QImode); /* a * d */
2275   operands[10] = gen_reg_rtx (QImode); /* b * c + a * d */
2276   operands[11] = gen_reg_rtx (QImode); /* (b *c + a * d) << 16 */
2277   operands[12] = gen_reg_rtx (QImode); /* -16 */
2278   operands[13] = gen_reg_rtx (QImode); /* arg1 */
2279   operands[14] = gen_reg_rtx (QImode); /* arg2 */
2280   ")
2281
2282 ;
2283 ; MPYSHI (C4x only)
2284 ;
2285 (define_expand "smulqi3_highpart"
2286   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2287                    (truncate:QI
2288                     (lshiftrt:HI
2289                      (mult:HI
2290                       (sign_extend:HI (match_operand:QI 1 "src_operand" ""))
2291                       (sign_extend:HI (match_operand:QI 2 "src_operand" "")))
2292                  (const_int 32))))
2293               (clobber (reg:CC_NOOV 21))])]
2294  ""
2295  "legitimize_operands (MULT, operands, QImode);
2296   if (TARGET_C3X)
2297     {
2298        c4x_emit_libcall_mulhi (SMULHI3_LIBCALL, SIGN_EXTEND, QImode, operands);
2299        DONE;
2300     }
2301  ")
2302
2303 (define_insn "*smulqi3_highpart_clobber"
2304   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2305         (truncate:QI 
2306          (lshiftrt:HI
2307           (mult:HI
2308            (sign_extend:HI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>"))
2309            (sign_extend:HI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2310       (const_int 32))))
2311    (clobber (reg:CC_NOOV 21))]
2312   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2313   "@
2314    mpyshi\\t%2,%0
2315    mpyshi3\\t%2,%1,%0
2316    mpyshi3\\t%2,%1,%0
2317    mpyshi\\t%2,%0
2318    mpyshi3\\t%2,%1,%0
2319    mpyshi3\\t%2,%1,%0"
2320   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2321    (set_attr "data" "int16,int16,int16,int16,int16,int16")])
2322
2323 (define_insn "*smulqi3_highpart_noclobber"
2324   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2325         (truncate:QI 
2326          (lshiftrt:HI
2327           (mult:HI
2328            (sign_extend:HI (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2329            (sign_extend:HI (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))
2330       (const_int 32))))]
2331   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2332   "@
2333    mpyshi\\t%2,%0
2334    mpyshi3\\t%2,%1,%0
2335    mpyshi3\\t%2,%1,%0"
2336   [(set_attr "type" "binary,binary,binary")
2337    (set_attr "data" "int16,int16,int16")])
2338
2339 ;
2340 ; MPYUHI (C4x only)
2341 ;
2342 (define_expand "umulqi3_highpart"
2343   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2344                (truncate:QI
2345                 (lshiftrt:HI
2346                  (mult:HI
2347                   (zero_extend:HI (match_operand:QI 1 "src_operand" ""))
2348                   (zero_extend:HI (match_operand:QI 2 "lsrc_operand" "")))
2349                  (const_int 32))))
2350               (clobber (reg:CC_NOOV 21))])]
2351  ""
2352  "legitimize_operands (MULT, operands, QImode);
2353   if (TARGET_C3X) 
2354     {
2355       c4x_emit_libcall_mulhi (UMULHI3_LIBCALL, ZERO_EXTEND, QImode, operands);
2356       DONE;
2357     }
2358  ")
2359
2360 (define_insn "*umulqi3_highpart_clobber"
2361   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2362         (truncate:QI
2363          (lshiftrt:HI
2364           (mult:HI 
2365            (zero_extend:HI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>"))
2366            (zero_extend:HI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2367           (const_int 32))))
2368    (clobber (reg:CC_NOOV 21))]
2369   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2370   "@
2371    mpyuhi\\t%2,%0
2372    mpyuhi3\\t%2,%1,%0
2373    mpyuhi3\\t%2,%1,%0
2374    mpyuhi\\t%2,%0
2375    mpyuhi3\\t%2,%1,%0
2376    mpyuhi3\\t%2,%1,%0"
2377   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2378    (set_attr "data" "uint16,uint16,uint16,uint16,uint16,uint16")])
2379
2380 (define_insn "*umulqi3_highpart_noclobber"
2381   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2382         (truncate:QI
2383          (lshiftrt:HI
2384           (mult:HI 
2385            (zero_extend:HI (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2386            (zero_extend:HI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))
2387           (const_int 32))))]
2388   "! TARGET_C3X && valid_operands (MULT, operands, QImode)"
2389   "@
2390    mpyuhi\\t%2,%0
2391    mpyuhi3\\t%2,%1,%0
2392    mpyuhi3\\t%2,%1,%0"
2393   [(set_attr "type" "binary,binary,binary")
2394    (set_attr "data" "uint16,uint16,uint16")])
2395
2396 ;
2397 ; AND
2398 ;
2399 (define_expand "andqi3"
2400   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2401                    (and:QI (match_operand:QI 1 "src_operand" "")
2402                            (match_operand:QI 2 "tsrc_operand" "")))
2403               (clobber (reg:CC 21))])]
2404  ""
2405  "legitimize_operands (AND, operands, QImode);")
2406
2407
2408 (define_insn "*andqi3_255_clobber"
2409   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2410         (and:QI (match_operand:QI 1 "src_operand" "mr,mr")
2411                 (const_int 255)))
2412    (clobber (reg:CC 21))]
2413  "! TARGET_C3X"
2414  "lbu0\\t%1,%0"
2415   [(set_attr "type" "unarycc,unary")])
2416
2417 (define_insn "*andqi3_255_noclobber"
2418   [(set (match_operand:QI 0 "reg_operand" "=c")
2419         (and:QI (match_operand:QI 1 "src_operand" "mr")
2420                 (const_int 255)))]
2421  "! TARGET_C3X"
2422  "lbu0\\t%1,%0"
2423   [(set_attr "type" "unary")])
2424
2425
2426 (define_insn "*andqi3_65535_clobber"
2427   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2428         (and:QI (match_operand:QI 1 "src_operand" "mr,mr")
2429                 (const_int 65535)))
2430    (clobber (reg:CC 21))]
2431  "! TARGET_C3X"
2432  "lhu0\\t%1,%0"
2433   [(set_attr "type" "unarycc,unary")])
2434
2435 (define_insn "*andqi3_65535_noclobber"
2436   [(set (match_operand:QI 0 "reg_operand" "=c")
2437         (and:QI (match_operand:QI 1 "src_operand" "mr")
2438                 (const_int 65535)))]
2439  "! TARGET_C3X"
2440  "lhu0\\t%1,%0"
2441   [(set_attr "type" "unary")])
2442
2443 (define_insn "*andqi3_clobber"
2444   [(set (match_operand:QI 0 "reg_operand" "=d,d,d,?d,c,c,c,?c")
2445         (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>,0,0,rR,rS<>")
2446                 (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>,N,rLm,JR,rS<>")))
2447    (clobber (reg:CC 21))]
2448   "valid_operands (AND, operands, QImode)"
2449   "@
2450    andn\\t%N2,%0
2451    and\\t%2,%0
2452    and3\\t%2,%1,%0
2453    and3\\t%2,%1,%0
2454    andn\\t%N2,%0
2455    and\\t%2,%0
2456    and3\\t%2,%1,%0
2457    and3\\t%2,%1,%0"
2458   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc,binary,binary,binary,binary")
2459    (set_attr "data" "not_uint16,uint16,int16,uint16,not_uint16,uint16,int16,uint16")])
2460
2461 (define_insn "*andqi3_noclobber"
2462   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c,?c")
2463         (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2464                 (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>")))]
2465   "valid_operands (AND, operands, QImode)"
2466   "@
2467    andn\\t%N2,%0
2468    and\\t%2,%0
2469    and3\\t%2,%1,%0
2470    and3\\t%2,%1,%0"
2471   [(set_attr "type" "binary,binary,binary,binary")
2472    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2473
2474 (define_split
2475   [(set (match_operand:QI 0 "std_reg_operand" "")
2476         (and:QI (match_operand:QI 1 "src_operand" "")
2477                 (match_operand:QI 2 "tsrc_operand" "")))
2478    (clobber (reg:CC 21))]
2479   "reload_completed"
2480   [(set (match_dup 0)
2481         (and:QI (match_dup 1)
2482                 (match_dup 2)))]
2483   "")
2484
2485 (define_insn "*andqi3_test"
2486   [(set (reg:CC 21)
2487         (compare:CC (and:QI (match_operand:QI 1 "src_operand" "%0,r,rR,rS<>")
2488                             (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>"))
2489                     (const_int 0)))
2490    (clobber (match_scratch:QI 0 "=d,X,X,?X"))]
2491   "valid_operands (AND, operands, QImode)"
2492   "@
2493    andn\\t%N2,%0
2494    tstb\\t%2,%1
2495    tstb3\\t%2,%1
2496    tstb3\\t%2,%1"
2497   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2498    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2499
2500 (define_peephole
2501   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2502                    (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2503                            (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>")))
2504               (clobber (reg:CC 21))])
2505    (set (reg:CC 21)
2506         (compare:CC (match_dup 0) (const_int 0)))]
2507   "valid_operands (AND, operands, QImode)"
2508   "@
2509    andn\\t%N2,%0
2510    and\\t%2,%0
2511    and3\\t%2,%1,%0
2512    and3\\t%2,%1,%0"
2513   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2514    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2515   
2516 (define_insn "*andqi3_set"
2517   [(set (reg:CC 21)
2518         (compare:CC (and:QI (match_operand:QI 1 "src_operand" "%0,0,rR,rS<>")
2519                             (match_operand:QI 2 "tsrc_operand" "N,rLm,JR,rS<>"))
2520                     (const_int 0)))
2521    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d,?d")
2522         (and:QI (match_dup 1)
2523                 (match_dup 2)))]
2524   "valid_operands (AND, operands, QImode)"
2525   "@
2526    andn\\t%N2,%0
2527    and\\t%2,%0
2528    and3\\t%2,%1,%0
2529    and3\\t%2,%1,%0"
2530   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")
2531    (set_attr "data" "not_uint16,uint16,int16,uint16")])
2532
2533 ;
2534 ; ANDN
2535 ;
2536 ; NB, this insn doesn't have commutative operands, but valid_operands
2537 ; assumes that the code AND does.  We might have to kludge this if
2538 ; we make valid_operands stricter.
2539 (define_insn "*andnqi3_clobber"
2540   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2541         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>"))
2542                 (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")))
2543    (clobber (reg:CC 21))]
2544   "valid_operands (AND, operands, QImode)"
2545   "@
2546    andn\\t%2,%0
2547    andn3\\t%2,%1,%0
2548    andn3\\t%2,%1,%0
2549    andn\\t%2,%0
2550    andn3\\t%2,%1,%0
2551    andn3\\t%2,%1,%0"
2552   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2553    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2554
2555 (define_insn "*andnqi3_noclobber"
2556   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2557         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2558                 (match_operand:QI 1 "src_operand" "0,rR,rS<>")))]
2559   "valid_operands (AND, operands, QImode)"
2560   "@
2561    andn\\t%2,%0
2562    andn3\\t%2,%1,%0
2563    andn3\\t%2,%1,%0"
2564   [(set_attr "type" "binary,binary,binary")
2565    (set_attr "data" "uint16,int16,uint16")])
2566
2567 (define_split
2568   [(set (match_operand:QI 0 "std_reg_operand" "")
2569         (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" ""))
2570                 (match_operand:QI 1 "src_operand" "")))
2571    (clobber (reg:CC 21))]
2572   "reload_completed"
2573   [(set (match_dup 0)
2574         (and:QI (not:QI (match_dup 2))
2575                 (match_dup 1)))]
2576   "")
2577
2578 (define_insn "*andnqi3_test"
2579   [(set (reg:CC 21)
2580         (compare:CC (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2581                             (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2582                     (const_int 0)))
2583    (clobber (match_scratch:QI 0 "=d,d,d"))]
2584   "valid_operands (AND, operands, QImode)"
2585   "@
2586    andn\\t%2,%0
2587    andn3\\t%2,%1,%0
2588    andn3\\t%2,%1,%0"
2589   [(set_attr "type" "binarycc,binarycc,binarycc")
2590    (set_attr "data" "uint16,int16,uint16")])
2591
2592 (define_insn "*andnqi3_set"
2593   [(set (reg:CC 21)
2594         (compare:CC (and:QI (not:QI (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2595                             (match_operand:QI 1 "src_operand" "0,rR,rS<>"))
2596                     (const_int 0)))
2597    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2598         (and:QI (not:QI (match_dup 2))
2599                 (match_dup 1)))]
2600   "valid_operands (AND, operands, QImode)"
2601   "@
2602    andn\\t%2,%0
2603    andn3\\t%2,%1,%0
2604    andn3\\t%2,%1,%0"
2605   [(set_attr "type" "binarycc,binarycc,binarycc")
2606    (set_attr "data" "uint16,int16,uint16")])
2607
2608 ;
2609 ; OR
2610 ;
2611 (define_expand "iorqi3"
2612   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2613                    (ior:QI (match_operand:QI 1 "src_operand" "")
2614                            (match_operand:QI 2 "lsrc_operand" "")))
2615               (clobber (reg:CC 21))])]
2616  ""
2617  "legitimize_operands (IOR, operands, QImode);")
2618
2619 (define_insn "*iorqi3_clobber"
2620   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2621         (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2622                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2623    (clobber (reg:CC 21))]
2624   "valid_operands (IOR, operands, QImode)"
2625   "@
2626    or\\t%2,%0
2627    or3\\t%2,%1,%0
2628    or3\\t%2,%1,%0
2629    or\\t%2,%0
2630    or3\\t%2,%1,%0
2631    or3\\t%2,%1,%0"
2632   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2633    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2634
2635 (define_split
2636   [(set (match_operand:QI 0 "std_reg_operand" "")
2637         (ior:QI (match_operand:QI 1 "src_operand" "")
2638                 (match_operand:QI 2 "lsrc_operand" "")))
2639    (clobber (reg:CC 21))]
2640   "reload_completed"
2641   [(set (match_dup 0)
2642         (ior:QI (match_dup 1)
2643                 (match_dup 2)))]
2644   "")
2645
2646 (define_insn "*iorqi3_test"
2647   [(set (reg:CC 21)
2648         (compare:CC (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2649                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2650                     (const_int 0)))
2651    (clobber (match_scratch:QI 0 "=d,d,d"))]
2652   "valid_operands (IOR, operands, QImode)"
2653   "@
2654    or\\t%2,%0
2655    or3\\t%2,%1,%0
2656    or3\\t%2,%1,%0"
2657   [(set_attr "type" "binarycc,binarycc,binarycc")
2658    (set_attr "data" "uint16,int16,uint16")])
2659
2660 (define_peephole
2661   [(parallel [(set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2662                    (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2663                            (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))
2664               (clobber (reg:CC 21))])
2665    (set (reg:CC 21)
2666         (compare:CC (match_dup 0) (const_int 0)))]
2667   "valid_operands (IOR, operands, QImode)"
2668   "@
2669    or\\t%2,%0
2670    or3\\t%2,%1,%0
2671    or3\\t%2,%1,%0"
2672   [(set_attr "type" "binarycc,binarycc,binarycc")
2673    (set_attr "data" "uint16,int16,uint16")])
2674   
2675 (define_insn "*iorqi3_set"
2676   [(set (reg:CC 21)
2677         (compare:CC (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2678                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2679                     (const_int 0)))
2680    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2681         (ior:QI (match_dup 1)
2682                 (match_dup 2)))]
2683   "valid_operands (IOR, operands, QImode)"
2684   "@
2685    or\\t%2,%0
2686    or3\\t%2,%1,%0
2687    or3\\t%2,%1,%0"
2688   [(set_attr "type" "binarycc,binarycc,binarycc")
2689    (set_attr "data" "uint16,int16,uint16")])
2690
2691 ; This pattern is used for loading symbol references in several parts. 
2692 (define_insn "iorqi3_noclobber"
2693   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,c")
2694         (ior:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2695                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))]
2696   "valid_operands (IOR, operands, QImode)"
2697   "@
2698    or\\t%2,%0
2699    or3\\t%2,%1,%0
2700    or3\\t%2,%1,%0"
2701   [(set_attr "type" "binary,binary,binary")
2702    (set_attr "data" "uint16,int16,uint16")])
2703
2704 ;
2705 ; XOR
2706 ;
2707 (define_expand "xorqi3"
2708   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2709                    (xor:QI (match_operand:QI 1 "src_operand" "")
2710                            (match_operand:QI 2 "lsrc_operand" "")))
2711               (clobber (reg:CC 21))])]
2712  ""
2713  "legitimize_operands (XOR, operands, QImode);")
2714
2715 (define_insn "*xorqi3_clobber"
2716   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2717         (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>,0,rR,rS<>")
2718                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>,rLm,JR,rS<>")))
2719    (clobber (reg:CC 21))]
2720   "valid_operands (XOR, operands, QImode)"
2721   "@
2722    xor\\t%2,%0
2723    xor3\\t%2,%1,%0
2724    xor3\\t%2,%1,%0
2725    xor\\t%2,%0
2726    xor3\\t%2,%1,%0
2727    xor3\\t%2,%1,%0"
2728   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")
2729    (set_attr "data" "uint16,int16,uint16,uint16,int16,uint16")])
2730
2731 (define_insn "*xorqi3_noclobber"
2732   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2733         (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2734                 (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>")))]
2735   "valid_operands (XOR, operands, QImode)"
2736   "@
2737    xor\\t%2,%0
2738    xor3\\t%2,%1,%0
2739    xor3\\t%2,%1,%0"
2740   [(set_attr "type" "binary,binary,binary")
2741    (set_attr "data" "uint16,int16,uint16")])
2742
2743 (define_split
2744   [(set (match_operand:QI 0 "std_reg_operand" "")
2745         (xor:QI (match_operand:QI 1 "src_operand" "")
2746                 (match_operand:QI 2 "lsrc_operand" "")))
2747    (clobber (reg:CC 21))]
2748   "reload_completed"
2749   [(set (match_dup 0)
2750         (xor:QI (match_dup 1)
2751                 (match_dup 2)))]
2752   "")
2753
2754 (define_insn "*xorqi3_test"
2755   [(set (reg:CC 21)
2756         (compare:CC (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2757                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2758                     (const_int 0)))
2759    (clobber (match_scratch:QI 0 "=d,d,d"))]
2760   "valid_operands (XOR, operands, QImode)"
2761   "@
2762    xor\\t%2,%0
2763    xor3\\t%2,%1,%0
2764    xor3\\t%2,%1,%0"
2765   [(set_attr "type" "binarycc,binarycc,binarycc")
2766    (set_attr "data" "uint16,int16,uint16")])
2767
2768 (define_insn "*xorqi3_set"
2769   [(set (reg:CC 21)
2770         (compare:CC (xor:QI (match_operand:QI 1 "src_operand" "%0,rR,rS<>")
2771                             (match_operand:QI 2 "lsrc_operand" "rLm,JR,rS<>"))
2772                     (const_int 0)))
2773    (set (match_operand:QI 0 "ext_reg_operand" "=d,d,d")
2774         (xor:QI (match_dup 1)
2775                 (match_dup 2)))]
2776   "valid_operands (XOR, operands, QImode)"
2777   "@
2778    xor\\t%2,%0
2779    xor3\\t%2,%1,%0
2780    xor3\\t%2,%1,%0"
2781   [(set_attr "type" "binarycc,binarycc,binarycc")
2782    (set_attr "data" "uint16,int16,uint16")])
2783
2784 ;
2785 ; LSH/ASH (left)
2786 ;
2787 ; The C3x and C4x have two shift instructions ASH and LSH
2788 ; If the shift count is positive, a left shift is performed
2789 ; otherwise a right shift is performed.  The number of bits
2790 ; shifted is determined by the seven LSBs of the shift count.
2791 ; If the absolute value of the count is 32 or greater, the result
2792 ; using the LSH instruction is zero; with the ASH insn the result
2793 ; is zero or negative 1.   Note that the ISO C standard allows 
2794 ; the result to be machine dependent whenever the shift count
2795 ; exceeds the size of the object.
2796 (define_expand "ashlqi3"
2797   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2798                    (ashift:QI (match_operand:QI 1 "src_operand" "")
2799                               (match_operand:QI 2 "src_operand" "")))
2800               (clobber (reg:CC 21))])]
2801  ""
2802  "legitimize_operands (ASHIFT, operands, QImode);")
2803
2804 (define_insn "*ashlqi3_clobber"
2805   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2806         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2807                    (match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")))
2808    (clobber (reg:CC 21))]
2809   "valid_operands (ASHIFT, operands, QImode)"
2810   "@
2811    ash\\t%2,%0
2812    ash3\\t%2,%1,%0
2813    ash3\\t%2,%1,%0
2814    ash\\t%2,%0
2815    ash3\\t%2,%1,%0
2816    ash3\\t%2,%1,%0"
2817   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2818 ; Default to int16 data attr.
2819
2820 (define_insn "*ashlqi3_set"
2821   [(set (reg:CC 21)
2822         (compare:CC
2823           (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2824                      (match_operand:QI 2 "src_operand" "rIm,JR,rS<>"))
2825           (const_int 0)))
2826    (set (match_operand:QI 0 "reg_operand" "=d,d,d")
2827         (ashift:QI (match_dup 1)
2828                    (match_dup 2)))]
2829   "valid_operands (ASHIFT, operands, QImode)"
2830   "@
2831    ash\\t%2,%0
2832    ash3\\t%2,%1,%0
2833    ash3\\t%2,%1,%0"
2834   [(set_attr "type" "binarycc,binarycc,binarycc")])
2835 ; Default to int16 data attr.
2836
2837 (define_insn "ashlqi3_noclobber"
2838   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2839         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2840                    (match_operand:QI 2 "src_operand" "rIm,JR,rS<>")))]
2841   "valid_operands (ASHIFT, operands, QImode)"
2842   "@
2843    ash\\t%2,%0
2844    ash3\\t%2,%1,%0
2845    ash3\\t%2,%1,%0"
2846   [(set_attr "type" "binary,binary,binary")])
2847 ; Default to int16 data attr.
2848
2849 (define_split
2850   [(set (match_operand:QI 0 "std_reg_operand" "")
2851         (ashift:QI (match_operand:QI 1 "src_operand" "")
2852                    (match_operand:QI 2 "src_operand" "")))
2853    (clobber (reg:CC 21))]
2854   "reload_completed"
2855   [(set (match_dup 0)
2856         (ashift:QI (match_dup 1)
2857                    (match_dup 2)))]
2858   "")
2859
2860 ; This is only used by lshrhi3_reg where we need a LSH insn that will
2861 ; shift both ways.
2862 (define_insn "*lshlqi3_clobber"
2863   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2864         (ashift:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2865                    (unspec:QI [(match_operand:QI 2 "src_operand" "rIm,JR,rS<>,rIm,JR,rS<>")] 3)))
2866    (clobber (reg:CC 21))]
2867   "valid_operands (ASHIFT, operands, QImode)"
2868   "@
2869    lsh\\t%2,%0
2870    lsh3\\t%2,%1,%0
2871    lsh3\\t%2,%1,%0
2872    lsh\\t%2,%0
2873    lsh3\\t%2,%1,%0
2874    lsh3\\t%2,%1,%0"
2875   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2876 ; Default to int16 data attr.
2877
2878 ;
2879 ; LSH (right)
2880 ;
2881 ; Logical right shift on the C[34]x works by negating the shift count,
2882 ; then emitting a right shift with the shift count negated.  This means
2883 ; that all actual shift counts in the RTL will be positive.
2884 ;
2885 (define_expand "lshrqi3"
2886   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
2887                    (lshiftrt:QI (match_operand:QI 1 "src_operand" "")
2888                                 (match_operand:QI 2 "src_operand" "")))
2889               (clobber (reg:CC 21))])]
2890   ""
2891   "legitimize_operands (LSHIFTRT, operands, QImode);")
2892
2893
2894 (define_insn "*lshrqi3_24_clobber"
2895   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2896         (lshiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2897                      (const_int 24)))
2898    (clobber (reg:CC 21))]
2899   "! TARGET_C3X"
2900   "lbu3\\t%1,%0"
2901   [(set_attr "type" "unarycc")])
2902
2903
2904 (define_insn "*ashrqi3_24_clobber"
2905   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2906         (ashiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2907                      (const_int 24)))
2908    (clobber (reg:CC 21))]
2909   "! TARGET_C3X"
2910   "lb3\\t%1,%0"
2911   [(set_attr "type" "unarycc")])
2912
2913
2914 (define_insn "lshrqi3_16_clobber"
2915   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2916         (lshiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2917                      (const_int 16)))
2918    (clobber (reg:CC 21))]
2919   "! TARGET_C3X"
2920   "lhu1\\t%1,%0"
2921   [(set_attr "type" "unarycc")])
2922
2923
2924 (define_insn "*ashrqi3_16_clobber"
2925   [(set (match_operand:QI 0 "reg_operand" "=d,c")
2926         (ashiftrt:QI (match_operand:QI 1 "src_operand" "mr,mr")
2927                      (const_int 16)))
2928    (clobber (reg:CC 21))]
2929   "! TARGET_C3X"
2930   "lh1\\t%1,%0"
2931   [(set_attr "type" "unarycc")])
2932
2933
2934 ; When the shift count is greater than the size of the word
2935 ; the result can be implementation specific
2936 (define_insn "*lshrqi3_const_clobber"
2937   [(set (match_operand:QI 0 "reg_operand" "=d,c,?d,?c")
2938         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,0,r,r")
2939                      (match_operand:QI 2 "const_int_operand" "n,n,J,J")))
2940    (clobber (reg:CC 21))]
2941   "valid_operands (LSHIFTRT, operands, QImode)"
2942   "@
2943    lsh\\t%n2,%0
2944    lsh\\t%n2,%0
2945    lsh3\\t%n2,%1,%0
2946    lsh3\\t%n2,%1,%0"
2947   [(set_attr "type" "binarycc,binary,binarycc,binary")])
2948
2949 (define_insn "*lshrqi3_const_noclobber"
2950   [(set (match_operand:QI 0 "std_reg_operand" "=c,?c")
2951         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
2952                      (match_operand:QI 2 "const_int_operand" "n,J")))]
2953   "valid_operands (LSHIFTRT, operands, QImode)"
2954   "@
2955    lsh\\t%n2,%0
2956    lsh3\\t%n2,%1,%0"
2957   [(set_attr "type" "binary,binary")])
2958
2959 ; When the shift count is greater than the size of the word
2960 ; the result can be implementation specific
2961 (define_insn "*lshrqi3_const_set"
2962   [(set (reg:CC 21)
2963         (compare:CC
2964           (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
2965                        (match_operand:QI 2 "const_int_operand" "n,J"))
2966           (const_int 0)))
2967    (set (match_operand:QI 0 "reg_operand" "=?d,d")
2968         (lshiftrt:QI (match_dup 1)
2969                      (match_dup 2)))]
2970   "valid_operands (LSHIFTRT, operands, QImode)"
2971   "@
2972    lsh\\t%n2,%0
2973    lsh3\\t%n2,%1,%0"
2974   [(set_attr "type" "binarycc,binarycc")])
2975
2976 (define_insn "*lshrqi3_nonconst_clobber"
2977   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
2978         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
2979                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>,rm,R,rS<>"))))
2980    (clobber (reg:CC 21))]
2981   "valid_operands (LSHIFTRT, operands, QImode)"
2982   "@
2983    lsh\\t%2,%0
2984    lsh3\\t%2,%1,%0
2985    lsh3\\t%2,%1,%0
2986    lsh\\t%2,%0
2987    lsh3\\t%2,%1,%0
2988    lsh3\\t%2,%1,%0"
2989   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
2990 ; Default to int16 data attr.
2991
2992 (define_insn "*lshrqi3_nonconst_noclobber"
2993   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
2994         (lshiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
2995                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>"))))]
2996   "valid_operands (LSHIFTRT, operands, QImode)"
2997   "@
2998    lsh\\t%2,%0
2999    lsh3\\t%2,%1,%0
3000    lsh3\\t%2,%1,%0"
3001   [(set_attr "type" "binary,binary,binary")])
3002 ; Default to int16 data attr.
3003
3004 ;
3005 ; ASH (right)
3006 ;
3007 ; Arithmetic right shift on the C[34]x works by negating the shift count,
3008 ; then emitting a right shift with the shift count negated.  This means
3009 ; that all actual shift counts in the RTL will be positive.
3010
3011 (define_expand "ashrqi3"
3012   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3013                    (ashiftrt:QI (match_operand:QI 1 "src_operand" "")
3014                                 (match_operand:QI 2 "src_operand" "")))
3015               (clobber (reg:CC 21))])]
3016   ""
3017   "legitimize_operands (ASHIFTRT, operands, QImode);")
3018
3019 ; When the shift count is greater than the size of the word
3020 ; the result can be implementation specific
3021 (define_insn "*ashrqi3_const_clobber"
3022   [(set (match_operand:QI 0 "reg_operand" "=d,c,?d,?c")
3023         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,0,r,r")
3024                      (match_operand:QI 2 "const_int_operand" "n,n,J,J")))
3025    (clobber (reg:CC 21))]
3026   "valid_operands (ASHIFTRT, operands, QImode)"
3027   "@
3028    ash\\t%n2,%0
3029    ash\\t%n2,%0
3030    ash3\\t%n2,%1,%0
3031    ash3\\t%n2,%1,%0"
3032   [(set_attr "type" "binarycc,binary,binarycc,binary")])
3033
3034 (define_insn "*ashrqi3_const_noclobber"
3035   [(set (match_operand:QI 0 "std_reg_operand" "=c,?c")
3036         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
3037                      (match_operand:QI 2 "const_int_operand" "n,J")))]
3038   "valid_operands (ASHIFTRT, operands, QImode)"
3039   "@
3040    ash\\t%n2,%0
3041    ash3\\t%n2,%1,%0"
3042   [(set_attr "type" "binarycc,binarycc")])
3043
3044 ; When the shift count is greater than the size of the word
3045 ; the result can be implementation specific
3046 (define_insn "*ashrqi3_const_set"
3047   [(set (reg:CC 21)
3048         (compare:CC
3049           (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,r")
3050                        (match_operand:QI 2 "const_int_operand" "n,J"))
3051           (const_int 0)))
3052    (set (match_operand:QI 0 "reg_operand" "=?d,d")
3053         (ashiftrt:QI (match_dup 1)
3054                      (match_dup 2)))]
3055   "valid_operands (ASHIFTRT, operands, QImode)"
3056   "@
3057    ash\\t%n2,%0
3058    ash3\\t%n2,%1,%0"
3059   [(set_attr "type" "binarycc,binarycc")])
3060
3061 (define_insn "*ashrqi3_nonconst_clobber"
3062   [(set (match_operand:QI 0 "reg_operand" "=d,d,?d,c,c,?c")
3063         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>,0,rR,rS<>")
3064                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>,rm,R,rS<>"))))
3065    (clobber (reg:CC 21))]
3066   "valid_operands (ASHIFTRT, operands, QImode)"
3067   "@
3068    ash\\t%2,%0
3069    ash3\\t%2,%1,%0
3070    ash3\\t%2,%1,%0
3071    ash\\t%2,%0
3072    ash3\\t%2,%1,%0
3073    ash3\\t%2,%1,%0"
3074   [(set_attr "type" "binarycc,binarycc,binarycc,binary,binary,binary")])
3075 ; Default to int16 data attr.
3076
3077 (define_insn "*ashrqi3_nonconst_noclobber"
3078   [(set (match_operand:QI 0 "std_reg_operand" "=c,c,?c")
3079         (ashiftrt:QI (match_operand:QI 1 "src_operand" "0,rR,rS<>")
3080                      (neg:QI (match_operand:QI 2 "src_operand" "rm,R,rS<>"))))]
3081   "valid_operands (ASHIFTRT, operands, QImode)"
3082   "@
3083    ash\\t%2,%0
3084    ash3\\t%2,%1,%0
3085    ash3\\t%2,%1,%0"
3086   [(set_attr "type" "binary,binary,binary")])
3087 ; Default to int16 data attr.
3088
3089 ;
3090 ; CMPI
3091 ;
3092 ; Unfortunately the C40 doesn't allow cmpi3 7, *ar0++ so the next best
3093 ; thing would be to get the small constant loaded into a register (say r0)
3094 ; so that it could be hoisted out of the loop so that we only
3095 ; would need to do cmpi3 *ar0++, r0.  Now the loop optimisation pass
3096 ; comes before the flow pass (which finds autoincrements) so we're stuck.
3097 ; Ideally, GCC requires another loop optimisation pass (preferably after
3098 ; reload) so that it can hoist invariants out of loops.
3099 ; The current solution modifies legitimize_operands () so that small
3100 ; constants are forced into a pseudo register.
3101
3102 (define_expand "cmpqi"
3103   [(set (reg:CC 21)
3104         (compare:CC (match_operand:QI 0 "src_operand" "")
3105                     (match_operand:QI 1 "src_operand" "")))]
3106   ""
3107   "legitimize_operands (COMPARE, operands, QImode);
3108    c4x_compare_op0 = operands[0];
3109    c4x_compare_op1 = operands[1];
3110    DONE;")
3111
3112 (define_insn "*cmpqi_test"
3113   [(set (reg:CC 21)
3114         (compare:CC (match_operand:QI 0 "src_operand" "r,rR,rS<>")
3115                     (match_operand:QI 1 "src_operand" "rIm,JR,rS<>")))]
3116   "valid_operands (COMPARE, operands, QImode)"
3117   "@
3118    cmpi\\t%1,%0
3119    cmpi3\\t%1,%0
3120    cmpi3\\t%1,%0"
3121   [(set_attr "type" "compare,compare,compare")])
3122
3123 (define_insn "*cmpqi_test_noov"
3124   [(set (reg:CC_NOOV 21)
3125         (compare:CC_NOOV (match_operand:QI 0 "src_operand" "r,rR,rS<>")
3126                          (match_operand:QI 1 "src_operand" "rIm,JR,rS<>")))]
3127   "valid_operands (COMPARE, operands, QImode)"
3128   "@
3129    cmpi\\t%1,%0
3130    cmpi3\\t%1,%0
3131    cmpi3\\t%1,%0"
3132   [(set_attr "type" "compare,compare,compare")])
3133
3134
3135 ;
3136 ; BIT-FIELD INSTRUCTIONS
3137 ;
3138
3139 ;
3140 ; LBx/LHw (C4x only)
3141 ;
3142 (define_expand "extv"
3143   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3144                    (sign_extract:QI (match_operand:QI 1 "src_operand" "")
3145                                     (match_operand:QI 2 "const_int_operand" "")
3146                                     (match_operand:QI 3 "const_int_operand" "")))
3147               (clobber (reg:CC 21))])]
3148  "! TARGET_C3X"
3149  "if ((INTVAL (operands[2]) != 8 && INTVAL (operands[2]) != 16)
3150       || (INTVAL (operands[3]) % INTVAL (operands[2]) != 0))
3151         FAIL;
3152  ")
3153
3154 (define_insn "*extv_clobber"
3155   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3156         (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm,rLm")
3157                          (match_operand:QI 2 "const_int_operand" "n,n")
3158                          (match_operand:QI 3 "const_int_operand" "n,n")))
3159    (clobber (reg:CC 21))]
3160   "! TARGET_C3X
3161    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3162    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3163   "*
3164    if (INTVAL (operands[2]) == 8)
3165      {
3166        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3167        return \"lb%3\\t%1,%0\";
3168      }
3169    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3170    return \"lh%3\\t%1,%0\";
3171   "
3172   [(set_attr "type" "binarycc,binary")
3173    (set_attr "data" "int16,int16")])
3174
3175 (define_insn "*extv_clobber_test"
3176   [(set (reg:CC 21)
3177         (compare:CC (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3178                                      (match_operand:QI 2 "const_int_operand" "n")
3179                                      (match_operand:QI 3 "const_int_operand" "n"))
3180                     (const_int 0)))
3181    (clobber (match_scratch:QI 0 "=d"))]
3182   "! TARGET_C3X
3183    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3184    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3185   "*
3186    if (INTVAL (operands[2]) == 8)
3187      {
3188        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3189        return \"lb%3\\t%1,%0\";
3190      }
3191    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3192    return \"lh%3\\t%1,%0\";
3193   "
3194   [(set_attr "type" "binarycc")
3195    (set_attr "data" "int16")])
3196
3197 (define_insn "*extv_clobber_set"
3198   [(set (reg:CC 21)
3199         (compare:CC (sign_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3200                                      (match_operand:QI 2 "const_int_operand" "n")
3201                                      (match_operand:QI 3 "const_int_operand" "n"))
3202                     (const_int 0)))
3203    (set (match_operand:QI 0 "reg_operand" "=d")
3204         (sign_extract:QI (match_dup 1)
3205                          (match_dup 2)
3206                          (match_dup 3)))]
3207   "! TARGET_C3X
3208    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3209    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3210   "*
3211    if (INTVAL (operands[2]) == 8)
3212      {
3213        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3214        return \"lb%3\\t%1,%0\";
3215      }
3216    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3217    return \"lh%3\\t%1,%0\";
3218   "
3219   [(set_attr "type" "binarycc")
3220    (set_attr "data" "int16")])
3221
3222 ;
3223 ; LBUx/LHUw (C4x only)
3224 ;
3225 (define_expand "extzv"
3226   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
3227                    (zero_extract:QI (match_operand:QI 1 "src_operand" "")
3228                                     (match_operand:QI 2 "const_int_operand" "")
3229                                     (match_operand:QI 3 "const_int_operand" "")))
3230               (clobber (reg:CC 21))])]
3231  "! TARGET_C3X"
3232  "if ((INTVAL (operands[2]) != 8 && INTVAL (operands[2]) != 16)
3233       || (INTVAL (operands[3]) % INTVAL (operands[2]) != 0))
3234         FAIL;
3235  ")
3236
3237 (define_insn "*extzv_clobber"
3238   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3239         (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm,rLm")
3240                          (match_operand:QI 2 "const_int_operand" "n,n")
3241                          (match_operand:QI 3 "const_int_operand" "n,n")))
3242    (clobber (reg:CC 21))]
3243   "! TARGET_C3X
3244    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3245    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3246   "*
3247    if (INTVAL (operands[2]) == 8)
3248      {
3249        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3250        return \"lbu%3\\t%1,%0\";
3251      }
3252    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3253    return \"lhu%3\\t%1,%0\";
3254   "
3255   [(set_attr "type" "binarycc,binary")
3256    (set_attr "data" "uint16,uint16")])
3257
3258 (define_insn "*extzv_test"
3259   [(set (reg:CC 21)
3260         (compare:CC (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3261                                      (match_operand:QI 2 "const_int_operand" "n")
3262                                      (match_operand:QI 3 "const_int_operand" "n"))
3263                     (const_int 0)))
3264    (clobber (match_scratch:QI 0 "=d"))]
3265   "! TARGET_C3X
3266    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3267    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3268   "*
3269    if (INTVAL (operands[2]) == 8)
3270      {
3271        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3272        return \"lbu%3\\t%1,%0\";
3273      }
3274    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3275    return \"lhu%3\\t%1,%0\";
3276   "
3277   [(set_attr "type" "binarycc")
3278    (set_attr "data" "uint16")])
3279
3280 (define_insn "*extzv_set"
3281   [(set (reg:CC 21)
3282         (compare:CC (zero_extract:QI (match_operand:QI 1 "src_operand" "rLm")
3283                                      (match_operand:QI 2 "const_int_operand" "n")
3284                                      (match_operand:QI 3 "const_int_operand" "n"))
3285                     (const_int 0)))
3286    (set (match_operand:QI 0 "ext_reg_operand" "=d")
3287         (zero_extract:QI (match_dup 1)
3288                          (match_dup 2)
3289                          (match_dup 3)))]
3290   "! TARGET_C3X
3291    && (INTVAL (operands[2]) == 8 || INTVAL (operands[2]) == 16)
3292    && (INTVAL (operands[3]) % INTVAL (operands[2]) == 0)"
3293   "*
3294    if (INTVAL (operands[2]) == 8)
3295      {
3296         /* 8 bit extract.  */
3297        operands[3] = GEN_INT (INTVAL (operands[3]) / 8);
3298        return \"lbu%3\\t%1,%0\";
3299      }
3300    /* 16 bit extract.  */
3301    operands[3] = GEN_INT (INTVAL (operands[3]) / 16);
3302    return \"lhu%3\\t%1,%0\";
3303   "
3304   [(set_attr "type" "binarycc")
3305    (set_attr "data" "uint16")])
3306
3307 ;
3308 ; MBx/MHw (C4x only)
3309 ;
3310 (define_expand "insv"
3311   [(parallel [(set (zero_extract:QI (match_operand:QI 0 "reg_operand" "")
3312                                     (match_operand:QI 1 "const_int_operand" "")
3313                                     (match_operand:QI 2 "const_int_operand" ""))
3314                    (match_operand:QI 3 "src_operand" ""))
3315               (clobber (reg:CC 21))])]
3316  "! TARGET_C3X"
3317  "if (! (((INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3318          && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0))
3319         || (INTVAL (operands[1]) == 24 && INTVAL (operands[2]) == 8)))
3320     FAIL;
3321  ")
3322
3323 (define_insn "*insv_clobber"
3324   [(set (zero_extract:QI (match_operand:QI 0 "reg_operand" "=d,c")
3325                          (match_operand:QI 1 "const_int_operand" "n,n")
3326                          (match_operand:QI 2 "const_int_operand" "n,n"))
3327         (match_operand:QI 3 "src_operand" "rLm,rLm"))
3328    (clobber (reg:CC 21))]
3329   "! TARGET_C3X
3330    && (((INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3331         && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0))
3332        || (INTVAL (operands[1]) == 24 && INTVAL (operands[2]) == 8))"
3333   "*
3334    if (INTVAL (operands[1]) == 8)
3335      {
3336        /* 8 bit insert.  */
3337        operands[2] = GEN_INT (INTVAL (operands[2]) / 8);
3338        return \"mb%2\\t%3,%0\";
3339      }
3340    else if (INTVAL (operands[1]) == 16)
3341      {
3342        /* 16 bit insert.  */
3343        operands[2] = GEN_INT (INTVAL (operands[2]) / 16);
3344        return \"mh%2\\t%3,%0\";
3345      }
3346    /* 24 bit insert.  */
3347    return \"lwl1\\t%3,%0\";
3348   "
3349   [(set_attr "type" "binarycc,binary")
3350    (set_attr "data" "uint16,uint16")])
3351
3352 (define_peephole
3353   [(parallel [(set (zero_extract:QI (match_operand:QI 0 "ext_reg_operand" "=d")
3354                                     (match_operand:QI 1 "const_int_operand" "n")
3355                                     (match_operand:QI 2 "const_int_operand" "n"))
3356                    (match_operand:QI 3 "src_operand" "rLm"))
3357               (clobber (reg:CC 21))])
3358    (set (reg:CC 21)
3359         (compare:CC (match_dup 0) (const_int 0)))]
3360   "! TARGET_C3X
3361    && (INTVAL (operands[1]) == 8 || INTVAL (operands[1]) == 16)
3362    && (INTVAL (operands[2]) % INTVAL (operands[1]) == 0)"
3363   "*
3364    if (INTVAL (operands[1]) == 8)
3365      {
3366        operands[2] = GEN_INT (INTVAL (operands[2]) / 8);
3367        return \"mb%2\\t%3,%0\";
3368      }
3369    operands[2] = GEN_INT (INTVAL (operands[2]) / 16);
3370    return \"mh%2\\t%3,%0\";
3371   "
3372   [(set_attr "type" "binarycc")
3373    (set_attr "data" "uint16")])
3374
3375
3376 ; TWO OPERAND FLOAT INSTRUCTIONS
3377 ;
3378
3379 ;
3380 ; LDF/STF
3381 ;
3382 ;  If one of the operands is not a register, then we should
3383 ;  emit two insns, using a scratch register.  This will produce
3384 ;  better code in loops if the source operand is invariant, since
3385 ;  the source reload can be optimised out.  During reload we cannot
3386 ;  use change_address or force_reg.
3387 (define_expand "movqf"
3388   [(set (match_operand:QF 0 "src_operand" "")
3389         (match_operand:QF 1 "src_operand" ""))]
3390  ""
3391  "
3392 {
3393   if (c4x_emit_move_sequence (operands, QFmode))
3394     DONE;
3395 }")
3396
3397 ; This can generate invalid stack slot displacements
3398 (define_split
3399  [(set (match_operand:QI 0 "reg_operand" "=r")
3400        (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))]
3401   "reload_completed"
3402   [(set (match_dup 3) (match_dup 1))
3403    (set (match_dup 0) (match_dup 2))]
3404   "operands[2] = assign_stack_temp (QImode, GET_MODE_SIZE (QImode), 0);
3405    operands[3] = copy_rtx (operands[2]);
3406    PUT_MODE (operands[3], QFmode);")
3407
3408
3409 (define_insn "storeqf_int"
3410  [(set (match_operand:QI 0 "reg_operand" "=r")
3411        (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))]
3412  ""
3413  "#"
3414   [(set_attr "type" "multi")])
3415
3416 (define_split
3417  [(parallel [(set (match_operand:QI 0 "reg_operand" "=r")
3418                   (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))
3419              (clobber (reg:CC 21))])]
3420   "reload_completed"
3421   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
3422         (match_dup 1))
3423    (parallel [(set (match_dup 0)
3424                    (mem:QI (post_dec:QI (reg:QI 20))))
3425               (clobber (reg:CC 21))])]
3426   "")
3427
3428
3429 ; We need accurate death notes for this...
3430 ;(define_peephole
3431 ;  [(set (match_operand:QF 0 "reg_operand" "=f")
3432 ;        (match_operand:QF 1 "memory_operand" "m"))
3433 ;   (set (mem:QF (pre_inc:QI (reg:QI 20)))
3434 ;        (match_dup 0))
3435 ;   (parallel [(set (match_operand:QI 2 "reg_operand" "r")
3436 ;                   (mem:QI (post_dec:QI (reg:QI 20))))
3437 ;              (clobber (reg:CC 21))])]
3438 ;  ""
3439 ;  "ldiu\\t%1,%0")
3440
3441 (define_insn "storeqf_int_clobber"
3442  [(parallel [(set (match_operand:QI 0 "reg_operand" "=r")
3443                   (unspec:QI [(match_operand:QF 1 "reg_operand" "f")] 12))
3444              (clobber (reg:CC 21))])]
3445  ""
3446  "#"
3447   [(set_attr "type" "multi")])
3448
3449
3450 ; This can generate invalid stack slot displacements
3451 (define_split
3452  [(set (match_operand:QF 0 "reg_operand" "=f")
3453        (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))]
3454   "reload_completed"
3455   [(set (match_dup 2) (match_dup 1))
3456    (set (match_dup 0) (match_dup 3))]
3457   "operands[2] = assign_stack_temp (QImode, GET_MODE_SIZE (QImode), 0);
3458    operands[3] = copy_rtx (operands[2]);
3459    PUT_MODE (operands[3], QFmode);")
3460
3461
3462 (define_insn "loadqf_int"
3463  [(set (match_operand:QF 0 "reg_operand" "=f")
3464        (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))]
3465  ""
3466  "#"
3467   [(set_attr "type" "multi")])
3468
3469 (define_split
3470  [(parallel [(set (match_operand:QF 0 "reg_operand" "=f")
3471                   (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))
3472              (clobber (reg:CC 21))])]
3473   "reload_completed"
3474   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
3475         (match_dup 1))
3476    (parallel [(set (match_dup 0)
3477                    (mem:QF (post_dec:QI (reg:QI 20))))
3478               (clobber (reg:CC 21))])]
3479   "")
3480
3481 (define_insn "loadqf_int_clobber"
3482  [(parallel [(set (match_operand:QF 0 "reg_operand" "=f")
3483                   (unspec:QF [(match_operand:QI 1 "reg_operand" "r")] 11))
3484              (clobber (reg:CC 21))])]
3485  ""
3486  "#"
3487   [(set_attr "type" "multi")])
3488
3489 ; We must provide an alternative to store to memory in case we have to
3490 ; spill a register.
3491 (define_insn "movqf_noclobber"
3492  [(set (match_operand:QF 0 "dst_operand" "=f,m")
3493        (match_operand:QF 1 "src_operand" "fHm,f"))]
3494  "REG_P (operands[0]) || REG_P (operands[1])"
3495  "@
3496   ldfu\\t%1,%0
3497   stf\\t%1,%0"
3498   [(set_attr "type" "unary,store")])
3499
3500 ;(define_insn "*movqf_clobber"
3501 ;  [(set (match_operand:QF 0 "reg_operand" "=f")
3502 ;        (match_operand:QF 1 "src_operand" "fHm"))
3503 ;   (clobber (reg:CC 21))]
3504 ; "0"
3505 ; "ldf\\t%1,%0"
3506 ;  [(set_attr "type" "unarycc")])
3507
3508 (define_insn "*movqf_test"
3509   [(set (reg:CC 21)
3510         (compare:CC (match_operand:QF 1 "src_operand" "fHm")
3511                     (const_int 0)))
3512    (clobber (match_scratch:QF 0 "=f"))]
3513  ""
3514  "ldf\\t%1,%0"
3515   [(set_attr "type" "unarycc")])
3516
3517 (define_insn "*movqf_set"
3518   [(set (reg:CC 21)
3519         (compare:CC (match_operand:QF 1 "src_operand" "fHm")
3520                     (match_operand:QF 2 "fp_zero_operand" "G")))
3521     (set (match_operand:QF 0 "reg_operand" "=f")
3522          (match_dup 1))]
3523  ""
3524  "ldf\\t%1,%0"
3525   [(set_attr "type" "unarycc")])
3526
3527
3528 (define_insn "*movqf_parallel"
3529  [(set (match_operand:QF 0 "parallel_operand" "=q,S<>!V,q,S<>!V")
3530        (match_operand:QF 1 "parallel_operand" "S<>!V,q,S<>!V,q"))
3531   (set (match_operand:QF 2 "parallel_operand" "=q,S<>!V,S<>!V,q")
3532        (match_operand:QF 3 "parallel_operand" "S<>!V,q,q,S<>!V"))]
3533  "TARGET_PARALLEL && valid_parallel_load_store (operands, QFmode)"
3534  "@
3535   ldf1\\t%1,%0\\n||\\tldf2\\t%3,%2
3536   stf1\\t%1,%0\\n||\\tstf2\\t%3,%2
3537   ldf\\t%1,%0\\n||\\tstf\\t%3,%2
3538   ldf\\t%3,%2\\n||\\tstf\\t%1,%0"
3539   [(set_attr "type" "load_load,store_store,load_store,store_load")])
3540
3541
3542 ;
3543 ; PUSH/POP
3544 ;
3545 (define_insn "*pushqf"
3546   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
3547         (match_operand:QF 0 "reg_operand" "f"))]
3548  ""
3549  "pushf\\t%0"
3550  [(set_attr "type" "push")])
3551
3552 (define_insn "*popqf"
3553   [(set (match_operand:QF 0 "reg_operand" "=f")
3554         (mem:QF (post_dec:QI (reg:QI 20))))
3555    (clobber (reg:CC 21))]
3556  ""
3557  "popf\\t%0"
3558  [(set_attr "type" "pop")])
3559
3560
3561 ;
3562 ; ABSF
3563 ;
3564 (define_expand "absqf2"
3565   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3566                    (abs:QF (match_operand:QF 1 "src_operand" "")))
3567               (clobber (reg:CC_NOOV 21))])]
3568 ""
3569 "")
3570
3571 (define_insn "*absqf2_clobber"
3572   [(set (match_operand:QF 0 "reg_operand" "=f")
3573         (abs:QF (match_operand:QF 1 "src_operand" "fHm")))
3574    (clobber (reg:CC_NOOV 21))]
3575   ""
3576   "absf\\t%1,%0"
3577   [(set_attr "type" "unarycc")])
3578
3579 (define_insn "*absqf2_test"
3580   [(set (reg:CC_NOOV 21)
3581         (compare:CC_NOOV (abs:QF (match_operand:QF 1 "src_operand" "fHm"))
3582                          (match_operand:QF 2 "fp_zero_operand" "G")))
3583    (clobber (match_scratch:QF 0 "=f"))]
3584   ""
3585   "absf\\t%1,%0"
3586   [(set_attr "type" "unarycc")])
3587
3588 (define_insn "*absqf2_set"
3589   [(set (reg:CC_NOOV 21)
3590         (compare:CC_NOOV (abs:QF (match_operand:QF 1 "src_operand" "fHm"))
3591                          (match_operand:QF 2 "fp_zero_operand" "G")))
3592    (set (match_operand:QF 0 "reg_operand" "=f")
3593         (abs:QF (match_dup 1)))]
3594
3595   ""
3596   "absf\\t%1,%0"
3597   [(set_attr "type" "unarycc")])
3598
3599 ;
3600 ; NEGF
3601 ;
3602 (define_expand "negqf2"
3603   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3604                    (neg:QF (match_operand:QF 1 "src_operand" "")))
3605               (clobber (reg:CC_NOOV 21))])]
3606 ""
3607 "")
3608
3609 (define_insn "*negqf2_clobber"
3610   [(set (match_operand:QF 0 "reg_operand" "=f")
3611         (neg:QF (match_operand:QF 1 "src_operand" "fHm")))
3612    (clobber (reg:CC_NOOV 21))]
3613   ""
3614   "negf\\t%1,%0"
3615   [(set_attr "type" "unarycc")])
3616
3617 (define_insn "*negqf2_test"
3618   [(set (reg:CC_NOOV 21)
3619         (compare:CC_NOOV (neg:QF (match_operand:QF 1 "src_operand" "fHm"))
3620                          (match_operand:QF 2 "fp_zero_operand" "G")))
3621    (clobber (match_scratch:QF 0 "=f"))]
3622   ""
3623   "negf\\t%1,%0"
3624   [(set_attr "type" "unarycc")])
3625
3626 (define_insn "*negqf2_set"
3627   [(set (reg:CC_NOOV 21)
3628         (compare:CC_NOOV (neg:QF (match_operand:QF 1 "src_operand" "fHm"))
3629                          (match_operand:QF 2 "fp_zero_operand" "G")))
3630    (set (match_operand:QF 0 "reg_operand" "=f")
3631         (neg:QF (match_dup 1)))]
3632   ""
3633   "negf\\t%1,%0"
3634   [(set_attr "type" "unarycc")])
3635
3636 ;
3637 ; FLOAT
3638 ;
3639 (define_insn "floatqiqf2"
3640   [(set (match_operand:QF 0 "reg_operand" "=f")
3641         (float:QF (match_operand:QI 1 "src_operand" "rIm")))
3642    (clobber (reg:CC 21))]
3643  ""
3644  "float\\t%1,%0"
3645   [(set_attr "type" "unarycc")])
3646
3647 (define_insn "*floatqiqf2_set"
3648   [(set (reg:CC 21)
3649         (compare:CC (float:QF (match_operand:QI 1 "src_operand" "rIm"))
3650                     (match_operand:QF 2 "fp_zero_operand" "G")))
3651    (set (match_operand:QF 0 "reg_operand" "=f")
3652         (float:QF (match_dup 1)))]
3653  ""
3654  "float\\t%1,%0"
3655   [(set_attr "type" "unarycc")])
3656
3657 ; Unsigned conversions are a little tricky because we need to
3658 ; add the value for the high bit if necessary.
3659
3660 ;
3661 (define_expand "floatunsqiqf2"
3662  [(set (match_dup 2) (match_dup 3))
3663   (parallel [(set (reg:CC 21)
3664                   (compare:CC (float:QF (match_operand:QI 1 "src_operand" ""))
3665                               (match_dup 3)))
3666              (set (match_dup 4)
3667                   (float:QF (match_dup 1)))])
3668   (set (match_dup 6)
3669        (if_then_else:QF (lt (reg:CC 21) (const_int 0))
3670                         (match_dup 5)
3671                         (match_dup 2)))
3672   (parallel [(set (match_operand:QF 0 "reg_operand" "")
3673                   (plus:QF (match_dup 6) (match_dup 4)))
3674              (clobber (reg:CC_NOOV 21))])]
3675  ""
3676  "operands[2] = gen_reg_rtx (QFmode);
3677   operands[3] = CONST0_RTX (QFmode); 
3678   operands[4] = gen_reg_rtx (QFmode);
3679   operands[5] = gen_reg_rtx (QFmode);
3680   operands[6] = gen_reg_rtx (QFmode);
3681   emit_move_insn (operands[5], 
3682    immed_real_const_1 (REAL_VALUE_ATOF (\"4294967296.0\", QFmode), QFmode));")
3683
3684 (define_insn "floatqihf2"
3685   [(set (match_operand:HF 0 "reg_operand" "=h")
3686         (float:HF (match_operand:QI 1 "src_operand" "rIm")))
3687    (clobber (reg:CC 21))]
3688  ""
3689  "float\\t%1,%0"
3690   [(set_attr "type" "unarycc")])
3691
3692 ;
3693 ; FIX
3694 ;
3695 (define_insn "fixqfqi_clobber"
3696   [(set (match_operand:QI 0 "reg_operand" "=d,c")
3697         (fix:QI (match_operand:QF 1 "src_operand" "fHm,fHm")))
3698    (clobber (reg:CC 21))]
3699  ""
3700  "fix\\t%1,%0"
3701   [(set_attr "type" "unarycc")])
3702
3703 (define_insn "*fixqfqi_set"
3704   [(set (reg:CC 21)
3705         (compare:CC (fix:QI (match_operand:QF 1 "src_operand" "fHm"))
3706                     (const_int 0)))
3707    (set (match_operand:QI 0 "ext_reg_operand" "=d")
3708         (fix:QI (match_dup 1)))]
3709  ""
3710  "fix\\t%1,%0"
3711   [(set_attr "type" "unarycc")])
3712
3713 ;
3714 ; The C[34]x fix instruction implements a floor, not a straight trunc,
3715 ; so we have to invert the number, fix it, and reinvert it if negative
3716 ;
3717 (define_expand "fix_truncqfqi2"
3718   [(parallel [(set (match_dup 2)
3719                    (fix:QI (match_operand:QF 1 "src_operand" "")))
3720               (clobber (reg:CC 21))])
3721    (parallel [(set (match_dup 3) (neg:QF (match_dup 1)))
3722               (clobber (reg:CC_NOOV 21))])
3723    (parallel [(set (match_dup 4) (fix:QI (match_dup 3)))
3724               (clobber (reg:CC 21))])
3725    (parallel [(set (reg:CC_NOOV 21)
3726                    (compare:CC_NOOV (neg:QI (match_dup 4)) (const_int 0)))
3727               (set (match_dup 5) (neg:QI (match_dup 4)))])
3728    (set (match_dup 2)
3729         (if_then_else:QI (le (reg:CC 21) (const_int 0))
3730                          (match_dup 5)
3731                          (match_dup 2)))
3732    (set (match_operand:QI 0 "reg_operand" "=r") (match_dup 2))]
3733  ""
3734  "if (TARGET_FAST_FIX)
3735     {
3736        emit_insn (gen_fixqfqi_clobber (operands[0], operands[1]));
3737        DONE;
3738     }
3739   operands[2] = gen_reg_rtx (QImode);
3740   operands[3] = gen_reg_rtx (QFmode);
3741   operands[4] = gen_reg_rtx (QImode);
3742   operands[5] = gen_reg_rtx (QImode);
3743  ")
3744
3745 (define_expand "fix_truncqfhi2"
3746   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
3747                    (fix:HI (match_operand:QF 1 "src_operand" "")))
3748               (clobber (reg:CC 21))])]
3749   ""
3750   "c4x_emit_libcall (FIX_TRUNCQFHI2_LIBCALL, FIX, HImode, QFmode, 2, operands);
3751    DONE;")
3752
3753 ; Is this allowed to be implementation dependent?  If so, we can
3754 ; omit the conditional load.  Otherwise we should emit a split.
3755 (define_expand "fixuns_truncqfqi2"
3756  [(parallel [(set (reg:CC 21)
3757                   (compare:CC (fix:QI (match_operand:QF 1 "src_operand" "fHm"))
3758                               (const_int 0)))
3759              (set (match_dup 2)
3760                   (fix:QI (match_dup 1)))])
3761   (set (match_operand:QI 0 "reg_operand" "=r")
3762        (if_then_else:QI (lt (reg:CC 21) (const_int 0))
3763                         (const_int 0)
3764                         (match_dup 2)))]
3765  ""
3766  "operands[2] = gen_reg_rtx (QImode);")
3767
3768 (define_expand "fixuns_truncqfhi2"
3769   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
3770                    (unsigned_fix:HI (match_operand:QF 1 "src_operand" "")))
3771               (clobber (reg:CC 21))])]
3772   ""
3773   "c4x_emit_libcall (FIXUNS_TRUNCQFHI2_LIBCALL, UNSIGNED_FIX, 
3774                      HImode, QFmode, 2, operands);
3775    DONE;")
3776
3777 ;
3778 ; RCPF
3779 ;
3780 (define_insn "*rcpfqf_clobber"
3781   [(set (match_operand:QF 0 "reg_operand" "=f")
3782         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] 5))
3783    (clobber (reg:CC_NOOV 21))]
3784   "! TARGET_C3X"
3785   "rcpf\\t%1,%0"
3786   [(set_attr "type" "unarycc")])
3787
3788 ;
3789 ; RSQRF
3790 ;
3791 (define_insn "*rsqrfqf_clobber"
3792   [(set (match_operand:QF 0 "reg_operand" "=f")
3793         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] 10))
3794    (clobber (reg:CC_NOOV 21))]
3795   "! TARGET_C3X"
3796   "rsqrf\\t%1,%0"
3797   [(set_attr "type" "unarycc")])
3798
3799 ;
3800 ; RNDF
3801 ;
3802 (define_insn "*rndqf_clobber"
3803   [(set (match_operand:QF 0 "reg_operand" "=f")
3804         (unspec:QF [(match_operand:QF 1 "src_operand" "fHm")] 6))
3805    (clobber (reg:CC_NOOV 21))]
3806   "! TARGET_C3X"
3807   "rnd\\t%1,%0"
3808   [(set_attr "type" "unarycc")])
3809
3810
3811 ; Inlined float square root for C4x
3812 (define_expand "sqrtqf2_inline"
3813   [(parallel [(set (match_dup 2)
3814                    (unspec:QF [(match_operand:QF 1 "src_operand" "")] 10))
3815               (clobber (reg:CC_NOOV 21))])
3816    (parallel [(set (match_dup 3) (mult:QF (match_dup 5) (match_dup 1)))
3817               (clobber (reg:CC_NOOV 21))])
3818    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
3819               (clobber (reg:CC_NOOV 21))])
3820    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 4)))
3821               (clobber (reg:CC_NOOV 21))])
3822    (parallel [(set (match_dup 4) (minus:QF (match_dup 6) (match_dup 4)))
3823               (clobber (reg:CC_NOOV 21))])
3824    (parallel [(set (match_dup 2) (mult:QF (match_dup 2) (match_dup 4)))
3825               (clobber (reg:CC_NOOV 21))])
3826    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
3827               (clobber (reg:CC_NOOV 21))])
3828    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 4)))
3829               (clobber (reg:CC_NOOV 21))])
3830    (parallel [(set (match_dup 4) (minus:QF (match_dup 6) (match_dup 4)))
3831               (clobber (reg:CC_NOOV 21))])
3832    (parallel [(set (match_dup 2) (mult:QF (match_dup 2) (match_dup 4)))
3833               (clobber (reg:CC_NOOV 21))])
3834    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 1)))
3835               (clobber (reg:CC_NOOV 21))])
3836    (parallel [(set (match_operand:QF 0 "reg_operand" "")
3837                    (unspec:QF [(match_dup 4)] 6))
3838               (clobber (reg:CC_NOOV 21))])]
3839   "! TARGET_C3X"
3840   "if (! reload_in_progress
3841        && ! reg_operand (operands[1], QFmode))
3842      operands[1] = force_reg (QFmode, operands[1]);
3843    operands[2] = gen_reg_rtx (QFmode);
3844    operands[3] = gen_reg_rtx (QFmode);
3845    operands[4] = gen_reg_rtx (QFmode);
3846    operands[5] = immed_real_const_1 (REAL_VALUE_ATOF (\"0.5\", QFmode),
3847                                      QFmode);
3848    operands[6] = immed_real_const_1 (REAL_VALUE_ATOF (\"1.5\", QFmode),
3849                                      QFmode);")
3850
3851 (define_expand "sqrtqf2"
3852   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3853                    (sqrt:QF (match_operand:QF 1 "src_operand" "")))
3854               (clobber (reg:CC 21))])]
3855   "! TARGET_C3X && TARGET_INLINE"
3856   "emit_insn (gen_sqrtqf2_inline (operands[0], operands[1]));
3857    DONE;")
3858
3859 ;
3860 ; THREE OPERAND FLOAT INSTRUCTIONS
3861 ;
3862
3863 ;
3864 ; ADDF
3865 ;
3866 (define_expand "addqf3"
3867   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3868                    (plus:QF (match_operand:QF 1 "src_operand" "")
3869                             (match_operand:QF 2 "src_operand" "")))
3870               (clobber (reg:CC_NOOV 21))])]
3871   ""
3872   "legitimize_operands (PLUS, operands, QFmode);")
3873
3874 (define_insn "*addqf3_clobber"
3875   [(set (match_operand:QF 0 "reg_operand" "=f,f,?f")
3876         (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3877                  (match_operand:QF 2 "src_operand" "fHm,R,fS<>")))
3878    (clobber (reg:CC_NOOV 21))]
3879   "valid_operands (PLUS, operands, QFmode)"
3880   "@
3881    addf\\t%2,%0
3882    addf3\\t%2,%1,%0
3883    addf3\\t%2,%1,%0"
3884   [(set_attr "type" "binarycc,binarycc,binarycc")])
3885
3886 (define_insn "*addqf3_test"
3887   [(set (reg:CC_NOOV 21)
3888         (compare:CC_NOOV (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3889                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
3890                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
3891    (clobber (match_scratch:QF 0 "=f,f,?f"))]
3892   "valid_operands (PLUS, operands, QFmode)"
3893   "@
3894    addf\\t%2,%0
3895    addf3\\t%2,%1,%0
3896    addf3\\t%2,%1,%0"
3897   [(set_attr "type" "binarycc,binarycc,binarycc")])
3898
3899 (define_insn "*addqf3_set"
3900   [(set (reg:CC_NOOV 21)
3901         (compare:CC_NOOV (plus:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3902                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
3903                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
3904    (set (match_operand:QF 0 "reg_operand" "=f,f,?f")
3905         (plus:QF (match_dup 1)
3906                  (match_dup 2)))]
3907   "valid_operands (PLUS, operands, QFmode)"
3908   "@
3909    addf\\t%2,%0
3910    addf3\\t%2,%1,%0
3911    addf3\\t%2,%1,%0"
3912   [(set_attr "type" "binarycc,binarycc,binarycc")])
3913
3914 ;
3915 ; SUBF/SUBRF
3916 ;
3917 (define_expand "subqf3"
3918   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3919                    (minus:QF (match_operand:QF 1 "src_operand" "")
3920                              (match_operand:QF 2 "src_operand" "")))
3921               (clobber (reg:CC_NOOV 21))])]
3922   ""
3923   "legitimize_operands (MINUS, operands, QFmode);")
3924
3925 (define_insn "*subqf3_clobber"
3926    [(set (match_operand:QF 0 "reg_operand" "=f,f,f,?f")
3927          (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
3928                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>")))
3929    (clobber (reg:CC_NOOV 21))]
3930   "valid_operands (MINUS, operands, QFmode)"
3931   "@
3932    subf\\t%2,%0
3933    subrf\\t%1,%0
3934    subf3\\t%2,%1,%0
3935    subf3\\t%2,%1,%0"
3936   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
3937
3938 (define_insn "*subqf3_test"
3939   [(set (reg:CC_NOOV 21)
3940         (compare:CC_NOOV (minus:QF (match_operand:QF 1 "src_operand" "0,fHm,fR,fS<>")
3941                                    (match_operand:QF 2 "src_operand" "fHm,0,R,fS<>"))
3942                          (match_operand:QF 3 "fp_zero_operand" "G,G,G,G")))
3943    (clobber (match_scratch:QF 0 "=f,f,f,?f"))]
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_set"
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    (set (match_operand:QF 0 "reg_operand" "=f,f,f,?f")
3958         (minus:QF (match_dup 1)
3959                   (match_dup 2)))]
3960   "valid_operands (MINUS, operands, QFmode)"
3961   "@
3962    subf\\t%2,%0
3963    subrf\\t%1,%0
3964    subf3\\t%2,%1,%0
3965    subf3\\t%2,%1,%0"
3966   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
3967
3968 ;
3969 ; MPYF
3970 ;
3971 (define_expand "mulqf3"
3972   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
3973                    (mult:QF (match_operand:QF 1 "src_operand" "")
3974                             (match_operand:QF 2 "src_operand" "")))
3975               (clobber (reg:CC_NOOV 21))])]
3976   ""
3977   "legitimize_operands (MULT, operands, QFmode);")
3978
3979 (define_insn "*mulqf3_clobber"
3980   [(set (match_operand:QF 0 "reg_operand" "=f,f,?f")
3981         (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3982                  (match_operand:QF 2 "src_operand" "fHm,R,fS<>")))
3983    (clobber (reg:CC_NOOV 21))]
3984   "valid_operands (MULT, operands, QFmode)"
3985   "@
3986    mpyf\\t%2,%0
3987    mpyf3\\t%2,%1,%0
3988    mpyf3\\t%2,%1,%0"
3989   [(set_attr "type" "binarycc,binarycc,binarycc")])
3990
3991 (define_insn "*mulqf3_test"
3992   [(set (reg:CC_NOOV 21)
3993         (compare:CC_NOOV (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
3994                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
3995                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
3996    (clobber (match_scratch:QF 0 "=f,f,?f"))]
3997   "valid_operands (MULT, operands, QFmode)"
3998   "@
3999    mpyf\\t%2,%0
4000    mpyf3\\t%2,%1,%0
4001    mpyf3\\t%2,%1,%0"
4002   [(set_attr "type" "binarycc,binarycc,binarycc")])
4003
4004 (define_insn "*mulqf3_set"
4005   [(set (reg:CC_NOOV 21)
4006         (compare:CC_NOOV (mult:QF (match_operand:QF 1 "src_operand" "%0,fR,fS<>")
4007                                   (match_operand:QF 2 "src_operand" "fHm,R,fS<>"))
4008                          (match_operand:QF 3 "fp_zero_operand" "G,G,G")))
4009    (set (match_operand:QF 0 "reg_operand" "=f,f,?f")
4010         (mult:QF (match_dup 1)
4011                  (match_dup 2)))]
4012   "valid_operands (MULT, operands, QFmode)"
4013   "@
4014    mpyf\\t%2,%0
4015    mpyf3\\t%2,%1,%0
4016    mpyf3\\t%2,%1,%0"
4017   [(set_attr "type" "binarycc,binarycc,binarycc")])
4018
4019 ;
4020 ; CMPF
4021 ;
4022 (define_expand "cmpqf"
4023   [(set (reg:CC 21)
4024         (compare:CC (match_operand:QF 0 "src_operand" "")
4025                     (match_operand:QF 1 "src_operand" "")))]
4026   ""
4027   "legitimize_operands (COMPARE, operands, QFmode);
4028    c4x_compare_op0 = operands[0];
4029    c4x_compare_op1 = operands[1];
4030    DONE;")
4031
4032 (define_insn "*cmpqf"
4033   [(set (reg:CC 21)
4034         (compare:CC (match_operand:QF 0 "src_operand" "f,fR,fS<>")
4035                     (match_operand:QF 1 "src_operand" "fHm,R,fS<>")))]
4036   "valid_operands (COMPARE, operands, QFmode)"
4037   "@
4038    cmpf\\t%1,%0
4039    cmpf3\\t%1,%0
4040    cmpf3\\t%1,%0"
4041   [(set_attr "type" "compare,compare,compare")])
4042
4043 (define_insn "*cmpqf_noov"
4044   [(set (reg:CC_NOOV 21)
4045         (compare:CC_NOOV (match_operand:QF 0 "src_operand" "f,fR,fS<>")
4046                          (match_operand:QF 1 "src_operand" "fHm,R,fS<>")))]
4047   "valid_operands (COMPARE, operands, QFmode)"
4048   "@
4049    cmpf\\t%1,%0
4050    cmpf3\\t%1,%0
4051    cmpf3\\t%1,%0"
4052   [(set_attr "type" "compare,compare,compare")])
4053
4054 ; Inlined float divide for C4x
4055 (define_expand "divqf3_inline"
4056   [(parallel [(set (match_dup 3)
4057                    (unspec:QF [(match_operand:QF 2 "src_operand" "")] 5))
4058               (clobber (reg:CC_NOOV 21))])
4059    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
4060               (clobber (reg:CC_NOOV 21))])
4061    (parallel [(set (match_dup 4) (minus:QF (match_dup 5) (match_dup 4)))
4062               (clobber (reg:CC_NOOV 21))])
4063    (parallel [(set (match_dup 3) (mult:QF (match_dup 3) (match_dup 4)))
4064               (clobber (reg:CC_NOOV 21))])
4065    (parallel [(set (match_dup 4) (mult:QF (match_dup 2) (match_dup 3)))
4066               (clobber (reg:CC_NOOV 21))])
4067    (parallel [(set (match_dup 4) (minus:QF (match_dup 5) (match_dup 4)))
4068               (clobber (reg:CC_NOOV 21))])
4069    (parallel [(set (match_dup 3) (mult:QF (match_dup 3) (match_dup 4)))
4070               (clobber (reg:CC_NOOV 21))])
4071    (parallel [(set (match_dup 3)
4072                    (mult:QF (match_operand:QF 1 "src_operand" "")
4073                             (match_dup 3)))
4074               (clobber (reg:CC_NOOV 21))])
4075    (parallel [(set (match_operand:QF 0 "reg_operand" "")
4076                    (unspec:QF [(match_dup 3)] 6))
4077               (clobber (reg:CC_NOOV 21))])]
4078   "! TARGET_C3X"
4079   "if (! reload_in_progress
4080       && ! reg_operand (operands[2], QFmode))
4081      operands[2] = force_reg (QFmode, operands[2]);
4082    operands[3] = gen_reg_rtx (QFmode);
4083    operands[4] = gen_reg_rtx (QFmode);
4084    operands[5] = CONST2_RTX (QFmode);")
4085
4086 (define_expand "divqf3"
4087   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
4088                    (div:QF (match_operand:QF 1 "src_operand" "")
4089                             (match_operand:QF 2 "src_operand" "")))
4090               (clobber (reg:CC 21))])]
4091   "! TARGET_C3X && TARGET_INLINE"
4092   "emit_insn (gen_divqf3_inline (operands[0], operands[1], operands[2]));
4093    DONE;")
4094
4095 ;
4096 ; CONDITIONAL MOVES
4097 ;
4098
4099 ; ???  We should make these pattern fail if the src operand combination
4100 ; is not valid.  Although reload will fix things up, it will introduce
4101 ; extra load instructions that won't be hoisted out of a loop.
4102
4103 (define_insn "*ldi_conditional"
4104   [(set (match_operand:QI 0 "reg_operand" "=r,r")
4105         (if_then_else:QI (match_operator 1 "comparison_operator"
4106                           [(reg:CC 21) (const_int 0)])
4107                          (match_operand:QI 2 "src_operand" "rIm,0")
4108                          (match_operand:QI 3 "src_operand" "0,rIm")))]
4109  ""
4110  "@
4111   ldi%1\\t%2,%0
4112   ldi%I1\\t%3,%0"
4113  [(set_attr "type" "binary")])
4114
4115 (define_insn "*ldi_conditional_noov"
4116   [(set (match_operand:QI 0 "reg_operand" "=r,r")
4117         (if_then_else:QI (match_operator 1 "comparison_operator"
4118                           [(reg:CC_NOOV 21) (const_int 0)])
4119                          (match_operand:QI 2 "src_operand" "rIm,0")
4120                          (match_operand:QI 3 "src_operand" "0,rIm")))]
4121  "GET_CODE (operands[1]) != LE
4122   && GET_CODE (operands[1]) != GE
4123   && GET_CODE (operands[1]) != LT
4124   && GET_CODE (operands[1]) != GT"
4125  "@
4126   ldi%1\\t%2,%0
4127   ldi%I1\\t%3,%0"
4128  [(set_attr "type" "binary")])
4129
4130 ; Move operand 2 to operand 0 if condition (operand 1) is true
4131 ; else move operand 3 to operand 0.
4132 ; The temporary register is required below because some of the operands
4133 ; might be identical (namely 0 and 2). 
4134 ;
4135 (define_expand "movqicc"
4136   [(set (match_operand:QI 0 "reg_operand" "")
4137         (if_then_else:QI (match_operand 1 "comparison_operator" "")
4138                          (match_operand:QI 2 "src_operand" "")
4139                          (match_operand:QI 3 "src_operand" "")))]
4140  ""
4141  "{ 
4142     enum rtx_code code = GET_CODE (operands[1]);
4143     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
4144     if (ccreg == NULL_RTX) FAIL;
4145     emit_insn (gen_rtx_SET (QImode, operands[0],
4146                             gen_rtx_IF_THEN_ELSE (QImode,
4147                                  gen_rtx (code, VOIDmode, ccreg, const0_rtx),
4148                                           operands[2], operands[3])));
4149     DONE;}")
4150                       
4151 (define_insn "*ldf_conditional"
4152   [(set (match_operand:QF 0 "reg_operand" "=f,f")
4153         (if_then_else:QF (match_operator 1 "comparison_operator"
4154                           [(reg:CC 21) (const_int 0)])
4155                          (match_operand:QF 2 "src_operand" "fHm,0")
4156                          (match_operand:QF 3 "src_operand" "0,fHm")))]
4157  ""
4158  "@
4159   ldf%1\\t%2,%0
4160   ldf%I1\\t%3,%0"
4161  [(set_attr "type" "binary")])
4162
4163 (define_insn "*ldf_conditional_noov"
4164   [(set (match_operand:QF 0 "reg_operand" "=f,f")
4165         (if_then_else:QF (match_operator 1 "comparison_operator"
4166                           [(reg:CC_NOOV 21) (const_int 0)])
4167                          (match_operand:QF 2 "src_operand" "fHm,0")
4168                          (match_operand:QF 3 "src_operand" "0,fHm")))]
4169  "GET_CODE (operands[1]) != LE
4170   && GET_CODE (operands[1]) != GE
4171   && GET_CODE (operands[1]) != LT
4172   && GET_CODE (operands[1]) != GT"
4173  "@
4174   ldf%1\\t%2,%0
4175   ldf%I1\\t%3,%0"
4176  [(set_attr "type" "binary")])
4177
4178 (define_expand "movqfcc"
4179   [(set (match_operand:QF 0 "reg_operand" "")
4180         (if_then_else:QF (match_operand 1 "comparison_operator" "")
4181                          (match_operand:QF 2 "src_operand" "")
4182                          (match_operand:QF 3 "src_operand" "")))]
4183  ""
4184  "{ 
4185     enum rtx_code code = GET_CODE (operands[1]);
4186     rtx ccreg = c4x_gen_compare_reg (code, c4x_compare_op0, c4x_compare_op1);
4187     if (ccreg == NULL_RTX) FAIL;
4188     emit_insn (gen_rtx_SET (QFmode, operands[0],
4189                             gen_rtx_IF_THEN_ELSE (QFmode,
4190                                  gen_rtx (code, VOIDmode, ccreg, const0_rtx),
4191                                           operands[2], operands[3])));
4192     DONE;}")
4193
4194 (define_expand "seq"
4195  [(set (match_operand:QI 0 "reg_operand" "")
4196        (const_int 0))
4197   (set (match_dup 0)
4198        (if_then_else:QI (eq (match_dup 1) (const_int 0))
4199                         (const_int 1)
4200                         (match_dup 0)))]
4201  ""
4202  "operands[1] = c4x_gen_compare_reg (EQ, c4x_compare_op0, c4x_compare_op1);")
4203
4204 (define_expand "sne"
4205  [(set (match_operand:QI 0 "reg_operand" "")
4206        (const_int 0))
4207   (set (match_dup 0)
4208        (if_then_else:QI (ne (match_dup 1) (const_int 0))
4209                         (const_int 1)
4210                         (match_dup 0)))]
4211  ""
4212  "operands[1] = c4x_gen_compare_reg (NE, c4x_compare_op0, c4x_compare_op1);")
4213
4214 (define_expand "slt"
4215   [(set (match_operand:QI 0 "reg_operand" "")
4216         (const_int 0))
4217    (set (match_dup 0)
4218         (if_then_else:QI (lt (match_dup 1) (const_int 0))
4219                         (const_int 1)
4220                          (match_dup 0)))]
4221   ""
4222   "operands[1] = c4x_gen_compare_reg (LT, c4x_compare_op0, c4x_compare_op1);
4223    if (operands[1] == NULL_RTX) FAIL;")
4224
4225 (define_expand "sltu"
4226   [(set (match_operand:QI 0 "reg_operand" "")
4227         (const_int 0))
4228    (set (match_dup 0)
4229         (if_then_else:QI (ltu (match_dup 1) (const_int 0))
4230                         (const_int 1)
4231                          (match_dup 0)))]
4232   ""
4233   "operands[1] = c4x_gen_compare_reg (LTU, c4x_compare_op0, c4x_compare_op1);")
4234
4235 (define_expand "sgt"
4236   [(set (match_operand:QI 0 "reg_operand" "")
4237         (const_int 0))
4238    (set (match_dup 0)
4239         (if_then_else:QI (gt (match_dup 1) (const_int 0))
4240                         (const_int 1)
4241                          (match_dup 0)))]
4242   "" 
4243   "operands[1] = c4x_gen_compare_reg (GT, c4x_compare_op0, c4x_compare_op1);
4244    if (operands[1] == NULL_RTX) FAIL;")
4245
4246 (define_expand "sgtu"
4247   [(set (match_operand:QI 0 "reg_operand" "")
4248         (const_int 0))
4249    (set (match_dup 0)
4250         (if_then_else:QI (gtu (match_dup 1) (const_int 0))
4251                         (const_int 1)
4252                          (match_dup 0)))]
4253   ""
4254   "operands[1] = c4x_gen_compare_reg (GTU, c4x_compare_op0, c4x_compare_op1);")
4255
4256 (define_expand "sle"
4257   [(set (match_operand:QI 0 "reg_operand" "")
4258         (const_int 0))
4259    (set (match_dup 0)
4260         (if_then_else:QI (le (match_dup 1) (const_int 0))
4261                          (const_int 1)
4262                          (match_dup 0)))]
4263   ""
4264   "operands[1] = c4x_gen_compare_reg (LE, c4x_compare_op0, c4x_compare_op1);
4265    if (operands[1] == NULL_RTX) FAIL;")
4266
4267 (define_expand "sleu"
4268   [(set (match_operand:QI 0 "reg_operand" "")
4269         (const_int 0))
4270    (set (match_dup 0)
4271         (if_then_else:QI (leu (match_dup 1) (const_int 0))
4272                          (const_int 1)
4273                          (match_dup 0)))]
4274   ""
4275   "operands[1] = c4x_gen_compare_reg (LEU, c4x_compare_op0, c4x_compare_op1);")
4276
4277 (define_expand "sge"
4278   [(set (match_operand:QI 0 "reg_operand" "")
4279         (const_int 0))
4280    (set (match_dup 0)
4281         (if_then_else:QI (ge (match_dup 1) (const_int 0))
4282                          (const_int 1)
4283                          (match_dup 0)))]
4284   ""
4285   "operands[1] = c4x_gen_compare_reg (GE, c4x_compare_op0, c4x_compare_op1);
4286    if (operands[1] == NULL_RTX) FAIL;")
4287
4288 (define_expand "sgeu"
4289   [(set (match_operand:QI 0 "reg_operand" "")
4290         (const_int 0))
4291    (set (match_dup 0)
4292         (if_then_else:QI (geu (match_dup 1) (const_int 0))
4293                          (const_int 1)
4294                          (match_dup 0)))]
4295   ""
4296   "operands[1] = c4x_gen_compare_reg (GEU, c4x_compare_op0, c4x_compare_op1);")
4297
4298 (define_split
4299   [(set (match_operand:QI 0 "reg_operand" "")
4300         (match_operator:QI 1 "comparison_operator" [(reg:CC 21) (const_int 0)]))]
4301   "reload_completed"
4302   [(set (match_dup 0) (const_int 0))
4303    (set (match_dup 0)
4304         (if_then_else:QI (match_op_dup 1 [(reg:CC 21) (const_int 0)])
4305                         (const_int 1)
4306                          (match_dup 0)))]
4307   "")
4308
4309 (define_split
4310   [(set (match_operand:QI 0 "reg_operand" "")
4311         (match_operator:QI 1 "comparison_operator" [(reg:CC_NOOV 21) (const_int 0)]))]
4312   "reload_completed"
4313   [(set (match_dup 0) (const_int 0))
4314    (set (match_dup 0)
4315         (if_then_else:QI (match_op_dup 1 [(reg:CC_NOOV 21) (const_int 0)])
4316                          (const_int 1)
4317                          (match_dup 0)))]
4318   "")
4319
4320 (define_insn "*bu"
4321   [(set (pc)
4322         (unspec [(match_operand:QI 0 "reg_operand" "r")] 1))]
4323   ""
4324   "bu%#\\t%0"
4325   [(set_attr "type" "jump")])
4326
4327 (define_expand "caseqi"
4328   [(parallel [(set (match_dup 5)
4329                    (minus:QI (match_operand:QI 0 "reg_operand" "")
4330                              (match_operand:QI 1 "src_operand" "")))
4331               (clobber (reg:CC_NOOV 21))])
4332    (set (reg:CC 21)
4333         (compare:CC (match_dup 5)
4334                     (match_operand:QI 2 "src_operand" "")))
4335    (set (pc)
4336         (if_then_else (gtu (reg:CC 21)
4337                            (const_int 0))
4338                       (label_ref (match_operand 4 "" ""))
4339                       (pc)))
4340    (parallel [(set (match_dup 6)
4341                    (plus:QI (match_dup 5)
4342                             (label_ref:QI (match_operand 3 "" ""))))
4343               (clobber (reg:CC_NOOV 21))])
4344    (set (match_dup 7)
4345         (mem:QI (match_dup 6)))
4346    (set (pc) (match_dup 7))]
4347   ""
4348   "operands[5] = gen_reg_rtx (QImode);
4349    operands[6] = gen_reg_rtx (QImode);
4350    operands[7] = gen_reg_rtx (QImode);")
4351                 
4352 ;
4353 ; PARALLEL FLOAT INSTRUCTIONS
4354 ;
4355 ; This patterns are under development
4356
4357 ;
4358 ; ABSF/STF
4359 ;
4360
4361 (define_insn "*absqf2_movqf_clobber"
4362   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4363         (abs:QF (match_operand:QF 1 "par_ind_operand" "S<>")))
4364    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4365         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4366    (clobber (reg:CC_NOOV 21))]
4367   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4368   "absf\\t%1,%0\\n||\\tstf\\t%3,%2"
4369   [(set_attr "type" "binarycc")])
4370
4371 ;
4372 ; ADDF/STF
4373 ;
4374
4375 (define_insn "*addqf3_movqf_clobber"
4376   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q,q")
4377         (plus:QF (match_operand:QF 1 "parallel_operand" "%q,S<>")
4378                  (match_operand:QF 2 "parallel_operand" "S<>,q")))
4379    (set (match_operand:QF 3 "par_ind_operand" "=S<>,S<>")
4380         (match_operand:QF 4 "ext_low_reg_operand" "q,q"))
4381    (clobber (reg:CC 21))]
4382   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4383   "addf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4384   [(set_attr "type" "binarycc,binarycc")])
4385
4386 ;
4387 ; FLOAT/STF
4388 ;
4389
4390 (define_insn "*floatqiqf2_movqf_clobber"
4391   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4392         (float:QF (match_operand:QI 1 "par_ind_operand" "S<>")))
4393    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4394         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4395    (clobber (reg:CC 21))]
4396   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4397   "float\\t%1,%0\\n||\\tstf\\t%3,%2"
4398   [(set_attr "type" "binarycc")])
4399
4400 ;
4401 ; MPYF/ADDF
4402 ;
4403
4404 (define_insn "*mulqf3_addqf3_clobber"
4405   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t,t,t,t")
4406         (mult:QF (match_operand:QF 1 "parallel_operand" "%S<>!V,q,S<>!V,q")
4407                  (match_operand:QF 2 "parallel_operand" "q,S<>!V,S<>!V,q")))
4408    (set (match_operand:QF 3 "r2r3_reg_operand" "=u,u,u,u")
4409         (plus:QF (match_operand:QF 4 "parallel_operand" "%S<>!V,q,q,S<>!V")
4410                  (match_operand:QF 5 "parallel_operand" "q,S<>!V,q,S<>!V")))
4411    (clobber (reg:CC_NOOV 21))]
4412   "TARGET_PARALLEL_MPY && valid_parallel_operands_6 (operands, QFmode)"
4413   "mpyf3\\t%2,%1,%0\\n||\\taddf3\\t%5,%4,%3"
4414   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4415
4416
4417 ;
4418 ; MPYF/STF
4419 ;
4420
4421 (define_insn "*mulqf3_movqf_clobber"
4422   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q,q")
4423         (mult:QF (match_operand:QF 1 "parallel_operand" "%q,S<>")
4424                  (match_operand:QF 2 "parallel_operand" "S<>,q")))
4425    (set (match_operand:QF 3 "par_ind_operand" "=S<>,S<>")
4426         (match_operand:QF 4 "ext_low_reg_operand" "q,q"))
4427    (clobber (reg:CC 21))]
4428   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4429   "mpyf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4430   [(set_attr "type" "binarycc,binarycc")])
4431
4432 ;
4433 ; MPYF/SUBF
4434 ;
4435
4436 (define_insn "*mulqf3_subqf3_clobber"
4437   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t,t")
4438         (mult:QF (match_operand:QF 1 "parallel_operand" "S<>,q")
4439                  (match_operand:QF 2 "parallel_operand" "q,S<>")))
4440    (set (match_operand:QF 3 "r2r3_reg_operand" "=u,u")
4441         (minus:QF (match_operand:QF 4 "parallel_operand" "S<>,q")
4442                   (match_operand:QF 5 "parallel_operand" "q,S<>")))
4443    (clobber (reg:CC 21))]
4444   "TARGET_PARALLEL_MPY && valid_parallel_operands_6 (operands, QFmode)"
4445   "mpyf3\\t%2,%1,%0\\n||\\tsubf3\\t%5,%4,%3"
4446   [(set_attr "type" "binarycc,binarycc")])
4447
4448 ;
4449 ; MPYF/LDF 0
4450 ;
4451
4452 (define_insn "*mulqf3_clrqf_clobber"
4453   [(set (match_operand:QF 0 "r0r1_reg_operand" "=t")
4454         (mult:QF (match_operand:QF 1 "par_ind_operand" "%S<>")
4455                  (match_operand:QF 2 "par_ind_operand" "S<>")))
4456    (set (match_operand:QF 3 "r2r3_reg_operand" "=u")
4457         (match_operand:QF 4 "fp_zero_operand" "G"))
4458    (clobber (reg:CC 21))]
4459   "TARGET_PARALLEL_MPY"
4460   "mpyf3\\t%2,%1,%0\\n||\\tsubf3\\t%3,%3,%3"
4461   [(set_attr "type" "binarycc")])
4462
4463 ;
4464 ; NEGF/STF
4465 ;
4466
4467 (define_insn "*negqf2_movqf_clobber"
4468   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4469         (neg:QF (match_operand:QF 1 "par_ind_operand" "S<>")))
4470    (set (match_operand:QF 2 "par_ind_operand" "=S<>")
4471         (match_operand:QF 3 "ext_low_reg_operand" "q"))
4472    (clobber (reg:CC 21))]
4473   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QFmode)"
4474   "negf\\t%1,%0\\n||\\tstf\\t%3,%2"
4475   [(set_attr "type" "binarycc")])
4476
4477 ;
4478 ; SUBF/STF
4479 ;
4480
4481 (define_insn "*subqf3_movqf_clobber"
4482   [(set (match_operand:QF 0 "ext_low_reg_operand" "=q")
4483         (minus:QF (match_operand:QF 1 "ext_low_reg_operand" "q")
4484                   (match_operand:QF 2 "par_ind_operand" "S<>")))
4485    (set (match_operand:QF 3 "par_ind_operand" "=S<>")
4486         (match_operand:QF 4 "ext_low_reg_operand" "q"))
4487    (clobber (reg:CC 21))]
4488   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QFmode)"
4489   "subf3\\t%2,%1,%0\\n||\\tstf\\t%4,%3"
4490   [(set_attr "type" "binarycc")])
4491
4492 ;
4493 ; PARALLEL INTEGER INSTRUCTIONS
4494 ;
4495
4496 ;
4497 ; ABSI/STI
4498 ;
4499
4500 (define_insn "*absqi2_movqi_clobber"
4501   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4502         (abs:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4503    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4504         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4505    (clobber (reg:CC_NOOV 21))]
4506   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4507   "absi\\t%1,%0\\n||\\tsti\\t%3,%2"
4508   [(set_attr "type" "binarycc")])
4509
4510 ;
4511 ; ADDI/STI
4512 ;
4513
4514 (define_insn "*addqi3_movqi_clobber"
4515   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4516         (plus:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4517                  (match_operand:QI 2 "parallel_operand" "S<>,q")))
4518    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4519         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4520    (clobber (reg:CC 21))]
4521   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4522   "addi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4523   [(set_attr "type" "binarycc,binarycc")])
4524
4525 ;
4526 ; AND/STI
4527 ;
4528
4529 (define_insn "*andqi3_movqi_clobber"
4530   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4531         (and:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4532                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4533    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4534         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4535    (clobber (reg:CC 21))]
4536   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4537   "and3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4538   [(set_attr "type" "binarycc,binarycc")])
4539
4540 ;
4541 ; ASH(left)/STI 
4542 ;
4543
4544 (define_insn "*ashlqi3_movqi_clobber"
4545   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4546         (ashift:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4547                    (match_operand:QI 2 "ext_low_reg_operand" "q")))
4548    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4549         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4550    (clobber (reg:CC 21))]
4551   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4552   "ash3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4553   [(set_attr "type" "binarycc")])
4554
4555 ;
4556 ; ASH(right)/STI 
4557 ;
4558
4559 (define_insn "*ashrqi3_movqi_clobber"
4560   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4561         (ashiftrt:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4562                      (neg:QI (match_operand:QI 2 "ext_low_reg_operand" "q"))))
4563    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4564         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4565    (clobber (reg:CC 21))]
4566   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4567   "ash3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4568   [(set_attr "type" "binarycc")])
4569
4570 ;
4571 ; FIX/STI
4572 ;
4573
4574 (define_insn "*fixqfqi2_movqi_clobber"
4575   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4576         (fix:QI (match_operand:QF 1 "par_ind_operand" "S<>")))
4577    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4578         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4579    (clobber (reg:CC 21))]
4580   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4581   "fix\\t%1,%0\\n||\\tsti\\t%3,%2"
4582   [(set_attr "type" "binarycc")])
4583
4584 ;
4585 ; LSH(right)/STI 
4586 ;
4587
4588 (define_insn "*lshrqi3_movqi_clobber"
4589   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4590         (lshiftrt:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4591                      (neg:QI (match_operand:QI 2 "ext_low_reg_operand" "q"))))
4592    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4593         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4594    (clobber (reg:CC 21))]
4595   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4596   "lsh3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4597   [(set_attr "type" "binarycc")])
4598
4599 ;
4600 ; MPYI/ADDI
4601 ;
4602
4603 (define_insn "*mulqi3_addqi3_clobber"
4604   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t,t,t,t")
4605         (mult:QI (match_operand:QI 1 "parallel_operand" "%S<>!V,q,S<>!V,q")
4606                  (match_operand:QI 2 "parallel_operand" "q,S<>!V,S<>!V,q")))
4607    (set (match_operand:QI 3 "r2r3_reg_operand" "=u,u,u,u")
4608         (plus:QI (match_operand:QI 4 "parallel_operand" "%S<>!V,q,q,S<>!V")
4609                  (match_operand:QI 5 "parallel_operand" "q,S<>!V,q,S<>!V")))
4610    (clobber (reg:CC 21))]
4611   "TARGET_PARALLEL_MPY && TARGET_MPYI 
4612    && valid_parallel_operands_6 (operands, QImode)"
4613   "mpyi3\\t%2,%1,%0\\n||\\taddi3\\t%5,%4,%3"
4614   [(set_attr "type" "binarycc,binarycc,binarycc,binarycc")])
4615
4616
4617 ;
4618 ; MPYI/STI
4619 ;
4620
4621 (define_insn "*mulqi3_movqi_clobber"
4622   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4623         (mult:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4624                  (match_operand:QI 2 "parallel_operand" "S<>,q")))
4625    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4626         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4627    (clobber (reg:CC 21))]
4628   "TARGET_PARALLEL && TARGET_MPYI
4629    && valid_parallel_operands_5 (operands, QImode)"
4630   "mpyi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4631   [(set_attr "type" "binarycc,binarycc")])
4632
4633 ;
4634 ; MPYI/SUBI
4635 ;
4636
4637 (define_insn "*mulqi3_subqi3_clobber"
4638   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t,t")
4639         (mult:QI (match_operand:QI 1 "parallel_operand" "S<>,q")
4640                  (match_operand:QI 2 "parallel_operand" "q,S<>")))
4641    (set (match_operand:QI 3 "r2r3_reg_operand" "=u,u")
4642         (minus:QI (match_operand:QI 4 "parallel_operand" "S<>,q")
4643                   (match_operand:QI 5 "parallel_operand" "q,S<>")))
4644    (clobber (reg:CC 21))]
4645   "TARGET_PARALLEL_MPY && TARGET_MPYI
4646    && valid_parallel_operands_6 (operands, QImode)"
4647   "mpyi3\\t%2,%1,%0\\n||\\tsubi3\\t%5,%4,%3"
4648   [(set_attr "type" "binarycc,binarycc")])
4649
4650 ;
4651 ; MPYI/LDI 0
4652 ;
4653
4654 (define_insn "*mulqi3_clrqi_clobber"
4655   [(set (match_operand:QI 0 "r0r1_reg_operand" "=t")
4656         (mult:QI (match_operand:QI 1 "par_ind_operand" "%S<>")
4657                  (match_operand:QI 2 "par_ind_operand" "S<>")))
4658    (set (match_operand:QI 3 "r2r3_reg_operand" "=u")
4659         (const_int 0))
4660    (clobber (reg:CC 21))]
4661   "TARGET_PARALLEL_MPY && TARGET_MPYI"
4662   "mpyi3\\t%2,%1,%0\\n||\\tsubi3\\t%3,%3,%3"
4663   [(set_attr "type" "binarycc")])
4664
4665 ;
4666 ; NEGI/STI
4667 ;
4668
4669 (define_insn "*negqi2_movqi_clobber"
4670   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4671         (neg:QI (match_operand:QI 1 "par_ind_operand" "S<>")))
4672    (set (match_operand:QI 2 "par_ind_operand" "=S<>")
4673         (match_operand:QI 3 "ext_low_reg_operand" "q"))
4674    (clobber (reg:CC 21))]
4675   "TARGET_PARALLEL && valid_parallel_operands_4 (operands, QImode)"
4676   "negi\\t%1,%0\\n||\\tsti\\t%3,%2"
4677   [(set_attr "type" "binarycc")])
4678
4679 ;
4680 ; NOT/STI
4681 ;
4682
4683 (define_insn "*notqi2_movqi_clobber"
4684   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4685         (not: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   "not\\t%1,%0\\n||\\tsti\\t%3,%2"
4691   [(set_attr "type" "binarycc")])
4692
4693 ;
4694 ; OR/STI
4695 ;
4696
4697 (define_insn "*iorqi3_movqi_clobber"
4698   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4699         (ior:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4700                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4701    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4702         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4703    (clobber (reg:CC 21))]
4704   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4705   "or3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4706   [(set_attr "type" "binarycc,binarycc")])
4707
4708 ;
4709 ; SUBI/STI
4710 ;
4711
4712 (define_insn "*subqi3_movqi_clobber"
4713   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q")
4714         (minus:QI (match_operand:QI 1 "par_ind_operand" "S<>")
4715                   (match_operand:QI 2 "ext_low_reg_operand" "q")))
4716    (set (match_operand:QI 3 "par_ind_operand" "=S<>")
4717         (match_operand:QI 4 "ext_low_reg_operand" "q"))
4718    (clobber (reg:CC 21))]
4719   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4720   "subi3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4721   [(set_attr "type" "binarycc")])
4722
4723 ;
4724 ; XOR/STI
4725 ;
4726
4727 (define_insn "*xorqi3_movqi_clobber"
4728   [(set (match_operand:QI 0 "ext_low_reg_operand" "=q,q")
4729         (xor:QI (match_operand:QI 1 "parallel_operand" "%q,S<>")
4730                 (match_operand:QI 2 "parallel_operand" "S<>,q")))
4731    (set (match_operand:QI 3 "par_ind_operand" "=S<>,S<>")
4732         (match_operand:QI 4 "ext_low_reg_operand" "q,q"))
4733    (clobber (reg:CC 21))]
4734   "TARGET_PARALLEL && valid_parallel_operands_5 (operands, QImode)"
4735   "xor3\\t%2,%1,%0\\n||\\tsti\\t%4,%3"
4736   [(set_attr "type" "binarycc,binarycc")])
4737
4738 ;
4739 ; BRANCH/CALL INSTRUCTIONS
4740 ;
4741
4742 ;
4743 ; Branch instructions
4744 ;
4745 (define_insn "*b"
4746   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4747                            [(reg:CC 21) (const_int 0)])
4748                            (label_ref (match_operand 1 "" ""))
4749                            (pc)))]
4750   ""
4751   "*
4752    return c4x_output_cbranch (\"b%0\", insn);"
4753   [(set_attr "type" "jmpc")])
4754
4755 (define_insn "*b_rev"
4756   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4757                            [(reg:CC 21) (const_int 0)])
4758                            (pc)
4759                            (label_ref (match_operand 1 "" ""))))]
4760   ""
4761   "*
4762    return c4x_output_cbranch (\"b%I0\", insn);"
4763   [(set_attr "type" "jmpc")])
4764
4765 (define_insn "*b_noov"
4766   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4767                            [(reg:CC_NOOV 21) (const_int 0)])
4768                            (label_ref (match_operand 1 "" ""))
4769                            (pc)))]
4770  "GET_CODE (operands[0]) != LE
4771   && GET_CODE (operands[0]) != GE
4772   && GET_CODE (operands[0]) != LT
4773   && GET_CODE (operands[0]) != GT"
4774   "*
4775    return c4x_output_cbranch (\"b%0\", insn);"
4776   [(set_attr "type" "jmpc")])
4777
4778 (define_insn "*b_noov_rev"
4779   [(set (pc) (if_then_else (match_operator 0 "comparison_operator"
4780                            [(reg:CC_NOOV 21) (const_int 0)])
4781                            (pc)
4782                            (label_ref (match_operand 1 "" ""))))]
4783  "GET_CODE (operands[0]) != LE
4784   && GET_CODE (operands[0]) != GE
4785   && GET_CODE (operands[0]) != LT
4786   && GET_CODE (operands[0]) != GT"
4787   "*
4788    return c4x_output_cbranch (\"b%I0\", insn);"
4789   [(set_attr "type" "jmpc")])
4790
4791 (define_expand "beq"
4792   [(set (pc) (if_then_else (eq (match_dup 1) (const_int 0))
4793                            (label_ref (match_operand 0 "" ""))
4794                            (pc)))]
4795   ""
4796   "operands[1] = c4x_gen_compare_reg (EQ, c4x_compare_op0, c4x_compare_op1);")
4797
4798 (define_expand "bne"
4799   [(set (pc) (if_then_else (ne (match_dup 1) (const_int 0))
4800                            (label_ref (match_operand 0 "" ""))
4801                            (pc)))]
4802   ""
4803   "operands[1] = c4x_gen_compare_reg (NE, c4x_compare_op0, c4x_compare_op1);")
4804
4805 (define_expand "blt"
4806   [(set (pc) (if_then_else (lt (match_dup 1) (const_int 0))
4807                            (label_ref (match_operand 0 "" ""))
4808                            (pc)))]
4809   ""
4810   "operands[1] = c4x_gen_compare_reg (LT, c4x_compare_op0, c4x_compare_op1);
4811    if (operands[1] == NULL_RTX) FAIL;")
4812
4813 (define_expand "bltu"
4814   [(set (pc) (if_then_else (ltu (match_dup 1) (const_int 0))
4815                            (label_ref (match_operand 0 "" ""))
4816                            (pc)))]
4817   ""
4818   "operands[1] = c4x_gen_compare_reg (LTU, c4x_compare_op0, c4x_compare_op1);")
4819
4820 (define_expand "bgt"
4821   [(set (pc) (if_then_else (gt (match_dup 1) (const_int 0))
4822                            (label_ref (match_operand 0 "" ""))
4823                            (pc)))]
4824   ""
4825   "operands[1] = c4x_gen_compare_reg (GT, c4x_compare_op0, c4x_compare_op1);
4826    if (operands[1] == NULL_RTX) FAIL;")
4827
4828 (define_expand "bgtu"
4829   [(set (pc) (if_then_else (gtu (match_dup 1) (const_int 0))
4830                            (label_ref (match_operand 0 "" ""))
4831                            (pc)))]
4832   ""
4833   "operands[1] = c4x_gen_compare_reg (GTU, c4x_compare_op0, c4x_compare_op1);")
4834
4835 (define_expand "ble"
4836   [(set (pc) (if_then_else (le (match_dup 1) (const_int 0))
4837                            (label_ref (match_operand 0 "" ""))
4838                            (pc)))]
4839   ""
4840   "operands[1] = c4x_gen_compare_reg (LE, c4x_compare_op0, c4x_compare_op1);
4841    if (operands[1] == NULL_RTX) FAIL;")
4842
4843 (define_expand "bleu"
4844   [(set (pc) (if_then_else (leu (match_dup 1) (const_int 0))
4845                            (label_ref (match_operand 0 "" ""))
4846                            (pc)))]
4847   ""
4848   "operands[1] = c4x_gen_compare_reg (LEU, c4x_compare_op0, c4x_compare_op1);")
4849
4850 (define_expand "bge"
4851   [(set (pc) (if_then_else (ge (match_dup 1) (const_int 0))
4852                            (label_ref (match_operand 0 "" ""))
4853                            (pc)))]
4854   ""
4855   "operands[1] = c4x_gen_compare_reg (GE, c4x_compare_op0, c4x_compare_op1);
4856    if (operands[1] == NULL_RTX) FAIL;")
4857
4858 (define_expand "bgeu"
4859   [(set (pc) (if_then_else (geu (match_dup 1) (const_int 0))
4860                            (label_ref (match_operand 0 "" ""))
4861                            (pc)))]
4862   ""
4863   "operands[1] = c4x_gen_compare_reg (GEU, c4x_compare_op0, c4x_compare_op1);")
4864
4865 (define_insn "*b_reg"
4866  [(set (pc) (match_operand:QI 0 "reg_operand" "r"))]
4867  ""
4868  "bu%#\\t%0"
4869   [(set_attr "type" "jump")])
4870
4871 (define_expand "indirect_jump"
4872  [(set (pc) (match_operand:QI 0 "reg_operand" ""))]
4873  ""
4874  "")
4875
4876 (define_insn "tablejump"
4877   [(set (pc) (match_operand:QI 0 "src_operand" "r"))
4878    (use (label_ref (match_operand 1 "" "")))]
4879   ""
4880   "bu%#\\t%0"
4881   [(set_attr "type" "jump")])
4882
4883 ;
4884 ; CALL
4885 ;
4886 (define_insn "*call_c3x"
4887  [(call (mem:QI (match_operand:QI 0 "call_address_operand" "Ur"))
4888         (match_operand:QI 1 "general_operand" ""))
4889   (clobber (reg:QI 31))]
4890   ;; Operand 1 not really used on the C4x.  The C30 doesn't have reg 31.
4891
4892   "TARGET_C3X"
4893   "call%U0\\t%C0"
4894   [(set_attr "type" "call")])
4895
4896 ; LAJ requires R11 (31) for the return address
4897 (define_insn "*laj"
4898  [(call (mem:QI (match_operand:QI 0 "call_address_operand" "Ur"))
4899         (match_operand:QI 1 "general_operand" ""))
4900   (clobber (reg:QI 31))]
4901   ;; Operand 1 not really used on the C4x.
4902
4903   "! TARGET_C3X"
4904   "*
4905    if (final_sequence)
4906      return \"laj%U0\\t%C0\";
4907    else
4908      return \"call%U0\\t%C0\";"
4909   [(set_attr "type" "laj")])
4910
4911 (define_expand "call"
4912  [(parallel [(call (match_operand:QI 0 "" "")
4913                    (match_operand:QI 1 "general_operand" ""))
4914              (clobber (reg:QI 31))])]
4915  ""
4916  "
4917 {
4918   if (GET_CODE (operands[0]) == MEM
4919       && ! call_address_operand (XEXP (operands[0], 0), Pmode))
4920     operands[0] = gen_rtx_MEM (GET_MODE (operands[0]),
4921                                force_reg (Pmode, XEXP (operands[0], 0)));
4922 }")
4923
4924 (define_insn "*callv_c3x"
4925  [(set (match_operand 0 "" "=r")
4926        (call (mem:QI (match_operand:QI 1 "call_address_operand" "Ur"))
4927              (match_operand:QI 2 "general_operand" "")))
4928   (clobber (reg:QI 31))]
4929   ;; Operand 0 and 2 not really used for the C4x. 
4930   ;; The C30 doesn't have reg 31.
4931
4932   "TARGET_C3X"
4933   "call%U1\\t%C1"
4934   [(set_attr "type" "call")])
4935
4936 ; LAJ requires R11 (31) for the return address
4937 (define_insn "*lajv"
4938  [(set (match_operand 0 "" "=r")
4939        (call (mem:QI (match_operand:QI 1 "call_address_operand" "Ur"))
4940              (match_operand:QI 2 "general_operand" "")))
4941   (clobber (reg:QI 31))]
4942   ;; Operand 0 and 2 not really used in the C30 instruction.
4943
4944   "! TARGET_C3X"
4945   "*
4946    if (final_sequence)
4947      return \"laj%U1\\t%C1\";
4948    else
4949      return \"call%U1\\t%C1\";"
4950   [(set_attr "type" "laj")])
4951
4952 (define_expand "call_value"
4953  [(parallel [(set (match_operand 0 "" "")
4954                   (call (match_operand:QI 1 "" "")
4955                         (match_operand:QI 2 "general_operand" "")))
4956              (clobber (reg:QI 31))])]
4957  ""
4958  "
4959 {
4960   if (GET_CODE (operands[0]) == MEM
4961       && ! call_address_operand (XEXP (operands[1], 0), Pmode))
4962     operands[0] = gen_rtx_MEM (GET_MODE (operands[1]),
4963                                force_reg (Pmode, XEXP (operands[1], 0)));
4964 }")
4965
4966 (define_insn "return"
4967   [(return)]
4968   "c4x_null_epilogue_p ()"
4969   "rets"
4970   [(set_attr "type" "rets")])
4971
4972 (define_insn "*return_cc"
4973   [(set (pc)
4974         (if_then_else (match_operator 0 "comparison_operator"
4975                       [(reg:CC 21) (const_int 0)])
4976                       (return)
4977                        (pc)))]
4978   "c4x_null_epilogue_p ()"
4979   "rets%0"
4980   [(set_attr "type" "rets")])
4981
4982 (define_insn "*return_cc_noov"
4983   [(set (pc)
4984         (if_then_else (match_operator 0 "comparison_operator"
4985                       [(reg:CC_NOOV 21) (const_int 0)])
4986                       (return)
4987                        (pc)))]
4988   "GET_CODE (operands[0]) != LE
4989    && GET_CODE (operands[0]) != GE
4990    && GET_CODE (operands[0]) != LT
4991    && GET_CODE (operands[0]) != GT
4992    && c4x_null_epilogue_p ()"
4993   "rets%0"
4994   [(set_attr "type" "rets")])
4995
4996 (define_insn "*return_cc_inverse"
4997   [(set (pc)
4998         (if_then_else (match_operator 0 "comparison_operator"
4999                       [(reg:CC 21) (const_int 0)])
5000                        (pc)
5001                       (return)))]
5002   "c4x_null_epilogue_p ()"
5003   "rets%I0"
5004   [(set_attr "type" "rets")])
5005
5006 (define_insn "*return_cc_noov_inverse"
5007   [(set (pc)
5008         (if_then_else (match_operator 0 "comparison_operator"
5009                       [(reg:CC_NOOV 21) (const_int 0)])
5010                        (pc)
5011                       (return)))]
5012   "GET_CODE (operands[0]) != LE
5013    && GET_CODE (operands[0]) != GE
5014    && GET_CODE (operands[0]) != LT
5015    && GET_CODE (operands[0]) != GT
5016    && c4x_null_epilogue_p ()"
5017   "rets%I0"
5018   [(set_attr "type" "rets")])
5019
5020 (define_insn "jump"
5021   [(set (pc) (label_ref (match_operand 0 "" "")))]
5022   ""
5023   "br%#\\t%l0"
5024   [(set_attr "type" "jump")])
5025
5026 ;
5027 ; DBcond
5028 ;
5029 ; Note we have to emit a dbu instruction if there are no delay slots
5030 ; to fill.
5031 ; Also note that GCC will try to reverse a loop to see if it can
5032 ; utilise this instruction.  However, if there are more than one
5033 ; memory reference in the loop, it cannot guarantee that reversing
5034 ; the loop will work :(  (see check_dbra_loop() in loop.c)
5035 ; Note that the C3x only decrements the 24 LSBs of the address register
5036 ; and the 8 MSBs are untouched.  The C4x uses all 32-bits.  We thus
5037 ; have an option to disable this instruction.
5038 (define_insn "*db"
5039   [(set (pc)
5040         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
5041                           (const_int 0))
5042                       (label_ref (match_operand 1 "" ""))
5043                       (pc)))
5044    (set (match_dup 0)
5045         (plus:QI (match_dup 0)
5046                  (const_int -1)))
5047    (clobber (reg:CC_NOOV 21))]
5048   "TARGET_DB && TARGET_LOOP_UNSIGNED"
5049   "*
5050   if (which_alternative == 0)
5051     return \"dbu%#\\t%0,%l1\";
5052   else if (which_alternative == 1)
5053     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5054   else if (which_alternative == 2)
5055     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5056   else
5057     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);
5058   "
5059   [(set_attr "type" "db,jmpc,jmpc,jmpc")])
5060
5061 (define_insn "*db_noclobber"
5062   [(set (pc)
5063         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "+a")
5064                           (const_int 0))
5065                       (label_ref (match_operand 1 "" ""))
5066                       (pc)))
5067    (set (match_dup 0)
5068         (plus:QI (match_dup 0)
5069                  (const_int -1)))]
5070   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5071   "dbu%#\\t%0,%l1"
5072   [(set_attr "type" "db")])
5073
5074 (define_split
5075   [(set (pc)
5076         (if_then_else (ne (match_operand:QI 0 "addr_reg_operand" "")
5077                           (const_int 0))
5078                       (label_ref (match_operand 1 "" ""))
5079                       (pc)))
5080    (set (match_dup 0)
5081         (plus:QI (match_dup 0)
5082                  (const_int -1)))
5083    (clobber (reg:CC_NOOV 21))]
5084   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5085   [(parallel [(set (pc)
5086                    (if_then_else (ne (match_dup 0)
5087                                      (const_int 0))
5088                                  (label_ref (match_dup 1))
5089                                  (pc)))
5090               (set (match_dup 0)
5091                    (plus:QI (match_dup 0)
5092                             (const_int -1)))])]
5093   "")
5094   
5095
5096 ; This insn is used for some loop tests, typically loops reversed when
5097 ; strength reduction is used.  It is actually created when the instruction
5098 ; combination phase combines the special loop test.  Since this insn
5099 ; is both a jump insn and has an output, it must deal with its own
5100 ; reloads, hence the `m' constraints. 
5101
5102 ; The C4x does the decrement and then compares the result against zero.
5103 ; It branches if the result was greater than or equal to zero.
5104 ; In the RTL the comparison and decrement are assumed to happen
5105 ; at the same time so we bias the iteration counter with by -1
5106 ; when we make the test.
5107 (define_insn "decrement_and_branch_until_zero"
5108   [(set (pc)
5109         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a,?*d,??*r,!m")
5110                                    (const_int -1))
5111                           (const_int 0))
5112                       (label_ref (match_operand 1 "" ""))
5113                       (pc)))
5114    (set (match_dup 0)
5115         (plus:QI (match_dup 0)
5116                  (const_int -1)))
5117    (clobber (reg:CC_NOOV 21))]
5118   "TARGET_DB && (find_reg_note (insn, REG_NONNEG, 0) || TARGET_LOOP_UNSIGNED)"
5119   "*
5120   if (which_alternative == 0)
5121     return \"dbu%#\\t%0,%l1\";
5122   else if (which_alternative == 1)
5123     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5124   else if (which_alternative == 2)
5125     return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5126   else
5127     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);
5128   "
5129   [(set_attr "type" "db,jmpc,jmpc,jmpc")])
5130
5131 (define_insn "*decrement_and_branch_until_zero_noclobber"
5132   [(set (pc)
5133         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a")
5134                                    (const_int -1))
5135                           (const_int 0))
5136                       (label_ref (match_operand 1 "" ""))
5137                       (pc)))
5138    (set (match_dup 0)
5139         (plus:QI (match_dup 0)
5140                  (const_int -1)))]
5141   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5142   "dbu%#\\t%0,%l1"
5143   [(set_attr "type" "db")])
5144
5145 (define_split
5146   [(set (pc)
5147         (if_then_else (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "")
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    (clobber (reg:CC_NOOV 21))]
5156   "reload_completed && TARGET_DB && TARGET_LOOP_UNSIGNED"
5157   [(parallel [(set (pc)
5158                    (if_then_else (ge (plus:QI (match_dup 0)
5159                                               (const_int -1))
5160                                      (const_int 0))
5161                                  (label_ref (match_dup 1))
5162                                  (pc)))
5163               (set (match_dup 0)
5164                    (plus:QI (match_dup 0)
5165                             (const_int -1)))])]
5166   "")
5167
5168 ;
5169 ; MISC INSTRUCTIONS
5170 ;
5171
5172 ;
5173 ; NOP
5174 ;
5175 (define_insn "nop"
5176   [(const_int 0)]
5177   ""
5178   "nop")
5179 ; Default to misc type attr.
5180
5181
5182 ;
5183 ; RPTB
5184 ;
5185 (define_insn "rptb_top"
5186   [(use (label_ref (match_operand 0 "" "")))
5187    (use (label_ref (match_operand 1 "" "")))
5188    (clobber (reg:QI 25))
5189    (clobber (reg:QI 26))]
5190   ""
5191   "*
5192    return ! final_sequence && c4x_rptb_rpts_p (insn, operands[0])
5193          ? \"rpts\\trc\" : \"rptb%#\\t%l1-1\";
5194   "
5195   [(set_attr "type" "repeat_top")])
5196
5197 (define_insn "rpts_top"
5198   [(unspec [(use (label_ref (match_operand 0 "" "")))
5199             (use (label_ref (match_operand 1 "" "")))] 2)
5200    (clobber (reg:QI 25))
5201    (clobber (reg:QI 26))]
5202   ""
5203   "*
5204    return ! final_sequence && c4x_rptb_rpts_p (insn, operands[0])
5205          ? \"rpts\\trc\" : \"rptb%#\\t%l1-1\";
5206   "
5207   [(set_attr "type" "repeat")])
5208
5209 ; This pattern needs to be emitted at the start of the loop to
5210 ; say that RS and RE are loaded.
5211 (define_insn "rptb_init"
5212   [(unspec [(match_operand:QI 0 "register_operand" "va")] 22)
5213    (clobber (reg:QI 25))
5214    (clobber (reg:QI 26))]
5215   ""
5216   ""
5217   [(set_attr "type" "repeat")])
5218
5219
5220 ; operand 0 is the loop count pseudo register
5221 ; operand 1 is the number of loop iterations or 0 if it is unknown
5222 ; operand 2 is the maximum number of loop iterations
5223 ; operand 3 is the number of levels of enclosed loops
5224 (define_expand "doloop_begin"
5225   [(use (match_operand 0 "register_operand" ""))
5226    (use (match_operand:QI 1 "const_int_operand" ""))
5227    (use (match_operand:QI 2 "const_int_operand" ""))
5228    (use (match_operand:QI 3 "const_int_operand" ""))]
5229   ""
5230   "if (INTVAL (operands[3]) > 1 || ! TARGET_RPTB)
5231      FAIL;
5232    emit_insn (gen_rptb_init (operands[0]));
5233    DONE;
5234   ")
5235
5236
5237 ; The RS (25) and RE (26) registers must be unviolate from the top of the loop
5238 ; to here.
5239 (define_insn "rptb_end"
5240   [(set (pc)
5241         (if_then_else (ge (match_operand:QI 0 "register_operand" "+v,?a,!*d,!*x*k,!m")
5242                           (const_int 0))
5243                       (label_ref (match_operand 1 "" ""))
5244                       (pc)))
5245    (set (match_dup 0)
5246         (plus:QI (match_dup 0)
5247                  (const_int -1)))
5248    (use (reg:QI 25))
5249    (use (reg:QI 26))
5250    (clobber (reg:CC_NOOV 21))]
5251   ""
5252   "*
5253    if (which_alternative == 0)
5254      return c4x_rptb_nop_p (insn) ? \"nop\" : \"\";
5255    else if (which_alternative == 1 && TARGET_DB)
5256      return \"dbu%#\\t%0,%l1\";
5257    else if (which_alternative == 2)
5258      return c4x_output_cbranch (\"subi\\t1,%0\\n\\tbge\", insn);
5259    else if (which_alternative == 3 || (which_alternative == 1 && ! TARGET_DB))
5260      return c4x_output_cbranch (\"subi\\t1,%0\\n\\tcmpi\\t0,%0\\n\\tbge\", insn);
5261    else
5262      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);
5263   "
5264   [(set_attr "type" "repeat,db,jmpc,jmpc,jmpc")])
5265
5266 (define_split
5267    [(set (pc)
5268         (if_then_else (ge (match_operand:QI 0 "addr_reg_operand" "")
5269                           (const_int 0))
5270                       (label_ref (match_operand 1 "" ""))
5271                       (pc)))
5272    (set (match_dup 0)
5273         (plus:QI (match_dup 0)
5274                  (const_int -1)))
5275    (use (match_operand:QI 2 "const_int_operand" ""))
5276    (use (match_operand:QI 3 "const_int_operand" ""))
5277    (use (match_operand:QI 4 "const_int_operand" ""))
5278    (use (reg:QI 25))
5279    (use (reg:QI 26))
5280    (clobber (reg:CC_NOOV 21))]
5281   "reload_completed"
5282   [(parallel [(set (pc)
5283                    (if_then_else (ge (match_dup 0)
5284                                      (const_int 0))
5285                                  (label_ref (match_dup 1))
5286                                  (pc)))
5287               (set (match_dup 0)
5288                    (plus:QI (match_dup 0)
5289                             (const_int -1)))])]
5290   "")
5291
5292 ; operand 0 is the loop count pseudo register
5293 ; operand 1 is the number of loop iterations or 0 if it is unknown
5294 ; operand 2 is the maximum number of loop iterations
5295 ; operand 3 is the number of levels of enclosed loops
5296 ; operand 4 is the label to jump to at the top of the loop
5297 (define_expand "doloop_end"
5298   [(use (match_operand 0 "register_operand" ""))
5299    (use (match_operand:QI 1 "const_int_operand" ""))
5300    (use (match_operand:QI 2 "const_int_operand" ""))
5301    (use (match_operand:QI 3 "const_int_operand" ""))
5302    (use (label_ref (match_operand 4 "" "")))]
5303   ""
5304   "if (! TARGET_LOOP_UNSIGNED 
5305        && (unsigned HOST_WIDE_INT) INTVAL (operands[2]) > (1U << 31))
5306      FAIL;
5307    if (INTVAL (operands[3]) > 1 || ! TARGET_RPTB)
5308      {
5309         /* The C30 maximum iteration count for DB is 2^24.  */
5310         if (! TARGET_DB)
5311           FAIL;
5312         emit_jump_insn (gen_decrement_and_branch_until_zero (operands[0],
5313                                                              operands[4]));
5314         DONE;
5315      }
5316     emit_jump_insn (gen_rptb_end (operands[0], operands[4]));
5317     DONE;
5318   ")
5319
5320 ; The current low overhead looping code is naff and is not failsafe
5321 ; If you want RTPB instructions to be generated, apply the patches
5322 ; from www.elec.canterbury.ac.nz/c4x.  This will utilise the
5323 ; doloop_begin and doloop_end patterns in this MD.
5324 (define_expand "decrement_and_branch_on_count"
5325   [(parallel [(set (pc)
5326                    (if_then_else (ge (match_operand:QI 0 "register_operand" "")
5327                                      (const_int 0))
5328                                  (label_ref (match_operand 1 "" ""))
5329                                  (pc)))
5330               (set (match_dup 0)
5331                    (plus:QI (match_dup 0)
5332                             (const_int -1)))
5333               (use (reg:QI 25))
5334               (use (reg:QI 26))
5335               (clobber (reg:CC_NOOV 21))])]
5336   "0"
5337   "")
5338
5339 (define_expand "movstrqi_small2"
5340   [(parallel [(set (mem:BLK (match_operand:BLK 0 "src_operand" ""))
5341                    (mem:BLK (match_operand:BLK 1 "src_operand" "")))
5342               (use (match_operand:QI 2 "immediate_operand" ""))
5343               (use (match_operand:QI 3 "immediate_operand" ""))
5344               (clobber (match_operand:QI 4 "ext_low_reg_operand" ""))])]
5345   ""
5346   "
5347  {
5348     rtx src, dst, tmp;
5349     rtx src_mem, dst_mem;    
5350     int len;
5351     int i;
5352
5353     dst = operands[0];
5354     src = operands[1];
5355     len = INTVAL (operands[2]);
5356     tmp = operands[4];
5357
5358     src_mem = gen_rtx_MEM (QImode, src);
5359     dst_mem = gen_rtx_MEM (QImode, dst);
5360
5361     if (TARGET_PARALLEL)
5362       {
5363         emit_insn (gen_movqi (tmp, src_mem));   
5364         emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));        
5365         for (i = 1; i < len; i++)
5366           {
5367             emit_insn (gen_movqi_parallel (tmp, src_mem, dst_mem, tmp));
5368             emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));    
5369             emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));    
5370           }
5371         emit_insn (gen_movqi (dst_mem, tmp));   
5372         emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));        
5373       }
5374     else
5375       {
5376         for (i = 0; i < len; i++)
5377           {
5378             emit_insn (gen_movqi (tmp, src_mem));       
5379             emit_insn (gen_movqi (dst_mem, tmp));       
5380             emit_insn (gen_addqi3_noclobber (src, src, const1_rtx));    
5381             emit_insn (gen_addqi3_noclobber (dst, dst, const1_rtx));    
5382           }
5383       }
5384     DONE;
5385   }
5386   ")
5387
5388
5389 ;
5390 ; BLOCK MOVE
5391 ; We should probably get RC loaded when using RPTB automagically...
5392 ; There's probably no need to call _memcpy() if we don't get
5393 ; a immediate operand for the size.  We could do a better job here
5394 ; than most memcpy() implementations.
5395 ; operand 2 is the number of bytes
5396 ; operand 3 is the shared alignment
5397 ; operand 4 is a scratch register
5398
5399 (define_insn "movstrqi_small"
5400   [(set (mem:BLK (match_operand:QI 0 "addr_reg_operand" "+a"))
5401         (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a")))
5402    (use (match_operand:QI 2 "immediate_operand" "i"))
5403    (use (match_operand:QI 3 "immediate_operand" ""))
5404    (clobber (match_operand:QI 4 "ext_low_reg_operand" "=&q"))
5405    (clobber (match_dup 0))
5406    (clobber (match_dup 1))]
5407   ""
5408   "*
5409  {
5410    int i;
5411    int len = INTVAL (operands[2]);
5412    int first = 1;
5413
5414    for (i = 0; i < len; i++)
5415     {
5416       if (first)
5417         output_asm_insn (\"ldiu\\t*%1++,%4\", operands);
5418       else
5419         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5420       output_asm_insn (\"sti\\t%4,*%0++\", operands);
5421       first = 0;
5422     } 
5423   return \"\";
5424   }
5425   "
5426   [(set_attr "type" "multi")])
5427
5428 (define_insn "movstrqi_large"
5429   [(set (mem:BLK (match_operand:QI 0 "addr_reg_operand" "+a"))
5430         (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a")))
5431    (use (match_operand:QI 2 "immediate_operand" "i"))
5432    (use (match_operand:QI 3 "immediate_operand" ""))
5433    (clobber (match_operand:QI 4 "ext_low_reg_operand" "=&q"))
5434    (clobber (match_dup 0))
5435    (clobber (match_dup 1))
5436    (clobber (reg:QI 25))
5437    (clobber (reg:QI 26))
5438    (clobber (reg:QI 27))]
5439   ""
5440   "*
5441  {
5442    int len = INTVAL (operands[2]);
5443
5444    output_asm_insn (\"ldiu\\t*%1++,%4\", operands);
5445    if (TARGET_RPTS_CYCLES (len))
5446      {
5447         output_asm_insn (\"rpts\\t%2-2\", operands);  
5448         output_asm_insn (\"sti\\t%4,*%0++\", operands);
5449         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5450         return \"sti\\t%4,*%0++\";
5451      }
5452    else
5453      {
5454         output_asm_insn (\"ldiu\\t%2-2,rc\", operands);
5455         output_asm_insn (\"rptb\\t$+1\", operands);  
5456         output_asm_insn (\"sti\\t%4,*%0++\", operands);
5457         output_asm_insn (\"|| ldi\\t*%1++,%4\", operands);
5458
5459         return \"sti\\t%4,*%0++\";
5460      }
5461   }
5462   "
5463   [(set_attr "type" "multi")])
5464
5465 ; Operand 2 is the count, operand 3 is the alignment.
5466 (define_expand "movstrqi"
5467   [(parallel [(set (mem:BLK (match_operand:BLK 0 "src_operand" ""))
5468                    (mem:BLK (match_operand:BLK 1 "src_operand" "")))
5469               (use (match_operand:QI 2 "immediate_operand" ""))
5470               (use (match_operand:QI 3 "immediate_operand" ""))])]
5471   ""
5472   "
5473  {
5474    rtx tmp;
5475    if (GET_CODE (operands[2]) != CONST_INT 
5476        || INTVAL (operands[2]) > 32767 
5477        || INTVAL (operands[2]) <= 0)
5478      {
5479         FAIL;  /* Try to call _memcpy */
5480      }
5481
5482    operands[0] = copy_to_mode_reg (Pmode, XEXP (operands[0], 0));
5483    operands[1] = copy_to_mode_reg (Pmode, XEXP (operands[1], 0));
5484    tmp = gen_reg_rtx (QImode);
5485    if (INTVAL (operands[2]) < 8)
5486      emit_insn (gen_movstrqi_small2 (operands[0], operands[1], operands[2],
5487                                     operands[3], tmp));
5488    else
5489      {
5490       emit_insn (gen_movstrqi_large (operands[0], operands[1], operands[2],
5491                                      operands[3], tmp));
5492      }
5493    DONE;
5494  }")
5495
5496
5497 (define_insn "*cmpstrqi"
5498   [(set (match_operand:QI 0 "ext_reg_operand" "=d")
5499         (compare:QI (mem:BLK (match_operand:QI 1 "addr_reg_operand" "+a"))
5500                     (mem:BLK (match_operand:QI 2 "addr_reg_operand" "+a"))))
5501    (use (match_operand:QI 3 "immediate_operand" "i"))
5502    (use (match_operand:QI 4 "immediate_operand" ""))
5503    (clobber (match_operand:QI 5 "std_reg_operand" "=&c"))
5504    (clobber (reg:QI 21))]
5505   ""
5506   "*
5507  {
5508     output_asm_insn (\"ldi\\t%3-1,%5\", operands);
5509     output_asm_insn (\"$1:\tsubi3\\t*%1++,*%2++,%0\", operands);
5510     output_asm_insn (\"dbeq\\t%5,$1\", operands);
5511     return \"\";
5512  }")
5513
5514 (define_expand "cmpstrqi"
5515   [(parallel [(set (match_operand:QI 0 "reg_operand" "")
5516                    (compare:QI (match_operand:BLK 1 "general_operand" "")
5517                                (match_operand:BLK 2 "general_operand" "")))
5518               (use (match_operand:QI 3 "immediate_operand" ""))
5519               (use (match_operand:QI 4 "immediate_operand" ""))
5520               (clobber (match_dup 5))
5521               (clobber (reg:QI 21))])]
5522   ""
5523   "
5524 {
5525    if (GET_CODE (operands[3]) != CONST_INT
5526        || INTVAL (operands[3]) > 32767 
5527        || INTVAL (operands[3]) <= 0)
5528      {
5529         FAIL;
5530      }
5531    operands[1] = copy_to_mode_reg (Pmode, XEXP (operands[1], 0));
5532    operands[2] = copy_to_mode_reg (Pmode, XEXP (operands[2], 0));
5533    operands[5] = gen_reg_rtx (QImode);
5534 }")
5535
5536 ;
5537 ; TWO OPERAND LONG DOUBLE INSTRUCTIONS
5538 ;
5539
5540 (define_expand "movhf"
5541   [(set (match_operand:HF 0 "src_operand" "")
5542         (match_operand:HF 1 "src_operand" ""))]
5543  ""
5544  "if (c4x_emit_move_sequence (operands, HFmode))
5545     DONE;")
5546
5547 (define_insn "*movhf_noclobber_reg"
5548   [(set (match_operand:HF 0 "reg_operand" "=h")
5549         (match_operand:HF 1 "src_operand" "Hh"))]
5550  "GET_CODE (operands[1]) != MEM"
5551  "ldfu\\t%1,%0"
5552   [(set_attr "type" "unary")])
5553
5554 (define_insn "*movhf_noclobber"
5555  [(set (match_operand:HF 0 "dst_operand" "=h,m")
5556        (match_operand:HF 1 "src_operand" "Hm,h"))]
5557  "reg_operand (operands[0], HFmode) ^ reg_operand (operands[1], HFmode)"
5558  "#"
5559  [(set_attr "type" "multi,multi")])
5560
5561 (define_insn "*movhf_test"
5562   [(set (reg:CC 21)
5563         (compare:CC (match_operand:HF 1 "reg_operand" "h")
5564                     (const_int 0)))
5565    (clobber (match_scratch:HF 0 "=h"))]
5566  ""
5567  "ldf\\t%1,%0"
5568   [(set_attr "type" "unarycc")])
5569
5570 (define_insn "*movhf_set"
5571   [(set (reg:CC 21)
5572         (compare:CC (match_operand:HF 1 "reg_operand" "h")
5573                     (match_operand:HF 2 "fp_zero_operand" "G")))
5574     (set (match_operand:HF 0 "reg_operand" "=h")
5575          (match_dup 1))]
5576  ""
5577  "ldf\\t%1,%0"
5578   [(set_attr "type" "unarycc")])
5579
5580 (define_split
5581  [(set (match_operand:HF 0 "reg_operand" "")
5582        (match_operand:HF 1 "memory_operand" ""))]
5583  "reload_completed"
5584  [(set (match_dup 0) (float_extend:HF (match_dup 2)))
5585   (set (match_dup 0) (unspec:HF [(subreg:QI (match_dup 0) 0)
5586                                             (match_dup 3)] 8))]
5587  "operands[2] = c4x_operand_subword (operands[1], 0, 1, HFmode);
5588   operands[3] = c4x_operand_subword (operands[1], 1, 1, HFmode);
5589   PUT_MODE (operands[2], QFmode);
5590   PUT_MODE (operands[3], QImode);")
5591
5592 (define_split
5593  [(set (match_operand:HF 0 "reg_operand" "")
5594        (match_operand:HF 1 "const_operand" ""))]
5595  "reload_completed && 0"
5596  [(set (match_dup 0) (float_extend:HF (match_dup 2)))
5597   (set (match_dup 0) (unspec:HF [(subreg:QI (match_dup 0) 0)
5598                                             (match_dup 3)] 8))]
5599  "operands[2] = c4x_operand_subword (operands[1], 0, 1, HFmode);
5600   operands[3] = c4x_operand_subword (operands[1], 1, 1, HFmode);
5601   PUT_MODE (operands[2], QFmode);
5602   PUT_MODE (operands[3], QImode);")
5603
5604 (define_split
5605  [(set (match_operand:HF 0 "memory_operand" "")
5606        (match_operand:HF 1 "reg_operand" ""))]
5607   "reload_completed"
5608   [(set (match_dup 2) (float_truncate:QF (match_dup 1)))
5609    (set (match_dup 3) (unspec:QI [(match_dup 1)] 9))]
5610  "operands[2] = c4x_operand_subword (operands[0], 0, 1, HFmode);
5611   operands[3] = c4x_operand_subword (operands[0], 1, 1, HFmode);
5612   PUT_MODE (operands[2], QFmode);
5613   PUT_MODE (operands[3], QImode);")
5614
5615 (define_insn "*loadhf_float"
5616  [(set (match_operand:HF 0 "reg_operand" "=h")
5617        (float_extend:HF (match_operand:QF 1 "src_operand" "fHm")))]
5618  ""
5619  "@
5620   ldfu\\t%1,%0"
5621   [(set_attr "type" "unary")])
5622
5623 (define_insn "*loadhf_int"
5624  [(set (match_operand:HF 0 "reg_operand" "=h")
5625        (unspec:HF [(subreg:QI (match_dup 0) 0)
5626                    (match_operand:QI 1 "src_operand" "rIm")] 8))]
5627  ""
5628  "@
5629   ldiu\\t%1,%0"
5630   [(set_attr "type" "unary")])
5631
5632 (define_insn "*storehf_float"
5633   [(set (match_operand:QF 0 "memory_operand" "=m")
5634         (float_truncate:QF (match_operand:HF 1 "reg_operand" "h")))]
5635   ""
5636   "stf\\t%1,%0"
5637   [(set_attr "type" "store")])
5638
5639 (define_insn "*storehf_int"
5640  [(set (match_operand:QI 0 "memory_operand" "=m")
5641        (unspec:QI [(match_operand:HF 1 "reg_operand" "h")] 9))]
5642  ""
5643  "@
5644   sti\\t%1,%0"
5645   [(set_attr "type" "store")])
5646
5647 (define_insn "extendqfhf2"
5648   [(set (match_operand:HF 0 "reg_operand" "=h")
5649         (float_extend:HF (match_operand:QF 1 "reg_operand" "h")))]
5650   ""
5651   "ldfu\\t%1,%0"
5652   [(set_attr "type" "unarycc")])
5653
5654 (define_insn "trunchfqf2"
5655   [(set (match_operand:QF 0 "reg_operand" "=h")
5656         (float_truncate:QF (match_operand:HF 1 "reg_operand" "0")))
5657    (clobber (reg:CC 21))]
5658   ""
5659   "andn\\t0ffh,%0"
5660   [(set_attr "type" "unarycc")])
5661
5662 ;
5663 ; PUSH/POP
5664 ;
5665 (define_insn "*pushhf"
5666   [(set (mem:HF (pre_inc:QI (reg:QI 20)))
5667         (match_operand:HF 0 "reg_operand" "h"))]
5668  ""
5669  "#"
5670  [(set_attr "type" "multi")])
5671
5672 (define_split
5673  [(set (mem:HF (pre_inc:QI (reg:QI 20)))
5674         (match_operand:HF 0 "reg_operand" ""))]
5675   "reload_completed"
5676   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
5677         (float_truncate:QF (match_dup 0)))
5678    (set (mem:QI (pre_inc:QI (reg:QI 20)))
5679         (unspec:QI [(match_dup 0)] 9))]
5680  "")
5681
5682 (define_insn "pushhf_trunc"
5683   [(set (mem:QF (pre_inc:QI (reg:QI 20)))
5684         (float_truncate:QF (match_operand:HF 0 "reg_operand" "h")))]
5685  ""
5686  "pushf\\t%0"
5687  [(set_attr "type" "push")])
5688
5689 (define_insn "pushhf_int"
5690   [(set (mem:QI (pre_inc:QI (reg:QI 20)))
5691         (unspec:QI [(match_operand:HF 0 "reg_operand" "h")] 9))]
5692  ""
5693  "push\\t%0"
5694  [(set_attr "type" "push")])
5695
5696 ; we can not use this because the popf will destroy the low 8 bits
5697 ;(define_insn "*pophf"
5698 ;  [(set (match_operand:HF 0 "reg_operand" "=h")
5699 ;        (mem:HF (post_dec:QI (reg:QI 20))))
5700 ;   (clobber (reg:CC 21))]
5701 ; ""
5702 ; "#"
5703 ; [(set_attr "type" "multi")])
5704
5705 (define_split
5706  [(set (match_operand:HF 0 "reg_operand" "")
5707        (mem:HF (post_dec:QI (reg:QI 20))))
5708    (clobber (reg:CC 21))]
5709   "reload_completed"
5710   [(parallel [(set (match_operand:HF 0 "reg_operand" "=h")
5711                    (float_extend:HF (mem:QF (post_dec:QI (reg:QI 20)))))
5712               (clobber (reg:CC 21))])
5713    (parallel [(set (match_dup 0)
5714                    (unspec:HF [(subreg:QI (match_dup 0) 0)
5715                    (mem:QI (post_dec:QI (reg:QI 20)))] 8))
5716               (clobber (reg:CC 21))])]
5717  "")
5718
5719 (define_insn "*pophf_int"
5720  [(set (match_operand:HF 0 "reg_operand" "=h")
5721        (unspec:HF [(subreg:QI (match_dup 0) 0)
5722                    (mem:QI (post_dec:QI (reg:QI 20)))] 8))
5723   (clobber (reg:CC 21))]
5724  ""
5725  "@
5726   pop\\t%0"
5727   [(set_attr "type" "pop")])
5728
5729 (define_insn "*pophf_float"
5730  [(set (match_operand:HF 0 "reg_operand" "=h")
5731        (float_extend:HF (mem:QF (post_dec:QI (reg:QI 20)))))
5732   (clobber (reg:CC 21))]
5733  ""
5734  "@
5735   popf\\t%0"
5736   [(set_attr "type" "unary")])
5737
5738 ;
5739 ; FIX
5740 ;
5741 (define_insn "fixhfqi_clobber"
5742   [(set (match_operand:QI 0 "reg_operand" "=dc")
5743         (fix:QI (match_operand:HF 1 "reg_or_const_operand" "hH")))
5744    (clobber (reg:CC 21))]
5745  ""
5746  "fix\\t%1,%0"
5747   [(set_attr "type" "unarycc")])
5748
5749 ;
5750 ; ABSF
5751 ;
5752 (define_expand "abshf2"
5753   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
5754                    (abs:HF (match_operand:HF 1 "reg_or_const_operand" "")))
5755               (clobber (reg:CC_NOOV 21))])]
5756 ""
5757 "")
5758
5759 (define_insn "*abshf2_clobber"
5760   [(set (match_operand:HF 0 "reg_operand" "=h")
5761         (abs:HF (match_operand:HF 1 "reg_or_const_operand" "hH")))
5762    (clobber (reg:CC_NOOV 21))]
5763   ""
5764   "absf\\t%1,%0"
5765   [(set_attr "type" "unarycc")])
5766
5767 (define_insn "*abshf2_test"
5768   [(set (reg:CC_NOOV 21)
5769         (compare:CC_NOOV (abs:HF (match_operand:HF 1 "reg_operand" "h"))
5770                          (match_operand:HF 2 "fp_zero_operand" "G")))
5771    (clobber (match_scratch:HF 0 "=h"))]
5772   ""
5773   "absf\\t%1,%0"
5774   [(set_attr "type" "unarycc")])
5775
5776 (define_insn "*abshf2_set"
5777   [(set (reg:CC_NOOV 21)
5778         (compare:CC_NOOV (abs:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
5779                          (match_operand:HF 2 "fp_zero_operand" "G")))
5780    (set (match_operand:HF 0 "reg_operand" "=h")
5781         (abs:HF (match_dup 1)))]
5782
5783   ""
5784   "absf\\t%1,%0"
5785   [(set_attr "type" "unarycc")])
5786
5787 ;
5788 ; NEGF
5789 ;
5790 (define_expand "neghf2"
5791   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
5792                    (neg:HF (match_operand:HF 1 "reg_or_const_operand" "")))
5793               (clobber (reg:CC 21))])]
5794 ""
5795 "")
5796
5797 (define_insn "*neghf2_clobber"
5798   [(set (match_operand:HF 0 "reg_operand" "=h")
5799         (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH")))
5800    (clobber (reg:CC 21))]
5801   ""
5802   "negf\\t%1,%0"
5803   [(set_attr "type" "unarycc")])
5804
5805 (define_insn "*neghf2_test"
5806   [(set (reg:CC 21)
5807         (compare:CC (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
5808                     (match_operand:HF 2 "fp_zero_operand" "G")))
5809    (clobber (match_scratch:HF 0 "=h"))]
5810   ""
5811   "negf\\t%1,%0"
5812   [(set_attr "type" "unarycc")])
5813
5814 (define_insn "*neghf2_set"
5815   [(set (reg:CC 21)
5816         (compare:CC (neg:HF (match_operand:HF 1 "reg_or_const_operand" "hH"))
5817                     (match_operand:HF 2 "fp_zero_operand" "G")))
5818    (set (match_operand:HF 0 "reg_operand" "=h")
5819         (neg:HF (match_dup 1)))]
5820   ""
5821   "negf\\t%1,%0"
5822   [(set_attr "type" "unarycc")])
5823
5824 ;
5825 ; RCPF
5826 ;
5827 (define_insn "*rcpfhf_clobber"
5828   [(set (match_operand:HF 0 "reg_operand" "=h")
5829         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] 5))
5830    (clobber (reg:CC_NOOV 21))]
5831   "! TARGET_C3X"
5832   "rcpf\\t%1,%0"
5833   [(set_attr "type" "unarycc")])
5834
5835 ;
5836 ; RSQRF
5837 ;
5838 (define_insn "*rsqrfhf_clobber"
5839   [(set (match_operand:HF 0 "reg_operand" "=h")
5840         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] 10))
5841    (clobber (reg:CC_NOOV 21))]
5842   "! TARGET_C3X"
5843   "rsqrf\\t%1,%0"
5844   [(set_attr "type" "unarycc")])
5845
5846 ;
5847 ; RNDF
5848 ;
5849 (define_insn "*rndhf_clobber"
5850   [(set (match_operand:HF 0 "reg_operand" "=h")
5851         (unspec:HF [(match_operand:HF 1 "reg_or_const_operand" "hH")] 6))
5852    (clobber (reg:CC_NOOV 21))]
5853   "! TARGET_C3X"
5854   "rnd\\t%1,%0"
5855   [(set_attr "type" "unarycc")])
5856
5857
5858 ; Inlined float square root for C4x
5859 (define_expand "sqrthf2_inline"
5860   [(parallel [(set (match_dup 2)
5861                    (unspec:HF [(match_operand:HF 1 "reg_operand" "")] 10))
5862               (clobber (reg:CC_NOOV 21))])
5863    (parallel [(set (match_dup 3) (mult:HF (match_dup 5) (match_dup 1)))
5864               (clobber (reg:CC_NOOV 21))])
5865    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
5866               (clobber (reg:CC_NOOV 21))])
5867    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 4)))
5868               (clobber (reg:CC_NOOV 21))])
5869    (parallel [(set (match_dup 4) (minus:HF (match_dup 6) (match_dup 4)))
5870               (clobber (reg:CC_NOOV 21))])
5871    (parallel [(set (match_dup 2) (mult:HF (match_dup 2) (match_dup 4)))
5872               (clobber (reg:CC_NOOV 21))])
5873    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
5874               (clobber (reg:CC_NOOV 21))])
5875    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 4)))
5876               (clobber (reg:CC_NOOV 21))])
5877    (parallel [(set (match_dup 4) (minus:HF (match_dup 6) (match_dup 4)))
5878               (clobber (reg:CC_NOOV 21))])
5879    (parallel [(set (match_dup 2) (mult:HF (match_dup 2) (match_dup 4)))
5880               (clobber (reg:CC_NOOV 21))])
5881    (parallel [(set (match_operand:HF 0 "reg_operand" "")
5882                    (mult:HF (match_dup 2) (match_dup 1)))
5883               (clobber (reg:CC_NOOV 21))])]
5884   "! TARGET_C3X"
5885   "
5886   operands[2] = gen_reg_rtx (HFmode);
5887   operands[3] = gen_reg_rtx (HFmode);
5888   operands[4] = gen_reg_rtx (HFmode);
5889   operands[5] = immed_real_const_1 (REAL_VALUE_ATOF (\"0.5\", HFmode), HFmode);
5890   operands[6] = immed_real_const_1 (REAL_VALUE_ATOF (\"1.5\", HFmode), HFmode);
5891   ")
5892
5893
5894 (define_expand "sqrthf2"
5895   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
5896                    (sqrt:HF (match_operand:HF 1 "reg_operand" "")))
5897               (clobber (reg:CC 21))])]
5898   "! TARGET_C3X && TARGET_INLINE"
5899   "emit_insn (gen_sqrthf2_inline (operands[0], operands[1]));
5900    DONE;")
5901
5902
5903 (define_expand "fix_trunchfhi2"
5904   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
5905                    (fix:HI (match_operand:HF 1 "reg_operand" "")))
5906               (clobber (reg:CC 21))])]
5907   ""
5908   "c4x_emit_libcall (FIX_TRUNCHFHI2_LIBCALL, FIX, HImode, HFmode, 2, operands);
5909    DONE;")
5910
5911 (define_expand "fixuns_trunchfhi2"
5912   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
5913                    (unsigned_fix:HI (match_operand:HF 1 "reg_operand" "")))
5914               (clobber (reg:CC 21))])]
5915   ""
5916   "c4x_emit_libcall (FIXUNS_TRUNCHFHI2_LIBCALL, UNSIGNED_FIX, 
5917                      HImode, HFmode, 2, operands);
5918    DONE;")
5919
5920 ;
5921 ; THREE OPERAND LONG DOUBLE INSTRUCTIONS
5922 ;
5923
5924 ;
5925 ; ADDF
5926 ;
5927 (define_insn "addhf3"
5928   [(set (match_operand:HF 0 "reg_operand" "=h,?h")
5929         (plus:HF (match_operand:HF 1 "reg_operand" "%0,h")
5930                  (match_operand:HF 2 "reg_or_const_operand" "H,h")))
5931    (clobber (reg:CC_NOOV 21))]
5932   ""
5933   "@
5934    addf\\t%2,%0
5935    addf3\\t%2,%1,%0"
5936   [(set_attr "type" "binarycc,binarycc")])
5937
5938 ;
5939 ; SUBF
5940 ;
5941 (define_insn "subhf3"
5942   [(set (match_operand:HF 0 "reg_operand" "=h,h,?h")
5943         (minus:HF (match_operand:HF 1 "reg_or_const_operand" "0,H,h")
5944                   (match_operand:HF 2 "reg_or_const_operand" "H,0,h")))
5945    (clobber (reg:CC_NOOV 21))]
5946   ""
5947   "@
5948    subf\\t%2,%0
5949    subrf\\t%1,%0
5950    subf3\\t%2,%1,%0"
5951   [(set_attr "type" "binarycc,binarycc,binarycc")])
5952
5953 ;
5954 ; MULF
5955 ;
5956 ; The C3x MPYF only uses 24 bit precision while the C4x uses 32 bit precison.
5957 ;
5958 (define_expand "mulhf3"
5959   [(parallel [(set (match_operand:HF 0 "reg_operand" "=h")
5960                    (mult:HF (match_operand:HF 1 "reg_operand" "h")
5961                             (match_operand:HF 2 "reg_operand" "h")))
5962               (clobber (reg:CC_NOOV 21))])]
5963   "! TARGET_C3X"
5964   "")
5965
5966 (define_insn "*mulhf3_c40"
5967   [(set (match_operand:HF 0 "reg_operand" "=h,?h")
5968         (mult:HF (match_operand:HF 1 "reg_operand" "%0,h")
5969                  (match_operand:HF 2 "reg_or_const_operand" "hH,h")))
5970    (clobber (reg:CC_NOOV 21))]
5971   ""
5972   "@
5973    mpyf\\t%2,%0
5974    mpyf3\\t%2,%1,%0"
5975   [(set_attr "type" "binarycc,binarycc")])
5976
5977 ;
5978 ; CMPF
5979 ;
5980 (define_expand "cmphf"
5981   [(set (reg:CC 21)
5982         (compare:CC (match_operand:HF 0 "reg_operand" "")
5983                     (match_operand:HF 1 "reg_or_const_operand" "")))]
5984   ""
5985   "c4x_compare_op0 = operands[0];
5986    c4x_compare_op1 = operands[1];
5987    DONE;")
5988
5989 (define_insn "*cmphf"
5990   [(set (reg:CC 21)
5991         (compare:CC (match_operand:HF 0 "reg_operand" "h")
5992                     (match_operand:HF 1 "reg_or_const_operand" "hH")))]
5993   ""
5994   "cmpf\\t%1,%0"
5995   [(set_attr "type" "compare")])
5996
5997 (define_insn "*cmphf_noov"
5998   [(set (reg:CC_NOOV 21)
5999         (compare:CC_NOOV (match_operand:HF 0 "reg_operand" "h")
6000                          (match_operand:HF 1 "reg_or_const_operand" "hH")))]
6001   ""
6002   "cmpf\\t%1,%0"
6003   [(set_attr "type" "compare")])
6004
6005 ; Inlined float divide for C4x
6006 (define_expand "divhf3_inline"
6007   [(parallel [(set (match_dup 3)
6008                    (unspec:HF [(match_operand:HF 2 "reg_operand" "")] 5))
6009               (clobber (reg:CC_NOOV 21))])
6010    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6011               (clobber (reg:CC_NOOV 21))])
6012    (parallel [(set (match_dup 4) (minus:HF (match_dup 5) (match_dup 4)))
6013               (clobber (reg:CC_NOOV 21))])
6014    (parallel [(set (match_dup 3) (mult:HF (match_dup 3) (match_dup 4)))
6015               (clobber (reg:CC_NOOV 21))])
6016    (parallel [(set (match_dup 4) (mult:HF (match_dup 2) (match_dup 3)))
6017               (clobber (reg:CC_NOOV 21))])
6018    (parallel [(set (match_dup 4) (minus:HF (match_dup 5) (match_dup 4)))
6019               (clobber (reg:CC_NOOV 21))])
6020    (parallel [(set (match_dup 3) (mult:HF (match_dup 3) (match_dup 4)))
6021               (clobber (reg:CC_NOOV 21))])
6022    (parallel [(set (match_operand:HF 0 "reg_operand" "")
6023                    (mult:HF (match_operand:HF 1 "reg_operand" "")
6024                             (match_dup 3)))
6025               (clobber (reg:CC_NOOV 21))])]
6026   "! TARGET_C3X"
6027   "
6028   operands[3] = gen_reg_rtx (HFmode);
6029   operands[4] = gen_reg_rtx (HFmode);
6030   operands[5] = CONST2_RTX (HFmode);
6031   ")
6032
6033 (define_expand "divhf3"
6034   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6035                    (div:HF (match_operand:HF 1 "reg_operand" "")
6036                            (match_operand:HF 2 "reg_operand" "")))
6037               (clobber (reg:CC 21))])]
6038   "! TARGET_C3X && TARGET_INLINE"
6039   "emit_insn (gen_divhf3_inline (operands[0], operands[1], operands[2]));
6040    DONE;")
6041
6042
6043 ;
6044 ; TWO OPERAND LONG LONG INSTRUCTIONS
6045 ;
6046
6047 (define_insn "*movhi_stik"
6048   [(set (match_operand:HI 0 "memory_operand" "=m")
6049         (match_operand:HI 1 "stik_const_operand" "K"))]
6050   "! TARGET_C3X"
6051   "#"
6052   [(set_attr "type" "multi")])
6053
6054 ; We could load some constants using define_splits for the C30
6055 ; in the large memory model---these would emit shift and or insns.
6056 (define_expand "movhi"
6057   [(set (match_operand:HI 0 "src_operand" "")
6058         (match_operand:HI 1 "src_operand" ""))]
6059  ""
6060  "if (c4x_emit_move_sequence (operands, HImode))
6061     DONE;")
6062
6063 ; The constraints for movhi must include 'r' if we don't
6064 ; restrict HImode regnos to start on an even number, since
6065 ; we can get RC, R8 allocated as a pair.  We want more
6066 ; votes for FP_REGS so we use dr as the constraints.
6067 (define_insn "*movhi_noclobber"
6068   [(set (match_operand:HI 0 "dst_operand" "=dr,m")
6069         (match_operand:HI 1 "src_operand" "drIm,r"))]
6070   "reg_operand (operands[0], HImode)
6071    || reg_operand (operands[1], HImode)"
6072   "#"
6073   [(set_attr "type" "multi,multi")])
6074
6075 ; This will fail miserably if the destination register is used in the 
6076 ; source memory address.
6077 ; The usual strategy in this case is to swap the order of insns we emit,
6078 ; however, this will fail if we have an autoincrement memory address.
6079 ; For example:
6080 ; ldi *ar0++, ar0
6081 ; ldi *ar0++, ar1
6082 ;
6083 ; We could convert this to
6084 ; ldi *ar0(1), ar1
6085 ; ldi *ar0, ar0
6086 ;
6087 ; However, things are likely to be very screwed up if we get this.
6088
6089 (define_split
6090   [(set (match_operand:HI 0 "dst_operand" "")
6091         (match_operand:HI 1 "src_operand" ""))]
6092   "reload_completed
6093    && (reg_operand (operands[0], HImode)
6094        || reg_operand (operands[1], HImode)
6095        || stik_const_operand (operands[1], HImode))"
6096   [(set (match_dup 2) (match_dup 4))
6097    (set (match_dup 3) (match_dup 5))]
6098   "operands[2] = c4x_operand_subword (operands[0], 0, 1, HImode);
6099    operands[3] = c4x_operand_subword (operands[0], 1, 1, HImode);
6100    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6101    operands[5] = c4x_operand_subword (operands[1], 1, 1, HImode);
6102    if (reg_overlap_mentioned_p (operands[2], operands[5]))
6103      {
6104         /* Swap order of move insns.  */
6105         rtx tmp;
6106         tmp = operands[2];
6107         operands[2] =operands[3];
6108         operands[3] = tmp;
6109         tmp = operands[4];
6110         operands[4] =operands[5];
6111         operands[5] = tmp;        
6112      }")
6113
6114
6115 (define_insn "extendqihi2"
6116   [(set (match_operand:HI 0 "reg_operand" "=dc")
6117         (sign_extend:HI (match_operand:QI 1 "src_operand" "rIm")))
6118    (clobber (reg:CC 21))]
6119   ""
6120   "#"
6121   [(set_attr "type" "multi")])
6122
6123 (define_split
6124   [(set (match_operand:HI 0 "reg_operand" "=?dc")
6125         (sign_extend:HI (match_operand:QI 1 "src_operand" "rIm")))
6126    (clobber (reg:CC 21))]
6127   "reload_completed && TARGET_C3X"
6128   [(set (match_dup 2) (match_dup 1))
6129    (set (match_dup 3) (match_dup 2))
6130    (parallel [(set (match_dup 3) (ashiftrt:QI (match_dup 3) (const_int 31)))
6131               (clobber (reg:CC 21))])]
6132   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6133    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6134
6135 (define_split
6136   [(set (match_operand:HI 0 "reg_operand" "=?dc")
6137         (sign_extend:HI (match_operand:QI 1 "src_operand" "rIm")))
6138    (clobber (reg:CC 21))]
6139   "reload_completed && ! TARGET_C3X"
6140   [(set (match_dup 2) (match_dup 1))
6141    (parallel [(set (match_dup 3) (ashiftrt:QI (match_dup 2) (const_int 31)))
6142               (clobber (reg:CC 21))])]
6143   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6144    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6145
6146 (define_insn "zero_extendqihi2"
6147   [(set (match_operand:HI 0 "reg_operand" "=?dc")
6148         (zero_extend:HI (match_operand:QI 1 "src_operand" "rIm")))
6149    (clobber (reg:CC 21))]
6150   ""
6151   "#"
6152   [(set_attr "type" "multi")])
6153
6154 ; If operand0 and operand1 are the same register we don't need
6155 ; the first set.
6156 (define_split
6157   [(set (match_operand:HI 0 "reg_operand" "=?dc")
6158         (zero_extend:HI (match_operand:QI 1 "src_operand" "rIm")))
6159    (clobber (reg:CC 21))]
6160   "reload_completed"
6161   [(set (match_dup 2) (match_dup 1))
6162    (set (match_dup 3) (const_int 0))]
6163   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6164    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6165
6166 ;
6167 ; PUSH/POP
6168 ;
6169 (define_insn "*pushhi"
6170   [(set (mem:HI (pre_inc:QI (reg:QI 20)))
6171         (match_operand:HI 0 "reg_operand" "r"))]
6172   ""
6173   "#"
6174   [(set_attr "type" "multi")])
6175
6176 (define_split
6177   [(set (mem:HI (pre_inc:QI (reg:QI 20)))
6178         (match_operand:HI 0 "reg_operand" ""))]
6179   "reload_completed"
6180   [(set (mem:QI (pre_inc:QI (reg:QI 20))) (match_dup 2))
6181    (set (mem:QI (pre_inc:QI (reg:QI 20))) (match_dup 3))]
6182   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6183    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6184
6185 (define_insn "*pophi"
6186   [(set (match_operand:HI 0 "reg_operand" "=r")
6187         (mem:HI (post_dec:QI (reg:QI 20))))
6188    (clobber (reg:CC 21))]
6189   ""
6190   "#"
6191   [(set_attr "type" "multi")])
6192
6193 (define_split
6194   [(set (match_operand:HI 0 "reg_operand" "")
6195        (mem:HI (pre_inc:QI (reg:QI 20))))]
6196   "reload_completed"
6197   [(set (match_dup 2) (mem:QI (pre_inc:QI (reg:QI 20))))
6198    (set (match_dup 3) (mem:QI (pre_inc:QI (reg:QI 20))))]
6199   "operands[2] = c4x_operand_subword (operands[0], 0, 0, HImode);
6200    operands[3] = c4x_operand_subword (operands[0], 1, 0, HImode);")
6201
6202 ;
6203 ; NEG
6204 ;
6205 (define_insn "neghi2"
6206   [(set (match_operand:HI 0 "ext_reg_operand" "=d")
6207         (neg:HI (match_operand:HI 1 "src_operand" "rm")))
6208    (clobber (reg:CC_NOOV 21))]
6209   ""
6210   "#"
6211   [(set_attr "type" "multi")])
6212
6213 (define_split
6214   [(set (match_operand:HI 0 "ext_reg_operand" "")
6215         (neg:HI (match_operand:HI 1 "src_operand" "")))
6216    (clobber (reg:CC_NOOV 21))]
6217   "reload_completed"
6218    [(parallel [(set (reg:CC_NOOV 21)
6219                     (compare:CC_NOOV (neg:QI (match_dup 3))
6220                                      (const_int 0)))
6221                (set (match_dup 2) (neg:QI (match_dup 3)))])
6222    (parallel [(set (match_dup 4) (neg:QI (match_dup 5)))
6223               (use (reg:CC_NOOV 21))
6224               (clobber (reg:CC_NOOV 21))])]
6225   "operands[2] = c4x_operand_subword (operands[0], 0, 1, HImode);
6226    operands[3] = c4x_operand_subword (operands[1], 0, 1, HImode);
6227    operands[4] = c4x_operand_subword (operands[0], 1, 1, HImode);
6228    operands[5] = c4x_operand_subword (operands[1], 1, 1, HImode);")
6229
6230 (define_insn "one_cmplhi2"
6231   [(set (match_operand:HI 0 "reg_operand" "=r")
6232         (not:HI (match_operand:HI 1 "src_operand" "rm")))
6233    (clobber (reg:CC 21))]
6234   ""
6235   "#"
6236   [(set_attr "type" "multi")])
6237
6238 (define_split
6239   [(set (match_operand:HI 0 "reg_operand" "")
6240         (not:HI (match_operand:HI 1 "src_operand" "")))
6241    (clobber (reg:CC 21))]
6242   "reload_completed"
6243    [(parallel [(set (match_dup 2) (not:QI (match_dup 3)))
6244                (clobber (reg:CC 21))])
6245     (parallel [(set (match_dup 4) (not:QI (match_dup 5)))
6246                (clobber (reg:CC 21))])]
6247   "operands[2] = c4x_operand_subword (operands[0], 0, 1, HImode);
6248    operands[3] = c4x_operand_subword (operands[1], 0, 1, HImode);
6249    operands[4] = c4x_operand_subword (operands[0], 1, 1, HImode);
6250    operands[5] = c4x_operand_subword (operands[1], 1, 1, HImode);")
6251
6252 (define_expand "floathiqf2"
6253   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
6254                    (float:QF (match_operand:HI 1 "src_operand" "")))
6255               (clobber (reg:CC 21))])]
6256   ""
6257   "c4x_emit_libcall (FLOATHIQF2_LIBCALL, FLOAT, QFmode, HImode, 2, operands);
6258    DONE;")
6259
6260 (define_expand "floatunshiqf2"
6261   [(parallel [(set (match_operand:QF 0 "reg_operand" "")
6262                    (unsigned_float:QF (match_operand:HI 1 "src_operand" "")))
6263               (clobber (reg:CC 21))])]
6264   ""
6265   "c4x_emit_libcall (FLOATUNSHIQF2_LIBCALL, UNSIGNED_FLOAT,
6266                      QFmode, HImode, 2, operands);
6267    DONE;")
6268
6269 (define_expand "floathihf2"
6270   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6271                    (float:HF (match_operand:HI 1 "src_operand" "")))
6272               (clobber (reg:CC 21))])]
6273   ""
6274   "c4x_emit_libcall (FLOATHIHF2_LIBCALL, FLOAT, HFmode, HImode, 2, operands);
6275    DONE;")
6276
6277 (define_expand "floatunshihf2"
6278   [(parallel [(set (match_operand:HF 0 "reg_operand" "")
6279                    (unsigned_float:HF (match_operand:HI 1 "src_operand" "")))
6280               (clobber (reg:CC 21))])]
6281   ""
6282   "c4x_emit_libcall (FLOATUNSHIHF2_LIBCALL, UNSIGNED_FLOAT,
6283                      HFmode, HImode, 2, operands);
6284    DONE;")
6285
6286
6287 ;
6288 ; THREE OPERAND LONG LONG INSTRUCTIONS
6289 ;
6290
6291 (define_expand "addhi3"
6292   [(parallel [(set (match_operand:HI 0 "ext_reg_operand" "")
6293                    (plus:HI (match_operand:HI 1 "src_operand" "")
6294                             (match_operand:HI 2 "src_operand" "")))
6295               (clobber (reg:CC_NOOV 21))])]
6296   ""
6297   "legitimize_operands (PLUS, operands, HImode);")
6298
6299 (define_insn "*addhi3_clobber"
6300   [(set (match_operand:HI 0 "ext_reg_operand" "=d,d,?d")
6301         (plus:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6302                  (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6303    (clobber (reg:CC_NOOV 21))]
6304   "valid_operands (PLUS, operands, HImode)"
6305   "#"
6306   [(set_attr "type" "multi,multi,multi")])
6307
6308 (define_split
6309  [(set (match_operand:HI 0 "ext_reg_operand" "")
6310        (plus:HI (match_operand:HI 1 "src_operand" "")
6311                 (match_operand:HI 2 "src_operand" "")))
6312   (clobber (reg:CC_NOOV 21))]
6313  "reload_completed"
6314   [(parallel [(set (reg:CC_NOOV 21)
6315                    (compare:CC_NOOV (plus:QI (match_dup 4) (match_dup 5))
6316                                     (const_int 0)))
6317               (set (match_dup 3) (plus:QI (match_dup 4) (match_dup 5)))])
6318    (parallel [(set (match_dup 6) (plus:QI (match_dup 7) (match_dup 8)))
6319               (use (reg:CC_NOOV 21))
6320               (clobber (reg:CC_NOOV 21))])]
6321   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6322    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6323    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6324    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6325    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6326    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6327
6328 (define_expand "subhi3"
6329   [(parallel [(set (match_operand:HI 0 "ext_reg_operand" "")
6330                    (minus:HI (match_operand:HI 1 "src_operand" "")
6331                              (match_operand:HI 2 "src_operand" "")))
6332               (clobber (reg:CC_NOOV 21))])]
6333   ""
6334   "legitimize_operands (MINUS, operands, HImode);")
6335
6336
6337 (define_insn "*subhi3_clobber"
6338   [(set (match_operand:HI 0 "ext_reg_operand" "=d,d,?d")
6339         (minus:HI (match_operand:HI 1 "src_operand" "0,rR,rS<>")
6340                   (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6341    (clobber (reg:CC_NOOV 21))]
6342   "valid_operands (MINUS, operands, HImode)"
6343   "#"
6344   [(set_attr "type" "multi,multi,multi")])
6345
6346 (define_split
6347  [(set (match_operand:HI 0 "ext_reg_operand" "")
6348        (minus:HI (match_operand:HI 1 "src_operand" "")
6349                  (match_operand:HI 2 "src_operand" "")))
6350   (clobber (reg:CC_NOOV 21))]
6351  "reload_completed"
6352   [(parallel [(set (reg:CC_NOOV 21)
6353                    (compare:CC_NOOV (minus:QI (match_dup 4) (match_dup 5))
6354                                     (const_int 0)))
6355               (set (match_dup 3) (minus:QI (match_dup 4) (match_dup 5)))])
6356    (parallel [(set (match_dup 6) (minus:QI (match_dup 7) (match_dup 8)))
6357               (use (reg:CC_NOOV 21))
6358               (clobber (reg:CC_NOOV 21))])]
6359   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6360    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6361    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6362    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6363    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6364    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6365
6366 (define_expand "iorhi3"
6367   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6368                    (ior:HI (match_operand:HI 1 "src_operand" "")
6369                            (match_operand:HI 2 "src_operand" "")))
6370               (clobber (reg:CC 21))])]
6371   ""
6372   "legitimize_operands (IOR, operands, HImode);")
6373
6374 (define_insn "*iorhi3_clobber"
6375   [(set (match_operand:HI 0 "reg_operand" "=d,d,?d")
6376         (ior:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6377                 (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6378    (clobber (reg:CC 21))]
6379   "valid_operands (IOR, operands, HImode)"
6380   "#"
6381   [(set_attr "type" "multi,multi,multi")])
6382
6383 (define_split
6384  [(set (match_operand:HI 0 "reg_operand" "")
6385        (ior:HI (match_operand:HI 1 "src_operand" "")
6386                (match_operand:HI 2 "src_operand" "")))
6387   (clobber (reg:CC 21))]
6388  "reload_completed"
6389   [(parallel [(set (match_dup 3) (ior:QI (match_dup 4) (match_dup 5)))
6390               (clobber (reg:CC 21))])
6391    (parallel [(set (match_dup 6) (ior:QI (match_dup 7) (match_dup 8)))
6392               (clobber (reg:CC 21))])]
6393   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6394    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6395    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6396    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6397    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6398    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6399
6400 (define_expand "andhi3"
6401   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6402                    (and:HI (match_operand:HI 1 "src_operand" "")
6403                            (match_operand:HI 2 "src_operand" "")))
6404               (clobber (reg:CC 21))])]
6405   ""
6406   "legitimize_operands (AND, operands, HImode);")
6407
6408 (define_insn "*andhi3_clobber"
6409   [(set (match_operand:HI 0 "reg_operand" "=d,d,?d")
6410         (and:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6411                 (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6412    (clobber (reg:CC 21))]
6413   "valid_operands (AND, operands, HImode)"
6414   "#"
6415   [(set_attr "type" "multi,multi,multi")])
6416
6417 (define_split
6418  [(set (match_operand:HI 0 "reg_operand" "")
6419        (and:HI (match_operand:HI 1 "src_operand" "")
6420                 (match_operand:HI 2 "src_operand" "")))
6421   (clobber (reg:CC 21))]
6422  "reload_completed"
6423   [(parallel [(set (match_dup 3) (and:QI (match_dup 4) (match_dup 5)))
6424               (clobber (reg:CC 21))])
6425    (parallel [(set (match_dup 6) (and:QI (match_dup 7) (match_dup 8)))
6426               (clobber (reg:CC 21))])]
6427   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6428    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6429    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6430    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6431    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6432    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6433
6434 (define_expand "xorhi3"
6435   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6436                    (xor:HI (match_operand:HI 1 "src_operand" "")
6437                            (match_operand:HI 2 "src_operand" "")))
6438               (clobber (reg:CC 21))])]
6439   ""
6440   "legitimize_operands (XOR, operands, HImode);")
6441
6442
6443 (define_insn "*xorhi3_clobber"
6444   [(set (match_operand:HI 0 "reg_operand" "=d,d,?d")
6445         (xor:HI (match_operand:HI 1 "src_operand" "%0,rR,rS<>")
6446                 (match_operand:HI 2 "src_operand" "rm,R,rS<>")))
6447    (clobber (reg:CC 21))]
6448   "valid_operands (XOR, operands, HImode)"
6449   "#"
6450   [(set_attr "type" "multi,multi,multi")])
6451
6452 (define_split
6453  [(set (match_operand:HI 0 "reg_operand" "")
6454        (xor:HI (match_operand:HI 1 "src_operand" "")
6455                (match_operand:HI 2 "src_operand" "")))
6456   (clobber (reg:CC 21))]
6457  "reload_completed"
6458   [(parallel [(set (match_dup 3) (xor:QI (match_dup 4) (match_dup 5)))
6459               (clobber (reg:CC 21))])
6460    (parallel [(set (match_dup 6) (xor:QI (match_dup 7) (match_dup 8)))
6461               (clobber (reg:CC 21))])]
6462   "operands[3] = c4x_operand_subword (operands[0], 0, 1, HImode);
6463    operands[4] = c4x_operand_subword (operands[1], 0, 1, HImode);
6464    operands[5] = c4x_operand_subword (operands[2], 0, 1, HImode);
6465    operands[6] = c4x_operand_subword (operands[0], 1, 1, HImode);
6466    operands[7] = c4x_operand_subword (operands[1], 1, 1, HImode);
6467    operands[8] = c4x_operand_subword (operands[2], 1, 1, HImode);")
6468
6469 (define_expand "ashlhi3"
6470  [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6471              (ashift:HI (match_operand:HI 1 "src_operand" "")
6472                         (match_operand:QI 2 "src_operand" "")))
6473              (clobber (reg:CC 21))])]
6474  ""
6475  "if (GET_CODE (operands[2]) == CONST_INT && INTVAL (operands[2]) >= 32)
6476     {
6477        rtx op0hi = operand_subword (operands[0], 1, 0, HImode);
6478        rtx op0lo = operand_subword (operands[0], 0, 0, HImode);
6479        rtx op1lo = operand_subword (operands[1], 0, 0, HImode);
6480        rtx count = GEN_INT ((INTVAL (operands[2]) - 32));
6481
6482        if (INTVAL (count))
6483          emit_insn (gen_ashlqi3 (op0hi, op1lo, count));
6484        else
6485          emit_insn (gen_movqi (op0hi, op1lo));
6486        emit_insn (gen_movqi (op0lo, const0_rtx));
6487        DONE;
6488     }
6489   if (! REG_P (operands[1]))
6490     operands[1] = force_reg (HImode, operands[1]);
6491   emit_insn (gen_ashlhi3_reg (operands[0], operands[1], operands[2]));
6492   DONE;
6493  ")
6494
6495 ; %0.lo = %1.lo << %2
6496 ; %0.hi = (%1.hi << %2 ) | (%1.lo >> (32 - %2))
6497 ; This algorithm should work for shift counts greater than 32
6498 (define_expand "ashlhi3_reg" 
6499  [(use (match_operand:HI 1 "reg_operand" ""))
6500   (use (match_operand:HI 0 "reg_operand" ""))
6501   /* If the shift count is greater than 32 this will give zero.  */
6502   (parallel [(set (match_dup 7)
6503                   (ashift:QI (match_dup 3)
6504                              (match_operand:QI 2 "reg_operand" "")))
6505              (clobber (reg:CC 21))])
6506   /* If the shift count is greater than 32 this will give zero.  */
6507   (parallel [(set (match_dup 8)
6508                   (ashift:QI (match_dup 4) (match_dup 2)))
6509              (clobber (reg:CC 21))])
6510   (parallel [(set (match_dup 10)
6511                   (plus:QI (match_dup 2) (const_int -32)))
6512              (clobber (reg:CC_NOOV 21))])
6513   /* If the shift count is greater than 32 this will do a left shift.  */
6514   (parallel [(set (match_dup 9)
6515                   (lshiftrt:QI (match_dup 3) (neg:QI (match_dup 10))))
6516              (clobber (reg:CC 21))])
6517   (set (match_dup 5) (match_dup 7))
6518   (parallel [(set (match_dup 6)
6519                   (ior:QI (match_dup 8) (match_dup 9)))
6520              (clobber (reg:CC 21))])]
6521  ""
6522  " 
6523   operands[3] = operand_subword (operands[1], 0, 1, HImode); /* lo */
6524   operands[4] = operand_subword (operands[1], 1, 1, HImode); /* hi */
6525   operands[5] = operand_subword (operands[0], 0, 1, HImode); /* lo */
6526   operands[6] = operand_subword (operands[0], 1, 1, HImode); /* hi */
6527   operands[7] = gen_reg_rtx (QImode); /* lo << count */
6528   operands[8] = gen_reg_rtx (QImode); /* hi << count */
6529   operands[9] = gen_reg_rtx (QImode); /* lo >> (32 - count) */
6530   operands[10] = gen_reg_rtx (QImode); /* 32 - count */
6531  ")
6532
6533 ; This should do all the dirty work with define_split
6534 (define_expand "lshrhi3"
6535  [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6536              (lshiftrt:HI (match_operand:HI 1 "src_operand" "")
6537                           (match_operand:QI 2 "src_operand" "")))
6538              (clobber (reg:CC 21))])]
6539  ""
6540  "if (GET_CODE (operands[2]) == CONST_INT && INTVAL (operands[2]) >= 32)
6541     {
6542        rtx op0hi = operand_subword (operands[0], 1, 0, HImode);
6543        rtx op0lo = operand_subword (operands[0], 0, 0, HImode);
6544        rtx op1hi = operand_subword (operands[1], 1, 0, HImode);
6545        rtx count = GEN_INT ((INTVAL (operands[2]) - 32));
6546
6547        if (INTVAL (count))
6548          emit_insn (gen_lshrqi3 (op0lo, op1hi, count));
6549        else
6550          emit_insn (gen_movqi (op0lo, op1hi));
6551        emit_insn (gen_movqi (op0hi, const0_rtx));
6552        DONE;
6553     }
6554   if (! REG_P (operands[1]))
6555     operands[1] = force_reg (HImode, operands[1]);
6556   emit_insn (gen_lshrhi3_reg (operands[0], operands[1], operands[2]));
6557   DONE;")
6558
6559 ; %0.hi = %1.hi >> %2
6560 ; %0.lo = (%1.lo >> %2 ) | (%1.hi << (32 - %2))
6561 ; This algorithm should work for shift counts greater than 32
6562 (define_expand "lshrhi3_reg" 
6563  [(use (match_operand:HI 1 "reg_operand" ""))
6564   (use (match_operand:HI 0 "reg_operand" ""))
6565   (parallel [(set (match_dup 11)
6566                   (neg:QI (match_operand:QI 2 "reg_operand" "")))
6567              (clobber (reg:CC_NOOV 21))])
6568   /* If the shift count is greater than 32 this will give zero.  */
6569   (parallel [(set (match_dup 7)
6570                   (lshiftrt:QI (match_dup 3)
6571                                (neg:QI (match_dup 11))))
6572              (clobber (reg:CC 21))])
6573   /* If the shift count is greater than 32 this will give zero.  */
6574   (parallel [(set (match_dup 8)
6575                   (lshiftrt:QI (match_dup 4) 
6576                                (neg:QI (match_dup 11))))
6577              (clobber (reg:CC 21))])
6578   (parallel [(set (match_dup 10)
6579                   (plus:QI (match_dup 11) (const_int 32)))
6580              (clobber (reg:CC_NOOV 21))])
6581   /* If the shift count is greater than 32 this will do an arithmetic
6582      right shift.  However, we need a logical right shift.  */
6583   (parallel [(set (match_dup 9)
6584                   (ashift:QI (match_dup 4) (unspec:QI [(match_dup 10)] 3)))
6585              (clobber (reg:CC 21))])
6586   (set (match_dup 6) (match_dup 8))
6587   (parallel [(set (match_dup 5)
6588                   (ior:QI (match_dup 7) (match_dup 9)))
6589              (clobber (reg:CC 21))])]
6590  ""
6591  " 
6592   operands[3] = operand_subword (operands[1], 0, 1, HImode); /* lo */
6593   operands[4] = operand_subword (operands[1], 1, 1, HImode); /* hi */
6594   operands[5] = operand_subword (operands[0], 0, 1, HImode); /* lo */
6595   operands[6] = operand_subword (operands[0], 1, 1, HImode); /* hi */
6596   operands[7] = gen_reg_rtx (QImode); /* lo >> count */
6597   operands[8] = gen_reg_rtx (QImode); /* hi >> count */
6598   operands[9] = gen_reg_rtx (QImode); /* hi << (32 - count) */
6599   operands[10] = gen_reg_rtx (QImode); /* 32 - count */
6600   operands[11] = gen_reg_rtx (QImode); /* -count */
6601  ")
6602
6603 ; This should do all the dirty work with define_split
6604 (define_expand "ashrhi3"
6605   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6606               (ashiftrt:HI (match_operand:HI 1 "src_operand" "")
6607                            (match_operand:QI 2 "src_operand" "")))
6608               (clobber (reg:CC 21))])]
6609  ""
6610  "if (GET_CODE (operands[2]) == CONST_INT && INTVAL (operands[2]) >= 32)
6611     {
6612        rtx op0hi = operand_subword (operands[0], 1, 0, HImode);
6613        rtx op0lo = operand_subword (operands[0], 0, 0, HImode);
6614        rtx op1hi = operand_subword (operands[1], 1, 0, HImode);
6615        rtx count = GEN_INT ((INTVAL (operands[2]) - 32));
6616
6617        if (INTVAL (count))
6618          emit_insn (gen_ashrqi3 (op0lo, op1hi, count));
6619        else
6620          emit_insn (gen_movqi (op0lo, op1hi));
6621        emit_insn (gen_ashrqi3 (op0hi, op1hi, GEN_INT (31)));
6622        DONE;
6623     }
6624   if (! REG_P (operands[1]))
6625     operands[1] = force_reg (HImode, operands[1]);
6626   emit_insn (gen_ashrhi3_reg (operands[0], operands[1], operands[2]));
6627   DONE;")
6628
6629 ; %0.hi = %1.hi >> %2
6630 ; %0.lo = (%1.lo >> %2 ) | (%1.hi << (32 - %2))
6631 ; This algorithm should work for shift counts greater than 32
6632 (define_expand "ashrhi3_reg" 
6633  [(use (match_operand:HI 1 "reg_operand" ""))
6634   (use (match_operand:HI 0 "reg_operand" ""))
6635   (parallel [(set (match_dup 11)
6636                   (neg:QI (match_operand:QI 2 "reg_operand" "")))
6637              (clobber (reg:CC_NOOV 21))])
6638   /* If the shift count is greater than 32 this will give zero.  */
6639   (parallel [(set (match_dup 7)
6640                   (lshiftrt:QI (match_dup 3)
6641                                (neg:QI (match_dup 11))))
6642              (clobber (reg:CC 21))])
6643   /* If the shift count is greater than 32 this will give zero.  */
6644   (parallel [(set (match_dup 8)
6645                   (ashiftrt:QI (match_dup 4) 
6646                                (neg:QI (match_dup 11))))
6647              (clobber (reg:CC 21))])
6648   (parallel [(set (match_dup 10)
6649                   (plus:QI (match_dup 11) (const_int 32)))
6650              (clobber (reg:CC_NOOV 21))])
6651   /* If the shift count is greater than 32 this will do an arithmetic
6652      right shift.  */
6653   (parallel [(set (match_dup 9)
6654                   (ashift:QI (match_dup 4) (match_dup 10)))
6655              (clobber (reg:CC 21))])
6656   (set (match_dup 6) (match_dup 8))
6657   (parallel [(set (match_dup 5)
6658                   (ior:QI (match_dup 7) (match_dup 9)))
6659              (clobber (reg:CC 21))])]
6660  ""
6661  " 
6662   operands[3] = operand_subword (operands[1], 0, 1, HImode); /* lo */
6663   operands[4] = operand_subword (operands[1], 1, 1, HImode); /* hi */
6664   operands[5] = operand_subword (operands[0], 0, 1, HImode); /* lo */
6665   operands[6] = operand_subword (operands[0], 1, 1, HImode); /* hi */
6666   operands[7] = gen_reg_rtx (QImode); /* lo >> count */
6667   operands[8] = gen_reg_rtx (QImode); /* hi >> count */
6668   operands[9] = gen_reg_rtx (QImode); /* hi << (32 - count) */
6669   operands[10] = gen_reg_rtx (QImode); /* 32 - count */
6670   operands[11] = gen_reg_rtx (QImode); /* -count */
6671  ")
6672
6673 (define_expand "cmphi"
6674   [(set (reg:CC 21)
6675         (compare:CC (match_operand:HI 0 "src_operand" "")
6676                     (match_operand:HI 1 "src_operand" "")))]
6677   ""
6678   "legitimize_operands (COMPARE, operands, HImode);
6679    c4x_compare_op0 = operands[0];
6680    c4x_compare_op1 = operands[1];
6681    DONE;")
6682
6683 ; This works only before reload because we need 2 extra registers.
6684 ; Use unspec to avoid recursive split.
6685 (define_split
6686   [(set (reg:CC 21)
6687         (compare:CC (match_operand:HI 0 "src_operand" "")
6688                     (match_operand:HI 1 "src_operand" "")))]
6689   "! reload_completed"
6690   [(parallel [(set (reg:CC 21)
6691                    (unspec:CC [(compare:CC (match_dup 0)
6692                                            (match_dup 1))] 4))
6693               (clobber (match_scratch:QI 2 ""))
6694               (clobber (match_scratch:QI 3 ""))])]
6695   "")
6696
6697 (define_split
6698   [(set (reg:CC_NOOV 21)
6699         (compare:CC_NOOV (match_operand:HI 0 "src_operand" "")
6700                          (match_operand:HI 1 "src_operand" "")))]
6701   "! reload_completed"
6702   [(parallel [(set (reg:CC_NOOV 21)
6703                    (unspec:CC_NOOV [(compare:CC_NOOV (match_dup 0)
6704                                                      (match_dup 1))] 4))
6705               (clobber (match_scratch:QI 2 ""))
6706               (clobber (match_scratch:QI 3 ""))])]
6707   "")
6708
6709 ; This is normally not used. The define splits above are used first.
6710 (define_insn "*cmphi"
6711   [(set (reg:CC 21)
6712         (compare:CC (match_operand:HI 0 "src_operand" "rR,rS<>")
6713                     (match_operand:HI 1 "src_operand" "R,rS<>")))]
6714   "valid_operands (COMPARE, operands, HImode)"
6715   "*
6716    {
6717      int use_ir1 = (reg_operand (operands[0], HImode)
6718                     && REG_P (operands[0])
6719                     && REGNO (operands[0]) == IR1_REGNO)
6720                     || (reg_operand (operands[1], HImode)
6721                         && REG_P (operands[1])
6722                         && REGNO (operands[1]) == IR1_REGNO);
6723
6724      if (use_ir1)
6725        output_asm_insn (\"push\\tir1\", operands);
6726      else
6727        output_asm_insn (\"push\\tbk\", operands);
6728      output_asm_insn (\"push\\tr0\", operands);
6729      output_asm_insn (\"subi3\\t%1,%0,r0\", operands);
6730      if (use_ir1)
6731        {
6732          output_asm_insn (\"ldiu\\tst,ir1\", operands);
6733          output_asm_insn (\"or\\t07bh,ir1\", operands);
6734        }
6735      else
6736        {
6737          output_asm_insn (\"ldiu\\tst,bk\", operands);
6738          output_asm_insn (\"or\\t07bh,bk\", operands);
6739        }
6740      output_asm_insn (\"subb3\\t%O1,%O0,r0\", operands);
6741      if (use_ir1)
6742        output_asm_insn (\"and3\\tir1,st,ir1\", operands);
6743      else
6744        output_asm_insn (\"and3\\tbk,st,bk\", operands);
6745      output_asm_insn (\"pop\\tr0\", operands);
6746      if (use_ir1)
6747        {
6748          output_asm_insn (\"ldiu\\tir1,st\", operands);
6749          output_asm_insn (\"pop\\tir1\", operands);
6750        }
6751      else
6752        {
6753          output_asm_insn (\"ldiu\\tbk,st\", operands);
6754          output_asm_insn (\"pop\\tbk\", operands);
6755        }
6756      return \"\";
6757    }"
6758   [(set_attr "type" "multi")])
6759  
6760 (define_insn "*cmphi_noov"
6761   [(set (reg:CC_NOOV 21)
6762         (compare:CC_NOOV (match_operand:HI 0 "src_operand" "rR,rS<>")
6763                     (match_operand:HI 1 "src_operand" "R,rS<>")))]
6764   "valid_operands (COMPARE, operands, HImode)"
6765   "*
6766    {
6767      int use_ir1 = (reg_operand (operands[0], HImode)
6768                     && REG_P (operands[0])
6769                     && REGNO (operands[0]) == IR1_REGNO)
6770                     || (reg_operand (operands[1], HImode)
6771                         && REG_P (operands[1])
6772                         && REGNO (operands[1]) == IR1_REGNO);
6773
6774      if (use_ir1)
6775        output_asm_insn (\"push\\tir1\", operands);
6776      else
6777        output_asm_insn (\"push\\tbk\", operands);
6778      output_asm_insn (\"push\\tr0\", operands);
6779      output_asm_insn (\"subi3\\t%1,%0,r0\", operands);
6780      if (use_ir1)
6781        {
6782          output_asm_insn (\"ldiu\\tst,ir1\", operands);
6783          output_asm_insn (\"or\\t07bh,ir1\", operands);
6784        }
6785      else
6786        {
6787          output_asm_insn (\"ldiu\\tst,bk\", operands);
6788          output_asm_insn (\"or\\t07bh,bk\", operands);
6789        }
6790      output_asm_insn (\"subb3\\t%O1,%O0,r0\", operands);
6791      if (use_ir1)
6792        output_asm_insn (\"and3\\tir1,st,ir1\", operands);
6793      else
6794        output_asm_insn (\"and3\\tbk,st,bk\", operands);
6795      output_asm_insn (\"pop\\tr0\", operands);
6796      if (use_ir1)
6797        {
6798          output_asm_insn (\"ldiu\\tir1,st\", operands);
6799          output_asm_insn (\"pop\\tir1\", operands);
6800        }
6801      else
6802        {
6803          output_asm_insn (\"ldiu\\tbk,st\", operands);
6804          output_asm_insn (\"pop\\tbk\", operands);
6805        }
6806      return \"\";
6807    }"
6808   [(set_attr "type" "multi")])
6809
6810  
6811 (define_insn "cmphi_cc"
6812   [(set (reg:CC 21)
6813         (unspec:CC [(compare:CC (match_operand:HI 0 "src_operand" "rR,rS<>")
6814                                 (match_operand:HI 1 "src_operand" "R,rS<>"))] 4))
6815    (clobber (match_scratch:QI 2 "=&d,&d"))
6816    (clobber (match_scratch:QI 3 "=&c,&c"))]
6817   "valid_operands (COMPARE, operands, HImode)"
6818   "*
6819    output_asm_insn (\"subi3\\t%1,%0,%2\", operands);
6820    output_asm_insn (\"ldiu\\tst,%3\", operands);
6821    output_asm_insn (\"or\\t07bh,%3\", operands);
6822    output_asm_insn (\"subb3\\t%O1,%O0,%2\", operands);
6823    output_asm_insn (\"and\\t%3,st\", operands);
6824    return \"\";"
6825   [(set_attr "type" "multi")])
6826
6827 (define_insn "cmphi_cc_noov"
6828   [(set (reg:CC_NOOV 21)
6829         (unspec:CC_NOOV [(compare:CC_NOOV (match_operand:HI 0 "src_operand" "rR,rS<>")
6830                                      (match_operand:HI 1 "src_operand" "R,rS<>"))] 4))
6831    (clobber (match_scratch:QI 2 "=&d,&d"))
6832    (clobber (match_scratch:QI 3 "=&c,&c"))]
6833   "valid_operands (COMPARE, operands, HImode)"
6834   "*
6835    output_asm_insn (\"subi3\\t%1,%0,%2\", operands);
6836    output_asm_insn (\"ldiu\\tst,%3\", operands);
6837    output_asm_insn (\"or\\t07bh,%3\", operands);
6838    output_asm_insn (\"subb3\\t%O1,%O0,%2\", operands);
6839    output_asm_insn (\"and\\t%3,st\", operands);
6840    return \"\";"
6841   [(set_attr "type" "multi")])
6842
6843 (define_expand "mulhi3"
6844   [(parallel [(set (match_operand:HI 0 "reg_operand" "")
6845                    (mult:HI (match_operand:HI 1 "src_operand" "")
6846                             (match_operand:HI 2 "src_operand" "")))
6847               (clobber (reg:CC 21))])]
6848   ""
6849   "c4x_emit_libcall3 (MULHI3_LIBCALL, MULT, HImode, operands);
6850    DONE;")
6851
6852
6853 ;
6854 ; PEEPHOLES
6855 ;
6856
6857 ; dbCC peepholes
6858 ;
6859 ; Turns
6860 ;   loop:
6861 ;           [ ... ]
6862 ;           bCC label           ; abnormal loop termination
6863 ;           dbu aN, loop        ; normal loop termination
6864 ;
6865 ; Into
6866 ;   loop:
6867 ;           [ ... ]
6868 ;           dbCC aN, loop
6869 ;           bCC label
6870 ;
6871 ; Which moves the bCC condition outside the inner loop for free.
6872 ;
6873 (define_peephole
6874   [(set (pc) (if_then_else (match_operator 3 "comparison_operator"
6875                            [(reg:CC 21) (const_int 0)])
6876                            (label_ref (match_operand 2 "" ""))
6877                            (pc)))
6878    (parallel
6879     [(set (pc)
6880           (if_then_else
6881             (ge (plus:QI (match_operand:QI 0 "addr_reg_operand" "+a")
6882                          (const_int -1))
6883                 (const_int 0))
6884             (label_ref (match_operand 1 "" ""))
6885             (pc)))
6886      (set (match_dup 0)
6887           (plus:QI (match_dup 0)
6888                    (const_int -1)))
6889      (clobber (reg:CC_NOOV 21))])]
6890   "! c4x_label_conflict (insn, operands[2], operands[1])"
6891   "db%I3\\t%0,%l1\\n\\tb%3\\t%l2"
6892   [(set_attr "type" "multi")])
6893
6894 (define_peephole
6895   [(set (pc) (if_then_else (match_operator 3 "comparison_operator"
6896                            [(reg:CC 21) (const_int 0)])
6897                            (label_ref (match_operand 2 "" ""))
6898                            (pc)))
6899    (parallel
6900     [(set (pc)
6901           (if_then_else
6902             (ne (match_operand:QI 0 "addr_reg_operand" "+a")
6903                 (const_int 0))
6904             (label_ref (match_operand 1 "" ""))
6905             (pc)))
6906      (set (match_dup 0)
6907           (plus:QI (match_dup 0)
6908                    (const_int -1)))])]
6909   "! c4x_label_conflict (insn, operands[2], operands[1])"
6910   "db%I3\\t%0,%l1\\n\\tb%3\\t%l2"
6911   [(set_attr "type" "multi")])
6912
6913 ;
6914 ; Peepholes to convert 'call label; rets' into jump label
6915 ;
6916
6917 (define_peephole
6918   [(parallel [(call (mem:QI (match_operand:QI 0 "call_address_operand" ""))
6919                     (match_operand:QI 1 "general_operand" ""))
6920               (clobber (reg:QI 31))])
6921    (return)]
6922   "c4x_null_epilogue_p ()"
6923   "*
6924    if (REG_P (operands[0]))
6925      return \"bu%#\\t%C0\";
6926    else
6927      return \"br%#\\t%C0\";"
6928   [(set_attr "type" "jump")])
6929
6930 (define_peephole
6931   [(parallel [(set (match_operand 0 "" "")
6932                    (call (mem:QI (match_operand:QI 1 "call_address_operand" ""))
6933                          (match_operand:QI 2 "general_operand" "")))
6934               (clobber (reg:QI 31))])
6935    (return)]
6936   "c4x_null_epilogue_p ()"
6937   "*
6938    if (REG_P (operands[1]))
6939      return \"bu%#\\t%C1\";
6940    else
6941      return \"br%#\\t%C1\";"
6942   [(set_attr "type" "jump")])
6943
6944
6945 ; This peephole should be unnecessary with my patches to flow.c
6946 ; for better autoincrement detection
6947 (define_peephole
6948  [(set (match_operand:QF 0 "ext_low_reg_operand" "")
6949        (mem:QF (match_operand:QI 1 "addr_reg_operand" "")))
6950   (set (match_operand:QF 2 "ext_low_reg_operand" "")
6951        (mem:QF (plus:QI (match_dup 1) (const_int 1))))
6952   (parallel [(set (match_dup 1) (plus:QI (match_dup 1) (const_int 2)))
6953              (clobber (reg:CC_NOOV 21))])]
6954  ""
6955  "ldf\\t*%1++,%0\\n\\tldf\\t*%1++,%2")
6956
6957
6958 ; This peephole should be unnecessary with my patches to flow.c
6959 ; for better autoincrement detection
6960 (define_peephole
6961  [(set (mem:QF (match_operand:QI 0 "addr_reg_operand" ""))
6962        (match_operand:QF 1 "ext_low_reg_operand" ""))
6963   (set (mem:QF (plus:QI (match_dup 0) (const_int 1)))
6964        (match_operand:QF 2 "ext_low_reg_operand" ""))
6965   (parallel [(set (match_dup 0) (plus:QI (match_dup 0) (const_int 2)))
6966              (clobber (reg:CC_NOOV 21))])]
6967  ""
6968  "stf\\t%1,*%0++\\n\\tstf\\t%2,*%0++")
6969
6970
6971 ; The following two peepholes remove an unecessary load
6972 ; often found at the end of a function.  These peepholes
6973 ; could be generalised to other binary operators.  They shouldn't
6974 ; be required if we run a post reload mop-up pass.
6975 (define_peephole
6976  [(parallel [(set (match_operand:QF 0 "ext_reg_operand" "")
6977                   (plus:QF (match_operand:QF 1 "ext_reg_operand" "")
6978                            (match_operand:QF 2 "ext_reg_operand" "")))
6979              (clobber (reg:CC_NOOV 21))])
6980   (set (match_operand:QF 3 "ext_reg_operand" "")
6981        (match_dup 0))]
6982  "dead_or_set_p (insn, operands[0])"
6983  "addf3\\t%2,%1,%3")
6984
6985 (define_peephole
6986  [(parallel [(set (match_operand:QI 0 "reg_operand" "")
6987                   (plus:QI (match_operand:QI 1 "reg_operand" "")
6988                            (match_operand:QI 2 "reg_operand" "")))
6989              (clobber (reg:CC_NOOV 21))])
6990   (set (match_operand:QI 3 "reg_operand" "")
6991        (match_dup 0))]
6992  "dead_or_set_p (insn, operands[0])"
6993  "addi3\\t%2,%1,%3")