1/* BFD back-end for Intel 386 COFF files.
2   Copyright 1990, 1991, 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999,
3   2000, 2001, 2002, 2003
4   Free Software Foundation, Inc.
5   Written by Cygnus Support.
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#include "bfd.h"
24#include "sysdep.h"
25#include "libbfd.h"
26
27#include "coff/i386.h"
28
29#include "coff/internal.h"
30
31#ifdef COFF_WITH_PE
32#include "coff/pe.h"
33#endif
34
35#ifdef COFF_GO32_EXE
36#include "coff/go32exe.h"
37#endif
38
39#include "libcoff.h"
40
41static bfd_reloc_status_type coff_i386_reloc
42  PARAMS ((bfd *, arelent *, asymbol *, PTR, asection *, bfd *, char **));
43static reloc_howto_type *coff_i386_rtype_to_howto
44  PARAMS ((bfd *, asection *, struct internal_reloc *,
45	   struct coff_link_hash_entry *, struct internal_syment *,
46	   bfd_vma *));
47static reloc_howto_type *coff_i386_reloc_type_lookup
48  PARAMS ((bfd *, bfd_reloc_code_real_type));
49
50#define COFF_DEFAULT_SECTION_ALIGNMENT_POWER (2)
51/* The page size is a guess based on ELF.  */
52
53#define COFF_PAGE_SIZE 0x1000
54
55/* For some reason when using i386 COFF the value stored in the .text
56   section for a reference to a common symbol is the value itself plus
57   any desired offset.  Ian Taylor, Cygnus Support.  */
58
59/* If we are producing relocatable output, we need to do some
60   adjustments to the object file that are not done by the
61   bfd_perform_relocation function.  This function is called by every
62   reloc type to make any required adjustments.  */
63
64static bfd_reloc_status_type
65coff_i386_reloc (abfd, reloc_entry, symbol, data, input_section, output_bfd,
66		 error_message)
67     bfd *abfd;
68     arelent *reloc_entry;
69     asymbol *symbol;
70     PTR data;
71     asection *input_section ATTRIBUTE_UNUSED;
72     bfd *output_bfd;
73     char **error_message ATTRIBUTE_UNUSED;
74{
75  symvalue diff;
76
77#ifndef COFF_WITH_PE
78  if (output_bfd == (bfd *) NULL)
79    return bfd_reloc_continue;
80#endif
81
82  if (bfd_is_com_section (symbol->section))
83    {
84#ifndef COFF_WITH_PE
85      /* We are relocating a common symbol.  The current value in the
86	 object file is ORIG + OFFSET, where ORIG is the value of the
87	 common symbol as seen by the object file when it was compiled
88	 (this may be zero if the symbol was undefined) and OFFSET is
89	 the offset into the common symbol (normally zero, but may be
90	 non-zero when referring to a field in a common structure).
91	 ORIG is the negative of reloc_entry->addend, which is set by
92	 the CALC_ADDEND macro below.  We want to replace the value in
93	 the object file with NEW + OFFSET, where NEW is the value of
94	 the common symbol which we are going to put in the final
95	 object file.  NEW is symbol->value.  */
96      diff = symbol->value + reloc_entry->addend;
97#else
98      /* In PE mode, we do not offset the common symbol.  */
99      diff = reloc_entry->addend;
100#endif
101    }
102  else
103    {
104      /* For some reason bfd_perform_relocation always effectively
105	 ignores the addend for a COFF target when producing
106	 relocatable output.  This seems to be always wrong for 386
107	 COFF, so we handle the addend here instead.  */
108#ifdef COFF_WITH_PE
109      if (output_bfd == (bfd *) NULL)
110	{
111	  reloc_howto_type *howto = reloc_entry->howto;
112
113	  /* Although PC relative relocations are very similar between
114	     PE and non-PE formats, but they are off by 1 << howto->size
115	     bytes. For the external relocation, PE is very different
116	     from others. See md_apply_fix3 () in gas/config/tc-i386.c.
117	     When we link PE and non-PE object files together to
118	     generate a non-PE executable, we have to compensate it
119	     here.  */
120	  if (howto->pc_relative && howto->pcrel_offset)
121	    diff = -(1 << howto->size);
122	  else
123	    diff = -reloc_entry->addend;
124	}
125      else
126#endif
127	diff = reloc_entry->addend;
128    }
129
130#ifdef COFF_WITH_PE
131  /* FIXME: How should this case be handled?  */
132  if (reloc_entry->howto->type == R_IMAGEBASE
133      && output_bfd != NULL
134      && bfd_get_flavour(output_bfd) == bfd_target_coff_flavour)
135    diff -= pe_data (output_bfd)->pe_opthdr.ImageBase;
136#endif
137
138#define DOIT(x) \
139  x = ((x & ~howto->dst_mask) | (((x & howto->src_mask) + diff) & howto->dst_mask))
140
141    if (diff != 0)
142      {
143	reloc_howto_type *howto = reloc_entry->howto;
144	unsigned char *addr = (unsigned char *) data + reloc_entry->address;
145
146	switch (howto->size)
147	  {
148	  case 0:
149	    {
150	      char x = bfd_get_8 (abfd, addr);
151	      DOIT (x);
152	      bfd_put_8 (abfd, x, addr);
153	    }
154	    break;
155
156	  case 1:
157	    {
158	      short x = bfd_get_16 (abfd, addr);
159	      DOIT (x);
160	      bfd_put_16 (abfd, (bfd_vma) x, addr);
161	    }
162	    break;
163
164	  case 2:
165	    {
166	      long x = bfd_get_32 (abfd, addr);
167	      DOIT (x);
168	      bfd_put_32 (abfd, (bfd_vma) x, addr);
169	    }
170	    break;
171
172	  default:
173	    abort ();
174	  }
175      }
176
177  /* Now let bfd_perform_relocation finish everything up.  */
178  return bfd_reloc_continue;
179}
180
181#ifdef COFF_WITH_PE
182/* Return TRUE if this relocation should appear in the output .reloc
183   section.  */
184
185static bfd_boolean in_reloc_p PARAMS ((bfd *, reloc_howto_type *));
186
187static bfd_boolean in_reloc_p (abfd, howto)
188     bfd * abfd ATTRIBUTE_UNUSED;
189     reloc_howto_type *howto;
190{
191  return ! howto->pc_relative && howto->type != R_IMAGEBASE;
192}
193#endif /* COFF_WITH_PE */
194
195#ifndef PCRELOFFSET
196#define PCRELOFFSET FALSE
197#endif
198
199static reloc_howto_type howto_table[] =
200{
201  EMPTY_HOWTO (0),
202  EMPTY_HOWTO (1),
203  EMPTY_HOWTO (2),
204  EMPTY_HOWTO (3),
205  EMPTY_HOWTO (4),
206  EMPTY_HOWTO (5),
207  HOWTO (R_DIR32,		/* type */
208	 0,			/* rightshift */
209	 2,			/* size (0 = byte, 1 = short, 2 = long) */
210	 32,			/* bitsize */
211	 FALSE,			/* pc_relative */
212	 0,			/* bitpos */
213	 complain_overflow_bitfield, /* complain_on_overflow */
214	 coff_i386_reloc,	/* special_function */
215	 "dir32",		/* name */
216	 TRUE,			/* partial_inplace */
217	 0xffffffff,		/* src_mask */
218	 0xffffffff,		/* dst_mask */
219	 TRUE),			/* pcrel_offset */
220  /* PE IMAGE_REL_I386_DIR32NB relocation (7).	*/
221  HOWTO (R_IMAGEBASE,		/* type */
222	 0,			/* rightshift */
223	 2,			/* size (0 = byte, 1 = short, 2 = long) */
224	 32,			/* bitsize */
225	 FALSE,			/* pc_relative */
226	 0,			/* bitpos */
227	 complain_overflow_bitfield, /* complain_on_overflow */
228	 coff_i386_reloc,	/* special_function */
229	 "rva32",		/* name */
230	 TRUE,			/* partial_inplace */
231	 0xffffffff,		/* src_mask */
232	 0xffffffff,		/* dst_mask */
233	 FALSE),		/* pcrel_offset */
234  EMPTY_HOWTO (010),
235  EMPTY_HOWTO (011),
236  EMPTY_HOWTO (012),
237  EMPTY_HOWTO (013),
238  EMPTY_HOWTO (014),
239  EMPTY_HOWTO (015),
240  EMPTY_HOWTO (016),
241  /* Byte relocation (017).  */
242  HOWTO (R_RELBYTE,		/* type */
243	 0,			/* rightshift */
244	 0,			/* size (0 = byte, 1 = short, 2 = long) */
245	 8,			/* bitsize */
246	 FALSE,			/* pc_relative */
247	 0,			/* bitpos */
248	 complain_overflow_bitfield, /* complain_on_overflow */
249	 coff_i386_reloc,	/* special_function */
250	 "8",			/* name */
251	 TRUE,			/* partial_inplace */
252	 0x000000ff,		/* src_mask */
253	 0x000000ff,		/* dst_mask */
254	 PCRELOFFSET),		/* pcrel_offset */
255  /* 16-bit word relocation (020).  */
256  HOWTO (R_RELWORD,		/* type */
257	 0,			/* rightshift */
258	 1,			/* size (0 = byte, 1 = short, 2 = long) */
259	 16,			/* bitsize */
260	 FALSE,			/* pc_relative */
261	 0,			/* bitpos */
262	 complain_overflow_bitfield, /* complain_on_overflow */
263	 coff_i386_reloc,	/* special_function */
264	 "16",			/* name */
265	 TRUE,			/* partial_inplace */
266	 0x0000ffff,		/* src_mask */
267	 0x0000ffff,		/* dst_mask */
268	 PCRELOFFSET),		/* pcrel_offset */
269  /* 32-bit longword relocation (021).	*/
270  HOWTO (R_RELLONG,		/* type */
271	 0,			/* rightshift */
272	 2,			/* size (0 = byte, 1 = short, 2 = long) */
273	 32,			/* bitsize */
274	 FALSE,			/* pc_relative */
275	 0,			/* bitpos */
276	 complain_overflow_bitfield, /* complain_on_overflow */
277	 coff_i386_reloc,	/* special_function */
278	 "32",			/* name */
279	 TRUE,			/* partial_inplace */
280	 0xffffffff,		/* src_mask */
281	 0xffffffff,		/* dst_mask */
282	 PCRELOFFSET),		/* pcrel_offset */
283  /* Byte PC relative relocation (022).	 */
284  HOWTO (R_PCRBYTE,		/* type */
285	 0,			/* rightshift */
286	 0,			/* size (0 = byte, 1 = short, 2 = long) */
287	 8,			/* bitsize */
288	 TRUE,			/* pc_relative */
289	 0,			/* bitpos */
290	 complain_overflow_signed, /* complain_on_overflow */
291	 coff_i386_reloc,	/* special_function */
292	 "DISP8",		/* name */
293	 TRUE,			/* partial_inplace */
294	 0x000000ff,		/* src_mask */
295	 0x000000ff,		/* dst_mask */
296	 PCRELOFFSET),		/* pcrel_offset */
297  /* 16-bit word PC relative relocation (023).	*/
298  HOWTO (R_PCRWORD,		/* type */
299	 0,			/* rightshift */
300	 1,			/* size (0 = byte, 1 = short, 2 = long) */
301	 16,			/* bitsize */
302	 TRUE,			/* pc_relative */
303	 0,			/* bitpos */
304	 complain_overflow_signed, /* complain_on_overflow */
305	 coff_i386_reloc,	/* special_function */
306	 "DISP16",		/* name */
307	 TRUE,			/* partial_inplace */
308	 0x0000ffff,		/* src_mask */
309	 0x0000ffff,		/* dst_mask */
310	 PCRELOFFSET),		/* pcrel_offset */
311  /* 32-bit longword PC relative relocation (024).  */
312  HOWTO (R_PCRLONG,		/* type */
313	 0,			/* rightshift */
314	 2,			/* size (0 = byte, 1 = short, 2 = long) */
315	 32,			/* bitsize */
316	 TRUE,			/* pc_relative */
317	 0,			/* bitpos */
318	 complain_overflow_signed, /* complain_on_overflow */
319	 coff_i386_reloc,	/* special_function */
320	 "DISP32",		/* name */
321	 TRUE,			/* partial_inplace */
322	 0xffffffff,		/* src_mask */
323	 0xffffffff,		/* dst_mask */
324	 PCRELOFFSET)		/* pcrel_offset */
325};
326
327/* Turn a howto into a reloc  nunmber */
328
329#define SELECT_RELOC(x,howto) { x.r_type = howto->type; }
330#define BADMAG(x) I386BADMAG(x)
331#define I386 1			/* Customize coffcode.h */
332
333#define RTYPE2HOWTO(cache_ptr, dst)					\
334  ((cache_ptr)->howto =							\
335   ((dst)->r_type < sizeof (howto_table) / sizeof (howto_table[0])	\
336    ? howto_table + (dst)->r_type					\
337    : NULL))
338
339/* For 386 COFF a STYP_NOLOAD | STYP_BSS section is part of a shared
340   library.  On some other COFF targets STYP_BSS is normally
341   STYP_NOLOAD.  */
342#define BSS_NOLOAD_IS_SHARED_LIBRARY
343
344/* Compute the addend of a reloc.  If the reloc is to a common symbol,
345   the object file contains the value of the common symbol.  By the
346   time this is called, the linker may be using a different symbol
347   from a different object file with a different value.  Therefore, we
348   hack wildly to locate the original symbol from this file so that we
349   can make the correct adjustment.  This macro sets coffsym to the
350   symbol from the original file, and uses it to set the addend value
351   correctly.  If this is not a common symbol, the usual addend
352   calculation is done, except that an additional tweak is needed for
353   PC relative relocs.
354   FIXME: This macro refers to symbols and asect; these are from the
355   calling function, not the macro arguments.  */
356
357#define CALC_ADDEND(abfd, ptr, reloc, cache_ptr)		\
358  {								\
359    coff_symbol_type *coffsym = (coff_symbol_type *) NULL;	\
360    if (ptr && bfd_asymbol_bfd (ptr) != abfd)			\
361      coffsym = (obj_symbols (abfd)				\
362	         + (cache_ptr->sym_ptr_ptr - symbols));		\
363    else if (ptr)						\
364      coffsym = coff_symbol_from (abfd, ptr);			\
365    if (coffsym != (coff_symbol_type *) NULL			\
366	&& coffsym->native->u.syment.n_scnum == 0)		\
367      cache_ptr->addend = - coffsym->native->u.syment.n_value;	\
368    else if (ptr && bfd_asymbol_bfd (ptr) == abfd		\
369	     && ptr->section != (asection *) NULL)		\
370      cache_ptr->addend = - (ptr->section->vma + ptr->value);	\
371    else							\
372      cache_ptr->addend = 0;					\
373    if (ptr && howto_table[reloc.r_type].pc_relative)		\
374      cache_ptr->addend += asect->vma;				\
375  }
376
377/* We use the special COFF backend linker.  For normal i386 COFF, we
378   can use the generic relocate_section routine.  For PE, we need our
379   own routine.  */
380
381#ifndef COFF_WITH_PE
382
383#define coff_relocate_section _bfd_coff_generic_relocate_section
384
385#else /* COFF_WITH_PE */
386
387/* The PE relocate section routine.  The only difference between this
388   and the regular routine is that we don't want to do anything for a
389   relocatable link.  */
390
391static bfd_boolean coff_pe_i386_relocate_section
392  PARAMS ((bfd *, struct bfd_link_info *, bfd *, asection *, bfd_byte *,
393	   struct internal_reloc *, struct internal_syment *, asection **));
394
395static bfd_boolean
396coff_pe_i386_relocate_section (output_bfd, info, input_bfd,
397			       input_section, contents, relocs, syms,
398			       sections)
399     bfd *output_bfd;
400     struct bfd_link_info *info;
401     bfd *input_bfd;
402     asection *input_section;
403     bfd_byte *contents;
404     struct internal_reloc *relocs;
405     struct internal_syment *syms;
406     asection **sections;
407{
408  if (info->relocatable)
409    return TRUE;
410
411  return _bfd_coff_generic_relocate_section (output_bfd, info, input_bfd,
412					     input_section, contents,
413					     relocs, syms, sections);
414}
415
416#define coff_relocate_section coff_pe_i386_relocate_section
417
418#endif /* COFF_WITH_PE */
419
420/* Convert an rtype to howto for the COFF backend linker.  */
421
422static reloc_howto_type *
423coff_i386_rtype_to_howto (abfd, sec, rel, h, sym, addendp)
424     bfd *abfd ATTRIBUTE_UNUSED;
425     asection *sec;
426     struct internal_reloc *rel;
427     struct coff_link_hash_entry *h;
428     struct internal_syment *sym;
429     bfd_vma *addendp;
430{
431  reloc_howto_type *howto;
432
433  if (rel->r_type > sizeof (howto_table) / sizeof (howto_table[0]))
434    {
435      bfd_set_error (bfd_error_bad_value);
436      return NULL;
437    }
438
439  howto = howto_table + rel->r_type;
440
441#ifdef COFF_WITH_PE
442  /* Cancel out code in _bfd_coff_generic_relocate_section.  */
443  *addendp = 0;
444#endif
445
446  if (howto->pc_relative)
447    *addendp += sec->vma;
448
449  if (sym != NULL && sym->n_scnum == 0 && sym->n_value != 0)
450    {
451      /* This is a common symbol.  The section contents include the
452	 size (sym->n_value) as an addend.  The relocate_section
453	 function will be adding in the final value of the symbol.  We
454	 need to subtract out the current size in order to get the
455	 correct result.  */
456
457      BFD_ASSERT (h != NULL);
458
459#ifndef COFF_WITH_PE
460      /* I think we *do* want to bypass this.  If we don't, I have
461	 seen some data parameters get the wrong relocation address.
462	 If I link two versions with and without this section bypassed
463	 and then do a binary comparison, the addresses which are
464	 different can be looked up in the map.  The case in which
465	 this section has been bypassed has addresses which correspond
466	 to values I can find in the map.  */
467      *addendp -= sym->n_value;
468#endif
469    }
470
471#ifndef COFF_WITH_PE
472  /* If the output symbol is common (in which case this must be a
473     relocatable link), we need to add in the final size of the
474     common symbol.  */
475  if (h != NULL && h->root.type == bfd_link_hash_common)
476    *addendp += h->root.u.c.size;
477#endif
478
479#ifdef COFF_WITH_PE
480  if (howto->pc_relative)
481    {
482      *addendp -= 4;
483
484      /* If the symbol is defined, then the generic code is going to
485         add back the symbol value in order to cancel out an
486         adjustment it made to the addend.  However, we set the addend
487         to 0 at the start of this function.  We need to adjust here,
488         to avoid the adjustment the generic code will make.  FIXME:
489         This is getting a bit hackish.  */
490      if (sym != NULL && sym->n_scnum != 0)
491	*addendp -= sym->n_value;
492    }
493
494  if (rel->r_type == R_IMAGEBASE
495      && (bfd_get_flavour(sec->output_section->owner)
496	  == bfd_target_coff_flavour))
497    {
498      *addendp -= pe_data(sec->output_section->owner)->pe_opthdr.ImageBase;
499    }
500#endif
501
502  return howto;
503}
504
505#define coff_bfd_reloc_type_lookup coff_i386_reloc_type_lookup
506
507static reloc_howto_type *
508coff_i386_reloc_type_lookup (abfd, code)
509     bfd *abfd ATTRIBUTE_UNUSED;
510     bfd_reloc_code_real_type code;
511{
512  switch (code)
513    {
514    case BFD_RELOC_RVA:
515      return howto_table + R_IMAGEBASE;
516    case BFD_RELOC_32:
517      return howto_table + R_DIR32;
518    case BFD_RELOC_32_PCREL:
519      return howto_table + R_PCRLONG;
520    case BFD_RELOC_16:
521      return howto_table + R_RELWORD;
522    case BFD_RELOC_16_PCREL:
523      return howto_table + R_PCRWORD;
524    case BFD_RELOC_8:
525      return howto_table + R_RELBYTE;
526    case BFD_RELOC_8_PCREL:
527      return howto_table + R_PCRBYTE;
528    default:
529      BFD_FAIL ();
530      return 0;
531    }
532}
533
534#define coff_rtype_to_howto coff_i386_rtype_to_howto
535
536#ifdef TARGET_UNDERSCORE
537
538/* If i386 gcc uses underscores for symbol names, then it does not use
539   a leading dot for local labels, so if TARGET_UNDERSCORE is defined
540   we treat all symbols starting with L as local.  */
541
542static bfd_boolean coff_i386_is_local_label_name
543  PARAMS ((bfd *, const char *));
544
545static bfd_boolean
546coff_i386_is_local_label_name (abfd, name)
547     bfd *abfd;
548     const char *name;
549{
550  if (name[0] == 'L')
551    return TRUE;
552
553  return _bfd_coff_is_local_label_name (abfd, name);
554}
555
556#define coff_bfd_is_local_label_name coff_i386_is_local_label_name
557
558#endif /* TARGET_UNDERSCORE */
559
560#include "coffcode.h"
561
562const bfd_target
563#ifdef TARGET_SYM
564  TARGET_SYM =
565#else
566  i386coff_vec =
567#endif
568{
569#ifdef TARGET_NAME
570  TARGET_NAME,
571#else
572  "coff-i386",			/* name */
573#endif
574  bfd_target_coff_flavour,
575  BFD_ENDIAN_LITTLE,		/* data byte order is little */
576  BFD_ENDIAN_LITTLE,		/* header byte order is little */
577
578  (HAS_RELOC | EXEC_P |		/* object flags */
579   HAS_LINENO | HAS_DEBUG |
580   HAS_SYMS | HAS_LOCALS | WP_TEXT | D_PAGED),
581
582  (SEC_HAS_CONTENTS | SEC_ALLOC | SEC_LOAD | SEC_RELOC /* section flags */
583#ifdef COFF_WITH_PE
584   | SEC_LINK_ONCE | SEC_LINK_DUPLICATES | SEC_READONLY
585#endif
586   | SEC_CODE | SEC_DATA),
587
588#ifdef TARGET_UNDERSCORE
589  TARGET_UNDERSCORE,		/* leading underscore */
590#else
591  0,				/* leading underscore */
592#endif
593  '/',				/* ar_pad_char */
594  15,				/* ar_max_namelen */
595
596  bfd_getl64, bfd_getl_signed_64, bfd_putl64,
597     bfd_getl32, bfd_getl_signed_32, bfd_putl32,
598     bfd_getl16, bfd_getl_signed_16, bfd_putl16, /* data */
599  bfd_getl64, bfd_getl_signed_64, bfd_putl64,
600     bfd_getl32, bfd_getl_signed_32, bfd_putl32,
601     bfd_getl16, bfd_getl_signed_16, bfd_putl16, /* hdrs */
602
603/* Note that we allow an object file to be treated as a core file as well.  */
604    {_bfd_dummy_target, coff_object_p, /* bfd_check_format */
605       bfd_generic_archive_p, coff_object_p},
606    {bfd_false, coff_mkobject, _bfd_generic_mkarchive, /* bfd_set_format */
607       bfd_false},
608    {bfd_false, coff_write_object_contents, /* bfd_write_contents */
609       _bfd_write_archive_contents, bfd_false},
610
611     BFD_JUMP_TABLE_GENERIC (coff),
612     BFD_JUMP_TABLE_COPY (coff),
613     BFD_JUMP_TABLE_CORE (_bfd_nocore),
614     BFD_JUMP_TABLE_ARCHIVE (_bfd_archive_coff),
615     BFD_JUMP_TABLE_SYMBOLS (coff),
616     BFD_JUMP_TABLE_RELOCS (coff),
617     BFD_JUMP_TABLE_WRITE (coff),
618     BFD_JUMP_TABLE_LINK (coff),
619     BFD_JUMP_TABLE_DYNAMIC (_bfd_nodynamic),
620
621  NULL,
622
623  COFF_SWAP_TABLE
624};
625