OSDN Git Service

* target.h (struct gcc_target): Add calls.pass_by_reference.
[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, 2002, 2003, 2004
3    Free Software Foundation, Inc.
4    Contributed by Jeff Law (law@cygnus.com).
5
6 This file is part of GCC.
7
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 2, or (at your option)
11 any later version.
12
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.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; 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 "coretypes.h"
26 #include "tm.h"
27 #include "rtl.h"
28 #include "tree.h"
29 #include "regs.h"
30 #include "hard-reg-set.h"
31 #include "real.h"
32 #include "insn-config.h"
33 #include "conditions.h"
34 #include "output.h"
35 #include "insn-attr.h"
36 #include "flags.h"
37 #include "recog.h"
38 #include "expr.h"
39 #include "optabs.h"
40 #include "function.h"
41 #include "obstack.h"
42 #include "toplev.h"
43 #include "tm_p.h"
44 #include "target.h"
45 #include "target-def.h"
46
47 /* This is used by GOTaddr2picreg to uniquely identify
48    UNSPEC_INT_LABELs.  */
49 int mn10300_unspec_int_label_counter;
50
51 /* This is used in the am33_2.0-linux-gnu port, in which global symbol
52    names are not prefixed by underscores, to tell whether to prefix a
53    label with a plus sign or not, so that the assembler can tell
54    symbol names from register names.  */
55 int mn10300_protect_label;
56
57 /* The size of the callee register save area.  Right now we save everything
58    on entry since it costs us nothing in code size.  It does cost us from a
59    speed standpoint, so we want to optimize this sooner or later.  */
60 #define REG_SAVE_BYTES (4 * regs_ever_live[2] \
61                         + 4 * regs_ever_live[3] \
62                         + 4 * regs_ever_live[6] \
63                         + 4 * regs_ever_live[7] \
64                         + 16 * (regs_ever_live[14] || regs_ever_live[15] \
65                                 || regs_ever_live[16] || regs_ever_live[17]))
66
67
68 static int mn10300_address_cost_1 (rtx, int *);
69 static int mn10300_address_cost (rtx);
70 static bool mn10300_rtx_costs (rtx, int, int, int *);
71 static void mn10300_file_start (void);
72 static bool mn10300_return_in_memory (tree, tree);
73 static rtx mn10300_builtin_saveregs (void);
74 static bool mn10300_pass_by_reference (CUMULATIVE_ARGS *, enum machine_mode,
75                                        tree, bool);
76 \f
77 /* Initialize the GCC target structure.  */
78 #undef TARGET_ASM_ALIGNED_HI_OP
79 #define TARGET_ASM_ALIGNED_HI_OP "\t.hword\t"
80
81 #undef TARGET_RTX_COSTS
82 #define TARGET_RTX_COSTS mn10300_rtx_costs
83 #undef TARGET_ADDRESS_COST
84 #define TARGET_ADDRESS_COST mn10300_address_cost
85
86 #undef TARGET_ASM_FILE_START
87 #define TARGET_ASM_FILE_START mn10300_file_start
88 #undef TARGET_ASM_FILE_START_FILE_DIRECTIVE
89 #define TARGET_ASM_FILE_START_FILE_DIRECTIVE true
90
91 #undef  TARGET_ENCODE_SECTION_INFO
92 #define TARGET_ENCODE_SECTION_INFO mn10300_encode_section_info
93
94 #undef TARGET_PROMOTE_PROTOTYPES
95 #define TARGET_PROMOTE_PROTOTYPES hook_bool_tree_true
96 #undef TARGET_RETURN_IN_MEMORY
97 #define TARGET_RETURN_IN_MEMORY mn10300_return_in_memory
98 #undef TARGET_PASS_BY_REFERENCE
99 #define TARGET_PASS_BY_REFERENCE mn10300_pass_by_reference
100
101 #undef TARGET_EXPAND_BUILTIN_SAVEREGS
102 #define TARGET_EXPAND_BUILTIN_SAVEREGS mn10300_builtin_saveregs
103
104 static void mn10300_encode_section_info (tree, rtx, int);
105 struct gcc_target targetm = TARGET_INITIALIZER;
106 \f
107 static void
108 mn10300_file_start (void)
109 {
110   default_file_start ();
111
112   if (TARGET_AM33_2)
113     fprintf (asm_out_file, "\t.am33_2\n");
114   else if (TARGET_AM33)
115     fprintf (asm_out_file, "\t.am33\n");
116 }
117 \f
118
119 /* Print operand X using operand code CODE to assembly language output file
120    FILE.  */
121
122 void
123 print_operand (FILE *file, rtx x, int code)
124 {
125   switch (code)
126     {
127       case 'b':
128       case 'B':
129         if (cc_status.mdep.fpCC)
130           {
131             switch (code == 'b' ? GET_CODE (x)
132                     : reverse_condition_maybe_unordered (GET_CODE (x)))
133               {
134               case NE:
135                 fprintf (file, "ne");
136                 break;
137               case EQ:
138                 fprintf (file, "eq");
139                 break;
140               case GE:
141                 fprintf (file, "ge");
142                 break;
143               case GT:
144                 fprintf (file, "gt");
145                 break;
146               case LE:
147                 fprintf (file, "le");
148                 break;
149               case LT:
150                 fprintf (file, "lt");
151                 break;
152               case ORDERED:
153                 fprintf (file, "lge");
154                 break;
155               case UNORDERED:
156                 fprintf (file, "uo");
157                 break;
158               case LTGT:
159                 fprintf (file, "lg");
160                 break;
161               case UNEQ:
162                 fprintf (file, "ue");
163                 break;
164               case UNGE:
165                 fprintf (file, "uge");
166                 break;
167               case UNGT:
168                 fprintf (file, "ug");
169                 break;
170               case UNLE:
171                 fprintf (file, "ule");
172                 break;
173               case UNLT:
174                 fprintf (file, "ul");
175                 break;
176               default:
177                 abort ();
178               }
179             break;
180           }
181         /* These are normal and reversed branches.  */
182         switch (code == 'b' ? GET_CODE (x) : reverse_condition (GET_CODE (x)))
183           {
184           case NE:
185             fprintf (file, "ne");
186             break;
187           case EQ:
188             fprintf (file, "eq");
189             break;
190           case GE:
191             fprintf (file, "ge");
192             break;
193           case GT:
194             fprintf (file, "gt");
195             break;
196           case LE:
197             fprintf (file, "le");
198             break;
199           case LT:
200             fprintf (file, "lt");
201             break;
202           case GEU:
203             fprintf (file, "cc");
204             break;
205           case GTU:
206             fprintf (file, "hi");
207             break;
208           case LEU:
209             fprintf (file, "ls");
210             break;
211           case LTU:
212             fprintf (file, "cs");
213             break;
214           default:
215             abort ();
216           }
217         break;
218       case 'C':
219         /* This is used for the operand to a call instruction;
220            if it's a REG, enclose it in parens, else output
221            the operand normally.  */
222         if (GET_CODE (x) == REG)
223           {
224             fputc ('(', file);
225             print_operand (file, x, 0);
226             fputc (')', file);
227           }
228         else
229           print_operand (file, x, 0);
230         break;
231      
232       case 'D':
233         switch (GET_CODE (x))
234           {
235           case MEM:
236             fputc ('(', file);
237             output_address (XEXP (x, 0));
238             fputc (')', file);
239             break;
240
241           case REG:
242             fprintf (file, "fd%d", REGNO (x) - 18);
243             break;
244
245           default:
246             abort ();
247           }
248         break;
249
250       /* These are the least significant word in a 64bit value.  */
251       case 'L':
252         switch (GET_CODE (x))
253           {
254           case MEM:
255             fputc ('(', file);
256             output_address (XEXP (x, 0));
257             fputc (')', file);
258             break;
259
260           case REG:
261             fprintf (file, "%s", reg_names[REGNO (x)]);
262             break;
263
264           case SUBREG:
265             fprintf (file, "%s", reg_names[subreg_regno (x)]);
266             break;
267
268           case CONST_DOUBLE:
269               {
270                 long val[2];
271                 REAL_VALUE_TYPE rv;
272
273                 switch (GET_MODE (x))
274                   {
275                     case DFmode:
276                       REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
277                       REAL_VALUE_TO_TARGET_DOUBLE (rv, val);
278                       fprintf (file, "0x%lx", val[0]);
279                       break;;
280                     case SFmode:
281                       REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
282                       REAL_VALUE_TO_TARGET_SINGLE (rv, val[0]);
283                       fprintf (file, "0x%lx", val[0]);
284                       break;;
285                     case VOIDmode:
286                     case DImode:
287                       print_operand_address (file,
288                                              GEN_INT (CONST_DOUBLE_LOW (x)));
289                       break;
290                     default:
291                       break;
292                   }
293                 break;
294               }
295
296           case CONST_INT:
297             {
298               rtx low, high;
299               split_double (x, &low, &high);
300               fprintf (file, "%ld", (long)INTVAL (low));
301               break;
302             }
303
304           default:
305             abort ();
306           }
307         break;
308
309       /* Similarly, but for the most significant word.  */
310       case 'H':
311         switch (GET_CODE (x))
312           {
313           case MEM:
314             fputc ('(', file);
315             x = adjust_address (x, SImode, 4);
316             output_address (XEXP (x, 0));
317             fputc (')', file);
318             break;
319
320           case REG:
321             fprintf (file, "%s", reg_names[REGNO (x) + 1]);
322             break;
323
324           case SUBREG:
325             fprintf (file, "%s", reg_names[subreg_regno (x) + 1]);
326             break;
327
328           case CONST_DOUBLE:
329               {
330                 long val[2];
331                 REAL_VALUE_TYPE rv;
332
333                 switch (GET_MODE (x))
334                   {
335                     case DFmode:
336                       REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
337                       REAL_VALUE_TO_TARGET_DOUBLE (rv, val);
338                       fprintf (file, "0x%lx", val[1]);
339                       break;;
340                     case SFmode:
341                       abort ();
342                     case VOIDmode:
343                     case DImode:
344                       print_operand_address (file, 
345                                              GEN_INT (CONST_DOUBLE_HIGH (x)));
346                       break;
347                     default:
348                       break;
349                   }
350                 break;
351               }
352
353           case CONST_INT:
354             {
355               rtx low, high;
356               split_double (x, &low, &high);
357               fprintf (file, "%ld", (long)INTVAL (high));
358               break;
359             }
360
361           default:
362             abort ();
363           }
364         break;
365
366       case 'A':
367         fputc ('(', file);
368         if (GET_CODE (XEXP (x, 0)) == REG)
369           output_address (gen_rtx_PLUS (SImode, XEXP (x, 0), const0_rtx));
370         else
371           output_address (XEXP (x, 0));
372         fputc (')', file);
373         break;
374
375       case 'N':
376         if (INTVAL (x) < -128 || INTVAL (x) > 255)
377           abort ();
378         fprintf (file, "%d", (int)((~INTVAL (x)) & 0xff));
379         break;
380
381       case 'U':
382         if (INTVAL (x) < -128 || INTVAL (x) > 255)
383           abort ();
384         fprintf (file, "%d", (int)(INTVAL (x) & 0xff));
385         break;
386
387       /* For shift counts.  The hardware ignores the upper bits of
388          any immediate, but the assembler will flag an out of range
389          shift count as an error.  So we mask off the high bits
390          of the immediate here.  */
391       case 'S':
392         if (GET_CODE (x) == CONST_INT)
393           {
394             fprintf (file, "%d", (int)(INTVAL (x) & 0x1f));
395             break;
396           }
397         /* FALL THROUGH */
398
399       default:
400         switch (GET_CODE (x))
401           {
402           case MEM:
403             fputc ('(', file);
404             output_address (XEXP (x, 0));
405             fputc (')', file);
406             break;
407
408           case PLUS:
409             output_address (x);
410             break;
411
412           case REG:
413             fprintf (file, "%s", reg_names[REGNO (x)]);
414             break;
415
416           case SUBREG:
417             fprintf (file, "%s", reg_names[subreg_regno (x)]);
418             break;
419
420           /* This will only be single precision....  */
421           case CONST_DOUBLE:
422             {
423               unsigned long val;
424               REAL_VALUE_TYPE rv;
425
426               REAL_VALUE_FROM_CONST_DOUBLE (rv, x);
427               REAL_VALUE_TO_TARGET_SINGLE (rv, val);
428               fprintf (file, "0x%lx", val);
429               break;
430             }
431
432           case CONST_INT:
433           case SYMBOL_REF:
434           case CONST:
435           case LABEL_REF:
436           case CODE_LABEL:
437           case UNSPEC:
438             print_operand_address (file, x);
439             break;
440           default:
441             abort ();
442           }
443         break;
444    }
445 }
446
447 /* Output assembly language output for the address ADDR to FILE.  */
448
449 void
450 print_operand_address (FILE *file, rtx addr)
451 {
452   switch (GET_CODE (addr))
453     {
454     case POST_INC:
455       print_operand_address (file, XEXP (addr, 0));
456       fputc ('+', file);
457       break;
458     case REG:
459       print_operand (file, addr, 0);
460       break;
461     case PLUS:
462       {
463         rtx base, index;
464         if (REG_P (XEXP (addr, 0))
465             && REG_OK_FOR_BASE_P (XEXP (addr, 0)))
466           base = XEXP (addr, 0), index = XEXP (addr, 1);
467         else if (REG_P (XEXP (addr, 1))
468             && REG_OK_FOR_BASE_P (XEXP (addr, 1)))
469           base = XEXP (addr, 1), index = XEXP (addr, 0);
470         else
471           abort ();
472         print_operand (file, index, 0);
473         fputc (',', file);
474         print_operand (file, base, 0);;
475         break;
476       }
477     case SYMBOL_REF:
478       output_addr_const (file, addr);
479       break;
480     default:
481       output_addr_const (file, addr);
482       break;
483     }
484 }
485
486 /* Count the number of FP registers that have to be saved.  */
487 static int
488 fp_regs_to_save (void)
489 {
490   int i, n = 0;
491
492   if (! TARGET_AM33_2)
493     return 0;
494
495   for (i = FIRST_FP_REGNUM; i <= LAST_FP_REGNUM; ++i)
496     if (regs_ever_live[i] && ! call_used_regs[i])
497       ++n;
498
499   return n;
500 }
501
502 /* Print a set of registers in the format required by "movm" and "ret".
503    Register K is saved if bit K of MASK is set.  The data and address
504    registers can be stored individually, but the extended registers cannot.
505    We assume that the mask alread takes that into account.  For instance,
506    bits 14 to 17 must have the same value.  */
507
508 void
509 mn10300_print_reg_list (FILE *file, int mask)
510 {
511   int need_comma;
512   int i;
513
514   need_comma = 0;
515   fputc ('[', file);
516
517   for (i = 0; i < FIRST_EXTENDED_REGNUM; i++)
518     if ((mask & (1 << i)) != 0)
519       {
520         if (need_comma)
521           fputc (',', file);
522         fputs (reg_names [i], file);
523         need_comma = 1;
524       }
525
526   if ((mask & 0x3c000) != 0)
527     {
528       if ((mask & 0x3c000) != 0x3c000)
529         abort();
530       if (need_comma)
531         fputc (',', file);
532       fputs ("exreg1", file);
533       need_comma = 1;
534     }
535
536   fputc (']', file);
537 }
538
539 int
540 can_use_return_insn (void)
541 {
542   /* size includes the fixed stack space needed for function calls.  */
543   int size = get_frame_size () + current_function_outgoing_args_size;
544
545   /* And space for the return pointer.  */
546   size += current_function_outgoing_args_size ? 4 : 0;
547
548   return (reload_completed
549           && size == 0
550           && !regs_ever_live[2]
551           && !regs_ever_live[3]
552           && !regs_ever_live[6]
553           && !regs_ever_live[7]
554           && !regs_ever_live[14]
555           && !regs_ever_live[15]
556           && !regs_ever_live[16]
557           && !regs_ever_live[17]
558           && fp_regs_to_save () == 0
559           && !frame_pointer_needed);
560 }
561
562 /* Returns the set of live, callee-saved registers as a bitmask.  The
563    callee-saved extended registers cannot be stored individually, so
564    all of them will be included in the mask if any one of them is used.  */
565
566 int
567 mn10300_get_live_callee_saved_regs (void)
568 {
569   int mask;
570   int i;
571
572   mask = 0;
573   for (i = 0; i <= LAST_EXTENDED_REGNUM; i++)
574     if (regs_ever_live[i] && ! call_used_regs[i])
575       mask |= (1 << i);
576   if ((mask & 0x3c000) != 0)
577     mask |= 0x3c000;
578
579   return mask;
580 }
581
582 /* Generate an instruction that pushes several registers onto the stack.
583    Register K will be saved if bit K in MASK is set.  The function does
584    nothing if MASK is zero.
585
586    To be compatible with the "movm" instruction, the lowest-numbered
587    register must be stored in the lowest slot.  If MASK is the set
588    { R1,...,RN }, where R1...RN are ordered least first, the generated
589    instruction will have the form:
590
591        (parallel
592          (set (reg:SI 9) (plus:SI (reg:SI 9) (const_int -N*4)))
593          (set (mem:SI (plus:SI (reg:SI 9)
594                                (const_int -1*4)))
595               (reg:SI RN))
596          ...
597          (set (mem:SI (plus:SI (reg:SI 9)
598                                (const_int -N*4)))
599               (reg:SI R1))) */
600
601 void
602 mn10300_gen_multiple_store (int mask)
603 {
604   if (mask != 0)
605     {
606       int i;
607       int count;
608       rtx par;
609       int pari;
610
611       /* Count how many registers need to be saved.  */
612       count = 0;
613       for (i = 0; i <= LAST_EXTENDED_REGNUM; i++)
614         if ((mask & (1 << i)) != 0)
615           count += 1;
616
617       /* We need one PARALLEL element to update the stack pointer and
618          an additional element for each register that is stored.  */
619       par = gen_rtx_PARALLEL (VOIDmode, rtvec_alloc (count + 1));
620
621       /* Create the instruction that updates the stack pointer.  */
622       XVECEXP (par, 0, 0)
623         = gen_rtx_SET (SImode,
624                        stack_pointer_rtx,
625                        gen_rtx_PLUS (SImode,
626                                      stack_pointer_rtx,
627                                      GEN_INT (-count * 4)));
628
629       /* Create each store.  */
630       pari = 1;
631       for (i = LAST_EXTENDED_REGNUM; i >= 0; i--)
632         if ((mask & (1 << i)) != 0)
633           {
634             rtx address = gen_rtx_PLUS (SImode,
635                                         stack_pointer_rtx,
636                                         GEN_INT (-pari * 4));
637             XVECEXP(par, 0, pari)
638               = gen_rtx_SET (VOIDmode,
639                              gen_rtx_MEM (SImode, address),
640                              gen_rtx_REG (SImode, i));
641             pari += 1;
642           }
643
644       par = emit_insn (par);
645       RTX_FRAME_RELATED_P (par) = 1;
646     }
647 }
648
649 void
650 expand_prologue (void)
651 {
652   HOST_WIDE_INT size;
653
654   /* SIZE includes the fixed stack space needed for function calls.  */
655   size = get_frame_size () + current_function_outgoing_args_size;
656   size += (current_function_outgoing_args_size ? 4 : 0);
657
658   /* If we use any of the callee-saved registers, save them now.  */
659   mn10300_gen_multiple_store (mn10300_get_live_callee_saved_regs ());
660
661   if (TARGET_AM33_2 && fp_regs_to_save ())
662     {
663       int num_regs_to_save = fp_regs_to_save (), i;
664       HOST_WIDE_INT xsize;
665       enum { save_sp_merge,
666              save_sp_no_merge,
667              save_sp_partial_merge,
668              save_a0_merge,
669              save_a0_no_merge } strategy;
670       unsigned int strategy_size = (unsigned)-1, this_strategy_size;
671       rtx reg;
672       rtx insn;
673
674       /* We have several different strategies to save FP registers.
675          We can store them using SP offsets, which is beneficial if
676          there are just a few registers to save, or we can use `a0' in
677          post-increment mode (`a0' is the only call-clobbered address
678          register that is never used to pass information to a
679          function).  Furthermore, if we don't need a frame pointer, we
680          can merge the two SP adds into a single one, but this isn't
681          always beneficial; sometimes we can just split the two adds
682          so that we don't exceed a 16-bit constant size.  The code
683          below will select which strategy to use, so as to generate
684          smallest code.  Ties are broken in favor or shorter sequences
685          (in terms of number of instructions).  */
686
687 #define SIZE_ADD_AX(S) ((((S) >= (1 << 15)) || ((S) < -(1 << 15))) ? 6 \
688                         : (((S) >= (1 << 7)) || ((S) < -(1 << 7))) ? 4 : 2)
689 #define SIZE_ADD_SP(S) ((((S) >= (1 << 15)) || ((S) < -(1 << 15))) ? 6 \
690                         : (((S) >= (1 << 7)) || ((S) < -(1 << 7))) ? 4 : 3)
691 #define SIZE_FMOV_LIMIT(S,N,L,SIZE1,SIZE2,ELSE) \
692   (((S) >= (L)) ? (SIZE1) * (N) \
693    : ((S) + 4 * (N) >= (L)) ? (((L) - (S)) / 4 * (SIZE2) \
694                                + ((S) + 4 * (N) - (L)) / 4 * (SIZE1)) \
695    : (ELSE))
696 #define SIZE_FMOV_SP_(S,N) \
697   (SIZE_FMOV_LIMIT ((S), (N), (1 << 24), 7, 6, \
698                    SIZE_FMOV_LIMIT ((S), (N), (1 << 8), 6, 4, \
699                                     (S) ? 4 * (N) : 3 + 4 * ((N) - 1))))
700 #define SIZE_FMOV_SP(S,N) (SIZE_FMOV_SP_ ((unsigned HOST_WIDE_INT)(S), (N)))
701
702       /* Consider alternative save_sp_merge only if we don't need the
703          frame pointer and size is nonzero.  */
704       if (! frame_pointer_needed && size)
705         {
706           /* Insn: add -(size + 4 * num_regs_to_save), sp.  */
707           this_strategy_size = SIZE_ADD_SP (-(size + 4 * num_regs_to_save));
708           /* Insn: fmov fs#, (##, sp), for each fs# to be saved.  */
709           this_strategy_size += SIZE_FMOV_SP (size, num_regs_to_save);
710
711           if (this_strategy_size < strategy_size)
712             {
713               strategy = save_sp_merge;
714               strategy_size = this_strategy_size;
715             }
716         }
717
718       /* Consider alternative save_sp_no_merge unconditionally.  */
719       /* Insn: add -4 * num_regs_to_save, sp.  */
720       this_strategy_size = SIZE_ADD_SP (-4 * num_regs_to_save);
721       /* Insn: fmov fs#, (##, sp), for each fs# to be saved.  */
722       this_strategy_size += SIZE_FMOV_SP (0, num_regs_to_save);
723       if (size)
724         {
725           /* Insn: add -size, sp.  */
726           this_strategy_size += SIZE_ADD_SP (-size);
727         }
728
729       if (this_strategy_size < strategy_size)
730         {
731           strategy = save_sp_no_merge;
732           strategy_size = this_strategy_size;
733         }
734
735       /* Consider alternative save_sp_partial_merge only if we don't
736          need a frame pointer and size is reasonably large.  */
737       if (! frame_pointer_needed && size + 4 * num_regs_to_save > 128)
738         {
739           /* Insn: add -128, sp.  */
740           this_strategy_size = SIZE_ADD_SP (-128);
741           /* Insn: fmov fs#, (##, sp), for each fs# to be saved.  */
742           this_strategy_size += SIZE_FMOV_SP (128 - 4 * num_regs_to_save,
743                                               num_regs_to_save);
744           if (size)
745             {
746               /* Insn: add 128-size, sp.  */
747               this_strategy_size += SIZE_ADD_SP (128 - size);
748             }
749
750           if (this_strategy_size < strategy_size)
751             {
752               strategy = save_sp_partial_merge;
753               strategy_size = this_strategy_size;
754             }
755         }
756
757       /* Consider alternative save_a0_merge only if we don't need a
758          frame pointer, size is nonzero and the user hasn't
759          changed the calling conventions of a0.  */
760       if (! frame_pointer_needed && size
761           && call_used_regs[FIRST_ADDRESS_REGNUM]
762           && ! fixed_regs[FIRST_ADDRESS_REGNUM])
763         {
764           /* Insn: add -(size + 4 * num_regs_to_save), sp.  */
765           this_strategy_size = SIZE_ADD_SP (-(size + 4 * num_regs_to_save));
766           /* Insn: mov sp, a0.  */
767           this_strategy_size++;
768           if (size)
769             {
770               /* Insn: add size, a0.  */
771               this_strategy_size += SIZE_ADD_AX (size);
772             }
773           /* Insn: fmov fs#, (a0+), for each fs# to be saved.  */
774           this_strategy_size += 3 * num_regs_to_save;
775
776           if (this_strategy_size < strategy_size)
777             {
778               strategy = save_a0_merge;
779               strategy_size = this_strategy_size;
780             }
781         }
782
783       /* Consider alternative save_a0_no_merge if the user hasn't
784          changed the calling conventions of a0.  */
785       if (call_used_regs[FIRST_ADDRESS_REGNUM]
786           && ! fixed_regs[FIRST_ADDRESS_REGNUM])
787         {
788           /* Insn: add -4 * num_regs_to_save, sp.  */
789           this_strategy_size = SIZE_ADD_SP (-4 * num_regs_to_save);
790           /* Insn: mov sp, a0.  */
791           this_strategy_size++;
792           /* Insn: fmov fs#, (a0+), for each fs# to be saved.  */
793           this_strategy_size += 3 * num_regs_to_save;
794           if (size)
795             {
796               /* Insn: add -size, sp.  */
797               this_strategy_size += SIZE_ADD_SP (-size);
798             }
799
800           if (this_strategy_size < strategy_size)
801             {
802               strategy = save_a0_no_merge;
803               strategy_size = this_strategy_size;
804             }
805         }
806
807       /* Emit the initial SP add, common to all strategies.  */
808       switch (strategy)
809         {
810         case save_sp_no_merge:
811         case save_a0_no_merge:
812           emit_insn (gen_addsi3 (stack_pointer_rtx,
813                                  stack_pointer_rtx,
814                                  GEN_INT (-4 * num_regs_to_save)));
815           xsize = 0;
816           break;
817
818         case save_sp_partial_merge:
819           emit_insn (gen_addsi3 (stack_pointer_rtx,
820                                  stack_pointer_rtx,
821                                  GEN_INT (-128)));
822           xsize = 128 - 4 * num_regs_to_save;
823           size -= xsize;
824           break;
825
826         case save_sp_merge:
827         case save_a0_merge:
828           emit_insn (gen_addsi3 (stack_pointer_rtx,
829                                  stack_pointer_rtx,
830                                  GEN_INT (-(size + 4 * num_regs_to_save))));
831           /* We'll have to adjust FP register saves according to the
832              frame size.  */
833           xsize = size;
834           /* Since we've already created the stack frame, don't do it
835              again at the end of the function.  */
836           size = 0;
837           break;
838
839         default:
840           abort ();
841         }
842           
843       /* Now prepare register a0, if we have decided to use it.  */
844       switch (strategy)
845         {
846         case save_sp_merge:
847         case save_sp_no_merge:
848         case save_sp_partial_merge:
849           reg = 0;
850           break;
851
852         case save_a0_merge:
853         case save_a0_no_merge:
854           reg = gen_rtx_REG (SImode, FIRST_ADDRESS_REGNUM);
855           emit_insn (gen_movsi (reg, stack_pointer_rtx));
856           if (xsize)
857             emit_insn (gen_addsi3 (reg, reg, GEN_INT (xsize)));
858           reg = gen_rtx_POST_INC (SImode, reg);
859           break;
860           
861         default:
862           abort ();
863         }
864       
865       /* Now actually save the FP registers.  */
866       for (i = FIRST_FP_REGNUM; i <= LAST_FP_REGNUM; ++i)
867         if (regs_ever_live[i] && ! call_used_regs[i])
868           {
869             rtx addr;
870
871             if (reg)
872               addr = reg;
873             else
874               {
875                 /* If we aren't using `a0', use an SP offset.  */
876                 if (xsize)
877                   {
878                     addr = gen_rtx_PLUS (SImode,
879                                          stack_pointer_rtx,
880                                          GEN_INT (xsize));
881                   }
882                 else
883                   addr = stack_pointer_rtx;
884                 
885                 xsize += 4;
886               }
887
888             insn = emit_insn (gen_movsi (gen_rtx_MEM (SImode, addr),
889                                          gen_rtx_REG (SImode, i)));
890
891             RTX_FRAME_RELATED_P (insn) = 1;
892           }
893     }
894
895   /* Now put the frame pointer into the frame pointer register.  */
896   if (frame_pointer_needed)
897     emit_move_insn (frame_pointer_rtx, stack_pointer_rtx);
898
899   /* Allocate stack for this frame.  */
900   if (size)
901     emit_insn (gen_addsi3 (stack_pointer_rtx,
902                            stack_pointer_rtx,
903                            GEN_INT (-size)));
904   if (flag_pic && regs_ever_live[PIC_OFFSET_TABLE_REGNUM])
905     {
906       rtx insn = get_last_insn ();
907       rtx last = emit_insn (gen_GOTaddr2picreg ());
908
909       /* Mark these insns as possibly dead.  Sometimes, flow2 may
910          delete all uses of the PIC register.  In this case, let it
911          delete the initialization too.  */
912       do
913         {
914           insn = NEXT_INSN (insn);
915
916           REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_MAYBE_DEAD,
917                                                 const0_rtx,
918                                                 REG_NOTES (insn));
919         }
920       while (insn != last);
921     }
922 }
923
924 void
925 expand_epilogue (void)
926 {
927   HOST_WIDE_INT size;
928
929   /* SIZE includes the fixed stack space needed for function calls.  */
930   size = get_frame_size () + current_function_outgoing_args_size;
931   size += (current_function_outgoing_args_size ? 4 : 0);
932
933   if (TARGET_AM33_2 && fp_regs_to_save ())
934     {
935       int num_regs_to_save = fp_regs_to_save (), i;
936       rtx reg = 0;
937
938       /* We have several options to restore FP registers.  We could
939          load them from SP offsets, but, if there are enough FP
940          registers to restore, we win if we use a post-increment
941          addressing mode.  */
942
943       /* If we have a frame pointer, it's the best option, because we
944          already know it has the value we want.  */
945       if (frame_pointer_needed)
946         reg = gen_rtx_REG (SImode, FRAME_POINTER_REGNUM);
947       /* Otherwise, we may use `a1', since it's call-clobbered and
948          it's never used for return values.  But only do so if it's
949          smaller than using SP offsets.  */
950       else
951         {
952           enum { restore_sp_post_adjust,
953                  restore_sp_pre_adjust,
954                  restore_sp_partial_adjust,
955                  restore_a1 } strategy;
956           unsigned int this_strategy_size, strategy_size = (unsigned)-1;
957
958           /* Consider using sp offsets before adjusting sp.  */
959           /* Insn: fmov (##,sp),fs#, for each fs# to be restored.  */
960           this_strategy_size = SIZE_FMOV_SP (size, num_regs_to_save);
961           /* If size is too large, we'll have to adjust SP with an
962                  add.  */
963           if (size + 4 * num_regs_to_save + REG_SAVE_BYTES > 255)
964             {
965               /* Insn: add size + 4 * num_regs_to_save, sp.  */
966               this_strategy_size += SIZE_ADD_SP (size + 4 * num_regs_to_save);
967             }
968           /* If we don't have to restore any non-FP registers,
969                  we'll be able to save one byte by using rets.  */
970           if (! REG_SAVE_BYTES)
971             this_strategy_size--;
972
973           if (this_strategy_size < strategy_size)
974             {
975               strategy = restore_sp_post_adjust;
976               strategy_size = this_strategy_size;
977             }
978
979           /* Consider using sp offsets after adjusting sp.  */
980           /* Insn: add size, sp.  */
981           this_strategy_size = SIZE_ADD_SP (size);
982           /* Insn: fmov (##,sp),fs#, for each fs# to be restored.  */
983           this_strategy_size += SIZE_FMOV_SP (0, num_regs_to_save);
984           /* We're going to use ret to release the FP registers
985                  save area, so, no savings.  */
986
987           if (this_strategy_size < strategy_size)
988             {
989               strategy = restore_sp_pre_adjust;
990               strategy_size = this_strategy_size;
991             }
992
993           /* Consider using sp offsets after partially adjusting sp.
994              When size is close to 32Kb, we may be able to adjust SP
995              with an imm16 add instruction while still using fmov
996              (d8,sp).  */
997           if (size + 4 * num_regs_to_save + REG_SAVE_BYTES > 255)
998             {
999               /* Insn: add size + 4 * num_regs_to_save
1000                                 + REG_SAVE_BYTES - 252,sp.  */
1001               this_strategy_size = SIZE_ADD_SP (size + 4 * num_regs_to_save
1002                                                 + REG_SAVE_BYTES - 252);
1003               /* Insn: fmov (##,sp),fs#, fo each fs# to be restored.  */
1004               this_strategy_size += SIZE_FMOV_SP (252 - REG_SAVE_BYTES
1005                                                   - 4 * num_regs_to_save,
1006                                                   num_regs_to_save);
1007               /* We're going to use ret to release the FP registers
1008                  save area, so, no savings.  */
1009
1010               if (this_strategy_size < strategy_size)
1011                 {
1012                   strategy = restore_sp_partial_adjust;
1013                   strategy_size = this_strategy_size;
1014                 }
1015             }
1016
1017           /* Consider using a1 in post-increment mode, as long as the
1018              user hasn't changed the calling conventions of a1.  */
1019           if (call_used_regs[FIRST_ADDRESS_REGNUM+1]
1020               && ! fixed_regs[FIRST_ADDRESS_REGNUM+1])
1021             {
1022               /* Insn: mov sp,a1.  */
1023               this_strategy_size = 1;
1024               if (size)
1025                 {
1026                   /* Insn: add size,a1.  */
1027                   this_strategy_size += SIZE_ADD_AX (size);
1028                 }
1029               /* Insn: fmov (a1+),fs#, for each fs# to be restored.  */
1030               this_strategy_size += 3 * num_regs_to_save;
1031               /* If size is large enough, we may be able to save a
1032                  couple of bytes.  */
1033               if (size + 4 * num_regs_to_save + REG_SAVE_BYTES > 255)
1034                 {
1035                   /* Insn: mov a1,sp.  */
1036                   this_strategy_size += 2;
1037                 }
1038               /* If we don't have to restore any non-FP registers,
1039                  we'll be able to save one byte by using rets.  */
1040               if (! REG_SAVE_BYTES)
1041                 this_strategy_size--;
1042
1043               if (this_strategy_size < strategy_size)
1044                 {
1045                   strategy = restore_a1;
1046                   strategy_size = this_strategy_size;
1047                 }
1048             }
1049
1050           switch (strategy)
1051             {
1052             case restore_sp_post_adjust:
1053               break;
1054
1055             case restore_sp_pre_adjust:
1056               emit_insn (gen_addsi3 (stack_pointer_rtx,
1057                                      stack_pointer_rtx,
1058                                      GEN_INT (size)));
1059               size = 0;
1060               break;
1061
1062             case restore_sp_partial_adjust:
1063               emit_insn (gen_addsi3 (stack_pointer_rtx,
1064                                      stack_pointer_rtx,
1065                                      GEN_INT (size + 4 * num_regs_to_save
1066                                               + REG_SAVE_BYTES - 252)));
1067               size = 252 - REG_SAVE_BYTES - 4 * num_regs_to_save;
1068               break;
1069               
1070             case restore_a1:
1071               reg = gen_rtx_REG (SImode, FIRST_ADDRESS_REGNUM + 1);
1072               emit_insn (gen_movsi (reg, stack_pointer_rtx));
1073               if (size)
1074                 emit_insn (gen_addsi3 (reg, reg, GEN_INT (size)));
1075               break;
1076
1077             default:
1078               abort ();
1079             }
1080         }
1081
1082       /* Adjust the selected register, if any, for post-increment.  */
1083       if (reg)
1084         reg = gen_rtx_POST_INC (SImode, reg);
1085
1086       for (i = FIRST_FP_REGNUM; i <= LAST_FP_REGNUM; ++i)
1087         if (regs_ever_live[i] && ! call_used_regs[i])
1088           {
1089             rtx addr;
1090             
1091             if (reg)
1092               addr = reg;
1093             else if (size)
1094               {
1095                 /* If we aren't using a post-increment register, use an
1096                    SP offset.  */
1097                 addr = gen_rtx_PLUS (SImode,
1098                                      stack_pointer_rtx,
1099                                      GEN_INT (size));
1100               }
1101             else
1102               addr = stack_pointer_rtx;
1103
1104             size += 4;
1105
1106             emit_insn (gen_movsi (gen_rtx_REG (SImode, i),
1107                                   gen_rtx_MEM (SImode, addr)));
1108           }
1109
1110       /* If we were using the restore_a1 strategy and the number of
1111          bytes to be released won't fit in the `ret' byte, copy `a1'
1112          to `sp', to avoid having to use `add' to adjust it.  */
1113       if (! frame_pointer_needed && reg && size + REG_SAVE_BYTES > 255)
1114         {
1115           emit_move_insn (stack_pointer_rtx, XEXP (reg, 0));
1116           size = 0;
1117         }
1118     }
1119
1120   /* Maybe cut back the stack, except for the register save area.
1121
1122      If the frame pointer exists, then use the frame pointer to
1123      cut back the stack.
1124
1125      If the stack size + register save area is more than 255 bytes,
1126      then the stack must be cut back here since the size + register
1127      save size is too big for a ret/retf instruction. 
1128
1129      Else leave it alone, it will be cut back as part of the
1130      ret/retf instruction, or there wasn't any stack to begin with.
1131
1132      Under no circumstances should the register save area be
1133      deallocated here, that would leave a window where an interrupt
1134      could occur and trash the register save area.  */
1135   if (frame_pointer_needed)
1136     {
1137       emit_move_insn (stack_pointer_rtx, frame_pointer_rtx);
1138       size = 0;
1139     }
1140   else if (size + REG_SAVE_BYTES > 255)
1141     {
1142       emit_insn (gen_addsi3 (stack_pointer_rtx,
1143                              stack_pointer_rtx,
1144                              GEN_INT (size)));
1145       size = 0;
1146     }
1147
1148   /* Adjust the stack and restore callee-saved registers, if any.  */
1149   if (size || regs_ever_live[2] || regs_ever_live[3]
1150       || regs_ever_live[6] || regs_ever_live[7]
1151       || regs_ever_live[14] || regs_ever_live[15]
1152       || regs_ever_live[16] || regs_ever_live[17]
1153       || frame_pointer_needed)
1154     emit_jump_insn (gen_return_internal_regs
1155                     (GEN_INT (size + REG_SAVE_BYTES)));
1156   else
1157     emit_jump_insn (gen_return_internal ());
1158 }
1159
1160 /* Update the condition code from the insn.  */
1161
1162 void
1163 notice_update_cc (rtx body, rtx insn)
1164 {
1165   switch (get_attr_cc (insn))
1166     {
1167     case CC_NONE:
1168       /* Insn does not affect CC at all.  */
1169       break;
1170
1171     case CC_NONE_0HIT:
1172       /* Insn does not change CC, but the 0'th operand has been changed.  */
1173       if (cc_status.value1 != 0
1174           && reg_overlap_mentioned_p (recog_data.operand[0], cc_status.value1))
1175         cc_status.value1 = 0;
1176       break;
1177
1178     case CC_SET_ZN:
1179       /* Insn sets the Z,N flags of CC to recog_data.operand[0].
1180          V,C are unusable.  */
1181       CC_STATUS_INIT;
1182       cc_status.flags |= CC_NO_CARRY | CC_OVERFLOW_UNUSABLE;
1183       cc_status.value1 = recog_data.operand[0];
1184       break;
1185
1186     case CC_SET_ZNV:
1187       /* Insn sets the Z,N,V flags of CC to recog_data.operand[0].
1188          C is unusable.  */
1189       CC_STATUS_INIT;
1190       cc_status.flags |= CC_NO_CARRY;
1191       cc_status.value1 = recog_data.operand[0];
1192       break;
1193
1194     case CC_COMPARE:
1195       /* The insn is a compare instruction.  */
1196       CC_STATUS_INIT;
1197       cc_status.value1 = SET_SRC (body);
1198       if (GET_CODE (cc_status.value1) == COMPARE
1199           && GET_MODE (XEXP (cc_status.value1, 0)) == SFmode)
1200         cc_status.mdep.fpCC = 1;
1201       break;
1202
1203     case CC_CLOBBER:
1204       /* Insn doesn't leave CC in a usable state.  */
1205       CC_STATUS_INIT;
1206       break;
1207
1208     default:
1209       abort ();
1210     }
1211 }
1212
1213 /* Recognize the PARALLEL rtx generated by mn10300_gen_multiple_store().
1214    This function is for MATCH_PARALLEL and so assumes OP is known to be
1215    parallel.  If OP is a multiple store, return a mask indicating which
1216    registers it saves.  Return 0 otherwise.  */
1217
1218 int
1219 store_multiple_operation (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
1220 {
1221   int count;
1222   int mask;
1223   int i;
1224   unsigned int last;
1225   rtx elt;
1226
1227   count = XVECLEN (op, 0);
1228   if (count < 2)
1229     return 0;
1230
1231   /* Check that first instruction has the form (set (sp) (plus A B)) */
1232   elt = XVECEXP (op, 0, 0);
1233   if (GET_CODE (elt) != SET
1234       || GET_CODE (SET_DEST (elt)) != REG
1235       || REGNO (SET_DEST (elt)) != STACK_POINTER_REGNUM
1236       || GET_CODE (SET_SRC (elt)) != PLUS)
1237     return 0;
1238
1239   /* Check that A is the stack pointer and B is the expected stack size.
1240      For OP to match, each subsequent instruction should push a word onto
1241      the stack.  We therefore expect the first instruction to create
1242      COUNT-1 stack slots.  */
1243   elt = SET_SRC (elt);
1244   if (GET_CODE (XEXP (elt, 0)) != REG
1245       || REGNO (XEXP (elt, 0)) != STACK_POINTER_REGNUM
1246       || GET_CODE (XEXP (elt, 1)) != CONST_INT
1247       || INTVAL (XEXP (elt, 1)) != -(count - 1) * 4)
1248     return 0;
1249
1250   /* Now go through the rest of the vector elements.  They must be
1251      ordered so that the first instruction stores the highest-numbered
1252      register to the highest stack slot and that subsequent instructions
1253      store a lower-numbered register to the slot below.
1254
1255      LAST keeps track of the smallest-numbered register stored so far.
1256      MASK is the set of stored registers.  */
1257   last = LAST_EXTENDED_REGNUM + 1;
1258   mask = 0;
1259   for (i = 1; i < count; i++)
1260     {
1261       /* Check that element i is a (set (mem M) R) and that R is valid.  */
1262       elt = XVECEXP (op, 0, i);
1263       if (GET_CODE (elt) != SET
1264           || GET_CODE (SET_DEST (elt)) != MEM
1265           || GET_CODE (SET_SRC (elt)) != REG
1266           || REGNO (SET_SRC (elt)) >= last)
1267         return 0;
1268
1269       /* R was OK, so provisionally add it to MASK.  We return 0 in any
1270          case if the rest of the instruction has a flaw.  */
1271       last = REGNO (SET_SRC (elt));
1272       mask |= (1 << last);
1273
1274       /* Check that M has the form (plus (sp) (const_int -I*4)) */
1275       elt = XEXP (SET_DEST (elt), 0);
1276       if (GET_CODE (elt) != PLUS
1277           || GET_CODE (XEXP (elt, 0)) != REG
1278           || REGNO (XEXP (elt, 0)) != STACK_POINTER_REGNUM
1279           || GET_CODE (XEXP (elt, 1)) != CONST_INT
1280           || INTVAL (XEXP (elt, 1)) != -i * 4)
1281         return 0;
1282     }
1283
1284   /* All or none of the callee-saved extended registers must be in the set.  */
1285   if ((mask & 0x3c000) != 0
1286       && (mask & 0x3c000) != 0x3c000)
1287     return 0;
1288
1289   return mask;
1290 }
1291
1292 /* Return true if OP is a valid call operand.  */
1293
1294 int
1295 call_address_operand (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
1296 {
1297   if (flag_pic)
1298     return (EXTRA_CONSTRAINT (op, 'S') || GET_CODE (op) == REG);
1299
1300   return (GET_CODE (op) == SYMBOL_REF || GET_CODE (op) == REG);
1301 }
1302
1303 /* What (if any) secondary registers are needed to move IN with mode
1304    MODE into a register in register class CLASS. 
1305
1306    We might be able to simplify this.  */
1307 enum reg_class
1308 secondary_reload_class (enum reg_class class, enum machine_mode mode, rtx in)
1309 {
1310   /* Memory loads less than a full word wide can't have an
1311      address or stack pointer destination.  They must use
1312      a data register as an intermediate register.  */
1313   if ((GET_CODE (in) == MEM
1314        || (GET_CODE (in) == REG
1315            && REGNO (in) >= FIRST_PSEUDO_REGISTER)
1316        || (GET_CODE (in) == SUBREG
1317            && GET_CODE (SUBREG_REG (in)) == REG
1318            && REGNO (SUBREG_REG (in)) >= FIRST_PSEUDO_REGISTER))
1319       && (mode == QImode || mode == HImode)
1320       && (class == ADDRESS_REGS || class == SP_REGS
1321           || class == SP_OR_ADDRESS_REGS))
1322     {
1323       if (TARGET_AM33)
1324         return DATA_OR_EXTENDED_REGS;
1325       return DATA_REGS;
1326     }
1327
1328   /* We can't directly load sp + const_int into a data register;
1329      we must use an address register as an intermediate.  */
1330   if (class != SP_REGS
1331       && class != ADDRESS_REGS
1332       && class != SP_OR_ADDRESS_REGS
1333       && class != SP_OR_EXTENDED_REGS
1334       && class != ADDRESS_OR_EXTENDED_REGS
1335       && class != SP_OR_ADDRESS_OR_EXTENDED_REGS
1336       && (in == stack_pointer_rtx
1337           || (GET_CODE (in) == PLUS
1338               && (XEXP (in, 0) == stack_pointer_rtx
1339                   || XEXP (in, 1) == stack_pointer_rtx))))
1340     return ADDRESS_REGS;
1341
1342   if (GET_CODE (in) == PLUS
1343       && (XEXP (in, 0) == stack_pointer_rtx
1344           || XEXP (in, 1) == stack_pointer_rtx))
1345     {
1346       if (TARGET_AM33)
1347         return DATA_OR_EXTENDED_REGS;
1348       return DATA_REGS;
1349     }
1350  
1351   if (TARGET_AM33_2 && class == FP_REGS
1352       && GET_CODE (in) == MEM && ! OK_FOR_Q (in))
1353     {
1354       if (TARGET_AM33)
1355         return DATA_OR_EXTENDED_REGS;
1356       return DATA_REGS;
1357     }
1358
1359   /* Otherwise assume no secondary reloads are needed.  */
1360   return NO_REGS;
1361 }
1362
1363 int
1364 initial_offset (int from, int to)
1365 {
1366   /* The difference between the argument pointer and the frame pointer
1367      is the size of the callee register save area.  */
1368   if (from == ARG_POINTER_REGNUM && to == FRAME_POINTER_REGNUM)
1369     {
1370       if (regs_ever_live[2] || regs_ever_live[3]
1371           || regs_ever_live[6] || regs_ever_live[7]
1372           || regs_ever_live[14] || regs_ever_live[15]
1373           || regs_ever_live[16] || regs_ever_live[17]
1374           || fp_regs_to_save ()
1375           || frame_pointer_needed)
1376         return REG_SAVE_BYTES
1377           + 4 * fp_regs_to_save ();
1378       else
1379         return 0;
1380     }
1381
1382   /* The difference between the argument pointer and the stack pointer is
1383      the sum of the size of this function's frame, the callee register save
1384      area, and the fixed stack space needed for function calls (if any).  */
1385   if (from == ARG_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
1386     {
1387       if (regs_ever_live[2] || regs_ever_live[3]
1388           || regs_ever_live[6] || regs_ever_live[7]
1389           || regs_ever_live[14] || regs_ever_live[15]
1390           || regs_ever_live[16] || regs_ever_live[17]
1391           || fp_regs_to_save ()
1392           || frame_pointer_needed)
1393         return (get_frame_size () + REG_SAVE_BYTES
1394                 + 4 * fp_regs_to_save ()
1395                 + (current_function_outgoing_args_size
1396                    ? current_function_outgoing_args_size + 4 : 0)); 
1397       else
1398         return (get_frame_size ()
1399                 + (current_function_outgoing_args_size
1400                    ? current_function_outgoing_args_size + 4 : 0)); 
1401     }
1402
1403   /* The difference between the frame pointer and stack pointer is the sum
1404      of the size of this function's frame and the fixed stack space needed
1405      for function calls (if any).  */
1406   if (from == FRAME_POINTER_REGNUM && to == STACK_POINTER_REGNUM)
1407     return (get_frame_size ()
1408             + (current_function_outgoing_args_size
1409                ? current_function_outgoing_args_size + 4 : 0)); 
1410
1411   abort ();
1412 }
1413
1414 /* Worker function for TARGET_RETURN_IN_MEMORY.  */
1415
1416 static bool
1417 mn10300_return_in_memory (tree type, tree fntype ATTRIBUTE_UNUSED)
1418 {
1419   /* Return values > 8 bytes in length in memory.  */
1420   return int_size_in_bytes (type) > 8 || TYPE_MODE (type) == BLKmode;
1421 }
1422
1423 /* Flush the argument registers to the stack for a stdarg function;
1424    return the new argument pointer.  */
1425 static rtx
1426 mn10300_builtin_saveregs (void)
1427 {
1428   rtx offset, mem;
1429   tree fntype = TREE_TYPE (current_function_decl);
1430   int argadj = ((!(TYPE_ARG_TYPES (fntype) != 0
1431                    && (TREE_VALUE (tree_last (TYPE_ARG_TYPES (fntype)))
1432                        != void_type_node)))
1433                 ? UNITS_PER_WORD : 0);
1434   int set = get_varargs_alias_set ();
1435
1436   if (argadj)
1437     offset = plus_constant (current_function_arg_offset_rtx, argadj);
1438   else
1439     offset = current_function_arg_offset_rtx;
1440
1441   mem = gen_rtx_MEM (SImode, current_function_internal_arg_pointer);
1442   set_mem_alias_set (mem, set);
1443   emit_move_insn (mem, gen_rtx_REG (SImode, 0));
1444
1445   mem = gen_rtx_MEM (SImode,
1446                      plus_constant (current_function_internal_arg_pointer, 4));
1447   set_mem_alias_set (mem, set);
1448   emit_move_insn (mem, gen_rtx_REG (SImode, 1));
1449
1450   return copy_to_reg (expand_binop (Pmode, add_optab,
1451                                     current_function_internal_arg_pointer,
1452                                     offset, 0, 0, OPTAB_LIB_WIDEN));
1453 }
1454
1455 void
1456 mn10300_va_start (tree valist, rtx nextarg)
1457 {
1458   nextarg = expand_builtin_saveregs ();
1459   std_expand_builtin_va_start (valist, nextarg);
1460 }
1461
1462 /* Return true when a parameter should be passed by reference.  */
1463
1464 static bool
1465 mn10300_pass_by_reference (CUMULATIVE_ARGS *cum ATTRIBUTE_UNUSED,
1466                            enum machine_mode mode, tree type,
1467                            bool named ATTRIBUTE_UNUSED)
1468 {
1469   unsigned HOST_WIDE_INT size;
1470
1471   if (type)
1472     size = int_size_in_bytes (type);
1473   else
1474     size = GET_MODE_SIZE (mode);
1475
1476   return size > 8;
1477 }
1478
1479 /* Return an RTX to represent where a value with mode MODE will be returned
1480    from a function.  If the result is 0, the argument is pushed.  */
1481
1482 rtx
1483 function_arg (CUMULATIVE_ARGS *cum, enum machine_mode mode,
1484               tree type, int named ATTRIBUTE_UNUSED)
1485 {
1486   rtx result = 0;
1487   int size, align;
1488
1489   /* We only support using 2 data registers as argument registers.  */
1490   int nregs = 2;
1491
1492   /* Figure out the size of the object to be passed.  */
1493   if (mode == BLKmode)
1494     size = int_size_in_bytes (type);
1495   else
1496     size = GET_MODE_SIZE (mode);
1497
1498   /* Figure out the alignment of the object to be passed.  */
1499   align = size;
1500
1501   cum->nbytes = (cum->nbytes + 3) & ~3;
1502
1503   /* Don't pass this arg via a register if all the argument registers
1504      are used up.  */
1505   if (cum->nbytes > nregs * UNITS_PER_WORD)
1506     return 0;
1507
1508   /* Don't pass this arg via a register if it would be split between
1509      registers and memory.  */
1510   if (type == NULL_TREE
1511       && cum->nbytes + size > nregs * UNITS_PER_WORD)
1512     return 0;
1513
1514   switch (cum->nbytes / UNITS_PER_WORD)
1515     {
1516     case 0:
1517       result = gen_rtx_REG (mode, 0);
1518       break;
1519     case 1:
1520       result = gen_rtx_REG (mode, 1);
1521       break;
1522     default:
1523       result = 0;
1524     }
1525
1526   return result;
1527 }
1528
1529 /* Return the number of registers to use for an argument passed partially
1530    in registers and partially in memory.  */
1531
1532 int
1533 function_arg_partial_nregs (CUMULATIVE_ARGS *cum, enum machine_mode mode,
1534                             tree type, int named ATTRIBUTE_UNUSED)
1535 {
1536   int size, align;
1537
1538   /* We only support using 2 data registers as argument registers.  */
1539   int nregs = 2;
1540
1541   /* Figure out the size of the object to be passed.  */
1542   if (mode == BLKmode)
1543     size = int_size_in_bytes (type);
1544   else
1545     size = GET_MODE_SIZE (mode);
1546
1547   /* Figure out the alignment of the object to be passed.  */
1548   align = size;
1549
1550   cum->nbytes = (cum->nbytes + 3) & ~3;
1551
1552   /* Don't pass this arg via a register if all the argument registers
1553      are used up.  */
1554   if (cum->nbytes > nregs * UNITS_PER_WORD)
1555     return 0;
1556
1557   if (cum->nbytes + size <= nregs * UNITS_PER_WORD)
1558     return 0;
1559
1560   /* Don't pass this arg via a register if it would be split between
1561      registers and memory.  */
1562   if (type == NULL_TREE
1563       && cum->nbytes + size > nregs * UNITS_PER_WORD)
1564     return 0;
1565
1566   return (nregs * UNITS_PER_WORD - cum->nbytes) / UNITS_PER_WORD;
1567 }
1568
1569 /* Output a tst insn.  */
1570 const char *
1571 output_tst (rtx operand, rtx insn)
1572 {
1573   rtx temp;
1574   int past_call = 0;
1575
1576   /* We can save a byte if we can find a register which has the value
1577      zero in it.  */
1578   temp = PREV_INSN (insn);
1579   while (optimize && temp)
1580     {
1581       rtx set;
1582
1583       /* We allow the search to go through call insns.  We record
1584          the fact that we've past a CALL_INSN and reject matches which
1585          use call clobbered registers.  */
1586       if (GET_CODE (temp) == CODE_LABEL
1587           || GET_CODE (temp) == JUMP_INSN
1588           || GET_CODE (temp) == BARRIER)
1589         break;
1590
1591       if (GET_CODE (temp) == CALL_INSN)
1592         past_call = 1;
1593
1594       if (GET_CODE (temp) == NOTE)
1595         {
1596           temp = PREV_INSN (temp);
1597           continue;
1598         }
1599
1600       /* It must be an insn, see if it is a simple set.  */
1601       set = single_set (temp);
1602       if (!set)
1603         {
1604           temp = PREV_INSN (temp);
1605           continue;
1606         }
1607
1608       /* Are we setting a data register to zero (this does not win for
1609          address registers)? 
1610
1611          If it's a call clobbered register, have we past a call?
1612
1613          Make sure the register we find isn't the same as ourself;
1614          the mn10300 can't encode that.
1615
1616          ??? reg_set_between_p return nonzero anytime we pass a CALL_INSN
1617          so the code to detect calls here isn't doing anything useful.  */
1618       if (REG_P (SET_DEST (set))
1619           && SET_SRC (set) == CONST0_RTX (GET_MODE (SET_DEST (set)))
1620           && !reg_set_between_p (SET_DEST (set), temp, insn)
1621           && (REGNO_REG_CLASS (REGNO (SET_DEST (set)))
1622               == REGNO_REG_CLASS (REGNO (operand)))
1623           && REGNO_REG_CLASS (REGNO (SET_DEST (set))) != EXTENDED_REGS
1624           && REGNO (SET_DEST (set)) != REGNO (operand)
1625           && (!past_call 
1626               || !call_used_regs[REGNO (SET_DEST (set))]))
1627         {
1628           rtx xoperands[2];
1629           xoperands[0] = operand;
1630           xoperands[1] = SET_DEST (set);
1631
1632           output_asm_insn ("cmp %1,%0", xoperands);
1633           return "";
1634         }
1635
1636       if (REGNO_REG_CLASS (REGNO (operand)) == EXTENDED_REGS
1637           && REG_P (SET_DEST (set))
1638           && SET_SRC (set) == CONST0_RTX (GET_MODE (SET_DEST (set)))
1639           && !reg_set_between_p (SET_DEST (set), temp, insn)
1640           && (REGNO_REG_CLASS (REGNO (SET_DEST (set)))
1641               != REGNO_REG_CLASS (REGNO (operand)))
1642           && REGNO_REG_CLASS (REGNO (SET_DEST (set))) == EXTENDED_REGS
1643           && REGNO (SET_DEST (set)) != REGNO (operand)
1644           && (!past_call 
1645               || !call_used_regs[REGNO (SET_DEST (set))]))
1646         {
1647           rtx xoperands[2];
1648           xoperands[0] = operand;
1649           xoperands[1] = SET_DEST (set);
1650
1651           output_asm_insn ("cmp %1,%0", xoperands);
1652           return "";
1653         }
1654       temp = PREV_INSN (temp);
1655     }
1656   return "cmp 0,%0";
1657 }
1658
1659 int
1660 impossible_plus_operand (rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
1661 {
1662   if (GET_CODE (op) != PLUS)
1663     return 0;
1664
1665   if (XEXP (op, 0) == stack_pointer_rtx
1666       || XEXP (op, 1) == stack_pointer_rtx)
1667     return 1;
1668
1669   return 0;
1670 }
1671
1672 /* Return 1 if X is a CONST_INT that is only 8 bits wide.  This is used
1673    for the btst insn which may examine memory or a register (the memory
1674    variant only allows an unsigned 8 bit integer).  */
1675 int
1676 const_8bit_operand (register rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
1677 {
1678   return (GET_CODE (op) == CONST_INT
1679           && INTVAL (op) >= 0
1680           && INTVAL (op) < 256);
1681 }
1682
1683 /* Return true if the operand is the 1.0f constant.  */
1684 int
1685 const_1f_operand (register rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
1686 {
1687   return (op == CONST1_RTX (SFmode));
1688 }
1689
1690 /* Similarly, but when using a zero_extract pattern for a btst where
1691    the source operand might end up in memory.  */
1692 int
1693 mask_ok_for_mem_btst (int len, int bit)
1694 {
1695   unsigned int mask = 0;
1696
1697   while (len > 0)
1698     {
1699       mask |= (1 << bit);
1700       bit++;
1701       len--;
1702     }
1703
1704   /* MASK must bit into an 8bit value.  */
1705   return (((mask & 0xff) == mask)
1706           || ((mask & 0xff00) == mask)
1707           || ((mask & 0xff0000) == mask)
1708           || ((mask & 0xff000000) == mask));
1709 }
1710
1711 /* Return 1 if X contains a symbolic expression.  We know these
1712    expressions will have one of a few well defined forms, so
1713    we need only check those forms.  */
1714 int
1715 symbolic_operand (register rtx op, enum machine_mode mode ATTRIBUTE_UNUSED)
1716 {
1717   switch (GET_CODE (op))
1718     {
1719     case SYMBOL_REF:
1720     case LABEL_REF:
1721       return 1;
1722     case CONST:
1723       op = XEXP (op, 0);
1724       return ((GET_CODE (XEXP (op, 0)) == SYMBOL_REF
1725                || GET_CODE (XEXP (op, 0)) == LABEL_REF)
1726               && GET_CODE (XEXP (op, 1)) == CONST_INT);
1727     default:
1728       return 0;
1729     }
1730 }
1731
1732 /* Try machine dependent ways of modifying an illegitimate address
1733    to be legitimate.  If we find one, return the new valid address.
1734    This macro is used in only one place: `memory_address' in explow.c.
1735
1736    OLDX is the address as it was before break_out_memory_refs was called.
1737    In some cases it is useful to look at this to decide what needs to be done.
1738
1739    MODE and WIN are passed so that this macro can use
1740    GO_IF_LEGITIMATE_ADDRESS.
1741
1742    Normally it is always safe for this macro to do nothing.  It exists to
1743    recognize opportunities to optimize the output.
1744
1745    But on a few ports with segmented architectures and indexed addressing
1746    (mn10300, hppa) it is used to rewrite certain problematical addresses.  */
1747 rtx
1748 legitimize_address (rtx x, rtx oldx ATTRIBUTE_UNUSED,
1749                     enum machine_mode mode ATTRIBUTE_UNUSED)
1750 {
1751   if (flag_pic && ! legitimate_pic_operand_p (x))
1752     x = legitimize_pic_address (oldx, NULL_RTX);
1753
1754   /* Uh-oh.  We might have an address for x[n-100000].  This needs
1755      special handling to avoid creating an indexed memory address
1756      with x-100000 as the base.  */
1757   if (GET_CODE (x) == PLUS
1758       && symbolic_operand (XEXP (x, 1), VOIDmode))
1759     {
1760       /* Ugly.  We modify things here so that the address offset specified
1761          by the index expression is computed first, then added to x to form
1762          the entire address.  */
1763
1764       rtx regx1, regy1, regy2, y;
1765
1766       /* Strip off any CONST.  */
1767       y = XEXP (x, 1);
1768       if (GET_CODE (y) == CONST)
1769         y = XEXP (y, 0);
1770
1771       if (GET_CODE (y) == PLUS || GET_CODE (y) == MINUS)
1772         {
1773           regx1 = force_reg (Pmode, force_operand (XEXP (x, 0), 0));
1774           regy1 = force_reg (Pmode, force_operand (XEXP (y, 0), 0));
1775           regy2 = force_reg (Pmode, force_operand (XEXP (y, 1), 0));
1776           regx1 = force_reg (Pmode,
1777                              gen_rtx_fmt_ee (GET_CODE (y), Pmode, regx1, regy2));
1778           return force_reg (Pmode, gen_rtx_PLUS (Pmode, regx1, regy1));
1779         }
1780     }
1781   return x;
1782 }
1783
1784 /* Convert a non-PIC address in `orig' to a PIC address using @GOT or
1785    @GOTOFF in `reg'.  */
1786 rtx
1787 legitimize_pic_address (rtx orig, rtx reg)
1788 {
1789   if (GET_CODE (orig) == LABEL_REF
1790       || (GET_CODE (orig) == SYMBOL_REF
1791           && (CONSTANT_POOL_ADDRESS_P (orig)
1792               || ! MN10300_GLOBAL_P (orig))))
1793     {
1794       if (reg == 0)
1795         reg = gen_reg_rtx (Pmode);
1796
1797       emit_insn (gen_symGOTOFF2reg (reg, orig));
1798       return reg;
1799     }
1800   else if (GET_CODE (orig) == SYMBOL_REF)
1801     {
1802       if (reg == 0)
1803         reg = gen_reg_rtx (Pmode);
1804
1805       emit_insn (gen_symGOT2reg (reg, orig));
1806       return reg;
1807     }
1808   return orig;
1809 }
1810
1811 /* Return zero if X references a SYMBOL_REF or LABEL_REF whose symbol
1812    isn't protected by a PIC unspec; nonzero otherwise.  */
1813 int
1814 legitimate_pic_operand_p (rtx x)
1815 {
1816   register const char *fmt;
1817   register int i;
1818
1819   if (GET_CODE (x) == SYMBOL_REF || GET_CODE (x) == LABEL_REF)
1820     return 0;
1821
1822   if (GET_CODE (x) == UNSPEC
1823       && (XINT (x, 1) == UNSPEC_PIC
1824           || XINT (x, 1) == UNSPEC_GOT
1825           || XINT (x, 1) == UNSPEC_GOTOFF
1826           || XINT (x, 1) == UNSPEC_PLT))
1827       return 1;
1828
1829   if (GET_CODE (x) == QUEUED)
1830     return legitimate_pic_operand_p (QUEUED_VAR (x));
1831
1832   fmt = GET_RTX_FORMAT (GET_CODE (x));
1833   for (i = GET_RTX_LENGTH (GET_CODE (x)) - 1; i >= 0; i--)
1834     {
1835       if (fmt[i] == 'E')
1836         {
1837           register int j;
1838
1839           for (j = XVECLEN (x, i) - 1; j >= 0; j--)
1840             if (! legitimate_pic_operand_p (XVECEXP (x, i, j)))
1841               return 0;
1842         }
1843       else if (fmt[i] == 'e' && ! legitimate_pic_operand_p (XEXP (x, i)))
1844         return 0;
1845     }
1846
1847   return 1;
1848 }
1849
1850 /* Return TRUE if the address X, taken from a (MEM:MODE X) rtx, is
1851    legitimate, and FALSE otherwise.  */
1852 bool
1853 legitimate_address_p (enum machine_mode mode, rtx x, int strict)
1854 {
1855   if (CONSTANT_ADDRESS_P (x)
1856       && (! flag_pic || legitimate_pic_operand_p (x)))
1857     return TRUE;
1858
1859   if (RTX_OK_FOR_BASE_P (x, strict))
1860     return TRUE;
1861
1862   if (TARGET_AM33
1863       && GET_CODE (x) == POST_INC
1864       && RTX_OK_FOR_BASE_P (XEXP (x, 0), strict)
1865       && (mode == SImode || mode == SFmode || mode == HImode))
1866     return TRUE;
1867
1868   if (GET_CODE (x) == PLUS)
1869     {
1870       rtx base = 0, index = 0;
1871
1872       if (REG_P (XEXP (x, 0))
1873           && REGNO_STRICT_OK_FOR_BASE_P (REGNO (XEXP (x, 0)), strict))
1874         {
1875           base = XEXP (x, 0);
1876           index = XEXP (x, 1);
1877         }
1878
1879       if (REG_P (XEXP (x, 1))
1880           && REGNO_STRICT_OK_FOR_BASE_P (REGNO (XEXP (x, 1)), strict))
1881         {
1882           base = XEXP (x, 1);
1883           index = XEXP (x, 0);
1884         }
1885
1886       if (base != 0 && index != 0)
1887         {
1888           if (GET_CODE (index) == CONST_INT)
1889             return TRUE;
1890           if (GET_CODE (index) == CONST
1891               && (! flag_pic
1892                   || legitimate_pic_operand_p (index)))
1893             return TRUE;
1894         }
1895     }
1896
1897   return FALSE;
1898 }
1899
1900 static int
1901 mn10300_address_cost_1 (rtx x, int *unsig)
1902 {
1903   switch (GET_CODE (x))
1904     {
1905     case REG:
1906       switch (REGNO_REG_CLASS (REGNO (x)))
1907         {
1908         case SP_REGS:
1909           *unsig = 1;
1910           return 0;
1911
1912         case ADDRESS_REGS:
1913           return 1;
1914
1915         case DATA_REGS:
1916         case EXTENDED_REGS:
1917         case FP_REGS:
1918           return 3;
1919
1920         case NO_REGS:
1921           return 5;
1922
1923         default:
1924           abort ();
1925         }
1926
1927     case PLUS:
1928     case MINUS:
1929     case ASHIFT:
1930     case AND:
1931     case IOR:
1932       return (mn10300_address_cost_1 (XEXP (x, 0), unsig)
1933               + mn10300_address_cost_1 (XEXP (x, 1), unsig));
1934
1935     case EXPR_LIST:
1936     case SUBREG:
1937     case MEM:
1938       return mn10300_address_cost (XEXP (x, 0));
1939
1940     case ZERO_EXTEND:
1941       *unsig = 1;
1942       return mn10300_address_cost_1 (XEXP (x, 0), unsig);
1943
1944     case CONST_INT:
1945       if (INTVAL (x) == 0)
1946         return 0;
1947       if (INTVAL (x) + (*unsig ? 0 : 0x80) < 0x100)
1948         return 1;
1949       if (INTVAL (x) + (*unsig ? 0 : 0x8000) < 0x10000)
1950         return 3;
1951       if (INTVAL (x) + (*unsig ? 0 : 0x800000) < 0x1000000)
1952         return 5;
1953       return 7;
1954
1955     case CONST:
1956     case SYMBOL_REF:
1957     case LABEL_REF:
1958       return 8;
1959
1960     default:
1961       abort ();
1962
1963     }
1964 }
1965
1966 static int
1967 mn10300_address_cost (rtx x)
1968 {
1969   int s = 0;
1970   return mn10300_address_cost_1 (x, &s);
1971 }
1972
1973 static bool
1974 mn10300_rtx_costs (rtx x, int code, int outer_code, int *total)
1975 {
1976   switch (code)
1977     {
1978     case CONST_INT:
1979       /* Zeros are extremely cheap.  */
1980       if (INTVAL (x) == 0 && outer_code == SET)
1981         *total = 0;
1982       /* If it fits in 8 bits, then it's still relatively cheap.  */
1983       else if (INT_8_BITS (INTVAL (x)))
1984         *total = 1;
1985       /* This is the "base" cost, includes constants where either the
1986          upper or lower 16bits are all zeros.  */
1987       else if (INT_16_BITS (INTVAL (x))
1988                || (INTVAL (x) & 0xffff) == 0
1989                || (INTVAL (x) & 0xffff0000) == 0)
1990         *total = 2;
1991       else
1992         *total = 4;
1993       return true;
1994
1995     case CONST:
1996     case LABEL_REF:
1997     case SYMBOL_REF:
1998       /* These are more costly than a CONST_INT, but we can relax them,
1999          so they're less costly than a CONST_DOUBLE.  */
2000       *total = 6;
2001       return true;
2002
2003     case CONST_DOUBLE:
2004       /* We don't optimize CONST_DOUBLEs well nor do we relax them well,
2005          so their cost is very high.  */
2006       *total = 8;
2007       return true;
2008
2009    /* ??? This probably needs more work.  */
2010     case MOD:
2011     case DIV:
2012     case MULT:
2013       *total = 8;
2014       return true;
2015
2016     default:
2017       return false;
2018     }
2019 }
2020
2021 /* Check whether a constant used to initialize a DImode or DFmode can
2022    use a clr instruction.  The code here must be kept in sync with
2023    movdf and movdi.  */
2024
2025 bool
2026 mn10300_wide_const_load_uses_clr (rtx operands[2])
2027 {
2028   long val[2];
2029
2030   if (GET_CODE (operands[0]) != REG
2031       || REGNO_REG_CLASS (REGNO (operands[0])) != DATA_REGS)
2032     return false;
2033
2034   switch (GET_CODE (operands[1]))
2035     {
2036     case CONST_INT:
2037       {
2038         rtx low, high;
2039         split_double (operands[1], &low, &high);
2040         val[0] = INTVAL (low);
2041         val[1] = INTVAL (high);
2042       }
2043       break;
2044       
2045     case CONST_DOUBLE:
2046       if (GET_MODE (operands[1]) == DFmode)
2047         {
2048           REAL_VALUE_TYPE rv;
2049
2050           REAL_VALUE_FROM_CONST_DOUBLE (rv, operands[1]);
2051           REAL_VALUE_TO_TARGET_DOUBLE (rv, val);
2052         }
2053       else if (GET_MODE (operands[1]) == VOIDmode
2054                || GET_MODE (operands[1]) == DImode)
2055         {
2056           val[0] = CONST_DOUBLE_LOW (operands[1]);
2057           val[1] = CONST_DOUBLE_HIGH (operands[1]);
2058         }
2059       break;
2060       
2061     default:
2062       return false;
2063     }
2064
2065   return val[0] == 0 || val[1] == 0;
2066 }
2067 /* If using PIC, mark a SYMBOL_REF for a non-global symbol so that we
2068    may access it using GOTOFF instead of GOT.  */
2069
2070 static void
2071 mn10300_encode_section_info (tree decl, rtx rtl, int first ATTRIBUTE_UNUSED)
2072 {
2073   rtx symbol;
2074
2075   if (GET_CODE (rtl) != MEM)
2076     return;
2077   symbol = XEXP (rtl, 0);
2078   if (GET_CODE (symbol) != SYMBOL_REF)
2079     return;
2080
2081   if (flag_pic)
2082     SYMBOL_REF_FLAG (symbol) = (*targetm.binds_local_p) (decl);
2083 }