1/* BFD back-end for AMD 29000 COFF binaries.
2   Copyright 1990, 1991, 1992, 1993, 1994, 1995, 1997, 1999, 2000, 2001,
3   2002, 2003
4   Free Software Foundation, Inc.
5   Contributed by David Wood at New York University 7/8/91.
6
7This file is part of BFD, the Binary File Descriptor library.
8
9This program is free software; you can redistribute it and/or modify
10it under the terms of the GNU General Public License as published by
11the Free Software Foundation; either version 2 of the License, or
12(at your option) any later version.
13
14This program is distributed in the hope that it will be useful,
15but WITHOUT ANY WARRANTY; without even the implied warranty of
16MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17GNU General Public License for more details.
18
19You should have received a copy of the GNU General Public License
20along with this program; if not, write to the Free Software
21Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
22
23#define A29K 1
24
25#include "bfd.h"
26#include "sysdep.h"
27#include "libbfd.h"
28#include "coff/a29k.h"
29#include "coff/internal.h"
30#include "libcoff.h"
31
32static long get_symbol_value PARAMS ((asymbol *));
33static bfd_reloc_status_type a29k_reloc
34  PARAMS ((bfd *, arelent *, asymbol *, PTR, asection *, bfd *, char **));
35static bfd_boolean coff_a29k_relocate_section
36  PARAMS ((bfd *, struct bfd_link_info *, bfd *, asection *, bfd_byte *,
37	   struct internal_reloc *, struct internal_syment *, asection **));
38static bfd_boolean coff_a29k_adjust_symndx
39  PARAMS ((bfd *, struct bfd_link_info *, bfd *, asection *,
40	   struct internal_reloc *, bfd_boolean *));
41static void reloc_processing
42  PARAMS ((arelent *, struct internal_reloc *, asymbol **, bfd *, asection *));
43
44#define COFF_DEFAULT_SECTION_ALIGNMENT_POWER (2)
45
46#define INSERT_HWORD(WORD,HWORD)	\
47    (((WORD) & 0xff00ff00) | (((HWORD) & 0xff00) << 8) | ((HWORD)& 0xff))
48#define EXTRACT_HWORD(WORD) \
49    ((((WORD) & 0x00ff0000) >> 8) | ((WORD) & 0xff))
50#define SIGN_EXTEND_HWORD(HWORD) \
51    (((HWORD) ^ 0x8000) - 0x8000)
52
53/* Provided the symbol, returns the value reffed.  */
54
55static long
56get_symbol_value (symbol)
57     asymbol *symbol;
58{
59  long relocation = 0;
60
61  if (bfd_is_com_section (symbol->section))
62    relocation = 0;
63  else
64    relocation = symbol->value +
65      symbol->section->output_section->vma +
66      symbol->section->output_offset;
67
68  return relocation;
69}
70
71/* This function is in charge of performing all the 29k relocations.  */
72
73static bfd_reloc_status_type
74a29k_reloc (abfd, reloc_entry, symbol_in, data, input_section, output_bfd,
75	    error_message)
76     bfd *abfd;
77     arelent *reloc_entry;
78     asymbol *symbol_in;
79     PTR data;
80     asection *input_section;
81     bfd *output_bfd;
82     char **error_message;
83{
84  /* The consth relocation comes in two parts, we have to remember
85     the state between calls, in these variables.  */
86  static bfd_boolean part1_consth_active = FALSE;
87  static unsigned long part1_consth_value;
88  unsigned long insn;
89  unsigned long sym_value;
90  unsigned long unsigned_value;
91  unsigned short r_type;
92  long signed_value;
93  unsigned long addr = reloc_entry->address ; /*+ input_section->vma*/
94  bfd_byte  *hit_data =addr + (bfd_byte *) (data);
95
96  r_type = reloc_entry->howto->type;
97
98  if (output_bfd)
99    {
100      /* Partial linking - do nothing.  */
101      reloc_entry->address += input_section->output_offset;
102      return bfd_reloc_ok;
103    }
104
105  if (symbol_in != NULL
106      && bfd_is_und_section (symbol_in->section))
107    {
108      /* Keep the state machine happy in case we're called again.  */
109      if (r_type == R_IHIHALF)
110	{
111	  part1_consth_active = TRUE;
112	  part1_consth_value  = 0;
113	}
114      return bfd_reloc_undefined;
115    }
116
117  if ((part1_consth_active) && (r_type != R_IHCONST))
118    {
119      part1_consth_active = FALSE;
120      *error_message = (char *) _("Missing IHCONST");
121
122      return bfd_reloc_dangerous;
123    }
124
125  sym_value = get_symbol_value(symbol_in);
126
127  switch (r_type)
128    {
129    case R_IREL:
130      insn = bfd_get_32 (abfd, hit_data);
131      /* Take the value in the field and sign extend it.  */
132      signed_value = EXTRACT_HWORD(insn);
133      signed_value = SIGN_EXTEND_HWORD(signed_value);
134      signed_value <<= 2;
135
136      /* See the note on the R_IREL reloc in coff_a29k_relocate_section.  */
137      if (signed_value == - (long) reloc_entry->address)
138	signed_value = 0;
139
140      signed_value += sym_value + reloc_entry->addend;
141      if ((signed_value & ~0x3ffff) == 0)
142	{				/* Absolute jmp/call */
143	  insn |= (1 << 24);		/* Make it absolute */
144	  /* FIXME: Should we change r_type to R_IABS.  */
145	}
146      else
147	{
148	  /* Relative jmp/call, so subtract from the value the
149	     address of the place we're coming from.  */
150	  signed_value -= (reloc_entry->address
151			   + input_section->output_section->vma
152			   + input_section->output_offset);
153	  if (signed_value > 0x1ffff || signed_value < -0x20000)
154	    return bfd_reloc_overflow;
155	}
156      signed_value >>= 2;
157      insn = INSERT_HWORD (insn, signed_value);
158      bfd_put_32 (abfd, (bfd_vma) insn ,hit_data);
159      break;
160    case R_ILOHALF:
161      insn = bfd_get_32 (abfd, hit_data);
162      unsigned_value = EXTRACT_HWORD(insn);
163      unsigned_value +=  sym_value + reloc_entry->addend;
164      insn = INSERT_HWORD(insn, unsigned_value);
165      bfd_put_32 (abfd, (bfd_vma) insn, hit_data);
166      break;
167    case R_IHIHALF:
168      insn = bfd_get_32 (abfd, hit_data);
169      /* consth, part 1
170	 Just get the symbol value that is referenced.  */
171      part1_consth_active = TRUE;
172      part1_consth_value = sym_value + reloc_entry->addend;
173      /* Don't modify insn until R_IHCONST.  */
174      break;
175    case R_IHCONST:
176      insn = bfd_get_32 (abfd, hit_data);
177      /* consth, part 2
178	 Now relocate the reference.  */
179      if (! part1_consth_active)
180	{
181	  *error_message = (char *) _("Missing IHIHALF");
182	  return bfd_reloc_dangerous;
183	}
184      /* sym_ptr_ptr = r_symndx, in coff_slurp_reloc_table() */
185      unsigned_value = 0;		/*EXTRACT_HWORD(insn) << 16;*/
186      unsigned_value += reloc_entry->addend; /* r_symndx */
187      unsigned_value += part1_consth_value;
188      unsigned_value = unsigned_value >> 16;
189      insn = INSERT_HWORD(insn, unsigned_value);
190      part1_consth_active = FALSE;
191      bfd_put_32 (abfd, (bfd_vma) insn, hit_data);
192      break;
193    case R_BYTE:
194      insn = bfd_get_8 (abfd, hit_data);
195      unsigned_value = insn + sym_value + reloc_entry->addend;
196      if (unsigned_value & 0xffffff00)
197	return bfd_reloc_overflow;
198      bfd_put_8 (abfd, unsigned_value, hit_data);
199      break;
200    case R_HWORD:
201      insn = bfd_get_16 (abfd, hit_data);
202      unsigned_value = insn + sym_value + reloc_entry->addend;
203      if (unsigned_value & 0xffff0000)
204	return bfd_reloc_overflow;
205      bfd_put_16 (abfd, (bfd_vma) insn, hit_data);
206      break;
207    case R_WORD:
208      insn = bfd_get_32 (abfd, hit_data);
209      insn += sym_value + reloc_entry->addend;
210      bfd_put_32 (abfd, (bfd_vma) insn, hit_data);
211      break;
212    default:
213      *error_message = _("Unrecognized reloc");
214      return bfd_reloc_dangerous;
215    }
216
217  return(bfd_reloc_ok);
218}
219
220/*FIXME: I'm not real sure about this table.  */
221static reloc_howto_type howto_table[] =
222  {
223    {R_ABS,     0, 3, 32, FALSE, 0, complain_overflow_bitfield,a29k_reloc,"ABS",     TRUE, 0xffffffff,0xffffffff, FALSE},
224    EMPTY_HOWTO (1),
225    EMPTY_HOWTO (2),
226    EMPTY_HOWTO (3),
227    EMPTY_HOWTO (4),
228    EMPTY_HOWTO (5),
229    EMPTY_HOWTO (6),
230    EMPTY_HOWTO (7),
231    EMPTY_HOWTO (8),
232    EMPTY_HOWTO (9),
233    EMPTY_HOWTO (10),
234    EMPTY_HOWTO (11),
235    EMPTY_HOWTO (12),
236    EMPTY_HOWTO (13),
237    EMPTY_HOWTO (14),
238    EMPTY_HOWTO (15),
239    EMPTY_HOWTO (16),
240    EMPTY_HOWTO (17),
241    EMPTY_HOWTO (18),
242    EMPTY_HOWTO (19),
243    EMPTY_HOWTO (20),
244    EMPTY_HOWTO (21),
245    EMPTY_HOWTO (22),
246    EMPTY_HOWTO (23),
247    {R_IREL,    0, 3, 32, TRUE,  0, complain_overflow_signed,a29k_reloc,"IREL",    TRUE, 0xffffffff,0xffffffff, FALSE},
248    {R_IABS,    0, 3, 32, FALSE, 0, complain_overflow_bitfield, a29k_reloc,"IABS",    TRUE, 0xffffffff,0xffffffff, FALSE},
249    {R_ILOHALF, 0, 3, 16, TRUE,  0, complain_overflow_signed, a29k_reloc,"ILOHALF", TRUE, 0x0000ffff,0x0000ffff, FALSE},
250    {R_IHIHALF, 0, 3, 16, TRUE,  16, complain_overflow_signed, a29k_reloc,"IHIHALF", TRUE, 0xffff0000,0xffff0000, FALSE},
251    {R_IHCONST, 0, 3, 16, TRUE,  0, complain_overflow_signed, a29k_reloc,"IHCONST", TRUE, 0xffff0000,0xffff0000, FALSE},
252    {R_BYTE,    0, 0, 8, FALSE, 0, complain_overflow_bitfield, a29k_reloc,"BYTE",    TRUE, 0x000000ff,0x000000ff, FALSE},
253    {R_HWORD,   0, 1, 16, FALSE, 0, complain_overflow_bitfield, a29k_reloc,"HWORD",   TRUE, 0x0000ffff,0x0000ffff, FALSE},
254    {R_WORD,    0, 2, 32, FALSE, 0, complain_overflow_bitfield, a29k_reloc,"WORD",    TRUE, 0xffffffff,0xffffffff, FALSE},
255  };
256
257#define BADMAG(x) A29KBADMAG(x)
258
259#define RELOC_PROCESSING(relent, reloc, symbols, abfd, section) \
260 reloc_processing(relent, reloc, symbols, abfd, section)
261
262static void
263reloc_processing (relent,reloc, symbols, abfd, section)
264     arelent *relent;
265     struct internal_reloc *reloc;
266     asymbol **symbols;
267     bfd *abfd;
268     asection *section;
269{
270  static bfd_vma ihihalf_vaddr = (bfd_vma) -1;
271
272  relent->address = reloc->r_vaddr;
273  relent->howto = howto_table + reloc->r_type;
274  if (reloc->r_type == R_IHCONST)
275    {
276      /* The address of an R_IHCONST should always be the address of
277	 the immediately preceding R_IHIHALF.  relocs generated by gas
278	 are correct, but relocs generated by High C are different (I
279	 can't figure out what the address means for High C).  We can
280	 handle both gas and High C by ignoring the address here, and
281	 simply reusing the address saved for R_IHIHALF.  */
282      if (ihihalf_vaddr == (bfd_vma) -1)
283	abort ();
284      relent->address = ihihalf_vaddr;
285      ihihalf_vaddr = (bfd_vma) -1;
286      relent->addend = reloc->r_symndx;
287      relent->sym_ptr_ptr= bfd_abs_section_ptr->symbol_ptr_ptr;
288    }
289  else
290    {
291      asymbol *ptr;
292
293      relent->sym_ptr_ptr = symbols + obj_convert (abfd)[reloc->r_symndx];
294
295      ptr = *(relent->sym_ptr_ptr);
296
297      if (ptr
298	  && bfd_asymbol_bfd(ptr) == abfd
299	  && ((ptr->flags & BSF_OLD_COMMON) == 0))
300	relent->addend = 0;
301      else
302	relent->addend = 0;
303
304      relent->address-= section->vma;
305      if (reloc->r_type == R_IHIHALF)
306	ihihalf_vaddr = relent->address;
307      else if (ihihalf_vaddr != (bfd_vma) -1)
308	abort ();
309    }
310}
311
312/* The reloc processing routine for the optimized COFF linker.  */
313
314static bfd_boolean
315coff_a29k_relocate_section (output_bfd, info, input_bfd, input_section,
316			    contents, relocs, syms, sections)
317     bfd *output_bfd ATTRIBUTE_UNUSED;
318     struct bfd_link_info *info;
319     bfd *input_bfd;
320     asection *input_section;
321     bfd_byte *contents;
322     struct internal_reloc *relocs;
323     struct internal_syment *syms;
324     asection **sections;
325{
326  struct internal_reloc *rel;
327  struct internal_reloc *relend;
328  bfd_boolean hihalf;
329  bfd_vma hihalf_val;
330
331  /* If we are performing a relocatable link, we don't need to do a
332     thing.  The caller will take care of adjusting the reloc
333     addresses and symbol indices.  */
334  if (info->relocatable)
335    return TRUE;
336
337  hihalf = FALSE;
338  hihalf_val = 0;
339
340  rel = relocs;
341  relend = rel + input_section->reloc_count;
342  for (; rel < relend; rel++)
343    {
344      long symndx;
345      bfd_byte *loc;
346      struct coff_link_hash_entry *h;
347      struct internal_syment *sym;
348      asection *sec;
349      bfd_vma val;
350      bfd_boolean overflow;
351      unsigned long insn;
352      long signed_value;
353      unsigned long unsigned_value;
354      bfd_reloc_status_type rstat;
355
356      symndx = rel->r_symndx;
357      loc = contents + rel->r_vaddr - input_section->vma;
358
359      if (symndx == -1 || rel->r_type == R_IHCONST)
360	h = NULL;
361      else
362	h = obj_coff_sym_hashes (input_bfd)[symndx];
363
364      sym = NULL;
365      sec = NULL;
366      val = 0;
367
368      /* An R_IHCONST reloc does not have a symbol.  Instead, the
369         symbol index is an addend.  R_IHCONST is always used in
370         conjunction with R_IHHALF.  */
371      if (rel->r_type != R_IHCONST)
372	{
373	  if (h == NULL)
374	    {
375	      if (symndx == -1)
376		sec = bfd_abs_section_ptr;
377	      else
378		{
379		  sym = syms + symndx;
380		  sec = sections[symndx];
381		  val = (sec->output_section->vma
382			 + sec->output_offset
383			 + sym->n_value
384			 - sec->vma);
385		}
386	    }
387	  else
388	    {
389	      if (   h->root.type == bfd_link_hash_defined
390		  || h->root.type == bfd_link_hash_defweak)
391		{
392		  sec = h->root.u.def.section;
393		  val = (h->root.u.def.value
394			 + sec->output_section->vma
395			 + sec->output_offset);
396		}
397	      else
398		{
399		  if (! ((*info->callbacks->undefined_symbol)
400			 (info, h->root.root.string, input_bfd, input_section,
401			  rel->r_vaddr - input_section->vma, TRUE)))
402		    return FALSE;
403		}
404	    }
405
406	  if (hihalf)
407	    {
408	      if (! ((*info->callbacks->reloc_dangerous)
409		     (info, _("missing IHCONST reloc"), input_bfd,
410		      input_section, rel->r_vaddr - input_section->vma)))
411		return FALSE;
412	      hihalf = FALSE;
413	    }
414	}
415
416      overflow = FALSE;
417
418      switch (rel->r_type)
419	{
420	default:
421	  bfd_set_error (bfd_error_bad_value);
422	  return FALSE;
423
424	case R_IREL:
425	  insn = bfd_get_32 (input_bfd, loc);
426
427	  /* Extract the addend.  */
428	  signed_value = EXTRACT_HWORD (insn);
429	  signed_value = SIGN_EXTEND_HWORD (signed_value);
430	  signed_value <<= 2;
431
432	  /* Unfortunately, there are two different versions of COFF
433	     a29k.  In the original AMD version, the value stored in
434	     the field for the R_IREL reloc is a simple addend.  In
435	     the GNU version, the value is the negative of the address
436	     of the reloc within section.  We try to cope here by
437	     assuming the AMD version, unless the addend is exactly
438	     the negative of the address; in the latter case we assume
439	     the GNU version.  This means that something like
440	         .text
441		 nop
442		 jmp i-4
443	     will fail, because the addend of -4 will happen to equal
444	     the negative of the address within the section.  The
445	     compiler will never generate code like this.
446
447	     At some point in the future we may want to take out this
448	     check.  */
449
450	  if (signed_value == - (long) (rel->r_vaddr - input_section->vma))
451	    signed_value = 0;
452
453	  /* Determine the destination of the jump.  */
454	  signed_value += val;
455
456	  if ((signed_value & ~0x3ffff) == 0)
457	    {
458	      /* We can use an absolute jump.  */
459	      insn |= (1 << 24);
460	    }
461	  else
462	    {
463	      /* Make the destination PC relative.  */
464	      signed_value -= (input_section->output_section->vma
465			       + input_section->output_offset
466			       + (rel->r_vaddr - input_section->vma));
467	      if (signed_value > 0x1ffff || signed_value < - 0x20000)
468		{
469		  overflow = TRUE;
470		  signed_value = 0;
471		}
472	    }
473
474	  /* Put the adjusted value back into the instruction.  */
475	  signed_value >>= 2;
476	  insn = INSERT_HWORD (insn, signed_value);
477
478	  bfd_put_32 (input_bfd, (bfd_vma) insn, loc);
479	  break;
480
481	case R_ILOHALF:
482	  insn = bfd_get_32 (input_bfd, loc);
483	  unsigned_value = EXTRACT_HWORD (insn);
484	  unsigned_value += val;
485	  insn = INSERT_HWORD (insn, unsigned_value);
486	  bfd_put_32 (input_bfd, (bfd_vma) insn, loc);
487	  break;
488
489	case R_IHIHALF:
490	  /* Save the value for the R_IHCONST reloc.  */
491	  hihalf = TRUE;
492	  hihalf_val = val;
493	  break;
494
495	case R_IHCONST:
496	  if (! hihalf)
497	    {
498	      if (! ((*info->callbacks->reloc_dangerous)
499		     (info, _("missing IHIHALF reloc"), input_bfd,
500		      input_section, rel->r_vaddr - input_section->vma)))
501		return FALSE;
502	      hihalf_val = 0;
503	    }
504
505	  insn = bfd_get_32 (input_bfd, loc);
506	  unsigned_value = rel->r_symndx + hihalf_val;
507	  unsigned_value >>= 16;
508	  insn = INSERT_HWORD (insn, unsigned_value);
509	  bfd_put_32 (input_bfd, (bfd_vma) insn, loc);
510
511	  hihalf = FALSE;
512
513	  break;
514
515	case R_BYTE:
516	case R_HWORD:
517	case R_WORD:
518	  rstat = _bfd_relocate_contents (howto_table + rel->r_type,
519					  input_bfd, val, loc);
520	  if (rstat == bfd_reloc_overflow)
521	    overflow = TRUE;
522	  else if (rstat != bfd_reloc_ok)
523	    abort ();
524	  break;
525	}
526
527      if (overflow)
528	{
529	  const char *name;
530	  char buf[SYMNMLEN + 1];
531
532	  if (symndx == -1)
533	    name = "*ABS*";
534	  else if (h != NULL)
535	    name = h->root.root.string;
536	  else if (sym == NULL)
537	    name = "*unknown*";
538	  else if (sym->_n._n_n._n_zeroes == 0
539		   && sym->_n._n_n._n_offset != 0)
540	    name = obj_coff_strings (input_bfd) + sym->_n._n_n._n_offset;
541	  else
542	    {
543	      strncpy (buf, sym->_n._n_name, SYMNMLEN);
544	      buf[SYMNMLEN] = '\0';
545	      name = buf;
546	    }
547
548	  if (! ((*info->callbacks->reloc_overflow)
549		 (info, name, howto_table[rel->r_type].name, (bfd_vma) 0,
550		  input_bfd, input_section,
551		  rel->r_vaddr - input_section->vma)))
552	    return FALSE;
553	}
554    }
555
556  return TRUE;
557}
558
559#define coff_relocate_section coff_a29k_relocate_section
560
561/* We don't want to change the symndx of a R_IHCONST reloc, since it
562   is actually an addend, not a symbol index at all.  */
563
564static bfd_boolean
565coff_a29k_adjust_symndx (obfd, info, ibfd, sec, irel, adjustedp)
566     bfd *obfd ATTRIBUTE_UNUSED;
567     struct bfd_link_info *info ATTRIBUTE_UNUSED;
568     bfd *ibfd ATTRIBUTE_UNUSED;
569     asection *sec ATTRIBUTE_UNUSED;
570     struct internal_reloc *irel;
571     bfd_boolean *adjustedp;
572{
573  if (irel->r_type == R_IHCONST)
574    *adjustedp = TRUE;
575  else
576    *adjustedp = FALSE;
577  return TRUE;
578}
579
580#define coff_adjust_symndx coff_a29k_adjust_symndx
581
582#include "coffcode.h"
583
584CREATE_BIG_COFF_TARGET_VEC (a29kcoff_big_vec, "coff-a29k-big", 0, SEC_READONLY, '_', NULL, COFF_SWAP_TABLE)
585