OSDN Git Service

f472867cf281d33f95340f33e03d53aa3e87f06f
[pf3gnuchains/gcc-fork.git] / gcc / config / mn10300 / mn10300.c
1 /* Subroutines for insn-output.c for Matsushita MN10300 series
2    Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001
3    Free Software Foundation, Inc.
4    Contributed by Jeff Law (law@cygnus.com).
5
6 This file is part of GNU CC.
7
8 GNU CC 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 2, or (at your option)
11 any later version.
12
13 GNU CC 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.
17
18 You should have received a copy of the GNU General Public License
19 along with GNU CC; see the file COPYING.  If not, write to
20 the Free Software Foundation, 59 Temple Place - Suite 330,
21 Boston, MA 02111-1307, USA.  */
22
23 #include "config.h"
24 #include "system.h"
25 #include "rtl.h"
26 #include "tree.h"
27 #include "regs.h"
28 #include "hard-reg-set.h"
29 #include "real.h"
30 #include "insn-config.h"
31 #include "conditions.h"
32 #include "output.h"
33 #include "insn-attr.h"
34 #include "flags.h"
35 #include "recog.h"
36 #include "expr.h"
37 #include "function.h"
38 #include "obstack.h"
39 #include "toplev.h"
40 #include "tm_p.h"
41 #include "target.h"
42 #include "target-def.h"
43
44 /* The size of the callee register save area.  Right now we save everything
45    on entry since it costs us nothing in code size.  It does cost us from a
46    speed standpoint, so we want to optimize this sooner or later.  */
47 #define REG_SAVE_BYTES (4 * regs_ever_live[2] \
48                         + 4 * regs_ever_live[3] \
49                         + 4 * regs_ever_live[6] \
50                         + 4 * regs_ever_live[7] \
51                         + 16 * (regs_ever_live[14] || regs_ever_live[15] \
52                                 || regs_ever_live[16] || regs_ever_live[17]))
53 \f
54 /* Initialize the GCC target structure.  */
55
56 struct gcc_target target = TARGET_INITIALIZER;
57 \f
58 void
59 asm_file_start (file)
60      FILE *file;
61 {
62   fprintf (file, "#\tGCC For the Matsushita MN10300\n");
63   if (optimize)
64     fprintf (file, "# -O%d\n", optimize);
65   else
66     fprintf (file, "\n\n");
67
68   if (TARGET_AM33)
69     fprintf (file, "\t.am33\n");
70   output_file_directive (file, main_input_filename);
71 }
72 \f
73
74 /* Print operand X using operand code CODE to assembly language output file
75    FILE.  */
76
77 void
78 print_operand (file, x, code)
79      FILE *file;
80      rtx x;
81      int code;
82 {
83   switch (code)
84     {
85       case 'b':
86       case 'B':
87         /* These are normal and reversed branches.  */
88         switch (code == 'b' ? GET_CODE (x) : reverse_condition (GET_CODE (x)))
89           {
90           case NE:
91             fprintf (file, "ne");
92             break;
93           case EQ:
94             fprintf (file, "eq");
95             break;
96           case GE:
97             fprintf (file, "ge");
98             break;
99           case GT:
100             fprintf (file, "gt");
101             break;
102           case LE:
103             fprintf (file, "le");
104             break;
105           case LT:
106             fprintf (file, "lt");
107             break;
108           case GEU:
109             fprintf (file, "cc");
110             break;
111           case GTU:
112             fprintf (file, "hi");
113             break;
114           case LEU:
115             fprintf (file, "ls");
116             break;
117           case LTU:
118             fprintf (file, "cs");
119             break;
120           default:
121             abort ();
122           }
123         break;
124       case 'C':
125         /* This is used for the operand to a call instruction;
126            if it's a REG, enclose it in parens, else output
127            the operand normally.  */
128         if (GET_CODE (x) == REG)
129           {
130             fputc ('(', file);
131             print_operand (file, x, 0);
132             fputc (')', file);
133           }
134         else
135           print_operand (file, x, 0);
136         break;
137      
138       /* These are the least significant word in a 64bit value.  */
139       case 'L':
140         switch (GET_CODE (x))
141           {
142           case MEM:
143             fputc ('(', file);
144             output_address (XEXP (x, 0));
145             fputc (')', file);
146             break;
147
148           case REG:
149             fprintf (file, "%s", reg_names[REGNO (x)]);
150             break;
151
152           case SUBREG:
153             fprintf (file, "%s", reg_names[subreg_regno (x)]);
154             break;
155
156           case CONST_DOUBLE:
157               {
158                 long val[2];
159                 REAL_VALUE_TYPE rv;
160
161                 switch (GET_MODE (x))
162                   {
163                     case DFmode:
164                       REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
165                       REAL_VALUE_TO_TARGET_DOUBLE (rv, val);
166                       fprintf (file, "0x%lx", val[0]);
167                       break;;
168                     case SFmode:
169                       REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
170                       REAL_VALUE_TO_TARGET_SINGLE (rv, val[0]);
171                       fprintf (file, "0x%lx", val[0]);
172                       break;;
173                     case VOIDmode:
174                     case DImode:
175                       print_operand_address (file,
176                                              GEN_INT (CONST_DOUBLE_LOW (x)));
177                       break;
178                     default:
179                       break;
180                   }
181                 break;
182               }
183
184           case CONST_INT:
185             {
186               rtx low, high;
187               split_double (x, &low, &high);
188               fprintf (file, "%ld", (long)INTVAL (low));
189               break;
190             }
191
192           default:
193             abort ();
194           }
195         break;
196
197       /* Similarly, but for the most significant word.  */
198       case 'H':
199         switch (GET_CODE (x))
200           {
201           case MEM:
202             fputc ('(', file);
203             x = adjust_address (x, SImode, 4);
204             output_address (XEXP (x, 0));
205             fputc (')', file);
206             break;
207
208           case REG:
209             fprintf (file, "%s", reg_names[REGNO (x) + 1]);
210             break;
211
212           case SUBREG:
213             fprintf (file, "%s", reg_names[subreg_regno (x) + 1]);
214             break;
215
216           case CONST_DOUBLE:
217               {
218                 long val[2];
219                 REAL_VALUE_TYPE rv;
220
221                 switch (GET_MODE (x))
222                   {
223                     case DFmode:
224                       REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
225                       REAL_VALUE_TO_TARGET_DOUBLE (rv, val);
226                       fprintf (file, "0x%lx", val[1]);
227                       break;;
228                     case SFmode:
229                       abort ();
230                     case VOIDmode:
231                     case DImode:
232                       print_operand_address (file, 
233                                              GEN_INT (CONST_DOUBLE_HIGH (x)));
234                       break;
235                     default:
236                       break;
237                   }
238                 break;
239               }
240
241           case CONST_INT:
242             {
243               rtx low, high;
244               split_double (x, &low, &high);
245               fprintf (file, "%ld", (long)INTVAL (high));
246               break;
247             }
248
249           default:
250             abort ();
251           }
252         break;
253
254       case 'A':
255         fputc ('(', file);
256         if (GET_CODE (XEXP (x, 0)) == REG)
257           output_address (gen_rtx_PLUS (SImode, XEXP (x, 0), GEN_INT (0)));
258         else
259           output_address (XEXP (x, 0));
260         fputc (')', file);
261         break;
262
263       case 'N':
264         output_address (GEN_INT ((~INTVAL (x)) & 0xff));
265         break;
266
267       /* For shift counts.  The hardware ignores the upper bits of
268          any immediate, but the assembler will flag an out of range
269          shift count as an error.  So we mask off the high bits
270          of the immediate here.  */
271       case 'S':
272         if (GET_CODE (x) == CONST_INT)
273           {
274             fprintf (file, "%d", INTVAL (x) & 0x1f);
275             break;
276           }
277         /* FALL THROUGH */
278
279       default:
280         switch (GET_CODE (x))
281           {
282           case MEM:
283             fputc ('(', file);
284             output_address (XEXP (x, 0));
285             fputc (')', file);
286             break;
287
288           case PLUS:
289             output_address (x);
290             break;
291
292           case REG:
293             fprintf (file, "%s", reg_names[REGNO (x)]);
294             break;
295
296           case SUBREG:
297             fprintf (file, "%s", reg_names[subreg_regno (x)]);
298             break;
299
300           /* This will only be single precision....  */
301           case CONST_DOUBLE:
302             {
303               unsigned long val;
304               REAL_VALUE_TYPE rv;
305
306               REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
307               REAL_VALUE_TO_TARGET_SINGLE (rv, val);
308               fprintf (file, "0x%lx", val);
309               break;
310             }
311
312           case CONST_INT:
313           case SYMBOL_REF:
314           case CONST:
315           case LABEL_REF:
316           case CODE_LABEL:
317             print_operand_address (file, x);
318             break;
319           default:
320             abort ();
321           }
322         break;
323    }
324 }
325
326 /* Output assembly language output for the address ADDR to FILE.  */
327
328 void
329 print_operand_address (file, addr)
330      FILE *file;
331      rtx addr;
332 {
333   switch (GET_CODE (addr))
334     {
335     case POST_INC:
336       print_operand_address (file, XEXP (addr, 0));
337       fputc ('+', file);
338       break;
339     case REG:
340       print_operand (file, addr, 0);
341       break;
342     case PLUS:
343       {
344         rtx base, index;
345         if (REG_P (XEXP (addr, 0))
346             && REG_OK_FOR_BASE_P (XEXP (addr, 0)))
347           base = XEXP (addr, 0), index = XEXP (addr, 1);
348         else if (REG_P (XEXP (addr, 1))
349             && REG_OK_FOR_BASE_P (XEXP (addr, 1)))
350           base = XEXP (addr, 1), index = XEXP (addr, 0);
351         else
352           abort ();
353         print_operand (file, index, 0);
354         fputc (',', file);
355         print_operand (file, base, 0);;
356         break;
357       }
358     case SYMBOL_REF:
359       output_addr_const (file, addr);
360       break;
361     default:
362       output_addr_const (file, addr);
363       break;
364     }
365 }
366
367 /* Print a set of registers in the format required by "movm" and "ret".
368    Register K is saved if bit K of MASK is set.  The data and address
369    registers can be stored individually, but the extended registers cannot.
370    We assume that the mask alread takes that into account.  For instance,
371    bits 14 to 17 must have the same value. */
372
373 void
374 mn10300_print_reg_list (file, mask)
375      FILE *file;
376      int mask;
377 {
378   int need_comma;
379   int i;
380
381   need_comma = 0;
382   fputc ('[', file);
383
384   for (i = 0; i < FIRST_EXTENDED_REGNUM; i++)
385     if ((mask & (1 << i)) != 0)
386       {
387         if (need_comma)
388           fputc (',', file);
389         fputs (reg_names [i], file);
390         need_comma = 1;
391       }
392
393   if ((mask & 0x3c000) != 0)
394     {
395       if ((mask & 0x3c000) != 0x3c000)
396         abort();
397       if (need_comma)
398         fputc (',', file);
399       fputs ("exreg1", file);
400       need_comma = 1;
401     }
402
403   fputc (']', file);
404 }
405
406 int
407 can_use_return_insn ()
408 {
409   /* size includes the fixed stack space needed for function calls.  */
410   int size = get_frame_size () + current_function_outgoing_args_size;
411
412   /* And space for the return pointer.  */
413   size += current_function_outgoing_args_size ? 4 : 0;
414
415   return (reload_completed
416           && size == 0
417           && !regs_ever_live[2]
418           && !regs_ever_live[3]
419           && !regs_ever_live[6]
420           && !regs_ever_live[7]
421           && !regs_ever_live[14]
422           && !regs_ever_live[15]
423           && !regs_ever_live[16]
424           && !regs_ever_live[17]
425           && !frame_pointer_needed);
426 }
427
428 /* Returns the set of live, callee-saved registers as a bitmask.  The
429    callee-saved extended registers cannot be stored individually, so
430    all of them will be included in the mask if any one of them is used. */
431
432 int
433 mn10300_get_live_callee_saved_regs ()
434 {
435   int mask;
436   int i;
437
438   mask = 0;
439   for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
440     if (regs_ever_live[i] && ! call_used_regs[i])
441       mask |= (1 << i);
442   if ((mask & 0x3c000) != 0)
443     mask |= 0x3c000;
444
445   return mask;
446 }
447
448 /* Generate an instruction that pushes several registers onto the stack.
449    Register K will be saved if bit K in MASK is set.  The function does
450    nothing if MASK is zero.
451
452    To be compatible with the "movm" instruction, the lowest-numbered
453    register must be stored in the lowest slot.  If MASK is the set
454    { R1,...,RN }, where R1...RN are ordered least first, the generated
455    instruction will have the form:
456
457        (parallel
458          (set (reg:SI 9) (plus:SI (reg:SI 9) (const_int -N*4)))
459          (set (mem:SI (plus:SI (reg:SI 9)
460                                (const_int -1*4)))
461               (reg:SI RN))
462          ...
463          (set (mem:SI (plus:SI (reg:SI 9)
464                                (const_int -N*4)))
465               (reg:SI R1))) */
466
467 void
468 mn10300_gen_multiple_store (mask)
469      int mask;
470 {
471   if (mask != 0)
472     {
473       int i;
474       int count;
475       rtx par;
476       int pari;
477
478       /* Count how many registers need to be saved. */
479       count = 0;
480       for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
481         if ((mask & (1 << i)) != 0)
482           count += 1;
483
484       /* We need one PARALLEL element to update the stack pointer and
485          an additional element for each register that is stored. */
486       par = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (count + 1));
487
488       /* Create the instruction that updates the stack pointer. */
489       XVECEXP (par, 0, 0)
490         = gen_rtx_SET (SImode,
491                        stack_pointer_rtx,
492                        gen_rtx_PLUS (SImode,
493                                      stack_pointer_rtx,
494                                      GEN_INT (-count * 4)));
495
496       /* Create each store. */
497       pari = 1;
498       for (i = FIRST_PSEUDO_REGISTER - 1; i >= 0; i--)
499         if ((mask & (1 << i)) != 0)
500           {
501             rtx address = gen_rtx_PLUS (SImode,
502                                         stack_pointer_rtx,
503                                         GEN_INT (-pari * 4));
504             XVECEXP(par, 0, pari)
505               = gen_rtx_SET (VOIDmode,
506                              gen_rtx_MEM (SImode, address),
507                              gen_rtx_REG (SImode, i));
508             pari += 1;
509           }
510
511       par = emit_insn (par);
512       RTX_FRAME_RELATED_P (par) = 1;
513     }
514 }
515
516 void
517 expand_prologue ()
518 {
519   HOST_WIDE_INT size;
520
521   /* SIZE includes the fixed stack space needed for function calls.  */
522   size = get_frame_size () + current_function_outgoing_args_size;
523   size += (current_function_outgoing_args_size ? 4 : 0);
524
525   /* If this is an old-style varargs function, then its arguments
526      need to be flushed back to the stack.  */
527   if (current_function_varargs)
528     {
529       emit_move_insn (gen_rtx_MEM (SImode,
530                                    plus_constant (stack_pointer_rtx, 4)),
531                       gen_rtx_REG (SImode, 0));
532       emit_move_insn (gen_rtx_MEM (SImode,
533                                    plus_constant (stack_pointer_rtx, 8)),
534                       gen_rtx_REG (SImode, 1));
535     }
536
537   /* If we use any of the callee-saved registers, save them now. */
538   mn10300_gen_multiple_store (mn10300_get_live_callee_saved_regs ());
539
540   /* Now put the frame pointer into the frame pointer register.  */
541   if (frame_pointer_needed)
542     emit_move_insn (frame_pointer_rtx, stack_pointer_rtx);
543
544   /* Allocate stack for this frame.  */
545   if (size)
546     emit_insn (gen_addsi3 (stack_pointer_rtx,
547                            stack_pointer_rtx,
548                            GEN_INT (-size)));
549 }
550
551 void
552 expand_epilogue ()
553 {
554   HOST_WIDE_INT size;
555
556   /* SIZE includes the fixed stack space needed for function calls.  */
557   size = get_frame_size () + current_function_outgoing_args_size;
558   size += (current_function_outgoing_args_size ? 4 : 0);
559
560   /* Maybe cut back the stack, except for the register save area.
561
562      If the frame pointer exists, then use the frame pointer to
563      cut back the stack.
564
565      If the stack size + register save area is more than 255 bytes,
566      then the stack must be cut back here since the size + register
567      save size is too big for a ret/retf instruction. 
568
569      Else leave it alone, it will be cut back as part of the
570      ret/retf instruction, or there wasn't any stack to begin with.
571
572      Under no circumstanes should the register save area be
573      deallocated here, that would leave a window where an interrupt
574      could occur and trash the register save area.  */
575   if (frame_pointer_needed)
576     {
577       emit_move_insn (stack_pointer_rtx, frame_pointer_rtx);
578       size = 0;
579     }
580   else if (size + REG_SAVE_BYTES > 255)
581     {
582       emit_insn (gen_addsi3 (stack_pointer_rtx,
583                              stack_pointer_rtx,
584                              GEN_INT (size)));
585       size = 0;
586     }
587
588   /* Adjust the stack and restore callee-saved registers, if any.  */
589   if (size || regs_ever_live[2] || regs_ever_live[3]
590       || regs_ever_live[6] || regs_ever_live[7]
591       || regs_ever_live[14] || regs_ever_live[15]
592       || regs_ever_live[16] || regs_ever_live[17]
593       || frame_pointer_needed)
594     emit_jump_insn (gen_return_internal_regs
595                     (GEN_INT (size + REG_SAVE_BYTES)));
596   else
597     emit_jump_insn (gen_return_internal ());
598 }
599
600 /* Update the condition code from the insn.  */
601
602 void
603 notice_update_cc (body, insn)
604      rtx body;
605      rtx insn;
606 {
607   switch (get_attr_cc (insn))
608     {
609     case CC_NONE:
610       /* Insn does not affect CC at all.  */
611       break;
612
613     case CC_NONE_0HIT:
614       /* Insn does not change CC, but the 0'th operand has been changed.  */
615       if (cc_status.value1 != 0
616           && reg_overlap_mentioned_p (recog_data.operand[0], cc_status.value1))
617         cc_status.value1 = 0;
618       break;
619
620     case CC_SET_ZN:
621       /* Insn sets the Z,N flags of CC to recog_data.operand[0].
622          V,C are unusable.  */
623       CC_STATUS_INIT;
624       cc_status.flags |= CC_NO_CARRY | CC_OVERFLOW_UNUSABLE;
625       cc_status.value1 = recog_data.operand[0];
626       break;
627
628     case CC_SET_ZNV:
629       /* Insn sets the Z,N,V flags of CC to recog_data.operand[0].
630          C is unusable.  */
631       CC_STATUS_INIT;
632       cc_status.flags |= CC_NO_CARRY;
633       cc_status.value1 = recog_data.operand[0];
634       break;
635
636     case CC_COMPARE:
637       /* The insn is a compare instruction.  */
638       CC_STATUS_INIT;
639       cc_status.value1 = SET_SRC (body);
640       break;
641
642     case CC_INVERT:
643       /* The insn is a compare instruction.  */
644       CC_STATUS_INIT;
645       cc_status.value1 = SET_SRC (body);
646       cc_status.flags |= CC_INVERTED;
647       break;
648
649     case CC_CLOBBER:
650       /* Insn doesn't leave CC in a usable state.  */
651       CC_STATUS_INIT;
652       break;
653
654     default:
655       abort ();
656     }
657 }
658
659 /* Recognise the PARALLEL rtx generated by mn10300_gen_multiple_store().
660    This function is for MATCH_PARALLEL and so assumes OP is known to be
661    parallel.  If OP is a multiple store, return a mask indicating which
662    registers it saves.  Return 0 otherwise.  */
663
664 int
665 store_multiple_operation (op, mode)
666      rtx op;
667      enum machine_mode mode ATTRIBUTE_UNUSED;
668 {
669   int count;
670   int mask;
671   int i;
672   unsigned int last;
673   rtx elt;
674
675   count = XVECLEN (op, 0);
676   if (count < 2)
677     return 0;
678
679   /* Check that first instruction has the form (set (sp) (plus A B)) */
680   elt = XVECEXP (op, 0, 0);
681   if (GET_CODE (elt) != SET
682       || GET_CODE (SET_DEST (elt)) != REG
683       || REGNO (SET_DEST (elt)) != STACK_POINTER_REGNUM
684       || GET_CODE (SET_SRC (elt)) != PLUS)
685     return 0;
686
687   /* Check that A is the stack pointer and B is the expected stack size.
688      For OP to match, each subsequent instruction should push a word onto
689      the stack.  We therefore expect the first instruction to create
690      COUNT-1 stack slots. */
691   elt = SET_SRC (elt);
692   if (GET_CODE (XEXP (elt, 0)) != REG
693       || REGNO (XEXP (elt, 0)) != STACK_POINTER_REGNUM
694       || GET_CODE (XEXP (elt, 1)) != CONST_INT
695       || INTVAL (XEXP (elt, 1)) != -(count - 1) * 4)
696     return 0;
697
698   /* Now go through the rest of the vector elements.  They must be
699      ordered so that the first instruction stores the highest-numbered
700      register to the highest stack slot and that subsequent instructions
701      store a lower-numbered register to the slot below.
702
703      LAST keeps track of the smallest-numbered register stored so far.
704      MASK is the set of stored registers. */
705   last = FIRST_PSEUDO_REGISTER;
706   mask = 0;
707   for (i = 1; i < count; i++)
708     {
709       /* Check that element i is a (set (mem M) R) and that R is valid. */
710       elt = XVECEXP (op, 0, i);
711       if (GET_CODE (elt) != SET
712           || GET_CODE (SET_DEST (elt)) != MEM
713           || GET_CODE (SET_SRC (elt)) != REG
714           || REGNO (SET_SRC (elt)) >= last)
715         return 0;
716
717       /* R was OK, so provisionally add it to MASK.  We return 0 in any
718          case if the rest of the instruction has a flaw. */
719       last = REGNO (SET_SRC (elt));
720       mask |= (1 << last);
721
722       /* Check that M has the form (plus (sp) (const_int -I*4)) */
723       elt = XEXP (SET_DEST (elt), 0);
724       if (GET_CODE (elt) != PLUS
725           || GET_CODE (XEXP (elt, 0)) != REG
726           || REGNO (XEXP (elt, 0)) != STACK_POINTER_REGNUM
727           || GET_CODE (XEXP (elt, 1)) != CONST_INT
728           || INTVAL (XEXP (elt, 1)) != -i * 4)
729         return 0;
730     }
731
732   /* All or none of the callee-saved extended registers must be in the set. */
733   if ((mask & 0x3c000) != 0
734       && (mask & 0x3c000) != 0x3c000)
735     return 0;
736
737   return mask;
738 }
739
740 /* Return true if OP is a valid call operand.  */
741
742 int
743 call_address_operand (op, mode)
744      rtx op;
745      enum machine_mode mode ATTRIBUTE_UNUSED;
746 {
747   return (GET_CODE (op) == SYMBOL_REF || GET_CODE (op) == REG);
748 }
749
750 /* What (if any) secondary registers are needed to move IN with mode
751    MODE into a register in register class CLASS. 
752
753    We might be able to simplify this.  */
754 enum reg_class
755 secondary_reload_class (class, mode, in)
756      enum reg_class class;
757      enum machine_mode mode;
758      rtx in;
759 {
760   /* Memory loads less than a full word wide can't have an
761      address or stack pointer destination.  They must use
762      a data register as an intermediate register.  */
763   if ((GET_CODE (in) == MEM
764        || (GET_CODE (in) == REG
765            && REGNO (in) >= FIRST_PSEUDO_REGISTER)
766        || (GET_CODE (in) == SUBREG
767            && GET_CODE (SUBREG_REG (in)) == REG
768            && REGNO (SUBREG_REG (in)) >= FIRST_PSEUDO_REGISTER))
769       && (mode == QImode || mode == HImode)
770       && (class == ADDRESS_REGS || class == SP_REGS
771           || class == SP_OR_ADDRESS_REGS))
772     {
773       if (TARGET_AM33)
774         return DATA_OR_EXTENDED_REGS;
775       return DATA_REGS;
776     }
777
778   /* We can't directly load sp + const_int into a data register;
779      we must use an address register as an intermediate.  */
780   if (class != SP_REGS
781       && class != ADDRESS_REGS
782       && class != SP_OR_ADDRESS_REGS
783       && class != SP_OR_EXTENDED_REGS
784       && class != ADDRESS_OR_EXTENDED_REGS
785       && class != SP_OR_ADDRESS_OR_EXTENDED_REGS
786       && (in == stack_pointer_rtx
787           || (GET_CODE (in) == PLUS
788               && (XEXP (in, 0) == stack_pointer_rtx
789                   || XEXP (in, 1) == stack_pointer_rtx))))
790     return ADDRESS_REGS;
791
792   if (GET_CODE (in) == PLUS
793       && (XEXP (in, 0) == stack_pointer_rtx
794           || XEXP (in, 1) == stack_pointer_rtx))
795     {
796       if (TARGET_AM33)
797         return DATA_OR_EXTENDED_REGS;
798       return DATA_REGS;
799     }
800  
801   /* Otherwise assume no secondary reloads are needed.  */
802   return NO_REGS;
803 }
804
805 int
806 initial_offset (from, to)
807      int from, to;
808 {
809   /* The difference between the argument pointer and the frame pointer
810      is the size of the callee register save area.  */
811   if (from == ARG_POINTER_REGNUM && to == FRAME_POINTER_REGNUM)
812     {
813       if (regs_ever_live[2] || regs_ever_live[3]
814           || regs_ever_live[6] || regs_ever_live[7]
815           || regs_ever_live[14] || regs_ever_live[15]
816           || regs_ever_live[16] || regs_ever_live[17]
817           || frame_pointer_needed)
818         return REG_SAVE_BYTES;
819       else
820         return 0;
821     }
822
823   /* The difference between the argument pointer and the stack pointer is
824      the sum of the size of this function's frame, the callee register save
825      area, and the fixed stack space needed for function calls (if any).  */
826   if (from == ARG_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
827     {
828       if (regs_ever_live[2] || regs_ever_live[3]
829           || regs_ever_live[6] || regs_ever_live[7]
830           || regs_ever_live[14] || regs_ever_live[15]
831           || regs_ever_live[16] || regs_ever_live[17]
832           || frame_pointer_needed)
833         return (get_frame_size () + REG_SAVE_BYTES
834                 + (current_function_outgoing_args_size
835                    ? current_function_outgoing_args_size + 4 : 0)); 
836       else
837         return (get_frame_size ()
838                 + (current_function_outgoing_args_size
839                    ? current_function_outgoing_args_size + 4 : 0)); 
840     }
841
842   /* The difference between the frame pointer and stack pointer is the sum
843      of the size of this function's frame and the fixed stack space needed
844      for function calls (if any).  */
845   if (from == FRAME_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
846     return (get_frame_size ()
847             + (current_function_outgoing_args_size
848                ? current_function_outgoing_args_size + 4 : 0)); 
849
850   abort ();
851 }
852
853 /* Flush the argument registers to the stack for a stdarg function;
854    return the new argument pointer.  */
855 rtx
856 mn10300_builtin_saveregs ()
857 {
858   rtx offset, mem;
859   tree fntype = TREE_TYPE (current_function_decl);
860   int argadj = ((!(TYPE_ARG_TYPES (fntype) != 0
861                    && (TREE_VALUE (tree_last (TYPE_ARG_TYPES (fntype)))
862                        != void_type_node)))
863                 ? UNITS_PER_WORD : 0);
864   int set = get_varargs_alias_set ();
865
866   if (argadj)
867     offset = plus_constant (current_function_arg_offset_rtx, argadj);
868   else
869     offset = current_function_arg_offset_rtx;
870
871   mem = gen_rtx_MEM (SImode, current_function_internal_arg_pointer);
872   MEM_ALIAS_SET (mem) = set;
873   emit_move_insn (mem, gen_rtx_REG (SImode, 0));
874
875   mem = gen_rtx_MEM (SImode,
876                      plus_constant (current_function_internal_arg_pointer, 4));
877   MEM_ALIAS_SET (mem) = set;
878   emit_move_insn (mem, gen_rtx_REG (SImode, 1));
879
880   return copy_to_reg (expand_binop (Pmode, add_optab,
881                                     current_function_internal_arg_pointer,
882                                     offset, 0, 0, OPTAB_LIB_WIDEN));
883 }
884
885 void
886 mn10300_va_start (stdarg_p, valist, nextarg)
887      int stdarg_p;
888      tree valist;
889      rtx nextarg;
890 {
891   if (stdarg_p)
892     nextarg = expand_builtin_saveregs ();
893
894   std_expand_builtin_va_start (stdarg_p, valist, nextarg);
895 }
896
897 rtx
898 mn10300_va_arg (valist, type)
899      tree valist, type;
900 {
901   HOST_WIDE_INT align, rsize;
902   tree t, ptr, pptr;
903
904   /* Compute the rounded size of the type.  */
905   align = PARM_BOUNDARY / BITS_PER_UNIT;
906   rsize = (((int_size_in_bytes (type) + align - 1) / align) * align);
907
908   t = build (POSTINCREMENT_EXPR, TREE_TYPE (valist), valist, 
909              build_int_2 ((rsize > 8 ? 4 : rsize), 0));
910   TREE_SIDE_EFFECTS (t) = 1;
911
912   ptr = build_pointer_type (type);
913
914   /* "Large" types are passed by reference.  */
915   if (rsize > 8)
916     {
917       pptr = build_pointer_type (ptr);
918       t = build1 (NOP_EXPR, pptr, t);
919       TREE_SIDE_EFFECTS (t) = 1;
920
921       t = build1 (INDIRECT_REF, ptr, t);
922       TREE_SIDE_EFFECTS (t) = 1;
923     }
924   else
925     {
926       t = build1 (NOP_EXPR, ptr, t);
927       TREE_SIDE_EFFECTS (t) = 1;
928     }
929
930   /* Calculate!  */
931   return expand_expr (t, NULL_RTX, Pmode, EXPAND_NORMAL);
932 }
933
934 /* Return an RTX to represent where a value with mode MODE will be returned
935    from a function.  If the result is 0, the argument is pushed.  */
936
937 rtx
938 function_arg (cum, mode, type, named)
939      CUMULATIVE_ARGS *cum;
940      enum machine_mode mode;
941      tree type;
942      int named ATTRIBUTE_UNUSED;
943 {
944   rtx result = 0;
945   int size, align;
946
947   /* We only support using 2 data registers as argument registers.  */
948   int nregs = 2;
949
950   /* Figure out the size of the object to be passed.  */
951   if (mode == BLKmode)
952     size = int_size_in_bytes (type);
953   else
954     size = GET_MODE_SIZE (mode);
955
956   /* Figure out the alignment of the object to be passed.  */
957   align = size;
958
959   cum->nbytes = (cum->nbytes + 3) & ~3;
960
961   /* Don't pass this arg via a register if all the argument registers
962      are used up.  */
963   if (cum->nbytes > nregs * UNITS_PER_WORD)
964     return 0;
965
966   /* Don't pass this arg via a register if it would be split between
967      registers and memory.  */
968   if (type == NULL_TREE
969       && cum->nbytes + size > nregs * UNITS_PER_WORD)
970     return 0;
971
972   switch (cum->nbytes / UNITS_PER_WORD)
973     {
974     case 0:
975       result = gen_rtx_REG (mode, 0);
976       break;
977     case 1:
978       result = gen_rtx_REG (mode, 1);
979       break;
980     default:
981       result = 0;
982     }
983
984   return result;
985 }
986
987 /* Return the number of registers to use for an argument passed partially
988    in registers and partially in memory.  */
989
990 int
991 function_arg_partial_nregs (cum, mode, type, named)
992      CUMULATIVE_ARGS *cum;
993      enum machine_mode mode;
994      tree type;
995      int named ATTRIBUTE_UNUSED;
996 {
997   int size, align;
998
999   /* We only support using 2 data registers as argument registers.  */
1000   int nregs = 2;
1001
1002   /* Figure out the size of the object to be passed.  */
1003   if (mode == BLKmode)
1004     size = int_size_in_bytes (type);
1005   else
1006     size = GET_MODE_SIZE (mode);
1007
1008   /* Figure out the alignment of the object to be passed.  */
1009   align = size;
1010
1011   cum->nbytes = (cum->nbytes + 3) & ~3;
1012
1013   /* Don't pass this arg via a register if all the argument registers
1014      are used up.  */
1015   if (cum->nbytes > nregs * UNITS_PER_WORD)
1016     return 0;
1017
1018   if (cum->nbytes + size <= nregs * UNITS_PER_WORD)
1019     return 0;
1020
1021   /* Don't pass this arg via a register if it would be split between
1022      registers and memory.  */
1023   if (type == NULL_TREE
1024       && cum->nbytes + size > nregs * UNITS_PER_WORD)
1025     return 0;
1026
1027   return (nregs * UNITS_PER_WORD - cum->nbytes) / UNITS_PER_WORD;
1028 }
1029
1030 /* Output a tst insn.  */
1031 char *
1032 output_tst (operand, insn)
1033      rtx operand, insn;
1034 {
1035   rtx temp;
1036   int past_call = 0;
1037
1038   /* We can save a byte if we can find a register which has the value
1039      zero in it.  */
1040   temp = PREV_INSN (insn);
1041   while (optimize && temp)
1042     {
1043       rtx set;
1044
1045       /* We allow the search to go through call insns.  We record
1046          the fact that we've past a CALL_INSN and reject matches which
1047          use call clobbered registers.  */
1048       if (GET_CODE (temp) == CODE_LABEL
1049           || GET_CODE (temp) == JUMP_INSN
1050           || GET_CODE (temp) == BARRIER)
1051         break;
1052
1053       if (GET_CODE (temp) == CALL_INSN)
1054         past_call = 1;
1055
1056       if (GET_CODE (temp) == NOTE)
1057         {
1058           temp = PREV_INSN (temp);
1059           continue;
1060         }
1061
1062       /* It must be an insn, see if it is a simple set. */
1063       set = single_set (temp);
1064       if (!set)
1065         {
1066           temp = PREV_INSN (temp);
1067           continue;
1068         }
1069
1070       /* Are we setting a data register to zero (this does not win for
1071          address registers)? 
1072
1073          If it's a call clobbered register, have we past a call?
1074
1075          Make sure the register we find isn't the same as ourself;
1076          the mn10300 can't encode that.
1077
1078          ??? reg_set_between_p return nonzero anytime we pass a CALL_INSN
1079          so the code to detect calls here isn't doing anything useful.  */
1080       if (REG_P (SET_DEST (set))
1081           && SET_SRC (set) == CONST0_RTX (GET_MODE (SET_DEST (set)))
1082           && !reg_set_between_p (SET_DEST (set), temp, insn)
1083           && (REGNO_REG_CLASS (REGNO (SET_DEST (set)))
1084               == REGNO_REG_CLASS (REGNO (operand)))
1085           && REGNO_REG_CLASS (REGNO (SET_DEST (set))) != EXTENDED_REGS
1086           && REGNO (SET_DEST (set)) != REGNO (operand)
1087           && (!past_call 
1088               || !call_used_regs[REGNO (SET_DEST (set))]))
1089         {
1090           rtx xoperands[2];
1091           xoperands[0] = operand;
1092           xoperands[1] = SET_DEST (set);
1093
1094           output_asm_insn ("cmp %1,%0", xoperands);
1095           return "";
1096         }
1097
1098       if (REGNO_REG_CLASS (REGNO (operand)) == EXTENDED_REGS
1099           && REG_P (SET_DEST (set))
1100           && SET_SRC (set) == CONST0_RTX (GET_MODE (SET_DEST (set)))
1101           && !reg_set_between_p (SET_DEST (set), temp, insn)
1102           && (REGNO_REG_CLASS (REGNO (SET_DEST (set)))
1103               != REGNO_REG_CLASS (REGNO (operand)))
1104           && REGNO_REG_CLASS (REGNO (SET_DEST (set))) == EXTENDED_REGS
1105           && REGNO (SET_DEST (set)) != REGNO (operand)
1106           && (!past_call 
1107               || !call_used_regs[REGNO (SET_DEST (set))]))
1108         {
1109           rtx xoperands[2];
1110           xoperands[0] = operand;
1111           xoperands[1] = SET_DEST (set);
1112
1113           output_asm_insn ("cmp %1,%0", xoperands);
1114           return "";
1115         }
1116       temp = PREV_INSN (temp);
1117     }
1118   return "cmp 0,%0";
1119 }
1120
1121 int
1122 impossible_plus_operand (op, mode)
1123      rtx op;
1124      enum machine_mode mode ATTRIBUTE_UNUSED;
1125 {
1126   if (GET_CODE (op) != PLUS)
1127     return 0;
1128
1129   if (XEXP (op, 0) == stack_pointer_rtx
1130       || XEXP (op, 1) == stack_pointer_rtx)
1131     return 1;
1132
1133   return 0;
1134 }
1135
1136 /* Return 1 if X is a CONST_INT that is only 8 bits wide.  This is used
1137    for the btst insn which may examine memory or a register (the memory
1138    variant only allows an unsigned 8 bit integer).  */
1139 int
1140 const_8bit_operand (op, mode)
1141     register rtx op;
1142     enum machine_mode mode ATTRIBUTE_UNUSED;
1143 {
1144   return (GET_CODE (op) == CONST_INT
1145           && INTVAL (op) >= 0
1146           && INTVAL (op) < 256);
1147 }
1148
1149 /* Similarly, but when using a zero_extract pattern for a btst where
1150    the source operand might end up in memory.  */
1151 int
1152 mask_ok_for_mem_btst (len, bit)
1153      int len;
1154      int bit;
1155 {
1156   int mask = 0;
1157
1158   while (len > 0)
1159     {
1160       mask |= (1 << bit);
1161       bit++;
1162       len--;
1163     }
1164
1165   /* MASK must bit into an 8bit value.  */
1166   return (((mask & 0xff) == mask)
1167           || ((mask & 0xff00) == mask)
1168           || ((mask & 0xff0000) == mask)
1169           || ((mask & 0xff000000) == mask));
1170 }
1171
1172 /* Return 1 if X contains a symbolic expression.  We know these
1173    expressions will have one of a few well defined forms, so
1174    we need only check those forms.  */
1175 int
1176 symbolic_operand (op, mode)
1177      register rtx op;
1178      enum machine_mode mode ATTRIBUTE_UNUSED;
1179 {
1180   switch (GET_CODE (op))
1181     {
1182     case SYMBOL_REF:
1183     case LABEL_REF:
1184       return 1;
1185     case CONST:
1186       op = XEXP (op, 0);
1187       return ((GET_CODE (XEXP (op, 0)) == SYMBOL_REF
1188                || GET_CODE (XEXP (op, 0)) == LABEL_REF)
1189               && GET_CODE (XEXP (op, 1)) == CONST_INT);
1190     default:
1191       return 0;
1192     }
1193 }
1194
1195 /* Try machine dependent ways of modifying an illegitimate address
1196    to be legitimate.  If we find one, return the new valid address.
1197    This macro is used in only one place: `memory_address' in explow.c.
1198
1199    OLDX is the address as it was before break_out_memory_refs was called.
1200    In some cases it is useful to look at this to decide what needs to be done.
1201
1202    MODE and WIN are passed so that this macro can use
1203    GO_IF_LEGITIMATE_ADDRESS.
1204
1205    Normally it is always safe for this macro to do nothing.  It exists to
1206    recognize opportunities to optimize the output.
1207
1208    But on a few ports with segmented architectures and indexed addressing
1209    (mn10300, hppa) it is used to rewrite certain problematical addresses.  */
1210 rtx
1211 legitimize_address (x, oldx, mode)
1212      rtx x;
1213      rtx oldx ATTRIBUTE_UNUSED;
1214      enum machine_mode mode ATTRIBUTE_UNUSED;
1215 {
1216   /* Uh-oh.  We might have an address for x[n-100000].  This needs
1217      special handling to avoid creating an indexed memory address
1218      with x-100000 as the base.  */
1219   if (GET_CODE (x) == PLUS
1220       && symbolic_operand (XEXP (x, 1), VOIDmode))
1221     {
1222       /* Ugly.  We modify things here so that the address offset specified
1223          by the index expression is computed first, then added to x to form
1224          the entire address.  */
1225
1226       rtx regx1, regy1, regy2, y;
1227
1228       /* Strip off any CONST.  */
1229       y = XEXP (x, 1);
1230       if (GET_CODE (y) == CONST)
1231         y = XEXP (y, 0);
1232
1233       if (GET_CODE (y) == PLUS || GET_CODE (y) == MINUS)
1234         {
1235           regx1 = force_reg (Pmode, force_operand (XEXP (x, 0), 0));
1236           regy1 = force_reg (Pmode, force_operand (XEXP (y, 0), 0));
1237           regy2 = force_reg (Pmode, force_operand (XEXP (y, 1), 0));
1238           regx1 = force_reg (Pmode,
1239                              gen_rtx (GET_CODE (y), Pmode, regx1, regy2));
1240           return force_reg (Pmode, gen_rtx_PLUS (Pmode, regx1, regy1));
1241         }
1242     }
1243   return x;
1244 }
1245
1246 int
1247 mn10300_address_cost (x, unsig)
1248      rtx x;
1249      int *unsig;
1250 {
1251   int _s = 0;
1252   if (unsig == 0)
1253     unsig = &_s;
1254   
1255   switch (GET_CODE (x))
1256     {
1257     case REG:
1258       switch (REGNO_REG_CLASS (REGNO (x)))
1259         {
1260         case SP_REGS:
1261           *unsig = 1;
1262           return 0;
1263
1264         case ADDRESS_REGS:
1265           return 1;
1266
1267         case DATA_REGS:
1268         case EXTENDED_REGS:
1269           return 3;
1270
1271         case NO_REGS:
1272           return 5;
1273
1274         default:
1275           abort ();
1276         }
1277
1278     case PLUS:
1279     case MINUS:
1280     case ASHIFT:
1281     case AND:
1282     case IOR:
1283       return (mn10300_address_cost (XEXP (x, 0), unsig)
1284               + mn10300_address_cost (XEXP (x, 1), unsig));
1285
1286     case EXPR_LIST:
1287     case SUBREG:
1288     case MEM:
1289       return ADDRESS_COST (XEXP (x, 0));
1290
1291     case ZERO_EXTEND:
1292       *unsig = 1;
1293       return mn10300_address_cost (XEXP (x, 0), unsig);
1294
1295     case CONST_INT:
1296       if (INTVAL (x) == 0)
1297         return 0;
1298       if (INTVAL (x) + (*unsig ? 0 : 0x80) < 0x100)
1299         return 1;
1300       if (INTVAL (x) + (*unsig ? 0 : 0x8000) < 0x10000)
1301         return 3;
1302       if (INTVAL (x) + (*unsig ? 0 : 0x800000) < 0x1000000)
1303         return 5;
1304       return 7;
1305
1306     case CONST:
1307     case SYMBOL_REF:
1308     case LABEL_REF:
1309       return 8;
1310
1311     case ADDRESSOF:
1312       switch (GET_CODE (XEXP (x, 0)))
1313         {
1314         case MEM:
1315           return ADDRESS_COST (XEXP (x, 0));
1316
1317         case REG:
1318           return 1;
1319
1320         default:
1321           abort ();
1322         }
1323
1324     default:
1325       abort ();
1326
1327     }
1328 }