xref: /openbsd/gnu/gcc/gcc/config/mt/mt.md (revision 404b540a)
1*404b540aSrobert;; Machine description for MorphoRISC1
2*404b540aSrobert;; Copyright (C) 2005 Free Software Foundation, Inc.
3*404b540aSrobert;; Contributed by Red Hat, Inc.
4*404b540aSrobert
5*404b540aSrobert;; This file is part of GCC.
6*404b540aSrobert
7*404b540aSrobert;; GCC is free software; you can redistribute it and/or modify
8*404b540aSrobert;; it under the terms of the GNU General Public License as published by
9*404b540aSrobert;; the Free Software Foundation; either version 2, or (at your option)
10*404b540aSrobert;; any later version.
11*404b540aSrobert
12*404b540aSrobert;; GCC is distributed in the hope that it will be useful,
13*404b540aSrobert;; but WITHOUT ANY WARRANTY; without even the implied warranty of
14*404b540aSrobert;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15*404b540aSrobert;; GNU General Public License for more details.
16*404b540aSrobert
17*404b540aSrobert;; You should have received a copy of the GNU General Public License
18*404b540aSrobert;; along with GCC; see the file COPYING.  If not, write to the Free
19*404b540aSrobert;; Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
20*404b540aSrobert;; 02110-1301, USA.
21*404b540aSrobert
22*404b540aSrobert;; UNSPECs
23*404b540aSrobert(define_constants
24*404b540aSrobert  [
25*404b540aSrobert    (UNSPEC_BLOCKAGE 0)
26*404b540aSrobert    (UNSPEC_EI 1)
27*404b540aSrobert    (UNSPEC_DI 2)
28*404b540aSrobert    (UNSPEC_LOOP 3)
29*404b540aSrobert  ])
30*404b540aSrobert
31*404b540aSrobert;; Attributes
32*404b540aSrobert(define_attr "type" "branch,call,load,store,io,arith,complex,unknown"
33*404b540aSrobert	 (const_string "unknown") )
34*404b540aSrobert
35*404b540aSrobert;; If the attribute takes numeric values, no `enum' type will be defined and
36*404b540aSrobert;; the function to obtain the attribute's value will return `int'.
37*404b540aSrobert
38*404b540aSrobert(define_attr "length" "" (const_int 4))
39*404b540aSrobert
40*404b540aSrobert
41*404b540aSrobert;; DFA scheduler.
42*404b540aSrobert(define_automaton "other")
43*404b540aSrobert(define_cpu_unit "decode_unit" "other")
44*404b540aSrobert(define_cpu_unit "memory_unit" "other")
45*404b540aSrobert(define_cpu_unit "branch_unit" "other")
46*404b540aSrobert
47*404b540aSrobert(define_insn_reservation "mem_access" 2
48*404b540aSrobert  (ior (eq_attr "type" "load") (eq_attr "type" "store"))
49*404b540aSrobert  "decode_unit+memory_unit*2")
50*404b540aSrobert
51*404b540aSrobert(define_insn_reservation "io_access" 2
52*404b540aSrobert  (eq_attr "type" "io")
53*404b540aSrobert  "decode_unit+memory_unit*2")
54*404b540aSrobert
55*404b540aSrobert(define_insn_reservation "branch_access" 2
56*404b540aSrobert  (ior (eq_attr "type" "branch")
57*404b540aSrobert       (eq_attr "type" "call"))
58*404b540aSrobert  "decode_unit+branch_unit*2")
59*404b540aSrobert
60*404b540aSrobert(define_insn_reservation "arith_access" 1
61*404b540aSrobert  (eq_attr "type" "arith")
62*404b540aSrobert  "decode_unit")
63*404b540aSrobert
64*404b540aSrobert(define_bypass 2 "arith_access" "branch_access")
65*404b540aSrobert(define_bypass 3 "mem_access" "branch_access")
66*404b540aSrobert(define_bypass 3 "io_access" "branch_access")
67*404b540aSrobert
68*404b540aSrobert
69*404b540aSrobert;; Delay Slots
70*404b540aSrobert
71*404b540aSrobert;; The mt does not allow branches in the delay slot.
72*404b540aSrobert;; The mt does not allow back to back memory or io instruction.
73*404b540aSrobert;; The compiler does not know what the type of instruction is at
74*404b540aSrobert;; the destination of the branch.  Thus, only type that will be acceptable
75*404b540aSrobert;; (safe) is the arith type.
76*404b540aSrobert
77*404b540aSrobert(define_delay (ior (eq_attr "type" "branch")
78*404b540aSrobert		   (eq_attr "type" "call"))
79*404b540aSrobert		 [(eq_attr "type" "arith") (nil) (nil)])
80*404b540aSrobert
81*404b540aSrobert
82*404b540aSrobert(define_insn "decrement_and_branch_until_zero"
83*404b540aSrobert   [(set (pc)
84*404b540aSrobert	 (if_then_else
85*404b540aSrobert	  (ne (match_operand:SI 0 "nonimmediate_operand" "+r,*m")
86*404b540aSrobert	      (const_int 0))
87*404b540aSrobert	  (label_ref (match_operand 1 "" ""))
88*404b540aSrobert	  (pc)))
89*404b540aSrobert    (set (match_dup 0)
90*404b540aSrobert	 (plus:SI (match_dup 0)
91*404b540aSrobert		  (const_int -1)))
92*404b540aSrobert    (clobber (match_scratch:SI 2 "=X,&r"))
93*404b540aSrobert    (clobber (match_scratch:SI 3 "=X,&r"))]
94*404b540aSrobert  "TARGET_MS1_16_003 || TARGET_MS2"
95*404b540aSrobert  "@
96*404b540aSrobert   dbnz\t%0, %l1%#
97*404b540aSrobert   #"
98*404b540aSrobert  [(set_attr "length" "4,16")
99*404b540aSrobert   (set_attr "type" "branch,unknown")]
100*404b540aSrobert)
101*404b540aSrobert
102*404b540aSrobert;; Split the above to handle the case where operand 0 is in memory
103*404b540aSrobert;; (a register that couldn't get a hard register).
104*404b540aSrobert(define_split
105*404b540aSrobert  [(set (pc)
106*404b540aSrobert	(if_then_else
107*404b540aSrobert	  (ne (match_operand:SI 0 "memory_operand" "")
108*404b540aSrobert	      (const_int 0))
109*404b540aSrobert	  (label_ref (match_operand 1 "" ""))
110*404b540aSrobert	  (pc)))
111*404b540aSrobert    (set (match_dup 0)
112*404b540aSrobert	 (plus:SI (match_dup 0)
113*404b540aSrobert		  (const_int -1)))
114*404b540aSrobert    (clobber (match_scratch:SI 2 ""))
115*404b540aSrobert    (clobber (match_scratch:SI 3 ""))]
116*404b540aSrobert  "TARGET_MS1_16_003 || TARGET_MS2"
117*404b540aSrobert  [(set (match_dup 2) (match_dup 0))
118*404b540aSrobert   (set (match_dup 3) (plus:SI (match_dup 2) (const_int -1)))
119*404b540aSrobert   (set (match_dup 0) (match_dup 3))
120*404b540aSrobert   (set (pc)
121*404b540aSrobert	(if_then_else
122*404b540aSrobert	 (ne (match_dup 2)
123*404b540aSrobert	     (const_int 0))
124*404b540aSrobert	 (label_ref (match_dup 1))
125*404b540aSrobert	 (pc)))]
126*404b540aSrobert  "")
127*404b540aSrobert
128*404b540aSrobert;; This peephole is defined in the vain hope that it might actually trigger one
129*404b540aSrobert;; day, although I have yet to find a test case that matches it.  The normal
130*404b540aSrobert;; problem is that GCC likes to move the loading of the constant value -1 out
131*404b540aSrobert;; of the loop, so it is not here to be matched.
132*404b540aSrobert
133*404b540aSrobert(define_peephole2
134*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "")
135*404b540aSrobert	(plus:SI (match_dup 0) (const_int -1)))
136*404b540aSrobert   (set (match_operand:SI 1 "register_operand" "")
137*404b540aSrobert     (const_int -1))
138*404b540aSrobert   (set (pc) (if_then_else
139*404b540aSrobert	        (ne (match_dup 0) (match_dup 1))
140*404b540aSrobert		(label_ref (match_operand 2 "" ""))
141*404b540aSrobert		(pc)))]
142*404b540aSrobert  "TARGET_MS1_16_003 || TARGET_MS2"
143*404b540aSrobert  [(parallel [(set (pc)
144*404b540aSrobert	           (if_then_else
145*404b540aSrobert	              (ne (match_dup 0) (const_int 0))
146*404b540aSrobert	              (label_ref (match_dup 2))
147*404b540aSrobert	              (pc)))
148*404b540aSrobert              (set (match_dup 0)
149*404b540aSrobert	           (plus:SI (match_dup 0) (const_int -1)))
150*404b540aSrobert	      (clobber (reg:SI 0))
151*404b540aSrobert	      (clobber (reg:SI 0))])]
152*404b540aSrobert  "")
153*404b540aSrobert
154*404b540aSrobert
155*404b540aSrobert;; Loop instructions.  ms2 has a low overhead looping instructions.
156*404b540aSrobert;; these take a constant or register loop count and a loop length
157*404b540aSrobert;; offset.  Unfortunately the loop can only be up to 256 instructions,
158*404b540aSrobert;; We deal with longer loops by moving the loop end upwards.  To do
159*404b540aSrobert;; otherwise would force us to to be very pessimistic right up until
160*404b540aSrobert;; the end.
161*404b540aSrobert
162*404b540aSrobert;; This instruction is a placeholder to make the control flow explicit.
163*404b540aSrobert(define_insn "loop_end"
164*404b540aSrobert  [(set (pc) (if_then_else
165*404b540aSrobert			  (ne (match_operand:SI 0 "register_operand" "")
166*404b540aSrobert			      (const_int 1))
167*404b540aSrobert			  (label_ref (match_operand 1 "" ""))
168*404b540aSrobert			  (pc)))
169*404b540aSrobert   (set (match_dup 0) (plus:SI (match_dup 0) (const_int -1)))
170*404b540aSrobert   (unspec [(const_int 0)] UNSPEC_LOOP)]
171*404b540aSrobert  "TARGET_MS2"
172*404b540aSrobert  ";loop end %0,%l1"
173*404b540aSrobert  [(set_attr "length" "0")])
174*404b540aSrobert
175*404b540aSrobert;; This is the real looping instruction.  It is placed just before the
176*404b540aSrobert;; loop body.  We make it a branch insn, so it stays at the end of the
177*404b540aSrobert;; block it is in.
178*404b540aSrobert(define_insn "loop_init"
179*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
180*404b540aSrobert	(match_operand:SI 1 "uns_arith_operand" "r,K"))
181*404b540aSrobert   (unspec [(label_ref (match_operand 2 "" ""))] UNSPEC_LOOP)]
182*404b540aSrobert  "TARGET_MS2"
183*404b540aSrobert  "@
184*404b540aSrobert   loop  %1,%l2 ;%0%#
185*404b540aSrobert   loopi %1,%l2 ;%0%#"
186*404b540aSrobert  [(set_attr "length" "4")
187*404b540aSrobert   (set_attr "type" "branch")])
188*404b540aSrobert
189*404b540aSrobert; operand 0 is the loop count pseudo register
190*404b540aSrobert; operand 1 is the number of loop iterations or 0 if it is unknown
191*404b540aSrobert; operand 2 is the maximum number of loop iterations
192*404b540aSrobert; operand 3 is the number of levels of enclosed loops
193*404b540aSrobert; operand 4 is the label to jump to at the top of the loop
194*404b540aSrobert(define_expand "doloop_end"
195*404b540aSrobert  [(parallel [(set (pc) (if_then_else
196*404b540aSrobert			  (ne (match_operand:SI 0 "nonimmediate_operand" "")
197*404b540aSrobert			      (const_int 0))
198*404b540aSrobert			  (label_ref (match_operand 4 "" ""))
199*404b540aSrobert			  (pc)))
200*404b540aSrobert	      (set (match_dup 0)
201*404b540aSrobert		   (plus:SI (match_dup 0)
202*404b540aSrobert			    (const_int -1)))
203*404b540aSrobert	      (clobber (match_scratch:SI 5 ""))
204*404b540aSrobert	      (clobber (match_scratch:SI 6 ""))])]
205*404b540aSrobert  "TARGET_MS1_16_003 || TARGET_MS2"
206*404b540aSrobert  {mt_add_loop ();})
207*404b540aSrobert
208*404b540aSrobert;; Moves
209*404b540aSrobert
210*404b540aSrobert(define_expand "loadqi"
211*404b540aSrobert  [
212*404b540aSrobert   ;; compute shift
213*404b540aSrobert   (set (match_operand:SI 2 "register_operand" "")
214*404b540aSrobert	(and:SI (match_dup 1) (const_int 3)))
215*404b540aSrobert   (set (match_dup 2)	(xor:SI (match_dup 2) (const_int 3)))
216*404b540aSrobert   (set (match_dup 2 )	(ashift:SI (match_dup 2) (const_int 3)))
217*404b540aSrobert
218*404b540aSrobert   ;; get word that contains byte
219*404b540aSrobert   (set (match_operand:SI 0 "register_operand" "")
220*404b540aSrobert	(mem:SI (and:SI (match_operand:SI 1 "register_operand" "")
221*404b540aSrobert			(const_int -3))))
222*404b540aSrobert
223*404b540aSrobert   ;; align byte
224*404b540aSrobert   (set (match_dup 0)   (ashiftrt:SI (match_dup 0) (match_dup 2)))
225*404b540aSrobert  ]
226*404b540aSrobert  ""
227*404b540aSrobert  "")
228*404b540aSrobert
229*404b540aSrobert
230*404b540aSrobert;; storeqi
231*404b540aSrobert;; operand 0 byte value to store
232*404b540aSrobert;; operand 1 address
233*404b540aSrobert;; operand 2 temp, word containing byte
234*404b540aSrobert;; operand 3 temp, shift count
235*404b540aSrobert;; operand 4 temp, mask, aligned and masked byte
236*404b540aSrobert;; operand 5 (unused)
237*404b540aSrobert(define_expand "storeqi"
238*404b540aSrobert  [
239*404b540aSrobert   ;; compute shift
240*404b540aSrobert   (set (match_operand:SI 3 "register_operand" "")
241*404b540aSrobert	(and:SI (match_operand:SI 1 "register_operand" "") (const_int 3)))
242*404b540aSrobert   (set (match_dup 3)	(xor:SI (match_dup 3) (const_int 3)))
243*404b540aSrobert   (set (match_dup 3)	(ashift:SI (match_dup 3) (const_int 3)))
244*404b540aSrobert
245*404b540aSrobert   ;; get word that contains byte
246*404b540aSrobert   (set (match_operand:SI 2 "register_operand" "")
247*404b540aSrobert	(mem:SI (and:SI (match_dup 1) (const_int -3))))
248*404b540aSrobert
249*404b540aSrobert   ;; generate mask
250*404b540aSrobert   (set (match_operand:SI 4 "register_operand" "") (const_int 255))
251*404b540aSrobert   (set (match_dup 4) (ashift:SI (match_dup 4) (match_dup 3)))
252*404b540aSrobert   (set (match_dup 4) (not:SI (match_dup 4)))
253*404b540aSrobert
254*404b540aSrobert   ;; clear appropriate bits
255*404b540aSrobert   (set (match_dup 2) (and:SI (match_dup 2) (match_dup 4)))
256*404b540aSrobert
257*404b540aSrobert   ;; align byte
258*404b540aSrobert   (set (match_dup 4)
259*404b540aSrobert	(and:SI (match_operand:SI 0 "register_operand" "") (const_int 255)))
260*404b540aSrobert   (set (match_dup 4) (ashift:SI (match_dup 4) (match_dup 3)))
261*404b540aSrobert
262*404b540aSrobert   ;; combine
263*404b540aSrobert   (set (match_dup 2) (ior:SI (match_dup 4) (match_dup 2)))
264*404b540aSrobert   ;; store updated word
265*404b540aSrobert   (set (mem:SI (and:SI (match_dup 1) (const_int -3))) (match_dup 2))
266*404b540aSrobert  ]
267*404b540aSrobert  ""
268*404b540aSrobert  "")
269*404b540aSrobert
270*404b540aSrobert
271*404b540aSrobert(define_expand "movqi"
272*404b540aSrobert  [(set (match_operand:QI 0 "general_operand" "")
273*404b540aSrobert	(match_operand:QI 1 "general_operand" ""))]
274*404b540aSrobert  ""
275*404b540aSrobert  "
276*404b540aSrobert{
277*404b540aSrobert  if (!reload_in_progress
278*404b540aSrobert      && !reload_completed
279*404b540aSrobert      && GET_CODE (operands[0]) == MEM
280*404b540aSrobert      && GET_CODE (operands[1]) == MEM)
281*404b540aSrobert    operands[1] = copy_to_mode_reg (QImode, operands[1]);
282*404b540aSrobert
283*404b540aSrobert  if ( (! TARGET_BYTE_ACCESS) && GET_CODE (operands[0]) == MEM)
284*404b540aSrobert    {
285*404b540aSrobert	rtx scratch1 = gen_reg_rtx (SImode);
286*404b540aSrobert	rtx scratch2 = gen_reg_rtx (SImode);
287*404b540aSrobert	rtx scratch3 = gen_reg_rtx (SImode);
288*404b540aSrobert	rtx data     = operands[1];
289*404b540aSrobert	rtx address  = XEXP (operands[0], 0);
290*404b540aSrobert	rtx seq;
291*404b540aSrobert
292*404b540aSrobert	if ( GET_CODE (data) != REG )
293*404b540aSrobert	    data = copy_to_mode_reg (QImode, data);
294*404b540aSrobert
295*404b540aSrobert	if ( GET_CODE (address) != REG )
296*404b540aSrobert	  address = copy_to_mode_reg (SImode, address);
297*404b540aSrobert
298*404b540aSrobert	start_sequence ();
299*404b540aSrobert	emit_insn (gen_storeqi (gen_lowpart (SImode, data), address,
300*404b540aSrobert				scratch1, scratch2, scratch3));
301*404b540aSrobert	mt_set_memflags (operands[0]);
302*404b540aSrobert	seq = get_insns ();
303*404b540aSrobert	end_sequence ();
304*404b540aSrobert	emit_insn (seq);
305*404b540aSrobert	DONE;
306*404b540aSrobert    }
307*404b540aSrobert
308*404b540aSrobert  if ( (! TARGET_BYTE_ACCESS) && GET_CODE (operands[1]) == MEM)
309*404b540aSrobert    {
310*404b540aSrobert	rtx scratch1 = gen_reg_rtx (SImode);
311*404b540aSrobert	rtx data = operands[0];
312*404b540aSrobert	rtx address = XEXP (operands[1], 0);
313*404b540aSrobert	rtx seq;
314*404b540aSrobert
315*404b540aSrobert	if ( GET_CODE (address) != REG )
316*404b540aSrobert	  address = copy_to_mode_reg (SImode, address);
317*404b540aSrobert
318*404b540aSrobert	start_sequence ();
319*404b540aSrobert	emit_insn (gen_loadqi (gen_lowpart (SImode, data), address, scratch1));
320*404b540aSrobert	mt_set_memflags (operands[1]);
321*404b540aSrobert	seq = get_insns ();
322*404b540aSrobert	end_sequence ();
323*404b540aSrobert	emit_insn (seq);
324*404b540aSrobert	DONE;
325*404b540aSrobert    }
326*404b540aSrobert
327*404b540aSrobert   /* If the load is a pseudo register in a stack slot, some simplification
328*404b540aSrobert      can be made because the loads are aligned */
329*404b540aSrobert  if ( (! TARGET_BYTE_ACCESS)
330*404b540aSrobert        && (reload_in_progress && GET_CODE (operands[1]) == SUBREG
331*404b540aSrobert	  && GET_CODE (SUBREG_REG (operands[1])) == REG
332*404b540aSrobert	  && REGNO (SUBREG_REG (operands[1])) >= FIRST_PSEUDO_REGISTER))
333*404b540aSrobert    {
334*404b540aSrobert	rtx data = operands[0];
335*404b540aSrobert	rtx address = XEXP (operands[1], 0);
336*404b540aSrobert	rtx seq;
337*404b540aSrobert
338*404b540aSrobert	start_sequence ();
339*404b540aSrobert	emit_insn (gen_movsi (gen_lowpart (SImode, data), address));
340*404b540aSrobert	mt_set_memflags (operands[1]);
341*404b540aSrobert	seq = get_insns ();
342*404b540aSrobert	end_sequence ();
343*404b540aSrobert	emit_insn (seq);
344*404b540aSrobert	DONE;
345*404b540aSrobert    }
346*404b540aSrobert}")
347*404b540aSrobert
348*404b540aSrobert(define_insn "*movqi_internal"
349*404b540aSrobert  [(set (match_operand:QI 0 "nonimmediate_operand" "=r,r,m,r")
350*404b540aSrobert	(match_operand:QI 1 "general_operand" "r,m,r,I"))]
351*404b540aSrobert  "TARGET_BYTE_ACCESS
352*404b540aSrobert    && (!memory_operand (operands[0], QImode)
353*404b540aSrobert        || !memory_operand (operands[1], QImode))"
354*404b540aSrobert  "@
355*404b540aSrobert   or  %0, %1, %1
356*404b540aSrobert   ldb %0, %1
357*404b540aSrobert   stb %1, %0
358*404b540aSrobert   addi %0, r0, %1"
359*404b540aSrobert  [(set_attr "length" "4,4,4,4")
360*404b540aSrobert   (set_attr "type" "arith,load,store,arith")])
361*404b540aSrobert
362*404b540aSrobert(define_insn "*movqi_internal_nobyte"
363*404b540aSrobert  [(set (match_operand:QI 0 "register_operand" "=r,r")
364*404b540aSrobert	(match_operand:QI 1 "arith_operand" "r,I"))]
365*404b540aSrobert  "!TARGET_BYTE_ACCESS
366*404b540aSrobert    && (!memory_operand (operands[0], QImode)
367*404b540aSrobert        || !memory_operand (operands[1], QImode))"
368*404b540aSrobert  "@
369*404b540aSrobert   or   %0, %1, %1
370*404b540aSrobert   addi %0, r0, %1"
371*404b540aSrobert  [(set_attr "length" "4,4")
372*404b540aSrobert   (set_attr "type" "arith,arith")])
373*404b540aSrobert
374*404b540aSrobert
375*404b540aSrobert;; The MorphoRISC does not have 16-bit loads and stores.
376*404b540aSrobert;; These operations must be synthesized.  Note that the code
377*404b540aSrobert;; for loadhi and storehi assumes that the least significant bits
378*404b540aSrobert;; is ignored.
379*404b540aSrobert
380*404b540aSrobert;; loadhi
381*404b540aSrobert;; operand 0 location of result
382*404b540aSrobert;; operand 1 memory address
383*404b540aSrobert;; operand 2 temp
384*404b540aSrobert(define_expand "loadhi"
385*404b540aSrobert  [
386*404b540aSrobert   ;; compute shift
387*404b540aSrobert   (set (match_operand:SI 2 "register_operand" "")
388*404b540aSrobert	(and:SI (match_dup 1) (const_int 2)))
389*404b540aSrobert   (set (match_dup 2)	(xor:SI (match_dup 2) (const_int 2)))
390*404b540aSrobert   (set (match_dup 2 )	(ashift:SI (match_dup 2) (const_int 3)))
391*404b540aSrobert
392*404b540aSrobert   ;; get word that contains the 16-bits
393*404b540aSrobert   (set (match_operand:SI 0 "register_operand" "")
394*404b540aSrobert	(mem:SI (and:SI (match_operand:SI 1 "register_operand" "")
395*404b540aSrobert			(const_int -3))))
396*404b540aSrobert
397*404b540aSrobert   ;; align 16-bit value
398*404b540aSrobert   (set (match_dup 0)	(ashiftrt:SI (match_dup 0) (match_dup 2)))
399*404b540aSrobert  ]
400*404b540aSrobert  ""
401*404b540aSrobert  "")
402*404b540aSrobert
403*404b540aSrobert;; storehi
404*404b540aSrobert;; operand 0 byte value to store
405*404b540aSrobert;; operand 1 address
406*404b540aSrobert;; operand 2 temp, word containing byte
407*404b540aSrobert;; operand 3 temp, shift count
408*404b540aSrobert;; operand 4 temp, mask, aligned and masked byte
409*404b540aSrobert;; operand 5 (unused)
410*404b540aSrobert(define_expand "storehi"
411*404b540aSrobert  [
412*404b540aSrobert   ;; compute shift
413*404b540aSrobert   (set (match_operand:SI 3 "register_operand" "")
414*404b540aSrobert	(and:SI (match_operand:SI 1 "register_operand" "") (const_int 2)))
415*404b540aSrobert   (set (match_dup 3)	(xor:SI (match_dup 3) (const_int 2)))
416*404b540aSrobert   (set (match_dup 3)	(ashift:SI (match_dup 3) (const_int 3)))
417*404b540aSrobert
418*404b540aSrobert   ;; get word that contains the 16-bits
419*404b540aSrobert   (set (match_operand:SI 2 "register_operand" "")
420*404b540aSrobert	(mem:SI (and:SI (match_dup 1) (const_int -3))))
421*404b540aSrobert
422*404b540aSrobert   ;; generate mask
423*404b540aSrobert   (set (match_operand:SI 4 "register_operand" "") (const_int 65535))
424*404b540aSrobert   (set (match_dup 4) (ashift:SI (match_dup 4) (match_dup 3)))
425*404b540aSrobert   (set (match_dup 4) (not:SI (match_dup 4)))
426*404b540aSrobert
427*404b540aSrobert   ;; clear appropriate bits
428*404b540aSrobert   (set (match_dup 2) (and:SI (match_dup 2) (match_dup 4)))
429*404b540aSrobert
430*404b540aSrobert   ;; align 16-bit value
431*404b540aSrobert   (set (match_dup 4)
432*404b540aSrobert	(and:SI (match_operand:SI 0 "register_operand" "") (const_int 65535)))
433*404b540aSrobert   (set (match_dup 4) (ashift:SI (match_dup 4) (match_dup 3)))
434*404b540aSrobert
435*404b540aSrobert   ;; combine
436*404b540aSrobert   (set (match_dup 2) (ior:SI (match_dup 4) (match_dup 2)))
437*404b540aSrobert   ;; store updated word
438*404b540aSrobert   (set (mem:SI (and:SI (match_dup 1) (const_int -3))) (match_dup 2))
439*404b540aSrobert  ]
440*404b540aSrobert  ""
441*404b540aSrobert  "")
442*404b540aSrobert
443*404b540aSrobert
444*404b540aSrobert(define_expand "movhi"
445*404b540aSrobert  [(set (match_operand:HI 0 "general_operand" "")
446*404b540aSrobert	(match_operand:HI 1 "general_operand" ""))]
447*404b540aSrobert  ""
448*404b540aSrobert  "
449*404b540aSrobert{
450*404b540aSrobert  if (!reload_in_progress
451*404b540aSrobert      && !reload_completed
452*404b540aSrobert      && GET_CODE (operands[0]) == MEM
453*404b540aSrobert      && GET_CODE (operands[1]) == MEM)
454*404b540aSrobert    operands[1] = copy_to_mode_reg (HImode, operands[1]);
455*404b540aSrobert
456*404b540aSrobert  if ( GET_CODE (operands[0]) == MEM)
457*404b540aSrobert    {
458*404b540aSrobert	rtx scratch1 = gen_reg_rtx (SImode);
459*404b540aSrobert	rtx scratch2 = gen_reg_rtx (SImode);
460*404b540aSrobert	rtx scratch3 = gen_reg_rtx (SImode);
461*404b540aSrobert	rtx data     = operands[1];
462*404b540aSrobert	rtx address  = XEXP (operands[0], 0);
463*404b540aSrobert	rtx seq;
464*404b540aSrobert
465*404b540aSrobert	if (GET_CODE (data) != REG)
466*404b540aSrobert	  data = copy_to_mode_reg (HImode, data);
467*404b540aSrobert
468*404b540aSrobert	if (GET_CODE (address) != REG)
469*404b540aSrobert	  address = copy_to_mode_reg (SImode, address);
470*404b540aSrobert
471*404b540aSrobert	start_sequence ();
472*404b540aSrobert	emit_insn (gen_storehi (gen_lowpart (SImode, data), address,
473*404b540aSrobert			        scratch1, scratch2, scratch3));
474*404b540aSrobert	mt_set_memflags (operands[0]);
475*404b540aSrobert	seq = get_insns ();
476*404b540aSrobert	end_sequence ();
477*404b540aSrobert	emit_insn (seq);
478*404b540aSrobert	DONE;
479*404b540aSrobert    }
480*404b540aSrobert
481*404b540aSrobert  if ( GET_CODE (operands[1]) == MEM)
482*404b540aSrobert    {
483*404b540aSrobert	rtx scratch1 = gen_reg_rtx (SImode);
484*404b540aSrobert	rtx data     = operands[0];
485*404b540aSrobert	rtx address  = XEXP (operands[1], 0);
486*404b540aSrobert	rtx seq;
487*404b540aSrobert
488*404b540aSrobert	if (GET_CODE (address) != REG)
489*404b540aSrobert	    address = copy_to_mode_reg (SImode, address);
490*404b540aSrobert
491*404b540aSrobert	start_sequence ();
492*404b540aSrobert	emit_insn (gen_loadhi (gen_lowpart (SImode, data), address,
493*404b540aSrobert			       scratch1));
494*404b540aSrobert	mt_set_memflags (operands[1]);
495*404b540aSrobert	seq = get_insns ();
496*404b540aSrobert	end_sequence ();
497*404b540aSrobert	emit_insn (seq);
498*404b540aSrobert	DONE;
499*404b540aSrobert    }
500*404b540aSrobert
501*404b540aSrobert   /* If the load is a pseudo register in a stack slot, some simplification
502*404b540aSrobert      can be made because the loads are aligned */
503*404b540aSrobert  if ( (reload_in_progress && GET_CODE (operands[1]) == SUBREG
504*404b540aSrobert	  && GET_CODE (SUBREG_REG (operands[1])) == REG
505*404b540aSrobert	  && REGNO (SUBREG_REG (operands[1])) >= FIRST_PSEUDO_REGISTER))
506*404b540aSrobert    {
507*404b540aSrobert	rtx data = operands[0];
508*404b540aSrobert	rtx address = XEXP (operands[1], 0);
509*404b540aSrobert	rtx seq;
510*404b540aSrobert
511*404b540aSrobert	start_sequence ();
512*404b540aSrobert	emit_insn (gen_movsi (gen_lowpart (SImode, data), address));
513*404b540aSrobert	mt_set_memflags (operands[1]);
514*404b540aSrobert	seq = get_insns ();
515*404b540aSrobert	end_sequence ();
516*404b540aSrobert	emit_insn (seq);
517*404b540aSrobert	DONE;
518*404b540aSrobert    }
519*404b540aSrobert}")
520*404b540aSrobert
521*404b540aSrobert(define_insn "*movhi_internal"
522*404b540aSrobert  [(set (match_operand:HI 0 "register_operand" "=r,r")
523*404b540aSrobert	(match_operand:HI 1 "arith_operand" "r,I"))]
524*404b540aSrobert  "!memory_operand (operands[0], HImode) || !memory_operand (operands[1], HImode)"
525*404b540aSrobert  "@
526*404b540aSrobert  or    %0, %1, %1
527*404b540aSrobert  addi  %0, r0, %1"
528*404b540aSrobert  [(set_attr "length" "4,4")
529*404b540aSrobert   (set_attr "type" "arith,arith")])
530*404b540aSrobert
531*404b540aSrobert(define_expand "movsi"
532*404b540aSrobert  [(set (match_operand:SI 0 "nonimmediate_operand" "")
533*404b540aSrobert	(match_operand:SI 1 "general_operand" ""))]
534*404b540aSrobert  ""
535*404b540aSrobert  "
536*404b540aSrobert{
537*404b540aSrobert  if (!reload_in_progress  && !reload_completed
538*404b540aSrobert      && !register_operand (operands[0], SImode)
539*404b540aSrobert      && !register_operand (operands[1], SImode))
540*404b540aSrobert    operands[1] = copy_to_mode_reg (SImode, operands[1]);
541*404b540aSrobert
542*404b540aSrobert  /* Take care of constants that don't fit in single instruction */
543*404b540aSrobert  if ( (reload_in_progress || reload_completed)
544*404b540aSrobert   && !single_const_operand (operands[1], SImode))
545*404b540aSrobert    {
546*404b540aSrobert      emit_insn (gen_movsi_high (operands[0], operands[1]));
547*404b540aSrobert      emit_insn (gen_movsi_lo_sum (operands[0], operands[0], operands[1]));
548*404b540aSrobert      DONE;
549*404b540aSrobert    }
550*404b540aSrobert
551*404b540aSrobert}")
552*404b540aSrobert
553*404b540aSrobert(define_insn "movsi_high"
554*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r")
555*404b540aSrobert        (high:SI (match_operand:SI 1 "general_operand" "i")))]
556*404b540aSrobert  ""
557*404b540aSrobert  "*
558*404b540aSrobert{
559*404b540aSrobert  return \"ldui\\t%0, %H1\";
560*404b540aSrobert}"
561*404b540aSrobert  [(set_attr "length" "4")
562*404b540aSrobert   (set_attr "type" "arith")])
563*404b540aSrobert
564*404b540aSrobert
565*404b540aSrobert(define_insn "movsi_lo_sum"
566*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r")
567*404b540aSrobert        (lo_sum:SI (match_operand:SI 1 "register_operand" "r")
568*404b540aSrobert                   (match_operand:SI 2 "general_operand" "i")))]
569*404b540aSrobert  ""
570*404b540aSrobert  "*
571*404b540aSrobert{
572*404b540aSrobert  return \"addui\\t%0, %1, %L2\";
573*404b540aSrobert}"
574*404b540aSrobert  [(set_attr "length" "4")
575*404b540aSrobert   (set_attr "type" "arith")])
576*404b540aSrobert
577*404b540aSrobert/* Take care of constants that don't fit in single instruction */
578*404b540aSrobert(define_split
579*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "")
580*404b540aSrobert	(match_operand:SI 1 "general_operand" ""))]
581*404b540aSrobert  "(reload_in_progress || reload_completed)
582*404b540aSrobert   && !single_const_operand (operands[1], SImode)"
583*404b540aSrobert
584*404b540aSrobert  [(set (match_dup 0 )
585*404b540aSrobert        (high:SI (match_dup 1)))
586*404b540aSrobert   (set (match_dup 0 )
587*404b540aSrobert        (lo_sum:SI (match_dup 0)
588*404b540aSrobert                   (match_dup 1)))]
589*404b540aSrobert)
590*404b540aSrobert
591*404b540aSrobert
592*404b540aSrobert;; The last pattern in movsi (with two instructions)
593*404b540aSrobert;; is really handled by the emit_insn's in movsi
594*404b540aSrobert;; and the define_split above.  This provides additional
595*404b540aSrobert;; instructions to fill delay slots.
596*404b540aSrobert
597*404b540aSrobert;; Note - it is best to only have one movsi pattern and to handle
598*404b540aSrobert;; all the various contingencies by the use of alternatives.  This
599*404b540aSrobert;; allows reload the greatest amount of flexibility (since reload will
600*404b540aSrobert;; only choose amoungst alternatives for a selected insn, it will not
601*404b540aSrobert;; replace the insn with another one).
602*404b540aSrobert(define_insn "*movsi_internal"
603*404b540aSrobert  [(set (match_operand:SI 0 "nonimmediate_operand" "=r,r,m,r,r,r,r,r")
604*404b540aSrobert	(match_operand:SI 1 "general_operand"       "r,m,r,I,P,L,N,i"))]
605*404b540aSrobert  "(!memory_operand (operands[0], SImode) || !memory_operand (operands[1], SImode))
606*404b540aSrobert   && !((reload_in_progress || reload_completed)
607*404b540aSrobert	 && !single_const_operand (operands[1], SImode))"
608*404b540aSrobert  "@
609*404b540aSrobert  or     %0, %1, %1
610*404b540aSrobert  ldw    %0, %1
611*404b540aSrobert  stw    %1, %0
612*404b540aSrobert  addi   %0, r0, %1
613*404b540aSrobert  addui  %0, r0, %1
614*404b540aSrobert  ldui   %0, %H1
615*404b540aSrobert  nori   %0, r0, %N1
616*404b540aSrobert  ldui   %0, %H1\;addui %0, %0, %L1"
617*404b540aSrobert  [(set_attr "length" "4,4,4,4,4,4,4,8")
618*404b540aSrobert   (set_attr "type" "arith,load,store,arith,arith,arith,arith,complex")]
619*404b540aSrobert)
620*404b540aSrobert
621*404b540aSrobert;; Floating Point Moves
622*404b540aSrobert;;
623*404b540aSrobert;; Note - Patterns for SF mode moves are compulsory, but
624*404b540aSrobert;; patterns for DF are optional, as GCC can synthesize them.
625*404b540aSrobert
626*404b540aSrobert(define_expand "movsf"
627*404b540aSrobert  [(set (match_operand:SF 0 "general_operand" "")
628*404b540aSrobert	(match_operand:SF 1 "general_operand" ""))]
629*404b540aSrobert  ""
630*404b540aSrobert  "
631*404b540aSrobert{
632*404b540aSrobert  if (!reload_in_progress
633*404b540aSrobert      && !reload_completed
634*404b540aSrobert      && GET_CODE (operands[0]) == MEM
635*404b540aSrobert      && (GET_CODE (operands[1]) == MEM
636*404b540aSrobert         || GET_CODE (operands[1]) == CONST_DOUBLE))
637*404b540aSrobert    operands[1] = copy_to_mode_reg (SFmode, operands[1]);
638*404b540aSrobert
639*404b540aSrobert  /* Take care of reg <- SF constant */
640*404b540aSrobert  if ( const_double_operand (operands[1], GET_MODE (operands[1]) ) )
641*404b540aSrobert    {
642*404b540aSrobert      emit_insn (gen_movsf_high (operands[0], operands[1]));
643*404b540aSrobert      emit_insn (gen_movsf_lo_sum (operands[0], operands[0], operands[1]));
644*404b540aSrobert      DONE;
645*404b540aSrobert    }
646*404b540aSrobert}")
647*404b540aSrobert
648*404b540aSrobert(define_insn "movsf_lo_sum"
649*404b540aSrobert  [(set (match_operand:SF 0 "register_operand" "=r")
650*404b540aSrobert        (lo_sum:SF (match_operand:SF 1 "register_operand" "r")
651*404b540aSrobert                   (match_operand:SF 2 "const_double_operand" "")))]
652*404b540aSrobert  ""
653*404b540aSrobert  "*
654*404b540aSrobert{
655*404b540aSrobert  REAL_VALUE_TYPE r;
656*404b540aSrobert  long i;
657*404b540aSrobert
658*404b540aSrobert  REAL_VALUE_FROM_CONST_DOUBLE (r, operands[2]);
659*404b540aSrobert  REAL_VALUE_TO_TARGET_SINGLE (r, i);
660*404b540aSrobert  operands[2] = GEN_INT (i);
661*404b540aSrobert  return \"addui\\t%0, %1, %L2\";
662*404b540aSrobert}"
663*404b540aSrobert  [(set_attr "length" "4")
664*404b540aSrobert   (set_attr "type" "arith")])
665*404b540aSrobert
666*404b540aSrobert(define_insn "movsf_high"
667*404b540aSrobert  [(set (match_operand:SF 0 "register_operand" "=r")
668*404b540aSrobert        (high:SF (match_operand:SF 1 "const_double_operand" "")))]
669*404b540aSrobert  ""
670*404b540aSrobert  "*
671*404b540aSrobert{
672*404b540aSrobert  REAL_VALUE_TYPE r;
673*404b540aSrobert  long i;
674*404b540aSrobert
675*404b540aSrobert  REAL_VALUE_FROM_CONST_DOUBLE (r, operands[1]);
676*404b540aSrobert  REAL_VALUE_TO_TARGET_SINGLE (r, i);
677*404b540aSrobert  operands[1] = GEN_INT (i);
678*404b540aSrobert  return \"ldui\\t%0, %H1\";
679*404b540aSrobert}"
680*404b540aSrobert  [(set_attr "length" "4")
681*404b540aSrobert   (set_attr "type" "arith")])
682*404b540aSrobert
683*404b540aSrobert
684*404b540aSrobert(define_insn "*movsf_internal"
685*404b540aSrobert  [(set (match_operand:SF 0 "nonimmediate_operand" "=r,r,m")
686*404b540aSrobert	(match_operand:SF 1 "nonimmediate_operand" "r,m,r"))]
687*404b540aSrobert  "!memory_operand (operands[0], SFmode) || !memory_operand (operands[1], SFmode)"
688*404b540aSrobert  "@
689*404b540aSrobert  or     %0, %1, %1
690*404b540aSrobert  ldw    %0, %1
691*404b540aSrobert  stw    %1, %0"
692*404b540aSrobert  [(set_attr "length" "4,4,4")
693*404b540aSrobert   (set_attr "type" "arith,load,store")]
694*404b540aSrobert)
695*404b540aSrobert
696*404b540aSrobert(define_expand "movdf"
697*404b540aSrobert  [(set (match_operand:DF 0 "general_operand" "")
698*404b540aSrobert	(match_operand:DF 1 "general_operand" ""))]
699*404b540aSrobert  ""
700*404b540aSrobert  "
701*404b540aSrobert{
702*404b540aSrobert  /* One of the ops has to be in a register or 0 */
703*404b540aSrobert  if (!register_operand (operand0, DFmode)
704*404b540aSrobert      && !reg_or_0_operand (operand1, DFmode))
705*404b540aSrobert    operands[1] = copy_to_mode_reg (DFmode, operand1);
706*404b540aSrobert}")
707*404b540aSrobert
708*404b540aSrobert(define_insn_and_split "*movdf_internal"
709*404b540aSrobert  [(set (match_operand:DF 0 "nonimmediate_operand" "=r,o")
710*404b540aSrobert	(match_operand:DF 1 "general_operand" 	   "rim,r"))]
711*404b540aSrobert  "! (memory_operand (operands[0], DFmode)
712*404b540aSrobert         && memory_operand (operands[1], DFmode))"
713*404b540aSrobert  "#"
714*404b540aSrobert
715*404b540aSrobert  "(reload_completed || reload_in_progress)"
716*404b540aSrobert
717*404b540aSrobert  [(set (match_dup 2) (match_dup 3))
718*404b540aSrobert   (set (match_dup 4) (match_dup 5))
719*404b540aSrobert  ]
720*404b540aSrobert
721*404b540aSrobert  "{
722*404b540aSrobert    /* figure out what precisely to put into operands 2, 3, 4, and 5 */
723*404b540aSrobert    mt_split_words (SImode, DFmode, operands);
724*404b540aSrobert  }"
725*404b540aSrobert)
726*404b540aSrobert
727*404b540aSrobert
728*404b540aSrobert;; Reloads
729*404b540aSrobert
730*404b540aSrobert;; Like `movM', but used when a scratch register is required to move between
731*404b540aSrobert;; operand 0 and operand 1.  Operand 2 describes the scratch register.  See the
732*404b540aSrobert;; discussion of the `SECONDARY_RELOAD_CLASS' macro.
733*404b540aSrobert
734*404b540aSrobert(define_expand "reload_inqi"
735*404b540aSrobert  [(set (match_operand:QI 0 "register_operand" "=r")
736*404b540aSrobert        (match_operand:QI 1 "memory_operand" "m"))
737*404b540aSrobert   (clobber (match_operand:DI 2 "register_operand" "=&r"))]
738*404b540aSrobert  "! TARGET_BYTE_ACCESS"
739*404b540aSrobert  "
740*404b540aSrobert{
741*404b540aSrobert  rtx scratch1 = gen_rtx_REG (SImode, REGNO (operands[2]));
742*404b540aSrobert  rtx scratch2 = gen_rtx_REG (SImode, REGNO (operands[2])+1);
743*404b540aSrobert  rtx data = operands[0];
744*404b540aSrobert  rtx address = XEXP (operands[1], 0);
745*404b540aSrobert  rtx swap, seq;
746*404b540aSrobert
747*404b540aSrobert  /* It is possible that the registers we got for scratch1
748*404b540aSrobert     might coincide with that of operands[0].  gen_loadqi
749*404b540aSrobert     requires operand0 and operand2 to be different registers.
750*404b540aSrobert     The following statement ensure that is always the case. */
751*404b540aSrobert  if (REGNO(operands[0]) == REGNO(scratch1))
752*404b540aSrobert    {
753*404b540aSrobert	swap = scratch1;
754*404b540aSrobert	scratch1 = scratch2;
755*404b540aSrobert	scratch2 = swap;
756*404b540aSrobert    }
757*404b540aSrobert
758*404b540aSrobert  /* need to make sure address is already in register */
759*404b540aSrobert  if ( GET_CODE (address) != REG )
760*404b540aSrobert    address = force_operand (address, scratch2);
761*404b540aSrobert
762*404b540aSrobert  start_sequence ();
763*404b540aSrobert  emit_insn (gen_loadqi (gen_lowpart (SImode, data), address, scratch1));
764*404b540aSrobert  mt_set_memflags (operands[1]);
765*404b540aSrobert  seq = get_insns ();
766*404b540aSrobert  end_sequence ();
767*404b540aSrobert  emit_insn (seq);
768*404b540aSrobert  DONE;
769*404b540aSrobert}")
770*404b540aSrobert
771*404b540aSrobert(define_expand "reload_outqi"
772*404b540aSrobert  [(set (match_operand:QI 0 "memory_operand" "=m")
773*404b540aSrobert        (match_operand:QI 1 "register_operand" "r"))
774*404b540aSrobert   (clobber (match_operand:TI 2 "register_operand" "=&r"))]
775*404b540aSrobert  "! TARGET_BYTE_ACCESS"
776*404b540aSrobert  "
777*404b540aSrobert{
778*404b540aSrobert  rtx scratch1 = gen_rtx_REG (SImode, REGNO (operands[2]));
779*404b540aSrobert  rtx scratch2 = gen_rtx_REG (SImode, REGNO (operands[2])+1);
780*404b540aSrobert  rtx scratch3 = gen_rtx_REG (SImode, REGNO (operands[2])+2);
781*404b540aSrobert  rtx scratch4 = gen_rtx_REG (SImode, REGNO (operands[2])+3);
782*404b540aSrobert  rtx data     = operands[1];
783*404b540aSrobert  rtx address  = XEXP (operands[0], 0);
784*404b540aSrobert  rtx seq;
785*404b540aSrobert
786*404b540aSrobert  /* need to make sure address is already in register */
787*404b540aSrobert  if ( GET_CODE (address) != REG )
788*404b540aSrobert    address = force_operand (address, scratch4);
789*404b540aSrobert
790*404b540aSrobert  start_sequence ();
791*404b540aSrobert  emit_insn (gen_storeqi (gen_lowpart (SImode, data), address,
792*404b540aSrobert			  scratch1, scratch2, scratch3));
793*404b540aSrobert  mt_set_memflags (operands[0]);
794*404b540aSrobert  seq = get_insns ();
795*404b540aSrobert  end_sequence ();
796*404b540aSrobert  emit_insn (seq);
797*404b540aSrobert  DONE;
798*404b540aSrobert}")
799*404b540aSrobert
800*404b540aSrobert(define_expand "reload_inhi"
801*404b540aSrobert  [(set (match_operand:HI 0 "register_operand" "=r")
802*404b540aSrobert        (match_operand:HI 1 "memory_operand" "m"))
803*404b540aSrobert   (clobber (match_operand:DI 2 "register_operand" "=&r"))]
804*404b540aSrobert  ""
805*404b540aSrobert  "
806*404b540aSrobert{
807*404b540aSrobert  rtx scratch1 = gen_rtx_REG (SImode, REGNO (operands[2]));
808*404b540aSrobert  rtx scratch2 = gen_rtx_REG (SImode, REGNO (operands[2])+1);
809*404b540aSrobert  rtx data     = operands[0];
810*404b540aSrobert  rtx address  = XEXP (operands[1], 0);
811*404b540aSrobert  rtx swap, seq;
812*404b540aSrobert
813*404b540aSrobert  /* It is possible that the registers we got for scratch1
814*404b540aSrobert     might coincide with that of operands[0].  gen_loadqi
815*404b540aSrobert     requires operand0 and operand2 to be different registers.
816*404b540aSrobert     The following statement ensure that is always the case. */
817*404b540aSrobert  if (REGNO(operands[0]) == REGNO(scratch1))
818*404b540aSrobert    {
819*404b540aSrobert	swap = scratch1;
820*404b540aSrobert	scratch1 = scratch2;
821*404b540aSrobert	scratch2 = swap;
822*404b540aSrobert    }
823*404b540aSrobert
824*404b540aSrobert  /* need to make sure address is already in register */
825*404b540aSrobert  if ( GET_CODE (address) != REG )
826*404b540aSrobert    address = force_operand (address, scratch2);
827*404b540aSrobert
828*404b540aSrobert  start_sequence ();
829*404b540aSrobert  emit_insn (gen_loadhi (gen_lowpart (SImode, data), address,
830*404b540aSrobert		         scratch1));
831*404b540aSrobert  mt_set_memflags (operands[1]);
832*404b540aSrobert  seq = get_insns ();
833*404b540aSrobert  end_sequence ();
834*404b540aSrobert  emit_insn (seq);
835*404b540aSrobert  DONE;
836*404b540aSrobert}")
837*404b540aSrobert
838*404b540aSrobert(define_expand "reload_outhi"
839*404b540aSrobert  [(set (match_operand:HI 0 "memory_operand" "=m")
840*404b540aSrobert        (match_operand:HI 1 "register_operand" "r"))
841*404b540aSrobert   (clobber (match_operand:TI 2 "register_operand" "=&r"))]
842*404b540aSrobert  ""
843*404b540aSrobert  "
844*404b540aSrobert{
845*404b540aSrobert  rtx scratch1 = gen_rtx_REG (SImode, REGNO (operands[2]));
846*404b540aSrobert  rtx scratch2 = gen_rtx_REG (SImode, REGNO (operands[2])+1);
847*404b540aSrobert  rtx scratch3 = gen_rtx_REG (SImode, REGNO (operands[2])+2);
848*404b540aSrobert  rtx scratch4 = gen_rtx_REG (SImode, REGNO (operands[2])+3);
849*404b540aSrobert  rtx data     = operands[1];
850*404b540aSrobert  rtx address  = XEXP (operands[0], 0);
851*404b540aSrobert  rtx seq;
852*404b540aSrobert
853*404b540aSrobert  /* need to make sure address is already in register */
854*404b540aSrobert  if ( GET_CODE (address) != REG )
855*404b540aSrobert    address = force_operand (address, scratch4);
856*404b540aSrobert
857*404b540aSrobert  start_sequence ();
858*404b540aSrobert  emit_insn (gen_storehi (gen_lowpart (SImode, data), address,
859*404b540aSrobert		          scratch1, scratch2, scratch3));
860*404b540aSrobert  mt_set_memflags (operands[0]);
861*404b540aSrobert  seq = get_insns ();
862*404b540aSrobert  end_sequence ();
863*404b540aSrobert  emit_insn (seq);
864*404b540aSrobert  DONE;
865*404b540aSrobert}")
866*404b540aSrobert
867*404b540aSrobert
868*404b540aSrobert;; 32 bit Integer arithmetic
869*404b540aSrobert
870*404b540aSrobert;; Addition
871*404b540aSrobert(define_insn "addsi3"
872*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
873*404b540aSrobert	(plus:SI (match_operand:SI 1 "register_operand" "%r,r")
874*404b540aSrobert		 (match_operand:SI 2 "arith_operand" "r,I")))]
875*404b540aSrobert  ""
876*404b540aSrobert  "@
877*404b540aSrobert  add %0, %1, %2
878*404b540aSrobert  addi %0, %1, %2"
879*404b540aSrobert  [(set_attr "length" "4,4")
880*404b540aSrobert   (set_attr "type" "arith,arith")])
881*404b540aSrobert
882*404b540aSrobert;; Subtraction
883*404b540aSrobert(define_insn "subsi3"
884*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
885*404b540aSrobert	(minus:SI (match_operand:SI 1 "reg_or_0_operand" "rJ,rJ")
886*404b540aSrobert		  (match_operand:SI 2 "arith_operand" "rJ,I")))]
887*404b540aSrobert  ""
888*404b540aSrobert  "@
889*404b540aSrobert  sub %0, %z1, %z2
890*404b540aSrobert  subi %0, %z1, %2"
891*404b540aSrobert  [(set_attr "length" "4,4")
892*404b540aSrobert   (set_attr "type" "arith,arith")])
893*404b540aSrobert
894*404b540aSrobert;;  Negation
895*404b540aSrobert(define_insn "negsi2"
896*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
897*404b540aSrobert	(neg:SI (match_operand:SI 1 "arith_operand" "r,I")))]
898*404b540aSrobert  ""
899*404b540aSrobert  "@
900*404b540aSrobert  sub  %0, r0, %1
901*404b540aSrobert  subi  %0, r0, %1"
902*404b540aSrobert  [(set_attr "length" "4,4")
903*404b540aSrobert   (set_attr "type" "arith,arith")])
904*404b540aSrobert
905*404b540aSrobert
906*404b540aSrobert;; 32 bit Integer Shifts and Rotates
907*404b540aSrobert
908*404b540aSrobert;; Arithmetic Shift Left
909*404b540aSrobert(define_insn "ashlsi3"
910*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
911*404b540aSrobert	(ashift:SI (match_operand:SI 1 "register_operand" "r,r")
912*404b540aSrobert		   (match_operand:SI 2 "arith_operand" "r,K")))]
913*404b540aSrobert  ""
914*404b540aSrobert  "@
915*404b540aSrobert  lsl %0, %1, %2
916*404b540aSrobert  lsli %0, %1, %2"
917*404b540aSrobert  [(set_attr "length" "4,4")
918*404b540aSrobert   (set_attr "type" "arith,arith")])
919*404b540aSrobert
920*404b540aSrobert;; Arithmetic Shift Right
921*404b540aSrobert(define_insn "ashrsi3"
922*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
923*404b540aSrobert	(ashiftrt:SI (match_operand:SI 1 "register_operand" "r,r")
924*404b540aSrobert		     (match_operand:SI 2 "uns_arith_operand" "r,K")))]
925*404b540aSrobert  ""
926*404b540aSrobert  "@
927*404b540aSrobert  asr %0, %1, %2
928*404b540aSrobert  asri %0, %1, %2"
929*404b540aSrobert  [(set_attr "length" "4,4")
930*404b540aSrobert   (set_attr "type" "arith,arith")])
931*404b540aSrobert
932*404b540aSrobert;; Logical Shift Right
933*404b540aSrobert(define_insn "lshrsi3"
934*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
935*404b540aSrobert	(lshiftrt:SI (match_operand:SI 1 "register_operand" "r,r")
936*404b540aSrobert		     (match_operand:SI 2 "uns_arith_operand" "r,K")))]
937*404b540aSrobert  ""
938*404b540aSrobert  "@
939*404b540aSrobert  lsr %0, %1, %2
940*404b540aSrobert  lsri %0, %1, %2"
941*404b540aSrobert  [(set_attr "length" "4,4")
942*404b540aSrobert   (set_attr "type" "arith,arith")])
943*404b540aSrobert
944*404b540aSrobert
945*404b540aSrobert;; 32 Bit Integer Logical operations
946*404b540aSrobert
947*404b540aSrobert;; Logical AND, 32 bit integers
948*404b540aSrobert(define_insn "andsi3"
949*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
950*404b540aSrobert	(and:SI (match_operand:SI 1 "register_operand" "%r,r")
951*404b540aSrobert		(match_operand:SI 2 "uns_arith_operand" "r,K")))]
952*404b540aSrobert  ""
953*404b540aSrobert  "@
954*404b540aSrobert  and %0, %1, %2
955*404b540aSrobert  andi %0, %1, %2"
956*404b540aSrobert  [(set_attr "length" "4,4")
957*404b540aSrobert   (set_attr "type" "arith,arith")])
958*404b540aSrobert
959*404b540aSrobert;; Inclusive OR, 32 bit integers
960*404b540aSrobert(define_insn "iorsi3"
961*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
962*404b540aSrobert	(ior:SI (match_operand:SI 1 "register_operand" "%r,r")
963*404b540aSrobert		(match_operand:SI 2 "uns_arith_operand" "r,K")))]
964*404b540aSrobert  ""
965*404b540aSrobert  "@
966*404b540aSrobert  or %0, %1, %2
967*404b540aSrobert  ori %0, %1, %2"
968*404b540aSrobert  [(set_attr "length" "4,4")
969*404b540aSrobert   (set_attr "type" "arith,arith")])
970*404b540aSrobert
971*404b540aSrobert;; Exclusive OR, 32 bit integers
972*404b540aSrobert(define_insn "xorsi3"
973*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
974*404b540aSrobert	(xor:SI (match_operand:SI 1 "register_operand" "%r,r")
975*404b540aSrobert		(match_operand:SI 2 "uns_arith_operand" "r,K")))]
976*404b540aSrobert  ""
977*404b540aSrobert  "@
978*404b540aSrobert  xor %0, %1, %2
979*404b540aSrobert  xori %0, %1, %2"
980*404b540aSrobert  [(set_attr "length" "4,4")
981*404b540aSrobert   (set_attr "type" "arith,arith")])
982*404b540aSrobert
983*404b540aSrobert
984*404b540aSrobert;; One's complement, 32 bit integers
985*404b540aSrobert(define_insn "one_cmplsi2"
986*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r")
987*404b540aSrobert	(not:SI (match_operand:SI 1 "register_operand" "r")))]
988*404b540aSrobert  ""
989*404b540aSrobert  "nor %0, %1, %1"
990*404b540aSrobert  [(set_attr "length" "4")
991*404b540aSrobert   (set_attr "type" "arith")])
992*404b540aSrobert
993*404b540aSrobert
994*404b540aSrobert;; Multiply
995*404b540aSrobert
996*404b540aSrobert(define_insn "mulhisi3"
997*404b540aSrobert  [(set (match_operand:SI 0 "register_operand" "=r,r")
998*404b540aSrobert     (mult:SI (sign_extend:SI (match_operand:HI 1 "register_operand" "%r,r"))
999*404b540aSrobert     	      (sign_extend:SI (match_operand:HI 2 "arith_operand" "r,I"))))]
1000*404b540aSrobert  "TARGET_MS1_16_003 || TARGET_MS2"
1001*404b540aSrobert  "@
1002*404b540aSrobert  mul %0, %1, %2
1003*404b540aSrobert  muli %0, %1, %2"
1004*404b540aSrobert  [(set_attr "length" "4,4")
1005*404b540aSrobert   (set_attr "type" "arith,arith")])
1006*404b540aSrobert
1007*404b540aSrobert
1008*404b540aSrobert;; Comparisons
1009*404b540aSrobert
1010*404b540aSrobert;; Note, we store the operands in the comparison insns, and use them later
1011*404b540aSrobert;; when generating the branch or scc operation.
1012*404b540aSrobert
1013*404b540aSrobert;; First the routines called by the machine independent part of the compiler
1014*404b540aSrobert(define_expand "cmpsi"
1015*404b540aSrobert  [(set (cc0)
1016*404b540aSrobert        (compare (match_operand:SI 0 "register_operand" "")
1017*404b540aSrobert  		 (match_operand:SI 1 "arith_operand" "")))]
1018*404b540aSrobert  ""
1019*404b540aSrobert  "
1020*404b540aSrobert{
1021*404b540aSrobert  mt_compare_op0 = operands[0];
1022*404b540aSrobert  mt_compare_op1 = operands[1];
1023*404b540aSrobert  DONE;
1024*404b540aSrobert}")
1025*404b540aSrobert
1026*404b540aSrobert
1027*404b540aSrobert;; Branches
1028*404b540aSrobert
1029*404b540aSrobert(define_expand "beq"
1030*404b540aSrobert  [(use (match_operand 0 "" ""))]
1031*404b540aSrobert  ""
1032*404b540aSrobert  "
1033*404b540aSrobert{
1034*404b540aSrobert  mt_emit_cbranch (EQ, operands[0], mt_compare_op0, mt_compare_op1);
1035*404b540aSrobert  DONE;
1036*404b540aSrobert}")
1037*404b540aSrobert
1038*404b540aSrobert(define_expand "bne"
1039*404b540aSrobert  [(use (match_operand 0 "" ""))]
1040*404b540aSrobert  ""
1041*404b540aSrobert  "
1042*404b540aSrobert{
1043*404b540aSrobert  mt_emit_cbranch (NE, operands[0], mt_compare_op0, mt_compare_op1);
1044*404b540aSrobert  DONE;
1045*404b540aSrobert}")
1046*404b540aSrobert
1047*404b540aSrobert(define_expand "bge"
1048*404b540aSrobert  [(use (match_operand 0 "" ""))]
1049*404b540aSrobert  ""
1050*404b540aSrobert  "
1051*404b540aSrobert{
1052*404b540aSrobert  mt_emit_cbranch (GE, operands[0], mt_compare_op0, mt_compare_op1);
1053*404b540aSrobert  DONE;
1054*404b540aSrobert}")
1055*404b540aSrobert
1056*404b540aSrobert(define_expand "bgt"
1057*404b540aSrobert  [(use (match_operand 0 "" ""))]
1058*404b540aSrobert  ""
1059*404b540aSrobert  "
1060*404b540aSrobert{
1061*404b540aSrobert  mt_emit_cbranch (GT, operands[0], mt_compare_op0, mt_compare_op1);
1062*404b540aSrobert  DONE;
1063*404b540aSrobert}")
1064*404b540aSrobert
1065*404b540aSrobert(define_expand "ble"
1066*404b540aSrobert  [(use (match_operand 0 "" ""))]
1067*404b540aSrobert  ""
1068*404b540aSrobert  "
1069*404b540aSrobert{
1070*404b540aSrobert  mt_emit_cbranch (LE, operands[0], mt_compare_op0, mt_compare_op1);
1071*404b540aSrobert  DONE;
1072*404b540aSrobert}")
1073*404b540aSrobert
1074*404b540aSrobert(define_expand "blt"
1075*404b540aSrobert  [(use (match_operand 0 "" ""))]
1076*404b540aSrobert  ""
1077*404b540aSrobert  "
1078*404b540aSrobert{
1079*404b540aSrobert  mt_emit_cbranch (LT, operands[0], mt_compare_op0, mt_compare_op1);
1080*404b540aSrobert  DONE;
1081*404b540aSrobert}")
1082*404b540aSrobert
1083*404b540aSrobert(define_expand "bgeu"
1084*404b540aSrobert  [(use (match_operand 0 "" ""))]
1085*404b540aSrobert  ""
1086*404b540aSrobert  "
1087*404b540aSrobert{
1088*404b540aSrobert  mt_emit_cbranch (GEU, operands[0], mt_compare_op0, mt_compare_op1);
1089*404b540aSrobert  DONE;
1090*404b540aSrobert}")
1091*404b540aSrobert
1092*404b540aSrobert(define_expand "bgtu"
1093*404b540aSrobert  [(use (match_operand 0 "" ""))]
1094*404b540aSrobert  ""
1095*404b540aSrobert  "
1096*404b540aSrobert{
1097*404b540aSrobert  mt_emit_cbranch (GTU, operands[0], mt_compare_op0, mt_compare_op1);
1098*404b540aSrobert  DONE;
1099*404b540aSrobert}")
1100*404b540aSrobert
1101*404b540aSrobert(define_expand "bleu"
1102*404b540aSrobert  [(use (match_operand 0 "" ""))]
1103*404b540aSrobert  ""
1104*404b540aSrobert  "
1105*404b540aSrobert{
1106*404b540aSrobert  mt_emit_cbranch (LEU, operands[0], mt_compare_op0, mt_compare_op1);
1107*404b540aSrobert  DONE;
1108*404b540aSrobert}")
1109*404b540aSrobert
1110*404b540aSrobert(define_expand "bltu"
1111*404b540aSrobert  [(use (match_operand 0 "" ""))]
1112*404b540aSrobert  ""
1113*404b540aSrobert  "
1114*404b540aSrobert{
1115*404b540aSrobert  mt_emit_cbranch (LTU, operands[0], mt_compare_op0, mt_compare_op1);
1116*404b540aSrobert  DONE;
1117*404b540aSrobert}")
1118*404b540aSrobert
1119*404b540aSrobert(define_expand "bunge"
1120*404b540aSrobert  [(use (match_operand 0 "" ""))]
1121*404b540aSrobert  ""
1122*404b540aSrobert  "
1123*404b540aSrobert{
1124*404b540aSrobert  mt_emit_cbranch (GEU, operands[0], mt_compare_op0, mt_compare_op1);
1125*404b540aSrobert  DONE;
1126*404b540aSrobert}")
1127*404b540aSrobert
1128*404b540aSrobert(define_expand "bungt"
1129*404b540aSrobert  [(use (match_operand 0 "" ""))]
1130*404b540aSrobert  ""
1131*404b540aSrobert  "
1132*404b540aSrobert{
1133*404b540aSrobert  mt_emit_cbranch (GTU, operands[0], mt_compare_op0, mt_compare_op1);
1134*404b540aSrobert  DONE;
1135*404b540aSrobert}")
1136*404b540aSrobert
1137*404b540aSrobert(define_expand "bunle"
1138*404b540aSrobert  [(use (match_operand 0 "" ""))]
1139*404b540aSrobert  ""
1140*404b540aSrobert  "
1141*404b540aSrobert{
1142*404b540aSrobert  mt_emit_cbranch (LEU, operands[0], mt_compare_op0, mt_compare_op1);
1143*404b540aSrobert  DONE;
1144*404b540aSrobert}")
1145*404b540aSrobert
1146*404b540aSrobert(define_expand "bunlt"
1147*404b540aSrobert  [(use (match_operand 0 "" ""))]
1148*404b540aSrobert  ""
1149*404b540aSrobert  "
1150*404b540aSrobert{
1151*404b540aSrobert  mt_emit_cbranch (LTU, operands[0], mt_compare_op0, mt_compare_op1);
1152*404b540aSrobert  DONE;
1153*404b540aSrobert}")
1154*404b540aSrobert
1155*404b540aSrobert(define_insn "*beq_true"
1156*404b540aSrobert  [(set (pc)
1157*404b540aSrobert	(if_then_else (eq (match_operand:SI 0 "reg_or_0_operand" "rJ")
1158*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1159*404b540aSrobert		      (label_ref (match_operand 2 "" ""))
1160*404b540aSrobert		      (pc)))]
1161*404b540aSrobert  ""
1162*404b540aSrobert  "breq %z0, %z1, %l2%#"
1163*404b540aSrobert  [(set_attr "length" "4")
1164*404b540aSrobert   (set_attr "type" "branch")])
1165*404b540aSrobert
1166*404b540aSrobert(define_insn "*beq_false"
1167*404b540aSrobert  [(set (pc)
1168*404b540aSrobert	(if_then_else (eq (match_operand:SI 0 "reg_or_0_operand" "rJ")
1169*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1170*404b540aSrobert		      (pc)
1171*404b540aSrobert		      (label_ref (match_operand 2 "" ""))))]
1172*404b540aSrobert  ""
1173*404b540aSrobert  "brne %z0, %z1, %l2%#"
1174*404b540aSrobert  [(set_attr "length" "4")
1175*404b540aSrobert   (set_attr "type" "branch")])
1176*404b540aSrobert
1177*404b540aSrobert
1178*404b540aSrobert(define_insn "*bne_true"
1179*404b540aSrobert  [(set (pc)
1180*404b540aSrobert	(if_then_else (ne (match_operand:SI 0 "reg_or_0_operand" "rJ")
1181*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1182*404b540aSrobert		      (label_ref (match_operand 2 "" ""))
1183*404b540aSrobert		      (pc)))]
1184*404b540aSrobert  ""
1185*404b540aSrobert  "brne %z0, %z1, %l2%#"
1186*404b540aSrobert  [(set_attr "length" "4")
1187*404b540aSrobert   (set_attr "type" "branch")])
1188*404b540aSrobert
1189*404b540aSrobert(define_insn "*bne_false"
1190*404b540aSrobert  [(set (pc)
1191*404b540aSrobert	(if_then_else (ne (match_operand:SI 0 "reg_or_0_operand" "rJ")
1192*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1193*404b540aSrobert		      (pc)
1194*404b540aSrobert		      (label_ref (match_operand 2 "" ""))))]
1195*404b540aSrobert  ""
1196*404b540aSrobert  "breq %z0, %z1, %l2%#"
1197*404b540aSrobert  [(set_attr "length" "4")
1198*404b540aSrobert   (set_attr "type" "branch")])
1199*404b540aSrobert
1200*404b540aSrobert(define_insn "*blt_true"
1201*404b540aSrobert  [(set (pc)
1202*404b540aSrobert	(if_then_else (lt (match_operand:SI 0 "reg_or_0_operand" "rJ")
1203*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1204*404b540aSrobert		      (label_ref (match_operand 2 "" ""))
1205*404b540aSrobert		      (pc)))]
1206*404b540aSrobert  ""
1207*404b540aSrobert  "brlt %z0, %z1, %l2%#"
1208*404b540aSrobert  [(set_attr "length" "4")
1209*404b540aSrobert   (set_attr "type" "branch")])
1210*404b540aSrobert
1211*404b540aSrobert(define_insn "*blt_false"
1212*404b540aSrobert  [(set (pc)
1213*404b540aSrobert	(if_then_else (lt (match_operand:SI 0 "reg_or_0_operand" "rJ")
1214*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1215*404b540aSrobert		      (pc)
1216*404b540aSrobert		      (label_ref (match_operand 2 "" ""))))]
1217*404b540aSrobert  ""
1218*404b540aSrobert  "brle %z1, %z0,%l2%#"
1219*404b540aSrobert  [(set_attr "length" "4")
1220*404b540aSrobert   (set_attr "type" "branch")])
1221*404b540aSrobert
1222*404b540aSrobert(define_insn "*ble_true"
1223*404b540aSrobert  [(set (pc)
1224*404b540aSrobert	(if_then_else (le (match_operand:SI 0 "reg_or_0_operand" "rJ")
1225*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1226*404b540aSrobert		      (label_ref (match_operand 2 "" ""))
1227*404b540aSrobert		      (pc)))]
1228*404b540aSrobert  ""
1229*404b540aSrobert  "brle %z0, %z1, %l2%#"
1230*404b540aSrobert  [(set_attr "length" "4")
1231*404b540aSrobert   (set_attr "type" "branch")])
1232*404b540aSrobert
1233*404b540aSrobert(define_insn "*ble_false"
1234*404b540aSrobert  [(set (pc)
1235*404b540aSrobert	(if_then_else (le (match_operand:SI 0 "reg_or_0_operand" "rJ")
1236*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1237*404b540aSrobert		      (pc)
1238*404b540aSrobert		      (label_ref (match_operand 2 "" ""))))]
1239*404b540aSrobert  ""
1240*404b540aSrobert  "brlt %z1, %z0,%l2%#"
1241*404b540aSrobert  [(set_attr "length" "4")
1242*404b540aSrobert   (set_attr "type" "branch")])
1243*404b540aSrobert
1244*404b540aSrobert(define_insn "*bgt_true"
1245*404b540aSrobert  [(set (pc)
1246*404b540aSrobert	(if_then_else (gt (match_operand:SI 0 "reg_or_0_operand" "rJ")
1247*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1248*404b540aSrobert		      (label_ref (match_operand 2 "" ""))
1249*404b540aSrobert		      (pc)))]
1250*404b540aSrobert  ""
1251*404b540aSrobert  "brlt %z1, %z0, %l2%#"
1252*404b540aSrobert  [(set_attr "length" "4")
1253*404b540aSrobert   (set_attr "type" "branch")])
1254*404b540aSrobert
1255*404b540aSrobert(define_insn "*bgt_false"
1256*404b540aSrobert  [(set (pc)
1257*404b540aSrobert	(if_then_else (gt (match_operand:SI 0 "reg_or_0_operand" "rJ")
1258*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1259*404b540aSrobert		      (pc)
1260*404b540aSrobert		      (label_ref (match_operand 2 "" ""))))]
1261*404b540aSrobert  ""
1262*404b540aSrobert  "brle %z0, %z1, %l2%#"
1263*404b540aSrobert  [(set_attr "length" "4")
1264*404b540aSrobert   (set_attr "type" "branch")])
1265*404b540aSrobert
1266*404b540aSrobert(define_insn "*bge_true"
1267*404b540aSrobert  [(set (pc)
1268*404b540aSrobert	(if_then_else (ge (match_operand:SI 0 "reg_or_0_operand" "rJ")
1269*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1270*404b540aSrobert		      (label_ref (match_operand 2 "" ""))
1271*404b540aSrobert		      (pc)))]
1272*404b540aSrobert  ""
1273*404b540aSrobert  "brle %z1, %z0,%l2%#"
1274*404b540aSrobert  [(set_attr "length" "4")
1275*404b540aSrobert   (set_attr "type" "branch")])
1276*404b540aSrobert
1277*404b540aSrobert(define_insn "*bge_false"
1278*404b540aSrobert  [(set (pc)
1279*404b540aSrobert	(if_then_else (ge (match_operand:SI 0 "reg_or_0_operand" "rJ")
1280*404b540aSrobert			  (match_operand:SI 1 "reg_or_0_operand" "rJ"))
1281*404b540aSrobert		      (pc)
1282*404b540aSrobert		      (label_ref (match_operand 2 "" ""))))]
1283*404b540aSrobert  ""
1284*404b540aSrobert  "brlt %z0, %z1, %l2%#"
1285*404b540aSrobert  [(set_attr "length" "4")
1286*404b540aSrobert   (set_attr "type" "branch")])
1287*404b540aSrobert
1288*404b540aSrobert;; No unsigned operators on Morpho mt.  All the unsigned operations are
1289*404b540aSrobert;; converted to the signed operations above.
1290*404b540aSrobert
1291*404b540aSrobert
1292*404b540aSrobert;; Set flag operations
1293*404b540aSrobert
1294*404b540aSrobert;; "seq", "sne", "slt", "sle", "sgt", "sge", "sltu", "sleu",
1295*404b540aSrobert;; "sgtu", and "sgeu" don't exist as regular instruction on the
1296*404b540aSrobert;; mt, so these are not defined
1297*404b540aSrobert
1298*404b540aSrobert;; Call and branch instructions
1299*404b540aSrobert
1300*404b540aSrobert(define_expand "call"
1301*404b540aSrobert  [(parallel [(call (mem:SI (match_operand:SI 0 "register_operand" ""))
1302*404b540aSrobert			    (match_operand 1 "" ""))
1303*404b540aSrobert	      (clobber (reg:SI 14))])]
1304*404b540aSrobert  ""
1305*404b540aSrobert  "
1306*404b540aSrobert{
1307*404b540aSrobert    operands[0] = force_reg (SImode, XEXP (operands[0], 0));
1308*404b540aSrobert}")
1309*404b540aSrobert
1310*404b540aSrobert(define_insn "call_internal"
1311*404b540aSrobert  [(call (mem:SI (match_operand 0 "register_operand" "r"))
1312*404b540aSrobert	 (match_operand 1 "" ""))
1313*404b540aSrobert   ;; possibly add a clobber of the reg that gets the return address
1314*404b540aSrobert   (clobber (reg:SI 14))]
1315*404b540aSrobert  ""
1316*404b540aSrobert  "jal r14, %0%#"
1317*404b540aSrobert  [(set_attr "length" "4")
1318*404b540aSrobert   (set_attr "type" "call")])
1319*404b540aSrobert
1320*404b540aSrobert(define_expand "call_value"
1321*404b540aSrobert  [(parallel [(set (match_operand 0 "register_operand" "")
1322*404b540aSrobert		   (call (mem:SI (match_operand:SI 1 "register_operand" ""))
1323*404b540aSrobert				 (match_operand 2 "general_operand" "")))
1324*404b540aSrobert	      (clobber (reg:SI 14))])]
1325*404b540aSrobert  ""
1326*404b540aSrobert  "
1327*404b540aSrobert{
1328*404b540aSrobert    operands[1] = force_reg (SImode, XEXP (operands[1], 0));
1329*404b540aSrobert}")
1330*404b540aSrobert
1331*404b540aSrobert
1332*404b540aSrobert(define_insn "call_value_internal"
1333*404b540aSrobert  [(set (match_operand 0 "register_operand" "=r")
1334*404b540aSrobert	(call (mem:SI (match_operand 1 "register_operand" "r"))
1335*404b540aSrobert	      (match_operand 2 "" "")))
1336*404b540aSrobert	;; possibly add a clobber of the reg that gets the return address
1337*404b540aSrobert	(clobber (reg:SI 14))]
1338*404b540aSrobert  ""
1339*404b540aSrobert  "jal r14, %1%#"
1340*404b540aSrobert  [(set_attr "length" "4")
1341*404b540aSrobert   (set_attr "type" "call")])
1342*404b540aSrobert
1343*404b540aSrobert;; Subroutine return
1344*404b540aSrobert(define_insn "return_internal"
1345*404b540aSrobert  [(const_int 2)
1346*404b540aSrobert   (return)
1347*404b540aSrobert   (use (reg:SI 14))]
1348*404b540aSrobert  ""
1349*404b540aSrobert  "jal r0, r14%#"
1350*404b540aSrobert  [(set_attr "length" "4")
1351*404b540aSrobert   (set_attr "type" "call")])
1352*404b540aSrobert
1353*404b540aSrobert;; Interrupt return
1354*404b540aSrobert(define_insn "return_interrupt_internal"
1355*404b540aSrobert  [(const_int 3)
1356*404b540aSrobert   (return)
1357*404b540aSrobert   (use (reg:SI 15))]
1358*404b540aSrobert  ""
1359*404b540aSrobert  "reti r15%#"
1360*404b540aSrobert  [(set_attr "length" "4")
1361*404b540aSrobert   (set_attr "type" "call")])
1362*404b540aSrobert
1363*404b540aSrobert;; Subroutine return
1364*404b540aSrobert(define_insn "eh_return_internal"
1365*404b540aSrobert  [(return)
1366*404b540aSrobert   (use (reg:SI 7))
1367*404b540aSrobert   (use (reg:SI 8))
1368*404b540aSrobert   (use (reg:SI 11))
1369*404b540aSrobert   (use (reg:SI 10))]
1370*404b540aSrobert  ""
1371*404b540aSrobert  "jal r0, r11%#"
1372*404b540aSrobert  [(set_attr "length" "4")
1373*404b540aSrobert   (set_attr "type" "call")])
1374*404b540aSrobert
1375*404b540aSrobert
1376*404b540aSrobert;; Normal unconditional jump
1377*404b540aSrobert(define_insn "jump"
1378*404b540aSrobert  [(set (pc) (label_ref (match_operand 0 "" "")))]
1379*404b540aSrobert  ""
1380*404b540aSrobert  "jmp %l0%#"
1381*404b540aSrobert  [(set_attr "length" "4")
1382*404b540aSrobert   (set_attr "type" "branch")])
1383*404b540aSrobert
1384*404b540aSrobert;; Indirect jump through a register
1385*404b540aSrobert(define_insn "indirect_jump"
1386*404b540aSrobert  [(set (pc) (match_operand 0 "register_operand" "r"))]
1387*404b540aSrobert  ""
1388*404b540aSrobert  "jal r0,%0%#"
1389*404b540aSrobert  [(set_attr "length" "4")
1390*404b540aSrobert   (set_attr "type" "call")])
1391*404b540aSrobert
1392*404b540aSrobert(define_insn "tablejump"
1393*404b540aSrobert  [(set (pc) (match_operand:SI 0 "register_operand" "r"))
1394*404b540aSrobert   (use (label_ref (match_operand 1 "" "")))]
1395*404b540aSrobert  ""
1396*404b540aSrobert  "jal r0, %0%#"
1397*404b540aSrobert  [(set_attr "length" "4")
1398*404b540aSrobert   (set_attr "type" "call")])
1399*404b540aSrobert
1400*404b540aSrobert
1401*404b540aSrobert(define_expand "prologue"
1402*404b540aSrobert  [(const_int 1)]
1403*404b540aSrobert  ""
1404*404b540aSrobert  "
1405*404b540aSrobert{
1406*404b540aSrobert  mt_expand_prologue ();
1407*404b540aSrobert  DONE;
1408*404b540aSrobert}")
1409*404b540aSrobert
1410*404b540aSrobert(define_expand "epilogue"
1411*404b540aSrobert  [(const_int 2)]
1412*404b540aSrobert  ""
1413*404b540aSrobert  "
1414*404b540aSrobert{
1415*404b540aSrobert  mt_expand_epilogue (NORMAL_EPILOGUE);
1416*404b540aSrobert  DONE;
1417*404b540aSrobert}")
1418*404b540aSrobert
1419*404b540aSrobert
1420*404b540aSrobert(define_expand "eh_return"
1421*404b540aSrobert  [(use (match_operand:SI 0 "register_operand" "r"))]
1422*404b540aSrobert  ""
1423*404b540aSrobert  "
1424*404b540aSrobert{
1425*404b540aSrobert  mt_expand_eh_return (operands);
1426*404b540aSrobert  DONE;
1427*404b540aSrobert}")
1428*404b540aSrobert
1429*404b540aSrobert
1430*404b540aSrobert(define_insn_and_split "eh_epilogue"
1431*404b540aSrobert  [(unspec [(match_operand 0 "register_operand" "r")] 6)]
1432*404b540aSrobert  ""
1433*404b540aSrobert  "#"
1434*404b540aSrobert  "reload_completed"
1435*404b540aSrobert  [(const_int 1)]
1436*404b540aSrobert  "mt_emit_eh_epilogue (operands); DONE;"
1437*404b540aSrobert)
1438*404b540aSrobert
1439*404b540aSrobert;; No operation, needed in case the user uses -g but not -O.
1440*404b540aSrobert(define_insn "nop"
1441*404b540aSrobert  [(const_int 0)]
1442*404b540aSrobert  ""
1443*404b540aSrobert  "nop"
1444*404b540aSrobert  [(set_attr "length" "4")
1445*404b540aSrobert   (set_attr "type" "arith")])
1446*404b540aSrobert
1447*404b540aSrobert;; ::::::::::::::::::::
1448*404b540aSrobert;; ::
1449*404b540aSrobert;; :: UNSPEC_VOLATILE usage
1450*404b540aSrobert;; ::
1451*404b540aSrobert;; ::::::::::::::::::::
1452*404b540aSrobert;;
1453*404b540aSrobert;;	0	blockage
1454*404b540aSrobert;;	1	Enable interrupts
1455*404b540aSrobert;;	2	Disable interrupts
1456*404b540aSrobert;;
1457*404b540aSrobert
1458*404b540aSrobert;; Pseudo instruction that prevents the scheduler from moving code above this
1459*404b540aSrobert;; point.
1460*404b540aSrobert(define_insn "blockage"
1461*404b540aSrobert  [(unspec_volatile [(const_int 0)] UNSPEC_BLOCKAGE)]
1462*404b540aSrobert  ""
1463*404b540aSrobert  ""
1464*404b540aSrobert  [(set_attr "length" "0")])
1465*404b540aSrobert
1466*404b540aSrobert;; Trap instruction to allow usage of the __builtin_trap function
1467*404b540aSrobert(define_insn "trap"
1468*404b540aSrobert  [(trap_if (const_int 1) (const_int 0))
1469*404b540aSrobert   (clobber (reg:SI 14))]
1470*404b540aSrobert  ""
1471*404b540aSrobert  "si	r14%#"
1472*404b540aSrobert  [(set_attr "length" "4")
1473*404b540aSrobert   (set_attr "type" "branch")])
1474*404b540aSrobert
1475*404b540aSrobert(define_expand "conditional_trap"
1476*404b540aSrobert  [(trap_if (match_operator 0 "comparison_operator"
1477*404b540aSrobert			    [(match_dup 2)
1478*404b540aSrobert			     (match_dup 3)])
1479*404b540aSrobert	    (match_operand 1 "const_int_operand" ""))]
1480*404b540aSrobert  ""
1481*404b540aSrobert  "
1482*404b540aSrobert{
1483*404b540aSrobert  operands[2] = mt_compare_op0;
1484*404b540aSrobert  operands[3] = mt_compare_op1;
1485*404b540aSrobert}")
1486*404b540aSrobert
1487*404b540aSrobert;; Templates to control handling of interrupts
1488*404b540aSrobert
1489*404b540aSrobert;; Enable interrupts template
1490*404b540aSrobert(define_insn "ei"
1491*404b540aSrobert  [(unspec_volatile [(const_int 0)] UNSPEC_EI)]
1492*404b540aSrobert  ""
1493*404b540aSrobert  "ei"
1494*404b540aSrobert  [(set_attr "length" "4")])
1495*404b540aSrobert
1496*404b540aSrobert;; Enable interrupts template
1497*404b540aSrobert(define_insn "di"
1498*404b540aSrobert  [(unspec_volatile [(const_int 0)] UNSPEC_DI)]
1499*404b540aSrobert  ""
1500*404b540aSrobert  "di"
1501*404b540aSrobert  [(set_attr "length" "4")])
1502