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