19990502 sourceware import
[external/binutils.git] / gas / config / tc-arc.c
1 /* tc-arc.c -- Assembler for the ARC
2    Copyright (C) 1994, 1995, 1997, 1998 Free Software Foundation, Inc.
3    Contributed by Doug Evans (dje@cygnus.com).
4
5    This file is part of GAS, the GNU Assembler.
6
7    GAS is free software; you can redistribute it and/or modify
8    it under the terms of the GNU General Public License as published by
9    the Free Software Foundation; either version 2, or (at your option)
10    any later version.
11
12    GAS is distributed in the hope that it will be useful,
13    but WITHOUT ANY WARRANTY; without even the implied warranty of
14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15    GNU General Public License for more details.
16
17    You should have received a copy of the GNU General Public License
18    along with GAS; see the file COPYING.  If not, write to
19    the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */
20
21 #include <stdio.h>
22 #include <ctype.h>
23 #include "as.h"
24 #include "subsegs.h"
25 #include "opcode/arc.h"
26 #include "elf/arc.h"
27
28 extern int arc_get_mach PARAMS ((char *));
29
30 static arc_insn arc_insert_operand PARAMS ((arc_insn,
31                                             const struct arc_operand *, int,
32                                             const struct arc_operand_value *,
33                                             offsetT, char *, unsigned int));
34 static void arc_common PARAMS ((int));
35 static void arc_cpu PARAMS ((int));
36 /*static void arc_rename PARAMS ((int));*/
37 static int get_arc_exp_reloc_type PARAMS ((int, int, expressionS *,
38                                            expressionS *));
39
40 const pseudo_typeS md_pseudo_table[] =
41 {
42   { "align", s_align_bytes, 0 },        /* Defaulting is invalid (0) */
43   { "common", arc_common, 0 },
44 /*{ "hword", cons, 2 }, - already exists */
45   { "word", cons, 4 },
46 /*{ "xword", cons, 8 },*/
47   { "cpu", arc_cpu, 0 },
48 /*{ "rename", arc_rename, 0 },*/
49   { NULL, 0, 0 },
50 };
51
52 /* This array holds the chars that always start a comment.  If the
53    pre-processor is disabled, these aren't very useful */
54 const char comment_chars[] = "#;";
55
56 /* This array holds the chars that only start a comment at the beginning of
57    a line.  If the line seems to have the form '# 123 filename'
58    .line and .file directives will appear in the pre-processed output */
59 /* Note that input_file.c hand checks for '#' at the beginning of the
60    first line of the input file.  This is because the compiler outputs
61    #NO_APP at the beginning of its output. */
62 /* Also note that comments started like this one will always
63    work if '/' isn't otherwise defined. */
64 const char line_comment_chars[] = "#";
65
66 const char line_separator_chars[] = "";
67
68 /* Chars that can be used to separate mant from exp in floating point nums */
69 const char EXP_CHARS[] = "eE";
70
71 /* Chars that mean this number is a floating point constant */
72 /* As in 0f12.456 */
73 /* or    0d1.2345e12 */
74 const char FLT_CHARS[] = "rRsSfFdD";
75
76 /* Byte order.  */
77 extern int target_big_endian;
78 const char *arc_target_format = DEFAULT_TARGET_FORMAT;
79 static int byte_order = DEFAULT_BYTE_ORDER;
80
81 /* One of bfd_mach_arc_xxx.  */
82 static int arc_mach_type = bfd_mach_arc_base;
83
84 /* Non-zero if the cpu type has been explicitly specified.  */
85 static int mach_type_specified_p = 0;
86
87 /* Non-zero if opcode tables have been initialized.
88    A .cpu command must appear before any instructions.  */
89 static int cpu_tables_init_p = 0;
90
91 static struct hash_control *arc_suffix_hash = NULL;
92 \f
93 const char *md_shortopts = "";
94 struct option md_longopts[] =
95 {
96 #define OPTION_EB (OPTION_MD_BASE + 0)
97   {"EB", no_argument, NULL, OPTION_EB},
98 #define OPTION_EL (OPTION_MD_BASE + 1)
99   {"EL", no_argument, NULL, OPTION_EL},
100   { NULL, no_argument, NULL, 0 }
101 };
102 size_t md_longopts_size = sizeof (md_longopts);
103
104 /*
105  * md_parse_option
106  *
107  * Invocation line includes a switch not recognized by the base assembler.
108  * See if it's a processor-specific option.
109  */
110
111 int
112 md_parse_option (c, arg)
113      int c;
114      char *arg;
115 {
116   switch (c)
117     {
118     case OPTION_EB:
119       byte_order = BIG_ENDIAN;
120       arc_target_format = "elf32-bigarc";
121       break;
122     case OPTION_EL:
123       byte_order = LITTLE_ENDIAN;
124       arc_target_format = "elf32-littlearc";
125       break;
126     default:
127       return 0;
128     }
129   return 1;
130 }
131
132 void
133 md_show_usage (stream)
134      FILE *stream;
135 {
136   fprintf (stream, _("\
137 ARC options:\n\
138 -EB                     generate big endian output\n\
139 -EL                     generate little endian output\n"));
140 }
141
142 /* This function is called once, at assembler startup time.  It should
143    set up all the tables, etc. that the MD part of the assembler will need.
144    Opcode selection is defered until later because we might see a .cpu
145    command.  */
146
147 void
148 md_begin ()
149 {
150   /* The endianness can be chosen "at the factory".  */
151   target_big_endian = byte_order == BIG_ENDIAN;
152
153   if (!bfd_set_arch_mach (stdoutput, bfd_arch_arc, arc_mach_type))
154     as_warn (_("could not set architecture and machine"));
155
156   /* Assume the base cpu.  This call is necessary because we need to
157      initialize `arc_operand_map' which may be needed before we see the
158      first insn.  */
159   arc_opcode_init_tables (arc_get_opcode_mach (bfd_mach_arc_base,
160                                                target_big_endian));
161 }
162
163 /* Initialize the various opcode and operand tables.
164    MACH is one of bfd_mach_arc_xxx.  */
165
166 static void
167 init_opcode_tables (mach)
168      int mach;
169 {
170   register unsigned int i;
171   char *last;
172
173   if ((arc_suffix_hash = hash_new ()) == NULL)
174     as_fatal (_("virtual memory exhausted"));
175
176   if (!bfd_set_arch_mach (stdoutput, bfd_arch_arc, mach))
177     as_warn (_("could not set architecture and machine"));
178
179   /* This initializes a few things in arc-opc.c that we need.
180      This must be called before the various arc_xxx_supported fns.  */
181   arc_opcode_init_tables (arc_get_opcode_mach (mach, target_big_endian));
182
183   /* Only put the first entry of each equivalently named suffix in the
184      table.  */
185   last = "";
186   for (i = 0; i < arc_suffixes_count; i++)
187     {
188       if (! arc_opval_supported (&arc_suffixes[i]))
189         continue;
190       if (strcmp (arc_suffixes[i].name, last) != 0)
191         hash_insert (arc_suffix_hash, arc_suffixes[i].name, (PTR) (arc_suffixes + i));
192       last = arc_suffixes[i].name;
193     }
194
195   /* Since registers don't have a prefix, we put them in the symbol table so
196      they can't be used as symbols.  This also simplifies argument parsing as
197      we can let gas parse registers for us.  The recorded register number is
198      the index in `arc_reg_names'.  */
199   for (i = 0; i < arc_reg_names_count; i++)
200     {
201       if (! arc_opval_supported (&arc_reg_names[i]))
202         continue;
203       /* Use symbol_create here instead of symbol_new so we don't try to
204          output registers into the object file's symbol table.  */
205       symbol_table_insert (symbol_create (arc_reg_names[i].name, reg_section,
206                                           i, &zero_address_frag));
207     }
208
209   /* Tell `s_cpu' it's too late.  */
210   cpu_tables_init_p = 1;
211 }
212 \f
213 /* Insert an operand value into an instruction.
214    If REG is non-NULL, it is a register number and ignore VAL.  */
215
216 static arc_insn
217 arc_insert_operand (insn, operand, mods, reg, val, file, line)
218      arc_insn insn;
219      const struct arc_operand *operand;
220      int mods;
221      const struct arc_operand_value *reg;
222      offsetT val;
223      char *file;
224      unsigned int line;
225 {
226   if (operand->bits != 32)
227     {
228       long min, max;
229       offsetT test;
230
231       if ((operand->flags & ARC_OPERAND_SIGNED) != 0)
232         {
233           if ((operand->flags & ARC_OPERAND_SIGNOPT) != 0)
234             max = (1 << operand->bits) - 1;
235           else
236             max = (1 << (operand->bits - 1)) - 1;
237           min = - (1 << (operand->bits - 1));
238         }
239       else
240         {
241           max = (1 << operand->bits) - 1;
242           min = 0;
243         }
244
245       if ((operand->flags & ARC_OPERAND_NEGATIVE) != 0)
246         test = - val;
247       else
248         test = val;
249
250       if (test < (offsetT) min || test > (offsetT) max)
251         {
252           const char *err =
253             _("operand out of range (%s not between %ld and %ld)");
254           char buf[100];
255
256           sprint_value (buf, test);
257           if (file == (char *) NULL)
258             as_warn (err, buf, min, max);
259           else
260             as_warn_where (file, line, err, buf, min, max);
261         }
262     }
263
264   if (operand->insert)
265     {
266       const char *errmsg;
267
268       errmsg = NULL;
269       insn = (*operand->insert) (insn, operand, mods, reg, (long) val, &errmsg);
270       if (errmsg != (const char *) NULL)
271         as_warn (errmsg);
272     }
273   else
274     insn |= (((long) val & ((1 << operand->bits) - 1))
275              << operand->shift);
276
277   return insn;
278 }
279
280 /* We need to keep a list of fixups.  We can't simply generate them as
281    we go, because that would require us to first create the frag, and
282    that would screw up references to ``.''.  */
283
284 struct arc_fixup
285 {
286   /* index into `arc_operands' */
287   int opindex;
288   expressionS exp;
289 };
290
291 #define MAX_FIXUPS 5
292
293 #define MAX_SUFFIXES 5
294
295 /* This routine is called for each instruction to be assembled.  */
296
297 void
298 md_assemble (str)
299      char *str;
300 {
301   const struct arc_opcode *opcode;
302   char *start;
303   arc_insn insn;
304   static int init_tables_p = 0;
305
306   /* Opcode table initialization is deferred until here because we have to
307      wait for a possible .cpu command.  */
308   if (!init_tables_p)
309     {
310       init_opcode_tables (arc_mach_type);
311       init_tables_p = 1;
312     }
313
314   /* Skip leading white space.  */
315   while (isspace (*str))
316     str++;
317
318   /* The instructions are stored in lists hashed by the first letter (though
319      we needn't care how they're hashed).  Get the first in the list.  */
320
321   opcode = arc_opcode_lookup_asm (str);
322
323   /* Keep looking until we find a match.  */
324
325   start = str;
326   for ( ; opcode != NULL; opcode = ARC_OPCODE_NEXT_ASM (opcode))
327     {
328       int past_opcode_p, fc, num_suffixes;
329       char *syn;
330       struct arc_fixup fixups[MAX_FIXUPS];
331       /* Used as a sanity check.  If we need a limm reloc, make sure we ask
332          for an extra 4 bytes from frag_more.  */
333       int limm_reloc_p;
334       const struct arc_operand_value *insn_suffixes[MAX_SUFFIXES];
335
336       /* Is this opcode supported by the selected cpu?  */
337       if (! arc_opcode_supported (opcode))
338         continue;
339
340       /* Scan the syntax string.  If it doesn't match, try the next one.  */
341
342       arc_opcode_init_insert ();
343       insn = opcode->value;
344       fc = 0;
345       past_opcode_p = 0;
346       num_suffixes = 0;
347       limm_reloc_p = 0;
348
349       /* We don't check for (*str != '\0') here because we want to parse
350          any trailing fake arguments in the syntax string.  */
351       for (str = start, syn = opcode->syntax; *syn != '\0'; )
352         {
353           int mods;
354           const struct arc_operand *operand;
355
356           /* Non operand chars must match exactly.  */
357           if (*syn != '%' || *++syn == '%')
358             {
359               /* Handle '+' specially as we want to allow "ld r0,[sp-4]".  */
360               /* ??? The syntax has changed to [sp,-4].  */
361               if (0 && *syn == '+' && *str == '-')
362                 {
363                   /* Skip over syn's +, but leave str's - alone.
364                      That makes the case identical to "ld r0,[sp+-4]".  */
365                   ++syn;
366                 }
367               else if (*str == *syn)
368                 {
369                   if (*syn == ' ')
370                     past_opcode_p = 1;
371                   ++syn;
372                   ++str;
373                 }
374               else
375                 break;
376               continue;
377             }
378
379           /* We have an operand.  Pick out any modifiers.  */
380           mods = 0;
381           while (ARC_MOD_P (arc_operands[arc_operand_map[*syn]].flags))
382             {
383               mods |= arc_operands[arc_operand_map[*syn]].flags & ARC_MOD_BITS;
384               ++syn;
385             }
386           operand = arc_operands + arc_operand_map[*syn];
387           if (operand->fmt == 0)
388             as_fatal (_("unknown syntax format character `%c'"), *syn);
389
390           if (operand->flags & ARC_OPERAND_FAKE)
391             {
392               const char *errmsg = NULL;
393               if (operand->insert)
394                 {
395                   insn = (*operand->insert) (insn, operand, mods, NULL, 0, &errmsg);
396                   /* If we get an error, go on to try the next insn.  */
397                   if (errmsg)
398                     break;
399                 }
400               ++syn;
401             }
402           /* Are we finished with suffixes?  */
403           else if (!past_opcode_p)
404             {
405               int found;
406               char c;
407               char *s,*t;
408               const struct arc_operand_value *suf,*suffix,*suffix_end;
409
410               if (!(operand->flags & ARC_OPERAND_SUFFIX))
411                 abort ();
412
413               /* If we're at a space in the input string, we want to skip the
414                  remaining suffixes.  There may be some fake ones though, so
415                  just go on to try the next one.  */
416               if (*str == ' ')
417                 {
418                   ++syn;
419                   continue;
420                 }
421
422               s = str;
423               if (mods & ARC_MOD_DOT)
424                 {
425                   if (*s != '.')
426                     break;
427                   ++s;
428                 }
429               else
430                 {
431                   /* This can happen in "b.nd foo" and we're currently looking
432                      for "%q" (ie: a condition code suffix).  */
433                   if (*s == '.')
434                     {
435                       ++syn;
436                       continue;
437                     }
438                 }
439
440               /* Pick the suffix out and look it up via the hash table.  */
441               for (t = s; *t && isalpha (*t); ++t)
442                 continue;
443               c = *t;
444               *t = '\0';
445               suf = hash_find (arc_suffix_hash, s);
446               *t = c;
447               if (!suf)
448                 {
449                   /* This can happen in "blle foo" and we're currently using
450                      the template "b%q%.n %j".  The "bl" insn occurs later in
451                      the table so "lle" isn't an illegal suffix.  */
452                   break;
453                 }
454
455               /* Is it the right type?  Note that the same character is used
456                  several times, so we have to examine all of them.  This is
457                  relatively efficient as equivalent entries are kept
458                  together.  If it's not the right type, don't increment `str'
459                  so we try the next one in the series.  */
460               found = 0;
461               suffix_end = arc_suffixes + arc_suffixes_count;
462               for (suffix = suf;
463                    suffix < suffix_end && strcmp (suffix->name, suf->name) == 0;
464                    ++suffix)
465                 {
466                   if (arc_operands[suffix->type].fmt == *syn)
467                     {
468                       /* Insert the suffix's value into the insn.  */
469                       if (operand->insert)
470                         insn = (*operand->insert) (insn, operand,
471                                                    mods, NULL, suffix->value,
472                                                    NULL);
473                       else
474                         insn |= suffix->value << operand->shift;
475
476                       str = t;
477                       found = 1;
478                       break;
479                     }
480                 }
481               ++syn;
482               if (!found)
483                 ; /* Wrong type.  Just go on to try next insn entry.  */
484               else
485                 {
486                   if (num_suffixes == MAX_SUFFIXES)
487                     as_bad (_("too many suffixes"));
488                   else
489                     insn_suffixes[num_suffixes++] = suffix;
490                 }
491             }
492           else
493             /* This is either a register or an expression of some kind.  */
494             {
495               char c;
496               char *hold;
497               const struct arc_operand_value *reg = NULL;
498               long value = 0;
499               expressionS exp;
500
501               if (operand->flags & ARC_OPERAND_SUFFIX)
502                 abort ();
503
504               /* Is there anything left to parse?
505                  We don't check for this at the top because we want to parse
506                  any trailing fake arguments in the syntax string.  */
507               if (*str == '\0')
508                 break;
509 #if 0
510               /* Is this a syntax character?  Eg: is there a '[' present when
511                  there shouldn't be?  */
512               if (!isalnum (*str)
513                   /* '.' as in ".LLC0" */
514                   && *str != '.'
515                   /* '_' as in "_print" */
516                   && *str != '_'
517                   /* '-' as in "[fp,-4]" */
518                   && *str != '-'
519                   /* '%' as in "%ia(_func)" */
520                   && *str != '%')
521                 break;
522 #endif
523
524               /* Parse the operand.  */
525               hold = input_line_pointer;
526               input_line_pointer = str;
527               expression (&exp);
528               str = input_line_pointer;
529               input_line_pointer = hold;
530
531               if (exp.X_op == O_illegal)
532                 as_bad (_("illegal operand"));
533               else if (exp.X_op == O_absent)
534                 as_bad (_("missing operand"));
535               else if (exp.X_op == O_constant)
536                 {
537                   value = exp.X_add_number;
538                 }
539               else if (exp.X_op == O_register)
540                 {
541                   reg = arc_reg_names + exp.X_add_number;
542                 }
543               else
544                 {
545                   /* We need to generate a fixup for this expression.  */
546                   if (fc >= MAX_FIXUPS)
547                     as_fatal (_("too many fixups"));
548                   fixups[fc].exp = exp;
549
550                   /* If this is a register constant (IE: one whose
551                      register value gets stored as 61-63) then this
552                      must be a limm.  We don't support shimm relocs.  */
553                   /* ??? This bit could use some cleaning up.
554                      Referencing the format chars like this goes
555                      against style.  */
556 #define IS_REG_OPERAND(o) ((o) == 'a' || (o) == 'b' || (o) == 'c')
557                   if (IS_REG_OPERAND (*syn))
558                     {
559                       const char *junk;
560
561                       fixups[fc].opindex = arc_operand_map['L'];
562                       limm_reloc_p = 1;
563                       /* Tell insert_reg we need a limm.  This is
564                          needed because the value at this point is
565                          zero, a shimm.  */
566                       /* ??? We need a cleaner interface than this.  */
567                       (*arc_operands[arc_operand_map['Q']].insert)
568                         (insn, operand, mods, reg, 0L, &junk);
569                     }
570                   else
571                     fixups[fc].opindex = arc_operand_map[*syn];
572                   ++fc;
573                   value = 0;
574                 }
575
576               /* Insert the register or expression into the instruction.  */
577               if (operand->insert)
578                 {
579                   const char *errmsg = NULL;
580                   insn = (*operand->insert) (insn, operand, mods,
581                                              reg, (long) value, &errmsg);
582 #if 0
583                   if (errmsg != (const char *) NULL)
584                     as_warn (errmsg);
585 #endif
586                   /* FIXME: We want to try shimm insns for limm ones.  But if
587                      the constant won't fit, we must go on to try the next
588                      possibility.  Where do we issue warnings for constants
589                      that are too big then?  At present, we'll flag the insn
590                      as unrecognizable!  Maybe have the "bad instruction"
591                      error message include our `errmsg'?  */
592                   if (errmsg != (const char *) NULL)
593                     break;
594                 }
595               else
596                 insn |= (value & ((1 << operand->bits) - 1)) << operand->shift;
597
598               ++syn;
599             }
600         }
601
602       /* If we're at the end of the syntax string, we're done.  */
603       /* FIXME: try to move this to a separate function.  */
604       if (*syn == '\0')
605         {
606           int i;
607           char *f;
608           long limm, limm_p;
609
610           /* For the moment we assume a valid `str' can only contain blanks
611              now.  IE: We needn't try again with a longer version of the
612              insn and it is assumed that longer versions of insns appear
613              before shorter ones (eg: lsr r2,r3,1 vs lsr r2,r3).  */
614
615           while (isspace (*str))
616             ++str;
617
618           if (*str != '\0')
619             as_bad (_("junk at end of line: `%s'"), str);
620
621           /* Is there a limm value?  */
622           limm_p = arc_opcode_limm_p (&limm);
623
624           /* Perform various error and warning tests.  */
625
626           {
627             static int in_delay_slot_p = 0;
628             static int prev_insn_needs_cc_nop_p = 0;
629             /* delay slot type seen */
630             int delay_slot_type = ARC_DELAY_NONE;
631             /* conditional execution flag seen */
632             int conditional = 0;
633             /* 1 if condition codes are being set */
634             int cc_set_p = 0;
635             /* 1 if conditional branch, including `b' "branch always" */
636             int cond_branch_p = opcode->flags & ARC_OPCODE_COND_BRANCH;
637             int need_cc_nop_p = 0;
638
639             for (i = 0; i < num_suffixes; ++i)
640               {
641                 switch (arc_operands[insn_suffixes[i]->type].fmt)
642                   {
643                   case 'n' :
644                     delay_slot_type = insn_suffixes[i]->value;
645                     break;
646                   case 'q' :
647                     conditional = insn_suffixes[i]->value;
648                     break;
649                   case 'f' :
650                     cc_set_p = 1;
651                     break;
652                   }
653               }
654
655             /* Putting an insn with a limm value in a delay slot is supposed to
656                be legal, but let's warn the user anyway.  Ditto for 8 byte
657                jumps with delay slots.  */
658             if (in_delay_slot_p && limm_p)
659               as_warn (_("8 byte instruction in delay slot"));
660             if (delay_slot_type != ARC_DELAY_NONE && limm_p)
661               as_warn (_("8 byte jump instruction with delay slot"));
662             in_delay_slot_p = (delay_slot_type != ARC_DELAY_NONE) && !limm_p;
663
664             /* Warn when a conditional branch immediately follows a set of
665                the condition codes.  Note that this needn't be done if the
666                insn that sets the condition codes uses a limm.  */
667             if (cond_branch_p && conditional != 0 /* 0 = "always" */
668                 && prev_insn_needs_cc_nop_p)
669               as_warn (_("conditional branch follows set of flags"));
670             prev_insn_needs_cc_nop_p = cc_set_p && !limm_p;
671           }
672
673           /* Write out the instruction.
674              It is important to fetch enough space in one call to `frag_more'.
675              We use (f - frag_now->fr_literal) to compute where we are and we
676              don't want frag_now to change between calls.  */
677           if (limm_p)
678             {
679               f = frag_more (8);
680               md_number_to_chars (f, insn, 4);
681               md_number_to_chars (f + 4, limm, 4);
682             }
683           else if (limm_reloc_p)
684             {
685               /* We need a limm reloc, but the tables think we don't.  */
686               abort ();
687             }
688           else
689             {
690               f = frag_more (4);
691               md_number_to_chars (f, insn, 4);
692             }
693
694           /* Create any fixups.  */
695           for (i = 0; i < fc; ++i)
696             {
697               int op_type, reloc_type;
698               expressionS exptmp;
699               const struct arc_operand *operand;
700
701               /* Create a fixup for this operand.
702                  At this point we do not use a bfd_reloc_code_real_type for
703                  operands residing in the insn, but instead just use the
704                  operand index.  This lets us easily handle fixups for any
705                  operand type, although that is admittedly not a very exciting
706                  feature.  We pick a BFD reloc type in md_apply_fix.
707
708                  Limm values (4 byte immediate "constants") must be treated
709                  normally because they're not part of the actual insn word
710                  and thus the insertion routines don't handle them.  */
711
712               if (arc_operands[fixups[i].opindex].flags & ARC_OPERAND_LIMM)
713                 {
714                   op_type = fixups[i].opindex;
715                   /* FIXME: can we add this data to the operand table?  */
716                   if (op_type == arc_operand_map['L'])
717                     reloc_type = BFD_RELOC_32;
718                   else if (op_type == arc_operand_map['J'])
719                     reloc_type = BFD_RELOC_ARC_B26;
720                   else
721                     abort ();
722                   reloc_type = get_arc_exp_reloc_type (1, reloc_type,
723                                                        &fixups[i].exp,
724                                                        &exptmp);
725                 }
726               else
727                 {
728                   op_type = get_arc_exp_reloc_type (0, fixups[i].opindex,
729                                                     &fixups[i].exp, &exptmp);
730                   reloc_type = op_type + (int) BFD_RELOC_UNUSED;
731                 }
732               operand = &arc_operands[op_type];
733               fix_new_exp (frag_now,
734                            ((f - frag_now->fr_literal)
735                             + (operand->flags & ARC_OPERAND_LIMM ? 4 : 0)), 4,
736                            &exptmp,
737                            (operand->flags & ARC_OPERAND_RELATIVE_BRANCH) != 0,
738                            (bfd_reloc_code_real_type) reloc_type);
739             }
740
741           /* All done.  */
742           return;
743         }
744
745       /* Try the next entry.  */
746     }
747
748   as_bad (_("bad instruction `%s'"), start);
749 }
750 \f
751 /* ??? This was copied from tc-sparc.c, I think.  Is it necessary?  */
752
753 static void
754 arc_common (ignore)
755      int ignore;
756 {
757   char *name;
758   char c;
759   char *p;
760   int temp, size;
761   symbolS *symbolP;
762
763   name = input_line_pointer;
764   c = get_symbol_end ();
765   /* just after name is now '\0' */
766   p = input_line_pointer;
767   *p = c;
768   SKIP_WHITESPACE ();
769   if (*input_line_pointer != ',')
770     {
771       as_bad (_("expected comma after symbol-name"));
772       ignore_rest_of_line ();
773       return;
774     }
775   input_line_pointer++;         /* skip ',' */
776   if ((temp = get_absolute_expression ()) < 0)
777     {
778       as_bad (_(".COMMon length (%d.) <0! Ignored."), temp);
779       ignore_rest_of_line ();
780       return;
781     }
782   size = temp;
783   *p = 0;
784   symbolP = symbol_find_or_make (name);
785   *p = c;
786   if (S_IS_DEFINED (symbolP) && ! S_IS_COMMON (symbolP))
787     {
788       as_bad (_("ignoring attempt to re-define symbol"));
789       ignore_rest_of_line ();
790       return;
791     }
792   if (S_GET_VALUE (symbolP) != 0)
793     {
794       if (S_GET_VALUE (symbolP) != size)
795         {
796           as_warn (_("Length of .comm \"%s\" is already %ld. Not changed to %d."),
797                    S_GET_NAME (symbolP), (long) S_GET_VALUE (symbolP), size);
798         }
799     }
800   assert (symbolP->sy_frag == &zero_address_frag);
801   if (*input_line_pointer != ',')
802     {
803       as_bad (_("expected comma after common length"));
804       ignore_rest_of_line ();
805       return;
806     }
807   input_line_pointer++;
808   SKIP_WHITESPACE ();
809   if (*input_line_pointer != '"')
810     {
811       temp = get_absolute_expression ();
812       if (temp < 0)
813         {
814           temp = 0;
815           as_warn (_("Common alignment negative; 0 assumed"));
816         }
817       if (symbolP->local)
818         {
819           segT old_sec;
820           int old_subsec;
821           char *p;
822           int align;
823
824         allocate_bss:
825           old_sec = now_seg;
826           old_subsec = now_subseg;
827           align = temp;
828           record_alignment (bss_section, align);
829           subseg_set (bss_section, 0);
830           if (align)
831             frag_align (align, 0, 0);
832           if (S_GET_SEGMENT (symbolP) == bss_section)
833             symbolP->sy_frag->fr_symbol = 0;
834           symbolP->sy_frag = frag_now;
835           p = frag_var (rs_org, 1, 1, (relax_substateT) 0, symbolP,
836                         (offsetT) size, (char *) 0);
837           *p = 0;
838           S_SET_SEGMENT (symbolP, bss_section);
839           S_CLEAR_EXTERNAL (symbolP);
840           subseg_set (old_sec, old_subsec);
841         }
842       else
843         {
844         allocate_common:
845           S_SET_VALUE (symbolP, (valueT) size);
846           S_SET_ALIGN (symbolP, temp);
847           S_SET_EXTERNAL (symbolP);
848           S_SET_SEGMENT (symbolP, bfd_com_section_ptr);
849         }
850     }
851   else
852     {
853       input_line_pointer++;
854       /* ??? Some say data, some say bss.  */
855       if (strncmp (input_line_pointer, ".bss\"", 5)
856           && strncmp (input_line_pointer, ".data\"", 6))
857         {
858           input_line_pointer--;
859           goto bad_common_segment;
860         }
861       while (*input_line_pointer++ != '"')
862         ;
863       goto allocate_common;
864     }
865   demand_empty_rest_of_line ();
866   return;
867
868   {
869   bad_common_segment:
870     p = input_line_pointer;
871     while (*p && *p != '\n')
872       p++;
873     c = *p;
874     *p = '\0';
875     as_bad (_("bad .common segment %s"), input_line_pointer + 1);
876     *p = c;
877     input_line_pointer = p;
878     ignore_rest_of_line ();
879     return;
880   }
881 }
882
883 /* Select the cpu we're assembling for.  */
884
885 static void
886 arc_cpu (ignore)
887      int ignore;
888 {
889   int mach;
890   char c;
891   char *cpu;
892
893   /* If an instruction has already been seen, it's too late.  */
894   if (cpu_tables_init_p)
895     {
896       as_bad (_(".cpu command must appear before any instructions"));
897       ignore_rest_of_line ();
898       return;
899     }
900
901   cpu = input_line_pointer;
902   c = get_symbol_end ();
903   mach = arc_get_mach (cpu);
904   *input_line_pointer = c;
905   if (mach == -1)
906     goto bad_cpu;
907
908   demand_empty_rest_of_line ();
909
910   /* The cpu may have been selected on the command line.
911      The choices must match.  */
912   /* ??? This was a command line option early on.  It's gone now, but
913      leave this in.  */
914   if (mach_type_specified_p && mach != arc_mach_type)
915     as_bad (_(".cpu conflicts with previous value"));
916   else
917     {
918       arc_mach_type = mach;
919       mach_type_specified_p = 1;
920       if (!bfd_set_arch_mach (stdoutput, bfd_arch_arc, mach))
921         as_warn (_("could not set architecture and machine"));
922     }
923   return;
924
925  bad_cpu:
926   as_bad (_("bad .cpu op"));
927   ignore_rest_of_line ();
928 }
929
930 #if 0
931 /* The .rename pseudo-op.  This is used by gcc to implement
932    -mmangle-cpu-libgcc.  */
933
934 static void
935 arc_rename (ignore)
936      int ignore;
937 {
938   char *name,*new;
939   char c;
940   symbolS *sym;
941   int len;
942
943   name = input_line_pointer;
944   c = get_symbol_end ();
945   sym = symbol_find_or_make (name);
946   *input_line_pointer = c;
947
948   if (*input_line_pointer != ',')
949     {
950       as_bad (_("missing rename string"));
951       ignore_rest_of_line ();
952       return;
953     }
954   ++input_line_pointer;
955   SKIP_WHITESPACE ();
956
957   name = input_line_pointer;
958   c = get_symbol_end ();
959   if (*name == '\0')
960     {
961       *input_line_pointer = c;
962       as_bad (_("invalid symbol to rename to"));
963       ignore_rest_of_line ();
964       return;
965     }
966   new = (char *) xmalloc (strlen (name) + 1);
967   strcpy (new, name);
968   *input_line_pointer = c;
969   sym->sy_tc.real_name = new;
970
971   demand_empty_rest_of_line ();
972 }
973 #endif
974 \f
975 /* Turn a string in input_line_pointer into a floating point constant of type
976    type, and store the appropriate bytes in *litP.  The number of LITTLENUMS
977    emitted is stored in *sizeP.
978    An error message is returned, or NULL on OK.  */
979
980 /* Equal to MAX_PRECISION in atof-ieee.c */
981 #define MAX_LITTLENUMS 6
982
983 char *
984 md_atof (type, litP, sizeP)
985      char type;
986      char *litP;
987      int *sizeP;
988 {
989   int prec;
990   LITTLENUM_TYPE words[MAX_LITTLENUMS];
991   LITTLENUM_TYPE *wordP;
992   char *t;
993   char *atof_ieee ();
994
995   switch (type)
996     {
997     case 'f':
998     case 'F':
999       prec = 2;
1000       break;
1001
1002     case 'd':
1003     case 'D':
1004       prec = 4;
1005       break;
1006
1007     default:
1008       *sizeP = 0;
1009       return _("bad call to md_atof");
1010     }
1011
1012   t = atof_ieee (input_line_pointer, type, words);
1013   if (t)
1014     input_line_pointer = t;
1015   *sizeP = prec * sizeof (LITTLENUM_TYPE);
1016   for (wordP = words; prec--;)
1017     {
1018       md_number_to_chars (litP, (valueT) (*wordP++), sizeof (LITTLENUM_TYPE));
1019       litP += sizeof (LITTLENUM_TYPE);
1020     }
1021
1022   return NULL;
1023 }
1024
1025 /* Write a value out to the object file, using the appropriate
1026    endianness.  */
1027
1028 void
1029 md_number_to_chars (buf, val, n)
1030      char *buf;
1031      valueT val;
1032      int n;
1033 {
1034   if (target_big_endian)
1035     number_to_chars_bigendian (buf, val, n);
1036   else
1037     number_to_chars_littleendian (buf, val, n);
1038 }
1039
1040 /* Round up a section size to the appropriate boundary. */
1041
1042 valueT
1043 md_section_align (segment, size)
1044      segT segment;
1045      valueT size;
1046 {
1047   int align = bfd_get_section_alignment (stdoutput, segment);
1048
1049   return ((size + (1 << align) - 1) & (-1 << align));
1050 }
1051
1052 /* We don't have any form of relaxing.  */
1053
1054 int
1055 md_estimate_size_before_relax (fragp, seg)
1056      fragS *fragp;
1057      asection *seg;
1058 {
1059   abort ();
1060 }
1061
1062 /* Convert a machine dependent frag.  We never generate these.  */
1063
1064 void
1065 md_convert_frag (abfd, sec, fragp)
1066      bfd *abfd;
1067      asection *sec;
1068      fragS *fragp;
1069 {
1070   abort ();
1071 }
1072
1073 /* Parse an operand that is machine-specific.
1074
1075    The ARC has a special %-op to adjust addresses so they're usable in
1076    branches.  The "st" is short for the STatus register.
1077    ??? Later expand this to take a flags value too.
1078
1079    ??? We can't create new expression types so we map the %-op's onto the
1080    existing syntax.  This means that the user could use the chosen syntax
1081    to achieve the same effect.  Perhaps put a special cookie in X_add_number
1082    to mark the expression as special.  */
1083
1084 void 
1085 md_operand (expressionP)
1086      expressionS *expressionP;
1087 {
1088   char *p = input_line_pointer;
1089
1090   if (*p == '%' && strncmp (p, "%st(", 4) == 0)
1091     {
1092       input_line_pointer += 4;
1093       expression (expressionP);
1094       if (*input_line_pointer != ')')
1095         {
1096           as_bad (_("missing ')' in %-op"));
1097           return;
1098         }
1099       ++input_line_pointer;
1100       if (expressionP->X_op == O_symbol
1101           && expressionP->X_add_number == 0
1102           /* I think this test is unnecessary but just as a sanity check... */
1103           && expressionP->X_op_symbol == NULL)
1104         {
1105           expressionS two;
1106
1107           expressionP->X_op = O_right_shift;
1108           two.X_op = O_constant;
1109           two.X_add_symbol = two.X_op_symbol = NULL;
1110           two.X_add_number = 2;
1111           expressionP->X_op_symbol = make_expr_symbol (&two);
1112         }
1113       /* allow %st(sym1-sym2) */
1114       else if (expressionP->X_op == O_subtract
1115                && expressionP->X_add_symbol != NULL
1116                && expressionP->X_op_symbol != NULL
1117                && expressionP->X_add_number == 0)
1118         {
1119           expressionS two;
1120
1121           expressionP->X_add_symbol = make_expr_symbol (expressionP);
1122           expressionP->X_op = O_right_shift;
1123           two.X_op = O_constant;
1124           two.X_add_symbol = two.X_op_symbol = NULL;
1125           two.X_add_number = 2;
1126           expressionP->X_op_symbol = make_expr_symbol (&two);
1127         }
1128       else
1129         {
1130           as_bad (_("expression too complex for %%st"));
1131           return;
1132         }
1133     }
1134 }
1135
1136 /* We have no need to default values of symbols.
1137    We could catch register names here, but that is handled by inserting
1138    them all in the symbol table to begin with.  */
1139
1140 symbolS *
1141 md_undefined_symbol (name)
1142      char *name;
1143 {
1144   return 0;
1145 }
1146 \f
1147 /* Functions concerning expressions.  */
1148
1149 /* Parse a .byte, .word, etc. expression.
1150
1151    Values for the status register are specified with %st(label).
1152    `label' will be right shifted by 2.  */
1153
1154 void
1155 arc_parse_cons_expression (exp, nbytes)
1156      expressionS *exp;
1157      int nbytes;
1158 {
1159   expr (0, exp);
1160 }
1161
1162 /* Record a fixup for a cons expression.  */
1163
1164 void
1165 arc_cons_fix_new (frag, where, nbytes, exp)
1166      fragS *frag;
1167      int where;
1168      int nbytes;
1169      expressionS *exp;
1170 {
1171   if (nbytes == 4)
1172     {
1173       int reloc_type;
1174       expressionS exptmp;
1175
1176       /* This may be a special ARC reloc (eg: %st()).  */
1177       reloc_type = get_arc_exp_reloc_type (1, BFD_RELOC_32, exp, &exptmp);
1178       fix_new_exp (frag, where, nbytes, &exptmp, 0, reloc_type);
1179     }
1180   else
1181     {
1182       fix_new_exp (frag, where, nbytes, exp, 0,
1183                    nbytes == 2 ? BFD_RELOC_16
1184                    : nbytes == 8 ? BFD_RELOC_64
1185                    : BFD_RELOC_32);
1186     }
1187 }
1188 \f
1189 /* Functions concerning relocs.  */
1190
1191 /* The location from which a PC relative jump should be calculated,
1192    given a PC relative reloc.  */
1193
1194 long 
1195 md_pcrel_from (fixP)
1196      fixS *fixP;
1197 {
1198   if (fixP->fx_addsy != (symbolS *) NULL
1199       && ! S_IS_DEFINED (fixP->fx_addsy))
1200     {
1201       /* The symbol is undefined.  Let the linker figure it out.  */
1202       return 0;
1203     }
1204
1205   /* Return the address of the delay slot.  */
1206   return fixP->fx_frag->fr_address + fixP->fx_where + fixP->fx_size;
1207 }
1208
1209 /* Compute the reloc type of an expression.
1210    The possibly modified expression is stored in EXPNEW.
1211
1212    This is used to convert the expressions generated by the %-op's into
1213    the appropriate operand type.  It is called for both data in instructions
1214    (operands) and data outside instructions (variables, debugging info, etc.).
1215
1216    Currently supported %-ops:
1217
1218    %st(symbol): represented as "symbol >> 2"
1219                 "st" is short for STatus as in the status register (pc)
1220
1221    DEFAULT_TYPE is the type to use if no special processing is required.
1222
1223    DATA_P is non-zero for data or limm values, zero for insn operands.
1224    Remember that the opcode "insertion fns" cannot be used on data, they're
1225    only for inserting operands into insns.  They also can't be used for limm
1226    values as the insertion routines don't handle limm values.  When called for
1227    insns we return fudged reloc types (real_value - BFD_RELOC_UNUSED).  When
1228    called for data or limm values we use real reloc types.  */
1229
1230 static int
1231 get_arc_exp_reloc_type (data_p, default_type, exp, expnew)
1232      int data_p;
1233      int default_type;
1234      expressionS *exp;
1235      expressionS *expnew;
1236 {
1237   /* If the expression is "symbol >> 2" we must change it to just "symbol",
1238      as fix_new_exp can't handle it.  Similarily for (symbol - symbol) >> 2.
1239      That's ok though.  What's really going on here is that we're using
1240      ">> 2" as a special syntax for specifying BFD_RELOC_ARC_B26.  */
1241
1242   if (exp->X_op == O_right_shift
1243       && exp->X_op_symbol != NULL
1244       && exp->X_op_symbol->sy_value.X_op == O_constant
1245       && exp->X_op_symbol->sy_value.X_add_number == 2
1246       && exp->X_add_number == 0)
1247     {
1248       if (exp->X_add_symbol != NULL
1249           && (exp->X_add_symbol->sy_value.X_op == O_constant
1250               || exp->X_add_symbol->sy_value.X_op == O_symbol))
1251         {
1252           *expnew = *exp;
1253           expnew->X_op = O_symbol;
1254           expnew->X_op_symbol = NULL;
1255           return data_p ? BFD_RELOC_ARC_B26 : arc_operand_map['J'];
1256         }
1257       else if (exp->X_add_symbol != NULL
1258                && exp->X_add_symbol->sy_value.X_op == O_subtract)
1259         {
1260           *expnew = exp->X_add_symbol->sy_value;
1261           return data_p ? BFD_RELOC_ARC_B26 : arc_operand_map['J'];
1262         }
1263     }
1264
1265   *expnew = *exp;
1266   return default_type;
1267 }
1268
1269 /* Apply a fixup to the object code.  This is called for all the
1270    fixups we generated by the call to fix_new_exp, above.  In the call
1271    above we used a reloc code which was the largest legal reloc code
1272    plus the operand index.  Here we undo that to recover the operand
1273    index.  At this point all symbol values should be fully resolved,
1274    and we attempt to completely resolve the reloc.  If we can not do
1275    that, we determine the correct reloc code and put it back in the fixup.  */
1276
1277 int
1278 md_apply_fix3 (fixP, valueP, seg)
1279      fixS *fixP;
1280      valueT *valueP;
1281      segT seg;
1282 {
1283   /*char *buf = fixP->fx_where + fixP->fx_frag->fr_literal;*/
1284   valueT value;
1285
1286   /* FIXME FIXME FIXME: The value we are passed in *valueP includes
1287      the symbol values.  Since we are using BFD_ASSEMBLER, if we are
1288      doing this relocation the code in write.c is going to call
1289      bfd_perform_relocation, which is also going to use the symbol
1290      value.  That means that if the reloc is fully resolved we want to
1291      use *valueP since bfd_perform_relocation is not being used.
1292      However, if the reloc is not fully resolved we do not want to use
1293      *valueP, and must use fx_offset instead.  However, if the reloc
1294      is PC relative, we do want to use *valueP since it includes the
1295      result of md_pcrel_from.  This is confusing.  */
1296
1297   if (fixP->fx_addsy == (symbolS *) NULL)
1298     {
1299       value = *valueP;
1300       fixP->fx_done = 1;
1301     }
1302   else if (fixP->fx_pcrel)
1303     {
1304       value = *valueP;
1305       /* ELF relocations are against symbols.
1306          If this symbol is in a different section then we need to leave it for
1307          the linker to deal with.  Unfortunately, md_pcrel_from can't tell,
1308          so we have to undo it's effects here.  */
1309       if (S_IS_DEFINED (fixP->fx_addsy)
1310           && S_GET_SEGMENT (fixP->fx_addsy) != seg)
1311         value += md_pcrel_from (fixP);
1312     }
1313   else
1314     {
1315       value = fixP->fx_offset;
1316       if (fixP->fx_subsy != (symbolS *) NULL)
1317         {
1318           if (S_GET_SEGMENT (fixP->fx_subsy) == absolute_section)
1319             value -= S_GET_VALUE (fixP->fx_subsy);
1320           else
1321             {
1322               /* We can't actually support subtracting a symbol.  */
1323               as_bad_where (fixP->fx_file, fixP->fx_line,
1324                             _("expression too complex"));
1325             }
1326         }
1327     }
1328
1329   if ((int) fixP->fx_r_type >= (int) BFD_RELOC_UNUSED)
1330     {
1331       int opindex;
1332       const struct arc_operand *operand;
1333       char *where;
1334       arc_insn insn;
1335
1336       opindex = (int) fixP->fx_r_type - (int) BFD_RELOC_UNUSED;
1337
1338       operand = &arc_operands[opindex];
1339
1340       /* Fetch the instruction, insert the fully resolved operand
1341          value, and stuff the instruction back again.  */
1342       where = fixP->fx_frag->fr_literal + fixP->fx_where;
1343       if (target_big_endian)
1344         insn = bfd_getb32 ((unsigned char *) where);
1345       else
1346         insn = bfd_getl32 ((unsigned char *) where);
1347       insn = arc_insert_operand (insn, operand, -1, NULL, (offsetT) value,
1348                                  fixP->fx_file, fixP->fx_line);
1349       if (target_big_endian)
1350         bfd_putb32 ((bfd_vma) insn, (unsigned char *) where);
1351       else
1352         bfd_putl32 ((bfd_vma) insn, (unsigned char *) where);
1353
1354       if (fixP->fx_done)
1355         {
1356           /* Nothing else to do here.  */
1357           return 1;
1358         }
1359
1360       /* Determine a BFD reloc value based on the operand information.
1361          We are only prepared to turn a few of the operands into relocs.
1362          !!! Note that we can't handle limm values here.  Since we're using
1363          implicit addends the addend must be inserted into the instruction,
1364          however, the opcode insertion routines currently do nothing with
1365          limm values.  */
1366       if (operand->fmt == 'B')
1367         {
1368           assert ((operand->flags & ARC_OPERAND_RELATIVE_BRANCH) != 0
1369                   && operand->bits == 20
1370                   && operand->shift == 7);
1371           fixP->fx_r_type = BFD_RELOC_ARC_B22_PCREL;
1372         }
1373       else if (0 && operand->fmt == 'J')
1374         {
1375           assert ((operand->flags & ARC_OPERAND_ABSOLUTE_BRANCH) != 0
1376                   && operand->bits == 24
1377                   && operand->shift == 32);
1378           fixP->fx_r_type = BFD_RELOC_ARC_B26;
1379         }
1380       else if (0 && operand->fmt == 'L')
1381         {
1382           assert ((operand->flags & ARC_OPERAND_LIMM) != 0
1383                   && operand->bits == 32
1384                   && operand->shift == 32);
1385           fixP->fx_r_type = BFD_RELOC_32;
1386         }
1387       else
1388         {
1389           as_bad_where (fixP->fx_file, fixP->fx_line,
1390                         _("unresolved expression that must be resolved"));
1391           fixP->fx_done = 1;
1392           return 1;
1393         }
1394     }
1395   else
1396     {
1397       switch (fixP->fx_r_type)
1398         {
1399         case BFD_RELOC_8:
1400           md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
1401                               value, 1);
1402           break;
1403         case BFD_RELOC_16:
1404           md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
1405                               value, 2);
1406           break;
1407         case BFD_RELOC_32:
1408           md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
1409                               value, 4);
1410           break;
1411 #if 0
1412         case BFD_RELOC_64:
1413           md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
1414                               value, 8);
1415           break;
1416 #endif
1417         case BFD_RELOC_ARC_B26:
1418           /* If !fixP->fx_done then `value' is an implicit addend.
1419              We must shift it right by 2 in this case as well because the
1420              linker performs the relocation and then adds this in (as opposed
1421              to adding this in and then shifting right by 2).  */
1422           value >>= 2;
1423           md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
1424                               value, 4);
1425           break;
1426         default:
1427           abort ();
1428         }
1429     }
1430
1431   fixP->fx_addnumber = value;
1432
1433   return 1;
1434 }
1435
1436 /* Translate internal representation of relocation info to BFD target
1437    format.  */
1438
1439 arelent *
1440 tc_gen_reloc (section, fixP)
1441      asection *section;
1442      fixS *fixP;
1443 {
1444   arelent *reloc;
1445
1446   reloc = (arelent *) xmalloc (sizeof (arelent));
1447
1448   reloc->sym_ptr_ptr = &fixP->fx_addsy->bsym;
1449   reloc->address = fixP->fx_frag->fr_address + fixP->fx_where;
1450   reloc->howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
1451   if (reloc->howto == (reloc_howto_type *) NULL)
1452     {
1453       as_bad_where (fixP->fx_file, fixP->fx_line,
1454                     _("internal error: can't export reloc type %d (`%s')"),
1455                     fixP->fx_r_type, bfd_get_reloc_code_name (fixP->fx_r_type));
1456       return NULL;
1457     }
1458
1459   assert (!fixP->fx_pcrel == !reloc->howto->pc_relative);
1460
1461   reloc->addend = fixP->fx_addnumber;
1462
1463   return reloc;
1464 }
1465 \f
1466 /* Frobbers.  */
1467
1468 #if 0
1469 /* Set the real name if the .rename pseudo-op was used.
1470    Return 1 if the symbol should not be included in the symbol table.  */
1471
1472 int
1473 arc_frob_symbol (sym)
1474      symbolS *sym;
1475 {
1476   if (sym->sy_tc.real_name != (char *) NULL)
1477     S_SET_NAME (sym, sym->sy_tc.real_name);
1478
1479   return 0;
1480 }
1481 #endif