ieee.c revision 130561
1208322Sjkim/* BFD back-end for ieee-695 objects.
2208322Sjkim   Copyright 1990, 1991, 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999,
3208322Sjkim   2000, 2001, 2002, 2003
4208322Sjkim   Free Software Foundation, Inc.
5208322Sjkim
6208322Sjkim   Written by Steve Chamberlain of Cygnus Support.
7208322Sjkim
8208322Sjkim   This file is part of BFD, the Binary File Descriptor library.
9208322Sjkim
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))]->_raw_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		      (_("%s: unimplemented ATI record %u for symbol %u"),
939		       bfd_archive_filename (abfd), symbol_attribute_def,
940		       symbol_name_index);
941		    bfd_set_error (bfd_error_bad_value);
942		    return FALSE;
943		    break;
944		  }
945		break;
946	      case ieee_external_reference_info_record_enum:
947		/* Skip over ATX record.  */
948		parse_int (&(ieee->h), &value);
949		parse_int (&(ieee->h), &value);
950		parse_int (&(ieee->h), &value);
951		parse_int (&(ieee->h), &value);
952		break;
953	      case ieee_atn_record_enum:
954		/* We may get call optimization information here,
955		   which we just ignore.  The format is
956		   {$F1}${CE}{index}{$00}{$3F}{$3F}{#_of_ASNs}.  */
957		parse_int (&ieee->h, &value);
958		parse_int (&ieee->h, &value);
959		parse_int (&ieee->h, &value);
960		if (value != 0x3f)
961		  {
962		    (*_bfd_error_handler)
963		      (_("%s: unexpected ATN type %d in external part"),
964			 bfd_archive_filename (abfd), (int) value);
965		    bfd_set_error (bfd_error_bad_value);
966		    return FALSE;
967		  }
968		parse_int (&ieee->h, &value);
969		parse_int (&ieee->h, &value);
970		while (value > 0)
971		  {
972		    bfd_vma val1;
973
974		    --value;
975
976		    switch (read_2bytes (&ieee->h))
977		      {
978		      case ieee_asn_record_enum:
979			parse_int (&ieee->h, &val1);
980			parse_int (&ieee->h, &val1);
981			break;
982
983		      default:
984			(*_bfd_error_handler)
985			  (_("%s: unexpected type after ATN"),
986			     bfd_archive_filename (abfd));
987			bfd_set_error (bfd_error_bad_value);
988			return FALSE;
989		      }
990		  }
991	      }
992	  }
993	  break;
994	case ieee_value_record_enum >> 8:
995	  {
996	    unsigned int symbol_name_index;
997	    ieee_symbol_index_type symbol_ignore;
998	    bfd_boolean pcrel_ignore;
999	    unsigned int extra;
1000	    next_byte (&(ieee->h));
1001	    next_byte (&(ieee->h));
1002
1003	    symbol_name_index = must_parse_int (&(ieee->h));
1004	    parse_expression (ieee,
1005			      &symbol->symbol.value,
1006			      &symbol_ignore,
1007			      &pcrel_ignore,
1008			      &extra,
1009			      &symbol->symbol.section);
1010
1011	    /* Fully linked IEEE-695 files tend to give every symbol
1012               an absolute value.  Try to convert that back into a
1013               section relative value.  FIXME: This won't always to
1014               the right thing.  */
1015	    if (bfd_is_abs_section (symbol->symbol.section)
1016		&& (abfd->flags & HAS_RELOC) == 0)
1017	      {
1018		bfd_vma val;
1019		asection *s;
1020
1021		val = symbol->symbol.value;
1022		for (s = abfd->sections; s != NULL; s = s->next)
1023		  {
1024		    if (val >= s->vma && val < s->vma + s->_raw_size)
1025		      {
1026			symbol->symbol.section = s;
1027			symbol->symbol.value -= s->vma;
1028			break;
1029		      }
1030		  }
1031	      }
1032
1033	    symbol->symbol.flags = BSF_GLOBAL | BSF_EXPORT;
1034
1035	  }
1036	  break;
1037	case ieee_weak_external_reference_enum:
1038	  {
1039	    bfd_vma size;
1040	    bfd_vma value;
1041	    next_byte (&(ieee->h));
1042	    /* Throw away the external reference index.  */
1043	    (void) must_parse_int (&(ieee->h));
1044	    /* Fetch the default size if not resolved.  */
1045	    size = must_parse_int (&(ieee->h));
1046	    /* Fetch the default value if available.  */
1047	    if (! parse_int (&(ieee->h), &value))
1048	      {
1049		value = 0;
1050	      }
1051	    /* This turns into a common.  */
1052	    symbol->symbol.section = bfd_com_section_ptr;
1053	    symbol->symbol.value = size;
1054	  }
1055	  break;
1056
1057	case ieee_external_reference_enum:
1058	  next_byte (&(ieee->h));
1059
1060	  symbol = get_symbol (abfd, ieee, symbol, &symbol_count,
1061			       &prev_reference_ptr,
1062			       &ieee->external_reference_max_index, 'X');
1063	  if (symbol == NULL)
1064	    return FALSE;
1065
1066	  symbol->symbol.the_bfd = abfd;
1067	  symbol->symbol.name = read_id (&(ieee->h));
1068	  symbol->symbol.udata.p = (PTR) NULL;
1069	  symbol->symbol.section = bfd_und_section_ptr;
1070	  symbol->symbol.value = (bfd_vma) 0;
1071	  symbol->symbol.flags = 0;
1072
1073	  BFD_ASSERT (symbol->index >= ieee->external_reference_min_index);
1074	  break;
1075
1076	default:
1077	  loop = FALSE;
1078	}
1079    }
1080
1081  if (ieee->external_symbol_max_index != 0)
1082    {
1083      ieee->external_symbol_count =
1084	ieee->external_symbol_max_index -
1085	ieee->external_symbol_min_index + 1;
1086    }
1087  else
1088    {
1089      ieee->external_symbol_count = 0;
1090    }
1091
1092  if (ieee->external_reference_max_index != 0)
1093    {
1094      ieee->external_reference_count =
1095	ieee->external_reference_max_index -
1096	ieee->external_reference_min_index + 1;
1097    }
1098  else
1099    {
1100      ieee->external_reference_count = 0;
1101    }
1102
1103  abfd->symcount =
1104    ieee->external_reference_count + ieee->external_symbol_count;
1105
1106  if (symbol_count != abfd->symcount)
1107    {
1108      /* There are gaps in the table -- */
1109      ieee->symbol_table_full = FALSE;
1110    }
1111
1112  *prev_symbols_ptr = (ieee_symbol_type *) NULL;
1113  *prev_reference_ptr = (ieee_symbol_type *) NULL;
1114
1115  return TRUE;
1116}
1117
1118static bfd_boolean
1119ieee_slurp_symbol_table (abfd)
1120     bfd *abfd;
1121{
1122  if (! IEEE_DATA (abfd)->read_symbols)
1123    {
1124      if (! ieee_slurp_external_symbols (abfd))
1125	return FALSE;
1126      IEEE_DATA (abfd)->read_symbols = TRUE;
1127    }
1128  return TRUE;
1129}
1130
1131static long
1132ieee_get_symtab_upper_bound (abfd)
1133     bfd *abfd;
1134{
1135  if (! ieee_slurp_symbol_table (abfd))
1136    return -1;
1137
1138  return (abfd->symcount != 0) ?
1139    (abfd->symcount + 1) * (sizeof (ieee_symbol_type *)) : 0;
1140}
1141
1142/* Move from our internal lists to the canon table, and insert in
1143   symbol index order.  */
1144
1145extern const bfd_target ieee_vec;
1146
1147static long
1148ieee_canonicalize_symtab (abfd, location)
1149     bfd *abfd;
1150     asymbol **location;
1151{
1152  ieee_symbol_type *symp;
1153  static bfd dummy_bfd;
1154  static asymbol empty_symbol =
1155  {
1156    &dummy_bfd,
1157    " ieee empty",
1158    (symvalue) 0,
1159    BSF_DEBUGGING,
1160    bfd_abs_section_ptr
1161#ifdef __STDC__
1162    /* K&R compilers can't initialise unions.  */
1163    , { 0 }
1164#endif
1165  };
1166
1167  if (abfd->symcount)
1168    {
1169      ieee_data_type *ieee = IEEE_DATA (abfd);
1170      dummy_bfd.xvec = &ieee_vec;
1171      if (! ieee_slurp_symbol_table (abfd))
1172	return -1;
1173
1174      if (! ieee->symbol_table_full)
1175	{
1176	  /* Arrgh - there are gaps in the table, run through and fill them
1177	     up with pointers to a null place.  */
1178	  unsigned int i;
1179
1180	  for (i = 0; i < abfd->symcount; i++)
1181	    location[i] = &empty_symbol;
1182	}
1183
1184      ieee->external_symbol_base_offset = -ieee->external_symbol_min_index;
1185      for (symp = IEEE_DATA (abfd)->external_symbols;
1186	   symp != (ieee_symbol_type *) NULL;
1187	   symp = symp->next)
1188	/* Place into table at correct index locations.  */
1189	location[symp->index + ieee->external_symbol_base_offset] = &symp->symbol;
1190
1191      /* The external refs are indexed in a bit.  */
1192      ieee->external_reference_base_offset =
1193	-ieee->external_reference_min_index + ieee->external_symbol_count;
1194
1195      for (symp = IEEE_DATA (abfd)->external_reference;
1196	   symp != (ieee_symbol_type *) NULL;
1197	   symp = symp->next)
1198	location[symp->index + ieee->external_reference_base_offset] =
1199	  &symp->symbol;
1200    }
1201
1202  if (abfd->symcount)
1203    location[abfd->symcount] = (asymbol *) NULL;
1204
1205  return abfd->symcount;
1206}
1207
1208static asection *
1209get_section_entry (abfd, ieee, index)
1210     bfd *abfd;
1211     ieee_data_type *ieee;
1212     unsigned int index;
1213{
1214  if (index >= ieee->section_table_size)
1215    {
1216      unsigned int c, i;
1217      asection **n;
1218      bfd_size_type amt;
1219
1220      c = ieee->section_table_size;
1221      if (c == 0)
1222	c = 20;
1223      while (c <= index)
1224	c *= 2;
1225
1226      amt = c;
1227      amt *= sizeof (asection *);
1228      n = (asection **) bfd_realloc (ieee->section_table, amt);
1229      if (n == NULL)
1230	return NULL;
1231
1232      for (i = ieee->section_table_size; i < c; i++)
1233	n[i] = NULL;
1234
1235      ieee->section_table = n;
1236      ieee->section_table_size = c;
1237    }
1238
1239  if (ieee->section_table[index] == (asection *) NULL)
1240    {
1241      char *tmp = bfd_alloc (abfd, (bfd_size_type) 11);
1242      asection *section;
1243
1244      if (!tmp)
1245	return NULL;
1246      sprintf (tmp, " fsec%4d", index);
1247      section = bfd_make_section (abfd, tmp);
1248      ieee->section_table[index] = section;
1249      section->flags = SEC_NO_FLAGS;
1250      section->target_index = index;
1251      ieee->section_table[index] = section;
1252    }
1253  return ieee->section_table[index];
1254}
1255
1256static void
1257ieee_slurp_sections (abfd)
1258     bfd *abfd;
1259{
1260  ieee_data_type *ieee = IEEE_DATA (abfd);
1261  file_ptr offset = ieee->w.r.section_part;
1262  char *name;
1263
1264  if (offset != 0)
1265    {
1266      bfd_byte section_type[3];
1267      ieee_seek (ieee, offset);
1268      while (TRUE)
1269	{
1270	  switch (this_byte (&(ieee->h)))
1271	    {
1272	    case ieee_section_type_enum:
1273	      {
1274		asection *section;
1275		unsigned int section_index;
1276		next_byte (&(ieee->h));
1277		section_index = must_parse_int (&(ieee->h));
1278
1279		section = get_section_entry (abfd, ieee, section_index);
1280
1281		section_type[0] = this_byte_and_next (&(ieee->h));
1282
1283		/* Set minimal section attributes. Attributes are
1284		   extended later, based on section contents.  */
1285		switch (section_type[0])
1286		  {
1287		  case 0xC1:
1288		    /* Normal attributes for absolute sections.  */
1289		    section_type[1] = this_byte (&(ieee->h));
1290		    section->flags = SEC_ALLOC;
1291		    switch (section_type[1])
1292		      {
1293		      case 0xD3:	/* AS Absolute section attributes.  */
1294			next_byte (&(ieee->h));
1295			section_type[2] = this_byte (&(ieee->h));
1296			switch (section_type[2])
1297			  {
1298			  case 0xD0:
1299			    /* Normal code.  */
1300			    next_byte (&(ieee->h));
1301			    section->flags |= SEC_CODE;
1302			    break;
1303			  case 0xC4:
1304			    /* Normal data.  */
1305			    next_byte (&(ieee->h));
1306			    section->flags |= SEC_DATA;
1307			    break;
1308			  case 0xD2:
1309			    next_byte (&(ieee->h));
1310			    /* Normal rom data.  */
1311			    section->flags |= SEC_ROM | SEC_DATA;
1312			    break;
1313			  default:
1314			    break;
1315			  }
1316		      }
1317		    break;
1318		  case 0xC3:	/* Named relocatable sections (type C).  */
1319		    section_type[1] = this_byte (&(ieee->h));
1320		    section->flags = SEC_ALLOC;
1321		    switch (section_type[1])
1322		      {
1323		      case 0xD0:	/* Normal code (CP).  */
1324			next_byte (&(ieee->h));
1325			section->flags |= SEC_CODE;
1326			break;
1327		      case 0xC4:	/* Normal data (CD).  */
1328			next_byte (&(ieee->h));
1329			section->flags |= SEC_DATA;
1330			break;
1331		      case 0xD2:	/* Normal rom data (CR).  */
1332			next_byte (&(ieee->h));
1333			section->flags |= SEC_ROM | SEC_DATA;
1334			break;
1335		      default:
1336			break;
1337		      }
1338		  }
1339
1340		/* Read section name, use it if non empty.  */
1341		name = read_id (&ieee->h);
1342		if (name[0])
1343		  section->name = name;
1344
1345		/* Skip these fields, which we don't care about.  */
1346		{
1347		  bfd_vma parent, brother, context;
1348		  parse_int (&(ieee->h), &parent);
1349		  parse_int (&(ieee->h), &brother);
1350		  parse_int (&(ieee->h), &context);
1351		}
1352	      }
1353	      break;
1354	    case ieee_section_alignment_enum:
1355	      {
1356		unsigned int section_index;
1357		bfd_vma value;
1358		asection *section;
1359		next_byte (&(ieee->h));
1360		section_index = must_parse_int (&ieee->h);
1361		section = get_section_entry (abfd, ieee, section_index);
1362		if (section_index > ieee->section_count)
1363		  {
1364		    ieee->section_count = section_index;
1365		  }
1366		section->alignment_power =
1367		  bfd_log2 (must_parse_int (&ieee->h));
1368		(void) parse_int (&(ieee->h), &value);
1369	      }
1370	      break;
1371	    case ieee_e2_first_byte_enum:
1372	      {
1373		asection *section;
1374		ieee_record_enum_type t;
1375
1376		t = (ieee_record_enum_type) (read_2bytes (&(ieee->h)));
1377		switch (t)
1378		  {
1379		  case ieee_section_size_enum:
1380		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1381		    section->_raw_size = must_parse_int (&(ieee->h));
1382		    break;
1383		  case ieee_physical_region_size_enum:
1384		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1385		    section->_raw_size = must_parse_int (&(ieee->h));
1386		    break;
1387		  case ieee_region_base_address_enum:
1388		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1389		    section->vma = must_parse_int (&(ieee->h));
1390		    section->lma = section->vma;
1391		    break;
1392		  case ieee_mau_size_enum:
1393		    must_parse_int (&(ieee->h));
1394		    must_parse_int (&(ieee->h));
1395		    break;
1396		  case ieee_m_value_enum:
1397		    must_parse_int (&(ieee->h));
1398		    must_parse_int (&(ieee->h));
1399		    break;
1400		  case ieee_section_base_address_enum:
1401		    section = ieee->section_table[must_parse_int (&(ieee->h))];
1402		    section->vma = must_parse_int (&(ieee->h));
1403		    section->lma = section->vma;
1404		    break;
1405		  case ieee_section_offset_enum:
1406		    (void) must_parse_int (&(ieee->h));
1407		    (void) must_parse_int (&(ieee->h));
1408		    break;
1409		  default:
1410		    return;
1411		  }
1412	      }
1413	      break;
1414	    default:
1415	      return;
1416	    }
1417	}
1418    }
1419}
1420
1421/* Make a section for the debugging information, if any.  We don't try
1422   to interpret the debugging information; we just point the section
1423   at the area in the file so that program which understand can dig it
1424   out.  */
1425
1426static bfd_boolean
1427ieee_slurp_debug (abfd)
1428     bfd *abfd;
1429{
1430  ieee_data_type *ieee = IEEE_DATA (abfd);
1431  asection *sec;
1432  file_ptr debug_end;
1433
1434  if (ieee->w.r.debug_information_part == 0)
1435    return TRUE;
1436
1437  sec = bfd_make_section (abfd, ".debug");
1438  if (sec == NULL)
1439    return FALSE;
1440  sec->flags |= SEC_DEBUGGING | SEC_HAS_CONTENTS;
1441  sec->filepos = ieee->w.r.debug_information_part;
1442
1443  debug_end = ieee_part_after (ieee, ieee->w.r.debug_information_part);
1444  sec->_raw_size = debug_end - ieee->w.r.debug_information_part;
1445
1446  return TRUE;
1447}
1448
1449/* Archive stuff.  */
1450
1451const bfd_target *
1452ieee_archive_p (abfd)
1453     bfd *abfd;
1454{
1455  char *library;
1456  unsigned int i;
1457  unsigned char buffer[512];
1458  file_ptr buffer_offset = 0;
1459  ieee_ar_data_type *save = abfd->tdata.ieee_ar_data;
1460  ieee_ar_data_type *ieee;
1461  bfd_size_type alc_elts;
1462  ieee_ar_obstack_type *elts = NULL;
1463  bfd_size_type amt = sizeof (ieee_ar_data_type);
1464
1465  abfd->tdata.ieee_ar_data = (ieee_ar_data_type *) bfd_alloc (abfd, amt);
1466  if (!abfd->tdata.ieee_ar_data)
1467    goto error_ret_restore;
1468  ieee = IEEE_AR_DATA (abfd);
1469
1470  /* Ignore the return value here.  It doesn't matter if we don't read
1471     the entire buffer.  We might have a very small ieee file.  */
1472  bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1473
1474  ieee->h.first_byte = buffer;
1475  ieee->h.input_p = buffer;
1476
1477  ieee->h.abfd = abfd;
1478
1479  if (this_byte (&(ieee->h)) != Module_Beginning)
1480    goto got_wrong_format_error;
1481
1482  next_byte (&(ieee->h));
1483  library = read_id (&(ieee->h));
1484  if (strcmp (library, "LIBRARY") != 0)
1485    goto got_wrong_format_error;
1486
1487  /* Throw away the filename.  */
1488  read_id (&(ieee->h));
1489
1490  ieee->element_count = 0;
1491  ieee->element_index = 0;
1492
1493  next_byte (&(ieee->h));	/* Drop the ad part.  */
1494  must_parse_int (&(ieee->h));	/* And the two dummy numbers.  */
1495  must_parse_int (&(ieee->h));
1496
1497  alc_elts = 10;
1498  elts = (ieee_ar_obstack_type *) bfd_malloc (alc_elts * sizeof *elts);
1499  if (elts == NULL)
1500    goto error_return;
1501
1502  /* Read the index of the BB table.  */
1503  while (1)
1504    {
1505      int rec;
1506      ieee_ar_obstack_type *t;
1507
1508      rec = read_2bytes (&(ieee->h));
1509      if (rec != (int) ieee_assign_value_to_variable_enum)
1510	break;
1511
1512      if (ieee->element_count >= alc_elts)
1513	{
1514	  ieee_ar_obstack_type *n;
1515
1516	  alc_elts *= 2;
1517	  n = ((ieee_ar_obstack_type *)
1518	       bfd_realloc (elts, alc_elts * sizeof *elts));
1519	  if (n == NULL)
1520	    goto error_return;
1521	  elts = n;
1522	}
1523
1524      t = &elts[ieee->element_count];
1525      ieee->element_count++;
1526
1527      must_parse_int (&(ieee->h));
1528      t->file_offset = must_parse_int (&(ieee->h));
1529      t->abfd = (bfd *) NULL;
1530
1531      /* Make sure that we don't go over the end of the buffer.  */
1532      if ((size_t) ieee_pos (IEEE_DATA (abfd)) > sizeof (buffer) / 2)
1533	{
1534	  /* Past half way, reseek and reprime.  */
1535	  buffer_offset += ieee_pos (IEEE_DATA (abfd));
1536	  if (bfd_seek (abfd, buffer_offset, SEEK_SET) != 0)
1537	    goto error_return;
1538
1539	  /* Again ignore return value of bfd_bread.  */
1540	  bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1541	  ieee->h.first_byte = buffer;
1542	  ieee->h.input_p = buffer;
1543	}
1544    }
1545
1546  amt = ieee->element_count;
1547  amt *= sizeof *ieee->elements;
1548  ieee->elements = (ieee_ar_obstack_type *) bfd_alloc (abfd, amt);
1549  if (ieee->elements == NULL)
1550    goto error_return;
1551
1552  memcpy (ieee->elements, elts, (size_t) amt);
1553  free (elts);
1554  elts = NULL;
1555
1556  /* Now scan the area again, and replace BB offsets with file offsets.  */
1557  for (i = 2; i < ieee->element_count; i++)
1558    {
1559      if (bfd_seek (abfd, ieee->elements[i].file_offset, SEEK_SET) != 0)
1560	goto error_return;
1561
1562      /* Again ignore return value of bfd_bread.  */
1563      bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1564      ieee->h.first_byte = buffer;
1565      ieee->h.input_p = buffer;
1566
1567      next_byte (&(ieee->h));		/* Drop F8.  */
1568      next_byte (&(ieee->h));		/* Drop 14.  */
1569      must_parse_int (&(ieee->h));	/* Drop size of block.  */
1570
1571      if (must_parse_int (&(ieee->h)) != 0)
1572	/* This object has been deleted.  */
1573	ieee->elements[i].file_offset = 0;
1574      else
1575	ieee->elements[i].file_offset = must_parse_int (&(ieee->h));
1576    }
1577
1578  /*  abfd->has_armap = ;*/
1579
1580  return abfd->xvec;
1581
1582 got_wrong_format_error:
1583  bfd_set_error (bfd_error_wrong_format);
1584 error_return:
1585  if (elts != NULL)
1586    free (elts);
1587  bfd_release (abfd, ieee);
1588 error_ret_restore:
1589  abfd->tdata.ieee_ar_data = save;
1590
1591  return NULL;
1592}
1593
1594const bfd_target *
1595ieee_object_p (abfd)
1596     bfd *abfd;
1597{
1598  char *processor;
1599  unsigned int part;
1600  ieee_data_type *ieee;
1601  unsigned char buffer[300];
1602  ieee_data_type *save = IEEE_DATA (abfd);
1603  bfd_size_type amt;
1604
1605  abfd->tdata.ieee_data = 0;
1606  ieee_mkobject (abfd);
1607
1608  ieee = IEEE_DATA (abfd);
1609  if (bfd_seek (abfd, (file_ptr) 0, SEEK_SET) != 0)
1610    goto fail;
1611  /* Read the first few bytes in to see if it makes sense.  Ignore
1612     bfd_bread return value;  The file might be very small.  */
1613  bfd_bread ((PTR) buffer, (bfd_size_type) sizeof (buffer), abfd);
1614
1615  ieee->h.input_p = buffer;
1616  if (this_byte_and_next (&(ieee->h)) != Module_Beginning)
1617    goto got_wrong_format;
1618
1619  ieee->read_symbols = FALSE;
1620  ieee->read_data = FALSE;
1621  ieee->section_count = 0;
1622  ieee->external_symbol_max_index = 0;
1623  ieee->external_symbol_min_index = IEEE_PUBLIC_BASE;
1624  ieee->external_reference_min_index = IEEE_REFERENCE_BASE;
1625  ieee->external_reference_max_index = 0;
1626  ieee->h.abfd = abfd;
1627  ieee->section_table = NULL;
1628  ieee->section_table_size = 0;
1629
1630  processor = ieee->mb.processor = read_id (&(ieee->h));
1631  if (strcmp (processor, "LIBRARY") == 0)
1632    goto got_wrong_format;
1633  ieee->mb.module_name = read_id (&(ieee->h));
1634  if (abfd->filename == (const char *) NULL)
1635    abfd->filename = ieee->mb.module_name;
1636
1637  /* Determine the architecture and machine type of the object file.  */
1638  {
1639    const bfd_arch_info_type *arch;
1640    char family[10];
1641
1642    /* IEEE does not specify the format of the processor identification
1643       string, so the compiler is free to put in it whatever it wants.
1644       We try here to recognize different processors belonging to the
1645       m68k family.  Code for other processors can be added here.  */
1646    if ((processor[0] == '6') && (processor[1] == '8'))
1647      {
1648	if (processor[2] == '3')	    /* 683xx integrated processors */
1649	  {
1650	    switch (processor[3])
1651	      {
1652	      case '0':			    /* 68302, 68306, 68307 */
1653	      case '2':			    /* 68322, 68328 */
1654	      case '5':			    /* 68356 */
1655		strcpy (family, "68000");   /* MC68000-based controllers */
1656		break;
1657
1658	      case '3':			    /* 68330, 68331, 68332, 68333,
1659					       68334, 68335, 68336, 68338 */
1660	      case '6':			    /* 68360 */
1661	      case '7':			    /* 68376 */
1662		strcpy (family, "68332");   /* CPU32 and CPU32+ */
1663		break;
1664
1665	      case '4':
1666		if (processor[4] == '9')    /* 68349 */
1667		  strcpy (family, "68030"); /* CPU030 */
1668		else		            /* 68340, 68341 */
1669		  strcpy (family, "68332"); /* CPU32 and CPU32+ */
1670		break;
1671
1672	      default:			    /* Does not exist yet */
1673		strcpy (family, "68332");   /* Guess it will be CPU32 */
1674	      }
1675	  }
1676	else if (TOUPPER (processor[3]) == 'F')  /* 68F333 */
1677	  strcpy (family, "68332");	           /* CPU32 */
1678	else if ((TOUPPER (processor[3]) == 'C') /* Embedded controllers.  */
1679		 && ((TOUPPER (processor[2]) == 'E')
1680		     || (TOUPPER (processor[2]) == 'H')
1681		     || (TOUPPER (processor[2]) == 'L')))
1682	  {
1683	    strcpy (family, "68");
1684	    strncat (family, processor + 4, 7);
1685	    family[9] = '\0';
1686	  }
1687	else				 /* "Regular" processors.  */
1688	  {
1689	    strncpy (family, processor, 9);
1690	    family[9] = '\0';
1691	  }
1692      }
1693    else if ((strncmp (processor, "cpu32", 5) == 0) /* CPU32 and CPU32+ */
1694	     || (strncmp (processor, "CPU32", 5) == 0))
1695      strcpy (family, "68332");
1696    else
1697      {
1698	strncpy (family, processor, 9);
1699	family[9] = '\0';
1700      }
1701
1702    arch = bfd_scan_arch (family);
1703    if (arch == 0)
1704      goto got_wrong_format;
1705    abfd->arch_info = arch;
1706  }
1707
1708  if (this_byte (&(ieee->h)) != (int) ieee_address_descriptor_enum)
1709    goto fail;
1710
1711  next_byte (&(ieee->h));
1712
1713  if (! parse_int (&(ieee->h), &ieee->ad.number_of_bits_mau))
1714    goto fail;
1715
1716  if (! parse_int (&(ieee->h), &ieee->ad.number_of_maus_in_address))
1717    goto fail;
1718
1719  /* If there is a byte order info, take it.  */
1720  if (this_byte (&(ieee->h)) == (int) ieee_variable_L_enum
1721      || this_byte (&(ieee->h)) == (int) ieee_variable_M_enum)
1722    next_byte (&(ieee->h));
1723
1724  for (part = 0; part < N_W_VARIABLES; part++)
1725    {
1726      bfd_boolean ok;
1727
1728      if (read_2bytes (&(ieee->h)) != (int) ieee_assign_value_to_variable_enum)
1729	goto fail;
1730
1731      if (this_byte_and_next (&(ieee->h)) != part)
1732	goto fail;
1733
1734      ieee->w.offset[part] = parse_i (&(ieee->h), &ok);
1735      if (! ok)
1736	goto fail;
1737    }
1738
1739  if (ieee->w.r.external_part != 0)
1740    abfd->flags = HAS_SYMS;
1741
1742  /* By now we know that this is a real IEEE file, we're going to read
1743     the whole thing into memory so that we can run up and down it
1744     quickly.  We can work out how big the file is from the trailer
1745     record.  */
1746
1747  amt = ieee->w.r.me_record + 1;
1748  IEEE_DATA (abfd)->h.first_byte =
1749    (unsigned char *) bfd_alloc (ieee->h.abfd, amt);
1750  if (!IEEE_DATA (abfd)->h.first_byte)
1751    goto fail;
1752  if (bfd_seek (abfd, (file_ptr) 0, SEEK_SET) != 0)
1753    goto fail;
1754  /* FIXME: Check return value.  I'm not sure whether it needs to read
1755     the entire buffer or not.  */
1756  bfd_bread ((PTR) (IEEE_DATA (abfd)->h.first_byte),
1757	    (bfd_size_type) ieee->w.r.me_record + 1, abfd);
1758
1759  ieee_slurp_sections (abfd);
1760
1761  if (! ieee_slurp_debug (abfd))
1762    goto fail;
1763
1764  /* Parse section data to activate file and section flags implied by
1765     section contents. */
1766  if (! ieee_slurp_section_data (abfd))
1767    goto fail;
1768
1769  return abfd->xvec;
1770got_wrong_format:
1771  bfd_set_error (bfd_error_wrong_format);
1772fail:
1773  bfd_release (abfd, ieee);
1774  abfd->tdata.ieee_data = save;
1775  return (const bfd_target *) NULL;
1776}
1777
1778static void
1779ieee_get_symbol_info (ignore_abfd, symbol, ret)
1780     bfd *ignore_abfd ATTRIBUTE_UNUSED;
1781     asymbol *symbol;
1782     symbol_info *ret;
1783{
1784  bfd_symbol_info (symbol, ret);
1785  if (symbol->name[0] == ' ')
1786    ret->name = "* empty table entry ";
1787  if (!symbol->section)
1788    ret->type = (symbol->flags & BSF_LOCAL) ? 'a' : 'A';
1789}
1790
1791static void
1792ieee_print_symbol (abfd, afile, symbol, how)
1793     bfd *abfd;
1794     PTR afile;
1795     asymbol *symbol;
1796     bfd_print_symbol_type how;
1797{
1798  FILE *file = (FILE *) afile;
1799
1800  switch (how)
1801    {
1802    case bfd_print_symbol_name:
1803      fprintf (file, "%s", symbol->name);
1804      break;
1805    case bfd_print_symbol_more:
1806#if 0
1807      fprintf (file, "%4x %2x", aout_symbol (symbol)->desc & 0xffff,
1808	       aout_symbol (symbol)->other & 0xff);
1809#endif
1810      BFD_FAIL ();
1811      break;
1812    case bfd_print_symbol_all:
1813      {
1814	const char *section_name =
1815	  (symbol->section == (asection *) NULL
1816	   ? "*abs"
1817	   : symbol->section->name);
1818
1819	if (symbol->name[0] == ' ')
1820	  {
1821	    fprintf (file, "* empty table entry ");
1822	  }
1823	else
1824	  {
1825	    bfd_print_symbol_vandf (abfd, (PTR) file, symbol);
1826
1827	    fprintf (file, " %-5s %04x %02x %s",
1828		     section_name,
1829		     (unsigned) ieee_symbol (symbol)->index,
1830		     (unsigned) 0,
1831		     symbol->name);
1832	  }
1833      }
1834      break;
1835    }
1836}
1837
1838static bfd_boolean
1839do_one (ieee, current_map, location_ptr, s, iterations)
1840     ieee_data_type *ieee;
1841     ieee_per_section_type *current_map;
1842     unsigned char *location_ptr;
1843     asection *s;
1844     int iterations;
1845{
1846  switch (this_byte (&(ieee->h)))
1847    {
1848    case ieee_load_constant_bytes_enum:
1849      {
1850	unsigned int number_of_maus;
1851	unsigned int i;
1852
1853	next_byte (&(ieee->h));
1854	number_of_maus = must_parse_int (&(ieee->h));
1855
1856	for (i = 0; i < number_of_maus; i++)
1857	  {
1858	    location_ptr[current_map->pc++] = this_byte (&(ieee->h));
1859	    next_byte (&(ieee->h));
1860	  }
1861      }
1862      break;
1863
1864    case ieee_load_with_relocation_enum:
1865      {
1866	bfd_boolean loop = TRUE;
1867
1868	next_byte (&(ieee->h));
1869	while (loop)
1870	  {
1871	    switch (this_byte (&(ieee->h)))
1872	      {
1873	      case ieee_variable_R_enum:
1874
1875	      case ieee_function_signed_open_b_enum:
1876	      case ieee_function_unsigned_open_b_enum:
1877	      case ieee_function_either_open_b_enum:
1878		{
1879		  unsigned int extra = 4;
1880		  bfd_boolean pcrel = FALSE;
1881		  asection *section;
1882		  ieee_reloc_type *r;
1883		  bfd_size_type amt = sizeof (ieee_reloc_type);
1884
1885		  r = (ieee_reloc_type *) bfd_alloc (ieee->h.abfd, amt);
1886		  if (!r)
1887		    return FALSE;
1888
1889		  *(current_map->reloc_tail_ptr) = r;
1890		  current_map->reloc_tail_ptr = &r->next;
1891		  r->next = (ieee_reloc_type *) NULL;
1892		  next_byte (&(ieee->h));
1893/*			    abort();*/
1894		  r->relent.sym_ptr_ptr = 0;
1895		  parse_expression (ieee,
1896				    &r->relent.addend,
1897				    &r->symbol,
1898				    &pcrel, &extra, &section);
1899		  r->relent.address = current_map->pc;
1900		  s->flags |= SEC_RELOC;
1901		  s->owner->flags |= HAS_RELOC;
1902		  s->reloc_count++;
1903		  if (r->relent.sym_ptr_ptr == NULL && section != NULL)
1904		    r->relent.sym_ptr_ptr = section->symbol_ptr_ptr;
1905
1906		  if (this_byte (&(ieee->h)) == (int) ieee_comma)
1907		    {
1908		      next_byte (&(ieee->h));
1909		      /* Fetch number of bytes to pad.  */
1910		      extra = must_parse_int (&(ieee->h));
1911		    };
1912
1913		  switch (this_byte (&(ieee->h)))
1914		    {
1915		    case ieee_function_signed_close_b_enum:
1916		      next_byte (&(ieee->h));
1917		      break;
1918		    case ieee_function_unsigned_close_b_enum:
1919		      next_byte (&(ieee->h));
1920		      break;
1921		    case ieee_function_either_close_b_enum:
1922		      next_byte (&(ieee->h));
1923		      break;
1924		    default:
1925		      break;
1926		    }
1927		  /* Build a relocation entry for this type.  */
1928		  /* If pc rel then stick -ve pc into instruction
1929		     and take out of reloc ..
1930
1931		     I've changed this. It's all too complicated. I
1932		     keep 0 in the instruction now.  */
1933
1934		  switch (extra)
1935		    {
1936		    case 0:
1937		    case 4:
1938
1939		      if (pcrel)
1940			{
1941#if KEEPMINUSPCININST
1942			  bfd_put_32 (ieee->h.abfd, -current_map->pc,
1943				      location_ptr + current_map->pc);
1944			  r->relent.howto = &rel32_howto;
1945			  r->relent.addend -= current_map->pc;
1946#else
1947			  bfd_put_32 (ieee->h.abfd, (bfd_vma) 0, location_ptr +
1948				      current_map->pc);
1949			  r->relent.howto = &rel32_howto;
1950#endif
1951			}
1952		      else
1953			{
1954			  bfd_put_32 (ieee->h.abfd, (bfd_vma) 0,
1955				      location_ptr + current_map->pc);
1956			  r->relent.howto = &abs32_howto;
1957			}
1958		      current_map->pc += 4;
1959		      break;
1960		    case 2:
1961		      if (pcrel)
1962			{
1963#if KEEPMINUSPCININST
1964			  bfd_put_16 (ieee->h.abfd, (bfd_vma) -current_map->pc,
1965				      location_ptr + current_map->pc);
1966			  r->relent.addend -= current_map->pc;
1967			  r->relent.howto = &rel16_howto;
1968#else
1969
1970			  bfd_put_16 (ieee->h.abfd, (bfd_vma) 0,
1971				      location_ptr + current_map->pc);
1972			  r->relent.howto = &rel16_howto;
1973#endif
1974			}
1975
1976		      else
1977			{
1978			  bfd_put_16 (ieee->h.abfd, (bfd_vma) 0,
1979				      location_ptr + current_map->pc);
1980			  r->relent.howto = &abs16_howto;
1981			}
1982		      current_map->pc += 2;
1983		      break;
1984		    case 1:
1985		      if (pcrel)
1986			{
1987#if KEEPMINUSPCININST
1988			  bfd_put_8 (ieee->h.abfd, (int) (-current_map->pc), location_ptr + current_map->pc);
1989			  r->relent.addend -= current_map->pc;
1990			  r->relent.howto = &rel8_howto;
1991#else
1992			  bfd_put_8 (ieee->h.abfd, 0, location_ptr + current_map->pc);
1993			  r->relent.howto = &rel8_howto;
1994#endif
1995			}
1996		      else
1997			{
1998			  bfd_put_8 (ieee->h.abfd, 0, location_ptr + current_map->pc);
1999			  r->relent.howto = &abs8_howto;
2000			}
2001		      current_map->pc += 1;
2002		      break;
2003
2004		    default:
2005		      BFD_FAIL ();
2006		      return FALSE;
2007		    }
2008		}
2009		break;
2010	      default:
2011		{
2012		  bfd_vma this_size;
2013		  if (parse_int (&(ieee->h), &this_size))
2014		    {
2015		      unsigned int i;
2016		      for (i = 0; i < this_size; i++)
2017			{
2018			  location_ptr[current_map->pc++] = this_byte (&(ieee->h));
2019			  next_byte (&(ieee->h));
2020			}
2021		    }
2022		  else
2023		    {
2024		      loop = FALSE;
2025		    }
2026		}
2027	      }
2028
2029	    /* Prevent more than the first load-item of an LR record
2030	       from being repeated (MRI convention). */
2031	    if (iterations != 1)
2032	      loop = FALSE;
2033	  }
2034      }
2035    }
2036  return TRUE;
2037}
2038
2039/* Read in all the section data and relocation stuff too.  */
2040
2041static bfd_boolean
2042ieee_slurp_section_data (abfd)
2043     bfd *abfd;
2044{
2045  bfd_byte *location_ptr = (bfd_byte *) NULL;
2046  ieee_data_type *ieee = IEEE_DATA (abfd);
2047  unsigned int section_number;
2048
2049  ieee_per_section_type *current_map = (ieee_per_section_type *) NULL;
2050  asection *s;
2051  /* Seek to the start of the data area.  */
2052  if (ieee->read_data)
2053    return TRUE;
2054  ieee->read_data = TRUE;
2055  ieee_seek (ieee, ieee->w.r.data_part);
2056
2057  /* Allocate enough space for all the section contents.  */
2058  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
2059    {
2060      ieee_per_section_type *per = ieee_per_section (s);
2061      if ((s->flags & SEC_DEBUGGING) != 0)
2062	continue;
2063      per->data = (bfd_byte *) bfd_alloc (ieee->h.abfd, s->_raw_size);
2064      if (!per->data)
2065	return FALSE;
2066      per->reloc_tail_ptr =
2067	(ieee_reloc_type **) & (s->relocation);
2068    }
2069
2070  while (TRUE)
2071    {
2072      switch (this_byte (&(ieee->h)))
2073	{
2074	  /* IF we see anything strange then quit.  */
2075	default:
2076	  return TRUE;
2077
2078	case ieee_set_current_section_enum:
2079	  next_byte (&(ieee->h));
2080	  section_number = must_parse_int (&(ieee->h));
2081	  s = ieee->section_table[section_number];
2082	  s->flags |= SEC_LOAD | SEC_HAS_CONTENTS;
2083	  current_map = ieee_per_section (s);
2084	  location_ptr = current_map->data - s->vma;
2085	  /* The document I have says that Microtec's compilers reset
2086	     this after a sec section, even though the standard says not
2087	     to, SO...  */
2088	  current_map->pc = s->vma;
2089	  break;
2090
2091	case ieee_e2_first_byte_enum:
2092	  next_byte (&(ieee->h));
2093	  switch (this_byte (&(ieee->h)))
2094	    {
2095	    case ieee_set_current_pc_enum & 0xff:
2096	      {
2097		bfd_vma value;
2098		ieee_symbol_index_type symbol;
2099		unsigned int extra;
2100		bfd_boolean pcrel;
2101
2102		next_byte (&(ieee->h));
2103		must_parse_int (&(ieee->h));	/* Throw away section #.  */
2104		parse_expression (ieee, &value,
2105				  &symbol,
2106				  &pcrel, &extra,
2107				  0);
2108		current_map->pc = value;
2109		BFD_ASSERT ((unsigned) (value - s->vma) <= s->_raw_size);
2110	      }
2111	      break;
2112
2113	    case ieee_value_starting_address_enum & 0xff:
2114	      next_byte (&(ieee->h));
2115	      if (this_byte (&(ieee->h)) == ieee_function_either_open_b_enum)
2116		next_byte (&(ieee->h));
2117	      abfd->start_address = must_parse_int (&(ieee->h));
2118	      /* We've got to the end of the data now -  */
2119	      return TRUE;
2120	    default:
2121	      BFD_FAIL ();
2122	      return FALSE;
2123	    }
2124	  break;
2125	case ieee_repeat_data_enum:
2126	  {
2127	    /* Repeat the following LD or LR n times - we do this by
2128	       remembering the stream pointer before running it and
2129	       resetting it and running it n times. We special case
2130	       the repetition of a repeat_data/load_constant.  */
2131	    unsigned int iterations;
2132	    unsigned char *start;
2133
2134	    next_byte (&(ieee->h));
2135	    iterations = must_parse_int (&(ieee->h));
2136	    start = ieee->h.input_p;
2137	    if (start[0] == (int) ieee_load_constant_bytes_enum
2138		&& start[1] == 1)
2139	      {
2140		while (iterations != 0)
2141		  {
2142		    location_ptr[current_map->pc++] = start[2];
2143		    iterations--;
2144		  }
2145		next_byte (&(ieee->h));
2146		next_byte (&(ieee->h));
2147		next_byte (&(ieee->h));
2148	      }
2149	    else
2150	      {
2151		while (iterations != 0)
2152		  {
2153		    ieee->h.input_p = start;
2154		    if (!do_one (ieee, current_map, location_ptr, s,
2155				 (int) iterations))
2156		      return FALSE;
2157		    iterations--;
2158		  }
2159	      }
2160	  }
2161	  break;
2162	case ieee_load_constant_bytes_enum:
2163	case ieee_load_with_relocation_enum:
2164	  if (!do_one (ieee, current_map, location_ptr, s, 1))
2165	    return FALSE;
2166	}
2167    }
2168}
2169
2170static bfd_boolean
2171ieee_new_section_hook (abfd, newsect)
2172     bfd *abfd;
2173     asection *newsect;
2174{
2175  newsect->used_by_bfd
2176    = (PTR) bfd_alloc (abfd, (bfd_size_type) sizeof (ieee_per_section_type));
2177  if (!newsect->used_by_bfd)
2178    return FALSE;
2179  ieee_per_section (newsect)->data = (bfd_byte *) NULL;
2180  ieee_per_section (newsect)->section = newsect;
2181  return TRUE;
2182}
2183
2184static long
2185ieee_get_reloc_upper_bound (abfd, asect)
2186     bfd *abfd;
2187     sec_ptr asect;
2188{
2189  if ((asect->flags & SEC_DEBUGGING) != 0)
2190    return 0;
2191  if (! ieee_slurp_section_data (abfd))
2192    return -1;
2193  return (asect->reloc_count + 1) * sizeof (arelent *);
2194}
2195
2196static bfd_boolean
2197ieee_get_section_contents (abfd, section, location, offset, count)
2198     bfd *abfd;
2199     sec_ptr section;
2200     PTR location;
2201     file_ptr offset;
2202     bfd_size_type count;
2203{
2204  ieee_per_section_type *p = ieee_per_section (section);
2205  if ((section->flags & SEC_DEBUGGING) != 0)
2206    return _bfd_generic_get_section_contents (abfd, section, location,
2207					      offset, count);
2208  ieee_slurp_section_data (abfd);
2209  (void) memcpy ((PTR) location, (PTR) (p->data + offset), (unsigned) count);
2210  return TRUE;
2211}
2212
2213static long
2214ieee_canonicalize_reloc (abfd, section, relptr, symbols)
2215     bfd *abfd;
2216     sec_ptr section;
2217     arelent **relptr;
2218     asymbol **symbols;
2219{
2220  ieee_reloc_type *src = (ieee_reloc_type *) (section->relocation);
2221  ieee_data_type *ieee = IEEE_DATA (abfd);
2222
2223  if ((section->flags & SEC_DEBUGGING) != 0)
2224    return 0;
2225
2226  while (src != (ieee_reloc_type *) NULL)
2227    {
2228      /* Work out which symbol to attach it this reloc to.  */
2229      switch (src->symbol.letter)
2230	{
2231	case 'I':
2232	  src->relent.sym_ptr_ptr =
2233	    symbols + src->symbol.index + ieee->external_symbol_base_offset;
2234	  break;
2235	case 'X':
2236	  src->relent.sym_ptr_ptr =
2237	    symbols + src->symbol.index + ieee->external_reference_base_offset;
2238	  break;
2239	case 0:
2240	  if (src->relent.sym_ptr_ptr != NULL)
2241	    src->relent.sym_ptr_ptr =
2242	      src->relent.sym_ptr_ptr[0]->section->symbol_ptr_ptr;
2243	  break;
2244	default:
2245
2246	  BFD_FAIL ();
2247	}
2248      *relptr++ = &src->relent;
2249      src = src->next;
2250    }
2251  *relptr = (arelent *) NULL;
2252  return section->reloc_count;
2253}
2254
2255static int
2256comp (ap, bp)
2257     const PTR ap;
2258     const PTR bp;
2259{
2260  arelent *a = *((arelent **) ap);
2261  arelent *b = *((arelent **) bp);
2262  return a->address - b->address;
2263}
2264
2265/* Write the section headers.  */
2266
2267static bfd_boolean
2268ieee_write_section_part (abfd)
2269     bfd *abfd;
2270{
2271  ieee_data_type *ieee = IEEE_DATA (abfd);
2272  asection *s;
2273  ieee->w.r.section_part = bfd_tell (abfd);
2274  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
2275    {
2276      if (! bfd_is_abs_section (s)
2277	  && (s->flags & SEC_DEBUGGING) == 0)
2278	{
2279	  if (! ieee_write_byte (abfd, ieee_section_type_enum)
2280	      || ! ieee_write_byte (abfd,
2281				    (bfd_byte) (s->index
2282						+ IEEE_SECTION_NUMBER_BASE)))
2283	    return FALSE;
2284
2285	  if (abfd->flags & EXEC_P)
2286	    {
2287	      /* This image is executable, so output absolute sections.  */
2288	      if (! ieee_write_byte (abfd, ieee_variable_A_enum)
2289		  || ! ieee_write_byte (abfd, ieee_variable_S_enum))
2290		return FALSE;
2291	    }
2292	  else
2293	    {
2294	      if (! ieee_write_byte (abfd, ieee_variable_C_enum))
2295		return FALSE;
2296	    }
2297
2298	  switch (s->flags & (SEC_CODE | SEC_DATA | SEC_ROM))
2299	    {
2300	    case SEC_CODE | SEC_LOAD:
2301	    case SEC_CODE:
2302	      if (! ieee_write_byte (abfd, ieee_variable_P_enum))
2303		return FALSE;
2304	      break;
2305	    case SEC_DATA:
2306	    default:
2307	      if (! ieee_write_byte (abfd, ieee_variable_D_enum))
2308		return FALSE;
2309	      break;
2310	    case SEC_ROM:
2311	    case SEC_ROM | SEC_DATA:
2312	    case SEC_ROM | SEC_LOAD:
2313	    case SEC_ROM | SEC_DATA | SEC_LOAD:
2314	      if (! ieee_write_byte (abfd, ieee_variable_R_enum))
2315		return FALSE;
2316	    }
2317
2318
2319	  if (! ieee_write_id (abfd, s->name))
2320	    return FALSE;
2321#if 0
2322	  ieee_write_int (abfd, 0);	/* Parent */
2323	  ieee_write_int (abfd, 0);	/* Brother */
2324	  ieee_write_int (abfd, 0);	/* Context */
2325#endif
2326	  /* Alignment.  */
2327	  if (! ieee_write_byte (abfd, ieee_section_alignment_enum)
2328	      || ! ieee_write_byte (abfd,
2329				    (bfd_byte) (s->index
2330						+ IEEE_SECTION_NUMBER_BASE))
2331	      || ! ieee_write_int (abfd, (bfd_vma) 1 << s->alignment_power))
2332	    return FALSE;
2333
2334	  /* Size.  */
2335	  if (! ieee_write_2bytes (abfd, ieee_section_size_enum)
2336	      || ! ieee_write_byte (abfd,
2337				    (bfd_byte) (s->index
2338						+ IEEE_SECTION_NUMBER_BASE))
2339	      || ! ieee_write_int (abfd, s->_raw_size))
2340	    return FALSE;
2341	  if (abfd->flags & EXEC_P)
2342	    {
2343	      /* Relocateable sections don't have asl records.  */
2344	      /* Vma.  */
2345	      if (! ieee_write_2bytes (abfd, ieee_section_base_address_enum)
2346		  || ! ieee_write_byte (abfd,
2347					((bfd_byte)
2348					 (s->index
2349					  + IEEE_SECTION_NUMBER_BASE)))
2350		  || ! ieee_write_int (abfd, s->lma))
2351		return FALSE;
2352	    }
2353	}
2354    }
2355
2356  return TRUE;
2357}
2358
2359
2360static bfd_boolean
2361do_with_relocs (abfd, s)
2362     bfd *abfd;
2363     asection *s;
2364{
2365  unsigned int number_of_maus_in_address =
2366    bfd_arch_bits_per_address (abfd) / bfd_arch_bits_per_byte (abfd);
2367  unsigned int relocs_to_go = s->reloc_count;
2368  bfd_byte *stream = ieee_per_section (s)->data;
2369  arelent **p = s->orelocation;
2370  bfd_size_type current_byte_index = 0;
2371
2372  qsort (s->orelocation,
2373	 relocs_to_go,
2374	 sizeof (arelent **),
2375	 comp);
2376
2377  /* Output the section preheader.  */
2378  if (! ieee_write_byte (abfd, ieee_set_current_section_enum)
2379      || ! ieee_write_byte (abfd,
2380			    (bfd_byte) (s->index + IEEE_SECTION_NUMBER_BASE))
2381      || ! ieee_write_2bytes (abfd, ieee_set_current_pc_enum)
2382      || ! ieee_write_byte (abfd,
2383			    (bfd_byte) (s->index + IEEE_SECTION_NUMBER_BASE)))
2384    return FALSE;
2385
2386  if ((abfd->flags & EXEC_P) != 0 && relocs_to_go == 0)
2387    {
2388      if (! ieee_write_int (abfd, s->lma))
2389	return FALSE;
2390    }
2391  else
2392    {
2393      if (! ieee_write_expression (abfd, (bfd_vma) 0, s->symbol, 0, 0))
2394	return FALSE;
2395    }
2396
2397  if (relocs_to_go == 0)
2398    {
2399      /* If there aren't any relocations then output the load constant
2400	 byte opcode rather than the load with relocation opcode.  */
2401      while (current_byte_index < s->_raw_size)
2402	{
2403	  bfd_size_type run;
2404	  unsigned int MAXRUN = 127;
2405
2406	  run = MAXRUN;
2407	  if (run > s->_raw_size - current_byte_index)
2408	    run = s->_raw_size - current_byte_index;
2409
2410	  if (run != 0)
2411	    {
2412	      if (! ieee_write_byte (abfd, ieee_load_constant_bytes_enum))
2413		return FALSE;
2414	      /* Output a stream of bytes.  */
2415	      if (! ieee_write_int (abfd, run))
2416		return FALSE;
2417	      if (bfd_bwrite ((PTR) (stream + current_byte_index), run, abfd)
2418		  != run)
2419		return FALSE;
2420	      current_byte_index += run;
2421	    }
2422	}
2423    }
2424  else
2425    {
2426      if (! ieee_write_byte (abfd, ieee_load_with_relocation_enum))
2427	return FALSE;
2428
2429      /* Output the data stream as the longest sequence of bytes
2430	 possible, allowing for the a reasonable packet size and
2431	 relocation stuffs.  */
2432
2433      if ((PTR) stream == (PTR) NULL)
2434	{
2435	  /* Outputting a section without data, fill it up.  */
2436	  stream = (unsigned char *) bfd_zalloc (abfd, s->_raw_size);
2437	  if (!stream)
2438	    return FALSE;
2439	}
2440      while (current_byte_index < s->_raw_size)
2441	{
2442	  bfd_size_type run;
2443	  unsigned int MAXRUN = 127;
2444
2445	  if (relocs_to_go)
2446	    {
2447	      run = (*p)->address - current_byte_index;
2448	      if (run > MAXRUN)
2449		run = MAXRUN;
2450	    }
2451	  else
2452	    run = MAXRUN;
2453
2454	  if (run > s->_raw_size - current_byte_index)
2455	    run = s->_raw_size - current_byte_index;
2456
2457	  if (run != 0)
2458	    {
2459	      /* Output a stream of bytes.  */
2460	      if (! ieee_write_int (abfd, run))
2461		return FALSE;
2462	      if (bfd_bwrite ((PTR) (stream + current_byte_index), run, abfd)
2463		  != run)
2464		return FALSE;
2465	      current_byte_index += run;
2466	    }
2467
2468	  /* Output any relocations here.  */
2469	  if (relocs_to_go && (*p) && (*p)->address == current_byte_index)
2470	    {
2471	      while (relocs_to_go
2472		     && (*p) && (*p)->address == current_byte_index)
2473		{
2474		  arelent *r = *p;
2475		  bfd_signed_vma ov;
2476#if 0
2477		  if (r->howto->pc_relative)
2478		    r->addend += current_byte_index;
2479#endif
2480		  switch (r->howto->size)
2481		    {
2482		    case 2:
2483
2484		      ov = bfd_get_signed_32 (abfd,
2485					      stream + current_byte_index);
2486		      current_byte_index += 4;
2487		      break;
2488		    case 1:
2489		      ov = bfd_get_signed_16 (abfd,
2490					      stream + current_byte_index);
2491		      current_byte_index += 2;
2492		      break;
2493		    case 0:
2494		      ov = bfd_get_signed_8 (abfd,
2495					     stream + current_byte_index);
2496		      current_byte_index++;
2497		      break;
2498		    default:
2499		      ov = 0;
2500		      BFD_FAIL ();
2501		      return FALSE;
2502		    }
2503
2504		  ov &= r->howto->src_mask;
2505
2506		  if (r->howto->pc_relative
2507		      && ! r->howto->pcrel_offset)
2508		    ov += r->address;
2509
2510		  if (! ieee_write_byte (abfd,
2511					 ieee_function_either_open_b_enum))
2512		    return FALSE;
2513
2514/*		  abort();*/
2515
2516		  if (r->sym_ptr_ptr != (asymbol **) NULL)
2517		    {
2518		      if (! ieee_write_expression (abfd, r->addend + ov,
2519						   *(r->sym_ptr_ptr),
2520						   r->howto->pc_relative,
2521						   (unsigned) s->index))
2522			return FALSE;
2523		    }
2524		  else
2525		    {
2526		      if (! ieee_write_expression (abfd, r->addend + ov,
2527						   (asymbol *) NULL,
2528						   r->howto->pc_relative,
2529						   (unsigned) s->index))
2530			return FALSE;
2531		    }
2532
2533		  if (number_of_maus_in_address
2534		      != bfd_get_reloc_size (r->howto))
2535		    {
2536		      bfd_vma rsize = bfd_get_reloc_size (r->howto);
2537		      if (! ieee_write_int (abfd, rsize))
2538			return FALSE;
2539		    }
2540		  if (! ieee_write_byte (abfd,
2541					 ieee_function_either_close_b_enum))
2542		    return FALSE;
2543
2544		  relocs_to_go--;
2545		  p++;
2546		}
2547
2548	    }
2549	}
2550    }
2551
2552  return TRUE;
2553}
2554
2555/* If there are no relocations in the output section then we can be
2556   clever about how we write.  We block items up into a max of 127
2557   bytes.  */
2558
2559static bfd_boolean
2560do_as_repeat (abfd, s)
2561     bfd *abfd;
2562     asection *s;
2563{
2564  if (s->_raw_size)
2565    {
2566      if (! ieee_write_byte (abfd, ieee_set_current_section_enum)
2567	  || ! ieee_write_byte (abfd,
2568				(bfd_byte) (s->index
2569					    + IEEE_SECTION_NUMBER_BASE))
2570	  || ! ieee_write_byte (abfd, ieee_set_current_pc_enum >> 8)
2571	  || ! ieee_write_byte (abfd, ieee_set_current_pc_enum & 0xff)
2572	  || ! ieee_write_byte (abfd,
2573				(bfd_byte) (s->index
2574					    + IEEE_SECTION_NUMBER_BASE)))
2575	return FALSE;
2576
2577      if ((abfd->flags & EXEC_P) != 0)
2578	{
2579	  if (! ieee_write_int (abfd, s->lma))
2580	    return FALSE;
2581	}
2582      else
2583	{
2584	  if (! ieee_write_expression (abfd, (bfd_vma) 0, s->symbol, 0, 0))
2585	    return FALSE;
2586	}
2587
2588      if (! ieee_write_byte (abfd, ieee_repeat_data_enum)
2589	  || ! ieee_write_int (abfd, s->_raw_size)
2590	  || ! ieee_write_byte (abfd, ieee_load_constant_bytes_enum)
2591	  || ! ieee_write_byte (abfd, 1)
2592	  || ! ieee_write_byte (abfd, 0))
2593	return FALSE;
2594    }
2595
2596  return TRUE;
2597}
2598
2599static bfd_boolean
2600do_without_relocs (abfd, s)
2601     bfd *abfd;
2602     asection *s;
2603{
2604  bfd_byte *stream = ieee_per_section (s)->data;
2605
2606  if (stream == 0 || ((s->flags & SEC_LOAD) == 0))
2607    {
2608      if (! do_as_repeat (abfd, s))
2609	return FALSE;
2610    }
2611  else
2612    {
2613      unsigned int i;
2614
2615      for (i = 0; i < s->_raw_size; i++)
2616	{
2617	  if (stream[i] != 0)
2618	    {
2619	      if (! do_with_relocs (abfd, s))
2620		return FALSE;
2621	      return TRUE;
2622	    }
2623	}
2624      if (! do_as_repeat (abfd, s))
2625	return FALSE;
2626    }
2627
2628  return TRUE;
2629}
2630
2631
2632static unsigned char *output_ptr_start;
2633static unsigned char *output_ptr;
2634static unsigned char *output_ptr_end;
2635static unsigned char *input_ptr_start;
2636static unsigned char *input_ptr;
2637static unsigned char *input_ptr_end;
2638static bfd *input_bfd;
2639static bfd *output_bfd;
2640static int output_buffer;
2641
2642static bfd_boolean
2643ieee_mkobject (abfd)
2644     bfd *abfd;
2645{
2646  bfd_size_type amt;
2647
2648  output_ptr_start = NULL;
2649  output_ptr = NULL;
2650  output_ptr_end = NULL;
2651  input_ptr_start = NULL;
2652  input_ptr = NULL;
2653  input_ptr_end = NULL;
2654  input_bfd = NULL;
2655  output_bfd = NULL;
2656  output_buffer = 0;
2657  amt = sizeof (ieee_data_type);
2658  abfd->tdata.ieee_data = (ieee_data_type *) bfd_zalloc (abfd, amt);
2659  return abfd->tdata.ieee_data != NULL;
2660}
2661
2662static void
2663fill ()
2664{
2665  bfd_size_type amt = input_ptr_end - input_ptr_start;
2666  /* FIXME: Check return value.  I'm not sure whether it needs to read
2667     the entire buffer or not.  */
2668  bfd_bread ((PTR) input_ptr_start, amt, input_bfd);
2669  input_ptr = input_ptr_start;
2670}
2671
2672static void
2673flush ()
2674{
2675  bfd_size_type amt = output_ptr - output_ptr_start;
2676
2677  if (bfd_bwrite ((PTR) (output_ptr_start), amt, output_bfd) != amt)
2678    abort ();
2679  output_ptr = output_ptr_start;
2680  output_buffer++;
2681}
2682
2683#define THIS() ( *input_ptr )
2684#define NEXT() { input_ptr++; if (input_ptr == input_ptr_end) fill(); }
2685#define OUT(x) { *output_ptr++ = (x); if(output_ptr == output_ptr_end)  flush(); }
2686
2687static void
2688write_int (value)
2689     int value;
2690{
2691  if (value >= 0 && value <= 127)
2692    {
2693      OUT (value);
2694    }
2695  else
2696    {
2697      unsigned int length;
2698      /* How many significant bytes ?  */
2699      /* FIXME FOR LONGER INTS.  */
2700      if (value & 0xff000000)
2701	length = 4;
2702      else if (value & 0x00ff0000)
2703	length = 3;
2704      else if (value & 0x0000ff00)
2705	length = 2;
2706      else
2707	length = 1;
2708
2709      OUT ((int) ieee_number_repeat_start_enum + length);
2710      switch (length)
2711	{
2712	case 4:
2713	  OUT (value >> 24);
2714	case 3:
2715	  OUT (value >> 16);
2716	case 2:
2717	  OUT (value >> 8);
2718	case 1:
2719	  OUT (value);
2720	}
2721    }
2722}
2723
2724static void
2725copy_id ()
2726{
2727  int length = THIS ();
2728  char ch;
2729
2730  OUT (length);
2731  NEXT ();
2732  while (length--)
2733    {
2734      ch = THIS ();
2735      OUT (ch);
2736      NEXT ();
2737    }
2738}
2739
2740#define VAR(x) ((x | 0x80))
2741static void
2742copy_expression ()
2743{
2744  int stack[10];
2745  int *tos = stack;
2746  int value;
2747
2748  while (1)
2749    {
2750      switch (THIS ())
2751	{
2752	case 0x84:
2753	  NEXT ();
2754	  value = THIS ();
2755	  NEXT ();
2756	  value = (value << 8) | THIS ();
2757	  NEXT ();
2758	  value = (value << 8) | THIS ();
2759	  NEXT ();
2760	  value = (value << 8) | THIS ();
2761	  NEXT ();
2762	  *tos++ = value;
2763	  break;
2764	case 0x83:
2765	  NEXT ();
2766	  value = THIS ();
2767	  NEXT ();
2768	  value = (value << 8) | THIS ();
2769	  NEXT ();
2770	  value = (value << 8) | THIS ();
2771	  NEXT ();
2772	  *tos++ = value;
2773	  break;
2774	case 0x82:
2775	  NEXT ();
2776	  value = THIS ();
2777	  NEXT ();
2778	  value = (value << 8) | THIS ();
2779	  NEXT ();
2780	  *tos++ = value;
2781	  break;
2782	case 0x81:
2783	  NEXT ();
2784	  value = THIS ();
2785	  NEXT ();
2786	  *tos++ = value;
2787	  break;
2788	case 0x80:
2789	  NEXT ();
2790	  *tos++ = 0;
2791	  break;
2792	default:
2793	  if (THIS () > 0x84)
2794	    {
2795	      /* Not a number, just bug out with the answer.  */
2796	      write_int (*(--tos));
2797	      return;
2798	    }
2799	  *tos++ = THIS ();
2800	  NEXT ();
2801	  break;
2802	case 0xa5:
2803	  /* PLUS anything.  */
2804	  value = *(--tos);
2805	  value += *(--tos);
2806	  *tos++ = value;
2807	  NEXT ();
2808	  break;
2809	case VAR ('R'):
2810	  {
2811	    int section_number;
2812	    ieee_data_type *ieee;
2813	    asection *s;
2814
2815	    NEXT ();
2816	    section_number = THIS ();
2817
2818	    NEXT ();
2819	    ieee = IEEE_DATA (input_bfd);
2820	    s = ieee->section_table[section_number];
2821	    value = 0;
2822	    if (s->output_section)
2823	      value = s->output_section->lma;
2824	    value += s->output_offset;
2825	    *tos++ = value;
2826	  }
2827	  break;
2828	case 0x90:
2829	  {
2830	    NEXT ();
2831	    write_int (*(--tos));
2832	    OUT (0x90);
2833	    return;
2834	  }
2835	}
2836    }
2837}
2838
2839/* Drop the int in the buffer, and copy a null into the gap, which we
2840   will overwrite later */
2841
2842static void
2843fill_int (buf)
2844     struct output_buffer_struct *buf;
2845{
2846  if (buf->buffer == output_buffer)
2847    {
2848      /* Still a chance to output the size.  */
2849      int value = output_ptr - buf->ptrp + 3;
2850      buf->ptrp[0] = value >> 24;
2851      buf->ptrp[1] = value >> 16;
2852      buf->ptrp[2] = value >> 8;
2853      buf->ptrp[3] = value >> 0;
2854    }
2855}
2856
2857static void
2858drop_int (buf)
2859     struct output_buffer_struct *buf;
2860{
2861  int type = THIS ();
2862  int ch;
2863
2864  if (type <= 0x84)
2865    {
2866      NEXT ();
2867      switch (type)
2868	{
2869	case 0x84:
2870	  ch = THIS ();
2871	  NEXT ();
2872	case 0x83:
2873	  ch = THIS ();
2874	  NEXT ();
2875	case 0x82:
2876	  ch = THIS ();
2877	  NEXT ();
2878	case 0x81:
2879	  ch = THIS ();
2880	  NEXT ();
2881	case 0x80:
2882	  break;
2883	}
2884    }
2885  OUT (0x84);
2886  buf->ptrp = output_ptr;
2887  buf->buffer = output_buffer;
2888  OUT (0);
2889  OUT (0);
2890  OUT (0);
2891  OUT (0);
2892}
2893
2894static void
2895copy_int ()
2896{
2897  int type = THIS ();
2898  int ch;
2899  if (type <= 0x84)
2900    {
2901      OUT (type);
2902      NEXT ();
2903      switch (type)
2904	{
2905	case 0x84:
2906	  ch = THIS ();
2907	  NEXT ();
2908	  OUT (ch);
2909	case 0x83:
2910	  ch = THIS ();
2911	  NEXT ();
2912	  OUT (ch);
2913	case 0x82:
2914	  ch = THIS ();
2915	  NEXT ();
2916	  OUT (ch);
2917	case 0x81:
2918	  ch = THIS ();
2919	  NEXT ();
2920	  OUT (ch);
2921	case 0x80:
2922	  break;
2923	}
2924    }
2925}
2926
2927#define ID copy_id()
2928#define INT copy_int()
2929#define EXP copy_expression()
2930#define INTn(q) copy_int()
2931#define EXPn(q) copy_expression()
2932
2933static void
2934f1_record ()
2935{
2936  int ch;
2937
2938  /* ATN record.  */
2939  NEXT ();
2940  ch = THIS ();
2941  switch (ch)
2942    {
2943    default:
2944      OUT (0xf1);
2945      OUT (ch);
2946      break;
2947    case 0xc9:
2948      NEXT ();
2949      OUT (0xf1);
2950      OUT (0xc9);
2951      INT;
2952      INT;
2953      ch = THIS ();
2954      switch (ch)
2955	{
2956	case 0x16:
2957	  NEXT ();
2958	  break;
2959	case 0x01:
2960	  NEXT ();
2961	  break;
2962	case 0x00:
2963	  NEXT ();
2964	  INT;
2965	  break;
2966	case 0x03:
2967	  NEXT ();
2968	  INT;
2969	  break;
2970	case 0x13:
2971	  EXPn (instruction address);
2972	  break;
2973	default:
2974	  break;
2975	}
2976      break;
2977    case 0xd8:
2978      /* EXternal ref.  */
2979      NEXT ();
2980      OUT (0xf1);
2981      OUT (0xd8);
2982      EXP;
2983      EXP;
2984      EXP;
2985      EXP;
2986      break;
2987    case 0xce:
2988      NEXT ();
2989      OUT (0xf1);
2990      OUT (0xce);
2991      INT;
2992      INT;
2993      ch = THIS ();
2994      INT;
2995      switch (ch)
2996	{
2997	case 0x01:
2998	  INT;
2999	  INT;
3000	  break;
3001	case 0x02:
3002	  INT;
3003	  break;
3004	case 0x04:
3005	  EXPn (external function);
3006	  break;
3007	case 0x05:
3008	  break;
3009	case 0x07:
3010	  INTn (line number);
3011	  INT;
3012	case 0x08:
3013	  break;
3014	case 0x0a:
3015	  INTn (locked register);
3016	  INT;
3017	  break;
3018	case 0x3f:
3019	  copy_till_end ();
3020	  break;
3021	case 0x3e:
3022	  copy_till_end ();
3023	  break;
3024	case 0x40:
3025	  copy_till_end ();
3026	  break;
3027	case 0x41:
3028	  ID;
3029	  break;
3030	}
3031    }
3032}
3033
3034static void
3035f0_record ()
3036{
3037  /* Attribute record.  */
3038  NEXT ();
3039  OUT (0xf0);
3040  INTn (Symbol name);
3041  ID;
3042}
3043
3044static void
3045copy_till_end ()
3046{
3047  int ch = THIS ();
3048
3049  while (1)
3050    {
3051      while (ch <= 0x80)
3052	{
3053	  OUT (ch);
3054	  NEXT ();
3055	  ch = THIS ();
3056	}
3057      switch (ch)
3058	{
3059	case 0x84:
3060	  OUT (THIS ());
3061	  NEXT ();
3062	case 0x83:
3063	  OUT (THIS ());
3064	  NEXT ();
3065	case 0x82:
3066	  OUT (THIS ());
3067	  NEXT ();
3068	case 0x81:
3069	  OUT (THIS ());
3070	  NEXT ();
3071	  OUT (THIS ());
3072	  NEXT ();
3073
3074	  ch = THIS ();
3075	  break;
3076	default:
3077	  return;
3078	}
3079    }
3080
3081}
3082
3083static void
3084f2_record ()
3085{
3086  NEXT ();
3087  OUT (0xf2);
3088  INT;
3089  NEXT ();
3090  OUT (0xce);
3091  INT;
3092  copy_till_end ();
3093}
3094
3095
3096static void
3097f8_record ()
3098{
3099  int ch;
3100  NEXT ();
3101  ch = THIS ();
3102  switch (ch)
3103    {
3104    case 0x01:
3105    case 0x02:
3106    case 0x03:
3107      /* Unique typedefs for module.  */
3108      /* GLobal typedefs.   */
3109      /* High level module scope beginning.  */
3110      {
3111	struct output_buffer_struct ob;
3112
3113	NEXT ();
3114	OUT (0xf8);
3115	OUT (ch);
3116	drop_int (&ob);
3117	ID;
3118
3119	block ();
3120
3121	NEXT ();
3122	fill_int (&ob);
3123	OUT (0xf9);
3124      }
3125      break;
3126    case 0x04:
3127      /* Global function.  */
3128      {
3129	struct output_buffer_struct ob;
3130
3131	NEXT ();
3132	OUT (0xf8);
3133	OUT (0x04);
3134	drop_int (&ob);
3135	ID;
3136	INTn (stack size);
3137	INTn (ret val);
3138	EXPn (offset);
3139
3140	block ();
3141
3142	NEXT ();
3143	OUT (0xf9);
3144	EXPn (size of block);
3145	fill_int (&ob);
3146      }
3147      break;
3148
3149    case 0x05:
3150      /* File name for source line numbers.  */
3151      {
3152	struct output_buffer_struct ob;
3153
3154	NEXT ();
3155	OUT (0xf8);
3156	OUT (0x05);
3157	drop_int (&ob);
3158	ID;
3159	INTn (year);
3160	INTn (month);
3161	INTn (day);
3162	INTn (hour);
3163	INTn (monute);
3164	INTn (second);
3165	block ();
3166	NEXT ();
3167	OUT (0xf9);
3168	fill_int (&ob);
3169      }
3170      break;
3171
3172    case 0x06:
3173      /* Local function.  */
3174      {
3175	struct output_buffer_struct ob;
3176
3177	NEXT ();
3178	OUT (0xf8);
3179	OUT (0x06);
3180	drop_int (&ob);
3181	ID;
3182	INTn (stack size);
3183	INTn (type return);
3184	EXPn (offset);
3185	block ();
3186	NEXT ();
3187	OUT (0xf9);
3188	EXPn (size);
3189	fill_int (&ob);
3190      }
3191      break;
3192
3193    case 0x0a:
3194      /* Assembler module scope beginning -  */
3195      {
3196	struct output_buffer_struct ob;
3197
3198	NEXT ();
3199	OUT (0xf8);
3200	OUT (0x0a);
3201	drop_int (&ob);
3202	ID;
3203	ID;
3204	INT;
3205	ID;
3206	INT;
3207	INT;
3208	INT;
3209	INT;
3210	INT;
3211	INT;
3212
3213	block ();
3214
3215	NEXT ();
3216	OUT (0xf9);
3217	fill_int (&ob);
3218      }
3219      break;
3220    case 0x0b:
3221      {
3222	struct output_buffer_struct ob;
3223
3224	NEXT ();
3225	OUT (0xf8);
3226	OUT (0x0b);
3227	drop_int (&ob);
3228	ID;
3229	INT;
3230	INTn (section index);
3231	EXPn (offset);
3232	INTn (stuff);
3233
3234	block ();
3235
3236	OUT (0xf9);
3237	NEXT ();
3238	EXPn (Size in Maus);
3239	fill_int (&ob);
3240      }
3241      break;
3242    }
3243}
3244
3245static void
3246e2_record ()
3247{
3248  OUT (0xe2);
3249  NEXT ();
3250  OUT (0xce);
3251  NEXT ();
3252  INT;
3253  EXP;
3254}
3255
3256static void
3257block ()
3258{
3259  int ch;
3260
3261  while (1)
3262    {
3263      ch = THIS ();
3264      switch (ch)
3265	{
3266	case 0xe1:
3267	case 0xe5:
3268	  return;
3269	case 0xf9:
3270	  return;
3271	case 0xf0:
3272	  f0_record ();
3273	  break;
3274	case 0xf1:
3275	  f1_record ();
3276	  break;
3277	case 0xf2:
3278	  f2_record ();
3279	  break;
3280	case 0xf8:
3281	  f8_record ();
3282	  break;
3283	case 0xe2:
3284	  e2_record ();
3285	  break;
3286
3287	}
3288    }
3289}
3290
3291
3292/* Moves all the debug information from the source bfd to the output
3293   bfd, and relocates any expressions it finds.  */
3294
3295static void
3296relocate_debug (output, input)
3297     bfd *output ATTRIBUTE_UNUSED;
3298     bfd *input;
3299{
3300#define IBS 400
3301#define OBS 400
3302  unsigned char input_buffer[IBS];
3303
3304  input_ptr_start = input_ptr = input_buffer;
3305  input_ptr_end = input_buffer + IBS;
3306  input_bfd = input;
3307  /* FIXME: Check return value.  I'm not sure whether it needs to read
3308     the entire buffer or not.  */
3309  bfd_bread ((PTR) input_ptr_start, (bfd_size_type) IBS, input);
3310  block ();
3311}
3312
3313/* Gather together all the debug information from each input BFD into
3314   one place, relocating it and emitting it as we go.  */
3315
3316static bfd_boolean
3317ieee_write_debug_part (abfd)
3318     bfd *abfd;
3319{
3320  ieee_data_type *ieee = IEEE_DATA (abfd);
3321  bfd_chain_type *chain = ieee->chain_root;
3322  unsigned char obuff[OBS];
3323  bfd_boolean some_debug = FALSE;
3324  file_ptr here = bfd_tell (abfd);
3325
3326  output_ptr_start = output_ptr = obuff;
3327  output_ptr_end = obuff + OBS;
3328  output_ptr = obuff;
3329  output_bfd = abfd;
3330
3331  if (chain == (bfd_chain_type *) NULL)
3332    {
3333      asection *s;
3334
3335      for (s = abfd->sections; s != NULL; s = s->next)
3336	if ((s->flags & SEC_DEBUGGING) != 0)
3337	  break;
3338      if (s == NULL)
3339	{
3340	  ieee->w.r.debug_information_part = 0;
3341	  return TRUE;
3342	}
3343
3344      ieee->w.r.debug_information_part = here;
3345      if (bfd_bwrite (s->contents, s->_raw_size, abfd) != s->_raw_size)
3346	return FALSE;
3347    }
3348  else
3349    {
3350      while (chain != (bfd_chain_type *) NULL)
3351	{
3352	  bfd *entry = chain->this;
3353	  ieee_data_type *entry_ieee = IEEE_DATA (entry);
3354
3355	  if (entry_ieee->w.r.debug_information_part)
3356	    {
3357	      if (bfd_seek (entry, entry_ieee->w.r.debug_information_part,
3358			    SEEK_SET) != 0)
3359		return FALSE;
3360	      relocate_debug (abfd, entry);
3361	    }
3362
3363	  chain = chain->next;
3364	}
3365
3366      if (some_debug)
3367	ieee->w.r.debug_information_part = here;
3368      else
3369	ieee->w.r.debug_information_part = 0;
3370
3371      flush ();
3372    }
3373
3374  return TRUE;
3375}
3376
3377/* Write the data in an ieee way.  */
3378
3379static bfd_boolean
3380ieee_write_data_part (abfd)
3381     bfd *abfd;
3382{
3383  asection *s;
3384
3385  ieee_data_type *ieee = IEEE_DATA (abfd);
3386  ieee->w.r.data_part = bfd_tell (abfd);
3387
3388  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
3389    {
3390      /* Skip sections that have no loadable contents (.bss,
3391         debugging, etc.)  */
3392      if ((s->flags & SEC_LOAD) == 0)
3393	continue;
3394
3395      /* Sort the reloc records so we can insert them in the correct
3396	 places */
3397      if (s->reloc_count != 0)
3398	{
3399	  if (! do_with_relocs (abfd, s))
3400	    return FALSE;
3401	}
3402      else
3403	{
3404	  if (! do_without_relocs (abfd, s))
3405	    return FALSE;
3406	}
3407    }
3408
3409  return TRUE;
3410}
3411
3412
3413static bfd_boolean
3414init_for_output (abfd)
3415     bfd *abfd;
3416{
3417  asection *s;
3418
3419  for (s = abfd->sections; s != (asection *) NULL; s = s->next)
3420    {
3421      if ((s->flags & SEC_DEBUGGING) != 0)
3422	continue;
3423      if (s->_raw_size != 0)
3424	{
3425	  bfd_size_type size = s->_raw_size;
3426	  ieee_per_section (s)->data = (bfd_byte *) (bfd_alloc (abfd, size));
3427	  if (!ieee_per_section (s)->data)
3428	    return FALSE;
3429	}
3430    }
3431  return TRUE;
3432}
3433
3434/* Exec and core file sections.  */
3435
3436/* Set section contents is complicated with IEEE since the format is
3437   not a byte image, but a record stream.  */
3438
3439static bfd_boolean
3440ieee_set_section_contents (abfd, section, location, offset, count)
3441     bfd *abfd;
3442     sec_ptr section;
3443     const PTR location;
3444     file_ptr offset;
3445     bfd_size_type count;
3446{
3447  if ((section->flags & SEC_DEBUGGING) != 0)
3448    {
3449      if (section->contents == NULL)
3450	{
3451	  bfd_size_type size = section->_raw_size;
3452	  section->contents = (unsigned char *) bfd_alloc (abfd, size);
3453	  if (section->contents == NULL)
3454	    return FALSE;
3455	}
3456      /* bfd_set_section_contents has already checked that everything
3457         is within range.  */
3458      memcpy (section->contents + offset, location, (size_t) count);
3459      return TRUE;
3460    }
3461
3462  if (ieee_per_section (section)->data == (bfd_byte *) NULL)
3463    {
3464      if (!init_for_output (abfd))
3465	return FALSE;
3466    }
3467  memcpy ((PTR) (ieee_per_section (section)->data + offset),
3468	  (PTR) location,
3469	  (unsigned int) count);
3470  return TRUE;
3471}
3472
3473/* Write the external symbols of a file.  IEEE considers two sorts of
3474   external symbols, public, and referenced.  It uses to internal
3475   forms to index them as well.  When we write them out we turn their
3476   symbol values into indexes from the right base.  */
3477
3478static bfd_boolean
3479ieee_write_external_part (abfd)
3480     bfd *abfd;
3481{
3482  asymbol **q;
3483  ieee_data_type *ieee = IEEE_DATA (abfd);
3484  unsigned int reference_index = IEEE_REFERENCE_BASE;
3485  unsigned int public_index = IEEE_PUBLIC_BASE + 2;
3486  file_ptr here = bfd_tell (abfd);
3487  bfd_boolean hadone = FALSE;
3488
3489  if (abfd->outsymbols != (asymbol **) NULL)
3490    {
3491
3492      for (q = abfd->outsymbols; *q != (asymbol *) NULL; q++)
3493	{
3494	  asymbol *p = *q;
3495
3496	  if (bfd_is_und_section (p->section))
3497	    {
3498	      /* This must be a symbol reference.  */
3499	      if (! ieee_write_byte (abfd, ieee_external_reference_enum)
3500		  || ! ieee_write_int (abfd, (bfd_vma) reference_index)
3501		  || ! ieee_write_id (abfd, p->name))
3502		return FALSE;
3503	      p->value = reference_index;
3504	      reference_index++;
3505	      hadone = TRUE;
3506	    }
3507	  else if (bfd_is_com_section (p->section))
3508	    {
3509	      /* This is a weak reference.  */
3510	      if (! ieee_write_byte (abfd, ieee_external_reference_enum)
3511		  || ! ieee_write_int (abfd, (bfd_vma) reference_index)
3512		  || ! ieee_write_id (abfd, p->name)
3513		  || ! ieee_write_byte (abfd,
3514					ieee_weak_external_reference_enum)
3515		  || ! ieee_write_int (abfd, (bfd_vma) reference_index)
3516		  || ! ieee_write_int (abfd, p->value))
3517		return FALSE;
3518	      p->value = reference_index;
3519	      reference_index++;
3520	      hadone = TRUE;
3521	    }
3522	  else if (p->flags & BSF_GLOBAL)
3523	    {
3524	      /* This must be a symbol definition.  */
3525	      if (! ieee_write_byte (abfd, ieee_external_symbol_enum)
3526		  || ! ieee_write_int (abfd, (bfd_vma) public_index)
3527		  || ! ieee_write_id (abfd, p->name)
3528		  || ! ieee_write_2bytes (abfd, ieee_attribute_record_enum)
3529		  || ! ieee_write_int (abfd, (bfd_vma) public_index)
3530		  || ! ieee_write_byte (abfd, 15) /* instruction address */
3531		  || ! ieee_write_byte (abfd, 19) /* static symbol */
3532		  || ! ieee_write_byte (abfd, 1)) /* one of them */
3533		return FALSE;
3534
3535	      /* Write out the value.  */
3536	      if (! ieee_write_2bytes (abfd, ieee_value_record_enum)
3537		  || ! ieee_write_int (abfd, (bfd_vma) public_index))
3538		return FALSE;
3539	      if (! bfd_is_abs_section (p->section))
3540		{
3541		  if (abfd->flags & EXEC_P)
3542		    {
3543		      /* If fully linked, then output all symbols
3544			 relocated.  */
3545		      if (! (ieee_write_int
3546			     (abfd,
3547			      (p->value
3548			       + p->section->output_offset
3549			       + p->section->output_section->vma))))
3550			return FALSE;
3551		    }
3552		  else
3553		    {
3554		      if (! (ieee_write_expression
3555			     (abfd,
3556			      p->value + p->section->output_offset,
3557			      p->section->output_section->symbol,
3558			      FALSE, 0)))
3559			return FALSE;
3560		    }
3561		}
3562	      else
3563		{
3564		  if (! ieee_write_expression (abfd,
3565					       p->value,
3566					       bfd_abs_section_ptr->symbol,
3567					       FALSE, 0))
3568		    return FALSE;
3569		}
3570	      p->value = public_index;
3571	      public_index++;
3572	      hadone = TRUE;
3573	    }
3574	  else
3575	    {
3576	      /* This can happen - when there are gaps in the symbols read
3577	         from an input ieee file.  */
3578	    }
3579	}
3580    }
3581  if (hadone)
3582    ieee->w.r.external_part = here;
3583
3584  return TRUE;
3585}
3586
3587
3588static const unsigned char exten[] =
3589{
3590  0xf0, 0x20, 0x00,
3591  0xf1, 0xce, 0x20, 0x00, 37, 3, 3,	/* Set version 3 rev 3.  */
3592  0xf1, 0xce, 0x20, 0x00, 39, 2,	/* Keep symbol in  original case.  */
3593  0xf1, 0xce, 0x20, 0x00, 38		/* Set object type relocatable to x.  */
3594};
3595
3596static const unsigned char envi[] =
3597{
3598  0xf0, 0x21, 0x00,
3599
3600/*    0xf1, 0xce, 0x21, 00, 50, 0x82, 0x07, 0xc7, 0x09, 0x11, 0x11,
3601    0x19, 0x2c,
3602*/
3603  0xf1, 0xce, 0x21, 00, 52, 0x00,	/* exec ok */
3604
3605  0xf1, 0xce, 0x21, 0, 53, 0x03,/* host unix */
3606/*    0xf1, 0xce, 0x21, 0, 54, 2,1,1	tool & version # */
3607};
3608
3609static bfd_boolean
3610ieee_write_me_part (abfd)
3611     bfd *abfd;
3612{
3613  ieee_data_type *ieee = IEEE_DATA (abfd);
3614  ieee->w.r.trailer_part = bfd_tell (abfd);
3615  if (abfd->start_address)
3616    {
3617      if (! ieee_write_2bytes (abfd, ieee_value_starting_address_enum)
3618	  || ! ieee_write_byte (abfd, ieee_function_either_open_b_enum)
3619	  || ! ieee_write_int (abfd, abfd->start_address)
3620	  || ! ieee_write_byte (abfd, ieee_function_either_close_b_enum))
3621	return FALSE;
3622    }
3623  ieee->w.r.me_record = bfd_tell (abfd);
3624  if (! ieee_write_byte (abfd, ieee_module_end_enum))
3625    return FALSE;
3626  return TRUE;
3627}
3628
3629/* Write out the IEEE processor ID.  */
3630
3631static bfd_boolean
3632ieee_write_processor (abfd)
3633     bfd *abfd;
3634{
3635  const bfd_arch_info_type *arch;
3636
3637  arch = bfd_get_arch_info (abfd);
3638  switch (arch->arch)
3639    {
3640    default:
3641      if (! ieee_write_id (abfd, bfd_printable_name (abfd)))
3642	return FALSE;
3643      break;
3644
3645    case bfd_arch_a29k:
3646      if (! ieee_write_id (abfd, "29000"))
3647	return FALSE;
3648      break;
3649
3650    case bfd_arch_h8300:
3651      if (! ieee_write_id (abfd, "H8/300"))
3652	return FALSE;
3653      break;
3654
3655    case bfd_arch_h8500:
3656      if (! ieee_write_id (abfd, "H8/500"))
3657	return FALSE;
3658      break;
3659
3660    case bfd_arch_i960:
3661      switch (arch->mach)
3662	{
3663	default:
3664	case bfd_mach_i960_core:
3665	case bfd_mach_i960_ka_sa:
3666	  if (! ieee_write_id (abfd, "80960KA"))
3667	    return FALSE;
3668	  break;
3669
3670	case bfd_mach_i960_kb_sb:
3671	  if (! ieee_write_id (abfd, "80960KB"))
3672	    return FALSE;
3673	  break;
3674
3675	case bfd_mach_i960_ca:
3676	  if (! ieee_write_id (abfd, "80960CA"))
3677	    return FALSE;
3678	  break;
3679
3680	case bfd_mach_i960_mc:
3681	case bfd_mach_i960_xa:
3682	  if (! ieee_write_id (abfd, "80960MC"))
3683	    return FALSE;
3684	  break;
3685	}
3686      break;
3687
3688    case bfd_arch_m68k:
3689      {
3690	const char *id;
3691
3692	switch (arch->mach)
3693	  {
3694	  default:		id = "68020"; break;
3695	  case bfd_mach_m68000: id = "68000"; break;
3696	  case bfd_mach_m68008: id = "68008"; break;
3697	  case bfd_mach_m68010: id = "68010"; break;
3698	  case bfd_mach_m68020: id = "68020"; break;
3699	  case bfd_mach_m68030: id = "68030"; break;
3700	  case bfd_mach_m68040: id = "68040"; break;
3701	  case bfd_mach_m68060: id = "68060"; break;
3702	  case bfd_mach_cpu32:  id = "cpu32"; break;
3703	  case bfd_mach_mcf5200:id = "5200";  break;
3704	  case bfd_mach_mcf5206e:id = "5206e"; break;
3705	  case bfd_mach_mcf5307:id = "5307";  break;
3706	  case bfd_mach_mcf5407:id = "5407";  break;
3707	  case bfd_mach_mcf528x:id = "5282";  break;
3708	  }
3709
3710	if (! ieee_write_id (abfd, id))
3711	  return FALSE;
3712      }
3713      break;
3714    }
3715
3716  return TRUE;
3717}
3718
3719static bfd_boolean
3720ieee_write_object_contents (abfd)
3721     bfd *abfd;
3722{
3723  ieee_data_type *ieee = IEEE_DATA (abfd);
3724  unsigned int i;
3725  file_ptr old;
3726
3727  /* Fast forward over the header area.  */
3728  if (bfd_seek (abfd, (file_ptr) 0, SEEK_SET) != 0)
3729    return FALSE;
3730
3731  if (! ieee_write_byte (abfd, ieee_module_beginning_enum)
3732      || ! ieee_write_processor (abfd)
3733      || ! ieee_write_id (abfd, abfd->filename))
3734    return FALSE;
3735
3736  /* Fast forward over the variable bits.  */
3737  if (! ieee_write_byte (abfd, ieee_address_descriptor_enum))
3738    return FALSE;
3739
3740  /* Bits per MAU.  */
3741  if (! ieee_write_byte (abfd, (bfd_byte) (bfd_arch_bits_per_byte (abfd))))
3742    return FALSE;
3743  /* MAU's per address.  */
3744  if (! ieee_write_byte (abfd,
3745			 (bfd_byte) (bfd_arch_bits_per_address (abfd)
3746				     / bfd_arch_bits_per_byte (abfd))))
3747    return FALSE;
3748
3749  old = bfd_tell (abfd);
3750  if (bfd_seek (abfd, (file_ptr) (8 * N_W_VARIABLES), SEEK_CUR) != 0)
3751    return FALSE;
3752
3753  ieee->w.r.extension_record = bfd_tell (abfd);
3754  if (bfd_bwrite ((char *) exten, (bfd_size_type) sizeof (exten), abfd)
3755      != sizeof (exten))
3756    return FALSE;
3757  if (abfd->flags & EXEC_P)
3758    {
3759      if (! ieee_write_byte (abfd, 0x1)) /* Absolute */
3760	return FALSE;
3761    }
3762  else
3763    {
3764      if (! ieee_write_byte (abfd, 0x2)) /* Relocateable */
3765	return FALSE;
3766    }
3767
3768  ieee->w.r.environmental_record = bfd_tell (abfd);
3769  if (bfd_bwrite ((char *) envi, (bfd_size_type) sizeof (envi), abfd)
3770      != sizeof (envi))
3771    return FALSE;
3772
3773  /* The HP emulator database requires a timestamp in the file.  */
3774  {
3775    time_t now;
3776    const struct tm *t;
3777
3778    time (&now);
3779    t = (struct tm *) localtime (&now);
3780    if (! ieee_write_2bytes (abfd, (int) ieee_atn_record_enum)
3781	|| ! ieee_write_byte (abfd, 0x21)
3782	|| ! ieee_write_byte (abfd, 0)
3783	|| ! ieee_write_byte (abfd, 50)
3784	|| ! ieee_write_int (abfd, (bfd_vma) (t->tm_year + 1900))
3785	|| ! ieee_write_int (abfd, (bfd_vma) (t->tm_mon + 1))
3786	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_mday)
3787	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_hour)
3788	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_min)
3789	|| ! ieee_write_int (abfd, (bfd_vma) t->tm_sec))
3790      return FALSE;
3791  }
3792
3793  output_bfd = abfd;
3794
3795  flush ();
3796
3797  if (! ieee_write_section_part (abfd))
3798    return FALSE;
3799  /* First write the symbols.  This changes their values into table
3800    indeces so we cant use it after this point.  */
3801  if (! ieee_write_external_part (abfd))
3802    return FALSE;
3803
3804  /* Write any debugs we have been told about.  */
3805  if (! ieee_write_debug_part (abfd))
3806    return FALSE;
3807
3808  /* Can only write the data once the symbols have been written, since
3809     the data contains relocation information which points to the
3810     symbols.  */
3811  if (! ieee_write_data_part (abfd))
3812    return FALSE;
3813
3814  /* At the end we put the end!  */
3815  if (! ieee_write_me_part (abfd))
3816    return FALSE;
3817
3818  /* Generate the header.  */
3819  if (bfd_seek (abfd, old, SEEK_SET) != 0)
3820    return FALSE;
3821
3822  for (i = 0; i < N_W_VARIABLES; i++)
3823    {
3824      if (! ieee_write_2bytes (abfd, ieee_assign_value_to_variable_enum)
3825	  || ! ieee_write_byte (abfd, (bfd_byte) i)
3826	  || ! ieee_write_int5_out (abfd, (bfd_vma) ieee->w.offset[i]))
3827	return FALSE;
3828    }
3829
3830  return TRUE;
3831}
3832
3833/* Native-level interface to symbols. */
3834
3835/* We read the symbols into a buffer, which is discarded when this
3836   function exits.  We read the strings into a buffer large enough to
3837   hold them all plus all the cached symbol entries.  */
3838
3839static asymbol *
3840ieee_make_empty_symbol (abfd)
3841     bfd *abfd;
3842{
3843  bfd_size_type amt = sizeof (ieee_symbol_type);
3844  ieee_symbol_type *new = (ieee_symbol_type *) bfd_zalloc (abfd, amt);
3845
3846  if (!new)
3847    return NULL;
3848  new->symbol.the_bfd = abfd;
3849  return &new->symbol;
3850}
3851
3852static bfd *
3853ieee_openr_next_archived_file (arch, prev)
3854     bfd *arch;
3855     bfd *prev;
3856{
3857  ieee_ar_data_type *ar = IEEE_AR_DATA (arch);
3858
3859  /* Take the next one from the arch state, or reset.  */
3860  if (prev == (bfd *) NULL)
3861    /* Reset the index - the first two entries are bogus.  */
3862    ar->element_index = 2;
3863
3864  while (TRUE)
3865    {
3866      ieee_ar_obstack_type *p = ar->elements + ar->element_index;
3867
3868      ar->element_index++;
3869      if (ar->element_index <= ar->element_count)
3870	{
3871	  if (p->file_offset != (file_ptr) 0)
3872	    {
3873	      if (p->abfd == (bfd *) NULL)
3874		{
3875		  p->abfd = _bfd_create_empty_archive_element_shell (arch);
3876		  p->abfd->origin = p->file_offset;
3877		}
3878	      return p->abfd;
3879	    }
3880	}
3881      else
3882	{
3883	  bfd_set_error (bfd_error_no_more_archived_files);
3884	  return (bfd *) NULL;
3885	}
3886    }
3887}
3888
3889static bfd_boolean
3890ieee_find_nearest_line (abfd, section, symbols, offset, filename_ptr,
3891			functionname_ptr, line_ptr)
3892     bfd *abfd ATTRIBUTE_UNUSED;
3893     asection *section ATTRIBUTE_UNUSED;
3894     asymbol **symbols ATTRIBUTE_UNUSED;
3895     bfd_vma offset ATTRIBUTE_UNUSED;
3896     const char **filename_ptr ATTRIBUTE_UNUSED;
3897     const char **functionname_ptr ATTRIBUTE_UNUSED;
3898     unsigned int *line_ptr ATTRIBUTE_UNUSED;
3899{
3900  return FALSE;
3901}
3902
3903static int
3904ieee_generic_stat_arch_elt (abfd, buf)
3905     bfd *abfd;
3906     struct stat *buf;
3907{
3908  ieee_ar_data_type *ar = (ieee_ar_data_type *) NULL;
3909  ieee_data_type *ieee;
3910
3911  if (abfd->my_archive != NULL)
3912    ar = abfd->my_archive->tdata.ieee_ar_data;
3913  if (ar == (ieee_ar_data_type *) NULL)
3914    {
3915      bfd_set_error (bfd_error_invalid_operation);
3916      return -1;
3917    }
3918
3919  if (IEEE_DATA (abfd) == NULL)
3920    {
3921      if (ieee_object_p (abfd) == NULL)
3922	{
3923	  bfd_set_error (bfd_error_wrong_format);
3924	  return -1;
3925	}
3926    }
3927
3928  ieee = IEEE_DATA (abfd);
3929
3930  buf->st_size = ieee->w.r.me_record + 1;
3931  buf->st_mode = 0644;
3932  return 0;
3933}
3934
3935static int
3936ieee_sizeof_headers (abfd, x)
3937     bfd *abfd ATTRIBUTE_UNUSED;
3938     bfd_boolean x ATTRIBUTE_UNUSED;
3939{
3940  return 0;
3941}
3942
3943
3944/* The debug info routines are never used.  */
3945#if 0
3946
3947static void
3948ieee_bfd_debug_info_start (abfd)
3949     bfd *abfd;
3950{
3951
3952}
3953
3954static void
3955ieee_bfd_debug_info_end (abfd)
3956     bfd *abfd;
3957{
3958
3959}
3960
3961
3962/* Add this section to the list of sections we have debug info for, to
3963   be ready to output it at close time.  */
3964static void
3965ieee_bfd_debug_info_accumulate (abfd, section)
3966     bfd *abfd;
3967     asection *section;
3968{
3969  ieee_data_type *ieee = IEEE_DATA (section->owner);
3970  ieee_data_type *output_ieee = IEEE_DATA (abfd);
3971
3972  /* Can only accumulate data from other ieee bfds.  */
3973  if (section->owner->xvec != abfd->xvec)
3974    return;
3975  /* Only bother once per bfd.  */
3976  if (ieee->done_debug)
3977    return;
3978  ieee->done_debug = TRUE;
3979
3980  /* Don't bother if there is no debug info.  */
3981  if (ieee->w.r.debug_information_part == 0)
3982    return;
3983
3984  /* Add to chain.  */
3985  {
3986    bfd_size_type amt = sizeof (bfd_chain_type);
3987    bfd_chain_type *n = (bfd_chain_type *) bfd_alloc (abfd, amt);
3988
3989    if (!n)
3990      abort ();		/* FIXME */
3991    n->this = section->owner;
3992    n->next = (bfd_chain_type *) NULL;
3993
3994    if (output_ieee->chain_head)
3995      output_ieee->chain_head->next = n;
3996    else
3997      output_ieee->chain_root = n;
3998
3999    output_ieee->chain_head = n;
4000  }
4001}
4002
4003#endif
4004
4005#define	ieee_close_and_cleanup _bfd_generic_close_and_cleanup
4006#define ieee_bfd_free_cached_info _bfd_generic_bfd_free_cached_info
4007
4008#define ieee_slurp_armap bfd_true
4009#define ieee_slurp_extended_name_table bfd_true
4010#define ieee_construct_extended_name_table \
4011  ((bfd_boolean (*) \
4012    PARAMS ((bfd *, char **, bfd_size_type *, const char **))) \
4013   bfd_true)
4014#define ieee_truncate_arname bfd_dont_truncate_arname
4015#define ieee_write_armap \
4016  ((bfd_boolean (*) \
4017    PARAMS ((bfd *, unsigned int, struct orl *, unsigned int, int))) \
4018   bfd_true)
4019#define ieee_read_ar_hdr bfd_nullvoidptr
4020#define ieee_update_armap_timestamp bfd_true
4021#define ieee_get_elt_at_index _bfd_generic_get_elt_at_index
4022
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_discard_group bfd_generic_discard_group
4041#define ieee_bfd_link_hash_table_create _bfd_generic_link_hash_table_create
4042#define ieee_bfd_link_hash_table_free _bfd_generic_link_hash_table_free
4043#define ieee_bfd_link_add_symbols _bfd_generic_link_add_symbols
4044#define ieee_bfd_link_just_syms _bfd_generic_link_just_syms
4045#define ieee_bfd_final_link _bfd_generic_final_link
4046#define ieee_bfd_link_split_section  _bfd_generic_link_split_section
4047
4048const bfd_target ieee_vec =
4049{
4050  "ieee",			/* name */
4051  bfd_target_ieee_flavour,
4052  BFD_ENDIAN_UNKNOWN,		/* target byte order */
4053  BFD_ENDIAN_UNKNOWN,		/* target headers byte order */
4054  (HAS_RELOC | EXEC_P |		/* object flags */
4055   HAS_LINENO | HAS_DEBUG |
4056   HAS_SYMS | HAS_LOCALS | WP_TEXT | D_PAGED),
4057  (SEC_CODE | SEC_DATA | SEC_ROM | SEC_HAS_CONTENTS
4058   | SEC_ALLOC | SEC_LOAD | SEC_RELOC),	/* section flags */
4059  '_',				/* leading underscore */
4060  ' ',				/* ar_pad_char */
4061  16,				/* ar_max_namelen */
4062  bfd_getb64, bfd_getb_signed_64, bfd_putb64,
4063  bfd_getb32, bfd_getb_signed_32, bfd_putb32,
4064  bfd_getb16, bfd_getb_signed_16, bfd_putb16,	/* data */
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,	/* hdrs */
4068
4069  {_bfd_dummy_target,
4070   ieee_object_p,		/* bfd_check_format */
4071   ieee_archive_p,
4072   _bfd_dummy_target,
4073  },
4074  {
4075    bfd_false,
4076    ieee_mkobject,
4077    _bfd_generic_mkarchive,
4078    bfd_false
4079  },
4080  {
4081    bfd_false,
4082    ieee_write_object_contents,
4083    _bfd_write_archive_contents,
4084    bfd_false,
4085  },
4086
4087  /* ieee_close_and_cleanup, ieee_bfd_free_cached_info, ieee_new_section_hook,
4088     ieee_get_section_contents, ieee_get_section_contents_in_window  */
4089  BFD_JUMP_TABLE_GENERIC (ieee),
4090
4091  BFD_JUMP_TABLE_COPY (_bfd_generic),
4092  BFD_JUMP_TABLE_CORE (_bfd_nocore),
4093
4094  /* ieee_slurp_armap, ieee_slurp_extended_name_table,
4095     ieee_construct_extended_name_table, ieee_truncate_arname,
4096     ieee_write_armap, ieee_read_ar_hdr, ieee_openr_next_archived_file,
4097     ieee_get_elt_at_index, ieee_generic_stat_arch_elt,
4098     ieee_update_armap_timestamp  */
4099  BFD_JUMP_TABLE_ARCHIVE (ieee),
4100
4101  /* ieee_get_symtab_upper_bound, ieee_canonicalize_symtab,
4102     ieee_make_empty_symbol, ieee_print_symbol, ieee_get_symbol_info,
4103     ieee_bfd_is_local_label_name, ieee_get_lineno,
4104     ieee_find_nearest_line, ieee_bfd_make_debug_symbol,
4105     ieee_read_minisymbols, ieee_minisymbol_to_symbol */
4106  BFD_JUMP_TABLE_SYMBOLS (ieee),
4107
4108  /* ieee_get_reloc_upper_bound, ieee_canonicalize_reloc,
4109     ieee_bfd_reloc_type_lookup  */
4110  BFD_JUMP_TABLE_RELOCS (ieee),
4111
4112  /* ieee_set_arch_mach, ieee_set_section_contents  */
4113  BFD_JUMP_TABLE_WRITE (ieee),
4114
4115  /* ieee_sizeof_headers, ieee_bfd_get_relocated_section_contents,
4116     ieee_bfd_relax_section, ieee_bfd_link_hash_table_create,
4117     _bfd_generic_link_hash_table_free,
4118     ieee_bfd_link_add_symbols, ieee_bfd_final_link,
4119     ieee_bfd_link_split_section, ieee_bfd_gc_sections,
4120     ieee_bfd_merge_sections  */
4121  BFD_JUMP_TABLE_LINK (ieee),
4122
4123  BFD_JUMP_TABLE_DYNAMIC (_bfd_nodynamic),
4124
4125  NULL,
4126
4127  (PTR) 0
4128};
4129