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