xref: /openbsd/gnu/gcc/gcc/config/m32c/bitops.md (revision 404b540a)
1*404b540aSrobert;; Machine Descriptions for R8C/M16C/M32C
2*404b540aSrobert;; Copyright (C) 2005
3*404b540aSrobert;; Free Software Foundation, Inc.
4*404b540aSrobert;; Contributed by Red Hat.
5*404b540aSrobert;;
6*404b540aSrobert;; This file is part of GCC.
7*404b540aSrobert;;
8*404b540aSrobert;; GCC is free software; you can redistribute it and/or modify it
9*404b540aSrobert;; under the terms of the GNU General Public License as published
10*404b540aSrobert;; by the Free Software Foundation; either version 2, or (at your
11*404b540aSrobert;; option) any later version.
12*404b540aSrobert;;
13*404b540aSrobert;; GCC is distributed in the hope that it will be useful, but WITHOUT
14*404b540aSrobert;; ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
15*404b540aSrobert;; or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public
16*404b540aSrobert;; License for more details.
17*404b540aSrobert;;
18*404b540aSrobert;; You should have received a copy of the GNU General Public License
19*404b540aSrobert;; along with GCC; see the file COPYING.  If not, write to the Free
20*404b540aSrobert;; Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
21*404b540aSrobert;; 02110-1301, USA.
22*404b540aSrobert
23*404b540aSrobert;; Bit-wise operations (and, ior, xor, shift)
24*404b540aSrobert
25*404b540aSrobert; On the R8C and M16C, "address" for bit instructions is usually (but
26*404b540aSrobert; not always!) the *bit* address, not the *byte* address.  This
27*404b540aSrobert; confuses gcc, so we avoid cases where gcc would produce the wrong
28*404b540aSrobert; code.  We're left with absolute addresses and registers, and the odd
29*404b540aSrobert; case of shifting a bit by a variable.
30*404b540aSrobert
31*404b540aSrobert; On the M32C, "address" for bit instructions is a regular address,
32*404b540aSrobert; and the bit number is stored in a separate field.  Thus, we can let
33*404b540aSrobert; gcc do more interesting things.  However, the M32C cannot set all
34*404b540aSrobert; the bits in a 16 bit register, which the R8C/M16C can do.
35*404b540aSrobert
36*404b540aSrobert; However, it all means that we end up with two sets of patterns, one
37*404b540aSrobert; for each chip.
38*404b540aSrobert
39*404b540aSrobert;;----------------------------------------------------------------------
40*404b540aSrobert
41*404b540aSrobert;; First off, all the ways we can set one bit, other than plain IOR.
42*404b540aSrobert
43*404b540aSrobert(define_insn "bset_qi"
44*404b540aSrobert  [(set (match_operand:QI 0 "memsym_operand" "+Si")
45*404b540aSrobert	(ior:QI (subreg:QI (ashift:HI (const_int 1)
46*404b540aSrobert				      (subreg:QI (match_operand:HI 1 "a_qi_operand" "Raa") 0)) 0)
47*404b540aSrobert		(match_operand:QI 2 "" "0")))]
48*404b540aSrobert  "TARGET_A16"
49*404b540aSrobert  "bset\t%0[%1]"
50*404b540aSrobert  [(set_attr "flags" "n")]
51*404b540aSrobert  )
52*404b540aSrobert
53*404b540aSrobert(define_insn "bset_hi"
54*404b540aSrobert  [(set (zero_extract:HI (match_operand:QI 0 "memsym_operand" "+Si")
55*404b540aSrobert			 (const_int 1)
56*404b540aSrobert			 (zero_extend:HI (subreg:QI (match_operand:HI 1 "a_qi_operand" "Raa") 0)))
57*404b540aSrobert	(const_int 1))]
58*404b540aSrobert  "TARGET_A16"
59*404b540aSrobert  "bset\t%0[%1]"
60*404b540aSrobert  [(set_attr "flags" "n")]
61*404b540aSrobert  )
62*404b540aSrobert
63*404b540aSrobert;;----------------------------------------------------------------------
64*404b540aSrobert
65*404b540aSrobert;; Now all the ways we can clear one bit, other than plain AND.
66*404b540aSrobert
67*404b540aSrobert; This is odd because the shift patterns use QI counts, but we can't
68*404b540aSrobert; easily put QI in $aN without causing problems elsewhere.
69*404b540aSrobert(define_insn "bclr_qi"
70*404b540aSrobert  [(set (zero_extract:HI (match_operand:QI 0 "memsym_operand" "+Si")
71*404b540aSrobert			 (const_int 1)
72*404b540aSrobert			 (zero_extend:HI (subreg:QI (match_operand:HI 1 "a_qi_operand" "Raa") 0)))
73*404b540aSrobert	(const_int 0))]
74*404b540aSrobert  "TARGET_A16"
75*404b540aSrobert  "bclr\t%0[%1]"
76*404b540aSrobert  [(set_attr "flags" "n")]
77*404b540aSrobert  )
78*404b540aSrobert
79*404b540aSrobert
80*404b540aSrobert;;----------------------------------------------------------------------
81*404b540aSrobert
82*404b540aSrobert;; Now the generic patterns.
83*404b540aSrobert
84*404b540aSrobert(define_insn "andqi3_16"
85*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "=Sp,Rqi,RhlSd,RhlSd,??Rmm,??Rmm")
86*404b540aSrobert	(and:QI (match_operand:QI 1 "mra_operand" "%0,0,0,0,0,0")
87*404b540aSrobert		(match_operand 2 "mrai_operand" "Imb,Imb,iRhlSd,?Rmm,iRhlSd,?Rmm")))]
88*404b540aSrobert  "TARGET_A16"
89*404b540aSrobert  "@
90*404b540aSrobert   bclr\t%B2,%0
91*404b540aSrobert   bclr\t%B2,%h0
92*404b540aSrobert   and.b\t%x2,%0
93*404b540aSrobert   and.b\t%x2,%0
94*404b540aSrobert   and.b\t%x2,%0
95*404b540aSrobert   and.b\t%x2,%0"
96*404b540aSrobert  [(set_attr "flags" "n,n,sz,sz,sz,sz")]
97*404b540aSrobert  )
98*404b540aSrobert
99*404b540aSrobert(define_insn "andhi3_16"
100*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "=Sp,Sp,Rhi,RhiSd,??Rmm,RhiSd,??Rmm")
101*404b540aSrobert	(and:HI (match_operand:HI 1 "mra_operand" "%0,0,0,0,0,0,0")
102*404b540aSrobert		(match_operand:HI 2 "mrai_operand" "Imb,Imw,Imw,iRhiSd,?Rmm,?Rmm,iRhiSd")))]
103*404b540aSrobert  "TARGET_A16"
104*404b540aSrobert  "@
105*404b540aSrobert
106*404b540aSrobert   bclr\t%B2,%0
107*404b540aSrobert   bclr\t%B2-8,1+%0
108*404b540aSrobert   bclr\t%B2,%0
109*404b540aSrobert   and.w\t%X2,%0
110*404b540aSrobert   and.w\t%X2,%0
111*404b540aSrobert   and.w\t%X2,%0
112*404b540aSrobert   and.w\t%X2,%0"
113*404b540aSrobert  [(set_attr "flags" "n,n,n,sz,sz,sz,sz")]
114*404b540aSrobert  )
115*404b540aSrobert
116*404b540aSrobert(define_insn "andsi3"
117*404b540aSrobert  [(set (match_operand:SI 0 "mra_operand" "=RsiSd,RsiSd,??Rmm,??Rmm,??Rmm,RsiSd")
118*404b540aSrobert        (and:SI (match_operand:SI 1 "mra_operand" "%0,0,0,0,0,0")
119*404b540aSrobert                (match_operand:SI 2 "mrai_operand" "i,?Rmm,i,RsiSd,?Rmm,RsiSd")))]
120*404b540aSrobert  ""
121*404b540aSrobert  "*
122*404b540aSrobert  switch (which_alternative)
123*404b540aSrobert    {
124*404b540aSrobert    case 0:
125*404b540aSrobert      output_asm_insn (\"and.w %X2,%h0\",operands);
126*404b540aSrobert      operands[2]= GEN_INT (INTVAL (operands[2]) >> 16);
127*404b540aSrobert      return \"and.w %X2,%H0\";
128*404b540aSrobert    case 1:
129*404b540aSrobert      return \"and.w %h2,%h0\;and.w %H2,%H0\";
130*404b540aSrobert    case 2:
131*404b540aSrobert      output_asm_insn (\"and.w %X2,%h0\",operands);
132*404b540aSrobert      operands[2]= GEN_INT (INTVAL (operands[2]) >> 16);
133*404b540aSrobert      return \"and.w %X2,%H0\";
134*404b540aSrobert    case 3:
135*404b540aSrobert      return \"and.w %h2,%h0\;and.w %H2,%H0\";
136*404b540aSrobert    case 4:
137*404b540aSrobert      return \"and.w %h2,%h0\;and.w %H2,%H0\";
138*404b540aSrobert    case 5:
139*404b540aSrobert      return \"and.w %h2,%h0\;and.w %H2,%H0\";
140*404b540aSrobert    }"
141*404b540aSrobert  [(set_attr "flags" "x,x,x,x,x,x")]
142*404b540aSrobert)
143*404b540aSrobert
144*404b540aSrobert
145*404b540aSrobert(define_insn "iorqi3_16"
146*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "=Sp,Rqi,RqiSd,??Rmm,RqiSd,??Rmm")
147*404b540aSrobert	(ior:QI (match_operand:QI 1 "mra_operand" "%0,0,0,0,0,0")
148*404b540aSrobert		(match_operand:QI 2 "mrai_operand" "Ilb,Ilb,iRhlSd,iRhlSd,?Rmm,?Rmm")))]
149*404b540aSrobert  "TARGET_A16"
150*404b540aSrobert  "@
151*404b540aSrobert   bset\t%B2,%0
152*404b540aSrobert   bset\t%B2,%h0
153*404b540aSrobert   or.b\t%x2,%0
154*404b540aSrobert   or.b\t%x2,%0
155*404b540aSrobert   or.b\t%x2,%0
156*404b540aSrobert   or.b\t%x2,%0"
157*404b540aSrobert  [(set_attr "flags" "n,n,sz,sz,sz,sz")]
158*404b540aSrobert  )
159*404b540aSrobert
160*404b540aSrobert(define_insn "iorhi3_16"
161*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "=Sp,Sp,Rhi,RhiSd,RhiSd,??Rmm,??Rmm")
162*404b540aSrobert	(ior:HI (match_operand:HI 1 "mra_operand" "%0,0,0,0,0,0,0")
163*404b540aSrobert		(match_operand:HI 2 "mrai_operand" "Imb,Imw,Ilw,iRhiSd,?Rmm,iRhiSd,?Rmm")))]
164*404b540aSrobert  "TARGET_A16"
165*404b540aSrobert  "@
166*404b540aSrobert   bset %B2,%0
167*404b540aSrobert   bset\t%B2-8,1+%0
168*404b540aSrobert   bset\t%B2,%0
169*404b540aSrobert   or.w\t%X2,%0
170*404b540aSrobert   or.w\t%X2,%0
171*404b540aSrobert   or.w\t%X2,%0
172*404b540aSrobert   or.w\t%X2,%0"
173*404b540aSrobert  [(set_attr "flags" "n,n,n,sz,sz,sz,sz")]
174*404b540aSrobert  )
175*404b540aSrobert
176*404b540aSrobert; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
177*404b540aSrobert
178*404b540aSrobert(define_insn "andqi3_24"
179*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "=Sd,Rqi,RhlSd,RhlSd,??Rmm,??Rmm")
180*404b540aSrobert	(and:QI (match_operand:QI 1 "mra_operand" "%0,0,0,0,0,0")
181*404b540aSrobert		(match_operand 2 "mrai_operand" "Imb,Imb,iRhlSd,?Rmm,iRhlSd,?Rmm")))]
182*404b540aSrobert  "TARGET_A24"
183*404b540aSrobert  "@
184*404b540aSrobert   bclr\t%B2,%0
185*404b540aSrobert   bclr\t%B2,%0
186*404b540aSrobert   and.b\t%x2,%0
187*404b540aSrobert   and.b\t%x2,%0
188*404b540aSrobert   and.b\t%x2,%0
189*404b540aSrobert   and.b\t%x2,%0"
190*404b540aSrobert  [(set_attr "flags" "n,n,sz,sz,sz,sz")]
191*404b540aSrobert  )
192*404b540aSrobert
193*404b540aSrobert(define_insn "andhi3_24"
194*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "=Sd,Sd,Rqi,Rqi,RhiSd,??Rmm,RhiSd,??Rmm")
195*404b540aSrobert	(and:HI (match_operand:HI 1 "mra_operand" "%0,0,0,0,0,0,0,0")
196*404b540aSrobert		(match_operand:HI 2 "mrai_operand" "Imb,Imw,Imb,Imw,iRhiSd,?Rmm,?Rmm,iRhiSd")))]
197*404b540aSrobert  "TARGET_A24"
198*404b540aSrobert  "@
199*404b540aSrobert   bclr\t%B2,%0
200*404b540aSrobert   bclr\t%B2-8,1+%0
201*404b540aSrobert   bclr\t%B2,%h0
202*404b540aSrobert   bclr\t%B2-8,%H0
203*404b540aSrobert   and.w\t%X2,%0
204*404b540aSrobert   and.w\t%X2,%0
205*404b540aSrobert   and.w\t%X2,%0
206*404b540aSrobert   and.w\t%X2,%0"
207*404b540aSrobert  [(set_attr "flags" "n,n,n,n,sz,sz,sz,sz")]
208*404b540aSrobert  )
209*404b540aSrobert
210*404b540aSrobert
211*404b540aSrobert
212*404b540aSrobert(define_insn "iorqi3_24"
213*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "=RqiSd,RqiSd,??Rmm,RqiSd,??Rmm")
214*404b540aSrobert	(ior:QI (match_operand:QI 1 "mra_operand" "%0,0,0,0,0")
215*404b540aSrobert		(match_operand:QI 2 "mrai_operand" "Ilb,iRhlSd,iRhlSd,?Rmm,?Rmm")))]
216*404b540aSrobert  "TARGET_A24"
217*404b540aSrobert  "@
218*404b540aSrobert   bset\t%B2,%0
219*404b540aSrobert   or.b\t%x2,%0
220*404b540aSrobert   or.b\t%x2,%0
221*404b540aSrobert   or.b\t%x2,%0
222*404b540aSrobert   or.b\t%x2,%0"
223*404b540aSrobert  [(set_attr "flags" "n,sz,sz,sz,sz")]
224*404b540aSrobert  )
225*404b540aSrobert
226*404b540aSrobert(define_insn "iorhi3_24"
227*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "=Sd,Sd,Rqi,Rqi,RhiSd,RhiSd,??Rmm,??Rmm")
228*404b540aSrobert	(ior:HI (match_operand:HI 1 "mra_operand" "%0,0,0,0,0,0,0,0")
229*404b540aSrobert		(match_operand:HI 2 "mrai_operand" "Ilb,Ilw,Ilb,Ilw,iRhiSd,?Rmm,iRhiSd,?Rmm")))]
230*404b540aSrobert  "TARGET_A24"
231*404b540aSrobert  "@
232*404b540aSrobert   bset\t%B2,%0
233*404b540aSrobert   bset\t%B2-8,1+%0
234*404b540aSrobert   bset\t%B2,%h0
235*404b540aSrobert   bset\t%B2-8,%H0
236*404b540aSrobert   or.w\t%X2,%0
237*404b540aSrobert   or.w\t%X2,%0
238*404b540aSrobert   or.w\t%X2,%0
239*404b540aSrobert   or.w\t%X2,%0"
240*404b540aSrobert  [(set_attr "flags" "n,n,n,n,sz,sz,sz,sz")]
241*404b540aSrobert  )
242*404b540aSrobert
243*404b540aSrobert
244*404b540aSrobert; ----------------------------------------------------------------------
245*404b540aSrobert
246*404b540aSrobert(define_expand "andqi3"
247*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "")
248*404b540aSrobert	(and:QI (match_operand:QI 1 "mra_operand" "")
249*404b540aSrobert		(match_operand:QI 2 "mrai_operand" "")))]
250*404b540aSrobert  ""
251*404b540aSrobert  "if (TARGET_A16)
252*404b540aSrobert     emit_insn (gen_andqi3_16 (operands[0], operands[1], operands[2]));
253*404b540aSrobert   else
254*404b540aSrobert     emit_insn (gen_andqi3_24 (operands[0], operands[1], operands[2]));
255*404b540aSrobert   DONE;"
256*404b540aSrobert  )
257*404b540aSrobert
258*404b540aSrobert(define_expand "andhi3"
259*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "")
260*404b540aSrobert	(and:HI (match_operand:HI 1 "mra_operand" "")
261*404b540aSrobert		(match_operand:HI 2 "mrai_operand" "")))]
262*404b540aSrobert  ""
263*404b540aSrobert  "if (TARGET_A16)
264*404b540aSrobert     emit_insn (gen_andhi3_16 (operands[0], operands[1], operands[2]));
265*404b540aSrobert   else
266*404b540aSrobert     emit_insn (gen_andhi3_24 (operands[0], operands[1], operands[2]));
267*404b540aSrobert   DONE;"
268*404b540aSrobert  )
269*404b540aSrobert
270*404b540aSrobert(define_expand "iorqi3"
271*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "")
272*404b540aSrobert	(ior:QI (match_operand:QI 1 "mra_operand" "")
273*404b540aSrobert		(match_operand:QI 2 "mrai_operand" "")))]
274*404b540aSrobert  ""
275*404b540aSrobert  "if (TARGET_A16)
276*404b540aSrobert     emit_insn (gen_iorqi3_16 (operands[0], operands[1], operands[2]));
277*404b540aSrobert   else
278*404b540aSrobert     emit_insn (gen_iorqi3_24 (operands[0], operands[1], operands[2]));
279*404b540aSrobert   DONE;"
280*404b540aSrobert  )
281*404b540aSrobert
282*404b540aSrobert(define_expand "iorhi3"
283*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "")
284*404b540aSrobert	(ior:HI (match_operand:HI 1 "mra_operand" "")
285*404b540aSrobert		(match_operand:HI 2 "mrai_operand" "")))]
286*404b540aSrobert  ""
287*404b540aSrobert  "if (TARGET_A16)
288*404b540aSrobert     emit_insn (gen_iorhi3_16 (operands[0], operands[1], operands[2]));
289*404b540aSrobert   else
290*404b540aSrobert     emit_insn (gen_iorhi3_24 (operands[0], operands[1], operands[2]));
291*404b540aSrobert   DONE;"
292*404b540aSrobert  )
293*404b540aSrobert
294*404b540aSrobert(define_insn "iorsi3"
295*404b540aSrobert  [(set (match_operand:SI 0 "mra_operand" "=RsiSd,RsiSd,??Rmm,??Rmm,??Rmm,RsiSd")
296*404b540aSrobert        (ior:SI (match_operand:SI 1 "mra_operand" "%0,0,0,0,0,0")
297*404b540aSrobert                (match_operand:SI 2 "mrai_operand" "i,?Rmm,i,RsiSd,?Rmm,RsiSd")))]
298*404b540aSrobert  ""
299*404b540aSrobert  "*
300*404b540aSrobert  switch (which_alternative)
301*404b540aSrobert    {
302*404b540aSrobert    case 0:
303*404b540aSrobert      output_asm_insn (\"or.w %X2,%h0\",operands);
304*404b540aSrobert      operands[2]= GEN_INT (INTVAL (operands[2]) >> 16);
305*404b540aSrobert      return \"or.w %X2,%H0\";
306*404b540aSrobert    case 1:
307*404b540aSrobert      return \"or.w %h2,%h0\;or.w %H2,%H0\";
308*404b540aSrobert    case 2:
309*404b540aSrobert      output_asm_insn (\"or.w %X2,%h0\",operands);
310*404b540aSrobert      operands[2]= GEN_INT (INTVAL (operands[2]) >> 16);
311*404b540aSrobert      return \"or.w %X2,%H0\";
312*404b540aSrobert    case 3:
313*404b540aSrobert      return \"or.w %h2,%h0\;or.w %H2,%H0\";
314*404b540aSrobert    case 4:
315*404b540aSrobert      return \"or.w %h2,%h0\;or.w %H2,%H0\";
316*404b540aSrobert    case 5:
317*404b540aSrobert      return \"or.w %h2,%h0\;or.w %H2,%H0\";
318*404b540aSrobert    }"
319*404b540aSrobert  [(set_attr "flags" "x,x,x,x,x,x")]
320*404b540aSrobert)
321*404b540aSrobert
322*404b540aSrobert(define_insn "xorqi3"
323*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "=RhlSd,RhlSd,??Rmm,??Rmm")
324*404b540aSrobert	(xor:QI (match_operand:QI 1 "mra_operand" "%0,0,0,0")
325*404b540aSrobert		(match_operand:QI 2 "mrai_operand" "iRhlSd,?Rmm,iRhlSd,?Rmm")))]
326*404b540aSrobert  ""
327*404b540aSrobert  "xor.b\t%x2,%0"
328*404b540aSrobert  [(set_attr "flags" "sz,sz,sz,sz")]
329*404b540aSrobert  )
330*404b540aSrobert
331*404b540aSrobert(define_insn "xorhi3"
332*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "=RhiSd,RhiSd,??Rmm,??Rmm")
333*404b540aSrobert	(xor:HI (match_operand:HI 1 "mra_operand" "%0,0,0,0")
334*404b540aSrobert		(match_operand:HI 2 "mrai_operand" "iRhiSd,?Rmm,iRhiSd,?Rmm")))]
335*404b540aSrobert  ""
336*404b540aSrobert  "xor.w\t%X2,%0"
337*404b540aSrobert  [(set_attr "flags" "sz,sz,sz,sz")]
338*404b540aSrobert  )
339*404b540aSrobert
340*404b540aSrobert(define_insn "xorsi3"
341*404b540aSrobert  [(set (match_operand:SI 0 "mra_operand" "=RsiSd,RsiSd,??Rmm,??Rmm,??Rmm,RsiSd")
342*404b540aSrobert        (xor:SI (match_operand:SI 1 "mra_operand" "%0,0,0,0,0,0")
343*404b540aSrobert                (match_operand:SI 2 "mrai_operand" "i,?Rmm,i,RsiSd,?Rmm,RsiSd")))]
344*404b540aSrobert  ""
345*404b540aSrobert  "*
346*404b540aSrobert  switch (which_alternative)
347*404b540aSrobert    {
348*404b540aSrobert    case 0:
349*404b540aSrobert      output_asm_insn (\"xor.w %X2,%h0\",operands);
350*404b540aSrobert      operands[2]= GEN_INT (INTVAL (operands[2]) >> 16);
351*404b540aSrobert      return \"xor.w %X2,%H0\";
352*404b540aSrobert    case 1:
353*404b540aSrobert      return \"xor.w %h2,%h0\;xor.w %H2,%H0\";
354*404b540aSrobert    case 2:
355*404b540aSrobert      output_asm_insn (\"xor.w %X2,%h0\",operands);
356*404b540aSrobert      operands[2]= GEN_INT (INTVAL (operands[2]) >> 16);
357*404b540aSrobert      return \"xor.w %X2,%H0\";
358*404b540aSrobert    case 3:
359*404b540aSrobert      return \"xor.w %h2,%h0\;xor.w %H2,%H0\";
360*404b540aSrobert    case 4:
361*404b540aSrobert      return \"xor.w %h2,%h0\;xor.w %H2,%H0\";
362*404b540aSrobert    case 5:
363*404b540aSrobert      return \"xor.w %h2,%h0\;xor.w %H2,%H0\";
364*404b540aSrobert    }"
365*404b540aSrobert  [(set_attr "flags" "x,x,x,x,x,x")]
366*404b540aSrobert)
367*404b540aSrobert
368*404b540aSrobert(define_insn "one_cmplqi2"
369*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "=RhlSd,??Rmm")
370*404b540aSrobert	(not:QI (match_operand:QI 1 "mra_operand" "0,0")))]
371*404b540aSrobert  ""
372*404b540aSrobert  "not.b\t%0"
373*404b540aSrobert  [(set_attr "flags" "sz,sz")]
374*404b540aSrobert  )
375*404b540aSrobert
376*404b540aSrobert(define_insn "one_cmplhi2"
377*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "=RhiSd,??Rmm")
378*404b540aSrobert	(not:HI (match_operand:HI 1 "mra_operand" "0,0")))]
379*404b540aSrobert  ""
380*404b540aSrobert  "not.w\t%0"
381*404b540aSrobert  [(set_attr "flags" "sz,sz")]
382*404b540aSrobert  )
383*404b540aSrobert
384*404b540aSrobert; Optimizations using bit opcodes
385*404b540aSrobert
386*404b540aSrobert; We need this because combine only looks at three insns at a time,
387*404b540aSrobert; and the bclr_qi pattern uses four - mov, shift, not, and.  GCC
388*404b540aSrobert; should never expand this pattern, because it only shifts a constant
389*404b540aSrobert; by a constant, so gcc should do that itself.
390*404b540aSrobert(define_insn "shift1_qi"
391*404b540aSrobert  [(set (match_operand:QI 0 "mra_operand" "=Rqi")
392*404b540aSrobert	(ashift:QI (const_int 1)
393*404b540aSrobert		   (match_operand 1 "const_int_operand" "In4")))]
394*404b540aSrobert  ""
395*404b540aSrobert  "mov.b\t#1,%0\n\tshl.b\t%1,%0"
396*404b540aSrobert  )
397*404b540aSrobert(define_insn "shift1_hi"
398*404b540aSrobert  [(set (match_operand:HI 0 "mra_operand" "=Rhi")
399*404b540aSrobert	(ashift:HI (const_int 1)
400*404b540aSrobert		   (match_operand 1 "const_int_operand" "In4")))]
401*404b540aSrobert  ""
402*404b540aSrobert  "mov.w\t#1,%0\n\tshl.w\t%1,%0"
403*404b540aSrobert  )
404*404b540aSrobert
405*404b540aSrobert; Generic insert-bit expander, needed so that we can use the bit
406*404b540aSrobert; opcodes for volatile bitfields.
407*404b540aSrobert
408*404b540aSrobert(define_expand "insv"
409*404b540aSrobert  [(set (zero_extract:HI (match_operand:HI 0 "mra_operand" "")
410*404b540aSrobert			 (match_operand 1 "const_int_operand" "")
411*404b540aSrobert			 (match_operand 2 "const_int_operand" ""))
412*404b540aSrobert	(match_operand:HI 3 "const_int_operand" ""))]
413*404b540aSrobert  ""
414*404b540aSrobert  "if (m32c_expand_insv (operands))
415*404b540aSrobert     FAIL;
416*404b540aSrobert   DONE;"
417*404b540aSrobert  )
418