obj-aout.c revision 77298
1245431Sdim/* a.out object file format
2234285Sdim   Copyright (C) 1989, 90, 91, 92, 93, 94, 95, 96, 97, 98, 99, 2000
3234285Sdim   Free Software Foundation, Inc.
4234285Sdim
5234285SdimThis file is part of GAS, the GNU Assembler.
6234285Sdim
7234285SdimGAS is free software; you can redistribute it and/or modify
8234285Sdimit under the terms of the GNU General Public License as
9234285Sdimpublished by the Free Software Foundation; either version 2,
10234285Sdimor (at your option) any later version.
11234285Sdim
12234285SdimGAS is distributed in the hope that it will be useful, but
13234285SdimWITHOUT ANY WARRANTY; without even the implied warranty of
14234285SdimMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See
15252723Sdimthe GNU General Public License for more details.
16234285Sdim
17252723SdimYou should have received a copy of the GNU General Public License
18252723Sdimalong with GAS; see the file COPYING.  If not, write to the Free
19252723SdimSoftware Foundation, 59 Temple Place - Suite 330, Boston, MA
20234285Sdim02111-1307, USA.  */
21234285Sdim
22234285Sdim#define OBJ_HEADER "obj-aout.h"
23234285Sdim
24252723Sdim#include "as.h"
25252723Sdim#ifdef BFD_ASSEMBLER
26252723Sdim#undef NO_RELOC
27252723Sdim#include "aout/aout64.h"
28252723Sdim#endif
29234285Sdim#include "obstack.h"
30234285Sdim
31234285Sdim#ifndef BFD_ASSEMBLER
32234285Sdim/* in: segT   out: N_TYPE bits */
33252723Sdimconst short seg_N_TYPE[] =
34252723Sdim{
35252723Sdim  N_ABS,
36234285Sdim  N_TEXT,
37234285Sdim  N_DATA,
38234285Sdim  N_BSS,
39234285Sdim  N_UNDF,			/* unknown */
40234285Sdim  N_UNDF,			/* error */
41234285Sdim  N_UNDF,			/* expression */
42234285Sdim  N_UNDF,			/* debug */
43234285Sdim  N_UNDF,			/* ntv */
44234285Sdim  N_UNDF,			/* ptv */
45234285Sdim  N_REGISTER,			/* register */
46234285Sdim};
47234285Sdim
48234285Sdimconst segT N_TYPE_seg[N_TYPE + 2] =
49234285Sdim{				/* N_TYPE == 0x1E = 32-2 */
50234285Sdim  SEG_UNKNOWN,			/* N_UNDF == 0 */
51234285Sdim  SEG_GOOF,
52252723Sdim  SEG_ABSOLUTE,			/* N_ABS == 2 */
53252723Sdim  SEG_GOOF,
54234285Sdim  SEG_TEXT,			/* N_TEXT == 4 */
55234285Sdim  SEG_GOOF,
56234285Sdim  SEG_DATA,			/* N_DATA == 6 */
57234285Sdim  SEG_GOOF,
58234285Sdim  SEG_BSS,			/* N_BSS == 8 */
59252723Sdim  SEG_GOOF,
60234285Sdim  SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF,
61234285Sdim  SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF,
62234285Sdim  SEG_GOOF, SEG_GOOF, SEG_GOOF, SEG_GOOF,
63234285Sdim  SEG_REGISTER,			/* dummy N_REGISTER for regs = 30 */
64234285Sdim  SEG_GOOF,
65234285Sdim};
66234285Sdim#endif
67234285Sdim
68234285Sdimstatic void obj_aout_line PARAMS ((int));
69234285Sdimstatic void obj_aout_weak PARAMS ((int));
70234285Sdimstatic void obj_aout_type PARAMS ((int));
71234285Sdim
72234285Sdimconst pseudo_typeS aout_pseudo_table[] =
73234285Sdim{
74234285Sdim  {"line", obj_aout_line, 0},	/* source code line number */
75234285Sdim  {"ln", obj_aout_line, 0},	/* coff line number that we use anyway */
76234285Sdim
77234285Sdim  {"weak", obj_aout_weak, 0},	/* mark symbol as weak.  */
78234285Sdim
79234285Sdim  {"type", obj_aout_type, 0},
80234285Sdim
81234285Sdim  /* coff debug pseudos (ignored) */
82234285Sdim  {"def", s_ignore, 0},
83234285Sdim  {"dim", s_ignore, 0},
84234285Sdim  {"endef", s_ignore, 0},
85234285Sdim  {"ident", s_ignore, 0},
86252723Sdim  {"line", s_ignore, 0},
87252723Sdim  {"ln", s_ignore, 0},
88234285Sdim  {"scl", s_ignore, 0},
89234285Sdim  {"size", s_ignore, 0},
90  {"tag", s_ignore, 0},
91  {"val", s_ignore, 0},
92  {"version", s_ignore, 0},
93
94  {"optim", s_ignore, 0},	/* For sun386i cc (?) */
95
96  /* other stuff */
97  {"ABORT", s_abort, 0},
98
99  {NULL, NULL, 0}		/* end sentinel */
100};				/* aout_pseudo_table */
101
102#ifdef BFD_ASSEMBLER
103
104void
105obj_aout_frob_symbol (sym, punt)
106     symbolS *sym;
107     int *punt ATTRIBUTE_UNUSED;
108{
109  flagword flags;
110  asection *sec;
111  int desc, type, other;
112
113  flags = symbol_get_bfdsym (sym)->flags;
114  desc = aout_symbol (symbol_get_bfdsym (sym))->desc;
115  type = aout_symbol (symbol_get_bfdsym (sym))->type;
116  other = aout_symbol (symbol_get_bfdsym (sym))->other;
117  sec = S_GET_SEGMENT (sym);
118
119  /* Only frob simple symbols this way right now.  */
120  if (! (type & ~ (N_TYPE | N_EXT)))
121    {
122      if (type == (N_UNDF | N_EXT)
123	  && sec == &bfd_abs_section)
124	{
125	  sec = bfd_und_section_ptr;
126	  S_SET_SEGMENT (sym, sec);
127	}
128
129      if ((type & N_TYPE) != N_INDR
130	  && (type & N_TYPE) != N_SETA
131	  && (type & N_TYPE) != N_SETT
132	  && (type & N_TYPE) != N_SETD
133	  && (type & N_TYPE) != N_SETB
134	  && type != N_WARNING
135	  && (sec == &bfd_abs_section
136	      || sec == &bfd_und_section))
137	return;
138      if (flags & BSF_EXPORT)
139	type |= N_EXT;
140
141      switch (type & N_TYPE)
142	{
143	case N_SETA:
144	case N_SETT:
145	case N_SETD:
146	case N_SETB:
147	  /* Set the debugging flag for constructor symbols so that
148	     BFD leaves them alone.  */
149	  symbol_get_bfdsym (sym)->flags |= BSF_DEBUGGING;
150
151	  /* You can't put a common symbol in a set.  The way a set
152	     element works is that the symbol has a definition and a
153	     name, and the linker adds the definition to the set of
154	     that name.  That does not work for a common symbol,
155	     because the linker can't tell which common symbol the
156	     user means.  FIXME: Using as_bad here may be
157	     inappropriate, since the user may want to force a
158	     particular type without regard to the semantics of sets;
159	     on the other hand, we certainly don't want anybody to be
160	     mislead into thinking that their code will work.  */
161	  if (S_IS_COMMON (sym))
162	    as_bad (_("Attempt to put a common symbol into set %s"),
163		    S_GET_NAME (sym));
164	  /* Similarly, you can't put an undefined symbol in a set.  */
165	  else if (! S_IS_DEFINED (sym))
166	    as_bad (_("Attempt to put an undefined symbol into set %s"),
167		    S_GET_NAME (sym));
168
169	  break;
170	case N_INDR:
171	  /* Put indirect symbols in the indirect section.  */
172	  S_SET_SEGMENT (sym, bfd_ind_section_ptr);
173	  symbol_get_bfdsym (sym)->flags |= BSF_INDIRECT;
174	  if (type & N_EXT)
175	    {
176	      symbol_get_bfdsym (sym)->flags |= BSF_EXPORT;
177	      symbol_get_bfdsym (sym)->flags &=~ BSF_LOCAL;
178	    }
179	  break;
180	case N_WARNING:
181	  /* Mark warning symbols.  */
182	  symbol_get_bfdsym (sym)->flags |= BSF_WARNING;
183	  break;
184	}
185    }
186  else
187    {
188      symbol_get_bfdsym (sym)->flags |= BSF_DEBUGGING;
189    }
190
191  aout_symbol (symbol_get_bfdsym (sym))->type = type;
192
193  /* Double check weak symbols.  */
194  if (S_IS_WEAK (sym))
195    {
196      if (S_IS_COMMON (sym))
197	as_bad (_("Symbol `%s' can not be both weak and common"),
198		S_GET_NAME (sym));
199    }
200}
201
202void
203obj_aout_frob_file ()
204{
205  /* Relocation processing may require knowing the VMAs of the sections.
206     Since writing to a section will cause the BFD back end to compute the
207     VMAs, fake it out here....  */
208  bfd_byte b = 0;
209  boolean x = true;
210  if (bfd_section_size (stdoutput, text_section) != 0)
211    {
212      x = bfd_set_section_contents (stdoutput, text_section, &b, (file_ptr) 0,
213				    (bfd_size_type) 1);
214    }
215  else if (bfd_section_size (stdoutput, data_section) != 0)
216    {
217      x = bfd_set_section_contents (stdoutput, data_section, &b, (file_ptr) 0,
218				    (bfd_size_type) 1);
219    }
220  assert (x == true);
221}
222
223#else /* ! BFD_ASSEMBLER */
224
225/* Relocation.  */
226
227/*
228 *		emit_relocations()
229 *
230 * Crawl along a fixS chain. Emit the segment's relocations.
231 */
232void
233obj_emit_relocations (where, fixP, segment_address_in_file)
234     char **where;
235     fixS *fixP;		/* Fixup chain for this segment.  */
236     relax_addressT segment_address_in_file;
237{
238  for (; fixP; fixP = fixP->fx_next)
239    if (fixP->fx_done == 0)
240      {
241	symbolS *sym;
242
243	sym = fixP->fx_addsy;
244	while (sym->sy_value.X_op == O_symbol
245	       && (! S_IS_DEFINED (sym) || S_IS_COMMON (sym)))
246	  sym = sym->sy_value.X_add_symbol;
247	fixP->fx_addsy = sym;
248
249	if (! sym->sy_resolved && ! S_IS_DEFINED (sym))
250	  {
251	    char *file;
252	    unsigned int line;
253
254	    if (expr_symbol_where (sym, &file, &line))
255	      as_bad_where (file, line, _("unresolved relocation"));
256	    else
257	      as_bad (_("bad relocation: symbol `%s' not in symbol table"),
258		      S_GET_NAME (sym));
259	  }
260
261	tc_aout_fix_to_chars (*where, fixP, segment_address_in_file);
262	*where += md_reloc_size;
263      }
264}
265
266#ifndef obj_header_append
267/* Aout file generation & utilities */
268void
269obj_header_append (where, headers)
270     char **where;
271     object_headers *headers;
272{
273  tc_headers_hook (headers);
274
275#ifdef CROSS_COMPILE
276  md_number_to_chars (*where, headers->header.a_info, sizeof (headers->header.a_info));
277  *where += sizeof (headers->header.a_info);
278  md_number_to_chars (*where, headers->header.a_text, sizeof (headers->header.a_text));
279  *where += sizeof (headers->header.a_text);
280  md_number_to_chars (*where, headers->header.a_data, sizeof (headers->header.a_data));
281  *where += sizeof (headers->header.a_data);
282  md_number_to_chars (*where, headers->header.a_bss, sizeof (headers->header.a_bss));
283  *where += sizeof (headers->header.a_bss);
284  md_number_to_chars (*where, headers->header.a_syms, sizeof (headers->header.a_syms));
285  *where += sizeof (headers->header.a_syms);
286  md_number_to_chars (*where, headers->header.a_entry, sizeof (headers->header.a_entry));
287  *where += sizeof (headers->header.a_entry);
288  md_number_to_chars (*where, headers->header.a_trsize, sizeof (headers->header.a_trsize));
289  *where += sizeof (headers->header.a_trsize);
290  md_number_to_chars (*where, headers->header.a_drsize, sizeof (headers->header.a_drsize));
291  *where += sizeof (headers->header.a_drsize);
292
293#else /* CROSS_COMPILE */
294
295  append (where, (char *) &headers->header, sizeof (headers->header));
296#endif /* CROSS_COMPILE */
297
298}
299#endif /* ! defined (obj_header_append) */
300
301void
302obj_symbol_to_chars (where, symbolP)
303     char **where;
304     symbolS *symbolP;
305{
306  md_number_to_chars ((char *) &(S_GET_OFFSET (symbolP)), S_GET_OFFSET (symbolP), sizeof (S_GET_OFFSET (symbolP)));
307  md_number_to_chars ((char *) &(S_GET_DESC (symbolP)), S_GET_DESC (symbolP), sizeof (S_GET_DESC (symbolP)));
308  md_number_to_chars ((char *) &(symbolP->sy_symbol.n_value), S_GET_VALUE (symbolP), sizeof (symbolP->sy_symbol.n_value));
309
310  append (where, (char *) &symbolP->sy_symbol, sizeof (obj_symbol_type));
311}
312
313void
314obj_emit_symbols (where, symbol_rootP)
315     char **where;
316     symbolS *symbol_rootP;
317{
318  symbolS *symbolP;
319
320  /* Emit all symbols left in the symbol chain.  */
321  for (symbolP = symbol_rootP; symbolP; symbolP = symbol_next (symbolP))
322    {
323      /* Used to save the offset of the name. It is used to point
324	 to the string in memory but must be a file offset.  */
325      register char *temp;
326
327      temp = S_GET_NAME (symbolP);
328      S_SET_OFFSET (symbolP, symbolP->sy_name_offset);
329
330      /* Any symbol still undefined and is not a dbg symbol is made N_EXT.  */
331      if (!S_IS_DEBUG (symbolP) && !S_IS_DEFINED (symbolP))
332	S_SET_EXTERNAL (symbolP);
333
334      /* Adjust the type of a weak symbol.  */
335      if (S_GET_WEAK (symbolP))
336	{
337	  switch (S_GET_TYPE (symbolP))
338	    {
339	    case N_UNDF: S_SET_TYPE (symbolP, N_WEAKU); break;
340	    case N_ABS:	 S_SET_TYPE (symbolP, N_WEAKA); break;
341	    case N_TEXT: S_SET_TYPE (symbolP, N_WEAKT); break;
342	    case N_DATA: S_SET_TYPE (symbolP, N_WEAKD); break;
343	    case N_BSS:  S_SET_TYPE (symbolP, N_WEAKB); break;
344	    default: as_bad (_("%s: bad type for weak symbol"), temp); break;
345	    }
346	}
347
348      obj_symbol_to_chars (where, symbolP);
349      S_SET_NAME (symbolP, temp);
350    }
351}
352
353#endif /* ! BFD_ASSEMBLER */
354
355static void
356obj_aout_line (ignore)
357     int ignore ATTRIBUTE_UNUSED;
358{
359  /* Assume delimiter is part of expression.
360     BSD4.2 as fails with delightful bug, so we
361     are not being incompatible here.  */
362  new_logical_line ((char *) NULL, (int) (get_absolute_expression ()));
363  demand_empty_rest_of_line ();
364}				/* obj_aout_line() */
365
366/* Handle .weak.  This is a GNU extension.  */
367
368static void
369obj_aout_weak (ignore)
370     int ignore ATTRIBUTE_UNUSED;
371{
372  char *name;
373  int c;
374  symbolS *symbolP;
375
376  do
377    {
378      name = input_line_pointer;
379      c = get_symbol_end ();
380      symbolP = symbol_find_or_make (name);
381      *input_line_pointer = c;
382      SKIP_WHITESPACE ();
383      S_SET_WEAK (symbolP);
384      if (c == ',')
385	{
386	  input_line_pointer++;
387	  SKIP_WHITESPACE ();
388	  if (*input_line_pointer == '\n')
389	    c = '\n';
390	}
391    }
392  while (c == ',');
393  demand_empty_rest_of_line ();
394}
395
396/* Handle .type.  On {Net,Open}BSD, this is used to set the n_other field,
397   which is then apparently used when doing dynamic linking.  Older
398   versions of gas ignored the .type pseudo-op, so we also ignore it if
399   we can't parse it.  */
400
401static void
402obj_aout_type (ignore)
403     int ignore ATTRIBUTE_UNUSED;
404{
405  char *name;
406  int c;
407  symbolS *sym;
408
409  name = input_line_pointer;
410  c = get_symbol_end ();
411  sym = symbol_find_or_make (name);
412  *input_line_pointer = c;
413  SKIP_WHITESPACE ();
414  if (*input_line_pointer == ',')
415    {
416      ++input_line_pointer;
417      SKIP_WHITESPACE ();
418      if (*input_line_pointer == '@')
419	{
420	  ++input_line_pointer;
421	  if (strncmp (input_line_pointer, "object", 6) == 0)
422#ifdef BFD_ASSEMBLER
423	    aout_symbol (symbol_get_bfdsym (sym))->other = 1;
424#else
425	  S_SET_OTHER (sym, 1);
426#endif
427	  else if (strncmp (input_line_pointer, "function", 8) == 0)
428#ifdef BFD_ASSEMBLER
429	    aout_symbol (symbol_get_bfdsym (sym))->other = 2;
430#else
431	  S_SET_OTHER (sym, 2);
432#endif
433	}
434    }
435
436  /* Ignore everything else on the line.  */
437  s_ignore (0);
438}
439
440#ifndef BFD_ASSEMBLER
441
442void
443obj_crawl_symbol_chain (headers)
444     object_headers *headers;
445{
446  symbolS *symbolP;
447  symbolS **symbolPP;
448  int symbol_number = 0;
449
450  tc_crawl_symbol_chain (headers);
451
452  symbolPP = &symbol_rootP;	/*->last symbol chain link.  */
453  while ((symbolP = *symbolPP) != NULL)
454    {
455      if (symbolP->sy_mri_common)
456	{
457	  if (S_IS_EXTERNAL (symbolP))
458	    as_bad (_("%s: global symbols not supported in common sections"),
459		    S_GET_NAME (symbolP));
460	  *symbolPP = symbol_next (symbolP);
461	  continue;
462	}
463
464      if (flag_readonly_data_in_text && (S_GET_SEGMENT (symbolP) == SEG_DATA))
465	{
466	  S_SET_SEGMENT (symbolP, SEG_TEXT);
467	}			/* if pusing data into text */
468
469      resolve_symbol_value (symbolP, 1);
470
471      /* Skip symbols which were equated to undefined or common
472	 symbols.  */
473      if (symbolP->sy_value.X_op == O_symbol
474	  && (! S_IS_DEFINED (symbolP) || S_IS_COMMON (symbolP)))
475	{
476	  *symbolPP = symbol_next (symbolP);
477	  continue;
478	}
479
480      /* OK, here is how we decide which symbols go out into the brave
481	 new symtab.  Symbols that do are:
482
483	 * symbols with no name (stabd's?)
484	 * symbols with debug info in their N_TYPE
485
486	 Symbols that don't are:
487	 * symbols that are registers
488	 * symbols with \1 as their 3rd character (numeric labels)
489	 * "local labels" as defined by S_LOCAL_NAME(name) if the -L
490	 switch was passed to gas.
491
492	 All other symbols are output.  We complain if a deleted
493	 symbol was marked external.  */
494
495      if (!S_IS_REGISTER (symbolP)
496	  && (!S_GET_NAME (symbolP)
497	      || S_IS_DEBUG (symbolP)
498	      || !S_IS_DEFINED (symbolP)
499	      || S_IS_EXTERNAL (symbolP)
500	      || (S_GET_NAME (symbolP)[0] != '\001'
501		  && (flag_keep_locals || !S_LOCAL_NAME (symbolP)))))
502	{
503	  symbolP->sy_number = symbol_number++;
504
505	  /* The + 1 after strlen account for the \0 at the
506			   end of each string */
507	  if (!S_IS_STABD (symbolP))
508	    {
509	      /* Ordinary case.  */
510	      symbolP->sy_name_offset = string_byte_count;
511	      string_byte_count += strlen (S_GET_NAME (symbolP)) + 1;
512	    }
513	  else			/* .Stabd case.  */
514	    symbolP->sy_name_offset = 0;
515	  symbolPP = &symbolP->sy_next;
516	}
517      else
518	{
519	  if (S_IS_EXTERNAL (symbolP) || !S_IS_DEFINED (symbolP))
520	    /* This warning should never get triggered any more.
521	       Well, maybe if you're doing twisted things with
522	       register names...  */
523	    {
524	      as_bad (_("Local symbol %s never defined."), decode_local_label_name (S_GET_NAME (symbolP)));
525	    }			/* oops.  */
526
527	  /* Unhook it from the chain */
528	  *symbolPP = symbol_next (symbolP);
529	}			/* if this symbol should be in the output */
530    }				/* for each symbol */
531
532  H_SET_SYMBOL_TABLE_SIZE (headers, symbol_number);
533}
534
535/*
536 * Find strings by crawling along symbol table chain.
537 */
538
539void
540obj_emit_strings (where)
541     char **where;
542{
543  symbolS *symbolP;
544
545#ifdef CROSS_COMPILE
546  /* Gotta do md_ byte-ordering stuff for string_byte_count first - KWK */
547  md_number_to_chars (*where, string_byte_count, sizeof (string_byte_count));
548  *where += sizeof (string_byte_count);
549#else /* CROSS_COMPILE */
550  append (where, (char *) &string_byte_count, (unsigned long) sizeof (string_byte_count));
551#endif /* CROSS_COMPILE */
552
553  for (symbolP = symbol_rootP; symbolP; symbolP = symbol_next (symbolP))
554    {
555      if (S_GET_NAME (symbolP))
556	append (&next_object_file_charP, S_GET_NAME (symbolP),
557		(unsigned long) (strlen (S_GET_NAME (symbolP)) + 1));
558    }				/* walk symbol chain */
559}
560
561#ifndef AOUT_VERSION
562#define AOUT_VERSION 0
563#endif
564
565void
566obj_pre_write_hook (headers)
567     object_headers *headers;
568{
569  H_SET_DYNAMIC (headers, 0);
570  H_SET_VERSION (headers, AOUT_VERSION);
571  H_SET_MACHTYPE (headers, AOUT_MACHTYPE);
572  tc_aout_pre_write_hook (headers);
573}
574
575void
576s_sect ()
577{
578  /* Strip out the section name */
579  char *section_name;
580  char *section_name_end;
581  char c;
582
583  unsigned int len;
584  unsigned int exp;
585  char *save;
586
587  section_name = input_line_pointer;
588  c = get_symbol_end ();
589  section_name_end = input_line_pointer;
590
591  len = section_name_end - section_name;
592  input_line_pointer++;
593  save = input_line_pointer;
594
595  SKIP_WHITESPACE ();
596  if (c == ',')
597    {
598      exp = get_absolute_expression ();
599    }
600  else if (*input_line_pointer == ',')
601    {
602      input_line_pointer++;
603      exp = get_absolute_expression ();
604    }
605  else
606    {
607      input_line_pointer = save;
608      exp = 0;
609    }
610  if (exp >= 1000)
611    {
612      as_bad (_("subsegment index too high"));
613    }
614
615  if (strcmp (section_name, ".text") == 0)
616    {
617      subseg_set (SEG_TEXT, (subsegT) exp);
618    }
619
620  if (strcmp (section_name, ".data") == 0)
621    {
622      if (flag_readonly_data_in_text)
623	subseg_set (SEG_TEXT, (subsegT) exp + 1000);
624      else
625	subseg_set (SEG_DATA, (subsegT) exp);
626    }
627
628  *section_name_end = c;
629}
630
631#endif /* ! BFD_ASSEMBLER */
632
633#ifdef BFD_ASSEMBLER
634
635/* Support for an AOUT emulation.  */
636
637static void aout_pop_insert PARAMS ((void));
638static int obj_aout_s_get_other PARAMS ((symbolS *));
639static void obj_aout_s_set_other PARAMS ((symbolS *, int));
640static int obj_aout_s_get_desc PARAMS ((symbolS *));
641static void obj_aout_s_set_desc PARAMS ((symbolS *, int));
642static int obj_aout_s_get_type PARAMS ((symbolS *));
643static void obj_aout_s_set_type PARAMS ((symbolS *, int));
644static int obj_aout_separate_stab_sections PARAMS ((void));
645static int obj_aout_sec_sym_ok_for_reloc PARAMS ((asection *));
646static void obj_aout_process_stab PARAMS ((segT, int, const char *, int, int, int));
647
648static void
649aout_pop_insert ()
650{
651  pop_insert (aout_pseudo_table);
652}
653
654static int
655obj_aout_s_get_other (sym)
656     symbolS *sym;
657{
658  return aout_symbol (symbol_get_bfdsym (sym))->other;
659}
660
661static void
662obj_aout_s_set_other (sym, o)
663     symbolS *sym;
664     int o;
665{
666  aout_symbol (symbol_get_bfdsym (sym))->other = o;
667}
668
669static int
670obj_aout_sec_sym_ok_for_reloc (sec)
671     asection *sec ATTRIBUTE_UNUSED;
672{
673  return obj_sec_sym_ok_for_reloc (sec);
674}
675
676static void
677obj_aout_process_stab (seg, w, s, t, o, d)
678     segT seg ATTRIBUTE_UNUSED;
679     int w;
680     const char *s;
681     int t;
682     int o;
683     int d;
684{
685  aout_process_stab (w, s, t, o, d);
686}
687
688static int
689obj_aout_s_get_desc (sym)
690     symbolS *sym;
691{
692  return aout_symbol (symbol_get_bfdsym (sym))->desc;
693}
694
695static void
696obj_aout_s_set_desc (sym, d)
697     symbolS *sym;
698     int d;
699{
700  aout_symbol (symbol_get_bfdsym (sym))->desc = d;
701}
702
703static int
704obj_aout_s_get_type (sym)
705     symbolS *sym;
706{
707  return aout_symbol (symbol_get_bfdsym (sym))->type;
708}
709
710static void
711obj_aout_s_set_type (sym, t)
712     symbolS *sym;
713     int t;
714{
715  aout_symbol (symbol_get_bfdsym (sym))->type = t;
716}
717
718static int
719obj_aout_separate_stab_sections ()
720{
721  return 0;
722}
723
724/* When changed, make sure these table entries match the single-format
725   definitions in obj-aout.h.  */
726const struct format_ops aout_format_ops =
727{
728  bfd_target_aout_flavour,
729  1,	/* dfl_leading_underscore */
730  0,	/* emit_section_symbols */
731  0,	/* begin */
732  0,	/* app_file */
733  obj_aout_frob_symbol,
734  obj_aout_frob_file,
735  0,	/* frob_file_before_adjust */
736  0,	/* frob_file_after_relocs */
737  0,	/* s_get_size */
738  0,	/* s_set_size */
739  0,	/* s_get_align */
740  0,	/* s_set_align */
741  obj_aout_s_get_other,
742  obj_aout_s_set_other,
743  obj_aout_s_get_desc,
744  obj_aout_s_set_desc,
745  obj_aout_s_get_type,
746  obj_aout_s_set_type,
747  0,	/* copy_symbol_attributes */
748  0,	/* generate_asm_lineno */
749  obj_aout_process_stab,
750  obj_aout_separate_stab_sections,
751  0,	/* init_stab_section */
752  obj_aout_sec_sym_ok_for_reloc,
753  aout_pop_insert,
754  0,	/* ecoff_set_ext */
755  0,	/* read_begin_hook */
756  0 	/* symbol_new_hook */
757};
758#endif BFD_ASSEMBLER
759