1/* BFD back-end for ieee-695 objects.
2   Copyright 1990, 1991, 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999,
3   2000, 2001, 2002, 2003, 2004
4   Free Software Foundation, Inc.
5
6   Written by Steve Chamberlain of Cygnus Support.
7
8   This file is part of BFD, the Binary File Descriptor library.
9
10   This program is free software; you can redistribute it and/or modify
11   it under the terms of the GNU General Public License as published by
12   the Free Software Foundation; either version 2 of the License, or
13   (at your option) any later version.
14
15   This program is distributed in the hope that it will be useful,
16   but WITHOUT ANY WARRANTY; without even the implied warranty of
17   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18   GNU General Public License for more details.
19
20   You should have received a copy of the GNU General Public License
21   along with this program; if not, write to the Free Software
22   Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
23
24#define KEEPMINUSPCININST 0
25
26/* IEEE 695 format is a stream of records, which we parse using a simple one-
27   token (which is one byte in this lexicon) lookahead recursive decent
28   parser.  */
29
30#include "bfd.h"
31#include "sysdep.h"
32#include "libbfd.h"
33#include "ieee.h"
34#include "libieee.h"
35#include "safe-ctype.h"
36
37struct output_buffer_struct
38{
39  unsigned char *ptrp;
40  int buffer;
41};
42
43static bfd_boolean ieee_write_byte
44  PARAMS ((bfd *, int));
45static bfd_boolean ieee_write_2bytes
46  PARAMS ((bfd *, int));
47static bfd_boolean ieee_write_int
48  PARAMS ((bfd *, bfd_vma));
49static bfd_boolean ieee_write_id
50  PARAMS ((bfd *, const char *));
51static unsigned short read_2bytes
52  PARAMS ((common_header_type *));
53static void bfd_get_string
54  PARAMS ((common_header_type *, char *, size_t));
55static char *read_id
56  PARAMS ((common_header_type *));
57static bfd_boolean ieee_write_expression
58  PARAMS ((bfd *, bfd_vma, asymbol *, bfd_boolean, unsigned int));
59static void ieee_write_int5
60  PARAMS ((bfd_byte *, bfd_vma));
61static bfd_boolean ieee_write_int5_out
62  PARAMS ((bfd *, bfd_vma));
63static bfd_boolean parse_int
64  PARAMS ((common_header_type *, bfd_vma *));
65static int parse_i
66  PARAMS ((common_header_type *, bfd_boolean *));
67static bfd_vma must_parse_int
68  PARAMS ((common_header_type *));
69static void parse_expression
70  PARAMS ((ieee_data_type *, bfd_vma *, ieee_symbol_index_type *,
71	   bfd_boolean *, unsigned int *, asection **));
72static file_ptr ieee_part_after
73  PARAMS ((ieee_data_type *, file_ptr));
74static ieee_symbol_type *get_symbol
75  PARAMS ((bfd *, ieee_data_type *, ieee_symbol_type *, unsigned int *,
76	   ieee_symbol_type ***, unsigned int *, int));
77static bfd_boolean ieee_slurp_external_symbols
78  PARAMS ((bfd *));
79static bfd_boolean ieee_slurp_symbol_table
80  PARAMS ((bfd *));
81static long ieee_get_symtab_upper_bound
82  PARAMS ((bfd *));
83static long ieee_canonicalize_symtab
84  PARAMS ((bfd *, asymbol **));
85static asection *get_section_entry
86  PARAMS ((bfd *, ieee_data_type *i, unsigned int));
87static void ieee_slurp_sections
88  PARAMS ((bfd *));
89static bfd_boolean ieee_slurp_debug
90  PARAMS ((bfd *));
91const bfd_target *ieee_archive_p
92  PARAMS ((bfd *));
93const bfd_target *ieee_object_p
94  PARAMS ((bfd *));
95static void ieee_get_symbol_info
96  PARAMS ((bfd *, asymbol *, symbol_info *));
97static void ieee_print_symbol
98  PARAMS ((bfd *, PTR, asymbol *, bfd_print_symbol_type));
99static bfd_boolean do_one
100  PARAMS ((ieee_data_type *, ieee_per_section_type *, unsigned char *,
101	   asection *, int));
102static bfd_boolean ieee_slurp_section_data
103  PARAMS ((bfd *));
104static bfd_boolean ieee_new_section_hook
105  PARAMS ((bfd *, asection *));
106static long ieee_get_reloc_upper_bound
107  PARAMS ((bfd *, sec_ptr));
108static bfd_boolean ieee_get_section_contents
109  PARAMS ((bfd *, sec_ptr, PTR, file_ptr, bfd_size_type));
110static long ieee_canonicalize_reloc
111  PARAMS ((bfd *, sec_ptr, arelent **, asymbol **));
112static int comp
113  PARAMS ((const PTR, const PTR));
114static bfd_boolean ieee_write_section_part
115  PARAMS ((bfd *));
116static bfd_boolean do_with_relocs
117  PARAMS ((bfd *, asection *));
118static bfd_boolean do_as_repeat
119  PARAMS ((bfd *, asection *));
120static bfd_boolean do_without_relocs
121  PARAMS ((bfd *, asection *));
122static bfd_boolean ieee_mkobject
123  PARAMS ((bfd *));
124static void fill
125  PARAMS ((void));
126static void flush
127  PARAMS ((void));
128static void write_int
129  PARAMS ((int));
130static void copy_id
131  PARAMS ((void));
132static void copy_expression
133  PARAMS ((void));
134static void fill_int
135  PARAMS ((struct output_buffer_struct *));
136static void drop_int
137  PARAMS ((struct output_buffer_struct *));
138static void copy_int
139  PARAMS ((void));
140static void f1_record
141  PARAMS ((void));
142static void f0_record
143  PARAMS ((void));
144static void copy_till_end
145  PARAMS ((void));
146static void f2_record
147  PARAMS ((void));
148static void f8_record
149  PARAMS ((void));
150static void e2_record
151  PARAMS ((void));
152static void block
153  PARAMS ((void));
154static void relocate_debug
155  PARAMS ((bfd *, bfd *));
156static bfd_boolean ieee_write_debug_part
157  PARAMS ((bfd *));
158static bfd_boolean ieee_write_data_part
159  PARAMS ((bfd *));
160static bfd_boolean init_for_output
161  PARAMS ((bfd *));
162static bfd_boolean ieee_set_section_contents
163  PARAMS ((bfd *, sec_ptr, const PTR, file_ptr, bfd_size_type));
164static bfd_boolean ieee_write_external_part
165  PARAMS ((bfd *));
166static bfd_boolean ieee_write_me_part
167  PARAMS ((bfd *));
168static bfd_boolean ieee_write_processor
169  PARAMS ((bfd *));
170static bfd_boolean ieee_write_object_contents
171  PARAMS ((bfd *));
172static asymbol *ieee_make_empty_symbol
173  PARAMS ((bfd *));
174static bfd *ieee_openr_next_archived_file
175  PARAMS ((bfd *, bfd *));
176static bfd_boolean ieee_find_nearest_line
177  PARAMS ((bfd *, asection *, asymbol **, bfd_vma, const char **,
178	   const char **, unsigned int *));
179static int ieee_generic_stat_arch_elt
180  PARAMS ((bfd *, struct stat *));
181static int ieee_sizeof_headers
182  PARAMS ((bfd *, bfd_boolean));
183
184/* Functions for writing to ieee files in the strange way that the
185   standard requires. */
186
187static bfd_boolean
188ieee_write_byte (abfd, barg)
189     bfd *abfd;
190     int barg;
191{
192  bfd_byte byte;
193
194  byte = barg;
195  if (bfd_bwrite ((PTR) &byte, (bfd_size_type) 1, abfd) != 1)
196    return FALSE;
197  return TRUE;
198}
199
200static bfd_boolean
201ieee_write_2bytes (abfd, bytes)
202     bfd *abfd;
203     int bytes;
204{
205  bfd_byte buffer[2];
206
207  buffer[0] = bytes >> 8;
208  buffer[1] = bytes & 0xff;
209  if (bfd_bwrite ((PTR) buffer, (bfd_size_type) 2, abfd) != 2)
210    return FALSE;
211  return TRUE;
212}
213
214static bfd_boolean
215ieee_write_int (abfd, value)
216     bfd *abfd;
217     bfd_vma value;
218{
219  if (value <= 127)
220    {
221      if (! ieee_write_byte (abfd, (bfd_byte) value))
222	return FALSE;
223    }
224  else
225    {
226      unsigned int length;
227
228      /* How many significant bytes ?  */
229      /* FIXME FOR LONGER INTS.  */
230      if (value & 0xff000000)
231	length = 4;
232      else if (value & 0x00ff0000)
233	length = 3;
234      else if (value & 0x0000ff00)
235	length = 2;
236      else
237	length = 1;
238
239      if (! ieee_write_byte (abfd,
240			     (bfd_byte) ((int) ieee_number_repeat_start_enum
241					 + length)))
242	return FALSE;
243      switch (length)
244	{
245	case 4:
246	  if (! ieee_write_byte (abfd, (bfd_byte) (value >> 24)))
247	    return FALSE;
248	  /* Fall through.  */
249	case 3:
250	  if (! ieee_write_byte (abfd, (bfd_byte) (value >> 16)))
251	    return FALSE;
252	  /* Fall through.  */
253	case 2:
254	  if (! ieee_write_byte (abfd, (bfd_byte) (value >> 8)))
255	    return FALSE;
256	  /* Fall through.  */
257	case 1:
258	  if (! ieee_write_byte (abfd, (bfd_byte) (value)))
259	    return FALSE;
260	}
261    }
262
263  return TRUE;
264}
265
266static bfd_boolean
267ieee_write_id (abfd, id)
268     bfd *abfd;
269     const char *id;
270{
271  size_t length = strlen (id);
272
273  if (length <= 127)
274    {
275      if (! ieee_write_byte (abfd, (bfd_byte) length))
276	return FALSE;
277    }
278  else if (length < 255)
279    {
280      if (! ieee_write_byte (abfd, ieee_extension_length_1_enum)
281	  || ! ieee_write_byte (abfd, (bfd_byte) length))
282	return FALSE;
283    }
284  else if (length < 65535)
285    {
286      if (! ieee_write_byte (abfd, ieee_extension_length_2_enum)
287	  || ! ieee_write_2bytes (abfd, (int) length))
288	return FALSE;
289    }
290  else
291    {
292      (*_bfd_error_handler)
293	(_("%s: string too long (%d chars, max 65535)"),
294	 bfd_get_filename (abfd), length);
295      bfd_set_error (bfd_error_invalid_operation);
296      return FALSE;
297    }
298
299  if (bfd_bwrite ((PTR) id, (bfd_size_type) length, abfd) != length)
300    return FALSE;
301  return TRUE;
302}
303
304/* Functions for reading from ieee files in the strange way that the
305   standard requires.  */
306
307#define this_byte(ieee) *((ieee)->input_p)
308#define next_byte(ieee) ((ieee)->input_p++)
309#define this_byte_and_next(ieee) (*((ieee)->input_p++))
310
311static unsigned short
312read_2bytes (ieee)
313     common_header_type *ieee;
314{
315  unsigned char c1 = this_byte_and_next (ieee);
316  unsigned char c2 = this_byte_and_next (ieee);
317
318  return (c1 << 8) | c2;
319}
320
321static void
322bfd_get_string (ieee, string, length)
323     common_header_type *ieee;
324     char *string;
325     size_t length;
326{
327  size_t i;
328
329  for (i = 0; i < length; i++)
330    string[i] = this_byte_and_next (ieee);
331}
332
333static char *
334read_id (ieee)
335     common_header_type *ieee;
336{
337  size_t length;
338  char *string;
339
340  length = this_byte_and_next (ieee);
341  if (length <= 0x7f)
342    {
343      /* Simple string of length 0 to 127.  */
344    }
345  else if (length == 0xde)
346    {
347      /* Length is next byte, allowing 0..255.  */
348      length = this_byte_and_next (ieee);
349    }
350  else if (length == 0xdf)
351    {
352      /* Length is next two bytes, allowing 0..65535.  */
353      length = this_byte_and_next (ieee);
354      length = (length * 256) + this_byte_and_next (ieee);
355    }
356
357  /* Buy memory and read string.  */
358  string = bfd_alloc (ieee->abfd, (bfd_size_type) length + 1);
359  if (!string)
360    return NULL;
361  bfd_get_string (ieee, string, length);
362  string[length] = 0;
363  return string;
364}
365
366static bfd_boolean
367ieee_write_expression (abfd, value, symbol, pcrel, index)
368     bfd *abfd;
369     bfd_vma value;
370     asymbol *symbol;
371     bfd_boolean pcrel;
372     unsigned int index;
373{
374  unsigned int term_count = 0;
375
376  if (value != 0)
377    {
378      if (! ieee_write_int (abfd, value))
379	return FALSE;
380      term_count++;
381    }
382
383  /* Badly formatted binaries can have a missing symbol,
384     so test here to prevent a seg fault.  */
385  if (symbol != NULL)
386    {
387      if (bfd_is_com_section (symbol->section)
388	  || bfd_is_und_section (symbol->section))
389	{
390	  /* Def of a common symbol.  */
391	  if (! ieee_write_byte (abfd, ieee_variable_X_enum)
392	      || ! ieee_write_int (abfd, symbol->value))
393	    return FALSE;
394	  term_count ++;
395	}
396      else if (! bfd_is_abs_section (symbol->section))
397	{
398	  /* Ref to defined symbol -  */
399
400	  if (symbol->flags & BSF_GLOBAL)
401	    {
402	      if (! ieee_write_byte (abfd, ieee_variable_I_enum)
403		  || ! ieee_write_int (abfd, symbol->value))
404		return FALSE;
405	      term_count++;
406	    }
407	  else if (symbol->flags & (BSF_LOCAL | BSF_SECTION_SYM))
408	    {
409	      /* This is a reference to a defined local symbol.  We can
410		 easily do a local as a section+offset.  */
411	      if (! ieee_write_byte (abfd, ieee_variable_R_enum)
412		  || ! ieee_write_byte (abfd,
413					(bfd_byte) (symbol->section->index
414						    + IEEE_SECTION_NUMBER_BASE)))
415		return FALSE;
416
417	      term_count++;
418	      if (symbol->value != 0)
419		{
420		  if (! ieee_write_int (abfd, symbol->value))
421		    return FALSE;
422		  term_count++;
423		}
424	    }
425	  else
426	    {
427	      (*_bfd_error_handler)
428		(_("%s: unrecognized symbol `%s' flags 0x%x"),
429		 bfd_get_filename (abfd), bfd_asymbol_name (symbol),
430		 symbol->flags);
431	      bfd_set_error (bfd_error_invalid_operation);
432	      return FALSE;
433	    }
434	}
435    }
436
437  if (pcrel)
438    {
439      /* Subtract the pc from here by asking for PC of this section.  */
440      if (! ieee_write_byte (abfd, ieee_variable_P_enum)
441	  || ! ieee_write_byte (abfd,
442				(bfd_byte) (index + IEEE_SECTION_NUMBER_BASE))
443	  || ! ieee_write_byte (abfd, ieee_function_minus_enum))
444	return FALSE;
445    }
446
447  /* Handle the degenerate case of a 0 address.  */
448  if (term_count == 0)
449    if (! ieee_write_int (abfd, (bfd_vma) 0))
450      return FALSE;
451
452  while (term_count > 1)
453    {
454      if (! ieee_write_byte (abfd, ieee_function_plus_enum))
455	return FALSE;
456      term_count--;
457    }
458
459  return TRUE;
460}
461
462/* Writes any integer into the buffer supplied and always takes 5 bytes.  */
463
464static void
465ieee_write_int5 (buffer, value)
466     bfd_byte *buffer;
467     bfd_vma value;
468{
469  buffer[0] = (bfd_byte) ieee_number_repeat_4_enum;
470  buffer[1] = (value >> 24) & 0xff;
471  buffer[2] = (value >> 16) & 0xff;
472  buffer[3] = (value >> 8) & 0xff;
473  buffer[4] = (value >> 0) & 0xff;
474}
475
476static bfd_boolean
477ieee_write_int5_out (abfd, value)
478     bfd *abfd;
479     bfd_vma value;
480{
481  bfd_byte b[5];
482
483  ieee_write_int5 (b, value);
484  if (bfd_bwrite ((PTR) b, (bfd_size_type) 5, abfd) != 5)
485    return FALSE;
486  return TRUE;
487}
488
489static bfd_boolean
490parse_int (ieee, value_ptr)
491     common_header_type *ieee;
492     bfd_vma *value_ptr;
493{
494  int value = this_byte (ieee);
495  int result;
496
497  if (value >= 0 && value <= 127)
498    {
499      *value_ptr = value;
500      next_byte (ieee);
501      return TRUE;
502    }
503  else if (value >= 0x80 && value <= 0x88)
504    {
505      unsigned int count = value & 0xf;
506
507      result = 0;
508      next_byte (ieee);
509      while (count)
510	{
511	  result = (result << 8) | this_byte_and_next (ieee);
512	  count--;
513	}
514      *value_ptr = result;
515      return TRUE;
516    }
517  return FALSE;
518}
519
520static int
521parse_i (ieee, ok)
522     common_header_type *ieee;
523     bfd_boolean *ok;
524{
525  bfd_vma x;
526  *ok = parse_int (ieee, &x);
527  return x;
528}
529
530static bfd_vma
531must_parse_int (ieee)
532     common_header_type *ieee;
533{
534  bfd_vma result;
535  BFD_ASSERT (parse_int (ieee, &result));
536  return result;
537}
538
539typedef struct
540{
541  bfd_vma value;
542  asection *section;
543  ieee_symbol_index_type symbol;
544} ieee_value_type;
545
546
547#if KEEPMINUSPCININST
548
549#define SRC_MASK(arg) arg
550#define PCREL_OFFSET FALSE
551
552#else
553
554#define SRC_MASK(arg) 0
555#define PCREL_OFFSET TRUE
556
557#endif
558
559static reloc_howto_type abs32_howto =
560  HOWTO (1,
561	 0,
562	 2,
563	 32,
564	 FALSE,
565	 0,
566	 complain_overflow_bitfield,
567	 0,
568	 "abs32",
569	 TRUE,
570	 0xffffffff,
571	 0xffffffff,
572	 FALSE);
573
574static reloc_howto_type abs16_howto =
575  HOWTO (1,
576	 0,
577	 1,
578	 16,
579	 FALSE,
580	 0,
581	 complain_overflow_bitfield,
582	 0,
583	 "abs16",
584	 TRUE,
585	 0x0000ffff,
586	 0x0000ffff,
587	 FALSE);
588
589static reloc_howto_type abs8_howto =
590  HOWTO (1,
591	 0,
592	 0,
593	 8,
594	 FALSE,
595	 0,
596	 complain_overflow_bitfield,
597	 0,
598	 "abs8",
599	 TRUE,
600	 0x000000ff,
601	 0x000000ff,
602	 FALSE);
603
604static reloc_howto_type rel32_howto =
605  HOWTO (1,
606	 0,
607	 2,
608	 32,
609	 TRUE,
610	 0,
611	 complain_overflow_signed,
612	 0,
613	 "rel32",
614	 TRUE,
615	 SRC_MASK (0xffffffff),
616	 0xffffffff,
617	 PCREL_OFFSET);
618
619static reloc_howto_type rel16_howto =
620  HOWTO (1,
621	 0,
622	 1,
623	 16,
624	 TRUE,
625	 0,
626	 complain_overflow_signed,
627	 0,
628	 "rel16",
629	 TRUE,
630	 SRC_MASK (0x0000ffff),
631	 0x0000ffff,
632	 PCREL_OFFSET);
633
634static reloc_howto_type rel8_howto =
635  HOWTO (1,
636	 0,
637	 0,
638	 8,
639	 TRUE,
640	 0,
641	 complain_overflow_signed,
642	 0,
643	 "rel8",
644	 TRUE,
645	 SRC_MASK (0x000000ff),
646	 0x000000ff,
647	 PCREL_OFFSET);
648
649static ieee_symbol_index_type NOSYMBOL = {0, 0};
650
651static void
652parse_expression (ieee, value, symbol, pcrel, extra, section)
653     ieee_data_type *ieee;
654     bfd_vma *value;
655     ieee_symbol_index_type *symbol;
656     bfd_boolean *pcrel;
657     unsigned int *extra;
658     asection **section;
659
660{
661#define POS sp[1]
662#define TOS sp[0]
663#define NOS sp[-1]
664#define INC sp++;
665#define DEC sp--;
666
667  bfd_boolean loop = TRUE;
668  ieee_value_type stack[10];
669
670  /* The stack pointer always points to the next unused location.  */
671#define PUSH(x,y,z) TOS.symbol=x;TOS.section=y;TOS.value=z;INC;
672#define POP(x,y,z) DEC;x=TOS.symbol;y=TOS.section;z=TOS.value;
673  ieee_value_type *sp = stack;
674  asection *dummy;
675
676  while (loop && ieee->h.input_p < ieee->h.last_byte)
677    {
678      switch (this_byte (&(ieee->h)))
679	{
680	case ieee_variable_P_enum:
681	  /* P variable, current program counter for section n.  */
682	  {
683	    int section_n;
684
685	    next_byte (&(ieee->h));
686	    *pcrel = TRUE;
687	    section_n = must_parse_int (&(ieee->h));
688	    PUSH (NOSYMBOL, bfd_abs_section_ptr, 0);
689	    break;
690	  }
691	case ieee_variable_L_enum:
692	  /* L variable  address of section N.  */
693	  next_byte (&(ieee->h));
694	  PUSH (NOSYMBOL, ieee->section_table[must_parse_int (&(ieee->h))], 0);
695	  break;
696	case ieee_variable_R_enum:
697	  /* R variable, logical address of section module.  */
698	  /* FIXME, this should be different to L.  */
699	  next_byte (&(ieee->h));
700	  PUSH (NOSYMBOL, ieee->section_table[must_parse_int (&(ieee->h))], 0);
701	  break;
702	case ieee_variable_S_enum:
703	  /* S variable, size in MAUS of section module.  */
704	  next_byte (&(ieee->h));
705	  PUSH (NOSYMBOL,
706		0,
707		ieee->section_table[must_parse_int (&(ieee->h))]->size);
708	  break;
709	case ieee_variable_I_enum:
710	  /* Push the address of variable n.  */
711	  {
712	    ieee_symbol_index_type sy;
713	    next_byte (&(ieee->h));
714	    sy.index = (int) must_parse_int (&(ieee->h));
715	    sy.letter = 'I';
716
717	    PUSH (sy, bfd_abs_section_ptr, 0);
718	  }
719	  break;
720	case ieee_variable_X_enum:
721	  /* Push the address of external variable n.  */
722	  {
723	    ieee_symbol_index_type sy;
724	    next_byte (&(ieee->h));
725	    sy.index = (int) (must_parse_int (&(ieee->h)));
726	    sy.letter = 'X';
727
728	    PUSH (sy, bfd_und_section_ptr, 0);
729	  }
730	  break;
731	case ieee_function_minus_enum:
732	  {
733	    bfd_vma value1, value2;
734	    asection *section1, *section_dummy;
735	    ieee_symbol_index_type sy;
736	    next_byte (&(ieee->h));
737
738	    POP (sy, section1, value1);
739	    POP (sy, section_dummy, value2);
740	    PUSH (sy, section1 ? section1 : section_dummy, value2 - value1);
741	  }
742	  break;
743	case ieee_function_plus_enum:
744	  {
745	    bfd_vma value1, value2;
746	    asection *section1;
747	    asection *section2;
748	    ieee_symbol_index_type sy1;
749	    ieee_symbol_index_type sy2;
750	    next_byte (&(ieee->h));
751
752	    POP (sy1, section1, value1);
753	    POP (sy2, section2, value2);
754	    PUSH (sy1.letter ? sy1 : sy2,
755		  bfd_is_abs_section (section1) ? section2 : section1,
756		  value1 + value2);
757	  }
758	  break;
759	default:
760	  {
761	    bfd_vma va;
762	    BFD_ASSERT (this_byte (&(ieee->h)) < (int) ieee_variable_A_enum
763		    || this_byte (&(ieee->h)) > (int) ieee_variable_Z_enum);
764	    if (parse_int (&(ieee->h), &va))
765	      {
766		PUSH (NOSYMBOL, bfd_abs_section_ptr, va);
767	      }
768	    else
769	      {
770		/* Thats all that we can understand.  */
771		loop = FALSE;
772	      }
773	  }
774	}
775    }
776
777  /* As far as I can see there is a bug in the Microtec IEEE output
778     which I'm using to scan, whereby the comma operator is omitted
779     sometimes in an expression, giving expressions with too many
780     terms.  We can tell if that's the case by ensuring that
781     sp == stack here.  If not, then we've pushed something too far,
782     so we keep adding.  */
783  while (sp != stack + 1)
784    {
785      asection *section1;
786      ieee_symbol_index_type sy1;
787      POP (sy1, section1, *extra);
788    }
789
790  POP (*symbol, dummy, *value);
791  if (section)
792    *section = dummy;
793}
794
795
796#define ieee_seek(ieee, offset) \
797  do								\
798    {								\
799      ieee->h.input_p = ieee->h.first_byte + offset;		\
800      ieee->h.last_byte = (ieee->h.first_byte			\
801			   + ieee_part_after (ieee, offset));	\
802    }								\
803  while (0)
804
805#define ieee_pos(ieee) \
806  (ieee->h.input_p - ieee->h.first_byte)
807
808/* Find the first part of the ieee file after HERE.  */
809
810static file_ptr
811ieee_part_after (ieee, here)
812     ieee_data_type *ieee;
813     file_ptr here;
814{
815  int part;
816  file_ptr after = ieee->w.r.me_record;
817
818  /* File parts can come in any order, except that module end is
819     guaranteed to be last (and the header first).  */
820  for (part = 0; part < N_W_VARIABLES; part++)
821    if (ieee->w.offset[part] > here && after > ieee->w.offset[part])
822      after = ieee->w.offset[part];
823
824  return after;
825}
826
827static unsigned int last_index;
828static char last_type;		/* Is the index for an X or a D.  */
829
830static ieee_symbol_type *
831get_symbol (abfd, ieee, last_symbol, symbol_count, pptr, max_index, this_type)
832     bfd *abfd ATTRIBUTE_UNUSED;
833     ieee_data_type *ieee;
834     ieee_symbol_type *last_symbol;
835     unsigned int *symbol_count;
836     ieee_symbol_type ***pptr;
837     unsigned int *max_index;
838     int this_type;
839{
840  /* Need a new symbol.  */
841  unsigned int new_index = must_parse_int (&(ieee->h));
842
843  if (new_index != last_index || this_type != last_type)
844    {
845      ieee_symbol_type *new_symbol;
846      bfd_size_type amt = sizeof (ieee_symbol_type);
847
848      new_symbol = (ieee_symbol_type *) bfd_alloc (ieee->h.abfd, amt);
849      if (!new_symbol)
850	return NULL;
851
852      new_symbol->index = new_index;
853      last_index = new_index;
854      (*symbol_count)++;
855      **pptr = new_symbol;
856      *pptr = &new_symbol->next;
857      if (new_index > *max_index)
858	*max_index = new_index;
859
860      last_type = this_type;
861      new_symbol->symbol.section = bfd_abs_section_ptr;
862      return new_symbol;
863    }
864  return last_symbol;
865}
866
867static bfd_boolean
868ieee_slurp_external_symbols (abfd)
869     bfd *abfd;
870{
871  ieee_data_type *ieee = IEEE_DATA (abfd);
872  file_ptr offset = ieee->w.r.external_part;
873
874  ieee_symbol_type **prev_symbols_ptr = &ieee->external_symbols;
875  ieee_symbol_type **prev_reference_ptr = &ieee->external_reference;
876  ieee_symbol_type *symbol = (ieee_symbol_type *) NULL;
877  unsigned int symbol_count = 0;
878  bfd_boolean loop = TRUE;
879  last_index = 0xffffff;
880  ieee->symbol_table_full = TRUE;
881
882  ieee_seek (ieee, offset);
883
884  while (loop)
885    {
886      switch (this_byte (&(ieee->h)))
887	{
888	case ieee_nn_record:
889	  next_byte (&(ieee->h));
890
891	  symbol = get_symbol (abfd, ieee, symbol, &symbol_count,
892			       &prev_symbols_ptr,
893			       &ieee->external_symbol_max_index, 'I');
894	  if (symbol == NULL)
895	    return FALSE;
896
897	  symbol->symbol.the_bfd = abfd;
898	  symbol->symbol.name = read_id (&(ieee->h));
899	  symbol->symbol.udata.p = (PTR) NULL;
900	  symbol->symbol.flags = BSF_NO_FLAGS;
901	  break;
902	case ieee_external_symbol_enum:
903	  next_byte (&(ieee->h));
904
905	  symbol = get_symbol (abfd, ieee, symbol, &symbol_count,
906			       &prev_symbols_ptr,
907			       &ieee->external_symbol_max_index, 'D');
908	  if (symbol == NULL)
909	    return FALSE;
910
911	  BFD_ASSERT (symbol->index >= ieee->external_symbol_min_index);
912
913	  symbol->symbol.the_bfd = abfd;
914	  symbol->symbol.name = read_id (&(ieee->h));
915	  symbol->symbol.udata.p = (PTR) NULL;
916	  symbol->symbol.flags = BSF_NO_FLAGS;
917	  break;
918	case ieee_attribute_record_enum >> 8:
919	  {
920	    unsigned int symbol_name_index;
921	    unsigned int symbol_type_index;
922	    unsigned int symbol_attribute_def;
923	    bfd_vma value;
924	    switch (read_2bytes (&ieee->h))
925	      {
926	      case ieee_attribute_record_enum:
927		symbol_name_index = must_parse_int (&(ieee->h));
928		symbol_type_index = must_parse_int (&(ieee->h));
929		symbol_attribute_def = must_parse_int (&(ieee->h));
930		switch (symbol_attribute_def)
931		  {
932		  case 8:
933		  case 19:
934		    parse_int (&ieee->h, &value);
935		    break;
936		  default:
937		    (*_bfd_error_handler)
938		      (_("%B: unimplemented ATI record %u for symbol %u"),
939		       abfd, symbol_attribute_def, symbol_name_index);
940		    bfd_set_error (bfd_error_bad_value);
941		    return FALSE;
942		    break;
943		  }
944		break;
945	      case ieee_external_reference_info_record_enum:
946		/* Skip over ATX record.  */
947		parse_int (&(ieee->h), &value);
948		parse_int (&(ieee->h), &value);
949		parse_int (&(ieee->h), &value);
950		parse_int (&(ieee->h), &value);
951		break;
952	      case ieee_atn_record_enum:
953		/* We may get call optimization information here,
954		   which we just ignore.  The format is
955		   {$F1}${CE}{index}{$00}{$3F}{$3F}{#_of_ASNs}.  */
956		parse_int (&ieee->h, &value);
957		parse_int (&ieee->h, &value);
958		parse_int (&ieee->h, &value);
959		if (value != 0x3f)
960		  {
961		    (*_bfd_error_handler)
962		      (_("%B: unexpected ATN type %d in external part"),
963			 abfd, (int) value);
964		    bfd_set_error (bfd_error_bad_value);
965		    return FALSE;
966		  }
967		parse_int (&ieee->h, &value);
968		parse_int (&ieee->h, &value);
969		while (value > 0)
970		  {
971		    bfd_vma val1;
972
973		    --value;
974
975		    switch (read_2bytes (&ieee->h))
976		      {
977		      case ieee_asn_record_enum:
978			parse_int (&ieee->h, &val1);
979			parse_int (&ieee->h, &val1);
980			break;
981
982		      default:
983			(*_bfd_error_handler)
984			  (_("%B: unexpected type after ATN"), abfd);
985			bfd_set_error (bfd_error_bad_value);
986			return FALSE;
987		      }
988		  }
989	      }
990	  }
991	  break;
992	case ieee_value_record_enum >> 8:
993	  {
994	    unsigned int symbol_name_index;
995	    ieee_symbol_index_type symbol_ignore;
996	    bfd_boolean pcrel_ignore;
997	    unsigned int extra;
998	    next_byte (&(ieee->h));
999	    next_byte (&(ieee->h));
1000
1001	    symbol_name_index = must_parse_int (&(ieee->h));
1002	    parse_expression (ieee,
1003			      &symbol->symbol.value,
1004			      &symbol_ignore,
1005			      &pcrel_ignore,
1006			      &extra,
1007			      &symbol->symbol.section);
1008
1009	    /* Fully linked IEEE-695 files tend to give every symbol
1010               an absolute value.  Try to convert that back into a
1011               section relative value.  FIXME: This won't always to
1012               the right thing.  */
1013	    if (bfd_is_abs_section (symbol->symbol.section)
1014		&& (abfd->flags & HAS_RELOC) == 0)
1015	      {
1016		bfd_vma val;
1017		asection *s;
1018
1019		val = symbol->symbol.value;
1020		for (s = abfd->sections; s != NULL; s = s->next)
1021		  {
1022		    if (val >= s->vma && val < s->vma + s->size)
1023		      {
1024			symbol->symbol.section = s;
1025			symbol->symbol.value -= s->vma;
1026			break;
1027		      }
1028		  }
1029	      }
1030
1031	    symbol->symbol.flags = BSF_GLOBAL | BSF_EXPORT;
1032
1033	  }
1034	  break;
1035	case ieee_weak_external_reference_enum:
1036	  {
1037	    bfd_vma size;
1038	    bfd_vma value;
1039	    next_byte (&(ieee->h));
1040	    /* Throw away the external reference index.  */
1041	    (void) must_parse_int (&(ieee->h));
1042	    /* Fetch the default size if not resolved.  */
1043	    size = must_parse_int (&(ieee->h));
1044	    /* Fetch the default value if available.  */
1045	    if (! parse_int (&(ieee->h), &value))
1046	      {
1047		value = 0;
1048	      }
1049	    /* This turns into a common.  */
1050	    symbol->symbol.section = bfd_com_section_ptr;
1051	    symbol->symbol.value = size;
1052	  }
1053	  break;
1054
1055	case ieee_external_reference_enum:
1056	  next_byte (&(ieee->h));
1057
1058	  symbol = get_symbol (abfd, ieee, symbol, &symbol_count,
1059			       &prev_reference_ptr,
1060			       &ieee->external_reference_max_index, 'X');
1061	  if (symbol == NULL)
1062	    return FALSE;
1063
1064	  symbol->symbol.the_bfd = abfd;
1065	  symbol->symbol.name = read_id (&(ieee->h));
1066	  symbol->symbol.udata.p = (PTR) NULL;
1067	  symbol->symbol.section = bfd_und_section_ptr;
1068	  symbol->symbol.value = (bfd_vma) 0;
1069	  symbol->symbol.flags = 0;
1070
1071	  BFD_ASSERT (symbol->index >= ieee->external_reference_min_index);
1072	  break;
1073
1074	default:
1075	  loop = FALSE;
1076	}
1077    }
1078
1079  if (ieee->external_symbol_max_index != 0)
1080    {
1081      ieee->external_symbol_count =
1082	ieee->external_symbol_max_index -
1083	ieee->external_symbol_min_index + 1;
1084    }
1085  else
1086    {
1087      ieee->external_symbol_count = 0;
1088    }
1089
1090  if (ieee->external_reference_max_index != 0)
1091    {
1092      ieee->external_reference_count =
1093	ieee->external_reference_max_index -
1094	ieee->external_reference_min_index + 1;
1095    }
1096  else
1097    {
1098      ieee->external_reference_count = 0;
1099    }
1100
1101  abfd->symcount =
1102    ieee->external_reference_count + ieee->external_symbol_count;
1103
1104  if (symbol_count != abfd->symcount)
1105    {
1106      /* There are gaps in the table -- */
1107      ieee->symbol_table_full = FALSE;
1108    }
1109
1110  *prev_symbols_ptr = (ieee_symbol_type *) NULL;
1111  *prev_reference_ptr = (ieee_symbol_type *) NULL;
1112
1113  return TRUE;
1114}
1115
1116static bfd_boolean
1117ieee_slurp_symbol_table (abfd)
1118     bfd *abfd;
1119{
1120  if (! IEEE_DATA (abfd)->read_symbols)
1121    {
1122      if (! ieee_slurp_external_symbols (abfd))
1123	return FALSE;
1124      IEEE_DATA (abfd)->read_symbols = TRUE;
1125    }
1126  return TRUE;
1127}
1128
1129static long
1130ieee_get_symtab_upper_bound (abfd)
1131     bfd *abfd;
1132{
1133  if (! ieee_slurp_symbol_table (abfd))
1134    return -1;
1135
1136  return (abfd->symcount != 0) ?
1137    (abfd->symcount + 1) * (sizeof (ieee_symbol_type *)) : 0;
1138}
1139
1140/* Move from our internal lists to the canon table, and insert in
1141   symbol index order.  */
1142
1143extern const bfd_target ieee_vec;
1144
1145static long
1146ieee_canonicalize_symtab (abfd, location)
1147     bfd *abfd;
1148     asymbol **location;
1149{
1150  ieee_symbol_type *symp;
1151  static bfd dummy_bfd;
1152  static asymbol empty_symbol =
1153  {
1154    &dummy_bfd,
1155    " ieee empty",
1156    (symvalue) 0,
1157    BSF_DEBUGGING,
1158    bfd_abs_section_ptr
1159#ifdef __STDC__
1160    /* K&R compilers can't initialise unions.  */
1161    , { 0 }
1162#endif
1163  };
1164
1165  if (abfd->symcount)
1166    {
1167      ieee_data_type *ieee = IEEE_DATA (abfd);
1168      dummy_bfd.xvec = &ieee_vec;
1169      if (! ieee_slurp_symbol_table (abfd))
1170	return -1;
1171
1172      if (! ieee->symbol_table_full)
1173	{
1174	  /* Arrgh - there are gaps in the table, run through and fill them
1175	     up with pointers to a null place.  */
1176	  unsigned int i;
1177
1178	  for (i = 0; i < abfd->symcount; i++)
1179	    location[i] = &empty_symbol;
1180	}
1181
1182      ieee->external_symbol_base_offset = -ieee->external_symbol_min_index;
1183      for (symp = IEEE_DATA (abfd)->external_symbols;
1184	   symp != (ieee_symbol_type *) NULL;
1185	   symp = symp->next)
1186	/* Place into table at correct index locations.  */
1187	location[symp->index + ieee->external_symbol_base_offset] = &symp->symbol;
1188
1189      /* The external refs are indexed in a bit.  */
1190      ieee->external_reference_base_offset =
1191	-ieee->external_reference_min_index + ieee->external_symbol_count;
1192
1193      for (symp = IEEE_DATA (abfd)->external_reference;
1194	   symp != (ieee_symbol_type *) NULL;
1195	   symp = symp->next)
1196	location[symp->index + ieee->external_reference_base_offset] =
1197	  &symp->symbol;
1198    }
1199
1200  if (abfd->symcount)
1201    location[abfd->symcount] = (asymbol *) NULL;
1202
1203  return abfd->symcount;
1204}
1205
1206static asection *
1207get_section_entry (abfd, ieee, index)
1208     bfd *abfd;
1209     ieee_data_type *ieee;
1210     unsigned int index;
1211{
1212  if (index >= ieee->section_table_size)
1213    {
1214      unsigned int c, i;
1215      asection **n;
1216      bfd_size_type amt;
1217
1218      c = ieee->section_table_size;
1219      if (c == 0)
1220	c = 20;
1221      while (c <= index)
1222	c *= 2;
1223
1224      amt = c;
1225      amt *= sizeof (asection *);
1226      n = (asection **) bfd_realloc (ieee->section_table, amt);
1227      if (n == NULL)
1228	return NULL;
1229
1230      for (i = ieee->section_table_size; i < c; i++)
1231	n[i] = NULL;
1232
1233      ieee->section_table = n;
1234      ieee->section_table_size = c;
1235    }
1236
1237  if (ieee->section_table[index] == (asection *) NULL)
1238    {
1239      char *tmp = bfd_alloc (abfd, (bfd_size_type) 11);
1240      asection *section;
1241
1242      if (!tmp)
1243	return NULL;
1244      sprintf (tmp, " fsec%4d", index);
1245      section = bfd_make_section (abfd, tmp);
1246      ieee->section_table[index] = section;
1247      section->flags = SEC_NO_FLAGS;
1248      section->target_index = index;
1249      ieee->section_table[index] = section;
1250    }
1251  return ieee->section_table[index];
1252}
1253
1254static void
1255ieee_slurp_sections (abfd)
1256     bfd *abfd;
1257{
1258  ieee_data_type *ieee = IEEE_DATA (abfd);
1259  file_ptr offset = ieee->w.r.section_part;
1260  char *name;
1261
1262  if (offset != 0)
1263    {
1264      bfd_byte section_type[3];
1265      ieee_seek (ieee, offset);
1266      while (TRUE)
1267	{
1268	  switch (this_byte (&(ieee->h)))
1269	    {
1270	    case ieee_section_type_enum:
1271	      {
1272		asection *section;
1273		unsigned int section_index;
1274		next_byte (&(ieee->h));
1275		section_index = must_parse_int (&(ieee->h));
1276
1277		section = get_section_entry (abfd, ieee, section_index);
1278
1279		section_type[0] = this_byte_and_next (&(ieee->h));
1280
1281		/* Set minimal section attributes. Attributes are
1282		   extended later, based on section contents.  */
1283		switch (section_type[0])
1284		  {
1285		  case 0xC1:
1286		    /* Normal attributes for absolute sections.  */
1287		    section_type[1] = this_byte (&(ieee->h));
1288		    section->flags = SEC_ALLOC;
1289		    switch (section_type[1])
1290		      {
1291		      case 0xD3:	/* AS Absolute section attributes.  */
1292			next_byte (&(ieee->h));
1293			section_type[2] = this_byte (&(ieee->h));
1294			switch (section_type[2])
1295			  {
1296			  case 0xD0:
1297			    /* Normal code.  */
1298			    next_byte (&(ieee->h));
1299			    section->flags |= SEC_CODE;
1300			    break;
1301			  case 0xC4:
1302			    /* Normal data.  */
1303			    next_byte (&(ieee->h));
1304			    section->flags |= SEC_DATA;
1305			    break;
1306			  case 0xD2:
1307			    next_byte (&(ieee->h));
1308			    /* Normal rom data.  */
1309			    section->flags |= SEC_ROM | SEC_DATA;
1310			    break;
1311			  default:
1312			    break;
1313			  }
1314		      }
1315		    break;
1316		  case 0xC3:	/* Named relocatable sections (type C).  */
1317		    section_type[1] = this_byte (&(ieee->h));
1318		    section->flags = SEC_ALLOC;
1319		    switch (section_type[1])
1320		      {
1321		      case 0xD0:	/* Normal code (CP).  */
1322			next_byte (&(ieee->h));
1323			section->flags |= SEC_CODE;
1324			break;
1325		      case 0xC4:	/* Normal data (CD).  */
1326			next_byte (&(ieee->h));
1327			section->flags |= SEC_DATA;
1328			break;
1329		      case 0xD2:	/* Normal rom data (CR).  */
1330			next_byte (&(ieee->h));
1331			section->flags |= SEC_ROM | SEC_DATA;
1332			break;
1333		      default:
1334			break;
1335		      }
1336		  }
1337
1338		/* Read section name, use it if non empty.  */
1339		name = read_id (&ieee->h);
1340		if (name[0])
1341		  section->name = name;
1342
1343		/* Skip these fields, which we don't care about.  */
1344		{
1345		  bfd_vma parent, brother, context;
1346		  parse_int (&(ieee->h), &parent);
1347		  parse_int (&(ieee->h), &brother);
1348		  parse_int (&(ieee->h), &context);
1349		}
1350	      }
1351	      break;
1352	    case ieee_section_alignment_enum:
1353	      {
1354		unsigned int section_index;
1355		bfd_vma value;
1356		asection *section;
1357		next_byte (&(ieee->h));
1358		section_index = must_parse_int (&ieee->h);
1359		section = get_section_entry (abfd, ieee, section_index);
1360		if (section_index > ieee->section_count)
1361		  {
1362		    ieee->section_count = section_index;
1363		  }
1364		section->alignment_power =
1365		  bfd_log2 (must_parse_int (&ieee->h));
1366		(void) parse_int (&(ieee->h), &value);
1367	      }
1368	      break;
1369	    case ieee_e2_first_byte_enum:
1370	      {
1371		asection *section;
1372		ieee_record_enum_type t;
1373
1374		t = (ieee_record_enum_type) (read_2bytes (&(ieee->h)));
1375		switch (t)
1376		  {
1377		  case ieee_section_size_enum:
1378		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1379		    section->size = must_parse_int (&(ieee->h));
1380		    break;
1381		  case ieee_physical_region_size_enum:
1382		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1383		    section->size = must_parse_int (&(ieee->h));
1384		    break;
1385		  case ieee_region_base_address_enum:
1386		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1387		    section->vma = must_parse_int (&(ieee->h));
1388		    section->lma = section->vma;
1389		    break;
1390		  case ieee_mau_size_enum:
1391		    must_parse_int (&(ieee->h));
1392		    must_parse_int (&(ieee->h));
1393		    break;
1394		  case ieee_m_value_enum:
1395		    must_parse_int (&(ieee->h));
1396		    must_parse_int (&(ieee->h));
1397		    break;
1398		  case ieee_section_base_address_enum:
1399		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1400		    section->vma = must_parse_int (&(ieee->h));
1401		    section->lma = section->vma;
1402		    break;
1403		  case ieee_section_offset_enum:
1404		    (void) must_parse_int (&(ieee->h));
1405		    (void) must_parse_int (&(ieee->h));
1406		    break;
1407		  default:
1408		    return;
1409		  }
1410	      }
1411	      break;
1412	    default:
1413	      return;
1414	    }
1415	}
1416    }
1417}
1418
1419/* Make a section for the debugging information, if any.  We don't try
1420   to interpret the debugging information; we just point the section
1421   at the area in the file so that program which understand can dig it
1422   out.  */
1423
1424static bfd_boolean
1425ieee_slurp_debug (abfd)
1426     bfd *abfd;
1427{
1428  ieee_data_type *ieee = IEEE_DATA (abfd);
1429  asection *sec;
1430  file_ptr debug_end;
1431
1432  if (ieee->w.r.debug_information_part == 0)
1433    return TRUE;
1434
1435  sec = bfd_make_section (abfd, ".debug");
1436  if (sec == NULL)
1437    return FALSE;
1438  sec->flags |= SEC_DEBUGGING | SEC_HAS_CONTENTS;
1439  sec->filepos = ieee->w.r.debug_information_part;
1440
1441  debug_end = ieee_part_after (ieee, ieee->w.r.debug_information_part);
1442  sec->size = debug_end - ieee->w.r.debug_information_part;
1443
1444  return TRUE;
1445}
1446
1447/* Archive stuff.  */
1448
1449const bfd_target *
1450ieee_archive_p (abfd)
1451     bfd *abfd;
1452{
1453  char *library;
1454  unsigned int i;
1455  unsigned char buffer[512];
1456  file_ptr buffer_offset = 0;
1457  ieee_ar_data_type *save = abfd->tdata.ieee_ar_data;
1458  ieee_ar_data_type *ieee;
1459  bfd_size_type alc_elts;
1460  ieee_ar_obstack_type *elts = NULL;
1461  bfd_size_type amt = sizeof (ieee_ar_data_type);
1462
1463  abfd->tdata.ieee_ar_data = (ieee_ar_data_type *) bfd_alloc (abfd, amt);
1464  if (!abfd->tdata.ieee_ar_data)
1465    goto error_ret_restore;
1466  ieee = IEEE_AR_DATA (abfd);
1467
1468  /* Ignore the return value here.  It doesn't matter if we don't read
1469     the entire buffer.  We might have a very small ieee file.  */
1470  bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1471
1472  ieee->h.first_byte = buffer;
1473  ieee->h.input_p = buffer;
1474
1475  ieee->h.abfd = abfd;
1476
1477  if (this_byte (&(ieee->h)) != Module_Beginning)
1478    goto got_wrong_format_error;
1479
1480  next_byte (&(ieee->h));
1481  library = read_id (&(ieee->h));
1482  if (strcmp (library, "LIBRARY") != 0)
1483    goto got_wrong_format_error;
1484
1485  /* Throw away the filename.  */
1486  read_id (&(ieee->h));
1487
1488  ieee->element_count = 0;
1489  ieee->element_index = 0;
1490
1491  next_byte (&(ieee->h));	/* Drop the ad part.  */
1492  must_parse_int (&(ieee->h));	/* And the two dummy numbers.  */
1493  must_parse_int (&(ieee->h));
1494
1495  alc_elts = 10;
1496  elts = (ieee_ar_obstack_type *) bfd_malloc (alc_elts * sizeof *elts);
1497  if (elts == NULL)
1498    goto error_return;
1499
1500  /* Read the index of the BB table.  */
1501  while (1)
1502    {
1503      int rec;
1504      ieee_ar_obstack_type *t;
1505
1506      rec = read_2bytes (&(ieee->h));
1507      if (rec != (int) ieee_assign_value_to_variable_enum)
1508	break;
1509
1510      if (ieee->element_count >= alc_elts)
1511	{
1512	  ieee_ar_obstack_type *n;
1513
1514	  alc_elts *= 2;
1515	  n = ((ieee_ar_obstack_type *)
1516	       bfd_realloc (elts, alc_elts * sizeof *elts));
1517	  if (n == NULL)
1518	    goto error_return;
1519	  elts = n;
1520	}
1521
1522      t = &elts[ieee->element_count];
1523      ieee->element_count++;
1524
1525      must_parse_int (&(ieee->h));
1526      t->file_offset = must_parse_int (&(ieee->h));
1527      t->abfd = (bfd *) NULL;
1528
1529      /* Make sure that we don't go over the end of the buffer.  */
1530      if ((size_t) ieee_pos (IEEE_DATA (abfd)) > sizeof (buffer) / 2)
1531	{
1532	  /* Past half way, reseek and reprime.  */
1533	  buffer_offset += ieee_pos (IEEE_DATA (abfd));
1534	  if (bfd_seek (abfd, buffer_offset, SEEK_SET) != 0)
1535	    goto error_return;
1536
1537	  /* Again ignore return value of bfd_bread.  */
1538	  bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1539	  ieee->h.first_byte = buffer;
1540	  ieee->h.input_p = buffer;
1541	}
1542    }
1543
1544  amt = ieee->element_count;
1545  amt *= sizeof *ieee->elements;
1546  ieee->elements = (ieee_ar_obstack_type *) bfd_alloc (abfd, amt);
1547  if (ieee->elements == NULL)
1548    goto error_return;
1549
1550  memcpy (ieee->elements, elts, (size_t) amt);
1551  free (elts);
1552  elts = NULL;
1553
1554  /* Now scan the area again, and replace BB offsets with file offsets.  */
1555  for (i = 2; i < ieee->element_count; i++)
1556    {
1557      if (bfd_seek (abfd, ieee->elements[i].file_offset, SEEK_SET) != 0)
1558	goto error_return;
1559
1560      /* Again ignore return value of bfd_bread.  */
1561      bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1562      ieee->h.first_byte = buffer;
1563      ieee->h.input_p = buffer;
1564
1565      next_byte (&(ieee->h));		/* Drop F8.  */
1566      next_byte (&(ieee->h));		/* Drop 14.  */
1567      must_parse_int (&(ieee->h));	/* Drop size of block.  */
1568
1569      if (must_parse_int (&(ieee->h)) != 0)
1570	/* This object has been deleted.  */
1571	ieee->elements[i].file_offset = 0;
1572      else
1573	ieee->elements[i].file_offset = must_parse_int (&(ieee->h));
1574    }
1575
1576  /*  abfd->has_armap = ;*/
1577
1578  return abfd->xvec;
1579
1580 got_wrong_format_error:
1581  bfd_set_error (bfd_error_wrong_format);
1582 error_return:
1583  if (elts != NULL)
1584    free (elts);
1585  bfd_release (abfd, ieee);
1586 error_ret_restore:
1587  abfd->tdata.ieee_ar_data = save;
1588
1589  return NULL;
1590}
1591
1592const bfd_target *
1593ieee_object_p (abfd)
1594     bfd *abfd;
1595{
1596  char *processor;
1597  unsigned int part;
1598  ieee_data_type *ieee;
1599  unsigned char buffer[300];
1600  ieee_data_type *save = IEEE_DATA (abfd);
1601  bfd_size_type amt;
1602
1603  abfd->tdata.ieee_data = 0;
1604  ieee_mkobject (abfd);
1605
1606  ieee = IEEE_DATA (abfd);
1607  if (bfd_seek (abfd, (file_ptr) 0, SEEK_SET) != 0)
1608    goto fail;
1609  /* Read the first few bytes in to see if it makes sense.  Ignore
1610     bfd_bread return value;  The file might be very small.  */
1611  bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1612
1613  ieee->h.input_p = buffer;
1614  if (this_byte_and_next (&(ieee->h)) != Module_Beginning)
1615    goto got_wrong_format;
1616
1617  ieee->read_symbols = FALSE;
1618  ieee->read_data = FALSE;
1619  ieee->section_count = 0;
1620  ieee->external_symbol_max_index = 0;
1621  ieee->external_symbol_min_index = IEEE_PUBLIC_BASE;
1622  ieee->external_reference_min_index = IEEE_REFERENCE_BASE;
1623  ieee->external_reference_max_index = 0;
1624  ieee->h.abfd = abfd;
1625  ieee->section_table = NULL;
1626  ieee->section_table_size = 0;
1627
1628  processor = ieee->mb.processor = read_id (&(ieee->h));
1629  if (strcmp (processor, "LIBRARY") == 0)
1630    goto got_wrong_format;
1631  ieee->mb.module_name = read_id (&(ieee->h));
1632  if (abfd->filename == (const char *) NULL)
1633    abfd->filename = ieee->mb.module_name;
1634
1635  /* Determine the architecture and machine type of the object file.  */
1636  {
1637    const bfd_arch_info_type *arch;
1638    char family[10];
1639
1640    /* IEEE does not specify the format of the processor identification
1641       string, so the compiler is free to put in it whatever it wants.
1642       We try here to recognize different processors belonging to the
1643       m68k family.  Code for other processors can be added here.  */
1644    if ((processor[0] == '6') && (processor[1] == '8'))
1645      {
1646	if (processor[2] == '3')	    /* 683xx integrated processors */
1647	  {
1648	    switch (processor[3])
1649	      {
1650	      case '0':			    /* 68302, 68306, 68307 */
1651	      case '2':			    /* 68322, 68328 */
1652	      case '5':			    /* 68356 */
1653		strcpy (family, "68000");   /* MC68000-based controllers */
1654		break;
1655
1656	      case '3':			    /* 68330, 68331, 68332, 68333,
1657					       68334, 68335, 68336, 68338 */
1658	      case '6':			    /* 68360 */
1659	      case '7':			    /* 68376 */
1660		strcpy (family, "68332");   /* CPU32 and CPU32+ */
1661		break;
1662
1663	      case '4':
1664		if (processor[4] == '9')    /* 68349 */
1665		  strcpy (family, "68030"); /* CPU030 */
1666		else		            /* 68340, 68341 */
1667		  strcpy (family, "68332"); /* CPU32 and CPU32+ */
1668		break;
1669
1670	      default:			    /* Does not exist yet */
1671		strcpy (family, "68332");   /* Guess it will be CPU32 */
1672	      }
1673	  }
1674	else if (TOUPPER (processor[3]) == 'F')  /* 68F333 */
1675	  strcpy (family, "68332");	           /* CPU32 */
1676	else if ((TOUPPER (processor[3]) == 'C') /* Embedded controllers.  */
1677		 && ((TOUPPER (processor[2]) == 'E')
1678		     || (TOUPPER (processor[2]) == 'H')
1679		     || (TOUPPER (processor[2]) == 'L')))
1680	  {
1681	    strcpy (family, "68");
1682	    strncat (family, processor + 4, 7);
1683	    family[9] = '\0';
1684	  }
1685	else				 /* "Regular" processors.  */
1686	  {
1687	    strncpy (family, processor, 9);
1688	    family[9] = '\0';
1689	  }
1690      }
1691    else if ((strncmp (processor, "cpu32", 5) == 0) /* CPU32 and CPU32+ */
1692	     || (strncmp (processor, "CPU32", 5) == 0))
1693      strcpy (family, "68332");
1694    else
1695      {
1696	strncpy (family, processor, 9);
1697	family[9] = '\0';
1698      }
1699
1700    arch = bfd_scan_arch (family);
1701    if (arch == 0)
1702      goto got_wrong_format;
1703    abfd->arch_info = arch;
1704  }
1705
1706  if (this_byte (&(ieee->h)) != (int) ieee_address_descriptor_enum)
1707    goto fail;
1708
1709  next_byte (&(ieee->h));
1710
1711  if (! parse_int (&(ieee->h), &ieee->ad.number_of_bits_mau))
1712    goto fail;
1713
1714  if (! parse_int (&(ieee->h), &ieee->ad.number_of_maus_in_address))
1715    goto fail;
1716
1717  /* If there is a byte order info, take it.  */
1718  if (this_byte (&(ieee->h)) == (int) ieee_variable_L_enum
1719      || this_byte (&(ieee->h)) == (int) ieee_variable_M_enum)
1720    next_byte (&(ieee->h));
1721
1722  for (part = 0; part < N_W_VARIABLES; part++)
1723    {
1724      bfd_boolean ok;
1725
1726      if (read_2bytes (&(ieee->h)) != (int) ieee_assign_value_to_variable_enum)
1727	goto fail;
1728
1729      if (this_byte_and_next (&(ieee->h)) != part)
1730	goto fail;
1731
1732      ieee->w.offset[part] = parse_i (&(ieee->h), &ok);
1733      if (! ok)
1734	goto fail;
1735    }
1736
1737  if (ieee->w.r.external_part != 0)
1738    abfd->flags = HAS_SYMS;
1739
1740  /* By now we know that this is a real IEEE file, we're going to read
1741     the whole thing into memory so that we can run up and down it
1742     quickly.  We can work out how big the file is from the trailer
1743     record.  */
1744
1745  amt = ieee->w.r.me_record + 1;
1746  IEEE_DATA (abfd)->h.first_byte =
1747    (unsigned char *) bfd_alloc (ieee->h.abfd, amt);
1748  if (!IEEE_DATA (abfd)->h.first_byte)
1749    goto fail;
1750  if (bfd_seek (abfd, (file_ptr) 0, SEEK_SET) != 0)
1751    goto fail;
1752  /* FIXME: Check return value.  I'm not sure whether it needs to read
1753     the entire buffer or not.  */
1754  bfd_bread ((PTR) (IEEE_DATA (abfd)->h.first_byte),
1755	    (bfd_size_type) ieee->w.r.me_record + 1, abfd);
1756
1757  ieee_slurp_sections (abfd);
1758
1759  if (! ieee_slurp_debug (abfd))
1760    goto fail;
1761
1762  /* Parse section data to activate file and section flags implied by
1763     section contents. */
1764  if (! ieee_slurp_section_data (abfd))
1765    goto fail;
1766
1767  return abfd->xvec;
1768got_wrong_format:
1769  bfd_set_error (bfd_error_wrong_format);
1770fail:
1771  bfd_release (abfd, ieee);
1772  abfd->tdata.ieee_data = save;
1773  return (const bfd_target *) NULL;
1774}
1775
1776static void
1777ieee_get_symbol_info (ignore_abfd, symbol, ret)
1778     bfd *ignore_abfd ATTRIBUTE_UNUSED;
1779     asymbol *symbol;
1780     symbol_info *ret;
1781{
1782  bfd_symbol_info (symbol, ret);
1783  if (symbol->name[0] == ' ')
1784    ret->name = "* empty table entry ";
1785  if (!symbol->section)
1786    ret->type = (symbol->flags & BSF_LOCAL) ? 'a' : 'A';
1787}
1788
1789static void
1790ieee_print_symbol (abfd, afile, symbol, how)
1791     bfd *abfd;
1792     PTR afile;
1793     asymbol *symbol;
1794     bfd_print_symbol_type how;
1795{
1796  FILE *file = (FILE *) afile;
1797
1798  switch (how)
1799    {
1800    case bfd_print_symbol_name:
1801      fprintf (file, "%s", symbol->name);
1802      break;
1803    case bfd_print_symbol_more:
1804#if 0
1805      fprintf (file, "%4x %2x", aout_symbol (symbol)->desc & 0xffff,
1806	       aout_symbol (symbol)->other & 0xff);
1807#endif
1808      BFD_FAIL ();
1809      break;
1810    case bfd_print_symbol_all:
1811      {
1812	const char *section_name =
1813	  (symbol->section == (asection *) NULL
1814	   ? "*abs"
1815	   : symbol->section->name);
1816
1817	if (symbol->name[0] == ' ')
1818	  {
1819	    fprintf (file, "* empty table entry ");
1820	  }
1821	else
1822	  {
1823	    bfd_print_symbol_vandf (abfd, (PTR) file, symbol);
1824
1825	    fprintf (file, " %-5s %04x %02x %s",
1826		     section_name,
1827		     (unsigned) ieee_symbol (symbol)->index,
1828		     (unsigned) 0,
1829		     symbol->name);
1830	  }
1831      }
1832      break;
1833    }
1834}
1835
1836static bfd_boolean
1837do_one (ieee, current_map, location_ptr, s, iterations)
1838     ieee_data_type *ieee;
1839     ieee_per_section_type *current_map;
1840     unsigned char *location_ptr;
1841     asection *s;
1842     int iterations;
1843{
1844  switch (this_byte (&(ieee->h)))
1845    {
1846    case ieee_load_constant_bytes_enum:
1847      {
1848	unsigned int number_of_maus;
1849	unsigned int i;
1850
1851	next_byte (&(ieee->h));
1852	number_of_maus = must_parse_int (&(ieee->h));
1853
1854	for (i = 0; i < number_of_maus; i++)
1855	  {
1856	    location_ptr[current_map->pc++] = this_byte (&(ieee->h));
1857	    next_byte (&(ieee->h));
1858	  }
1859      }
1860      break;
1861
1862    case ieee_load_with_relocation_enum:
1863      {
1864	bfd_boolean loop = TRUE;
1865
1866	next_byte (&(ieee->h));
1867	while (loop)
1868	  {
1869	    switch (this_byte (&(ieee->h)))
1870	      {
1871	      case ieee_variable_R_enum:
1872
1873	      case ieee_function_signed_open_b_enum:
1874	      case ieee_function_unsigned_open_b_enum:
1875	      case ieee_function_either_open_b_enum:
1876		{
1877		  unsigned int extra = 4;
1878		  bfd_boolean pcrel = FALSE;
1879		  asection *section;
1880		  ieee_reloc_type *r;
1881		  bfd_size_type amt = sizeof (ieee_reloc_type);
1882
1883		  r = (ieee_reloc_type *) bfd_alloc (ieee->h.abfd, amt);
1884		  if (!r)
1885		    return FALSE;
1886
1887		  *(current_map->reloc_tail_ptr) = r;
1888		  current_map->reloc_tail_ptr = &r->next;
1889		  r->next = (ieee_reloc_type *) NULL;
1890		  next_byte (&(ieee->h));
1891/*			    abort();*/
1892		  r->relent.sym_ptr_ptr = 0;
1893		  parse_expression (ieee,
1894				    &r->relent.addend,
1895				    &r->symbol,
1896				    &pcrel, &extra, &section);
1897		  r->relent.address = current_map->pc;
1898		  s->flags |= SEC_RELOC;
1899		  s->owner->flags |= HAS_RELOC;
1900		  s->reloc_count++;
1901		  if (r->relent.sym_ptr_ptr == NULL && section != NULL)
1902		    r->relent.sym_ptr_ptr = section->symbol_ptr_ptr;
1903
1904		  if (this_byte (&(ieee->h)) == (int) ieee_comma)
1905		    {
1906		      next_byte (&(ieee->h));
1907		      /* Fetch number of bytes to pad.  */
1908		      extra = must_parse_int (&(ieee->h));
1909		    };
1910
1911		  switch (this_byte (&(ieee->h)))
1912		    {
1913		    case ieee_function_signed_close_b_enum:
1914		      next_byte (&(ieee->h));
1915		      break;
1916		    case ieee_function_unsigned_close_b_enum:
1917		      next_byte (&(ieee->h));
1918		      break;
1919		    case ieee_function_either_close_b_enum:
1920		      next_byte (&(ieee->h));
1921		      break;
1922		    default:
1923		      break;
1924		    }
1925		  /* Build a relocation entry for this type.  */
1926		  /* If pc rel then stick -ve pc into instruction
1927		     and take out of reloc ..
1928
1929		     I've changed this. It's all too complicated. I
1930		     keep 0 in the instruction now.  */
1931
1932		  switch (extra)
1933		    {
1934		    case 0:
1935		    case 4:
1936
1937		      if (pcrel)
1938			{
1939#if KEEPMINUSPCININST
1940			  bfd_put_32 (ieee->h.abfd, -current_map->pc,
1941				      location_ptr + current_map->pc);
1942			  r->relent.howto = &rel32_howto;
1943			  r->relent.addend -= current_map->pc;
1944#else
1945			  bfd_put_32 (ieee->h.abfd, (bfd_vma) 0, location_ptr +
1946				      current_map->pc);
1947			  r->relent.howto = &rel32_howto;
1948#endif
1949			}
1950		      else
1951			{
1952			  bfd_put_32 (ieee->h.abfd, (bfd_vma) 0,
1953				      location_ptr + current_map->pc);
1954			  r->relent.howto = &abs32_howto;
1955			}
1956		      current_map->pc += 4;
1957		      break;
1958		    case 2:
1959		      if (pcrel)
1960			{
1961#if KEEPMINUSPCININST
1962			  bfd_put_16 (ieee->h.abfd, (bfd_vma) -current_map->pc,
1963				      location_ptr + current_map->pc);
1964			  r->relent.addend -= current_map->pc;
1965			  r->relent.howto = &rel16_howto;
1966#else
1967
1968			  bfd_put_16 (ieee->h.abfd, (bfd_vma) 0,
1969				      location_ptr + current_map->pc);
1970			  r->relent.howto = &rel16_howto;
1971#endif
1972			}
1973
1974		      else
1975			{
1976			  bfd_put_16 (ieee->h.abfd, (bfd_vma) 0,
1977				      location_ptr + current_map->pc);
1978			  r->relent.howto = &abs16_howto;
1979			}
1980		      current_map->pc += 2;
1981		      break;
1982		    case 1:
1983		      if (pcrel)
1984			{
1985#if KEEPMINUSPCININST
1986			  bfd_put_8 (ieee->h.abfd, (int) (-current_map->pc), location_ptr + current_map->pc);
1987			  r->relent.addend -= current_map->pc;
1988			  r->relent.howto = &rel8_howto;
1989#else
1990			  bfd_put_8 (ieee->h.abfd, 0, location_ptr + current_map->pc);
1991			  r->relent.howto = &rel8_howto;
1992#endif
1993			}
1994		      else
1995			{
1996			  bfd_put_8 (ieee->h.abfd, 0, location_ptr + current_map->pc);
1997			  r->relent.howto = &abs8_howto;
1998			}
1999		      current_map->pc += 1;
2000		      break;
2001
2002		    default:
2003		      BFD_FAIL ();
2004		      return FALSE;
2005		    }
2006		}
2007		break;
2008	      default:
2009		{
2010		  bfd_vma this_size;
2011		  if (parse_int (&(ieee->h), &this_size))
2012		    {
2013		      unsigned int i;
2014		      for (i = 0; i < this_size; i++)
2015			{
2016			  location_ptr[current_map->pc++] = this_byte (&(ieee->h));
2017			  next_byte (&(ieee->h));
2018			}
2019		    }
2020		  else
2021		    {
2022		      loop = FALSE;
2023		    }
2024		}
2025	      }
2026
2027	    /* Prevent more than the first load-item of an LR record
2028	       from being repeated (MRI convention). */
2029	    if (iterations != 1)
2030	      loop = FALSE;
2031	  }
2032      }
2033    }
2034  return TRUE;
2035}
2036
2037/* Read in all the section data and relocation stuff too.  */
2038
2039static bfd_boolean
2040ieee_slurp_section_data (abfd)
2041     bfd *abfd;
2042{
2043  bfd_byte *location_ptr = (bfd_byte *) NULL;
2044  ieee_data_type *ieee = IEEE_DATA (abfd);
2045  unsigned int section_number;
2046
2047  ieee_per_section_type *current_map = (ieee_per_section_type *) NULL;
2048  asection *s;
2049  /* Seek to the start of the data area.  */
2050  if (ieee->read_data)
2051    return TRUE;
2052  ieee->read_data = TRUE;
2053  ieee_seek (ieee, ieee->w.r.data_part);
2054
2055  /* Allocate enough space for all the section contents.  */
2056  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
2057    {
2058      ieee_per_section_type *per = ieee_per_section (s);
2059      if ((s->flags & SEC_DEBUGGING) != 0)
2060	continue;
2061      per->data = (bfd_byte *) bfd_alloc (ieee->h.abfd, s->size);
2062      if (!per->data)
2063	return FALSE;
2064      per->reloc_tail_ptr =
2065	(ieee_reloc_type **) & (s->relocation);
2066    }
2067
2068  while (TRUE)
2069    {
2070      switch (this_byte (&(ieee->h)))
2071	{
2072	  /* IF we see anything strange then quit.  */
2073	default:
2074	  return TRUE;
2075
2076	case ieee_set_current_section_enum:
2077	  next_byte (&(ieee->h));
2078	  section_number = must_parse_int (&(ieee->h));
2079	  s = ieee->section_table[section_number];
2080	  s->flags |= SEC_LOAD | SEC_HAS_CONTENTS;
2081	  current_map = ieee_per_section (s);
2082	  location_ptr = current_map->data - s->vma;
2083	  /* The document I have says that Microtec's compilers reset
2084	     this after a sec section, even though the standard says not
2085	     to, SO...  */
2086	  current_map->pc = s->vma;
2087	  break;
2088
2089	case ieee_e2_first_byte_enum:
2090	  next_byte (&(ieee->h));
2091	  switch (this_byte (&(ieee->h)))
2092	    {
2093	    case ieee_set_current_pc_enum & 0xff:
2094	      {
2095		bfd_vma value;
2096		ieee_symbol_index_type symbol;
2097		unsigned int extra;
2098		bfd_boolean pcrel;
2099
2100		next_byte (&(ieee->h));
2101		must_parse_int (&(ieee->h));	/* Throw away section #.  */
2102		parse_expression (ieee, &value,
2103				  &symbol,
2104				  &pcrel, &extra,
2105				  0);
2106		current_map->pc = value;
2107		BFD_ASSERT ((unsigned) (value - s->vma) <= s->size);
2108	      }
2109	      break;
2110
2111	    case ieee_value_starting_address_enum & 0xff:
2112	      next_byte (&(ieee->h));
2113	      if (this_byte (&(ieee->h)) == ieee_function_either_open_b_enum)
2114		next_byte (&(ieee->h));
2115	      abfd->start_address = must_parse_int (&(ieee->h));
2116	      /* We've got to the end of the data now -  */
2117	      return TRUE;
2118	    default:
2119	      BFD_FAIL ();
2120	      return FALSE;
2121	    }
2122	  break;
2123	case ieee_repeat_data_enum:
2124	  {
2125	    /* Repeat the following LD or LR n times - we do this by
2126	       remembering the stream pointer before running it and
2127	       resetting it and running it n times. We special case
2128	       the repetition of a repeat_data/load_constant.  */
2129	    unsigned int iterations;
2130	    unsigned char *start;
2131
2132	    next_byte (&(ieee->h));
2133	    iterations = must_parse_int (&(ieee->h));
2134	    start = ieee->h.input_p;
2135	    if (start[0] == (int) ieee_load_constant_bytes_enum
2136		&& start[1] == 1)
2137	      {
2138		while (iterations != 0)
2139		  {
2140		    location_ptr[current_map->pc++] = start[2];
2141		    iterations--;
2142		  }
2143		next_byte (&(ieee->h));
2144		next_byte (&(ieee->h));
2145		next_byte (&(ieee->h));
2146	      }
2147	    else
2148	      {
2149		while (iterations != 0)
2150		  {
2151		    ieee->h.input_p = start;
2152		    if (!do_one (ieee, current_map, location_ptr, s,
2153				 (int) iterations))
2154		      return FALSE;
2155		    iterations--;
2156		  }
2157	      }
2158	  }
2159	  break;
2160	case ieee_load_constant_bytes_enum:
2161	case ieee_load_with_relocation_enum:
2162	  if (!do_one (ieee, current_map, location_ptr, s, 1))
2163	    return FALSE;
2164	}
2165    }
2166}
2167
2168static bfd_boolean
2169ieee_new_section_hook (abfd, newsect)
2170     bfd *abfd;
2171     asection *newsect;
2172{
2173  newsect->used_by_bfd
2174    = (PTR) bfd_alloc (abfd, (bfd_size_type) sizeof (ieee_per_section_type));
2175  if (!newsect->used_by_bfd)
2176    return FALSE;
2177  ieee_per_section (newsect)->data = (bfd_byte *) NULL;
2178  ieee_per_section (newsect)->section = newsect;
2179  return TRUE;
2180}
2181
2182static long
2183ieee_get_reloc_upper_bound (abfd, asect)
2184     bfd *abfd;
2185     sec_ptr asect;
2186{
2187  if ((asect->flags & SEC_DEBUGGING) != 0)
2188    return 0;
2189  if (! ieee_slurp_section_data (abfd))
2190    return -1;
2191  return (asect->reloc_count + 1) * sizeof (arelent *);
2192}
2193
2194static bfd_boolean
2195ieee_get_section_contents (abfd, section, location, offset, count)
2196     bfd *abfd;
2197     sec_ptr section;
2198     PTR location;
2199     file_ptr offset;
2200     bfd_size_type count;
2201{
2202  ieee_per_section_type *p = ieee_per_section (section);
2203  if ((section->flags & SEC_DEBUGGING) != 0)
2204    return _bfd_generic_get_section_contents (abfd, section, location,
2205					      offset, count);
2206  ieee_slurp_section_data (abfd);
2207  (void) memcpy ((PTR) location, (PTR) (p->data + offset), (unsigned) count);
2208  return TRUE;
2209}
2210
2211static long
2212ieee_canonicalize_reloc (abfd, section, relptr, symbols)
2213     bfd *abfd;
2214     sec_ptr section;
2215     arelent **relptr;
2216     asymbol **symbols;
2217{
2218  ieee_reloc_type *src = (ieee_reloc_type *) (section->relocation);
2219  ieee_data_type *ieee = IEEE_DATA (abfd);
2220
2221  if ((section->flags & SEC_DEBUGGING) != 0)
2222    return 0;
2223
2224  while (src != (ieee_reloc_type *) NULL)
2225    {
2226      /* Work out which symbol to attach it this reloc to.  */
2227      switch (src->symbol.letter)
2228	{
2229	case 'I':
2230	  src->relent.sym_ptr_ptr =
2231	    symbols + src->symbol.index + ieee->external_symbol_base_offset;
2232	  break;
2233	case 'X':
2234	  src->relent.sym_ptr_ptr =
2235	    symbols + src->symbol.index + ieee->external_reference_base_offset;
2236	  break;
2237	case 0:
2238	  if (src->relent.sym_ptr_ptr != NULL)
2239	    src->relent.sym_ptr_ptr =
2240	      src->relent.sym_ptr_ptr[0]->section->symbol_ptr_ptr;
2241	  break;
2242	default:
2243
2244	  BFD_FAIL ();
2245	}
2246      *relptr++ = &src->relent;
2247      src = src->next;
2248    }
2249  *relptr = (arelent *) NULL;
2250  return section->reloc_count;
2251}
2252
2253static int
2254comp (ap, bp)
2255     const PTR ap;
2256     const PTR bp;
2257{
2258  arelent *a = *((arelent **) ap);
2259  arelent *b = *((arelent **) bp);
2260  return a->address - b->address;
2261}
2262
2263/* Write the section headers.  */
2264
2265static bfd_boolean
2266ieee_write_section_part (abfd)
2267     bfd *abfd;
2268{
2269  ieee_data_type *ieee = IEEE_DATA (abfd);
2270  asection *s;
2271  ieee->w.r.section_part = bfd_tell (abfd);
2272  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
2273    {
2274      if (! bfd_is_abs_section (s)
2275	  && (s->flags & SEC_DEBUGGING) == 0)
2276	{
2277	  if (! ieee_write_byte (abfd, ieee_section_type_enum)
2278	      || ! ieee_write_byte (abfd,
2279				    (bfd_byte) (s->index
2280						+ IEEE_SECTION_NUMBER_BASE)))
2281	    return FALSE;
2282
2283	  if (abfd->flags & EXEC_P)
2284	    {
2285	      /* This image is executable, so output absolute sections.  */
2286	      if (! ieee_write_byte (abfd, ieee_variable_A_enum)
2287		  || ! ieee_write_byte (abfd, ieee_variable_S_enum))
2288		return FALSE;
2289	    }
2290	  else
2291	    {
2292	      if (! ieee_write_byte (abfd, ieee_variable_C_enum))
2293		return FALSE;
2294	    }
2295
2296	  switch (s->flags & (SEC_CODE | SEC_DATA | SEC_ROM))
2297	    {
2298	    case SEC_CODE | SEC_LOAD:
2299	    case SEC_CODE:
2300	      if (! ieee_write_byte (abfd, ieee_variable_P_enum))
2301		return FALSE;
2302	      break;
2303	    case SEC_DATA:
2304	    default:
2305	      if (! ieee_write_byte (abfd, ieee_variable_D_enum))
2306		return FALSE;
2307	      break;
2308	    case SEC_ROM:
2309	    case SEC_ROM | SEC_DATA:
2310	    case SEC_ROM | SEC_LOAD:
2311	    case SEC_ROM | SEC_DATA | SEC_LOAD:
2312	      if (! ieee_write_byte (abfd, ieee_variable_R_enum))
2313		return FALSE;
2314	    }
2315
2316
2317	  if (! ieee_write_id (abfd, s->name))
2318	    return FALSE;
2319#if 0
2320	  ieee_write_int (abfd, 0);	/* Parent */
2321	  ieee_write_int (abfd, 0);	/* Brother */
2322	  ieee_write_int (abfd, 0);	/* Context */
2323#endif
2324	  /* Alignment.  */
2325	  if (! ieee_write_byte (abfd, ieee_section_alignment_enum)
2326	      || ! ieee_write_byte (abfd,
2327				    (bfd_byte) (s->index
2328						+ IEEE_SECTION_NUMBER_BASE))
2329	      || ! ieee_write_int (abfd, (bfd_vma) 1 << s->alignment_power))
2330	    return FALSE;
2331
2332	  /* Size.  */
2333	  if (! ieee_write_2bytes (abfd, ieee_section_size_enum)
2334	      || ! ieee_write_byte (abfd,
2335				    (bfd_byte) (s->index
2336						+ IEEE_SECTION_NUMBER_BASE))
2337	      || ! ieee_write_int (abfd, s->size))
2338	    return FALSE;
2339	  if (abfd->flags & EXEC_P)
2340	    {
2341	      /* Relocateable sections don't have asl records.  */
2342	      /* Vma.  */
2343	      if (! ieee_write_2bytes (abfd, ieee_section_base_address_enum)
2344		  || ! ieee_write_byte (abfd,
2345					((bfd_byte)
2346					 (s->index
2347					  + IEEE_SECTION_NUMBER_BASE)))
2348		  || ! ieee_write_int (abfd, s->lma))
2349		return FALSE;
2350	    }
2351	}
2352    }
2353
2354  return TRUE;
2355}
2356
2357
2358static bfd_boolean
2359do_with_relocs (abfd, s)
2360     bfd *abfd;
2361     asection *s;
2362{
2363  unsigned int number_of_maus_in_address =
2364    bfd_arch_bits_per_address (abfd) / bfd_arch_bits_per_byte (abfd);
2365  unsigned int relocs_to_go = s->reloc_count;
2366  bfd_byte *stream = ieee_per_section (s)->data;
2367  arelent **p = s->orelocation;
2368  bfd_size_type current_byte_index = 0;
2369
2370  qsort (s->orelocation,
2371	 relocs_to_go,
2372	 sizeof (arelent **),
2373	 comp);
2374
2375  /* Output the section preheader.  */
2376  if (! ieee_write_byte (abfd, ieee_set_current_section_enum)
2377      || ! ieee_write_byte (abfd,
2378			    (bfd_byte) (s->index + IEEE_SECTION_NUMBER_BASE))
2379      || ! ieee_write_2bytes (abfd, ieee_set_current_pc_enum)
2380      || ! ieee_write_byte (abfd,
2381			    (bfd_byte) (s->index + IEEE_SECTION_NUMBER_BASE)))
2382    return FALSE;
2383
2384  if ((abfd->flags & EXEC_P) != 0 && relocs_to_go == 0)
2385    {
2386      if (! ieee_write_int (abfd, s->lma))
2387	return FALSE;
2388    }
2389  else
2390    {
2391      if (! ieee_write_expression (abfd, (bfd_vma) 0, s->symbol, 0, 0))
2392	return FALSE;
2393    }
2394
2395  if (relocs_to_go == 0)
2396    {
2397      /* If there aren't any relocations then output the load constant
2398	 byte opcode rather than the load with relocation opcode.  */
2399      while (current_byte_index < s->size)
2400	{
2401	  bfd_size_type run;
2402	  unsigned int MAXRUN = 127;
2403
2404	  run = MAXRUN;
2405	  if (run > s->size - current_byte_index)
2406	    run = s->size - current_byte_index;
2407
2408	  if (run != 0)
2409	    {
2410	      if (! ieee_write_byte (abfd, ieee_load_constant_bytes_enum))
2411		return FALSE;
2412	      /* Output a stream of bytes.  */
2413	      if (! ieee_write_int (abfd, run))
2414		return FALSE;
2415	      if (bfd_bwrite ((PTR) (stream + current_byte_index), run, abfd)
2416		  != run)
2417		return FALSE;
2418	      current_byte_index += run;
2419	    }
2420	}
2421    }
2422  else
2423    {
2424      if (! ieee_write_byte (abfd, ieee_load_with_relocation_enum))
2425	return FALSE;
2426
2427      /* Output the data stream as the longest sequence of bytes
2428	 possible, allowing for the a reasonable packet size and
2429	 relocation stuffs.  */
2430
2431      if ((PTR) stream == (PTR) NULL)
2432	{
2433	  /* Outputting a section without data, fill it up.  */
2434	  stream = (unsigned char *) bfd_zalloc (abfd, s->size);
2435	  if (!stream)
2436	    return FALSE;
2437	}
2438      while (current_byte_index < s->size)
2439	{
2440	  bfd_size_type run;
2441	  unsigned int MAXRUN = 127;
2442
2443	  if (relocs_to_go)
2444	    {
2445	      run = (*p)->address - current_byte_index;
2446	      if (run > MAXRUN)
2447		run = MAXRUN;
2448	    }
2449	  else
2450	    run = MAXRUN;
2451
2452	  if (run > s->size - current_byte_index)
2453	    run = s->size - current_byte_index;
2454
2455	  if (run != 0)
2456	    {
2457	      /* Output a stream of bytes.  */
2458	      if (! ieee_write_int (abfd, run))
2459		return FALSE;
2460	      if (bfd_bwrite ((PTR) (stream + current_byte_index), run, abfd)
2461		  != run)
2462		return FALSE;
2463	      current_byte_index += run;
2464	    }
2465
2466	  /* Output any relocations here.  */
2467	  if (relocs_to_go && (*p) && (*p)->address == current_byte_index)
2468	    {
2469	      while (relocs_to_go
2470		     && (*p) && (*p)->address == current_byte_index)
2471		{
2472		  arelent *r = *p;
2473		  bfd_signed_vma ov;
2474#if 0
2475		  if (r->howto->pc_relative)
2476		    r->addend += current_byte_index;
2477#endif
2478		  switch (r->howto->size)
2479		    {
2480		    case 2:
2481
2482		      ov = bfd_get_signed_32 (abfd,
2483					      stream + current_byte_index);
2484		      current_byte_index += 4;
2485		      break;
2486		    case 1:
2487		      ov = bfd_get_signed_16 (abfd,
2488					      stream + current_byte_index);
2489		      current_byte_index += 2;
2490		      break;
2491		    case 0:
2492		      ov = bfd_get_signed_8 (abfd,
2493					     stream + current_byte_index);
2494		      current_byte_index++;
2495		      break;
2496		    default:
2497		      ov = 0;
2498		      BFD_FAIL ();
2499		      return FALSE;
2500		    }
2501
2502		  ov &= r->howto->src_mask;
2503
2504		  if (r->howto->pc_relative
2505		      && ! r->howto->pcrel_offset)
2506		    ov += r->address;
2507
2508		  if (! ieee_write_byte (abfd,
2509					 ieee_function_either_open_b_enum))
2510		    return FALSE;
2511
2512/*		  abort();*/
2513
2514		  if (r->sym_ptr_ptr != (asymbol **) NULL)
2515		    {
2516		      if (! ieee_write_expression (abfd, r->addend + ov,
2517						   *(r->sym_ptr_ptr),
2518						   r->howto->pc_relative,
2519						   (unsigned) s->index))
2520			return FALSE;
2521		    }
2522		  else
2523		    {
2524		      if (! ieee_write_expression (abfd, r->addend + ov,
2525						   (asymbol *) NULL,
2526						   r->howto->pc_relative,
2527						   (unsigned) s->index))
2528			return FALSE;
2529		    }
2530
2531		  if (number_of_maus_in_address
2532		      != bfd_get_reloc_size (r->howto))
2533		    {
2534		      bfd_vma rsize = bfd_get_reloc_size (r->howto);
2535		      if (! ieee_write_int (abfd, rsize))
2536			return FALSE;
2537		    }
2538		  if (! ieee_write_byte (abfd,
2539					 ieee_function_either_close_b_enum))
2540		    return FALSE;
2541
2542		  relocs_to_go--;
2543		  p++;
2544		}
2545
2546	    }
2547	}
2548    }
2549
2550  return TRUE;
2551}
2552
2553/* If there are no relocations in the output section then we can be
2554   clever about how we write.  We block items up into a max of 127
2555   bytes.  */
2556
2557static bfd_boolean
2558do_as_repeat (abfd, s)
2559     bfd *abfd;
2560     asection *s;
2561{
2562  if (s->size)
2563    {
2564      if (! ieee_write_byte (abfd, ieee_set_current_section_enum)
2565	  || ! ieee_write_byte (abfd,
2566				(bfd_byte) (s->index
2567					    + IEEE_SECTION_NUMBER_BASE))
2568	  || ! ieee_write_byte (abfd, ieee_set_current_pc_enum >> 8)
2569	  || ! ieee_write_byte (abfd, ieee_set_current_pc_enum & 0xff)
2570	  || ! ieee_write_byte (abfd,
2571				(bfd_byte) (s->index
2572					    + IEEE_SECTION_NUMBER_BASE)))
2573	return FALSE;
2574
2575      if ((abfd->flags & EXEC_P) != 0)
2576	{
2577	  if (! ieee_write_int (abfd, s->lma))
2578	    return FALSE;
2579	}
2580      else
2581	{
2582	  if (! ieee_write_expression (abfd, (bfd_vma) 0, s->symbol, 0, 0))
2583	    return FALSE;
2584	}
2585
2586      if (! ieee_write_byte (abfd, ieee_repeat_data_enum)
2587	  || ! ieee_write_int (abfd, s->size)
2588	  || ! ieee_write_byte (abfd, ieee_load_constant_bytes_enum)
2589	  || ! ieee_write_byte (abfd, 1)
2590	  || ! ieee_write_byte (abfd, 0))
2591	return FALSE;
2592    }
2593
2594  return TRUE;
2595}
2596
2597static bfd_boolean
2598do_without_relocs (abfd, s)
2599     bfd *abfd;
2600     asection *s;
2601{
2602  bfd_byte *stream = ieee_per_section (s)->data;
2603
2604  if (stream == 0 || ((s->flags & SEC_LOAD) == 0))
2605    {
2606      if (! do_as_repeat (abfd, s))
2607	return FALSE;
2608    }
2609  else
2610    {
2611      unsigned int i;
2612
2613      for (i = 0; i < s->size; i++)
2614	{
2615	  if (stream[i] != 0)
2616	    {
2617	      if (! do_with_relocs (abfd, s))
2618		return FALSE;
2619	      return TRUE;
2620	    }
2621	}
2622      if (! do_as_repeat (abfd, s))
2623	return FALSE;
2624    }
2625
2626  return TRUE;
2627}
2628
2629
2630static unsigned char *output_ptr_start;
2631static unsigned char *output_ptr;
2632static unsigned char *output_ptr_end;
2633static unsigned char *input_ptr_start;
2634static unsigned char *input_ptr;
2635static unsigned char *input_ptr_end;
2636static bfd *input_bfd;
2637static bfd *output_bfd;
2638static int output_buffer;
2639
2640static bfd_boolean
2641ieee_mkobject (abfd)
2642     bfd *abfd;
2643{
2644  bfd_size_type amt;
2645
2646  output_ptr_start = NULL;
2647  output_ptr = NULL;
2648  output_ptr_end = NULL;
2649  input_ptr_start = NULL;
2650  input_ptr = NULL;
2651  input_ptr_end = NULL;
2652  input_bfd = NULL;
2653  output_bfd = NULL;
2654  output_buffer = 0;
2655  amt = sizeof (ieee_data_type);
2656  abfd->tdata.ieee_data = (ieee_data_type *) bfd_zalloc (abfd, amt);
2657  return abfd->tdata.ieee_data != NULL;
2658}
2659
2660static void
2661fill ()
2662{
2663  bfd_size_type amt = input_ptr_end - input_ptr_start;
2664  /* FIXME: Check return value.  I'm not sure whether it needs to read
2665     the entire buffer or not.  */
2666  bfd_bread ((PTR) input_ptr_start, amt, input_bfd);
2667  input_ptr = input_ptr_start;
2668}
2669
2670static void
2671flush ()
2672{
2673  bfd_size_type amt = output_ptr - output_ptr_start;
2674
2675  if (bfd_bwrite ((PTR) (output_ptr_start), amt, output_bfd) != amt)
2676    abort ();
2677  output_ptr = output_ptr_start;
2678  output_buffer++;
2679}
2680
2681#define THIS() ( *input_ptr )
2682#define NEXT() { input_ptr++; if (input_ptr == input_ptr_end) fill(); }
2683#define OUT(x) { *output_ptr++ = (x); if(output_ptr == output_ptr_end)  flush(); }
2684
2685static void
2686write_int (value)
2687     int value;
2688{
2689  if (value >= 0 && value <= 127)
2690    {
2691      OUT (value);
2692    }
2693  else
2694    {
2695      unsigned int length;
2696      /* How many significant bytes ?  */
2697      /* FIXME FOR LONGER INTS.  */
2698      if (value & 0xff000000)
2699	length = 4;
2700      else if (value & 0x00ff0000)
2701	length = 3;
2702      else if (value & 0x0000ff00)
2703	length = 2;
2704      else
2705	length = 1;
2706
2707      OUT ((int) ieee_number_repeat_start_enum + length);
2708      switch (length)
2709	{
2710	case 4:
2711	  OUT (value >> 24);
2712	case 3:
2713	  OUT (value >> 16);
2714	case 2:
2715	  OUT (value >> 8);
2716	case 1:
2717	  OUT (value);
2718	}
2719    }
2720}
2721
2722static void
2723copy_id ()
2724{
2725  int length = THIS ();
2726  char ch;
2727
2728  OUT (length);
2729  NEXT ();
2730  while (length--)
2731    {
2732      ch = THIS ();
2733      OUT (ch);
2734      NEXT ();
2735    }
2736}
2737
2738#define VAR(x) ((x | 0x80))
2739static void
2740copy_expression ()
2741{
2742  int stack[10];
2743  int *tos = stack;
2744  int value;
2745
2746  while (1)
2747    {
2748      switch (THIS ())
2749	{
2750	case 0x84:
2751	  NEXT ();
2752	  value = THIS ();
2753	  NEXT ();
2754	  value = (value << 8) | THIS ();
2755	  NEXT ();
2756	  value = (value << 8) | THIS ();
2757	  NEXT ();
2758	  value = (value << 8) | THIS ();
2759	  NEXT ();
2760	  *tos++ = value;
2761	  break;
2762	case 0x83:
2763	  NEXT ();
2764	  value = THIS ();
2765	  NEXT ();
2766	  value = (value << 8) | THIS ();
2767	  NEXT ();
2768	  value = (value << 8) | THIS ();
2769	  NEXT ();
2770	  *tos++ = value;
2771	  break;
2772	case 0x82:
2773	  NEXT ();
2774	  value = THIS ();
2775	  NEXT ();
2776	  value = (value << 8) | THIS ();
2777	  NEXT ();
2778	  *tos++ = value;
2779	  break;
2780	case 0x81:
2781	  NEXT ();
2782	  value = THIS ();
2783	  NEXT ();
2784	  *tos++ = value;
2785	  break;
2786	case 0x80:
2787	  NEXT ();
2788	  *tos++ = 0;
2789	  break;
2790	default:
2791	  if (THIS () > 0x84)
2792	    {
2793	      /* Not a number, just bug out with the answer.  */
2794	      write_int (*(--tos));
2795	      return;
2796	    }
2797	  *tos++ = THIS ();
2798	  NEXT ();
2799	  break;
2800	case 0xa5:
2801	  /* PLUS anything.  */
2802	  value = *(--tos);
2803	  value += *(--tos);
2804	  *tos++ = value;
2805	  NEXT ();
2806	  break;
2807	case VAR ('R'):
2808	  {
2809	    int section_number;
2810	    ieee_data_type *ieee;
2811	    asection *s;
2812
2813	    NEXT ();
2814	    section_number = THIS ();
2815
2816	    NEXT ();
2817	    ieee = IEEE_DATA (input_bfd);
2818	    s = ieee->section_table[section_number];
2819	    value = 0;
2820	    if (s->output_section)
2821	      value = s->output_section->lma;
2822	    value += s->output_offset;
2823	    *tos++ = value;
2824	  }
2825	  break;
2826	case 0x90:
2827	  {
2828	    NEXT ();
2829	    write_int (*(--tos));
2830	    OUT (0x90);
2831	    return;
2832	  }
2833	}
2834    }
2835}
2836
2837/* Drop the int in the buffer, and copy a null into the gap, which we
2838   will overwrite later */
2839
2840static void
2841fill_int (buf)
2842     struct output_buffer_struct *buf;
2843{
2844  if (buf->buffer == output_buffer)
2845    {
2846      /* Still a chance to output the size.  */
2847      int value = output_ptr - buf->ptrp + 3;
2848      buf->ptrp[0] = value >> 24;
2849      buf->ptrp[1] = value >> 16;
2850      buf->ptrp[2] = value >> 8;
2851      buf->ptrp[3] = value >> 0;
2852    }
2853}
2854
2855static void
2856drop_int (buf)
2857     struct output_buffer_struct *buf;
2858{
2859  int type = THIS ();
2860  int ch;
2861
2862  if (type <= 0x84)
2863    {
2864      NEXT ();
2865      switch (type)
2866	{
2867	case 0x84:
2868	  ch = THIS ();
2869	  NEXT ();
2870	case 0x83:
2871	  ch = THIS ();
2872	  NEXT ();
2873	case 0x82:
2874	  ch = THIS ();
2875	  NEXT ();
2876	case 0x81:
2877	  ch = THIS ();
2878	  NEXT ();
2879	case 0x80:
2880	  break;
2881	}
2882    }
2883  OUT (0x84);
2884  buf->ptrp = output_ptr;
2885  buf->buffer = output_buffer;
2886  OUT (0);
2887  OUT (0);
2888  OUT (0);
2889  OUT (0);
2890}
2891
2892static void
2893copy_int ()
2894{
2895  int type = THIS ();
2896  int ch;
2897  if (type <= 0x84)
2898    {
2899      OUT (type);
2900      NEXT ();
2901      switch (type)
2902	{
2903	case 0x84:
2904	  ch = THIS ();
2905	  NEXT ();
2906	  OUT (ch);
2907	case 0x83:
2908	  ch = THIS ();
2909	  NEXT ();
2910	  OUT (ch);
2911	case 0x82:
2912	  ch = THIS ();
2913	  NEXT ();
2914	  OUT (ch);
2915	case 0x81:
2916	  ch = THIS ();
2917	  NEXT ();
2918	  OUT (ch);
2919	case 0x80:
2920	  break;
2921	}
2922    }
2923}
2924
2925#define ID copy_id()
2926#define INT copy_int()
2927#define EXP copy_expression()
2928#define INTn(q) copy_int()
2929#define EXPn(q) copy_expression()
2930
2931static void
2932f1_record ()
2933{
2934  int ch;
2935
2936  /* ATN record.  */
2937  NEXT ();
2938  ch = THIS ();
2939  switch (ch)
2940    {
2941    default:
2942      OUT (0xf1);
2943      OUT (ch);
2944      break;
2945    case 0xc9:
2946      NEXT ();
2947      OUT (0xf1);
2948      OUT (0xc9);
2949      INT;
2950      INT;
2951      ch = THIS ();
2952      switch (ch)
2953	{
2954	case 0x16:
2955	  NEXT ();
2956	  break;
2957	case 0x01:
2958	  NEXT ();
2959	  break;
2960	case 0x00:
2961	  NEXT ();
2962	  INT;
2963	  break;
2964	case 0x03:
2965	  NEXT ();
2966	  INT;
2967	  break;
2968	case 0x13:
2969	  EXPn (instruction address);
2970	  break;
2971	default:
2972	  break;
2973	}
2974      break;
2975    case 0xd8:
2976      /* EXternal ref.  */
2977      NEXT ();
2978      OUT (0xf1);
2979      OUT (0xd8);
2980      EXP;
2981      EXP;
2982      EXP;
2983      EXP;
2984      break;
2985    case 0xce:
2986      NEXT ();
2987      OUT (0xf1);
2988      OUT (0xce);
2989      INT;
2990      INT;
2991      ch = THIS ();
2992      INT;
2993      switch (ch)
2994	{
2995	case 0x01:
2996	  INT;
2997	  INT;
2998	  break;
2999	case 0x02:
3000	  INT;
3001	  break;
3002	case 0x04:
3003	  EXPn (external function);
3004	  break;
3005	case 0x05:
3006	  break;
3007	case 0x07:
3008	  INTn (line number);
3009	  INT;
3010	case 0x08:
3011	  break;
3012	case 0x0a:
3013	  INTn (locked register);
3014	  INT;
3015	  break;
3016	case 0x3f:
3017	  copy_till_end ();
3018	  break;
3019	case 0x3e:
3020	  copy_till_end ();
3021	  break;
3022	case 0x40:
3023	  copy_till_end ();
3024	  break;
3025	case 0x41:
3026	  ID;
3027	  break;
3028	}
3029    }
3030}
3031
3032static void
3033f0_record ()
3034{
3035  /* Attribute record.  */
3036  NEXT ();
3037  OUT (0xf0);
3038  INTn (Symbol name);
3039  ID;
3040}
3041
3042static void
3043copy_till_end ()
3044{
3045  int ch = THIS ();
3046
3047  while (1)
3048    {
3049      while (ch <= 0x80)
3050	{
3051	  OUT (ch);
3052	  NEXT ();
3053	  ch = THIS ();
3054	}
3055      switch (ch)
3056	{
3057	case 0x84:
3058	  OUT (THIS ());
3059	  NEXT ();
3060	case 0x83:
3061	  OUT (THIS ());
3062	  NEXT ();
3063	case 0x82:
3064	  OUT (THIS ());
3065	  NEXT ();
3066	case 0x81:
3067	  OUT (THIS ());
3068	  NEXT ();
3069	  OUT (THIS ());
3070	  NEXT ();
3071
3072	  ch = THIS ();
3073	  break;
3074	default:
3075	  return;
3076	}
3077    }
3078
3079}
3080
3081static void
3082f2_record ()
3083{
3084  NEXT ();
3085  OUT (0xf2);
3086  INT;
3087  NEXT ();
3088  OUT (0xce);
3089  INT;
3090  copy_till_end ();
3091}
3092
3093
3094static void
3095f8_record ()
3096{
3097  int ch;
3098  NEXT ();
3099  ch = THIS ();
3100  switch (ch)
3101    {
3102    case 0x01:
3103    case 0x02:
3104    case 0x03:
3105      /* Unique typedefs for module.  */
3106      /* GLobal typedefs.   */
3107      /* High level module scope beginning.  */
3108      {
3109	struct output_buffer_struct ob;
3110
3111	NEXT ();
3112	OUT (0xf8);
3113	OUT (ch);
3114	drop_int (&ob);
3115	ID;
3116
3117	block ();
3118
3119	NEXT ();
3120	fill_int (&ob);
3121	OUT (0xf9);
3122      }
3123      break;
3124    case 0x04:
3125      /* Global function.  */
3126      {
3127	struct output_buffer_struct ob;
3128
3129	NEXT ();
3130	OUT (0xf8);
3131	OUT (0x04);
3132	drop_int (&ob);
3133	ID;
3134	INTn (stack size);
3135	INTn (ret val);
3136	EXPn (offset);
3137
3138	block ();
3139
3140	NEXT ();
3141	OUT (0xf9);
3142	EXPn (size of block);
3143	fill_int (&ob);
3144      }
3145      break;
3146
3147    case 0x05:
3148      /* File name for source line numbers.  */
3149      {
3150	struct output_buffer_struct ob;
3151
3152	NEXT ();
3153	OUT (0xf8);
3154	OUT (0x05);
3155	drop_int (&ob);
3156	ID;
3157	INTn (year);
3158	INTn (month);
3159	INTn (day);
3160	INTn (hour);
3161	INTn (monute);
3162	INTn (second);
3163	block ();
3164	NEXT ();
3165	OUT (0xf9);
3166	fill_int (&ob);
3167      }
3168      break;
3169
3170    case 0x06:
3171      /* Local function.  */
3172      {
3173	struct output_buffer_struct ob;
3174
3175	NEXT ();
3176	OUT (0xf8);
3177	OUT (0x06);
3178	drop_int (&ob);
3179	ID;
3180	INTn (stack size);
3181	INTn (type return);
3182	EXPn (offset);
3183	block ();
3184	NEXT ();
3185	OUT (0xf9);
3186	EXPn (size);
3187	fill_int (&ob);
3188      }
3189      break;
3190
3191    case 0x0a:
3192      /* Assembler module scope beginning -  */
3193      {
3194	struct output_buffer_struct ob;
3195
3196	NEXT ();
3197	OUT (0xf8);
3198	OUT (0x0a);
3199	drop_int (&ob);
3200	ID;
3201	ID;
3202	INT;
3203	ID;
3204	INT;
3205	INT;
3206	INT;
3207	INT;
3208	INT;
3209	INT;
3210
3211	block ();
3212
3213	NEXT ();
3214	OUT (0xf9);
3215	fill_int (&ob);
3216      }
3217      break;
3218    case 0x0b:
3219      {
3220	struct output_buffer_struct ob;
3221
3222	NEXT ();
3223	OUT (0xf8);
3224	OUT (0x0b);
3225	drop_int (&ob);
3226	ID;
3227	INT;
3228	INTn (section index);
3229	EXPn (offset);
3230	INTn (stuff);
3231
3232	block ();
3233
3234	OUT (0xf9);
3235	NEXT ();
3236	EXPn (Size in Maus);
3237	fill_int (&ob);
3238      }
3239      break;
3240    }
3241}
3242
3243static void
3244e2_record ()
3245{
3246  OUT (0xe2);
3247  NEXT ();
3248  OUT (0xce);
3249  NEXT ();
3250  INT;
3251  EXP;
3252}
3253
3254static void
3255block ()
3256{
3257  int ch;
3258
3259  while (1)
3260    {
3261      ch = THIS ();
3262      switch (ch)
3263	{
3264	case 0xe1:
3265	case 0xe5:
3266	  return;
3267	case 0xf9:
3268	  return;
3269	case 0xf0:
3270	  f0_record ();
3271	  break;
3272	case 0xf1:
3273	  f1_record ();
3274	  break;
3275	case 0xf2:
3276	  f2_record ();
3277	  break;
3278	case 0xf8:
3279	  f8_record ();
3280	  break;
3281	case 0xe2:
3282	  e2_record ();
3283	  break;
3284
3285	}
3286    }
3287}
3288
3289
3290/* Moves all the debug information from the source bfd to the output
3291   bfd, and relocates any expressions it finds.  */
3292
3293static void
3294relocate_debug (output, input)
3295     bfd *output ATTRIBUTE_UNUSED;
3296     bfd *input;
3297{
3298#define IBS 400
3299#define OBS 400
3300  unsigned char input_buffer[IBS];
3301
3302  input_ptr_start = input_ptr = input_buffer;
3303  input_ptr_end = input_buffer + IBS;
3304  input_bfd = input;
3305  /* FIXME: Check return value.  I'm not sure whether it needs to read
3306     the entire buffer or not.  */
3307  bfd_bread ((PTR) input_ptr_start, (bfd_size_type) IBS, input);
3308  block ();
3309}
3310
3311/* Gather together all the debug information from each input BFD into
3312   one place, relocating it and emitting it as we go.  */
3313
3314static bfd_boolean
3315ieee_write_debug_part (abfd)
3316     bfd *abfd;
3317{
3318  ieee_data_type *ieee = IEEE_DATA (abfd);
3319  bfd_chain_type *chain = ieee->chain_root;
3320  unsigned char obuff[OBS];
3321  bfd_boolean some_debug = FALSE;
3322  file_ptr here = bfd_tell (abfd);
3323
3324  output_ptr_start = output_ptr = obuff;
3325  output_ptr_end = obuff + OBS;
3326  output_ptr = obuff;
3327  output_bfd = abfd;
3328
3329  if (chain == (bfd_chain_type *) NULL)
3330    {
3331      asection *s;
3332
3333      for (s = abfd->sections; s != NULL; s = s->next)
3334	if ((s->flags & SEC_DEBUGGING) != 0)
3335	  break;
3336      if (s == NULL)
3337	{
3338	  ieee->w.r.debug_information_part = 0;
3339	  return TRUE;
3340	}
3341
3342      ieee->w.r.debug_information_part = here;
3343      if (bfd_bwrite (s->contents, s->size, abfd) != s->size)
3344	return FALSE;
3345    }
3346  else
3347    {
3348      while (chain != (bfd_chain_type *) NULL)
3349	{
3350	  bfd *entry = chain->this;
3351	  ieee_data_type *entry_ieee = IEEE_DATA (entry);
3352
3353	  if (entry_ieee->w.r.debug_information_part)
3354	    {
3355	      if (bfd_seek (entry, entry_ieee->w.r.debug_information_part,
3356			    SEEK_SET) != 0)
3357		return FALSE;
3358	      relocate_debug (abfd, entry);
3359	    }
3360
3361	  chain = chain->next;
3362	}
3363
3364      if (some_debug)
3365	ieee->w.r.debug_information_part = here;
3366      else
3367	ieee->w.r.debug_information_part = 0;
3368
3369      flush ();
3370    }
3371
3372  return TRUE;
3373}
3374
3375/* Write the data in an ieee way.  */
3376
3377static bfd_boolean
3378ieee_write_data_part (abfd)
3379     bfd *abfd;
3380{
3381  asection *s;
3382
3383  ieee_data_type *ieee = IEEE_DATA (abfd);
3384  ieee->w.r.data_part = bfd_tell (abfd);
3385
3386  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
3387    {
3388      /* Skip sections that have no loadable contents (.bss,
3389         debugging, etc.)  */
3390      if ((s->flags & SEC_LOAD) == 0)
3391	continue;
3392
3393      /* Sort the reloc records so we can insert them in the correct
3394	 places */
3395      if (s->reloc_count != 0)
3396	{
3397	  if (! do_with_relocs (abfd, s))
3398	    return FALSE;
3399	}
3400      else
3401	{
3402	  if (! do_without_relocs (abfd, s))
3403	    return FALSE;
3404	}
3405    }
3406
3407  return TRUE;
3408}
3409
3410
3411static bfd_boolean
3412init_for_output (abfd)
3413     bfd *abfd;
3414{
3415  asection *s;
3416
3417  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
3418    {
3419      if ((s->flags & SEC_DEBUGGING) != 0)
3420	continue;
3421      if (s->size != 0)
3422	{
3423	  bfd_size_type size = s->size;
3424	  ieee_per_section (s)->data = (bfd_byte *) (bfd_alloc (abfd, size));
3425	  if (!ieee_per_section (s)->data)
3426	    return FALSE;
3427	}
3428    }
3429  return TRUE;
3430}
3431
3432/* Exec and core file sections.  */
3433
3434/* Set section contents is complicated with IEEE since the format is
3435   not a byte image, but a record stream.  */
3436
3437static bfd_boolean
3438ieee_set_section_contents (abfd, section, location, offset, count)
3439     bfd *abfd;
3440     sec_ptr section;
3441     const PTR location;
3442     file_ptr offset;
3443     bfd_size_type count;
3444{
3445  if ((section->flags & SEC_DEBUGGING) != 0)
3446    {
3447      if (section->contents == NULL)
3448	{
3449	  bfd_size_type size = section->size;
3450	  section->contents = (unsigned char *) bfd_alloc (abfd, size);
3451	  if (section->contents == NULL)
3452	    return FALSE;
3453	}
3454      /* bfd_set_section_contents has already checked that everything
3455         is within range.  */
3456      memcpy (section->contents + offset, location, (size_t) count);
3457      return TRUE;
3458    }
3459
3460  if (ieee_per_section (section)->data == (bfd_byte *) NULL)
3461    {
3462      if (!init_for_output (abfd))
3463	return FALSE;
3464    }
3465  memcpy ((PTR) (ieee_per_section (section)->data + offset),
3466	  (PTR) location,
3467	  (unsigned int) count);
3468  return TRUE;
3469}
3470
3471/* Write the external symbols of a file.  IEEE considers two sorts of
3472   external symbols, public, and referenced.  It uses to internal
3473   forms to index them as well.  When we write them out we turn their
3474   symbol values into indexes from the right base.  */
3475
3476static bfd_boolean
3477ieee_write_external_part (abfd)
3478     bfd *abfd;
3479{
3480  asymbol **q;
3481  ieee_data_type *ieee = IEEE_DATA (abfd);
3482  unsigned int reference_index = IEEE_REFERENCE_BASE;
3483  unsigned int public_index = IEEE_PUBLIC_BASE + 2;
3484  file_ptr here = bfd_tell (abfd);
3485  bfd_boolean hadone = FALSE;
3486
3487  if (abfd->outsymbols != (asymbol **) NULL)
3488    {
3489
3490      for (q = abfd->outsymbols; *q != (asymbol *) NULL; q++)
3491	{
3492	  asymbol *p = *q;
3493
3494	  if (bfd_is_und_section (p->section))
3495	    {
3496	      /* This must be a symbol reference.  */
3497	      if (! ieee_write_byte (abfd, ieee_external_reference_enum)
3498		  || ! ieee_write_int (abfd, (bfd_vma) reference_index)
3499		  || ! ieee_write_id (abfd, p->name))
3500		return FALSE;
3501	      p->value = reference_index;
3502	      reference_index++;
3503	      hadone = TRUE;
3504	    }
3505	  else if (bfd_is_com_section (p->section))
3506	    {
3507	      /* This is a weak reference.  */
3508	      if (! ieee_write_byte (abfd, ieee_external_reference_enum)
3509		  || ! ieee_write_int (abfd, (bfd_vma) reference_index)
3510		  || ! ieee_write_id (abfd, p->name)
3511		  || ! ieee_write_byte (abfd,
3512					ieee_weak_external_reference_enum)
3513		  || ! ieee_write_int (abfd, (bfd_vma) reference_index)
3514		  || ! ieee_write_int (abfd, p->value))
3515		return FALSE;
3516	      p->value = reference_index;
3517	      reference_index++;
3518	      hadone = TRUE;
3519	    }
3520	  else if (p->flags & BSF_GLOBAL)
3521	    {
3522	      /* This must be a symbol definition.  */
3523	      if (! ieee_write_byte (abfd, ieee_external_symbol_enum)
3524		  || ! ieee_write_int (abfd, (bfd_vma) public_index)
3525		  || ! ieee_write_id (abfd, p->name)
3526		  || ! ieee_write_2bytes (abfd, ieee_attribute_record_enum)
3527		  || ! ieee_write_int (abfd, (bfd_vma) public_index)
3528		  || ! ieee_write_byte (abfd, 15) /* instruction address */
3529		  || ! ieee_write_byte (abfd, 19) /* static symbol */
3530		  || ! ieee_write_byte (abfd, 1)) /* one of them */
3531		return FALSE;
3532
3533	      /* Write out the value.  */
3534	      if (! ieee_write_2bytes (abfd, ieee_value_record_enum)
3535		  || ! ieee_write_int (abfd, (bfd_vma) public_index))
3536		return FALSE;
3537	      if (! bfd_is_abs_section (p->section))
3538		{
3539		  if (abfd->flags & EXEC_P)
3540		    {
3541		      /* If fully linked, then output all symbols
3542			 relocated.  */
3543		      if (! (ieee_write_int
3544			     (abfd,
3545			      (p->value
3546			       + p->section->output_offset
3547			       + p->section->output_section->vma))))
3548			return FALSE;
3549		    }
3550		  else
3551		    {
3552		      if (! (ieee_write_expression
3553			     (abfd,
3554			      p->value + p->section->output_offset,
3555			      p->section->output_section->symbol,
3556			      FALSE, 0)))
3557			return FALSE;
3558		    }
3559		}
3560	      else
3561		{
3562		  if (! ieee_write_expression (abfd,
3563					       p->value,
3564					       bfd_abs_section_ptr->symbol,
3565					       FALSE, 0))
3566		    return FALSE;
3567		}
3568	      p->value = public_index;
3569	      public_index++;
3570	      hadone = TRUE;
3571	    }
3572	  else
3573	    {
3574	      /* This can happen - when there are gaps in the symbols read
3575	         from an input ieee file.  */
3576	    }
3577	}
3578    }
3579  if (hadone)
3580    ieee->w.r.external_part = here;
3581
3582  return TRUE;
3583}
3584
3585
3586static const unsigned char exten[] =
3587{
3588  0xf0, 0x20, 0x00,
3589  0xf1, 0xce, 0x20, 0x00, 37, 3, 3,	/* Set version 3 rev 3.  */
3590  0xf1, 0xce, 0x20, 0x00, 39, 2,	/* Keep symbol in  original case.  */
3591  0xf1, 0xce, 0x20, 0x00, 38		/* Set object type relocatable to x.  */
3592};
3593
3594static const unsigned char envi[] =
3595{
3596  0xf0, 0x21, 0x00,
3597
3598/*    0xf1, 0xce, 0x21, 00, 50, 0x82, 0x07, 0xc7, 0x09, 0x11, 0x11,
3599    0x19, 0x2c,
3600*/
3601  0xf1, 0xce, 0x21, 00, 52, 0x00,	/* exec ok */
3602
3603  0xf1, 0xce, 0x21, 0, 53, 0x03,/* host unix */
3604/*    0xf1, 0xce, 0x21, 0, 54, 2,1,1	tool & version # */
3605};
3606
3607static bfd_boolean
3608ieee_write_me_part (abfd)
3609     bfd *abfd;
3610{
3611  ieee_data_type *ieee = IEEE_DATA (abfd);
3612  ieee->w.r.trailer_part = bfd_tell (abfd);
3613  if (abfd->start_address)
3614    {
3615      if (! ieee_write_2bytes (abfd, ieee_value_starting_address_enum)
3616	  || ! ieee_write_byte (abfd, ieee_function_either_open_b_enum)
3617	  || ! ieee_write_int (abfd, abfd->start_address)
3618	  || ! ieee_write_byte (abfd, ieee_function_either_close_b_enum))
3619	return FALSE;
3620    }
3621  ieee->w.r.me_record = bfd_tell (abfd);
3622  if (! ieee_write_byte (abfd, ieee_module_end_enum))
3623    return FALSE;
3624  return TRUE;
3625}
3626
3627/* Write out the IEEE processor ID.  */
3628
3629static bfd_boolean
3630ieee_write_processor (abfd)
3631     bfd *abfd;
3632{
3633  const bfd_arch_info_type *arch;
3634
3635  arch = bfd_get_arch_info (abfd);
3636  switch (arch->arch)
3637    {
3638    default:
3639      if (! ieee_write_id (abfd, bfd_printable_name (abfd)))
3640	return FALSE;
3641      break;
3642
3643    case bfd_arch_a29k:
3644      if (! ieee_write_id (abfd, "29000"))
3645	return FALSE;
3646      break;
3647
3648    case bfd_arch_h8300:
3649      if (! ieee_write_id (abfd, "H8/300"))
3650	return FALSE;
3651      break;
3652
3653    case bfd_arch_h8500:
3654      if (! ieee_write_id (abfd, "H8/500"))
3655	return FALSE;
3656      break;
3657
3658    case bfd_arch_i960:
3659      switch (arch->mach)
3660	{
3661	default:
3662	case bfd_mach_i960_core:
3663	case bfd_mach_i960_ka_sa:
3664	  if (! ieee_write_id (abfd, "80960KA"))
3665	    return FALSE;
3666	  break;
3667
3668	case bfd_mach_i960_kb_sb:
3669	  if (! ieee_write_id (abfd, "80960KB"))
3670	    return FALSE;
3671	  break;
3672
3673	case bfd_mach_i960_ca:
3674	  if (! ieee_write_id (abfd, "80960CA"))
3675	    return FALSE;
3676	  break;
3677
3678	case bfd_mach_i960_mc:
3679	case bfd_mach_i960_xa:
3680	  if (! ieee_write_id (abfd, "80960MC"))
3681	    return FALSE;
3682	  break;
3683	}
3684      break;
3685
3686    case bfd_arch_m68k:
3687      {
3688	const char *id;
3689
3690	switch (arch->mach)
3691	  {
3692	  default:		id = "68020"; break;
3693	  case bfd_mach_m68000: id = "68000"; break;
3694	  case bfd_mach_m68008: id = "68008"; break;
3695	  case bfd_mach_m68010: id = "68010"; break;
3696	  case bfd_mach_m68020: id = "68020"; break;
3697	  case bfd_mach_m68030: id = "68030"; break;
3698	  case bfd_mach_m68040: id = "68040"; break;
3699	  case bfd_mach_m68060: id = "68060"; break;
3700	  case bfd_mach_cpu32:  id = "cpu32"; break;
3701	  case bfd_mach_mcf5200:id = "5200";  break;
3702	  case bfd_mach_mcf5206e:id = "5206e"; break;
3703	  case bfd_mach_mcf5307:id = "5307";  break;
3704	  case bfd_mach_mcf5407:id = "5407";  break;
3705	  case bfd_mach_mcf528x:id = "5282";  break;
3706	  }
3707
3708	if (! ieee_write_id (abfd, id))
3709	  return FALSE;
3710      }
3711      break;
3712    }
3713
3714  return TRUE;
3715}
3716
3717static bfd_boolean
3718ieee_write_object_contents (abfd)
3719     bfd *abfd;
3720{
3721  ieee_data_type *ieee = IEEE_DATA (abfd);
3722  unsigned int i;
3723  file_ptr old;
3724
3725  /* Fast forward over the header area.  */
3726  if (bfd_seek (abfd, (file_ptr) 0, SEEK_SET) != 0)
3727    return FALSE;
3728
3729  if (! ieee_write_byte (abfd, ieee_module_beginning_enum)
3730      || ! ieee_write_processor (abfd)
3731      || ! ieee_write_id (abfd, abfd->filename))
3732    return FALSE;
3733
3734  /* Fast forward over the variable bits.  */
3735  if (! ieee_write_byte (abfd, ieee_address_descriptor_enum))
3736    return FALSE;
3737
3738  /* Bits per MAU.  */
3739  if (! ieee_write_byte (abfd, (bfd_byte) (bfd_arch_bits_per_byte (abfd))))
3740    return FALSE;
3741  /* MAU's per address.  */
3742  if (! ieee_write_byte (abfd,
3743			 (bfd_byte) (bfd_arch_bits_per_address (abfd)
3744				     / bfd_arch_bits_per_byte (abfd))))
3745    return FALSE;
3746
3747  old = bfd_tell (abfd);
3748  if (bfd_seek (abfd, (file_ptr) (8 * N_W_VARIABLES), SEEK_CUR) != 0)
3749    return FALSE;
3750
3751  ieee->w.r.extension_record = bfd_tell (abfd);
3752  if (bfd_bwrite ((char *) exten, (bfd_size_type) sizeof (exten), abfd)
3753      != sizeof (exten))
3754    return FALSE;
3755  if (abfd->flags & EXEC_P)
3756    {
3757      if (! ieee_write_byte (abfd, 0x1)) /* Absolute */
3758	return FALSE;
3759    }
3760  else
3761    {
3762      if (! ieee_write_byte (abfd, 0x2)) /* Relocateable */
3763	return FALSE;
3764    }
3765
3766  ieee->w.r.environmental_record = bfd_tell (abfd);
3767  if (bfd_bwrite ((char *) envi, (bfd_size_type) sizeof (envi), abfd)
3768      != sizeof (envi))
3769    return FALSE;
3770
3771  /* The HP emulator database requires a timestamp in the file.  */
3772  {
3773    time_t now;
3774    const struct tm *t;
3775
3776    time (&now);
3777    t = (struct tm *) localtime (&now);
3778    if (! ieee_write_2bytes (abfd, (int) ieee_atn_record_enum)
3779	|| ! ieee_write_byte (abfd, 0x21)
3780	|| ! ieee_write_byte (abfd, 0)
3781	|| ! ieee_write_byte (abfd, 50)
3782	|| ! ieee_write_int (abfd, (bfd_vma) (t->tm_year + 1900))
3783	|| ! ieee_write_int (abfd, (bfd_vma) (t->tm_mon + 1))
3784	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_mday)
3785	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_hour)
3786	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_min)
3787	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_sec))
3788      return FALSE;
3789  }
3790
3791  output_bfd = abfd;
3792
3793  flush ();
3794
3795  if (! ieee_write_section_part (abfd))
3796    return FALSE;
3797  /* First write the symbols.  This changes their values into table
3798    indeces so we cant use it after this point.  */
3799  if (! ieee_write_external_part (abfd))
3800    return FALSE;
3801
3802  /* Write any debugs we have been told about.  */
3803  if (! ieee_write_debug_part (abfd))
3804    return FALSE;
3805
3806  /* Can only write the data once the symbols have been written, since
3807     the data contains relocation information which points to the
3808     symbols.  */
3809  if (! ieee_write_data_part (abfd))
3810    return FALSE;
3811
3812  /* At the end we put the end!  */
3813  if (! ieee_write_me_part (abfd))
3814    return FALSE;
3815
3816  /* Generate the header.  */
3817  if (bfd_seek (abfd, old, SEEK_SET) != 0)
3818    return FALSE;
3819
3820  for (i = 0; i < N_W_VARIABLES; i++)
3821    {
3822      if (! ieee_write_2bytes (abfd, ieee_assign_value_to_variable_enum)
3823	  || ! ieee_write_byte (abfd, (bfd_byte) i)
3824	  || ! ieee_write_int5_out (abfd, (bfd_vma) ieee->w.offset[i]))
3825	return FALSE;
3826    }
3827
3828  return TRUE;
3829}
3830
3831/* Native-level interface to symbols. */
3832
3833/* We read the symbols into a buffer, which is discarded when this
3834   function exits.  We read the strings into a buffer large enough to
3835   hold them all plus all the cached symbol entries.  */
3836
3837static asymbol *
3838ieee_make_empty_symbol (abfd)
3839     bfd *abfd;
3840{
3841  bfd_size_type amt = sizeof (ieee_symbol_type);
3842  ieee_symbol_type *new = (ieee_symbol_type *) bfd_zalloc (abfd, amt);
3843
3844  if (!new)
3845    return NULL;
3846  new->symbol.the_bfd = abfd;
3847  return &new->symbol;
3848}
3849
3850static bfd *
3851ieee_openr_next_archived_file (arch, prev)
3852     bfd *arch;
3853     bfd *prev;
3854{
3855  ieee_ar_data_type *ar = IEEE_AR_DATA (arch);
3856
3857  /* Take the next one from the arch state, or reset.  */
3858  if (prev == (bfd *) NULL)
3859    /* Reset the index - the first two entries are bogus.  */
3860    ar->element_index = 2;
3861
3862  while (TRUE)
3863    {
3864      ieee_ar_obstack_type *p = ar->elements + ar->element_index;
3865
3866      ar->element_index++;
3867      if (ar->element_index <= ar->element_count)
3868	{
3869	  if (p->file_offset != (file_ptr) 0)
3870	    {
3871	      if (p->abfd == (bfd *) NULL)
3872		{
3873		  p->abfd = _bfd_create_empty_archive_element_shell (arch);
3874		  p->abfd->origin = p->file_offset;
3875		}
3876	      return p->abfd;
3877	    }
3878	}
3879      else
3880	{
3881	  bfd_set_error (bfd_error_no_more_archived_files);
3882	  return (bfd *) NULL;
3883	}
3884    }
3885}
3886
3887static bfd_boolean
3888ieee_find_nearest_line (abfd, section, symbols, offset, filename_ptr,
3889			functionname_ptr, line_ptr)
3890     bfd *abfd ATTRIBUTE_UNUSED;
3891     asection *section ATTRIBUTE_UNUSED;
3892     asymbol **symbols ATTRIBUTE_UNUSED;
3893     bfd_vma offset ATTRIBUTE_UNUSED;
3894     const char **filename_ptr ATTRIBUTE_UNUSED;
3895     const char **functionname_ptr ATTRIBUTE_UNUSED;
3896     unsigned int *line_ptr ATTRIBUTE_UNUSED;
3897{
3898  return FALSE;
3899}
3900
3901static int
3902ieee_generic_stat_arch_elt (abfd, buf)
3903     bfd *abfd;
3904     struct stat *buf;
3905{
3906  ieee_ar_data_type *ar = (ieee_ar_data_type *) NULL;
3907  ieee_data_type *ieee;
3908
3909  if (abfd->my_archive != NULL)
3910    ar = abfd->my_archive->tdata.ieee_ar_data;
3911  if (ar == (ieee_ar_data_type *) NULL)
3912    {
3913      bfd_set_error (bfd_error_invalid_operation);
3914      return -1;
3915    }
3916
3917  if (IEEE_DATA (abfd) == NULL)
3918    {
3919      if (ieee_object_p (abfd) == NULL)
3920	{
3921	  bfd_set_error (bfd_error_wrong_format);
3922	  return -1;
3923	}
3924    }
3925
3926  ieee = IEEE_DATA (abfd);
3927
3928  buf->st_size = ieee->w.r.me_record + 1;
3929  buf->st_mode = 0644;
3930  return 0;
3931}
3932
3933static int
3934ieee_sizeof_headers (abfd, x)
3935     bfd *abfd ATTRIBUTE_UNUSED;
3936     bfd_boolean x ATTRIBUTE_UNUSED;
3937{
3938  return 0;
3939}
3940
3941
3942/* The debug info routines are never used.  */
3943#if 0
3944
3945static void
3946ieee_bfd_debug_info_start (abfd)
3947     bfd *abfd;
3948{
3949
3950}
3951
3952static void
3953ieee_bfd_debug_info_end (abfd)
3954     bfd *abfd;
3955{
3956
3957}
3958
3959
3960/* Add this section to the list of sections we have debug info for, to
3961   be ready to output it at close time.  */
3962static void
3963ieee_bfd_debug_info_accumulate (abfd, section)
3964     bfd *abfd;
3965     asection *section;
3966{
3967  ieee_data_type *ieee = IEEE_DATA (section->owner);
3968  ieee_data_type *output_ieee = IEEE_DATA (abfd);
3969
3970  /* Can only accumulate data from other ieee bfds.  */
3971  if (section->owner->xvec != abfd->xvec)
3972    return;
3973  /* Only bother once per bfd.  */
3974  if (ieee->done_debug)
3975    return;
3976  ieee->done_debug = TRUE;
3977
3978  /* Don't bother if there is no debug info.  */
3979  if (ieee->w.r.debug_information_part == 0)
3980    return;
3981
3982  /* Add to chain.  */
3983  {
3984    bfd_size_type amt = sizeof (bfd_chain_type);
3985    bfd_chain_type *n = (bfd_chain_type *) bfd_alloc (abfd, amt);
3986
3987    if (!n)
3988      abort ();		/* FIXME */
3989    n->this = section->owner;
3990    n->next = (bfd_chain_type *) NULL;
3991
3992    if (output_ieee->chain_head)
3993      output_ieee->chain_head->next = n;
3994    else
3995      output_ieee->chain_root = n;
3996
3997    output_ieee->chain_head = n;
3998  }
3999}
4000
4001#endif
4002
4003#define	ieee_close_and_cleanup _bfd_generic_close_and_cleanup
4004#define ieee_bfd_free_cached_info _bfd_generic_bfd_free_cached_info
4005
4006#define ieee_slurp_armap bfd_true
4007#define ieee_slurp_extended_name_table bfd_true
4008#define ieee_construct_extended_name_table \
4009  ((bfd_boolean (*) \
4010    PARAMS ((bfd *, char **, bfd_size_type *, const char **))) \
4011   bfd_true)
4012#define ieee_truncate_arname bfd_dont_truncate_arname
4013#define ieee_write_armap \
4014  ((bfd_boolean (*) \
4015    PARAMS ((bfd *, unsigned int, struct orl *, unsigned int, int))) \
4016   bfd_true)
4017#define ieee_read_ar_hdr bfd_nullvoidptr
4018#define ieee_update_armap_timestamp bfd_true
4019#define ieee_get_elt_at_index _bfd_generic_get_elt_at_index
4020
4021#define ieee_bfd_is_target_special_symbol  \
4022  ((bfd_boolean (*) (bfd *, asymbol *)) bfd_false)
4023#define ieee_bfd_is_local_label_name bfd_generic_is_local_label_name
4024#define ieee_get_lineno _bfd_nosymbols_get_lineno
4025#define ieee_bfd_make_debug_symbol _bfd_nosymbols_bfd_make_debug_symbol
4026#define ieee_read_minisymbols _bfd_generic_read_minisymbols
4027#define ieee_minisymbol_to_symbol _bfd_generic_minisymbol_to_symbol
4028
4029#define ieee_bfd_reloc_type_lookup _bfd_norelocs_bfd_reloc_type_lookup
4030
4031#define ieee_set_arch_mach _bfd_generic_set_arch_mach
4032
4033#define ieee_get_section_contents_in_window \
4034  _bfd_generic_get_section_contents_in_window
4035#define ieee_bfd_get_relocated_section_contents \
4036  bfd_generic_get_relocated_section_contents
4037#define ieee_bfd_relax_section bfd_generic_relax_section
4038#define ieee_bfd_gc_sections bfd_generic_gc_sections
4039#define ieee_bfd_merge_sections bfd_generic_merge_sections
4040#define ieee_bfd_is_group_section bfd_generic_is_group_section
4041#define ieee_bfd_discard_group bfd_generic_discard_group
4042#define ieee_section_already_linked \
4043  _bfd_generic_section_already_linked
4044#define ieee_bfd_link_hash_table_create _bfd_generic_link_hash_table_create
4045#define ieee_bfd_link_hash_table_free _bfd_generic_link_hash_table_free
4046#define ieee_bfd_link_add_symbols _bfd_generic_link_add_symbols
4047#define ieee_bfd_link_just_syms _bfd_generic_link_just_syms
4048#define ieee_bfd_final_link _bfd_generic_final_link
4049#define ieee_bfd_link_split_section  _bfd_generic_link_split_section
4050
4051const bfd_target ieee_vec =
4052{
4053  "ieee",			/* name */
4054  bfd_target_ieee_flavour,
4055  BFD_ENDIAN_UNKNOWN,		/* target byte order */
4056  BFD_ENDIAN_UNKNOWN,		/* target headers byte order */
4057  (HAS_RELOC | EXEC_P |		/* object flags */
4058   HAS_LINENO | HAS_DEBUG |
4059   HAS_SYMS | HAS_LOCALS | WP_TEXT | D_PAGED),
4060  (SEC_CODE | SEC_DATA | SEC_ROM | SEC_HAS_CONTENTS
4061   | SEC_ALLOC | SEC_LOAD | SEC_RELOC),	/* section flags */
4062  '_',				/* leading underscore */
4063  ' ',				/* ar_pad_char */
4064  16,				/* ar_max_namelen */
4065  bfd_getb64, bfd_getb_signed_64, bfd_putb64,
4066  bfd_getb32, bfd_getb_signed_32, bfd_putb32,
4067  bfd_getb16, bfd_getb_signed_16, bfd_putb16,	/* data */
4068  bfd_getb64, bfd_getb_signed_64, bfd_putb64,
4069  bfd_getb32, bfd_getb_signed_32, bfd_putb32,
4070  bfd_getb16, bfd_getb_signed_16, bfd_putb16,	/* hdrs */
4071
4072  {_bfd_dummy_target,
4073   ieee_object_p,		/* bfd_check_format */
4074   ieee_archive_p,
4075   _bfd_dummy_target,
4076  },
4077  {
4078    bfd_false,
4079    ieee_mkobject,
4080    _bfd_generic_mkarchive,
4081    bfd_false
4082  },
4083  {
4084    bfd_false,
4085    ieee_write_object_contents,
4086    _bfd_write_archive_contents,
4087    bfd_false,
4088  },
4089
4090  /* ieee_close_and_cleanup, ieee_bfd_free_cached_info, ieee_new_section_hook,
4091     ieee_get_section_contents, ieee_get_section_contents_in_window  */
4092  BFD_JUMP_TABLE_GENERIC (ieee),
4093
4094  BFD_JUMP_TABLE_COPY (_bfd_generic),
4095  BFD_JUMP_TABLE_CORE (_bfd_nocore),
4096
4097  /* ieee_slurp_armap, ieee_slurp_extended_name_table,
4098     ieee_construct_extended_name_table, ieee_truncate_arname,
4099     ieee_write_armap, ieee_read_ar_hdr, ieee_openr_next_archived_file,
4100     ieee_get_elt_at_index, ieee_generic_stat_arch_elt,
4101     ieee_update_armap_timestamp  */
4102  BFD_JUMP_TABLE_ARCHIVE (ieee),
4103
4104  /* ieee_get_symtab_upper_bound, ieee_canonicalize_symtab,
4105     ieee_make_empty_symbol, ieee_print_symbol, ieee_get_symbol_info,
4106     ieee_bfd_is_local_label_name, ieee_get_lineno,
4107     ieee_find_nearest_line, ieee_bfd_make_debug_symbol,
4108     ieee_read_minisymbols, ieee_minisymbol_to_symbol */
4109  BFD_JUMP_TABLE_SYMBOLS (ieee),
4110
4111  /* ieee_get_reloc_upper_bound, ieee_canonicalize_reloc,
4112     ieee_bfd_reloc_type_lookup  */
4113  BFD_JUMP_TABLE_RELOCS (ieee),
4114
4115  /* ieee_set_arch_mach, ieee_set_section_contents  */
4116  BFD_JUMP_TABLE_WRITE (ieee),
4117
4118  /* ieee_sizeof_headers, ieee_bfd_get_relocated_section_contents,
4119     ieee_bfd_relax_section, ieee_bfd_link_hash_table_create,
4120     _bfd_generic_link_hash_table_free,
4121     ieee_bfd_link_add_symbols, ieee_bfd_final_link,
4122     ieee_bfd_link_split_section, ieee_bfd_gc_sections,
4123     ieee_bfd_merge_sections  */
4124  BFD_JUMP_TABLE_LINK (ieee),
4125
4126  BFD_JUMP_TABLE_DYNAMIC (_bfd_nodynamic),
4127
4128  NULL,
4129
4130  (PTR) 0
4131};
4132