PR tree-optimization/84480 - bogus -Wstringop-truncation despite assignment with...
[official-gcc.git] / gcc / config / microblaze / microblaze.md
blobf698e541c23858c6c3ec7499e7584e8e44528e73
1 ;; microblaze.md -- Machine description for Xilinx MicroBlaze processors.
2 ;; Copyright (C) 2009-2018 Free Software Foundation, Inc.
4 ;; Contributed by Michael Eager <eager@eagercon.com>.
6 ;; This file is part of GCC.
8 ;; GCC is free software; you can redistribute it and/or modify
9 ;; it under the terms of the GNU General Public License as published by
10 ;; the Free Software Foundation; either version 3, or (at your option)
11 ;; any later version.
13 ;; GCC is distributed in the hope that it will be useful,
14 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
15 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16 ;; GNU General Public License for more details.
18 ;; You should have received a copy of the GNU General Public License
19 ;; along with GCC; see the file COPYING3.  If not see
20 ;; <http://www.gnu.org/licenses/>.  */
22 (include "constraints.md")
23 (include "predicates.md")
25 ;;----------------------------------------------------
26 ;; Constants
27 ;;----------------------------------------------------
28 (define_constants [
29   (R_SP        1)       ;; Stack pointer reg
30   (R_SR       15)       ;; Sub-routine return addr reg
31   (R_IR       14)       ;; Interrupt return addr reg
32   (R_DR       16)       ;; Debug trap return addr reg
33   (R_ER       17)       ;; Exception return addr reg
34   (R_TMP      18)       ;; Assembler temporary reg
35   (R_GOT      20)       ;; GOT ptr reg
36   (MB_PIPE_3   0)       ;; Microblaze 3-stage pipeline 
37   (MB_PIPE_5   1)       ;; Microblaze 5-stage pipeline 
38   (UNSPEC_SET_GOT       101)    ;;
39   (UNSPEC_GOTOFF        102)    ;; GOT offset
40   (UNSPEC_PLT           103)    ;; jump table
41   (UNSPEC_CMP           104)    ;; signed compare
42   (UNSPEC_CMPU          105)    ;; unsigned compare
43   (UNSPEC_TLS           106)    ;; jump table
46 (define_c_enum "unspec" [
47   UNSPEC_IPREFETCH
50 ;;----------------------------------------------------
51 ;; Instruction Attributes
52 ;;----------------------------------------------------
54 ;; Classification of each insn.
55 ;; branch       conditional branch
56 ;; jump         unconditional jump
57 ;; call         unconditional call
58 ;; load         load instruction(s)
59 ;; store        store instruction(s)
60 ;; move         data movement within same register set
61 ;; arith        integer arithmetic instruction
62 ;; darith       double precision integer arithmetic instructions
63 ;; imul         integer multiply
64 ;; idiv         integer divide
65 ;; icmp         integer compare
66 ;; Xfadd                floating point add/subtract
67 ;; Xfmul                floating point multiply
68 ;; Xfmadd       floating point multiply-add
69 ;; Xfdiv                floating point divide
70 ;; Xfabs                floating point absolute value
71 ;; Xfneg                floating point negation
72 ;; Xfcmp                floating point compare
73 ;; Xfcvt                floating point convert
74 ;; Xfsqrt       floating point square root
75 ;; multi        multiword sequence (or user asm statements)
76 ;; nop          no operation
77 ;; bshift       Shift operations
79 (define_attr "type"
80   "unknown,branch,jump,call,load,store,move,arith,darith,imul,idiv,icmp,multi,nop,no_delay_arith,no_delay_load,no_delay_store,no_delay_imul,no_delay_move,bshift,fadd,frsub,fmul,fdiv,fcmp,fsl,fsqrt,fcvt,trap"
81   (const_string "unknown"))
83 ;; Main data type used by the insn
84 (define_attr "mode" "unknown,none,QI,HI,SI,DI,SF,DF" (const_string "unknown"))
86 ;; # instructions (4 bytes each)
87 (define_attr "length" "" (const_int 4))
89 (define_code_iterator any_return [return simple_return])
91 ;; <optab> expands to the name of the optab for a particular code.
92 (define_code_attr optab [(return "return")
93                          (simple_return "simple_return")])
96 ;;----------------------------------------------------
97 ;; Attribute describing the processor.  
98 ;;----------------------------------------------------
100 ;; Describe a user's asm statement.
101 (define_asm_attributes
102   [(set_attr "type" "multi")])
104 ;; whether or not generating calls to position independent functions
105 (define_attr "abicalls" "no,yes"
106   (const (symbol_ref "microblaze_abicalls_attr")))
108 ;;----------------------------------------------------------------
109 ;; Microblaze DFA Pipeline description
110 ;;----------------------------------------------------------------
111                   
112 ;;-----------------------------------------------------------------
114    This is description of pipeline hazards based on DFA.  The
115    following constructions can be used for this:
117    o define_cpu_unit string [string]) describes a cpu functional unit
118      (separated by comma).
120      1st operand: Names of cpu function units.
121      2nd operand: Name of automaton (see comments for
122      DEFINE_AUTOMATON).
124      All define_reservations and define_cpu_units should have unique
125      names which can not be "nothing".
127    o (exclusion_set string string) means that each CPU function unit
128      in the first string can not be reserved simultaneously with each
129      unit whose name is in the second string and vise versa.  CPU
130      units in the string are separated by commas. For example, it is
131      useful for description CPU with fully pipelined floating point
132      functional unit which can execute simultaneously only single
133      floating point insns or only double floating point insns.
135    o (presence_set string string) means that each CPU function unit in
136      the first string can not be reserved unless at least one of units
137      whose names are in the second string is reserved.  This is an
138      asymmetric relation.  CPU units in the string are separated by
139      commas.  For example, it is useful for description that slot1 is
140      reserved after slot0 reservation for a VLIW processor.
142    o (absence_set string string) means that each CPU function unit in
143      the first string can not be reserved only if each unit whose name
144      is in the second string is not reserved.  This is an asymmetric
145      relation (actually exclusion set is analogous to this one but it
146      is symmetric).  CPU units in the string are separated by commas.
147      For example, it is useful for description that slot0 can not be
148      reserved after slot1 or slot2 reservation for a VLIW processor.
150    o (define_bypass number out_insn_names in_insn_names) names bypass with
151      given latency (the first number) from insns given by the first
152      string (see define_insn_reservation) into insns given by the
153      second string.  Insn names in the strings are separated by
154      commas.
156    o (define_automaton string) describes names of an automaton
157      generated and used for pipeline hazards recognition.  The names
158      are separated by comma.  Actually it is possibly to generate the
159      single automaton but unfortunately it can be very large.  If we
160      use more one automata, the summary size of the automata usually
161      is less than the single one.  The automaton name is used in
162      define_cpu_unit.  All automata should have unique names.
164    o (define_reservation string string) names reservation (the first
165      string) of cpu functional units (the 2nd string).  Sometimes unit
166      reservations for different insns contain common parts.  In such
167      case, you describe common part and use one its name (the 1st
168      parameter) in regular expression in define_insn_reservation.  All
169      define_reservations, define results and define_cpu_units should
170      have unique names which can not be "nothing".
172    o (define_insn_reservation name default_latency condition regexpr)
173      describes reservation of cpu functional units (the 3nd operand)
174      for instruction which is selected by the condition (the 2nd
175      parameter).  The first parameter is used for output of debugging
176      information.  The reservations are described by a regular
177      expression according the following syntax:
179        regexp = regexp "," oneof
180               | oneof
182        oneof = oneof "|" allof
183              | allof
185        allof = allof "+" repeat
186              | repeat
188        repeat = element "*" number
189               | element
191        element = cpu_function_name
192                | reservation_name
193                | result_name
194                | "nothing"
195                | "(" regexp ")"
197        1. "," is used for describing start of the next cycle in
198           reservation.
200        2. "|" is used for describing the reservation described by the
201           first regular expression *or* the reservation described by
202           the second regular expression *or* etc.
204        3. "+" is used for describing the reservation described by the
205           first regular expression *and* the reservation described by
206           the second regular expression *and* etc.
208        4. "*" is used for convenience and simply means sequence in
209           which the regular expression are repeated NUMBER times with
210           cycle advancing (see ",").
212        5. cpu function unit name which means reservation.
214        6. reservation name -- see define_reservation.
216        7. string "nothing" means no units reservation.
219 ;;-----------------------------------------------------------------
222 ;;----------------------------------------------------------------
223 ;; Microblaze 5-stage pipeline description (v5.00.a and later)
224 ;;----------------------------------------------------------------                 
225                     
226 (define_automaton   "mbpipe_5")
227 (define_cpu_unit    "mb_issue,mb_iu,mb_wb,mb_fpu,mb_fpu_2,mb_mul,mb_mul_2,mb_div,mb_div_2,mb_bs,mb_bs_2" "mbpipe_5")
229 (define_insn_reservation "mb-integer" 1 
230   (and (eq_attr "type" "branch,jump,call,arith,darith,icmp,nop,no_delay_arith")
231        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
232   "mb_issue,mb_iu,mb_wb")
234 (define_insn_reservation "mb-special-move" 2
235   (and (eq_attr "type" "move")
236        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
237   "mb_issue,mb_iu*2,mb_wb")
239 (define_insn_reservation "mb-mem-load" 3
240   (and (eq_attr "type" "load,no_delay_load")
241        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
242   "mb_issue,mb_iu,mb_wb")
244 (define_insn_reservation "mb-mem-store" 1
245   (and (eq_attr "type" "store,no_delay_store")
246        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
247   "mb_issue,mb_iu,mb_wb")
249 (define_insn_reservation "mb-mul" 3
250   (and (eq_attr "type" "imul,no_delay_imul")
251        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
252   "mb_issue,mb_mul,mb_mul_2*2,mb_wb")
254 (define_insn_reservation "mb-div" 34            
255   (and (eq_attr "type" "idiv")
256        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
257     "mb_issue,mb_div,mb_div_2*33,mb_wb")
259 (define_insn_reservation "mb-bs" 2 
260   (and (eq_attr "type" "bshift")
261        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
262    "mb_issue,mb_bs,mb_bs_2,mb_wb")
264 (define_insn_reservation "mb-fpu-add-sub-mul" 6
265   (and (eq_attr "type" "fadd,frsub,fmul")
266        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
267   "mb_issue,mb_fpu,mb_fpu_2*5,mb_wb")
269 (define_insn_reservation "mb-fpu-fcmp" 3
270   (and (eq_attr "type" "fcmp")
271        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
272   "mb_issue,mb_fpu,mb_fpu*2,mb_wb")
274 (define_insn_reservation "mb-fpu-div" 30
275   (and (eq_attr "type" "fdiv")
276        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
277   "mb_issue,mb_fpu,mb_fpu_2*29,mb_wb")
279 (define_insn_reservation "mb-fpu-sqrt" 30
280   (and (eq_attr "type" "fsqrt")
281        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
282   "mb_issue,mb_fpu,mb_fpu_2*29,mb_wb")
284 (define_insn_reservation "mb-fpu-fcvt" 4
285   (and (eq_attr "type" "fcvt")
286        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_5)))
287   "mb_issue,mb_fpu,mb_fpu_2*3,mb_wb")
289 ;;----------------------------------------------------------------
290 ;; Microblaze 3-stage pipeline description (for v4.00.a and earlier)
291 ;;----------------------------------------------------------------
293 (define_automaton   "mbpipe_3")
294 (define_cpu_unit    "mb3_iu" "mbpipe_3")
296 (define_insn_reservation "mb3-integer" 1 
297   (and (eq_attr "type" "branch,jump,call,arith,darith,icmp,nop,no_delay_arith")
298        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
299   "mb3_iu")
301 (define_insn_reservation "mb3-special-move" 2
302   (and (eq_attr "type" "move")
303        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
304   "mb3_iu*2")
306 (define_insn_reservation "mb3-mem-load" 2
307   (and (eq_attr "type" "load,no_delay_load")
308        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
309   "mb3_iu")
311 (define_insn_reservation "mb3-mem-store" 1
312   (and (eq_attr "type" "store,no_delay_store")
313        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
314   "mb3_iu")
316 (define_insn_reservation "mb3-mul" 3
317   (and (eq_attr "type" "imul,no_delay_imul")
318        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
319   "mb3_iu")
321 (define_insn_reservation "mb3-div" 34            
322   (and (eq_attr "type" "idiv")
323        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
324     "mb3_iu")
326 (define_insn_reservation "mb3-bs" 2 
327   (and (eq_attr "type" "bshift")
328        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
329    "mb3_iu")
331 (define_insn_reservation "mb3-fpu-add-sub-mul" 6
332   (and (eq_attr "type" "fadd,frsub,fmul")
333        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
334   "mb3_iu")
336 (define_insn_reservation "mb3-fpu-fcmp" 3
337   (and (eq_attr "type" "fcmp")
338        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
339   "mb3_iu")
341 (define_insn_reservation "mb3-fpu-div" 30
342   (and (eq_attr "type" "fdiv")
343        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
344   "mb3_iu")
346 (define_insn_reservation "mb3-fpu-sqrt" 30
347   (and (eq_attr "type" "fsqrt")
348        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
349   "mb3_iu")
351 (define_insn_reservation "mb3-fpu-fcvt" 4
352   (and (eq_attr "type" "fcvt")
353        (eq (symbol_ref  "microblaze_pipe") (const_int MB_PIPE_3)))
354   "mb3_iu")
356 (automata_option "v")
357 (automata_option "time")
358 (automata_option "progress")
360 (define_insn "bswapsi2"
361   [(set (match_operand:SI 0 "register_operand" "=r")
362         (bswap:SI (match_operand:SI 1 "register_operand" "r")))]
363   "TARGET_REORDER"
364   "swapb %0, %1"
367 (define_insn "bswaphi2"
368   [(set (match_operand:HI 0 "register_operand" "=r")
369         (bswap:HI (match_operand:HI 1 "register_operand" "r")))]
370   "TARGET_REORDER"
371   "swapb %0, %1
372    swaph %0, %0"
375 ;;----------------------------------------------------------------
376 ;; Microblaze delay slot description
377 ;;----------------------------------------------------------------
378 (define_delay (eq_attr "type" "branch,call,jump")
379   [(and (eq_attr "type" "!branch,call,jump,icmp,multi,no_delay_arith,no_delay_load,no_delay_store,no_delay_imul,no_delay_move,darith") 
380         (ior (not (match_test "microblaze_no_unsafe_delay"))
381              (eq_attr "type" "!fadd,frsub,fmul,fdiv,fcmp,store,load")
382              ))
383   (nil) (nil)])
386 ;;----------------------------------------------------------------
387 ;; Microblaze FPU
388 ;;----------------------------------------------------------------
390 (define_insn "addsf3"
391   [(set (match_operand:SF 0 "register_operand" "=d")
392         (plus:SF (match_operand:SF 1 "register_operand" "d")
393                  (match_operand:SF 2 "register_operand" "d")))]
394   "TARGET_HARD_FLOAT"
395   "fadd\t%0,%1,%2"
396   [(set_attr "type"     "fadd")
397   (set_attr "mode"      "SF")
398   (set_attr "length"    "4")])
400 (define_insn "subsf3"
401   [(set (match_operand:SF 0 "register_operand" "=d")
402         (minus:SF (match_operand:SF 1 "register_operand" "d")
403                   (match_operand:SF 2 "register_operand" "d")))]
404   "TARGET_HARD_FLOAT"
405   "frsub\t%0,%2,%1"
406   [(set_attr "type"     "frsub")
407   (set_attr "mode"      "SF")
408   (set_attr "length"    "4")])
410 (define_insn "mulsf3"
411   [(set (match_operand:SF 0 "register_operand" "=d")
412         (mult:SF (match_operand:SF 1 "register_operand" "d")
413                  (match_operand:SF 2 "register_operand" "d")))]
414   "TARGET_HARD_FLOAT"
415   "fmul\t%0,%1,%2"
416   [(set_attr "type"     "fmul")
417   (set_attr "mode"      "SF")
418   (set_attr "length"    "4")])
421 (define_insn "divsf3"
422   [(set (match_operand:SF 0 "register_operand" "=d")
423         (div:SF (match_operand:SF 1 "register_operand" "d")
424                 (match_operand:SF 2 "register_operand" "d")))]
425   "TARGET_HARD_FLOAT"
426   "fdiv\t%0,%2,%1"
427   [(set_attr "type"     "fdiv")
428   (set_attr "mode"      "SF")
429   (set_attr "length"    "4")])
431 (define_insn "sqrtsf2"
432   [(set (match_operand:SF 0 "register_operand" "=d")
433         (sqrt:SF (match_operand:SF 1 "register_operand" "d")))]
434   "TARGET_HARD_FLOAT && TARGET_FLOAT_SQRT"
435   "fsqrt\t%0,%1"
436   [(set_attr "type"     "fsqrt")
437   (set_attr "mode"      "SF")
438   (set_attr "length"    "4")])
440 (define_insn "floatsisf2"
441   [(set (match_operand:SF 0 "register_operand" "=d")
442         (float:SF (match_operand:SI 1 "register_operand" "d")))]
443   "TARGET_HARD_FLOAT && TARGET_FLOAT_CONVERT"
444   "flt\t%0,%1"
445   [(set_attr "type"     "fcvt")
446   (set_attr "mode"      "SF")
447   (set_attr "length"    "4")])
449 (define_insn "fix_truncsfsi2"
450   [(set (match_operand:SI 0 "register_operand" "=d")
451         (fix:SI (match_operand:SF 1 "register_operand" "d")))]
452   "TARGET_HARD_FLOAT && TARGET_FLOAT_CONVERT"
453   "fint\t%0,%1"
454   [(set_attr "type"     "fcvt")
455   (set_attr "mode"      "SF")
456   (set_attr "length"    "4")])
458 ;;----------------------------------------------------------------
459 ;; Add
460 ;;----------------------------------------------------------------
462 ;; Add 2 SImode integers [ src1 = reg ; src2 = arith ; dest = reg ]
463 ;; Leave carry as is
464 (define_insn "addsi3"
465   [(set (match_operand:SI 0 "register_operand" "=d,d,d")
466         (plus:SI (match_operand:SI 1 "reg_or_0_operand" "%dJ,dJ,dJ")
467                  (match_operand:SI 2 "arith_plus_operand" "d,I,i")))]
468   ""
469   "@
470    addk\t%0,%z1,%2
471    addik\t%0,%z1,%2
472    addik\t%0,%z1,%2"
473   [(set_attr "type"     "arith,arith,no_delay_arith")
474   (set_attr "mode"      "SI,SI,SI")
475   (set_attr "length"    "4,4,8")])
477 ;;----------------------------------------------------------------
478 ;; Double Precision Additions
479 ;;----------------------------------------------------------------
481 ;; reg_DI_dest = reg_DI_src1 + DI_src2
483 ;; Adding 2 DI operands in register or reg/imm
485 (define_insn "adddi3"
486   [(set (match_operand:DI 0 "register_operand" "=d,d,d")
487         (plus:DI (match_operand:DI 1 "register_operand" "%d,d,d")
488                  (match_operand:DI 2 "arith_operand32" "d,P,N")))]
489   ""
490   "@
491   add\t%L0,%L1,%L2\;addc\t%M0,%M1,%M2
492   addi\t%L0,%L1,%2\;addc\t%M0,%M1,r0
493   addi\t%L0,%L1,%2\;addc\t%M0,%M1,r0\;addi\t%M0,%M0,-1"
494   [(set_attr "type"     "darith")
495   (set_attr "mode"      "DI")
496   (set_attr "length"    "8,8,12")])
498 ;;----------------------------------------------------------------
499 ;; Subtraction
500 ;;----------------------------------------------------------------
502 (define_insn "subsi3"
503   [(set (match_operand:SI 0 "register_operand" "=d,d")
504         (minus:SI (match_operand:SI 1 "arith_operand" "d,d")
505                   (match_operand:SI 2 "arith_operand" "d,n")))]
506   ""
507   "@
508    rsubk\t%0,%2,%z1
509    addik\t%0,%z1,-%2"
510   [(set_attr "type"     "arith,no_delay_arith")
511   (set_attr "mode"      "SI")
512   (set_attr "length"    "4,8")])
514 (define_insn "iprefetch"
515   [(unspec [(match_operand:SI 0 "const_int_operand" "n")] UNSPEC_IPREFETCH)
516    (clobber (mem:BLK (scratch)))]
517    "TARGET_PREFETCH"
518   {
519     operands[2] = gen_rtx_REG (SImode, MB_ABI_ASM_TEMP_REGNUM);
520     return "mfs\t%2,rpc\n\twic\t%2,r0";
521   }
522   [(set_attr "type" "arith")
523    (set_attr "mode"  "SI")
524    (set_attr "length"    "8")])
526 ;;----------------------------------------------------------------
527 ;; Double Precision Subtraction
528 ;;----------------------------------------------------------------
530 (define_insn "subdi3"
531   [(set (match_operand:DI 0 "register_operand" "=&d")
532         (minus:DI (match_operand:DI 1 "register_operand" "d")
533                   (match_operand:DI 2 "arith_operand32" "d")))]
534   ""
535   "rsub\t%L0,%L2,%L1\;rsubc\t%M0,%M2,%M1"
536   [(set_attr "type"     "darith")
537   (set_attr "mode"      "DI")
538   (set_attr "length"    "8")])
541 ;;----------------------------------------------------------------
542 ;; Multiplication
543 ;;----------------------------------------------------------------
545 (define_insn "mulsi3"
546   [(set (match_operand:SI 0 "register_operand" "=d,d,d")
547         (mult:SI (match_operand:SI 1 "register_operand" "d,d,d")
548                  (match_operand:SI 2 "arith_operand" "d,I,i")))]
549   "!TARGET_SOFT_MUL"
550   "@
551   mul\t%0,%1,%2
552   muli\t%0,%1,%2
553   muli\t%0,%1,%2"
554   [(set_attr "type"     "imul,imul,no_delay_imul")
555   (set_attr "mode"      "SI")
556   (set_attr "length"    "4,4,8")])
558 (define_insn "mulsidi3"
559   [(set (match_operand:DI 0 "register_operand" "=&d")
560         (mult:DI
561          (sign_extend:DI (match_operand:SI 1 "register_operand" "d"))
562          (sign_extend:DI (match_operand:SI 2 "register_operand" "d"))))]
563   "!TARGET_SOFT_MUL && TARGET_MULTIPLY_HIGH"
564   "mul\t%L0,%1,%2\;mulh\t%M0,%1,%2"
565   [(set_attr "type"     "no_delay_arith")
566    (set_attr "mode"     "DI")
567    (set_attr "length"   "8")])
569 (define_insn "umulsidi3"
570   [(set (match_operand:DI 0 "register_operand" "=&d")
571         (mult:DI
572          (zero_extend:DI (match_operand:SI 1 "register_operand" "d"))
573          (zero_extend:DI (match_operand:SI 2 "register_operand" "d"))))]
574   "!TARGET_SOFT_MUL && TARGET_MULTIPLY_HIGH"
575   "mul\t%L0,%1,%2\;mulhu\t%M0,%1,%2"
576   [(set_attr "type"     "no_delay_arith")
577    (set_attr "mode"     "DI")
578    (set_attr "length"   "8")])
580 (define_insn "usmulsidi3"
581   [(set (match_operand:DI 0 "register_operand" "=&d")
582         (mult:DI
583          (zero_extend:DI (match_operand:SI 1 "register_operand" "d"))
584          (sign_extend:DI (match_operand:SI 2 "register_operand" "d"))))]
585   "!TARGET_SOFT_MUL && TARGET_MULTIPLY_HIGH"
586   "mul\t%L0,%1,%2\;mulhsu\t%M0,%2,%1"
587   [(set_attr "type"     "no_delay_arith")
588    (set_attr "mode"     "DI")
589    (set_attr "length"   "8")])
591 (define_insn "*smulsi3_highpart"
592   [(set (match_operand:SI 0 "register_operand" "=d")
593         (truncate:SI
594          (lshiftrt:DI
595           (mult:DI (sign_extend:DI (match_operand:SI 1 "register_operand"  "d"))
596                    (sign_extend:DI (match_operand:SI 2 "register_operand"  "d")))
597           (const_int 32))))]
598   "!TARGET_SOFT_MUL && TARGET_MULTIPLY_HIGH"
599   "mulh\t%0,%1,%2"
600   [(set_attr "type"     "imul")
601   (set_attr "mode"      "SI")
602   (set_attr "length"    "4")])
604 (define_insn "*umulsi3_highpart"
605   [(set (match_operand:SI 0 "register_operand"                            "=d")
606         (truncate:SI
607          (lshiftrt:DI
608           (mult:DI (zero_extend:DI (match_operand:SI 1 "register_operand"  "d"))
609                    (zero_extend:DI (match_operand:SI 2 "register_operand"  "d"))
611           (const_int 32))))]
612   "!TARGET_SOFT_MUL && TARGET_MULTIPLY_HIGH"
613   "mulhu\t%0,%1,%2"
614   [(set_attr "type"     "imul")
615   (set_attr "mode"      "SI")
616   (set_attr "length"    "4")])
618 (define_insn "*usmulsi3_highpart"
619   [(set (match_operand:SI 0 "register_operand"                            "=d")
620         (truncate:SI
621          (lshiftrt:DI
622           (mult:DI (zero_extend:DI (match_operand:SI 1 "register_operand"  "d"))
623                    (sign_extend:DI (match_operand:SI 2 "register_operand"  "d"))
625           (const_int 32))))]
626   "!TARGET_SOFT_MUL && TARGET_MULTIPLY_HIGH"
627   "mulhsu\t%0,%2,%1"
628   [(set_attr "type"     "imul")
629   (set_attr "mode"      "SI")
630   (set_attr "length"    "4")])
633 ;;----------------------------------------------------------------
634 ;; Division and remainder
635 ;;----------------------------------------------------------------
636 (define_expand "divsi3"
637   [(set (match_operand:SI 0 "register_operand" "=d")
638         (div:SI (match_operand:SI 1 "register_operand" "d")
639                 (match_operand:SI 2 "register_operand" "d")))
640   ]
641   "(!TARGET_SOFT_DIV) || (TARGET_BARREL_SHIFT && TARGET_SMALL_DIVIDES)"
642   {
643     if (TARGET_SOFT_DIV && TARGET_BARREL_SHIFT && TARGET_SMALL_DIVIDES) 
644       { 
645         microblaze_expand_divide (operands);
646         DONE;
647       } 
648     else if (!TARGET_SOFT_DIV) 
649       {
650         emit_insn (gen_divsi3_internal (operands[0], operands[1], operands[2]));
651         DONE;
652       }
653   }     
657 (define_insn "divsi3_internal"
658   [(set (match_operand:SI 0 "register_operand" "=d")
659         (div:SI (match_operand:SI 1 "register_operand" "d")
660                 (match_operand:SI 2 "register_operand" "d")))
661   ]
662   "!TARGET_SOFT_DIV"
663   "idiv\t%0,%2,%1"
664   [(set_attr "type"     "idiv")
665   (set_attr "mode"      "SI")
666   (set_attr "length"    "4")]
669 (define_insn "udivsi3"
670   [(set (match_operand:SI 0 "register_operand" "=d")
671         (udiv:SI (match_operand:SI 1 "register_operand" "d")
672                  (match_operand:SI 2 "register_operand" "d")))
673   ]
674   "!TARGET_SOFT_DIV"
675   "idivu\t%0,%2,%1"
676   [(set_attr "type"     "idiv")
677   (set_attr "mode"      "SI")
678   (set_attr "length"    "4")])
680 (define_peephole2
681   [(set (match_operand:SI 0 "register_operand")
682         (fix:SI (match_operand:SF 1 "register_operand")))
683    (set (pc)
684         (if_then_else (match_operator 2 "ordered_comparison_operator"
685                        [(match_operand:SI 3 "register_operand")
686                         (match_operand:SI 4 "arith_operand")])
687                       (label_ref (match_operand 5))
688                       (pc)))]
689    "TARGET_HARD_FLOAT"
690    [(set (match_dup 1) (match_dup 3))]
692   {
693     rtx condition;
694     rtx cmp_op0 = operands[3];
695     rtx cmp_op1 = operands[4];
696     rtx comp_reg =  gen_rtx_REG (SImode, MB_ABI_ASM_TEMP_REGNUM);
698     emit_insn (gen_cstoresf4 (comp_reg, operands[2],
699                               gen_rtx_REG (SFmode, REGNO (cmp_op0)),
700                               gen_rtx_REG (SFmode, REGNO (cmp_op1))));
701     condition = gen_rtx_NE (SImode, comp_reg, const0_rtx);
702     emit_jump_insn (gen_condjump (condition, operands[5]));
703   }
706 ;;----------------------------------------------------------------
707 ;; Negation and one's complement
708 ;;----------------------------------------------------------------
710 (define_insn "negsi2"
711   [(set (match_operand:SI 0 "register_operand" "=d")
712         (neg:SI (match_operand:SI 1 "register_operand" "d")))]
713   ""
714   "rsubk\t%0,%1,r0"
715   [(set_attr "type"     "arith")
716   (set_attr "mode"      "SI")
717   (set_attr "length"    "4")])
719 (define_insn "negdi2"
720   [(set (match_operand:DI 0 "register_operand" "=d")
721         (neg:DI (match_operand:DI 1 "register_operand" "d")))]
722   ""
723   "rsub\t%L0,%L1,r0\;rsubc\t%M0,%M1,r0"
724   [(set_attr "type"     "darith")
725   (set_attr "mode"      "DI")
726   (set_attr "length"    "8")])
729 (define_insn "one_cmplsi2"
730   [(set (match_operand:SI 0 "register_operand" "=d")
731         (not:SI (match_operand:SI 1 "register_operand" "d")))]
732   ""
733   "xori\t%0,%1,-1"
734   [(set_attr "type"     "arith")
735   (set_attr "mode"      "SI")
736   (set_attr "length"    "4")])
738 (define_insn "*one_cmpldi2"
739   [(set (match_operand:DI 0 "register_operand" "=d")
740         (not:DI (match_operand:DI 1 "register_operand" "d")))]
741   ""
742   "nor\t%M0,r0,%M1\;nor\t%L0,r0,%L1"
743   [(set_attr "type"     "darith")
744   (set_attr "mode"      "DI")
745   (set_attr "length"    "8")]
748 (define_split
749   [(set (match_operand:DI 0 "register_operand" "")
750         (not:DI (match_operand:DI 1 "register_operand" "")))]
751   "reload_completed 
752    && GET_CODE (operands[0]) == REG && GP_REG_P (REGNO (operands[0]))
753    && GET_CODE (operands[1]) == REG && GP_REG_P (REGNO (operands[1]))"
755   [(set (subreg:SI (match_dup 0) 0) (not:SI (subreg:SI (match_dup 1) 0)))
756   (set (subreg:SI (match_dup 0) 4) (not:SI (subreg:SI (match_dup 1) 4)))]
757   "")
760 ;;----------------------------------------------------------------
761 ;; Logical
762 ;;----------------------------------------------------------------
764 (define_insn "andsi3"
765   [(set (match_operand:SI 0 "register_operand" "=d,d,d,d")
766         (and:SI (match_operand:SI 1 "arith_operand" "%d,d,d,d")
767                 (match_operand:SI 2 "arith_operand" "d,I,i,M")))]
768   ""
769   "@
770    and\t%0,%1,%2
771    andi\t%0,%1,%2 #and1
772    andi\t%0,%1,%2 #and2
773    andi\t%0,%1,%2 #and3"
774   [(set_attr "type"     "arith,arith,no_delay_arith,no_delay_arith")
775   (set_attr "mode"      "SI,SI,SI,SI")
776   (set_attr "length"    "4,8,8,8")])
779 (define_insn "iorsi3"
780   [(set (match_operand:SI 0 "register_operand" "=d,d,d,d")
781         (ior:SI (match_operand:SI 1 "arith_operand" "%d,d,d,d")
782                 (match_operand:SI 2 "arith_operand" "d,I,M,i")))]
783   ""
784   "@
785    or\t%0,%1,%2
786    ori\t%0,%1,%2
787    ori\t%0,%1,%2
788    ori\t%0,%1,%2" 
789   [(set_attr "type"     "arith,no_delay_arith,no_delay_arith,no_delay_arith")
790   (set_attr "mode"      "SI,SI,SI,SI")
791   (set_attr "length"    "4,8,8,8")])
793 (define_insn "xorsi3"
794   [(set (match_operand:SI 0 "register_operand" "=d,d,d")
795         (xor:SI (match_operand:SI 1 "arith_operand" "%d,d,d")
796                 (match_operand:SI 2 "arith_operand" "d,I,i")))]
797   ""
798   "@
799    xor\t%0,%1,%2
800    xori\t%0,%1,%2
801    xori\t%0,%1,%2"
802   [(set_attr "type"     "arith,arith,no_delay_arith")
803   (set_attr "mode"      "SI,SI,SI")
804   (set_attr "length"    "4,8,8")])
806 ;;----------------------------------------------------------------
807 ;; Zero extension
808 ;;----------------------------------------------------------------
810 (define_insn "zero_extendhisi2"
811   [(set (match_operand:SI 0 "register_operand" "=d,d,d")
812         (zero_extend:SI (match_operand:HI 1 "nonimmediate_operand" "d,R,m")))]
813   ""
814   "@
815   andi\t%0,%1,0xffff
816   lhu%i1\t%0,%1
817   lhu%i1\t%0,%1"
818   [(set_attr "type"     "no_delay_arith,load,no_delay_load")
819   (set_attr "mode"      "SI,SI,SI")
820   (set_attr "length"    "8,4,8")])
822 (define_insn "zero_extendqihi2"
823   [(set (match_operand:HI 0 "register_operand" "=d,d,d")
824         (zero_extend:HI (match_operand:QI 1 "nonimmediate_operand" "d,R,m")))]
825   ""
826   "@
827   andi\t%0,%1,0x00ff
828   lbu%i1\t%0,%1
829   lbu%i1\t%0,%1"
830   [(set_attr "type"     "arith,load,no_delay_load")
831   (set_attr "mode"      "HI")
832   (set_attr "length"    "4,4,8")])
833   
834 (define_insn "zero_extendqisi2"
835   [(set (match_operand:SI 0 "register_operand" "=d,d,d")
836         (zero_extend:SI (match_operand:QI 1 "nonimmediate_operand" "d,R,m")))]
837   ""
838   "@
839   andi\t%0,%1,0x00ff
840   lbu%i1\t%0,%1
841   lbu%i1\t%0,%1"
842   [(set_attr "type"     "arith,load,no_delay_load")
843   (set_attr "mode"      "SI,SI,SI")
844   (set_attr "length"    "4,4,8")])
846 ;;----------------------------------------------------------------
847 ;; Sign extension
848 ;;----------------------------------------------------------------
850 ;; basic Sign Extend Operations
852 (define_insn "extendqisi2"
853   [(set (match_operand:SI 0 "register_operand" "=d")
854         (sign_extend:SI (match_operand:QI 1 "register_operand" "d")))]
855   ""
856   "sext8\t%0,%1"
857   [(set_attr "type"     "arith")
858   (set_attr "mode"      "SI")
859   (set_attr "length"    "4")])
861 (define_insn "extendhisi2"
862   [(set (match_operand:SI 0 "register_operand" "=d")
863         (sign_extend:SI (match_operand:HI 1 "register_operand" "d")))]
864   ""
865   "sext16\t%0,%1"
866   [(set_attr "type"     "arith")
867   (set_attr "mode"      "SI")
868   (set_attr "length"    "4")])
870 ;; Those for integer source operand are ordered
871 ;; widest source type first.
873 (define_insn "extendsidi2"
874   [(set (match_operand:DI 0 "register_operand" "=d,d,d")
875         (sign_extend:DI (match_operand:SI 1 "nonimmediate_operand" "d,R,m")))]
876   ""
877   { 
878      if (which_alternative == 0)
879        output_asm_insn ("addk\t%L0,r0,%1", operands);
880      else
881        output_asm_insn ("lw%i1\t%L0,%1", operands);
883      output_asm_insn ("add\t%M0,%L0,%L0", operands);
884      output_asm_insn ("addc\t%M0,r0,r0", operands);
885      output_asm_insn ("beqi\t%M0,.+8", operands);
886      return "addi\t%M0,r0,0xffffffff";
887   }
888   [(set_attr "type"     "multi,multi,multi")
889   (set_attr "mode"      "DI")
890   (set_attr "length"    "20,20,20")])
892 ;;----------------------------------------------------------------
893 ;; Data movement
894 ;;----------------------------------------------------------------
896 ;; 64-bit integer moves
898 ;; Unlike most other insns, the move insns can't be split with
899 ;; different predicates, because register spilling and other parts of
900 ;; the compiler, have memoized the insn number already.
902 (define_expand "movdi"
903   [(set (match_operand:DI 0 "nonimmediate_operand" "")
904         (match_operand:DI 1 "general_operand" ""))]
905   ""
906   {
907     /* If operands[1] is a constant address illegal for pic, then we need to
908        handle it just like microblaze_legitimize_address does.  */
909     if (flag_pic && pic_address_needs_scratch (operands[1]))
910     {
911         rtx temp = force_reg (DImode, XEXP (XEXP (operands[1], 0), 0));
912         rtx temp2 = XEXP (XEXP (operands[1], 0), 1);
913         emit_move_insn (operands[0], gen_rtx_PLUS (DImode, temp, temp2));
914         DONE;
915     }
918     if ((reload_in_progress | reload_completed) == 0
919         && !register_operand (operands[0], DImode)
920         && !register_operand (operands[1], DImode)
921         && (((GET_CODE (operands[1]) != CONST_INT || INTVAL (operands[1]) != 0)
922                && operands[1] != CONST0_RTX (DImode))))
923     {
925       rtx temp = force_reg (DImode, operands[1]);
926       emit_move_insn (operands[0], temp);
927       DONE;
928     }
929   }
934 (define_insn "*movdi_internal"
935   [(set (match_operand:DI 0 "nonimmediate_operand" "=d,d,d,d,d,R,o")
936         (match_operand:DI 1 "general_operand"      " d,i,J,R,o,d,d"))]
937   ""
938   { 
939     switch (which_alternative)
940     {
941       case 0:
942         return "addk\t%0,%1\n\taddk\t%D0,%d1";
943       case 1:
944         return "addik\t%M0,r0,%h1\n\taddik\t%L0,r0,%j1 #li => la";
945       case 2:
946           return "addk\t%0,r0,r0\n\taddk\t%D0,r0,r0";
947       case 3:
948       case 4:
949         if (reg_mentioned_p (operands[0], operands[1]))
950           return "lwi\t%D0,%o1\n\tlwi\t%0,%1";
951         else
952           return "lwi\t%0,%1\n\tlwi\t%D0,%o1";
953       case 5:
954       case 6:
955         return "swi\t%1,%0\n\tswi\t%D1,%o0";
956     }
957     return "unreachable";
958   }
959   [(set_attr "type"     "no_delay_move,no_delay_arith,no_delay_arith,no_delay_load,no_delay_load,no_delay_store,no_delay_store")
960   (set_attr "mode"      "DI")
961   (set_attr "length"   "8,8,8,8,12,8,12")])
963 (define_split
964   [(set (match_operand:DI 0 "register_operand" "")
965         (match_operand:DI 1 "register_operand" ""))]
966   "reload_completed 
967    && GET_CODE (operands[0]) == REG && GP_REG_P (REGNO (operands[0]))
968    && GET_CODE (operands[1]) == REG && GP_REG_P (REGNO (operands[1])) 
969    && (REGNO(operands[0]) == (REGNO(operands[1]) + 1))"
971   [(set (subreg:SI (match_dup 0) 4) (subreg:SI (match_dup 1) 4))
972   (set (subreg:SI (match_dup 0) 0) (subreg:SI (match_dup 1) 0))]
973   "")
975 (define_split
976   [(set (match_operand:DI 0 "register_operand" "")
977         (match_operand:DI 1 "register_operand" ""))]
978   "reload_completed 
979    && GET_CODE (operands[0]) == REG && GP_REG_P (REGNO (operands[0]))
980    && GET_CODE (operands[1]) == REG && GP_REG_P (REGNO (operands[1])) 
981    && (REGNO (operands[0]) != (REGNO (operands[1]) + 1))"
983   [(set (subreg:SI (match_dup 0) 0) (subreg:SI (match_dup 1) 0))
984   (set (subreg:SI (match_dup 0) 4) (subreg:SI (match_dup 1) 4))]
985   "")
987 ;; Unlike most other insns, the move insns can't be split with
988 ;; different predicates, because register spilling and other parts of
989 ;; the compiler, have memoized the insn number already.
991 (define_expand "movsi"
992   [(set (match_operand:SI 0 "nonimmediate_operand" "")
993         (match_operand:SI 1 "general_operand" ""))]
994   ""
995   {
996     if (microblaze_expand_move (SImode, operands)) DONE;
997   }
1000 ;; Added for status registers
1001 (define_insn "movsi_status"
1002   [(set (match_operand:SI 0 "register_operand" "=d,d,z")
1003         (match_operand:SI 1 "register_operand" "z,d,d"))]
1004   "microblaze_is_interrupt_variant ()"
1005   "@
1006         mfs\t%0,%1  #mfs
1007         addk\t%0,%1,r0 #add movsi
1008         mts\t%0,%1  #mts"       
1009   [(set_attr "type" "move")
1010   (set_attr "mode" "SI")
1011   (set_attr "length" "12")])
1013 ;; This move will be not be moved to delay slot.        
1014 (define_insn "*movsi_internal3"
1015   [(set (match_operand:SI 0 "nonimmediate_operand" "=d,d,d")
1016         (match_operand:SI 1 "immediate_operand" "J,I,Mnis"))]
1017   "(register_operand (operands[0], SImode) && 
1018            (GET_CODE (operands[1]) == CONST_INT && 
1019                  (INTVAL (operands[1]) <= 32767 && INTVAL (operands[1]) >= -32768)))"  
1020   "@
1021    addk\t%0,r0,r0
1022    addik\t%0,r0,%1\t# %X1
1023    addik\t%0,r0,%1\t# %X1"
1024   [(set_attr "type"     "arith,arith,no_delay_arith")
1025   (set_attr "mode"      "SI")
1026   (set_attr "length"    "4")])
1028 ;; This move may be used for PLT label operand
1029 (define_insn "*movsi_internal5_pltop"
1030   [(set (match_operand:SI 0 "register_operand" "=d,d")
1031         (match_operand:SI 1 "call_insn_operand" ""))]
1032   "(register_operand (operands[0], Pmode) && 
1033            PLT_ADDR_P (operands[1]))"
1034   { 
1035      gcc_unreachable ();
1036   }
1037   [(set_attr "type"     "load")
1038   (set_attr "mode"      "SI")
1039   (set_attr "length"    "4")])
1041 (define_insn "*movsi_internal2"
1042   [(set (match_operand:SI 0 "nonimmediate_operand" "=d,d,d,   d,d,R,m")
1043         (match_operand:SI 1 "move_src_operand"         " d,I,Mnis,R,m,dJ,dJ"))]
1044   ""
1045   "@
1046    addk\t%0,%1,r0
1047    addik\t%0,r0,%1\t# %X1
1048    addik\t%0,%a1
1049    lw%i1\t%0,%1
1050    lw%i1\t%0,%1
1051    sw%i0\t%z1,%0
1052    sw%i0\t%z1,%0"
1053   [(set_attr "type"     "load,load,no_delay_load,load,no_delay_load,store,no_delay_store")
1054   (set_attr "mode"      "SI")
1055   (set_attr "length"    "4,4,8,4,8,4,8")])
1058 ;; 16-bit Integer moves
1060 ;; Unlike most other insns, the move insns can't be split with
1061 ;; different predicates, because register spilling and other parts of
1062 ;; the compiler, have memoized the insn number already.
1063 ;; Unsigned loads are used because BYTE_LOADS_ZERO_EXTEND is defined
1065 (define_expand "movhi"
1066   [(set (match_operand:HI 0 "nonimmediate_operand" "")
1067         (match_operand:HI 1 "general_operand" ""))]
1068   ""
1069   {
1070     if ((reload_in_progress | reload_completed) == 0
1071         && !register_operand (operands[0], HImode)
1072         && !register_operand (operands[1], HImode)
1073         && ((GET_CODE (operands[1]) != CONST_INT
1074             || INTVAL (operands[1]) != 0)))
1075     {
1076         rtx temp = force_reg (HImode, operands[1]);
1077         emit_move_insn (operands[0], temp);
1078         DONE;
1079     }
1080   }
1083 (define_insn "*movhi_internal2"
1084   [(set (match_operand:HI 0 "nonimmediate_operand" "=d,d,d,d,R,m")
1085         (match_operand:HI 1 "general_operand"       "I,d,R,m,dJ,dJ"))]
1086   ""
1087   "@
1088    addik\t%0,r0,%1\t# %X1
1089    addk\t%0,%1,r0
1090    lhui\t%0,%1
1091    lhui\t%0,%1
1092    sh%i0\t%z1,%0
1093    sh%i0\t%z1,%0"
1094   [(set_attr "type"     "arith,move,load,no_delay_load,store,no_delay_store")
1095   (set_attr "mode"      "HI")
1096   (set_attr "length"    "4,4,4,8,8,8")])
1098 ;; 8-bit Integer moves
1100 ;; Unlike most other insns, the move insns can't be split with
1101 ;; different predicates, because register spilling and other parts of
1102 ;; the compiler, have memoized the insn number already.
1103 ;; Unsigned loads are used because BYTE_LOADS_ZERO_EXTEND is defined
1105 (define_expand "movqi"
1106   [(set (match_operand:QI 0 "nonimmediate_operand" "")
1107         (match_operand:QI 1 "general_operand" ""))]
1108   ""
1109   {
1110     if ((reload_in_progress | reload_completed) == 0
1111         && !register_operand (operands[0], QImode)
1112         && !register_operand (operands[1], QImode)
1113         && ((GET_CODE (operands[1]) != CONST_INT
1114             || INTVAL (operands[1]) != 0)))
1115     {
1116         rtx temp = force_reg (QImode, operands[1]);
1117         emit_move_insn (operands[0], temp);
1118         DONE;
1119     }
1120   }
1123 (define_insn "*movqi_internal2"
1124   [(set (match_operand:QI 0 "nonimmediate_operand" "=d,d,d,d,d,R,m")
1125         (match_operand:QI 1 "general_operand"       "J,I,d,R,m,dJ,dJ"))]
1126   ""
1127   "@
1128    addk\t%0,r0,%z1
1129    addik\t%0,r0,%1\t# %X1
1130    addk\t%0,%1,r0
1131    lbu%i1\t%0,%1
1132    lbu%i1\t%0,%1
1133    sb%i0\t%z1,%0
1134    sbi\t%z1,%0"
1135   [(set_attr "type"     "arith,arith,move,load,no_delay_load,store,no_delay_store")
1136   (set_attr "mode"      "QI")
1137   (set_attr "length"    "4,4,8,4,8,4,8")])
1139 ;; Block moves, see microblaze.c for more details.
1140 ;; Argument 0 is the destination
1141 ;; Argument 1 is the source
1142 ;; Argument 2 is the length
1143 ;; Argument 3 is the alignment
1145 (define_expand "movmemsi"
1146   [(parallel [(set (match_operand:BLK 0 "general_operand")
1147                    (match_operand:BLK 1 "general_operand"))
1148               (use (match_operand:SI 2 ""))
1149               (use (match_operand:SI 3 "const_int_operand"))])]
1150   ""
1151   {
1152     if (microblaze_expand_block_move (operands[0], operands[1], 
1153                                       operands[2], operands[3]))
1154         DONE;
1155     else  
1156         FAIL;
1157   }
1160 ;;Load and store reverse
1161 (define_insn "movsi4_rev"
1162   [(set (match_operand:SI 0 "reg_or_mem_operand" "=r,Q")
1163         (bswap:SI (match_operand:SF 1 "reg_or_mem_operand" "Q,r")))]
1164   "TARGET_REORDER"
1165   "@
1166    lwr\t%0,%y1,r0
1167    swr\t%1,%y0,r0"
1168   [(set_attr "type"     "load,store")
1169   (set_attr "mode"      "SI")
1170   (set_attr "length"    "4,4")])
1172 ;; 32-bit floating point moves
1174 (define_expand "movsf"
1175   [(set (match_operand:SF 0 "nonimmediate_operand" "")
1176         (match_operand:SF 1 "general_operand" ""))]
1177   ""
1178   {
1179     if ((reload_in_progress | reload_completed) == 0
1180         && !register_operand (operands[0], SFmode)
1181         && !register_operand (operands[1], SFmode)
1182         && ( ((GET_CODE (operands[1]) != CONST_INT || INTVAL (operands[1]) != 0)
1183                  && operands[1] != CONST0_RTX (SFmode))))
1184     {
1185         rtx temp = force_reg (SFmode, operands[1]);
1186         emit_move_insn (operands[0], temp);
1187         DONE;
1188     }
1189   }
1192 ;; Applies to both TARGET_SOFT_FLOAT and TARGET_HARD_FLOAT
1194 (define_insn "*movsf_internal"
1195   [(set (match_operand:SF 0 "nonimmediate_operand" "=d,d,d,d,d,R,m")
1196         (match_operand:SF 1 "general_operand" "G,d,R,F,m,d,d"))]
1197   "(register_operand (operands[0], SFmode)
1198        || register_operand (operands[1], SFmode)
1199        || operands[1] == CONST0_RTX (SFmode))"
1200   "@
1201    addk\t%0,r0,r0
1202    addk\t%0,%1,r0
1203    lw%i1\t%0,%1
1204    addik\t%0,r0,%F1
1205    lw%i1\t%0,%1
1206    sw%i0\t%z1,%0
1207    swi\t%z1,%0"
1208   [(set_attr "type"     "move,no_delay_load,load,no_delay_load,no_delay_load,store,no_delay_store")
1209   (set_attr "mode"      "SF")
1210   (set_attr "length"    "4,4,4,4,4,4,4")])
1212 ;; 64-bit floating point moves
1213 (define_expand "movdf"
1214   [(set (match_operand:DF 0 "nonimmediate_operand" "")
1215         (match_operand:DF 1 "general_operand" ""))]
1216   ""
1217   {
1218     if (flag_pic == 2) {
1219       if (GET_CODE (operands[1]) == MEM 
1220           && !microblaze_legitimate_address_p (DFmode, XEXP (operands[1],0), 0))
1221       {
1222         rtx ptr_reg;
1223         rtx result;
1224         ptr_reg = force_reg (Pmode, XEXP (operands[1],0));
1225         result = gen_rtx_MEM (DFmode, ptr_reg);
1226         emit_move_insn (operands[0], result);
1227         DONE;
1228       }
1229     }
1230     if ((reload_in_progress | reload_completed) == 0
1231         && !register_operand (operands[0], DFmode)
1232         && !register_operand (operands[1], DFmode)
1233         && (((GET_CODE (operands[1]) != CONST_INT || INTVAL (operands[1]) != 0)
1234                  && operands[1] != CONST0_RTX (DFmode))))
1235     {
1236         rtx temp = force_reg (DFmode, operands[1]);
1237         emit_move_insn (operands[0], temp);
1238         DONE;
1239     }
1240   }
1243 ;; movdf_internal
1244 ;; Applies to both TARGET_SOFT_FLOAT and TARGET_HARD_FLOAT
1246 (define_insn "*movdf_internal"
1247   [(set (match_operand:DF 0 "nonimmediate_operand" "=d,d,d,d,o")
1248         (match_operand:DF 1 "general_operand" "dG,o,F,T,d"))]
1249   ""
1250   {
1251     switch (which_alternative)
1252     {
1253       case 0:
1254         return "addk\t%0,r0,r0\n\taddk\t%D0,r0,r0";
1255       case 1:
1256       case 3:
1257         if (reg_mentioned_p (operands[0], operands[1]))
1258           return "lwi\t%D0,%o1\n\tlwi\t%0,%1";
1259         else
1260           return "lwi\t%0,%1\n\tlwi\t%D0,%o1";
1261       case 2:
1262       {
1263         return "addik\t%0,r0,%h1 \n\taddik\t%D0,r0,%j1 #Xfer Lo";
1264       }
1265       case 4:
1266         return "swi\t%1,%0\n\tswi\t%D1,%o0";
1267     }
1268     gcc_unreachable ();
1269   }
1270   [(set_attr "type"     "no_delay_move,no_delay_load,no_delay_load,no_delay_load,no_delay_store")
1271   (set_attr "mode"      "DF")
1272   (set_attr "length"    "4,8,8,16,8")])
1274 (define_split
1275   [(set (match_operand:DF 0 "register_operand" "")
1276         (match_operand:DF 1 "register_operand" ""))]
1277   "reload_completed
1278    && GET_CODE (operands[0]) == REG && GP_REG_P (REGNO (operands[0]))
1279    && GET_CODE (operands[1]) == REG && GP_REG_P (REGNO (operands[1]))
1280    && (REGNO (operands[0]) == (REGNO (operands[1]) + 1))"
1281   [(set (subreg:SI (match_dup 0) 4) (subreg:SI (match_dup 1) 4))
1282   (set (subreg:SI (match_dup 0) 0) (subreg:SI (match_dup 1) 0))]
1283   "")
1285 (define_split
1286   [(set (match_operand:DF 0 "register_operand" "")
1287         (match_operand:DF 1 "register_operand" ""))]
1288   "reload_completed
1289    && GET_CODE (operands[0]) == REG && GP_REG_P (REGNO (operands[0]))
1290    && GET_CODE (operands[1]) == REG && GP_REG_P (REGNO (operands[1]))
1291    && (REGNO (operands[0]) != (REGNO (operands[1]) + 1))"
1292   [(set (subreg:SI (match_dup 0) 0) (subreg:SI (match_dup 1) 0))
1293   (set (subreg:SI (match_dup 0) 4) (subreg:SI (match_dup 1) 4))]
1294   "")
1296 ;;----------------------------------------------------------------
1297 ;; Shifts
1298 ;;----------------------------------------------------------------
1300 ;;----------------------------------------------------------------
1301 ;; 32-bit left shifts
1302 ;;----------------------------------------------------------------
1303 (define_expand "ashlsi3"
1304   [(set (match_operand:SI 0 "register_operand" "=&d")
1305         (ashift:SI (match_operand:SI 1 "register_operand" "d")
1306                    (match_operand:SI 2 "arith_operand" "")))]
1307   ""
1308   { 
1309     /* Avoid recursion for trivial cases. */
1310     if (!((GET_CODE (operands [2]) == CONST_INT) && (INTVAL (operands[2]) == 1)))
1311       if (microblaze_expand_shift (operands))
1312         DONE;
1313   }
1316 ;; Irrespective of if we have a barrel-shifter or not, we want to match 
1317 ;; shifts by 1 with a special pattern. When a barrel shifter is present, 
1318 ;; saves a cycle. If not, allows us to annotate the instruction for delay 
1319 ;; slot optimization
1320 (define_insn "*ashlsi3_byone"
1321   [(set (match_operand:SI 0 "register_operand" "=d")
1322         (ashift:SI (match_operand:SI 1 "register_operand" "d")
1323                    (match_operand:SI 2 "arith_operand"    "I")))] 
1324   "(operands[2] == const1_rtx)"
1325   "addk\t%0,%1,%1"
1326   [(set_attr "type"     "arith")
1327    (set_attr "mode"     "SI")
1328    (set_attr "length"   "4")]
1331 ;; Barrel shift left
1332 (define_insn "ashlsi3_bshift"
1333   [(set (match_operand:SI 0 "register_operand" "=d,d")
1334         (ashift:SI (match_operand:SI 1 "register_operand" "d,d")
1335                    (match_operand:SI 2 "arith_operand"    "I,d")))]
1336   "TARGET_BARREL_SHIFT"
1337   "@
1338   bslli\t%0,%1,%2
1339   bsll\t%0,%1,%2"
1340   [(set_attr "type"     "bshift,bshift")
1341   (set_attr "mode"      "SI,SI")
1342   (set_attr "length"    "4,4")]
1345 ;; The following patterns apply when there is no barrel shifter present
1347 (define_insn "*ashlsi3_with_mul_delay"
1348   [(set (match_operand:SI 0 "register_operand" "=d")
1349         (ashift:SI (match_operand:SI 1 "register_operand"  "d")
1350                    (match_operand:SI 2 "immediate_operand" "I")))] 
1351   "!TARGET_SOFT_MUL 
1352    && ((1 << INTVAL (operands[2])) <= 32767 && (1 << INTVAL (operands[2])) >= -32768)"
1353   "muli\t%0,%1,%m2"
1354   ;; This MUL will not generate an imm. Can go into a delay slot.
1355   [(set_attr "type"     "arith")
1356    (set_attr "mode"     "SI")
1357    (set_attr "length"   "4")]
1360 (define_insn "*ashlsi3_with_mul_nodelay"
1361   [(set (match_operand:SI 0 "register_operand" "=d")
1362         (ashift:SI (match_operand:SI 1 "register_operand"  "d")
1363                    (match_operand:SI 2 "immediate_operand" "I")))] 
1364   "!TARGET_SOFT_MUL"
1365   "muli\t%0,%1,%m2"
1366   ;; This MUL will generate an IMM. Cannot go into a delay slot
1367   [(set_attr "type"     "no_delay_arith")
1368    (set_attr "mode"     "SI")
1369    (set_attr "length"   "8")]
1372 (define_insn "*ashlsi3_with_size_opt"
1373   [(set (match_operand:SI 0 "register_operand" "=&d")
1374        (ashift:SI (match_operand:SI 1 "register_operand"  "d")
1375                    (match_operand:SI 2 "immediate_operand" "I")))]
1376   "(INTVAL (operands[2]) > 5 && optimize_size)"
1377   {
1378     operands[3] = gen_rtx_REG (SImode, MB_ABI_ASM_TEMP_REGNUM);
1380     output_asm_insn ("ori\t%3,r0,%2", operands);
1381     if (REGNO (operands[0]) != REGNO (operands[1]))
1382         output_asm_insn ("addk\t%0,%1,r0", operands);
1384     output_asm_insn ("addik\t%3,%3,-1", operands);
1385     output_asm_insn ("bneid\t%3,.-4", operands);
1386     return "addk\t%0,%0,%0";
1387   }
1388   [(set_attr "type"    "multi")
1389    (set_attr "mode"    "SI")
1390    (set_attr "length"  "20")]
1393 (define_insn "*ashlsi3_with_rotate"
1394   [(set (match_operand:SI 0 "register_operand" "=&d")
1395        (ashift:SI (match_operand:SI 1 "register_operand"  "d")
1396                    (match_operand:SI 2 "immediate_operand" "I")))]
1397   "(INTVAL (operands[2]) > 17 && !optimize_size)"
1398   {
1399     int i, nshift;
1400     
1401     nshift = INTVAL (operands[2]);
1402     operands[3] = gen_int_mode (0xFFFFFFFF << nshift, SImode);
1404     /* We do one extra shift so that the first bit (carry) coming into the MSB
1405        will be masked out */
1406     output_asm_insn ("src\t%0,%1", operands);
1407     for (i = 0; i < (32 - nshift); i++)
1408        output_asm_insn ("src\t%0,%0", operands);
1410     return "andi\t%0,%0,%3";
1411   }
1412   [(set_attr "type"    "multi")
1413   (set_attr "mode"     "SI")
1414   (set_attr "length"   "80")]
1417 (define_insn "*ashlsi_inline"
1418   [(set (match_operand:SI 0 "register_operand" "=&d")
1419        (ashift:SI (match_operand:SI 1 "register_operand"  "d")
1420                    (match_operand:SI 2 "immediate_operand" "I")))]
1421   ""
1422   {
1423     int i;
1424     int nshift = INTVAL (operands[2]);
1425     if (REGNO (operands[0]) != REGNO (operands[1]))
1426       output_asm_insn ("addk\t%0,r0,%1", operands);
1427     output_asm_insn ("addk\t%0,%1,%1", operands);
1428     for (i = 0; i < (nshift - 2); i++)
1429       output_asm_insn ("addk\t%0,%0,%0", operands);
1430     return "addk\t%0,%0,%0";
1431   }
1432   [(set_attr "type"    "multi")
1433   (set_attr "mode"     "SI")
1434   (set_attr "length"   "124")]
1437 (define_insn "*ashlsi_reg"
1438   [(set (match_operand:SI 0 "register_operand" "=&d")
1439        (ashift:SI (match_operand:SI 1 "register_operand"  "d")
1440                    (match_operand:SI 2 "register_operand" "d")))]
1441   ""
1442   {
1443     operands[3] = gen_rtx_REG (SImode, MB_ABI_ASM_TEMP_REGNUM);
1444     output_asm_insn ("andi\t%3,%2,31", operands);
1445     if (REGNO (operands[0]) != REGNO (operands[1])) 
1446       output_asm_insn ("addk\t%0,r0,%1", operands);
1447     /* Exit the loop if zero shift. */
1448     output_asm_insn ("beqid\t%3,.+20", operands);
1449     /* Emit the loop.  */
1450     output_asm_insn ("addk\t%0,%0,r0", operands);
1451     output_asm_insn ("addik\t%3,%3,-1", operands);
1452     output_asm_insn ("bneid\t%3,.-4", operands);
1453     return "addk\t%0,%0,%0";
1454   }
1455   [(set_attr "type"    "multi")
1456   (set_attr "mode"     "SI")
1457   (set_attr "length"   "28")]
1461 ;;----------------------------------------------------------------
1462 ;; 32-bit right shifts
1463 ;;----------------------------------------------------------------
1464 (define_expand "ashrsi3"
1465   [(set (match_operand:SI 0 "register_operand" "=&d")
1466         (ashiftrt:SI (match_operand:SI 1 "register_operand" "d")
1467                      (match_operand:SI 2 "arith_operand" "")))]
1468   ""
1469   {
1470     /* Avoid recursion for trivial cases. */
1471     if (!((GET_CODE (operands [2]) == CONST_INT) && (INTVAL (operands[2]) == 1)))
1472       if (microblaze_expand_shift (operands))
1473         DONE;
1474   }
1477 ;; Irrespective of if we have a barrel-shifter or not, we want to match 
1478 ;; shifts by 1 with a special pattern. When a barrel shifter is present, 
1479 ;; saves a cycle. If not, allows us to annotate the instruction for delay 
1480 ;; slot optimization
1481 (define_insn "*ashrsi3_byone"
1482   [(set (match_operand:SI 0 "register_operand" "=d")
1483         (ashiftrt:SI (match_operand:SI 1 "register_operand" "d")
1484                      (match_operand:SI 2 "arith_operand"    "I")))] 
1485   "(operands[2] == const1_rtx)"
1486   "sra\t%0,%1"
1487   [(set_attr "type"     "arith")
1488    (set_attr "mode"     "SI")
1489    (set_attr "length"   "4")]
1492 ;; Barrel shift right logical
1493 (define_insn "*ashrsi3_bshift"
1494   [(set (match_operand:SI 0 "register_operand" "=d,d")
1495         (ashiftrt:SI (match_operand:SI 1 "register_operand" "d,d")
1496                      (match_operand:SI 2 "arith_operand"    "I,d")))]
1497   "TARGET_BARREL_SHIFT"
1498   "@
1499   bsrai\t%0,%1,%2
1500   bsra\t%0,%1,%2"
1501   [(set_attr "type"     "bshift,bshift")
1502   (set_attr "mode"      "SI,SI")
1503   (set_attr "length"    "4,4")]
1506 (define_insn "*ashrsi_inline"
1507   [(set (match_operand:SI 0 "register_operand" "=&d")
1508        (ashiftrt:SI (match_operand:SI 1 "register_operand"  "d")
1509                    (match_operand:SI 2 "immediate_operand" "I")))]
1510   ""
1511   {
1512     int i;
1513     int nshift = INTVAL (operands[2]);
1514     if (REGNO (operands[0]) != REGNO (operands[1]))
1515       output_asm_insn ("addk\t%0,r0,%1", operands);
1516     output_asm_insn ("sra\t%0,%1", operands);
1517     for (i = 0; i < (nshift - 2); i++)
1518       output_asm_insn ("sra\t%0,%0", operands);
1519     return "sra\t%0,%0";
1520   }
1521   [(set_attr "type"    "multi")
1522   (set_attr "mode"     "SI")
1523   (set_attr "length"   "124")]
1526 (define_insn "*ashrsi_reg"
1527   [(set (match_operand:SI 0 "register_operand" "=&d")
1528        (ashiftrt:SI (match_operand:SI 1 "register_operand"  "d")
1529                    (match_operand:SI 2 "register_operand" "d")))]
1530   ""
1531   {
1532     operands[3] = gen_rtx_REG (SImode, MB_ABI_ASM_TEMP_REGNUM);
1533     output_asm_insn ("andi\t%3,%2,31", operands);
1534     if (REGNO (operands[0]) != REGNO (operands[1])) 
1535       output_asm_insn ("addk\t%0,r0,%1", operands);
1536     /* Exit the loop if zero shift. */
1537     output_asm_insn ("beqid\t%3,.+20", operands);
1538     /* Emit the loop.  */
1539     output_asm_insn ("addk\t%0,%0,r0", operands);
1540     output_asm_insn ("addik\t%3,%3,-1", operands);
1541     output_asm_insn ("bneid\t%3,.-4", operands);
1542     return "sra\t%0,%0";
1543   }
1544   [(set_attr "type"    "multi")
1545   (set_attr "mode"     "SI")
1546   (set_attr "length"   "28")]
1549 ;;----------------------------------------------------------------
1550 ;; 32-bit right shifts (logical)
1551 ;;----------------------------------------------------------------
1553 (define_expand "lshrsi3"
1554   [(set (match_operand:SI 0 "register_operand" "=&d")
1555         (lshiftrt:SI (match_operand:SI 1 "register_operand" "d")
1556                      (match_operand:SI 2 "arith_operand" "")))]
1557   ""
1558   {
1559     /* Avoid recursion for trivial cases. */
1560     if (!((GET_CODE (operands [2]) == CONST_INT) && (INTVAL (operands[2]) == 1)))
1561       if (microblaze_expand_shift (operands))
1562         DONE;
1563   }
1566 ;; Irrespective of if we have a barrel-shifter or not, we want to match 
1567 ;; shifts by 1 with a special pattern. When a barrel shifter is present, 
1568 ;; saves a cycle. If not, allows us to annotate the instruction for delay 
1569 ;; slot optimization
1570 (define_insn "*lshrsi3_byone"
1571   [(set (match_operand:SI 0 "register_operand" "=d")
1572         (lshiftrt:SI (match_operand:SI 1 "register_operand" "d")
1573                      (match_operand:SI 2 "arith_operand"    "I")))] 
1574   "(operands[2] == const1_rtx)"
1575   "srl\t%0,%1"
1576   [(set_attr "type"     "arith")
1577    (set_attr "mode"     "SI")
1578    (set_attr "length"   "4")]
1581 ;; Barrel shift right logical
1582 (define_insn "*lshrsi3_bshift"
1583   [(set (match_operand:SI 0 "register_operand" "=d,d")
1584         (lshiftrt:SI (match_operand:SI 1 "register_operand" "d,d")
1585                      (match_operand:SI 2 "arith_operand"    "I,d")))]
1586   "TARGET_BARREL_SHIFT"
1587   "@
1588   bsrli\t%0,%1,%2
1589   bsrl\t%0,%1,%2"
1590   [(set_attr "type"     "bshift,bshift")
1591   (set_attr "mode"      "SI,SI")
1592   (set_attr "length"    "4,4")]
1595 (define_insn "*lshrsi_inline"
1596   [(set (match_operand:SI 0 "register_operand" "=&d")
1597        (lshiftrt:SI (match_operand:SI 1 "register_operand"  "d")
1598                    (match_operand:SI 2 "immediate_operand" "I")))]
1599   ""
1600   {
1601     int i;
1602     int nshift = INTVAL (operands[2]);
1603     if (REGNO (operands[0]) != REGNO (operands[1]))
1604       output_asm_insn ("addk\t%0,r0,%1", operands);
1605     output_asm_insn ("srl\t%0,%1", operands);
1606     for (i = 0; i < (nshift - 2); i++)
1607       output_asm_insn ("srl\t%0,%0", operands);
1608     return "srl\t%0,%0";
1609   }
1610   [(set_attr "type"    "multi")
1611   (set_attr "mode"     "SI")
1612   (set_attr "length"   "124")]
1615 (define_insn "*lshrsi_reg"
1616   [(set (match_operand:SI 0 "register_operand" "=&d")
1617        (lshiftrt:SI (match_operand:SI 1 "register_operand"  "d")
1618                    (match_operand:SI 2 "register_operand" "d")))]
1619   ""
1620   {
1621     operands[3] = gen_rtx_REG (SImode, MB_ABI_ASM_TEMP_REGNUM);
1622     output_asm_insn ("andi\t%3,%2,31", operands);
1623     if (REGNO (operands[0]) != REGNO (operands[1])) 
1624       output_asm_insn ("addk\t%0,r0,%1", operands);
1625     /* Exit the loop if zero shift. */
1626     output_asm_insn ("beqid\t%3,.+20", operands);
1627     /* Emit the loop.  */
1628     output_asm_insn ("addk\t%0,%0,r0", operands);
1629     output_asm_insn ("addik\t%3,%3,-1", operands);
1630     output_asm_insn ("bneid\t%3,.-4", operands);
1631     return "srl\t%0,%0";
1632   }
1633   [(set_attr "type"    "multi")
1634   (set_attr "mode"     "SI")
1635   (set_attr "length"   "28")]
1638 ;;----------------------------------------------------------------
1639 ;; Setting a register from an integer comparison. 
1640 ;;----------------------------------------------------------------
1641 (define_expand "cstoresi4"
1642    [(set (match_operand:SI 0 "register_operand")
1643         (match_operator:SI 1 "ordered_comparison_operator"
1644               [(match_operand:SI 2 "register_operand")
1645                (match_operand:SI 3 "register_operand")]))]
1646   "TARGET_PATTERN_COMPARE"
1647   "if (GET_CODE (operand1) != EQ && GET_CODE (operand1) != NE) 
1648      FAIL;
1649   "
1652 (define_insn "seq_internal_pat" 
1653   [(set (match_operand:SI 0 "register_operand" "=d")
1654         (eq:SI 
1655                (match_operand:SI 1 "register_operand" "d")
1656                (match_operand:SI 2 "register_operand" "d")))]
1657   "TARGET_PATTERN_COMPARE"
1658   "pcmpeq\t%0,%1,%2"
1659   [(set_attr "type"     "arith")
1660    (set_attr "mode"     "SI")
1661    (set_attr "length"   "4")]
1662 )              
1664 (define_insn "sne_internal_pat" 
1665   [(set (match_operand:SI 0 "register_operand" "=d")
1666         (ne:SI 
1667                (match_operand:SI 1 "register_operand" "d")
1668                (match_operand:SI 2 "register_operand" "d")))]
1669   "TARGET_PATTERN_COMPARE"
1670   "pcmpne\t%0,%1,%2"
1671   [(set_attr "type"     "arith")
1672   (set_attr "mode"      "SI")
1673   (set_attr "length"    "4")]
1674 )              
1676 ;;----------------------------------------------------------------
1677 ;; Setting a register from an floating point comparison. 
1678 ;;----------------------------------------------------------------
1679 (define_insn "cstoresf4"
1680    [(set (match_operand:SI 0 "register_operand" "=r")
1681         (match_operator:SI 1 "ordered_comparison_operator"
1682               [(match_operand:SF 2 "register_operand" "r")
1683                (match_operand:SF 3 "register_operand" "r")]))]
1684   "TARGET_HARD_FLOAT"
1685   "fcmp.%C1\t%0,%3,%2"
1686   [(set_attr "type"     "fcmp")
1687    (set_attr "mode"      "SF")
1688    (set_attr "length"    "4")]
1691 ;;----------------------------------------------------------------
1692 ;; Conditional branches
1693 ;;----------------------------------------------------------------
1695 (define_expand "cbranchsi4"
1696   [(set (pc)
1697         (if_then_else (match_operator 0 "ordered_comparison_operator"
1698                        [(match_operand:SI 1 "register_operand")
1699                         (match_operand:SI 2 "arith_operand" "I,i")])
1700                       (label_ref (match_operand 3 ""))
1701                       (pc)))]
1702   ""
1704   microblaze_expand_conditional_branch (SImode, operands);
1705   DONE;
1708 (define_expand "cbranchsi4_reg"
1709   [(set (pc)
1710         (if_then_else (match_operator 0 "ordered_comparison_operator"
1711                        [(match_operand:SI 1 "register_operand")
1712                         (match_operand:SI 2 "register_operand")])
1713                       (label_ref (match_operand 3 ""))
1714                       (pc)))]
1715   ""
1717   microblaze_expand_conditional_branch_reg (SImode, operands);
1718   DONE;
1721 (define_expand "cbranchsf4"
1722   [(set (pc)
1723         (if_then_else (match_operator 0 "ordered_comparison_operator"
1724                        [(match_operand:SF 1 "register_operand")
1725                         (match_operand:SF 2 "register_operand")])
1726                       (label_ref (match_operand 3 ""))
1727                       (pc)))]
1728   "TARGET_HARD_FLOAT"
1730   microblaze_expand_conditional_branch_sf (operands);
1731   DONE;
1735 ;; Used to implement comparison instructions
1736 (define_expand "condjump"
1737   [(set (pc)
1738         (if_then_else (match_operand 0)
1739                       (label_ref (match_operand 1))
1740                       (pc)))])
1742 (define_insn "branch_zero"
1743   [(set (pc)
1744         (if_then_else (match_operator:SI 0 "ordered_comparison_operator"
1745                                  [(match_operand:SI 1 "register_operand" "d")
1746                                   (const_int 0)])
1747                       (match_operand:SI 2 "pc_or_label_operand" "")
1748                       (match_operand:SI 3 "pc_or_label_operand" "")))
1749   ]
1750   ""
1751   {
1752     if (operands[3] == pc_rtx) 
1753       return "b%C0i%?\t%z1,%2";
1754     else 
1755       return "b%N0i%?\t%z1,%3";
1756   }
1757   [(set_attr "type"     "branch")
1758    (set_attr "mode"     "none")
1759    (set_attr "length"   "4")]
1762 (define_insn "branch_compare"
1763   [(set (pc)
1764         (if_then_else (match_operator:SI 0 "cmp_op"
1765                                          [(match_operand:SI 1 "register_operand" "d")
1766                                           (match_operand:SI 2 "register_operand" "d")
1767                                          ])
1768                       (label_ref (match_operand 3))
1769                       (pc)))
1770   (clobber(reg:SI R_TMP))]
1771   ""
1772   {
1773     operands[4] = gen_rtx_REG (SImode, MB_ABI_ASM_TEMP_REGNUM);
1774     enum rtx_code code = GET_CODE (operands[0]);
1776     if (code == GT || code == LE)
1777       {
1778         output_asm_insn ("cmp\tr18,%z1,%z2", operands);
1779         code = swap_condition (code);
1780       }
1781     else if (code == GTU || code == LEU)
1782       {
1783         output_asm_insn ("cmpu\tr18,%z1,%z2", operands);
1784         code = swap_condition (code);
1785       }
1786     else if (code == GE || code == LT)
1787       {
1788         output_asm_insn ("cmp\tr18,%z2,%z1", operands);
1789       }
1790     else if (code == GEU || code == LTU)
1791       {
1792         output_asm_insn ("cmpu\tr18,%z2,%z1", operands);
1793       }
1795     operands[0] = gen_rtx_fmt_ee (signed_condition (code), SImode, operands[4], const0_rtx);
1796     return "b%C0i%?\tr18,%3";
1797   }
1798   [(set_attr "type"     "branch")
1799    (set_attr "mode"     "none")
1800    (set_attr "length"   "12")]
1803 ;;----------------------------------------------------------------
1804 ;; Unconditional branches
1805 ;;----------------------------------------------------------------
1806 (define_insn "jump"
1807   [(set (pc)
1808         (label_ref (match_operand 0 "" "")))]
1809   ""
1810   {
1811     if (GET_CODE (operands[0]) == REG)
1812         return "br%?\t%0";
1813     else        
1814         return "bri%?\t%l0";
1815   }
1816   [(set_attr "type"     "jump")
1817   (set_attr "mode"      "none")
1818   (set_attr "length"    "4")])
1820 (define_expand "indirect_jump"
1821   [(set (pc) (match_operand 0 "register_operand" "d"))]
1822   ""
1823   {
1824     rtx dest = operands[0];
1825     if (GET_CODE (dest) != REG || GET_MODE (dest) != Pmode)
1826       operands[0] = copy_to_mode_reg (Pmode, dest);
1828     emit_jump_insn (gen_indirect_jump_internal1 (operands[0]));
1829     DONE;
1830   }
1833 ;; Indirect jumps. Jump to register values. Assuming absolute jumps
1835 (define_insn "indirect_jump_internal1"
1836   [(set (pc) (match_operand:SI 0 "register_operand" "d"))]
1837   ""
1838   "bra%?\t%0"
1839   [(set_attr "type"     "jump")
1840   (set_attr "mode"      "none")
1841   (set_attr "length"    "4")])
1843 (define_expand "tablejump"
1844   [(set (pc)
1845         (match_operand 0 "register_operand" "d"))
1846   (use (label_ref (match_operand 1 "" "")))]
1847   ""
1848   {
1849     gcc_assert (GET_MODE (operands[0]) == Pmode);
1851     if (!flag_pic)
1852       emit_jump_insn (gen_tablejump_internal1 (operands[0], operands[1]));
1853     else
1854       emit_jump_insn (gen_tablejump_internal3 (operands[0], operands[1]));
1855     DONE;
1856   }
1859 (define_insn "tablejump_internal1"
1860   [(set (pc)
1861         (match_operand:SI 0 "register_operand" "d"))
1862   (use (label_ref (match_operand 1 "" "")))]
1863   ""
1864   "bra%?\t%0 "
1865   [(set_attr "type"     "jump")
1866   (set_attr "mode"      "none")
1867   (set_attr "length"    "4")])
1869 (define_expand "tablejump_internal3"
1870   [(parallel [(set (pc)
1871                    (plus:SI (match_operand:SI 0 "register_operand" "d")
1872                             (label_ref:SI (match_operand:SI 1 "" ""))))
1873              (use (label_ref:SI (match_dup 1)))])]
1874   ""
1875   ""
1878 ;; need to change for MicroBlaze PIC
1879 (define_insn ""
1880  [(set (pc)
1881         (plus:SI (match_operand:SI 0 "register_operand" "d")
1882                  (label_ref:SI (match_operand 1 "" ""))))
1883   (use (label_ref:SI (match_dup 1)))]
1884  "NEXT_INSN (as_a <rtx_insn *> (operands[1])) != 0
1885   && GET_CODE (PATTERN (NEXT_INSN (as_a <rtx_insn *> (operands[1])))) == ADDR_DIFF_VEC
1886   && flag_pic"
1887   {
1888     output_asm_insn ("addk\t%0,%0,r20",operands);
1889     return "bra%?\t%0";
1891  [(set_attr "type"      "jump")
1892   (set_attr "mode"      "none")
1893   (set_attr "length"    "4")])
1895 (define_expand "tablejump_internal4"
1896   [(parallel [(set (pc)
1897                    (plus:DI (match_operand:DI 0 "register_operand" "d")
1898                             (label_ref:DI (match_operand:SI 1 "" ""))))
1899              (use (label_ref:DI (match_dup 1)))])]
1900   ""
1901   ""
1904 ;;----------------------------------------------------------------
1905 ;; Function prologue/epilogue and stack allocation
1906 ;;----------------------------------------------------------------
1907 (define_expand "prologue"
1908   [(const_int 1)]
1909   ""
1910   {
1911       microblaze_expand_prologue ();
1912       DONE;
1913   }
1916 (define_expand "epilogue"
1917   [(use (const_int 0))]
1918   ""
1919   {
1920       microblaze_expand_epilogue ();
1921       DONE;
1922   }
1925 ;; An insn to allocate new stack space for dynamic use (e.g., alloca).
1926 ;; We copy the return address, decrement the stack pointer and save the 
1927 ;; return address again at the new stack top 
1929 (define_expand "allocate_stack"
1930   [(set (match_operand 0 "register_operand" "=r")
1931         (minus (reg 1) (match_operand 1 "register_operand" "")))
1932    (set (reg 1)
1933         (minus (reg 1) (match_dup 1)))]
1934   ""
1935   { 
1936     rtx retaddr = gen_rtx_MEM (Pmode, stack_pointer_rtx);
1937     rtx rtmp    = gen_rtx_REG (SImode, R_TMP);
1938     rtx neg_op0;
1940     emit_move_insn (rtmp, retaddr);
1941     if (GET_CODE (operands[1]) != CONST_INT)
1942     {
1943         neg_op0 = gen_reg_rtx (Pmode);
1944         emit_insn (gen_negsi2 (neg_op0, operands[1]));
1945     } else
1946         neg_op0 = GEN_INT (- INTVAL (operands[1]));
1948     emit_insn (gen_addsi3 (stack_pointer_rtx, stack_pointer_rtx, neg_op0));
1949     emit_move_insn (gen_rtx_MEM (Pmode, stack_pointer_rtx), rtmp);
1950     emit_move_insn (operands[0], virtual_stack_dynamic_rtx);
1951     emit_insn (gen_rtx_CLOBBER (SImode, rtmp));
1952     DONE;
1953   }
1956 (define_expand "save_stack_block"
1957   [(match_operand 0 "register_operand" "")
1958    (match_operand 1 "register_operand" "")]
1959   ""
1960   {
1961     emit_move_insn (operands[0], operands[1]);
1962     DONE;
1963   }
1966 (define_expand "restore_stack_block"
1967   [(match_operand 0 "register_operand" "")
1968    (match_operand 1 "register_operand" "")]
1969   ""
1970   {
1971     rtx retaddr = gen_rtx_MEM (Pmode, stack_pointer_rtx);
1972     rtx rtmp    = gen_rtx_REG (SImode, R_TMP);
1974     /* Move the retaddr.  */
1975     emit_move_insn (rtmp, retaddr);
1976     emit_move_insn (operands[0], operands[1]);
1977     emit_move_insn (gen_rtx_MEM (Pmode, operands[0]), rtmp);
1978     DONE;
1979   }
1982 ;; Trivial return.  Make it look like a normal return insn as that
1983 ;; allows jump optimizations to work better .
1984 (define_expand "return"
1985   [(simple_return)]
1986   "microblaze_can_use_return_insn ()"
1987   {}
1990 (define_expand "simple_return"
1991   [(simple_return)]
1992   ""
1993   {}
1996 (define_insn "*<optab>"
1997   [(any_return)]
1998   ""
1999   {
2000     if (microblaze_is_break_handler ())
2001         return "rtbd\tr16, 8\;%#";
2002     else if (microblaze_is_interrupt_variant ())
2003         return "rtid\tr14, 0\;%#";
2004     else
2005         return "rtsd\tr15, 8\;%#";
2006   }
2007   [(set_attr "type"     "jump")
2008   (set_attr "mode"      "none")
2009   (set_attr "length"    "4")]
2012 ;; Normal return.
2014 (define_insn "<optab>_internal"
2015   [(any_return)
2016    (use (match_operand:SI 0 "register_operand" ""))]
2017   ""
2018   {
2019     if (microblaze_is_break_handler ())
2020         return "rtbd\tr16,8\;%#";
2021     else if (microblaze_is_interrupt_variant ())
2022         return "rtid\tr14,0 \;%#";
2023     else
2024         return "rtsd\tr15,8 \;%#";
2025   }
2026   [(set_attr "type"     "jump")
2027   (set_attr "mode"      "none")
2028   (set_attr "length"    "4")])
2031 ;; Block any insns from across this point
2032 ;; Useful to group sequences together.
2033 (define_insn "blockage"
2034   [(unspec_volatile [(const_int 0)] 0)]
2035   ""
2036   ""
2037   [(set_attr "type"     "unknown")
2038   (set_attr "mode"      "none")
2039   (set_attr "length"    "0")])
2041   
2042 ;;----------------------------------------------------------------
2043 ;; Function calls
2044 ;;----------------------------------------------------------------
2046 (define_expand "call"
2047   [(parallel [(call (match_operand 0 "memory_operand" "m")
2048                     (match_operand 1 "" "i"))
2049              (clobber (reg:SI R_SR))
2050              (use (match_operand 2 "" ""))
2051              (use (match_operand 3 "" ""))])]
2052   ""
2053   {
2054     rtx addr = XEXP (operands[0], 0);
2056     if (flag_pic == 2 && GET_CODE (addr) == SYMBOL_REF 
2057         && !SYMBOL_REF_LOCAL_P (addr)) 
2058       {
2059         rtx temp = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, addr), UNSPEC_PLT);
2060         XEXP (operands[0], 0) = temp;
2061       }
2062     
2063     if ((GET_CODE (addr) != REG && !CONSTANT_ADDRESS_P (addr))
2064         || !call_insn_operand (addr, VOIDmode))
2065       XEXP (operands[0], 0) = copy_to_mode_reg (Pmode, addr);
2067     if (GET_CODE (XEXP (operands[0], 0)) == UNSPEC)
2068       emit_call_insn (gen_call_internal_plt0 (operands[0], operands[1],
2069                         gen_rtx_REG (SImode, 
2070                                      GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM),
2071                                      pic_offset_table_rtx));
2072     else
2073       emit_call_insn (gen_call_internal0 (operands[0], operands[1],
2074                         gen_rtx_REG (SImode, 
2075                                      GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM)));
2077         DONE;
2078   }
2081 (define_expand "call_internal0"
2082   [(parallel [(call (match_operand 0 "" "")
2083                     (match_operand 1 "" ""))
2084              (clobber (match_operand:SI 2 "" ""))])]
2085   ""
2086   {
2087   }
2090 (define_expand "call_internal_plt0"
2091   [(parallel [(call (match_operand 0 "" "")
2092                     (match_operand 1 "" ""))
2093              (clobber (match_operand:SI 2 "" ""))
2094              (use (match_operand:SI 3 "" ""))])]
2095   ""
2096   {
2097   }
2100 (define_insn "call_internal_plt"
2101   [(call (mem (match_operand:SI 0 "call_insn_plt_operand" ""))
2102          (match_operand:SI 1 "" "i"))
2103   (clobber (reg:SI R_SR))
2104   (use (reg:SI R_GOT))]
2105   "flag_pic"
2106   {
2107     register rtx target2 = gen_rtx_REG (Pmode, 
2108                               GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM);
2109     gen_rtx_CLOBBER (VOIDmode, target2);
2110     return "brlid\tr15,%0\;%#";
2111   }
2112   [(set_attr "type"     "call")
2113   (set_attr "mode"      "none")
2114   (set_attr "length"    "4")])
2116 (define_insn "call_internal1"
2117   [(call (mem (match_operand:VOID 0 "call_insn_simple_operand" "ri"))
2118          (match_operand:SI 1 "" "i"))
2119   (clobber (reg:SI R_SR))]
2120   ""
2121   {
2122     register rtx target = operands[0];
2123     register rtx target2 = gen_rtx_REG (Pmode,
2124                               GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM);
2125     if (GET_CODE (target) == SYMBOL_REF) {
2126         if (microblaze_break_function_p (SYMBOL_REF_DECL (target))) {
2127             gen_rtx_CLOBBER (VOIDmode, target2);
2128             return "brki\tr16,%0\;%#";
2129         }
2130         else {
2131             gen_rtx_CLOBBER (VOIDmode, target2);
2132             return "brlid\tr15,%0\;%#";
2133         }
2134     } else if (GET_CODE (target) == CONST_INT)
2135         return "la\t%@,r0,%0\;brald\tr15,%@\;%#";
2136     else if (GET_CODE (target) == REG)
2137         return "brald\tr15,%0\;%#";     
2138     else {
2139         fprintf (stderr,"Unsupported call insn\n");
2140         return NULL;
2141     }
2142   }
2143   [(set_attr "type"     "call")
2144   (set_attr "mode"      "none")
2145   (set_attr "length"    "4")])
2147 ;; calls.c now passes a fourth argument, make saber happy
2149 (define_expand "call_value"
2150   [(parallel [(set (match_operand 0 "register_operand" "=d")
2151                    (call (match_operand 1 "memory_operand" "m")
2152                          (match_operand 2 "" "i")))
2153              (clobber (reg:SI R_SR))
2154              (use (match_operand 3 "" ""))])] ;; next_arg_reg
2155   ""
2156   {
2157     rtx addr = XEXP (operands[1], 0);
2159     if (flag_pic == 2 && GET_CODE (addr) == SYMBOL_REF
2160         && !SYMBOL_REF_LOCAL_P (addr)) 
2161       {
2162         rtx temp = gen_rtx_UNSPEC (Pmode, gen_rtvec (1, addr), UNSPEC_PLT);
2163         XEXP (operands[1], 0) = temp;
2164       }
2166     if ((GET_CODE (addr) != REG && !CONSTANT_ADDRESS_P (addr))
2167         || !call_insn_operand (addr, VOIDmode))
2168       XEXP (operands[1], 0) = copy_to_mode_reg (Pmode, addr);
2170     if (GET_CODE (XEXP (operands[1], 0)) == UNSPEC)
2171       emit_call_insn (gen_call_value_intern_plt0 (operands[0], operands[1], 
2172                         operands[2],
2173                         gen_rtx_REG (SImode, 
2174                                      GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM),
2175                                      pic_offset_table_rtx));
2176     else
2177       emit_call_insn (gen_call_value_internal (operands[0], operands[1], 
2178                         operands[2],
2179                         gen_rtx_REG (SImode, 
2180                                      GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM)));
2182     DONE;
2183   }
2187 (define_expand "call_value_internal"
2188   [(parallel [(set (match_operand 0 "" "")
2189                    (call (match_operand 1 "" "")
2190                          (match_operand 2 "" "")))
2191              (clobber (match_operand:SI 3 "" ""))
2192              ])]
2193   ""
2194   {}
2197 (define_expand "call_value_intern_plt0"
2198   [(parallel[(set (match_operand 0 "" "")
2199                   (call (match_operand 1 "" "")
2200                         (match_operand 2 "" "")))
2201              (clobber (match_operand:SI 3 "" ""))
2202              (use (match_operand:SI 4 "" ""))])]
2203   "flag_pic"
2204   {}
2207 (define_insn "call_value_intern_plt"
2208   [(set (match_operand:VOID 0 "register_operand" "=d")
2209         (call (mem (match_operand:SI 1 "call_insn_plt_operand" ""))
2210               (match_operand:SI 2 "" "i")))
2211    (clobber (match_operand:SI 3 "register_operand" "=d"))
2212    (use (match_operand:SI 4 "register_operand"))]
2213   "flag_pic"
2214   { 
2215     register rtx target2=gen_rtx_REG (Pmode,GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM);
2217     gen_rtx_CLOBBER (VOIDmode,target2);
2218     return "brlid\tr15,%1\;%#";
2219   }
2220   [(set_attr "type"     "call")
2221   (set_attr "mode"      "none")
2222   (set_attr "length"    "4")])
2224 (define_insn "call_value_intern"
2225   [(set (match_operand:VOID 0 "register_operand" "=d")
2226         (call (mem (match_operand:VOID 1 "call_insn_operand" "ri"))
2227               (match_operand:SI 2 "" "i")))
2228    (clobber (match_operand:SI 3 "register_operand" "=d"))]
2229   ""
2230   { 
2231     register rtx target = operands[1];
2232     register rtx target2=gen_rtx_REG (Pmode,GP_REG_FIRST + MB_ABI_SUB_RETURN_ADDR_REGNUM);
2234     if (GET_CODE (target) == SYMBOL_REF)
2235     {
2236       gen_rtx_CLOBBER (VOIDmode,target2);
2237       if (microblaze_break_function_p (SYMBOL_REF_DECL (target)))
2238         return "brki\tr16,%1\;%#";
2239       else if (SYMBOL_REF_FLAGS (target) & SYMBOL_FLAG_FUNCTION)
2240         {
2241           return "brlid\tr15,%1\;%#";
2242         }
2243       else
2244         {
2245             return "bralid\tr15,%1\;%#";
2246         }
2247     }
2248     else if (GET_CODE (target) == CONST_INT)
2249         return "la\t%@,r0,%1\;brald\tr15,%@\;%#";
2250     else if (GET_CODE (target) == REG)
2251         return "brald\tr15,%1\;%#";     
2252     else 
2253         return "Unsupported call insn\n";
2254   }
2255   [(set_attr "type"     "call")
2256   (set_attr "mode"      "none")
2257   (set_attr "length"    "4")])
2260 ;; Call subroutine returning any type.
2261 (define_expand "untyped_call"
2262   [(parallel [(call (match_operand 0 "" "")
2263                     (const_int 0))
2264              (match_operand 1 "" "")
2265              (match_operand 2 "" "")])]
2266   ""
2267   {
2268     if (operands[0])            /* silence statement not reached warnings */
2269     {
2270         int i;
2272         emit_call_insn (gen_call (operands[0], const0_rtx, NULL, const0_rtx));
2274         for (i = 0; i < XVECLEN (operands[2], 0); i++)
2275         {
2276             rtx set = XVECEXP (operands[2], 0, i);
2277             emit_move_insn (SET_DEST (set), SET_SRC (set));
2278         }
2280         emit_insn (gen_blockage ());
2281         DONE;
2282       }
2283   }
2286 ;;----------------------------------------------------------------
2287 ;; Misc.
2288 ;;----------------------------------------------------------------
2290 (define_insn "nop"
2291   [(const_int 0)]
2292   ""
2293   "nop"
2294   [(set_attr "type"     "nop")
2295   (set_attr "mode"      "none")
2296   (set_attr "length"    "4")])
2298 ;; Trap instruction pattern for __builtin_trap. Same as the glibc ABORT_INSTRUCTION
2299 (define_insn "trap"
2300   [(trap_if (const_int 1) (const_int 0))]
2301   ""
2302   "brki\tr0,-1"
2303  [(set_attr "type" "trap")]
2306 ;; The insn to set GOT. The hardcoded number "8" accounts for $pc difference
2307 ;; between "mfs" and "addik" instructions.
2308 (define_insn "set_got"
2309   [(set (match_operand:SI 0 "register_operand" "=r")
2310     (unspec:SI [(const_int 0)] UNSPEC_SET_GOT))]
2311   ""
2312   "mfs\t%0,rpc\n\taddik\t%0,%0,_GLOBAL_OFFSET_TABLE_+8"
2313   [(set_attr "type" "multi")
2314    (set_attr "length" "12")])
2316 ;; This insn gives the count of leading number of zeros for the second
2317 ;; operand and stores the result in first operand.
2318 (define_insn "clzsi2"
2319   [(set (match_operand:SI 0 "register_operand" "=r")
2320         (clz:SI (match_operand:SI 1 "register_operand" "r")))]
2321   "TARGET_HAS_CLZ"
2322   "clz\t%0,%1"
2323   [(set_attr "type"     "arith")
2324   (set_attr "mode"      "SI")
2325   (set_attr "length"    "4")])
2327 ; This is used in compiling the unwind routines.
2328 (define_expand "eh_return"
2329   [(use (match_operand 0 "general_operand" ""))]
2330   ""
2331   "
2333   microblaze_eh_return (operands[0]);
2334   DONE;
2337 (include "sync.md")