OSDN Git Service

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