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