OSDN Git Service

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