PR binutils/15834
[external/binutils.git] / bfd / elfnn-aarch64.c
1 /* AArch64-specific support for NN-bit ELF.
2    Copyright 2009-2013  Free Software Foundation, Inc.
3    Contributed by ARM Ltd.
4
5    This file is part of BFD, the Binary File Descriptor library.
6
7    This program is free software; you can redistribute it and/or modify
8    it under the terms of the GNU General Public License as published by
9    the Free Software Foundation; either version 3 of the License, or
10    (at your option) any later version.
11
12    This program is distributed in the hope that it will be useful,
13    but WITHOUT ANY WARRANTY; without even the implied warranty of
14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15    GNU General Public License for more details.
16
17    You should have received a copy of the GNU General Public License
18    along with this program; see the file COPYING3. If not,
19    see <http://www.gnu.org/licenses/>.  */
20
21 /* Notes on implementation:
22
23   Thread Local Store (TLS)
24
25   Overview:
26
27   The implementation currently supports both traditional TLS and TLS
28   descriptors, but only general dynamic (GD).
29
30   For traditional TLS the assembler will present us with code
31   fragments of the form:
32
33   adrp x0, :tlsgd:foo
34                            R_AARCH64_TLSGD_ADR_PAGE21(foo)
35   add  x0, :tlsgd_lo12:foo
36                            R_AARCH64_TLSGD_ADD_LO12_NC(foo)
37   bl   __tls_get_addr
38   nop
39
40   For TLS descriptors the assembler will present us with code
41   fragments of the form:
42
43   adrp  x0, :tlsdesc:foo                      R_AARCH64_TLSDESC_ADR_PAGE21(foo)
44   ldr   x1, [x0, #:tlsdesc_lo12:foo]          R_AARCH64_TLSDESC_LD64_LO12(foo)
45   add   x0, x0, #:tlsdesc_lo12:foo            R_AARCH64_TLSDESC_ADD_LO12(foo)
46   .tlsdesccall foo
47   blr   x1                                    R_AARCH64_TLSDESC_CALL(foo)
48
49   The relocations R_AARCH64_TLSGD_{ADR_PREL21,ADD_LO12_NC} against foo
50   indicate that foo is thread local and should be accessed via the
51   traditional TLS mechanims.
52
53   The relocations R_AARCH64_TLSDESC_{ADR_PAGE21,LD64_LO12_NC,ADD_LO12_NC}
54   against foo indicate that 'foo' is thread local and should be accessed
55   via a TLS descriptor mechanism.
56
57   The precise instruction sequence is only relevant from the
58   perspective of linker relaxation which is currently not implemented.
59
60   The static linker must detect that 'foo' is a TLS object and
61   allocate a double GOT entry. The GOT entry must be created for both
62   global and local TLS symbols. Note that this is different to none
63   TLS local objects which do not need a GOT entry.
64
65   In the traditional TLS mechanism, the double GOT entry is used to
66   provide the tls_index structure, containing module and offset
67   entries. The static linker places the relocation R_AARCH64_TLS_DTPMOD
68   on the module entry. The loader will subsequently fixup this
69   relocation with the module identity.
70
71   For global traditional TLS symbols the static linker places an
72   R_AARCH64_TLS_DTPREL relocation on the offset entry. The loader
73   will subsequently fixup the offset. For local TLS symbols the static
74   linker fixes up offset.
75
76   In the TLS descriptor mechanism the double GOT entry is used to
77   provide the descriptor. The static linker places the relocation
78   R_AARCH64_TLSDESC on the first GOT slot. The loader will
79   subsequently fix this up.
80
81   Implementation:
82
83   The handling of TLS symbols is implemented across a number of
84   different backend functions. The following is a top level view of
85   what processing is performed where.
86
87   The TLS implementation maintains state information for each TLS
88   symbol. The state information for local and global symbols is kept
89   in different places. Global symbols use generic BFD structures while
90   local symbols use backend specific structures that are allocated and
91   maintained entirely by the backend.
92
93   The flow:
94
95   elfNN_aarch64_check_relocs()
96
97   This function is invoked for each relocation.
98
99   The TLS relocations R_AARCH64_TLSGD_{ADR_PREL21,ADD_LO12_NC} and
100   R_AARCH64_TLSDESC_{ADR_PAGE21,LD64_LO12_NC,ADD_LO12_NC} are
101   spotted. One time creation of local symbol data structures are
102   created when the first local symbol is seen.
103
104   The reference count for a symbol is incremented.  The GOT type for
105   each symbol is marked as general dynamic.
106
107   elfNN_aarch64_allocate_dynrelocs ()
108
109   For each global with positive reference count we allocate a double
110   GOT slot. For a traditional TLS symbol we allocate space for two
111   relocation entries on the GOT, for a TLS descriptor symbol we
112   allocate space for one relocation on the slot. Record the GOT offset
113   for this symbol.
114
115   elfNN_aarch64_size_dynamic_sections ()
116
117   Iterate all input BFDS, look for in the local symbol data structure
118   constructed earlier for local TLS symbols and allocate them double
119   GOT slots along with space for a single GOT relocation. Update the
120   local symbol structure to record the GOT offset allocated.
121
122   elfNN_aarch64_relocate_section ()
123
124   Calls elfNN_aarch64_final_link_relocate ()
125
126   Emit the relevant TLS relocations against the GOT for each TLS
127   symbol. For local TLS symbols emit the GOT offset directly. The GOT
128   relocations are emitted once the first time a TLS symbol is
129   encountered. The implementation uses the LSB of the GOT offset to
130   flag that the relevant GOT relocations for a symbol have been
131   emitted. All of the TLS code that uses the GOT offset needs to take
132   care to mask out this flag bit before using the offset.
133
134   elfNN_aarch64_final_link_relocate ()
135
136   Fixup the R_AARCH64_TLSGD_{ADR_PREL21, ADD_LO12_NC} relocations.  */
137
138 #include "sysdep.h"
139 #include "bfd.h"
140 #include "libiberty.h"
141 #include "libbfd.h"
142 #include "bfd_stdint.h"
143 #include "elf-bfd.h"
144 #include "bfdlink.h"
145 #include "elf/aarch64.h"
146 #include "elfxx-aarch64.h"
147
148 #define ARCH_SIZE       NN
149
150 #if ARCH_SIZE == 64
151 #define AARCH64_R(NAME)         R_AARCH64_ ## NAME
152 #define AARCH64_R_STR(NAME)     "R_AARCH64_" #NAME
153 #define HOWTO64(...)            HOWTO (__VA_ARGS__)
154 #define HOWTO32(...)            EMPTY_HOWTO (0)
155 #define LOG_FILE_ALIGN  3
156 #endif
157
158 #if ARCH_SIZE == 32
159 #define AARCH64_R(NAME)         R_AARCH64_P32_ ## NAME
160 #define AARCH64_R_STR(NAME)     "R_AARCH64_P32_" #NAME
161 #define HOWTO64(...)            EMPTY_HOWTO (0)
162 #define HOWTO32(...)            HOWTO (__VA_ARGS__)
163 #define LOG_FILE_ALIGN  2
164 #endif
165
166 #define IS_AARCH64_TLS_RELOC(R_TYPE)                            \
167   ((R_TYPE) == BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21               \
168    || (R_TYPE) == BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC           \
169    || (R_TYPE) == BFD_RELOC_AARCH64_TLSIE_MOVW_GOTTPREL_G1      \
170    || (R_TYPE) == BFD_RELOC_AARCH64_TLSIE_MOVW_GOTTPREL_G0_NC   \
171    || (R_TYPE) == BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21   \
172    || (R_TYPE) == BFD_RELOC_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC \
173    || (R_TYPE) == BFD_RELOC_AARCH64_TLSIE_LD32_GOTTPREL_LO12_NC \
174    || (R_TYPE) == BFD_RELOC_AARCH64_TLSIE_LD_GOTTPREL_PREL19    \
175    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12        \
176    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_HI12        \
177    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12_NC     \
178    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G2         \
179    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1         \
180    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1_NC      \
181    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0         \
182    || (R_TYPE) == BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC      \
183    || (R_TYPE) == BFD_RELOC_AARCH64_TLS_DTPMOD                  \
184    || (R_TYPE) == BFD_RELOC_AARCH64_TLS_DTPREL                  \
185    || (R_TYPE) == BFD_RELOC_AARCH64_TLS_TPREL                   \
186    || IS_AARCH64_TLSDESC_RELOC ((R_TYPE)))
187
188 #define IS_AARCH64_TLSDESC_RELOC(R_TYPE)                        \
189   ((R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_LD_PREL19              \
190    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_ADR_PREL21          \
191    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21          \
192    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC         \
193    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_LD64_LO12_NC        \
194    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_LD32_LO12_NC        \
195    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_OFF_G1              \
196    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_OFF_G0_NC           \
197    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_LDR                 \
198    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_ADD                 \
199    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC_CALL                \
200    || (R_TYPE) == BFD_RELOC_AARCH64_TLSDESC)
201
202 #define ELIMINATE_COPY_RELOCS 0
203
204 /* Return size of a relocation entry.  HTAB is the bfd's
205    elf_aarch64_link_hash_entry.  */
206 #define RELOC_SIZE(HTAB) (sizeof (ElfNN_External_Rela))
207
208 /* GOT Entry size - 8 bytes in ELF64 and 4 bytes in ELF32.  */
209 #define GOT_ENTRY_SIZE                  (ARCH_SIZE / 8)
210 #define PLT_ENTRY_SIZE                  (32)
211 #define PLT_SMALL_ENTRY_SIZE            (16)
212 #define PLT_TLSDESC_ENTRY_SIZE          (32)
213
214 /* Encoding of the nop instruction */
215 #define INSN_NOP 0xd503201f
216
217 #define aarch64_compute_jump_table_size(htab)           \
218   (((htab)->root.srelplt == NULL) ? 0                   \
219    : (htab)->root.srelplt->reloc_count * GOT_ENTRY_SIZE)
220
221 /* The first entry in a procedure linkage table looks like this
222    if the distance between the PLTGOT and the PLT is < 4GB use
223    these PLT entries. Note that the dynamic linker gets &PLTGOT[2]
224    in x16 and needs to work out PLTGOT[1] by using an address of
225    [x16,#-GOT_ENTRY_SIZE].  */
226 static const bfd_byte elfNN_aarch64_small_plt0_entry[PLT_ENTRY_SIZE] =
227 {
228   0xf0, 0x7b, 0xbf, 0xa9,       /* stp x16, x30, [sp, #-16]!  */
229   0x10, 0x00, 0x00, 0x90,       /* adrp x16, (GOT+16)  */
230 #if ARCH_SIZE == 64
231   0x11, 0x0A, 0x40, 0xf9,       /* ldr x17, [x16, #PLT_GOT+0x10]  */
232   0x10, 0x42, 0x00, 0x91,       /* add x16, x16,#PLT_GOT+0x10   */
233 #else
234   0x11, 0x0A, 0x40, 0xb9,       /* ldr w17, [x16, #PLT_GOT+0x8]  */
235   0x10, 0x22, 0x00, 0x11,       /* add w16, w16,#PLT_GOT+0x8   */
236 #endif
237   0x20, 0x02, 0x1f, 0xd6,       /* br x17  */
238   0x1f, 0x20, 0x03, 0xd5,       /* nop */
239   0x1f, 0x20, 0x03, 0xd5,       /* nop */
240   0x1f, 0x20, 0x03, 0xd5,       /* nop */
241 };
242
243 /* Per function entry in a procedure linkage table looks like this
244    if the distance between the PLTGOT and the PLT is < 4GB use
245    these PLT entries.  */
246 static const bfd_byte elfNN_aarch64_small_plt_entry[PLT_SMALL_ENTRY_SIZE] =
247 {
248   0x10, 0x00, 0x00, 0x90,       /* adrp x16, PLTGOT + n * 8  */
249 #if ARCH_SIZE == 64
250   0x11, 0x02, 0x40, 0xf9,       /* ldr x17, [x16, PLTGOT + n * 8] */
251   0x10, 0x02, 0x00, 0x91,       /* add x16, x16, :lo12:PLTGOT + n * 8  */
252 #else
253   0x11, 0x02, 0x40, 0xb9,       /* ldr w17, [x16, PLTGOT + n * 4] */
254   0x10, 0x02, 0x00, 0x11,       /* add w16, w16, :lo12:PLTGOT + n * 4  */
255 #endif
256   0x20, 0x02, 0x1f, 0xd6,       /* br x17.  */
257 };
258
259 static const bfd_byte
260 elfNN_aarch64_tlsdesc_small_plt_entry[PLT_TLSDESC_ENTRY_SIZE] =
261 {
262   0xe2, 0x0f, 0xbf, 0xa9,       /* stp x2, x3, [sp, #-16]! */
263   0x02, 0x00, 0x00, 0x90,       /* adrp x2, 0 */
264   0x03, 0x00, 0x00, 0x90,       /* adrp x3, 0 */
265 #if ARCH_SIZE == 64
266   0x42, 0x00, 0x40, 0xf9,       /* ldr x2, [x2, #0] */
267   0x63, 0x00, 0x00, 0x91,       /* add x3, x3, 0 */
268 #else
269   0x42, 0x00, 0x40, 0xb9,       /* ldr w2, [x2, #0] */
270   0x63, 0x00, 0x00, 0x11,       /* add w3, w3, 0 */
271 #endif
272   0x40, 0x00, 0x1f, 0xd6,       /* br x2 */
273   0x1f, 0x20, 0x03, 0xd5,       /* nop */
274   0x1f, 0x20, 0x03, 0xd5,       /* nop */
275 };
276
277 #define elf_info_to_howto               elfNN_aarch64_info_to_howto
278 #define elf_info_to_howto_rel           elfNN_aarch64_info_to_howto
279
280 #define AARCH64_ELF_ABI_VERSION         0
281
282 /* In case we're on a 32-bit machine, construct a 64-bit "-1" value.  */
283 #define ALL_ONES (~ (bfd_vma) 0)
284
285 /* Indexed by the bfd interal reloc enumerators.
286    Therefore, the table needs to be synced with BFD_RELOC_AARCH64_*
287    in reloc.c.   */
288
289 static reloc_howto_type elfNN_aarch64_howto_table[] =
290 {
291   EMPTY_HOWTO (0),
292
293   /* Basic data relocations.  */
294
295 #if ARCH_SIZE == 64
296   HOWTO (R_AARCH64_NULL,        /* type */
297          0,                     /* rightshift */
298          0,                     /* size (0 = byte, 1 = short, 2 = long) */
299          0,                     /* bitsize */
300          FALSE,                 /* pc_relative */
301          0,                     /* bitpos */
302          complain_overflow_dont,        /* complain_on_overflow */
303          bfd_elf_generic_reloc, /* special_function */
304          "R_AARCH64_NULL",      /* name */
305          FALSE,                 /* partial_inplace */
306          0,                     /* src_mask */
307          0,                     /* dst_mask */
308          FALSE),                /* pcrel_offset */
309 #else
310   HOWTO (R_AARCH64_NONE,        /* type */
311          0,                     /* rightshift */
312          0,                     /* size (0 = byte, 1 = short, 2 = long) */
313          0,                     /* bitsize */
314          FALSE,                 /* pc_relative */
315          0,                     /* bitpos */
316          complain_overflow_dont,        /* complain_on_overflow */
317          bfd_elf_generic_reloc, /* special_function */
318          "R_AARCH64_NONE",      /* name */
319          FALSE,                 /* partial_inplace */
320          0,                     /* src_mask */
321          0,                     /* dst_mask */
322          FALSE),                /* pcrel_offset */
323 #endif
324
325   /* .xword: (S+A) */
326   HOWTO64 (AARCH64_R (ABS64),   /* type */
327          0,                     /* rightshift */
328          4,                     /* size (4 = long long) */
329          64,                    /* bitsize */
330          FALSE,                 /* pc_relative */
331          0,                     /* bitpos */
332          complain_overflow_unsigned,    /* complain_on_overflow */
333          bfd_elf_generic_reloc, /* special_function */
334          AARCH64_R_STR (ABS64), /* name */
335          FALSE,                 /* partial_inplace */
336          ALL_ONES,              /* src_mask */
337          ALL_ONES,              /* dst_mask */
338          FALSE),                /* pcrel_offset */
339
340   /* .word: (S+A) */
341   HOWTO (AARCH64_R (ABS32),     /* type */
342          0,                     /* rightshift */
343          2,                     /* size (0 = byte, 1 = short, 2 = long) */
344          32,                    /* bitsize */
345          FALSE,                 /* pc_relative */
346          0,                     /* bitpos */
347          complain_overflow_unsigned,    /* complain_on_overflow */
348          bfd_elf_generic_reloc, /* special_function */
349          AARCH64_R_STR (ABS32), /* name */
350          FALSE,                 /* partial_inplace */
351          0xffffffff,            /* src_mask */
352          0xffffffff,            /* dst_mask */
353          FALSE),                /* pcrel_offset */
354
355   /* .half:  (S+A) */
356   HOWTO (AARCH64_R (ABS16),     /* type */
357          0,                     /* rightshift */
358          1,                     /* size (0 = byte, 1 = short, 2 = long) */
359          16,                    /* bitsize */
360          FALSE,                 /* pc_relative */
361          0,                     /* bitpos */
362          complain_overflow_unsigned,    /* complain_on_overflow */
363          bfd_elf_generic_reloc, /* special_function */
364          AARCH64_R_STR (ABS16), /* name */
365          FALSE,                 /* partial_inplace */
366          0xffff,                /* src_mask */
367          0xffff,                /* dst_mask */
368          FALSE),                /* pcrel_offset */
369
370   /* .xword: (S+A-P) */
371   HOWTO64 (AARCH64_R (PREL64),  /* type */
372          0,                     /* rightshift */
373          4,                     /* size (4 = long long) */
374          64,                    /* bitsize */
375          TRUE,                  /* pc_relative */
376          0,                     /* bitpos */
377          complain_overflow_signed,      /* complain_on_overflow */
378          bfd_elf_generic_reloc, /* special_function */
379          AARCH64_R_STR (PREL64),        /* name */
380          FALSE,                 /* partial_inplace */
381          ALL_ONES,              /* src_mask */
382          ALL_ONES,              /* dst_mask */
383          TRUE),                 /* pcrel_offset */
384
385   /* .word: (S+A-P) */
386   HOWTO (AARCH64_R (PREL32),    /* type */
387          0,                     /* rightshift */
388          2,                     /* size (0 = byte, 1 = short, 2 = long) */
389          32,                    /* bitsize */
390          TRUE,                  /* pc_relative */
391          0,                     /* bitpos */
392          complain_overflow_signed,      /* complain_on_overflow */
393          bfd_elf_generic_reloc, /* special_function */
394          AARCH64_R_STR (PREL32),        /* name */
395          FALSE,                 /* partial_inplace */
396          0xffffffff,            /* src_mask */
397          0xffffffff,            /* dst_mask */
398          TRUE),                 /* pcrel_offset */
399
400   /* .half: (S+A-P) */
401   HOWTO (AARCH64_R (PREL16),    /* type */
402          0,                     /* rightshift */
403          1,                     /* size (0 = byte, 1 = short, 2 = long) */
404          16,                    /* bitsize */
405          TRUE,                  /* pc_relative */
406          0,                     /* bitpos */
407          complain_overflow_signed,      /* complain_on_overflow */
408          bfd_elf_generic_reloc, /* special_function */
409          AARCH64_R_STR (PREL16),        /* name */
410          FALSE,                 /* partial_inplace */
411          0xffff,                /* src_mask */
412          0xffff,                /* dst_mask */
413          TRUE),                 /* pcrel_offset */
414
415   /* Group relocations to create a 16, 32, 48 or 64 bit
416      unsigned data or abs address inline.  */
417
418   /* MOVZ:   ((S+A) >>  0) & 0xffff */
419   HOWTO (AARCH64_R (MOVW_UABS_G0),      /* type */
420          0,                     /* rightshift */
421          2,                     /* size (0 = byte, 1 = short, 2 = long) */
422          16,                    /* bitsize */
423          FALSE,                 /* pc_relative */
424          0,                     /* bitpos */
425          complain_overflow_unsigned,    /* complain_on_overflow */
426          bfd_elf_generic_reloc, /* special_function */
427          AARCH64_R_STR (MOVW_UABS_G0),  /* name */
428          FALSE,                 /* partial_inplace */
429          0xffff,                /* src_mask */
430          0xffff,                /* dst_mask */
431          FALSE),                /* pcrel_offset */
432
433   /* MOVK:   ((S+A) >>  0) & 0xffff [no overflow check] */
434   HOWTO (AARCH64_R (MOVW_UABS_G0_NC),   /* type */
435          0,                     /* rightshift */
436          2,                     /* size (0 = byte, 1 = short, 2 = long) */
437          16,                    /* bitsize */
438          FALSE,                 /* pc_relative */
439          0,                     /* bitpos */
440          complain_overflow_dont,        /* complain_on_overflow */
441          bfd_elf_generic_reloc, /* special_function */
442          AARCH64_R_STR (MOVW_UABS_G0_NC),       /* name */
443          FALSE,                 /* partial_inplace */
444          0xffff,                /* src_mask */
445          0xffff,                /* dst_mask */
446          FALSE),                /* pcrel_offset */
447
448   /* MOVZ:   ((S+A) >> 16) & 0xffff */
449   HOWTO (AARCH64_R (MOVW_UABS_G1),      /* type */
450          16,                    /* rightshift */
451          2,                     /* size (0 = byte, 1 = short, 2 = long) */
452          16,                    /* bitsize */
453          FALSE,                 /* pc_relative */
454          0,                     /* bitpos */
455          complain_overflow_unsigned,    /* complain_on_overflow */
456          bfd_elf_generic_reloc, /* special_function */
457          AARCH64_R_STR (MOVW_UABS_G1),  /* name */
458          FALSE,                 /* partial_inplace */
459          0xffff,                /* src_mask */
460          0xffff,                /* dst_mask */
461          FALSE),                /* pcrel_offset */
462
463   /* MOVK:   ((S+A) >> 16) & 0xffff [no overflow check] */
464   HOWTO64 (AARCH64_R (MOVW_UABS_G1_NC), /* type */
465          16,                    /* rightshift */
466          2,                     /* size (0 = byte, 1 = short, 2 = long) */
467          16,                    /* bitsize */
468          FALSE,                 /* pc_relative */
469          0,                     /* bitpos */
470          complain_overflow_dont,        /* complain_on_overflow */
471          bfd_elf_generic_reloc, /* special_function */
472          AARCH64_R_STR (MOVW_UABS_G1_NC),       /* name */
473          FALSE,                 /* partial_inplace */
474          0xffff,                /* src_mask */
475          0xffff,                /* dst_mask */
476          FALSE),                /* pcrel_offset */
477
478   /* MOVZ:   ((S+A) >> 32) & 0xffff */
479   HOWTO64 (AARCH64_R (MOVW_UABS_G2),    /* type */
480          32,                    /* rightshift */
481          2,                     /* size (0 = byte, 1 = short, 2 = long) */
482          16,                    /* bitsize */
483          FALSE,                 /* pc_relative */
484          0,                     /* bitpos */
485          complain_overflow_unsigned,    /* complain_on_overflow */
486          bfd_elf_generic_reloc, /* special_function */
487          AARCH64_R_STR (MOVW_UABS_G2),  /* name */
488          FALSE,                 /* partial_inplace */
489          0xffff,                /* src_mask */
490          0xffff,                /* dst_mask */
491          FALSE),                /* pcrel_offset */
492
493   /* MOVK:   ((S+A) >> 32) & 0xffff [no overflow check] */
494   HOWTO64 (AARCH64_R (MOVW_UABS_G2_NC), /* type */
495          32,                    /* rightshift */
496          2,                     /* size (0 = byte, 1 = short, 2 = long) */
497          16,                    /* bitsize */
498          FALSE,                 /* pc_relative */
499          0,                     /* bitpos */
500          complain_overflow_dont,        /* complain_on_overflow */
501          bfd_elf_generic_reloc, /* special_function */
502          AARCH64_R_STR (MOVW_UABS_G2_NC),       /* name */
503          FALSE,                 /* partial_inplace */
504          0xffff,                /* src_mask */
505          0xffff,                /* dst_mask */
506          FALSE),                /* pcrel_offset */
507
508   /* MOVZ:   ((S+A) >> 48) & 0xffff */
509   HOWTO64 (AARCH64_R (MOVW_UABS_G3),    /* type */
510          48,                    /* rightshift */
511          2,                     /* size (0 = byte, 1 = short, 2 = long) */
512          16,                    /* bitsize */
513          FALSE,                 /* pc_relative */
514          0,                     /* bitpos */
515          complain_overflow_unsigned,    /* complain_on_overflow */
516          bfd_elf_generic_reloc, /* special_function */
517          AARCH64_R_STR (MOVW_UABS_G3),  /* name */
518          FALSE,                 /* partial_inplace */
519          0xffff,                /* src_mask */
520          0xffff,                /* dst_mask */
521          FALSE),                /* pcrel_offset */
522
523   /* Group relocations to create high part of a 16, 32, 48 or 64 bit
524      signed data or abs address inline. Will change instruction
525      to MOVN or MOVZ depending on sign of calculated value.  */
526
527   /* MOV[ZN]:   ((S+A) >>  0) & 0xffff */
528   HOWTO (AARCH64_R (MOVW_SABS_G0),      /* type */
529          0,                     /* rightshift */
530          2,                     /* size (0 = byte, 1 = short, 2 = long) */
531          16,                    /* bitsize */
532          FALSE,                 /* pc_relative */
533          0,                     /* bitpos */
534          complain_overflow_signed,      /* complain_on_overflow */
535          bfd_elf_generic_reloc, /* special_function */
536          AARCH64_R_STR (MOVW_SABS_G0),  /* name */
537          FALSE,                 /* partial_inplace */
538          0xffff,                /* src_mask */
539          0xffff,                /* dst_mask */
540          FALSE),                /* pcrel_offset */
541
542   /* MOV[ZN]:   ((S+A) >> 16) & 0xffff */
543   HOWTO64 (AARCH64_R (MOVW_SABS_G1),    /* type */
544          16,                    /* rightshift */
545          2,                     /* size (0 = byte, 1 = short, 2 = long) */
546          16,                    /* bitsize */
547          FALSE,                 /* pc_relative */
548          0,                     /* bitpos */
549          complain_overflow_signed,      /* complain_on_overflow */
550          bfd_elf_generic_reloc, /* special_function */
551          AARCH64_R_STR (MOVW_SABS_G1),  /* name */
552          FALSE,                 /* partial_inplace */
553          0xffff,                /* src_mask */
554          0xffff,                /* dst_mask */
555          FALSE),                /* pcrel_offset */
556
557   /* MOV[ZN]:   ((S+A) >> 32) & 0xffff */
558   HOWTO64 (AARCH64_R (MOVW_SABS_G2),    /* type */
559          32,                    /* rightshift */
560          2,                     /* size (0 = byte, 1 = short, 2 = long) */
561          16,                    /* bitsize */
562          FALSE,                 /* pc_relative */
563          0,                     /* bitpos */
564          complain_overflow_signed,      /* complain_on_overflow */
565          bfd_elf_generic_reloc, /* special_function */
566          AARCH64_R_STR (MOVW_SABS_G2),  /* name */
567          FALSE,                 /* partial_inplace */
568          0xffff,                /* src_mask */
569          0xffff,                /* dst_mask */
570          FALSE),                /* pcrel_offset */
571
572 /* Relocations to generate 19, 21 and 33 bit PC-relative load/store
573    addresses: PG(x) is (x & ~0xfff).  */
574
575   /* LD-lit: ((S+A-P) >> 2) & 0x7ffff */
576   HOWTO (AARCH64_R (LD_PREL_LO19),      /* type */
577          2,                     /* rightshift */
578          2,                     /* size (0 = byte, 1 = short, 2 = long) */
579          19,                    /* bitsize */
580          TRUE,                  /* pc_relative */
581          0,                     /* bitpos */
582          complain_overflow_signed,      /* complain_on_overflow */
583          bfd_elf_generic_reloc, /* special_function */
584          AARCH64_R_STR (LD_PREL_LO19),  /* name */
585          FALSE,                 /* partial_inplace */
586          0x7ffff,               /* src_mask */
587          0x7ffff,               /* dst_mask */
588          TRUE),                 /* pcrel_offset */
589
590   /* ADR:    (S+A-P) & 0x1fffff */
591   HOWTO (AARCH64_R (ADR_PREL_LO21),     /* type */
592          0,                     /* rightshift */
593          2,                     /* size (0 = byte, 1 = short, 2 = long) */
594          21,                    /* bitsize */
595          TRUE,                  /* pc_relative */
596          0,                     /* bitpos */
597          complain_overflow_signed,      /* complain_on_overflow */
598          bfd_elf_generic_reloc, /* special_function */
599          AARCH64_R_STR (ADR_PREL_LO21), /* name */
600          FALSE,                 /* partial_inplace */
601          0x1fffff,              /* src_mask */
602          0x1fffff,              /* dst_mask */
603          TRUE),                 /* pcrel_offset */
604
605   /* ADRP:   ((PG(S+A)-PG(P)) >> 12) & 0x1fffff */
606   HOWTO (AARCH64_R (ADR_PREL_PG_HI21),  /* type */
607          12,                    /* rightshift */
608          2,                     /* size (0 = byte, 1 = short, 2 = long) */
609          21,                    /* bitsize */
610          TRUE,                  /* pc_relative */
611          0,                     /* bitpos */
612          complain_overflow_signed,      /* complain_on_overflow */
613          bfd_elf_generic_reloc, /* special_function */
614          AARCH64_R_STR (ADR_PREL_PG_HI21),      /* name */
615          FALSE,                 /* partial_inplace */
616          0x1fffff,              /* src_mask */
617          0x1fffff,              /* dst_mask */
618          TRUE),                 /* pcrel_offset */
619
620   /* ADRP:   ((PG(S+A)-PG(P)) >> 12) & 0x1fffff [no overflow check] */
621   HOWTO64 (AARCH64_R (ADR_PREL_PG_HI21_NC),     /* type */
622          12,                    /* rightshift */
623          2,                     /* size (0 = byte, 1 = short, 2 = long) */
624          21,                    /* bitsize */
625          TRUE,                  /* pc_relative */
626          0,                     /* bitpos */
627          complain_overflow_dont,        /* complain_on_overflow */
628          bfd_elf_generic_reloc, /* special_function */
629          AARCH64_R_STR (ADR_PREL_PG_HI21_NC),   /* name */
630          FALSE,                 /* partial_inplace */
631          0x1fffff,              /* src_mask */
632          0x1fffff,              /* dst_mask */
633          TRUE),                 /* pcrel_offset */
634
635   /* ADD:    (S+A) & 0xfff [no overflow check] */
636   HOWTO (AARCH64_R (ADD_ABS_LO12_NC),   /* type */
637          0,                     /* rightshift */
638          2,                     /* size (0 = byte, 1 = short, 2 = long) */
639          12,                    /* bitsize */
640          FALSE,                 /* pc_relative */
641          10,                    /* bitpos */
642          complain_overflow_dont,        /* complain_on_overflow */
643          bfd_elf_generic_reloc, /* special_function */
644          AARCH64_R_STR (ADD_ABS_LO12_NC),       /* name */
645          FALSE,                 /* partial_inplace */
646          0x3ffc00,              /* src_mask */
647          0x3ffc00,              /* dst_mask */
648          FALSE),                /* pcrel_offset */
649
650   /* LD/ST8:  (S+A) & 0xfff */
651   HOWTO (AARCH64_R (LDST8_ABS_LO12_NC), /* type */
652          0,                     /* rightshift */
653          2,                     /* size (0 = byte, 1 = short, 2 = long) */
654          12,                    /* bitsize */
655          FALSE,                 /* pc_relative */
656          0,                     /* bitpos */
657          complain_overflow_dont,        /* complain_on_overflow */
658          bfd_elf_generic_reloc, /* special_function */
659          AARCH64_R_STR (LDST8_ABS_LO12_NC),     /* name */
660          FALSE,                 /* partial_inplace */
661          0xfff,                 /* src_mask */
662          0xfff,                 /* dst_mask */
663          FALSE),                /* pcrel_offset */
664
665   /* Relocations for control-flow instructions.  */
666
667   /* TBZ/NZ: ((S+A-P) >> 2) & 0x3fff */
668   HOWTO (AARCH64_R (TSTBR14),   /* type */
669          2,                     /* rightshift */
670          2,                     /* size (0 = byte, 1 = short, 2 = long) */
671          14,                    /* bitsize */
672          TRUE,                  /* pc_relative */
673          0,                     /* bitpos */
674          complain_overflow_signed,      /* complain_on_overflow */
675          bfd_elf_generic_reloc, /* special_function */
676          AARCH64_R_STR (TSTBR14),       /* name */
677          FALSE,                 /* partial_inplace */
678          0x3fff,                /* src_mask */
679          0x3fff,                /* dst_mask */
680          TRUE),                 /* pcrel_offset */
681
682   /* B.cond: ((S+A-P) >> 2) & 0x7ffff */
683   HOWTO (AARCH64_R (CONDBR19),  /* type */
684          2,                     /* rightshift */
685          2,                     /* size (0 = byte, 1 = short, 2 = long) */
686          19,                    /* bitsize */
687          TRUE,                  /* pc_relative */
688          0,                     /* bitpos */
689          complain_overflow_signed,      /* complain_on_overflow */
690          bfd_elf_generic_reloc, /* special_function */
691          AARCH64_R_STR (CONDBR19),      /* name */
692          FALSE,                 /* partial_inplace */
693          0x7ffff,               /* src_mask */
694          0x7ffff,               /* dst_mask */
695          TRUE),                 /* pcrel_offset */
696
697   /* B:      ((S+A-P) >> 2) & 0x3ffffff */
698   HOWTO (AARCH64_R (JUMP26),    /* type */
699          2,                     /* rightshift */
700          2,                     /* size (0 = byte, 1 = short, 2 = long) */
701          26,                    /* bitsize */
702          TRUE,                  /* pc_relative */
703          0,                     /* bitpos */
704          complain_overflow_signed,      /* complain_on_overflow */
705          bfd_elf_generic_reloc, /* special_function */
706          AARCH64_R_STR (JUMP26),        /* name */
707          FALSE,                 /* partial_inplace */
708          0x3ffffff,             /* src_mask */
709          0x3ffffff,             /* dst_mask */
710          TRUE),                 /* pcrel_offset */
711
712   /* BL:     ((S+A-P) >> 2) & 0x3ffffff */
713   HOWTO (AARCH64_R (CALL26),    /* type */
714          2,                     /* rightshift */
715          2,                     /* size (0 = byte, 1 = short, 2 = long) */
716          26,                    /* bitsize */
717          TRUE,                  /* pc_relative */
718          0,                     /* bitpos */
719          complain_overflow_signed,      /* complain_on_overflow */
720          bfd_elf_generic_reloc, /* special_function */
721          AARCH64_R_STR (CALL26),        /* name */
722          FALSE,                 /* partial_inplace */
723          0x3ffffff,             /* src_mask */
724          0x3ffffff,             /* dst_mask */
725          TRUE),                 /* pcrel_offset */
726
727   /* LD/ST16:  (S+A) & 0xffe */
728   HOWTO (AARCH64_R (LDST16_ABS_LO12_NC),        /* type */
729          1,                     /* rightshift */
730          2,                     /* size (0 = byte, 1 = short, 2 = long) */
731          12,                    /* bitsize */
732          FALSE,                 /* pc_relative */
733          0,                     /* bitpos */
734          complain_overflow_dont,        /* complain_on_overflow */
735          bfd_elf_generic_reloc, /* special_function */
736          AARCH64_R_STR (LDST16_ABS_LO12_NC),    /* name */
737          FALSE,                 /* partial_inplace */
738          0xffe,                 /* src_mask */
739          0xffe,                 /* dst_mask */
740          FALSE),                /* pcrel_offset */
741
742   /* LD/ST32:  (S+A) & 0xffc */
743   HOWTO (AARCH64_R (LDST32_ABS_LO12_NC),        /* type */
744          2,                     /* rightshift */
745          2,                     /* size (0 = byte, 1 = short, 2 = long) */
746          12,                    /* bitsize */
747          FALSE,                 /* pc_relative */
748          0,                     /* bitpos */
749          complain_overflow_dont,        /* complain_on_overflow */
750          bfd_elf_generic_reloc, /* special_function */
751          AARCH64_R_STR (LDST32_ABS_LO12_NC),    /* name */
752          FALSE,                 /* partial_inplace */
753          0xffc,                 /* src_mask */
754          0xffc,                 /* dst_mask */
755          FALSE),                /* pcrel_offset */
756
757   /* LD/ST64:  (S+A) & 0xff8 */
758   HOWTO (AARCH64_R (LDST64_ABS_LO12_NC),        /* type */
759          3,                     /* rightshift */
760          2,                     /* size (0 = byte, 1 = short, 2 = long) */
761          12,                    /* bitsize */
762          FALSE,                 /* pc_relative */
763          0,                     /* bitpos */
764          complain_overflow_dont,        /* complain_on_overflow */
765          bfd_elf_generic_reloc, /* special_function */
766          AARCH64_R_STR (LDST64_ABS_LO12_NC),    /* name */
767          FALSE,                 /* partial_inplace */
768          0xff8,                 /* src_mask */
769          0xff8,                 /* dst_mask */
770          FALSE),                /* pcrel_offset */
771
772   /* LD/ST128:  (S+A) & 0xff0 */
773   HOWTO (AARCH64_R (LDST128_ABS_LO12_NC),       /* type */
774          4,                     /* rightshift */
775          2,                     /* size (0 = byte, 1 = short, 2 = long) */
776          12,                    /* bitsize */
777          FALSE,                 /* pc_relative */
778          0,                     /* bitpos */
779          complain_overflow_dont,        /* complain_on_overflow */
780          bfd_elf_generic_reloc, /* special_function */
781          AARCH64_R_STR (LDST128_ABS_LO12_NC),   /* name */
782          FALSE,                 /* partial_inplace */
783          0xff0,                 /* src_mask */
784          0xff0,                 /* dst_mask */
785          FALSE),                /* pcrel_offset */
786
787   /* Set a load-literal immediate field to bits
788      0x1FFFFC of G(S)-P */
789   HOWTO (AARCH64_R (GOT_LD_PREL19),     /* type */
790          2,                             /* rightshift */
791          2,                             /* size (0 = byte,1 = short,2 = long) */
792          19,                            /* bitsize */
793          TRUE,                          /* pc_relative */
794          0,                             /* bitpos */
795          complain_overflow_signed,      /* complain_on_overflow */
796          bfd_elf_generic_reloc,         /* special_function */
797          AARCH64_R_STR (GOT_LD_PREL19), /* name */
798          FALSE,                         /* partial_inplace */
799          0xffffe0,                      /* src_mask */
800          0xffffe0,                      /* dst_mask */
801          TRUE),                         /* pcrel_offset */
802
803   /* Get to the page for the GOT entry for the symbol
804      (G(S) - P) using an ADRP instruction.  */
805   HOWTO (AARCH64_R (ADR_GOT_PAGE),      /* type */
806          12,                    /* rightshift */
807          2,                     /* size (0 = byte, 1 = short, 2 = long) */
808          21,                    /* bitsize */
809          TRUE,                  /* pc_relative */
810          0,                     /* bitpos */
811          complain_overflow_dont,        /* complain_on_overflow */
812          bfd_elf_generic_reloc, /* special_function */
813          AARCH64_R_STR (ADR_GOT_PAGE),  /* name */
814          FALSE,                 /* partial_inplace */
815          0x1fffff,              /* src_mask */
816          0x1fffff,              /* dst_mask */
817          TRUE),                 /* pcrel_offset */
818
819   /* LD64: GOT offset G(S) & 0xff8  */
820   HOWTO64 (AARCH64_R (LD64_GOT_LO12_NC),        /* type */
821          3,                     /* rightshift */
822          2,                     /* size (0 = byte, 1 = short, 2 = long) */
823          12,                    /* bitsize */
824          FALSE,                 /* pc_relative */
825          0,                     /* bitpos */
826          complain_overflow_dont,        /* complain_on_overflow */
827          bfd_elf_generic_reloc, /* special_function */
828          AARCH64_R_STR (LD64_GOT_LO12_NC),      /* name */
829          FALSE,                 /* partial_inplace */
830          0xff8,                 /* src_mask */
831          0xff8,                 /* dst_mask */
832          FALSE),                /* pcrel_offset */
833
834   /* LD32: GOT offset G(S) & 0xffc  */
835   HOWTO32 (AARCH64_R (LD32_GOT_LO12_NC),        /* type */
836          2,                     /* rightshift */
837          2,                     /* size (0 = byte, 1 = short, 2 = long) */
838          12,                    /* bitsize */
839          FALSE,                 /* pc_relative */
840          0,                     /* bitpos */
841          complain_overflow_dont,        /* complain_on_overflow */
842          bfd_elf_generic_reloc, /* special_function */
843          AARCH64_R_STR (LD32_GOT_LO12_NC),      /* name */
844          FALSE,                 /* partial_inplace */
845          0xffc,                 /* src_mask */
846          0xffc,                 /* dst_mask */
847          FALSE),                /* pcrel_offset */
848
849   /* Get to the page for the GOT entry for the symbol
850      (G(S) - P) using an ADRP instruction.  */
851   HOWTO (AARCH64_R (TLSGD_ADR_PAGE21),  /* type */
852          12,                    /* rightshift */
853          2,                     /* size (0 = byte, 1 = short, 2 = long) */
854          21,                    /* bitsize */
855          TRUE,                  /* pc_relative */
856          0,                     /* bitpos */
857          complain_overflow_dont,        /* complain_on_overflow */
858          bfd_elf_generic_reloc, /* special_function */
859          AARCH64_R_STR (TLSGD_ADR_PAGE21),      /* name */
860          FALSE,                 /* partial_inplace */
861          0x1fffff,              /* src_mask */
862          0x1fffff,              /* dst_mask */
863          TRUE),                 /* pcrel_offset */
864
865   /* ADD: GOT offset G(S) & 0xff8 [no overflow check] */
866   HOWTO (AARCH64_R (TLSGD_ADD_LO12_NC), /* type */
867          0,                     /* rightshift */
868          2,                     /* size (0 = byte, 1 = short, 2 = long) */
869          12,                    /* bitsize */
870          FALSE,                 /* pc_relative */
871          0,                     /* bitpos */
872          complain_overflow_dont,        /* complain_on_overflow */
873          bfd_elf_generic_reloc, /* special_function */
874          AARCH64_R_STR (TLSGD_ADD_LO12_NC),     /* name */
875          FALSE,                 /* partial_inplace */
876          0xfff,                 /* src_mask */
877          0xfff,                 /* dst_mask */
878          FALSE),                /* pcrel_offset */
879
880   HOWTO64 (AARCH64_R (TLSIE_MOVW_GOTTPREL_G1),  /* type */
881          16,                    /* rightshift */
882          2,                     /* size (0 = byte, 1 = short, 2 = long) */
883          16,                    /* bitsize */
884          FALSE,                 /* pc_relative */
885          0,                     /* bitpos */
886          complain_overflow_dont,        /* complain_on_overflow */
887          bfd_elf_generic_reloc, /* special_function */
888          AARCH64_R_STR (TLSIE_MOVW_GOTTPREL_G1),        /* name */
889          FALSE,                 /* partial_inplace */
890          0xffff,                /* src_mask */
891          0xffff,                /* dst_mask */
892          FALSE),                /* pcrel_offset */
893
894   HOWTO64 (AARCH64_R (TLSIE_MOVW_GOTTPREL_G0_NC),       /* type */
895          0,                     /* rightshift */
896          2,                     /* size (0 = byte, 1 = short, 2 = long) */
897          32,                    /* bitsize */
898          FALSE,                 /* pc_relative */
899          0,                     /* bitpos */
900          complain_overflow_dont,        /* complain_on_overflow */
901          bfd_elf_generic_reloc, /* special_function */
902          AARCH64_R_STR (TLSIE_MOVW_GOTTPREL_G0_NC),     /* name */
903          FALSE,                 /* partial_inplace */
904          0xffff,                /* src_mask */
905          0xffff,                /* dst_mask */
906          FALSE),                /* pcrel_offset */
907
908   HOWTO (AARCH64_R (TLSIE_ADR_GOTTPREL_PAGE21), /* type */
909          12,                    /* rightshift */
910          2,                     /* size (0 = byte, 1 = short, 2 = long) */
911          21,                    /* bitsize */
912          FALSE,                 /* pc_relative */
913          0,                     /* bitpos */
914          complain_overflow_dont,        /* complain_on_overflow */
915          bfd_elf_generic_reloc, /* special_function */
916          AARCH64_R_STR (TLSIE_ADR_GOTTPREL_PAGE21),     /* name */
917          FALSE,                 /* partial_inplace */
918          0x1fffff,              /* src_mask */
919          0x1fffff,              /* dst_mask */
920          FALSE),                /* pcrel_offset */
921
922   HOWTO64 (AARCH64_R (TLSIE_LD64_GOTTPREL_LO12_NC),     /* type */
923          3,                     /* rightshift */
924          2,                     /* size (0 = byte, 1 = short, 2 = long) */
925          12,                    /* bitsize */
926          FALSE,                 /* pc_relative */
927          0,                     /* bitpos */
928          complain_overflow_dont,        /* complain_on_overflow */
929          bfd_elf_generic_reloc, /* special_function */
930          AARCH64_R_STR (TLSIE_LD64_GOTTPREL_LO12_NC),   /* name */
931          FALSE,                 /* partial_inplace */
932          0xff8,                 /* src_mask */
933          0xff8,                 /* dst_mask */
934          FALSE),                /* pcrel_offset */
935
936   HOWTO32 (AARCH64_R (TLSIE_LD32_GOTTPREL_LO12_NC),     /* type */
937          2,                     /* rightshift */
938          2,                     /* size (0 = byte, 1 = short, 2 = long) */
939          12,                    /* bitsize */
940          FALSE,                 /* pc_relative */
941          0,                     /* bitpos */
942          complain_overflow_dont,        /* complain_on_overflow */
943          bfd_elf_generic_reloc, /* special_function */
944          AARCH64_R_STR (TLSIE_LD32_GOTTPREL_LO12_NC),   /* name */
945          FALSE,                 /* partial_inplace */
946          0xffc,                 /* src_mask */
947          0xffc,                 /* dst_mask */
948          FALSE),                /* pcrel_offset */
949
950   HOWTO (AARCH64_R (TLSIE_LD_GOTTPREL_PREL19),  /* type */
951          2,                     /* rightshift */
952          2,                     /* size (0 = byte, 1 = short, 2 = long) */
953          21,                    /* bitsize */
954          FALSE,                 /* pc_relative */
955          0,                     /* bitpos */
956          complain_overflow_dont,        /* complain_on_overflow */
957          bfd_elf_generic_reloc, /* special_function */
958          AARCH64_R_STR (TLSIE_LD_GOTTPREL_PREL19),      /* name */
959          FALSE,                 /* partial_inplace */
960          0x1ffffc,              /* src_mask */
961          0x1ffffc,              /* dst_mask */
962          FALSE),                /* pcrel_offset */
963
964   HOWTO64 (AARCH64_R (TLSLE_MOVW_TPREL_G2),     /* type */
965          32,                    /* rightshift */
966          2,                     /* size (0 = byte, 1 = short, 2 = long) */
967          12,                    /* bitsize */
968          FALSE,                 /* pc_relative */
969          0,                     /* bitpos */
970          complain_overflow_dont,        /* complain_on_overflow */
971          bfd_elf_generic_reloc, /* special_function */
972          AARCH64_R_STR (TLSLE_MOVW_TPREL_G2),   /* name */
973          FALSE,                 /* partial_inplace */
974          0xffff,                /* src_mask */
975          0xffff,                /* dst_mask */
976          FALSE),                /* pcrel_offset */
977
978   HOWTO (AARCH64_R (TLSLE_MOVW_TPREL_G1),       /* type */
979          16,                    /* rightshift */
980          2,                     /* size (0 = byte, 1 = short, 2 = long) */
981          12,                    /* bitsize */
982          FALSE,                 /* pc_relative */
983          0,                     /* bitpos */
984          complain_overflow_dont,        /* complain_on_overflow */
985          bfd_elf_generic_reloc, /* special_function */
986          AARCH64_R_STR (TLSLE_MOVW_TPREL_G1),   /* name */
987          FALSE,                 /* partial_inplace */
988          0xffff,                /* src_mask */
989          0xffff,                /* dst_mask */
990          FALSE),                /* pcrel_offset */
991
992   HOWTO64 (AARCH64_R (TLSLE_MOVW_TPREL_G1_NC),  /* type */
993          16,                    /* rightshift */
994          2,                     /* size (0 = byte, 1 = short, 2 = long) */
995          12,                    /* bitsize */
996          FALSE,                 /* pc_relative */
997          0,                     /* bitpos */
998          complain_overflow_dont,        /* complain_on_overflow */
999          bfd_elf_generic_reloc, /* special_function */
1000          AARCH64_R_STR (TLSLE_MOVW_TPREL_G1_NC),        /* name */
1001          FALSE,                 /* partial_inplace */
1002          0xffff,                /* src_mask */
1003          0xffff,                /* dst_mask */
1004          FALSE),                /* pcrel_offset */
1005
1006   HOWTO (AARCH64_R (TLSLE_MOVW_TPREL_G0),       /* type */
1007          0,                     /* rightshift */
1008          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1009          12,                    /* bitsize */
1010          FALSE,                 /* pc_relative */
1011          0,                     /* bitpos */
1012          complain_overflow_dont,        /* complain_on_overflow */
1013          bfd_elf_generic_reloc, /* special_function */
1014          AARCH64_R_STR (TLSLE_MOVW_TPREL_G0),   /* name */
1015          FALSE,                 /* partial_inplace */
1016          0xffff,                /* src_mask */
1017          0xffff,                /* dst_mask */
1018          FALSE),                /* pcrel_offset */
1019
1020   HOWTO (AARCH64_R (TLSLE_MOVW_TPREL_G0_NC),    /* type */
1021          0,                     /* rightshift */
1022          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1023          12,                    /* bitsize */
1024          FALSE,                 /* pc_relative */
1025          0,                     /* bitpos */
1026          complain_overflow_dont,        /* complain_on_overflow */
1027          bfd_elf_generic_reloc, /* special_function */
1028          AARCH64_R_STR (TLSLE_MOVW_TPREL_G0_NC),        /* name */
1029          FALSE,                 /* partial_inplace */
1030          0xffff,                /* src_mask */
1031          0xffff,                /* dst_mask */
1032          FALSE),                /* pcrel_offset */
1033
1034   HOWTO (AARCH64_R (TLSLE_ADD_TPREL_HI12),      /* type */
1035          12,                    /* rightshift */
1036          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1037          12,                    /* bitsize */
1038          FALSE,                 /* pc_relative */
1039          0,                     /* bitpos */
1040          complain_overflow_dont,        /* complain_on_overflow */
1041          bfd_elf_generic_reloc, /* special_function */
1042          AARCH64_R_STR (TLSLE_ADD_TPREL_HI12),  /* name */
1043          FALSE,                 /* partial_inplace */
1044          0xfff,                 /* src_mask */
1045          0xfff,                 /* dst_mask */
1046          FALSE),                /* pcrel_offset */
1047
1048   HOWTO (AARCH64_R (TLSLE_ADD_TPREL_LO12),      /* type */
1049          0,                     /* rightshift */
1050          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1051          12,                    /* bitsize */
1052          FALSE,                 /* pc_relative */
1053          0,                     /* bitpos */
1054          complain_overflow_dont,        /* complain_on_overflow */
1055          bfd_elf_generic_reloc, /* special_function */
1056          AARCH64_R_STR (TLSLE_ADD_TPREL_LO12),  /* name */
1057          FALSE,                 /* partial_inplace */
1058          0xfff,                 /* src_mask */
1059          0xfff,                 /* dst_mask */
1060          FALSE),                /* pcrel_offset */
1061
1062   HOWTO (AARCH64_R (TLSLE_ADD_TPREL_LO12_NC),   /* type */
1063          0,                     /* rightshift */
1064          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1065          12,                    /* bitsize */
1066          FALSE,                 /* pc_relative */
1067          0,                     /* bitpos */
1068          complain_overflow_dont,        /* complain_on_overflow */
1069          bfd_elf_generic_reloc, /* special_function */
1070          AARCH64_R_STR (TLSLE_ADD_TPREL_LO12_NC),       /* name */
1071          FALSE,                 /* partial_inplace */
1072          0xfff,                 /* src_mask */
1073          0xfff,                 /* dst_mask */
1074          FALSE),                /* pcrel_offset */
1075
1076   HOWTO (AARCH64_R (TLSDESC_LD_PREL19), /* type */
1077          2,                     /* rightshift */
1078          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1079          21,                    /* bitsize */
1080          TRUE,                  /* pc_relative */
1081          0,                     /* bitpos */
1082          complain_overflow_dont,        /* complain_on_overflow */
1083          bfd_elf_generic_reloc, /* special_function */
1084          AARCH64_R_STR (TLSDESC_LD_PREL19),     /* name */
1085          FALSE,                 /* partial_inplace */
1086          0x1ffffc,              /* src_mask */
1087          0x1ffffc,              /* dst_mask */
1088          TRUE),                 /* pcrel_offset */
1089
1090   HOWTO (AARCH64_R (TLSDESC_ADR_PREL21),        /* type */
1091          0,                     /* rightshift */
1092          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1093          21,                    /* bitsize */
1094          TRUE,                  /* pc_relative */
1095          0,                     /* bitpos */
1096          complain_overflow_dont,        /* complain_on_overflow */
1097          bfd_elf_generic_reloc, /* special_function */
1098          AARCH64_R_STR (TLSDESC_ADR_PREL21),    /* name */
1099          FALSE,                 /* partial_inplace */
1100          0x1fffff,              /* src_mask */
1101          0x1fffff,              /* dst_mask */
1102          TRUE),                 /* pcrel_offset */
1103
1104   /* Get to the page for the GOT entry for the symbol
1105      (G(S) - P) using an ADRP instruction.  */
1106   HOWTO (AARCH64_R (TLSDESC_ADR_PAGE21),        /* type */
1107          12,                    /* rightshift */
1108          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1109          21,                    /* bitsize */
1110          TRUE,                  /* pc_relative */
1111          0,                     /* bitpos */
1112          complain_overflow_dont,        /* complain_on_overflow */
1113          bfd_elf_generic_reloc, /* special_function */
1114          AARCH64_R_STR (TLSDESC_ADR_PAGE21),    /* name */
1115          FALSE,                 /* partial_inplace */
1116          0x1fffff,              /* src_mask */
1117          0x1fffff,              /* dst_mask */
1118          TRUE),                 /* pcrel_offset */
1119
1120   /* LD64: GOT offset G(S) & 0xff8.  */
1121   HOWTO64 (AARCH64_R (TLSDESC_LD64_LO12_NC),    /* type */
1122          3,                     /* rightshift */
1123          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1124          12,                    /* bitsize */
1125          FALSE,                 /* pc_relative */
1126          0,                     /* bitpos */
1127          complain_overflow_dont,        /* complain_on_overflow */
1128          bfd_elf_generic_reloc, /* special_function */
1129          AARCH64_R_STR (TLSDESC_LD64_LO12_NC),  /* name */
1130          FALSE,                 /* partial_inplace */
1131          0xff8,                 /* src_mask */
1132          0xff8,                 /* dst_mask */
1133          FALSE),                /* pcrel_offset */
1134
1135   /* LD32: GOT offset G(S) & 0xffc.  */
1136   HOWTO32 (AARCH64_R (TLSDESC_LD32_LO12_NC),    /* type */
1137          2,                     /* rightshift */
1138          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1139          12,                    /* bitsize */
1140          FALSE,                 /* pc_relative */
1141          0,                     /* bitpos */
1142          complain_overflow_dont,        /* complain_on_overflow */
1143          bfd_elf_generic_reloc, /* special_function */
1144          AARCH64_R_STR (TLSDESC_LD32_LO12_NC),  /* name */
1145          FALSE,                 /* partial_inplace */
1146          0xffc,                 /* src_mask */
1147          0xffc,                 /* dst_mask */
1148          FALSE),                /* pcrel_offset */
1149
1150   /* ADD: GOT offset G(S) & 0xfff.  */
1151   HOWTO (AARCH64_R (TLSDESC_ADD_LO12_NC),       /* type */
1152          0,                     /* rightshift */
1153          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1154          12,                    /* bitsize */
1155          FALSE,                 /* pc_relative */
1156          0,                     /* bitpos */
1157          complain_overflow_dont,        /* complain_on_overflow */
1158          bfd_elf_generic_reloc, /* special_function */
1159          AARCH64_R_STR (TLSDESC_ADD_LO12_NC),   /* name */
1160          FALSE,                 /* partial_inplace */
1161          0xfff,                 /* src_mask */
1162          0xfff,                 /* dst_mask */
1163          FALSE),                /* pcrel_offset */
1164
1165   HOWTO64 (AARCH64_R (TLSDESC_OFF_G1),  /* type */
1166          16,                    /* rightshift */
1167          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1168          12,                    /* bitsize */
1169          FALSE,                 /* pc_relative */
1170          0,                     /* bitpos */
1171          complain_overflow_dont,        /* complain_on_overflow */
1172          bfd_elf_generic_reloc, /* special_function */
1173          AARCH64_R_STR (TLSDESC_OFF_G1),        /* name */
1174          FALSE,                 /* partial_inplace */
1175          0xffff,                /* src_mask */
1176          0xffff,                /* dst_mask */
1177          FALSE),                /* pcrel_offset */
1178
1179   HOWTO64 (AARCH64_R (TLSDESC_OFF_G0_NC),       /* type */
1180          0,                     /* rightshift */
1181          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1182          12,                    /* bitsize */
1183          FALSE,                 /* pc_relative */
1184          0,                     /* bitpos */
1185          complain_overflow_dont,        /* complain_on_overflow */
1186          bfd_elf_generic_reloc, /* special_function */
1187          AARCH64_R_STR (TLSDESC_OFF_G0_NC),     /* name */
1188          FALSE,                 /* partial_inplace */
1189          0xffff,                /* src_mask */
1190          0xffff,                /* dst_mask */
1191          FALSE),                /* pcrel_offset */
1192
1193   HOWTO64 (AARCH64_R (TLSDESC_LDR),     /* type */
1194          0,                     /* rightshift */
1195          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1196          12,                    /* bitsize */
1197          FALSE,                 /* pc_relative */
1198          0,                     /* bitpos */
1199          complain_overflow_dont,        /* complain_on_overflow */
1200          bfd_elf_generic_reloc, /* special_function */
1201          AARCH64_R_STR (TLSDESC_LDR),   /* name */
1202          FALSE,                 /* partial_inplace */
1203          0x0,                   /* src_mask */
1204          0x0,                   /* dst_mask */
1205          FALSE),                /* pcrel_offset */
1206
1207   HOWTO64 (AARCH64_R (TLSDESC_ADD),     /* type */
1208          0,                     /* rightshift */
1209          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1210          12,                    /* bitsize */
1211          FALSE,                 /* pc_relative */
1212          0,                     /* bitpos */
1213          complain_overflow_dont,        /* complain_on_overflow */
1214          bfd_elf_generic_reloc, /* special_function */
1215          AARCH64_R_STR (TLSDESC_ADD),   /* name */
1216          FALSE,                 /* partial_inplace */
1217          0x0,                   /* src_mask */
1218          0x0,                   /* dst_mask */
1219          FALSE),                /* pcrel_offset */
1220
1221   HOWTO (AARCH64_R (TLSDESC_CALL),      /* type */
1222          0,                     /* rightshift */
1223          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1224          12,                    /* bitsize */
1225          FALSE,                 /* pc_relative */
1226          0,                     /* bitpos */
1227          complain_overflow_dont,        /* complain_on_overflow */
1228          bfd_elf_generic_reloc, /* special_function */
1229          AARCH64_R_STR (TLSDESC_CALL),  /* name */
1230          FALSE,                 /* partial_inplace */
1231          0x0,                   /* src_mask */
1232          0x0,                   /* dst_mask */
1233          FALSE),                /* pcrel_offset */
1234
1235   HOWTO (AARCH64_R (COPY),      /* type */
1236          0,                     /* rightshift */
1237          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1238          64,                    /* bitsize */
1239          FALSE,                 /* pc_relative */
1240          0,                     /* bitpos */
1241          complain_overflow_bitfield,    /* complain_on_overflow */
1242          bfd_elf_generic_reloc, /* special_function */
1243          AARCH64_R_STR (COPY),  /* name */
1244          TRUE,                  /* partial_inplace */
1245          0xffffffff,            /* src_mask */
1246          0xffffffff,            /* dst_mask */
1247          FALSE),                /* pcrel_offset */
1248
1249   HOWTO (AARCH64_R (GLOB_DAT),  /* type */
1250          0,                     /* rightshift */
1251          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1252          64,                    /* bitsize */
1253          FALSE,                 /* pc_relative */
1254          0,                     /* bitpos */
1255          complain_overflow_bitfield,    /* complain_on_overflow */
1256          bfd_elf_generic_reloc, /* special_function */
1257          AARCH64_R_STR (GLOB_DAT),      /* name */
1258          TRUE,                  /* partial_inplace */
1259          0xffffffff,            /* src_mask */
1260          0xffffffff,            /* dst_mask */
1261          FALSE),                /* pcrel_offset */
1262
1263   HOWTO (AARCH64_R (JUMP_SLOT), /* type */
1264          0,                     /* rightshift */
1265          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1266          64,                    /* bitsize */
1267          FALSE,                 /* pc_relative */
1268          0,                     /* bitpos */
1269          complain_overflow_bitfield,    /* complain_on_overflow */
1270          bfd_elf_generic_reloc, /* special_function */
1271          AARCH64_R_STR (JUMP_SLOT),     /* name */
1272          TRUE,                  /* partial_inplace */
1273          0xffffffff,            /* src_mask */
1274          0xffffffff,            /* dst_mask */
1275          FALSE),                /* pcrel_offset */
1276
1277   HOWTO (AARCH64_R (RELATIVE),  /* type */
1278          0,                     /* rightshift */
1279          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1280          64,                    /* bitsize */
1281          FALSE,                 /* pc_relative */
1282          0,                     /* bitpos */
1283          complain_overflow_bitfield,    /* complain_on_overflow */
1284          bfd_elf_generic_reloc, /* special_function */
1285          AARCH64_R_STR (RELATIVE),      /* name */
1286          TRUE,                  /* partial_inplace */
1287          ALL_ONES,              /* src_mask */
1288          ALL_ONES,              /* dst_mask */
1289          FALSE),                /* pcrel_offset */
1290
1291   HOWTO (AARCH64_R (TLS_DTPMOD),        /* type */
1292          0,                     /* rightshift */
1293          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1294          64,                    /* bitsize */
1295          FALSE,                 /* pc_relative */
1296          0,                     /* bitpos */
1297          complain_overflow_dont,        /* complain_on_overflow */
1298          bfd_elf_generic_reloc, /* special_function */
1299          AARCH64_R_STR (TLS_DTPMOD),    /* name */
1300          FALSE,                 /* partial_inplace */
1301          0,                     /* src_mask */
1302          ALL_ONES,              /* dst_mask */
1303          FALSE),                /* pc_reloffset */
1304
1305   HOWTO (AARCH64_R (TLS_DTPREL),        /* type */
1306          0,                     /* rightshift */
1307          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1308          64,                    /* bitsize */
1309          FALSE,                 /* pc_relative */
1310          0,                     /* bitpos */
1311          complain_overflow_dont,        /* complain_on_overflow */
1312          bfd_elf_generic_reloc, /* special_function */
1313          AARCH64_R_STR (TLS_DTPREL),    /* name */
1314          FALSE,                 /* partial_inplace */
1315          0,                     /* src_mask */
1316          ALL_ONES,              /* dst_mask */
1317          FALSE),                /* pcrel_offset */
1318
1319   HOWTO (AARCH64_R (TLS_TPREL), /* type */
1320          0,                     /* rightshift */
1321          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1322          64,                    /* bitsize */
1323          FALSE,                 /* pc_relative */
1324          0,                     /* bitpos */
1325          complain_overflow_dont,        /* complain_on_overflow */
1326          bfd_elf_generic_reloc, /* special_function */
1327          AARCH64_R_STR (TLS_TPREL),     /* name */
1328          FALSE,                 /* partial_inplace */
1329          0,                     /* src_mask */
1330          ALL_ONES,              /* dst_mask */
1331          FALSE),                /* pcrel_offset */
1332
1333   HOWTO (AARCH64_R (TLSDESC),   /* type */
1334          0,                     /* rightshift */
1335          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1336          64,                    /* bitsize */
1337          FALSE,                 /* pc_relative */
1338          0,                     /* bitpos */
1339          complain_overflow_dont,        /* complain_on_overflow */
1340          bfd_elf_generic_reloc, /* special_function */
1341          AARCH64_R_STR (TLSDESC),       /* name */
1342          FALSE,                 /* partial_inplace */
1343          0,                     /* src_mask */
1344          ALL_ONES,              /* dst_mask */
1345          FALSE),                /* pcrel_offset */
1346
1347   HOWTO (AARCH64_R (IRELATIVE), /* type */
1348          0,                     /* rightshift */
1349          2,                     /* size (0 = byte, 1 = short, 2 = long) */
1350          64,                    /* bitsize */
1351          FALSE,                 /* pc_relative */
1352          0,                     /* bitpos */
1353          complain_overflow_bitfield,    /* complain_on_overflow */
1354          bfd_elf_generic_reloc, /* special_function */
1355          AARCH64_R_STR (IRELATIVE),     /* name */
1356          FALSE,                 /* partial_inplace */
1357          0,                     /* src_mask */
1358          ALL_ONES,              /* dst_mask */
1359          FALSE),                /* pcrel_offset */
1360
1361   EMPTY_HOWTO (0),
1362 };
1363
1364 static reloc_howto_type elfNN_aarch64_howto_none =
1365   HOWTO (R_AARCH64_NONE,        /* type */
1366          0,                     /* rightshift */
1367          0,                     /* size (0 = byte, 1 = short, 2 = long) */
1368          0,                     /* bitsize */
1369          FALSE,                 /* pc_relative */
1370          0,                     /* bitpos */
1371          complain_overflow_dont,/* complain_on_overflow */
1372          bfd_elf_generic_reloc, /* special_function */
1373          "R_AARCH64_NONE",      /* name */
1374          FALSE,                 /* partial_inplace */
1375          0,                     /* src_mask */
1376          0,                     /* dst_mask */
1377          FALSE);                /* pcrel_offset */
1378
1379 /* Given HOWTO, return the bfd internal relocation enumerator.  */
1380
1381 static bfd_reloc_code_real_type
1382 elfNN_aarch64_bfd_reloc_from_howto (reloc_howto_type *howto)
1383 {
1384   const int size
1385     = (int) ARRAY_SIZE (elfNN_aarch64_howto_table);
1386   const ptrdiff_t offset
1387     = howto - elfNN_aarch64_howto_table;
1388
1389   if (offset > 0 && offset < size - 1)
1390     return BFD_RELOC_AARCH64_RELOC_START + offset;
1391
1392   if (howto == &elfNN_aarch64_howto_none)
1393     return BFD_RELOC_AARCH64_NONE;
1394
1395   return BFD_RELOC_AARCH64_RELOC_START;
1396 }
1397
1398 /* Given R_TYPE, return the bfd internal relocation enumerator.  */
1399
1400 static bfd_reloc_code_real_type
1401 elfNN_aarch64_bfd_reloc_from_type (unsigned int r_type)
1402 {
1403   static bfd_boolean initialized_p = FALSE;
1404   /* Indexed by R_TYPE, values are offsets in the howto_table.  */
1405   static unsigned int offsets[R_AARCH64_end];
1406
1407   if (initialized_p == FALSE)
1408     {
1409       unsigned int i;
1410
1411       for (i = 1; i < ARRAY_SIZE (elfNN_aarch64_howto_table) - 1; ++i)
1412         if (elfNN_aarch64_howto_table[i].type != 0)
1413           offsets[elfNN_aarch64_howto_table[i].type] = i;
1414
1415       initialized_p = TRUE;
1416     }
1417
1418   if (r_type == R_AARCH64_NONE || r_type == R_AARCH64_NULL)
1419     return BFD_RELOC_AARCH64_NONE;
1420
1421   return BFD_RELOC_AARCH64_RELOC_START + offsets[r_type];
1422 }
1423
1424 struct elf_aarch64_reloc_map
1425 {
1426   bfd_reloc_code_real_type from;
1427   bfd_reloc_code_real_type to;
1428 };
1429
1430 /* Map bfd generic reloc to AArch64-specific reloc.  */
1431 static const struct elf_aarch64_reloc_map elf_aarch64_reloc_map[] =
1432 {
1433   {BFD_RELOC_NONE, BFD_RELOC_AARCH64_NONE},
1434
1435   /* Basic data relocations.  */
1436   {BFD_RELOC_CTOR, BFD_RELOC_AARCH64_NN},
1437   {BFD_RELOC_64, BFD_RELOC_AARCH64_64},
1438   {BFD_RELOC_32, BFD_RELOC_AARCH64_32},
1439   {BFD_RELOC_16, BFD_RELOC_AARCH64_16},
1440   {BFD_RELOC_64_PCREL, BFD_RELOC_AARCH64_64_PCREL},
1441   {BFD_RELOC_32_PCREL, BFD_RELOC_AARCH64_32_PCREL},
1442   {BFD_RELOC_16_PCREL, BFD_RELOC_AARCH64_16_PCREL},
1443 };
1444
1445 /* Given the bfd internal relocation enumerator in CODE, return the
1446    corresponding howto entry.  */
1447
1448 static reloc_howto_type *
1449 elfNN_aarch64_howto_from_bfd_reloc (bfd_reloc_code_real_type code)
1450 {
1451   unsigned int i;
1452
1453   /* Convert bfd generic reloc to AArch64-specific reloc.  */
1454   if (code < BFD_RELOC_AARCH64_RELOC_START
1455       || code > BFD_RELOC_AARCH64_RELOC_END)
1456     for (i = 0; i < ARRAY_SIZE (elf_aarch64_reloc_map); i++)
1457       if (elf_aarch64_reloc_map[i].from == code)
1458         {
1459           code = elf_aarch64_reloc_map[i].to;
1460           break;
1461         }
1462
1463   if (code > BFD_RELOC_AARCH64_RELOC_START
1464       && code < BFD_RELOC_AARCH64_RELOC_END)
1465     if (elfNN_aarch64_howto_table[code - BFD_RELOC_AARCH64_RELOC_START].type)
1466       return &elfNN_aarch64_howto_table[code - BFD_RELOC_AARCH64_RELOC_START];
1467
1468   if (code == BFD_RELOC_AARCH64_NONE)
1469     return &elfNN_aarch64_howto_none;
1470
1471   return NULL;
1472 }
1473
1474 static reloc_howto_type *
1475 elfNN_aarch64_howto_from_type (unsigned int r_type)
1476 {
1477   bfd_reloc_code_real_type val;
1478   reloc_howto_type *howto;
1479
1480 #if ARCH_SIZE == 32
1481   if (r_type > 256)
1482     {
1483       bfd_set_error (bfd_error_bad_value);
1484       return NULL;
1485     }
1486 #endif
1487
1488   if (r_type == R_AARCH64_NONE)
1489     return &elfNN_aarch64_howto_none;
1490
1491   val = elfNN_aarch64_bfd_reloc_from_type (r_type);
1492   howto = elfNN_aarch64_howto_from_bfd_reloc (val);
1493
1494   if (howto != NULL)
1495     return howto;
1496
1497   bfd_set_error (bfd_error_bad_value);
1498   return NULL;
1499 }
1500
1501 static void
1502 elfNN_aarch64_info_to_howto (bfd *abfd ATTRIBUTE_UNUSED, arelent *bfd_reloc,
1503                              Elf_Internal_Rela *elf_reloc)
1504 {
1505   unsigned int r_type;
1506
1507   r_type = ELFNN_R_TYPE (elf_reloc->r_info);
1508   bfd_reloc->howto = elfNN_aarch64_howto_from_type (r_type);
1509 }
1510
1511 static reloc_howto_type *
1512 elfNN_aarch64_reloc_type_lookup (bfd *abfd ATTRIBUTE_UNUSED,
1513                                  bfd_reloc_code_real_type code)
1514 {
1515   reloc_howto_type *howto = elfNN_aarch64_howto_from_bfd_reloc (code);
1516
1517   if (howto != NULL)
1518     return howto;
1519
1520   bfd_set_error (bfd_error_bad_value);
1521   return NULL;
1522 }
1523
1524 static reloc_howto_type *
1525 elfNN_aarch64_reloc_name_lookup (bfd *abfd ATTRIBUTE_UNUSED,
1526                                  const char *r_name)
1527 {
1528   unsigned int i;
1529
1530   for (i = 1; i < ARRAY_SIZE (elfNN_aarch64_howto_table) - 1; ++i)
1531     if (elfNN_aarch64_howto_table[i].name != NULL
1532         && strcasecmp (elfNN_aarch64_howto_table[i].name, r_name) == 0)
1533       return &elfNN_aarch64_howto_table[i];
1534
1535   return NULL;
1536 }
1537
1538 #define TARGET_LITTLE_SYM               bfd_elfNN_littleaarch64_vec
1539 #define TARGET_LITTLE_NAME              "elfNN-littleaarch64"
1540 #define TARGET_BIG_SYM                  bfd_elfNN_bigaarch64_vec
1541 #define TARGET_BIG_NAME                 "elfNN-bigaarch64"
1542
1543 /* The linker script knows the section names for placement.
1544    The entry_names are used to do simple name mangling on the stubs.
1545    Given a function name, and its type, the stub can be found. The
1546    name can be changed. The only requirement is the %s be present.  */
1547 #define STUB_ENTRY_NAME   "__%s_veneer"
1548
1549 /* The name of the dynamic interpreter.  This is put in the .interp
1550    section.  */
1551 #define ELF_DYNAMIC_INTERPRETER     "/lib/ld.so.1"
1552
1553 #define AARCH64_MAX_FWD_BRANCH_OFFSET \
1554   (((1 << 25) - 1) << 2)
1555 #define AARCH64_MAX_BWD_BRANCH_OFFSET \
1556   (-((1 << 25) << 2))
1557
1558 #define AARCH64_MAX_ADRP_IMM ((1 << 20) - 1)
1559 #define AARCH64_MIN_ADRP_IMM (-(1 << 20))
1560
1561 static int
1562 aarch64_valid_for_adrp_p (bfd_vma value, bfd_vma place)
1563 {
1564   bfd_signed_vma offset = (bfd_signed_vma) (PG (value) - PG (place)) >> 12;
1565   return offset <= AARCH64_MAX_ADRP_IMM && offset >= AARCH64_MIN_ADRP_IMM;
1566 }
1567
1568 static int
1569 aarch64_valid_branch_p (bfd_vma value, bfd_vma place)
1570 {
1571   bfd_signed_vma offset = (bfd_signed_vma) (value - place);
1572   return (offset <= AARCH64_MAX_FWD_BRANCH_OFFSET
1573           && offset >= AARCH64_MAX_BWD_BRANCH_OFFSET);
1574 }
1575
1576 static const uint32_t aarch64_adrp_branch_stub [] =
1577 {
1578   0x90000010,                   /*      adrp    ip0, X */
1579                                 /*              R_AARCH64_ADR_HI21_PCREL(X) */
1580   0x91000210,                   /*      add     ip0, ip0, :lo12:X */
1581                                 /*              R_AARCH64_ADD_ABS_LO12_NC(X) */
1582   0xd61f0200,                   /*      br      ip0 */
1583 };
1584
1585 static const uint32_t aarch64_long_branch_stub[] =
1586 {
1587 #if ARCH_SIZE == 64
1588   0x58000090,                   /*      ldr   ip0, 1f */
1589 #else
1590   0x18000090,                   /*      ldr   wip0, 1f */
1591 #endif
1592   0x10000011,                   /*      adr   ip1, #0 */
1593   0x8b110210,                   /*      add   ip0, ip0, ip1 */
1594   0xd61f0200,                   /*      br      ip0 */
1595   0x00000000,                   /* 1:   .xword or .word
1596                                    R_AARCH64_PRELNN(X) + 12
1597                                  */
1598   0x00000000,
1599 };
1600
1601 /* Section name for stubs is the associated section name plus this
1602    string.  */
1603 #define STUB_SUFFIX ".stub"
1604
1605 enum elf_aarch64_stub_type
1606 {
1607   aarch64_stub_none,
1608   aarch64_stub_adrp_branch,
1609   aarch64_stub_long_branch,
1610 };
1611
1612 struct elf_aarch64_stub_hash_entry
1613 {
1614   /* Base hash table entry structure.  */
1615   struct bfd_hash_entry root;
1616
1617   /* The stub section.  */
1618   asection *stub_sec;
1619
1620   /* Offset within stub_sec of the beginning of this stub.  */
1621   bfd_vma stub_offset;
1622
1623   /* Given the symbol's value and its section we can determine its final
1624      value when building the stubs (so the stub knows where to jump).  */
1625   bfd_vma target_value;
1626   asection *target_section;
1627
1628   enum elf_aarch64_stub_type stub_type;
1629
1630   /* The symbol table entry, if any, that this was derived from.  */
1631   struct elf_aarch64_link_hash_entry *h;
1632
1633   /* Destination symbol type */
1634   unsigned char st_type;
1635
1636   /* Where this stub is being called from, or, in the case of combined
1637      stub sections, the first input section in the group.  */
1638   asection *id_sec;
1639
1640   /* The name for the local symbol at the start of this stub.  The
1641      stub name in the hash table has to be unique; this does not, so
1642      it can be friendlier.  */
1643   char *output_name;
1644 };
1645
1646 /* Used to build a map of a section.  This is required for mixed-endian
1647    code/data.  */
1648
1649 typedef struct elf_elf_section_map
1650 {
1651   bfd_vma vma;
1652   char type;
1653 }
1654 elf_aarch64_section_map;
1655
1656
1657 typedef struct _aarch64_elf_section_data
1658 {
1659   struct bfd_elf_section_data elf;
1660   unsigned int mapcount;
1661   unsigned int mapsize;
1662   elf_aarch64_section_map *map;
1663 }
1664 _aarch64_elf_section_data;
1665
1666 #define elf_aarch64_section_data(sec) \
1667   ((_aarch64_elf_section_data *) elf_section_data (sec))
1668
1669 /* The size of the thread control block.  */
1670 #define TCB_SIZE        16
1671
1672 struct elf_aarch64_local_symbol
1673 {
1674   unsigned int got_type;
1675   bfd_signed_vma got_refcount;
1676   bfd_vma got_offset;
1677
1678   /* Offset of the GOTPLT entry reserved for the TLS descriptor. The
1679      offset is from the end of the jump table and reserved entries
1680      within the PLTGOT.
1681
1682      The magic value (bfd_vma) -1 indicates that an offset has not be
1683      allocated.  */
1684   bfd_vma tlsdesc_got_jump_table_offset;
1685 };
1686
1687 struct elf_aarch64_obj_tdata
1688 {
1689   struct elf_obj_tdata root;
1690
1691   /* local symbol descriptors */
1692   struct elf_aarch64_local_symbol *locals;
1693
1694   /* Zero to warn when linking objects with incompatible enum sizes.  */
1695   int no_enum_size_warning;
1696
1697   /* Zero to warn when linking objects with incompatible wchar_t sizes.  */
1698   int no_wchar_size_warning;
1699 };
1700
1701 #define elf_aarch64_tdata(bfd)                          \
1702   ((struct elf_aarch64_obj_tdata *) (bfd)->tdata.any)
1703
1704 #define elf_aarch64_locals(bfd) (elf_aarch64_tdata (bfd)->locals)
1705
1706 #define is_aarch64_elf(bfd)                             \
1707   (bfd_get_flavour (bfd) == bfd_target_elf_flavour      \
1708    && elf_tdata (bfd) != NULL                           \
1709    && elf_object_id (bfd) == AARCH64_ELF_DATA)
1710
1711 static bfd_boolean
1712 elfNN_aarch64_mkobject (bfd *abfd)
1713 {
1714   return bfd_elf_allocate_object (abfd, sizeof (struct elf_aarch64_obj_tdata),
1715                                   AARCH64_ELF_DATA);
1716 }
1717
1718 #define elf_aarch64_hash_entry(ent) \
1719   ((struct elf_aarch64_link_hash_entry *)(ent))
1720
1721 #define GOT_UNKNOWN    0
1722 #define GOT_NORMAL     1
1723 #define GOT_TLS_GD     2
1724 #define GOT_TLS_IE     4
1725 #define GOT_TLSDESC_GD 8
1726
1727 #define GOT_TLS_GD_ANY_P(type)  ((type & GOT_TLS_GD) || (type & GOT_TLSDESC_GD))
1728
1729 /* AArch64 ELF linker hash entry.  */
1730 struct elf_aarch64_link_hash_entry
1731 {
1732   struct elf_link_hash_entry root;
1733
1734   /* Track dynamic relocs copied for this symbol.  */
1735   struct elf_dyn_relocs *dyn_relocs;
1736
1737   /* Since PLT entries have variable size, we need to record the
1738      index into .got.plt instead of recomputing it from the PLT
1739      offset.  */
1740   bfd_signed_vma plt_got_offset;
1741
1742   /* Bit mask representing the type of GOT entry(s) if any required by
1743      this symbol.  */
1744   unsigned int got_type;
1745
1746   /* A pointer to the most recently used stub hash entry against this
1747      symbol.  */
1748   struct elf_aarch64_stub_hash_entry *stub_cache;
1749
1750   /* Offset of the GOTPLT entry reserved for the TLS descriptor.  The offset
1751      is from the end of the jump table and reserved entries within the PLTGOT.
1752
1753      The magic value (bfd_vma) -1 indicates that an offset has not
1754      be allocated.  */
1755   bfd_vma tlsdesc_got_jump_table_offset;
1756 };
1757
1758 static unsigned int
1759 elfNN_aarch64_symbol_got_type (struct elf_link_hash_entry *h,
1760                                bfd *abfd,
1761                                unsigned long r_symndx)
1762 {
1763   if (h)
1764     return elf_aarch64_hash_entry (h)->got_type;
1765
1766   if (! elf_aarch64_locals (abfd))
1767     return GOT_UNKNOWN;
1768
1769   return elf_aarch64_locals (abfd)[r_symndx].got_type;
1770 }
1771
1772 /* Get the AArch64 elf linker hash table from a link_info structure.  */
1773 #define elf_aarch64_hash_table(info)                                    \
1774   ((struct elf_aarch64_link_hash_table *) ((info)->hash))
1775
1776 #define aarch64_stub_hash_lookup(table, string, create, copy)           \
1777   ((struct elf_aarch64_stub_hash_entry *)                               \
1778    bfd_hash_lookup ((table), (string), (create), (copy)))
1779
1780 /* AArch64 ELF linker hash table.  */
1781 struct elf_aarch64_link_hash_table
1782 {
1783   /* The main hash table.  */
1784   struct elf_link_hash_table root;
1785
1786   /* Nonzero to force PIC branch veneers.  */
1787   int pic_veneer;
1788
1789   /* The number of bytes in the initial entry in the PLT.  */
1790   bfd_size_type plt_header_size;
1791
1792   /* The number of bytes in the subsequent PLT etries.  */
1793   bfd_size_type plt_entry_size;
1794
1795   /* Short-cuts to get to dynamic linker sections.  */
1796   asection *sdynbss;
1797   asection *srelbss;
1798
1799   /* Small local sym cache.  */
1800   struct sym_cache sym_cache;
1801
1802   /* For convenience in allocate_dynrelocs.  */
1803   bfd *obfd;
1804
1805   /* The amount of space used by the reserved portion of the sgotplt
1806      section, plus whatever space is used by the jump slots.  */
1807   bfd_vma sgotplt_jump_table_size;
1808
1809   /* The stub hash table.  */
1810   struct bfd_hash_table stub_hash_table;
1811
1812   /* Linker stub bfd.  */
1813   bfd *stub_bfd;
1814
1815   /* Linker call-backs.  */
1816   asection *(*add_stub_section) (const char *, asection *);
1817   void (*layout_sections_again) (void);
1818
1819   /* Array to keep track of which stub sections have been created, and
1820      information on stub grouping.  */
1821   struct map_stub
1822   {
1823     /* This is the section to which stubs in the group will be
1824        attached.  */
1825     asection *link_sec;
1826     /* The stub section.  */
1827     asection *stub_sec;
1828   } *stub_group;
1829
1830   /* Assorted information used by elfNN_aarch64_size_stubs.  */
1831   unsigned int bfd_count;
1832   int top_index;
1833   asection **input_list;
1834
1835   /* The offset into splt of the PLT entry for the TLS descriptor
1836      resolver.  Special values are 0, if not necessary (or not found
1837      to be necessary yet), and -1 if needed but not determined
1838      yet.  */
1839   bfd_vma tlsdesc_plt;
1840
1841   /* The GOT offset for the lazy trampoline.  Communicated to the
1842      loader via DT_TLSDESC_GOT.  The magic value (bfd_vma) -1
1843      indicates an offset is not allocated.  */
1844   bfd_vma dt_tlsdesc_got;
1845 };
1846
1847 /* Create an entry in an AArch64 ELF linker hash table.  */
1848
1849 static struct bfd_hash_entry *
1850 elfNN_aarch64_link_hash_newfunc (struct bfd_hash_entry *entry,
1851                                  struct bfd_hash_table *table,
1852                                  const char *string)
1853 {
1854   struct elf_aarch64_link_hash_entry *ret =
1855     (struct elf_aarch64_link_hash_entry *) entry;
1856
1857   /* Allocate the structure if it has not already been allocated by a
1858      subclass.  */
1859   if (ret == NULL)
1860     ret = bfd_hash_allocate (table,
1861                              sizeof (struct elf_aarch64_link_hash_entry));
1862   if (ret == NULL)
1863     return (struct bfd_hash_entry *) ret;
1864
1865   /* Call the allocation method of the superclass.  */
1866   ret = ((struct elf_aarch64_link_hash_entry *)
1867          _bfd_elf_link_hash_newfunc ((struct bfd_hash_entry *) ret,
1868                                      table, string));
1869   if (ret != NULL)
1870     {
1871       ret->dyn_relocs = NULL;
1872       ret->got_type = GOT_UNKNOWN;
1873       ret->plt_got_offset = (bfd_vma) - 1;
1874       ret->stub_cache = NULL;
1875       ret->tlsdesc_got_jump_table_offset = (bfd_vma) - 1;
1876     }
1877
1878   return (struct bfd_hash_entry *) ret;
1879 }
1880
1881 /* Initialize an entry in the stub hash table.  */
1882
1883 static struct bfd_hash_entry *
1884 stub_hash_newfunc (struct bfd_hash_entry *entry,
1885                    struct bfd_hash_table *table, const char *string)
1886 {
1887   /* Allocate the structure if it has not already been allocated by a
1888      subclass.  */
1889   if (entry == NULL)
1890     {
1891       entry = bfd_hash_allocate (table,
1892                                  sizeof (struct
1893                                          elf_aarch64_stub_hash_entry));
1894       if (entry == NULL)
1895         return entry;
1896     }
1897
1898   /* Call the allocation method of the superclass.  */
1899   entry = bfd_hash_newfunc (entry, table, string);
1900   if (entry != NULL)
1901     {
1902       struct elf_aarch64_stub_hash_entry *eh;
1903
1904       /* Initialize the local fields.  */
1905       eh = (struct elf_aarch64_stub_hash_entry *) entry;
1906       eh->stub_sec = NULL;
1907       eh->stub_offset = 0;
1908       eh->target_value = 0;
1909       eh->target_section = NULL;
1910       eh->stub_type = aarch64_stub_none;
1911       eh->h = NULL;
1912       eh->id_sec = NULL;
1913     }
1914
1915   return entry;
1916 }
1917
1918
1919 /* Copy the extra info we tack onto an elf_link_hash_entry.  */
1920
1921 static void
1922 elfNN_aarch64_copy_indirect_symbol (struct bfd_link_info *info,
1923                                     struct elf_link_hash_entry *dir,
1924                                     struct elf_link_hash_entry *ind)
1925 {
1926   struct elf_aarch64_link_hash_entry *edir, *eind;
1927
1928   edir = (struct elf_aarch64_link_hash_entry *) dir;
1929   eind = (struct elf_aarch64_link_hash_entry *) ind;
1930
1931   if (eind->dyn_relocs != NULL)
1932     {
1933       if (edir->dyn_relocs != NULL)
1934         {
1935           struct elf_dyn_relocs **pp;
1936           struct elf_dyn_relocs *p;
1937
1938           /* Add reloc counts against the indirect sym to the direct sym
1939              list.  Merge any entries against the same section.  */
1940           for (pp = &eind->dyn_relocs; (p = *pp) != NULL;)
1941             {
1942               struct elf_dyn_relocs *q;
1943
1944               for (q = edir->dyn_relocs; q != NULL; q = q->next)
1945                 if (q->sec == p->sec)
1946                   {
1947                     q->pc_count += p->pc_count;
1948                     q->count += p->count;
1949                     *pp = p->next;
1950                     break;
1951                   }
1952               if (q == NULL)
1953                 pp = &p->next;
1954             }
1955           *pp = edir->dyn_relocs;
1956         }
1957
1958       edir->dyn_relocs = eind->dyn_relocs;
1959       eind->dyn_relocs = NULL;
1960     }
1961
1962   if (ind->root.type == bfd_link_hash_indirect)
1963     {
1964       /* Copy over PLT info.  */
1965       if (dir->got.refcount <= 0)
1966         {
1967           edir->got_type = eind->got_type;
1968           eind->got_type = GOT_UNKNOWN;
1969         }
1970     }
1971
1972   _bfd_elf_link_hash_copy_indirect (info, dir, ind);
1973 }
1974
1975 /* Create an AArch64 elf linker hash table.  */
1976
1977 static struct bfd_link_hash_table *
1978 elfNN_aarch64_link_hash_table_create (bfd *abfd)
1979 {
1980   struct elf_aarch64_link_hash_table *ret;
1981   bfd_size_type amt = sizeof (struct elf_aarch64_link_hash_table);
1982
1983   ret = bfd_zmalloc (amt);
1984   if (ret == NULL)
1985     return NULL;
1986
1987   if (!_bfd_elf_link_hash_table_init
1988       (&ret->root, abfd, elfNN_aarch64_link_hash_newfunc,
1989        sizeof (struct elf_aarch64_link_hash_entry), AARCH64_ELF_DATA))
1990     {
1991       free (ret);
1992       return NULL;
1993     }
1994
1995   ret->plt_header_size = PLT_ENTRY_SIZE;
1996   ret->plt_entry_size = PLT_SMALL_ENTRY_SIZE;
1997   ret->obfd = abfd;
1998   ret->dt_tlsdesc_got = (bfd_vma) - 1;
1999
2000   if (!bfd_hash_table_init (&ret->stub_hash_table, stub_hash_newfunc,
2001                             sizeof (struct elf_aarch64_stub_hash_entry)))
2002     {
2003       free (ret);
2004       return NULL;
2005     }
2006
2007   return &ret->root.root;
2008 }
2009
2010 /* Free the derived linker hash table.  */
2011
2012 static void
2013 elfNN_aarch64_hash_table_free (struct bfd_link_hash_table *hash)
2014 {
2015   struct elf_aarch64_link_hash_table *ret
2016     = (struct elf_aarch64_link_hash_table *) hash;
2017
2018   bfd_hash_table_free (&ret->stub_hash_table);
2019   _bfd_elf_link_hash_table_free (hash);
2020 }
2021
2022 static bfd_boolean
2023 aarch64_relocate (unsigned int r_type, bfd *input_bfd, asection *input_section,
2024                   bfd_vma offset, bfd_vma value)
2025 {
2026   reloc_howto_type *howto;
2027   bfd_vma place;
2028
2029   howto = elfNN_aarch64_howto_from_type (r_type);
2030   place = (input_section->output_section->vma + input_section->output_offset
2031            + offset);
2032
2033   r_type = elfNN_aarch64_bfd_reloc_from_type (r_type);
2034   value = _bfd_aarch64_elf_resolve_relocation (r_type, place, value, 0, FALSE);
2035   return _bfd_aarch64_elf_put_addend (input_bfd,
2036                                       input_section->contents + offset, r_type,
2037                                       howto, value);
2038 }
2039
2040 static enum elf_aarch64_stub_type
2041 aarch64_select_branch_stub (bfd_vma value, bfd_vma place)
2042 {
2043   if (aarch64_valid_for_adrp_p (value, place))
2044     return aarch64_stub_adrp_branch;
2045   return aarch64_stub_long_branch;
2046 }
2047
2048 /* Determine the type of stub needed, if any, for a call.  */
2049
2050 static enum elf_aarch64_stub_type
2051 aarch64_type_of_stub (struct bfd_link_info *info,
2052                       asection *input_sec,
2053                       const Elf_Internal_Rela *rel,
2054                       unsigned char st_type,
2055                       struct elf_aarch64_link_hash_entry *hash,
2056                       bfd_vma destination)
2057 {
2058   bfd_vma location;
2059   bfd_signed_vma branch_offset;
2060   unsigned int r_type;
2061   struct elf_aarch64_link_hash_table *globals;
2062   enum elf_aarch64_stub_type stub_type = aarch64_stub_none;
2063   bfd_boolean via_plt_p;
2064
2065   if (st_type != STT_FUNC)
2066     return stub_type;
2067
2068   globals = elf_aarch64_hash_table (info);
2069   via_plt_p = (globals->root.splt != NULL && hash != NULL
2070                && hash->root.plt.offset != (bfd_vma) - 1);
2071
2072   if (via_plt_p)
2073     return stub_type;
2074
2075   /* Determine where the call point is.  */
2076   location = (input_sec->output_offset
2077               + input_sec->output_section->vma + rel->r_offset);
2078
2079   branch_offset = (bfd_signed_vma) (destination - location);
2080
2081   r_type = ELFNN_R_TYPE (rel->r_info);
2082
2083   /* We don't want to redirect any old unconditional jump in this way,
2084      only one which is being used for a sibcall, where it is
2085      acceptable for the IP0 and IP1 registers to be clobbered.  */
2086   if ((r_type == AARCH64_R (CALL26) || r_type == AARCH64_R (JUMP26))
2087       && (branch_offset > AARCH64_MAX_FWD_BRANCH_OFFSET
2088           || branch_offset < AARCH64_MAX_BWD_BRANCH_OFFSET))
2089     {
2090       stub_type = aarch64_stub_long_branch;
2091     }
2092
2093   return stub_type;
2094 }
2095
2096 /* Build a name for an entry in the stub hash table.  */
2097
2098 static char *
2099 elfNN_aarch64_stub_name (const asection *input_section,
2100                          const asection *sym_sec,
2101                          const struct elf_aarch64_link_hash_entry *hash,
2102                          const Elf_Internal_Rela *rel)
2103 {
2104   char *stub_name;
2105   bfd_size_type len;
2106
2107   if (hash)
2108     {
2109       len = 8 + 1 + strlen (hash->root.root.root.string) + 1 + 16 + 1;
2110       stub_name = bfd_malloc (len);
2111       if (stub_name != NULL)
2112         snprintf (stub_name, len, "%08x_%s+%" BFD_VMA_FMT "x",
2113                   (unsigned int) input_section->id,
2114                   hash->root.root.root.string,
2115                   rel->r_addend);
2116     }
2117   else
2118     {
2119       len = 8 + 1 + 8 + 1 + 8 + 1 + 16 + 1;
2120       stub_name = bfd_malloc (len);
2121       if (stub_name != NULL)
2122         snprintf (stub_name, len, "%08x_%x:%x+%" BFD_VMA_FMT "x",
2123                   (unsigned int) input_section->id,
2124                   (unsigned int) sym_sec->id,
2125                   (unsigned int) ELFNN_R_SYM (rel->r_info),
2126                   rel->r_addend);
2127     }
2128
2129   return stub_name;
2130 }
2131
2132 /* Look up an entry in the stub hash.  Stub entries are cached because
2133    creating the stub name takes a bit of time.  */
2134
2135 static struct elf_aarch64_stub_hash_entry *
2136 elfNN_aarch64_get_stub_entry (const asection *input_section,
2137                               const asection *sym_sec,
2138                               struct elf_link_hash_entry *hash,
2139                               const Elf_Internal_Rela *rel,
2140                               struct elf_aarch64_link_hash_table *htab)
2141 {
2142   struct elf_aarch64_stub_hash_entry *stub_entry;
2143   struct elf_aarch64_link_hash_entry *h =
2144     (struct elf_aarch64_link_hash_entry *) hash;
2145   const asection *id_sec;
2146
2147   if ((input_section->flags & SEC_CODE) == 0)
2148     return NULL;
2149
2150   /* If this input section is part of a group of sections sharing one
2151      stub section, then use the id of the first section in the group.
2152      Stub names need to include a section id, as there may well be
2153      more than one stub used to reach say, printf, and we need to
2154      distinguish between them.  */
2155   id_sec = htab->stub_group[input_section->id].link_sec;
2156
2157   if (h != NULL && h->stub_cache != NULL
2158       && h->stub_cache->h == h && h->stub_cache->id_sec == id_sec)
2159     {
2160       stub_entry = h->stub_cache;
2161     }
2162   else
2163     {
2164       char *stub_name;
2165
2166       stub_name = elfNN_aarch64_stub_name (id_sec, sym_sec, h, rel);
2167       if (stub_name == NULL)
2168         return NULL;
2169
2170       stub_entry = aarch64_stub_hash_lookup (&htab->stub_hash_table,
2171                                              stub_name, FALSE, FALSE);
2172       if (h != NULL)
2173         h->stub_cache = stub_entry;
2174
2175       free (stub_name);
2176     }
2177
2178   return stub_entry;
2179 }
2180
2181 /* Add a new stub entry to the stub hash.  Not all fields of the new
2182    stub entry are initialised.  */
2183
2184 static struct elf_aarch64_stub_hash_entry *
2185 elfNN_aarch64_add_stub (const char *stub_name,
2186                         asection *section,
2187                         struct elf_aarch64_link_hash_table *htab)
2188 {
2189   asection *link_sec;
2190   asection *stub_sec;
2191   struct elf_aarch64_stub_hash_entry *stub_entry;
2192
2193   link_sec = htab->stub_group[section->id].link_sec;
2194   stub_sec = htab->stub_group[section->id].stub_sec;
2195   if (stub_sec == NULL)
2196     {
2197       stub_sec = htab->stub_group[link_sec->id].stub_sec;
2198       if (stub_sec == NULL)
2199         {
2200           size_t namelen;
2201           bfd_size_type len;
2202           char *s_name;
2203
2204           namelen = strlen (link_sec->name);
2205           len = namelen + sizeof (STUB_SUFFIX);
2206           s_name = bfd_alloc (htab->stub_bfd, len);
2207           if (s_name == NULL)
2208             return NULL;
2209
2210           memcpy (s_name, link_sec->name, namelen);
2211           memcpy (s_name + namelen, STUB_SUFFIX, sizeof (STUB_SUFFIX));
2212           stub_sec = (*htab->add_stub_section) (s_name, link_sec);
2213           if (stub_sec == NULL)
2214             return NULL;
2215           htab->stub_group[link_sec->id].stub_sec = stub_sec;
2216         }
2217       htab->stub_group[section->id].stub_sec = stub_sec;
2218     }
2219
2220   /* Enter this entry into the linker stub hash table.  */
2221   stub_entry = aarch64_stub_hash_lookup (&htab->stub_hash_table, stub_name,
2222                                          TRUE, FALSE);
2223   if (stub_entry == NULL)
2224     {
2225       (*_bfd_error_handler) (_("%s: cannot create stub entry %s"),
2226                              section->owner, stub_name);
2227       return NULL;
2228     }
2229
2230   stub_entry->stub_sec = stub_sec;
2231   stub_entry->stub_offset = 0;
2232   stub_entry->id_sec = link_sec;
2233
2234   return stub_entry;
2235 }
2236
2237 static bfd_boolean
2238 aarch64_build_one_stub (struct bfd_hash_entry *gen_entry,
2239                         void *in_arg ATTRIBUTE_UNUSED)
2240 {
2241   struct elf_aarch64_stub_hash_entry *stub_entry;
2242   asection *stub_sec;
2243   bfd *stub_bfd;
2244   bfd_byte *loc;
2245   bfd_vma sym_value;
2246   unsigned int template_size;
2247   const uint32_t *template;
2248   unsigned int i;
2249
2250   /* Massage our args to the form they really have.  */
2251   stub_entry = (struct elf_aarch64_stub_hash_entry *) gen_entry;
2252
2253   stub_sec = stub_entry->stub_sec;
2254
2255   /* Make a note of the offset within the stubs for this entry.  */
2256   stub_entry->stub_offset = stub_sec->size;
2257   loc = stub_sec->contents + stub_entry->stub_offset;
2258
2259   stub_bfd = stub_sec->owner;
2260
2261   /* This is the address of the stub destination.  */
2262   sym_value = (stub_entry->target_value
2263                + stub_entry->target_section->output_offset
2264                + stub_entry->target_section->output_section->vma);
2265
2266   if (stub_entry->stub_type == aarch64_stub_long_branch)
2267     {
2268       bfd_vma place = (stub_entry->stub_offset + stub_sec->output_section->vma
2269                        + stub_sec->output_offset);
2270
2271       /* See if we can relax the stub.  */
2272       if (aarch64_valid_for_adrp_p (sym_value, place))
2273         stub_entry->stub_type = aarch64_select_branch_stub (sym_value, place);
2274     }
2275
2276   switch (stub_entry->stub_type)
2277     {
2278     case aarch64_stub_adrp_branch:
2279       template = aarch64_adrp_branch_stub;
2280       template_size = sizeof (aarch64_adrp_branch_stub);
2281       break;
2282     case aarch64_stub_long_branch:
2283       template = aarch64_long_branch_stub;
2284       template_size = sizeof (aarch64_long_branch_stub);
2285       break;
2286     default:
2287       BFD_FAIL ();
2288       return FALSE;
2289     }
2290
2291   for (i = 0; i < (template_size / sizeof template[0]); i++)
2292     {
2293       bfd_putl32 (template[i], loc);
2294       loc += 4;
2295     }
2296
2297   template_size = (template_size + 7) & ~7;
2298   stub_sec->size += template_size;
2299
2300   switch (stub_entry->stub_type)
2301     {
2302     case aarch64_stub_adrp_branch:
2303       if (aarch64_relocate (AARCH64_R (ADR_PREL_PG_HI21), stub_bfd, stub_sec,
2304                             stub_entry->stub_offset, sym_value))
2305         /* The stub would not have been relaxed if the offset was out
2306            of range.  */
2307         BFD_FAIL ();
2308
2309       _bfd_final_link_relocate
2310         (elfNN_aarch64_howto_from_type (AARCH64_R (ADD_ABS_LO12_NC)),
2311          stub_bfd,
2312          stub_sec,
2313          stub_sec->contents,
2314          stub_entry->stub_offset + 4,
2315          sym_value,
2316          0);
2317       break;
2318
2319     case aarch64_stub_long_branch:
2320       /* We want the value relative to the address 12 bytes back from the
2321          value itself.  */
2322       _bfd_final_link_relocate (elfNN_aarch64_howto_from_type
2323                                 (AARCH64_R (PRELNN)), stub_bfd, stub_sec,
2324                                 stub_sec->contents,
2325                                 stub_entry->stub_offset + 16,
2326                                 sym_value + 12, 0);
2327       break;
2328     default:
2329       break;
2330     }
2331
2332   return TRUE;
2333 }
2334
2335 /* As above, but don't actually build the stub.  Just bump offset so
2336    we know stub section sizes.  */
2337
2338 static bfd_boolean
2339 aarch64_size_one_stub (struct bfd_hash_entry *gen_entry,
2340                        void *in_arg ATTRIBUTE_UNUSED)
2341 {
2342   struct elf_aarch64_stub_hash_entry *stub_entry;
2343   int size;
2344
2345   /* Massage our args to the form they really have.  */
2346   stub_entry = (struct elf_aarch64_stub_hash_entry *) gen_entry;
2347
2348   switch (stub_entry->stub_type)
2349     {
2350     case aarch64_stub_adrp_branch:
2351       size = sizeof (aarch64_adrp_branch_stub);
2352       break;
2353     case aarch64_stub_long_branch:
2354       size = sizeof (aarch64_long_branch_stub);
2355       break;
2356     default:
2357       BFD_FAIL ();
2358       return FALSE;
2359       break;
2360     }
2361
2362   size = (size + 7) & ~7;
2363   stub_entry->stub_sec->size += size;
2364   return TRUE;
2365 }
2366
2367 /* External entry points for sizing and building linker stubs.  */
2368
2369 /* Set up various things so that we can make a list of input sections
2370    for each output section included in the link.  Returns -1 on error,
2371    0 when no stubs will be needed, and 1 on success.  */
2372
2373 int
2374 elfNN_aarch64_setup_section_lists (bfd *output_bfd,
2375                                    struct bfd_link_info *info)
2376 {
2377   bfd *input_bfd;
2378   unsigned int bfd_count;
2379   int top_id, top_index;
2380   asection *section;
2381   asection **input_list, **list;
2382   bfd_size_type amt;
2383   struct elf_aarch64_link_hash_table *htab =
2384     elf_aarch64_hash_table (info);
2385
2386   if (!is_elf_hash_table (htab))
2387     return 0;
2388
2389   /* Count the number of input BFDs and find the top input section id.  */
2390   for (input_bfd = info->input_bfds, bfd_count = 0, top_id = 0;
2391        input_bfd != NULL; input_bfd = input_bfd->link_next)
2392     {
2393       bfd_count += 1;
2394       for (section = input_bfd->sections;
2395            section != NULL; section = section->next)
2396         {
2397           if (top_id < section->id)
2398             top_id = section->id;
2399         }
2400     }
2401   htab->bfd_count = bfd_count;
2402
2403   amt = sizeof (struct map_stub) * (top_id + 1);
2404   htab->stub_group = bfd_zmalloc (amt);
2405   if (htab->stub_group == NULL)
2406     return -1;
2407
2408   /* We can't use output_bfd->section_count here to find the top output
2409      section index as some sections may have been removed, and
2410      _bfd_strip_section_from_output doesn't renumber the indices.  */
2411   for (section = output_bfd->sections, top_index = 0;
2412        section != NULL; section = section->next)
2413     {
2414       if (top_index < section->index)
2415         top_index = section->index;
2416     }
2417
2418   htab->top_index = top_index;
2419   amt = sizeof (asection *) * (top_index + 1);
2420   input_list = bfd_malloc (amt);
2421   htab->input_list = input_list;
2422   if (input_list == NULL)
2423     return -1;
2424
2425   /* For sections we aren't interested in, mark their entries with a
2426      value we can check later.  */
2427   list = input_list + top_index;
2428   do
2429     *list = bfd_abs_section_ptr;
2430   while (list-- != input_list);
2431
2432   for (section = output_bfd->sections;
2433        section != NULL; section = section->next)
2434     {
2435       if ((section->flags & SEC_CODE) != 0)
2436         input_list[section->index] = NULL;
2437     }
2438
2439   return 1;
2440 }
2441
2442 /* Used by elfNN_aarch64_next_input_section and group_sections.  */
2443 #define PREV_SEC(sec) (htab->stub_group[(sec)->id].link_sec)
2444
2445 /* The linker repeatedly calls this function for each input section,
2446    in the order that input sections are linked into output sections.
2447    Build lists of input sections to determine groupings between which
2448    we may insert linker stubs.  */
2449
2450 void
2451 elfNN_aarch64_next_input_section (struct bfd_link_info *info, asection *isec)
2452 {
2453   struct elf_aarch64_link_hash_table *htab =
2454     elf_aarch64_hash_table (info);
2455
2456   if (isec->output_section->index <= htab->top_index)
2457     {
2458       asection **list = htab->input_list + isec->output_section->index;
2459
2460       if (*list != bfd_abs_section_ptr)
2461         {
2462           /* Steal the link_sec pointer for our list.  */
2463           /* This happens to make the list in reverse order,
2464              which is what we want.  */
2465           PREV_SEC (isec) = *list;
2466           *list = isec;
2467         }
2468     }
2469 }
2470
2471 /* See whether we can group stub sections together.  Grouping stub
2472    sections may result in fewer stubs.  More importantly, we need to
2473    put all .init* and .fini* stubs at the beginning of the .init or
2474    .fini output sections respectively, because glibc splits the
2475    _init and _fini functions into multiple parts.  Putting a stub in
2476    the middle of a function is not a good idea.  */
2477
2478 static void
2479 group_sections (struct elf_aarch64_link_hash_table *htab,
2480                 bfd_size_type stub_group_size,
2481                 bfd_boolean stubs_always_before_branch)
2482 {
2483   asection **list = htab->input_list + htab->top_index;
2484
2485   do
2486     {
2487       asection *tail = *list;
2488
2489       if (tail == bfd_abs_section_ptr)
2490         continue;
2491
2492       while (tail != NULL)
2493         {
2494           asection *curr;
2495           asection *prev;
2496           bfd_size_type total;
2497
2498           curr = tail;
2499           total = tail->size;
2500           while ((prev = PREV_SEC (curr)) != NULL
2501                  && ((total += curr->output_offset - prev->output_offset)
2502                      < stub_group_size))
2503             curr = prev;
2504
2505           /* OK, the size from the start of CURR to the end is less
2506              than stub_group_size and thus can be handled by one stub
2507              section.  (Or the tail section is itself larger than
2508              stub_group_size, in which case we may be toast.)
2509              We should really be keeping track of the total size of
2510              stubs added here, as stubs contribute to the final output
2511              section size.  */
2512           do
2513             {
2514               prev = PREV_SEC (tail);
2515               /* Set up this stub group.  */
2516               htab->stub_group[tail->id].link_sec = curr;
2517             }
2518           while (tail != curr && (tail = prev) != NULL);
2519
2520           /* But wait, there's more!  Input sections up to stub_group_size
2521              bytes before the stub section can be handled by it too.  */
2522           if (!stubs_always_before_branch)
2523             {
2524               total = 0;
2525               while (prev != NULL
2526                      && ((total += tail->output_offset - prev->output_offset)
2527                          < stub_group_size))
2528                 {
2529                   tail = prev;
2530                   prev = PREV_SEC (tail);
2531                   htab->stub_group[tail->id].link_sec = curr;
2532                 }
2533             }
2534           tail = prev;
2535         }
2536     }
2537   while (list-- != htab->input_list);
2538
2539   free (htab->input_list);
2540 }
2541
2542 #undef PREV_SEC
2543
2544 /* Determine and set the size of the stub section for a final link.
2545
2546    The basic idea here is to examine all the relocations looking for
2547    PC-relative calls to a target that is unreachable with a "bl"
2548    instruction.  */
2549
2550 bfd_boolean
2551 elfNN_aarch64_size_stubs (bfd *output_bfd,
2552                           bfd *stub_bfd,
2553                           struct bfd_link_info *info,
2554                           bfd_signed_vma group_size,
2555                           asection * (*add_stub_section) (const char *,
2556                                                           asection *),
2557                           void (*layout_sections_again) (void))
2558 {
2559   bfd_size_type stub_group_size;
2560   bfd_boolean stubs_always_before_branch;
2561   bfd_boolean stub_changed = 0;
2562   struct elf_aarch64_link_hash_table *htab = elf_aarch64_hash_table (info);
2563
2564   /* Propagate mach to stub bfd, because it may not have been
2565      finalized when we created stub_bfd.  */
2566   bfd_set_arch_mach (stub_bfd, bfd_get_arch (output_bfd),
2567                      bfd_get_mach (output_bfd));
2568
2569   /* Stash our params away.  */
2570   htab->stub_bfd = stub_bfd;
2571   htab->add_stub_section = add_stub_section;
2572   htab->layout_sections_again = layout_sections_again;
2573   stubs_always_before_branch = group_size < 0;
2574   if (group_size < 0)
2575     stub_group_size = -group_size;
2576   else
2577     stub_group_size = group_size;
2578
2579   if (stub_group_size == 1)
2580     {
2581       /* Default values.  */
2582       /* AArch64 branch range is +-128MB. The value used is 1MB less.  */
2583       stub_group_size = 127 * 1024 * 1024;
2584     }
2585
2586   group_sections (htab, stub_group_size, stubs_always_before_branch);
2587
2588   while (1)
2589     {
2590       bfd *input_bfd;
2591       unsigned int bfd_indx;
2592       asection *stub_sec;
2593
2594       for (input_bfd = info->input_bfds, bfd_indx = 0;
2595            input_bfd != NULL; input_bfd = input_bfd->link_next, bfd_indx++)
2596         {
2597           Elf_Internal_Shdr *symtab_hdr;
2598           asection *section;
2599           Elf_Internal_Sym *local_syms = NULL;
2600
2601           /* We'll need the symbol table in a second.  */
2602           symtab_hdr = &elf_tdata (input_bfd)->symtab_hdr;
2603           if (symtab_hdr->sh_info == 0)
2604             continue;
2605
2606           /* Walk over each section attached to the input bfd.  */
2607           for (section = input_bfd->sections;
2608                section != NULL; section = section->next)
2609             {
2610               Elf_Internal_Rela *internal_relocs, *irelaend, *irela;
2611
2612               /* If there aren't any relocs, then there's nothing more
2613                  to do.  */
2614               if ((section->flags & SEC_RELOC) == 0
2615                   || section->reloc_count == 0
2616                   || (section->flags & SEC_CODE) == 0)
2617                 continue;
2618
2619               /* If this section is a link-once section that will be
2620                  discarded, then don't create any stubs.  */
2621               if (section->output_section == NULL
2622                   || section->output_section->owner != output_bfd)
2623                 continue;
2624
2625               /* Get the relocs.  */
2626               internal_relocs
2627                 = _bfd_elf_link_read_relocs (input_bfd, section, NULL,
2628                                              NULL, info->keep_memory);
2629               if (internal_relocs == NULL)
2630                 goto error_ret_free_local;
2631
2632               /* Now examine each relocation.  */
2633               irela = internal_relocs;
2634               irelaend = irela + section->reloc_count;
2635               for (; irela < irelaend; irela++)
2636                 {
2637                   unsigned int r_type, r_indx;
2638                   enum elf_aarch64_stub_type stub_type;
2639                   struct elf_aarch64_stub_hash_entry *stub_entry;
2640                   asection *sym_sec;
2641                   bfd_vma sym_value;
2642                   bfd_vma destination;
2643                   struct elf_aarch64_link_hash_entry *hash;
2644                   const char *sym_name;
2645                   char *stub_name;
2646                   const asection *id_sec;
2647                   unsigned char st_type;
2648                   bfd_size_type len;
2649
2650                   r_type = ELFNN_R_TYPE (irela->r_info);
2651                   r_indx = ELFNN_R_SYM (irela->r_info);
2652
2653                   if (r_type >= (unsigned int) R_AARCH64_end)
2654                     {
2655                       bfd_set_error (bfd_error_bad_value);
2656                     error_ret_free_internal:
2657                       if (elf_section_data (section)->relocs == NULL)
2658                         free (internal_relocs);
2659                       goto error_ret_free_local;
2660                     }
2661
2662                   /* Only look for stubs on unconditional branch and
2663                      branch and link instructions.  */
2664                   if (r_type != (unsigned int) AARCH64_R (CALL26)
2665                       && r_type != (unsigned int) AARCH64_R (JUMP26))
2666                     continue;
2667
2668                   /* Now determine the call target, its name, value,
2669                      section.  */
2670                   sym_sec = NULL;
2671                   sym_value = 0;
2672                   destination = 0;
2673                   hash = NULL;
2674                   sym_name = NULL;
2675                   if (r_indx < symtab_hdr->sh_info)
2676                     {
2677                       /* It's a local symbol.  */
2678                       Elf_Internal_Sym *sym;
2679                       Elf_Internal_Shdr *hdr;
2680
2681                       if (local_syms == NULL)
2682                         {
2683                           local_syms
2684                             = (Elf_Internal_Sym *) symtab_hdr->contents;
2685                           if (local_syms == NULL)
2686                             local_syms
2687                               = bfd_elf_get_elf_syms (input_bfd, symtab_hdr,
2688                                                       symtab_hdr->sh_info, 0,
2689                                                       NULL, NULL, NULL);
2690                           if (local_syms == NULL)
2691                             goto error_ret_free_internal;
2692                         }
2693
2694                       sym = local_syms + r_indx;
2695                       hdr = elf_elfsections (input_bfd)[sym->st_shndx];
2696                       sym_sec = hdr->bfd_section;
2697                       if (!sym_sec)
2698                         /* This is an undefined symbol.  It can never
2699                            be resolved.  */
2700                         continue;
2701
2702                       if (ELF_ST_TYPE (sym->st_info) != STT_SECTION)
2703                         sym_value = sym->st_value;
2704                       destination = (sym_value + irela->r_addend
2705                                      + sym_sec->output_offset
2706                                      + sym_sec->output_section->vma);
2707                       st_type = ELF_ST_TYPE (sym->st_info);
2708                       sym_name
2709                         = bfd_elf_string_from_elf_section (input_bfd,
2710                                                            symtab_hdr->sh_link,
2711                                                            sym->st_name);
2712                     }
2713                   else
2714                     {
2715                       int e_indx;
2716
2717                       e_indx = r_indx - symtab_hdr->sh_info;
2718                       hash = ((struct elf_aarch64_link_hash_entry *)
2719                               elf_sym_hashes (input_bfd)[e_indx]);
2720
2721                       while (hash->root.root.type == bfd_link_hash_indirect
2722                              || hash->root.root.type == bfd_link_hash_warning)
2723                         hash = ((struct elf_aarch64_link_hash_entry *)
2724                                 hash->root.root.u.i.link);
2725
2726                       if (hash->root.root.type == bfd_link_hash_defined
2727                           || hash->root.root.type == bfd_link_hash_defweak)
2728                         {
2729                           struct elf_aarch64_link_hash_table *globals =
2730                             elf_aarch64_hash_table (info);
2731                           sym_sec = hash->root.root.u.def.section;
2732                           sym_value = hash->root.root.u.def.value;
2733                           /* For a destination in a shared library,
2734                              use the PLT stub as target address to
2735                              decide whether a branch stub is
2736                              needed.  */
2737                           if (globals->root.splt != NULL && hash != NULL
2738                               && hash->root.plt.offset != (bfd_vma) - 1)
2739                             {
2740                               sym_sec = globals->root.splt;
2741                               sym_value = hash->root.plt.offset;
2742                               if (sym_sec->output_section != NULL)
2743                                 destination = (sym_value
2744                                                + sym_sec->output_offset
2745                                                +
2746                                                sym_sec->output_section->vma);
2747                             }
2748                           else if (sym_sec->output_section != NULL)
2749                             destination = (sym_value + irela->r_addend
2750                                            + sym_sec->output_offset
2751                                            + sym_sec->output_section->vma);
2752                         }
2753                       else if (hash->root.root.type == bfd_link_hash_undefined
2754                                || (hash->root.root.type
2755                                    == bfd_link_hash_undefweak))
2756                         {
2757                           /* For a shared library, use the PLT stub as
2758                              target address to decide whether a long
2759                              branch stub is needed.
2760                              For absolute code, they cannot be handled.  */
2761                           struct elf_aarch64_link_hash_table *globals =
2762                             elf_aarch64_hash_table (info);
2763
2764                           if (globals->root.splt != NULL && hash != NULL
2765                               && hash->root.plt.offset != (bfd_vma) - 1)
2766                             {
2767                               sym_sec = globals->root.splt;
2768                               sym_value = hash->root.plt.offset;
2769                               if (sym_sec->output_section != NULL)
2770                                 destination = (sym_value
2771                                                + sym_sec->output_offset
2772                                                +
2773                                                sym_sec->output_section->vma);
2774                             }
2775                           else
2776                             continue;
2777                         }
2778                       else
2779                         {
2780                           bfd_set_error (bfd_error_bad_value);
2781                           goto error_ret_free_internal;
2782                         }
2783                       st_type = ELF_ST_TYPE (hash->root.type);
2784                       sym_name = hash->root.root.root.string;
2785                     }
2786
2787                   /* Determine what (if any) linker stub is needed.  */
2788                   stub_type = aarch64_type_of_stub
2789                     (info, section, irela, st_type, hash, destination);
2790                   if (stub_type == aarch64_stub_none)
2791                     continue;
2792
2793                   /* Support for grouping stub sections.  */
2794                   id_sec = htab->stub_group[section->id].link_sec;
2795
2796                   /* Get the name of this stub.  */
2797                   stub_name = elfNN_aarch64_stub_name (id_sec, sym_sec, hash,
2798                                                        irela);
2799                   if (!stub_name)
2800                     goto error_ret_free_internal;
2801
2802                   stub_entry =
2803                     aarch64_stub_hash_lookup (&htab->stub_hash_table,
2804                                               stub_name, FALSE, FALSE);
2805                   if (stub_entry != NULL)
2806                     {
2807                       /* The proper stub has already been created.  */
2808                       free (stub_name);
2809                       continue;
2810                     }
2811
2812                   stub_entry = elfNN_aarch64_add_stub (stub_name, section,
2813                                                        htab);
2814                   if (stub_entry == NULL)
2815                     {
2816                       free (stub_name);
2817                       goto error_ret_free_internal;
2818                     }
2819
2820                   stub_entry->target_value = sym_value;
2821                   stub_entry->target_section = sym_sec;
2822                   stub_entry->stub_type = stub_type;
2823                   stub_entry->h = hash;
2824                   stub_entry->st_type = st_type;
2825
2826                   if (sym_name == NULL)
2827                     sym_name = "unnamed";
2828                   len = sizeof (STUB_ENTRY_NAME) + strlen (sym_name);
2829                   stub_entry->output_name = bfd_alloc (htab->stub_bfd, len);
2830                   if (stub_entry->output_name == NULL)
2831                     {
2832                       free (stub_name);
2833                       goto error_ret_free_internal;
2834                     }
2835
2836                   snprintf (stub_entry->output_name, len, STUB_ENTRY_NAME,
2837                             sym_name);
2838
2839                   stub_changed = TRUE;
2840                 }
2841
2842               /* We're done with the internal relocs, free them.  */
2843               if (elf_section_data (section)->relocs == NULL)
2844                 free (internal_relocs);
2845             }
2846         }
2847
2848       if (!stub_changed)
2849         break;
2850
2851       /* OK, we've added some stubs.  Find out the new size of the
2852          stub sections.  */
2853       for (stub_sec = htab->stub_bfd->sections;
2854            stub_sec != NULL; stub_sec = stub_sec->next)
2855         stub_sec->size = 0;
2856
2857       bfd_hash_traverse (&htab->stub_hash_table, aarch64_size_one_stub, htab);
2858
2859       /* Ask the linker to do its stuff.  */
2860       (*htab->layout_sections_again) ();
2861       stub_changed = FALSE;
2862     }
2863
2864   return TRUE;
2865
2866 error_ret_free_local:
2867   return FALSE;
2868 }
2869
2870 /* Build all the stubs associated with the current output file.  The
2871    stubs are kept in a hash table attached to the main linker hash
2872    table.  We also set up the .plt entries for statically linked PIC
2873    functions here.  This function is called via aarch64_elf_finish in the
2874    linker.  */
2875
2876 bfd_boolean
2877 elfNN_aarch64_build_stubs (struct bfd_link_info *info)
2878 {
2879   asection *stub_sec;
2880   struct bfd_hash_table *table;
2881   struct elf_aarch64_link_hash_table *htab;
2882
2883   htab = elf_aarch64_hash_table (info);
2884
2885   for (stub_sec = htab->stub_bfd->sections;
2886        stub_sec != NULL; stub_sec = stub_sec->next)
2887     {
2888       bfd_size_type size;
2889
2890       /* Ignore non-stub sections.  */
2891       if (!strstr (stub_sec->name, STUB_SUFFIX))
2892         continue;
2893
2894       /* Allocate memory to hold the linker stubs.  */
2895       size = stub_sec->size;
2896       stub_sec->contents = bfd_zalloc (htab->stub_bfd, size);
2897       if (stub_sec->contents == NULL && size != 0)
2898         return FALSE;
2899       stub_sec->size = 0;
2900     }
2901
2902   /* Build the stubs as directed by the stub hash table.  */
2903   table = &htab->stub_hash_table;
2904   bfd_hash_traverse (table, aarch64_build_one_stub, info);
2905
2906   return TRUE;
2907 }
2908
2909
2910 /* Add an entry to the code/data map for section SEC.  */
2911
2912 static void
2913 elfNN_aarch64_section_map_add (asection *sec, char type, bfd_vma vma)
2914 {
2915   struct _aarch64_elf_section_data *sec_data =
2916     elf_aarch64_section_data (sec);
2917   unsigned int newidx;
2918
2919   if (sec_data->map == NULL)
2920     {
2921       sec_data->map = bfd_malloc (sizeof (elf_aarch64_section_map));
2922       sec_data->mapcount = 0;
2923       sec_data->mapsize = 1;
2924     }
2925
2926   newidx = sec_data->mapcount++;
2927
2928   if (sec_data->mapcount > sec_data->mapsize)
2929     {
2930       sec_data->mapsize *= 2;
2931       sec_data->map = bfd_realloc_or_free
2932         (sec_data->map, sec_data->mapsize * sizeof (elf_aarch64_section_map));
2933     }
2934
2935   if (sec_data->map)
2936     {
2937       sec_data->map[newidx].vma = vma;
2938       sec_data->map[newidx].type = type;
2939     }
2940 }
2941
2942
2943 /* Initialise maps of insn/data for input BFDs.  */
2944 void
2945 bfd_elfNN_aarch64_init_maps (bfd *abfd)
2946 {
2947   Elf_Internal_Sym *isymbuf;
2948   Elf_Internal_Shdr *hdr;
2949   unsigned int i, localsyms;
2950
2951   /* Make sure that we are dealing with an AArch64 elf binary.  */
2952   if (!is_aarch64_elf (abfd))
2953     return;
2954
2955   if ((abfd->flags & DYNAMIC) != 0)
2956     return;
2957
2958   hdr = &elf_symtab_hdr (abfd);
2959   localsyms = hdr->sh_info;
2960
2961   /* Obtain a buffer full of symbols for this BFD. The hdr->sh_info field
2962      should contain the number of local symbols, which should come before any
2963      global symbols.  Mapping symbols are always local.  */
2964   isymbuf = bfd_elf_get_elf_syms (abfd, hdr, localsyms, 0, NULL, NULL, NULL);
2965
2966   /* No internal symbols read?  Skip this BFD.  */
2967   if (isymbuf == NULL)
2968     return;
2969
2970   for (i = 0; i < localsyms; i++)
2971     {
2972       Elf_Internal_Sym *isym = &isymbuf[i];
2973       asection *sec = bfd_section_from_elf_index (abfd, isym->st_shndx);
2974       const char *name;
2975
2976       if (sec != NULL && ELF_ST_BIND (isym->st_info) == STB_LOCAL)
2977         {
2978           name = bfd_elf_string_from_elf_section (abfd,
2979                                                   hdr->sh_link,
2980                                                   isym->st_name);
2981
2982           if (bfd_is_aarch64_special_symbol_name
2983               (name, BFD_AARCH64_SPECIAL_SYM_TYPE_MAP))
2984             elfNN_aarch64_section_map_add (sec, name[1], isym->st_value);
2985         }
2986     }
2987 }
2988
2989 /* Set option values needed during linking.  */
2990 void
2991 bfd_elfNN_aarch64_set_options (struct bfd *output_bfd,
2992                                struct bfd_link_info *link_info,
2993                                int no_enum_warn,
2994                                int no_wchar_warn, int pic_veneer)
2995 {
2996   struct elf_aarch64_link_hash_table *globals;
2997
2998   globals = elf_aarch64_hash_table (link_info);
2999   globals->pic_veneer = pic_veneer;
3000
3001   BFD_ASSERT (is_aarch64_elf (output_bfd));
3002   elf_aarch64_tdata (output_bfd)->no_enum_size_warning = no_enum_warn;
3003   elf_aarch64_tdata (output_bfd)->no_wchar_size_warning = no_wchar_warn;
3004 }
3005
3006 static bfd_vma
3007 aarch64_calculate_got_entry_vma (struct elf_link_hash_entry *h,
3008                                  struct elf_aarch64_link_hash_table
3009                                  *globals, struct bfd_link_info *info,
3010                                  bfd_vma value, bfd *output_bfd,
3011                                  bfd_boolean *unresolved_reloc_p)
3012 {
3013   bfd_vma off = (bfd_vma) - 1;
3014   asection *basegot = globals->root.sgot;
3015   bfd_boolean dyn = globals->root.dynamic_sections_created;
3016
3017   if (h != NULL)
3018     {
3019       BFD_ASSERT (basegot != NULL);
3020       off = h->got.offset;
3021       BFD_ASSERT (off != (bfd_vma) - 1);
3022       if (!WILL_CALL_FINISH_DYNAMIC_SYMBOL (dyn, info->shared, h)
3023           || (info->shared
3024               && SYMBOL_REFERENCES_LOCAL (info, h))
3025           || (ELF_ST_VISIBILITY (h->other)
3026               && h->root.type == bfd_link_hash_undefweak))
3027         {
3028           /* This is actually a static link, or it is a -Bsymbolic link
3029              and the symbol is defined locally.  We must initialize this
3030              entry in the global offset table.  Since the offset must
3031              always be a multiple of 8 (4 in the case of ILP32), we use
3032              the least significant bit to record whether we have
3033              initialized it already.
3034              When doing a dynamic link, we create a .rel(a).got relocation
3035              entry to initialize the value.  This is done in the
3036              finish_dynamic_symbol routine.  */
3037           if ((off & 1) != 0)
3038             off &= ~1;
3039           else
3040             {
3041               bfd_put_NN (output_bfd, value, basegot->contents + off);
3042               h->got.offset |= 1;
3043             }
3044         }
3045       else
3046         *unresolved_reloc_p = FALSE;
3047
3048       off = off + basegot->output_section->vma + basegot->output_offset;
3049     }
3050
3051   return off;
3052 }
3053
3054 /* Change R_TYPE to a more efficient access model where possible,
3055    return the new reloc type.  */
3056
3057 static bfd_reloc_code_real_type
3058 aarch64_tls_transition_without_check (bfd_reloc_code_real_type r_type,
3059                                       struct elf_link_hash_entry *h)
3060 {
3061   bfd_boolean is_local = h == NULL;
3062
3063   switch (r_type)
3064     {
3065     case BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21:
3066     case BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21:
3067       return (is_local
3068               ? BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1
3069               : BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21);
3070
3071     case BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC:
3072     case BFD_RELOC_AARCH64_TLSDESC_LDNN_LO12_NC:
3073       return (is_local
3074               ? BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC
3075               : BFD_RELOC_AARCH64_TLSIE_LDNN_GOTTPREL_LO12_NC);
3076
3077     case BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
3078       return is_local ? BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1 : r_type;
3079
3080     case BFD_RELOC_AARCH64_TLSIE_LDNN_GOTTPREL_LO12_NC:
3081       return is_local ? BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC : r_type;
3082
3083     case BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC:
3084     case BFD_RELOC_AARCH64_TLSDESC_CALL:
3085       /* Instructions with these relocations will become NOPs.  */
3086       return BFD_RELOC_AARCH64_NONE;
3087
3088     default:
3089       break;
3090     }
3091
3092   return r_type;
3093 }
3094
3095 static unsigned int
3096 aarch64_reloc_got_type (bfd_reloc_code_real_type r_type)
3097 {
3098   switch (r_type)
3099     {
3100     case BFD_RELOC_AARCH64_LD64_GOT_LO12_NC:
3101     case BFD_RELOC_AARCH64_LD32_GOT_LO12_NC:
3102     case BFD_RELOC_AARCH64_ADR_GOT_PAGE:
3103     case BFD_RELOC_AARCH64_GOT_LD_PREL19:
3104       return GOT_NORMAL;
3105
3106     case BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21:
3107     case BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC:
3108       return GOT_TLS_GD;
3109
3110     case BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC:
3111     case BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21:
3112     case BFD_RELOC_AARCH64_TLSDESC_CALL:
3113     case BFD_RELOC_AARCH64_TLSDESC_LD64_LO12_NC:
3114     case BFD_RELOC_AARCH64_TLSDESC_LD32_LO12_NC:
3115       return GOT_TLSDESC_GD;
3116
3117     case BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
3118     case BFD_RELOC_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
3119     case BFD_RELOC_AARCH64_TLSIE_LD32_GOTTPREL_LO12_NC:
3120       return GOT_TLS_IE;
3121
3122     case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_HI12:
3123     case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12:
3124     case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
3125     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0:
3126     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
3127     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1:
3128     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
3129     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G2:
3130       return GOT_UNKNOWN;
3131
3132     default:
3133       break;
3134     }
3135   return GOT_UNKNOWN;
3136 }
3137
3138 static bfd_boolean
3139 aarch64_can_relax_tls (bfd *input_bfd,
3140                        struct bfd_link_info *info,
3141                        bfd_reloc_code_real_type r_type,
3142                        struct elf_link_hash_entry *h,
3143                        unsigned long r_symndx)
3144 {
3145   unsigned int symbol_got_type;
3146   unsigned int reloc_got_type;
3147
3148   if (! IS_AARCH64_TLS_RELOC (r_type))
3149     return FALSE;
3150
3151   symbol_got_type = elfNN_aarch64_symbol_got_type (h, input_bfd, r_symndx);
3152   reloc_got_type = aarch64_reloc_got_type (r_type);
3153
3154   if (symbol_got_type == GOT_TLS_IE && GOT_TLS_GD_ANY_P (reloc_got_type))
3155     return TRUE;
3156
3157   if (info->shared)
3158     return FALSE;
3159
3160   if  (h && h->root.type == bfd_link_hash_undefweak)
3161     return FALSE;
3162
3163   return TRUE;
3164 }
3165
3166 /* Given the relocation code R_TYPE, return the relaxed bfd reloc
3167    enumerator.  */
3168
3169 static bfd_reloc_code_real_type
3170 aarch64_tls_transition (bfd *input_bfd,
3171                         struct bfd_link_info *info,
3172                         unsigned int r_type,
3173                         struct elf_link_hash_entry *h,
3174                         unsigned long r_symndx)
3175 {
3176   bfd_reloc_code_real_type bfd_r_type
3177     = elfNN_aarch64_bfd_reloc_from_type (r_type);
3178
3179   if (! aarch64_can_relax_tls (input_bfd, info, bfd_r_type, h, r_symndx))
3180     return bfd_r_type;
3181
3182   return aarch64_tls_transition_without_check (bfd_r_type, h);
3183 }
3184
3185 /* Return the base VMA address which should be subtracted from real addresses
3186    when resolving R_AARCH64_TLS_DTPREL relocation.  */
3187
3188 static bfd_vma
3189 dtpoff_base (struct bfd_link_info *info)
3190 {
3191   /* If tls_sec is NULL, we should have signalled an error already.  */
3192   BFD_ASSERT (elf_hash_table (info)->tls_sec != NULL);
3193   return elf_hash_table (info)->tls_sec->vma;
3194 }
3195
3196 /* Return the base VMA address which should be subtracted from real addresses
3197    when resolving R_AARCH64_TLS_GOTTPREL64 relocations.  */
3198
3199 static bfd_vma
3200 tpoff_base (struct bfd_link_info *info)
3201 {
3202   struct elf_link_hash_table *htab = elf_hash_table (info);
3203
3204   /* If tls_sec is NULL, we should have signalled an error already.  */
3205   if (htab->tls_sec == NULL)
3206     return 0;
3207
3208   bfd_vma base = align_power ((bfd_vma) TCB_SIZE,
3209                               htab->tls_sec->alignment_power);
3210   return htab->tls_sec->vma - base;
3211 }
3212
3213 static bfd_vma *
3214 symbol_got_offset_ref (bfd *input_bfd, struct elf_link_hash_entry *h,
3215                        unsigned long r_symndx)
3216 {
3217   /* Calculate the address of the GOT entry for symbol
3218      referred to in h.  */
3219   if (h != NULL)
3220     return &h->got.offset;
3221   else
3222     {
3223       /* local symbol */
3224       struct elf_aarch64_local_symbol *l;
3225
3226       l = elf_aarch64_locals (input_bfd);
3227       return &l[r_symndx].got_offset;
3228     }
3229 }
3230
3231 static void
3232 symbol_got_offset_mark (bfd *input_bfd, struct elf_link_hash_entry *h,
3233                         unsigned long r_symndx)
3234 {
3235   bfd_vma *p;
3236   p = symbol_got_offset_ref (input_bfd, h, r_symndx);
3237   *p |= 1;
3238 }
3239
3240 static int
3241 symbol_got_offset_mark_p (bfd *input_bfd, struct elf_link_hash_entry *h,
3242                           unsigned long r_symndx)
3243 {
3244   bfd_vma value;
3245   value = * symbol_got_offset_ref (input_bfd, h, r_symndx);
3246   return value & 1;
3247 }
3248
3249 static bfd_vma
3250 symbol_got_offset (bfd *input_bfd, struct elf_link_hash_entry *h,
3251                    unsigned long r_symndx)
3252 {
3253   bfd_vma value;
3254   value = * symbol_got_offset_ref (input_bfd, h, r_symndx);
3255   value &= ~1;
3256   return value;
3257 }
3258
3259 static bfd_vma *
3260 symbol_tlsdesc_got_offset_ref (bfd *input_bfd, struct elf_link_hash_entry *h,
3261                                unsigned long r_symndx)
3262 {
3263   /* Calculate the address of the GOT entry for symbol
3264      referred to in h.  */
3265   if (h != NULL)
3266     {
3267       struct elf_aarch64_link_hash_entry *eh;
3268       eh = (struct elf_aarch64_link_hash_entry *) h;
3269       return &eh->tlsdesc_got_jump_table_offset;
3270     }
3271   else
3272     {
3273       /* local symbol */
3274       struct elf_aarch64_local_symbol *l;
3275
3276       l = elf_aarch64_locals (input_bfd);
3277       return &l[r_symndx].tlsdesc_got_jump_table_offset;
3278     }
3279 }
3280
3281 static void
3282 symbol_tlsdesc_got_offset_mark (bfd *input_bfd, struct elf_link_hash_entry *h,
3283                                 unsigned long r_symndx)
3284 {
3285   bfd_vma *p;
3286   p = symbol_tlsdesc_got_offset_ref (input_bfd, h, r_symndx);
3287   *p |= 1;
3288 }
3289
3290 static int
3291 symbol_tlsdesc_got_offset_mark_p (bfd *input_bfd,
3292                                   struct elf_link_hash_entry *h,
3293                                   unsigned long r_symndx)
3294 {
3295   bfd_vma value;
3296   value = * symbol_tlsdesc_got_offset_ref (input_bfd, h, r_symndx);
3297   return value & 1;
3298 }
3299
3300 static bfd_vma
3301 symbol_tlsdesc_got_offset (bfd *input_bfd, struct elf_link_hash_entry *h,
3302                           unsigned long r_symndx)
3303 {
3304   bfd_vma value;
3305   value = * symbol_tlsdesc_got_offset_ref (input_bfd, h, r_symndx);
3306   value &= ~1;
3307   return value;
3308 }
3309
3310 /* Perform a relocation as part of a final link.  */
3311 static bfd_reloc_status_type
3312 elfNN_aarch64_final_link_relocate (reloc_howto_type *howto,
3313                                    bfd *input_bfd,
3314                                    bfd *output_bfd,
3315                                    asection *input_section,
3316                                    bfd_byte *contents,
3317                                    Elf_Internal_Rela *rel,
3318                                    bfd_vma value,
3319                                    struct bfd_link_info *info,
3320                                    asection *sym_sec,
3321                                    struct elf_link_hash_entry *h,
3322                                    bfd_boolean *unresolved_reloc_p,
3323                                    bfd_boolean save_addend,
3324                                    bfd_vma *saved_addend)
3325 {
3326   unsigned int r_type = howto->type;
3327   bfd_reloc_code_real_type bfd_r_type
3328     = elfNN_aarch64_bfd_reloc_from_howto (howto);
3329   bfd_reloc_code_real_type new_bfd_r_type;
3330   unsigned long r_symndx;
3331   bfd_byte *hit_data = contents + rel->r_offset;
3332   bfd_vma place;
3333   bfd_signed_vma signed_addend;
3334   struct elf_aarch64_link_hash_table *globals;
3335   bfd_boolean weak_undef_p;
3336
3337   globals = elf_aarch64_hash_table (info);
3338
3339   BFD_ASSERT (is_aarch64_elf (input_bfd));
3340
3341   r_symndx = ELFNN_R_SYM (rel->r_info);
3342
3343   /* It is possible to have linker relaxations on some TLS access
3344      models.  Update our information here.  */
3345   new_bfd_r_type = aarch64_tls_transition (input_bfd, info, r_type, h, r_symndx);
3346   if (new_bfd_r_type != bfd_r_type)
3347     {
3348       bfd_r_type = new_bfd_r_type;
3349       howto = elfNN_aarch64_howto_from_bfd_reloc (bfd_r_type);
3350       BFD_ASSERT (howto != NULL);
3351       r_type = howto->type;
3352     }
3353
3354   place = input_section->output_section->vma
3355     + input_section->output_offset + rel->r_offset;
3356
3357   /* Get addend, accumulating the addend for consecutive relocs
3358      which refer to the same offset.  */
3359   signed_addend = saved_addend ? *saved_addend : 0;
3360   signed_addend += rel->r_addend;
3361
3362   weak_undef_p = (h ? h->root.type == bfd_link_hash_undefweak
3363                   : bfd_is_und_section (sym_sec));
3364
3365   switch (bfd_r_type)
3366     {
3367     case BFD_RELOC_AARCH64_NONE:
3368     case BFD_RELOC_AARCH64_TLSDESC_CALL:
3369       *unresolved_reloc_p = FALSE;
3370       return bfd_reloc_ok;
3371
3372     case BFD_RELOC_AARCH64_NN:
3373
3374       /* When generating a shared object or relocatable executable, these
3375          relocations are copied into the output file to be resolved at
3376          run time.  */
3377       if (((info->shared == TRUE) || globals->root.is_relocatable_executable)
3378           && (input_section->flags & SEC_ALLOC)
3379           && (h == NULL
3380               || ELF_ST_VISIBILITY (h->other) == STV_DEFAULT
3381               || h->root.type != bfd_link_hash_undefweak))
3382         {
3383           Elf_Internal_Rela outrel;
3384           bfd_byte *loc;
3385           bfd_boolean skip, relocate;
3386           asection *sreloc;
3387
3388           *unresolved_reloc_p = FALSE;
3389
3390           sreloc = _bfd_elf_get_dynamic_reloc_section (input_bfd,
3391                                                        input_section, 1);
3392           if (sreloc == NULL)
3393             return bfd_reloc_notsupported;
3394
3395           skip = FALSE;
3396           relocate = FALSE;
3397
3398           outrel.r_addend = signed_addend;
3399           outrel.r_offset =
3400             _bfd_elf_section_offset (output_bfd, info, input_section,
3401                                      rel->r_offset);
3402           if (outrel.r_offset == (bfd_vma) - 1)
3403             skip = TRUE;
3404           else if (outrel.r_offset == (bfd_vma) - 2)
3405             {
3406               skip = TRUE;
3407               relocate = TRUE;
3408             }
3409
3410           outrel.r_offset += (input_section->output_section->vma
3411                               + input_section->output_offset);
3412
3413           if (skip)
3414             memset (&outrel, 0, sizeof outrel);
3415           else if (h != NULL
3416                    && h->dynindx != -1
3417                    && (!info->shared || !info->symbolic || !h->def_regular))
3418             outrel.r_info = ELFNN_R_INFO (h->dynindx, r_type);
3419           else
3420             {
3421               int symbol;
3422
3423               /* On SVR4-ish systems, the dynamic loader cannot
3424                  relocate the text and data segments independently,
3425                  so the symbol does not matter.  */
3426               symbol = 0;
3427               outrel.r_info = ELFNN_R_INFO (symbol, AARCH64_R (RELATIVE));
3428               outrel.r_addend += value;
3429             }
3430
3431           loc = sreloc->contents + sreloc->reloc_count++ * RELOC_SIZE (htab);
3432           bfd_elfNN_swap_reloca_out (output_bfd, &outrel, loc);
3433
3434           if (sreloc->reloc_count * RELOC_SIZE (htab) > sreloc->size)
3435             {
3436               /* Sanity to check that we have previously allocated
3437                  sufficient space in the relocation section for the
3438                  number of relocations we actually want to emit.  */
3439               abort ();
3440             }
3441
3442           /* If this reloc is against an external symbol, we do not want to
3443              fiddle with the addend.  Otherwise, we need to include the symbol
3444              value so that it becomes an addend for the dynamic reloc.  */
3445           if (!relocate)
3446             return bfd_reloc_ok;
3447
3448           return _bfd_final_link_relocate (howto, input_bfd, input_section,
3449                                            contents, rel->r_offset, value,
3450                                            signed_addend);
3451         }
3452       else
3453         value += signed_addend;
3454       break;
3455
3456     case BFD_RELOC_AARCH64_JUMP26:
3457     case BFD_RELOC_AARCH64_CALL26:
3458       {
3459         asection *splt = globals->root.splt;
3460         bfd_boolean via_plt_p =
3461           splt != NULL && h != NULL && h->plt.offset != (bfd_vma) - 1;
3462
3463         /* A call to an undefined weak symbol is converted to a jump to
3464            the next instruction unless a PLT entry will be created.
3465            The jump to the next instruction is optimized as a NOP.
3466            Do the same for local undefined symbols.  */
3467         if (weak_undef_p && ! via_plt_p)
3468           {
3469             bfd_putl32 (INSN_NOP, hit_data);
3470             return bfd_reloc_ok;
3471           }
3472
3473         /* If the call goes through a PLT entry, make sure to
3474            check distance to the right destination address.  */
3475         if (via_plt_p)
3476           {
3477             value = (splt->output_section->vma
3478                      + splt->output_offset + h->plt.offset);
3479             *unresolved_reloc_p = FALSE;
3480           }
3481
3482         /* If the target symbol is global and marked as a function the
3483            relocation applies a function call or a tail call.  In this
3484            situation we can veneer out of range branches.  The veneers
3485            use IP0 and IP1 hence cannot be used arbitrary out of range
3486            branches that occur within the body of a function.  */
3487         if (h && h->type == STT_FUNC)
3488           {
3489             /* Check if a stub has to be inserted because the destination
3490                is too far away.  */
3491             if (! aarch64_valid_branch_p (value, place))
3492               {
3493                 /* The target is out of reach, so redirect the branch to
3494                    the local stub for this function.  */
3495                 struct elf_aarch64_stub_hash_entry *stub_entry;
3496                 stub_entry = elfNN_aarch64_get_stub_entry (input_section,
3497                                                            sym_sec, h,
3498                                                            rel, globals);
3499                 if (stub_entry != NULL)
3500                   value = (stub_entry->stub_offset
3501                            + stub_entry->stub_sec->output_offset
3502                            + stub_entry->stub_sec->output_section->vma);
3503               }
3504           }
3505       }
3506       value = _bfd_aarch64_elf_resolve_relocation (bfd_r_type, place, value,
3507                                                    signed_addend, weak_undef_p);
3508       break;
3509
3510     case BFD_RELOC_AARCH64_16:
3511 #if ARCH_SIZE == 64
3512     case BFD_RELOC_AARCH64_32:
3513 #endif
3514     case BFD_RELOC_AARCH64_ADD_LO12:
3515     case BFD_RELOC_AARCH64_ADR_LO21_PCREL:
3516     case BFD_RELOC_AARCH64_ADR_HI21_PCREL:
3517     case BFD_RELOC_AARCH64_ADR_HI21_NC_PCREL:
3518     case BFD_RELOC_AARCH64_BRANCH19:
3519     case BFD_RELOC_AARCH64_LD_LO19_PCREL:
3520     case BFD_RELOC_AARCH64_LDST8_LO12:
3521     case BFD_RELOC_AARCH64_LDST16_LO12:
3522     case BFD_RELOC_AARCH64_LDST32_LO12:
3523     case BFD_RELOC_AARCH64_LDST64_LO12:
3524     case BFD_RELOC_AARCH64_LDST128_LO12:
3525     case BFD_RELOC_AARCH64_MOVW_G0_S:
3526     case BFD_RELOC_AARCH64_MOVW_G1_S:
3527     case BFD_RELOC_AARCH64_MOVW_G2_S:
3528     case BFD_RELOC_AARCH64_MOVW_G0:
3529     case BFD_RELOC_AARCH64_MOVW_G0_NC:
3530     case BFD_RELOC_AARCH64_MOVW_G1:
3531     case BFD_RELOC_AARCH64_MOVW_G1_NC:
3532     case BFD_RELOC_AARCH64_MOVW_G2:
3533     case BFD_RELOC_AARCH64_MOVW_G2_NC:
3534     case BFD_RELOC_AARCH64_MOVW_G3:
3535     case BFD_RELOC_AARCH64_16_PCREL:
3536     case BFD_RELOC_AARCH64_32_PCREL:
3537     case BFD_RELOC_AARCH64_64_PCREL:
3538     case BFD_RELOC_AARCH64_TSTBR14:
3539       value = _bfd_aarch64_elf_resolve_relocation (bfd_r_type, place, value,
3540                                                    signed_addend, weak_undef_p);
3541       break;
3542
3543     case BFD_RELOC_AARCH64_LD64_GOT_LO12_NC:
3544     case BFD_RELOC_AARCH64_LD32_GOT_LO12_NC:
3545     case BFD_RELOC_AARCH64_ADR_GOT_PAGE:
3546     case BFD_RELOC_AARCH64_GOT_LD_PREL19:
3547       if (globals->root.sgot == NULL)
3548         BFD_ASSERT (h != NULL);
3549
3550       if (h != NULL)
3551         {
3552           value = aarch64_calculate_got_entry_vma (h, globals, info, value,
3553                                                    output_bfd,
3554                                                    unresolved_reloc_p);
3555           value = _bfd_aarch64_elf_resolve_relocation (bfd_r_type, place, value,
3556                                                        0, weak_undef_p);
3557         }
3558       break;
3559
3560     case BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21:
3561     case BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC:
3562     case BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
3563     case BFD_RELOC_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
3564     case BFD_RELOC_AARCH64_TLSIE_LD32_GOTTPREL_LO12_NC:
3565       if (globals->root.sgot == NULL)
3566         return bfd_reloc_notsupported;
3567
3568       value = (symbol_got_offset (input_bfd, h, r_symndx)
3569                + globals->root.sgot->output_section->vma
3570                + globals->root.sgot->output_section->output_offset);
3571
3572       value = _bfd_aarch64_elf_resolve_relocation (bfd_r_type, place, value,
3573                                                    0, weak_undef_p);
3574       *unresolved_reloc_p = FALSE;
3575       break;
3576
3577     case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_HI12:
3578     case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12:
3579     case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
3580     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0:
3581     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
3582     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1:
3583     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
3584     case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G2:
3585       value = _bfd_aarch64_elf_resolve_relocation (bfd_r_type, place, value,
3586                                                    signed_addend - tpoff_base (info),
3587                                                    weak_undef_p);
3588       *unresolved_reloc_p = FALSE;
3589       break;
3590
3591     case BFD_RELOC_AARCH64_TLSDESC_ADD:
3592     case BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC:
3593     case BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21:
3594     case BFD_RELOC_AARCH64_TLSDESC_LD32_LO12_NC:
3595     case BFD_RELOC_AARCH64_TLSDESC_LD64_LO12_NC:
3596     case BFD_RELOC_AARCH64_TLSDESC_LDR:
3597       if (globals->root.sgot == NULL)
3598         return bfd_reloc_notsupported;
3599
3600       value = (symbol_tlsdesc_got_offset (input_bfd, h, r_symndx)
3601                + globals->root.sgotplt->output_section->vma
3602                + globals->root.sgotplt->output_section->output_offset
3603                + globals->sgotplt_jump_table_size);
3604
3605       value = _bfd_aarch64_elf_resolve_relocation (bfd_r_type, place, value,
3606                                                    0, weak_undef_p);
3607       *unresolved_reloc_p = FALSE;
3608       break;
3609
3610     default:
3611       return bfd_reloc_notsupported;
3612     }
3613
3614   if (saved_addend)
3615     *saved_addend = value;
3616
3617   /* Only apply the final relocation in a sequence.  */
3618   if (save_addend)
3619     return bfd_reloc_continue;
3620
3621   return _bfd_aarch64_elf_put_addend (input_bfd, hit_data, bfd_r_type,
3622                                       howto, value);
3623 }
3624
3625 /* Handle TLS relaxations.  Relaxing is possible for symbols that use
3626    R_AARCH64_TLSDESC_ADR_{PAGE, LD64_LO12_NC, ADD_LO12_NC} during a static
3627    link.
3628
3629    Return bfd_reloc_ok if we're done, bfd_reloc_continue if the caller
3630    is to then call final_link_relocate.  Return other values in the
3631    case of error.  */
3632
3633 static bfd_reloc_status_type
3634 elfNN_aarch64_tls_relax (struct elf_aarch64_link_hash_table *globals,
3635                          bfd *input_bfd, bfd_byte *contents,
3636                          Elf_Internal_Rela *rel, struct elf_link_hash_entry *h)
3637 {
3638   bfd_boolean is_local = h == NULL;
3639   unsigned int r_type = ELFNN_R_TYPE (rel->r_info);
3640   unsigned long insn;
3641
3642   BFD_ASSERT (globals && input_bfd && contents && rel);
3643
3644   switch (elfNN_aarch64_bfd_reloc_from_type (r_type))
3645     {
3646     case BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21:
3647     case BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21:
3648       if (is_local)
3649         {
3650           /* GD->LE relaxation:
3651              adrp x0, :tlsgd:var     =>   movz x0, :tprel_g1:var
3652              or
3653              adrp x0, :tlsdesc:var   =>   movz x0, :tprel_g1:var
3654            */
3655           bfd_putl32 (0xd2a00000, contents + rel->r_offset);
3656           return bfd_reloc_continue;
3657         }
3658       else
3659         {
3660           /* GD->IE relaxation:
3661              adrp x0, :tlsgd:var     =>   adrp x0, :gottprel:var
3662              or
3663              adrp x0, :tlsdesc:var   =>   adrp x0, :gottprel:var
3664            */
3665           insn = bfd_getl32 (contents + rel->r_offset);
3666           return bfd_reloc_continue;
3667         }
3668
3669     case BFD_RELOC_AARCH64_TLSDESC_LDNN_LO12_NC:
3670       if (is_local)
3671         {
3672           /* GD->LE relaxation:
3673              ldr xd, [x0, #:tlsdesc_lo12:var]   =>   movk x0, :tprel_g0_nc:var
3674            */
3675           bfd_putl32 (0xf2800000, contents + rel->r_offset);
3676           return bfd_reloc_continue;
3677         }
3678       else
3679         {
3680           /* GD->IE relaxation:
3681              ldr xd, [x0, #:tlsdesc_lo12:var] => ldr x0, [x0, #:gottprel_lo12:var]
3682            */
3683           insn = bfd_getl32 (contents + rel->r_offset);
3684           insn &= 0xfffffff0;
3685           bfd_putl32 (insn, contents + rel->r_offset);
3686           return bfd_reloc_continue;
3687         }
3688
3689     case BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC:
3690       if (is_local)
3691         {
3692           /* GD->LE relaxation
3693              add  x0, #:tlsgd_lo12:var  => movk x0, :tprel_g0_nc:var
3694              bl   __tls_get_addr        => mrs  x1, tpidr_el0
3695              nop                        => add  x0, x1, x0
3696            */
3697
3698           /* First kill the tls_get_addr reloc on the bl instruction.  */
3699           BFD_ASSERT (rel->r_offset + 4 == rel[1].r_offset);
3700           rel[1].r_info = ELFNN_R_INFO (STN_UNDEF, R_AARCH64_NONE);
3701
3702           bfd_putl32 (0xf2800000, contents + rel->r_offset);
3703           bfd_putl32 (0xd53bd041, contents + rel->r_offset + 4);
3704           bfd_putl32 (0x8b000020, contents + rel->r_offset + 8);
3705           return bfd_reloc_continue;
3706         }
3707       else
3708         {
3709           /* GD->IE relaxation
3710              ADD  x0, #:tlsgd_lo12:var  => ldr  x0, [x0, #:gottprel_lo12:var]
3711              BL   __tls_get_addr        => mrs  x1, tpidr_el0
3712                R_AARCH64_CALL26
3713              NOP                        => add  x0, x1, x0
3714            */
3715
3716           BFD_ASSERT (ELFNN_R_TYPE (rel[1].r_info) == AARCH64_R (CALL26));
3717
3718           /* Remove the relocation on the BL instruction.  */
3719           rel[1].r_info = ELFNN_R_INFO (STN_UNDEF, R_AARCH64_NONE);
3720
3721           bfd_putl32 (0xf9400000, contents + rel->r_offset);
3722
3723           /* We choose to fixup the BL and NOP instructions using the
3724              offset from the second relocation to allow flexibility in
3725              scheduling instructions between the ADD and BL.  */
3726           bfd_putl32 (0xd53bd041, contents + rel[1].r_offset);
3727           bfd_putl32 (0x8b000020, contents + rel[1].r_offset + 4);
3728           return bfd_reloc_continue;
3729         }
3730
3731     case BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC:
3732     case BFD_RELOC_AARCH64_TLSDESC_CALL:
3733       /* GD->IE/LE relaxation:
3734          add x0, x0, #:tlsdesc_lo12:var   =>   nop
3735          blr xd                           =>   nop
3736        */
3737       bfd_putl32 (INSN_NOP, contents + rel->r_offset);
3738       return bfd_reloc_ok;
3739
3740     case BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
3741       /* IE->LE relaxation:
3742          adrp xd, :gottprel:var   =>   movz xd, :tprel_g1:var
3743        */
3744       if (is_local)
3745         {
3746           insn = bfd_getl32 (contents + rel->r_offset);
3747           bfd_putl32 (0xd2a00000 | (insn & 0x1f), contents + rel->r_offset);
3748         }
3749       return bfd_reloc_continue;
3750
3751     case BFD_RELOC_AARCH64_TLSIE_LDNN_GOTTPREL_LO12_NC:
3752       /* IE->LE relaxation:
3753          ldr  xd, [xm, #:gottprel_lo12:var]   =>   movk xd, :tprel_g0_nc:var
3754        */
3755       if (is_local)
3756         {
3757           insn = bfd_getl32 (contents + rel->r_offset);
3758           bfd_putl32 (0xf2800000 | (insn & 0x1f), contents + rel->r_offset);
3759         }
3760       return bfd_reloc_continue;
3761
3762     default:
3763       return bfd_reloc_continue;
3764     }
3765
3766   return bfd_reloc_ok;
3767 }
3768
3769 /* Relocate an AArch64 ELF section.  */
3770
3771 static bfd_boolean
3772 elfNN_aarch64_relocate_section (bfd *output_bfd,
3773                                 struct bfd_link_info *info,
3774                                 bfd *input_bfd,
3775                                 asection *input_section,
3776                                 bfd_byte *contents,
3777                                 Elf_Internal_Rela *relocs,
3778                                 Elf_Internal_Sym *local_syms,
3779                                 asection **local_sections)
3780 {
3781   Elf_Internal_Shdr *symtab_hdr;
3782   struct elf_link_hash_entry **sym_hashes;
3783   Elf_Internal_Rela *rel;
3784   Elf_Internal_Rela *relend;
3785   const char *name;
3786   struct elf_aarch64_link_hash_table *globals;
3787   bfd_boolean save_addend = FALSE;
3788   bfd_vma addend = 0;
3789
3790   globals = elf_aarch64_hash_table (info);
3791
3792   symtab_hdr = &elf_symtab_hdr (input_bfd);
3793   sym_hashes = elf_sym_hashes (input_bfd);
3794
3795   rel = relocs;
3796   relend = relocs + input_section->reloc_count;
3797   for (; rel < relend; rel++)
3798     {
3799       unsigned int r_type;
3800       bfd_reloc_code_real_type bfd_r_type;
3801       bfd_reloc_code_real_type relaxed_bfd_r_type;
3802       reloc_howto_type *howto;
3803       unsigned long r_symndx;
3804       Elf_Internal_Sym *sym;
3805       asection *sec;
3806       struct elf_link_hash_entry *h;
3807       bfd_vma relocation;
3808       bfd_reloc_status_type r;
3809       arelent bfd_reloc;
3810       char sym_type;
3811       bfd_boolean unresolved_reloc = FALSE;
3812       char *error_message = NULL;
3813
3814       r_symndx = ELFNN_R_SYM (rel->r_info);
3815       r_type = ELFNN_R_TYPE (rel->r_info);
3816
3817       bfd_reloc.howto = elfNN_aarch64_howto_from_type (r_type);
3818       howto = bfd_reloc.howto;
3819
3820       if (howto == NULL)
3821         {
3822           (*_bfd_error_handler)
3823             (_("%B: unrecognized relocation (0x%x) in section `%A'"),
3824              input_bfd, input_section, r_type);
3825           return FALSE;
3826         }
3827       bfd_r_type = elfNN_aarch64_bfd_reloc_from_howto (howto);
3828
3829       h = NULL;
3830       sym = NULL;
3831       sec = NULL;
3832
3833       if (r_symndx < symtab_hdr->sh_info)
3834         {
3835           sym = local_syms + r_symndx;
3836           sym_type = ELFNN_ST_TYPE (sym->st_info);
3837           sec = local_sections[r_symndx];
3838
3839           /* An object file might have a reference to a local
3840              undefined symbol.  This is a daft object file, but we
3841              should at least do something about it.  */
3842           if (r_type != R_AARCH64_NONE && r_type != R_AARCH64_NULL
3843               && bfd_is_und_section (sec)
3844               && ELF_ST_BIND (sym->st_info) != STB_WEAK)
3845             {
3846               if (!info->callbacks->undefined_symbol
3847                   (info, bfd_elf_string_from_elf_section
3848                    (input_bfd, symtab_hdr->sh_link, sym->st_name),
3849                    input_bfd, input_section, rel->r_offset, TRUE))
3850                 return FALSE;
3851             }
3852
3853           relocation = _bfd_elf_rela_local_sym (output_bfd, sym, &sec, rel);
3854         }
3855       else
3856         {
3857           bfd_boolean warned;
3858
3859           RELOC_FOR_GLOBAL_SYMBOL (info, input_bfd, input_section, rel,
3860                                    r_symndx, symtab_hdr, sym_hashes,
3861                                    h, sec, relocation,
3862                                    unresolved_reloc, warned);
3863
3864           sym_type = h->type;
3865         }
3866
3867       if (sec != NULL && discarded_section (sec))
3868         RELOC_AGAINST_DISCARDED_SECTION (info, input_bfd, input_section,
3869                                          rel, 1, relend, howto, 0, contents);
3870
3871       if (info->relocatable)
3872         {
3873           /* This is a relocatable link.  We don't have to change
3874              anything, unless the reloc is against a section symbol,
3875              in which case we have to adjust according to where the
3876              section symbol winds up in the output section.  */
3877           if (sym != NULL && ELF_ST_TYPE (sym->st_info) == STT_SECTION)
3878             rel->r_addend += sec->output_offset;
3879           continue;
3880         }
3881
3882       if (h != NULL)
3883         name = h->root.root.string;
3884       else
3885         {
3886           name = (bfd_elf_string_from_elf_section
3887                   (input_bfd, symtab_hdr->sh_link, sym->st_name));
3888           if (name == NULL || *name == '\0')
3889             name = bfd_section_name (input_bfd, sec);
3890         }
3891
3892       if (r_symndx != 0
3893           && r_type != R_AARCH64_NONE
3894           && r_type != R_AARCH64_NULL
3895           && (h == NULL
3896               || h->root.type == bfd_link_hash_defined
3897               || h->root.type == bfd_link_hash_defweak)
3898           && IS_AARCH64_TLS_RELOC (bfd_r_type) != (sym_type == STT_TLS))
3899         {
3900           (*_bfd_error_handler)
3901             ((sym_type == STT_TLS
3902               ? _("%B(%A+0x%lx): %s used with TLS symbol %s")
3903               : _("%B(%A+0x%lx): %s used with non-TLS symbol %s")),
3904              input_bfd,
3905              input_section, (long) rel->r_offset, howto->name, name);
3906         }
3907
3908       /* We relax only if we can see that there can be a valid transition
3909          from a reloc type to another.
3910          We call elfNN_aarch64_final_link_relocate unless we're completely
3911          done, i.e., the relaxation produced the final output we want.  */
3912
3913       relaxed_bfd_r_type = aarch64_tls_transition (input_bfd, info, r_type,
3914                                                    h, r_symndx);
3915       if (relaxed_bfd_r_type != bfd_r_type)
3916         {
3917           bfd_r_type = relaxed_bfd_r_type;
3918           howto = elfNN_aarch64_howto_from_bfd_reloc (bfd_r_type);
3919           BFD_ASSERT (howto != NULL);
3920           r_type = howto->type;
3921           r = elfNN_aarch64_tls_relax (globals, input_bfd, contents, rel, h);
3922           unresolved_reloc = 0;
3923         }
3924       else
3925         r = bfd_reloc_continue;
3926
3927       /* There may be multiple consecutive relocations for the
3928          same offset.  In that case we are supposed to treat the
3929          output of each relocation as the addend for the next.  */
3930       if (rel + 1 < relend
3931           && rel->r_offset == rel[1].r_offset
3932           && ELFNN_R_TYPE (rel[1].r_info) != R_AARCH64_NONE
3933           && ELFNN_R_TYPE (rel[1].r_info) != R_AARCH64_NULL)
3934         save_addend = TRUE;
3935       else
3936         save_addend = FALSE;
3937
3938       if (r == bfd_reloc_continue)
3939         r = elfNN_aarch64_final_link_relocate (howto, input_bfd, output_bfd,
3940                                                input_section, contents, rel,
3941                                                relocation, info, sec,
3942                                                h, &unresolved_reloc,
3943                                                save_addend, &addend);
3944
3945       switch (elfNN_aarch64_bfd_reloc_from_type (r_type))
3946         {
3947         case BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21:
3948         case BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC:
3949           if (! symbol_got_offset_mark_p (input_bfd, h, r_symndx))
3950             {
3951               bfd_boolean need_relocs = FALSE;
3952               bfd_byte *loc;
3953               int indx;
3954               bfd_vma off;
3955
3956               off = symbol_got_offset (input_bfd, h, r_symndx);
3957               indx = h && h->dynindx != -1 ? h->dynindx : 0;
3958
3959               need_relocs =
3960                 (info->shared || indx != 0) &&
3961                 (h == NULL
3962                  || ELF_ST_VISIBILITY (h->other) == STV_DEFAULT
3963                  || h->root.type != bfd_link_hash_undefweak);
3964
3965               BFD_ASSERT (globals->root.srelgot != NULL);
3966
3967               if (need_relocs)
3968                 {
3969                   Elf_Internal_Rela rela;
3970                   rela.r_info = ELFNN_R_INFO (indx, AARCH64_R (TLS_DTPMOD));
3971                   rela.r_addend = 0;
3972                   rela.r_offset = globals->root.sgot->output_section->vma +
3973                     globals->root.sgot->output_offset + off;
3974
3975
3976                   loc = globals->root.srelgot->contents;
3977                   loc += globals->root.srelgot->reloc_count++
3978                     * RELOC_SIZE (htab);
3979                   bfd_elfNN_swap_reloca_out (output_bfd, &rela, loc);
3980
3981                   if (indx == 0)
3982                     {
3983                       bfd_put_NN (output_bfd,
3984                                   relocation - dtpoff_base (info),
3985                                   globals->root.sgot->contents + off
3986                                   + GOT_ENTRY_SIZE);
3987                     }
3988                   else
3989                     {
3990                       /* This TLS symbol is global. We emit a
3991                          relocation to fixup the tls offset at load
3992                          time.  */
3993                       rela.r_info =
3994                         ELFNN_R_INFO (indx, AARCH64_R (TLS_DTPREL));
3995                       rela.r_addend = 0;
3996                       rela.r_offset =
3997                         (globals->root.sgot->output_section->vma
3998                          + globals->root.sgot->output_offset + off
3999                          + GOT_ENTRY_SIZE);
4000
4001                       loc = globals->root.srelgot->contents;
4002                       loc += globals->root.srelgot->reloc_count++
4003                         * RELOC_SIZE (globals);
4004                       bfd_elfNN_swap_reloca_out (output_bfd, &rela, loc);
4005                       bfd_put_NN (output_bfd, (bfd_vma) 0,
4006                                   globals->root.sgot->contents + off
4007                                   + GOT_ENTRY_SIZE);
4008                     }
4009                 }
4010               else
4011                 {
4012                   bfd_put_NN (output_bfd, (bfd_vma) 1,
4013                               globals->root.sgot->contents + off);
4014                   bfd_put_NN (output_bfd,
4015                               relocation - dtpoff_base (info),
4016                               globals->root.sgot->contents + off
4017                               + GOT_ENTRY_SIZE);
4018                 }
4019
4020               symbol_got_offset_mark (input_bfd, h, r_symndx);
4021             }
4022           break;
4023
4024         case BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4025         case BFD_RELOC_AARCH64_TLSIE_LDNN_GOTTPREL_LO12_NC:
4026           if (! symbol_got_offset_mark_p (input_bfd, h, r_symndx))
4027             {
4028               bfd_boolean need_relocs = FALSE;
4029               bfd_byte *loc;
4030               int indx;
4031               bfd_vma off;
4032
4033               off = symbol_got_offset (input_bfd, h, r_symndx);
4034
4035               indx = h && h->dynindx != -1 ? h->dynindx : 0;
4036
4037               need_relocs =
4038                 (info->shared || indx != 0) &&
4039                 (h == NULL
4040                  || ELF_ST_VISIBILITY (h->other) == STV_DEFAULT
4041                  || h->root.type != bfd_link_hash_undefweak);
4042
4043               BFD_ASSERT (globals->root.srelgot != NULL);
4044
4045               if (need_relocs)
4046                 {
4047                   Elf_Internal_Rela rela;
4048
4049                   if (indx == 0)
4050                     rela.r_addend = relocation - dtpoff_base (info);
4051                   else
4052                     rela.r_addend = 0;
4053
4054                   rela.r_info = ELFNN_R_INFO (indx, AARCH64_R (TLS_TPREL));
4055                   rela.r_offset = globals->root.sgot->output_section->vma +
4056                     globals->root.sgot->output_offset + off;
4057
4058                   loc = globals->root.srelgot->contents;
4059                   loc += globals->root.srelgot->reloc_count++
4060                     * RELOC_SIZE (htab);
4061
4062                   bfd_elfNN_swap_reloca_out (output_bfd, &rela, loc);
4063
4064                   bfd_put_NN (output_bfd, rela.r_addend,
4065                               globals->root.sgot->contents + off);
4066                 }
4067               else
4068                 bfd_put_NN (output_bfd, relocation - tpoff_base (info),
4069                             globals->root.sgot->contents + off);
4070
4071               symbol_got_offset_mark (input_bfd, h, r_symndx);
4072             }
4073           break;
4074
4075         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12:
4076         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_HI12:
4077         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
4078         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G2:
4079         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1:
4080         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
4081         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0:
4082         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
4083           break;
4084
4085         case BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC:
4086         case BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21:
4087         case BFD_RELOC_AARCH64_TLSDESC_LDNN_LO12_NC:
4088           if (! symbol_tlsdesc_got_offset_mark_p (input_bfd, h, r_symndx))
4089             {
4090               bfd_boolean need_relocs = FALSE;
4091               int indx = h && h->dynindx != -1 ? h->dynindx : 0;
4092               bfd_vma off = symbol_tlsdesc_got_offset (input_bfd, h, r_symndx);
4093
4094               need_relocs = (h == NULL
4095                              || ELF_ST_VISIBILITY (h->other) == STV_DEFAULT
4096                              || h->root.type != bfd_link_hash_undefweak);
4097
4098               BFD_ASSERT (globals->root.srelgot != NULL);
4099               BFD_ASSERT (globals->root.sgot != NULL);
4100
4101               if (need_relocs)
4102                 {
4103                   bfd_byte *loc;
4104                   Elf_Internal_Rela rela;
4105                   rela.r_info = ELFNN_R_INFO (indx, AARCH64_R (TLSDESC));
4106
4107                   rela.r_addend = 0;
4108                   rela.r_offset = (globals->root.sgotplt->output_section->vma
4109                                    + globals->root.sgotplt->output_offset
4110                                    + off + globals->sgotplt_jump_table_size);
4111
4112                   if (indx == 0)
4113                     rela.r_addend = relocation - dtpoff_base (info);
4114
4115                   /* Allocate the next available slot in the PLT reloc
4116                      section to hold our R_AARCH64_TLSDESC, the next
4117                      available slot is determined from reloc_count,
4118                      which we step. But note, reloc_count was
4119                      artifically moved down while allocating slots for
4120                      real PLT relocs such that all of the PLT relocs
4121                      will fit above the initial reloc_count and the
4122                      extra stuff will fit below.  */
4123                   loc = globals->root.srelplt->contents;
4124                   loc += globals->root.srelplt->reloc_count++
4125                     * RELOC_SIZE (globals);
4126
4127                   bfd_elfNN_swap_reloca_out (output_bfd, &rela, loc);
4128
4129                   bfd_put_NN (output_bfd, (bfd_vma) 0,
4130                               globals->root.sgotplt->contents + off +
4131                               globals->sgotplt_jump_table_size);
4132                   bfd_put_NN (output_bfd, (bfd_vma) 0,
4133                               globals->root.sgotplt->contents + off +
4134                               globals->sgotplt_jump_table_size +
4135                               GOT_ENTRY_SIZE);
4136                 }
4137
4138               symbol_tlsdesc_got_offset_mark (input_bfd, h, r_symndx);
4139             }
4140           break;
4141         default:
4142           break;
4143         }
4144
4145       if (!save_addend)
4146         addend = 0;
4147
4148
4149       /* Dynamic relocs are not propagated for SEC_DEBUGGING sections
4150          because such sections are not SEC_ALLOC and thus ld.so will
4151          not process them.  */
4152       if (unresolved_reloc
4153           && !((input_section->flags & SEC_DEBUGGING) != 0
4154                && h->def_dynamic)
4155           && _bfd_elf_section_offset (output_bfd, info, input_section,
4156                                       +rel->r_offset) != (bfd_vma) - 1)
4157         {
4158           (*_bfd_error_handler)
4159             (_
4160              ("%B(%A+0x%lx): unresolvable %s relocation against symbol `%s'"),
4161              input_bfd, input_section, (long) rel->r_offset, howto->name,
4162              h->root.root.string);
4163           return FALSE;
4164         }
4165
4166       if (r != bfd_reloc_ok && r != bfd_reloc_continue)
4167         {
4168           switch (r)
4169             {
4170             case bfd_reloc_overflow:
4171               /* If the overflowing reloc was to an undefined symbol,
4172                  we have already printed one error message and there
4173                  is no point complaining again.  */
4174               if ((!h ||
4175                    h->root.type != bfd_link_hash_undefined)
4176                   && (!((*info->callbacks->reloc_overflow)
4177                         (info, (h ? &h->root : NULL), name, howto->name,
4178                          (bfd_vma) 0, input_bfd, input_section,
4179                          rel->r_offset))))
4180                 return FALSE;
4181               break;
4182
4183             case bfd_reloc_undefined:
4184               if (!((*info->callbacks->undefined_symbol)
4185                     (info, name, input_bfd, input_section,
4186                      rel->r_offset, TRUE)))
4187                 return FALSE;
4188               break;
4189
4190             case bfd_reloc_outofrange:
4191               error_message = _("out of range");
4192               goto common_error;
4193
4194             case bfd_reloc_notsupported:
4195               error_message = _("unsupported relocation");
4196               goto common_error;
4197
4198             case bfd_reloc_dangerous:
4199               /* error_message should already be set.  */
4200               goto common_error;
4201
4202             default:
4203               error_message = _("unknown error");
4204               /* Fall through.  */
4205
4206             common_error:
4207               BFD_ASSERT (error_message != NULL);
4208               if (!((*info->callbacks->reloc_dangerous)
4209                     (info, error_message, input_bfd, input_section,
4210                      rel->r_offset)))
4211                 return FALSE;
4212               break;
4213             }
4214         }
4215     }
4216
4217   return TRUE;
4218 }
4219
4220 /* Set the right machine number.  */
4221
4222 static bfd_boolean
4223 elfNN_aarch64_object_p (bfd *abfd)
4224 {
4225 #if ARCH_SIZE == 32
4226   bfd_default_set_arch_mach (abfd, bfd_arch_aarch64, bfd_mach_aarch64_ilp32);
4227 #else
4228   bfd_default_set_arch_mach (abfd, bfd_arch_aarch64, bfd_mach_aarch64);
4229 #endif
4230   return TRUE;
4231 }
4232
4233 /* Function to keep AArch64 specific flags in the ELF header.  */
4234
4235 static bfd_boolean
4236 elfNN_aarch64_set_private_flags (bfd *abfd, flagword flags)
4237 {
4238   if (elf_flags_init (abfd) && elf_elfheader (abfd)->e_flags != flags)
4239     {
4240     }
4241   else
4242     {
4243       elf_elfheader (abfd)->e_flags = flags;
4244       elf_flags_init (abfd) = TRUE;
4245     }
4246
4247   return TRUE;
4248 }
4249
4250 /* Copy backend specific data from one object module to another.  */
4251
4252 static bfd_boolean
4253 elfNN_aarch64_copy_private_bfd_data (bfd *ibfd, bfd *obfd)
4254 {
4255   flagword in_flags;
4256
4257   if (!is_aarch64_elf (ibfd) || !is_aarch64_elf (obfd))
4258     return TRUE;
4259
4260   in_flags = elf_elfheader (ibfd)->e_flags;
4261
4262   elf_elfheader (obfd)->e_flags = in_flags;
4263   elf_flags_init (obfd) = TRUE;
4264
4265   /* Also copy the EI_OSABI field.  */
4266   elf_elfheader (obfd)->e_ident[EI_OSABI] =
4267     elf_elfheader (ibfd)->e_ident[EI_OSABI];
4268
4269   /* Copy object attributes.  */
4270   _bfd_elf_copy_obj_attributes (ibfd, obfd);
4271
4272   return TRUE;
4273 }
4274
4275 /* Merge backend specific data from an object file to the output
4276    object file when linking.  */
4277
4278 static bfd_boolean
4279 elfNN_aarch64_merge_private_bfd_data (bfd *ibfd, bfd *obfd)
4280 {
4281   flagword out_flags;
4282   flagword in_flags;
4283   bfd_boolean flags_compatible = TRUE;
4284   asection *sec;
4285
4286   /* Check if we have the same endianess.  */
4287   if (!_bfd_generic_verify_endian_match (ibfd, obfd))
4288     return FALSE;
4289
4290   if (!is_aarch64_elf (ibfd) || !is_aarch64_elf (obfd))
4291     return TRUE;
4292
4293   /* The input BFD must have had its flags initialised.  */
4294   /* The following seems bogus to me -- The flags are initialized in
4295      the assembler but I don't think an elf_flags_init field is
4296      written into the object.  */
4297   /* BFD_ASSERT (elf_flags_init (ibfd)); */
4298
4299   in_flags = elf_elfheader (ibfd)->e_flags;
4300   out_flags = elf_elfheader (obfd)->e_flags;
4301
4302   if (!elf_flags_init (obfd))
4303     {
4304       /* If the input is the default architecture and had the default
4305          flags then do not bother setting the flags for the output
4306          architecture, instead allow future merges to do this.  If no
4307          future merges ever set these flags then they will retain their
4308          uninitialised values, which surprise surprise, correspond
4309          to the default values.  */
4310       if (bfd_get_arch_info (ibfd)->the_default
4311           && elf_elfheader (ibfd)->e_flags == 0)
4312         return TRUE;
4313
4314       elf_flags_init (obfd) = TRUE;
4315       elf_elfheader (obfd)->e_flags = in_flags;
4316
4317       if (bfd_get_arch (obfd) == bfd_get_arch (ibfd)
4318           && bfd_get_arch_info (obfd)->the_default)
4319         return bfd_set_arch_mach (obfd, bfd_get_arch (ibfd),
4320                                   bfd_get_mach (ibfd));
4321
4322       return TRUE;
4323     }
4324
4325   /* Identical flags must be compatible.  */
4326   if (in_flags == out_flags)
4327     return TRUE;
4328
4329   /* Check to see if the input BFD actually contains any sections.  If
4330      not, its flags may not have been initialised either, but it
4331      cannot actually cause any incompatiblity.  Do not short-circuit
4332      dynamic objects; their section list may be emptied by
4333      elf_link_add_object_symbols.
4334
4335      Also check to see if there are no code sections in the input.
4336      In this case there is no need to check for code specific flags.
4337      XXX - do we need to worry about floating-point format compatability
4338      in data sections ?  */
4339   if (!(ibfd->flags & DYNAMIC))
4340     {
4341       bfd_boolean null_input_bfd = TRUE;
4342       bfd_boolean only_data_sections = TRUE;
4343
4344       for (sec = ibfd->sections; sec != NULL; sec = sec->next)
4345         {
4346           if ((bfd_get_section_flags (ibfd, sec)
4347                & (SEC_LOAD | SEC_CODE | SEC_HAS_CONTENTS))
4348               == (SEC_LOAD | SEC_CODE | SEC_HAS_CONTENTS))
4349             only_data_sections = FALSE;
4350
4351           null_input_bfd = FALSE;
4352           break;
4353         }
4354
4355       if (null_input_bfd || only_data_sections)
4356         return TRUE;
4357     }
4358
4359   return flags_compatible;
4360 }
4361
4362 /* Display the flags field.  */
4363
4364 static bfd_boolean
4365 elfNN_aarch64_print_private_bfd_data (bfd *abfd, void *ptr)
4366 {
4367   FILE *file = (FILE *) ptr;
4368   unsigned long flags;
4369
4370   BFD_ASSERT (abfd != NULL && ptr != NULL);
4371
4372   /* Print normal ELF private data.  */
4373   _bfd_elf_print_private_bfd_data (abfd, ptr);
4374
4375   flags = elf_elfheader (abfd)->e_flags;
4376   /* Ignore init flag - it may not be set, despite the flags field
4377      containing valid data.  */
4378
4379   /* xgettext:c-format */
4380   fprintf (file, _("private flags = %lx:"), elf_elfheader (abfd)->e_flags);
4381
4382   if (flags)
4383     fprintf (file, _("<Unrecognised flag bits set>"));
4384
4385   fputc ('\n', file);
4386
4387   return TRUE;
4388 }
4389
4390 /* Update the got entry reference counts for the section being removed.  */
4391
4392 static bfd_boolean
4393 elfNN_aarch64_gc_sweep_hook (bfd *abfd,
4394                              struct bfd_link_info *info,
4395                              asection *sec,
4396                              const Elf_Internal_Rela * relocs)
4397 {
4398   struct elf_aarch64_link_hash_table *htab;
4399   Elf_Internal_Shdr *symtab_hdr;
4400   struct elf_link_hash_entry **sym_hashes;
4401   struct elf_aarch64_local_symbol *locals;
4402   const Elf_Internal_Rela *rel, *relend;
4403
4404   if (info->relocatable)
4405     return TRUE;
4406
4407   htab = elf_aarch64_hash_table (info);
4408
4409   if (htab == NULL)
4410     return FALSE;
4411
4412   elf_section_data (sec)->local_dynrel = NULL;
4413
4414   symtab_hdr = &elf_symtab_hdr (abfd);
4415   sym_hashes = elf_sym_hashes (abfd);
4416
4417   locals = elf_aarch64_locals (abfd);
4418
4419   relend = relocs + sec->reloc_count;
4420   for (rel = relocs; rel < relend; rel++)
4421     {
4422       unsigned long r_symndx;
4423       unsigned int r_type;
4424       struct elf_link_hash_entry *h = NULL;
4425
4426       r_symndx = ELFNN_R_SYM (rel->r_info);
4427
4428       if (r_symndx >= symtab_hdr->sh_info)
4429         {
4430           struct elf_aarch64_link_hash_entry *eh;
4431           struct elf_dyn_relocs **pp;
4432           struct elf_dyn_relocs *p;
4433
4434           h = sym_hashes[r_symndx - symtab_hdr->sh_info];
4435           while (h->root.type == bfd_link_hash_indirect
4436                  || h->root.type == bfd_link_hash_warning)
4437             h = (struct elf_link_hash_entry *) h->root.u.i.link;
4438           eh = (struct elf_aarch64_link_hash_entry *) h;
4439
4440           for (pp = &eh->dyn_relocs; (p = *pp) != NULL; pp = &p->next)
4441             {
4442               if (p->sec == sec)
4443                 {
4444                   /* Everything must go for SEC.  */
4445                   *pp = p->next;
4446                   break;
4447                 }
4448             }
4449         }
4450       else
4451         {
4452           Elf_Internal_Sym *isym;
4453
4454           /* A local symbol.  */
4455           isym = bfd_sym_from_r_symndx (&htab->sym_cache,
4456                                         abfd, r_symndx);
4457           if (isym == NULL)
4458             return FALSE;
4459         }
4460
4461       r_type = ELFNN_R_TYPE (rel->r_info);
4462       switch (aarch64_tls_transition (abfd,info, r_type, h ,r_symndx))
4463         {
4464         case BFD_RELOC_AARCH64_ADR_GOT_PAGE:
4465         case BFD_RELOC_AARCH64_GOT_LD_PREL19:
4466         case BFD_RELOC_AARCH64_LD32_GOT_LO12_NC:
4467         case BFD_RELOC_AARCH64_LD64_GOT_LO12_NC:
4468         case BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC:
4469         case BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21:
4470         case BFD_RELOC_AARCH64_TLSDESC_LD32_LO12_NC:
4471         case BFD_RELOC_AARCH64_TLSDESC_LD64_LO12_NC:
4472         case BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC:
4473         case BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21:
4474         case BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4475         case BFD_RELOC_AARCH64_TLSIE_LD32_GOTTPREL_LO12_NC:
4476         case BFD_RELOC_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
4477         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_HI12:
4478         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12:
4479         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
4480         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0:
4481         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
4482         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1:
4483         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
4484         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G2:
4485           if (h != NULL)
4486             {
4487               if (h->got.refcount > 0)
4488                 h->got.refcount -= 1;
4489             }
4490           else if (locals != NULL)
4491             {
4492               if (locals[r_symndx].got_refcount > 0)
4493                 locals[r_symndx].got_refcount -= 1;
4494             }
4495           break;
4496
4497         case BFD_RELOC_AARCH64_ADR_HI21_NC_PCREL:
4498         case BFD_RELOC_AARCH64_ADR_HI21_PCREL:
4499         case BFD_RELOC_AARCH64_ADR_LO21_PCREL:
4500           if (h != NULL && info->executable)
4501             {
4502               if (h->plt.refcount > 0)
4503                 h->plt.refcount -= 1;
4504             }
4505           break;
4506
4507         case BFD_RELOC_AARCH64_CALL26:
4508         case BFD_RELOC_AARCH64_JUMP26:
4509           /* If this is a local symbol then we resolve it
4510              directly without creating a PLT entry.  */
4511           if (h == NULL)
4512             continue;
4513
4514           if (h->plt.refcount > 0)
4515             h->plt.refcount -= 1;
4516           break;
4517
4518         case BFD_RELOC_AARCH64_NN:
4519           if (h != NULL && info->executable)
4520             {
4521               if (h->plt.refcount > 0)
4522                 h->plt.refcount -= 1;
4523             }
4524           break;
4525
4526         default:
4527           break;
4528         }
4529     }
4530
4531   return TRUE;
4532 }
4533
4534 /* Adjust a symbol defined by a dynamic object and referenced by a
4535    regular object.  The current definition is in some section of the
4536    dynamic object, but we're not including those sections.  We have to
4537    change the definition to something the rest of the link can
4538    understand.  */
4539
4540 static bfd_boolean
4541 elfNN_aarch64_adjust_dynamic_symbol (struct bfd_link_info *info,
4542                                      struct elf_link_hash_entry *h)
4543 {
4544   struct elf_aarch64_link_hash_table *htab;
4545   asection *s;
4546
4547   /* If this is a function, put it in the procedure linkage table.  We
4548      will fill in the contents of the procedure linkage table later,
4549      when we know the address of the .got section.  */
4550   if (h->type == STT_FUNC || h->needs_plt)
4551     {
4552       if (h->plt.refcount <= 0
4553           || SYMBOL_CALLS_LOCAL (info, h)
4554           || (ELF_ST_VISIBILITY (h->other) != STV_DEFAULT
4555               && h->root.type == bfd_link_hash_undefweak))
4556         {
4557           /* This case can occur if we saw a CALL26 reloc in
4558              an input file, but the symbol wasn't referred to
4559              by a dynamic object or all references were
4560              garbage collected. In which case we can end up
4561              resolving.  */
4562           h->plt.offset = (bfd_vma) - 1;
4563           h->needs_plt = 0;
4564         }
4565
4566       return TRUE;
4567     }
4568   else
4569     /* It's possible that we incorrectly decided a .plt reloc was
4570        needed for an R_X86_64_PC32 reloc to a non-function sym in
4571        check_relocs.  We can't decide accurately between function and
4572        non-function syms in check-relocs;  Objects loaded later in
4573        the link may change h->type.  So fix it now.  */
4574     h->plt.offset = (bfd_vma) - 1;
4575
4576
4577   /* If this is a weak symbol, and there is a real definition, the
4578      processor independent code will have arranged for us to see the
4579      real definition first, and we can just use the same value.  */
4580   if (h->u.weakdef != NULL)
4581     {
4582       BFD_ASSERT (h->u.weakdef->root.type == bfd_link_hash_defined
4583                   || h->u.weakdef->root.type == bfd_link_hash_defweak);
4584       h->root.u.def.section = h->u.weakdef->root.u.def.section;
4585       h->root.u.def.value = h->u.weakdef->root.u.def.value;
4586       if (ELIMINATE_COPY_RELOCS || info->nocopyreloc)
4587         h->non_got_ref = h->u.weakdef->non_got_ref;
4588       return TRUE;
4589     }
4590
4591   /* If we are creating a shared library, we must presume that the
4592      only references to the symbol are via the global offset table.
4593      For such cases we need not do anything here; the relocations will
4594      be handled correctly by relocate_section.  */
4595   if (info->shared)
4596     return TRUE;
4597
4598   /* If there are no references to this symbol that do not use the
4599      GOT, we don't need to generate a copy reloc.  */
4600   if (!h->non_got_ref)
4601     return TRUE;
4602
4603   /* If -z nocopyreloc was given, we won't generate them either.  */
4604   if (info->nocopyreloc)
4605     {
4606       h->non_got_ref = 0;
4607       return TRUE;
4608     }
4609
4610   /* We must allocate the symbol in our .dynbss section, which will
4611      become part of the .bss section of the executable.  There will be
4612      an entry for this symbol in the .dynsym section.  The dynamic
4613      object will contain position independent code, so all references
4614      from the dynamic object to this symbol will go through the global
4615      offset table.  The dynamic linker will use the .dynsym entry to
4616      determine the address it must put in the global offset table, so
4617      both the dynamic object and the regular object will refer to the
4618      same memory location for the variable.  */
4619
4620   htab = elf_aarch64_hash_table (info);
4621
4622   /* We must generate a R_AARCH64_COPY reloc to tell the dynamic linker
4623      to copy the initial value out of the dynamic object and into the
4624      runtime process image.  */
4625   if ((h->root.u.def.section->flags & SEC_ALLOC) != 0 && h->size != 0)
4626     {
4627       htab->srelbss->size += RELOC_SIZE (htab);
4628       h->needs_copy = 1;
4629     }
4630
4631   s = htab->sdynbss;
4632
4633   return _bfd_elf_adjust_dynamic_copy (h, s);
4634
4635 }
4636
4637 static bfd_boolean
4638 elfNN_aarch64_allocate_local_symbols (bfd *abfd, unsigned number)
4639 {
4640   struct elf_aarch64_local_symbol *locals;
4641   locals = elf_aarch64_locals (abfd);
4642   if (locals == NULL)
4643     {
4644       locals = (struct elf_aarch64_local_symbol *)
4645         bfd_zalloc (abfd, number * sizeof (struct elf_aarch64_local_symbol));
4646       if (locals == NULL)
4647         return FALSE;
4648       elf_aarch64_locals (abfd) = locals;
4649     }
4650   return TRUE;
4651 }
4652
4653 /* Create the .got section to hold the global offset table.  */
4654
4655 static bfd_boolean
4656 aarch64_elf_create_got_section (bfd *abfd, struct bfd_link_info *info)
4657 {
4658   const struct elf_backend_data *bed = get_elf_backend_data (abfd);
4659   flagword flags;
4660   asection *s;
4661   struct elf_link_hash_entry *h;
4662   struct elf_link_hash_table *htab = elf_hash_table (info);
4663
4664   /* This function may be called more than once.  */
4665   s = bfd_get_linker_section (abfd, ".got");
4666   if (s != NULL)
4667     return TRUE;
4668
4669   flags = bed->dynamic_sec_flags;
4670
4671   s = bfd_make_section_anyway_with_flags (abfd,
4672                                           (bed->rela_plts_and_copies_p
4673                                            ? ".rela.got" : ".rel.got"),
4674                                           (bed->dynamic_sec_flags
4675                                            | SEC_READONLY));
4676   if (s == NULL
4677       || ! bfd_set_section_alignment (abfd, s, bed->s->log_file_align))
4678     return FALSE;
4679   htab->srelgot = s;
4680
4681   s = bfd_make_section_anyway_with_flags (abfd, ".got", flags);
4682   if (s == NULL
4683       || !bfd_set_section_alignment (abfd, s, bed->s->log_file_align))
4684     return FALSE;
4685   htab->sgot = s;
4686   htab->sgot->size += GOT_ENTRY_SIZE;
4687
4688   if (bed->want_got_sym)
4689     {
4690       /* Define the symbol _GLOBAL_OFFSET_TABLE_ at the start of the .got
4691          (or .got.plt) section.  We don't do this in the linker script
4692          because we don't want to define the symbol if we are not creating
4693          a global offset table.  */
4694       h = _bfd_elf_define_linkage_sym (abfd, info, s,
4695                                        "_GLOBAL_OFFSET_TABLE_");
4696       elf_hash_table (info)->hgot = h;
4697       if (h == NULL)
4698         return FALSE;
4699     }
4700
4701   if (bed->want_got_plt)
4702     {
4703       s = bfd_make_section_anyway_with_flags (abfd, ".got.plt", flags);
4704       if (s == NULL
4705           || !bfd_set_section_alignment (abfd, s,
4706                                          bed->s->log_file_align))
4707         return FALSE;
4708       htab->sgotplt = s;
4709     }
4710
4711   /* The first bit of the global offset table is the header.  */
4712   s->size += bed->got_header_size;
4713
4714   return TRUE;
4715 }
4716
4717 /* Look through the relocs for a section during the first phase.  */
4718
4719 static bfd_boolean
4720 elfNN_aarch64_check_relocs (bfd *abfd, struct bfd_link_info *info,
4721                             asection *sec, const Elf_Internal_Rela *relocs)
4722 {
4723   Elf_Internal_Shdr *symtab_hdr;
4724   struct elf_link_hash_entry **sym_hashes;
4725   const Elf_Internal_Rela *rel;
4726   const Elf_Internal_Rela *rel_end;
4727   asection *sreloc;
4728
4729   struct elf_aarch64_link_hash_table *htab;
4730
4731   if (info->relocatable)
4732     return TRUE;
4733
4734   BFD_ASSERT (is_aarch64_elf (abfd));
4735
4736   htab = elf_aarch64_hash_table (info);
4737   sreloc = NULL;
4738
4739   symtab_hdr = &elf_symtab_hdr (abfd);
4740   sym_hashes = elf_sym_hashes (abfd);
4741
4742   rel_end = relocs + sec->reloc_count;
4743   for (rel = relocs; rel < rel_end; rel++)
4744     {
4745       struct elf_link_hash_entry *h;
4746       unsigned long r_symndx;
4747       unsigned int r_type;
4748       bfd_reloc_code_real_type bfd_r_type;
4749
4750       r_symndx = ELFNN_R_SYM (rel->r_info);
4751       r_type = ELFNN_R_TYPE (rel->r_info);
4752
4753       if (r_symndx >= NUM_SHDR_ENTRIES (symtab_hdr))
4754         {
4755           (*_bfd_error_handler) (_("%B: bad symbol index: %d"), abfd,
4756                                  r_symndx);
4757           return FALSE;
4758         }
4759
4760       if (r_symndx < symtab_hdr->sh_info)
4761         h = NULL;
4762       else
4763         {
4764           h = sym_hashes[r_symndx - symtab_hdr->sh_info];
4765           while (h->root.type == bfd_link_hash_indirect
4766                  || h->root.type == bfd_link_hash_warning)
4767             h = (struct elf_link_hash_entry *) h->root.u.i.link;
4768
4769           /* PR15323, ref flags aren't set for references in the same
4770              object.  */
4771           h->root.non_ir_ref = 1;
4772         }
4773
4774       /* Could be done earlier, if h were already available.  */
4775       bfd_r_type = aarch64_tls_transition (abfd, info, r_type, h, r_symndx);
4776
4777       switch (bfd_r_type)
4778         {
4779         case BFD_RELOC_AARCH64_NN:
4780
4781           /* We don't need to handle relocs into sections not going into
4782              the "real" output.  */
4783           if ((sec->flags & SEC_ALLOC) == 0)
4784             break;
4785
4786           if (h != NULL)
4787             {
4788               if (!info->shared)
4789                 h->non_got_ref = 1;
4790
4791               h->plt.refcount += 1;
4792               h->pointer_equality_needed = 1;
4793             }
4794
4795           /* No need to do anything if we're not creating a shared
4796              object.  */
4797           if (! info->shared)
4798             break;
4799
4800           {
4801             struct elf_dyn_relocs *p;
4802             struct elf_dyn_relocs **head;
4803
4804             /* We must copy these reloc types into the output file.
4805                Create a reloc section in dynobj and make room for
4806                this reloc.  */
4807             if (sreloc == NULL)
4808               {
4809                 if (htab->root.dynobj == NULL)
4810                   htab->root.dynobj = abfd;
4811
4812                 sreloc = _bfd_elf_make_dynamic_reloc_section
4813                   (sec, htab->root.dynobj, LOG_FILE_ALIGN, abfd, /*rela? */ TRUE);
4814
4815                 if (sreloc == NULL)
4816                   return FALSE;
4817               }
4818
4819             /* If this is a global symbol, we count the number of
4820                relocations we need for this symbol.  */
4821             if (h != NULL)
4822               {
4823                 struct elf_aarch64_link_hash_entry *eh;
4824                 eh = (struct elf_aarch64_link_hash_entry *) h;
4825                 head = &eh->dyn_relocs;
4826               }
4827             else
4828               {
4829                 /* Track dynamic relocs needed for local syms too.
4830                    We really need local syms available to do this
4831                    easily.  Oh well.  */
4832
4833                 asection *s;
4834                 void **vpp;
4835                 Elf_Internal_Sym *isym;
4836
4837                 isym = bfd_sym_from_r_symndx (&htab->sym_cache,
4838                                               abfd, r_symndx);
4839                 if (isym == NULL)
4840                   return FALSE;
4841
4842                 s = bfd_section_from_elf_index (abfd, isym->st_shndx);
4843                 if (s == NULL)
4844                   s = sec;
4845
4846                 /* Beware of type punned pointers vs strict aliasing
4847                    rules.  */
4848                 vpp = &(elf_section_data (s)->local_dynrel);
4849                 head = (struct elf_dyn_relocs **) vpp;
4850               }
4851
4852             p = *head;
4853             if (p == NULL || p->sec != sec)
4854               {
4855                 bfd_size_type amt = sizeof *p;
4856                 p = ((struct elf_dyn_relocs *)
4857                      bfd_zalloc (htab->root.dynobj, amt));
4858                 if (p == NULL)
4859                   return FALSE;
4860                 p->next = *head;
4861                 *head = p;
4862                 p->sec = sec;
4863               }
4864
4865             p->count += 1;
4866
4867           }
4868           break;
4869
4870           /* RR: We probably want to keep a consistency check that
4871              there are no dangling GOT_PAGE relocs.  */
4872         case BFD_RELOC_AARCH64_ADR_GOT_PAGE:
4873         case BFD_RELOC_AARCH64_GOT_LD_PREL19:
4874         case BFD_RELOC_AARCH64_LD32_GOT_LO12_NC:
4875         case BFD_RELOC_AARCH64_LD64_GOT_LO12_NC:
4876         case BFD_RELOC_AARCH64_TLSDESC_ADD_LO12_NC:
4877         case BFD_RELOC_AARCH64_TLSDESC_ADR_PAGE21:
4878         case BFD_RELOC_AARCH64_TLSDESC_LD32_LO12_NC:
4879         case BFD_RELOC_AARCH64_TLSDESC_LD64_LO12_NC:
4880         case BFD_RELOC_AARCH64_TLSGD_ADD_LO12_NC:
4881         case BFD_RELOC_AARCH64_TLSGD_ADR_PAGE21:
4882         case BFD_RELOC_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4883         case BFD_RELOC_AARCH64_TLSIE_LD32_GOTTPREL_LO12_NC:
4884         case BFD_RELOC_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
4885         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_HI12:
4886         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12:
4887         case BFD_RELOC_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
4888         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0:
4889         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
4890         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1:
4891         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
4892         case BFD_RELOC_AARCH64_TLSLE_MOVW_TPREL_G2:
4893           {
4894             unsigned got_type;
4895             unsigned old_got_type;
4896
4897             got_type = aarch64_reloc_got_type (bfd_r_type);
4898
4899             if (h)
4900               {
4901                 h->got.refcount += 1;
4902                 old_got_type = elf_aarch64_hash_entry (h)->got_type;
4903               }
4904             else
4905               {
4906                 struct elf_aarch64_local_symbol *locals;
4907
4908                 if (!elfNN_aarch64_allocate_local_symbols
4909                     (abfd, symtab_hdr->sh_info))
4910                   return FALSE;
4911
4912                 locals = elf_aarch64_locals (abfd);
4913                 BFD_ASSERT (r_symndx < symtab_hdr->sh_info);
4914                 locals[r_symndx].got_refcount += 1;
4915                 old_got_type = locals[r_symndx].got_type;
4916               }
4917
4918             /* If a variable is accessed with both general dynamic TLS
4919                methods, two slots may be created.  */
4920             if (GOT_TLS_GD_ANY_P (old_got_type) && GOT_TLS_GD_ANY_P (got_type))
4921               got_type |= old_got_type;
4922
4923             /* We will already have issued an error message if there
4924                is a TLS/non-TLS mismatch, based on the symbol type.
4925                So just combine any TLS types needed.  */
4926             if (old_got_type != GOT_UNKNOWN && old_got_type != GOT_NORMAL
4927                 && got_type != GOT_NORMAL)
4928               got_type |= old_got_type;
4929
4930             /* If the symbol is accessed by both IE and GD methods, we
4931                are able to relax.  Turn off the GD flag, without
4932                messing up with any other kind of TLS types that may be
4933                involved.  */
4934             if ((got_type & GOT_TLS_IE) && GOT_TLS_GD_ANY_P (got_type))
4935               got_type &= ~ (GOT_TLSDESC_GD | GOT_TLS_GD);
4936
4937             if (old_got_type != got_type)
4938               {
4939                 if (h != NULL)
4940                   elf_aarch64_hash_entry (h)->got_type = got_type;
4941                 else
4942                   {
4943                     struct elf_aarch64_local_symbol *locals;
4944                     locals = elf_aarch64_locals (abfd);
4945                     BFD_ASSERT (r_symndx < symtab_hdr->sh_info);
4946                     locals[r_symndx].got_type = got_type;
4947                   }
4948               }
4949
4950             if (htab->root.dynobj == NULL)
4951               htab->root.dynobj = abfd;
4952             if (! aarch64_elf_create_got_section (htab->root.dynobj, info))
4953               return FALSE;
4954             break;
4955           }
4956
4957         case BFD_RELOC_AARCH64_ADR_HI21_NC_PCREL:
4958         case BFD_RELOC_AARCH64_ADR_HI21_PCREL:
4959         case BFD_RELOC_AARCH64_ADR_LO21_PCREL:
4960           if (h != NULL && info->executable)
4961             {
4962               /* If this reloc is in a read-only section, we might
4963                  need a copy reloc.  We can't check reliably at this
4964                  stage whether the section is read-only, as input
4965                  sections have not yet been mapped to output sections.
4966                  Tentatively set the flag for now, and correct in
4967                  adjust_dynamic_symbol.  */
4968               h->non_got_ref = 1;
4969               h->plt.refcount += 1;
4970               h->pointer_equality_needed = 1;
4971             }
4972           /* FIXME:: RR need to handle these in shared libraries
4973              and essentially bomb out as these being non-PIC
4974              relocations in shared libraries.  */
4975           break;
4976
4977         case BFD_RELOC_AARCH64_CALL26:
4978         case BFD_RELOC_AARCH64_JUMP26:
4979           /* If this is a local symbol then we resolve it
4980              directly without creating a PLT entry.  */
4981           if (h == NULL)
4982             continue;
4983
4984           h->needs_plt = 1;
4985           h->plt.refcount += 1;
4986           break;
4987
4988         default:
4989           break;
4990         }
4991     }
4992
4993   return TRUE;
4994 }
4995
4996 /* Treat mapping symbols as special target symbols.  */
4997
4998 static bfd_boolean
4999 elfNN_aarch64_is_target_special_symbol (bfd *abfd ATTRIBUTE_UNUSED,
5000                                         asymbol *sym)
5001 {
5002   return bfd_is_aarch64_special_symbol_name (sym->name,
5003                                              BFD_AARCH64_SPECIAL_SYM_TYPE_ANY);
5004 }
5005
5006 /* This is a copy of elf_find_function () from elf.c except that
5007    AArch64 mapping symbols are ignored when looking for function names.  */
5008
5009 static bfd_boolean
5010 aarch64_elf_find_function (bfd *abfd ATTRIBUTE_UNUSED,
5011                            asection *section,
5012                            asymbol **symbols,
5013                            bfd_vma offset,
5014                            const char **filename_ptr,
5015                            const char **functionname_ptr)
5016 {
5017   const char *filename = NULL;
5018   asymbol *func = NULL;
5019   bfd_vma low_func = 0;
5020   asymbol **p;
5021
5022   for (p = symbols; *p != NULL; p++)
5023     {
5024       elf_symbol_type *q;
5025
5026       q = (elf_symbol_type *) * p;
5027
5028       switch (ELF_ST_TYPE (q->internal_elf_sym.st_info))
5029         {
5030         default:
5031           break;
5032         case STT_FILE:
5033           filename = bfd_asymbol_name (&q->symbol);
5034           break;
5035         case STT_FUNC:
5036         case STT_NOTYPE:
5037           /* Skip mapping symbols.  */
5038           if ((q->symbol.flags & BSF_LOCAL)
5039               && (bfd_is_aarch64_special_symbol_name
5040                   (q->symbol.name, BFD_AARCH64_SPECIAL_SYM_TYPE_ANY)))
5041             continue;
5042           /* Fall through.  */
5043           if (bfd_get_section (&q->symbol) == section
5044               && q->symbol.value >= low_func && q->symbol.value <= offset)
5045             {
5046               func = (asymbol *) q;
5047               low_func = q->symbol.value;
5048             }
5049           break;
5050         }
5051     }
5052
5053   if (func == NULL)
5054     return FALSE;
5055
5056   if (filename_ptr)
5057     *filename_ptr = filename;
5058   if (functionname_ptr)
5059     *functionname_ptr = bfd_asymbol_name (func);
5060
5061   return TRUE;
5062 }
5063
5064
5065 /* Find the nearest line to a particular section and offset, for error
5066    reporting.   This code is a duplicate of the code in elf.c, except
5067    that it uses aarch64_elf_find_function.  */
5068
5069 static bfd_boolean
5070 elfNN_aarch64_find_nearest_line (bfd *abfd,
5071                                  asection *section,
5072                                  asymbol **symbols,
5073                                  bfd_vma offset,
5074                                  const char **filename_ptr,
5075                                  const char **functionname_ptr,
5076                                  unsigned int *line_ptr)
5077 {
5078   bfd_boolean found = FALSE;
5079
5080   /* We skip _bfd_dwarf1_find_nearest_line since no known AArch64
5081      toolchain uses it.  */
5082
5083   if (_bfd_dwarf2_find_nearest_line (abfd, dwarf_debug_sections,
5084                                      section, symbols, offset,
5085                                      filename_ptr, functionname_ptr,
5086                                      line_ptr, NULL, 0,
5087                                      &elf_tdata (abfd)->dwarf2_find_line_info))
5088     {
5089       if (!*functionname_ptr)
5090         aarch64_elf_find_function (abfd, section, symbols, offset,
5091                                    *filename_ptr ? NULL : filename_ptr,
5092                                    functionname_ptr);
5093
5094       return TRUE;
5095     }
5096
5097   if (!_bfd_stab_section_find_nearest_line (abfd, symbols, section, offset,
5098                                             &found, filename_ptr,
5099                                             functionname_ptr, line_ptr,
5100                                             &elf_tdata (abfd)->line_info))
5101     return FALSE;
5102
5103   if (found && (*functionname_ptr || *line_ptr))
5104     return TRUE;
5105
5106   if (symbols == NULL)
5107     return FALSE;
5108
5109   if (!aarch64_elf_find_function (abfd, section, symbols, offset,
5110                                   filename_ptr, functionname_ptr))
5111     return FALSE;
5112
5113   *line_ptr = 0;
5114   return TRUE;
5115 }
5116
5117 static bfd_boolean
5118 elfNN_aarch64_find_inliner_info (bfd *abfd,
5119                                  const char **filename_ptr,
5120                                  const char **functionname_ptr,
5121                                  unsigned int *line_ptr)
5122 {
5123   bfd_boolean found;
5124   found = _bfd_dwarf2_find_inliner_info
5125     (abfd, filename_ptr,
5126      functionname_ptr, line_ptr, &elf_tdata (abfd)->dwarf2_find_line_info);
5127   return found;
5128 }
5129
5130
5131 static void
5132 elfNN_aarch64_post_process_headers (bfd *abfd,
5133                                     struct bfd_link_info *link_info
5134                                     ATTRIBUTE_UNUSED)
5135 {
5136   Elf_Internal_Ehdr *i_ehdrp;   /* ELF file header, internal form.  */
5137
5138   i_ehdrp = elf_elfheader (abfd);
5139   i_ehdrp->e_ident[EI_OSABI] = 0;
5140   i_ehdrp->e_ident[EI_ABIVERSION] = AARCH64_ELF_ABI_VERSION;
5141 }
5142
5143 static enum elf_reloc_type_class
5144 elfNN_aarch64_reloc_type_class (const struct bfd_link_info *info ATTRIBUTE_UNUSED,
5145                                 const asection *rel_sec ATTRIBUTE_UNUSED,
5146                                 const Elf_Internal_Rela *rela)
5147 {
5148   switch ((int) ELFNN_R_TYPE (rela->r_info))
5149     {
5150     case AARCH64_R (RELATIVE):
5151       return reloc_class_relative;
5152     case AARCH64_R (JUMP_SLOT):
5153       return reloc_class_plt;
5154     case AARCH64_R (COPY):
5155       return reloc_class_copy;
5156     default:
5157       return reloc_class_normal;
5158     }
5159 }
5160
5161 /* Set the right machine number for an AArch64 ELF file.  */
5162
5163 static bfd_boolean
5164 elfNN_aarch64_section_flags (flagword *flags, const Elf_Internal_Shdr *hdr)
5165 {
5166   if (hdr->sh_type == SHT_NOTE)
5167     *flags |= SEC_LINK_ONCE | SEC_LINK_DUPLICATES_SAME_CONTENTS;
5168
5169   return TRUE;
5170 }
5171
5172 /* Handle an AArch64 specific section when reading an object file.  This is
5173    called when bfd_section_from_shdr finds a section with an unknown
5174    type.  */
5175
5176 static bfd_boolean
5177 elfNN_aarch64_section_from_shdr (bfd *abfd,
5178                                  Elf_Internal_Shdr *hdr,
5179                                  const char *name, int shindex)
5180 {
5181   /* There ought to be a place to keep ELF backend specific flags, but
5182      at the moment there isn't one.  We just keep track of the
5183      sections by their name, instead.  Fortunately, the ABI gives
5184      names for all the AArch64 specific sections, so we will probably get
5185      away with this.  */
5186   switch (hdr->sh_type)
5187     {
5188     case SHT_AARCH64_ATTRIBUTES:
5189       break;
5190
5191     default:
5192       return FALSE;
5193     }
5194
5195   if (!_bfd_elf_make_section_from_shdr (abfd, hdr, name, shindex))
5196     return FALSE;
5197
5198   return TRUE;
5199 }
5200
5201 /* A structure used to record a list of sections, independently
5202    of the next and prev fields in the asection structure.  */
5203 typedef struct section_list
5204 {
5205   asection *sec;
5206   struct section_list *next;
5207   struct section_list *prev;
5208 }
5209 section_list;
5210
5211 /* Unfortunately we need to keep a list of sections for which
5212    an _aarch64_elf_section_data structure has been allocated.  This
5213    is because it is possible for functions like elfNN_aarch64_write_section
5214    to be called on a section which has had an elf_data_structure
5215    allocated for it (and so the used_by_bfd field is valid) but
5216    for which the AArch64 extended version of this structure - the
5217    _aarch64_elf_section_data structure - has not been allocated.  */
5218 static section_list *sections_with_aarch64_elf_section_data = NULL;
5219
5220 static void
5221 record_section_with_aarch64_elf_section_data (asection *sec)
5222 {
5223   struct section_list *entry;
5224
5225   entry = bfd_malloc (sizeof (*entry));
5226   if (entry == NULL)
5227     return;
5228   entry->sec = sec;
5229   entry->next = sections_with_aarch64_elf_section_data;
5230   entry->prev = NULL;
5231   if (entry->next != NULL)
5232     entry->next->prev = entry;
5233   sections_with_aarch64_elf_section_data = entry;
5234 }
5235
5236 static struct section_list *
5237 find_aarch64_elf_section_entry (asection *sec)
5238 {
5239   struct section_list *entry;
5240   static struct section_list *last_entry = NULL;
5241
5242   /* This is a short cut for the typical case where the sections are added
5243      to the sections_with_aarch64_elf_section_data list in forward order and
5244      then looked up here in backwards order.  This makes a real difference
5245      to the ld-srec/sec64k.exp linker test.  */
5246   entry = sections_with_aarch64_elf_section_data;
5247   if (last_entry != NULL)
5248     {
5249       if (last_entry->sec == sec)
5250         entry = last_entry;
5251       else if (last_entry->next != NULL && last_entry->next->sec == sec)
5252         entry = last_entry->next;
5253     }
5254
5255   for (; entry; entry = entry->next)
5256     if (entry->sec == sec)
5257       break;
5258
5259   if (entry)
5260     /* Record the entry prior to this one - it is the entry we are
5261        most likely to want to locate next time.  Also this way if we
5262        have been called from
5263        unrecord_section_with_aarch64_elf_section_data () we will not
5264        be caching a pointer that is about to be freed.  */
5265     last_entry = entry->prev;
5266
5267   return entry;
5268 }
5269
5270 static void
5271 unrecord_section_with_aarch64_elf_section_data (asection *sec)
5272 {
5273   struct section_list *entry;
5274
5275   entry = find_aarch64_elf_section_entry (sec);
5276
5277   if (entry)
5278     {
5279       if (entry->prev != NULL)
5280         entry->prev->next = entry->next;
5281       if (entry->next != NULL)
5282         entry->next->prev = entry->prev;
5283       if (entry == sections_with_aarch64_elf_section_data)
5284         sections_with_aarch64_elf_section_data = entry->next;
5285       free (entry);
5286     }
5287 }
5288
5289
5290 typedef struct
5291 {
5292   void *finfo;
5293   struct bfd_link_info *info;
5294   asection *sec;
5295   int sec_shndx;
5296   int (*func) (void *, const char *, Elf_Internal_Sym *,
5297                asection *, struct elf_link_hash_entry *);
5298 } output_arch_syminfo;
5299
5300 enum map_symbol_type
5301 {
5302   AARCH64_MAP_INSN,
5303   AARCH64_MAP_DATA
5304 };
5305
5306
5307 /* Output a single mapping symbol.  */
5308
5309 static bfd_boolean
5310 elfNN_aarch64_output_map_sym (output_arch_syminfo *osi,
5311                               enum map_symbol_type type, bfd_vma offset)
5312 {
5313   static const char *names[2] = { "$x", "$d" };
5314   Elf_Internal_Sym sym;
5315
5316   sym.st_value = (osi->sec->output_section->vma
5317                   + osi->sec->output_offset + offset);
5318   sym.st_size = 0;
5319   sym.st_other = 0;
5320   sym.st_info = ELF_ST_INFO (STB_LOCAL, STT_NOTYPE);
5321   sym.st_shndx = osi->sec_shndx;
5322   return osi->func (osi->finfo, names[type], &sym, osi->sec, NULL) == 1;
5323 }
5324
5325
5326
5327 /* Output mapping symbols for PLT entries associated with H.  */
5328
5329 static bfd_boolean
5330 elfNN_aarch64_output_plt_map (struct elf_link_hash_entry *h, void *inf)
5331 {
5332   output_arch_syminfo *osi = (output_arch_syminfo *) inf;
5333   bfd_vma addr;
5334
5335   if (h->root.type == bfd_link_hash_indirect)
5336     return TRUE;
5337
5338   if (h->root.type == bfd_link_hash_warning)
5339     /* When warning symbols are created, they **replace** the "real"
5340        entry in the hash table, thus we never get to see the real
5341        symbol in a hash traversal.  So look at it now.  */
5342     h = (struct elf_link_hash_entry *) h->root.u.i.link;
5343
5344   if (h->plt.offset == (bfd_vma) - 1)
5345     return TRUE;
5346
5347   addr = h->plt.offset;
5348   if (addr == 32)
5349     {
5350       if (!elfNN_aarch64_output_map_sym (osi, AARCH64_MAP_INSN, addr))
5351         return FALSE;
5352     }
5353   return TRUE;
5354 }
5355
5356
5357 /* Output a single local symbol for a generated stub.  */
5358
5359 static bfd_boolean
5360 elfNN_aarch64_output_stub_sym (output_arch_syminfo *osi, const char *name,
5361                                bfd_vma offset, bfd_vma size)
5362 {
5363   Elf_Internal_Sym sym;
5364
5365   sym.st_value = (osi->sec->output_section->vma
5366                   + osi->sec->output_offset + offset);
5367   sym.st_size = size;
5368   sym.st_other = 0;
5369   sym.st_info = ELF_ST_INFO (STB_LOCAL, STT_FUNC);
5370   sym.st_shndx = osi->sec_shndx;
5371   return osi->func (osi->finfo, name, &sym, osi->sec, NULL) == 1;
5372 }
5373
5374 static bfd_boolean
5375 aarch64_map_one_stub (struct bfd_hash_entry *gen_entry, void *in_arg)
5376 {
5377   struct elf_aarch64_stub_hash_entry *stub_entry;
5378   asection *stub_sec;
5379   bfd_vma addr;
5380   char *stub_name;
5381   output_arch_syminfo *osi;
5382
5383   /* Massage our args to the form they really have.  */
5384   stub_entry = (struct elf_aarch64_stub_hash_entry *) gen_entry;
5385   osi = (output_arch_syminfo *) in_arg;
5386
5387   stub_sec = stub_entry->stub_sec;
5388
5389   /* Ensure this stub is attached to the current section being
5390      processed.  */
5391   if (stub_sec != osi->sec)
5392     return TRUE;
5393
5394   addr = (bfd_vma) stub_entry->stub_offset;
5395
5396   stub_name = stub_entry->output_name;
5397
5398   switch (stub_entry->stub_type)
5399     {
5400     case aarch64_stub_adrp_branch:
5401       if (!elfNN_aarch64_output_stub_sym (osi, stub_name, addr,
5402                                           sizeof (aarch64_adrp_branch_stub)))
5403         return FALSE;
5404       if (!elfNN_aarch64_output_map_sym (osi, AARCH64_MAP_INSN, addr))
5405         return FALSE;
5406       break;
5407     case aarch64_stub_long_branch:
5408       if (!elfNN_aarch64_output_stub_sym
5409           (osi, stub_name, addr, sizeof (aarch64_long_branch_stub)))
5410         return FALSE;
5411       if (!elfNN_aarch64_output_map_sym (osi, AARCH64_MAP_INSN, addr))
5412         return FALSE;
5413       if (!elfNN_aarch64_output_map_sym (osi, AARCH64_MAP_DATA, addr + 16))
5414         return FALSE;
5415       break;
5416     default:
5417       BFD_FAIL ();
5418     }
5419
5420   return TRUE;
5421 }
5422
5423 /* Output mapping symbols for linker generated sections.  */
5424
5425 static bfd_boolean
5426 elfNN_aarch64_output_arch_local_syms (bfd *output_bfd,
5427                                       struct bfd_link_info *info,
5428                                       void *finfo,
5429                                       int (*func) (void *, const char *,
5430                                                    Elf_Internal_Sym *,
5431                                                    asection *,
5432                                                    struct elf_link_hash_entry
5433                                                    *))
5434 {
5435   output_arch_syminfo osi;
5436   struct elf_aarch64_link_hash_table *htab;
5437
5438   htab = elf_aarch64_hash_table (info);
5439
5440   osi.finfo = finfo;
5441   osi.info = info;
5442   osi.func = func;
5443
5444   /* Long calls stubs.  */
5445   if (htab->stub_bfd && htab->stub_bfd->sections)
5446     {
5447       asection *stub_sec;
5448
5449       for (stub_sec = htab->stub_bfd->sections;
5450            stub_sec != NULL; stub_sec = stub_sec->next)
5451         {
5452           /* Ignore non-stub sections.  */
5453           if (!strstr (stub_sec->name, STUB_SUFFIX))
5454             continue;
5455
5456           osi.sec = stub_sec;
5457
5458           osi.sec_shndx = _bfd_elf_section_from_bfd_section
5459             (output_bfd, osi.sec->output_section);
5460
5461           bfd_hash_traverse (&htab->stub_hash_table, aarch64_map_one_stub,
5462                              &osi);
5463         }
5464     }
5465
5466   /* Finally, output mapping symbols for the PLT.  */
5467   if (!htab->root.splt || htab->root.splt->size == 0)
5468     return TRUE;
5469
5470   /* For now live without mapping symbols for the plt.  */
5471   osi.sec_shndx = _bfd_elf_section_from_bfd_section
5472     (output_bfd, htab->root.splt->output_section);
5473   osi.sec = htab->root.splt;
5474
5475   elf_link_hash_traverse (&htab->root, elfNN_aarch64_output_plt_map,
5476                           (void *) &osi);
5477
5478   return TRUE;
5479
5480 }
5481
5482 /* Allocate target specific section data.  */
5483
5484 static bfd_boolean
5485 elfNN_aarch64_new_section_hook (bfd *abfd, asection *sec)
5486 {
5487   if (!sec->used_by_bfd)
5488     {
5489       _aarch64_elf_section_data *sdata;
5490       bfd_size_type amt = sizeof (*sdata);
5491
5492       sdata = bfd_zalloc (abfd, amt);
5493       if (sdata == NULL)
5494         return FALSE;
5495       sec->used_by_bfd = sdata;
5496     }
5497
5498   record_section_with_aarch64_elf_section_data (sec);
5499
5500   return _bfd_elf_new_section_hook (abfd, sec);
5501 }
5502
5503
5504 static void
5505 unrecord_section_via_map_over_sections (bfd *abfd ATTRIBUTE_UNUSED,
5506                                         asection *sec,
5507                                         void *ignore ATTRIBUTE_UNUSED)
5508 {
5509   unrecord_section_with_aarch64_elf_section_data (sec);
5510 }
5511
5512 static bfd_boolean
5513 elfNN_aarch64_close_and_cleanup (bfd *abfd)
5514 {
5515   if (abfd->sections)
5516     bfd_map_over_sections (abfd,
5517                            unrecord_section_via_map_over_sections, NULL);
5518
5519   return _bfd_elf_close_and_cleanup (abfd);
5520 }
5521
5522 static bfd_boolean
5523 elfNN_aarch64_bfd_free_cached_info (bfd *abfd)
5524 {
5525   if (abfd->sections)
5526     bfd_map_over_sections (abfd,
5527                            unrecord_section_via_map_over_sections, NULL);
5528
5529   return _bfd_free_cached_info (abfd);
5530 }
5531
5532 static bfd_boolean
5533 elfNN_aarch64_is_function_type (unsigned int type)
5534 {
5535   return type == STT_FUNC;
5536 }
5537
5538 /* Create dynamic sections. This is different from the ARM backend in that
5539    the got, plt, gotplt and their relocation sections are all created in the
5540    standard part of the bfd elf backend.  */
5541
5542 static bfd_boolean
5543 elfNN_aarch64_create_dynamic_sections (bfd *dynobj,
5544                                        struct bfd_link_info *info)
5545 {
5546   struct elf_aarch64_link_hash_table *htab;
5547
5548   /* We need to create .got section.  */
5549   if (!aarch64_elf_create_got_section (dynobj, info))
5550     return FALSE;
5551
5552   if (!_bfd_elf_create_dynamic_sections (dynobj, info))
5553     return FALSE;
5554
5555   htab = elf_aarch64_hash_table (info);
5556   htab->sdynbss = bfd_get_linker_section (dynobj, ".dynbss");
5557   if (!info->shared)
5558     htab->srelbss = bfd_get_linker_section (dynobj, ".rela.bss");
5559
5560   if (!htab->sdynbss || (!info->shared && !htab->srelbss))
5561     abort ();
5562
5563   return TRUE;
5564 }
5565
5566
5567 /* Allocate space in .plt, .got and associated reloc sections for
5568    dynamic relocs.  */
5569
5570 static bfd_boolean
5571 elfNN_aarch64_allocate_dynrelocs (struct elf_link_hash_entry *h, void *inf)
5572 {
5573   struct bfd_link_info *info;
5574   struct elf_aarch64_link_hash_table *htab;
5575   struct elf_aarch64_link_hash_entry *eh;
5576   struct elf_dyn_relocs *p;
5577
5578   /* An example of a bfd_link_hash_indirect symbol is versioned
5579      symbol. For example: __gxx_personality_v0(bfd_link_hash_indirect)
5580      -> __gxx_personality_v0(bfd_link_hash_defined)
5581
5582      There is no need to process bfd_link_hash_indirect symbols here
5583      because we will also be presented with the concrete instance of
5584      the symbol and elfNN_aarch64_copy_indirect_symbol () will have been
5585      called to copy all relevant data from the generic to the concrete
5586      symbol instance.
5587    */
5588   if (h->root.type == bfd_link_hash_indirect)
5589     return TRUE;
5590
5591   if (h->root.type == bfd_link_hash_warning)
5592     h = (struct elf_link_hash_entry *) h->root.u.i.link;
5593
5594   info = (struct bfd_link_info *) inf;
5595   htab = elf_aarch64_hash_table (info);
5596
5597   if (htab->root.dynamic_sections_created && h->plt.refcount > 0)
5598     {
5599       /* Make sure this symbol is output as a dynamic symbol.
5600          Undefined weak syms won't yet be marked as dynamic.  */
5601       if (h->dynindx == -1 && !h->forced_local)
5602         {
5603           if (!bfd_elf_link_record_dynamic_symbol (info, h))
5604             return FALSE;
5605         }
5606
5607       if (info->shared || WILL_CALL_FINISH_DYNAMIC_SYMBOL (1, 0, h))
5608         {
5609           asection *s = htab->root.splt;
5610
5611           /* If this is the first .plt entry, make room for the special
5612              first entry.  */
5613           if (s->size == 0)
5614             s->size += htab->plt_header_size;
5615
5616           h->plt.offset = s->size;
5617
5618           /* If this symbol is not defined in a regular file, and we are
5619              not generating a shared library, then set the symbol to this
5620              location in the .plt.  This is required to make function
5621              pointers compare as equal between the normal executable and
5622              the shared library.  */
5623           if (!info->shared && !h->def_regular)
5624             {
5625               h->root.u.def.section = s;
5626               h->root.u.def.value = h->plt.offset;
5627             }
5628
5629           /* Make room for this entry. For now we only create the
5630              small model PLT entries. We later need to find a way
5631              of relaxing into these from the large model PLT entries.  */
5632           s->size += PLT_SMALL_ENTRY_SIZE;
5633
5634           /* We also need to make an entry in the .got.plt section, which
5635              will be placed in the .got section by the linker script.  */
5636           htab->root.sgotplt->size += GOT_ENTRY_SIZE;
5637
5638           /* We also need to make an entry in the .rela.plt section.  */
5639           htab->root.srelplt->size += RELOC_SIZE (htab);
5640
5641           /* We need to ensure that all GOT entries that serve the PLT
5642              are consecutive with the special GOT slots [0] [1] and
5643              [2]. Any addtional relocations, such as
5644              R_AARCH64_TLSDESC, must be placed after the PLT related
5645              entries.  We abuse the reloc_count such that during
5646              sizing we adjust reloc_count to indicate the number of
5647              PLT related reserved entries.  In subsequent phases when
5648              filling in the contents of the reloc entries, PLT related
5649              entries are placed by computing their PLT index (0
5650              .. reloc_count). While other none PLT relocs are placed
5651              at the slot indicated by reloc_count and reloc_count is
5652              updated.  */
5653
5654           htab->root.srelplt->reloc_count++;
5655         }
5656       else
5657         {
5658           h->plt.offset = (bfd_vma) - 1;
5659           h->needs_plt = 0;
5660         }
5661     }
5662   else
5663     {
5664       h->plt.offset = (bfd_vma) - 1;
5665       h->needs_plt = 0;
5666     }
5667
5668   eh = (struct elf_aarch64_link_hash_entry *) h;
5669   eh->tlsdesc_got_jump_table_offset = (bfd_vma) - 1;
5670
5671   if (h->got.refcount > 0)
5672     {
5673       bfd_boolean dyn;
5674       unsigned got_type = elf_aarch64_hash_entry (h)->got_type;
5675
5676       h->got.offset = (bfd_vma) - 1;
5677
5678       dyn = htab->root.dynamic_sections_created;
5679
5680       /* Make sure this symbol is output as a dynamic symbol.
5681          Undefined weak syms won't yet be marked as dynamic.  */
5682       if (dyn && h->dynindx == -1 && !h->forced_local)
5683         {
5684           if (!bfd_elf_link_record_dynamic_symbol (info, h))
5685             return FALSE;
5686         }
5687
5688       if (got_type == GOT_UNKNOWN)
5689         {
5690         }
5691       else if (got_type == GOT_NORMAL)
5692         {
5693           h->got.offset = htab->root.sgot->size;
5694           htab->root.sgot->size += GOT_ENTRY_SIZE;
5695           if ((ELF_ST_VISIBILITY (h->other) == STV_DEFAULT
5696                || h->root.type != bfd_link_hash_undefweak)
5697               && (info->shared
5698                   || WILL_CALL_FINISH_DYNAMIC_SYMBOL (dyn, 0, h)))
5699             {
5700               htab->root.srelgot->size += RELOC_SIZE (htab);
5701             }
5702         }
5703       else
5704         {
5705           int indx;
5706           if (got_type & GOT_TLSDESC_GD)
5707             {
5708               eh->tlsdesc_got_jump_table_offset =
5709                 (htab->root.sgotplt->size
5710                  - aarch64_compute_jump_table_size (htab));
5711               htab->root.sgotplt->size += GOT_ENTRY_SIZE * 2;
5712               h->got.offset = (bfd_vma) - 2;
5713             }
5714
5715           if (got_type & GOT_TLS_GD)
5716             {
5717               h->got.offset = htab->root.sgot->size;
5718               htab->root.sgot->size += GOT_ENTRY_SIZE * 2;
5719             }
5720
5721           if (got_type & GOT_TLS_IE)
5722             {
5723               h->got.offset = htab->root.sgot->size;
5724               htab->root.sgot->size += GOT_ENTRY_SIZE;
5725             }
5726
5727           indx = h && h->dynindx != -1 ? h->dynindx : 0;
5728           if ((ELF_ST_VISIBILITY (h->other) == STV_DEFAULT
5729                || h->root.type != bfd_link_hash_undefweak)
5730               && (info->shared
5731                   || indx != 0
5732                   || WILL_CALL_FINISH_DYNAMIC_SYMBOL (dyn, 0, h)))
5733             {
5734               if (got_type & GOT_TLSDESC_GD)
5735                 {
5736                   htab->root.srelplt->size += RELOC_SIZE (htab);
5737                   /* Note reloc_count not incremented here!  We have
5738                      already adjusted reloc_count for this relocation
5739                      type.  */
5740
5741                   /* TLSDESC PLT is now needed, but not yet determined.  */
5742                   htab->tlsdesc_plt = (bfd_vma) - 1;
5743                 }
5744
5745               if (got_type & GOT_TLS_GD)
5746                 htab->root.srelgot->size += RELOC_SIZE (htab) * 2;
5747
5748               if (got_type & GOT_TLS_IE)
5749                 htab->root.srelgot->size += RELOC_SIZE (htab);
5750             }
5751         }
5752     }
5753   else
5754     {
5755       h->got.offset = (bfd_vma) - 1;
5756     }
5757
5758   if (eh->dyn_relocs == NULL)
5759     return TRUE;
5760
5761   /* In the shared -Bsymbolic case, discard space allocated for
5762      dynamic pc-relative relocs against symbols which turn out to be
5763      defined in regular objects.  For the normal shared case, discard
5764      space for pc-relative relocs that have become local due to symbol
5765      visibility changes.  */
5766
5767   if (info->shared)
5768     {
5769       /* Relocs that use pc_count are those that appear on a call
5770          insn, or certain REL relocs that can generated via assembly.
5771          We want calls to protected symbols to resolve directly to the
5772          function rather than going via the plt.  If people want
5773          function pointer comparisons to work as expected then they
5774          should avoid writing weird assembly.  */
5775       if (SYMBOL_CALLS_LOCAL (info, h))
5776         {
5777           struct elf_dyn_relocs **pp;
5778
5779           for (pp = &eh->dyn_relocs; (p = *pp) != NULL;)
5780             {
5781               p->count -= p->pc_count;
5782               p->pc_count = 0;
5783               if (p->count == 0)
5784                 *pp = p->next;
5785               else
5786                 pp = &p->next;
5787             }
5788         }
5789
5790       /* Also discard relocs on undefined weak syms with non-default
5791          visibility.  */
5792       if (eh->dyn_relocs != NULL && h->root.type == bfd_link_hash_undefweak)
5793         {
5794           if (ELF_ST_VISIBILITY (h->other) != STV_DEFAULT)
5795             eh->dyn_relocs = NULL;
5796
5797           /* Make sure undefined weak symbols are output as a dynamic
5798              symbol in PIEs.  */
5799           else if (h->dynindx == -1
5800                    && !h->forced_local
5801                    && !bfd_elf_link_record_dynamic_symbol (info, h))
5802             return FALSE;
5803         }
5804
5805     }
5806   else if (ELIMINATE_COPY_RELOCS)
5807     {
5808       /* For the non-shared case, discard space for relocs against
5809          symbols which turn out to need copy relocs or are not
5810          dynamic.  */
5811
5812       if (!h->non_got_ref
5813           && ((h->def_dynamic
5814                && !h->def_regular)
5815               || (htab->root.dynamic_sections_created
5816                   && (h->root.type == bfd_link_hash_undefweak
5817                       || h->root.type == bfd_link_hash_undefined))))
5818         {
5819           /* Make sure this symbol is output as a dynamic symbol.
5820              Undefined weak syms won't yet be marked as dynamic.  */
5821           if (h->dynindx == -1
5822               && !h->forced_local
5823               && !bfd_elf_link_record_dynamic_symbol (info, h))
5824             return FALSE;
5825
5826           /* If that succeeded, we know we'll be keeping all the
5827              relocs.  */
5828           if (h->dynindx != -1)
5829             goto keep;
5830         }
5831
5832       eh->dyn_relocs = NULL;
5833
5834     keep:;
5835     }
5836
5837   /* Finally, allocate space.  */
5838   for (p = eh->dyn_relocs; p != NULL; p = p->next)
5839     {
5840       asection *sreloc;
5841
5842       sreloc = elf_section_data (p->sec)->sreloc;
5843
5844       BFD_ASSERT (sreloc != NULL);
5845
5846       sreloc->size += p->count * RELOC_SIZE (htab);
5847     }
5848
5849   return TRUE;
5850 }
5851
5852
5853 /* This is the most important function of all . Innocuosly named
5854    though !  */
5855 static bfd_boolean
5856 elfNN_aarch64_size_dynamic_sections (bfd *output_bfd ATTRIBUTE_UNUSED,
5857                                      struct bfd_link_info *info)
5858 {
5859   struct elf_aarch64_link_hash_table *htab;
5860   bfd *dynobj;
5861   asection *s;
5862   bfd_boolean relocs;
5863   bfd *ibfd;
5864
5865   htab = elf_aarch64_hash_table ((info));
5866   dynobj = htab->root.dynobj;
5867
5868   BFD_ASSERT (dynobj != NULL);
5869
5870   if (htab->root.dynamic_sections_created)
5871     {
5872       if (info->executable)
5873         {
5874           s = bfd_get_linker_section (dynobj, ".interp");
5875           if (s == NULL)
5876             abort ();
5877           s->size = sizeof ELF_DYNAMIC_INTERPRETER;
5878           s->contents = (unsigned char *) ELF_DYNAMIC_INTERPRETER;
5879         }
5880     }
5881
5882   /* Set up .got offsets for local syms, and space for local dynamic
5883      relocs.  */
5884   for (ibfd = info->input_bfds; ibfd != NULL; ibfd = ibfd->link_next)
5885     {
5886       struct elf_aarch64_local_symbol *locals = NULL;
5887       Elf_Internal_Shdr *symtab_hdr;
5888       asection *srel;
5889       unsigned int i;
5890
5891       if (!is_aarch64_elf (ibfd))
5892         continue;
5893
5894       for (s = ibfd->sections; s != NULL; s = s->next)
5895         {
5896           struct elf_dyn_relocs *p;
5897
5898           for (p = (struct elf_dyn_relocs *)
5899                (elf_section_data (s)->local_dynrel); p != NULL; p = p->next)
5900             {
5901               if (!bfd_is_abs_section (p->sec)
5902                   && bfd_is_abs_section (p->sec->output_section))
5903                 {
5904                   /* Input section has been discarded, either because
5905                      it is a copy of a linkonce section or due to
5906                      linker script /DISCARD/, so we'll be discarding
5907                      the relocs too.  */
5908                 }
5909               else if (p->count != 0)
5910                 {
5911                   srel = elf_section_data (p->sec)->sreloc;
5912                   srel->size += p->count * RELOC_SIZE (htab);
5913                   if ((p->sec->output_section->flags & SEC_READONLY) != 0)
5914                     info->flags |= DF_TEXTREL;
5915                 }
5916             }
5917         }
5918
5919       locals = elf_aarch64_locals (ibfd);
5920       if (!locals)
5921         continue;
5922
5923       symtab_hdr = &elf_symtab_hdr (ibfd);
5924       srel = htab->root.srelgot;
5925       for (i = 0; i < symtab_hdr->sh_info; i++)
5926         {
5927           locals[i].got_offset = (bfd_vma) - 1;
5928           locals[i].tlsdesc_got_jump_table_offset = (bfd_vma) - 1;
5929           if (locals[i].got_refcount > 0)
5930             {
5931               unsigned got_type = locals[i].got_type;
5932               if (got_type & GOT_TLSDESC_GD)
5933                 {
5934                   locals[i].tlsdesc_got_jump_table_offset =
5935                     (htab->root.sgotplt->size
5936                      - aarch64_compute_jump_table_size (htab));
5937                   htab->root.sgotplt->size += GOT_ENTRY_SIZE * 2;
5938                   locals[i].got_offset = (bfd_vma) - 2;
5939                 }
5940
5941               if (got_type & GOT_TLS_GD)
5942                 {
5943                   locals[i].got_offset = htab->root.sgot->size;
5944                   htab->root.sgot->size += GOT_ENTRY_SIZE * 2;
5945                 }
5946
5947               if (got_type & GOT_TLS_IE)
5948                 {
5949                   locals[i].got_offset = htab->root.sgot->size;
5950                   htab->root.sgot->size += GOT_ENTRY_SIZE;
5951                 }
5952
5953               if (got_type == GOT_UNKNOWN)
5954                 {
5955                 }
5956
5957               if (got_type == GOT_NORMAL)
5958                 {
5959                 }
5960
5961               if (info->shared)
5962                 {
5963                   if (got_type & GOT_TLSDESC_GD)
5964                     {
5965                       htab->root.srelplt->size += RELOC_SIZE (htab);
5966                       /* Note RELOC_COUNT not incremented here! */
5967                       htab->tlsdesc_plt = (bfd_vma) - 1;
5968                     }
5969
5970                   if (got_type & GOT_TLS_GD)
5971                     htab->root.srelgot->size += RELOC_SIZE (htab) * 2;
5972
5973                   if (got_type & GOT_TLS_IE)
5974                     htab->root.srelgot->size += RELOC_SIZE (htab);
5975                 }
5976             }
5977           else
5978             {
5979               locals[i].got_refcount = (bfd_vma) - 1;
5980             }
5981         }
5982     }
5983
5984
5985   /* Allocate global sym .plt and .got entries, and space for global
5986      sym dynamic relocs.  */
5987   elf_link_hash_traverse (&htab->root, elfNN_aarch64_allocate_dynrelocs,
5988                           info);
5989
5990
5991   /* For every jump slot reserved in the sgotplt, reloc_count is
5992      incremented.  However, when we reserve space for TLS descriptors,
5993      it's not incremented, so in order to compute the space reserved
5994      for them, it suffices to multiply the reloc count by the jump
5995      slot size.  */
5996
5997   if (htab->root.srelplt)
5998     htab->sgotplt_jump_table_size = aarch64_compute_jump_table_size (htab);
5999
6000   if (htab->tlsdesc_plt)
6001     {
6002       if (htab->root.splt->size == 0)
6003         htab->root.splt->size += PLT_ENTRY_SIZE;
6004
6005       htab->tlsdesc_plt = htab->root.splt->size;
6006       htab->root.splt->size += PLT_TLSDESC_ENTRY_SIZE;
6007
6008       /* If we're not using lazy TLS relocations, don't generate the
6009          GOT entry required.  */
6010       if (!(info->flags & DF_BIND_NOW))
6011         {
6012           htab->dt_tlsdesc_got = htab->root.sgot->size;
6013           htab->root.sgot->size += GOT_ENTRY_SIZE;
6014         }
6015     }
6016
6017   /* We now have determined the sizes of the various dynamic sections.
6018      Allocate memory for them.  */
6019   relocs = FALSE;
6020   for (s = dynobj->sections; s != NULL; s = s->next)
6021     {
6022       if ((s->flags & SEC_LINKER_CREATED) == 0)
6023         continue;
6024
6025       if (s == htab->root.splt
6026           || s == htab->root.sgot
6027           || s == htab->root.sgotplt
6028           || s == htab->root.iplt
6029           || s == htab->root.igotplt || s == htab->sdynbss)
6030         {
6031           /* Strip this section if we don't need it; see the
6032              comment below.  */
6033         }
6034       else if (CONST_STRNEQ (bfd_get_section_name (dynobj, s), ".rela"))
6035         {
6036           if (s->size != 0 && s != htab->root.srelplt)
6037             relocs = TRUE;
6038
6039           /* We use the reloc_count field as a counter if we need
6040              to copy relocs into the output file.  */
6041           if (s != htab->root.srelplt)
6042             s->reloc_count = 0;
6043         }
6044       else
6045         {
6046           /* It's not one of our sections, so don't allocate space.  */
6047           continue;
6048         }
6049
6050       if (s->size == 0)
6051         {
6052           /* If we don't need this section, strip it from the
6053              output file.  This is mostly to handle .rela.bss and
6054              .rela.plt.  We must create both sections in
6055              create_dynamic_sections, because they must be created
6056              before the linker maps input sections to output
6057              sections.  The linker does that before
6058              adjust_dynamic_symbol is called, and it is that
6059              function which decides whether anything needs to go
6060              into these sections.  */
6061
6062           s->flags |= SEC_EXCLUDE;
6063           continue;
6064         }
6065
6066       if ((s->flags & SEC_HAS_CONTENTS) == 0)
6067         continue;
6068
6069       /* Allocate memory for the section contents.  We use bfd_zalloc
6070          here in case unused entries are not reclaimed before the
6071          section's contents are written out.  This should not happen,
6072          but this way if it does, we get a R_AARCH64_NONE reloc instead
6073          of garbage.  */
6074       s->contents = (bfd_byte *) bfd_zalloc (dynobj, s->size);
6075       if (s->contents == NULL)
6076         return FALSE;
6077     }
6078
6079   if (htab->root.dynamic_sections_created)
6080     {
6081       /* Add some entries to the .dynamic section.  We fill in the
6082          values later, in elfNN_aarch64_finish_dynamic_sections, but we
6083          must add the entries now so that we get the correct size for
6084          the .dynamic section.  The DT_DEBUG entry is filled in by the
6085          dynamic linker and used by the debugger.  */
6086 #define add_dynamic_entry(TAG, VAL)                     \
6087       _bfd_elf_add_dynamic_entry (info, TAG, VAL)
6088
6089       if (info->executable)
6090         {
6091           if (!add_dynamic_entry (DT_DEBUG, 0))
6092             return FALSE;
6093         }
6094
6095       if (htab->root.splt->size != 0)
6096         {
6097           if (!add_dynamic_entry (DT_PLTGOT, 0)
6098               || !add_dynamic_entry (DT_PLTRELSZ, 0)
6099               || !add_dynamic_entry (DT_PLTREL, DT_RELA)
6100               || !add_dynamic_entry (DT_JMPREL, 0))
6101             return FALSE;
6102
6103           if (htab->tlsdesc_plt
6104               && (!add_dynamic_entry (DT_TLSDESC_PLT, 0)
6105                   || !add_dynamic_entry (DT_TLSDESC_GOT, 0)))
6106             return FALSE;
6107         }
6108
6109       if (relocs)
6110         {
6111           if (!add_dynamic_entry (DT_RELA, 0)
6112               || !add_dynamic_entry (DT_RELASZ, 0)
6113               || !add_dynamic_entry (DT_RELAENT, RELOC_SIZE (htab)))
6114             return FALSE;
6115
6116           /* If any dynamic relocs apply to a read-only section,
6117              then we need a DT_TEXTREL entry.  */
6118           if ((info->flags & DF_TEXTREL) != 0)
6119             {
6120               if (!add_dynamic_entry (DT_TEXTREL, 0))
6121                 return FALSE;
6122             }
6123         }
6124     }
6125 #undef add_dynamic_entry
6126
6127   return TRUE;
6128 }
6129
6130 static inline void
6131 elf_aarch64_update_plt_entry (bfd *output_bfd,
6132                               bfd_reloc_code_real_type r_type,
6133                               bfd_byte *plt_entry, bfd_vma value)
6134 {
6135   reloc_howto_type *howto = elfNN_aarch64_howto_from_bfd_reloc (r_type);
6136
6137   _bfd_aarch64_elf_put_addend (output_bfd, plt_entry, r_type, howto, value);
6138 }
6139
6140 static void
6141 elfNN_aarch64_create_small_pltn_entry (struct elf_link_hash_entry *h,
6142                                        struct elf_aarch64_link_hash_table
6143                                        *htab, bfd *output_bfd)
6144 {
6145   bfd_byte *plt_entry;
6146   bfd_vma plt_index;
6147   bfd_vma got_offset;
6148   bfd_vma gotplt_entry_address;
6149   bfd_vma plt_entry_address;
6150   Elf_Internal_Rela rela;
6151   bfd_byte *loc;
6152
6153   plt_index = (h->plt.offset - htab->plt_header_size) / htab->plt_entry_size;
6154
6155   /* Offset in the GOT is PLT index plus got GOT headers(3)
6156      times GOT_ENTRY_SIZE.  */
6157   got_offset = (plt_index + 3) * GOT_ENTRY_SIZE;
6158   plt_entry = htab->root.splt->contents + h->plt.offset;
6159   plt_entry_address = htab->root.splt->output_section->vma
6160     + htab->root.splt->output_section->output_offset + h->plt.offset;
6161   gotplt_entry_address = htab->root.sgotplt->output_section->vma +
6162     htab->root.sgotplt->output_offset + got_offset;
6163
6164   /* Copy in the boiler-plate for the PLTn entry.  */
6165   memcpy (plt_entry, elfNN_aarch64_small_plt_entry, PLT_SMALL_ENTRY_SIZE);
6166
6167   /* Fill in the top 21 bits for this: ADRP x16, PLT_GOT + n * 8.
6168      ADRP:   ((PG(S+A)-PG(P)) >> 12) & 0x1fffff */
6169   elf_aarch64_update_plt_entry (output_bfd, BFD_RELOC_AARCH64_ADR_HI21_PCREL,
6170                                 plt_entry,
6171                                 PG (gotplt_entry_address) -
6172                                 PG (plt_entry_address));
6173
6174   /* Fill in the lo12 bits for the load from the pltgot.  */
6175   elf_aarch64_update_plt_entry (output_bfd, BFD_RELOC_AARCH64_LDSTNN_LO12,
6176                                 plt_entry + 4,
6177                                 PG_OFFSET (gotplt_entry_address));
6178
6179   /* Fill in the lo12 bits for the add from the pltgot entry.  */
6180   elf_aarch64_update_plt_entry (output_bfd, BFD_RELOC_AARCH64_ADD_LO12,
6181                                 plt_entry + 8,
6182                                 PG_OFFSET (gotplt_entry_address));
6183
6184   /* All the GOTPLT Entries are essentially initialized to PLT0.  */
6185   bfd_put_NN (output_bfd,
6186               (htab->root.splt->output_section->vma
6187                + htab->root.splt->output_offset),
6188               htab->root.sgotplt->contents + got_offset);
6189
6190   /* Fill in the entry in the .rela.plt section.  */
6191   rela.r_offset = gotplt_entry_address;
6192   rela.r_info = ELFNN_R_INFO (h->dynindx, AARCH64_R (JUMP_SLOT));
6193   rela.r_addend = 0;
6194
6195   /* Compute the relocation entry to used based on PLT index and do
6196      not adjust reloc_count. The reloc_count has already been adjusted
6197      to account for this entry.  */
6198   loc = htab->root.srelplt->contents + plt_index * RELOC_SIZE (htab);
6199   bfd_elfNN_swap_reloca_out (output_bfd, &rela, loc);
6200 }
6201
6202 /* Size sections even though they're not dynamic.  We use it to setup
6203    _TLS_MODULE_BASE_, if needed.  */
6204
6205 static bfd_boolean
6206 elfNN_aarch64_always_size_sections (bfd *output_bfd,
6207                                     struct bfd_link_info *info)
6208 {
6209   asection *tls_sec;
6210
6211   if (info->relocatable)
6212     return TRUE;
6213
6214   tls_sec = elf_hash_table (info)->tls_sec;
6215
6216   if (tls_sec)
6217     {
6218       struct elf_link_hash_entry *tlsbase;
6219
6220       tlsbase = elf_link_hash_lookup (elf_hash_table (info),
6221                                       "_TLS_MODULE_BASE_", TRUE, TRUE, FALSE);
6222
6223       if (tlsbase)
6224         {
6225           struct bfd_link_hash_entry *h = NULL;
6226           const struct elf_backend_data *bed =
6227             get_elf_backend_data (output_bfd);
6228
6229           if (!(_bfd_generic_link_add_one_symbol
6230                 (info, output_bfd, "_TLS_MODULE_BASE_", BSF_LOCAL,
6231                  tls_sec, 0, NULL, FALSE, bed->collect, &h)))
6232             return FALSE;
6233
6234           tlsbase->type = STT_TLS;
6235           tlsbase = (struct elf_link_hash_entry *) h;
6236           tlsbase->def_regular = 1;
6237           tlsbase->other = STV_HIDDEN;
6238           (*bed->elf_backend_hide_symbol) (info, tlsbase, TRUE);
6239         }
6240     }
6241
6242   return TRUE;
6243 }
6244
6245 /* Finish up dynamic symbol handling.  We set the contents of various
6246    dynamic sections here.  */
6247 static bfd_boolean
6248 elfNN_aarch64_finish_dynamic_symbol (bfd *output_bfd,
6249                                      struct bfd_link_info *info,
6250                                      struct elf_link_hash_entry *h,
6251                                      Elf_Internal_Sym *sym)
6252 {
6253   struct elf_aarch64_link_hash_table *htab;
6254   htab = elf_aarch64_hash_table (info);
6255
6256   if (h->plt.offset != (bfd_vma) - 1)
6257     {
6258       /* This symbol has an entry in the procedure linkage table.  Set
6259          it up.  */
6260
6261       if (h->dynindx == -1
6262           || htab->root.splt == NULL
6263           || htab->root.sgotplt == NULL || htab->root.srelplt == NULL)
6264         abort ();
6265
6266       elfNN_aarch64_create_small_pltn_entry (h, htab, output_bfd);
6267       if (!h->def_regular)
6268         {
6269           /* Mark the symbol as undefined, rather than as defined in
6270              the .plt section.  Leave the value alone.  This is a clue
6271              for the dynamic linker, to make function pointer
6272              comparisons work between an application and shared
6273              library.  */
6274           sym->st_shndx = SHN_UNDEF;
6275         }
6276     }
6277
6278   if (h->got.offset != (bfd_vma) - 1
6279       && elf_aarch64_hash_entry (h)->got_type == GOT_NORMAL)
6280     {
6281       Elf_Internal_Rela rela;
6282       bfd_byte *loc;
6283
6284       /* This symbol has an entry in the global offset table.  Set it
6285          up.  */
6286       if (htab->root.sgot == NULL || htab->root.srelgot == NULL)
6287         abort ();
6288
6289       rela.r_offset = (htab->root.sgot->output_section->vma
6290                        + htab->root.sgot->output_offset
6291                        + (h->got.offset & ~(bfd_vma) 1));
6292
6293       if (info->shared && SYMBOL_REFERENCES_LOCAL (info, h))
6294         {
6295           if (!h->def_regular)
6296             return FALSE;
6297
6298           BFD_ASSERT ((h->got.offset & 1) != 0);
6299           rela.r_info = ELFNN_R_INFO (0, AARCH64_R (RELATIVE));
6300           rela.r_addend = (h->root.u.def.value
6301                            + h->root.u.def.section->output_section->vma
6302                            + h->root.u.def.section->output_offset);
6303         }
6304       else
6305         {
6306           BFD_ASSERT ((h->got.offset & 1) == 0);
6307           bfd_put_NN (output_bfd, (bfd_vma) 0,
6308                       htab->root.sgot->contents + h->got.offset);
6309           rela.r_info = ELFNN_R_INFO (h->dynindx, AARCH64_R (GLOB_DAT));
6310           rela.r_addend = 0;
6311         }
6312
6313       loc = htab->root.srelgot->contents;
6314       loc += htab->root.srelgot->reloc_count++ * RELOC_SIZE (htab);
6315       bfd_elfNN_swap_reloca_out (output_bfd, &rela, loc);
6316     }
6317
6318   if (h->needs_copy)
6319     {
6320       Elf_Internal_Rela rela;
6321       bfd_byte *loc;
6322
6323       /* This symbol needs a copy reloc.  Set it up.  */
6324
6325       if (h->dynindx == -1
6326           || (h->root.type != bfd_link_hash_defined
6327               && h->root.type != bfd_link_hash_defweak)
6328           || htab->srelbss == NULL)
6329         abort ();
6330
6331       rela.r_offset = (h->root.u.def.value
6332                        + h->root.u.def.section->output_section->vma
6333                        + h->root.u.def.section->output_offset);
6334       rela.r_info = ELFNN_R_INFO (h->dynindx, AARCH64_R (COPY));
6335       rela.r_addend = 0;
6336       loc = htab->srelbss->contents;
6337       loc += htab->srelbss->reloc_count++ * RELOC_SIZE (htab);
6338       bfd_elfNN_swap_reloca_out (output_bfd, &rela, loc);
6339     }
6340
6341   /* Mark _DYNAMIC and _GLOBAL_OFFSET_TABLE_ as absolute.  SYM may
6342      be NULL for local symbols.  */
6343   if (sym != NULL
6344       && (h == elf_hash_table (info)->hdynamic
6345           || h == elf_hash_table (info)->hgot))
6346     sym->st_shndx = SHN_ABS;
6347
6348   return TRUE;
6349 }
6350
6351 static void
6352 elfNN_aarch64_init_small_plt0_entry (bfd *output_bfd ATTRIBUTE_UNUSED,
6353                                      struct elf_aarch64_link_hash_table
6354                                      *htab)
6355 {
6356   /* Fill in PLT0. Fixme:RR Note this doesn't distinguish between
6357      small and large plts and at the minute just generates
6358      the small PLT.  */
6359
6360   /* PLT0 of the small PLT looks like this in ELF64 -
6361      stp x16, x30, [sp, #-16]!          // Save the reloc and lr on stack.
6362      adrp x16, PLT_GOT + 16             // Get the page base of the GOTPLT
6363      ldr  x17, [x16, #:lo12:PLT_GOT+16] // Load the address of the
6364                                         // symbol resolver
6365      add  x16, x16, #:lo12:PLT_GOT+16   // Load the lo12 bits of the
6366                                         // GOTPLT entry for this.
6367      br   x17
6368      PLT0 will be slightly different in ELF32 due to different got entry
6369      size.
6370    */
6371   bfd_vma plt_got_2nd_ent;      /* Address of GOT[2].  */
6372   bfd_vma plt_base;
6373
6374
6375   memcpy (htab->root.splt->contents, elfNN_aarch64_small_plt0_entry,
6376           PLT_ENTRY_SIZE);
6377   elf_section_data (htab->root.splt->output_section)->this_hdr.sh_entsize =
6378     PLT_ENTRY_SIZE;
6379
6380   plt_got_2nd_ent = (htab->root.sgotplt->output_section->vma
6381                   + htab->root.sgotplt->output_offset
6382                   + GOT_ENTRY_SIZE * 2);
6383
6384   plt_base = htab->root.splt->output_section->vma +
6385     htab->root.splt->output_section->output_offset;
6386
6387   /* Fill in the top 21 bits for this: ADRP x16, PLT_GOT + n * 8.
6388      ADRP:   ((PG(S+A)-PG(P)) >> 12) & 0x1fffff */
6389   elf_aarch64_update_plt_entry (output_bfd, BFD_RELOC_AARCH64_ADR_HI21_PCREL,
6390                                 htab->root.splt->contents + 4,
6391                                 PG (plt_got_2nd_ent) - PG (plt_base + 4));
6392
6393   elf_aarch64_update_plt_entry (output_bfd, BFD_RELOC_AARCH64_LDSTNN_LO12,
6394                                 htab->root.splt->contents + 8,
6395                                 PG_OFFSET (plt_got_2nd_ent));
6396
6397   elf_aarch64_update_plt_entry (output_bfd, BFD_RELOC_AARCH64_ADD_LO12,
6398                                 htab->root.splt->contents + 12,
6399                                 PG_OFFSET (plt_got_2nd_ent));
6400 }
6401
6402 static bfd_boolean
6403 elfNN_aarch64_finish_dynamic_sections (bfd *output_bfd,
6404                                        struct bfd_link_info *info)
6405 {
6406   struct elf_aarch64_link_hash_table *htab;
6407   bfd *dynobj;
6408   asection *sdyn;
6409
6410   htab = elf_aarch64_hash_table (info);
6411   dynobj = htab->root.dynobj;
6412   sdyn = bfd_get_linker_section (dynobj, ".dynamic");
6413
6414   if (htab->root.dynamic_sections_created)
6415     {
6416       ElfNN_External_Dyn *dyncon, *dynconend;
6417
6418       if (sdyn == NULL || htab->root.sgot == NULL)
6419         abort ();
6420
6421       dyncon = (ElfNN_External_Dyn *) sdyn->contents;
6422       dynconend = (ElfNN_External_Dyn *) (sdyn->contents + sdyn->size);
6423       for (; dyncon < dynconend; dyncon++)
6424         {
6425           Elf_Internal_Dyn dyn;
6426           asection *s;
6427
6428           bfd_elfNN_swap_dyn_in (dynobj, dyncon, &dyn);
6429
6430           switch (dyn.d_tag)
6431             {
6432             default:
6433               continue;
6434
6435             case DT_PLTGOT:
6436               s = htab->root.sgotplt;
6437               dyn.d_un.d_ptr = s->output_section->vma + s->output_offset;
6438               break;
6439
6440             case DT_JMPREL:
6441               dyn.d_un.d_ptr = htab->root.srelplt->output_section->vma;
6442               break;
6443
6444             case DT_PLTRELSZ:
6445               s = htab->root.srelplt->output_section;
6446               dyn.d_un.d_val = s->size;
6447               break;
6448
6449             case DT_RELASZ:
6450               /* The procedure linkage table relocs (DT_JMPREL) should
6451                  not be included in the overall relocs (DT_RELA).
6452                  Therefore, we override the DT_RELASZ entry here to
6453                  make it not include the JMPREL relocs.  Since the
6454                  linker script arranges for .rela.plt to follow all
6455                  other relocation sections, we don't have to worry
6456                  about changing the DT_RELA entry.  */
6457               if (htab->root.srelplt != NULL)
6458                 {
6459                   s = htab->root.srelplt->output_section;
6460                   dyn.d_un.d_val -= s->size;
6461                 }
6462               break;
6463
6464             case DT_TLSDESC_PLT:
6465               s = htab->root.splt;
6466               dyn.d_un.d_ptr = s->output_section->vma + s->output_offset
6467                 + htab->tlsdesc_plt;
6468               break;
6469
6470             case DT_TLSDESC_GOT:
6471               s = htab->root.sgot;
6472               dyn.d_un.d_ptr = s->output_section->vma + s->output_offset
6473                 + htab->dt_tlsdesc_got;
6474               break;
6475             }
6476
6477           bfd_elfNN_swap_dyn_out (output_bfd, &dyn, dyncon);
6478         }
6479
6480     }
6481
6482   /* Fill in the special first entry in the procedure linkage table.  */
6483   if (htab->root.splt && htab->root.splt->size > 0)
6484     {
6485       elfNN_aarch64_init_small_plt0_entry (output_bfd, htab);
6486
6487       elf_section_data (htab->root.splt->output_section)->
6488         this_hdr.sh_entsize = htab->plt_entry_size;
6489
6490
6491       if (htab->tlsdesc_plt)
6492         {
6493           bfd_put_NN (output_bfd, (bfd_vma) 0,
6494                       htab->root.sgot->contents + htab->dt_tlsdesc_got);
6495
6496           memcpy (htab->root.splt->contents + htab->tlsdesc_plt,
6497                   elfNN_aarch64_tlsdesc_small_plt_entry,
6498                   sizeof (elfNN_aarch64_tlsdesc_small_plt_entry));
6499
6500           {
6501             bfd_vma adrp1_addr =
6502               htab->root.splt->output_section->vma
6503               + htab->root.splt->output_offset + htab->tlsdesc_plt + 4;
6504
6505             bfd_vma adrp2_addr = adrp1_addr + 4;
6506
6507             bfd_vma got_addr =
6508               htab->root.sgot->output_section->vma
6509               + htab->root.sgot->output_offset;
6510
6511             bfd_vma pltgot_addr =
6512               htab->root.sgotplt->output_section->vma
6513               + htab->root.sgotplt->output_offset;
6514
6515             bfd_vma dt_tlsdesc_got = got_addr + htab->dt_tlsdesc_got;
6516
6517             bfd_byte *plt_entry =
6518               htab->root.splt->contents + htab->tlsdesc_plt;
6519
6520             /* adrp x2, DT_TLSDESC_GOT */
6521             elf_aarch64_update_plt_entry (output_bfd,
6522                                           BFD_RELOC_AARCH64_ADR_HI21_PCREL,
6523                                           plt_entry + 4,
6524                                           (PG (dt_tlsdesc_got)
6525                                            - PG (adrp1_addr)));
6526
6527             /* adrp x3, 0 */
6528             elf_aarch64_update_plt_entry (output_bfd,
6529                                           BFD_RELOC_AARCH64_ADR_HI21_PCREL,
6530                                           plt_entry + 8,
6531                                           (PG (pltgot_addr)
6532                                            - PG (adrp2_addr)));
6533
6534             /* ldr x2, [x2, #0] */
6535             elf_aarch64_update_plt_entry (output_bfd,
6536                                           BFD_RELOC_AARCH64_LDSTNN_LO12,
6537                                           plt_entry + 12,
6538                                           PG_OFFSET (dt_tlsdesc_got));
6539
6540             /* add x3, x3, 0 */
6541             elf_aarch64_update_plt_entry (output_bfd,
6542                                           BFD_RELOC_AARCH64_ADD_LO12,
6543                                           plt_entry + 16,
6544                                           PG_OFFSET (pltgot_addr));
6545           }
6546         }
6547     }
6548
6549   if (htab->root.sgotplt)
6550     {
6551       if (bfd_is_abs_section (htab->root.sgotplt->output_section))
6552         {
6553           (*_bfd_error_handler)
6554             (_("discarded output section: `%A'"), htab->root.sgotplt);
6555           return FALSE;
6556         }
6557
6558       /* Fill in the first three entries in the global offset table.  */
6559       if (htab->root.sgotplt->size > 0)
6560         {
6561           bfd_put_NN (output_bfd, (bfd_vma) 0, htab->root.sgotplt->contents);
6562
6563           /* Write GOT[1] and GOT[2], needed for the dynamic linker.  */
6564           bfd_put_NN (output_bfd,
6565                       (bfd_vma) 0,
6566                       htab->root.sgotplt->contents + GOT_ENTRY_SIZE);
6567           bfd_put_NN (output_bfd,
6568                       (bfd_vma) 0,
6569                       htab->root.sgotplt->contents + GOT_ENTRY_SIZE * 2);
6570         }
6571
6572       if (htab->root.sgot)
6573         {
6574           if (htab->root.sgot->size > 0)
6575             {
6576               bfd_vma addr =
6577                 sdyn ? sdyn->output_section->vma + sdyn->output_offset : 0;
6578               bfd_put_NN (output_bfd, addr, htab->root.sgot->contents);
6579             }
6580         }
6581
6582       elf_section_data (htab->root.sgotplt->output_section)->
6583         this_hdr.sh_entsize = GOT_ENTRY_SIZE;
6584     }
6585
6586   if (htab->root.sgot && htab->root.sgot->size > 0)
6587     elf_section_data (htab->root.sgot->output_section)->this_hdr.sh_entsize
6588       = GOT_ENTRY_SIZE;
6589
6590   return TRUE;
6591 }
6592
6593 /* Return address for Ith PLT stub in section PLT, for relocation REL
6594    or (bfd_vma) -1 if it should not be included.  */
6595
6596 static bfd_vma
6597 elfNN_aarch64_plt_sym_val (bfd_vma i, const asection *plt,
6598                            const arelent *rel ATTRIBUTE_UNUSED)
6599 {
6600   return plt->vma + PLT_ENTRY_SIZE + i * PLT_SMALL_ENTRY_SIZE;
6601 }
6602
6603
6604 /* We use this so we can override certain functions
6605    (though currently we don't).  */
6606
6607 const struct elf_size_info elfNN_aarch64_size_info =
6608 {
6609   sizeof (ElfNN_External_Ehdr),
6610   sizeof (ElfNN_External_Phdr),
6611   sizeof (ElfNN_External_Shdr),
6612   sizeof (ElfNN_External_Rel),
6613   sizeof (ElfNN_External_Rela),
6614   sizeof (ElfNN_External_Sym),
6615   sizeof (ElfNN_External_Dyn),
6616   sizeof (Elf_External_Note),
6617   4,                            /* Hash table entry size.  */
6618   1,                            /* Internal relocs per external relocs.  */
6619   ARCH_SIZE,                    /* Arch size.  */
6620   LOG_FILE_ALIGN,               /* Log_file_align.  */
6621   ELFCLASSNN, EV_CURRENT,
6622   bfd_elfNN_write_out_phdrs,
6623   bfd_elfNN_write_shdrs_and_ehdr,
6624   bfd_elfNN_checksum_contents,
6625   bfd_elfNN_write_relocs,
6626   bfd_elfNN_swap_symbol_in,
6627   bfd_elfNN_swap_symbol_out,
6628   bfd_elfNN_slurp_reloc_table,
6629   bfd_elfNN_slurp_symbol_table,
6630   bfd_elfNN_swap_dyn_in,
6631   bfd_elfNN_swap_dyn_out,
6632   bfd_elfNN_swap_reloc_in,
6633   bfd_elfNN_swap_reloc_out,
6634   bfd_elfNN_swap_reloca_in,
6635   bfd_elfNN_swap_reloca_out
6636 };
6637
6638 #define ELF_ARCH                        bfd_arch_aarch64
6639 #define ELF_MACHINE_CODE                EM_AARCH64
6640 #define ELF_MAXPAGESIZE                 0x10000
6641 #define ELF_MINPAGESIZE                 0x1000
6642 #define ELF_COMMONPAGESIZE              0x1000
6643
6644 #define bfd_elfNN_close_and_cleanup             \
6645   elfNN_aarch64_close_and_cleanup
6646
6647 #define bfd_elfNN_bfd_copy_private_bfd_data     \
6648   elfNN_aarch64_copy_private_bfd_data
6649
6650 #define bfd_elfNN_bfd_free_cached_info          \
6651   elfNN_aarch64_bfd_free_cached_info
6652
6653 #define bfd_elfNN_bfd_is_target_special_symbol  \
6654   elfNN_aarch64_is_target_special_symbol
6655
6656 #define bfd_elfNN_bfd_link_hash_table_create    \
6657   elfNN_aarch64_link_hash_table_create
6658
6659 #define bfd_elfNN_bfd_link_hash_table_free      \
6660   elfNN_aarch64_hash_table_free
6661
6662 #define bfd_elfNN_bfd_merge_private_bfd_data    \
6663   elfNN_aarch64_merge_private_bfd_data
6664
6665 #define bfd_elfNN_bfd_print_private_bfd_data    \
6666   elfNN_aarch64_print_private_bfd_data
6667
6668 #define bfd_elfNN_bfd_reloc_type_lookup         \
6669   elfNN_aarch64_reloc_type_lookup
6670
6671 #define bfd_elfNN_bfd_reloc_name_lookup         \
6672   elfNN_aarch64_reloc_name_lookup
6673
6674 #define bfd_elfNN_bfd_set_private_flags         \
6675   elfNN_aarch64_set_private_flags
6676
6677 #define bfd_elfNN_find_inliner_info             \
6678   elfNN_aarch64_find_inliner_info
6679
6680 #define bfd_elfNN_find_nearest_line             \
6681   elfNN_aarch64_find_nearest_line
6682
6683 #define bfd_elfNN_mkobject                      \
6684   elfNN_aarch64_mkobject
6685
6686 #define bfd_elfNN_new_section_hook              \
6687   elfNN_aarch64_new_section_hook
6688
6689 #define elf_backend_adjust_dynamic_symbol       \
6690   elfNN_aarch64_adjust_dynamic_symbol
6691
6692 #define elf_backend_always_size_sections        \
6693   elfNN_aarch64_always_size_sections
6694
6695 #define elf_backend_check_relocs                \
6696   elfNN_aarch64_check_relocs
6697
6698 #define elf_backend_copy_indirect_symbol        \
6699   elfNN_aarch64_copy_indirect_symbol
6700
6701 /* Create .dynbss, and .rela.bss sections in DYNOBJ, and set up shortcuts
6702    to them in our hash.  */
6703 #define elf_backend_create_dynamic_sections     \
6704   elfNN_aarch64_create_dynamic_sections
6705
6706 #define elf_backend_init_index_section          \
6707   _bfd_elf_init_2_index_sections
6708
6709 #define elf_backend_is_function_type            \
6710   elfNN_aarch64_is_function_type
6711
6712 #define elf_backend_finish_dynamic_sections     \
6713   elfNN_aarch64_finish_dynamic_sections
6714
6715 #define elf_backend_finish_dynamic_symbol       \
6716   elfNN_aarch64_finish_dynamic_symbol
6717
6718 #define elf_backend_gc_sweep_hook               \
6719   elfNN_aarch64_gc_sweep_hook
6720
6721 #define elf_backend_object_p                    \
6722   elfNN_aarch64_object_p
6723
6724 #define elf_backend_output_arch_local_syms      \
6725   elfNN_aarch64_output_arch_local_syms
6726
6727 #define elf_backend_plt_sym_val                 \
6728   elfNN_aarch64_plt_sym_val
6729
6730 #define elf_backend_post_process_headers        \
6731   elfNN_aarch64_post_process_headers
6732
6733 #define elf_backend_relocate_section            \
6734   elfNN_aarch64_relocate_section
6735
6736 #define elf_backend_reloc_type_class            \
6737   elfNN_aarch64_reloc_type_class
6738
6739 #define elf_backend_section_flags               \
6740   elfNN_aarch64_section_flags
6741
6742 #define elf_backend_section_from_shdr           \
6743   elfNN_aarch64_section_from_shdr
6744
6745 #define elf_backend_size_dynamic_sections       \
6746   elfNN_aarch64_size_dynamic_sections
6747
6748 #define elf_backend_size_info                   \
6749   elfNN_aarch64_size_info
6750
6751 #define elf_backend_can_refcount       1
6752 #define elf_backend_can_gc_sections    1
6753 #define elf_backend_plt_readonly       1
6754 #define elf_backend_want_got_plt       1
6755 #define elf_backend_want_plt_sym       0
6756 #define elf_backend_may_use_rel_p      0
6757 #define elf_backend_may_use_rela_p     1
6758 #define elf_backend_default_use_rela_p 1
6759 #define elf_backend_got_header_size (GOT_ENTRY_SIZE * 3)
6760 #define elf_backend_default_execstack  0
6761
6762 #undef  elf_backend_obj_attrs_section
6763 #define elf_backend_obj_attrs_section           ".ARM.attributes"
6764
6765 #include "elfNN-target.h"