1/* tc-tic54x.c -- Assembly code for the Texas Instruments TMS320C54X
2   Copyright (C) 1999-2017 Free Software Foundation, Inc.
3   Contributed by Timothy Wall (twall@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 3, 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 the Free
19   Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
20   02110-1301, USA.  */
21
22/* Texas Instruments TMS320C54X machine specific gas.
23   Written by Timothy Wall (twall@alum.mit.edu).
24
25   Valuable things to do:
26   Pipeline conflict warnings
27   We encode/decode "ld #_label, dp" differently in relocatable files
28     This means we're not compatible with TI output containing those
29     expressions.  We store the upper nine bits; TI stores the lower nine
30     bits.  How they recover the original upper nine bits is beyond me.
31
32   Tests to add to expect testsuite:
33     '=' and '==' with .if, .elseif, and .break
34
35   Incompatibilities (mostly trivial):
36   We don't allow '''
37   We fill text section with zeroes instead of "nop"s
38   We don't convert '' or "" to a single instance
39   We don't convert '' to '\0'
40   We don't allow strings with .byte/.half/.short/.long
41   Probably details of the subsym stuff are different
42   TI sets labels to be data type 4 (T_INT); GAS uses T_NULL.
43
44   COFF1 limits section names to 8 characters.
45   Some of the default behavior changed from COFF1 to COFF2.  */
46
47#include "as.h"
48#include <limits.h>
49#include "safe-ctype.h"
50#include "sb.h"
51#include "macro.h"
52#include "subsegs.h"
53#include "struc-symbol.h"
54#include "opcode/tic54x.h"
55#include "obj-coff.h"
56#include <math.h>
57
58
59static struct stag
60{
61  symbolS *sym;		        /* Symbol for this stag; value is offset.  */
62  const char *name;		/* Shortcut to symbol name.  */
63  bfd_vma size;		        /* Size of struct/union.  */
64  int current_bitfield_offset;  /* Temporary for tracking fields.  */
65  int is_union;
66  struct stag_field		/* List of fields.  */
67  {
68    const char *name;
69    bfd_vma offset;		/* Of start of this field.  */
70    int bitfield_offset;	/* Of start of this field.  */
71    struct stag *stag;	        /* If field is struct/union.  */
72    struct stag_field *next;
73  } *field;
74  /* For nesting; used only in stag construction.  */
75  struct stag *inner;	        /* Enclosed .struct.  */
76  struct stag *outer;	        /* Enclosing .struct.  */
77} *current_stag = NULL;
78
79#define MAX_LINE 256 /* Lines longer than this are truncated by TI's asm.  */
80
81typedef struct _tic54x_insn
82{
83  const insn_template *tm;	/* Opcode template.  */
84
85  char mnemonic[MAX_LINE];	/* Opcode name/mnemonic.  */
86  char parmnemonic[MAX_LINE];   /* 2nd mnemonic of parallel insn.  */
87
88  int opcount;
89  struct opstruct
90  {
91    char buf[MAX_LINE];
92    enum optype type;
93    expressionS exp;
94  } operands[MAX_OPERANDS];
95
96  int paropcount;
97  struct opstruct paroperands[MAX_OPERANDS];
98
99  int is_lkaddr;
100  int lkoperand;
101  int words;			/* Size of insn in 16-bit words.  */
102  int using_default_dst;	/* Do we need to explicitly set an
103				   omitted OP_DST operand?  */
104  struct
105  {
106    unsigned short word;	     /* Final encoded opcode data.  */
107    int unresolved;
108    int r_nchars;		     /* Relocation size.  */
109    bfd_reloc_code_real_type r_type; /* Relocation type.  */
110    expressionS addr_expr;	     /* Storage for unresolved expressions.  */
111  } opcode[3];
112} tic54x_insn;
113
114enum cpu_version
115{
116  VNONE = 0, V541 = 1, V542 = 2, V543 = 3, V545 = 5, V548 = 8, V549 = 9,
117  V545LP = 15, V546LP = 16
118};
119
120enum address_mode
121{
122  c_mode,   /* 16-bit addresses.  */
123  far_mode  /* >16-bit addresses.  */
124};
125
126static segT stag_saved_seg;
127static subsegT stag_saved_subseg;
128
129const char comment_chars[] = ";";
130const char line_comment_chars[] = ";*#"; /* At column zero only.  */
131const char line_separator_chars[] = ""; /* Not permitted.  */
132
133int emitting_long = 0;
134
135/* Characters which indicate that this is a floating point constant.  */
136const char FLT_CHARS[] = "fF";
137
138/* Characters that can be used to separate mantissa from exp in FP
139   nums.  */
140const char EXP_CHARS[] = "eE";
141
142const char *md_shortopts = "";
143
144#define OPTION_ADDRESS_MODE     (OPTION_MD_BASE)
145#define OPTION_CPU_VERSION      (OPTION_ADDRESS_MODE + 1)
146#define OPTION_COFF_VERSION     (OPTION_CPU_VERSION + 1)
147#define OPTION_STDERR_TO_FILE   (OPTION_COFF_VERSION + 1)
148
149struct option md_longopts[] =
150{
151  { "mfar-mode",       no_argument,	    NULL, OPTION_ADDRESS_MODE },
152  { "mf",	       no_argument,	    NULL, OPTION_ADDRESS_MODE },
153  { "mcpu",	       required_argument,   NULL, OPTION_CPU_VERSION },
154  { "merrors-to-file", required_argument,   NULL, OPTION_STDERR_TO_FILE },
155  { "me",	       required_argument,   NULL, OPTION_STDERR_TO_FILE },
156  { NULL,              no_argument,         NULL, 0},
157};
158
159size_t md_longopts_size = sizeof (md_longopts);
160
161static int assembly_begun = 0;
162/* Addressing mode is not entirely implemented; the latest rev of the Other
163   assembler doesn't seem to make any distinction whatsoever; all relocations
164   are stored as extended relocatiosn.  Older versions used REL16 vs RELEXT16,
165   but now it seems all relocations are RELEXT16.  We use all RELEXT16.
166
167   The cpu version is kind of a waste of time as well.  There is one
168   instruction (RND) for LP devices only, and several for devices with
169   extended addressing only.  We include it for compatibility.  */
170static enum address_mode amode = c_mode;
171static enum cpu_version cpu = VNONE;
172
173/* Include string substitutions in listing?  */
174static int listing_sslist = 0;
175
176/* Did we do subsym substitutions on the line?  */
177static int substitution_line = 0;
178
179/* Last label seen.  */
180static symbolS *last_label_seen = NULL;
181
182/* This ensures that all new labels are unique.  */
183static int local_label_id;
184
185static struct hash_control *subsym_recurse_hash; /* Prevent infinite recurse.  */
186static struct hash_control *math_hash; /* Built-in math functions.  */
187/* Allow maximum levels of macro nesting; level 0 is the main substitution
188   symbol table.  The other assembler only does 32 levels, so there!  */
189static struct hash_control *subsym_hash[100];
190
191/* Keep track of local labels so we can substitute them before GAS sees them
192   since macros use their own 'namespace' for local labels, use a separate hash
193
194   We do our own local label handling 'cuz it's subtly different from the
195   stock GAS handling.
196
197   We use our own macro nesting counter, since GAS overloads it when expanding
198   other things (like conditionals and repeat loops).  */
199static int macro_level = 0;
200static struct hash_control *local_label_hash[100];
201/* Keep track of struct/union tags.  */
202static struct hash_control *stag_hash;
203static struct hash_control *op_hash;
204static struct hash_control *parop_hash;
205static struct hash_control *reg_hash;
206static struct hash_control *mmreg_hash;
207static struct hash_control *cc_hash;
208static struct hash_control *cc2_hash;
209static struct hash_control *cc3_hash;
210static struct hash_control *sbit_hash;
211static struct hash_control *misc_symbol_hash;
212
213/* Only word (et al.), align, or conditionals are allowed within
214   .struct/.union.  */
215#define ILLEGAL_WITHIN_STRUCT()					\
216  do								\
217    if (current_stag != NULL)					\
218      { 							\
219	as_bad (_("pseudo-op illegal within .struct/.union"));	\
220	return;							\
221      }								\
222  while (0)
223
224
225static void subsym_create_or_replace (char *, char *);
226static char *subsym_lookup (char *, int);
227static char *subsym_substitute (char *, int);
228
229
230void
231md_show_usage (FILE *stream)
232{
233  fprintf (stream, _("C54x-specific command line  options:\n"));
234  fprintf (stream, _("-mfar-mode | -mf          Use extended addressing\n"));
235  fprintf (stream, _("-mcpu=<CPU version>       Specify the CPU version\n"));
236  fprintf (stream, _("-merrors-to-file <filename>\n"));
237  fprintf (stream, _("-me <filename>            Redirect errors to a file\n"));
238}
239
240/* Output a single character (upper octect is zero).  */
241
242static void
243tic54x_emit_char (char c)
244{
245  expressionS expn;
246
247  expn.X_op = O_constant;
248  expn.X_add_number = c;
249  emit_expr (&expn, 2);
250}
251
252/* Walk backwards in the frag chain.  */
253
254static fragS *
255frag_prev (fragS *frag, segT seg)
256{
257  segment_info_type *seginfo = seg_info (seg);
258  fragS *fragp;
259
260  for (fragp = seginfo->frchainP->frch_root; fragp; fragp = fragp->fr_next)
261    if (fragp->fr_next == frag)
262      return fragp;
263
264  return NULL;
265}
266
267static fragS *
268bit_offset_frag (fragS *frag, segT seg)
269{
270  while (frag != NULL)
271    {
272      if (frag->fr_fix == 0
273	  && frag->fr_opcode == NULL
274	  && frag->tc_frag_data == 0)
275	frag = frag_prev (frag, seg);
276      else
277	return frag;
278    }
279  return NULL;
280}
281
282/* Return the number of bits allocated in the most recent word, or zero if
283   none. .field/.space/.bes may leave words partially allocated.  */
284
285static int
286frag_bit_offset (fragS *frag, segT seg)
287{
288  frag = bit_offset_frag (frag, seg);
289
290  if (frag)
291    return frag->fr_opcode != NULL ? -1 : frag->tc_frag_data;
292
293  return 0;
294}
295
296/* Read an expression from a C string; returns a pointer past the end of the
297   expression.  */
298
299static char *
300parse_expression (char *str, expressionS *expn)
301{
302  char *s;
303  char *tmp;
304
305  tmp = input_line_pointer;	/* Save line pointer.  */
306  input_line_pointer = str;
307  expression (expn);
308  s = input_line_pointer;
309  input_line_pointer = tmp;	/* Restore line pointer.  */
310  return s;			/* Return pointer to where parsing stopped.  */
311}
312
313/* .asg "character-string"|character-string, symbol
314
315   .eval is the only pseudo-op allowed to perform arithmetic on substitution
316   symbols.  all other use of symbols defined with .asg are currently
317   unsupported.  */
318
319static void
320tic54x_asg (int x ATTRIBUTE_UNUSED)
321{
322  int c;
323  char *name;
324  char *str;
325  int quoted = *input_line_pointer == '"';
326
327  ILLEGAL_WITHIN_STRUCT ();
328
329  if (quoted)
330    {
331      int len;
332      str = demand_copy_C_string (&len);
333      c = *input_line_pointer;
334    }
335  else
336    {
337      str = input_line_pointer;
338      while ((c = *input_line_pointer) != ',')
339	{
340	  if (is_end_of_line[(int) *input_line_pointer])
341	    break;
342	  ++input_line_pointer;
343	}
344      *input_line_pointer = 0;
345    }
346  if (c != ',')
347    {
348      as_bad (_("Comma and symbol expected for '.asg STRING, SYMBOL'"));
349      ignore_rest_of_line ();
350      return;
351    }
352
353  ++input_line_pointer;
354  c = get_symbol_name (&name);	/* Get terminator.  */
355  if (!ISALPHA (*name))
356    {
357      as_bad (_("symbols assigned with .asg must begin with a letter"));
358      ignore_rest_of_line ();
359      return;
360    }
361
362  str = xstrdup (str);
363  name = xstrdup (name);
364  subsym_create_or_replace (name, str);
365  (void) restore_line_pointer (c);
366  demand_empty_rest_of_line ();
367}
368
369/* .eval expression, symbol
370   There's something screwy about this.  The other assembler sometimes does and
371   sometimes doesn't substitute symbols defined with .eval.
372   We'll put the symbols into the subsym table as well as the normal symbol
373   table, since that's what works best.  */
374
375static void
376tic54x_eval (int x ATTRIBUTE_UNUSED)
377{
378  char c;
379  int value;
380  char *name;
381  symbolS *symbolP;
382  char valuestr[32], *tmp;
383  int quoted;
384
385  ILLEGAL_WITHIN_STRUCT ();
386
387  SKIP_WHITESPACE ();
388
389  quoted = *input_line_pointer == '"';
390  if (quoted)
391    ++input_line_pointer;
392  value = get_absolute_expression ();
393  if (quoted)
394    {
395      if (*input_line_pointer != '"')
396	{
397	  as_bad (_("Unterminated string after absolute expression"));
398	  ignore_rest_of_line ();
399	  return;
400	}
401      ++input_line_pointer;
402    }
403  if (*input_line_pointer++ != ',')
404    {
405      as_bad (_("Comma and symbol expected for '.eval EXPR, SYMBOL'"));
406      ignore_rest_of_line ();
407      return;
408    }
409  c = get_symbol_name (&name);	/* Get terminator.  */
410  name = xstrdup (name);
411  (void) restore_line_pointer (c);
412
413  if (!ISALPHA (*name))
414    {
415      as_bad (_("symbols assigned with .eval must begin with a letter"));
416      ignore_rest_of_line ();
417      return;
418    }
419  symbolP = symbol_new (name, absolute_section,
420			(valueT) value, &zero_address_frag);
421  SF_SET_LOCAL (symbolP);
422  symbol_table_insert (symbolP);
423
424  /* The "other" assembler sometimes doesn't put .eval's in the subsym table
425     But since there's not written rule as to when, don't even bother trying
426     to match their behavior.  */
427  sprintf (valuestr, "%d", value);
428  tmp = xstrdup (valuestr);
429  subsym_create_or_replace (name, tmp);
430
431  demand_empty_rest_of_line ();
432}
433
434/* .bss symbol, size [, [blocking flag] [, alignment flag]
435
436   alignment is to a longword boundary; blocking is to 128-word boundary.
437
438   1) if there is a hole in memory, this directive should attempt to fill it
439      (not yet implemented).
440
441   2) if the blocking flag is not set, allocate at the current SPC
442      otherwise, check to see if the current SPC plus the space to be
443      allocated crosses the page boundary (128 words).
444      if there's not enough space, create a hole and align with the next page
445      boundary.
446      (not yet implemented).  */
447
448static void
449tic54x_bss (int x ATTRIBUTE_UNUSED)
450{
451  char c;
452  char *name;
453  char *p;
454  int words;
455  segT current_seg;
456  subsegT current_subseg;
457  symbolS *symbolP;
458  int block = 0;
459  int align = 0;
460
461  ILLEGAL_WITHIN_STRUCT ();
462
463  current_seg = now_seg;	/* Save current seg.  */
464  current_subseg = now_subseg;	/* Save current subseg.  */
465
466  c = get_symbol_name (&name);	/* Get terminator.  */
467  if (c == '"')
468    c = * ++ input_line_pointer;
469  if (c != ',')
470    {
471      as_bad (_(".bss size argument missing\n"));
472      ignore_rest_of_line ();
473      return;
474    }
475
476  ++input_line_pointer;
477  words = get_absolute_expression ();
478  if (words < 0)
479    {
480      as_bad (_(".bss size %d < 0!"), words);
481      ignore_rest_of_line ();
482      return;
483    }
484
485  if (*input_line_pointer == ',')
486    {
487      /* The blocking flag may be missing.  */
488      ++input_line_pointer;
489      if (*input_line_pointer != ',')
490	block = get_absolute_expression ();
491      else
492	block = 0;
493
494      if (*input_line_pointer == ',')
495	{
496	  ++input_line_pointer;
497	  align = get_absolute_expression ();
498	}
499      else
500	align = 0;
501    }
502  else
503    block = align = 0;
504
505  subseg_set (bss_section, 0);
506  symbolP = symbol_find_or_make (name);
507
508  if (S_GET_SEGMENT (symbolP) == bss_section)
509    symbolP->sy_frag->fr_symbol = (symbolS *) NULL;
510
511  symbol_set_frag (symbolP, frag_now);
512  p = frag_var (rs_org, 1, 1, (relax_substateT) 0, symbolP,
513		(offsetT) (words * OCTETS_PER_BYTE), (char *) 0);
514  *p = 0;			/* Fill char.  */
515
516  S_SET_SEGMENT (symbolP, bss_section);
517
518  /* The symbol may already have been created with a preceding
519     ".globl" directive -- be careful not to step on storage class
520     in that case.  Otherwise, set it to static.  */
521  if (S_GET_STORAGE_CLASS (symbolP) != C_EXT)
522    S_SET_STORAGE_CLASS (symbolP, C_STAT);
523
524  if (align)
525    {
526      /* s_align eats end of line; restore it */
527      s_align_bytes (4);
528      --input_line_pointer;
529    }
530
531  if (block)
532    bss_section->flags |= SEC_TIC54X_BLOCK;
533
534  subseg_set (current_seg, current_subseg);	/* Restore current seg.  */
535  demand_empty_rest_of_line ();
536}
537
538static void
539stag_add_field_symbols (struct stag *stag,
540			const char *path,
541			bfd_vma base_offset,
542			symbolS *rootsym,
543			const char *root_stag_name)
544{
545  char * prefix;
546  struct stag_field *field = stag->field;
547
548  /* Construct a symbol for every field contained within this structure
549     including fields within structure fields.  */
550  prefix = concat (path, *path ? "." : "", NULL);
551
552  while (field != NULL)
553    {
554      char *name = concat (prefix, field->name, NULL);
555
556      if (rootsym == NULL)
557	{
558	  symbolS *sym;
559	  sym = symbol_new (name, absolute_section,
560			    (field->stag ? field->offset :
561			     (valueT) (base_offset + field->offset)),
562			    &zero_address_frag);
563	  SF_SET_LOCAL (sym);
564	  symbol_table_insert (sym);
565	}
566      else
567	{
568	  char *replacement;
569
570	  replacement = concat (S_GET_NAME (rootsym), "+", root_stag_name,
571				name + strlen (S_GET_NAME (rootsym)), NULL);
572	  hash_insert (subsym_hash[0], name, replacement);
573	}
574
575      /* Recurse if the field is a structure.
576	 Note the field offset is relative to the outermost struct.  */
577      if (field->stag != NULL)
578	stag_add_field_symbols (field->stag, name,
579				field->offset,
580				rootsym, root_stag_name);
581      field = field->next;
582      free (name);
583    }
584  free (prefix);
585}
586
587/* Keep track of stag fields so that when structures are nested we can add the
588   complete dereferencing symbols to the symbol table.  */
589
590static void
591stag_add_field (struct stag *parent,
592		const char *name,
593		bfd_vma offset,
594		struct stag *stag)
595{
596  struct stag_field *sfield = XCNEW (struct stag_field);
597
598  sfield->name = xstrdup (name);
599  sfield->offset = offset;
600  sfield->bitfield_offset = parent->current_bitfield_offset;
601  sfield->stag = stag;
602  if (parent->field == NULL)
603    parent->field = sfield;
604  else
605    {
606      struct stag_field *sf = parent->field;
607      while (sf->next != NULL)
608	sf = sf->next;
609      sf->next = sfield;
610    }
611  /* Only create a symbol for this field if the parent has no name.  */
612  if (!strncmp (".fake", parent->name, 5))
613    {
614      symbolS *sym = symbol_new (name, absolute_section,
615				 (valueT) offset, &zero_address_frag);
616      SF_SET_LOCAL (sym);
617      symbol_table_insert (sym);
618    }
619}
620
621/* [STAG] .struct       [OFFSET]
622   Start defining structure offsets (symbols in absolute section).  */
623
624static void
625tic54x_struct (int arg)
626{
627  int start_offset = 0;
628  int is_union = arg;
629
630  if (!current_stag)
631    {
632      /* Starting a new struct, switch to absolute section.  */
633      stag_saved_seg = now_seg;
634      stag_saved_subseg = now_subseg;
635      subseg_set (absolute_section, 0);
636    }
637  /* Align the current pointer.  */
638  else if (current_stag->current_bitfield_offset != 0)
639    {
640      ++abs_section_offset;
641      current_stag->current_bitfield_offset = 0;
642    }
643
644  /* Offset expression is only meaningful for global .structs.  */
645  if (!is_union)
646    {
647      /* Offset is ignored in inner structs.  */
648      SKIP_WHITESPACE ();
649      if (!is_end_of_line[(int) *input_line_pointer])
650	start_offset = get_absolute_expression ();
651      else
652	start_offset = 0;
653    }
654
655  if (current_stag)
656    {
657      /* Nesting, link to outer one.  */
658      current_stag->inner = XCNEW (struct stag);
659      current_stag->inner->outer = current_stag;
660      current_stag = current_stag->inner;
661      if (start_offset)
662	as_warn (_("Offset on nested structures is ignored"));
663      start_offset = abs_section_offset;
664    }
665  else
666    {
667      current_stag = XCNEW (struct stag);
668      abs_section_offset = start_offset;
669    }
670  current_stag->is_union = is_union;
671
672  if (line_label == NULL)
673    {
674      static int struct_count = 0;
675      char fake[] = ".fake_stagNNNNNNN";
676      sprintf (fake, ".fake_stag%d", struct_count++);
677      current_stag->sym = symbol_new (fake, absolute_section,
678				      (valueT) abs_section_offset,
679				      &zero_address_frag);
680    }
681  else
682    {
683      char * label = xstrdup (S_GET_NAME (line_label));
684      current_stag->sym = symbol_new (label,
685				      absolute_section,
686				      (valueT) abs_section_offset,
687				      &zero_address_frag);
688      free (label);
689    }
690  current_stag->name = S_GET_NAME (current_stag->sym);
691  SF_SET_LOCAL (current_stag->sym);
692  /* Nested .structs don't go into the symbol table.  */
693  if (current_stag->outer == NULL)
694    symbol_table_insert (current_stag->sym);
695
696  line_label = NULL;
697}
698
699/* [LABEL] .endstruct
700   finish defining structure offsets; optional LABEL's value will be the size
701   of the structure.  */
702
703static void
704tic54x_endstruct (int is_union)
705{
706  int size;
707  const char *path =
708    !strncmp (current_stag->name, ".fake", 5) ? "" : current_stag->name;
709
710  if (!current_stag || current_stag->is_union != is_union)
711    {
712      as_bad (_(".end%s without preceding .%s"),
713	      is_union ? "union" : "struct",
714	      is_union ? "union" : "struct");
715      ignore_rest_of_line ();
716      return;
717    }
718
719  /* Align end of structures.  */
720  if (current_stag->current_bitfield_offset)
721    {
722      ++abs_section_offset;
723      current_stag->current_bitfield_offset = 0;
724    }
725
726  if (current_stag->is_union)
727    size = current_stag->size;
728  else
729    size = abs_section_offset - S_GET_VALUE (current_stag->sym);
730  if (line_label != NULL)
731    {
732      S_SET_VALUE (line_label, size);
733      symbol_table_insert (line_label);
734      line_label = NULL;
735    }
736
737  /* Union size has already been calculated.  */
738  if (!current_stag->is_union)
739    current_stag->size = size;
740  /* Nested .structs don't get put in the stag table.  */
741  if (current_stag->outer == NULL)
742    {
743      hash_insert (stag_hash, current_stag->name, current_stag);
744      stag_add_field_symbols (current_stag, path,
745			      S_GET_VALUE (current_stag->sym),
746			      NULL, NULL);
747    }
748  current_stag = current_stag->outer;
749
750  /* If this is a nested .struct/.union, add it as a field to the enclosing
751     one.  otherwise, restore the section we were in.  */
752  if (current_stag != NULL)
753    {
754      stag_add_field (current_stag, current_stag->inner->name,
755		      S_GET_VALUE (current_stag->inner->sym),
756		      current_stag->inner);
757    }
758  else
759    subseg_set (stag_saved_seg, stag_saved_subseg);
760}
761
762/* [LABEL]      .tag    STAG
763   Reference a structure within a structure, as a sized field with an optional
764   label.
765   If used outside of a .struct/.endstruct, overlays the given structure
766   format on the existing allocated space.  */
767
768static void
769tic54x_tag (int ignore ATTRIBUTE_UNUSED)
770{
771  char *name;
772  int c = get_symbol_name (&name);
773  struct stag *stag = (struct stag *) hash_find (stag_hash, name);
774
775  if (!stag)
776    {
777      if (*name)
778	as_bad (_("Unrecognized struct/union tag '%s'"), name);
779      else
780	as_bad (_(".tag requires a structure tag"));
781      ignore_rest_of_line ();
782      return;
783    }
784  if (line_label == NULL)
785    {
786      as_bad (_("Label required for .tag"));
787      ignore_rest_of_line ();
788      return;
789    }
790  else
791    {
792      char * label;
793
794      label = xstrdup (S_GET_NAME (line_label));
795      if (current_stag != NULL)
796	stag_add_field (current_stag, label,
797			abs_section_offset - S_GET_VALUE (current_stag->sym),
798			stag);
799      else
800	{
801	  symbolS *sym = symbol_find (label);
802
803	  if (!sym)
804	    {
805	      as_bad (_(".tag target '%s' undefined"), label);
806	      ignore_rest_of_line ();
807	      free (label);
808	      return;
809	    }
810	  stag_add_field_symbols (stag, S_GET_NAME (sym),
811				  S_GET_VALUE (stag->sym), sym, stag->name);
812	}
813      free (label);
814    }
815
816  /* Bump by the struct size, but only if we're within a .struct section.  */
817  if (current_stag != NULL && !current_stag->is_union)
818    abs_section_offset += stag->size;
819
820  (void) restore_line_pointer (c);
821  demand_empty_rest_of_line ();
822  line_label = NULL;
823}
824
825/* Handle all .byte, .char, .double, .field, .float, .half, .int, .long,
826   .short, .string, .ubyte, .uchar, .uhalf, .uint, .ulong, .ushort, .uword,
827   and .word.  */
828
829static void
830tic54x_struct_field (int type)
831{
832  int size;
833  int count = 1;
834  int new_bitfield_offset = 0;
835  int field_align = current_stag->current_bitfield_offset != 0;
836  int longword_align = 0;
837
838  SKIP_WHITESPACE ();
839  if (!is_end_of_line[(int) *input_line_pointer])
840    count = get_absolute_expression ();
841
842  switch (type)
843    {
844    case 'b':
845    case 'B':
846    case 'c':
847    case 'C':
848    case 'h':
849    case 'H':
850    case 'i':
851    case 'I':
852    case 's':
853    case 'S':
854    case 'w':
855    case 'W':
856    case '*': /* String.  */
857      size = 1;
858      break;
859    case 'f':
860    case 'l':
861    case 'L':
862      longword_align = 1;
863      size = 2;
864      break;
865    case '.': /* Bitfield.  */
866      size = 0;
867      if (count < 1 || count > 32)
868	{
869	  as_bad (_(".field count '%d' out of range (1 <= X <= 32)"), count);
870	  ignore_rest_of_line ();
871	  return;
872	}
873      if (current_stag->current_bitfield_offset + count > 16)
874	{
875	  /* Set the appropriate size and new field offset.  */
876	  if (count == 32)
877	    {
878	      size = 2;
879	      count = 1;
880	    }
881	  else if (count > 16)
882	    {
883	      size = 1;
884	      count = 1;
885	      new_bitfield_offset = count - 16;
886	    }
887	  else
888	    new_bitfield_offset = count;
889	}
890      else
891	{
892	  field_align = 0;
893	  new_bitfield_offset = current_stag->current_bitfield_offset + count;
894	}
895      break;
896    default:
897      as_bad (_("Unrecognized field type '%c'"), type);
898      ignore_rest_of_line ();
899      return;
900    }
901
902  if (field_align)
903    {
904      /* Align to the actual starting position of the field.  */
905      current_stag->current_bitfield_offset = 0;
906      ++abs_section_offset;
907    }
908  /* Align to longword boundary.  */
909  if (longword_align && (abs_section_offset & 0x1))
910    ++abs_section_offset;
911
912  if (line_label == NULL)
913    {
914      static int fieldno = 0;
915      char fake[] = ".fake_fieldNNNNN";
916
917      sprintf (fake, ".fake_field%d", fieldno++);
918      stag_add_field (current_stag, fake,
919		      abs_section_offset - S_GET_VALUE (current_stag->sym),
920		      NULL);
921    }
922  else
923    {
924      char * label;
925
926      label = xstrdup (S_GET_NAME (line_label));
927      stag_add_field (current_stag, label,
928		      abs_section_offset - S_GET_VALUE (current_stag->sym),
929		      NULL);
930      free (label);
931    }
932
933  if (current_stag->is_union)
934    {
935      /* Note we treat the element as if it were an array of COUNT.  */
936      if (current_stag->size < (unsigned) size * count)
937	current_stag->size = size * count;
938    }
939  else
940    {
941      abs_section_offset += (unsigned) size * count;
942      current_stag->current_bitfield_offset = new_bitfield_offset;
943    }
944  line_label = NULL;
945}
946
947/* Handle .byte, .word. .int, .long and all variants.  */
948
949static void
950tic54x_cons (int type)
951{
952  unsigned int c;
953  int octets;
954
955  /* If we're within a .struct construct, don't actually allocate space.  */
956  if (current_stag != NULL)
957    {
958      tic54x_struct_field (type);
959      return;
960    }
961
962#ifdef md_flush_pending_output
963  md_flush_pending_output ();
964#endif
965
966  generate_lineno_debug ();
967
968  /* Align long words to long word boundaries (4 octets).  */
969  if (type == 'l' || type == 'L')
970    {
971      frag_align (2, 0, 2);
972      /* If there's a label, assign it to the first allocated word.  */
973      if (line_label != NULL)
974	{
975	  symbol_set_frag (line_label, frag_now);
976	  S_SET_VALUE (line_label, frag_now_fix ());
977	}
978    }
979
980  switch (type)
981    {
982    case 'l':
983    case 'L':
984    case 'x':
985      octets = 4;
986      break;
987    case 'b':
988    case 'B':
989    case 'c':
990    case 'C':
991      octets = 1;
992      break;
993    default:
994      octets = 2;
995      break;
996    }
997
998  do
999    {
1000      if (*input_line_pointer == '"')
1001	{
1002	  input_line_pointer++;
1003	  while (is_a_char (c = next_char_of_string ()))
1004	    tic54x_emit_char (c);
1005	  know (input_line_pointer[-1] == '\"');
1006	}
1007      else
1008	{
1009	  expressionS expn;
1010
1011	  input_line_pointer = parse_expression (input_line_pointer, &expn);
1012	  if (expn.X_op == O_constant)
1013	    {
1014	      offsetT value = expn.X_add_number;
1015	      /* Truncate overflows.  */
1016	      switch (octets)
1017		{
1018		case 1:
1019		  if ((value > 0 && value > 0xFF)
1020		      || (value < 0 && value < - 0x100))
1021		    as_warn (_("Overflow in expression, truncated to 8 bits"));
1022		  break;
1023		case 2:
1024		  if ((value > 0 && value > 0xFFFF)
1025		      || (value < 0 && value < - 0x10000))
1026		    as_warn (_("Overflow in expression, truncated to 16 bits"));
1027		  break;
1028		}
1029	    }
1030	  if (expn.X_op != O_constant && octets < 2)
1031	    {
1032	      /* Disallow .byte with a non constant expression that will
1033		 require relocation.  */
1034	      as_bad (_("Relocatable values require at least WORD storage"));
1035	      ignore_rest_of_line ();
1036	      return;
1037	    }
1038
1039	  if (expn.X_op != O_constant
1040	      && amode == c_mode
1041	      && octets == 4)
1042	    {
1043	      /* FIXME -- at one point TI tools used to output REL16
1044		 relocations, but I don't think the latest tools do at all
1045		 The current tools output extended relocations regardless of
1046		 the addressing mode (I actually think that ".c_mode" is
1047		 totally ignored in the latest tools).  */
1048	      amode = far_mode;
1049	      emitting_long = 1;
1050	      emit_expr (&expn, 4);
1051	      emitting_long = 0;
1052	      amode = c_mode;
1053	    }
1054	  else
1055	    {
1056	      emitting_long = octets == 4;
1057	      emit_expr (&expn, (octets == 1) ? 2 : octets);
1058	      emitting_long = 0;
1059	    }
1060	}
1061    }
1062  while (*input_line_pointer++ == ',');
1063
1064  input_line_pointer--;		/* Put terminator back into stream.  */
1065  demand_empty_rest_of_line ();
1066}
1067
1068/* .global <symbol>[,...,<symbolN>]
1069   .def    <symbol>[,...,<symbolN>]
1070   .ref    <symbol>[,...,<symbolN>]
1071
1072   These all identify global symbols.
1073
1074   .def means the symbol is defined in the current module and can be accessed
1075   by other files.  The symbol should be placed in the symbol table.
1076
1077   .ref means the symbol is used in the current module but defined in another
1078   module.  The linker is to resolve this symbol's definition at link time.
1079
1080   .global should act as a .ref or .def, as needed.
1081
1082   global, def and ref all have symbol storage classes of C_EXT.
1083
1084   I can't identify any difference in how the "other" c54x assembler treats
1085   these, so we ignore the type here.  */
1086
1087void
1088tic54x_global (int type)
1089{
1090  char *name;
1091  int c;
1092  symbolS *symbolP;
1093
1094  if (type == 'r')
1095    as_warn (_("Use of .def/.ref is deprecated.  Use .global instead"));
1096
1097  ILLEGAL_WITHIN_STRUCT ();
1098
1099  do
1100    {
1101      c = get_symbol_name (&name);
1102      symbolP = symbol_find_or_make (name);
1103      c = restore_line_pointer (c);
1104
1105      S_SET_STORAGE_CLASS (symbolP, C_EXT);
1106      if (c == ',')
1107	{
1108	  input_line_pointer++;
1109	  if (is_end_of_line[(int) *input_line_pointer])
1110	    c = *input_line_pointer;
1111	}
1112    }
1113  while (c == ',');
1114
1115  demand_empty_rest_of_line ();
1116}
1117
1118/* Remove the symbol from the local label hash lookup.  */
1119
1120static void
1121tic54x_remove_local_label (const char *key, void *value ATTRIBUTE_UNUSED)
1122{
1123  void *elem = hash_delete (local_label_hash[macro_level], key, FALSE);
1124  free (elem);
1125}
1126
1127/* Reset all local labels.  */
1128
1129static void
1130tic54x_clear_local_labels (int ignored ATTRIBUTE_UNUSED)
1131{
1132  hash_traverse (local_label_hash[macro_level], tic54x_remove_local_label);
1133}
1134
1135/* .text
1136   .data
1137   .sect "section name"
1138
1139   Initialized section
1140   make sure local labels get cleared when changing sections
1141
1142   ARG is 't' for text, 'd' for data, or '*' for a named section
1143
1144   For compatibility, '*' sections are SEC_CODE if instructions are
1145   encountered, or SEC_DATA if not.
1146*/
1147
1148static void
1149tic54x_sect (int arg)
1150{
1151  ILLEGAL_WITHIN_STRUCT ();
1152
1153  /* Local labels are cleared when changing sections.  */
1154  tic54x_clear_local_labels (0);
1155
1156  if (arg == 't')
1157    s_text (0);
1158  else if (arg == 'd')
1159    s_data (0);
1160  else
1161    {
1162      char *name = NULL;
1163      int len;
1164      /* Make sure all named initialized sections flagged properly.  If we
1165         encounter instructions, we'll flag it with SEC_CODE as well.  */
1166      const char *flags = ",\"w\"\n";
1167
1168      /* If there are quotes, remove them.  */
1169      if (*input_line_pointer == '"')
1170	{
1171	  name = demand_copy_C_string (&len);
1172	  demand_empty_rest_of_line ();
1173	  name = concat (name, flags, (char *) NULL);
1174	}
1175      else
1176	{
1177	  int c;
1178
1179	  c = get_symbol_name (&name);
1180	  name = concat (name, flags, (char *) NULL);
1181	  (void) restore_line_pointer (c);
1182	  demand_empty_rest_of_line ();
1183	}
1184
1185      input_scrub_insert_line (name);
1186      obj_coff_section (0);
1187
1188      /* If there was a line label, make sure that it gets assigned the proper
1189	 section.  This is for compatibility, even though the actual behavior
1190	 is not explicitly defined.  For consistency, we make .sect behave
1191	 like .usect, since that is probably what people expect.  */
1192      if (line_label != NULL)
1193	{
1194	  S_SET_SEGMENT (line_label, now_seg);
1195	  symbol_set_frag (line_label, frag_now);
1196	  S_SET_VALUE (line_label, frag_now_fix ());
1197	  if (S_GET_STORAGE_CLASS (line_label) != C_EXT)
1198	    S_SET_STORAGE_CLASS (line_label, C_LABEL);
1199	}
1200    }
1201}
1202
1203/* [symbol] .space space_in_bits
1204   [symbol] .bes space_in_bits
1205   BES puts the symbol at the *last* word allocated
1206
1207   cribbed from s_space.  */
1208
1209static void
1210tic54x_space (int arg)
1211{
1212  expressionS expn;
1213  char *p = 0;
1214  int octets = 0;
1215  long words;
1216  int bits_per_byte = (OCTETS_PER_BYTE * 8);
1217  int bit_offset = 0;
1218  symbolS *label = line_label;
1219  int bes = arg;
1220
1221  ILLEGAL_WITHIN_STRUCT ();
1222
1223#ifdef md_flush_pending_output
1224  md_flush_pending_output ();
1225#endif
1226
1227  /* Read the bit count.  */
1228  expression (&expn);
1229
1230  /* Some expressions are unresolvable until later in the assembly pass;
1231     postpone until relaxation/fixup.  we also have to postpone if a previous
1232     partial allocation has not been completed yet.  */
1233  if (expn.X_op != O_constant || frag_bit_offset (frag_now, now_seg) == -1)
1234    {
1235      struct bit_info *bi = XNEW (struct bit_info);
1236
1237      bi->seg = now_seg;
1238      bi->type = bes;
1239      bi->sym = label;
1240      p = frag_var (rs_machine_dependent,
1241		    65536 * 2, 1, (relax_substateT) 0,
1242		    make_expr_symbol (&expn), (offsetT) 0,
1243		    (char *) bi);
1244      if (p)
1245	*p = 0;
1246
1247      return;
1248    }
1249
1250  /* Reduce the required size by any bit offsets currently left over
1251     from a previous .space/.bes/.field directive.  */
1252  bit_offset = frag_now->tc_frag_data;
1253  if (bit_offset != 0 && bit_offset < 16)
1254    {
1255      int spare_bits = bits_per_byte - bit_offset;
1256
1257      if (spare_bits >= expn.X_add_number)
1258	{
1259	  /* Don't have to do anything; sufficient bits have already been
1260	     allocated; just point the label to the right place.  */
1261	  if (label != NULL)
1262	    {
1263	      symbol_set_frag (label, frag_now);
1264	      S_SET_VALUE (label, frag_now_fix () - 1);
1265	      label = NULL;
1266	    }
1267	  frag_now->tc_frag_data += expn.X_add_number;
1268	  goto getout;
1269	}
1270      expn.X_add_number -= spare_bits;
1271      /* Set the label to point to the first word allocated, which in this
1272	 case is the previous word, which was only partially filled.  */
1273      if (!bes && label != NULL)
1274	{
1275	  symbol_set_frag (label, frag_now);
1276	  S_SET_VALUE (label, frag_now_fix () - 1);
1277	  label = NULL;
1278	}
1279    }
1280  /* Convert bits to bytes/words and octets, rounding up.  */
1281  words = ((expn.X_add_number + bits_per_byte - 1) / bits_per_byte);
1282  /* How many do we have left over?  */
1283  bit_offset = expn.X_add_number % bits_per_byte;
1284  octets = words * OCTETS_PER_BYTE;
1285  if (octets < 0)
1286    {
1287      as_warn (_(".space/.bes repeat count is negative, ignored"));
1288      goto getout;
1289    }
1290  else if (octets == 0)
1291    {
1292      as_warn (_(".space/.bes repeat count is zero, ignored"));
1293      goto getout;
1294    }
1295
1296  /* If we are in the absolute section, just bump the offset.  */
1297  if (now_seg == absolute_section)
1298    {
1299      abs_section_offset += words;
1300      if (bes && label != NULL)
1301	S_SET_VALUE (label, abs_section_offset - 1);
1302      frag_now->tc_frag_data = bit_offset;
1303      goto getout;
1304    }
1305
1306  if (!need_pass_2)
1307    p = frag_var (rs_fill, 1, 1,
1308		  (relax_substateT) 0, (symbolS *) 0,
1309		  (offsetT) octets, (char *) 0);
1310
1311  /* Make note of how many bits of this word we've allocated so far.  */
1312  frag_now->tc_frag_data = bit_offset;
1313
1314  /* .bes puts label at *last* word allocated.  */
1315  if (bes && label != NULL)
1316    {
1317      symbol_set_frag (label, frag_now);
1318      S_SET_VALUE (label, frag_now_fix () - 1);
1319    }
1320
1321  if (p)
1322    *p = 0;
1323
1324 getout:
1325
1326  demand_empty_rest_of_line ();
1327}
1328
1329/* [symbol] .usect "section-name", size-in-words
1330		   [, [blocking-flag] [, alignment-flag]]
1331
1332   Uninitialized section.
1333   Non-zero blocking means that if the section would cross a page (128-word)
1334   boundary, it will be page-aligned.
1335   Non-zero alignment aligns on a longword boundary.
1336
1337   Has no effect on the current section.  */
1338
1339static void
1340tic54x_usect (int x ATTRIBUTE_UNUSED)
1341{
1342  char c;
1343  char *name;
1344  char *section_name;
1345  char *p;
1346  segT seg;
1347  int size, blocking_flag, alignment_flag;
1348  segT current_seg;
1349  subsegT current_subseg;
1350  flagword flags;
1351
1352  ILLEGAL_WITHIN_STRUCT ();
1353
1354  current_seg = now_seg;	/* Save current seg.  */
1355  current_subseg = now_subseg;	/* Save current subseg.  */
1356
1357  c = get_symbol_name (&section_name);	/* Get terminator.  */
1358  name = xstrdup (section_name);
1359  c = restore_line_pointer (c);
1360
1361  if (c == ',')
1362    ++input_line_pointer;
1363  else
1364    {
1365      as_bad (_("Missing size argument"));
1366      ignore_rest_of_line ();
1367      return;
1368    }
1369
1370  size = get_absolute_expression ();
1371
1372  /* Read a possibly present third argument (blocking flag).  */
1373  if (*input_line_pointer == ',')
1374    {
1375      ++input_line_pointer;
1376      if (*input_line_pointer != ',')
1377	blocking_flag = get_absolute_expression ();
1378      else
1379	blocking_flag = 0;
1380
1381      /* Read a possibly present fourth argument (alignment flag).  */
1382      if (*input_line_pointer == ',')
1383	{
1384	  ++input_line_pointer;
1385	  alignment_flag = get_absolute_expression ();
1386	}
1387      else
1388	alignment_flag = 0;
1389    }
1390  else
1391    blocking_flag = alignment_flag = 0;
1392
1393  seg = subseg_new (name, 0);
1394  flags = bfd_get_section_flags (stdoutput, seg) | SEC_ALLOC;
1395
1396  if (alignment_flag)
1397    {
1398      /* s_align eats end of line; restore it.  */
1399      s_align_bytes (4);
1400      --input_line_pointer;
1401    }
1402
1403  if (line_label != NULL)
1404    {
1405      S_SET_SEGMENT (line_label, seg);
1406      symbol_set_frag (line_label, frag_now);
1407      S_SET_VALUE (line_label, frag_now_fix ());
1408      /* Set scl to label, since that's what TI does.  */
1409      if (S_GET_STORAGE_CLASS (line_label) != C_EXT)
1410	S_SET_STORAGE_CLASS (line_label, C_LABEL);
1411    }
1412
1413  seg_info (seg)->bss = 1;	/* Uninitialized data.  */
1414
1415  p = frag_var (rs_fill, 1, 1,
1416		(relax_substateT) 0, (symbolS *) line_label,
1417		size * OCTETS_PER_BYTE, (char *) 0);
1418  *p = 0;
1419
1420  if (blocking_flag)
1421    flags |= SEC_TIC54X_BLOCK;
1422
1423  if (!bfd_set_section_flags (stdoutput, seg, flags))
1424    as_warn (_("Error setting flags for \"%s\": %s"), name,
1425	     bfd_errmsg (bfd_get_error ()));
1426
1427  subseg_set (current_seg, current_subseg);	/* Restore current seg.  */
1428  demand_empty_rest_of_line ();
1429}
1430
1431static enum cpu_version
1432lookup_version (const char *ver)
1433{
1434  enum cpu_version version = VNONE;
1435
1436  if (ver[0] == '5' && ver[1] == '4')
1437    {
1438      if (strlen (ver) == 3
1439	  && (ver[2] == '1' || ver[2] == '2' || ver[2] == '3'
1440	      || ver[2] == '5' || ver[2] == '8' || ver[2] == '9'))
1441	version = ver[2] - '0';
1442      else if (strlen (ver) == 5
1443	       && TOUPPER (ver[3]) == 'L'
1444	       && TOUPPER (ver[4]) == 'P'
1445	       && (ver[2] == '5' || ver[2] == '6'))
1446	version = ver[2] - '0' + 10;
1447    }
1448
1449  return version;
1450}
1451
1452static void
1453set_cpu (enum cpu_version version)
1454{
1455  cpu = version;
1456  if (version == V545LP || version == V546LP)
1457    {
1458      symbolS *symbolP = symbol_new ("__allow_lp", absolute_section,
1459				     (valueT) 1, &zero_address_frag);
1460      SF_SET_LOCAL (symbolP);
1461      symbol_table_insert (symbolP);
1462    }
1463}
1464
1465/* .version cpu-version
1466   cpu-version may be one of the following:
1467   541
1468   542
1469   543
1470   545
1471   545LP
1472   546LP
1473   548
1474   549
1475
1476   This is for compatibility only.  It currently has no affect on assembly.  */
1477static int cpu_needs_set = 1;
1478
1479static void
1480tic54x_version (int x ATTRIBUTE_UNUSED)
1481{
1482  enum cpu_version version = VNONE;
1483  enum cpu_version old_version = cpu;
1484  int c;
1485  char *ver;
1486
1487  ILLEGAL_WITHIN_STRUCT ();
1488
1489  SKIP_WHITESPACE ();
1490  ver = input_line_pointer;
1491  while (!is_end_of_line[(int) *input_line_pointer])
1492    ++input_line_pointer;
1493  c = *input_line_pointer;
1494  *input_line_pointer = 0;
1495
1496  version = lookup_version (ver);
1497
1498  if (cpu != VNONE && cpu != version)
1499    as_warn (_("CPU version has already been set"));
1500
1501  if (version == VNONE)
1502    {
1503      as_bad (_("Unrecognized version '%s'"), ver);
1504      ignore_rest_of_line ();
1505      return;
1506    }
1507  else if (assembly_begun && version != old_version)
1508    {
1509      as_bad (_("Changing of CPU version on the fly not supported"));
1510      ignore_rest_of_line ();
1511      return;
1512    }
1513
1514  set_cpu (version);
1515
1516  *input_line_pointer = c;
1517  demand_empty_rest_of_line ();
1518}
1519
1520/* 'f' = float, 'x' = xfloat, 'd' = double, 'l' = ldouble.  */
1521
1522static void
1523tic54x_float_cons (int type)
1524{
1525  if (current_stag != 0)
1526    tic54x_struct_field ('f');
1527
1528#ifdef md_flush_pending_output
1529  md_flush_pending_output ();
1530#endif
1531
1532  /* Align to long word boundary (4 octets) unless it's ".xfloat".  */
1533  if (type != 'x')
1534    {
1535      frag_align (2, 0, 2);
1536      /* If there's a label, assign it to the first allocated word.  */
1537      if (line_label != NULL)
1538	{
1539	  symbol_set_frag (line_label, frag_now);
1540	  S_SET_VALUE (line_label, frag_now_fix ());
1541	}
1542    }
1543
1544  float_cons ('f');
1545}
1546
1547/* The argument is capitalized if it should be zero-terminated
1548   's' is normal string with upper 8-bits zero-filled, 'p' is packed.
1549   Code copied from stringer, and slightly modified so that strings are packed
1550   and encoded into the correct octets.  */
1551
1552static void
1553tic54x_stringer (int type)
1554{
1555  unsigned int c;
1556  int append_zero = type == 'S' || type == 'P';
1557  int packed = type == 'p' || type == 'P';
1558  int last_char = -1; /* Packed strings need two bytes at a time to encode.  */
1559
1560  if (current_stag != NULL)
1561    {
1562      tic54x_struct_field ('*');
1563      return;
1564    }
1565
1566#ifdef md_flush_pending_output
1567  md_flush_pending_output ();
1568#endif
1569
1570  c = ',';			/* Do loop.  */
1571  while (c == ',')
1572    {
1573      SKIP_WHITESPACE ();
1574      switch (*input_line_pointer)
1575	{
1576	default:
1577	  {
1578	    unsigned short value = get_absolute_expression ();
1579	    FRAG_APPEND_1_CHAR ( value       & 0xFF);
1580	    FRAG_APPEND_1_CHAR ((value >> 8) & 0xFF);
1581	    break;
1582	  }
1583	case '\"':
1584	  ++input_line_pointer;	/* -> 1st char of string.  */
1585	  while (is_a_char (c = next_char_of_string ()))
1586	    {
1587	      if (!packed)
1588		{
1589		  FRAG_APPEND_1_CHAR (c);
1590		  FRAG_APPEND_1_CHAR (0);
1591		}
1592	      else
1593		{
1594		  /* Packed strings are filled MS octet first.  */
1595		  if (last_char == -1)
1596		    last_char = c;
1597		  else
1598		    {
1599		      FRAG_APPEND_1_CHAR (c);
1600		      FRAG_APPEND_1_CHAR (last_char);
1601		      last_char = -1;
1602		    }
1603		}
1604	    }
1605	  if (append_zero)
1606	    {
1607	      if (packed && last_char != -1)
1608		{
1609		  FRAG_APPEND_1_CHAR (0);
1610		  FRAG_APPEND_1_CHAR (last_char);
1611		  last_char = -1;
1612		}
1613	      else
1614		{
1615		  FRAG_APPEND_1_CHAR (0);
1616		  FRAG_APPEND_1_CHAR (0);
1617		}
1618	    }
1619	  know (input_line_pointer[-1] == '\"');
1620	  break;
1621	}
1622      SKIP_WHITESPACE ();
1623      c = *input_line_pointer;
1624      if (!is_end_of_line[c])
1625	++input_line_pointer;
1626    }
1627
1628  /* Finish up any leftover packed string.  */
1629  if (packed && last_char != -1)
1630    {
1631      FRAG_APPEND_1_CHAR (0);
1632      FRAG_APPEND_1_CHAR (last_char);
1633    }
1634  demand_empty_rest_of_line ();
1635}
1636
1637static void
1638tic54x_p2align (int arg ATTRIBUTE_UNUSED)
1639{
1640  as_bad (_("p2align not supported on this target"));
1641}
1642
1643static void
1644tic54x_align_words (int arg)
1645{
1646  /* Only ".align" with no argument is allowed within .struct/.union.  */
1647  int count = arg;
1648
1649  if (!is_end_of_line[(int) *input_line_pointer])
1650    {
1651      if (arg == 2)
1652	as_warn (_("Argument to .even ignored"));
1653      else
1654	count = get_absolute_expression ();
1655    }
1656
1657  if (current_stag != NULL && arg == 128)
1658    {
1659      if (current_stag->current_bitfield_offset != 0)
1660	{
1661	  current_stag->current_bitfield_offset = 0;
1662	  ++abs_section_offset;
1663	}
1664      demand_empty_rest_of_line ();
1665      return;
1666    }
1667
1668  ILLEGAL_WITHIN_STRUCT ();
1669
1670  s_align_bytes (count << 1);
1671}
1672
1673/* Initialize multiple-bit fields within a single word of memory.  */
1674
1675static void
1676tic54x_field (int ignore ATTRIBUTE_UNUSED)
1677{
1678  expressionS expn;
1679  int size = 16;
1680  char *p;
1681  valueT value;
1682  symbolS *label = line_label;
1683
1684  if (current_stag != NULL)
1685    {
1686      tic54x_struct_field ('.');
1687      return;
1688    }
1689
1690  input_line_pointer = parse_expression (input_line_pointer, &expn);
1691
1692  if (*input_line_pointer == ',')
1693    {
1694      ++input_line_pointer;
1695      size = get_absolute_expression ();
1696      if (size < 1 || size > 32)
1697	{
1698	  as_bad (_("Invalid field size, must be from 1 to 32"));
1699	  ignore_rest_of_line ();
1700	  return;
1701	}
1702    }
1703
1704  /* Truncate values to the field width.  */
1705  if (expn.X_op != O_constant)
1706    {
1707      /* If the expression value is relocatable, the field size *must*
1708         be 16.  */
1709      if (size != 16)
1710	{
1711	  as_bad (_("field size must be 16 when value is relocatable"));
1712	  ignore_rest_of_line ();
1713	  return;
1714	}
1715
1716      frag_now->tc_frag_data = 0;
1717      emit_expr (&expn, 2);
1718    }
1719  else
1720    {
1721      unsigned long fmask = (size == 32) ? 0xFFFFFFFF : (1ul << size) - 1;
1722
1723      value = expn.X_add_number;
1724      expn.X_add_number &= fmask;
1725      if (value != (valueT) expn.X_add_number)
1726	as_warn (_("field value truncated"));
1727      value = expn.X_add_number;
1728      /* Bits are stored MS first.  */
1729      while (size >= 16)
1730	{
1731	  frag_now->tc_frag_data = 0;
1732	  p = frag_more (2);
1733	  md_number_to_chars (p, (value >> (size - 16)) & 0xFFFF, 2);
1734	  size -= 16;
1735	}
1736      if (size > 0)
1737	{
1738	  int bit_offset = frag_bit_offset (frag_now, now_seg);
1739
1740	  fragS *alloc_frag = bit_offset_frag (frag_now, now_seg);
1741	  if (bit_offset == -1)
1742	    {
1743	      struct bit_info *bi = XNEW (struct bit_info);
1744	      /* We don't know the previous offset at this time, so store the
1745		 info we need and figure it out later.  */
1746	      expressionS size_exp;
1747
1748	      size_exp.X_op = O_constant;
1749	      size_exp.X_add_number = size;
1750	      bi->seg = now_seg;
1751	      bi->type = TYPE_FIELD;
1752	      bi->value = value;
1753	      p = frag_var (rs_machine_dependent,
1754			    4, 1, (relax_substateT) 0,
1755			    make_expr_symbol (&size_exp), (offsetT) 0,
1756			    (char *) bi);
1757	      goto getout;
1758	    }
1759	  else if (bit_offset == 0 || bit_offset + size > 16)
1760	    {
1761	      /* Align a new field.  */
1762	      p = frag_more (2);
1763	      frag_now->tc_frag_data = 0;
1764	      alloc_frag = frag_now;
1765	    }
1766	  else
1767	    {
1768	      /* Put the new value entirely within the existing one.  */
1769	      p = alloc_frag == frag_now ?
1770		frag_now->fr_literal + frag_now_fix_octets () - 2 :
1771		alloc_frag->fr_literal;
1772	      if (label != NULL)
1773		{
1774		  symbol_set_frag (label, alloc_frag);
1775		  if (alloc_frag == frag_now)
1776		    S_SET_VALUE (label, frag_now_fix () - 1);
1777		  label = NULL;
1778		}
1779	    }
1780	  value <<= 16 - alloc_frag->tc_frag_data - size;
1781
1782	  /* OR in existing value.  */
1783	  if (alloc_frag->tc_frag_data)
1784	    value |= ((unsigned short) p[1] << 8) | p[0];
1785	  md_number_to_chars (p, value, 2);
1786	  alloc_frag->tc_frag_data += size;
1787	  if (alloc_frag->tc_frag_data == 16)
1788	    alloc_frag->tc_frag_data = 0;
1789	}
1790    }
1791 getout:
1792  demand_empty_rest_of_line ();
1793}
1794
1795/* Ideally, we want to check SEC_LOAD and SEC_HAS_CONTENTS, but those aren't
1796   available yet.  seg_info ()->bss is the next best thing.  */
1797
1798static int
1799tic54x_initialized_section (segT seg)
1800{
1801  return !seg_info (seg)->bss;
1802}
1803
1804/* .clink ["section name"]
1805
1806   Marks the section as conditionally linked (link only if contents are
1807   referenced elsewhere.
1808   Without a name, refers to the current initialized section.
1809   Name is required for uninitialized sections.  */
1810
1811static void
1812tic54x_clink (int ignored ATTRIBUTE_UNUSED)
1813{
1814  segT seg = now_seg;
1815
1816  ILLEGAL_WITHIN_STRUCT ();
1817
1818  if (*input_line_pointer == '\"')
1819    {
1820      char *section_name = ++input_line_pointer;
1821      char *name;
1822
1823      while (is_a_char (next_char_of_string ()))
1824	;
1825      know (input_line_pointer[-1] == '\"');
1826      input_line_pointer[-1] = 0;
1827      name = xstrdup (section_name);
1828
1829      seg = bfd_get_section_by_name (stdoutput, name);
1830      if (seg == NULL)
1831	{
1832	  as_bad (_("Unrecognized section '%s'"), section_name);
1833	  ignore_rest_of_line ();
1834	  return;
1835	}
1836    }
1837  else
1838    {
1839      if (!tic54x_initialized_section (seg))
1840	{
1841	  as_bad (_("Current section is unitialized, "
1842		    "section name required for .clink"));
1843	  ignore_rest_of_line ();
1844	  return;
1845	}
1846    }
1847
1848  seg->flags |= SEC_TIC54X_CLINK;
1849
1850  demand_empty_rest_of_line ();
1851}
1852
1853/* Change the default include directory to be the current source file's
1854   directory, instead of the current working directory.  If DOT is non-zero,
1855   set to "." instead.  */
1856
1857static void
1858tic54x_set_default_include (void)
1859{
1860  char *dir, *tmp = NULL;
1861  const char *curfile;
1862  unsigned lineno;
1863
1864  curfile = as_where (&lineno);
1865  dir = xstrdup (curfile);
1866  tmp = strrchr (dir, '/');
1867  if (tmp != NULL)
1868    {
1869      int len;
1870
1871      *tmp = '\0';
1872      len = strlen (dir);
1873      if (include_dir_count == 0)
1874	{
1875	  include_dirs = XNEWVEC (const char *, 1);
1876	  include_dir_count = 1;
1877	}
1878      include_dirs[0] = dir;
1879      if (len > include_dir_maxlen)
1880	include_dir_maxlen = len;
1881    }
1882  else if (include_dirs != NULL)
1883    include_dirs[0] = ".";
1884}
1885
1886/* .include "filename" | filename
1887   .copy    "filename" | filename
1888
1889   FIXME 'include' file should be omitted from any output listing,
1890     'copy' should be included in any output listing
1891   FIXME -- prevent any included files from changing listing (compat only)
1892   FIXME -- need to include source file directory in search path; what's a
1893      good way to do this?
1894
1895   Entering/exiting included/copied file clears all local labels.  */
1896
1897static void
1898tic54x_include (int ignored ATTRIBUTE_UNUSED)
1899{
1900  char newblock[] = " .newblock\n";
1901  char *filename;
1902  char *input;
1903  int len, c = -1;
1904
1905  ILLEGAL_WITHIN_STRUCT ();
1906
1907  SKIP_WHITESPACE ();
1908
1909  if (*input_line_pointer == '"')
1910    {
1911      filename = demand_copy_C_string (&len);
1912      demand_empty_rest_of_line ();
1913    }
1914  else
1915    {
1916      filename = input_line_pointer;
1917      while (!is_end_of_line[(int) *input_line_pointer])
1918	++input_line_pointer;
1919      c = *input_line_pointer;
1920      *input_line_pointer = '\0';
1921      filename = xstrdup (filename);
1922      *input_line_pointer = c;
1923      demand_empty_rest_of_line ();
1924    }
1925  /* Insert a partial line with the filename (for the sake of s_include)
1926     and a .newblock.
1927     The included file will be inserted before the newblock, so that the
1928     newblock is executed after the included file is processed.  */
1929  input = concat ("\"", filename, "\"\n", newblock, (char *) NULL);
1930  input_scrub_insert_line (input);
1931
1932  tic54x_clear_local_labels (0);
1933
1934  tic54x_set_default_include ();
1935
1936  s_include (0);
1937}
1938
1939static void
1940tic54x_message (int type)
1941{
1942  char *msg;
1943  char c;
1944  int len;
1945
1946  ILLEGAL_WITHIN_STRUCT ();
1947
1948  if (*input_line_pointer == '"')
1949    msg = demand_copy_C_string (&len);
1950  else
1951    {
1952      msg = input_line_pointer;
1953      while (!is_end_of_line[(int) *input_line_pointer])
1954	++input_line_pointer;
1955      c = *input_line_pointer;
1956      *input_line_pointer = 0;
1957      msg = xstrdup (msg);
1958      *input_line_pointer = c;
1959    }
1960
1961  switch (type)
1962    {
1963    case 'm':
1964      as_tsktsk ("%s", msg);
1965      break;
1966    case 'w':
1967      as_warn ("%s", msg);
1968      break;
1969    case 'e':
1970      as_bad ("%s", msg);
1971      break;
1972    }
1973
1974  demand_empty_rest_of_line ();
1975}
1976
1977/* .label <symbol>
1978   Define a special symbol that refers to the loadtime address rather than the
1979   runtime address within the current section.
1980
1981   This symbol gets a special storage class so that when it is resolved, it is
1982   resolved relative to the load address (lma) of the section rather than the
1983   run address (vma).  */
1984
1985static void
1986tic54x_label (int ignored ATTRIBUTE_UNUSED)
1987{
1988  char *name;
1989  symbolS *symbolP;
1990  int c;
1991
1992  ILLEGAL_WITHIN_STRUCT ();
1993
1994  c = get_symbol_name (&name);
1995  symbolP = colon (name);
1996  S_SET_STORAGE_CLASS (symbolP, C_STATLAB);
1997
1998  (void) restore_line_pointer (c);
1999  demand_empty_rest_of_line ();
2000}
2001
2002/* .mmregs
2003   Install all memory-mapped register names into the symbol table as
2004   absolute local symbols.  */
2005
2006static void
2007tic54x_mmregs (int ignored ATTRIBUTE_UNUSED)
2008{
2009  tic54x_symbol *sym;
2010
2011  ILLEGAL_WITHIN_STRUCT ();
2012
2013  for (sym = (tic54x_symbol *) mmregs; sym->name; sym++)
2014    {
2015      symbolS *symbolP = symbol_new (sym->name, absolute_section,
2016				     (valueT) sym->value, &zero_address_frag);
2017      SF_SET_LOCAL (symbolP);
2018      symbol_table_insert (symbolP);
2019    }
2020}
2021
2022/* .loop [count]
2023   Count defaults to 1024.  */
2024
2025static void
2026tic54x_loop (int count)
2027{
2028  ILLEGAL_WITHIN_STRUCT ();
2029
2030  SKIP_WHITESPACE ();
2031  if (!is_end_of_line[(int) *input_line_pointer])
2032    count = get_absolute_expression ();
2033
2034  do_repeat (count, "LOOP", "ENDLOOP");
2035}
2036
2037/* Normally, endloop gets eaten by the preceding loop.  */
2038
2039static void
2040tic54x_endloop (int ignore ATTRIBUTE_UNUSED)
2041{
2042  as_bad (_("ENDLOOP without corresponding LOOP"));
2043  ignore_rest_of_line ();
2044}
2045
2046/* .break [condition].  */
2047
2048static void
2049tic54x_break (int ignore ATTRIBUTE_UNUSED)
2050{
2051  int cond = 1;
2052
2053  ILLEGAL_WITHIN_STRUCT ();
2054
2055  SKIP_WHITESPACE ();
2056  if (!is_end_of_line[(int) *input_line_pointer])
2057    cond = get_absolute_expression ();
2058
2059  if (cond)
2060    end_repeat (substitution_line ? 1 : 0);
2061}
2062
2063static void
2064set_address_mode (int mode)
2065{
2066  amode = mode;
2067  if (mode == far_mode)
2068    {
2069      symbolS *symbolP = symbol_new ("__allow_far", absolute_section,
2070				     (valueT) 1, &zero_address_frag);
2071      SF_SET_LOCAL (symbolP);
2072      symbol_table_insert (symbolP);
2073    }
2074}
2075
2076static int address_mode_needs_set = 1;
2077
2078static void
2079tic54x_address_mode (int mode)
2080{
2081  if (assembly_begun && amode != (unsigned) mode)
2082    {
2083      as_bad (_("Mixing of normal and extended addressing not supported"));
2084      ignore_rest_of_line ();
2085      return;
2086    }
2087  if (mode == far_mode && cpu != VNONE && cpu != V548 && cpu != V549)
2088    {
2089      as_bad (_("Extended addressing not supported on the specified CPU"));
2090      ignore_rest_of_line ();
2091      return;
2092    }
2093
2094  set_address_mode (mode);
2095  demand_empty_rest_of_line ();
2096}
2097
2098/* .sblock "section"|section [,...,"section"|section]
2099   Designate initialized sections for blocking.  */
2100
2101static void
2102tic54x_sblock (int ignore ATTRIBUTE_UNUSED)
2103{
2104  int c = ',';
2105
2106  ILLEGAL_WITHIN_STRUCT ();
2107
2108  while (c == ',')
2109    {
2110      segT seg;
2111      char *name;
2112
2113      if (*input_line_pointer == '"')
2114	{
2115	  int len;
2116
2117	  name = demand_copy_C_string (&len);
2118	}
2119      else
2120	{
2121	  char *section_name;
2122
2123	  c = get_symbol_name (&section_name);
2124	  name = xstrdup (section_name);
2125	  (void) restore_line_pointer (c);
2126	}
2127
2128      seg = bfd_get_section_by_name (stdoutput, name);
2129      if (seg == NULL)
2130	{
2131	  as_bad (_("Unrecognized section '%s'"), name);
2132	  ignore_rest_of_line ();
2133	  return;
2134	}
2135      else if (!tic54x_initialized_section (seg))
2136	{
2137	  as_bad (_(".sblock may be used for initialized sections only"));
2138	  ignore_rest_of_line ();
2139	  return;
2140	}
2141      seg->flags |= SEC_TIC54X_BLOCK;
2142
2143      c = *input_line_pointer;
2144      if (!is_end_of_line[(int) c])
2145	++input_line_pointer;
2146    }
2147
2148  demand_empty_rest_of_line ();
2149}
2150
2151/* symbol .set value
2152   symbol .equ value
2153
2154   value must be defined externals; no forward-referencing allowed
2155   symbols assigned with .set/.equ may not be redefined.  */
2156
2157static void
2158tic54x_set (int ignore ATTRIBUTE_UNUSED)
2159{
2160  symbolS *symbolP;
2161  char *name;
2162
2163  ILLEGAL_WITHIN_STRUCT ();
2164
2165  if (!line_label)
2166    {
2167      as_bad (_("Symbol missing for .set/.equ"));
2168      ignore_rest_of_line ();
2169      return;
2170    }
2171  name = xstrdup (S_GET_NAME (line_label));
2172  line_label = NULL;
2173  if ((symbolP = symbol_find (name)) == NULL
2174      && (symbolP = md_undefined_symbol (name)) == NULL)
2175    {
2176      symbolP = symbol_new (name, absolute_section, 0, &zero_address_frag);
2177      S_SET_STORAGE_CLASS (symbolP, C_STAT);
2178    }
2179  free (name);
2180  S_SET_DATA_TYPE (symbolP, T_INT);
2181  S_SET_SEGMENT (symbolP, absolute_section);
2182  symbol_table_insert (symbolP);
2183  pseudo_set (symbolP);
2184  demand_empty_rest_of_line ();
2185}
2186
2187/* .fclist
2188   .fcnolist
2189   List false conditional blocks.  */
2190
2191static void
2192tic54x_fclist (int show)
2193{
2194  if (show)
2195    listing &= ~LISTING_NOCOND;
2196  else
2197    listing |= LISTING_NOCOND;
2198  demand_empty_rest_of_line ();
2199}
2200
2201static void
2202tic54x_sslist (int show)
2203{
2204  ILLEGAL_WITHIN_STRUCT ();
2205
2206  listing_sslist = show;
2207}
2208
2209/* .var SYM[,...,SYMN]
2210   Define a substitution string to be local to a macro.  */
2211
2212static void
2213tic54x_var (int ignore ATTRIBUTE_UNUSED)
2214{
2215  static char empty[] = "";
2216  char *name;
2217  int c;
2218
2219  ILLEGAL_WITHIN_STRUCT ();
2220
2221  if (macro_level == 0)
2222    {
2223      as_bad (_(".var may only be used within a macro definition"));
2224      ignore_rest_of_line ();
2225      return;
2226    }
2227  do
2228    {
2229      if (!ISALPHA (*input_line_pointer))
2230	{
2231	  as_bad (_("Substitution symbols must begin with a letter"));
2232	  ignore_rest_of_line ();
2233	  return;
2234	}
2235      c = get_symbol_name (&name);
2236      /* .var symbols start out with a null string.  */
2237      name = xstrdup (name);
2238      hash_insert (subsym_hash[macro_level], name, empty);
2239      c = restore_line_pointer (c);
2240      if (c == ',')
2241	{
2242	  ++input_line_pointer;
2243	  if (is_end_of_line[(int) *input_line_pointer])
2244	    c = *input_line_pointer;
2245	}
2246    }
2247  while (c == ',');
2248
2249  demand_empty_rest_of_line ();
2250}
2251
2252/* .mlib <macro library filename>
2253
2254   Macro libraries are archived (standard AR-format) text macro definitions
2255   Expand the file and include it.
2256
2257   FIXME need to try the source file directory as well.  */
2258
2259static void
2260tic54x_mlib (int ignore ATTRIBUTE_UNUSED)
2261{
2262  char *filename;
2263  char *path;
2264  int len, i;
2265  bfd *abfd, *mbfd;
2266
2267  ILLEGAL_WITHIN_STRUCT ();
2268
2269  /* Parse the filename.  */
2270  if (*input_line_pointer == '"')
2271    {
2272      if ((filename = demand_copy_C_string (&len)) == NULL)
2273	return;
2274    }
2275  else
2276    {
2277      SKIP_WHITESPACE ();
2278      len = 0;
2279      while (!is_end_of_line[(int) *input_line_pointer]
2280	     && !ISSPACE (*input_line_pointer))
2281	{
2282	  obstack_1grow (&notes, *input_line_pointer);
2283	  ++input_line_pointer;
2284	  ++len;
2285	}
2286      obstack_1grow (&notes, '\0');
2287      filename = obstack_finish (&notes);
2288    }
2289  demand_empty_rest_of_line ();
2290
2291  tic54x_set_default_include ();
2292  path = XNEWVEC (char, (unsigned long) len + include_dir_maxlen + 5);
2293
2294  for (i = 0; i < include_dir_count; i++)
2295    {
2296      FILE *try;
2297
2298      strcpy (path, include_dirs[i]);
2299      strcat (path, "/");
2300      strcat (path, filename);
2301      if ((try = fopen (path, "r")) != NULL)
2302	{
2303	  fclose (try);
2304	  break;
2305	}
2306    }
2307
2308  if (i >= include_dir_count)
2309    {
2310      free (path);
2311      path = filename;
2312    }
2313
2314  /* FIXME: if path is found, malloc'd storage is not freed.  Of course, this
2315     happens all over the place, and since the assembler doesn't usually keep
2316     running for a very long time, it really doesn't matter.  */
2317  register_dependency (path);
2318
2319  /* Expand all archive entries to temporary files and include them.  */
2320  abfd = bfd_openr (path, NULL);
2321  if (!abfd)
2322    {
2323      as_bad (_("can't open macro library file '%s' for reading: %s"),
2324	      path, bfd_errmsg (bfd_get_error ()));
2325      ignore_rest_of_line ();
2326      return;
2327    }
2328  if (!bfd_check_format (abfd, bfd_archive))
2329    {
2330      as_bad (_("File '%s' not in macro archive format"), path);
2331      ignore_rest_of_line ();
2332      return;
2333    }
2334
2335  /* Open each BFD as binary (it should be straight ASCII text).  */
2336  for (mbfd = bfd_openr_next_archived_file (abfd, NULL);
2337       mbfd != NULL; mbfd = bfd_openr_next_archived_file (abfd, mbfd))
2338    {
2339      /* Get a size at least as big as the archive member.  */
2340      bfd_size_type size = bfd_get_size (mbfd);
2341      char *buf = XNEWVEC (char, size);
2342      char *fname = tmpnam (NULL);
2343      FILE *ftmp;
2344
2345      /* We're not sure how big it is, but it will be smaller than "size".  */
2346      size = bfd_bread (buf, size, mbfd);
2347
2348      /* Write to a temporary file, then use s_include to include it
2349	 a bit of a hack.  */
2350      ftmp = fopen (fname, "w+b");
2351      fwrite ((void *) buf, size, 1, ftmp);
2352      if (size == 0 || buf[size - 1] != '\n')
2353	fwrite ("\n", 1, 1, ftmp);
2354      fclose (ftmp);
2355      free (buf);
2356      input_scrub_insert_file (fname);
2357      unlink (fname);
2358    }
2359}
2360
2361const pseudo_typeS md_pseudo_table[] =
2362{
2363  { "algebraic", s_ignore                 ,          0 },
2364  { "align"    , tic54x_align_words       ,        128 },
2365  { "ascii"    , tic54x_stringer          ,        'p' },
2366  { "asciz"    , tic54x_stringer          ,        'P' },
2367  { "even"     , tic54x_align_words       ,          2 },
2368  { "asg"      , tic54x_asg               ,          0 },
2369  { "eval"     , tic54x_eval              ,          0 },
2370  { "bss"      , tic54x_bss               ,          0 },
2371  { "byte"     , tic54x_cons              ,        'b' },
2372  { "ubyte"    , tic54x_cons              ,        'B' },
2373  { "char"     , tic54x_cons              ,        'c' },
2374  { "uchar"    , tic54x_cons              ,        'C' },
2375  { "clink"    , tic54x_clink             ,          0 },
2376  { "c_mode"   , tic54x_address_mode      ,     c_mode },
2377  { "copy"     , tic54x_include           ,        'c' },
2378  { "include"  , tic54x_include           ,        'i' },
2379  { "data"     , tic54x_sect              ,        'd' },
2380  { "double"   , tic54x_float_cons        ,        'd' },
2381  { "ldouble"  , tic54x_float_cons        ,        'l' },
2382  { "drlist"   , s_ignore                 ,          0 },
2383  { "drnolist" , s_ignore                 ,          0 },
2384  { "emsg"     , tic54x_message           ,        'e' },
2385  { "mmsg"     , tic54x_message           ,        'm' },
2386  { "wmsg"     , tic54x_message           ,        'w' },
2387  { "far_mode" , tic54x_address_mode      ,   far_mode },
2388  { "fclist"   , tic54x_fclist            ,          1 },
2389  { "fcnolist" , tic54x_fclist            ,          0 },
2390  { "field"    , tic54x_field             ,         -1 },
2391  { "float"    , tic54x_float_cons        ,        'f' },
2392  { "xfloat"   , tic54x_float_cons        ,        'x' },
2393  { "global"   , tic54x_global            ,        'g' },
2394  { "def"      , tic54x_global            ,        'd' },
2395  { "ref"      , tic54x_global            ,        'r' },
2396  { "half"     , tic54x_cons              ,        'h' },
2397  { "uhalf"    , tic54x_cons              ,        'H' },
2398  { "short"    , tic54x_cons              ,        's' },
2399  { "ushort"   , tic54x_cons              ,        'S' },
2400  { "if"       , s_if                     , (int) O_ne },
2401  { "elseif"   , s_elseif                 , (int) O_ne },
2402  { "else"     , s_else                   ,          0 },
2403  { "endif"    , s_endif                  ,          0 },
2404  { "int"      , tic54x_cons              ,        'i' },
2405  { "uint"     , tic54x_cons              ,        'I' },
2406  { "word"     , tic54x_cons              ,        'w' },
2407  { "uword"    , tic54x_cons              ,        'W' },
2408  { "label"    , tic54x_label             ,          0 }, /* Loadtime
2409                                                             address.  */
2410  { "length"   , s_ignore                 ,          0 },
2411  { "width"    , s_ignore                 ,          0 },
2412  { "long"     , tic54x_cons              ,        'l' },
2413  { "ulong"    , tic54x_cons              ,        'L' },
2414  { "xlong"    , tic54x_cons              ,        'x' },
2415  { "loop"     , tic54x_loop              ,       1024 },
2416  { "break"    , tic54x_break             ,          0 },
2417  { "endloop"  , tic54x_endloop           ,          0 },
2418  { "mlib"     , tic54x_mlib              ,          0 },
2419  { "mlist"    , s_ignore                 ,          0 },
2420  { "mnolist"  , s_ignore                 ,          0 },
2421  { "mmregs"   , tic54x_mmregs            ,          0 },
2422  { "newblock" , tic54x_clear_local_labels,          0 },
2423  { "option"   , s_ignore                 ,          0 },
2424  { "p2align"  , tic54x_p2align           ,          0 },
2425  { "sblock"   , tic54x_sblock            ,          0 },
2426  { "sect"     , tic54x_sect              ,        '*' },
2427  { "set"      , tic54x_set               ,          0 },
2428  { "equ"      , tic54x_set               ,          0 },
2429  { "space"    , tic54x_space             ,          0 },
2430  { "bes"      , tic54x_space             ,          1 },
2431  { "sslist"   , tic54x_sslist            ,          1 },
2432  { "ssnolist" , tic54x_sslist            ,          0 },
2433  { "string"   , tic54x_stringer          ,        's' },
2434  { "pstring"  , tic54x_stringer          ,        'p' },
2435  { "struct"   , tic54x_struct            ,          0 },
2436  { "tag"      , tic54x_tag               ,          0 },
2437  { "endstruct", tic54x_endstruct         ,          0 },
2438  { "tab"      , s_ignore                 ,          0 },
2439  { "text"     , tic54x_sect              ,        't' },
2440  { "union"    , tic54x_struct            ,          1 },
2441  { "endunion" , tic54x_endstruct         ,          1 },
2442  { "usect"    , tic54x_usect             ,          0 },
2443  { "var"      , tic54x_var               ,          0 },
2444  { "version"  , tic54x_version           ,          0 },
2445  {0           , 0                        ,          0 }
2446};
2447
2448int
2449md_parse_option (int c, const char *arg)
2450{
2451  switch (c)
2452    {
2453    default:
2454      return 0;
2455    case OPTION_COFF_VERSION:
2456      {
2457	int version = atoi (arg);
2458
2459	if (version != 0 && version != 1 && version != 2)
2460	  as_fatal (_("Bad COFF version '%s'"), arg);
2461	/* FIXME -- not yet implemented.  */
2462	break;
2463      }
2464    case OPTION_CPU_VERSION:
2465      {
2466	cpu = lookup_version (arg);
2467	cpu_needs_set = 1;
2468	if (cpu == VNONE)
2469	  as_fatal (_("Bad CPU version '%s'"), arg);
2470	break;
2471      }
2472    case OPTION_ADDRESS_MODE:
2473      amode = far_mode;
2474      address_mode_needs_set = 1;
2475      break;
2476    case OPTION_STDERR_TO_FILE:
2477      {
2478	const char *filename = arg;
2479	FILE *fp = fopen (filename, "w+");
2480
2481	if (fp == NULL)
2482	  as_fatal (_("Can't redirect stderr to the file '%s'"), filename);
2483	fclose (fp);
2484	if ((fp = freopen (filename, "w+", stderr)) == NULL)
2485	  as_fatal (_("Can't redirect stderr to the file '%s'"), filename);
2486	break;
2487      }
2488    }
2489
2490  return 1;
2491}
2492
2493/* Create a "local" substitution string hash table for a new macro level
2494   Some docs imply that macros have to use .newblock in order to be able
2495   to re-use a local label.  We effectively do an automatic .newblock by
2496   deleting the local label hash between macro invocations.  */
2497
2498void
2499tic54x_macro_start (void)
2500{
2501  ++macro_level;
2502  subsym_hash[macro_level] = hash_new ();
2503  local_label_hash[macro_level] = hash_new ();
2504}
2505
2506void
2507tic54x_macro_info (const macro_entry *macro)
2508{
2509  const formal_entry *entry;
2510
2511  /* Put the formal args into the substitution symbol table.  */
2512  for (entry = macro->formals; entry; entry = entry->next)
2513    {
2514      char *name = xstrndup (entry->name.ptr, entry->name.len);
2515      char *value = xstrndup (entry->actual.ptr, entry->actual.len);
2516
2517      name[entry->name.len] = '\0';
2518      value[entry->actual.len] = '\0';
2519      hash_insert (subsym_hash[macro_level], name, value);
2520    }
2521}
2522
2523/* Get rid of this macro's .var's, arguments, and local labels.  */
2524
2525void
2526tic54x_macro_end (void)
2527{
2528  hash_die (subsym_hash[macro_level]);
2529  subsym_hash[macro_level] = NULL;
2530  hash_die (local_label_hash[macro_level]);
2531  local_label_hash[macro_level] = NULL;
2532  --macro_level;
2533}
2534
2535static int
2536subsym_symlen (char *a, char *ignore ATTRIBUTE_UNUSED)
2537{
2538  return strlen (a);
2539}
2540
2541/* Compare symbol A to string B.  */
2542
2543static int
2544subsym_symcmp (char *a, char *b)
2545{
2546  return strcmp (a, b);
2547}
2548
2549/* Return the index of the first occurrence of B in A, or zero if none
2550   assumes b is an integer char value as a string.  Index is one-based.  */
2551
2552static int
2553subsym_firstch (char *a, char *b)
2554{
2555  int val = atoi (b);
2556  char *tmp = strchr (a, val);
2557
2558  return tmp ? tmp - a + 1 : 0;
2559}
2560
2561/* Similar to firstch, but returns index of last occurrence of B in A.  */
2562
2563static int
2564subsym_lastch (char *a, char *b)
2565{
2566  int val = atoi (b);
2567  char *tmp = strrchr (a, val);
2568
2569  return tmp ? tmp - a + 1 : 0;
2570}
2571
2572/* Returns 1 if string A is defined in the symbol table (NOT the substitution
2573   symbol table).  */
2574
2575static int
2576subsym_isdefed (char *a, char *ignore ATTRIBUTE_UNUSED)
2577{
2578  symbolS *symbolP = symbol_find (a);
2579
2580  return symbolP != NULL;
2581}
2582
2583/* Assign first member of comma-separated list B (e.g. "1,2,3") to the symbol
2584   A, or zero if B is a null string.  Both arguments *must* be substitution
2585   symbols, unsubstituted.  */
2586
2587static int
2588subsym_ismember (char *sym, char *list)
2589{
2590  char *elem, *ptr, *listv;
2591
2592  if (!list)
2593    return 0;
2594
2595  listv = subsym_lookup (list, macro_level);
2596  if (!listv)
2597    {
2598      as_bad (_("Undefined substitution symbol '%s'"), list);
2599      ignore_rest_of_line ();
2600      return 0;
2601    }
2602
2603  ptr = elem = xstrdup (listv);
2604  while (*ptr && *ptr != ',')
2605    ++ptr;
2606  *ptr++ = 0;
2607
2608  subsym_create_or_replace (sym, elem);
2609
2610  /* Reassign the list.  */
2611  subsym_create_or_replace (list, ptr);
2612
2613  /* Assume this value, docs aren't clear.  */
2614  return *list != 0;
2615}
2616
2617/* Return zero if not a constant; otherwise:
2618   1 if binary
2619   2 if octal
2620   3 if hexadecimal
2621   4 if character
2622   5 if decimal.  */
2623
2624static int
2625subsym_iscons (char *a, char *ignore ATTRIBUTE_UNUSED)
2626{
2627  expressionS expn;
2628
2629  parse_expression (a, &expn);
2630
2631  if (expn.X_op == O_constant)
2632    {
2633      int len = strlen (a);
2634
2635      switch (TOUPPER (a[len - 1]))
2636	{
2637	case 'B':
2638	  return 1;
2639	case 'Q':
2640	  return 2;
2641	case 'H':
2642	  return 3;
2643	case '\'':
2644	  return 4;
2645	default:
2646	  break;
2647	}
2648      /* No suffix; either octal, hex, or decimal.  */
2649      if (*a == '0' && len > 1)
2650	{
2651	  if (TOUPPER (a[1]) == 'X')
2652	    return 3;
2653	  return 2;
2654	}
2655      return 5;
2656    }
2657
2658  return 0;
2659}
2660
2661/* Return 1 if A is a valid symbol name.  Expects string input.   */
2662
2663static int
2664subsym_isname (char *a, char *ignore ATTRIBUTE_UNUSED)
2665{
2666  if (!is_name_beginner (*a))
2667    return 0;
2668  while (*a)
2669    {
2670      if (!is_part_of_name (*a))
2671	return 0;
2672      ++a;
2673    }
2674  return 1;
2675}
2676
2677/* Return whether the string is a register; accepts ar0-7, unless .mmregs has
2678   been seen; if so, recognize any memory-mapped register.
2679   Note this does not recognize "A" or "B" accumulators.  */
2680
2681static int
2682subsym_isreg (char *a, char *ignore ATTRIBUTE_UNUSED)
2683{
2684  if (hash_find (reg_hash, a))
2685    return 1;
2686  if (hash_find (mmreg_hash, a))
2687    return 1;
2688  return 0;
2689}
2690
2691/* Return the structure size, given the stag.  */
2692
2693static int
2694subsym_structsz (char *name, char *ignore ATTRIBUTE_UNUSED)
2695{
2696  struct stag *stag = (struct stag *) hash_find (stag_hash, name);
2697
2698  if (stag)
2699    return stag->size;
2700
2701  return 0;
2702}
2703
2704/* If anybody actually uses this, they can fix it :)
2705   FIXME I'm not sure what the "reference point" of a structure is.  It might
2706   be either the initial offset given .struct, or it may be the offset of the
2707   structure within another structure, or it might be something else
2708   altogether.  since the TI assembler doesn't seem to ever do anything but
2709   return zero, we punt and return zero.  */
2710
2711static int
2712subsym_structacc (char *stag_name ATTRIBUTE_UNUSED,
2713		  char *ignore ATTRIBUTE_UNUSED)
2714{
2715  return 0;
2716}
2717
2718static float
2719math_ceil (float arg1, float ignore ATTRIBUTE_UNUSED)
2720{
2721  return (float) ceil (arg1);
2722}
2723
2724static float
2725math_cvi (float arg1, float ignore ATTRIBUTE_UNUSED)
2726{
2727  return (int) arg1;
2728}
2729
2730static float
2731math_floor (float arg1, float ignore ATTRIBUTE_UNUSED)
2732{
2733  return (float) floor (arg1);
2734}
2735
2736static float
2737math_fmod (float arg1, float arg2)
2738{
2739  return (int) arg1 % (int) arg2;
2740}
2741
2742static float
2743math_int (float arg1, float ignore ATTRIBUTE_UNUSED)
2744{
2745  return ((float) ((int) arg1)) == arg1;
2746}
2747
2748static float
2749math_round (float arg1, float ignore ATTRIBUTE_UNUSED)
2750{
2751  return arg1 > 0 ? (int) (arg1 + 0.5) : (int) (arg1 - 0.5);
2752}
2753
2754static float
2755math_sgn (float arg1, float ignore ATTRIBUTE_UNUSED)
2756{
2757  return (arg1 < 0) ? -1 : (arg1 ? 1 : 0);
2758}
2759
2760static float
2761math_trunc (float arg1, float ignore ATTRIBUTE_UNUSED)
2762{
2763  return (int) arg1;
2764}
2765
2766static float
2767math_acos (float arg1, float ignore ATTRIBUTE_UNUSED)
2768{
2769  return (float) acos (arg1);
2770}
2771
2772static float
2773math_asin (float arg1, float ignore ATTRIBUTE_UNUSED)
2774{
2775  return (float) asin (arg1);
2776}
2777
2778static float
2779math_atan (float arg1, float ignore ATTRIBUTE_UNUSED)
2780{
2781  return (float) atan (arg1);
2782}
2783
2784static float
2785math_atan2 (float arg1, float arg2)
2786{
2787  return (float) atan2 (arg1, arg2);
2788}
2789
2790static float
2791math_cosh (float arg1, float ignore ATTRIBUTE_UNUSED)
2792{
2793  return (float) cosh (arg1);
2794}
2795
2796static float
2797math_cos (float arg1, float ignore ATTRIBUTE_UNUSED)
2798{
2799  return (float) cos (arg1);
2800}
2801
2802static float
2803math_cvf (float arg1, float ignore ATTRIBUTE_UNUSED)
2804{
2805  return (float) arg1;
2806}
2807
2808static float
2809math_exp (float arg1, float ignore ATTRIBUTE_UNUSED)
2810{
2811  return (float) exp (arg1);
2812}
2813
2814static float
2815math_fabs (float arg1, float ignore ATTRIBUTE_UNUSED)
2816{
2817  return (float) fabs (arg1);
2818}
2819
2820/* expr1 * 2^expr2.  */
2821
2822static float
2823math_ldexp (float arg1, float arg2)
2824{
2825  return arg1 * (float) pow (2.0, arg2);
2826}
2827
2828static float
2829math_log10 (float arg1, float ignore ATTRIBUTE_UNUSED)
2830{
2831  return (float) log10 (arg1);
2832}
2833
2834static float
2835math_log (float arg1, float ignore ATTRIBUTE_UNUSED)
2836{
2837  return (float) log (arg1);
2838}
2839
2840static float
2841math_max (float arg1, float arg2)
2842{
2843  return (arg1 > arg2) ? arg1 : arg2;
2844}
2845
2846static float
2847math_min (float arg1, float arg2)
2848{
2849  return (arg1 < arg2) ? arg1 : arg2;
2850}
2851
2852static float
2853math_pow (float arg1, float arg2)
2854{
2855  return (float) pow (arg1, arg2);
2856}
2857
2858static float
2859math_sin (float arg1, float ignore ATTRIBUTE_UNUSED)
2860{
2861  return (float) sin (arg1);
2862}
2863
2864static float
2865math_sinh (float arg1, float ignore ATTRIBUTE_UNUSED)
2866{
2867  return (float) sinh (arg1);
2868}
2869
2870static float
2871math_sqrt (float arg1, float ignore ATTRIBUTE_UNUSED)
2872{
2873  return (float) sqrt (arg1);
2874}
2875
2876static float
2877math_tan (float arg1, float ignore ATTRIBUTE_UNUSED)
2878{
2879  return (float) tan (arg1);
2880}
2881
2882static float
2883math_tanh (float arg1, float ignore ATTRIBUTE_UNUSED)
2884{
2885  return (float) tanh (arg1);
2886}
2887
2888/* Built-in substitution symbol functions and math functions.  */
2889typedef struct
2890{
2891  const char *name;
2892  int (*proc) (char *, char *);
2893  int nargs;
2894} subsym_proc_entry;
2895
2896static const subsym_proc_entry subsym_procs[] =
2897{
2898  /* Assembler built-in string substitution functions.  */
2899  { "$symlen", subsym_symlen, 1,  },
2900  { "$symcmp", subsym_symcmp, 2,  },
2901  { "$firstch", subsym_firstch, 2,  },
2902  { "$lastch", subsym_lastch, 2,  },
2903  { "$isdefed", subsym_isdefed, 1,  },
2904  { "$ismember", subsym_ismember, 2,  },
2905  { "$iscons", subsym_iscons, 1,  },
2906  { "$isname", subsym_isname, 1,  },
2907  { "$isreg", subsym_isreg, 1,  },
2908  { "$structsz", subsym_structsz, 1,  },
2909  { "$structacc", subsym_structacc, 1,  },
2910  { NULL, NULL, 0 },
2911};
2912
2913typedef struct
2914{
2915  const char *name;
2916  float (*proc) (float, float);
2917  int nargs;
2918  int int_return;
2919} math_proc_entry;
2920
2921static const math_proc_entry math_procs[] =
2922{
2923  /* Integer-returning built-in math functions.  */
2924  { "$cvi", math_cvi, 1, 1 },
2925  { "$int", math_int, 1, 1 },
2926  { "$sgn", math_sgn, 1, 1 },
2927
2928  /* Float-returning built-in math functions.  */
2929  { "$acos", math_acos, 1, 0 },
2930  { "$asin", math_asin, 1, 0 },
2931  { "$atan", math_atan, 1, 0 },
2932  { "$atan2", math_atan2, 2, 0 },
2933  { "$ceil", math_ceil, 1, 0 },
2934  { "$cosh", math_cosh, 1, 0 },
2935  { "$cos", math_cos, 1, 0 },
2936  { "$cvf", math_cvf, 1, 0 },
2937  { "$exp", math_exp, 1, 0 },
2938  { "$fabs", math_fabs, 1, 0 },
2939  { "$floor", math_floor, 1, 0 },
2940  { "$fmod", math_fmod, 2, 0 },
2941  { "$ldexp", math_ldexp, 2, 0 },
2942  { "$log10", math_log10, 1, 0 },
2943  { "$log", math_log, 1, 0 },
2944  { "$max", math_max, 2, 0 },
2945  { "$min", math_min, 2, 0 },
2946  { "$pow", math_pow, 2, 0 },
2947  { "$round", math_round, 1, 0 },
2948  { "$sin", math_sin, 1, 0 },
2949  { "$sinh", math_sinh, 1, 0 },
2950  { "$sqrt", math_sqrt, 1, 0 },
2951  { "$tan", math_tan, 1, 0 },
2952  { "$tanh", math_tanh, 1, 0 },
2953  { "$trunc", math_trunc, 1, 0 },
2954  { NULL, NULL, 0, 0 },
2955};
2956
2957void
2958md_begin (void)
2959{
2960  insn_template *tm;
2961  tic54x_symbol *sym;
2962  const subsym_proc_entry *subsym_proc;
2963  const math_proc_entry *math_proc;
2964  const char *hash_err;
2965  char **symname;
2966  char *TIC54X_DIR = getenv ("TIC54X_DIR");
2967  char *A_DIR = TIC54X_DIR ? TIC54X_DIR : getenv ("A_DIR");
2968
2969  local_label_id = 0;
2970
2971  /* Look for A_DIR and add it to the include list.  */
2972  if (A_DIR != NULL)
2973    {
2974      char *tmp = xstrdup (A_DIR);
2975
2976      do
2977	{
2978	  char *next = strchr (tmp, ';');
2979
2980	  if (next)
2981	    *next++ = '\0';
2982	  add_include_dir (tmp);
2983	  tmp = next;
2984	}
2985      while (tmp != NULL);
2986    }
2987
2988  op_hash = hash_new ();
2989  for (tm = (insn_template *) tic54x_optab; tm->name; tm++)
2990    {
2991      if (hash_find (op_hash, tm->name))
2992	continue;
2993      hash_err = hash_insert (op_hash, tm->name, (char *) tm);
2994      if (hash_err)
2995	as_fatal ("Internal Error: Can't hash %s: %s",
2996		  tm->name, hash_err);
2997    }
2998  parop_hash = hash_new ();
2999  for (tm = (insn_template *) tic54x_paroptab; tm->name; tm++)
3000    {
3001      if (hash_find (parop_hash, tm->name))
3002	continue;
3003      hash_err = hash_insert (parop_hash, tm->name, (char *) tm);
3004      if (hash_err)
3005	as_fatal ("Internal Error: Can't hash %s: %s",
3006		  tm->name, hash_err);
3007    }
3008  reg_hash = hash_new ();
3009  for (sym = (tic54x_symbol *) regs; sym->name; sym++)
3010    {
3011      /* Add basic registers to the symbol table.  */
3012      symbolS *symbolP = symbol_new (sym->name, absolute_section,
3013				     (valueT) sym->value, &zero_address_frag);
3014      SF_SET_LOCAL (symbolP);
3015      symbol_table_insert (symbolP);
3016      hash_err = hash_insert (reg_hash, sym->name, (char *) sym);
3017    }
3018  for (sym = (tic54x_symbol *) mmregs; sym->name; sym++)
3019    hash_err = hash_insert (reg_hash, sym->name, (char *) sym);
3020  mmreg_hash = hash_new ();
3021  for (sym = (tic54x_symbol *) mmregs; sym->name; sym++)
3022    hash_err = hash_insert (mmreg_hash, sym->name, (char *) sym);
3023
3024  cc_hash = hash_new ();
3025  for (sym = (tic54x_symbol *) condition_codes; sym->name; sym++)
3026    hash_err = hash_insert (cc_hash, sym->name, (char *) sym);
3027
3028  cc2_hash = hash_new ();
3029  for (sym = (tic54x_symbol *) cc2_codes; sym->name; sym++)
3030    hash_err = hash_insert (cc2_hash, sym->name, (char *) sym);
3031
3032  cc3_hash = hash_new ();
3033  for (sym = (tic54x_symbol *) cc3_codes; sym->name; sym++)
3034    hash_err = hash_insert (cc3_hash, sym->name, (char *) sym);
3035
3036  sbit_hash = hash_new ();
3037  for (sym = (tic54x_symbol *) status_bits; sym->name; sym++)
3038    hash_err = hash_insert (sbit_hash, sym->name, (char *) sym);
3039
3040  misc_symbol_hash = hash_new ();
3041  for (symname = (char **) misc_symbols; *symname; symname++)
3042    hash_err = hash_insert (misc_symbol_hash, *symname, *symname);
3043
3044  /* Only the base substitution table and local label table are initialized;
3045     the others (for local macro substitution) get instantiated as needed.  */
3046  local_label_hash[0] = hash_new ();
3047  subsym_hash[0] = hash_new ();
3048  for (subsym_proc = subsym_procs; subsym_proc->name; subsym_proc++)
3049    hash_err = hash_insert (subsym_hash[0], subsym_proc->name,
3050			    (char *) subsym_proc);
3051
3052  math_hash = hash_new ();
3053  for (math_proc = math_procs; math_proc->name; math_proc++)
3054    {
3055      /* Insert into the main subsym hash for recognition; insert into
3056	 the math hash to actually store information.  */
3057      hash_err = hash_insert (subsym_hash[0], math_proc->name,
3058			      (char *) math_proc);
3059      hash_err = hash_insert (math_hash, math_proc->name,
3060			      (char *) math_proc);
3061    }
3062  subsym_recurse_hash = hash_new ();
3063  stag_hash = hash_new ();
3064}
3065
3066static int
3067is_accumulator (struct opstruct *operand)
3068{
3069  return strcasecmp (operand->buf, "a") == 0
3070    || strcasecmp (operand->buf, "b") == 0;
3071}
3072
3073/* Return the number of operands found, or -1 on error, copying the
3074   operands into the given array and the accompanying expressions into
3075   the next array.  */
3076
3077static int
3078get_operands (struct opstruct operands[], char *line)
3079{
3080  char *lptr = line;
3081  int numexp = 0;
3082  int expecting_operand = 0;
3083  int i;
3084
3085  while (numexp < MAX_OPERANDS && !is_end_of_line[(int) *lptr])
3086    {
3087      int paren_not_balanced = 0;
3088      char *op_start, *op_end;
3089
3090      while (*lptr && ISSPACE (*lptr))
3091	++lptr;
3092      op_start = lptr;
3093      while (paren_not_balanced || *lptr != ',')
3094	{
3095	  if (*lptr == '\0')
3096	    {
3097	      if (paren_not_balanced)
3098		{
3099		  as_bad (_("Unbalanced parenthesis in operand %d"), numexp);
3100		  return -1;
3101		}
3102	      else
3103		break;
3104	    }
3105	  if (*lptr == '(')
3106	    ++paren_not_balanced;
3107	  else if (*lptr == ')')
3108	    --paren_not_balanced;
3109	  ++lptr;
3110	}
3111      op_end = lptr;
3112      if (op_end != op_start)
3113	{
3114	  int len = op_end - op_start;
3115
3116	  strncpy (operands[numexp].buf, op_start, len);
3117	  operands[numexp].buf[len] = 0;
3118	  /* Trim trailing spaces; while the preprocessor gets rid of most,
3119	     there are weird usage patterns that can introduce them
3120	     (i.e. using strings for macro args).  */
3121	  while (len > 0 && ISSPACE (operands[numexp].buf[len - 1]))
3122	    operands[numexp].buf[--len] = 0;
3123	  lptr = op_end;
3124	  ++numexp;
3125	}
3126      else
3127	{
3128	  if (expecting_operand || *lptr == ',')
3129	    {
3130	      as_bad (_("Expecting operand after ','"));
3131	      return -1;
3132	    }
3133	}
3134      if (*lptr == ',')
3135	{
3136	  if (*++lptr == '\0')
3137	    {
3138	      as_bad (_("Expecting operand after ','"));
3139	      return -1;
3140	    }
3141	  expecting_operand = 1;
3142	}
3143    }
3144
3145  while (*lptr && ISSPACE (*lptr++))
3146    ;
3147  if (!is_end_of_line[(int) *lptr])
3148    {
3149      as_bad (_("Extra junk on line"));
3150      return -1;
3151    }
3152
3153  /* OK, now parse them into expressions.  */
3154  for (i = 0; i < numexp; i++)
3155    {
3156      memset (&operands[i].exp, 0, sizeof (operands[i].exp));
3157      if (operands[i].buf[0] == '#')
3158	{
3159	  /* Immediate.  */
3160	  parse_expression (operands[i].buf + 1, &operands[i].exp);
3161	}
3162      else if (operands[i].buf[0] == '@')
3163	{
3164	  /* Direct notation.  */
3165	  parse_expression (operands[i].buf + 1, &operands[i].exp);
3166	}
3167      else if (operands[i].buf[0] == '*')
3168	{
3169	  /* Indirect.  */
3170	  char *paren = strchr (operands[i].buf, '(');
3171
3172	  /* Allow immediate syntax in the inner expression.  */
3173	  if (paren && paren[1] == '#')
3174	    *++paren = '(';
3175
3176	  /* Pull out the lk expression or SP offset, if present.  */
3177	  if (paren != NULL)
3178	    {
3179	      int len = strlen (paren);
3180	      char *end = paren + len;
3181	      int c;
3182
3183	      while (end[-1] != ')')
3184		if (--end <= paren)
3185		  {
3186		    as_bad (_("Badly formed address expression"));
3187		    return -1;
3188		  }
3189	      c = *end;
3190	      *end = '\0';
3191	      parse_expression (paren, &operands[i].exp);
3192	      *end = c;
3193	    }
3194	  else
3195	    operands[i].exp.X_op = O_absent;
3196	}
3197      else
3198	parse_expression (operands[i].buf, &operands[i].exp);
3199    }
3200
3201  return numexp;
3202}
3203
3204/* Predicates for different operand types.  */
3205
3206static int
3207is_immediate (struct opstruct *operand)
3208{
3209  return *operand->buf == '#';
3210}
3211
3212/* This is distinguished from immediate because some numbers must be constants
3213   and must *not* have the '#' prefix.  */
3214
3215static int
3216is_absolute (struct opstruct *operand)
3217{
3218  return operand->exp.X_op == O_constant && !is_immediate (operand);
3219}
3220
3221/* Is this an indirect operand?  */
3222
3223static int
3224is_indirect (struct opstruct *operand)
3225{
3226  return operand->buf[0] == '*';
3227}
3228
3229/* Is this a valid dual-memory operand?  */
3230
3231static int
3232is_dual (struct opstruct *operand)
3233{
3234  if (is_indirect (operand) && strncasecmp (operand->buf, "*ar", 3) == 0)
3235    {
3236      char *tmp = operand->buf + 3;
3237      int arf;
3238      int valid_mod;
3239
3240      arf = *tmp++ - '0';
3241      /* Only allow *ARx, *ARx-, *ARx+, or *ARx+0%.  */
3242      valid_mod = *tmp == '\0' ||
3243	strcasecmp (tmp, "-") == 0 ||
3244	strcasecmp (tmp, "+") == 0 ||
3245	strcasecmp (tmp, "+0%") == 0;
3246      return arf >= 2 && arf <= 5 && valid_mod;
3247    }
3248  return 0;
3249}
3250
3251static int
3252is_mmreg (struct opstruct *operand)
3253{
3254  return (is_absolute (operand)
3255	  || is_immediate (operand)
3256	  || hash_find (mmreg_hash, operand->buf) != 0);
3257}
3258
3259static int
3260is_type (struct opstruct *operand, enum optype type)
3261{
3262  switch (type)
3263    {
3264    case OP_None:
3265      return operand->buf[0] == 0;
3266    case OP_Xmem:
3267    case OP_Ymem:
3268      return is_dual (operand);
3269    case OP_Sind:
3270      return is_indirect (operand);
3271    case OP_xpmad_ms7:
3272      /* This one *must* be immediate.  */
3273      return is_immediate (operand);
3274    case OP_xpmad:
3275    case OP_pmad:
3276    case OP_PA:
3277    case OP_dmad:
3278    case OP_Lmem:
3279    case OP_MMR:
3280      return 1;
3281    case OP_Smem:
3282      /* Address may be a numeric, indirect, or an expression.  */
3283      return !is_immediate (operand);
3284    case OP_MMRY:
3285    case OP_MMRX:
3286      return is_mmreg (operand);
3287    case OP_SRC:
3288    case OP_SRC1:
3289    case OP_RND:
3290    case OP_DST:
3291      return is_accumulator (operand);
3292    case OP_B:
3293      return is_accumulator (operand) && TOUPPER (operand->buf[0]) == 'B';
3294    case OP_A:
3295      return is_accumulator (operand) && TOUPPER (operand->buf[0]) == 'A';
3296    case OP_ARX:
3297      return strncasecmp ("ar", operand->buf, 2) == 0
3298	&& ISDIGIT (operand->buf[2]);
3299    case OP_SBIT:
3300      return hash_find (sbit_hash, operand->buf) != 0 || is_absolute (operand);
3301    case OP_CC:
3302      return hash_find (cc_hash, operand->buf) != 0;
3303    case OP_CC2:
3304      return hash_find (cc2_hash, operand->buf) != 0;
3305    case OP_CC3:
3306      return hash_find (cc3_hash, operand->buf) != 0
3307	|| is_immediate (operand) || is_absolute (operand);
3308    case OP_16:
3309      return (is_immediate (operand) || is_absolute (operand))
3310	&& operand->exp.X_add_number == 16;
3311    case OP_N:
3312      /* Allow st0 or st1 instead of a numeric.  */
3313      return is_absolute (operand) || is_immediate (operand) ||
3314	strcasecmp ("st0", operand->buf) == 0 ||
3315	strcasecmp ("st1", operand->buf) == 0;
3316    case OP_12:
3317    case OP_123:
3318      return is_absolute (operand) || is_immediate (operand);
3319    case OP_SHFT:
3320      return (is_immediate (operand) || is_absolute (operand))
3321	&& operand->exp.X_add_number >= 0 && operand->exp.X_add_number < 16;
3322    case OP_SHIFT:
3323      /* Let this one catch out-of-range values.  */
3324      return (is_immediate (operand) || is_absolute (operand))
3325	&& operand->exp.X_add_number != 16;
3326    case OP_BITC:
3327    case OP_031:
3328    case OP_k8:
3329      return is_absolute (operand) || is_immediate (operand);
3330    case OP_k8u:
3331      return is_immediate (operand)
3332	&& operand->exp.X_op == O_constant
3333	&& operand->exp.X_add_number >= 0
3334	&& operand->exp.X_add_number < 256;
3335    case OP_lk:
3336    case OP_lku:
3337      /* Allow anything; assumes opcodes are ordered with Smem operands
3338	 versions first.  */
3339      return 1;
3340    case OP_k5:
3341    case OP_k3:
3342    case OP_k9:
3343      /* Just make sure it's an integer; check range later.  */
3344      return is_immediate (operand);
3345    case OP_T:
3346      return strcasecmp ("t", operand->buf) == 0 ||
3347	strcasecmp ("treg", operand->buf) == 0;
3348    case OP_TS:
3349      return strcasecmp ("ts", operand->buf) == 0;
3350    case OP_ASM:
3351      return strcasecmp ("asm", operand->buf) == 0;
3352    case OP_TRN:
3353      return strcasecmp ("trn", operand->buf) == 0;
3354    case OP_DP:
3355      return strcasecmp ("dp", operand->buf) == 0;
3356    case OP_ARP:
3357      return strcasecmp ("arp", operand->buf) == 0;
3358    default:
3359      return 0;
3360    }
3361}
3362
3363static int
3364operands_match (tic54x_insn *insn,
3365		struct opstruct *operands,
3366		int opcount,
3367		const enum optype *refoptype,
3368		int minops,
3369		int maxops)
3370{
3371  int op = 0, refop = 0;
3372
3373  if (opcount == 0 && minops == 0)
3374    return 1;
3375
3376  while (op <= maxops && refop <= maxops)
3377    {
3378      while (!is_type (&operands[op], OPTYPE (refoptype[refop])))
3379	{
3380	  /* Skip an optional template operand if it doesn't agree
3381	     with the current operand.  */
3382	  if (refoptype[refop] & OPT)
3383	    {
3384	      ++refop;
3385	      --maxops;
3386	      if (refop > maxops)
3387		return 0;
3388	    }
3389	  else
3390	    return 0;
3391	}
3392
3393      /* Save the actual operand type for later use.  */
3394      operands[op].type = OPTYPE (refoptype[refop]);
3395      ++refop;
3396      ++op;
3397      /* Have we matched them all yet?  */
3398      if (op == opcount)
3399	{
3400	  while (op < maxops)
3401	    {
3402	      /* If a later operand is *not* optional, no match.  */
3403	      if ((refoptype[refop] & OPT) == 0)
3404		return 0;
3405	      /* Flag any implicit default OP_DST operands so we know to add
3406		 them explicitly when encoding the operand later.  */
3407	      if (OPTYPE (refoptype[refop]) == OP_DST)
3408		insn->using_default_dst = 1;
3409	      ++refop;
3410	      ++op;
3411	    }
3412
3413	  return 1;
3414	}
3415    }
3416
3417  return 0;
3418}
3419
3420/* 16-bit direct memory address
3421   Explicit dmad operands are always in last word of insn (usually second
3422   word, but bumped to third if lk addressing is used)
3423
3424   We allow *(dmad) notation because the TI assembler allows it.
3425
3426   XPC_CODE:
3427   0 for 16-bit addresses
3428   1 for full 23-bit addresses
3429   2 for the upper 7 bits of a 23-bit address (LDX).  */
3430
3431static int
3432encode_dmad (tic54x_insn *insn, struct opstruct *operand, int xpc_code)
3433{
3434  int op = 1 + insn->is_lkaddr;
3435
3436  /* Only allow *(dmad) expressions; all others are invalid.  */
3437  if (is_indirect (operand) && operand->buf[strlen (operand->buf) - 1] != ')')
3438    {
3439      as_bad (_("Invalid dmad syntax '%s'"), operand->buf);
3440      return 0;
3441    }
3442
3443  insn->opcode[op].addr_expr = operand->exp;
3444
3445  if (insn->opcode[op].addr_expr.X_op == O_constant)
3446    {
3447      valueT value = insn->opcode[op].addr_expr.X_add_number;
3448
3449      if (xpc_code == 1)
3450	{
3451	  insn->opcode[0].word &= 0xFF80;
3452	  insn->opcode[0].word |= (value >> 16) & 0x7F;
3453	  insn->opcode[1].word = value & 0xFFFF;
3454	}
3455      else if (xpc_code == 2)
3456	insn->opcode[op].word = (value >> 16) & 0xFFFF;
3457      else
3458	insn->opcode[op].word = value;
3459    }
3460  else
3461    {
3462      /* Do the fixup later; just store the expression.  */
3463      insn->opcode[op].word = 0;
3464      insn->opcode[op].r_nchars = 2;
3465
3466      if (amode == c_mode)
3467	insn->opcode[op].r_type = BFD_RELOC_TIC54X_16_OF_23;
3468      else if (xpc_code == 1)
3469	{
3470	  /* This relocation spans two words, so adjust accordingly.  */
3471	  insn->opcode[0].addr_expr = operand->exp;
3472	  insn->opcode[0].r_type = BFD_RELOC_TIC54X_23;
3473	  insn->opcode[0].r_nchars = 4;
3474	  insn->opcode[0].unresolved = 1;
3475	  /* It's really 2 words, but we want to stop encoding after the
3476	     first, since we must encode both words at once.  */
3477	  insn->words = 1;
3478	}
3479      else if (xpc_code == 2)
3480	insn->opcode[op].r_type = BFD_RELOC_TIC54X_MS7_OF_23;
3481      else
3482	insn->opcode[op].r_type = BFD_RELOC_TIC54X_16_OF_23;
3483
3484      insn->opcode[op].unresolved = 1;
3485    }
3486
3487  return 1;
3488}
3489
3490/* 7-bit direct address encoding.  */
3491
3492static int
3493encode_address (tic54x_insn *insn, struct opstruct *operand)
3494{
3495  /* Assumes that dma addresses are *always* in word 0 of the opcode.  */
3496  insn->opcode[0].addr_expr = operand->exp;
3497
3498  if (operand->exp.X_op == O_constant)
3499    insn->opcode[0].word |= (operand->exp.X_add_number & 0x7F);
3500  else
3501    {
3502      if (operand->exp.X_op == O_register)
3503        as_bad (_("Use the .mmregs directive to use memory-mapped register names such as '%s'"), operand->buf);
3504      /* Do the fixup later; just store the expression.  */
3505      insn->opcode[0].r_nchars = 1;
3506      insn->opcode[0].r_type = BFD_RELOC_TIC54X_PARTLS7;
3507      insn->opcode[0].unresolved = 1;
3508    }
3509
3510  return 1;
3511}
3512
3513static int
3514encode_indirect (tic54x_insn *insn, struct opstruct *operand)
3515{
3516  int arf;
3517  int mod;
3518
3519  if (insn->is_lkaddr)
3520    {
3521      /* lk addresses always go in the second insn word.  */
3522      mod = ((TOUPPER (operand->buf[1]) == 'A') ? 12 :
3523	     (operand->buf[1] == '(') ? 15 :
3524	     (strchr (operand->buf, '%') != NULL) ? 14 : 13);
3525      arf = ((mod == 12) ? operand->buf[3] - '0' :
3526	     (mod == 15) ? 0 : operand->buf[4] - '0');
3527
3528      insn->opcode[1].addr_expr = operand->exp;
3529
3530      if (operand->exp.X_op == O_constant)
3531	insn->opcode[1].word = operand->exp.X_add_number;
3532      else
3533	{
3534	  insn->opcode[1].word = 0;
3535	  insn->opcode[1].r_nchars = 2;
3536	  insn->opcode[1].r_type = BFD_RELOC_TIC54X_16_OF_23;
3537	  insn->opcode[1].unresolved = 1;
3538	}
3539    }
3540  else if (strncasecmp (operand->buf, "*sp (", 4) == 0)
3541    {
3542      /* Stack offsets look the same as 7-bit direct addressing.  */
3543      return encode_address (insn, operand);
3544    }
3545  else
3546    {
3547      arf = (TOUPPER (operand->buf[1]) == 'A' ?
3548	     operand->buf[3] : operand->buf[4]) - '0';
3549
3550      if (operand->buf[1] == '+')
3551	{
3552	  mod = 3;		    /* *+ARx  */
3553	  if (insn->tm->flags & FL_SMR)
3554	    as_warn (_("Address mode *+ARx is write-only. "
3555		       "Results of reading are undefined."));
3556	}
3557      else if (operand->buf[4] == '\0')
3558	mod = 0;		    /* *ARx  */
3559      else if (operand->buf[5] == '\0')
3560	mod = (operand->buf[4] == '-' ? 1 : 2); /* *ARx+ / *ARx-  */
3561      else if (operand->buf[6] == '\0')
3562	{
3563	  if (operand->buf[5] == '0')
3564	    mod = (operand->buf[4] == '-' ? 5 : 6); /* *ARx+0 / *ARx-0  */
3565	  else
3566	    mod = (operand->buf[4] == '-' ? 8 : 10);/* *ARx+% / *ARx-%  */
3567	}
3568      else if (TOUPPER (operand->buf[6]) == 'B')
3569	mod = (operand->buf[4] == '-' ? 4 : 7); /* ARx+0B / *ARx-0B  */
3570      else if (TOUPPER (operand->buf[6]) == '%')
3571	mod = (operand->buf[4] == '-' ? 9 : 11); /* ARx+0% / *ARx - 0%  */
3572      else
3573	{
3574	  as_bad (_("Unrecognized indirect address format \"%s\""),
3575		  operand->buf);
3576	  return 0;
3577	}
3578    }
3579
3580  insn->opcode[0].word |= 0x80 | (mod << 3) | arf;
3581
3582  return 1;
3583}
3584
3585static int
3586encode_integer (tic54x_insn *insn,
3587		struct opstruct *operand,
3588		int which,
3589		int min,
3590		int max,
3591		unsigned short mask)
3592{
3593  long parse, integer;
3594
3595  insn->opcode[which].addr_expr = operand->exp;
3596
3597  if (operand->exp.X_op == O_constant)
3598    {
3599      parse = operand->exp.X_add_number;
3600      /* Hack -- fixup for 16-bit hex quantities that get converted positive
3601	 instead of negative.  */
3602      if ((parse & 0x8000) && min == -32768 && max == 32767)
3603	integer = (short) parse;
3604      else
3605	integer = parse;
3606
3607      if (integer >= min && integer <= max)
3608	{
3609	  insn->opcode[which].word |= (integer & mask);
3610	  return 1;
3611	}
3612      as_bad (_("Operand '%s' out of range (%d <= x <= %d)"),
3613	      operand->buf, min, max);
3614    }
3615  else
3616    {
3617      if (insn->opcode[which].addr_expr.X_op == O_constant)
3618	{
3619	  insn->opcode[which].word |=
3620	    insn->opcode[which].addr_expr.X_add_number & mask;
3621	}
3622      else
3623	{
3624	  /* Do the fixup later; just store the expression.  */
3625	  bfd_reloc_code_real_type rtype =
3626	    (mask == 0x1FF ? BFD_RELOC_TIC54X_PARTMS9 :
3627	     mask == 0xFFFF ? BFD_RELOC_TIC54X_16_OF_23 :
3628	     mask == 0x7F ? BFD_RELOC_TIC54X_PARTLS7 : BFD_RELOC_8);
3629	  int size = (mask == 0x1FF || mask == 0xFFFF) ? 2 : 1;
3630
3631	  if (rtype == BFD_RELOC_8)
3632	    as_bad (_("Error in relocation handling"));
3633
3634	  insn->opcode[which].r_nchars = size;
3635	  insn->opcode[which].r_type = rtype;
3636	  insn->opcode[which].unresolved = 1;
3637	}
3638
3639      return 1;
3640    }
3641
3642  return 0;
3643}
3644
3645static int
3646encode_condition (tic54x_insn *insn, struct opstruct *operand)
3647{
3648  tic54x_symbol *cc = (tic54x_symbol *) hash_find (cc_hash, operand->buf);
3649  if (!cc)
3650    {
3651      as_bad (_("Unrecognized condition code \"%s\""), operand->buf);
3652      return 0;
3653    }
3654#define CC_GROUP 0x40
3655#define CC_ACC   0x08
3656#define CATG_A1  0x07
3657#define CATG_B1  0x30
3658#define CATG_A2  0x30
3659#define CATG_B2  0x0C
3660#define CATG_C2  0x03
3661  /* Disallow group 1 conditions mixed with group 2 conditions
3662     if group 1, allow only one category A and one category B
3663     if group 2, allow only one each of category A, B, and C.  */
3664  if (((insn->opcode[0].word & 0xFF) != 0))
3665    {
3666      if ((insn->opcode[0].word & CC_GROUP) != (cc->value & CC_GROUP))
3667	{
3668	  as_bad (_("Condition \"%s\" does not match preceding group"),
3669		  operand->buf);
3670	  return 0;
3671	}
3672      if (insn->opcode[0].word & CC_GROUP)
3673	{
3674	  if ((insn->opcode[0].word & CC_ACC) != (cc->value & CC_ACC))
3675	    {
3676	      as_bad (_("Condition \"%s\" uses a different accumulator from "
3677			"a preceding condition"),
3678		      operand->buf);
3679	      return 0;
3680	    }
3681	  if ((insn->opcode[0].word & CATG_A1) && (cc->value & CATG_A1))
3682	    {
3683	      as_bad (_("Only one comparison conditional allowed"));
3684	      return 0;
3685	    }
3686	  if ((insn->opcode[0].word & CATG_B1) && (cc->value & CATG_B1))
3687	    {
3688	      as_bad (_("Only one overflow conditional allowed"));
3689	      return 0;
3690	    }
3691	}
3692      else if (   ((insn->opcode[0].word & CATG_A2) && (cc->value & CATG_A2))
3693	       || ((insn->opcode[0].word & CATG_B2) && (cc->value & CATG_B2))
3694	       || ((insn->opcode[0].word & CATG_C2) && (cc->value & CATG_C2)))
3695	{
3696	  as_bad (_("Duplicate %s conditional"), operand->buf);
3697	  return 0;
3698	}
3699    }
3700
3701  insn->opcode[0].word |= cc->value;
3702  return 1;
3703}
3704
3705static int
3706encode_cc3 (tic54x_insn *insn, struct opstruct *operand)
3707{
3708  tic54x_symbol *cc3 = (tic54x_symbol *) hash_find (cc3_hash, operand->buf);
3709  int value = cc3 ? cc3->value : operand->exp.X_add_number << 8;
3710
3711  if ((value & 0x0300) != value)
3712    {
3713      as_bad (_("Unrecognized condition code \"%s\""), operand->buf);
3714      return 0;
3715    }
3716  insn->opcode[0].word |= value;
3717  return 1;
3718}
3719
3720static int
3721encode_arx (tic54x_insn *insn, struct opstruct *operand)
3722{
3723  int arf = strlen (operand->buf) >= 3 ? operand->buf[2] - '0' : -1;
3724
3725  if (strncasecmp ("ar", operand->buf, 2) || arf < 0 || arf > 7)
3726    {
3727      as_bad (_("Invalid auxiliary register (use AR0-AR7)"));
3728      return 0;
3729    }
3730  insn->opcode[0].word |= arf;
3731  return 1;
3732}
3733
3734static int
3735encode_cc2 (tic54x_insn *insn, struct opstruct *operand)
3736{
3737  tic54x_symbol *cc2 = (tic54x_symbol *) hash_find (cc2_hash, operand->buf);
3738
3739  if (!cc2)
3740    {
3741      as_bad (_("Unrecognized condition code \"%s\""), operand->buf);
3742      return 0;
3743    }
3744  insn->opcode[0].word |= cc2->value;
3745  return 1;
3746}
3747
3748static int
3749encode_operand (tic54x_insn *insn, enum optype type, struct opstruct *operand)
3750{
3751  int ext = (insn->tm->flags & FL_EXT) != 0;
3752
3753  if (type == OP_MMR && operand->exp.X_op != O_constant)
3754    {
3755      /* Disallow long-constant addressing for memory-mapped addressing.  */
3756      if (insn->is_lkaddr)
3757	{
3758	  as_bad (_("lk addressing modes are invalid for memory-mapped "
3759		    "register addressing"));
3760	  return 0;
3761	}
3762      type = OP_Smem;
3763      /* Warn about *+ARx when used with MMR operands.  */
3764      if (strncasecmp (operand->buf, "*+ar", 4) == 0)
3765	{
3766	  as_warn (_("Address mode *+ARx is not allowed in memory-mapped "
3767		     "register addressing.  Resulting behavior is "
3768		     "undefined."));
3769	}
3770    }
3771
3772  switch (type)
3773    {
3774    case OP_None:
3775      return 1;
3776    case OP_dmad:
3777      /* 16-bit immediate value.  */
3778      return encode_dmad (insn, operand, 0);
3779    case OP_SRC:
3780      if (TOUPPER (*operand->buf) == 'B')
3781	{
3782	  insn->opcode[ext ? (1 + insn->is_lkaddr) : 0].word |= (1 << 9);
3783	  if (insn->using_default_dst)
3784	    insn->opcode[ext ? (1 + insn->is_lkaddr) : 0].word |= (1 << 8);
3785	}
3786      return 1;
3787    case OP_RND:
3788      /* Make sure this agrees with the OP_DST operand.  */
3789      if (!((TOUPPER (operand->buf[0]) == 'B') ^
3790	    ((insn->opcode[0].word & (1 << 8)) != 0)))
3791	{
3792	  as_bad (_("Destination accumulator for each part of this parallel "
3793		    "instruction must be different"));
3794	  return 0;
3795	}
3796      return 1;
3797    case OP_SRC1:
3798    case OP_DST:
3799      if (TOUPPER (operand->buf[0]) == 'B')
3800	insn->opcode[ext ? (1 + insn->is_lkaddr) : 0].word |= (1 << 8);
3801      return 1;
3802    case OP_Xmem:
3803    case OP_Ymem:
3804      {
3805	int mod = (operand->buf[4] == '\0' ? 0 : /* *arx  */
3806		   operand->buf[4] == '-' ? 1 : /* *arx-  */
3807		   operand->buf[5] == '\0' ? 2 : 3); /* *arx+, *arx+0%  */
3808	int arf = operand->buf[3] - '0' - 2;
3809	int code = (mod << 2) | arf;
3810	insn->opcode[0].word |= (code << (type == OP_Xmem ? 4 : 0));
3811	return 1;
3812      }
3813    case OP_Lmem:
3814    case OP_Smem:
3815      if (!is_indirect (operand))
3816	return encode_address (insn, operand);
3817      /* Fall through.  */
3818    case OP_Sind:
3819      return encode_indirect (insn, operand);
3820    case OP_xpmad_ms7:
3821      return encode_dmad (insn, operand, 2);
3822    case OP_xpmad:
3823      return encode_dmad (insn, operand, 1);
3824    case OP_PA:
3825    case OP_pmad:
3826      return encode_dmad (insn, operand, 0);
3827    case OP_ARX:
3828      return encode_arx (insn, operand);
3829    case OP_MMRX:
3830    case OP_MMRY:
3831    case OP_MMR:
3832      {
3833	int value = operand->exp.X_add_number;
3834
3835	if (type == OP_MMR)
3836	  insn->opcode[0].word |= value;
3837	else
3838	  {
3839	    if (value < 16 || value > 24)
3840	      {
3841		as_bad (_("Memory mapped register \"%s\" out of range"),
3842			operand->buf);
3843		return 0;
3844	      }
3845	    if (type == OP_MMRX)
3846	      insn->opcode[0].word |= (value - 16) << 4;
3847	    else
3848	      insn->opcode[0].word |= (value - 16);
3849	  }
3850	return 1;
3851      }
3852    case OP_B:
3853    case OP_A:
3854      return 1;
3855    case OP_SHFT:
3856      return encode_integer (insn, operand, ext + insn->is_lkaddr,
3857			     0, 15, 0xF);
3858    case OP_SHIFT:
3859      return encode_integer (insn, operand, ext + insn->is_lkaddr,
3860			     -16, 15, 0x1F);
3861    case OP_lk:
3862      return encode_integer (insn, operand, 1 + insn->is_lkaddr,
3863			     -32768, 32767, 0xFFFF);
3864    case OP_CC:
3865      return encode_condition (insn, operand);
3866    case OP_CC2:
3867      return encode_cc2 (insn, operand);
3868    case OP_CC3:
3869      return encode_cc3 (insn, operand);
3870    case OP_BITC:
3871      return encode_integer (insn, operand, 0, 0, 15, 0xF);
3872    case OP_k8:
3873      return encode_integer (insn, operand, 0, -128, 127, 0xFF);
3874    case OP_123:
3875      {
3876	int value = operand->exp.X_add_number;
3877	int code;
3878	if (value < 1 || value > 3)
3879	  {
3880	    as_bad (_("Invalid operand (use 1, 2, or 3)"));
3881	    return 0;
3882	  }
3883	code = value == 1 ? 0 : value == 2 ? 0x2 : 0x1;
3884	insn->opcode[0].word |= (code << 8);
3885	return 1;
3886      }
3887    case OP_031:
3888      return encode_integer (insn, operand, 0, 0, 31, 0x1F);
3889    case OP_k8u:
3890      return encode_integer (insn, operand, 0, 0, 255, 0xFF);
3891    case OP_lku:
3892      return encode_integer (insn, operand, 1 + insn->is_lkaddr,
3893			     0, 65535, 0xFFFF);
3894    case OP_SBIT:
3895      {
3896	tic54x_symbol *sbit = (tic54x_symbol *)
3897	  hash_find (sbit_hash, operand->buf);
3898	int value = is_absolute (operand) ?
3899	  operand->exp.X_add_number : (sbit ? sbit->value : -1);
3900	int reg = 0;
3901
3902	if (insn->opcount == 1)
3903	  {
3904	    if (!sbit)
3905	      {
3906		as_bad (_("A status register or status bit name is required"));
3907		return 0;
3908	      }
3909	    /* Guess the register based on the status bit; "ovb" is the last
3910	       status bit defined for st0.  */
3911	    if (sbit > (tic54x_symbol *) hash_find (sbit_hash, "ovb"))
3912	      reg = 1;
3913	  }
3914	if (value == -1)
3915	  {
3916	    as_bad (_("Unrecognized status bit \"%s\""), operand->buf);
3917	    return 0;
3918	  }
3919	insn->opcode[0].word |= value;
3920	insn->opcode[0].word |= (reg << 9);
3921	return 1;
3922      }
3923    case OP_N:
3924      if (strcasecmp (operand->buf, "st0") == 0
3925	  || strcasecmp (operand->buf, "st1") == 0)
3926	{
3927	  insn->opcode[0].word |=
3928	    ((unsigned short) (operand->buf[2] - '0')) << 9;
3929	  return 1;
3930	}
3931      else if (operand->exp.X_op == O_constant
3932	       && (operand->exp.X_add_number == 0
3933		   || operand->exp.X_add_number == 1))
3934	{
3935	  insn->opcode[0].word |=
3936	    ((unsigned short) (operand->exp.X_add_number)) << 9;
3937	  return 1;
3938	}
3939      as_bad (_("Invalid status register \"%s\""), operand->buf);
3940      return 0;
3941    case OP_k5:
3942      return encode_integer (insn, operand, 0, -16, 15, 0x1F);
3943    case OP_k3:
3944      return encode_integer (insn, operand, 0, 0, 7, 0x7);
3945    case OP_k9:
3946      return encode_integer (insn, operand, 0, 0, 0x1FF, 0x1FF);
3947    case OP_12:
3948      if (operand->exp.X_add_number != 1
3949	  && operand->exp.X_add_number != 2)
3950	{
3951	  as_bad (_("Operand \"%s\" out of range (use 1 or 2)"), operand->buf);
3952	  return 0;
3953	}
3954      insn->opcode[0].word |= (operand->exp.X_add_number - 1) << 9;
3955      return 1;
3956    case OP_16:
3957    case OP_T:
3958    case OP_TS:
3959    case OP_ASM:
3960    case OP_TRN:
3961    case OP_DP:
3962    case OP_ARP:
3963      /* No encoding necessary.  */
3964      return 1;
3965    default:
3966      return 0;
3967    }
3968
3969  return 1;
3970}
3971
3972static void
3973emit_insn (tic54x_insn *insn)
3974{
3975  int i;
3976  flagword oldflags = bfd_get_section_flags (stdoutput, now_seg);
3977  flagword flags = oldflags | SEC_CODE;
3978
3979  if (! bfd_set_section_flags (stdoutput, now_seg, flags))
3980        as_warn (_("error setting flags for \"%s\": %s"),
3981                 bfd_section_name (stdoutput, now_seg),
3982                 bfd_errmsg (bfd_get_error ()));
3983
3984  for (i = 0; i < insn->words; i++)
3985    {
3986      int size = (insn->opcode[i].unresolved
3987		  && insn->opcode[i].r_type == BFD_RELOC_TIC54X_23) ? 4 : 2;
3988      char *p = frag_more (size);
3989
3990      if (size == 2)
3991	md_number_to_chars (p, (valueT) insn->opcode[i].word, 2);
3992      else
3993	md_number_to_chars (p, (valueT) insn->opcode[i].word << 16, 4);
3994
3995      if (insn->opcode[i].unresolved)
3996	fix_new_exp (frag_now, p - frag_now->fr_literal,
3997		     insn->opcode[i].r_nchars, &insn->opcode[i].addr_expr,
3998		     FALSE, insn->opcode[i].r_type);
3999    }
4000}
4001
4002/* Convert the operand strings into appropriate opcode values
4003   return the total number of words used by the instruction.  */
4004
4005static int
4006build_insn (tic54x_insn *insn)
4007{
4008  int i;
4009
4010  /* Only non-parallel instructions support lk addressing.  */
4011  if (!(insn->tm->flags & FL_PAR))
4012    {
4013      for (i = 0; i < insn->opcount; i++)
4014	{
4015	  if ((OPTYPE (insn->operands[i].type) == OP_Smem
4016	       || OPTYPE (insn->operands[i].type) == OP_Lmem
4017	       || OPTYPE (insn->operands[i].type) == OP_Sind)
4018	      && strchr (insn->operands[i].buf, '(')
4019	      /* Don't mistake stack-relative addressing for lk addressing.  */
4020	      && strncasecmp (insn->operands[i].buf, "*sp (", 4) != 0)
4021	    {
4022	      insn->is_lkaddr = 1;
4023	      insn->lkoperand = i;
4024	      break;
4025	    }
4026	}
4027    }
4028  insn->words = insn->tm->words + insn->is_lkaddr;
4029
4030  insn->opcode[0].word = insn->tm->opcode;
4031  if (insn->tm->flags & FL_EXT)
4032    insn->opcode[1 + insn->is_lkaddr].word = insn->tm->opcode2;
4033
4034  for (i = 0; i < insn->opcount; i++)
4035    {
4036      enum optype type = insn->operands[i].type;
4037
4038      if (!encode_operand (insn, type, &insn->operands[i]))
4039	return 0;
4040    }
4041  if (insn->tm->flags & FL_PAR)
4042    for (i = 0; i < insn->paropcount; i++)
4043      {
4044	enum optype partype = insn->paroperands[i].type;
4045
4046	if (!encode_operand (insn, partype, &insn->paroperands[i]))
4047	  return 0;
4048      }
4049
4050  emit_insn (insn);
4051
4052  return insn->words;
4053}
4054
4055static int
4056optimize_insn (tic54x_insn *insn)
4057{
4058  /* Optimize some instructions, helping out the brain-dead programmer.  */
4059#define is_zero(op) ((op).exp.X_op == O_constant && (op).exp.X_add_number == 0)
4060  if (strcasecmp (insn->tm->name, "add") == 0)
4061    {
4062      if (insn->opcount > 1
4063	  && is_accumulator (&insn->operands[insn->opcount - 2])
4064	  && is_accumulator (&insn->operands[insn->opcount - 1])
4065	  && strcasecmp (insn->operands[insn->opcount - 2].buf,
4066			 insn->operands[insn->opcount - 1].buf) == 0)
4067	{
4068	  --insn->opcount;
4069	  insn->using_default_dst = 1;
4070	  return 1;
4071	}
4072
4073      /* Try to collapse if Xmem and shift count is zero.  */
4074      if ((OPTYPE (insn->tm->operand_types[0]) == OP_Xmem
4075	   && OPTYPE (insn->tm->operand_types[1]) == OP_SHFT
4076	   && is_zero (insn->operands[1]))
4077	  /* Or if Smem, shift is zero or absent, and SRC == DST.  */
4078	  || (OPTYPE (insn->tm->operand_types[0]) == OP_Smem
4079	      && OPTYPE (insn->tm->operand_types[1]) == OP_SHIFT
4080	      && is_type (&insn->operands[1], OP_SHIFT)
4081	      && is_zero (insn->operands[1]) && insn->opcount == 3))
4082	{
4083	  insn->operands[1] = insn->operands[2];
4084	  insn->opcount = 2;
4085	  return 1;
4086	}
4087    }
4088  else if (strcasecmp (insn->tm->name, "ld") == 0)
4089    {
4090      if (insn->opcount == 3 && insn->operands[0].type != OP_SRC)
4091	{
4092	  if ((OPTYPE (insn->tm->operand_types[1]) == OP_SHIFT
4093	       || OPTYPE (insn->tm->operand_types[1]) == OP_SHFT)
4094	      && is_zero (insn->operands[1])
4095	      && (OPTYPE (insn->tm->operand_types[0]) != OP_lk
4096		  || (insn->operands[0].exp.X_op == O_constant
4097		      && insn->operands[0].exp.X_add_number <= 255
4098		      && insn->operands[0].exp.X_add_number >= 0)))
4099	    {
4100	      insn->operands[1] = insn->operands[2];
4101	      insn->opcount = 2;
4102	      return 1;
4103	    }
4104	}
4105    }
4106  else if (strcasecmp (insn->tm->name, "sth") == 0
4107	   || strcasecmp (insn->tm->name, "stl") == 0)
4108    {
4109      if ((OPTYPE (insn->tm->operand_types[1]) == OP_SHIFT
4110	   || OPTYPE (insn->tm->operand_types[1]) == OP_SHFT)
4111	  && is_zero (insn->operands[1]))
4112	{
4113	  insn->operands[1] = insn->operands[2];
4114	  insn->opcount = 2;
4115	  return 1;
4116	}
4117    }
4118  else if (strcasecmp (insn->tm->name, "sub") == 0)
4119    {
4120      if (insn->opcount > 1
4121	  && is_accumulator (&insn->operands[insn->opcount - 2])
4122	  && is_accumulator (&insn->operands[insn->opcount - 1])
4123	  && strcasecmp (insn->operands[insn->opcount - 2].buf,
4124			 insn->operands[insn->opcount - 1].buf) == 0)
4125	{
4126	  --insn->opcount;
4127	  insn->using_default_dst = 1;
4128	  return 1;
4129	}
4130
4131      if (   ((OPTYPE (insn->tm->operand_types[0]) == OP_Smem
4132	    && OPTYPE (insn->tm->operand_types[1]) == OP_SHIFT)
4133	   || (OPTYPE (insn->tm->operand_types[0]) == OP_Xmem
4134	    && OPTYPE (insn->tm->operand_types[1]) == OP_SHFT))
4135	  && is_zero (insn->operands[1])
4136	  && insn->opcount == 3)
4137	{
4138	  insn->operands[1] = insn->operands[2];
4139	  insn->opcount = 2;
4140	  return 1;
4141	}
4142    }
4143  return 0;
4144}
4145
4146/* Find a matching template if possible, and get the operand strings.  */
4147
4148static int
4149tic54x_parse_insn (tic54x_insn *insn, char *line)
4150{
4151  insn->tm = (insn_template *) hash_find (op_hash, insn->mnemonic);
4152  if (!insn->tm)
4153    {
4154      as_bad (_("Unrecognized instruction \"%s\""), insn->mnemonic);
4155      return 0;
4156    }
4157
4158  insn->opcount = get_operands (insn->operands, line);
4159  if (insn->opcount < 0)
4160    return 0;
4161
4162  /* Check each variation of operands for this mnemonic.  */
4163  while (insn->tm->name && strcasecmp (insn->tm->name, insn->mnemonic) == 0)
4164    {
4165      if (insn->opcount >= insn->tm->minops
4166	  && insn->opcount <= insn->tm->maxops
4167	  && operands_match (insn, &insn->operands[0], insn->opcount,
4168			     insn->tm->operand_types,
4169			     insn->tm->minops, insn->tm->maxops))
4170	{
4171	  /* SUCCESS! now try some optimizations.  */
4172	  if (optimize_insn (insn))
4173	    {
4174	      insn->tm = (insn_template *) hash_find (op_hash,
4175                                                      insn->mnemonic);
4176	      continue;
4177	    }
4178
4179	  return 1;
4180	}
4181      ++(insn->tm);
4182    }
4183  as_bad (_("Unrecognized operand list '%s' for instruction '%s'"),
4184	  line, insn->mnemonic);
4185  return 0;
4186}
4187
4188/* We set this in start_line_hook, 'cause if we do a line replacement, we
4189   won't be able to see the next line.  */
4190static int parallel_on_next_line_hint = 0;
4191
4192/* See if this is part of a parallel instruction
4193   Look for a subsequent line starting with "||".  */
4194
4195static int
4196next_line_shows_parallel (char *next_line)
4197{
4198  /* Look for the second half.  */
4199  while (ISSPACE (*next_line))
4200    ++next_line;
4201
4202  return (next_line[0] == PARALLEL_SEPARATOR
4203	  && next_line[1] == PARALLEL_SEPARATOR);
4204}
4205
4206static int
4207tic54x_parse_parallel_insn_firstline (tic54x_insn *insn, char *line)
4208{
4209  insn->tm = (insn_template *) hash_find (parop_hash, insn->mnemonic);
4210  if (!insn->tm)
4211    {
4212      as_bad (_("Unrecognized parallel instruction \"%s\""),
4213	      insn->mnemonic);
4214      return 0;
4215    }
4216
4217  while (insn->tm->name && strcasecmp (insn->tm->name,
4218                                       insn->mnemonic) == 0)
4219    {
4220      insn->opcount = get_operands (insn->operands, line);
4221      if (insn->opcount < 0)
4222	return 0;
4223      if (insn->opcount == 2
4224	  && operands_match (insn, &insn->operands[0], insn->opcount,
4225			     insn->tm->operand_types, 2, 2))
4226	{
4227	  return 1;
4228	}
4229      ++(insn->tm);
4230    }
4231  /* Didn't find a matching parallel; try for a normal insn.  */
4232  return 0;
4233}
4234
4235/* Parse the second line of a two-line parallel instruction.  */
4236
4237static int
4238tic54x_parse_parallel_insn_lastline (tic54x_insn *insn, char *line)
4239{
4240  int valid_mnemonic = 0;
4241
4242  insn->paropcount = get_operands (insn->paroperands, line);
4243  while (insn->tm->name && strcasecmp (insn->tm->name,
4244				       insn->mnemonic) == 0)
4245    {
4246      if (strcasecmp (insn->tm->parname, insn->parmnemonic) == 0)
4247	{
4248	  valid_mnemonic = 1;
4249
4250	  if (insn->paropcount >= insn->tm->minops
4251	      && insn->paropcount <= insn->tm->maxops
4252	      && operands_match (insn, insn->paroperands,
4253				 insn->paropcount,
4254				 insn->tm->paroperand_types,
4255				 insn->tm->minops, insn->tm->maxops))
4256	    return 1;
4257	}
4258      ++(insn->tm);
4259    }
4260  if (valid_mnemonic)
4261    as_bad (_("Invalid operand (s) for parallel instruction \"%s\""),
4262	    insn->parmnemonic);
4263  else
4264    as_bad (_("Unrecognized parallel instruction combination \"%s || %s\""),
4265	    insn->mnemonic, insn->parmnemonic);
4266
4267  return 0;
4268}
4269
4270/* If quotes found, return copy of line up to closing quote;
4271   otherwise up until terminator.
4272   If it's a string, pass as-is; otherwise attempt substitution symbol
4273   replacement on the value.  */
4274
4275static char *
4276subsym_get_arg (char *line, const char *terminators, char **str, int nosub)
4277{
4278  char *ptr = line;
4279  char *endp;
4280  int is_string = *line == '"';
4281  int is_char = ISDIGIT (*line);
4282
4283  if (is_char)
4284    {
4285      while (ISDIGIT (*ptr))
4286	++ptr;
4287      endp = ptr;
4288      *str = xmemdup0 (line, ptr - line);
4289    }
4290  else if (is_string)
4291    {
4292      char *savedp = input_line_pointer;
4293      int len;
4294
4295      input_line_pointer = ptr;
4296      *str = demand_copy_C_string (&len);
4297      endp = input_line_pointer;
4298      input_line_pointer = savedp;
4299
4300      /* Do forced substitutions if requested.  */
4301      if (!nosub && **str == ':')
4302	*str = subsym_substitute (*str, 1);
4303    }
4304  else
4305    {
4306      const char *term = terminators;
4307      char *value = NULL;
4308
4309      while (*ptr && *ptr != *term)
4310	{
4311	  if (!*term)
4312	    {
4313	      term = terminators;
4314	      ++ptr;
4315	    }
4316	  else
4317	    ++term;
4318	}
4319      endp = ptr;
4320      *str = xmemdup0 (line, ptr - line);
4321      /* Do simple substitution, if available.  */
4322      if (!nosub && (value = subsym_lookup (*str, macro_level)) != NULL)
4323	*str = value;
4324    }
4325
4326  return endp;
4327}
4328
4329/* Replace the given substitution string.
4330   We start at the innermost macro level, so that existing locals remain local
4331   Note: we're treating macro args identically to .var's; I don't know if
4332   that's compatible w/TI's assembler.  */
4333
4334static void
4335subsym_create_or_replace (char *name, char *value)
4336{
4337  int i;
4338
4339  for (i = macro_level; i > 0; i--)
4340    {
4341      if (hash_find (subsym_hash[i], name))
4342	{
4343	  hash_replace (subsym_hash[i], name, value);
4344	  return;
4345	}
4346    }
4347  if (hash_find (subsym_hash[0], name))
4348    hash_replace (subsym_hash[0], name, value);
4349  else
4350    hash_insert (subsym_hash[0], name, value);
4351}
4352
4353/* Look up the substitution string replacement for the given symbol.
4354   Start with the innermost macro substitution table given and work
4355   outwards.  */
4356
4357static char *
4358subsym_lookup (char *name, int nest_level)
4359{
4360  char *value = hash_find (subsym_hash[nest_level], name);
4361
4362  if (value || nest_level == 0)
4363    return value;
4364
4365  return subsym_lookup (name, nest_level - 1);
4366}
4367
4368/* Do substitution-symbol replacement on the given line (recursively).
4369   return the argument if no substitution was done
4370
4371   Also look for built-in functions ($func (arg)) and local labels.
4372
4373   If FORCED is set, look for forced substitutions of the form ':SYMBOL:'.  */
4374
4375static char *
4376subsym_substitute (char *line, int forced)
4377{
4378  /* For each apparent symbol, see if it's a substitution symbol, and if so,
4379     replace it in the input.  */
4380  char *replacement; /* current replacement for LINE.  */
4381  char *head; /* Start of line.  */
4382  char *ptr; /* Current examination point.  */
4383  int changed = 0; /* Did we make a substitution?  */
4384  int eval_line = 0; /* Is this line a .eval/.asg statement?  */
4385  int eval_symbol = 0; /* Are we in the middle of the symbol for
4386                          .eval/.asg?  */
4387  char *eval_end = NULL;
4388  int recurse = 1;
4389  int line_conditional = 0;
4390  char *tmp;
4391
4392  /* Work with a copy of the input line.  */
4393  replacement = xstrdup (line);
4394
4395  ptr = head = replacement;
4396
4397  /* Flag lines where we might need to replace a single '=' with two;
4398     GAS uses single '=' to assign macro args values, and possibly other
4399     places, so limit what we replace.  */
4400  if (strstr (line, ".if")
4401      || strstr (line, ".elseif")
4402      || strstr (line, ".break"))
4403    line_conditional = 1;
4404
4405  /* Watch out for .eval, so that we avoid doing substitution on the
4406     symbol being assigned a value.  */
4407  if (strstr (line, ".eval") || strstr (line, ".asg"))
4408    eval_line = 1;
4409
4410  /* If it's a macro definition, don't do substitution on the argument
4411     names.  */
4412  if (strstr (line, ".macro"))
4413    return line;
4414
4415  while (!is_end_of_line[(int) *ptr])
4416    {
4417      int current_char = *ptr;
4418
4419      /* Need to update this since LINE may have been modified.  */
4420      if (eval_line)
4421	eval_end = strrchr (ptr, ',');
4422
4423      /* Replace triple double quotes with bounding quote/escapes.  */
4424      if (current_char == '"' && ptr[1] == '"' && ptr[2] == '"')
4425	{
4426	  ptr[1] = '\\';
4427	  tmp = strstr (ptr + 2, "\"\"\"");
4428	  if (tmp)
4429	    tmp[0] = '\\';
4430	  changed = 1;
4431	}
4432
4433      /* Replace a single '=' with a '==';
4434	 for compatibility with older code only.  */
4435      if (line_conditional && current_char == '=')
4436	{
4437	  if (ptr[1] == '=')
4438	    {
4439	      ptr += 2;
4440	      continue;
4441	    }
4442	  *ptr++ = '\0';
4443	  tmp = concat (head, "==", ptr, (char *) NULL);
4444	  /* Continue examining after the '=='.  */
4445	  ptr = tmp + strlen (head) + 2;
4446	  free (replacement);
4447	  head = replacement = tmp;
4448	  changed = 1;
4449	}
4450
4451      /* Flag when we've reached the symbol part of .eval/.asg.  */
4452      if (eval_line && ptr >= eval_end)
4453	eval_symbol = 1;
4454
4455      /* For each apparent symbol, see if it's a substitution symbol, and if
4456	 so, replace it in the input.  */
4457      if ((forced && current_char == ':')
4458	  || (!forced && is_name_beginner (current_char)))
4459	{
4460	  char *name; /* Symbol to be replaced.  */
4461	  char *savedp = input_line_pointer;
4462	  int c;
4463	  char *value = NULL;
4464	  char *tail; /* Rest of line after symbol.  */
4465
4466	  /* Skip the colon.  */
4467	  if (forced)
4468	    ++ptr;
4469
4470	  input_line_pointer = ptr;
4471	  c = get_symbol_name (&name);
4472	  /* '?' is not normally part of a symbol, but it IS part of a local
4473	     label.  */
4474	  if (c == '?')
4475	    {
4476	      *input_line_pointer++ = c;
4477	      c = *input_line_pointer;
4478	      *input_line_pointer = '\0';
4479	    }
4480	  /* Avoid infinite recursion; if a symbol shows up a second time for
4481	     substitution, leave it as is.  */
4482	  if (hash_find (subsym_recurse_hash, name) == NULL)
4483	    value = subsym_lookup (name, macro_level);
4484	  else
4485	    as_warn (_("%s symbol recursion stopped at "
4486		       "second appearance of '%s'"),
4487		     forced ? "Forced substitution" : "Substitution", name);
4488	  ptr = tail = input_line_pointer;
4489	  input_line_pointer = savedp;
4490
4491	  /* Check for local labels; replace them with the appropriate
4492	     substitution.  */
4493	  if ((*name == '$' && ISDIGIT (name[1]) && name[2] == '\0')
4494	      || name[strlen (name) - 1] == '?')
4495	    {
4496	      /* Use an existing identifier for that label if, available, or
4497		 create a new, unique identifier.  */
4498	      value = hash_find (local_label_hash[macro_level], name);
4499	      if (value == NULL)
4500		{
4501		  char digit[11];
4502		  char *namecopy = xstrdup (name);
4503
4504		  value = strcpy (xmalloc (strlen (name) + sizeof (digit) + 1),
4505				  name);
4506		  if (*value != '$')
4507		    value[strlen (value) - 1] = '\0';
4508		  sprintf (digit, ".%d", local_label_id++);
4509		  strcat (value, digit);
4510		  hash_insert (local_label_hash[macro_level], namecopy, value);
4511		}
4512	      /* Indicate where to continue looking for substitutions.  */
4513	      ptr = tail;
4514	    }
4515	  /* Check for built-in subsym and math functions.  */
4516	  else if (value != NULL && *name == '$')
4517	    {
4518	      subsym_proc_entry *entry = (subsym_proc_entry *) value;
4519	      math_proc_entry *math_entry = hash_find (math_hash, name);
4520	      char *arg1, *arg2 = NULL;
4521
4522	      *ptr = c;
4523	      if (entry == NULL)
4524		{
4525		  as_bad (_("Unrecognized substitution symbol function"));
4526		  break;
4527		}
4528	      else if (*ptr != '(')
4529		{
4530		  as_bad (_("Missing '(' after substitution symbol function"));
4531		  break;
4532		}
4533	      ++ptr;
4534	      if (math_entry != NULL)
4535		{
4536		  float farg1, farg2 = 0;
4537		  volatile float fresult;
4538
4539		  farg1 = (float) strtod (ptr, &ptr);
4540		  if (math_entry->nargs == 2)
4541		    {
4542		      if (*ptr++ != ',')
4543			{
4544			  as_bad (_("Expecting second argument"));
4545			  break;
4546			}
4547		      farg2 = (float) strtod (ptr, &ptr);
4548		    }
4549		  fresult = (*math_entry->proc) (farg1, farg2);
4550		  value = XNEWVEC (char, 128);
4551		  if (math_entry->int_return)
4552		    sprintf (value, "%d", (int) fresult);
4553		  else
4554		    sprintf (value, "%f", fresult);
4555		  if (*ptr++ != ')')
4556		    {
4557		      as_bad (_("Extra junk in function call, expecting ')'"));
4558		      break;
4559		    }
4560		  /* Don't bother recursing; the replacement isn't a
4561                     symbol.  */
4562		  recurse = 0;
4563		}
4564	      else
4565		{
4566		  int val;
4567		  int arg_type[2] = { *ptr == '"' , 0 };
4568		  int ismember = !strcmp (entry->name, "$ismember");
4569
4570		  /* Parse one or two args, which must be a substitution
4571		     symbol, string or a character-string constant.  */
4572		  /* For all functions, a string or substitution symbol may be
4573		     used, with the following exceptions:
4574		     firstch/lastch: 2nd arg must be character constant
4575		     ismember: both args must be substitution symbols.  */
4576		  ptr = subsym_get_arg (ptr, ",)", &arg1, ismember);
4577		  if (!arg1)
4578		    break;
4579		  if (entry->nargs == 2)
4580		    {
4581		      if (*ptr++ != ',')
4582			{
4583			  as_bad (_("Function expects two arguments"));
4584			  break;
4585			}
4586		      /* Character constants are converted to numerics
4587			 by the preprocessor.  */
4588		      arg_type[1] = (ISDIGIT (*ptr)) ? 2 : (*ptr == '"');
4589		      ptr = subsym_get_arg (ptr, ")", &arg2, ismember);
4590		    }
4591		  /* Args checking.  */
4592		  if ((!strcmp (entry->name, "$firstch")
4593		       || !strcmp (entry->name, "$lastch"))
4594		      && arg_type[1] != 2)
4595		    {
4596		      as_bad (_("Expecting character constant argument"));
4597		      break;
4598		    }
4599		  if (ismember
4600		      && (arg_type[0] != 0 || arg_type[1] != 0))
4601		    {
4602		      as_bad (_("Both arguments must be substitution symbols"));
4603		      break;
4604		    }
4605		  if (*ptr++ != ')')
4606		    {
4607		      as_bad (_("Extra junk in function call, expecting ')'"));
4608		      break;
4609		    }
4610		  val = (*entry->proc) (arg1, arg2);
4611		  value = XNEWVEC (char, 64);
4612		  sprintf (value, "%d", val);
4613		}
4614	      /* Fix things up to replace the entire expression, not just the
4615		 function name.  */
4616	      tail = ptr;
4617	      c = *tail;
4618	    }
4619
4620	  if (value != NULL && !eval_symbol)
4621	    {
4622	      /* Replace the symbol with its string replacement and
4623		 continue.  Recursively replace VALUE until either no
4624		 substitutions are performed, or a substitution that has been
4625		 previously made is encountered again.
4626
4627		 Put the symbol into the recursion hash table so we only
4628		 try to replace a symbol once.  */
4629	      if (recurse)
4630		{
4631		  hash_insert (subsym_recurse_hash, name, name);
4632		  value = subsym_substitute (value, macro_level > 0);
4633		  hash_delete (subsym_recurse_hash, name, FALSE);
4634		}
4635
4636	      /* Temporarily zero-terminate where the symbol started.  */
4637	      *name = 0;
4638	      if (forced)
4639		{
4640		  if (c == '(')
4641		    {
4642		      /* Subscripted substitution symbol -- use just the
4643			 indicated portion of the string; the description
4644			 kinda indicates that forced substitution is not
4645			 supposed to be recursive, but I'm not sure.  */
4646		      unsigned beg, len = 1; /* default to a single char */
4647		      char *newval = xstrdup (value);
4648
4649		      savedp = input_line_pointer;
4650		      input_line_pointer = tail + 1;
4651		      beg = get_absolute_expression ();
4652		      if (beg < 1)
4653			{
4654			  as_bad (_("Invalid subscript (use 1 to %d)"),
4655				  (int) strlen (value));
4656			  break;
4657			}
4658		      if (*input_line_pointer == ',')
4659			{
4660			  ++input_line_pointer;
4661			  len = get_absolute_expression ();
4662			  if (beg + len > strlen (value))
4663			    {
4664			      as_bad (_("Invalid length (use 0 to %d"),
4665				      (int) strlen (value) - beg);
4666			      break;
4667			    }
4668			}
4669		      newval += beg - 1;
4670		      newval[len] = 0;
4671		      tail = input_line_pointer;
4672		      if (*tail++ != ')')
4673			{
4674			  as_bad (_("Missing ')' in subscripted substitution "
4675				    "symbol expression"));
4676			  break;
4677			}
4678		      c = *tail;
4679		      input_line_pointer = savedp;
4680
4681		      value = newval;
4682		    }
4683		  name[-1] = 0;
4684		}
4685	      tmp = xmalloc (strlen (head) + strlen (value) +
4686			     strlen (tail + 1) + 2);
4687	      strcpy (tmp, head);
4688	      strcat (tmp, value);
4689	      /* Make sure forced substitutions are properly terminated.  */
4690	      if (forced)
4691		{
4692		  if (c != ':')
4693		    {
4694		      as_bad (_("Missing forced substitution terminator ':'"));
4695		      break;
4696		    }
4697		  ++tail;
4698		}
4699	      else
4700		/* Restore the character after the symbol end.  */
4701		*tail = c;
4702	      strcat (tmp, tail);
4703	      /* Continue examining after the replacement value.  */
4704	      ptr = tmp + strlen (head) + strlen (value);
4705	      free (replacement);
4706	      head = replacement = tmp;
4707	      changed = 1;
4708	    }
4709	  else
4710	    *ptr = c;
4711	}
4712      else
4713	{
4714	  ++ptr;
4715	}
4716    }
4717
4718  if (changed)
4719    return replacement;
4720  else
4721    return line;
4722}
4723
4724/* We use this to handle substitution symbols
4725   hijack input_line_pointer, replacing it with our substituted string.
4726
4727   .sslist should enable listing the line after replacements are made...
4728
4729   returns the new buffer limit.  */
4730
4731void
4732tic54x_start_line_hook (void)
4733{
4734  char *line, *endp;
4735  char *replacement = NULL;
4736
4737  /* Work with a copy of the input line, including EOL char.  */
4738  endp = input_line_pointer;
4739  while (!is_end_of_line[(int) *endp++])
4740    ;
4741  line = xmemdup0 (input_line_pointer, endp - input_line_pointer);
4742
4743  /* Scan ahead for parallel insns.  */
4744  parallel_on_next_line_hint = next_line_shows_parallel (endp);
4745
4746  /* If within a macro, first process forced replacements.  */
4747  if (macro_level > 0)
4748    replacement = subsym_substitute (line, 1);
4749  else
4750    replacement = line;
4751  replacement = subsym_substitute (replacement, 0);
4752
4753  if (replacement != line)
4754    {
4755      char *tmp = replacement;
4756      char *comment = strchr (replacement, ';');
4757      char endc = replacement[strlen (replacement) - 1];
4758
4759      /* Clean up the replacement; we'd prefer to have this done by the
4760	 standard preprocessing equipment (maybe do_scrub_chars?)
4761	 but for now, do a quick-and-dirty.  */
4762      if (comment != NULL)
4763	{
4764	  comment[0] = endc;
4765	  comment[1] = 0;
4766	  --comment;
4767	}
4768      else
4769	comment = replacement + strlen (replacement) - 1;
4770
4771      /* Trim trailing whitespace.  */
4772      while (ISSPACE (*comment))
4773	{
4774	  comment[0] = endc;
4775	  comment[1] = 0;
4776	  --comment;
4777	}
4778
4779      /* Compact leading whitespace.  */
4780      while (ISSPACE (tmp[0]) && ISSPACE (tmp[1]))
4781	++tmp;
4782
4783      input_line_pointer = endp;
4784      input_scrub_insert_line (tmp);
4785      free (replacement);
4786      free (line);
4787      /* Keep track of whether we've done a substitution.  */
4788      substitution_line = 1;
4789    }
4790  else
4791    {
4792      /* No change.  */
4793      free (line);
4794      substitution_line = 0;
4795    }
4796}
4797
4798/* This is the guts of the machine-dependent assembler.  STR points to a
4799   machine dependent instruction.  This function is supposed to emit
4800   the frags/bytes it assembles to.  */
4801void
4802md_assemble (char *line)
4803{
4804  static int repeat_slot = 0;
4805  static int delay_slots = 0; /* How many delay slots left to fill?  */
4806  static int is_parallel = 0;
4807  static tic54x_insn insn;
4808  char *lptr;
4809  char *savedp = input_line_pointer;
4810  int c;
4811
4812  input_line_pointer = line;
4813  c = get_symbol_name (&line);
4814
4815  if (cpu == VNONE)
4816    cpu = V542;
4817  if (address_mode_needs_set)
4818    {
4819      set_address_mode (amode);
4820      address_mode_needs_set = 0;
4821    }
4822  if (cpu_needs_set)
4823    {
4824      set_cpu (cpu);
4825      cpu_needs_set = 0;
4826    }
4827  assembly_begun = 1;
4828
4829  if (is_parallel)
4830    {
4831      is_parallel = 0;
4832
4833      strcpy (insn.parmnemonic, line);
4834      lptr = input_line_pointer;
4835      *lptr = c;
4836      input_line_pointer = savedp;
4837
4838      if (tic54x_parse_parallel_insn_lastline (&insn, lptr))
4839	{
4840	  int words = build_insn (&insn);
4841
4842	  if (delay_slots != 0)
4843	    {
4844	      if (words > delay_slots)
4845		{
4846		  as_bad (_("Instruction does not fit in available delay "
4847			    "slots (%d-word insn, %d slots left)"),
4848			  words, delay_slots);
4849		  delay_slots = 0;
4850		  return;
4851		}
4852	      delay_slots -= words;
4853	    }
4854	}
4855      return;
4856    }
4857
4858  memset (&insn, 0, sizeof (insn));
4859  strcpy (insn.mnemonic, line);
4860  lptr = input_line_pointer;
4861  *lptr = c;
4862  input_line_pointer = savedp;
4863
4864  /* See if this line is part of a parallel instruction; if so, either this
4865     line or the next line will have the "||" specifier preceding the
4866     mnemonic, and we look for it in the parallel insn hash table.  */
4867  if (strstr (line, "||") != NULL || parallel_on_next_line_hint)
4868    {
4869      char *tmp = strstr (line, "||");
4870      if (tmp != NULL)
4871	*tmp = '\0';
4872
4873      if (tic54x_parse_parallel_insn_firstline (&insn, lptr))
4874	{
4875	  is_parallel = 1;
4876	  /* If the parallel part is on the same line, process it now,
4877	     otherwise let the assembler pick up the next line for us.  */
4878	  if (tmp != NULL)
4879	    {
4880	      while (ISSPACE (tmp[2]))
4881		++tmp;
4882	      md_assemble (tmp + 2);
4883	    }
4884	}
4885      else
4886	{
4887	  as_bad (_("Unrecognized parallel instruction '%s'"), line);
4888	}
4889      return;
4890    }
4891
4892  if (tic54x_parse_insn (&insn, lptr))
4893    {
4894      int words;
4895
4896      if ((insn.tm->flags & FL_LP)
4897	  && cpu != V545LP && cpu != V546LP)
4898	{
4899	  as_bad (_("Instruction '%s' requires an LP cpu version"),
4900		  insn.tm->name);
4901	  return;
4902	}
4903      if ((insn.tm->flags & FL_FAR)
4904	  && amode != far_mode)
4905	{
4906	  as_bad (_("Instruction '%s' requires far mode addressing"),
4907		  insn.tm->name);
4908	  return;
4909	}
4910
4911      words = build_insn (&insn);
4912
4913      /* Is this instruction in a delay slot?  */
4914      if (delay_slots)
4915	{
4916	  if (words > delay_slots)
4917	    {
4918	      as_warn (_("Instruction does not fit in available delay "
4919			 "slots (%d-word insn, %d slots left). "
4920			 "Resulting behavior is undefined."),
4921		       words, delay_slots);
4922	      delay_slots = 0;
4923	      return;
4924	    }
4925	  /* Branches in delay slots are not allowed.  */
4926	  if (insn.tm->flags & FL_BMASK)
4927	    {
4928	      as_warn (_("Instructions which cause PC discontinuity are not "
4929			 "allowed in a delay slot. "
4930			 "Resulting behavior is undefined."));
4931	    }
4932	  delay_slots -= words;
4933	}
4934
4935      /* Is this instruction the target of a repeat?  */
4936      if (repeat_slot)
4937	{
4938	  if (insn.tm->flags & FL_NR)
4939	    as_warn (_("'%s' is not repeatable. "
4940		       "Resulting behavior is undefined."),
4941		     insn.tm->name);
4942	  else if (insn.is_lkaddr)
4943	    as_warn (_("Instructions using long offset modifiers or absolute "
4944		       "addresses are not repeatable. "
4945		       "Resulting behavior is undefined."));
4946	  repeat_slot = 0;
4947	}
4948
4949      /* Make sure we check the target of a repeat instruction.  */
4950      if (insn.tm->flags & B_REPEAT)
4951	{
4952	  repeat_slot = 1;
4953	  /* FIXME -- warn if repeat_slot == 1 at EOF.  */
4954	}
4955      /* Make sure we check our delay slots for validity.  */
4956      if (insn.tm->flags & FL_DELAY)
4957	{
4958	  delay_slots = 2;
4959	  /* FIXME -- warn if delay_slots != 0 at EOF.  */
4960	}
4961    }
4962}
4963
4964/* Do a final adjustment on the symbol table; in this case, make sure we have
4965   a ".file" symbol.  */
4966
4967void
4968tic54x_adjust_symtab (void)
4969{
4970  if (symbol_rootP == NULL
4971      || S_GET_STORAGE_CLASS (symbol_rootP) != C_FILE)
4972    {
4973      unsigned lineno;
4974      const char * filename = as_where (&lineno);
4975      c_dot_file_symbol (filename, 0);
4976    }
4977}
4978
4979/* In order to get gas to ignore any | chars at the start of a line,
4980   this function returns true if a | is found in a line.
4981   This lets us process parallel instructions, which span two lines.  */
4982
4983int
4984tic54x_unrecognized_line (int c)
4985{
4986  return c == PARALLEL_SEPARATOR;
4987}
4988
4989/* Watch for local labels of the form $[0-9] and [_a-zA-Z][_a-zA-Z0-9]*?
4990   Encode their names so that only we see them and can map them to the
4991   appropriate places.
4992   FIXME -- obviously this isn't done yet.  These locals still show up in the
4993   symbol table.  */
4994void
4995tic54x_define_label (symbolS *sym)
4996{
4997  /* Just in case we need this later; note that this is not necessarily the
4998     same thing as line_label...
4999     When aligning or assigning labels to fields, sometimes the label is
5000     assigned other than the address at which the label appears.
5001     FIXME -- is this really needed? I think all the proper label assignment
5002     is done in tic54x_cons.  */
5003  last_label_seen = sym;
5004}
5005
5006/* Try to parse something that normal parsing failed at.  */
5007
5008symbolS *
5009tic54x_undefined_symbol (char *name)
5010{
5011  tic54x_symbol *sym;
5012
5013  /* Not sure how to handle predefined symbols.  */
5014  if ((sym = (tic54x_symbol *) hash_find (cc_hash, name)) != NULL ||
5015      (sym = (tic54x_symbol *) hash_find (cc2_hash, name)) != NULL ||
5016      (sym = (tic54x_symbol *) hash_find (cc3_hash, name)) != NULL ||
5017      (sym = (tic54x_symbol *) hash_find (misc_symbol_hash, name)) != NULL ||
5018      (sym = (tic54x_symbol *) hash_find (sbit_hash, name)) != NULL)
5019    {
5020      return symbol_new (name, reg_section,
5021			 (valueT) sym->value,
5022			 &zero_address_frag);
5023    }
5024
5025  if ((sym = (tic54x_symbol *) hash_find (reg_hash, name)) != NULL ||
5026      (sym = (tic54x_symbol *) hash_find (mmreg_hash, name)) != NULL ||
5027      !strcasecmp (name, "a") || !strcasecmp (name, "b"))
5028    {
5029      return symbol_new (name, reg_section,
5030			 (valueT) sym ? sym->value : 0,
5031			 &zero_address_frag);
5032    }
5033
5034  return NULL;
5035}
5036
5037/* Parse a name in an expression before the expression parser takes a stab at
5038   it.  */
5039
5040int
5041tic54x_parse_name (char *name ATTRIBUTE_UNUSED,
5042		   expressionS *expn ATTRIBUTE_UNUSED)
5043{
5044  return 0;
5045}
5046
5047const char *
5048md_atof (int type, char *literalP, int *sizeP)
5049{
5050  /* Target data is little-endian, but floats are stored
5051     big-"word"ian.  ugh.  */
5052  return ieee_md_atof (type, literalP, sizeP, TRUE);
5053}
5054
5055arelent *
5056tc_gen_reloc (asection *section, fixS *fixP)
5057{
5058  arelent *rel;
5059  bfd_reloc_code_real_type code = fixP->fx_r_type;
5060  asymbol *sym = symbol_get_bfdsym (fixP->fx_addsy);
5061
5062  rel = XNEW (arelent);
5063  rel->sym_ptr_ptr = XNEW (asymbol *);
5064  *rel->sym_ptr_ptr = sym;
5065  /* We assume that all rel->address are host byte offsets.  */
5066  rel->address = fixP->fx_frag->fr_address + fixP->fx_where;
5067  rel->address /= OCTETS_PER_BYTE;
5068  rel->howto = bfd_reloc_type_lookup (stdoutput, code);
5069  if (!strcmp (sym->name, section->name))
5070    rel->howto += HOWTO_BANK;
5071
5072  if (!rel->howto)
5073    {
5074      const char *name = S_GET_NAME (fixP->fx_addsy);
5075      if (name == NULL)
5076	name = "<unknown>";
5077      as_fatal ("Cannot generate relocation type for symbol %s, code %s",
5078		name, bfd_get_reloc_code_name (code));
5079      return NULL;
5080    }
5081  return rel;
5082}
5083
5084/* Handle cons expressions.  */
5085
5086void
5087tic54x_cons_fix_new (fragS *frag, int where, int octets, expressionS *expn,
5088		     bfd_reloc_code_real_type r)
5089{
5090  switch (octets)
5091    {
5092    default:
5093      as_bad (_("Unsupported relocation size %d"), octets);
5094      r = BFD_RELOC_TIC54X_16_OF_23;
5095      break;
5096    case 2:
5097      r = BFD_RELOC_TIC54X_16_OF_23;
5098      break;
5099    case 4:
5100      /* TI assembler always uses this, regardless of addressing mode.  */
5101      if (emitting_long)
5102	r = BFD_RELOC_TIC54X_23;
5103      else
5104	/* We never want to directly generate this; this is provided for
5105	   stabs support only.  */
5106	r = BFD_RELOC_32;
5107      break;
5108    }
5109  fix_new_exp (frag, where, octets, expn, 0, r);
5110}
5111
5112/* Attempt to simplify or even eliminate a fixup.
5113   To indicate that a fixup has been eliminated, set fixP->fx_done.
5114
5115   If fixp->fx_addsy is non-NULL, we'll have to generate a reloc entry.   */
5116
5117void
5118md_apply_fix (fixS *fixP, valueT *valP, segT seg ATTRIBUTE_UNUSED)
5119{
5120  char *buf = fixP->fx_where + fixP->fx_frag->fr_literal;
5121  valueT val = * valP;
5122
5123  switch (fixP->fx_r_type)
5124    {
5125    default:
5126      as_fatal ("Bad relocation type: 0x%02x", fixP->fx_r_type);
5127      return;
5128    case BFD_RELOC_TIC54X_MS7_OF_23:
5129      val = (val >> 16) & 0x7F;
5130      /* Fall through.  */
5131    case BFD_RELOC_TIC54X_16_OF_23:
5132    case BFD_RELOC_16:
5133      bfd_put_16 (stdoutput, val, buf);
5134      /* Indicate what we're actually writing, so that we don't get warnings
5135	 about exceeding available space.  */
5136      *valP = val & 0xFFFF;
5137      break;
5138    case BFD_RELOC_TIC54X_PARTLS7:
5139      bfd_put_16 (stdoutput,
5140		  (bfd_get_16 (stdoutput, buf) & 0xFF80) | (val & 0x7F),
5141		  buf);
5142      /* Indicate what we're actually writing, so that we don't get warnings
5143	 about exceeding available space.  */
5144      *valP = val & 0x7F;
5145      break;
5146    case BFD_RELOC_TIC54X_PARTMS9:
5147      /* TI assembler doesn't shift its encoding for relocatable files, and is
5148	 thus incompatible with this implementation's relocatable files.  */
5149      bfd_put_16 (stdoutput,
5150		  (bfd_get_16 (stdoutput, buf) & 0xFE00) | (val >> 7),
5151		  buf);
5152      break;
5153    case BFD_RELOC_32:
5154    case BFD_RELOC_TIC54X_23:
5155      bfd_put_32 (stdoutput,
5156		  (bfd_get_32 (stdoutput, buf) & 0xFF800000) | val,
5157		  buf);
5158      break;
5159    }
5160
5161  if (fixP->fx_addsy == NULL && fixP->fx_pcrel == 0)
5162    fixP->fx_done = 1;
5163}
5164
5165/* This is our chance to record section alignment
5166   don't need to do anything here, since BFD does the proper encoding.  */
5167
5168valueT
5169md_section_align (segT segment ATTRIBUTE_UNUSED, valueT section_size)
5170{
5171  return section_size;
5172}
5173
5174long
5175md_pcrel_from (fixS *fixP ATTRIBUTE_UNUSED)
5176{
5177  return 0;
5178}
5179
5180/* Mostly little-endian, but longwords (4 octets) get MS word stored
5181   first.  */
5182
5183void
5184tic54x_number_to_chars (char *buf, valueT val, int n)
5185{
5186  if (n != 4)
5187    number_to_chars_littleendian (buf, val, n);
5188  else
5189    {
5190      number_to_chars_littleendian (buf    , val >> 16   , 2);
5191      number_to_chars_littleendian (buf + 2, val & 0xFFFF, 2);
5192    }
5193}
5194
5195int
5196tic54x_estimate_size_before_relax (fragS *frag ATTRIBUTE_UNUSED,
5197				   segT seg ATTRIBUTE_UNUSED)
5198{
5199  return 0;
5200}
5201
5202/* We use this to handle bit allocations which we couldn't handle before due
5203   to symbols being in different frags.  return number of octets added.  */
5204
5205int
5206tic54x_relax_frag (fragS *frag, long stretch ATTRIBUTE_UNUSED)
5207{
5208  symbolS *sym = frag->fr_symbol;
5209  int growth = 0;
5210  int i;
5211
5212  if (sym != NULL)
5213    {
5214      struct bit_info *bi = (struct bit_info *) frag->fr_opcode;
5215      int bit_offset = frag_bit_offset (frag_prev (frag, bi->seg), bi->seg);
5216      int size = S_GET_VALUE (sym);
5217      fragS *prev_frag = bit_offset_frag (frag_prev (frag, bi->seg), bi->seg);
5218      int available = 16 - bit_offset;
5219
5220      if (symbol_get_frag (sym) != &zero_address_frag
5221	  || S_IS_COMMON (sym)
5222	  || !S_IS_DEFINED (sym))
5223	as_bad_where (frag->fr_file, frag->fr_line,
5224		      _("non-absolute value used with .space/.bes"));
5225
5226      if (size < 0)
5227	{
5228	  as_warn (_("negative value ignored in %s"),
5229		   bi->type == TYPE_SPACE ? ".space" :
5230		   bi->type == TYPE_BES ? ".bes" : ".field");
5231	  growth = 0;
5232	  frag->tc_frag_data = frag->fr_fix = 0;
5233	  return 0;
5234	}
5235
5236      if (bi->type == TYPE_FIELD)
5237	{
5238	  /* Bit fields of 16 or larger will have already been handled.  */
5239	  if (bit_offset != 0 && available >= size)
5240	    {
5241	      char *p = prev_frag->fr_literal;
5242
5243	      valueT value = bi->value;
5244	      value <<= available - size;
5245	      value |= ((unsigned short) p[1] << 8) | p[0];
5246	      md_number_to_chars (p, value, 2);
5247	      if ((prev_frag->tc_frag_data += size) == 16)
5248		prev_frag->tc_frag_data = 0;
5249	      if (bi->sym)
5250		symbol_set_frag (bi->sym, prev_frag);
5251	      /* This frag is no longer used.  */
5252	      growth = -frag->fr_fix;
5253	      frag->fr_fix = 0;
5254	      frag->tc_frag_data = 0;
5255	    }
5256	  else
5257	    {
5258	      char *p = frag->fr_literal;
5259
5260	      valueT value = bi->value << (16 - size);
5261	      md_number_to_chars (p, value, 2);
5262	      if ((frag->tc_frag_data = size) == 16)
5263		frag->tc_frag_data = 0;
5264	      growth = 0;
5265	    }
5266	}
5267      else
5268	{
5269	  if (bit_offset != 0 && bit_offset < 16)
5270	    {
5271	      if (available >= size)
5272		{
5273		  if ((prev_frag->tc_frag_data += size) == 16)
5274		    prev_frag->tc_frag_data = 0;
5275		  if (bi->sym)
5276		    symbol_set_frag (bi->sym, prev_frag);
5277		  /* This frag is no longer used.  */
5278		  growth = -frag->fr_fix;
5279		  frag->fr_fix = 0;
5280		  frag->tc_frag_data = 0;
5281		  goto getout;
5282		}
5283	      if (bi->type == TYPE_SPACE && bi->sym)
5284		symbol_set_frag (bi->sym, prev_frag);
5285	      size -= available;
5286	    }
5287	  growth = (size + 15) / 16 * OCTETS_PER_BYTE - frag->fr_fix;
5288	  for (i = 0; i < growth; i++)
5289	    frag->fr_literal[i] = 0;
5290	  frag->fr_fix = growth;
5291	  frag->tc_frag_data = size % 16;
5292	  /* Make sure any BES label points to the LAST word allocated.  */
5293	  if (bi->type == TYPE_BES && bi->sym)
5294	    S_SET_VALUE (bi->sym, frag->fr_fix / OCTETS_PER_BYTE - 1);
5295	}
5296    getout:
5297      frag->fr_symbol = 0;
5298      frag->fr_opcode = 0;
5299      free ((void *) bi);
5300    }
5301  return growth;
5302}
5303
5304void
5305tic54x_convert_frag (bfd *abfd ATTRIBUTE_UNUSED,
5306		     segT seg ATTRIBUTE_UNUSED,
5307		     fragS *frag)
5308{
5309  /* Offset is in bytes.  */
5310  frag->fr_offset = (frag->fr_next->fr_address
5311		     - frag->fr_address
5312		     - frag->fr_fix) / frag->fr_var;
5313  if (frag->fr_offset < 0)
5314    {
5315      as_bad_where (frag->fr_file, frag->fr_line,
5316		    _("attempt to .space/.bes backwards? (%ld)"),
5317		    (long) frag->fr_offset);
5318    }
5319  frag->fr_type = rs_space;
5320}
5321
5322/* We need to avoid having labels defined for certain directives/pseudo-ops
5323   since once the label is defined, it's in the symbol table for good.  TI
5324   syntax puts the symbol *before* the pseudo (which is kinda like MRI syntax,
5325   I guess, except I've never seen a definition of MRI syntax).
5326
5327   Don't allow labels to start with '.'  */
5328
5329int
5330tic54x_start_label (int nul_char, int next_char)
5331{
5332  char *rest;
5333
5334  /* If within .struct/.union, no auto line labels, please.  */
5335  if (current_stag != NULL)
5336    return 0;
5337
5338  /* Disallow labels starting with "."  */
5339  if (next_char != ':')
5340    {
5341      char *label = input_line_pointer;
5342
5343      while (!is_end_of_line[(int) label[-1]])
5344	--label;
5345      if (*label == '.')
5346	{
5347	  as_bad (_("Invalid label '%s'"), label);
5348	  return 0;
5349	}
5350    }
5351
5352  if (is_end_of_line[(int) next_char])
5353    return 1;
5354
5355  rest = input_line_pointer;
5356  if (nul_char == '"')
5357    ++rest;
5358  while (ISSPACE (next_char))
5359    next_char = *++rest;
5360  if (next_char != '.')
5361    return 1;
5362
5363  /* Don't let colon () define a label for any of these...  */
5364  return ((strncasecmp (rest, ".tag", 4) != 0 || !ISSPACE (rest[4]))
5365	  && (strncasecmp (rest, ".struct", 7) != 0 || !ISSPACE (rest[7]))
5366	  && (strncasecmp (rest, ".union", 6) != 0 || !ISSPACE (rest[6]))
5367	  && (strncasecmp (rest, ".macro", 6) != 0 || !ISSPACE (rest[6]))
5368	  && (strncasecmp (rest, ".set", 4) != 0 || !ISSPACE (rest[4]))
5369	  && (strncasecmp (rest, ".equ", 4) != 0 || !ISSPACE (rest[4])));
5370}
5371