1/* BFD back-end for PDP-11 a.out binaries.
2   Copyright 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2009, 2010
3   Free Software Foundation, Inc.
4
5   This file is part of BFD, the Binary File Descriptor library.
6
7   This program 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 of the License, or
10   (at your option) any later version.
11
12   This program 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 this program; if not, write to the Free Software
19   Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
20   MA 02110-1301, USA. */
21
22
23/* BFD backend for PDP-11, running 2.11BSD in particular.
24
25   This file was hacked up by looking hard at the existing vaxnetbsd
26   back end and the header files in 2.11BSD.
27
28   TODO
29   * support for V7 file formats
30   * support for overlay object files (see 2.11 a.out(5))
31   * support for old and very old archives
32   (see 2.11 ar(5), historical section)
33
34   Search for TODO to find other areas needing more work.  */
35
36#define	BYTES_IN_WORD	2
37#define	BYTES_IN_LONG	4
38#define ARCH_SIZE	16
39#undef TARGET_IS_BIG_ENDIAN_P
40
41#define	TARGET_PAGE_SIZE	1024
42#define	SEGMENT__SIZE	TARGET_PAGE_SIZE
43
44#define	DEFAULT_ARCH	bfd_arch_pdp11
45#define	DEFAULT_MID 	M_PDP11
46
47/* Do not "beautify" the CONCAT* macro args.  Traditional C will not
48   remove whitespace added here, and thus will fail to concatenate
49   the tokens.  */
50#define MY(OP) CONCAT2 (pdp11_aout_,OP)
51
52/* This needs to start with a.out so GDB knows it is an a.out variant.  */
53#define TARGETNAME "a.out-pdp11"
54
55/* This is the normal load address for executables.  */
56#define TEXT_START_ADDR		0
57
58/* The header is not included in the text segment.  */
59#define N_HEADER_IN_TEXT(x)	0
60
61/* There is no flags field.  */
62#define N_FLAGS(exec)		0
63
64#define N_SET_FLAGS(exec, flags) do { } while (0)
65#define N_BADMAG(x) (N_MAGIC(x) != OMAGIC	\
66		     && N_MAGIC(x) != NMAGIC	\
67		     && N_MAGIC(x) != ZMAGIC)
68
69#include "sysdep.h"
70#include "bfd.h"
71
72#define external_exec pdp11_external_exec
73struct pdp11_external_exec
74{
75  bfd_byte e_info[2];		/* Magic number.  */
76  bfd_byte e_text[2];		/* Length of text section in bytes.  */
77  bfd_byte e_data[2];		/* Length of data section in bytes.  */
78  bfd_byte e_bss[2];		/* Length of bss area in bytes.  */
79  bfd_byte e_syms[2];		/* Length of symbol table in bytes.  */
80  bfd_byte e_entry[2];		/* Start address.  */
81  bfd_byte e_unused[2];		/* Not used.  */
82  bfd_byte e_flag[2];		/* Relocation info stripped.  */
83  bfd_byte e_relocatable; 	/* Ugly hack.  */
84};
85
86#define	EXEC_BYTES_SIZE	(8 * 2)
87
88#define	A_MAGIC1	OMAGIC
89#define OMAGIC		0407	/* ...object file or impure executable.  */
90#define	A_MAGIC2	NMAGIC
91#define NMAGIC		0410	/* Pure executable.  */
92#define ZMAGIC		0413	/* Demand-paged executable.  */
93#define	A_MAGIC3	0411	/* Separated I&D.  */
94#define	A_MAGIC4	0405	/* Overlay.  */
95#define	A_MAGIC5	0430	/* Auto-overlay (nonseparate).  */
96#define	A_MAGIC6	0431	/* Auto-overlay (separate).  */
97#define QMAGIC		0
98#define BMAGIC		0
99
100#define A_FLAG_RELOC_STRIPPED	0x0001
101
102#define external_nlist pdp11_external_nlist
103struct pdp11_external_nlist
104{
105  bfd_byte e_unused[2];		/* Unused.  */
106  bfd_byte e_strx[2];		/* Index into string table of name.  */
107  bfd_byte e_type[1];		/* Type of symbol.  */
108  bfd_byte e_ovly[1];		/* Overlay number.  */
109  bfd_byte e_value[2];		/* Value of symbol.  */
110};
111
112#define	EXTERNAL_NLIST_SIZE	8
113
114#define N_TXTOFF(x)	(EXEC_BYTES_SIZE)
115#define N_DATOFF(x)	(N_TXTOFF(x) + (x).a_text)
116#define N_TRELOFF(x)	(N_DATOFF(x) + (x).a_data)
117#define N_DRELOFF(x)	(N_TRELOFF(x) + (x).a_trsize)
118#define N_SYMOFF(x)	(N_DRELOFF(x) + (x).a_drsize)
119#define N_STROFF(x)	(N_SYMOFF(x) + (x).a_syms)
120
121#define WRITE_HEADERS(abfd, execp) pdp11_aout_write_headers (abfd, execp)
122
123#include "libbfd.h"
124#include "libaout.h"
125
126#define SWAP_MAGIC(ext) bfd_getl16 (ext)
127
128#define MY_entry_is_text_address 1
129
130#define MY_write_object_contents MY(write_object_contents)
131static bfd_boolean MY(write_object_contents) (bfd *);
132#define MY_text_includes_header 1
133
134#define MY_BFD_TARGET
135
136#include "aout-target.h"
137
138/* Start of modified aoutx.h.  */
139#define KEEPIT udata.i
140
141#include <string.h>		/* For strchr and friends.  */
142#include "bfd.h"
143#include "sysdep.h"
144#include "safe-ctype.h"
145#include "bfdlink.h"
146
147#include "libaout.h"
148#include "aout/aout64.h"
149#include "aout/stab_gnu.h"
150#include "aout/ar.h"
151
152#undef N_TYPE
153#undef N_UNDF
154#undef N_ABS
155#undef N_TEXT
156#undef N_DATA
157#undef N_BSS
158#undef N_REG
159#undef N_FN
160#undef N_EXT
161#define N_TYPE		0x1f	/* Type mask.  */
162#define N_UNDF		0x00	/* Undefined.  */
163#define N_ABS		0x01	/* Absolute.  */
164#define N_TEXT		0x02	/* Text segment.  */
165#define N_DATA		0x03	/* Data segment.  */
166#define N_BSS		0x04	/* Bss segment.  */
167#define N_REG		0x14	/* Register symbol.  */
168#define N_FN		0x1f	/* File name.  */
169#define N_EXT		0x20	/* External flag.  */
170
171#define RELOC_SIZE 2
172
173#define RELFLG		0x0001	/* PC-relative flag.  */
174#define RTYPE		0x000e	/* Type mask.  */
175#define RIDXMASK	0xfff0	/* Index mask.  */
176
177#define RABS		0x00	/* Absolute.  */
178#define RTEXT		0x02	/* Text.  */
179#define RDATA		0x04	/* Data.  */
180#define RBSS		0x06	/* Bss.  */
181#define REXT		0x08	/* External.  */
182
183#define RINDEX(x)	(((x) & 0xfff0) >> 4)
184
185#ifndef MY_final_link_relocate
186#define MY_final_link_relocate _bfd_final_link_relocate
187#endif
188
189#ifndef MY_relocate_contents
190#define MY_relocate_contents _bfd_relocate_contents
191#endif
192
193/* A hash table used for header files with N_BINCL entries.  */
194
195struct aout_link_includes_table
196{
197  struct bfd_hash_table root;
198};
199
200/* A linked list of totals that we have found for a particular header
201   file.  */
202
203struct aout_link_includes_totals
204{
205  struct aout_link_includes_totals *next;
206  bfd_vma total;
207};
208
209/* An entry in the header file hash table.  */
210
211struct aout_link_includes_entry
212{
213  struct bfd_hash_entry root;
214  /* List of totals we have found for this file.  */
215  struct aout_link_includes_totals *totals;
216};
217
218/* During the final link step we need to pass around a bunch of
219   information, so we do it in an instance of this structure.  */
220
221struct aout_final_link_info
222{
223  /* General link information.  */
224  struct bfd_link_info *info;
225  /* Output bfd.  */
226  bfd *output_bfd;
227  /* Reloc file positions.  */
228  file_ptr treloff, dreloff;
229  /* File position of symbols.  */
230  file_ptr symoff;
231  /* String table.  */
232  struct bfd_strtab_hash *strtab;
233  /* Header file hash table.  */
234  struct aout_link_includes_table includes;
235  /* A buffer large enough to hold the contents of any section.  */
236  bfd_byte *contents;
237  /* A buffer large enough to hold the relocs of any section.  */
238  void * relocs;
239  /* A buffer large enough to hold the symbol map of any input BFD.  */
240  int *symbol_map;
241  /* A buffer large enough to hold output symbols of any input BFD.  */
242  struct external_nlist *output_syms;
243};
244
245reloc_howto_type howto_table_pdp11[] =
246{
247  /* type              rs size bsz  pcrel bitpos ovrf                     sf name     part_inpl readmask  setmask    pcdone */
248HOWTO( 0,	       0,  1,  16,  FALSE, 0, complain_overflow_signed,0,"16",	TRUE, 0x0000ffff,0x0000ffff, FALSE),
249HOWTO( 1,	       0,  1,  16,  TRUE,  0, complain_overflow_signed,0,"DISP16",	TRUE, 0x0000ffff,0x0000ffff, FALSE),
250};
251
252#define TABLE_SIZE(TABLE)	(sizeof(TABLE)/sizeof(TABLE[0]))
253
254
255static bfd_boolean aout_link_check_archive_element (bfd *, struct bfd_link_info *, bfd_boolean *);
256static bfd_boolean aout_link_add_object_symbols    (bfd *, struct bfd_link_info *);
257static bfd_boolean aout_link_add_symbols           (bfd *, struct bfd_link_info *);
258static bfd_boolean aout_link_write_symbols         (struct aout_final_link_info *, bfd *);
259
260
261reloc_howto_type *
262NAME (aout, reloc_type_lookup) (bfd * abfd ATTRIBUTE_UNUSED,
263				bfd_reloc_code_real_type code)
264{
265  switch (code)
266    {
267    case BFD_RELOC_16:
268      return &howto_table_pdp11[0];
269    case BFD_RELOC_16_PCREL:
270      return &howto_table_pdp11[1];
271    default:
272      return NULL;
273    }
274}
275
276reloc_howto_type *
277NAME (aout, reloc_name_lookup) (bfd *abfd ATTRIBUTE_UNUSED,
278				      const char *r_name)
279{
280  unsigned int i;
281
282  for (i = 0;
283       i < sizeof (howto_table_pdp11) / sizeof (howto_table_pdp11[0]);
284       i++)
285    if (howto_table_pdp11[i].name != NULL
286	&& strcasecmp (howto_table_pdp11[i].name, r_name) == 0)
287      return &howto_table_pdp11[i];
288
289  return NULL;
290}
291
292static int
293pdp11_aout_write_headers (bfd *abfd, struct internal_exec *execp)
294{
295  struct external_exec exec_bytes;
296  bfd_size_type text_size;
297  file_ptr text_end;
298
299  if (adata(abfd).magic == undecided_magic)
300    NAME (aout, adjust_sizes_and_vmas) (abfd, &text_size, &text_end);
301
302  execp->a_syms = bfd_get_symcount (abfd) * EXTERNAL_NLIST_SIZE;
303  execp->a_entry = bfd_get_start_address (abfd);
304
305  if (obj_textsec (abfd)->reloc_count > 0
306      || obj_datasec (abfd)->reloc_count > 0)
307    {
308      execp->a_trsize = execp->a_text;
309      execp->a_drsize = execp->a_data;
310    }
311  else
312    {
313      execp->a_trsize = 0;
314      execp->a_drsize = 0;
315    }
316
317  NAME (aout, swap_exec_header_out) (abfd, execp, & exec_bytes);
318
319  if (bfd_seek (abfd, (file_ptr) 0, SEEK_SET) != 0)
320    return FALSE;
321
322  if (bfd_bwrite ((void *) &exec_bytes, (bfd_size_type) EXEC_BYTES_SIZE, abfd)
323      != EXEC_BYTES_SIZE)
324    return FALSE;
325
326  /* Now write out reloc info, followed by syms and strings.  */
327  if (bfd_get_outsymbols (abfd) != NULL
328      && bfd_get_symcount (abfd) != 0)
329    {
330      if (bfd_seek (abfd, (file_ptr) (N_SYMOFF(*execp)), SEEK_SET) != 0)
331	return FALSE;
332
333      if (! NAME (aout, write_syms) (abfd))
334	return FALSE;
335    }
336
337  if (obj_textsec (abfd)->reloc_count > 0
338      || obj_datasec (abfd)->reloc_count > 0)
339    {
340      if (bfd_seek (abfd, (file_ptr) (N_TRELOFF(*execp)), SEEK_SET) != 0
341	  || !NAME (aout, squirt_out_relocs) (abfd, obj_textsec (abfd))
342	  || bfd_seek (abfd, (file_ptr) (N_DRELOFF(*execp)), SEEK_SET) != 0
343	  || !NAME (aout, squirt_out_relocs) (abfd, obj_datasec (abfd)))
344	return FALSE;
345    }
346
347  return TRUE;
348}
349
350/* Write an object file.
351   Section contents have already been written.  We write the
352   file header, symbols, and relocation.  */
353
354static bfd_boolean
355MY(write_object_contents) (bfd *abfd)
356{
357  struct internal_exec *execp = exec_hdr (abfd);
358
359  /* We must make certain that the magic number has been set.  This
360     will normally have been done by set_section_contents, but only if
361     there actually are some section contents.  */
362  if (! abfd->output_has_begun)
363    {
364      bfd_size_type text_size;
365      file_ptr text_end;
366
367      NAME (aout, adjust_sizes_and_vmas) (abfd, &text_size, &text_end);
368    }
369
370  obj_reloc_entry_size (abfd) = RELOC_SIZE;
371
372  return WRITE_HEADERS (abfd, execp);
373}
374
375/* Swap the information in an executable header @var{raw_bytes} taken
376   from a raw byte stream memory image into the internal exec header
377   structure "execp".  */
378
379#ifndef NAME_swap_exec_header_in
380void
381NAME (aout, swap_exec_header_in) (bfd *abfd,
382				  struct external_exec *bytes,
383				  struct internal_exec *execp)
384{
385  /* The internal_exec structure has some fields that are unused in this
386     configuration (IE for i960), so ensure that all such uninitialized
387     fields are zero'd out.  There are places where two of these structs
388     are memcmp'd, and thus the contents do matter.  */
389  memset ((void *) execp, 0, sizeof (struct internal_exec));
390  /* Now fill in fields in the execp, from the bytes in the raw data.  */
391  execp->a_info   = GET_MAGIC (abfd, bytes->e_info);
392  execp->a_text   = GET_WORD (abfd, bytes->e_text);
393  execp->a_data   = GET_WORD (abfd, bytes->e_data);
394  execp->a_bss    = GET_WORD (abfd, bytes->e_bss);
395  execp->a_syms   = GET_WORD (abfd, bytes->e_syms);
396  execp->a_entry  = GET_WORD (abfd, bytes->e_entry);
397
398  if (GET_WORD (abfd, bytes->e_flag) & A_FLAG_RELOC_STRIPPED)
399    {
400      execp->a_trsize = 0;
401      execp->a_drsize = 0;
402    }
403  else
404    {
405      execp->a_trsize = execp->a_text;
406      execp->a_drsize = execp->a_data;
407    }
408}
409#define NAME_swap_exec_header_in NAME (aout, swap_exec_header_in)
410#endif
411
412/*  Swap the information in an internal exec header structure
413    "execp" into the buffer "bytes" ready for writing to disk.  */
414void
415NAME (aout, swap_exec_header_out) (bfd *abfd,
416				   struct internal_exec *execp,
417				   struct external_exec *bytes)
418{
419  /* Now fill in fields in the raw data, from the fields in the exec struct.  */
420  PUT_MAGIC (abfd, execp->a_info,		bytes->e_info);
421  PUT_WORD (abfd, execp->a_text,		bytes->e_text);
422  PUT_WORD (abfd, execp->a_data,		bytes->e_data);
423  PUT_WORD (abfd, execp->a_bss,			bytes->e_bss);
424  PUT_WORD (abfd, execp->a_syms,		bytes->e_syms);
425  PUT_WORD (abfd, execp->a_entry,		bytes->e_entry);
426  PUT_WORD (abfd, 0,				bytes->e_unused);
427
428  if ((execp->a_trsize == 0 || execp->a_text == 0)
429      && (execp->a_drsize == 0 || execp->a_data == 0))
430    PUT_WORD (abfd, A_FLAG_RELOC_STRIPPED, bytes->e_flag);
431  else if (execp->a_trsize == execp->a_text
432	   && execp->a_drsize == execp->a_data)
433    PUT_WORD (abfd, 0, bytes->e_flag);
434  else
435    {
436      /* TODO: print a proper warning message.  */
437      fprintf (stderr, "BFD:%s:%d: internal error\n", __FILE__, __LINE__);
438      PUT_WORD (abfd, 0,			bytes->e_flag);
439    }
440}
441
442/* Make all the section for an a.out file.  */
443
444bfd_boolean
445NAME (aout, make_sections) (bfd *abfd)
446{
447  if (obj_textsec (abfd) == NULL && bfd_make_section (abfd, ".text") == NULL)
448    return FALSE;
449  if (obj_datasec (abfd) == NULL && bfd_make_section (abfd, ".data") == NULL)
450    return FALSE;
451  if (obj_bsssec (abfd) == NULL  && bfd_make_section (abfd, ".bss") == NULL)
452    return FALSE;
453  return TRUE;
454}
455
456/* Some a.out variant thinks that the file open in ABFD
457   checking is an a.out file.  Do some more checking, and set up
458   for access if it really is.  Call back to the calling
459   environment's "finish up" function just before returning, to
460   handle any last-minute setup.  */
461
462const bfd_target *
463NAME (aout, some_aout_object_p) (bfd *abfd,
464				 struct internal_exec *execp,
465				 const bfd_target *(*callback_to_real_object_p) (bfd *))
466{
467  struct aout_data_struct *rawptr, *oldrawptr;
468  const bfd_target *result;
469  bfd_size_type amt = sizeof (struct aout_data_struct);
470
471  rawptr = bfd_zalloc (abfd, amt);
472  if (rawptr == NULL)
473    return 0;
474
475  oldrawptr = abfd->tdata.aout_data;
476  abfd->tdata.aout_data = rawptr;
477
478  /* Copy the contents of the old tdata struct.
479     In particular, we want the subformat, since for hpux it was set in
480     hp300hpux.c:swap_exec_header_in and will be used in
481     hp300hpux.c:callback.  */
482  if (oldrawptr != NULL)
483    *abfd->tdata.aout_data = *oldrawptr;
484
485  abfd->tdata.aout_data->a.hdr = &rawptr->e;
486  *(abfd->tdata.aout_data->a.hdr) = *execp;	/* Copy in the internal_exec struct.  */
487  execp = abfd->tdata.aout_data->a.hdr;
488
489  /* Set the file flags.  */
490  abfd->flags = BFD_NO_FLAGS;
491  if (execp->a_drsize || execp->a_trsize)
492    abfd->flags |= HAS_RELOC;
493  /* Setting of EXEC_P has been deferred to the bottom of this function.  */
494  if (execp->a_syms)
495    abfd->flags |= HAS_LINENO | HAS_DEBUG | HAS_SYMS | HAS_LOCALS;
496  if (N_DYNAMIC(*execp))
497    abfd->flags |= DYNAMIC;
498
499  if (N_MAGIC (*execp) == ZMAGIC)
500    {
501      abfd->flags |= D_PAGED | WP_TEXT;
502      adata (abfd).magic = z_magic;
503    }
504  else if (N_MAGIC (*execp) == NMAGIC)
505    {
506      abfd->flags |= WP_TEXT;
507      adata (abfd).magic = n_magic;
508    }
509  else if (N_MAGIC (*execp) == OMAGIC)
510    adata (abfd).magic = o_magic;
511  else
512    {
513      /* Should have been checked with N_BADMAG before this routine
514	 was called.  */
515      abort ();
516    }
517
518  bfd_get_start_address (abfd) = execp->a_entry;
519
520  obj_aout_symbols (abfd) = NULL;
521  bfd_get_symcount (abfd) = execp->a_syms / sizeof (struct external_nlist);
522
523  /* The default relocation entry size is that of traditional V7 Unix.  */
524  obj_reloc_entry_size (abfd) = RELOC_SIZE;
525
526  /* The default symbol entry size is that of traditional Unix.  */
527  obj_symbol_entry_size (abfd) = EXTERNAL_NLIST_SIZE;
528
529#ifdef USE_MMAP
530  bfd_init_window (&obj_aout_sym_window (abfd));
531  bfd_init_window (&obj_aout_string_window (abfd));
532#endif
533
534  obj_aout_external_syms (abfd) = NULL;
535  obj_aout_external_strings (abfd) = NULL;
536  obj_aout_sym_hashes (abfd) = NULL;
537
538  if (! NAME (aout, make_sections) (abfd))
539    return NULL;
540
541  obj_datasec (abfd)->size = execp->a_data;
542  obj_bsssec (abfd)->size = execp->a_bss;
543
544  obj_textsec (abfd)->flags =
545    (execp->a_trsize != 0
546     ? (SEC_ALLOC | SEC_LOAD | SEC_CODE | SEC_HAS_CONTENTS | SEC_RELOC)
547     : (SEC_ALLOC | SEC_LOAD | SEC_CODE | SEC_HAS_CONTENTS));
548  obj_datasec (abfd)->flags =
549    (execp->a_drsize != 0
550     ? (SEC_ALLOC | SEC_LOAD | SEC_DATA | SEC_HAS_CONTENTS | SEC_RELOC)
551     : (SEC_ALLOC | SEC_LOAD | SEC_DATA | SEC_HAS_CONTENTS));
552  obj_bsssec (abfd)->flags = SEC_ALLOC;
553
554#ifdef THIS_IS_ONLY_DOCUMENTATION
555  /* The common code can't fill in these things because they depend
556     on either the start address of the text segment, the rounding
557     up of virtual addresses between segments, or the starting file
558     position of the text segment -- all of which varies among different
559     versions of a.out.  */
560
561  /* Call back to the format-dependent code to fill in the rest of the
562     fields and do any further cleanup.  Things that should be filled
563     in by the callback:  */
564  struct exec *execp = exec_hdr (abfd);
565
566  obj_textsec (abfd)->size = N_TXTSIZE(*execp);
567  /* Data and bss are already filled in since they're so standard.  */
568
569  /* The virtual memory addresses of the sections.  */
570  obj_textsec (abfd)->vma = N_TXTADDR(*execp);
571  obj_datasec (abfd)->vma = N_DATADDR(*execp);
572  obj_bsssec  (abfd)->vma = N_BSSADDR(*execp);
573
574  /* The file offsets of the sections.  */
575  obj_textsec (abfd)->filepos = N_TXTOFF(*execp);
576  obj_datasec (abfd)->filepos = N_DATOFF(*execp);
577
578  /* The file offsets of the relocation info.  */
579  obj_textsec (abfd)->rel_filepos = N_TRELOFF(*execp);
580  obj_datasec (abfd)->rel_filepos = N_DRELOFF(*execp);
581
582  /* The file offsets of the string table and symbol table.  */
583  obj_str_filepos (abfd) = N_STROFF (*execp);
584  obj_sym_filepos (abfd) = N_SYMOFF (*execp);
585
586  /* Determine the architecture and machine type of the object file.  */
587  abfd->obj_arch = bfd_arch_obscure;
588
589  adata(abfd)->page_size = TARGET_PAGE_SIZE;
590  adata(abfd)->segment_size = SEGMENT_SIZE;
591  adata(abfd)->exec_bytes_size = EXEC_BYTES_SIZE;
592
593  return abfd->xvec;
594
595  /* The architecture is encoded in various ways in various a.out variants,
596     or is not encoded at all in some of them.  The relocation size depends
597     on the architecture and the a.out variant.  Finally, the return value
598     is the bfd_target vector in use.  If an error occurs, return zero and
599     set bfd_error to the appropriate error code.
600
601     Formats such as b.out, which have additional fields in the a.out
602     header, should cope with them in this callback as well.  */
603#endif	/* DOCUMENTATION */
604
605  result = (*callback_to_real_object_p)(abfd);
606
607  /* Now that the segment addresses have been worked out, take a better
608     guess at whether the file is executable.  If the entry point
609     is within the text segment, assume it is.  (This makes files
610     executable even if their entry point address is 0, as long as
611     their text starts at zero.).
612
613     This test had to be changed to deal with systems where the text segment
614     runs at a different location than the default.  The problem is that the
615     entry address can appear to be outside the text segment, thus causing an
616     erroneous conclusion that the file isn't executable.
617
618     To fix this, we now accept any non-zero entry point as an indication of
619     executability.  This will work most of the time, since only the linker
620     sets the entry point, and that is likely to be non-zero for most systems. */
621
622  if (execp->a_entry != 0
623      || (execp->a_entry >= obj_textsec(abfd)->vma
624	  && execp->a_entry < obj_textsec(abfd)->vma + obj_textsec(abfd)->size))
625    abfd->flags |= EXEC_P;
626#ifdef STAT_FOR_EXEC
627  else
628    {
629      struct stat stat_buf;
630
631      /* The original heuristic doesn't work in some important cases.
632        The a.out file has no information about the text start
633        address.  For files (like kernels) linked to non-standard
634        addresses (ld -Ttext nnn) the entry point may not be between
635        the default text start (obj_textsec(abfd)->vma) and
636        (obj_textsec(abfd)->vma) + text size.  This is not just a mach
637        issue.  Many kernels are loaded at non standard addresses.  */
638      if (abfd->iostream != NULL
639	  && (abfd->flags & BFD_IN_MEMORY) == 0
640	  && (fstat(fileno((FILE *) (abfd->iostream)), &stat_buf) == 0)
641	  && ((stat_buf.st_mode & 0111) != 0))
642	abfd->flags |= EXEC_P;
643    }
644#endif /* STAT_FOR_EXEC */
645
646  if (!result)
647    {
648      free (rawptr);
649      abfd->tdata.aout_data = oldrawptr;
650    }
651  return result;
652}
653
654/* Initialize ABFD for use with a.out files.  */
655
656bfd_boolean
657NAME (aout, mkobject) (bfd *abfd)
658{
659  struct aout_data_struct  *rawptr;
660  bfd_size_type amt = sizeof (struct aout_data_struct);
661
662  bfd_set_error (bfd_error_system_call);
663
664  /* Use an intermediate variable for clarity.  */
665  rawptr = bfd_zalloc (abfd, amt);
666
667  if (rawptr == NULL)
668    return FALSE;
669
670  abfd->tdata.aout_data = rawptr;
671  exec_hdr (abfd) = &(rawptr->e);
672
673  obj_textsec (abfd) = NULL;
674  obj_datasec (abfd) = NULL;
675  obj_bsssec (abfd)  = NULL;
676
677  return TRUE;
678}
679
680/* Keep track of machine architecture and machine type for
681   a.out's. Return the <<machine_type>> for a particular
682   architecture and machine, or <<M_UNKNOWN>> if that exact architecture
683   and machine can't be represented in a.out format.
684
685   If the architecture is understood, machine type 0 (default)
686   is always understood.  */
687
688enum machine_type
689NAME (aout, machine_type) (enum bfd_architecture arch,
690			   unsigned long machine,
691			   bfd_boolean *unknown)
692{
693  enum machine_type arch_flags;
694
695  arch_flags = M_UNKNOWN;
696  *unknown = TRUE;
697
698  switch (arch)
699    {
700    case bfd_arch_sparc:
701      if (machine == 0
702	  || machine == bfd_mach_sparc
703	  || machine == bfd_mach_sparc_sparclite
704	  || machine == bfd_mach_sparc_v9)
705	arch_flags = M_SPARC;
706      else if (machine == bfd_mach_sparc_sparclet)
707	arch_flags = M_SPARCLET;
708      break;
709
710    case bfd_arch_m68k:
711      switch (machine)
712	{
713	case 0:		      arch_flags = M_68010; break;
714	case bfd_mach_m68000: arch_flags = M_UNKNOWN; *unknown = FALSE; break;
715	case bfd_mach_m68010: arch_flags = M_68010; break;
716	case bfd_mach_m68020: arch_flags = M_68020; break;
717	default:	      arch_flags = M_UNKNOWN; break;
718	}
719      break;
720
721    case bfd_arch_i386:
722      if (machine == 0
723	  || machine == bfd_mach_i386_i386
724	  || machine == bfd_mach_i386_i386_intel_syntax)
725	arch_flags = M_386;
726      break;
727
728    case bfd_arch_arm:
729      if (machine == 0)	arch_flags = M_ARM;
730      break;
731
732    case bfd_arch_mips:
733      switch (machine)
734	{
735	case 0:
736	case 2000:
737	case bfd_mach_mips3000:
738          arch_flags = M_MIPS1;
739	  break;
740	case bfd_mach_mips4000: /* MIPS3 */
741	case bfd_mach_mips4400:
742	case bfd_mach_mips8000: /* MIPS4 */
743	case bfd_mach_mips6000: /* Real MIPS2: */
744          arch_flags = M_MIPS2;
745	  break;
746	default:
747	  arch_flags = M_UNKNOWN;
748	  break;
749	}
750      break;
751
752    case bfd_arch_ns32k:
753      switch (machine)
754	{
755	case 0:    		arch_flags = M_NS32532; break;
756	case 32032:		arch_flags = M_NS32032; break;
757	case 32532:		arch_flags = M_NS32532; break;
758	default:		arch_flags = M_UNKNOWN; break;
759	}
760      break;
761
762    case bfd_arch_pdp11:
763      /* TODO: arch_flags = M_PDP11; */
764      *unknown = FALSE;
765      break;
766
767    case bfd_arch_vax:
768      *unknown = FALSE;
769      break;
770
771    default:
772      arch_flags = M_UNKNOWN;
773    }
774
775  if (arch_flags != M_UNKNOWN)
776    *unknown = FALSE;
777
778  return arch_flags;
779}
780
781/* Set the architecture and the machine of the ABFD to the
782   values ARCH and MACHINE.  Verify that @ABFD's format
783   can support the architecture required.  */
784
785bfd_boolean
786NAME (aout, set_arch_mach) (bfd *abfd,
787			    enum bfd_architecture arch,
788			    unsigned long machine)
789{
790  if (! bfd_default_set_arch_mach (abfd, arch, machine))
791    return FALSE;
792
793  if (arch != bfd_arch_unknown)
794    {
795      bfd_boolean unknown;
796
797      NAME (aout, machine_type) (arch, machine, &unknown);
798      if (unknown)
799	return FALSE;
800    }
801
802  obj_reloc_entry_size (abfd) = RELOC_SIZE;
803
804  return (*aout_backend_info(abfd)->set_sizes) (abfd);
805}
806
807static void
808adjust_o_magic (bfd *abfd, struct internal_exec *execp)
809{
810  file_ptr pos = adata (abfd).exec_bytes_size;
811  bfd_vma vma = 0;
812  int pad = 0;
813
814  /* Text.  */
815  obj_textsec (abfd)->filepos = pos;
816  if (! obj_textsec (abfd)->user_set_vma)
817    obj_textsec (abfd)->vma = vma;
818  else
819    vma = obj_textsec (abfd)->vma;
820
821  pos += obj_textsec (abfd)->size;
822  vma += obj_textsec (abfd)->size;
823
824  /* Data.  */
825  if (!obj_datasec (abfd)->user_set_vma)
826    {
827      obj_textsec (abfd)->size += pad;
828      pos += pad;
829      vma += pad;
830      obj_datasec (abfd)->vma = vma;
831    }
832  else
833    vma = obj_datasec (abfd)->vma;
834  obj_datasec (abfd)->filepos = pos;
835  pos += obj_datasec (abfd)->size;
836  vma += obj_datasec (abfd)->size;
837
838  /* BSS.  */
839  if (! obj_bsssec (abfd)->user_set_vma)
840    {
841      obj_datasec (abfd)->size += pad;
842      pos += pad;
843      vma += pad;
844      obj_bsssec (abfd)->vma = vma;
845    }
846  else
847    {
848      /* The VMA of the .bss section is set by the VMA of the
849         .data section plus the size of the .data section.  We may
850         need to add padding bytes to make this true.  */
851      pad = obj_bsssec (abfd)->vma - vma;
852      if (pad > 0)
853	{
854	  obj_datasec (abfd)->size += pad;
855	  pos += pad;
856	}
857    }
858  obj_bsssec (abfd)->filepos = pos;
859
860  /* Fix up the exec header.  */
861  execp->a_text = obj_textsec (abfd)->size;
862  execp->a_data = obj_datasec (abfd)->size;
863  execp->a_bss  = obj_bsssec (abfd)->size;
864  N_SET_MAGIC (*execp, OMAGIC);
865}
866
867static void
868adjust_z_magic (bfd *abfd, struct internal_exec *execp)
869{
870  bfd_size_type data_pad, text_pad;
871  file_ptr text_end;
872  const struct aout_backend_data *abdp;
873  int ztih;			/* Nonzero if text includes exec header.  */
874
875  abdp = aout_backend_info (abfd);
876
877  /* Text.  */
878  ztih = (abdp != NULL
879	  && (abdp->text_includes_header
880	      || obj_aout_subformat (abfd) == q_magic_format));
881  obj_textsec(abfd)->filepos = (ztih
882				? adata(abfd).exec_bytes_size
883				: adata(abfd).zmagic_disk_block_size);
884  if (! obj_textsec(abfd)->user_set_vma)
885    {
886      /* ?? Do we really need to check for relocs here?  */
887      obj_textsec(abfd)->vma = ((abfd->flags & HAS_RELOC)
888				? 0
889				: (ztih
890				   ? (abdp->default_text_vma
891				      + adata (abfd).exec_bytes_size)
892				   : abdp->default_text_vma));
893      text_pad = 0;
894    }
895  else
896    {
897      /* The .text section is being loaded at an unusual address.  We
898         may need to pad it such that the .data section starts at a page
899         boundary.  */
900      if (ztih)
901	text_pad = ((obj_textsec (abfd)->filepos - obj_textsec (abfd)->vma)
902		    & (adata (abfd).page_size - 1));
903      else
904	text_pad = ((- obj_textsec (abfd)->vma)
905		    & (adata (abfd).page_size - 1));
906    }
907
908  /* Find start of data.  */
909  if (ztih)
910    {
911      text_end = obj_textsec (abfd)->filepos + obj_textsec (abfd)->size;
912      text_pad += BFD_ALIGN (text_end, adata (abfd).page_size) - text_end;
913    }
914  else
915    {
916      /* Note that if page_size == zmagic_disk_block_size, then
917	 filepos == page_size, and this case is the same as the ztih
918	 case.  */
919      text_end = obj_textsec (abfd)->size;
920      text_pad += BFD_ALIGN (text_end, adata (abfd).page_size) - text_end;
921      text_end += obj_textsec (abfd)->filepos;
922    }
923
924  obj_textsec (abfd)->size += text_pad;
925  text_end += text_pad;
926
927  /* Data.  */
928  if (!obj_datasec(abfd)->user_set_vma)
929    {
930      bfd_vma vma;
931      vma = obj_textsec(abfd)->vma + obj_textsec(abfd)->size;
932      obj_datasec(abfd)->vma = BFD_ALIGN (vma, adata(abfd).segment_size);
933    }
934  if (abdp && abdp->zmagic_mapped_contiguous)
935    {
936      text_pad = (obj_datasec(abfd)->vma
937		  - obj_textsec(abfd)->vma
938		  - obj_textsec(abfd)->size);
939      obj_textsec(abfd)->size += text_pad;
940    }
941  obj_datasec (abfd)->filepos = (obj_textsec (abfd)->filepos
942				+ obj_textsec (abfd)->size);
943
944  /* Fix up exec header while we're at it.  */
945  execp->a_text = obj_textsec(abfd)->size;
946  if (ztih && (!abdp || (abdp && !abdp->exec_header_not_counted)))
947    execp->a_text += adata(abfd).exec_bytes_size;
948  N_SET_MAGIC (*execp, ZMAGIC);
949
950  /* Spec says data section should be rounded up to page boundary.  */
951  obj_datasec(abfd)->size
952    = align_power (obj_datasec(abfd)->size,
953		   obj_bsssec(abfd)->alignment_power);
954  execp->a_data = BFD_ALIGN (obj_datasec(abfd)->size,
955			     adata(abfd).page_size);
956  data_pad = execp->a_data - obj_datasec(abfd)->size;
957
958  /* BSS.  */
959  if (!obj_bsssec(abfd)->user_set_vma)
960    obj_bsssec(abfd)->vma = (obj_datasec(abfd)->vma
961			     + obj_datasec(abfd)->size);
962  /* If the BSS immediately follows the data section and extra space
963     in the page is left after the data section, fudge data
964     in the header so that the bss section looks smaller by that
965     amount.  We'll start the bss section there, and lie to the OS.
966     (Note that a linker script, as well as the above assignment,
967     could have explicitly set the BSS vma to immediately follow
968     the data section.)  */
969  if (align_power (obj_bsssec(abfd)->vma, obj_bsssec(abfd)->alignment_power)
970      == obj_datasec(abfd)->vma + obj_datasec(abfd)->size)
971    execp->a_bss = (data_pad > obj_bsssec(abfd)->size) ? 0 :
972      obj_bsssec(abfd)->size - data_pad;
973  else
974    execp->a_bss = obj_bsssec(abfd)->size;
975}
976
977static void
978adjust_n_magic (bfd *abfd, struct internal_exec *execp)
979{
980  file_ptr pos = adata(abfd).exec_bytes_size;
981  bfd_vma vma = 0;
982  int pad;
983
984  /* Text.  */
985  obj_textsec(abfd)->filepos = pos;
986  if (!obj_textsec(abfd)->user_set_vma)
987    obj_textsec(abfd)->vma = vma;
988  else
989    vma = obj_textsec(abfd)->vma;
990  pos += obj_textsec(abfd)->size;
991  vma += obj_textsec(abfd)->size;
992
993  /* Data.  */
994  obj_datasec(abfd)->filepos = pos;
995  if (!obj_datasec(abfd)->user_set_vma)
996    obj_datasec(abfd)->vma = BFD_ALIGN (vma, adata(abfd).segment_size);
997  vma = obj_datasec(abfd)->vma;
998
999  /* Since BSS follows data immediately, see if it needs alignment.  */
1000  vma += obj_datasec(abfd)->size;
1001  pad = align_power (vma, obj_bsssec(abfd)->alignment_power) - vma;
1002  obj_datasec(abfd)->size += pad;
1003  pos += obj_datasec(abfd)->size;
1004
1005  /* BSS.  */
1006  if (!obj_bsssec(abfd)->user_set_vma)
1007    obj_bsssec(abfd)->vma = vma;
1008  else
1009    vma = obj_bsssec(abfd)->vma;
1010
1011  /* Fix up exec header.  */
1012  execp->a_text = obj_textsec(abfd)->size;
1013  execp->a_data = obj_datasec(abfd)->size;
1014  execp->a_bss = obj_bsssec(abfd)->size;
1015  N_SET_MAGIC (*execp, NMAGIC);
1016}
1017
1018bfd_boolean
1019NAME (aout, adjust_sizes_and_vmas) (bfd *abfd,
1020				    bfd_size_type *text_size,
1021				    file_ptr * text_end ATTRIBUTE_UNUSED)
1022{
1023  struct internal_exec *execp = exec_hdr (abfd);
1024
1025  if (! NAME (aout, make_sections) (abfd))
1026    return FALSE;
1027
1028  if (adata(abfd).magic != undecided_magic)
1029    return TRUE;
1030
1031  obj_textsec(abfd)->size =
1032    align_power(obj_textsec(abfd)->size,
1033		obj_textsec(abfd)->alignment_power);
1034
1035  *text_size = obj_textsec (abfd)->size;
1036  /* Rule (heuristic) for when to pad to a new page.  Note that there
1037     are (at least) two ways demand-paged (ZMAGIC) files have been
1038     handled.  Most Berkeley-based systems start the text segment at
1039     (TARGET_PAGE_SIZE).  However, newer versions of SUNOS start the text
1040     segment right after the exec header; the latter is counted in the
1041     text segment size, and is paged in by the kernel with the rest of
1042     the text. */
1043
1044  /* This perhaps isn't the right way to do this, but made it simpler for me
1045     to understand enough to implement it.  Better would probably be to go
1046     right from BFD flags to alignment/positioning characteristics.  But the
1047     old code was sloppy enough about handling the flags, and had enough
1048     other magic, that it was a little hard for me to understand.  I think
1049     I understand it better now, but I haven't time to do the cleanup this
1050     minute.  */
1051
1052  if (abfd->flags & WP_TEXT)
1053    adata(abfd).magic = n_magic;
1054  else
1055    adata(abfd).magic = o_magic;
1056
1057#ifdef BFD_AOUT_DEBUG /* requires gcc2 */
1058#if __GNUC__ >= 2
1059  fprintf (stderr, "%s text=<%x,%x,%x> data=<%x,%x,%x> bss=<%x,%x,%x>\n",
1060	   ({ char *str;
1061	      switch (adata(abfd).magic) {
1062	      case n_magic: str = "NMAGIC"; break;
1063	      case o_magic: str = "OMAGIC"; break;
1064	      case z_magic: str = "ZMAGIC"; break;
1065	      default: abort ();
1066	      }
1067	      str;
1068	    }),
1069	   obj_textsec(abfd)->vma, obj_textsec(abfd)->size,
1070	   	obj_textsec(abfd)->alignment_power,
1071	   obj_datasec(abfd)->vma, obj_datasec(abfd)->size,
1072	   	obj_datasec(abfd)->alignment_power,
1073	   obj_bsssec(abfd)->vma, obj_bsssec(abfd)->size,
1074	   	obj_bsssec(abfd)->alignment_power);
1075#endif
1076#endif
1077
1078  switch (adata(abfd).magic)
1079    {
1080    case o_magic:
1081      adjust_o_magic (abfd, execp);
1082      break;
1083    case z_magic:
1084      adjust_z_magic (abfd, execp);
1085      break;
1086    case n_magic:
1087      adjust_n_magic (abfd, execp);
1088      break;
1089    default:
1090      abort ();
1091    }
1092
1093#ifdef BFD_AOUT_DEBUG
1094  fprintf (stderr, "       text=<%x,%x,%x> data=<%x,%x,%x> bss=<%x,%x>\n",
1095	   obj_textsec(abfd)->vma, obj_textsec(abfd)->size,
1096	   	obj_textsec(abfd)->filepos,
1097	   obj_datasec(abfd)->vma, obj_datasec(abfd)->size,
1098	   	obj_datasec(abfd)->filepos,
1099	   obj_bsssec(abfd)->vma, obj_bsssec(abfd)->size);
1100#endif
1101
1102  return TRUE;
1103}
1104
1105/* Called by the BFD in response to a bfd_make_section request.  */
1106
1107bfd_boolean
1108NAME (aout, new_section_hook) (bfd *abfd, asection *newsect)
1109{
1110  /* Align to double at least.  */
1111  newsect->alignment_power = bfd_get_arch_info(abfd)->section_align_power;
1112
1113  if (bfd_get_format (abfd) == bfd_object)
1114    {
1115      if (obj_textsec (abfd) == NULL
1116	  && !strcmp (newsect->name, ".text"))
1117	{
1118	  obj_textsec(abfd)= newsect;
1119	  newsect->target_index = N_TEXT;
1120	}
1121      else if (obj_datasec (abfd) == NULL
1122	       && !strcmp (newsect->name, ".data"))
1123	{
1124	  obj_datasec (abfd) = newsect;
1125	  newsect->target_index = N_DATA;
1126	}
1127      else if (obj_bsssec (abfd) == NULL
1128	       && !strcmp (newsect->name, ".bss"))
1129	{
1130	  obj_bsssec (abfd) = newsect;
1131	  newsect->target_index = N_BSS;
1132	}
1133    }
1134
1135  /* We allow more than three sections internally.  */
1136  return _bfd_generic_new_section_hook (abfd, newsect);
1137}
1138
1139bfd_boolean
1140NAME (aout, set_section_contents) (bfd *abfd,
1141				   sec_ptr section,
1142				   const void * location,
1143				   file_ptr offset,
1144				   bfd_size_type count)
1145{
1146  file_ptr text_end;
1147  bfd_size_type text_size;
1148
1149  if (! abfd->output_has_begun)
1150    {
1151      if (! NAME (aout, adjust_sizes_and_vmas) (abfd, & text_size, & text_end))
1152	return FALSE;
1153    }
1154
1155  if (section == obj_bsssec (abfd))
1156    {
1157      bfd_set_error (bfd_error_no_contents);
1158      return FALSE;
1159    }
1160
1161  if (section != obj_textsec (abfd)
1162      && section != obj_datasec (abfd))
1163    {
1164      (*_bfd_error_handler)
1165	("%s: can not represent section `%s' in a.out object file format",
1166	 bfd_get_filename (abfd), bfd_get_section_name (abfd, section));
1167      bfd_set_error (bfd_error_nonrepresentable_section);
1168      return FALSE;
1169    }
1170
1171  if (count != 0)
1172    {
1173      if (bfd_seek (abfd, section->filepos + offset, SEEK_SET) != 0
1174	  || bfd_bwrite (location, count, abfd) != count)
1175	return FALSE;
1176    }
1177
1178  return TRUE;
1179}
1180
1181/* Read the external symbols from an a.out file.  */
1182
1183static bfd_boolean
1184aout_get_external_symbols (bfd *abfd)
1185{
1186  if (obj_aout_external_syms (abfd) == NULL)
1187    {
1188      bfd_size_type count;
1189      struct external_nlist *syms;
1190
1191      count = exec_hdr (abfd)->a_syms / EXTERNAL_NLIST_SIZE;
1192
1193#ifdef USE_MMAP
1194      if (! bfd_get_file_window (abfd, obj_sym_filepos (abfd),
1195				 exec_hdr (abfd)->a_syms,
1196				 &obj_aout_sym_window (abfd), TRUE))
1197	return FALSE;
1198      syms = (struct external_nlist *) obj_aout_sym_window (abfd).data;
1199#else
1200      /* We allocate using malloc to make the values easy to free
1201	 later on.  If we put them on the objalloc it might not be
1202	 possible to free them.  */
1203      syms = bfd_malloc (count * EXTERNAL_NLIST_SIZE);
1204      if (syms == NULL && count != 0)
1205	return FALSE;
1206
1207      if (bfd_seek (abfd, obj_sym_filepos (abfd), SEEK_SET) != 0
1208	  || (bfd_bread (syms, exec_hdr (abfd)->a_syms, abfd)
1209	      != exec_hdr (abfd)->a_syms))
1210	{
1211	  free (syms);
1212	  return FALSE;
1213	}
1214#endif
1215
1216      obj_aout_external_syms (abfd) = syms;
1217      obj_aout_external_sym_count (abfd) = count;
1218    }
1219
1220  if (obj_aout_external_strings (abfd) == NULL
1221      && exec_hdr (abfd)->a_syms != 0)
1222    {
1223      unsigned char string_chars[BYTES_IN_LONG];
1224      bfd_size_type stringsize;
1225      char *strings;
1226
1227      /* Get the size of the strings.  */
1228      if (bfd_seek (abfd, obj_str_filepos (abfd), SEEK_SET) != 0
1229	  || (bfd_bread ((void *) string_chars, (bfd_size_type) BYTES_IN_LONG,
1230			abfd) != BYTES_IN_LONG))
1231	return FALSE;
1232      stringsize = H_GET_32 (abfd, string_chars);
1233
1234#ifdef USE_MMAP
1235      if (! bfd_get_file_window (abfd, obj_str_filepos (abfd), stringsize,
1236				 &obj_aout_string_window (abfd), TRUE))
1237	return FALSE;
1238      strings = (char *) obj_aout_string_window (abfd).data;
1239#else
1240      strings = bfd_malloc (stringsize + 1);
1241      if (strings == NULL)
1242	return FALSE;
1243
1244      /* Skip space for the string count in the buffer for convenience
1245	 when using indexes.  */
1246      if (bfd_bread (strings + 4, stringsize - 4, abfd) != stringsize - 4)
1247	{
1248	  free (strings);
1249	  return FALSE;
1250	}
1251#endif
1252      /* Ensure that a zero index yields an empty string.  */
1253      strings[0] = '\0';
1254
1255      strings[stringsize - 1] = 0;
1256
1257      obj_aout_external_strings (abfd) = strings;
1258      obj_aout_external_string_size (abfd) = stringsize;
1259    }
1260
1261  return TRUE;
1262}
1263
1264/* Translate an a.out symbol into a BFD symbol.  The desc, other, type
1265   and symbol->value fields of CACHE_PTR will be set from the a.out
1266   nlist structure.  This function is responsible for setting
1267   symbol->flags and symbol->section, and adjusting symbol->value.  */
1268
1269static bfd_boolean
1270translate_from_native_sym_flags (bfd *abfd,
1271				 aout_symbol_type *cache_ptr)
1272{
1273  flagword visible;
1274
1275  if (cache_ptr->type == N_FN)
1276    {
1277      asection *sec;
1278
1279      /* This is a debugging symbol.  */
1280      cache_ptr->symbol.flags = BSF_DEBUGGING;
1281
1282      /* Work out the symbol section.  */
1283      switch (cache_ptr->type & N_TYPE)
1284	{
1285	case N_TEXT:
1286	case N_FN:
1287	  sec = obj_textsec (abfd);
1288	  break;
1289	case N_DATA:
1290	  sec = obj_datasec (abfd);
1291	  break;
1292	case N_BSS:
1293	  sec = obj_bsssec (abfd);
1294	  break;
1295	default:
1296	case N_ABS:
1297	  sec = bfd_abs_section_ptr;
1298	  break;
1299	}
1300
1301      cache_ptr->symbol.section = sec;
1302      cache_ptr->symbol.value -= sec->vma;
1303
1304      return TRUE;
1305    }
1306
1307  /* Get the default visibility.  This does not apply to all types, so
1308     we just hold it in a local variable to use if wanted.  */
1309  if ((cache_ptr->type & N_EXT) == 0)
1310    visible = BSF_LOCAL;
1311  else
1312    visible = BSF_GLOBAL;
1313
1314  switch (cache_ptr->type)
1315    {
1316    default:
1317    case N_ABS: case N_ABS | N_EXT:
1318      cache_ptr->symbol.section = bfd_abs_section_ptr;
1319      cache_ptr->symbol.flags = visible;
1320      break;
1321
1322    case N_UNDF | N_EXT:
1323      if (cache_ptr->symbol.value != 0)
1324	{
1325	  /* This is a common symbol.  */
1326	  cache_ptr->symbol.flags = BSF_GLOBAL;
1327	  cache_ptr->symbol.section = bfd_com_section_ptr;
1328	}
1329      else
1330	{
1331	  cache_ptr->symbol.flags = 0;
1332	  cache_ptr->symbol.section = bfd_und_section_ptr;
1333	}
1334      break;
1335
1336    case N_TEXT: case N_TEXT | N_EXT:
1337      cache_ptr->symbol.section = obj_textsec (abfd);
1338      cache_ptr->symbol.value -= cache_ptr->symbol.section->vma;
1339      cache_ptr->symbol.flags = visible;
1340      break;
1341
1342    case N_DATA: case N_DATA | N_EXT:
1343      cache_ptr->symbol.section = obj_datasec (abfd);
1344      cache_ptr->symbol.value -= cache_ptr->symbol.section->vma;
1345      cache_ptr->symbol.flags = visible;
1346      break;
1347
1348    case N_BSS: case N_BSS | N_EXT:
1349      cache_ptr->symbol.section = obj_bsssec (abfd);
1350      cache_ptr->symbol.value -= cache_ptr->symbol.section->vma;
1351      cache_ptr->symbol.flags = visible;
1352      break;
1353    }
1354
1355  return TRUE;
1356}
1357
1358/* Set the fields of SYM_POINTER according to CACHE_PTR.  */
1359
1360static bfd_boolean
1361translate_to_native_sym_flags (bfd *abfd,
1362			       asymbol *cache_ptr,
1363			       struct external_nlist *sym_pointer)
1364{
1365  bfd_vma value = cache_ptr->value;
1366  asection *sec;
1367  bfd_vma off;
1368
1369  /* Mask out any existing type bits in case copying from one section
1370     to another.  */
1371  sym_pointer->e_type[0] &= ~N_TYPE;
1372
1373  sec = bfd_get_section (cache_ptr);
1374  off = 0;
1375
1376  if (sec == NULL)
1377    {
1378      /* This case occurs, e.g., for the *DEBUG* section of a COFF
1379	 file.  */
1380      (*_bfd_error_handler)
1381	("%B: can not represent section for symbol `%s' in a.out object file format",
1382	 abfd, cache_ptr->name != NULL ? cache_ptr->name : "*unknown*");
1383      bfd_set_error (bfd_error_nonrepresentable_section);
1384      return FALSE;
1385    }
1386
1387  if (sec->output_section != NULL)
1388    {
1389      off = sec->output_offset;
1390      sec = sec->output_section;
1391    }
1392
1393  if (bfd_is_abs_section (sec))
1394    sym_pointer->e_type[0] |= N_ABS;
1395  else if (sec == obj_textsec (abfd))
1396    sym_pointer->e_type[0] |= N_TEXT;
1397  else if (sec == obj_datasec (abfd))
1398    sym_pointer->e_type[0] |= N_DATA;
1399  else if (sec == obj_bsssec (abfd))
1400    sym_pointer->e_type[0] |= N_BSS;
1401  else if (bfd_is_und_section (sec))
1402    sym_pointer->e_type[0] = N_UNDF | N_EXT;
1403  else if (bfd_is_com_section (sec))
1404    sym_pointer->e_type[0] = N_UNDF | N_EXT;
1405  else
1406    {
1407      (*_bfd_error_handler)
1408	("%B: can not represent section `%A' in a.out object file format",
1409	 abfd, sec);
1410      bfd_set_error (bfd_error_nonrepresentable_section);
1411      return FALSE;
1412    }
1413
1414  /* Turn the symbol from section relative to absolute again */
1415  value += sec->vma + off;
1416
1417  if ((cache_ptr->flags & BSF_DEBUGGING) != 0)
1418    sym_pointer->e_type[0] = ((aout_symbol_type *) cache_ptr)->type;
1419  else if ((cache_ptr->flags & BSF_GLOBAL) != 0)
1420    sym_pointer->e_type[0] |= N_EXT;
1421
1422  PUT_WORD(abfd, value, sym_pointer->e_value);
1423
1424  return TRUE;
1425}
1426
1427/* Native-level interface to symbols. */
1428
1429asymbol *
1430NAME (aout, make_empty_symbol) (bfd *abfd)
1431{
1432  bfd_size_type amt = sizeof (aout_symbol_type);
1433  aout_symbol_type *new_symbol_type = bfd_zalloc (abfd, amt);
1434
1435  if (!new_symbol_type)
1436    return NULL;
1437  new_symbol_type->symbol.the_bfd = abfd;
1438
1439  return &new_symbol_type->symbol;
1440}
1441
1442/* Translate a set of internal symbols into external symbols.  */
1443
1444bfd_boolean
1445NAME (aout, translate_symbol_table) (bfd *abfd,
1446				     aout_symbol_type *in,
1447				     struct external_nlist *ext,
1448				     bfd_size_type count,
1449				     char *str,
1450				     bfd_size_type strsize,
1451				     bfd_boolean dynamic)
1452{
1453  struct external_nlist *ext_end;
1454
1455  ext_end = ext + count;
1456  for (; ext < ext_end; ext++, in++)
1457    {
1458      bfd_vma x;
1459
1460      x = GET_WORD (abfd, ext->e_strx);
1461      in->symbol.the_bfd = abfd;
1462
1463      /* For the normal symbols, the zero index points at the number
1464	 of bytes in the string table but is to be interpreted as the
1465	 null string.  For the dynamic symbols, the number of bytes in
1466	 the string table is stored in the __DYNAMIC structure and the
1467	 zero index points at an actual string.  */
1468      if (x == 0 && ! dynamic)
1469	in->symbol.name = "";
1470      else if (x < strsize)
1471	in->symbol.name = str + x;
1472      else
1473	return FALSE;
1474
1475      in->symbol.value = GET_SWORD (abfd,  ext->e_value);
1476      /* TODO: is 0 a safe value here?  */
1477      in->desc = 0;
1478      in->other = 0;
1479      in->type = H_GET_8 (abfd,  ext->e_type);
1480      in->symbol.udata.p = NULL;
1481
1482      if (! translate_from_native_sym_flags (abfd, in))
1483	return FALSE;
1484
1485      if (dynamic)
1486	in->symbol.flags |= BSF_DYNAMIC;
1487    }
1488
1489  return TRUE;
1490}
1491
1492/* We read the symbols into a buffer, which is discarded when this
1493   function exits.  We read the strings into a buffer large enough to
1494   hold them all plus all the cached symbol entries.  */
1495
1496bfd_boolean
1497NAME (aout, slurp_symbol_table) (bfd *abfd)
1498{
1499  struct external_nlist *old_external_syms;
1500  aout_symbol_type *cached;
1501  bfd_size_type cached_size;
1502
1503  /* If there's no work to be done, don't do any.  */
1504  if (obj_aout_symbols (abfd) != NULL)
1505    return TRUE;
1506
1507  old_external_syms = obj_aout_external_syms (abfd);
1508
1509  if (! aout_get_external_symbols (abfd))
1510    return FALSE;
1511
1512  cached_size = obj_aout_external_sym_count (abfd);
1513  cached_size *= sizeof (aout_symbol_type);
1514  cached = bfd_zmalloc (cached_size);
1515  if (cached == NULL && cached_size != 0)
1516    return FALSE;
1517
1518  /* Convert from external symbol information to internal.  */
1519  if (! (NAME (aout, translate_symbol_table)
1520	 (abfd, cached,
1521	  obj_aout_external_syms (abfd),
1522	  obj_aout_external_sym_count (abfd),
1523	  obj_aout_external_strings (abfd),
1524	  obj_aout_external_string_size (abfd),
1525	  FALSE)))
1526    {
1527      free (cached);
1528      return FALSE;
1529    }
1530
1531  bfd_get_symcount (abfd) = obj_aout_external_sym_count (abfd);
1532
1533  obj_aout_symbols (abfd) = cached;
1534
1535  /* It is very likely that anybody who calls this function will not
1536     want the external symbol information, so if it was allocated
1537     because of our call to aout_get_external_symbols, we free it up
1538     right away to save space.  */
1539  if (old_external_syms == NULL
1540      && obj_aout_external_syms (abfd) != NULL)
1541    {
1542#ifdef USE_MMAP
1543      bfd_free_window (&obj_aout_sym_window (abfd));
1544#else
1545      free (obj_aout_external_syms (abfd));
1546#endif
1547      obj_aout_external_syms (abfd) = NULL;
1548    }
1549
1550  return TRUE;
1551}
1552
1553/* We use a hash table when writing out symbols so that we only write
1554   out a particular string once.  This helps particularly when the
1555   linker writes out stabs debugging entries, because each different
1556   contributing object file tends to have many duplicate stabs
1557   strings.
1558
1559   This hash table code breaks dbx on SunOS 4.1.3, so we don't do it
1560   if BFD_TRADITIONAL_FORMAT is set.  */
1561
1562/* Get the index of a string in a strtab, adding it if it is not
1563   already present.  */
1564
1565static INLINE bfd_size_type
1566add_to_stringtab (bfd *abfd,
1567		  struct bfd_strtab_hash *tab,
1568		  const char *str,
1569		  bfd_boolean copy)
1570{
1571  bfd_boolean hash;
1572  bfd_size_type str_index;
1573
1574  /* An index of 0 always means the empty string.  */
1575  if (str == 0 || *str == '\0')
1576    return 0;
1577
1578  /* Don't hash if BFD_TRADITIONAL_FORMAT is set, because SunOS dbx
1579     doesn't understand a hashed string table.  */
1580  hash = TRUE;
1581  if ((abfd->flags & BFD_TRADITIONAL_FORMAT) != 0)
1582    hash = FALSE;
1583
1584  str_index = _bfd_stringtab_add (tab, str, hash, copy);
1585
1586  if (str_index != (bfd_size_type) -1)
1587    /* Add BYTES_IN_LONG to the return value to account for the
1588       space taken up by the string table size.  */
1589    str_index += BYTES_IN_LONG;
1590
1591  return str_index;
1592}
1593
1594/* Write out a strtab.  ABFD is already at the right location in the
1595   file.  */
1596
1597static bfd_boolean
1598emit_stringtab (bfd *abfd, struct bfd_strtab_hash *tab)
1599{
1600  bfd_byte buffer[BYTES_IN_LONG];
1601
1602  /* The string table starts with the size.  */
1603  H_PUT_32 (abfd, _bfd_stringtab_size (tab) + BYTES_IN_LONG, buffer);
1604  if (bfd_bwrite ((void *) buffer, (bfd_size_type) BYTES_IN_LONG, abfd)
1605      != BYTES_IN_LONG)
1606    return FALSE;
1607
1608  return _bfd_stringtab_emit (abfd, tab);
1609}
1610
1611bfd_boolean
1612NAME (aout, write_syms) (bfd *abfd)
1613{
1614  unsigned int count ;
1615  asymbol **generic = bfd_get_outsymbols (abfd);
1616  struct bfd_strtab_hash *strtab;
1617
1618  strtab = _bfd_stringtab_init ();
1619  if (strtab == NULL)
1620    return FALSE;
1621
1622  for (count = 0; count < bfd_get_symcount (abfd); count++)
1623    {
1624      asymbol *g = generic[count];
1625      bfd_size_type indx;
1626      struct external_nlist nsp;
1627
1628      PUT_WORD (abfd, 0, nsp.e_unused);
1629
1630      indx = add_to_stringtab (abfd, strtab, g->name, FALSE);
1631      if (indx == (bfd_size_type) -1)
1632	goto error_return;
1633      PUT_WORD (abfd, indx, nsp.e_strx);
1634
1635      if (bfd_asymbol_flavour(g) == abfd->xvec->flavour)
1636	H_PUT_8 (abfd, aout_symbol(g)->type,  nsp.e_type);
1637      else
1638	H_PUT_8 (abfd, 0, nsp.e_type);
1639
1640      if (! translate_to_native_sym_flags (abfd, g, &nsp))
1641	goto error_return;
1642
1643      H_PUT_8 (abfd, 0, nsp.e_ovly);
1644
1645      if (bfd_bwrite ((void *)&nsp, (bfd_size_type) EXTERNAL_NLIST_SIZE, abfd)
1646	  != EXTERNAL_NLIST_SIZE)
1647	goto error_return;
1648
1649      /* NB: `KEEPIT' currently overlays `udata.p', so set this only
1650	 here, at the end.  */
1651      g->KEEPIT = count;
1652    }
1653
1654  if (! emit_stringtab (abfd, strtab))
1655    goto error_return;
1656
1657  _bfd_stringtab_free (strtab);
1658
1659  return TRUE;
1660
1661error_return:
1662  _bfd_stringtab_free (strtab);
1663  return FALSE;
1664}
1665
1666
1667long
1668NAME (aout, canonicalize_symtab) (bfd *abfd, asymbol **location)
1669{
1670  unsigned int counter = 0;
1671  aout_symbol_type *symbase;
1672
1673  if (!NAME (aout, slurp_symbol_table) (abfd))
1674    return -1;
1675
1676  for (symbase = obj_aout_symbols (abfd); counter++ < bfd_get_symcount (abfd);)
1677    *(location++) = (asymbol *)(symbase++);
1678  *location++ =0;
1679  return bfd_get_symcount (abfd);
1680}
1681
1682
1683/* Output extended relocation information to a file in target byte order.  */
1684
1685static void
1686pdp11_aout_swap_reloc_out (bfd *abfd, arelent *g, bfd_byte *natptr)
1687{
1688  int r_index;
1689  int r_pcrel;
1690  int reloc_entry;
1691  int r_type;
1692  asymbol *sym = *(g->sym_ptr_ptr);
1693  asection *output_section = sym->section->output_section;
1694
1695  if (g->addend != 0)
1696    fprintf (stderr, "BFD: can't do this reloc addend stuff\n");
1697
1698  r_pcrel = g->howto->pc_relative;
1699
1700  if (bfd_is_abs_section (output_section))
1701    r_type = RABS;
1702  else if (output_section == obj_textsec (abfd))
1703    r_type = RTEXT;
1704  else if (output_section == obj_datasec (abfd))
1705    r_type = RDATA;
1706  else if (output_section == obj_bsssec (abfd))
1707    r_type = RBSS;
1708  else if (bfd_is_und_section (output_section))
1709    r_type = REXT;
1710  else if (bfd_is_com_section (output_section))
1711    r_type = REXT;
1712  else
1713    r_type = -1;
1714
1715  BFD_ASSERT (r_type != -1);
1716
1717  if (r_type == RABS)
1718    r_index = 0;
1719  else
1720    r_index = (*(g->sym_ptr_ptr))->KEEPIT;
1721
1722  reloc_entry = r_index << 4 | r_type | r_pcrel;
1723
1724  PUT_WORD (abfd, reloc_entry, natptr);
1725}
1726
1727/* BFD deals internally with all things based from the section they're
1728   in. so, something in 10 bytes into a text section  with a base of
1729   50 would have a symbol (.text+10) and know .text vma was 50.
1730
1731   Aout keeps all it's symbols based from zero, so the symbol would
1732   contain 60. This macro subs the base of each section from the value
1733   to give the true offset from the section */
1734
1735
1736#define MOVE_ADDRESS(ad)       						\
1737  if (r_extern) 							\
1738    {									\
1739      /* Undefined symbol.  */						\
1740      cache_ptr->sym_ptr_ptr = symbols + r_index;			\
1741      cache_ptr->addend = ad;						\
1742    }									\
1743  else									\
1744    {									\
1745      /* Defined, section relative. replace symbol with pointer to    	\
1746	 symbol which points to section.  */				\
1747      switch (r_index)							\
1748	{								\
1749	case N_TEXT:							\
1750	case N_TEXT | N_EXT:						\
1751	  cache_ptr->sym_ptr_ptr  = obj_textsec (abfd)->symbol_ptr_ptr;	\
1752	  cache_ptr->addend = ad  - su->textsec->vma;			\
1753	  break;							\
1754	case N_DATA:							\
1755	case N_DATA | N_EXT:						\
1756	  cache_ptr->sym_ptr_ptr  = obj_datasec (abfd)->symbol_ptr_ptr;	\
1757	  cache_ptr->addend = ad - su->datasec->vma;			\
1758	  break;							\
1759	case N_BSS:							\
1760	case N_BSS | N_EXT:						\
1761	  cache_ptr->sym_ptr_ptr  = obj_bsssec (abfd)->symbol_ptr_ptr;	\
1762	  cache_ptr->addend = ad - su->bsssec->vma;			\
1763	  break;							\
1764	default:							\
1765	case N_ABS:							\
1766	case N_ABS | N_EXT:						\
1767	  cache_ptr->sym_ptr_ptr = bfd_abs_section_ptr->symbol_ptr_ptr;	\
1768	  cache_ptr->addend = ad;					\
1769	  break;							\
1770	}								\
1771    }
1772
1773static void
1774pdp11_aout_swap_reloc_in (bfd *          abfd,
1775			  bfd_byte *     bytes,
1776			  arelent *      cache_ptr,
1777			  bfd_size_type  offset,
1778			  asymbol **     symbols,
1779			  bfd_size_type  symcount)
1780{
1781  struct aoutdata *su = &(abfd->tdata.aout_data->a);
1782  unsigned int r_index;
1783  int reloc_entry;
1784  int r_extern;
1785  int r_pcrel;
1786
1787  reloc_entry = GET_WORD (abfd, (void *) bytes);
1788
1789  r_pcrel = reloc_entry & RELFLG;
1790
1791  cache_ptr->address = offset;
1792  cache_ptr->howto = howto_table_pdp11 + (r_pcrel ? 1 : 0);
1793
1794  if ((reloc_entry & RTYPE) == RABS)
1795    r_index = N_ABS;
1796  else
1797    r_index = RINDEX (reloc_entry);
1798
1799  /* r_extern reflects whether the symbol the reloc is against is
1800     local or global.  */
1801  r_extern = (reloc_entry & RTYPE) == REXT;
1802
1803  if (r_extern && r_index > symcount)
1804    {
1805      /* We could arrange to return an error, but it might be useful
1806         to see the file even if it is bad.  */
1807      r_extern = 0;
1808      r_index = N_ABS;
1809    }
1810
1811  MOVE_ADDRESS(0);
1812}
1813
1814/* Read and swap the relocs for a section.  */
1815
1816bfd_boolean
1817NAME (aout, slurp_reloc_table) (bfd *abfd, sec_ptr asect, asymbol **symbols)
1818{
1819  bfd_byte *rptr;
1820  bfd_size_type count;
1821  bfd_size_type reloc_size;
1822  void * relocs;
1823  arelent *reloc_cache;
1824  size_t each_size;
1825  unsigned int counter = 0;
1826  arelent *cache_ptr;
1827
1828  if (asect->relocation)
1829    return TRUE;
1830
1831  if (asect->flags & SEC_CONSTRUCTOR)
1832    return TRUE;
1833
1834  if (asect == obj_datasec (abfd))
1835    reloc_size = exec_hdr(abfd)->a_drsize;
1836  else if (asect == obj_textsec (abfd))
1837    reloc_size = exec_hdr(abfd)->a_trsize;
1838  else if (asect == obj_bsssec (abfd))
1839    reloc_size = 0;
1840  else
1841    {
1842      bfd_set_error (bfd_error_invalid_operation);
1843      return FALSE;
1844    }
1845
1846  if (bfd_seek (abfd, asect->rel_filepos, SEEK_SET) != 0)
1847    return FALSE;
1848
1849  each_size = obj_reloc_entry_size (abfd);
1850
1851  relocs = bfd_malloc (reloc_size);
1852  if (relocs == NULL && reloc_size != 0)
1853    return FALSE;
1854
1855  if (bfd_bread (relocs, reloc_size, abfd) != reloc_size)
1856    {
1857      free (relocs);
1858      return FALSE;
1859    }
1860
1861  count = reloc_size / each_size;
1862
1863  /* Count the number of NON-ZERO relocs, this is the count we want.  */
1864  {
1865    unsigned int real_count = 0;
1866
1867    for (counter = 0; counter < count; counter++)
1868      {
1869	int x;
1870
1871	x = GET_WORD (abfd, (char *) relocs + each_size * counter);
1872	if (x != 0)
1873	  real_count++;
1874      }
1875
1876    count = real_count;
1877  }
1878
1879  reloc_cache = bfd_zmalloc (count * sizeof (arelent));
1880  if (reloc_cache == NULL && count != 0)
1881    return FALSE;
1882
1883  cache_ptr = reloc_cache;
1884
1885  rptr = relocs;
1886  for (counter = 0;
1887       counter < count;
1888       counter++, rptr += RELOC_SIZE, cache_ptr++)
1889    {
1890      while (GET_WORD (abfd, (void *) rptr) == 0)
1891	{
1892	  rptr += RELOC_SIZE;
1893	  if ((char *) rptr >= (char *) relocs + reloc_size)
1894	    goto done;
1895	}
1896
1897      pdp11_aout_swap_reloc_in (abfd, rptr, cache_ptr,
1898				(bfd_size_type) ((char *) rptr - (char *) relocs),
1899				symbols,
1900				(bfd_size_type) bfd_get_symcount (abfd));
1901    }
1902 done:
1903  /* Just in case, if rptr >= relocs + reloc_size should happen
1904     too early.  */
1905  BFD_ASSERT (counter == count);
1906
1907  free (relocs);
1908
1909  asect->relocation = reloc_cache;
1910  asect->reloc_count = cache_ptr - reloc_cache;
1911
1912  return TRUE;
1913}
1914
1915/* Write out a relocation section into an object file.  */
1916
1917bfd_boolean
1918NAME (aout, squirt_out_relocs) (bfd *abfd, asection *section)
1919{
1920  arelent **generic;
1921  unsigned char *native;
1922  unsigned int count = section->reloc_count;
1923  bfd_size_type natsize;
1924
1925  natsize = section->size;
1926  native = bfd_zalloc (abfd, natsize);
1927  if (!native)
1928    return FALSE;
1929
1930  generic = section->orelocation;
1931  if (generic != NULL)
1932    {
1933      while (count > 0)
1934	{
1935	  bfd_byte *r;
1936
1937	  r = native + (*generic)->address;
1938	  pdp11_aout_swap_reloc_out (abfd, *generic, r);
1939	  count--;
1940	  generic++;
1941	}
1942    }
1943
1944  if (bfd_bwrite ((void *) native, natsize, abfd) != natsize)
1945    {
1946      bfd_release (abfd, native);
1947      return FALSE;
1948    }
1949
1950  bfd_release (abfd, native);
1951  return TRUE;
1952}
1953
1954/* This is stupid.  This function should be a boolean predicate.  */
1955
1956long
1957NAME (aout, canonicalize_reloc) (bfd *abfd,
1958				 sec_ptr section,
1959				 arelent **relptr,
1960				 asymbol **symbols)
1961{
1962  arelent *tblptr = section->relocation;
1963  unsigned int count;
1964
1965  if (section == obj_bsssec (abfd))
1966    {
1967      *relptr = NULL;
1968      return 0;
1969    }
1970
1971  if (!(tblptr || NAME (aout, slurp_reloc_table)(abfd, section, symbols)))
1972    return -1;
1973
1974  if (section->flags & SEC_CONSTRUCTOR)
1975    {
1976      arelent_chain *chain = section->constructor_chain;
1977
1978      for (count = 0; count < section->reloc_count; count ++)
1979	{
1980	  *relptr ++ = &chain->relent;
1981	  chain = chain->next;
1982	}
1983    }
1984  else
1985    {
1986      tblptr = section->relocation;
1987
1988      for (count = 0; count++ < section->reloc_count;)
1989	*relptr++ = tblptr++;
1990    }
1991
1992  *relptr = 0;
1993
1994  return section->reloc_count;
1995}
1996
1997long
1998NAME (aout, get_reloc_upper_bound) (bfd *abfd, sec_ptr asect)
1999{
2000  if (bfd_get_format (abfd) != bfd_object)
2001    {
2002      bfd_set_error (bfd_error_invalid_operation);
2003      return -1;
2004    }
2005
2006  if (asect->flags & SEC_CONSTRUCTOR)
2007    return (sizeof (arelent *) * (asect->reloc_count + 1));
2008
2009  if (asect == obj_datasec (abfd))
2010    return (sizeof (arelent *)
2011	    * ((exec_hdr (abfd)->a_drsize / obj_reloc_entry_size (abfd))
2012	       + 1));
2013
2014  if (asect == obj_textsec (abfd))
2015    return (sizeof (arelent *)
2016	    * ((exec_hdr (abfd)->a_trsize / obj_reloc_entry_size (abfd))
2017	       + 1));
2018
2019  /* TODO: why are there two if statements for obj_bsssec()? */
2020
2021  if (asect == obj_bsssec (abfd))
2022    return sizeof (arelent *);
2023
2024  if (asect == obj_bsssec (abfd))
2025    return 0;
2026
2027  bfd_set_error (bfd_error_invalid_operation);
2028  return -1;
2029}
2030
2031
2032long
2033NAME (aout, get_symtab_upper_bound) (bfd *abfd)
2034{
2035  if (!NAME (aout, slurp_symbol_table) (abfd))
2036    return -1;
2037
2038  return (bfd_get_symcount (abfd) + 1) * (sizeof (aout_symbol_type *));
2039}
2040
2041alent *
2042NAME (aout, get_lineno) (bfd * abfd ATTRIBUTE_UNUSED,
2043			 asymbol * symbol ATTRIBUTE_UNUSED)
2044{
2045  return NULL;
2046}
2047
2048void
2049NAME (aout, get_symbol_info) (bfd * abfd ATTRIBUTE_UNUSED,
2050			      asymbol *symbol,
2051			      symbol_info *ret)
2052{
2053  bfd_symbol_info (symbol, ret);
2054
2055  if (ret->type == '?')
2056    {
2057      int type_code = aout_symbol(symbol)->type & 0xff;
2058      const char *stab_name = bfd_get_stab_name (type_code);
2059      static char buf[10];
2060
2061      if (stab_name == NULL)
2062	{
2063	  sprintf(buf, "(%d)", type_code);
2064	  stab_name = buf;
2065	}
2066      ret->type = '-';
2067      ret->stab_type  = type_code;
2068      ret->stab_other = (unsigned) (aout_symbol(symbol)->other & 0xff);
2069      ret->stab_desc  = (unsigned) (aout_symbol(symbol)->desc & 0xffff);
2070      ret->stab_name  = stab_name;
2071    }
2072}
2073
2074void
2075NAME (aout, print_symbol) (bfd * abfd,
2076			   void * afile,
2077			   asymbol *symbol,
2078			   bfd_print_symbol_type how)
2079{
2080  FILE *file = (FILE *) afile;
2081
2082  switch (how)
2083    {
2084    case bfd_print_symbol_name:
2085      if (symbol->name)
2086	fprintf(file,"%s", symbol->name);
2087      break;
2088    case bfd_print_symbol_more:
2089      fprintf(file,"%4x %2x %2x",
2090	      (unsigned) (aout_symbol (symbol)->desc & 0xffff),
2091	      (unsigned) (aout_symbol (symbol)->other & 0xff),
2092	      (unsigned) (aout_symbol (symbol)->type));
2093      break;
2094    case bfd_print_symbol_all:
2095      {
2096	const char *section_name = symbol->section->name;
2097
2098	bfd_print_symbol_vandf (abfd, (void *) file, symbol);
2099
2100	fprintf (file," %-5s %04x %02x %02x",
2101		 section_name,
2102		 (unsigned) (aout_symbol (symbol)->desc & 0xffff),
2103		 (unsigned) (aout_symbol (symbol)->other & 0xff),
2104		 (unsigned) (aout_symbol (symbol)->type  & 0xff));
2105	if (symbol->name)
2106	  fprintf(file," %s", symbol->name);
2107      }
2108      break;
2109    }
2110}
2111
2112/* If we don't have to allocate more than 1MB to hold the generic
2113   symbols, we use the generic minisymbol method: it's faster, since
2114   it only translates the symbols once, not multiple times.  */
2115#define MINISYM_THRESHOLD (1000000 / sizeof (asymbol))
2116
2117/* Read minisymbols.  For minisymbols, we use the unmodified a.out
2118   symbols.  The minisymbol_to_symbol function translates these into
2119   BFD asymbol structures.  */
2120
2121long
2122NAME (aout, read_minisymbols) (bfd *abfd,
2123			       bfd_boolean dynamic,
2124			       void * *minisymsp,
2125			       unsigned int *sizep)
2126{
2127  if (dynamic)
2128    /* We could handle the dynamic symbols here as well, but it's
2129       easier to hand them off.  */
2130    return _bfd_generic_read_minisymbols (abfd, dynamic, minisymsp, sizep);
2131
2132  if (! aout_get_external_symbols (abfd))
2133    return -1;
2134
2135  if (obj_aout_external_sym_count (abfd) < MINISYM_THRESHOLD)
2136    return _bfd_generic_read_minisymbols (abfd, dynamic, minisymsp, sizep);
2137
2138  *minisymsp = (void *) obj_aout_external_syms (abfd);
2139
2140  /* By passing the external symbols back from this routine, we are
2141     giving up control over the memory block.  Clear
2142     obj_aout_external_syms, so that we do not try to free it
2143     ourselves.  */
2144  obj_aout_external_syms (abfd) = NULL;
2145
2146  *sizep = EXTERNAL_NLIST_SIZE;
2147  return obj_aout_external_sym_count (abfd);
2148}
2149
2150/* Convert a minisymbol to a BFD asymbol.  A minisymbol is just an
2151   unmodified a.out symbol.  The SYM argument is a structure returned
2152   by bfd_make_empty_symbol, which we fill in here.  */
2153
2154asymbol *
2155NAME (aout, minisymbol_to_symbol) (bfd *abfd,
2156				   bfd_boolean dynamic,
2157				   const void * minisym,
2158				   asymbol *sym)
2159{
2160  if (dynamic
2161      || obj_aout_external_sym_count (abfd) < MINISYM_THRESHOLD)
2162    return _bfd_generic_minisymbol_to_symbol (abfd, dynamic, minisym, sym);
2163
2164  memset (sym, 0, sizeof (aout_symbol_type));
2165
2166  /* We call translate_symbol_table to translate a single symbol.  */
2167  if (! (NAME (aout, translate_symbol_table)
2168	 (abfd,
2169	  (aout_symbol_type *) sym,
2170	  (struct external_nlist *) minisym,
2171	  (bfd_size_type) 1,
2172	  obj_aout_external_strings (abfd),
2173	  obj_aout_external_string_size (abfd),
2174	  FALSE)))
2175    return NULL;
2176
2177  return sym;
2178}
2179
2180/* Provided a BFD, a section and an offset into the section, calculate
2181   and return the name of the source file and the line nearest to the
2182   wanted location.  */
2183
2184bfd_boolean
2185NAME (aout, find_nearest_line) (bfd *abfd,
2186				asection *section,
2187				asymbol **symbols,
2188				bfd_vma offset,
2189				const char **filename_ptr,
2190				const char **functionname_ptr,
2191				unsigned int *line_ptr)
2192{
2193  /* Run down the file looking for the filename, function and linenumber.  */
2194  asymbol **p;
2195  const char *directory_name = NULL;
2196  const char *main_file_name = NULL;
2197  const char *current_file_name = NULL;
2198  const char *line_file_name = NULL; /* Value of current_file_name at line number.  */
2199  bfd_vma low_line_vma = 0;
2200  bfd_vma low_func_vma = 0;
2201  asymbol *func = 0;
2202  size_t filelen, funclen;
2203  char *buf;
2204
2205  *filename_ptr = abfd->filename;
2206  *functionname_ptr = 0;
2207  *line_ptr = 0;
2208
2209  if (symbols != NULL)
2210    {
2211      for (p = symbols; *p; p++)
2212	{
2213	  aout_symbol_type  *q = (aout_symbol_type *)(*p);
2214	next:
2215	  switch (q->type)
2216	    {
2217	    case N_TEXT:
2218	      /* If this looks like a file name symbol, and it comes after
2219		 the line number we have found so far, but before the
2220		 offset, then we have probably not found the right line
2221		 number.  */
2222	      if (q->symbol.value <= offset
2223		  && ((q->symbol.value > low_line_vma
2224		       && (line_file_name != NULL
2225			   || *line_ptr != 0))
2226		      || (q->symbol.value > low_func_vma
2227			  && func != NULL)))
2228		{
2229		  const char * symname;
2230
2231		  symname = q->symbol.name;
2232		  if (strcmp (symname + strlen (symname) - 2, ".o") == 0)
2233		    {
2234		      if (q->symbol.value > low_line_vma)
2235			{
2236			  *line_ptr = 0;
2237			  line_file_name = NULL;
2238			}
2239		      if (q->symbol.value > low_func_vma)
2240			func = NULL;
2241		    }
2242		}
2243	      break;
2244
2245	    case N_SO:
2246	      /* If this symbol is less than the offset, but greater than
2247		 the line number we have found so far, then we have not
2248		 found the right line number.  */
2249	      if (q->symbol.value <= offset)
2250		{
2251		  if (q->symbol.value > low_line_vma)
2252		    {
2253		      *line_ptr = 0;
2254		      line_file_name = NULL;
2255		    }
2256		  if (q->symbol.value > low_func_vma)
2257		    func = NULL;
2258		}
2259
2260	      main_file_name = current_file_name = q->symbol.name;
2261	      /* Look ahead to next symbol to check if that too is an N_SO.  */
2262	      p++;
2263	      if (*p == NULL)
2264		break;
2265	      q = (aout_symbol_type *)(*p);
2266	      if (q->type != (int) N_SO)
2267		goto next;
2268
2269	      /* Found a second N_SO  First is directory; second is filename.  */
2270	      directory_name = current_file_name;
2271	      main_file_name = current_file_name = q->symbol.name;
2272	      if (obj_textsec(abfd) != section)
2273		goto done;
2274	      break;
2275	    case N_SOL:
2276	      current_file_name = q->symbol.name;
2277	      break;
2278
2279	    case N_SLINE:
2280	    case N_DSLINE:
2281	    case N_BSLINE:
2282	      /* We'll keep this if it resolves nearer than the one we have
2283		 already.  */
2284	      if (q->symbol.value >= low_line_vma
2285		  && q->symbol.value <= offset)
2286		{
2287		  *line_ptr = q->desc;
2288		  low_line_vma = q->symbol.value;
2289		  line_file_name = current_file_name;
2290		}
2291	      break;
2292
2293	    case N_FUN:
2294	      {
2295		/* We'll keep this if it is nearer than the one we have already.  */
2296		if (q->symbol.value >= low_func_vma &&
2297		    q->symbol.value <= offset)
2298		  {
2299		    low_func_vma = q->symbol.value;
2300		    func = (asymbol *) q;
2301		  }
2302		else if (q->symbol.value > offset)
2303		  goto done;
2304	      }
2305	      break;
2306	    }
2307	}
2308    }
2309
2310 done:
2311  if (*line_ptr != 0)
2312    main_file_name = line_file_name;
2313
2314  if (main_file_name == NULL
2315      || main_file_name[0] == '/'
2316      || directory_name == NULL)
2317    filelen = 0;
2318  else
2319    filelen = strlen (directory_name) + strlen (main_file_name);
2320  if (func == NULL)
2321    funclen = 0;
2322  else
2323    funclen = strlen (bfd_asymbol_name (func));
2324
2325  if (adata (abfd).line_buf != NULL)
2326    free (adata (abfd).line_buf);
2327  if (filelen + funclen == 0)
2328    adata (abfd).line_buf = buf = NULL;
2329  else
2330    {
2331      buf = bfd_malloc ((bfd_size_type) filelen + funclen + 3);
2332      adata (abfd).line_buf = buf;
2333      if (buf == NULL)
2334	return FALSE;
2335    }
2336
2337  if (main_file_name != NULL)
2338    {
2339      if (main_file_name[0] == '/' || directory_name == NULL)
2340	*filename_ptr = main_file_name;
2341      else
2342	{
2343	  sprintf (buf, "%s%s", directory_name, main_file_name);
2344	  *filename_ptr = buf;
2345	  buf += filelen + 1;
2346	}
2347    }
2348
2349  if (func)
2350    {
2351      const char *function = func->name;
2352      char *colon;
2353
2354      /* The caller expects a symbol name.  We actually have a
2355	 function name, without the leading underscore.  Put the
2356	 underscore back in, so that the caller gets a symbol name.  */
2357      if (bfd_get_symbol_leading_char (abfd) == '\0')
2358	strcpy (buf, function);
2359      else
2360	{
2361	  buf[0] = bfd_get_symbol_leading_char (abfd);
2362	  strcpy (buf + 1, function);
2363	}
2364
2365      /* Have to remove : stuff.  */
2366      colon = strchr (buf, ':');
2367      if (colon != NULL)
2368	*colon = '\0';
2369      *functionname_ptr = buf;
2370    }
2371
2372  return TRUE;
2373}
2374
2375int
2376NAME (aout, sizeof_headers) (bfd *abfd,
2377			     struct bfd_link_info *info ATTRIBUTE_UNUSED)
2378{
2379  return adata (abfd).exec_bytes_size;
2380}
2381
2382/* Free all information we have cached for this BFD.  We can always
2383   read it again later if we need it.  */
2384
2385bfd_boolean
2386NAME (aout, bfd_free_cached_info) (bfd *abfd)
2387{
2388  asection *o;
2389
2390  if (bfd_get_format (abfd) != bfd_object)
2391    return TRUE;
2392
2393#define BFCI_FREE(x) if (x != NULL) { free (x); x = NULL; }
2394  BFCI_FREE (obj_aout_symbols (abfd));
2395
2396#ifdef USE_MMAP
2397  obj_aout_external_syms (abfd) = 0;
2398  bfd_free_window (&obj_aout_sym_window (abfd));
2399  bfd_free_window (&obj_aout_string_window (abfd));
2400  obj_aout_external_strings (abfd) = 0;
2401#else
2402  BFCI_FREE (obj_aout_external_syms (abfd));
2403  BFCI_FREE (obj_aout_external_strings (abfd));
2404#endif
2405  for (o = abfd->sections; o != NULL; o = o->next)
2406    BFCI_FREE (o->relocation);
2407#undef BFCI_FREE
2408
2409  return TRUE;
2410}
2411
2412/* Routine to create an entry in an a.out link hash table.  */
2413
2414struct bfd_hash_entry *
2415NAME (aout, link_hash_newfunc) (struct bfd_hash_entry *entry,
2416				struct bfd_hash_table *table,
2417				const char *string)
2418{
2419  struct aout_link_hash_entry *ret = (struct aout_link_hash_entry *) entry;
2420
2421  /* Allocate the structure if it has not already been allocated by a
2422     subclass.  */
2423  if (ret == NULL)
2424    ret = bfd_hash_allocate (table, sizeof (* ret));
2425  if (ret == NULL)
2426    return NULL;
2427
2428  /* Call the allocation method of the superclass.  */
2429  ret = (struct aout_link_hash_entry *)
2430	 _bfd_link_hash_newfunc ((struct bfd_hash_entry *) ret, table, string);
2431  if (ret)
2432    {
2433      /* Set local fields.  */
2434      ret->written = FALSE;
2435      ret->indx = -1;
2436    }
2437
2438  return (struct bfd_hash_entry *) ret;
2439}
2440
2441/* Initialize an a.out link hash table.  */
2442
2443bfd_boolean
2444NAME (aout, link_hash_table_init) (struct aout_link_hash_table *table,
2445				   bfd *abfd,
2446				   struct bfd_hash_entry *(*newfunc) (struct bfd_hash_entry *,
2447								     struct bfd_hash_table *,
2448								     const char *),
2449				   unsigned int entsize)
2450{
2451  return _bfd_link_hash_table_init (&table->root, abfd, newfunc, entsize);
2452}
2453
2454/* Create an a.out link hash table.  */
2455
2456struct bfd_link_hash_table *
2457NAME (aout, link_hash_table_create) (bfd *abfd)
2458{
2459  struct aout_link_hash_table *ret;
2460  bfd_size_type amt = sizeof (struct aout_link_hash_table);
2461
2462  ret = bfd_alloc (abfd, amt);
2463  if (ret == NULL)
2464    return NULL;
2465  if (! NAME (aout, link_hash_table_init) (ret, abfd,
2466					   NAME (aout, link_hash_newfunc),
2467					   sizeof (struct aout_link_hash_entry)))
2468    {
2469      free (ret);
2470      return NULL;
2471    }
2472  return &ret->root;
2473}
2474
2475/* Free up the internal symbols read from an a.out file.  */
2476
2477static bfd_boolean
2478aout_link_free_symbols (bfd *abfd)
2479{
2480  if (obj_aout_external_syms (abfd) != NULL)
2481    {
2482#ifdef USE_MMAP
2483      bfd_free_window (&obj_aout_sym_window (abfd));
2484#else
2485      free ((void *) obj_aout_external_syms (abfd));
2486#endif
2487      obj_aout_external_syms (abfd) = NULL;
2488    }
2489
2490  if (obj_aout_external_strings (abfd) != NULL)
2491    {
2492#ifdef USE_MMAP
2493      bfd_free_window (&obj_aout_string_window (abfd));
2494#else
2495      free ((void *) obj_aout_external_strings (abfd));
2496#endif
2497      obj_aout_external_strings (abfd) = NULL;
2498    }
2499  return TRUE;
2500}
2501
2502/* Given an a.out BFD, add symbols to the global hash table as
2503   appropriate.  */
2504
2505bfd_boolean
2506NAME (aout, link_add_symbols) (bfd *abfd, struct bfd_link_info *info)
2507{
2508  switch (bfd_get_format (abfd))
2509    {
2510    case bfd_object:
2511      return aout_link_add_object_symbols (abfd, info);
2512    case bfd_archive:
2513      return _bfd_generic_link_add_archive_symbols
2514	(abfd, info, aout_link_check_archive_element);
2515    default:
2516      bfd_set_error (bfd_error_wrong_format);
2517      return FALSE;
2518    }
2519}
2520
2521/* Add symbols from an a.out object file.  */
2522
2523static bfd_boolean
2524aout_link_add_object_symbols (bfd *abfd, struct bfd_link_info *info)
2525{
2526  if (! aout_get_external_symbols (abfd))
2527    return FALSE;
2528  if (! aout_link_add_symbols (abfd, info))
2529    return FALSE;
2530  if (! info->keep_memory)
2531    {
2532      if (! aout_link_free_symbols (abfd))
2533	return FALSE;
2534    }
2535  return TRUE;
2536}
2537
2538/* Look through the internal symbols to see if this object file should
2539   be included in the link.  We should include this object file if it
2540   defines any symbols which are currently undefined.  If this object
2541   file defines a common symbol, then we may adjust the size of the
2542   known symbol but we do not include the object file in the link
2543   (unless there is some other reason to include it).  */
2544
2545static bfd_boolean
2546aout_link_check_ar_symbols (bfd *abfd,
2547			    struct bfd_link_info *info,
2548			    bfd_boolean *pneeded,
2549			    bfd **subsbfd)
2550{
2551  struct external_nlist *p;
2552  struct external_nlist *pend;
2553  char *strings;
2554
2555  *pneeded = FALSE;
2556
2557  /* Look through all the symbols.  */
2558  p = obj_aout_external_syms (abfd);
2559  pend = p + obj_aout_external_sym_count (abfd);
2560  strings = obj_aout_external_strings (abfd);
2561  for (; p < pend; p++)
2562    {
2563      int type = H_GET_8 (abfd, p->e_type);
2564      const char *name;
2565      struct bfd_link_hash_entry *h;
2566
2567      /* Ignore symbols that are not externally visible.  This is an
2568	 optimization only, as we check the type more thoroughly
2569	 below.  */
2570      if ((type & N_EXT) == 0
2571	  || type == N_FN)
2572	continue;
2573
2574      name = strings + GET_WORD (abfd, p->e_strx);
2575      h = bfd_link_hash_lookup (info->hash, name, FALSE, FALSE, TRUE);
2576
2577      /* We are only interested in symbols that are currently
2578	 undefined or common.  */
2579      if (h == NULL
2580	  || (h->type != bfd_link_hash_undefined
2581	      && h->type != bfd_link_hash_common))
2582	continue;
2583
2584      if (type == (N_TEXT | N_EXT)
2585	  || type == (N_DATA | N_EXT)
2586	  || type == (N_BSS | N_EXT)
2587	  || type == (N_ABS | N_EXT))
2588	{
2589	  /* This object file defines this symbol.  We must link it
2590	     in.  This is true regardless of whether the current
2591	     definition of the symbol is undefined or common.  If the
2592	     current definition is common, we have a case in which we
2593	     have already seen an object file including
2594	         int a;
2595	     and this object file from the archive includes
2596	         int a = 5;
2597	     In such a case we must include this object file.
2598
2599	     FIXME: The SunOS 4.1.3 linker will pull in the archive
2600	     element if the symbol is defined in the .data section,
2601	     but not if it is defined in the .text section.  That
2602	     seems a bit crazy to me, and I haven't implemented it.
2603	     However, it might be correct.  */
2604	  if (!(*info->callbacks
2605		->add_archive_element) (info, abfd, name, subsbfd))
2606	    return FALSE;
2607	  *pneeded = TRUE;
2608	  return TRUE;
2609	}
2610
2611      if (type == (N_UNDF | N_EXT))
2612	{
2613	  bfd_vma value;
2614
2615	  value = GET_WORD (abfd, p->e_value);
2616	  if (value != 0)
2617	    {
2618	      /* This symbol is common in the object from the archive
2619		 file.  */
2620	      if (h->type == bfd_link_hash_undefined)
2621		{
2622		  bfd *symbfd;
2623		  unsigned int power;
2624
2625		  symbfd = h->u.undef.abfd;
2626		  if (symbfd == NULL)
2627		    {
2628		      /* This symbol was created as undefined from
2629			 outside BFD.  We assume that we should link
2630			 in the object file.  This is done for the -u
2631			 option in the linker.  */
2632		      if (!(*info->callbacks
2633			    ->add_archive_element) (info, abfd, name, subsbfd))
2634			return FALSE;
2635		      *pneeded = TRUE;
2636		      return TRUE;
2637		    }
2638		  /* Turn the current link symbol into a common
2639		     symbol.  It is already on the undefs list.  */
2640		  h->type = bfd_link_hash_common;
2641		  h->u.c.p = bfd_hash_allocate (&info->hash->table,
2642						sizeof (struct bfd_link_hash_common_entry));
2643		  if (h->u.c.p == NULL)
2644		    return FALSE;
2645
2646		  h->u.c.size = value;
2647
2648		  /* FIXME: This isn't quite right.  The maximum
2649		     alignment of a common symbol should be set by the
2650		     architecture of the output file, not of the input
2651		     file.  */
2652		  power = bfd_log2 (value);
2653		  if (power > bfd_get_arch_info (abfd)->section_align_power)
2654		    power = bfd_get_arch_info (abfd)->section_align_power;
2655		  h->u.c.p->alignment_power = power;
2656
2657		  h->u.c.p->section = bfd_make_section_old_way (symbfd,
2658								"COMMON");
2659		}
2660	      else
2661		{
2662		  /* Adjust the size of the common symbol if
2663		     necessary.  */
2664		  if (value > h->u.c.size)
2665		    h->u.c.size = value;
2666		}
2667	    }
2668	}
2669    }
2670
2671  /* We do not need this object file.  */
2672  return TRUE;
2673}
2674
2675/* Check a single archive element to see if we need to include it in
2676   the link.  *PNEEDED is set according to whether this element is
2677   needed in the link or not.  This is called from
2678   _bfd_generic_link_add_archive_symbols.  */
2679
2680static bfd_boolean
2681aout_link_check_archive_element (bfd *abfd,
2682				 struct bfd_link_info *info,
2683				 bfd_boolean *pneeded)
2684{
2685  bfd *oldbfd;
2686  bfd_boolean needed;
2687
2688  if (!aout_get_external_symbols (abfd))
2689    return FALSE;
2690
2691  oldbfd = abfd;
2692  if (!aout_link_check_ar_symbols (abfd, info, pneeded, &abfd))
2693    return FALSE;
2694
2695  needed = *pneeded;
2696  if (needed)
2697    {
2698      /* Potentially, the add_archive_element hook may have set a
2699	 substitute BFD for us.  */
2700      if (abfd != oldbfd)
2701	{
2702	  if (!info->keep_memory
2703	      && !aout_link_free_symbols (oldbfd))
2704	    return FALSE;
2705	  if (!aout_get_external_symbols (abfd))
2706	    return FALSE;
2707	}
2708      if (!aout_link_add_symbols (abfd, info))
2709	return FALSE;
2710    }
2711
2712  if (!info->keep_memory || !needed)
2713    {
2714      if (!aout_link_free_symbols (abfd))
2715	return FALSE;
2716    }
2717
2718  return TRUE;
2719}
2720
2721/* Add all symbols from an object file to the hash table.  */
2722
2723static bfd_boolean
2724aout_link_add_symbols (bfd *abfd, struct bfd_link_info *info)
2725{
2726  bfd_boolean (*add_one_symbol)
2727    (struct bfd_link_info *, bfd *, const char *, flagword, asection *,
2728     bfd_vma, const char *, bfd_boolean, bfd_boolean,
2729     struct bfd_link_hash_entry **);
2730  struct external_nlist *syms;
2731  bfd_size_type sym_count;
2732  char *strings;
2733  bfd_boolean copy;
2734  struct aout_link_hash_entry **sym_hash;
2735  struct external_nlist *p;
2736  struct external_nlist *pend;
2737
2738  syms = obj_aout_external_syms (abfd);
2739  sym_count = obj_aout_external_sym_count (abfd);
2740  strings = obj_aout_external_strings (abfd);
2741  if (info->keep_memory)
2742    copy = FALSE;
2743  else
2744    copy = TRUE;
2745
2746  if (aout_backend_info (abfd)->add_dynamic_symbols != NULL)
2747    {
2748      if (! ((*aout_backend_info (abfd)->add_dynamic_symbols)
2749	     (abfd, info, &syms, &sym_count, &strings)))
2750	return FALSE;
2751    }
2752
2753  /* We keep a list of the linker hash table entries that correspond
2754     to particular symbols.  We could just look them up in the hash
2755     table, but keeping the list is more efficient.  Perhaps this
2756     should be conditional on info->keep_memory.  */
2757  sym_hash = bfd_alloc (abfd,
2758			sym_count * sizeof (struct aout_link_hash_entry *));
2759  if (sym_hash == NULL && sym_count != 0)
2760    return FALSE;
2761  obj_aout_sym_hashes (abfd) = sym_hash;
2762
2763  add_one_symbol = aout_backend_info (abfd)->add_one_symbol;
2764  if (add_one_symbol == NULL)
2765    add_one_symbol = _bfd_generic_link_add_one_symbol;
2766
2767  p = syms;
2768  pend = p + sym_count;
2769  for (; p < pend; p++, sym_hash++)
2770    {
2771      int type;
2772      const char *name;
2773      bfd_vma value;
2774      asection *section;
2775      flagword flags;
2776      const char *string;
2777
2778      *sym_hash = NULL;
2779
2780      type = H_GET_8 (abfd, p->e_type);
2781
2782      name = strings + GET_WORD (abfd, p->e_strx);
2783      value = GET_WORD (abfd, p->e_value);
2784      flags = BSF_GLOBAL;
2785      string = NULL;
2786      switch (type)
2787	{
2788	default:
2789	  /* Anything else should be a debugging symbol.  */
2790	  BFD_ASSERT ((type & N_STAB) != 0);
2791	  continue;
2792
2793	case N_UNDF:
2794	case N_ABS:
2795	case N_TEXT:
2796	case N_DATA:
2797	case N_BSS:
2798	case N_REG:
2799	case N_FN:
2800	  /* Ignore symbols that are not externally visible.  */
2801	  continue;
2802
2803	case N_UNDF | N_EXT:
2804	  if (value == 0)
2805	    {
2806	      section = bfd_und_section_ptr;
2807	      flags = 0;
2808	    }
2809	  else
2810	    section = bfd_com_section_ptr;
2811	  break;
2812	case N_ABS | N_EXT:
2813	  section = bfd_abs_section_ptr;
2814	  break;
2815	case N_TEXT | N_EXT:
2816	  section = obj_textsec (abfd);
2817	  value -= bfd_get_section_vma (abfd, section);
2818	  break;
2819	case N_DATA | N_EXT:
2820	  /* Treat N_SETV symbols as N_DATA symbol; see comment in
2821	     translate_from_native_sym_flags.  */
2822	  section = obj_datasec (abfd);
2823	  value -= bfd_get_section_vma (abfd, section);
2824	  break;
2825	case N_BSS | N_EXT:
2826	  section = obj_bsssec (abfd);
2827	  value -= bfd_get_section_vma (abfd, section);
2828	  break;
2829	}
2830
2831      if (! ((*add_one_symbol)
2832	     (info, abfd, name, flags, section, value, string, copy, FALSE,
2833	      (struct bfd_link_hash_entry **) sym_hash)))
2834	return FALSE;
2835
2836      /* Restrict the maximum alignment of a common symbol based on
2837	 the architecture, since a.out has no way to represent
2838	 alignment requirements of a section in a .o file.  FIXME:
2839	 This isn't quite right: it should use the architecture of the
2840	 output file, not the input files.  */
2841      if ((*sym_hash)->root.type == bfd_link_hash_common
2842	  && ((*sym_hash)->root.u.c.p->alignment_power >
2843	      bfd_get_arch_info (abfd)->section_align_power))
2844	(*sym_hash)->root.u.c.p->alignment_power =
2845	  bfd_get_arch_info (abfd)->section_align_power;
2846
2847      /* If this is a set symbol, and we are not building sets, then
2848	 it is possible for the hash entry to not have been set.  In
2849	 such a case, treat the symbol as not globally defined.  */
2850      if ((*sym_hash)->root.type == bfd_link_hash_new)
2851	{
2852	  BFD_ASSERT ((flags & BSF_CONSTRUCTOR) != 0);
2853	  *sym_hash = NULL;
2854	}
2855    }
2856
2857  return TRUE;
2858}
2859
2860/* Look up an entry in an the header file hash table.  */
2861
2862#define aout_link_includes_lookup(table, string, create, copy) \
2863  ((struct aout_link_includes_entry *) \
2864   bfd_hash_lookup (&(table)->root, (string), (create), (copy)))
2865
2866/* The function to create a new entry in the header file hash table.  */
2867
2868static struct bfd_hash_entry *
2869aout_link_includes_newfunc (struct bfd_hash_entry *entry,
2870			    struct bfd_hash_table *table,
2871			    const char *string)
2872{
2873  struct aout_link_includes_entry * ret =
2874    (struct aout_link_includes_entry *) entry;
2875
2876  /* Allocate the structure if it has not already been allocated by a
2877     subclass.  */
2878  if (ret == NULL)
2879    ret = bfd_hash_allocate (table,
2880			     sizeof (struct aout_link_includes_entry));
2881  if (ret == NULL)
2882    return NULL;
2883
2884  /* Call the allocation method of the superclass.  */
2885  ret = ((struct aout_link_includes_entry *)
2886	 bfd_hash_newfunc ((struct bfd_hash_entry *) ret, table, string));
2887  if (ret)
2888    /* Set local fields.  */
2889    ret->totals = NULL;
2890
2891  return (struct bfd_hash_entry *) ret;
2892}
2893
2894static bfd_boolean
2895aout_link_write_other_symbol (struct aout_link_hash_entry *h, void * data)
2896{
2897  struct aout_final_link_info *finfo = (struct aout_final_link_info *) data;
2898  bfd *output_bfd;
2899  int type;
2900  bfd_vma val;
2901  struct external_nlist outsym;
2902  bfd_size_type indx;
2903  bfd_size_type amt;
2904
2905  if (h->root.type == bfd_link_hash_warning)
2906    {
2907      h = (struct aout_link_hash_entry *) h->root.u.i.link;
2908      if (h->root.type == bfd_link_hash_new)
2909	return TRUE;
2910    }
2911
2912  output_bfd = finfo->output_bfd;
2913
2914  if (aout_backend_info (output_bfd)->write_dynamic_symbol != NULL)
2915    {
2916      if (! ((*aout_backend_info (output_bfd)->write_dynamic_symbol)
2917	     (output_bfd, finfo->info, h)))
2918	{
2919	  /* FIXME: No way to handle errors.  */
2920	  abort ();
2921	}
2922    }
2923
2924  if (h->written)
2925    return TRUE;
2926
2927  h->written = TRUE;
2928
2929  /* An indx of -2 means the symbol must be written.  */
2930  if (h->indx != -2
2931      && (finfo->info->strip == strip_all
2932	  || (finfo->info->strip == strip_some
2933	      && bfd_hash_lookup (finfo->info->keep_hash, h->root.root.string,
2934				  FALSE, FALSE) == NULL)))
2935    return TRUE;
2936
2937  switch (h->root.type)
2938    {
2939    default:
2940      abort ();
2941      /* Avoid variable not initialized warnings.  */
2942      return TRUE;
2943    case bfd_link_hash_new:
2944      /* This can happen for set symbols when sets are not being
2945         built.  */
2946      return TRUE;
2947    case bfd_link_hash_undefined:
2948      type = N_UNDF | N_EXT;
2949      val = 0;
2950      break;
2951    case bfd_link_hash_defined:
2952    case bfd_link_hash_defweak:
2953      {
2954	asection *sec;
2955
2956	sec = h->root.u.def.section->output_section;
2957	BFD_ASSERT (bfd_is_abs_section (sec)
2958		    || sec->owner == output_bfd);
2959	if (sec == obj_textsec (output_bfd))
2960	  type = h->root.type == bfd_link_hash_defined ? N_TEXT : N_WEAKT;
2961	else if (sec == obj_datasec (output_bfd))
2962	  type = h->root.type == bfd_link_hash_defined ? N_DATA : N_WEAKD;
2963	else if (sec == obj_bsssec (output_bfd))
2964	  type = h->root.type == bfd_link_hash_defined ? N_BSS : N_WEAKB;
2965	else
2966	  type = h->root.type == bfd_link_hash_defined ? N_ABS : N_WEAKA;
2967	type |= N_EXT;
2968	val = (h->root.u.def.value
2969	       + sec->vma
2970	       + h->root.u.def.section->output_offset);
2971      }
2972      break;
2973    case bfd_link_hash_common:
2974      type = N_UNDF | N_EXT;
2975      val = h->root.u.c.size;
2976      break;
2977    case bfd_link_hash_undefweak:
2978      type = N_WEAKU;
2979      val = 0;
2980    case bfd_link_hash_indirect:
2981    case bfd_link_hash_warning:
2982      /* FIXME: Ignore these for now.  The circumstances under which
2983	 they should be written out are not clear to me.  */
2984      return TRUE;
2985    }
2986
2987  H_PUT_8 (output_bfd, type, outsym.e_type);
2988  indx = add_to_stringtab (output_bfd, finfo->strtab, h->root.root.string,
2989			   FALSE);
2990  if (indx == (bfd_size_type) -1)
2991    /* FIXME: No way to handle errors.  */
2992    abort ();
2993
2994  PUT_WORD (output_bfd, indx, outsym.e_strx);
2995  PUT_WORD (output_bfd, val, outsym.e_value);
2996
2997  amt = EXTERNAL_NLIST_SIZE;
2998  if (bfd_seek (output_bfd, finfo->symoff, SEEK_SET) != 0
2999      || bfd_bwrite ((void *) &outsym, amt, output_bfd) != amt)
3000    /* FIXME: No way to handle errors.  */
3001    abort ();
3002
3003  finfo->symoff += amt;
3004  h->indx = obj_aout_external_sym_count (output_bfd);
3005  ++obj_aout_external_sym_count (output_bfd);
3006
3007  return TRUE;
3008}
3009
3010/* Handle a link order which is supposed to generate a reloc.  */
3011
3012static bfd_boolean
3013aout_link_reloc_link_order (struct aout_final_link_info *finfo,
3014			    asection *o,
3015			    struct bfd_link_order *p)
3016{
3017  struct bfd_link_order_reloc *pr;
3018  int r_index;
3019  int r_extern;
3020  reloc_howto_type *howto;
3021  file_ptr *reloff_ptr;
3022  struct reloc_std_external srel;
3023  void * rel_ptr;
3024  bfd_size_type rel_size;
3025
3026  pr = p->u.reloc.p;
3027
3028  if (p->type == bfd_section_reloc_link_order)
3029    {
3030      r_extern = 0;
3031      if (bfd_is_abs_section (pr->u.section))
3032	r_index = N_ABS | N_EXT;
3033      else
3034	{
3035	  BFD_ASSERT (pr->u.section->owner == finfo->output_bfd);
3036	  r_index = pr->u.section->target_index;
3037	}
3038    }
3039  else
3040    {
3041      struct aout_link_hash_entry *h;
3042
3043      BFD_ASSERT (p->type == bfd_symbol_reloc_link_order);
3044      r_extern = 1;
3045      h = ((struct aout_link_hash_entry *)
3046	   bfd_wrapped_link_hash_lookup (finfo->output_bfd, finfo->info,
3047					 pr->u.name, FALSE, FALSE, TRUE));
3048      if (h != NULL
3049	  && h->indx >= 0)
3050	r_index = h->indx;
3051      else if (h != NULL)
3052	{
3053	  /* We decided to strip this symbol, but it turns out that we
3054	     can't.  Note that we lose the other and desc information
3055	     here.  I don't think that will ever matter for a global
3056	     symbol.  */
3057	  h->indx = -2;
3058	  h->written = FALSE;
3059	  if (! aout_link_write_other_symbol (h, (void *) finfo))
3060	    return FALSE;
3061	  r_index = h->indx;
3062	}
3063      else
3064	{
3065	  if (! ((*finfo->info->callbacks->unattached_reloc)
3066		 (finfo->info, pr->u.name, NULL, NULL, (bfd_vma) 0)))
3067	    return FALSE;
3068	  r_index = 0;
3069	}
3070    }
3071
3072  howto = bfd_reloc_type_lookup (finfo->output_bfd, pr->reloc);
3073  if (howto == 0)
3074    {
3075      bfd_set_error (bfd_error_bad_value);
3076      return FALSE;
3077    }
3078
3079  if (o == obj_textsec (finfo->output_bfd))
3080    reloff_ptr = &finfo->treloff;
3081  else if (o == obj_datasec (finfo->output_bfd))
3082    reloff_ptr = &finfo->dreloff;
3083  else
3084    abort ();
3085
3086#ifdef MY_put_reloc
3087  MY_put_reloc(finfo->output_bfd, r_extern, r_index, p->offset, howto,
3088	       &srel);
3089#else
3090  {
3091    int r_pcrel;
3092    int r_baserel;
3093    int r_jmptable;
3094    int r_relative;
3095    int r_length;
3096
3097    fprintf (stderr, "TODO: line %d in bfd/pdp11.c\n", __LINE__);
3098
3099    r_pcrel = howto->pc_relative;
3100    r_baserel = (howto->type & 8) != 0;
3101    r_jmptable = (howto->type & 16) != 0;
3102    r_relative = (howto->type & 32) != 0;
3103    r_length = howto->size;
3104
3105    PUT_WORD (finfo->output_bfd, p->offset, srel.r_address);
3106    if (bfd_header_big_endian (finfo->output_bfd))
3107      {
3108	srel.r_index[0] = r_index >> 16;
3109	srel.r_index[1] = r_index >> 8;
3110	srel.r_index[2] = r_index;
3111	srel.r_type[0] =
3112	  ((r_extern ?     RELOC_STD_BITS_EXTERN_BIG : 0)
3113	   | (r_pcrel ?    RELOC_STD_BITS_PCREL_BIG : 0)
3114	   | (r_baserel ?  RELOC_STD_BITS_BASEREL_BIG : 0)
3115	   | (r_jmptable ? RELOC_STD_BITS_JMPTABLE_BIG : 0)
3116	   | (r_relative ? RELOC_STD_BITS_RELATIVE_BIG : 0)
3117	   | (r_length <<  RELOC_STD_BITS_LENGTH_SH_BIG));
3118      }
3119    else
3120      {
3121	srel.r_index[2] = r_index >> 16;
3122	srel.r_index[1] = r_index >> 8;
3123	srel.r_index[0] = r_index;
3124	srel.r_type[0] =
3125	  ((r_extern ?     RELOC_STD_BITS_EXTERN_LITTLE : 0)
3126	   | (r_pcrel ?    RELOC_STD_BITS_PCREL_LITTLE : 0)
3127	   | (r_baserel ?  RELOC_STD_BITS_BASEREL_LITTLE : 0)
3128	   | (r_jmptable ? RELOC_STD_BITS_JMPTABLE_LITTLE : 0)
3129	   | (r_relative ? RELOC_STD_BITS_RELATIVE_LITTLE : 0)
3130	   | (r_length <<  RELOC_STD_BITS_LENGTH_SH_LITTLE));
3131      }
3132  }
3133#endif
3134  rel_ptr = (void *) &srel;
3135
3136  /* We have to write the addend into the object file, since
3137     standard a.out relocs are in place.  It would be more
3138     reliable if we had the current contents of the file here,
3139     rather than assuming zeroes, but we can't read the file since
3140     it was opened using bfd_openw.  */
3141  if (pr->addend != 0)
3142    {
3143      bfd_size_type size;
3144      bfd_reloc_status_type r;
3145      bfd_byte *buf;
3146      bfd_boolean ok;
3147
3148      size = bfd_get_reloc_size (howto);
3149      buf = bfd_zmalloc (size);
3150      if (buf == NULL)
3151	return FALSE;
3152      r = MY_relocate_contents (howto, finfo->output_bfd,
3153				pr->addend, buf);
3154      switch (r)
3155	{
3156	case bfd_reloc_ok:
3157	  break;
3158	default:
3159	case bfd_reloc_outofrange:
3160	  abort ();
3161	case bfd_reloc_overflow:
3162	  if (! ((*finfo->info->callbacks->reloc_overflow)
3163		 (finfo->info, NULL,
3164		  (p->type == bfd_section_reloc_link_order
3165		   ? bfd_section_name (finfo->output_bfd,
3166				       pr->u.section)
3167		   : pr->u.name),
3168		  howto->name, pr->addend, NULL,
3169		  (asection *) NULL, (bfd_vma) 0)))
3170	    {
3171	      free (buf);
3172	      return FALSE;
3173	    }
3174	  break;
3175	}
3176      ok = bfd_set_section_contents (finfo->output_bfd, o,
3177				     (void *) buf,
3178				     (file_ptr) p->offset,
3179				     size);
3180      free (buf);
3181      if (! ok)
3182	return FALSE;
3183    }
3184
3185  rel_size = obj_reloc_entry_size (finfo->output_bfd);
3186  if (bfd_seek (finfo->output_bfd, *reloff_ptr, SEEK_SET) != 0
3187      || bfd_bwrite (rel_ptr, rel_size, finfo->output_bfd) != rel_size)
3188    return FALSE;
3189
3190  *reloff_ptr += rel_size;
3191
3192  /* Assert that the relocs have not run into the symbols, and that n
3193     the text relocs have not run into the data relocs.  */
3194  BFD_ASSERT (*reloff_ptr <= obj_sym_filepos (finfo->output_bfd)
3195	      && (reloff_ptr != &finfo->treloff
3196		  || (*reloff_ptr
3197		      <= obj_datasec (finfo->output_bfd)->rel_filepos)));
3198
3199  return TRUE;
3200}
3201
3202/* Get the section corresponding to a reloc index.  */
3203
3204static inline asection *
3205aout_reloc_type_to_section (bfd *abfd, int type)
3206{
3207  switch (type)
3208    {
3209    case RTEXT:	return obj_textsec (abfd);
3210    case RDATA: return obj_datasec (abfd);
3211    case RBSS:  return obj_bsssec (abfd);
3212    case RABS:  return bfd_abs_section_ptr;
3213    case REXT:  return bfd_und_section_ptr;
3214    default:    abort ();
3215    }
3216}
3217
3218static bfd_boolean
3219pdp11_aout_link_input_section (struct aout_final_link_info *finfo,
3220			       bfd *input_bfd,
3221			       asection *input_section,
3222			       bfd_byte *relocs,
3223			       bfd_size_type rel_size,
3224			       bfd_byte *contents)
3225{
3226  bfd_boolean (*check_dynamic_reloc)
3227    (struct bfd_link_info *, bfd *, asection *,
3228     struct aout_link_hash_entry *, void *, bfd_byte *, bfd_boolean *,
3229     bfd_vma *);
3230  bfd *output_bfd;
3231  bfd_boolean relocatable;
3232  struct external_nlist *syms;
3233  char *strings;
3234  struct aout_link_hash_entry **sym_hashes;
3235  int *symbol_map;
3236  bfd_byte *rel;
3237  bfd_byte *rel_end;
3238
3239  output_bfd = finfo->output_bfd;
3240  check_dynamic_reloc = aout_backend_info (output_bfd)->check_dynamic_reloc;
3241
3242  BFD_ASSERT (obj_reloc_entry_size (input_bfd) == RELOC_SIZE);
3243  BFD_ASSERT (input_bfd->xvec->header_byteorder
3244	      == output_bfd->xvec->header_byteorder);
3245
3246  relocatable = finfo->info->relocatable;
3247  syms = obj_aout_external_syms (input_bfd);
3248  strings = obj_aout_external_strings (input_bfd);
3249  sym_hashes = obj_aout_sym_hashes (input_bfd);
3250  symbol_map = finfo->symbol_map;
3251
3252  rel = relocs;
3253  rel_end = rel + rel_size;
3254  for (; rel < rel_end; rel += RELOC_SIZE)
3255    {
3256      bfd_vma r_addr;
3257      int r_index;
3258      int r_type;
3259      int r_pcrel;
3260      int r_extern;
3261      reloc_howto_type *howto;
3262      struct aout_link_hash_entry *h = NULL;
3263      bfd_vma relocation;
3264      bfd_reloc_status_type r;
3265      int reloc_entry;
3266
3267      reloc_entry = GET_WORD (input_bfd, (void *) rel);
3268      if (reloc_entry == 0)
3269	continue;
3270
3271      {
3272	unsigned int howto_idx;
3273
3274	r_index = (reloc_entry & RIDXMASK) >> 4;
3275	r_type = reloc_entry & RTYPE;
3276	r_pcrel = reloc_entry & RELFLG;
3277	r_addr = (char *) rel - (char *) relocs;
3278
3279	r_extern = (r_type == REXT);
3280
3281	howto_idx = r_pcrel;
3282	BFD_ASSERT (howto_idx < TABLE_SIZE (howto_table_pdp11));
3283	howto = howto_table_pdp11 + howto_idx;
3284      }
3285
3286      if (relocatable)
3287	{
3288	  /* We are generating a relocatable output file, and must
3289	     modify the reloc accordingly.  */
3290	  if (r_extern)
3291	    {
3292	      /* If we know the symbol this relocation is against,
3293		 convert it into a relocation against a section.  This
3294		 is what the native linker does.  */
3295	      h = sym_hashes[r_index];
3296	      if (h != NULL
3297		  && (h->root.type == bfd_link_hash_defined
3298		      || h->root.type == bfd_link_hash_defweak))
3299		{
3300		  asection *output_section;
3301
3302		  /* Compute a new r_index.  */
3303		  output_section = h->root.u.def.section->output_section;
3304		  if (output_section == obj_textsec (output_bfd))
3305		    r_type = N_TEXT;
3306		  else if (output_section == obj_datasec (output_bfd))
3307		    r_type = N_DATA;
3308		  else if (output_section == obj_bsssec (output_bfd))
3309		    r_type = N_BSS;
3310		  else
3311		    r_type = N_ABS;
3312
3313		  /* Add the symbol value and the section VMA to the
3314		     addend stored in the contents.  */
3315		  relocation = (h->root.u.def.value
3316				+ output_section->vma
3317				+ h->root.u.def.section->output_offset);
3318		}
3319	      else
3320		{
3321		  /* We must change r_index according to the symbol
3322		     map.  */
3323		  r_index = symbol_map[r_index];
3324
3325		  if (r_index == -1)
3326		    {
3327		      if (h != NULL)
3328			{
3329			  /* We decided to strip this symbol, but it
3330                             turns out that we can't.  Note that we
3331                             lose the other and desc information here.
3332                             I don't think that will ever matter for a
3333                             global symbol.  */
3334			  if (h->indx < 0)
3335			    {
3336			      h->indx = -2;
3337			      h->written = FALSE;
3338			      if (! aout_link_write_other_symbol (h,
3339								  (void *) finfo))
3340				return FALSE;
3341			    }
3342			  r_index = h->indx;
3343			}
3344		      else
3345			{
3346			  const char *name;
3347
3348			  name = strings + GET_WORD (input_bfd,
3349						     syms[r_index].e_strx);
3350			  if (! ((*finfo->info->callbacks->unattached_reloc)
3351				 (finfo->info, name, input_bfd, input_section,
3352				  r_addr)))
3353			    return FALSE;
3354			  r_index = 0;
3355			}
3356		    }
3357
3358		  relocation = 0;
3359		}
3360
3361	      /* Write out the new r_index value.  */
3362	      reloc_entry = GET_WORD (input_bfd, rel);
3363	      reloc_entry &= RIDXMASK;
3364	      reloc_entry |= r_index << 4;
3365	      PUT_WORD (input_bfd, reloc_entry, rel);
3366	    }
3367	  else
3368	    {
3369	      asection *section;
3370
3371	      /* This is a relocation against a section.  We must
3372		 adjust by the amount that the section moved.  */
3373	      section = aout_reloc_type_to_section (input_bfd, r_type);
3374	      relocation = (section->output_section->vma
3375			    + section->output_offset
3376			    - section->vma);
3377	    }
3378
3379	  /* Change the address of the relocation.  */
3380	  fprintf (stderr, "TODO: change the address of the relocation\n");
3381
3382	  /* Adjust a PC relative relocation by removing the reference
3383	     to the original address in the section and including the
3384	     reference to the new address.  */
3385	  if (r_pcrel)
3386	    relocation -= (input_section->output_section->vma
3387			   + input_section->output_offset
3388			   - input_section->vma);
3389
3390#ifdef MY_relocatable_reloc
3391	  MY_relocatable_reloc (howto, output_bfd, rel, relocation, r_addr);
3392#endif
3393
3394	  if (relocation == 0)
3395	    r = bfd_reloc_ok;
3396	  else
3397	    r = MY_relocate_contents (howto,
3398				      input_bfd, relocation,
3399				      contents + r_addr);
3400	}
3401      else
3402	{
3403	  bfd_boolean hundef;
3404
3405	  /* We are generating an executable, and must do a full
3406	     relocation.  */
3407	  hundef = FALSE;
3408	  if (r_extern)
3409	    {
3410	      h = sym_hashes[r_index];
3411
3412	      if (h != NULL
3413		  && (h->root.type == bfd_link_hash_defined
3414		      || h->root.type == bfd_link_hash_defweak))
3415		{
3416		  relocation = (h->root.u.def.value
3417				+ h->root.u.def.section->output_section->vma
3418				+ h->root.u.def.section->output_offset);
3419		}
3420	      else if (h != NULL
3421		       && h->root.type == bfd_link_hash_undefweak)
3422		relocation = 0;
3423	      else
3424		{
3425		  hundef = TRUE;
3426		  relocation = 0;
3427		}
3428	    }
3429	  else
3430	    {
3431	      asection *section;
3432
3433	      section = aout_reloc_type_to_section (input_bfd, r_type);
3434	      relocation = (section->output_section->vma
3435			    + section->output_offset
3436			    - section->vma);
3437	      if (r_pcrel)
3438		relocation += input_section->vma;
3439	    }
3440
3441	  if (check_dynamic_reloc != NULL)
3442	    {
3443	      bfd_boolean skip;
3444
3445	      if (! ((*check_dynamic_reloc)
3446		     (finfo->info, input_bfd, input_section, h,
3447		      (void *) rel, contents, &skip, &relocation)))
3448		return FALSE;
3449	      if (skip)
3450		continue;
3451	    }
3452
3453	  /* Now warn if a global symbol is undefined.  We could not
3454             do this earlier, because check_dynamic_reloc might want
3455             to skip this reloc.  */
3456	  if (hundef && ! finfo->info->shared)
3457	    {
3458	      const char *name;
3459
3460	      if (h != NULL)
3461		name = h->root.root.string;
3462	      else
3463		name = strings + GET_WORD (input_bfd, syms[r_index].e_strx);
3464	      if (! ((*finfo->info->callbacks->undefined_symbol)
3465		     (finfo->info, name, input_bfd, input_section,
3466		      r_addr, TRUE)))
3467		return FALSE;
3468	    }
3469
3470	  r = MY_final_link_relocate (howto,
3471				      input_bfd, input_section,
3472				      contents, r_addr, relocation,
3473				      (bfd_vma) 0);
3474	}
3475
3476      if (r != bfd_reloc_ok)
3477	{
3478	  switch (r)
3479	    {
3480	    default:
3481	    case bfd_reloc_outofrange:
3482	      abort ();
3483	    case bfd_reloc_overflow:
3484	      {
3485		const char *name;
3486
3487		if (h != NULL)
3488		  name = NULL;
3489		else if (r_extern)
3490		  name = strings + GET_WORD (input_bfd,
3491					     syms[r_index].e_strx);
3492		else
3493		  {
3494		    asection *s;
3495
3496		    s = aout_reloc_type_to_section (input_bfd, r_type);
3497		    name = bfd_section_name (input_bfd, s);
3498		  }
3499		if (! ((*finfo->info->callbacks->reloc_overflow)
3500		       (finfo->info, (h ? &h->root : NULL), name,
3501			howto->name, (bfd_vma) 0, input_bfd,
3502			input_section, r_addr)))
3503		  return FALSE;
3504	      }
3505	      break;
3506	    }
3507	}
3508    }
3509
3510  return TRUE;
3511}
3512
3513/* Link an a.out section into the output file.  */
3514
3515static bfd_boolean
3516aout_link_input_section (struct aout_final_link_info *finfo,
3517			 bfd *input_bfd,
3518			 asection *input_section,
3519			 file_ptr *reloff_ptr,
3520			 bfd_size_type rel_size)
3521{
3522  bfd_size_type input_size;
3523  void * relocs;
3524
3525  /* Get the section contents.  */
3526  input_size = input_section->size;
3527  if (! bfd_get_section_contents (input_bfd, input_section,
3528				  (void *) finfo->contents,
3529				  (file_ptr) 0, input_size))
3530    return FALSE;
3531
3532  /* Read in the relocs if we haven't already done it.  */
3533  if (aout_section_data (input_section) != NULL
3534      && aout_section_data (input_section)->relocs != NULL)
3535    relocs = aout_section_data (input_section)->relocs;
3536  else
3537    {
3538      relocs = finfo->relocs;
3539      if (rel_size > 0)
3540	{
3541	  if (bfd_seek (input_bfd, input_section->rel_filepos, SEEK_SET) != 0
3542	      || bfd_bread (relocs, rel_size, input_bfd) != rel_size)
3543	    return FALSE;
3544	}
3545    }
3546
3547  /* Relocate the section contents.  */
3548  if (! pdp11_aout_link_input_section (finfo, input_bfd, input_section,
3549				       (bfd_byte *) relocs,
3550				       rel_size, finfo->contents))
3551    return FALSE;
3552
3553  /* Write out the section contents.  */
3554  if (! bfd_set_section_contents (finfo->output_bfd,
3555				  input_section->output_section,
3556				  (void *) finfo->contents,
3557				  (file_ptr) input_section->output_offset,
3558				  input_size))
3559    return FALSE;
3560
3561  /* If we are producing relocatable output, the relocs were
3562     modified, and we now write them out.  */
3563  if (finfo->info->relocatable && rel_size > 0)
3564    {
3565      if (bfd_seek (finfo->output_bfd, *reloff_ptr, SEEK_SET) != 0)
3566	return FALSE;
3567      if (bfd_bwrite (relocs, rel_size, finfo->output_bfd) != rel_size)
3568	return FALSE;
3569      *reloff_ptr += rel_size;
3570
3571      /* Assert that the relocs have not run into the symbols, and
3572	 that if these are the text relocs they have not run into the
3573	 data relocs.  */
3574      BFD_ASSERT (*reloff_ptr <= obj_sym_filepos (finfo->output_bfd)
3575		  && (reloff_ptr != &finfo->treloff
3576		      || (*reloff_ptr
3577			  <= obj_datasec (finfo->output_bfd)->rel_filepos)));
3578    }
3579
3580  return TRUE;
3581}
3582
3583/* Link an a.out input BFD into the output file.  */
3584
3585static bfd_boolean
3586aout_link_input_bfd (struct aout_final_link_info *finfo, bfd *input_bfd)
3587{
3588  BFD_ASSERT (bfd_get_format (input_bfd) == bfd_object);
3589
3590  /* If this is a dynamic object, it may need special handling.  */
3591  if ((input_bfd->flags & DYNAMIC) != 0
3592      && aout_backend_info (input_bfd)->link_dynamic_object != NULL)
3593    return ((*aout_backend_info (input_bfd)->link_dynamic_object)
3594	    (finfo->info, input_bfd));
3595
3596  /* Get the symbols.  We probably have them already, unless
3597     finfo->info->keep_memory is FALSE.  */
3598  if (! aout_get_external_symbols (input_bfd))
3599    return FALSE;
3600
3601  /* Write out the symbols and get a map of the new indices.  The map
3602     is placed into finfo->symbol_map.  */
3603  if (! aout_link_write_symbols (finfo, input_bfd))
3604    return FALSE;
3605
3606  /* Relocate and write out the sections.  These functions use the
3607     symbol map created by aout_link_write_symbols.  The linker_mark
3608     field will be set if these sections are to be included in the
3609     link, which will normally be the case.  */
3610  if (obj_textsec (input_bfd)->linker_mark)
3611    {
3612      if (! aout_link_input_section (finfo, input_bfd,
3613				     obj_textsec (input_bfd),
3614				     &finfo->treloff,
3615				     exec_hdr (input_bfd)->a_trsize))
3616	return FALSE;
3617    }
3618  if (obj_datasec (input_bfd)->linker_mark)
3619    {
3620      if (! aout_link_input_section (finfo, input_bfd,
3621				     obj_datasec (input_bfd),
3622				     &finfo->dreloff,
3623				     exec_hdr (input_bfd)->a_drsize))
3624	return FALSE;
3625    }
3626
3627  /* If we are not keeping memory, we don't need the symbols any
3628     longer.  We still need them if we are keeping memory, because the
3629     strings in the hash table point into them.  */
3630  if (! finfo->info->keep_memory)
3631    {
3632      if (! aout_link_free_symbols (input_bfd))
3633	return FALSE;
3634    }
3635
3636  return TRUE;
3637}
3638
3639/* Do the final link step.  This is called on the output BFD.  The
3640   INFO structure should point to a list of BFDs linked through the
3641   link_next field which can be used to find each BFD which takes part
3642   in the output.  Also, each section in ABFD should point to a list
3643   of bfd_link_order structures which list all the input sections for
3644   the output section.  */
3645
3646bfd_boolean
3647NAME (aout, final_link) (bfd *abfd,
3648			 struct bfd_link_info *info,
3649			 void (*callback) (bfd *, file_ptr *, file_ptr *, file_ptr *))
3650{
3651  struct aout_final_link_info aout_info;
3652  bfd_boolean includes_hash_initialized = FALSE;
3653  bfd *sub;
3654  bfd_size_type trsize, drsize;
3655  bfd_size_type max_contents_size;
3656  bfd_size_type max_relocs_size;
3657  bfd_size_type max_sym_count;
3658  bfd_size_type text_size;
3659  file_ptr text_end;
3660  struct bfd_link_order *p;
3661  asection *o;
3662  bfd_boolean have_link_order_relocs;
3663
3664  if (info->shared)
3665    abfd->flags |= DYNAMIC;
3666
3667  aout_info.info = info;
3668  aout_info.output_bfd = abfd;
3669  aout_info.contents = NULL;
3670  aout_info.relocs = NULL;
3671  aout_info.symbol_map = NULL;
3672  aout_info.output_syms = NULL;
3673
3674  if (!bfd_hash_table_init_n (&aout_info.includes.root,
3675			      aout_link_includes_newfunc,
3676			      sizeof (struct aout_link_includes_entry),
3677			      251))
3678    goto error_return;
3679  includes_hash_initialized = TRUE;
3680
3681  /* Figure out the largest section size.  Also, if generating
3682     relocatable output, count the relocs.  */
3683  trsize = 0;
3684  drsize = 0;
3685  max_contents_size = 0;
3686  max_relocs_size = 0;
3687  max_sym_count = 0;
3688  for (sub = info->input_bfds; sub != NULL; sub = sub->link_next)
3689    {
3690      size_t sz;
3691
3692      if (info->relocatable)
3693	{
3694	  if (bfd_get_flavour (sub) == bfd_target_aout_flavour)
3695	    {
3696	      trsize += exec_hdr (sub)->a_trsize;
3697	      drsize += exec_hdr (sub)->a_drsize;
3698	    }
3699	  else
3700	    {
3701	      /* FIXME: We need to identify the .text and .data sections
3702		 and call get_reloc_upper_bound and canonicalize_reloc to
3703		 work out the number of relocs needed, and then multiply
3704		 by the reloc size.  */
3705	      (*_bfd_error_handler)
3706		("%s: relocatable link from %s to %s not supported",
3707		 bfd_get_filename (abfd),
3708		 sub->xvec->name, abfd->xvec->name);
3709	      bfd_set_error (bfd_error_invalid_operation);
3710	      goto error_return;
3711	    }
3712	}
3713
3714      if (bfd_get_flavour (sub) == bfd_target_aout_flavour)
3715	{
3716	  sz = obj_textsec (sub)->size;
3717	  if (sz > max_contents_size)
3718	    max_contents_size = sz;
3719	  sz = obj_datasec (sub)->size;
3720	  if (sz > max_contents_size)
3721	    max_contents_size = sz;
3722
3723	  sz = exec_hdr (sub)->a_trsize;
3724	  if (sz > max_relocs_size)
3725	    max_relocs_size = sz;
3726	  sz = exec_hdr (sub)->a_drsize;
3727	  if (sz > max_relocs_size)
3728	    max_relocs_size = sz;
3729
3730	  sz = obj_aout_external_sym_count (sub);
3731	  if (sz > max_sym_count)
3732	    max_sym_count = sz;
3733	}
3734    }
3735
3736  if (info->relocatable)
3737    {
3738      if (obj_textsec (abfd) != NULL)
3739	trsize += (_bfd_count_link_order_relocs (obj_textsec (abfd)
3740						 ->map_head.link_order)
3741		   * obj_reloc_entry_size (abfd));
3742      if (obj_datasec (abfd) != NULL)
3743	drsize += (_bfd_count_link_order_relocs (obj_datasec (abfd)
3744						 ->map_head.link_order)
3745		   * obj_reloc_entry_size (abfd));
3746    }
3747
3748  exec_hdr (abfd)->a_trsize = trsize;
3749  exec_hdr (abfd)->a_drsize = drsize;
3750  exec_hdr (abfd)->a_entry = bfd_get_start_address (abfd);
3751
3752  /* Adjust the section sizes and vmas according to the magic number.
3753     This sets a_text, a_data and a_bss in the exec_hdr and sets the
3754     filepos for each section.  */
3755  if (! NAME (aout, adjust_sizes_and_vmas) (abfd, &text_size, &text_end))
3756    goto error_return;
3757
3758  /* The relocation and symbol file positions differ among a.out
3759     targets.  We are passed a callback routine from the backend
3760     specific code to handle this.
3761     FIXME: At this point we do not know how much space the symbol
3762     table will require.  This will not work for any (nonstandard)
3763     a.out target that needs to know the symbol table size before it
3764     can compute the relocation file positions.  This may or may not
3765     be the case for the hp300hpux target, for example.  */
3766  (*callback) (abfd, &aout_info.treloff, &aout_info.dreloff,
3767	       &aout_info.symoff);
3768  obj_textsec (abfd)->rel_filepos = aout_info.treloff;
3769  obj_datasec (abfd)->rel_filepos = aout_info.dreloff;
3770  obj_sym_filepos (abfd) = aout_info.symoff;
3771
3772  /* We keep a count of the symbols as we output them.  */
3773  obj_aout_external_sym_count (abfd) = 0;
3774
3775  /* We accumulate the string table as we write out the symbols.  */
3776  aout_info.strtab = _bfd_stringtab_init ();
3777  if (aout_info.strtab == NULL)
3778    goto error_return;
3779
3780  /* Allocate buffers to hold section contents and relocs.  */
3781  aout_info.contents = bfd_malloc (max_contents_size);
3782  aout_info.relocs = bfd_malloc (max_relocs_size);
3783  aout_info.symbol_map = bfd_malloc (max_sym_count * sizeof (int *));
3784  aout_info.output_syms = bfd_malloc ((max_sym_count + 1)
3785				      * sizeof (struct external_nlist));
3786  if ((aout_info.contents == NULL && max_contents_size != 0)
3787      || (aout_info.relocs == NULL && max_relocs_size != 0)
3788      || (aout_info.symbol_map == NULL && max_sym_count != 0)
3789      || aout_info.output_syms == NULL)
3790    goto error_return;
3791
3792  /* If we have a symbol named __DYNAMIC, force it out now.  This is
3793     required by SunOS.  Doing this here rather than in sunos.c is a
3794     hack, but it's easier than exporting everything which would be
3795     needed.  */
3796  {
3797    struct aout_link_hash_entry *h;
3798
3799    h = aout_link_hash_lookup (aout_hash_table (info), "__DYNAMIC",
3800			       FALSE, FALSE, FALSE);
3801    if (h != NULL)
3802      aout_link_write_other_symbol (h, &aout_info);
3803  }
3804
3805  /* The most time efficient way to do the link would be to read all
3806     the input object files into memory and then sort out the
3807     information into the output file.  Unfortunately, that will
3808     probably use too much memory.  Another method would be to step
3809     through everything that composes the text section and write it
3810     out, and then everything that composes the data section and write
3811     it out, and then write out the relocs, and then write out the
3812     symbols.  Unfortunately, that requires reading stuff from each
3813     input file several times, and we will not be able to keep all the
3814     input files open simultaneously, and reopening them will be slow.
3815
3816     What we do is basically process one input file at a time.  We do
3817     everything we need to do with an input file once--copy over the
3818     section contents, handle the relocation information, and write
3819     out the symbols--and then we throw away the information we read
3820     from it.  This approach requires a lot of lseeks of the output
3821     file, which is unfortunate but still faster than reopening a lot
3822     of files.
3823
3824     We use the output_has_begun field of the input BFDs to see
3825     whether we have already handled it.  */
3826  for (sub = info->input_bfds; sub != NULL; sub = sub->link_next)
3827    sub->output_has_begun = FALSE;
3828
3829  /* Mark all sections which are to be included in the link.  This
3830     will normally be every section.  We need to do this so that we
3831     can identify any sections which the linker has decided to not
3832     include.  */
3833  for (o = abfd->sections; o != NULL; o = o->next)
3834    {
3835      for (p = o->map_head.link_order; p != NULL; p = p->next)
3836	if (p->type == bfd_indirect_link_order)
3837	  p->u.indirect.section->linker_mark = TRUE;
3838    }
3839
3840  have_link_order_relocs = FALSE;
3841  for (o = abfd->sections; o != NULL; o = o->next)
3842    {
3843      for (p = o->map_head.link_order;
3844	   p != NULL;
3845	   p = p->next)
3846	{
3847	  if (p->type == bfd_indirect_link_order
3848	      && (bfd_get_flavour (p->u.indirect.section->owner)
3849		  == bfd_target_aout_flavour))
3850	    {
3851	      bfd *input_bfd;
3852
3853	      input_bfd = p->u.indirect.section->owner;
3854	      if (! input_bfd->output_has_begun)
3855		{
3856		  if (! aout_link_input_bfd (&aout_info, input_bfd))
3857		    goto error_return;
3858		  input_bfd->output_has_begun = TRUE;
3859		}
3860	    }
3861	  else if (p->type == bfd_section_reloc_link_order
3862		   || p->type == bfd_symbol_reloc_link_order)
3863	    /* These are handled below.  */
3864	    have_link_order_relocs = TRUE;
3865	  else
3866	    {
3867	      if (! _bfd_default_link_order (abfd, info, o, p))
3868		goto error_return;
3869	    }
3870	}
3871    }
3872
3873  /* Write out any symbols that we have not already written out.  */
3874  aout_link_hash_traverse (aout_hash_table (info),
3875			   aout_link_write_other_symbol,
3876			   (void *) &aout_info);
3877
3878  /* Now handle any relocs we were asked to create by the linker.
3879     These did not come from any input file.  We must do these after
3880     we have written out all the symbols, so that we know the symbol
3881     indices to use.  */
3882  if (have_link_order_relocs)
3883    {
3884      for (o = abfd->sections; o != NULL; o = o->next)
3885	{
3886	  for (p = o->map_head.link_order;
3887	       p != NULL;
3888	       p = p->next)
3889	    {
3890	      if (p->type == bfd_section_reloc_link_order
3891		  || p->type == bfd_symbol_reloc_link_order)
3892		{
3893		  if (! aout_link_reloc_link_order (&aout_info, o, p))
3894		    goto error_return;
3895		}
3896	    }
3897	}
3898    }
3899
3900  if (aout_info.contents != NULL)
3901    {
3902      free (aout_info.contents);
3903      aout_info.contents = NULL;
3904    }
3905  if (aout_info.relocs != NULL)
3906    {
3907      free (aout_info.relocs);
3908      aout_info.relocs = NULL;
3909    }
3910  if (aout_info.symbol_map != NULL)
3911    {
3912      free (aout_info.symbol_map);
3913      aout_info.symbol_map = NULL;
3914    }
3915  if (aout_info.output_syms != NULL)
3916    {
3917      free (aout_info.output_syms);
3918      aout_info.output_syms = NULL;
3919    }
3920  if (includes_hash_initialized)
3921    {
3922      bfd_hash_table_free (&aout_info.includes.root);
3923      includes_hash_initialized = FALSE;
3924    }
3925
3926  /* Finish up any dynamic linking we may be doing.  */
3927  if (aout_backend_info (abfd)->finish_dynamic_link != NULL)
3928    {
3929      if (! (*aout_backend_info (abfd)->finish_dynamic_link) (abfd, info))
3930	goto error_return;
3931    }
3932
3933  /* Update the header information.  */
3934  abfd->symcount = obj_aout_external_sym_count (abfd);
3935  exec_hdr (abfd)->a_syms = abfd->symcount * EXTERNAL_NLIST_SIZE;
3936  obj_str_filepos (abfd) = obj_sym_filepos (abfd) + exec_hdr (abfd)->a_syms;
3937  obj_textsec (abfd)->reloc_count =
3938    exec_hdr (abfd)->a_trsize / obj_reloc_entry_size (abfd);
3939  obj_datasec (abfd)->reloc_count =
3940    exec_hdr (abfd)->a_drsize / obj_reloc_entry_size (abfd);
3941
3942  /* Write out the string table, unless there are no symbols.  */
3943  if (abfd->symcount > 0)
3944    {
3945      if (bfd_seek (abfd, obj_str_filepos (abfd), SEEK_SET) != 0
3946	  || ! emit_stringtab (abfd, aout_info.strtab))
3947	goto error_return;
3948    }
3949  else if (obj_textsec (abfd)->reloc_count == 0
3950	   && obj_datasec (abfd)->reloc_count == 0)
3951    {
3952      bfd_byte b;
3953
3954      b = 0;
3955      if (bfd_seek (abfd,
3956		    (file_ptr) (obj_datasec (abfd)->filepos
3957				+ exec_hdr (abfd)->a_data
3958				- 1),
3959		    SEEK_SET) != 0
3960	  || bfd_bwrite (&b, (bfd_size_type) 1, abfd) != 1)
3961	goto error_return;
3962    }
3963
3964  return TRUE;
3965
3966 error_return:
3967  if (aout_info.contents != NULL)
3968    free (aout_info.contents);
3969  if (aout_info.relocs != NULL)
3970    free (aout_info.relocs);
3971  if (aout_info.symbol_map != NULL)
3972    free (aout_info.symbol_map);
3973  if (aout_info.output_syms != NULL)
3974    free (aout_info.output_syms);
3975  if (includes_hash_initialized)
3976    bfd_hash_table_free (&aout_info.includes.root);
3977  return FALSE;
3978}
3979
3980/* Adjust and write out the symbols for an a.out file.  Set the new
3981   symbol indices into a symbol_map.  */
3982
3983static bfd_boolean
3984aout_link_write_symbols (struct aout_final_link_info *finfo, bfd *input_bfd)
3985{
3986  bfd *output_bfd;
3987  bfd_size_type sym_count;
3988  char *strings;
3989  enum bfd_link_strip strip;
3990  enum bfd_link_discard discard;
3991  struct external_nlist *outsym;
3992  bfd_size_type strtab_index;
3993  struct external_nlist *sym;
3994  struct external_nlist *sym_end;
3995  struct aout_link_hash_entry **sym_hash;
3996  int *symbol_map;
3997  bfd_boolean pass;
3998  bfd_boolean skip_next;
3999
4000  output_bfd = finfo->output_bfd;
4001  sym_count = obj_aout_external_sym_count (input_bfd);
4002  strings = obj_aout_external_strings (input_bfd);
4003  strip = finfo->info->strip;
4004  discard = finfo->info->discard;
4005  outsym = finfo->output_syms;
4006
4007  /* First write out a symbol for this object file, unless we are
4008     discarding such symbols.  */
4009  if (strip != strip_all
4010      && (strip != strip_some
4011	  || bfd_hash_lookup (finfo->info->keep_hash, input_bfd->filename,
4012			      FALSE, FALSE) != NULL)
4013      && discard != discard_all)
4014    {
4015      H_PUT_8 (output_bfd, N_TEXT, outsym->e_type);
4016      strtab_index = add_to_stringtab (output_bfd, finfo->strtab,
4017				       input_bfd->filename, FALSE);
4018      if (strtab_index == (bfd_size_type) -1)
4019	return FALSE;
4020      PUT_WORD (output_bfd, strtab_index, outsym->e_strx);
4021      PUT_WORD (output_bfd,
4022		(bfd_get_section_vma (output_bfd,
4023				      obj_textsec (input_bfd)->output_section)
4024		 + obj_textsec (input_bfd)->output_offset),
4025		outsym->e_value);
4026      ++obj_aout_external_sym_count (output_bfd);
4027      ++outsym;
4028    }
4029
4030  pass = FALSE;
4031  skip_next = FALSE;
4032  sym = obj_aout_external_syms (input_bfd);
4033  sym_end = sym + sym_count;
4034  sym_hash = obj_aout_sym_hashes (input_bfd);
4035  symbol_map = finfo->symbol_map;
4036  memset (symbol_map, 0, (size_t) sym_count * sizeof *symbol_map);
4037  for (; sym < sym_end; sym++, sym_hash++, symbol_map++)
4038    {
4039      const char *name;
4040      int type;
4041      struct aout_link_hash_entry *h;
4042      bfd_boolean skip;
4043      asection *symsec;
4044      bfd_vma val = 0;
4045      bfd_boolean copy;
4046
4047      /* We set *symbol_map to 0 above for all symbols.  If it has
4048         already been set to -1 for this symbol, it means that we are
4049         discarding it because it appears in a duplicate header file.
4050         See the N_BINCL code below.  */
4051      if (*symbol_map == -1)
4052	continue;
4053
4054      /* Initialize *symbol_map to -1, which means that the symbol was
4055         not copied into the output file.  We will change it later if
4056         we do copy the symbol over.  */
4057      *symbol_map = -1;
4058
4059      type = H_GET_8 (input_bfd, sym->e_type);
4060      name = strings + GET_WORD (input_bfd, sym->e_strx);
4061
4062      h = NULL;
4063
4064      if (pass)
4065	{
4066	  /* Pass this symbol through.  It is the target of an
4067	     indirect or warning symbol.  */
4068	  val = GET_WORD (input_bfd, sym->e_value);
4069	  pass = FALSE;
4070	}
4071      else if (skip_next)
4072	{
4073	  /* Skip this symbol, which is the target of an indirect
4074	     symbol that we have changed to no longer be an indirect
4075	     symbol.  */
4076	  skip_next = FALSE;
4077	  continue;
4078	}
4079      else
4080	{
4081	  struct aout_link_hash_entry *hresolve;
4082
4083	  /* We have saved the hash table entry for this symbol, if
4084	     there is one.  Note that we could just look it up again
4085	     in the hash table, provided we first check that it is an
4086	     external symbol. */
4087	  h = *sym_hash;
4088
4089	  /* Use the name from the hash table, in case the symbol was
4090             wrapped.  */
4091	  if (h != NULL)
4092	    name = h->root.root.string;
4093
4094	  /* If this is an indirect or warning symbol, then change
4095	     hresolve to the base symbol.  We also change *sym_hash so
4096	     that the relocation routines relocate against the real
4097	     symbol.  */
4098	  hresolve = h;
4099	  if (h != NULL
4100	      && (h->root.type == bfd_link_hash_indirect
4101		  || h->root.type == bfd_link_hash_warning))
4102	    {
4103	      hresolve = (struct aout_link_hash_entry *) h->root.u.i.link;
4104	      while (hresolve->root.type == bfd_link_hash_indirect
4105		     || hresolve->root.type == bfd_link_hash_warning)
4106		hresolve = ((struct aout_link_hash_entry *)
4107			    hresolve->root.u.i.link);
4108	      *sym_hash = hresolve;
4109	    }
4110
4111	  /* If the symbol has already been written out, skip it.  */
4112	  if (h != NULL
4113	      && h->root.type != bfd_link_hash_warning
4114	      && h->written)
4115	    {
4116	      if ((type & N_TYPE) == N_INDR
4117		  || type == N_WARNING)
4118		skip_next = TRUE;
4119	      *symbol_map = h->indx;
4120	      continue;
4121	    }
4122
4123	  /* See if we are stripping this symbol.  */
4124	  skip = FALSE;
4125	  switch (strip)
4126	    {
4127	    case strip_none:
4128	      break;
4129	    case strip_debugger:
4130	      if ((type & N_STAB) != 0)
4131		skip = TRUE;
4132	      break;
4133	    case strip_some:
4134	      if (bfd_hash_lookup (finfo->info->keep_hash, name, FALSE, FALSE)
4135		  == NULL)
4136		skip = TRUE;
4137	      break;
4138	    case strip_all:
4139	      skip = TRUE;
4140	      break;
4141	    }
4142	  if (skip)
4143	    {
4144	      if (h != NULL)
4145		h->written = TRUE;
4146	      continue;
4147	    }
4148
4149	  /* Get the value of the symbol.  */
4150	  if ((type & N_TYPE) == N_TEXT
4151	      || type == N_WEAKT)
4152	    symsec = obj_textsec (input_bfd);
4153	  else if ((type & N_TYPE) == N_DATA
4154		   || type == N_WEAKD)
4155	    symsec = obj_datasec (input_bfd);
4156	  else if ((type & N_TYPE) == N_BSS
4157		   || type == N_WEAKB)
4158	    symsec = obj_bsssec (input_bfd);
4159	  else if ((type & N_TYPE) == N_ABS
4160		   || type == N_WEAKA)
4161	    symsec = bfd_abs_section_ptr;
4162	  else if (((type & N_TYPE) == N_INDR
4163		    && (hresolve == NULL
4164			|| (hresolve->root.type != bfd_link_hash_defined
4165			    && hresolve->root.type != bfd_link_hash_defweak
4166			    && hresolve->root.type != bfd_link_hash_common)))
4167		   || type == N_WARNING)
4168	    {
4169	      /* Pass the next symbol through unchanged.  The
4170		 condition above for indirect symbols is so that if
4171		 the indirect symbol was defined, we output it with
4172		 the correct definition so the debugger will
4173		 understand it.  */
4174	      pass = TRUE;
4175	      val = GET_WORD (input_bfd, sym->e_value);
4176	      symsec = NULL;
4177	    }
4178	  else if ((type & N_STAB) != 0)
4179	    {
4180	      val = GET_WORD (input_bfd, sym->e_value);
4181	      symsec = NULL;
4182	    }
4183	  else
4184	    {
4185	      /* If we get here with an indirect symbol, it means that
4186		 we are outputting it with a real definition.  In such
4187		 a case we do not want to output the next symbol,
4188		 which is the target of the indirection.  */
4189	      if ((type & N_TYPE) == N_INDR)
4190		skip_next = TRUE;
4191
4192	      symsec = NULL;
4193
4194	      /* We need to get the value from the hash table.  We use
4195		 hresolve so that if we have defined an indirect
4196		 symbol we output the final definition.  */
4197	      if (h == NULL)
4198		{
4199		  switch (type & N_TYPE)
4200		    {
4201		    case N_SETT:
4202		      symsec = obj_textsec (input_bfd);
4203		      break;
4204		    case N_SETD:
4205		      symsec = obj_datasec (input_bfd);
4206		      break;
4207		    case N_SETB:
4208		      symsec = obj_bsssec (input_bfd);
4209		      break;
4210		    case N_SETA:
4211		      symsec = bfd_abs_section_ptr;
4212		      break;
4213		    default:
4214		      val = 0;
4215		      break;
4216		    }
4217		}
4218	      else if (hresolve->root.type == bfd_link_hash_defined
4219		       || hresolve->root.type == bfd_link_hash_defweak)
4220		{
4221		  asection *input_section;
4222		  asection *output_section;
4223
4224		  /* This case usually means a common symbol which was
4225		     turned into a defined symbol.  */
4226		  input_section = hresolve->root.u.def.section;
4227		  output_section = input_section->output_section;
4228		  BFD_ASSERT (bfd_is_abs_section (output_section)
4229			      || output_section->owner == output_bfd);
4230		  val = (hresolve->root.u.def.value
4231			 + bfd_get_section_vma (output_bfd, output_section)
4232			 + input_section->output_offset);
4233
4234		  /* Get the correct type based on the section.  If
4235		     this is a constructed set, force it to be
4236		     globally visible.  */
4237		  if (type == N_SETT
4238		      || type == N_SETD
4239		      || type == N_SETB
4240		      || type == N_SETA)
4241		    type |= N_EXT;
4242
4243		  type &=~ N_TYPE;
4244
4245		  if (output_section == obj_textsec (output_bfd))
4246		    type |= (hresolve->root.type == bfd_link_hash_defined
4247			     ? N_TEXT
4248			     : N_WEAKT);
4249		  else if (output_section == obj_datasec (output_bfd))
4250		    type |= (hresolve->root.type == bfd_link_hash_defined
4251			     ? N_DATA
4252			     : N_WEAKD);
4253		  else if (output_section == obj_bsssec (output_bfd))
4254		    type |= (hresolve->root.type == bfd_link_hash_defined
4255			     ? N_BSS
4256			     : N_WEAKB);
4257		  else
4258		    type |= (hresolve->root.type == bfd_link_hash_defined
4259			     ? N_ABS
4260			     : N_WEAKA);
4261		}
4262	      else if (hresolve->root.type == bfd_link_hash_common)
4263		val = hresolve->root.u.c.size;
4264	      else if (hresolve->root.type == bfd_link_hash_undefweak)
4265		{
4266		  val = 0;
4267		  type = N_WEAKU;
4268		}
4269	      else
4270		val = 0;
4271	    }
4272	  if (symsec != NULL)
4273	    val = (symsec->output_section->vma
4274		   + symsec->output_offset
4275		   + (GET_WORD (input_bfd, sym->e_value)
4276		      - symsec->vma));
4277
4278	  /* If this is a global symbol set the written flag, and if
4279	     it is a local symbol see if we should discard it.  */
4280	  if (h != NULL)
4281	    {
4282	      h->written = TRUE;
4283	      h->indx = obj_aout_external_sym_count (output_bfd);
4284	    }
4285	  else if ((type & N_TYPE) != N_SETT
4286		   && (type & N_TYPE) != N_SETD
4287		   && (type & N_TYPE) != N_SETB
4288		   && (type & N_TYPE) != N_SETA)
4289	    {
4290	      switch (discard)
4291		{
4292		case discard_none:
4293		case discard_sec_merge:
4294		  break;
4295		case discard_l:
4296		  if ((type & N_STAB) == 0
4297		      && bfd_is_local_label_name (input_bfd, name))
4298		    skip = TRUE;
4299		  break;
4300		case discard_all:
4301		  skip = TRUE;
4302		  break;
4303		}
4304	      if (skip)
4305		{
4306		  pass = FALSE;
4307		  continue;
4308		}
4309	    }
4310
4311	  /* An N_BINCL symbol indicates the start of the stabs
4312	     entries for a header file.  We need to scan ahead to the
4313	     next N_EINCL symbol, ignoring nesting, adding up all the
4314	     characters in the symbol names, not including the file
4315	     numbers in types (the first number after an open
4316	     parenthesis).  */
4317	  if (type == N_BINCL)
4318	    {
4319	      struct external_nlist *incl_sym;
4320	      int nest;
4321	      struct aout_link_includes_entry *incl_entry;
4322	      struct aout_link_includes_totals *t;
4323
4324	      val = 0;
4325	      nest = 0;
4326	      for (incl_sym = sym + 1; incl_sym < sym_end; incl_sym++)
4327		{
4328		  int incl_type;
4329
4330		  incl_type = H_GET_8 (input_bfd, incl_sym->e_type);
4331		  if (incl_type == N_EINCL)
4332		    {
4333		      if (nest == 0)
4334			break;
4335		      --nest;
4336		    }
4337		  else if (incl_type == N_BINCL)
4338		    ++nest;
4339		  else if (nest == 0)
4340		    {
4341		      const char *s;
4342
4343		      s = strings + GET_WORD (input_bfd, incl_sym->e_strx);
4344		      for (; *s != '\0'; s++)
4345			{
4346			  val += *s;
4347			  if (*s == '(')
4348			    {
4349			      /* Skip the file number.  */
4350			      ++s;
4351			      while (ISDIGIT (*s))
4352				++s;
4353			      --s;
4354			    }
4355			}
4356		    }
4357		}
4358
4359	      /* If we have already included a header file with the
4360                 same value, then replace this one with an N_EXCL
4361                 symbol.  */
4362	      copy = ! finfo->info->keep_memory;
4363	      incl_entry = aout_link_includes_lookup (&finfo->includes,
4364						      name, TRUE, copy);
4365	      if (incl_entry == NULL)
4366		return FALSE;
4367	      for (t = incl_entry->totals; t != NULL; t = t->next)
4368		if (t->total == val)
4369		  break;
4370	      if (t == NULL)
4371		{
4372		  /* This is the first time we have seen this header
4373                     file with this set of stabs strings.  */
4374		  t = bfd_hash_allocate (&finfo->includes.root,
4375					 sizeof *t);
4376		  if (t == NULL)
4377		    return FALSE;
4378		  t->total = val;
4379		  t->next = incl_entry->totals;
4380		  incl_entry->totals = t;
4381		}
4382	      else
4383		{
4384		  int *incl_map;
4385
4386		  /* This is a duplicate header file.  We must change
4387                     it to be an N_EXCL entry, and mark all the
4388                     included symbols to prevent outputting them.  */
4389		  type = N_EXCL;
4390
4391		  nest = 0;
4392		  for (incl_sym = sym + 1, incl_map = symbol_map + 1;
4393		       incl_sym < sym_end;
4394		       incl_sym++, incl_map++)
4395		    {
4396		      int incl_type;
4397
4398		      incl_type = H_GET_8 (input_bfd, incl_sym->e_type);
4399		      if (incl_type == N_EINCL)
4400			{
4401			  if (nest == 0)
4402			    {
4403			      *incl_map = -1;
4404			      break;
4405			    }
4406			  --nest;
4407			}
4408		      else if (incl_type == N_BINCL)
4409			++nest;
4410		      else if (nest == 0)
4411			*incl_map = -1;
4412		    }
4413		}
4414	    }
4415	}
4416
4417      /* Copy this symbol into the list of symbols we are going to
4418	 write out.  */
4419      H_PUT_8 (output_bfd, type, outsym->e_type);
4420      copy = FALSE;
4421      if (! finfo->info->keep_memory)
4422	{
4423	  /* name points into a string table which we are going to
4424	     free.  If there is a hash table entry, use that string.
4425	     Otherwise, copy name into memory.  */
4426	  if (h != NULL)
4427	    name = h->root.root.string;
4428	  else
4429	    copy = TRUE;
4430	}
4431      strtab_index = add_to_stringtab (output_bfd, finfo->strtab,
4432				       name, copy);
4433      if (strtab_index == (bfd_size_type) -1)
4434	return FALSE;
4435      PUT_WORD (output_bfd, strtab_index, outsym->e_strx);
4436      PUT_WORD (output_bfd, val, outsym->e_value);
4437      *symbol_map = obj_aout_external_sym_count (output_bfd);
4438      ++obj_aout_external_sym_count (output_bfd);
4439      ++outsym;
4440    }
4441
4442  /* Write out the output symbols we have just constructed.  */
4443  if (outsym > finfo->output_syms)
4444    {
4445      bfd_size_type size;
4446
4447      if (bfd_seek (output_bfd, finfo->symoff, SEEK_SET) != 0)
4448	return FALSE;
4449      size = outsym - finfo->output_syms;
4450      size *= EXTERNAL_NLIST_SIZE;
4451      if (bfd_bwrite ((void *) finfo->output_syms, size, output_bfd) != size)
4452	return FALSE;
4453      finfo->symoff += size;
4454    }
4455
4456  return TRUE;
4457}
4458
4459/* Write out a symbol that was not associated with an a.out input
4460   object.  */
4461
4462static bfd_vma
4463bfd_getp32 (const void *p)
4464{
4465  const bfd_byte *addr = p;
4466  unsigned long v;
4467
4468  v = (unsigned long) addr[1] << 24;
4469  v |= (unsigned long) addr[0] << 16;
4470  v |= (unsigned long) addr[3] << 8;
4471  v |= (unsigned long) addr[2];
4472  return v;
4473}
4474
4475#define COERCE32(x) (((bfd_signed_vma) (x) ^ 0x80000000) - 0x80000000)
4476
4477static bfd_signed_vma
4478bfd_getp_signed_32 (const void *p)
4479{
4480  const bfd_byte *addr = p;
4481  unsigned long v;
4482
4483  v = (unsigned long) addr[1] << 24;
4484  v |= (unsigned long) addr[0] << 16;
4485  v |= (unsigned long) addr[3] << 8;
4486  v |= (unsigned long) addr[2];
4487  return COERCE32 (v);
4488}
4489
4490static void
4491bfd_putp32 (bfd_vma data, void *p)
4492{
4493  bfd_byte *addr = p;
4494
4495  addr[0] = (data >> 16) & 0xff;
4496  addr[1] = (data >> 24) & 0xff;
4497  addr[2] = (data >> 0) & 0xff;
4498  addr[3] = (data >> 8) & 0xff;
4499}
4500
4501const bfd_target MY (vec) =
4502{
4503  TARGETNAME,			/* Name.  */
4504  bfd_target_aout_flavour,
4505  BFD_ENDIAN_LITTLE,		/* Target byte order (little).  */
4506  BFD_ENDIAN_LITTLE,		/* Target headers byte order (little).  */
4507  (HAS_RELOC | EXEC_P |		/* Object flags.  */
4508   HAS_LINENO | HAS_DEBUG |
4509   HAS_SYMS | HAS_LOCALS | WP_TEXT),
4510  (SEC_HAS_CONTENTS | SEC_ALLOC | SEC_LOAD | SEC_RELOC | SEC_CODE | SEC_DATA),
4511  MY_symbol_leading_char,
4512  AR_PAD_CHAR,			/* AR_pad_char.  */
4513  15,				/* AR_max_namelen.  */
4514  bfd_getl64, bfd_getl_signed_64, bfd_putl64,
4515     bfd_getp32, bfd_getp_signed_32, bfd_putp32,
4516     bfd_getl16, bfd_getl_signed_16, bfd_putl16, /* Data.  */
4517  bfd_getl64, bfd_getl_signed_64, bfd_putl64,
4518     bfd_getp32, bfd_getp_signed_32, bfd_putp32,
4519     bfd_getl16, bfd_getl_signed_16, bfd_putl16, /* Headers.  */
4520    {_bfd_dummy_target, MY_object_p, 		/* bfd_check_format.  */
4521       bfd_generic_archive_p, MY_core_file_p},
4522    {bfd_false, MY_mkobject,			/* bfd_set_format.  */
4523       _bfd_generic_mkarchive, bfd_false},
4524    {bfd_false, MY_write_object_contents, 	/* bfd_write_contents.  */
4525       _bfd_write_archive_contents, bfd_false},
4526
4527     BFD_JUMP_TABLE_GENERIC (MY),
4528     BFD_JUMP_TABLE_COPY (MY),
4529     BFD_JUMP_TABLE_CORE (MY),
4530     BFD_JUMP_TABLE_ARCHIVE (MY),
4531     BFD_JUMP_TABLE_SYMBOLS (MY),
4532     BFD_JUMP_TABLE_RELOCS (MY),
4533     BFD_JUMP_TABLE_WRITE (MY),
4534     BFD_JUMP_TABLE_LINK (MY),
4535     BFD_JUMP_TABLE_DYNAMIC (MY),
4536
4537  /* Alternative_target.  */
4538  NULL,
4539
4540  (void *) MY_backend_data
4541};
4542