OSDN Git Service

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