OSDN Git Service

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