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