Support AARCH64_TLSLD_ADD_DTPREL_* relocations.
[external/binutils.git] / gold / aarch64.cc
1 // aarch64.cc -- aarch64 target support for gold.
2
3 // Copyright (C) 2014-2015 Free Software Foundation, Inc.
4 // Written by Jing Yu <jingyu@google.com> and Han Shen <shenhan@google.com>.
5
6 // This file is part of gold.
7
8 // This program is free software; you can redistribute it and/or modify
9 // it under the terms of the GNU General Public License as published by
10 // the Free Software Foundation; either version 3 of the License, or
11 // (at your option) any later version.
12
13 // This program is distributed in the hope that it will be useful,
14 // but WITHOUT ANY WARRANTY; without even the implied warranty of
15 // MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16 // GNU General Public License for more details.
17
18 // You should have received a copy of the GNU General Public License
19 // along with this program; if not, write to the Free Software
20 // Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
21 // MA 02110-1301, USA.
22
23 #include "gold.h"
24
25 #include <cstring>
26
27 #include "elfcpp.h"
28 #include "dwarf.h"
29 #include "parameters.h"
30 #include "reloc.h"
31 #include "aarch64.h"
32 #include "object.h"
33 #include "symtab.h"
34 #include "layout.h"
35 #include "output.h"
36 #include "copy-relocs.h"
37 #include "target.h"
38 #include "target-reloc.h"
39 #include "target-select.h"
40 #include "tls.h"
41 #include "freebsd.h"
42 #include "nacl.h"
43 #include "gc.h"
44 #include "icf.h"
45 #include "aarch64-reloc-property.h"
46
47 // The first three .got.plt entries are reserved.
48 const int32_t AARCH64_GOTPLT_RESERVE_COUNT = 3;
49
50
51 namespace
52 {
53
54 using namespace gold;
55
56 template<int size, bool big_endian>
57 class Output_data_plt_aarch64;
58
59 template<int size, bool big_endian>
60 class Output_data_plt_aarch64_standard;
61
62 template<int size, bool big_endian>
63 class Target_aarch64;
64
65 template<int size, bool big_endian>
66 class AArch64_relocate_functions;
67
68 // Output_data_got_aarch64 class.
69
70 template<int size, bool big_endian>
71 class Output_data_got_aarch64 : public Output_data_got<size, big_endian>
72 {
73  public:
74   typedef typename elfcpp::Elf_types<size>::Elf_Addr Valtype;
75   Output_data_got_aarch64(Symbol_table* symtab, Layout* layout)
76     : Output_data_got<size, big_endian>(),
77       symbol_table_(symtab), layout_(layout)
78   { }
79
80   // Add a static entry for the GOT entry at OFFSET.  GSYM is a global
81   // symbol and R_TYPE is the code of a dynamic relocation that needs to be
82   // applied in a static link.
83   void
84   add_static_reloc(unsigned int got_offset, unsigned int r_type, Symbol* gsym)
85   { this->static_relocs_.push_back(Static_reloc(got_offset, r_type, gsym)); }
86
87
88   // Add a static reloc for the GOT entry at OFFSET.  RELOBJ is an object
89   // defining a local symbol with INDEX.  R_TYPE is the code of a dynamic
90   // relocation that needs to be applied in a static link.
91   void
92   add_static_reloc(unsigned int got_offset, unsigned int r_type,
93                    Sized_relobj_file<size, big_endian>* relobj,
94                    unsigned int index)
95   {
96     this->static_relocs_.push_back(Static_reloc(got_offset, r_type, relobj,
97                                                 index));
98   }
99
100
101  protected:
102   // Write out the GOT table.
103   void
104   do_write(Output_file* of) {
105     // The first entry in the GOT is the address of the .dynamic section.
106     gold_assert(this->data_size() >= size / 8);
107     Output_section* dynamic = this->layout_->dynamic_section();
108     Valtype dynamic_addr = dynamic == NULL ? 0 : dynamic->address();
109     this->replace_constant(0, dynamic_addr);
110     Output_data_got<size, big_endian>::do_write(of);
111
112     // Handling static relocs
113     if (this->static_relocs_.empty())
114       return;
115
116     typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
117
118     gold_assert(parameters->doing_static_link());
119     const off_t offset = this->offset();
120     const section_size_type oview_size =
121       convert_to_section_size_type(this->data_size());
122     unsigned char* const oview = of->get_output_view(offset, oview_size);
123
124     Output_segment* tls_segment = this->layout_->tls_segment();
125     gold_assert(tls_segment != NULL);
126
127     AArch64_address aligned_tcb_address =
128       align_address(Target_aarch64<size, big_endian>::TCB_SIZE,
129                     tls_segment->maximum_alignment());
130
131     for (size_t i = 0; i < this->static_relocs_.size(); ++i)
132       {
133         Static_reloc& reloc(this->static_relocs_[i]);
134         AArch64_address value;
135
136         if (!reloc.symbol_is_global())
137           {
138             Sized_relobj_file<size, big_endian>* object = reloc.relobj();
139             const Symbol_value<size>* psymval =
140               reloc.relobj()->local_symbol(reloc.index());
141
142             // We are doing static linking.  Issue an error and skip this
143             // relocation if the symbol is undefined or in a discarded_section.
144             bool is_ordinary;
145             unsigned int shndx = psymval->input_shndx(&is_ordinary);
146             if ((shndx == elfcpp::SHN_UNDEF)
147                 || (is_ordinary
148                     && shndx != elfcpp::SHN_UNDEF
149                     && !object->is_section_included(shndx)
150                     && !this->symbol_table_->is_section_folded(object, shndx)))
151               {
152                 gold_error(_("undefined or discarded local symbol %u from "
153                              " object %s in GOT"),
154                            reloc.index(), reloc.relobj()->name().c_str());
155                 continue;
156               }
157             value = psymval->value(object, 0);
158           }
159         else
160           {
161             const Symbol* gsym = reloc.symbol();
162             gold_assert(gsym != NULL);
163             if (gsym->is_forwarder())
164               gsym = this->symbol_table_->resolve_forwards(gsym);
165
166             // We are doing static linking.  Issue an error and skip this
167             // relocation if the symbol is undefined or in a discarded_section
168             // unless it is a weakly_undefined symbol.
169             if ((gsym->is_defined_in_discarded_section()
170                  || gsym->is_undefined())
171                 && !gsym->is_weak_undefined())
172               {
173                 gold_error(_("undefined or discarded symbol %s in GOT"),
174                            gsym->name());
175                 continue;
176               }
177
178             if (!gsym->is_weak_undefined())
179               {
180                 const Sized_symbol<size>* sym =
181                   static_cast<const Sized_symbol<size>*>(gsym);
182                 value = sym->value();
183               }
184             else
185               value = 0;
186           }
187
188         unsigned got_offset = reloc.got_offset();
189         gold_assert(got_offset < oview_size);
190
191         typedef typename elfcpp::Swap<size, big_endian>::Valtype Valtype;
192         Valtype* wv = reinterpret_cast<Valtype*>(oview + got_offset);
193         Valtype x;
194         switch (reloc.r_type())
195           {
196           case elfcpp::R_AARCH64_TLS_DTPREL64:
197             x = value;
198             break;
199           case elfcpp::R_AARCH64_TLS_TPREL64:
200             x = value + aligned_tcb_address;
201             break;
202           default:
203             gold_unreachable();
204           }
205         elfcpp::Swap<size, big_endian>::writeval(wv, x);
206       }
207
208     of->write_output_view(offset, oview_size, oview);
209   }
210
211  private:
212   // Symbol table of the output object.
213   Symbol_table* symbol_table_;
214   // A pointer to the Layout class, so that we can find the .dynamic
215   // section when we write out the GOT section.
216   Layout* layout_;
217
218   // This class represent dynamic relocations that need to be applied by
219   // gold because we are using TLS relocations in a static link.
220   class Static_reloc
221   {
222    public:
223     Static_reloc(unsigned int got_offset, unsigned int r_type, Symbol* gsym)
224       : got_offset_(got_offset), r_type_(r_type), symbol_is_global_(true)
225     { this->u_.global.symbol = gsym; }
226
227     Static_reloc(unsigned int got_offset, unsigned int r_type,
228           Sized_relobj_file<size, big_endian>* relobj, unsigned int index)
229       : got_offset_(got_offset), r_type_(r_type), symbol_is_global_(false)
230     {
231       this->u_.local.relobj = relobj;
232       this->u_.local.index = index;
233     }
234
235     // Return the GOT offset.
236     unsigned int
237     got_offset() const
238     { return this->got_offset_; }
239
240     // Relocation type.
241     unsigned int
242     r_type() const
243     { return this->r_type_; }
244
245     // Whether the symbol is global or not.
246     bool
247     symbol_is_global() const
248     { return this->symbol_is_global_; }
249
250     // For a relocation against a global symbol, the global symbol.
251     Symbol*
252     symbol() const
253     {
254       gold_assert(this->symbol_is_global_);
255       return this->u_.global.symbol;
256     }
257
258     // For a relocation against a local symbol, the defining object.
259     Sized_relobj_file<size, big_endian>*
260     relobj() const
261     {
262       gold_assert(!this->symbol_is_global_);
263       return this->u_.local.relobj;
264     }
265
266     // For a relocation against a local symbol, the local symbol index.
267     unsigned int
268     index() const
269     {
270       gold_assert(!this->symbol_is_global_);
271       return this->u_.local.index;
272     }
273
274    private:
275     // GOT offset of the entry to which this relocation is applied.
276     unsigned int got_offset_;
277     // Type of relocation.
278     unsigned int r_type_;
279     // Whether this relocation is against a global symbol.
280     bool symbol_is_global_;
281     // A global or local symbol.
282     union
283     {
284       struct
285       {
286         // For a global symbol, the symbol itself.
287         Symbol* symbol;
288       } global;
289       struct
290       {
291         // For a local symbol, the object defining the symbol.
292         Sized_relobj_file<size, big_endian>* relobj;
293         // For a local symbol, the symbol index.
294         unsigned int index;
295       } local;
296     } u_;
297   };  // End of inner class Static_reloc
298
299   std::vector<Static_reloc> static_relocs_;
300 };  // End of Output_data_got_aarch64
301
302
303 template<int size, bool big_endian>
304 class AArch64_input_section;
305
306
307 template<int size, bool big_endian>
308 class AArch64_output_section;
309
310
311 // Reloc stub class.
312
313 template<int size, bool big_endian>
314 class Reloc_stub
315 {
316  public:
317   typedef Reloc_stub<size, big_endian> This;
318   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
319
320   // Do not change the value of the enums, they are used to index into
321   // stub_insns array.
322   typedef enum
323   {
324     ST_NONE = 0,
325
326     // Using adrp/add pair, 4 insns (including alignment) without mem access,
327     // the fastest stub. This has a limited jump distance, which is tested by
328     // aarch64_valid_for_adrp_p.
329     ST_ADRP_BRANCH = 1,
330
331     // Using ldr-absolute-address/br-register, 4 insns with 1 mem access,
332     // unlimited in jump distance.
333     ST_LONG_BRANCH_ABS = 2,
334
335     // Using ldr/calculate-pcrel/jump, 8 insns (including alignment) with 1 mem
336     // access, slowest one. Only used in position independent executables.
337     ST_LONG_BRANCH_PCREL = 3,
338
339   } Stub_type;
340
341   // Branch range. This is used to calculate the section group size, as well as
342   // determine whether a stub is needed.
343   static const int MAX_BRANCH_OFFSET = ((1 << 25) - 1) << 2;
344   static const int MIN_BRANCH_OFFSET = -((1 << 25) << 2);
345
346   // Constant used to determine if an offset fits in the adrp instruction
347   // encoding.
348   static const int MAX_ADRP_IMM = (1 << 20) - 1;
349   static const int MIN_ADRP_IMM = -(1 << 20);
350
351   static const int BYTES_PER_INSN = 4;
352   static const int STUB_ADDR_ALIGN = 4;
353
354   // Determine whether the offset fits in the jump/branch instruction.
355   static bool
356   aarch64_valid_branch_offset_p(int64_t offset)
357   { return offset >= MIN_BRANCH_OFFSET && offset <= MAX_BRANCH_OFFSET; }
358
359   // Determine whether the offset fits in the adrp immediate field.
360   static bool
361   aarch64_valid_for_adrp_p(AArch64_address location, AArch64_address dest)
362   {
363     typedef AArch64_relocate_functions<size, big_endian> Reloc;
364     int64_t adrp_imm = (Reloc::Page(dest) - Reloc::Page(location)) >> 12;
365     return adrp_imm >= MIN_ADRP_IMM && adrp_imm <= MAX_ADRP_IMM;
366   }
367
368   // Determine the stub type for a certain relocation or ST_NONE, if no stub is
369   // needed.
370   static Stub_type
371   stub_type_for_reloc(unsigned int r_type, AArch64_address address,
372                       AArch64_address target);
373
374   Reloc_stub(Stub_type stub_type)
375     : stub_type_(stub_type), offset_(invalid_offset),
376       destination_address_(invalid_address)
377   { }
378
379   ~Reloc_stub()
380   { }
381
382   // Return offset of code stub from beginning of its containing stub table.
383   section_offset_type
384   offset() const
385   {
386     gold_assert(this->offset_ != invalid_offset);
387     return this->offset_;
388   }
389
390   // Set offset of code stub from beginning of its containing stub table.
391   void
392   set_offset(section_offset_type offset)
393   { this->offset_ = offset; }
394
395   // Return destination address.
396   AArch64_address
397   destination_address() const
398   {
399     gold_assert(this->destination_address_ != this->invalid_address);
400     return this->destination_address_;
401   }
402
403   // Set destination address.
404   void
405   set_destination_address(AArch64_address address)
406   {
407     gold_assert(address != this->invalid_address);
408     this->destination_address_ = address;
409   }
410
411   // Reset the destination address.
412   void
413   reset_destination_address()
414   { this->destination_address_ = this->invalid_address; }
415
416   // Return the stub type.
417   Stub_type
418   stub_type() const
419   { return stub_type_; }
420
421   // Return the stub size.
422   uint32_t
423   stub_size() const
424   { return this->stub_insn_number() * BYTES_PER_INSN; }
425
426   // Return the instruction number of this stub instance.
427   int
428   stub_insn_number() const
429   { return stub_insns_[this->stub_type_][0]; }
430
431   // Note the first "insn" is the number of total insns in this array.
432   const uint32_t*
433   stub_insns() const
434   { return stub_insns_[this->stub_type_]; }
435
436   // Write stub to output file.
437   void
438   write(unsigned char* view, section_size_type view_size)
439   { this->do_write(view, view_size); }
440
441   // The key class used to index the stub instance in the stub table's stub map.
442   class Key
443   {
444    public:
445     Key(Stub_type stub_type, const Symbol* symbol, const Relobj* relobj,
446         unsigned int r_sym, int32_t addend)
447       : stub_type_(stub_type), addend_(addend)
448     {
449       if (symbol != NULL)
450         {
451           this->r_sym_ = Reloc_stub::invalid_index;
452           this->u_.symbol = symbol;
453         }
454       else
455         {
456           gold_assert(relobj != NULL && r_sym != invalid_index);
457           this->r_sym_ = r_sym;
458           this->u_.relobj = relobj;
459         }
460     }
461
462     ~Key()
463     { }
464
465     // Return stub type.
466     Stub_type
467     stub_type() const
468     { return this->stub_type_; }
469
470     // Return the local symbol index or invalid_index.
471     unsigned int
472     r_sym() const
473     { return this->r_sym_; }
474
475     // Return the symbol if there is one.
476     const Symbol*
477     symbol() const
478     { return this->r_sym_ == invalid_index ? this->u_.symbol : NULL; }
479
480     // Return the relobj if there is one.
481     const Relobj*
482     relobj() const
483     { return this->r_sym_ != invalid_index ? this->u_.relobj : NULL; }
484
485     // Whether this equals to another key k.
486     bool
487     eq(const Key& k) const
488     {
489       return ((this->stub_type_ == k.stub_type_)
490               && (this->r_sym_ == k.r_sym_)
491               && ((this->r_sym_ != Reloc_stub::invalid_index)
492                   ? (this->u_.relobj == k.u_.relobj)
493                   : (this->u_.symbol == k.u_.symbol))
494               && (this->addend_ == k.addend_));
495     }
496
497     // Return a hash value.
498     size_t
499     hash_value() const
500     {
501       size_t name_hash_value = gold::string_hash<char>(
502           (this->r_sym_ != Reloc_stub::invalid_index)
503           ? this->u_.relobj->name().c_str()
504           : this->u_.symbol->name());
505       // We only have 4 stub types.
506       size_t stub_type_hash_value = 0x03 & this->stub_type_;
507       return (name_hash_value
508               ^ stub_type_hash_value
509               ^ ((this->r_sym_ & 0x3fff) << 2)
510               ^ ((this->addend_ & 0xffff) << 16));
511     }
512
513     // Functors for STL associative containers.
514     struct hash
515     {
516       size_t
517       operator()(const Key& k) const
518       { return k.hash_value(); }
519     };
520
521     struct equal_to
522     {
523       bool
524       operator()(const Key& k1, const Key& k2) const
525       { return k1.eq(k2); }
526     };
527
528    private:
529     // Stub type.
530     const Stub_type stub_type_;
531     // If this is a local symbol, this is the index in the defining object.
532     // Otherwise, it is invalid_index for a global symbol.
533     unsigned int r_sym_;
534     // If r_sym_ is an invalid index, this points to a global symbol.
535     // Otherwise, it points to a relobj.  We used the unsized and target
536     // independent Symbol and Relobj classes instead of Sized_symbol<32> and
537     // Arm_relobj, in order to avoid making the stub class a template
538     // as most of the stub machinery is endianness-neutral.  However, it
539     // may require a bit of casting done by users of this class.
540     union
541     {
542       const Symbol* symbol;
543       const Relobj* relobj;
544     } u_;
545     // Addend associated with a reloc.
546     int32_t addend_;
547   };  // End of inner class Reloc_stub::Key
548
549  protected:
550   // This may be overridden in the child class.
551   virtual void
552   do_write(unsigned char*, section_size_type);
553
554  private:
555   static const section_offset_type invalid_offset =
556       static_cast<section_offset_type>(-1);
557   static const unsigned int invalid_index = static_cast<unsigned int>(-1);
558   static const AArch64_address invalid_address =
559       static_cast<AArch64_address>(-1);
560
561   static const uint32_t stub_insns_[][10];
562
563   const Stub_type stub_type_;
564   section_offset_type offset_;
565   AArch64_address destination_address_;
566 };  // End of Reloc_stub
567
568
569 // Write data to output file.
570
571 template<int size, bool big_endian>
572 void
573 Reloc_stub<size, big_endian>::
574 do_write(unsigned char* view, section_size_type)
575 {
576   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
577   const uint32_t* insns = this->stub_insns();
578   uint32_t num_insns = this->stub_insn_number();
579   Insntype* ip = reinterpret_cast<Insntype*>(view);
580   for (uint32_t i = 1; i <= num_insns; ++i)
581     elfcpp::Swap<32, big_endian>::writeval(ip + i - 1, insns[i]);
582 }
583
584
585 // Stubs instructions definition.
586
587 template<int size, bool big_endian>
588 const uint32_t
589 Reloc_stub<size, big_endian>::stub_insns_[][10] =
590   {
591     // The first element of each group is the num of the insns.
592
593     // ST_NONE
594     {0, 0},
595
596     // ST_ADRP_BRANCH
597     {
598         4,
599         0x90000010,     /*      adrp    ip0, X             */
600                         /*        ADR_PREL_PG_HI21(X)      */
601         0x91000210,     /*      add     ip0, ip0, :lo12:X  */
602                         /*        ADD_ABS_LO12_NC(X)       */
603         0xd61f0200,     /*      br      ip0                */
604         0x00000000,     /*      alignment padding          */
605     },
606
607     // ST_LONG_BRANCH_ABS
608     {
609         4,
610         0x58000050,     /*      ldr   ip0, 0x8             */
611         0xd61f0200,     /*      br    ip0                  */
612         0x00000000,     /*      address field              */
613         0x00000000,     /*      address fields             */
614     },
615
616     // ST_LONG_BRANCH_PCREL
617     {
618       8,
619         0x58000090,     /*      ldr   ip0, 0x10            */
620         0x10000011,     /*      adr   ip1, #0              */
621         0x8b110210,     /*      add   ip0, ip0, ip1        */
622         0xd61f0200,     /*      br    ip0                  */
623         0x00000000,     /*      address field              */
624         0x00000000,     /*      address field              */
625         0x00000000,     /*      alignment padding          */
626         0x00000000,     /*      alignment padding          */
627     }
628   };
629
630
631 // Determine the stub type for a certain relocation or ST_NONE, if no stub is
632 // needed.
633
634 template<int size, bool big_endian>
635 inline
636 typename Reloc_stub<size, big_endian>::Stub_type
637 Reloc_stub<size, big_endian>::stub_type_for_reloc(
638     unsigned int r_type, AArch64_address location, AArch64_address dest)
639 {
640   int64_t branch_offset = 0;
641   switch(r_type)
642     {
643     case elfcpp::R_AARCH64_CALL26:
644     case elfcpp::R_AARCH64_JUMP26:
645       branch_offset = dest - location;
646       break;
647     default:
648       gold_unreachable();
649     }
650
651   if (aarch64_valid_branch_offset_p(branch_offset))
652     return ST_NONE;
653
654   if (aarch64_valid_for_adrp_p(location, dest))
655     return ST_ADRP_BRANCH;
656
657   if (parameters->options().output_is_position_independent()
658       && parameters->options().output_is_executable())
659     return ST_LONG_BRANCH_PCREL;
660
661   return ST_LONG_BRANCH_ABS;
662 }
663
664 // A class to hold stubs for the ARM target.
665
666 template<int size, bool big_endian>
667 class Stub_table : public Output_data
668 {
669  public:
670   typedef Target_aarch64<size, big_endian> The_target_aarch64;
671   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
672   typedef AArch64_input_section<size, big_endian> The_aarch64_input_section;
673   typedef Reloc_stub<size, big_endian> The_reloc_stub;
674   typedef typename The_reloc_stub::Key The_reloc_stub_key;
675   typedef typename The_reloc_stub_key::hash The_reloc_stub_key_hash;
676   typedef typename The_reloc_stub_key::equal_to The_reloc_stub_key_equal_to;
677   typedef Stub_table<size, big_endian> The_stub_table;
678   typedef Unordered_map<The_reloc_stub_key, The_reloc_stub*,
679                         The_reloc_stub_key_hash, The_reloc_stub_key_equal_to>
680                         Reloc_stub_map;
681   typedef typename Reloc_stub_map::const_iterator Reloc_stub_map_const_iter;
682   typedef Relocate_info<size, big_endian> The_relocate_info;
683
684   Stub_table(The_aarch64_input_section* owner)
685     : Output_data(), owner_(owner), reloc_stubs_size_(0), prev_data_size_(0)
686   { }
687
688   ~Stub_table()
689   { }
690
691   The_aarch64_input_section*
692   owner() const
693   { return owner_; }
694
695   // Whether this stub table is empty.
696   bool
697   empty() const
698   { return reloc_stubs_.empty(); }
699
700   // Return the current data size.
701   off_t
702   current_data_size() const
703   { return this->current_data_size_for_child(); }
704
705   // Add a STUB using KEY.  The caller is responsible for avoiding addition
706   // if a STUB with the same key has already been added.
707   void
708   add_reloc_stub(The_reloc_stub* stub, const The_reloc_stub_key& key);
709
710   // Finalize stubs. No-op here, just for completeness.
711   void
712   finalize_stubs()
713   { }
714
715   // Look up a relocation stub using KEY. Return NULL if there is none.
716   The_reloc_stub*
717   find_reloc_stub(The_reloc_stub_key& key)
718   {
719     Reloc_stub_map_const_iter p = this->reloc_stubs_.find(key);
720     return (p != this->reloc_stubs_.end()) ? p->second : NULL;
721   }
722
723   // Relocate stubs in this stub table.
724   void
725   relocate_stubs(const The_relocate_info*,
726                  The_target_aarch64*,
727                  Output_section*,
728                  unsigned char*,
729                  AArch64_address,
730                  section_size_type);
731
732   // Update data size at the end of a relaxation pass.  Return true if data size
733   // is different from that of the previous relaxation pass.
734   bool
735   update_data_size_changed_p()
736   {
737     // No addralign changed here.
738     off_t s = this->reloc_stubs_size_;
739     bool changed = (s != this->prev_data_size_);
740     this->prev_data_size_ = s;
741     return changed;
742   }
743
744  protected:
745   // Write out section contents.
746   void
747   do_write(Output_file*);
748
749   // Return the required alignment.
750   uint64_t
751   do_addralign() const
752   { return The_reloc_stub::STUB_ADDR_ALIGN; }
753
754   // Reset address and file offset.
755   void
756   do_reset_address_and_file_offset()
757   { this->set_current_data_size_for_child(this->prev_data_size_); }
758
759   // Set final data size.
760   void
761   set_final_data_size()
762   { this->set_data_size(this->current_data_size()); }
763
764  private:
765   // Relocate one stub.
766   void
767   relocate_stub(The_reloc_stub*,
768                 const The_relocate_info*,
769                 The_target_aarch64*,
770                 Output_section*,
771                 unsigned char*,
772                 AArch64_address,
773                 section_size_type);
774
775  private:
776   // Owner of this stub table.
777   The_aarch64_input_section* owner_;
778   // The relocation stubs.
779   Reloc_stub_map reloc_stubs_;
780   // Size of reloc stubs.
781   off_t reloc_stubs_size_;
782   // data size of this in the previous pass.
783   off_t prev_data_size_;
784 };  // End of Stub_table
785
786
787 // Add a STUB using KEY.  The caller is responsible for avoiding addition
788 // if a STUB with the same key has already been added.
789
790 template<int size, bool big_endian>
791 void
792 Stub_table<size, big_endian>::add_reloc_stub(
793     The_reloc_stub* stub, const The_reloc_stub_key& key)
794 {
795   gold_assert(stub->stub_type() == key.stub_type());
796   this->reloc_stubs_[key] = stub;
797
798   // Assign stub offset early.  We can do this because we never remove
799   // reloc stubs and they are in the beginning of the stub table.
800   this->reloc_stubs_size_ = align_address(this->reloc_stubs_size_,
801                                           The_reloc_stub::STUB_ADDR_ALIGN);
802   stub->set_offset(this->reloc_stubs_size_);
803   this->reloc_stubs_size_ += stub->stub_size();
804 }
805
806
807 // Relocate all stubs in this stub table.
808
809 template<int size, bool big_endian>
810 void
811 Stub_table<size, big_endian>::
812 relocate_stubs(const The_relocate_info* relinfo,
813                The_target_aarch64* target_aarch64,
814                Output_section* output_section,
815                unsigned char* view,
816                AArch64_address address,
817                section_size_type view_size)
818 {
819   // "view_size" is the total size of the stub_table.
820   gold_assert(address == this->address() &&
821               view_size == static_cast<section_size_type>(this->data_size()));
822   for(Reloc_stub_map_const_iter p = this->reloc_stubs_.begin();
823       p != this->reloc_stubs_.end(); ++p)
824     relocate_stub(p->second, relinfo, target_aarch64, output_section,
825                   view, address, view_size);
826 }
827
828
829 // Relocate one stub.  This is a helper for Stub_table::relocate_stubs().
830
831 template<int size, bool big_endian>
832 void
833 Stub_table<size, big_endian>::
834 relocate_stub(The_reloc_stub* stub,
835               const The_relocate_info* relinfo,
836               The_target_aarch64* target_aarch64,
837               Output_section* output_section,
838               unsigned char* view,
839               AArch64_address address,
840               section_size_type view_size)
841 {
842   // "offset" is the offset from the beginning of the stub_table.
843   section_size_type offset = stub->offset();
844   section_size_type stub_size = stub->stub_size();
845   // "view_size" is the total size of the stub_table.
846   gold_assert(offset + stub_size <= view_size);
847
848   target_aarch64->relocate_stub(stub, relinfo, output_section,
849                                 view + offset, address + offset, view_size);
850 }
851
852
853 // Write out the stubs to file.
854
855 template<int size, bool big_endian>
856 void
857 Stub_table<size, big_endian>::do_write(Output_file* of)
858 {
859   off_t offset = this->offset();
860   const section_size_type oview_size =
861     convert_to_section_size_type(this->data_size());
862   unsigned char* const oview = of->get_output_view(offset, oview_size);
863
864   // Write relocation stubs.
865   for (typename Reloc_stub_map::const_iterator p = this->reloc_stubs_.begin();
866       p != this->reloc_stubs_.end(); ++p)
867     {
868       The_reloc_stub* stub = p->second;
869       AArch64_address address = this->address() + stub->offset();
870       gold_assert(address ==
871                   align_address(address, The_reloc_stub::STUB_ADDR_ALIGN));
872       stub->write(oview + stub->offset(), stub->stub_size());
873     }
874
875   of->write_output_view(this->offset(), oview_size, oview);
876 }
877
878
879 // AArch64_relobj class.
880
881 template<int size, bool big_endian>
882 class AArch64_relobj : public Sized_relobj_file<size, big_endian>
883 {
884  public:
885   typedef AArch64_relobj<size, big_endian> This;
886   typedef Target_aarch64<size, big_endian> The_target_aarch64;
887   typedef AArch64_input_section<size, big_endian> The_aarch64_input_section;
888   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
889   typedef Stub_table<size, big_endian> The_stub_table;
890   typedef std::vector<The_stub_table*> Stub_table_list;
891   static const AArch64_address invalid_address =
892       static_cast<AArch64_address>(-1);
893
894   AArch64_relobj(const std::string& name, Input_file* input_file, off_t offset,
895                  const typename elfcpp::Ehdr<size, big_endian>& ehdr)
896     : Sized_relobj_file<size, big_endian>(name, input_file, offset, ehdr),
897       stub_tables_()
898   { }
899
900   ~AArch64_relobj()
901   { }
902
903   // Return the stub table of the SHNDX-th section if there is one.
904   The_stub_table*
905   stub_table(unsigned int shndx) const
906   {
907     gold_assert(shndx < this->stub_tables_.size());
908     return this->stub_tables_[shndx];
909   }
910
911   // Set STUB_TABLE to be the stub_table of the SHNDX-th section.
912   void
913   set_stub_table(unsigned int shndx, The_stub_table* stub_table)
914   {
915     gold_assert(shndx < this->stub_tables_.size());
916     this->stub_tables_[shndx] = stub_table;
917   }
918
919  // Scan all relocation sections for stub generation.
920   void
921   scan_sections_for_stubs(The_target_aarch64*, const Symbol_table*,
922                           const Layout*);
923
924   // Whether a section is a scannable text section.
925   bool
926   text_section_is_scannable(const elfcpp::Shdr<size, big_endian>&, unsigned int,
927                             const Output_section*, const Symbol_table*);
928
929   // Convert regular input section with index SHNDX to a relaxed section.
930   void
931   convert_input_section_to_relaxed_section(unsigned /* shndx */)
932   {
933     // The stubs have relocations and we need to process them after writing
934     // out the stubs.  So relocation now must follow section write.
935     this->set_relocs_must_follow_section_writes();
936   }
937
938  protected:
939   // Post constructor setup.
940   void
941   do_setup()
942   {
943     // Call parent's setup method.
944     Sized_relobj_file<size, big_endian>::do_setup();
945
946     // Initialize look-up tables.
947     this->stub_tables_.resize(this->shnum());
948   }
949
950   virtual void
951   do_relocate_sections(
952       const Symbol_table* symtab, const Layout* layout,
953       const unsigned char* pshdrs, Output_file* of,
954       typename Sized_relobj_file<size, big_endian>::Views* pviews);
955
956  private:
957   // Whether a section needs to be scanned for relocation stubs.
958   bool
959   section_needs_reloc_stub_scanning(const elfcpp::Shdr<size, big_endian>&,
960                                     const Relobj::Output_sections&,
961                                     const Symbol_table*, const unsigned char*);
962
963   // List of stub tables.
964   Stub_table_list stub_tables_;
965 };  // End of AArch64_relobj
966
967
968 // Relocate sections.
969
970 template<int size, bool big_endian>
971 void
972 AArch64_relobj<size, big_endian>::do_relocate_sections(
973     const Symbol_table* symtab, const Layout* layout,
974     const unsigned char* pshdrs, Output_file* of,
975     typename Sized_relobj_file<size, big_endian>::Views* pviews)
976 {
977   // Call parent to relocate sections.
978   Sized_relobj_file<size, big_endian>::do_relocate_sections(symtab, layout,
979                                                             pshdrs, of, pviews);
980
981   // We do not generate stubs if doing a relocatable link.
982   if (parameters->options().relocatable())
983     return;
984
985   Relocate_info<size, big_endian> relinfo;
986   relinfo.symtab = symtab;
987   relinfo.layout = layout;
988   relinfo.object = this;
989
990   // Relocate stub tables.
991   unsigned int shnum = this->shnum();
992   The_target_aarch64* target = The_target_aarch64::current_target();
993
994   for (unsigned int i = 1; i < shnum; ++i)
995     {
996       The_aarch64_input_section* aarch64_input_section =
997           target->find_aarch64_input_section(this, i);
998       if (aarch64_input_section != NULL
999           && aarch64_input_section->is_stub_table_owner()
1000           && !aarch64_input_section->stub_table()->empty())
1001         {
1002           Output_section* os = this->output_section(i);
1003           gold_assert(os != NULL);
1004
1005           relinfo.reloc_shndx = elfcpp::SHN_UNDEF;
1006           relinfo.reloc_shdr = NULL;
1007           relinfo.data_shndx = i;
1008           relinfo.data_shdr = pshdrs + i * elfcpp::Elf_sizes<size>::shdr_size;
1009
1010           typename Sized_relobj_file<size, big_endian>::View_size&
1011               view_struct = (*pviews)[i];
1012           gold_assert(view_struct.view != NULL);
1013
1014           The_stub_table* stub_table = aarch64_input_section->stub_table();
1015           off_t offset = stub_table->address() - view_struct.address;
1016           unsigned char* view = view_struct.view + offset;
1017           AArch64_address address = stub_table->address();
1018           section_size_type view_size = stub_table->data_size();
1019           stub_table->relocate_stubs(&relinfo, target, os, view, address,
1020                                      view_size);
1021         }
1022     }
1023 }
1024
1025
1026 // Determine if an input section is scannable for stub processing.  SHDR is
1027 // the header of the section and SHNDX is the section index.  OS is the output
1028 // section for the input section and SYMTAB is the global symbol table used to
1029 // look up ICF information.
1030
1031 template<int size, bool big_endian>
1032 bool
1033 AArch64_relobj<size, big_endian>::text_section_is_scannable(
1034     const elfcpp::Shdr<size, big_endian>& text_shdr,
1035     unsigned int text_shndx,
1036     const Output_section* os,
1037     const Symbol_table* symtab)
1038 {
1039   // Skip any empty sections, unallocated sections or sections whose
1040   // type are not SHT_PROGBITS.
1041   if (text_shdr.get_sh_size() == 0
1042       || (text_shdr.get_sh_flags() & elfcpp::SHF_ALLOC) == 0
1043       || text_shdr.get_sh_type() != elfcpp::SHT_PROGBITS)
1044     return false;
1045
1046   // Skip any discarded or ICF'ed sections.
1047   if (os == NULL || symtab->is_section_folded(this, text_shndx))
1048     return false;
1049
1050   // Skip exception frame.
1051   if (strcmp(os->name(), ".eh_frame") == 0)
1052     return false ;
1053
1054   gold_assert(!this->is_output_section_offset_invalid(text_shndx) ||
1055               os->find_relaxed_input_section(this, text_shndx) != NULL);
1056
1057   return true;
1058 }
1059
1060
1061 // Determine if we want to scan the SHNDX-th section for relocation stubs.
1062 // This is a helper for AArch64_relobj::scan_sections_for_stubs().
1063
1064 template<int size, bool big_endian>
1065 bool
1066 AArch64_relobj<size, big_endian>::section_needs_reloc_stub_scanning(
1067     const elfcpp::Shdr<size, big_endian>& shdr,
1068     const Relobj::Output_sections& out_sections,
1069     const Symbol_table* symtab,
1070     const unsigned char* pshdrs)
1071 {
1072   unsigned int sh_type = shdr.get_sh_type();
1073   if (sh_type != elfcpp::SHT_RELA)
1074     return false;
1075
1076   // Ignore empty section.
1077   off_t sh_size = shdr.get_sh_size();
1078   if (sh_size == 0)
1079     return false;
1080
1081   // Ignore reloc section with unexpected symbol table.  The
1082   // error will be reported in the final link.
1083   if (this->adjust_shndx(shdr.get_sh_link()) != this->symtab_shndx())
1084     return false;
1085
1086   gold_assert(sh_type == elfcpp::SHT_RELA);
1087   unsigned int reloc_size = elfcpp::Elf_sizes<size>::rela_size;
1088
1089   // Ignore reloc section with unexpected entsize or uneven size.
1090   // The error will be reported in the final link.
1091   if (reloc_size != shdr.get_sh_entsize() || sh_size % reloc_size != 0)
1092     return false;
1093
1094   // Ignore reloc section with bad info.  This error will be
1095   // reported in the final link.
1096   unsigned int text_shndx = this->adjust_shndx(shdr.get_sh_info());
1097   if (text_shndx >= this->shnum())
1098     return false;
1099
1100   const unsigned int shdr_size = elfcpp::Elf_sizes<size>::shdr_size;
1101   const elfcpp::Shdr<size, big_endian> text_shdr(pshdrs +
1102                                                  text_shndx * shdr_size);
1103   return this->text_section_is_scannable(text_shdr, text_shndx,
1104                                          out_sections[text_shndx], symtab);
1105 }
1106
1107
1108 // Scan relocations for stub generation.
1109
1110 template<int size, bool big_endian>
1111 void
1112 AArch64_relobj<size, big_endian>::scan_sections_for_stubs(
1113     The_target_aarch64* target,
1114     const Symbol_table* symtab,
1115     const Layout* layout)
1116 {
1117   unsigned int shnum = this->shnum();
1118   const unsigned int shdr_size = elfcpp::Elf_sizes<size>::shdr_size;
1119
1120   // Read the section headers.
1121   const unsigned char* pshdrs = this->get_view(this->elf_file()->shoff(),
1122                                                shnum * shdr_size,
1123                                                true, true);
1124
1125   // To speed up processing, we set up hash tables for fast lookup of
1126   // input offsets to output addresses.
1127   this->initialize_input_to_output_maps();
1128
1129   const Relobj::Output_sections& out_sections(this->output_sections());
1130
1131   Relocate_info<size, big_endian> relinfo;
1132   relinfo.symtab = symtab;
1133   relinfo.layout = layout;
1134   relinfo.object = this;
1135
1136   // Do relocation stubs scanning.
1137   const unsigned char* p = pshdrs + shdr_size;
1138   for (unsigned int i = 1; i < shnum; ++i, p += shdr_size)
1139     {
1140       const elfcpp::Shdr<size, big_endian> shdr(p);
1141       if (this->section_needs_reloc_stub_scanning(shdr, out_sections, symtab,
1142                                                   pshdrs))
1143         {
1144           unsigned int index = this->adjust_shndx(shdr.get_sh_info());
1145           AArch64_address output_offset =
1146               this->get_output_section_offset(index);
1147           AArch64_address output_address;
1148           if (output_offset != invalid_address)
1149             {
1150               output_address = out_sections[index]->address() + output_offset;
1151             }
1152           else
1153             {
1154               // Currently this only happens for a relaxed section.
1155               const Output_relaxed_input_section* poris =
1156                   out_sections[index]->find_relaxed_input_section(this, index);
1157               gold_assert(poris != NULL);
1158               output_address = poris->address();
1159             }
1160
1161           // Get the relocations.
1162           const unsigned char* prelocs = this->get_view(shdr.get_sh_offset(),
1163                                                         shdr.get_sh_size(),
1164                                                         true, false);
1165
1166           // Get the section contents.
1167           section_size_type input_view_size = 0;
1168           const unsigned char* input_view =
1169               this->section_contents(index, &input_view_size, false);
1170
1171           relinfo.reloc_shndx = i;
1172           relinfo.data_shndx = index;
1173           unsigned int sh_type = shdr.get_sh_type();
1174           unsigned int reloc_size;
1175           gold_assert (sh_type == elfcpp::SHT_RELA);
1176           reloc_size = elfcpp::Elf_sizes<size>::rela_size;
1177
1178           Output_section* os = out_sections[index];
1179           target->scan_section_for_stubs(&relinfo, sh_type, prelocs,
1180                                          shdr.get_sh_size() / reloc_size,
1181                                          os,
1182                                          output_offset == invalid_address,
1183                                          input_view, output_address,
1184                                          input_view_size);
1185         }
1186     }
1187 }
1188
1189
1190 // A class to wrap an ordinary input section containing executable code.
1191
1192 template<int size, bool big_endian>
1193 class AArch64_input_section : public Output_relaxed_input_section
1194 {
1195  public:
1196   typedef Stub_table<size, big_endian> The_stub_table;
1197
1198   AArch64_input_section(Relobj* relobj, unsigned int shndx)
1199     : Output_relaxed_input_section(relobj, shndx, 1),
1200       stub_table_(NULL),
1201       original_contents_(NULL), original_size_(0),
1202       original_addralign_(1)
1203   { }
1204
1205   ~AArch64_input_section()
1206   { delete[] this->original_contents_; }
1207
1208   // Initialize.
1209   void
1210   init();
1211
1212   // Set the stub_table.
1213   void
1214   set_stub_table(The_stub_table* st)
1215   { this->stub_table_ = st; }
1216
1217   // Whether this is a stub table owner.
1218   bool
1219   is_stub_table_owner() const
1220   { return this->stub_table_ != NULL && this->stub_table_->owner() == this; }
1221
1222   // Return the original size of the section.
1223   uint32_t
1224   original_size() const
1225   { return this->original_size_; }
1226
1227   // Return the stub table.
1228   The_stub_table*
1229   stub_table()
1230   { return stub_table_; }
1231
1232  protected:
1233   // Write out this input section.
1234   void
1235   do_write(Output_file*);
1236
1237   // Return required alignment of this.
1238   uint64_t
1239   do_addralign() const
1240   {
1241     if (this->is_stub_table_owner())
1242       return std::max(this->stub_table_->addralign(),
1243                       static_cast<uint64_t>(this->original_addralign_));
1244     else
1245       return this->original_addralign_;
1246   }
1247
1248   // Finalize data size.
1249   void
1250   set_final_data_size();
1251
1252   // Reset address and file offset.
1253   void
1254   do_reset_address_and_file_offset();
1255
1256   // Output offset.
1257   bool
1258   do_output_offset(const Relobj* object, unsigned int shndx,
1259                    section_offset_type offset,
1260                    section_offset_type* poutput) const
1261   {
1262     if ((object == this->relobj())
1263         && (shndx == this->shndx())
1264         && (offset >= 0)
1265         && (offset <=
1266             convert_types<section_offset_type, uint32_t>(this->original_size_)))
1267       {
1268         *poutput = offset;
1269         return true;
1270       }
1271     else
1272       return false;
1273   }
1274
1275  private:
1276   // Copying is not allowed.
1277   AArch64_input_section(const AArch64_input_section&);
1278   AArch64_input_section& operator=(const AArch64_input_section&);
1279
1280   // The relocation stubs.
1281   The_stub_table* stub_table_;
1282   // Original section contents.  We have to make a copy here since the file
1283   // containing the original section may not be locked when we need to access
1284   // the contents.
1285   unsigned char* original_contents_;
1286   // Section size of the original input section.
1287   uint32_t original_size_;
1288   // Address alignment of the original input section.
1289   uint32_t original_addralign_;
1290 };  // End of AArch64_input_section
1291
1292
1293 // Finalize data size.
1294
1295 template<int size, bool big_endian>
1296 void
1297 AArch64_input_section<size, big_endian>::set_final_data_size()
1298 {
1299   off_t off = convert_types<off_t, uint64_t>(this->original_size_);
1300
1301   if (this->is_stub_table_owner())
1302     {
1303       this->stub_table_->finalize_data_size();
1304       off = align_address(off, this->stub_table_->addralign());
1305       off += this->stub_table_->data_size();
1306     }
1307   this->set_data_size(off);
1308 }
1309
1310
1311 // Reset address and file offset.
1312
1313 template<int size, bool big_endian>
1314 void
1315 AArch64_input_section<size, big_endian>::do_reset_address_and_file_offset()
1316 {
1317   // Size of the original input section contents.
1318   off_t off = convert_types<off_t, uint64_t>(this->original_size_);
1319
1320   // If this is a stub table owner, account for the stub table size.
1321   if (this->is_stub_table_owner())
1322     {
1323       The_stub_table* stub_table = this->stub_table_;
1324
1325       // Reset the stub table's address and file offset.  The
1326       // current data size for child will be updated after that.
1327       stub_table_->reset_address_and_file_offset();
1328       off = align_address(off, stub_table_->addralign());
1329       off += stub_table->current_data_size();
1330     }
1331
1332   this->set_current_data_size(off);
1333 }
1334
1335
1336 // Initialize an Arm_input_section.
1337
1338 template<int size, bool big_endian>
1339 void
1340 AArch64_input_section<size, big_endian>::init()
1341 {
1342   Relobj* relobj = this->relobj();
1343   unsigned int shndx = this->shndx();
1344
1345   // We have to cache original size, alignment and contents to avoid locking
1346   // the original file.
1347   this->original_addralign_ =
1348       convert_types<uint32_t, uint64_t>(relobj->section_addralign(shndx));
1349
1350   // This is not efficient but we expect only a small number of relaxed
1351   // input sections for stubs.
1352   section_size_type section_size;
1353   const unsigned char* section_contents =
1354       relobj->section_contents(shndx, &section_size, false);
1355   this->original_size_ =
1356       convert_types<uint32_t, uint64_t>(relobj->section_size(shndx));
1357
1358   gold_assert(this->original_contents_ == NULL);
1359   this->original_contents_ = new unsigned char[section_size];
1360   memcpy(this->original_contents_, section_contents, section_size);
1361
1362   // We want to make this look like the original input section after
1363   // output sections are finalized.
1364   Output_section* os = relobj->output_section(shndx);
1365   off_t offset = relobj->output_section_offset(shndx);
1366   gold_assert(os != NULL && !relobj->is_output_section_offset_invalid(shndx));
1367   this->set_address(os->address() + offset);
1368   this->set_file_offset(os->offset() + offset);
1369   this->set_current_data_size(this->original_size_);
1370   this->finalize_data_size();
1371 }
1372
1373
1374 // Write data to output file.
1375
1376 template<int size, bool big_endian>
1377 void
1378 AArch64_input_section<size, big_endian>::do_write(Output_file* of)
1379 {
1380   // We have to write out the original section content.
1381   gold_assert(this->original_contents_ != NULL);
1382   of->write(this->offset(), this->original_contents_,
1383             this->original_size_);
1384
1385   // If this owns a stub table and it is not empty, write it.
1386   if (this->is_stub_table_owner() && !this->stub_table_->empty())
1387     this->stub_table_->write(of);
1388 }
1389
1390
1391 // Arm output section class.  This is defined mainly to add a number of stub
1392 // generation methods.
1393
1394 template<int size, bool big_endian>
1395 class AArch64_output_section : public Output_section
1396 {
1397  public:
1398   typedef Target_aarch64<size, big_endian> The_target_aarch64;
1399   typedef AArch64_relobj<size, big_endian> The_aarch64_relobj;
1400   typedef Stub_table<size, big_endian> The_stub_table;
1401   typedef AArch64_input_section<size, big_endian> The_aarch64_input_section;
1402
1403  public:
1404   AArch64_output_section(const char* name, elfcpp::Elf_Word type,
1405                          elfcpp::Elf_Xword flags)
1406     : Output_section(name, type, flags)
1407   { }
1408
1409   ~AArch64_output_section() {}
1410
1411   // Group input sections for stub generation.
1412   void
1413   group_sections(section_size_type, bool, Target_aarch64<size, big_endian>*,
1414                  const Task*);
1415
1416  private:
1417   typedef Output_section::Input_section Input_section;
1418   typedef Output_section::Input_section_list Input_section_list;
1419
1420   // Create a stub group.
1421   void
1422   create_stub_group(Input_section_list::const_iterator,
1423                     Input_section_list::const_iterator,
1424                     Input_section_list::const_iterator,
1425                     The_target_aarch64*,
1426                     std::vector<Output_relaxed_input_section*>&,
1427                     const Task*);
1428 };  // End of AArch64_output_section
1429
1430
1431 // Create a stub group for input sections from FIRST to LAST. OWNER points to
1432 // the input section that will be the owner of the stub table.
1433
1434 template<int size, bool big_endian> void
1435 AArch64_output_section<size, big_endian>::create_stub_group(
1436     Input_section_list::const_iterator first,
1437     Input_section_list::const_iterator last,
1438     Input_section_list::const_iterator owner,
1439     The_target_aarch64* target,
1440     std::vector<Output_relaxed_input_section*>& new_relaxed_sections,
1441     const Task* task)
1442 {
1443   // Currently we convert ordinary input sections into relaxed sections only
1444   // at this point.
1445   The_aarch64_input_section* input_section;
1446   if (owner->is_relaxed_input_section())
1447     gold_unreachable();
1448   else
1449     {
1450       gold_assert(owner->is_input_section());
1451       // Create a new relaxed input section.  We need to lock the original
1452       // file.
1453       Task_lock_obj<Object> tl(task, owner->relobj());
1454       input_section =
1455           target->new_aarch64_input_section(owner->relobj(), owner->shndx());
1456       new_relaxed_sections.push_back(input_section);
1457     }
1458
1459   // Create a stub table.
1460   The_stub_table* stub_table =
1461       target->new_stub_table(input_section);
1462
1463   input_section->set_stub_table(stub_table);
1464
1465   Input_section_list::const_iterator p = first;
1466   // Look for input sections or relaxed input sections in [first ... last].
1467   do
1468     {
1469       if (p->is_input_section() || p->is_relaxed_input_section())
1470         {
1471           // The stub table information for input sections live
1472           // in their objects.
1473           The_aarch64_relobj* aarch64_relobj =
1474               static_cast<The_aarch64_relobj*>(p->relobj());
1475           aarch64_relobj->set_stub_table(p->shndx(), stub_table);
1476         }
1477     }
1478   while (p++ != last);
1479 }
1480
1481
1482 // Group input sections for stub generation. GROUP_SIZE is roughly the limit of
1483 // stub groups. We grow a stub group by adding input section until the size is
1484 // just below GROUP_SIZE. The last input section will be converted into a stub
1485 // table owner. If STUB_ALWAYS_AFTER_BRANCH is false, we also add input sectiond
1486 // after the stub table, effectively doubling the group size.
1487 //
1488 // This is similar to the group_sections() function in elf32-arm.c but is
1489 // implemented differently.
1490
1491 template<int size, bool big_endian>
1492 void AArch64_output_section<size, big_endian>::group_sections(
1493     section_size_type group_size,
1494     bool stubs_always_after_branch,
1495     Target_aarch64<size, big_endian>* target,
1496     const Task* task)
1497 {
1498   typedef enum
1499   {
1500     NO_GROUP,
1501     FINDING_STUB_SECTION,
1502     HAS_STUB_SECTION
1503   } State;
1504
1505   std::vector<Output_relaxed_input_section*> new_relaxed_sections;
1506
1507   State state = NO_GROUP;
1508   section_size_type off = 0;
1509   section_size_type group_begin_offset = 0;
1510   section_size_type group_end_offset = 0;
1511   section_size_type stub_table_end_offset = 0;
1512   Input_section_list::const_iterator group_begin =
1513       this->input_sections().end();
1514   Input_section_list::const_iterator stub_table =
1515       this->input_sections().end();
1516   Input_section_list::const_iterator group_end = this->input_sections().end();
1517   for (Input_section_list::const_iterator p = this->input_sections().begin();
1518        p != this->input_sections().end();
1519        ++p)
1520     {
1521       section_size_type section_begin_offset =
1522         align_address(off, p->addralign());
1523       section_size_type section_end_offset =
1524         section_begin_offset + p->data_size();
1525
1526       // Check to see if we should group the previously seen sections.
1527       switch (state)
1528         {
1529         case NO_GROUP:
1530           break;
1531
1532         case FINDING_STUB_SECTION:
1533           // Adding this section makes the group larger than GROUP_SIZE.
1534           if (section_end_offset - group_begin_offset >= group_size)
1535             {
1536               if (stubs_always_after_branch)
1537                 {
1538                   gold_assert(group_end != this->input_sections().end());
1539                   this->create_stub_group(group_begin, group_end, group_end,
1540                                           target, new_relaxed_sections,
1541                                           task);
1542                   state = NO_GROUP;
1543                 }
1544               else
1545                 {
1546                   // Input sections up to stub_group_size bytes after the stub
1547                   // table can be handled by it too.
1548                   state = HAS_STUB_SECTION;
1549                   stub_table = group_end;
1550                   stub_table_end_offset = group_end_offset;
1551                 }
1552             }
1553             break;
1554
1555         case HAS_STUB_SECTION:
1556           // Adding this section makes the post stub-section group larger
1557           // than GROUP_SIZE.
1558           gold_unreachable();
1559           // NOT SUPPORTED YET. For completeness only.
1560           if (section_end_offset - stub_table_end_offset >= group_size)
1561            {
1562              gold_assert(group_end != this->input_sections().end());
1563              this->create_stub_group(group_begin, group_end, stub_table,
1564                                      target, new_relaxed_sections, task);
1565              state = NO_GROUP;
1566            }
1567            break;
1568
1569           default:
1570             gold_unreachable();
1571         }
1572
1573       // If we see an input section and currently there is no group, start
1574       // a new one.  Skip any empty sections.  We look at the data size
1575       // instead of calling p->relobj()->section_size() to avoid locking.
1576       if ((p->is_input_section() || p->is_relaxed_input_section())
1577           && (p->data_size() != 0))
1578         {
1579           if (state == NO_GROUP)
1580             {
1581               state = FINDING_STUB_SECTION;
1582               group_begin = p;
1583               group_begin_offset = section_begin_offset;
1584             }
1585
1586           // Keep track of the last input section seen.
1587           group_end = p;
1588           group_end_offset = section_end_offset;
1589         }
1590
1591       off = section_end_offset;
1592     }
1593
1594   // Create a stub group for any ungrouped sections.
1595   if (state == FINDING_STUB_SECTION || state == HAS_STUB_SECTION)
1596     {
1597       gold_assert(group_end != this->input_sections().end());
1598       this->create_stub_group(group_begin, group_end,
1599                               (state == FINDING_STUB_SECTION
1600                                ? group_end
1601                                : stub_table),
1602                               target, new_relaxed_sections, task);
1603     }
1604
1605   if (!new_relaxed_sections.empty())
1606     this->convert_input_sections_to_relaxed_sections(new_relaxed_sections);
1607
1608   // Update the section offsets
1609   for (size_t i = 0; i < new_relaxed_sections.size(); ++i)
1610     {
1611       The_aarch64_relobj* relobj = static_cast<The_aarch64_relobj*>(
1612           new_relaxed_sections[i]->relobj());
1613       unsigned int shndx = new_relaxed_sections[i]->shndx();
1614       // Tell AArch64_relobj that this input section is converted.
1615       relobj->convert_input_section_to_relaxed_section(shndx);
1616     }
1617 }  // End of AArch64_output_section::group_sections
1618
1619
1620 AArch64_reloc_property_table* aarch64_reloc_property_table = NULL;
1621
1622
1623 // The aarch64 target class.
1624 // See the ABI at
1625 // http://infocenter.arm.com/help/topic/com.arm.doc.ihi0056b/IHI0056B_aaelf64.pdf
1626 template<int size, bool big_endian>
1627 class Target_aarch64 : public Sized_target<size, big_endian>
1628 {
1629  public:
1630   typedef Target_aarch64<size, big_endian> This;
1631   typedef Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>
1632       Reloc_section;
1633   typedef Relocate_info<size, big_endian> The_relocate_info;
1634   typedef typename elfcpp::Elf_types<size>::Elf_Addr Address;
1635   typedef AArch64_relobj<size, big_endian> The_aarch64_relobj;
1636   typedef Reloc_stub<size, big_endian> The_reloc_stub;
1637   typedef typename The_reloc_stub::Stub_type The_reloc_stub_type;
1638   typedef typename Reloc_stub<size, big_endian>::Key The_reloc_stub_key;
1639   typedef Stub_table<size, big_endian> The_stub_table;
1640   typedef std::vector<The_stub_table*> Stub_table_list;
1641   typedef typename Stub_table_list::iterator Stub_table_iterator;
1642   typedef AArch64_input_section<size, big_endian> The_aarch64_input_section;
1643   typedef AArch64_output_section<size, big_endian> The_aarch64_output_section;
1644   typedef Unordered_map<Section_id,
1645                         AArch64_input_section<size, big_endian>*,
1646                         Section_id_hash> AArch64_input_section_map;
1647   const static int TCB_SIZE = size / 8 * 2;
1648
1649   Target_aarch64(const Target::Target_info* info = &aarch64_info)
1650     : Sized_target<size, big_endian>(info),
1651       got_(NULL), plt_(NULL), got_plt_(NULL), got_irelative_(NULL),
1652       got_tlsdesc_(NULL), global_offset_table_(NULL), rela_dyn_(NULL),
1653       rela_irelative_(NULL), copy_relocs_(elfcpp::R_AARCH64_COPY),
1654       got_mod_index_offset_(-1U),
1655       tlsdesc_reloc_info_(), tls_base_symbol_defined_(false),
1656       stub_tables_(), stub_group_size_(0), aarch64_input_section_map_()
1657   { }
1658
1659   // Scan the relocations to determine unreferenced sections for
1660   // garbage collection.
1661   void
1662   gc_process_relocs(Symbol_table* symtab,
1663                     Layout* layout,
1664                     Sized_relobj_file<size, big_endian>* object,
1665                     unsigned int data_shndx,
1666                     unsigned int sh_type,
1667                     const unsigned char* prelocs,
1668                     size_t reloc_count,
1669                     Output_section* output_section,
1670                     bool needs_special_offset_handling,
1671                     size_t local_symbol_count,
1672                     const unsigned char* plocal_symbols);
1673
1674   // Scan the relocations to look for symbol adjustments.
1675   void
1676   scan_relocs(Symbol_table* symtab,
1677               Layout* layout,
1678               Sized_relobj_file<size, big_endian>* object,
1679               unsigned int data_shndx,
1680               unsigned int sh_type,
1681               const unsigned char* prelocs,
1682               size_t reloc_count,
1683               Output_section* output_section,
1684               bool needs_special_offset_handling,
1685               size_t local_symbol_count,
1686               const unsigned char* plocal_symbols);
1687
1688   // Finalize the sections.
1689   void
1690   do_finalize_sections(Layout*, const Input_objects*, Symbol_table*);
1691
1692   // Return the value to use for a dynamic which requires special
1693   // treatment.
1694   uint64_t
1695   do_dynsym_value(const Symbol*) const;
1696
1697   // Relocate a section.
1698   void
1699   relocate_section(const Relocate_info<size, big_endian>*,
1700                    unsigned int sh_type,
1701                    const unsigned char* prelocs,
1702                    size_t reloc_count,
1703                    Output_section* output_section,
1704                    bool needs_special_offset_handling,
1705                    unsigned char* view,
1706                    typename elfcpp::Elf_types<size>::Elf_Addr view_address,
1707                    section_size_type view_size,
1708                    const Reloc_symbol_changes*);
1709
1710   // Scan the relocs during a relocatable link.
1711   void
1712   scan_relocatable_relocs(Symbol_table* symtab,
1713                           Layout* layout,
1714                           Sized_relobj_file<size, big_endian>* object,
1715                           unsigned int data_shndx,
1716                           unsigned int sh_type,
1717                           const unsigned char* prelocs,
1718                           size_t reloc_count,
1719                           Output_section* output_section,
1720                           bool needs_special_offset_handling,
1721                           size_t local_symbol_count,
1722                           const unsigned char* plocal_symbols,
1723                           Relocatable_relocs*);
1724
1725   // Relocate a section during a relocatable link.
1726   void
1727   relocate_relocs(
1728       const Relocate_info<size, big_endian>*,
1729       unsigned int sh_type,
1730       const unsigned char* prelocs,
1731       size_t reloc_count,
1732       Output_section* output_section,
1733       typename elfcpp::Elf_types<size>::Elf_Off offset_in_output_section,
1734       const Relocatable_relocs*,
1735       unsigned char* view,
1736       typename elfcpp::Elf_types<size>::Elf_Addr view_address,
1737       section_size_type view_size,
1738       unsigned char* reloc_view,
1739       section_size_type reloc_view_size);
1740
1741   // Return the symbol index to use for a target specific relocation.
1742   // The only target specific relocation is R_AARCH64_TLSDESC for a
1743   // local symbol, which is an absolute reloc.
1744   unsigned int
1745   do_reloc_symbol_index(void*, unsigned int r_type) const
1746   {
1747     gold_assert(r_type == elfcpp::R_AARCH64_TLSDESC);
1748     return 0;
1749   }
1750
1751   // Return the addend to use for a target specific relocation.
1752   typename elfcpp::Elf_types<size>::Elf_Addr
1753   do_reloc_addend(void* arg, unsigned int r_type,
1754                   typename elfcpp::Elf_types<size>::Elf_Addr addend) const;
1755
1756   // Return the PLT section.
1757   uint64_t
1758   do_plt_address_for_global(const Symbol* gsym) const
1759   { return this->plt_section()->address_for_global(gsym); }
1760
1761   uint64_t
1762   do_plt_address_for_local(const Relobj* relobj, unsigned int symndx) const
1763   { return this->plt_section()->address_for_local(relobj, symndx); }
1764
1765   // This function should be defined in targets that can use relocation
1766   // types to determine (implemented in local_reloc_may_be_function_pointer
1767   // and global_reloc_may_be_function_pointer)
1768   // if a function's pointer is taken.  ICF uses this in safe mode to only
1769   // fold those functions whose pointer is defintely not taken.
1770   bool
1771   do_can_check_for_function_pointers() const
1772   { return true; }
1773
1774   // Return the number of entries in the PLT.
1775   unsigned int
1776   plt_entry_count() const;
1777
1778   //Return the offset of the first non-reserved PLT entry.
1779   unsigned int
1780   first_plt_entry_offset() const;
1781
1782   // Return the size of each PLT entry.
1783   unsigned int
1784   plt_entry_size() const;
1785
1786   // Create a stub table.
1787   The_stub_table*
1788   new_stub_table(The_aarch64_input_section*);
1789
1790   // Create an aarch64 input section.
1791   The_aarch64_input_section*
1792   new_aarch64_input_section(Relobj*, unsigned int);
1793
1794   // Find an aarch64 input section instance for a given OBJ and SHNDX.
1795   The_aarch64_input_section*
1796   find_aarch64_input_section(Relobj*, unsigned int) const;
1797
1798   // Return the thread control block size.
1799   unsigned int
1800   tcb_size() const { return This::TCB_SIZE; }
1801
1802   // Scan a section for stub generation.
1803   void
1804   scan_section_for_stubs(const Relocate_info<size, big_endian>*, unsigned int,
1805                          const unsigned char*, size_t, Output_section*,
1806                          bool, const unsigned char*,
1807                          Address,
1808                          section_size_type);
1809
1810   // Scan a relocation section for stub.
1811   template<int sh_type>
1812   void
1813   scan_reloc_section_for_stubs(
1814       const The_relocate_info* relinfo,
1815       const unsigned char* prelocs,
1816       size_t reloc_count,
1817       Output_section* output_section,
1818       bool needs_special_offset_handling,
1819       const unsigned char* view,
1820       Address view_address,
1821       section_size_type);
1822
1823   // Relocate a single stub.
1824   void
1825   relocate_stub(The_reloc_stub*, const Relocate_info<size, big_endian>*,
1826                 Output_section*, unsigned char*, Address,
1827                 section_size_type);
1828
1829   // Get the default AArch64 target.
1830   static This*
1831   current_target()
1832   {
1833     gold_assert(parameters->target().machine_code() == elfcpp::EM_AARCH64
1834                 && parameters->target().get_size() == size
1835                 && parameters->target().is_big_endian() == big_endian);
1836     return static_cast<This*>(parameters->sized_target<size, big_endian>());
1837   }
1838
1839  protected:
1840   void
1841   do_select_as_default_target()
1842   {
1843     gold_assert(aarch64_reloc_property_table == NULL);
1844     aarch64_reloc_property_table = new AArch64_reloc_property_table();
1845   }
1846
1847   // Add a new reloc argument, returning the index in the vector.
1848   size_t
1849   add_tlsdesc_info(Sized_relobj_file<size, big_endian>* object,
1850                    unsigned int r_sym)
1851   {
1852     this->tlsdesc_reloc_info_.push_back(Tlsdesc_info(object, r_sym));
1853     return this->tlsdesc_reloc_info_.size() - 1;
1854   }
1855
1856   virtual Output_data_plt_aarch64<size, big_endian>*
1857   do_make_data_plt(Layout* layout,
1858                    Output_data_got_aarch64<size, big_endian>* got,
1859                    Output_data_space* got_plt,
1860                    Output_data_space* got_irelative)
1861   {
1862     return new Output_data_plt_aarch64_standard<size, big_endian>(
1863       layout, got, got_plt, got_irelative);
1864   }
1865
1866
1867   // do_make_elf_object to override the same function in the base class.
1868   Object*
1869   do_make_elf_object(const std::string&, Input_file*, off_t,
1870                      const elfcpp::Ehdr<size, big_endian>&);
1871
1872   Output_data_plt_aarch64<size, big_endian>*
1873   make_data_plt(Layout* layout,
1874                 Output_data_got_aarch64<size, big_endian>* got,
1875                 Output_data_space* got_plt,
1876                 Output_data_space* got_irelative)
1877   {
1878     return this->do_make_data_plt(layout, got, got_plt, got_irelative);
1879   }
1880
1881   // We only need to generate stubs, and hence perform relaxation if we are
1882   // not doing relocatable linking.
1883   virtual bool
1884   do_may_relax() const
1885   { return !parameters->options().relocatable(); }
1886
1887   // Relaxation hook.  This is where we do stub generation.
1888   virtual bool
1889   do_relax(int, const Input_objects*, Symbol_table*, Layout*, const Task*);
1890
1891   void
1892   group_sections(Layout* layout,
1893                  section_size_type group_size,
1894                  bool stubs_always_after_branch,
1895                  const Task* task);
1896
1897   void
1898   scan_reloc_for_stub(const The_relocate_info*, unsigned int,
1899                       const Sized_symbol<size>*, unsigned int,
1900                       const Symbol_value<size>*,
1901                       typename elfcpp::Elf_types<size>::Elf_Swxword,
1902                       Address Elf_Addr);
1903
1904   // Make an output section.
1905   Output_section*
1906   do_make_output_section(const char* name, elfcpp::Elf_Word type,
1907                          elfcpp::Elf_Xword flags)
1908   { return new The_aarch64_output_section(name, type, flags); }
1909
1910  private:
1911   // The class which scans relocations.
1912   class Scan
1913   {
1914   public:
1915     Scan()
1916       : issued_non_pic_error_(false)
1917     { }
1918
1919     inline void
1920     local(Symbol_table* symtab, Layout* layout, Target_aarch64* target,
1921           Sized_relobj_file<size, big_endian>* object,
1922           unsigned int data_shndx,
1923           Output_section* output_section,
1924           const elfcpp::Rela<size, big_endian>& reloc, unsigned int r_type,
1925           const elfcpp::Sym<size, big_endian>& lsym,
1926           bool is_discarded);
1927
1928     inline void
1929     global(Symbol_table* symtab, Layout* layout, Target_aarch64* target,
1930            Sized_relobj_file<size, big_endian>* object,
1931            unsigned int data_shndx,
1932            Output_section* output_section,
1933            const elfcpp::Rela<size, big_endian>& reloc, unsigned int r_type,
1934            Symbol* gsym);
1935
1936     inline bool
1937     local_reloc_may_be_function_pointer(Symbol_table* , Layout* ,
1938                                         Target_aarch64<size, big_endian>* ,
1939                                         Sized_relobj_file<size, big_endian>* ,
1940                                         unsigned int ,
1941                                         Output_section* ,
1942                                         const elfcpp::Rela<size, big_endian>& ,
1943                                         unsigned int r_type,
1944                                         const elfcpp::Sym<size, big_endian>&);
1945
1946     inline bool
1947     global_reloc_may_be_function_pointer(Symbol_table* , Layout* ,
1948                                          Target_aarch64<size, big_endian>* ,
1949                                          Sized_relobj_file<size, big_endian>* ,
1950                                          unsigned int ,
1951                                          Output_section* ,
1952                                          const elfcpp::Rela<size, big_endian>& ,
1953                                          unsigned int r_type,
1954                                          Symbol* gsym);
1955
1956   private:
1957     static void
1958     unsupported_reloc_local(Sized_relobj_file<size, big_endian>*,
1959                             unsigned int r_type);
1960
1961     static void
1962     unsupported_reloc_global(Sized_relobj_file<size, big_endian>*,
1963                              unsigned int r_type, Symbol*);
1964
1965     inline bool
1966     possible_function_pointer_reloc(unsigned int r_type);
1967
1968     void
1969     check_non_pic(Relobj*, unsigned int r_type);
1970
1971     bool
1972     reloc_needs_plt_for_ifunc(Sized_relobj_file<size, big_endian>*,
1973                               unsigned int r_type);
1974
1975     // Whether we have issued an error about a non-PIC compilation.
1976     bool issued_non_pic_error_;
1977   };
1978
1979   // The class which implements relocation.
1980   class Relocate
1981   {
1982    public:
1983     Relocate()
1984       : skip_call_tls_get_addr_(false)
1985     { }
1986
1987     ~Relocate()
1988     { }
1989
1990     // Do a relocation.  Return false if the caller should not issue
1991     // any warnings about this relocation.
1992     inline bool
1993     relocate(const Relocate_info<size, big_endian>*, Target_aarch64*,
1994              Output_section*,
1995              size_t relnum, const elfcpp::Rela<size, big_endian>&,
1996              unsigned int r_type, const Sized_symbol<size>*,
1997              const Symbol_value<size>*,
1998              unsigned char*, typename elfcpp::Elf_types<size>::Elf_Addr,
1999              section_size_type);
2000
2001   private:
2002     inline typename AArch64_relocate_functions<size, big_endian>::Status
2003     relocate_tls(const Relocate_info<size, big_endian>*,
2004                  Target_aarch64<size, big_endian>*,
2005                  size_t,
2006                  const elfcpp::Rela<size, big_endian>&,
2007                  unsigned int r_type, const Sized_symbol<size>*,
2008                  const Symbol_value<size>*,
2009                  unsigned char*,
2010                  typename elfcpp::Elf_types<size>::Elf_Addr);
2011
2012     inline typename AArch64_relocate_functions<size, big_endian>::Status
2013     tls_gd_to_le(
2014                  const Relocate_info<size, big_endian>*,
2015                  Target_aarch64<size, big_endian>*,
2016                  const elfcpp::Rela<size, big_endian>&,
2017                  unsigned int,
2018                  unsigned char*,
2019                  const Symbol_value<size>*);
2020
2021     inline typename AArch64_relocate_functions<size, big_endian>::Status
2022     tls_ld_to_le(
2023                  const Relocate_info<size, big_endian>*,
2024                  Target_aarch64<size, big_endian>*,
2025                  const elfcpp::Rela<size, big_endian>&,
2026                  unsigned int,
2027                  unsigned char*,
2028                  const Symbol_value<size>*);
2029
2030     inline typename AArch64_relocate_functions<size, big_endian>::Status
2031     tls_ie_to_le(
2032                  const Relocate_info<size, big_endian>*,
2033                  Target_aarch64<size, big_endian>*,
2034                  const elfcpp::Rela<size, big_endian>&,
2035                  unsigned int,
2036                  unsigned char*,
2037                  const Symbol_value<size>*);
2038
2039     inline typename AArch64_relocate_functions<size, big_endian>::Status
2040     tls_desc_gd_to_le(
2041                  const Relocate_info<size, big_endian>*,
2042                  Target_aarch64<size, big_endian>*,
2043                  const elfcpp::Rela<size, big_endian>&,
2044                  unsigned int,
2045                  unsigned char*,
2046                  const Symbol_value<size>*);
2047
2048     inline typename AArch64_relocate_functions<size, big_endian>::Status
2049     tls_desc_gd_to_ie(
2050                  const Relocate_info<size, big_endian>*,
2051                  Target_aarch64<size, big_endian>*,
2052                  const elfcpp::Rela<size, big_endian>&,
2053                  unsigned int,
2054                  unsigned char*,
2055                  const Symbol_value<size>*,
2056                  typename elfcpp::Elf_types<size>::Elf_Addr,
2057                  typename elfcpp::Elf_types<size>::Elf_Addr);
2058
2059     bool skip_call_tls_get_addr_;
2060
2061   };  // End of class Relocate
2062
2063   // A class which returns the size required for a relocation type,
2064   // used while scanning relocs during a relocatable link.
2065   class Relocatable_size_for_reloc
2066   {
2067    public:
2068     unsigned int
2069     get_size_for_reloc(unsigned int, Relobj*);
2070   };
2071
2072   // Adjust TLS relocation type based on the options and whether this
2073   // is a local symbol.
2074   static tls::Tls_optimization
2075   optimize_tls_reloc(bool is_final, int r_type);
2076
2077   // Get the GOT section, creating it if necessary.
2078   Output_data_got_aarch64<size, big_endian>*
2079   got_section(Symbol_table*, Layout*);
2080
2081   // Get the GOT PLT section.
2082   Output_data_space*
2083   got_plt_section() const
2084   {
2085     gold_assert(this->got_plt_ != NULL);
2086     return this->got_plt_;
2087   }
2088
2089   // Get the GOT section for TLSDESC entries.
2090   Output_data_got<size, big_endian>*
2091   got_tlsdesc_section() const
2092   {
2093     gold_assert(this->got_tlsdesc_ != NULL);
2094     return this->got_tlsdesc_;
2095   }
2096
2097   // Create the PLT section.
2098   void
2099   make_plt_section(Symbol_table* symtab, Layout* layout);
2100
2101   // Create a PLT entry for a global symbol.
2102   void
2103   make_plt_entry(Symbol_table*, Layout*, Symbol*);
2104
2105   // Create a PLT entry for a local STT_GNU_IFUNC symbol.
2106   void
2107   make_local_ifunc_plt_entry(Symbol_table*, Layout*,
2108                              Sized_relobj_file<size, big_endian>* relobj,
2109                              unsigned int local_sym_index);
2110
2111   // Define the _TLS_MODULE_BASE_ symbol in the TLS segment.
2112   void
2113   define_tls_base_symbol(Symbol_table*, Layout*);
2114
2115   // Create the reserved PLT and GOT entries for the TLS descriptor resolver.
2116   void
2117   reserve_tlsdesc_entries(Symbol_table* symtab, Layout* layout);
2118
2119   // Create a GOT entry for the TLS module index.
2120   unsigned int
2121   got_mod_index_entry(Symbol_table* symtab, Layout* layout,
2122                       Sized_relobj_file<size, big_endian>* object);
2123
2124   // Get the PLT section.
2125   Output_data_plt_aarch64<size, big_endian>*
2126   plt_section() const
2127   {
2128     gold_assert(this->plt_ != NULL);
2129     return this->plt_;
2130   }
2131
2132   // Get the dynamic reloc section, creating it if necessary.
2133   Reloc_section*
2134   rela_dyn_section(Layout*);
2135
2136   // Get the section to use for TLSDESC relocations.
2137   Reloc_section*
2138   rela_tlsdesc_section(Layout*) const;
2139
2140   // Get the section to use for IRELATIVE relocations.
2141   Reloc_section*
2142   rela_irelative_section(Layout*);
2143
2144   // Add a potential copy relocation.
2145   void
2146   copy_reloc(Symbol_table* symtab, Layout* layout,
2147              Sized_relobj_file<size, big_endian>* object,
2148              unsigned int shndx, Output_section* output_section,
2149              Symbol* sym, const elfcpp::Rela<size, big_endian>& reloc)
2150   {
2151     this->copy_relocs_.copy_reloc(symtab, layout,
2152                                   symtab->get_sized_symbol<size>(sym),
2153                                   object, shndx, output_section,
2154                                   reloc, this->rela_dyn_section(layout));
2155   }
2156
2157   // Information about this specific target which we pass to the
2158   // general Target structure.
2159   static const Target::Target_info aarch64_info;
2160
2161   // The types of GOT entries needed for this platform.
2162   // These values are exposed to the ABI in an incremental link.
2163   // Do not renumber existing values without changing the version
2164   // number of the .gnu_incremental_inputs section.
2165   enum Got_type
2166   {
2167     GOT_TYPE_STANDARD = 0,      // GOT entry for a regular symbol
2168     GOT_TYPE_TLS_OFFSET = 1,    // GOT entry for TLS offset
2169     GOT_TYPE_TLS_PAIR = 2,      // GOT entry for TLS module/offset pair
2170     GOT_TYPE_TLS_DESC = 3       // GOT entry for TLS_DESC pair
2171   };
2172
2173   // This type is used as the argument to the target specific
2174   // relocation routines.  The only target specific reloc is
2175   // R_AARCh64_TLSDESC against a local symbol.
2176   struct Tlsdesc_info
2177   {
2178     Tlsdesc_info(Sized_relobj_file<size, big_endian>* a_object,
2179                  unsigned int a_r_sym)
2180       : object(a_object), r_sym(a_r_sym)
2181     { }
2182
2183     // The object in which the local symbol is defined.
2184     Sized_relobj_file<size, big_endian>* object;
2185     // The local symbol index in the object.
2186     unsigned int r_sym;
2187   };
2188
2189   // The GOT section.
2190   Output_data_got_aarch64<size, big_endian>* got_;
2191   // The PLT section.
2192   Output_data_plt_aarch64<size, big_endian>* plt_;
2193   // The GOT PLT section.
2194   Output_data_space* got_plt_;
2195   // The GOT section for IRELATIVE relocations.
2196   Output_data_space* got_irelative_;
2197   // The GOT section for TLSDESC relocations.
2198   Output_data_got<size, big_endian>* got_tlsdesc_;
2199   // The _GLOBAL_OFFSET_TABLE_ symbol.
2200   Symbol* global_offset_table_;
2201   // The dynamic reloc section.
2202   Reloc_section* rela_dyn_;
2203   // The section to use for IRELATIVE relocs.
2204   Reloc_section* rela_irelative_;
2205   // Relocs saved to avoid a COPY reloc.
2206   Copy_relocs<elfcpp::SHT_RELA, size, big_endian> copy_relocs_;
2207   // Offset of the GOT entry for the TLS module index.
2208   unsigned int got_mod_index_offset_;
2209   // We handle R_AARCH64_TLSDESC against a local symbol as a target
2210   // specific relocation. Here we store the object and local symbol
2211   // index for the relocation.
2212   std::vector<Tlsdesc_info> tlsdesc_reloc_info_;
2213   // True if the _TLS_MODULE_BASE_ symbol has been defined.
2214   bool tls_base_symbol_defined_;
2215   // List of stub_tables
2216   Stub_table_list stub_tables_;
2217   // Actual stub group size
2218   section_size_type stub_group_size_;
2219   AArch64_input_section_map aarch64_input_section_map_;
2220 };  // End of Target_aarch64
2221
2222
2223 template<>
2224 const Target::Target_info Target_aarch64<64, false>::aarch64_info =
2225 {
2226   64,                   // size
2227   false,                // is_big_endian
2228   elfcpp::EM_AARCH64,   // machine_code
2229   false,                // has_make_symbol
2230   false,                // has_resolve
2231   false,                // has_code_fill
2232   true,                 // is_default_stack_executable
2233   true,                 // can_icf_inline_merge_sections
2234   '\0',                 // wrap_char
2235   "/lib/ld.so.1",       // program interpreter
2236   0x400000,             // default_text_segment_address
2237   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2238   0x1000,               // common_pagesize (overridable by -z common-page-size)
2239   false,                // isolate_execinstr
2240   0,                    // rosegment_gap
2241   elfcpp::SHN_UNDEF,    // small_common_shndx
2242   elfcpp::SHN_UNDEF,    // large_common_shndx
2243   0,                    // small_common_section_flags
2244   0,                    // large_common_section_flags
2245   NULL,                 // attributes_section
2246   NULL,                 // attributes_vendor
2247   "_start"              // entry_symbol_name
2248 };
2249
2250 template<>
2251 const Target::Target_info Target_aarch64<32, false>::aarch64_info =
2252 {
2253   32,                   // size
2254   false,                // is_big_endian
2255   elfcpp::EM_AARCH64,   // machine_code
2256   false,                // has_make_symbol
2257   false,                // has_resolve
2258   false,                // has_code_fill
2259   true,                 // is_default_stack_executable
2260   false,                // can_icf_inline_merge_sections
2261   '\0',                 // wrap_char
2262   "/lib/ld.so.1",       // program interpreter
2263   0x400000,             // default_text_segment_address
2264   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2265   0x1000,               // common_pagesize (overridable by -z common-page-size)
2266   false,                // isolate_execinstr
2267   0,                    // rosegment_gap
2268   elfcpp::SHN_UNDEF,    // small_common_shndx
2269   elfcpp::SHN_UNDEF,    // large_common_shndx
2270   0,                    // small_common_section_flags
2271   0,                    // large_common_section_flags
2272   NULL,                 // attributes_section
2273   NULL,                 // attributes_vendor
2274   "_start"              // entry_symbol_name
2275 };
2276
2277 template<>
2278 const Target::Target_info Target_aarch64<64, true>::aarch64_info =
2279 {
2280   64,                   // size
2281   true,                 // is_big_endian
2282   elfcpp::EM_AARCH64,   // machine_code
2283   false,                // has_make_symbol
2284   false,                // has_resolve
2285   false,                // has_code_fill
2286   true,                 // is_default_stack_executable
2287   true,                 // can_icf_inline_merge_sections
2288   '\0',                 // wrap_char
2289   "/lib/ld.so.1",       // program interpreter
2290   0x400000,             // default_text_segment_address
2291   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2292   0x1000,               // common_pagesize (overridable by -z common-page-size)
2293   false,                // isolate_execinstr
2294   0,                    // rosegment_gap
2295   elfcpp::SHN_UNDEF,    // small_common_shndx
2296   elfcpp::SHN_UNDEF,    // large_common_shndx
2297   0,                    // small_common_section_flags
2298   0,                    // large_common_section_flags
2299   NULL,                 // attributes_section
2300   NULL,                 // attributes_vendor
2301   "_start"              // entry_symbol_name
2302 };
2303
2304 template<>
2305 const Target::Target_info Target_aarch64<32, true>::aarch64_info =
2306 {
2307   32,                   // size
2308   true,                 // is_big_endian
2309   elfcpp::EM_AARCH64,   // machine_code
2310   false,                // has_make_symbol
2311   false,                // has_resolve
2312   false,                // has_code_fill
2313   true,                 // is_default_stack_executable
2314   false,                // can_icf_inline_merge_sections
2315   '\0',                 // wrap_char
2316   "/lib/ld.so.1",       // program interpreter
2317   0x400000,             // default_text_segment_address
2318   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2319   0x1000,               // common_pagesize (overridable by -z common-page-size)
2320   false,                // isolate_execinstr
2321   0,                    // rosegment_gap
2322   elfcpp::SHN_UNDEF,    // small_common_shndx
2323   elfcpp::SHN_UNDEF,    // large_common_shndx
2324   0,                    // small_common_section_flags
2325   0,                    // large_common_section_flags
2326   NULL,                 // attributes_section
2327   NULL,                 // attributes_vendor
2328   "_start"              // entry_symbol_name
2329 };
2330
2331 // Get the GOT section, creating it if necessary.
2332
2333 template<int size, bool big_endian>
2334 Output_data_got_aarch64<size, big_endian>*
2335 Target_aarch64<size, big_endian>::got_section(Symbol_table* symtab,
2336                                               Layout* layout)
2337 {
2338   if (this->got_ == NULL)
2339     {
2340       gold_assert(symtab != NULL && layout != NULL);
2341
2342       // When using -z now, we can treat .got.plt as a relro section.
2343       // Without -z now, it is modified after program startup by lazy
2344       // PLT relocations.
2345       bool is_got_plt_relro = parameters->options().now();
2346       Output_section_order got_order = (is_got_plt_relro
2347                                         ? ORDER_RELRO
2348                                         : ORDER_RELRO_LAST);
2349       Output_section_order got_plt_order = (is_got_plt_relro
2350                                             ? ORDER_RELRO
2351                                             : ORDER_NON_RELRO_FIRST);
2352
2353       // Layout of .got and .got.plt sections.
2354       // .got[0] &_DYNAMIC                          <-_GLOBAL_OFFSET_TABLE_
2355       // ...
2356       // .gotplt[0] reserved for ld.so (&linkmap)   <--DT_PLTGOT
2357       // .gotplt[1] reserved for ld.so (resolver)
2358       // .gotplt[2] reserved
2359
2360       // Generate .got section.
2361       this->got_ = new Output_data_got_aarch64<size, big_endian>(symtab,
2362                                                                  layout);
2363       layout->add_output_section_data(".got", elfcpp::SHT_PROGBITS,
2364                                       (elfcpp::SHF_ALLOC | elfcpp::SHF_WRITE),
2365                                       this->got_, got_order, true);
2366       // The first word of GOT is reserved for the address of .dynamic.
2367       // We put 0 here now. The value will be replaced later in
2368       // Output_data_got_aarch64::do_write.
2369       this->got_->add_constant(0);
2370
2371       // Define _GLOBAL_OFFSET_TABLE_ at the start of the PLT.
2372       // _GLOBAL_OFFSET_TABLE_ value points to the start of the .got section,
2373       // even if there is a .got.plt section.
2374       this->global_offset_table_ =
2375         symtab->define_in_output_data("_GLOBAL_OFFSET_TABLE_", NULL,
2376                                       Symbol_table::PREDEFINED,
2377                                       this->got_,
2378                                       0, 0, elfcpp::STT_OBJECT,
2379                                       elfcpp::STB_LOCAL,
2380                                       elfcpp::STV_HIDDEN, 0,
2381                                       false, false);
2382
2383       // Generate .got.plt section.
2384       this->got_plt_ = new Output_data_space(size / 8, "** GOT PLT");
2385       layout->add_output_section_data(".got.plt", elfcpp::SHT_PROGBITS,
2386                                       (elfcpp::SHF_ALLOC
2387                                        | elfcpp::SHF_WRITE),
2388                                       this->got_plt_, got_plt_order,
2389                                       is_got_plt_relro);
2390
2391       // The first three entries are reserved.
2392       this->got_plt_->set_current_data_size(
2393         AARCH64_GOTPLT_RESERVE_COUNT * (size / 8));
2394
2395       // If there are any IRELATIVE relocations, they get GOT entries
2396       // in .got.plt after the jump slot entries.
2397       this->got_irelative_ = new Output_data_space(size / 8,
2398                                                    "** GOT IRELATIVE PLT");
2399       layout->add_output_section_data(".got.plt", elfcpp::SHT_PROGBITS,
2400                                       (elfcpp::SHF_ALLOC
2401                                        | elfcpp::SHF_WRITE),
2402                                       this->got_irelative_,
2403                                       got_plt_order,
2404                                       is_got_plt_relro);
2405
2406       // If there are any TLSDESC relocations, they get GOT entries in
2407       // .got.plt after the jump slot and IRELATIVE entries.
2408       this->got_tlsdesc_ = new Output_data_got<size, big_endian>();
2409       layout->add_output_section_data(".got.plt", elfcpp::SHT_PROGBITS,
2410                                       (elfcpp::SHF_ALLOC
2411                                        | elfcpp::SHF_WRITE),
2412                                       this->got_tlsdesc_,
2413                                       got_plt_order,
2414                                       is_got_plt_relro);
2415
2416       if (!is_got_plt_relro)
2417         {
2418           // Those bytes can go into the relro segment.
2419           layout->increase_relro(
2420             AARCH64_GOTPLT_RESERVE_COUNT * (size / 8));
2421         }
2422
2423     }
2424   return this->got_;
2425 }
2426
2427 // Get the dynamic reloc section, creating it if necessary.
2428
2429 template<int size, bool big_endian>
2430 typename Target_aarch64<size, big_endian>::Reloc_section*
2431 Target_aarch64<size, big_endian>::rela_dyn_section(Layout* layout)
2432 {
2433   if (this->rela_dyn_ == NULL)
2434     {
2435       gold_assert(layout != NULL);
2436       this->rela_dyn_ = new Reloc_section(parameters->options().combreloc());
2437       layout->add_output_section_data(".rela.dyn", elfcpp::SHT_RELA,
2438                                       elfcpp::SHF_ALLOC, this->rela_dyn_,
2439                                       ORDER_DYNAMIC_RELOCS, false);
2440     }
2441   return this->rela_dyn_;
2442 }
2443
2444 // Get the section to use for IRELATIVE relocs, creating it if
2445 // necessary.  These go in .rela.dyn, but only after all other dynamic
2446 // relocations.  They need to follow the other dynamic relocations so
2447 // that they can refer to global variables initialized by those
2448 // relocs.
2449
2450 template<int size, bool big_endian>
2451 typename Target_aarch64<size, big_endian>::Reloc_section*
2452 Target_aarch64<size, big_endian>::rela_irelative_section(Layout* layout)
2453 {
2454   if (this->rela_irelative_ == NULL)
2455     {
2456       // Make sure we have already created the dynamic reloc section.
2457       this->rela_dyn_section(layout);
2458       this->rela_irelative_ = new Reloc_section(false);
2459       layout->add_output_section_data(".rela.dyn", elfcpp::SHT_RELA,
2460                                       elfcpp::SHF_ALLOC, this->rela_irelative_,
2461                                       ORDER_DYNAMIC_RELOCS, false);
2462       gold_assert(this->rela_dyn_->output_section()
2463                   == this->rela_irelative_->output_section());
2464     }
2465   return this->rela_irelative_;
2466 }
2467
2468
2469 // do_make_elf_object to override the same function in the base class.  We need
2470 // to use a target-specific sub-class of Sized_relobj_file<size, big_endian> to
2471 // store backend specific information. Hence we need to have our own ELF object
2472 // creation.
2473
2474 template<int size, bool big_endian>
2475 Object*
2476 Target_aarch64<size, big_endian>::do_make_elf_object(
2477     const std::string& name,
2478     Input_file* input_file,
2479     off_t offset, const elfcpp::Ehdr<size, big_endian>& ehdr)
2480 {
2481   int et = ehdr.get_e_type();
2482   // ET_EXEC files are valid input for --just-symbols/-R,
2483   // and we treat them as relocatable objects.
2484   if (et == elfcpp::ET_EXEC && input_file->just_symbols())
2485     return Sized_target<size, big_endian>::do_make_elf_object(
2486         name, input_file, offset, ehdr);
2487   else if (et == elfcpp::ET_REL)
2488     {
2489       AArch64_relobj<size, big_endian>* obj =
2490         new AArch64_relobj<size, big_endian>(name, input_file, offset, ehdr);
2491       obj->setup();
2492       return obj;
2493     }
2494   else if (et == elfcpp::ET_DYN)
2495     {
2496       // Keep base implementation.
2497       Sized_dynobj<size, big_endian>* obj =
2498           new Sized_dynobj<size, big_endian>(name, input_file, offset, ehdr);
2499       obj->setup();
2500       return obj;
2501     }
2502   else
2503     {
2504       gold_error(_("%s: unsupported ELF file type %d"),
2505                  name.c_str(), et);
2506       return NULL;
2507     }
2508 }
2509
2510
2511 // Scan a relocation for stub generation.
2512
2513 template<int size, bool big_endian>
2514 void
2515 Target_aarch64<size, big_endian>::scan_reloc_for_stub(
2516     const Relocate_info<size, big_endian>* relinfo,
2517     unsigned int r_type,
2518     const Sized_symbol<size>* gsym,
2519     unsigned int r_sym,
2520     const Symbol_value<size>* psymval,
2521     typename elfcpp::Elf_types<size>::Elf_Swxword addend,
2522     Address address)
2523 {
2524   const AArch64_relobj<size, big_endian>* aarch64_relobj =
2525       static_cast<AArch64_relobj<size, big_endian>*>(relinfo->object);
2526
2527   Symbol_value<size> symval;
2528   if (gsym != NULL)
2529     {
2530       const AArch64_reloc_property* arp = aarch64_reloc_property_table->
2531         get_reloc_property(r_type);
2532       if (gsym->use_plt_offset(arp->reference_flags()))
2533         {
2534           // This uses a PLT, change the symbol value.
2535           symval.set_output_value(this->plt_section()->address()
2536                                   + gsym->plt_offset());
2537           psymval = &symval;
2538         }
2539       else if (gsym->is_undefined())
2540         // There is no need to generate a stub symbol is undefined.
2541         return;
2542     }
2543
2544   // Get the symbol value.
2545   typename Symbol_value<size>::Value value = psymval->value(aarch64_relobj, 0);
2546
2547   // Owing to pipelining, the PC relative branches below actually skip
2548   // two instructions when the branch offset is 0.
2549   Address destination = static_cast<Address>(-1);
2550   switch (r_type)
2551     {
2552     case elfcpp::R_AARCH64_CALL26:
2553     case elfcpp::R_AARCH64_JUMP26:
2554       destination = value + addend;
2555       break;
2556     default:
2557       gold_unreachable();
2558     }
2559
2560   typename The_reloc_stub::Stub_type stub_type = The_reloc_stub::
2561       stub_type_for_reloc(r_type, address, destination);
2562   if (stub_type == The_reloc_stub::ST_NONE)
2563     return ;
2564
2565   The_stub_table* stub_table = aarch64_relobj->stub_table(relinfo->data_shndx);
2566   gold_assert(stub_table != NULL);
2567
2568   The_reloc_stub_key key(stub_type, gsym, aarch64_relobj, r_sym, addend);
2569   The_reloc_stub* stub = stub_table->find_reloc_stub(key);
2570   if (stub == NULL)
2571     {
2572       stub = new The_reloc_stub(stub_type);
2573       stub_table->add_reloc_stub(stub, key);
2574     }
2575   stub->set_destination_address(destination);
2576 }  // End of Target_aarch64::scan_reloc_for_stub
2577
2578
2579 // This function scans a relocation section for stub generation.
2580 // The template parameter Relocate must be a class type which provides
2581 // a single function, relocate(), which implements the machine
2582 // specific part of a relocation.
2583
2584 // BIG_ENDIAN is the endianness of the data.  SH_TYPE is the section type:
2585 // SHT_REL or SHT_RELA.
2586
2587 // PRELOCS points to the relocation data.  RELOC_COUNT is the number
2588 // of relocs.  OUTPUT_SECTION is the output section.
2589 // NEEDS_SPECIAL_OFFSET_HANDLING is true if input offsets need to be
2590 // mapped to output offsets.
2591
2592 // VIEW is the section data, VIEW_ADDRESS is its memory address, and
2593 // VIEW_SIZE is the size.  These refer to the input section, unless
2594 // NEEDS_SPECIAL_OFFSET_HANDLING is true, in which case they refer to
2595 // the output section.
2596
2597 template<int size, bool big_endian>
2598 template<int sh_type>
2599 void inline
2600 Target_aarch64<size, big_endian>::scan_reloc_section_for_stubs(
2601     const Relocate_info<size, big_endian>* relinfo,
2602     const unsigned char* prelocs,
2603     size_t reloc_count,
2604     Output_section* /*output_section*/,
2605     bool /*needs_special_offset_handling*/,
2606     const unsigned char* /*view*/,
2607     Address view_address,
2608     section_size_type)
2609 {
2610   typedef typename Reloc_types<sh_type,size,big_endian>::Reloc Reltype;
2611
2612   const int reloc_size =
2613       Reloc_types<sh_type,size,big_endian>::reloc_size;
2614   AArch64_relobj<size, big_endian>* object =
2615       static_cast<AArch64_relobj<size, big_endian>*>(relinfo->object);
2616   unsigned int local_count = object->local_symbol_count();
2617
2618   gold::Default_comdat_behavior default_comdat_behavior;
2619   Comdat_behavior comdat_behavior = CB_UNDETERMINED;
2620
2621   for (size_t i = 0; i < reloc_count; ++i, prelocs += reloc_size)
2622     {
2623       Reltype reloc(prelocs);
2624       typename elfcpp::Elf_types<size>::Elf_WXword r_info = reloc.get_r_info();
2625       unsigned int r_sym = elfcpp::elf_r_sym<size>(r_info);
2626       unsigned int r_type = elfcpp::elf_r_type<size>(r_info);
2627       if (r_type != elfcpp::R_AARCH64_CALL26
2628           && r_type != elfcpp::R_AARCH64_JUMP26)
2629         continue;
2630
2631       section_offset_type offset =
2632           convert_to_section_size_type(reloc.get_r_offset());
2633
2634       // Get the addend.
2635       typename elfcpp::Elf_types<size>::Elf_Swxword addend =
2636           reloc.get_r_addend();
2637
2638       const Sized_symbol<size>* sym;
2639       Symbol_value<size> symval;
2640       const Symbol_value<size> *psymval;
2641       bool is_defined_in_discarded_section;
2642       unsigned int shndx;
2643       if (r_sym < local_count)
2644         {
2645           sym = NULL;
2646           psymval = object->local_symbol(r_sym);
2647
2648           // If the local symbol belongs to a section we are discarding,
2649           // and that section is a debug section, try to find the
2650           // corresponding kept section and map this symbol to its
2651           // counterpart in the kept section.  The symbol must not
2652           // correspond to a section we are folding.
2653           bool is_ordinary;
2654           shndx = psymval->input_shndx(&is_ordinary);
2655           is_defined_in_discarded_section =
2656             (is_ordinary
2657              && shndx != elfcpp::SHN_UNDEF
2658              && !object->is_section_included(shndx)
2659              && !relinfo->symtab->is_section_folded(object, shndx));
2660
2661           // We need to compute the would-be final value of this local
2662           // symbol.
2663           if (!is_defined_in_discarded_section)
2664             {
2665               typedef Sized_relobj_file<size, big_endian> ObjType;
2666               typename ObjType::Compute_final_local_value_status status =
2667                 object->compute_final_local_value(r_sym, psymval, &symval,
2668                                                   relinfo->symtab);
2669               if (status == ObjType::CFLV_OK)
2670                 {
2671                   // Currently we cannot handle a branch to a target in
2672                   // a merged section.  If this is the case, issue an error
2673                   // and also free the merge symbol value.
2674                   if (!symval.has_output_value())
2675                     {
2676                       const std::string& section_name =
2677                         object->section_name(shndx);
2678                       object->error(_("cannot handle branch to local %u "
2679                                           "in a merged section %s"),
2680                                         r_sym, section_name.c_str());
2681                     }
2682                   psymval = &symval;
2683                 }
2684               else
2685                 {
2686                   // We cannot determine the final value.
2687                   continue;
2688                 }
2689             }
2690         }
2691       else
2692         {
2693           const Symbol* gsym;
2694           gsym = object->global_symbol(r_sym);
2695           gold_assert(gsym != NULL);
2696           if (gsym->is_forwarder())
2697             gsym = relinfo->symtab->resolve_forwards(gsym);
2698
2699           sym = static_cast<const Sized_symbol<size>*>(gsym);
2700           if (sym->has_symtab_index() && sym->symtab_index() != -1U)
2701             symval.set_output_symtab_index(sym->symtab_index());
2702           else
2703             symval.set_no_output_symtab_entry();
2704
2705           // We need to compute the would-be final value of this global
2706           // symbol.
2707           const Symbol_table* symtab = relinfo->symtab;
2708           const Sized_symbol<size>* sized_symbol =
2709               symtab->get_sized_symbol<size>(gsym);
2710           Symbol_table::Compute_final_value_status status;
2711           typename elfcpp::Elf_types<size>::Elf_Addr value =
2712               symtab->compute_final_value<size>(sized_symbol, &status);
2713
2714           // Skip this if the symbol has not output section.
2715           if (status == Symbol_table::CFVS_NO_OUTPUT_SECTION)
2716             continue;
2717           symval.set_output_value(value);
2718
2719           if (gsym->type() == elfcpp::STT_TLS)
2720             symval.set_is_tls_symbol();
2721           else if (gsym->type() == elfcpp::STT_GNU_IFUNC)
2722             symval.set_is_ifunc_symbol();
2723           psymval = &symval;
2724
2725           is_defined_in_discarded_section =
2726               (gsym->is_defined_in_discarded_section()
2727                && gsym->is_undefined());
2728           shndx = 0;
2729         }
2730
2731       Symbol_value<size> symval2;
2732       if (is_defined_in_discarded_section)
2733         {
2734           if (comdat_behavior == CB_UNDETERMINED)
2735             {
2736               std::string name = object->section_name(relinfo->data_shndx);
2737               comdat_behavior = default_comdat_behavior.get(name.c_str());
2738             }
2739           if (comdat_behavior == CB_PRETEND)
2740             {
2741               bool found;
2742               typename elfcpp::Elf_types<size>::Elf_Addr value =
2743                 object->map_to_kept_section(shndx, &found);
2744               if (found)
2745                 symval2.set_output_value(value + psymval->input_value());
2746               else
2747                 symval2.set_output_value(0);
2748             }
2749           else
2750             {
2751               if (comdat_behavior == CB_WARNING)
2752                 gold_warning_at_location(relinfo, i, offset,
2753                                          _("relocation refers to discarded "
2754                                            "section"));
2755               symval2.set_output_value(0);
2756             }
2757           symval2.set_no_output_symtab_entry();
2758           psymval = &symval2;
2759         }
2760
2761       // If symbol is a section symbol, we don't know the actual type of
2762       // destination.  Give up.
2763       if (psymval->is_section_symbol())
2764         continue;
2765
2766       this->scan_reloc_for_stub(relinfo, r_type, sym, r_sym, psymval,
2767                                 addend, view_address + offset);
2768     }  // End of iterating relocs in a section
2769 }  // End of Target_aarch64::scan_reloc_section_for_stubs
2770
2771
2772 // Scan an input section for stub generation.
2773
2774 template<int size, bool big_endian>
2775 void
2776 Target_aarch64<size, big_endian>::scan_section_for_stubs(
2777     const Relocate_info<size, big_endian>* relinfo,
2778     unsigned int sh_type,
2779     const unsigned char* prelocs,
2780     size_t reloc_count,
2781     Output_section* output_section,
2782     bool needs_special_offset_handling,
2783     const unsigned char* view,
2784     Address view_address,
2785     section_size_type view_size)
2786 {
2787   gold_assert(sh_type == elfcpp::SHT_RELA);
2788   this->scan_reloc_section_for_stubs<elfcpp::SHT_RELA>(
2789       relinfo,
2790       prelocs,
2791       reloc_count,
2792       output_section,
2793       needs_special_offset_handling,
2794       view,
2795       view_address,
2796       view_size);
2797 }
2798
2799
2800 // Relocate a single stub.
2801
2802 template<int size, bool big_endian>
2803 void Target_aarch64<size, big_endian>::
2804 relocate_stub(The_reloc_stub* stub,
2805               const The_relocate_info*,
2806               Output_section*,
2807               unsigned char* view,
2808               Address address,
2809               section_size_type)
2810 {
2811   typedef AArch64_relocate_functions<size, big_endian> The_reloc_functions;
2812   typedef typename The_reloc_functions::Status The_reloc_functions_status;
2813   typedef typename elfcpp::Swap<32,big_endian>::Valtype Insntype;
2814
2815   Insntype* ip = reinterpret_cast<Insntype*>(view);
2816   int insn_number = stub->stub_insn_number();
2817   const uint32_t* insns = stub->stub_insns();
2818   // Check the insns are really those stub insns.
2819   for (int i = 0; i < insn_number; ++i)
2820     {
2821       Insntype insn = elfcpp::Swap<32,big_endian>::readval(ip + i);
2822       gold_assert(((uint32_t)insn == insns[i+1]));
2823     }
2824
2825   Address dest = stub->destination_address();
2826
2827   switch(stub->stub_type())
2828     {
2829     case The_reloc_stub::ST_ADRP_BRANCH:
2830       {
2831         // 1st reloc is ADR_PREL_PG_HI21
2832         The_reloc_functions_status status =
2833             The_reloc_functions::adrp(view, dest, address);
2834         // An error should never arise in the above step. If so, please
2835         // check 'aarch64_valid_for_adrp_p'.
2836         gold_assert(status == The_reloc_functions::STATUS_OKAY);
2837
2838         // 2nd reloc is ADD_ABS_LO12_NC
2839         const AArch64_reloc_property* arp =
2840             aarch64_reloc_property_table->get_reloc_property(
2841                 elfcpp::R_AARCH64_ADD_ABS_LO12_NC);
2842         gold_assert(arp != NULL);
2843         status = The_reloc_functions::template
2844             rela_general<32>(view + 4, dest, 0, arp);
2845         // An error should never arise, it is an "_NC" relocation.
2846         gold_assert(status == The_reloc_functions::STATUS_OKAY);
2847       }
2848       break;
2849
2850     case The_reloc_stub::ST_LONG_BRANCH_ABS:
2851       // 1st reloc is R_AARCH64_PREL64, at offset 8
2852       elfcpp::Swap<64,big_endian>::writeval(view + 8, dest);
2853       break;
2854
2855     case The_reloc_stub::ST_LONG_BRANCH_PCREL:
2856       {
2857         // "PC" calculation is the 2nd insn in the stub.
2858         uint64_t offset = dest - (address + 4);
2859         // Offset is placed at offset 4 and 5.
2860         elfcpp::Swap<64,big_endian>::writeval(view + 16, offset);
2861       }
2862       break;
2863
2864     default:
2865       gold_unreachable();
2866     }
2867 }
2868
2869
2870 // A class to handle the PLT data.
2871 // This is an abstract base class that handles most of the linker details
2872 // but does not know the actual contents of PLT entries.  The derived
2873 // classes below fill in those details.
2874
2875 template<int size, bool big_endian>
2876 class Output_data_plt_aarch64 : public Output_section_data
2877 {
2878  public:
2879   typedef Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>
2880       Reloc_section;
2881   typedef typename elfcpp::Elf_types<size>::Elf_Addr Address;
2882
2883   Output_data_plt_aarch64(Layout* layout,
2884                           uint64_t addralign,
2885                           Output_data_got_aarch64<size, big_endian>* got,
2886                           Output_data_space* got_plt,
2887                           Output_data_space* got_irelative)
2888     : Output_section_data(addralign), tlsdesc_rel_(NULL), irelative_rel_(NULL),
2889       got_(got), got_plt_(got_plt), got_irelative_(got_irelative),
2890       count_(0), irelative_count_(0), tlsdesc_got_offset_(-1U)
2891   { this->init(layout); }
2892
2893   // Initialize the PLT section.
2894   void
2895   init(Layout* layout);
2896
2897   // Add an entry to the PLT.
2898   void
2899   add_entry(Symbol_table*, Layout*, Symbol* gsym);
2900
2901   // Add an entry to the PLT for a local STT_GNU_IFUNC symbol.
2902   unsigned int
2903   add_local_ifunc_entry(Symbol_table* symtab, Layout*,
2904                         Sized_relobj_file<size, big_endian>* relobj,
2905                         unsigned int local_sym_index);
2906
2907   // Add the relocation for a PLT entry.
2908   void
2909   add_relocation(Symbol_table*, Layout*, Symbol* gsym,
2910                  unsigned int got_offset);
2911
2912   // Add the reserved TLSDESC_PLT entry to the PLT.
2913   void
2914   reserve_tlsdesc_entry(unsigned int got_offset)
2915   { this->tlsdesc_got_offset_ = got_offset; }
2916
2917   // Return true if a TLSDESC_PLT entry has been reserved.
2918   bool
2919   has_tlsdesc_entry() const
2920   { return this->tlsdesc_got_offset_ != -1U; }
2921
2922   // Return the GOT offset for the reserved TLSDESC_PLT entry.
2923   unsigned int
2924   get_tlsdesc_got_offset() const
2925   { return this->tlsdesc_got_offset_; }
2926
2927   // Return the PLT offset of the reserved TLSDESC_PLT entry.
2928   unsigned int
2929   get_tlsdesc_plt_offset() const
2930   {
2931     return (this->first_plt_entry_offset() +
2932             (this->count_ + this->irelative_count_)
2933             * this->get_plt_entry_size());
2934   }
2935
2936   // Return the .rela.plt section data.
2937   Reloc_section*
2938   rela_plt()
2939   { return this->rel_; }
2940
2941   // Return where the TLSDESC relocations should go.
2942   Reloc_section*
2943   rela_tlsdesc(Layout*);
2944
2945   // Return where the IRELATIVE relocations should go in the PLT
2946   // relocations.
2947   Reloc_section*
2948   rela_irelative(Symbol_table*, Layout*);
2949
2950   // Return whether we created a section for IRELATIVE relocations.
2951   bool
2952   has_irelative_section() const
2953   { return this->irelative_rel_ != NULL; }
2954
2955   // Return the number of PLT entries.
2956   unsigned int
2957   entry_count() const
2958   { return this->count_ + this->irelative_count_; }
2959
2960   // Return the offset of the first non-reserved PLT entry.
2961   unsigned int
2962   first_plt_entry_offset() const
2963   { return this->do_first_plt_entry_offset(); }
2964
2965   // Return the size of a PLT entry.
2966   unsigned int
2967   get_plt_entry_size() const
2968   { return this->do_get_plt_entry_size(); }
2969
2970   // Return the reserved tlsdesc entry size.
2971   unsigned int
2972   get_plt_tlsdesc_entry_size() const
2973   { return this->do_get_plt_tlsdesc_entry_size(); }
2974
2975   // Return the PLT address to use for a global symbol.
2976   uint64_t
2977   address_for_global(const Symbol*);
2978
2979   // Return the PLT address to use for a local symbol.
2980   uint64_t
2981   address_for_local(const Relobj*, unsigned int symndx);
2982
2983  protected:
2984   // Fill in the first PLT entry.
2985   void
2986   fill_first_plt_entry(unsigned char* pov,
2987                        Address got_address,
2988                        Address plt_address)
2989   { this->do_fill_first_plt_entry(pov, got_address, plt_address); }
2990
2991   // Fill in a normal PLT entry.
2992   void
2993   fill_plt_entry(unsigned char* pov,
2994                  Address got_address,
2995                  Address plt_address,
2996                  unsigned int got_offset,
2997                  unsigned int plt_offset)
2998   {
2999     this->do_fill_plt_entry(pov, got_address, plt_address,
3000                             got_offset, plt_offset);
3001   }
3002
3003   // Fill in the reserved TLSDESC PLT entry.
3004   void
3005   fill_tlsdesc_entry(unsigned char* pov,
3006                      Address gotplt_address,
3007                      Address plt_address,
3008                      Address got_base,
3009                      unsigned int tlsdesc_got_offset,
3010                      unsigned int plt_offset)
3011   {
3012     this->do_fill_tlsdesc_entry(pov, gotplt_address, plt_address, got_base,
3013                                 tlsdesc_got_offset, plt_offset);
3014   }
3015
3016   virtual unsigned int
3017   do_first_plt_entry_offset() const = 0;
3018
3019   virtual unsigned int
3020   do_get_plt_entry_size() const = 0;
3021
3022   virtual unsigned int
3023   do_get_plt_tlsdesc_entry_size() const = 0;
3024
3025   virtual void
3026   do_fill_first_plt_entry(unsigned char* pov,
3027                           Address got_addr,
3028                           Address plt_addr) = 0;
3029
3030   virtual void
3031   do_fill_plt_entry(unsigned char* pov,
3032                     Address got_address,
3033                     Address plt_address,
3034                     unsigned int got_offset,
3035                     unsigned int plt_offset) = 0;
3036
3037   virtual void
3038   do_fill_tlsdesc_entry(unsigned char* pov,
3039                         Address gotplt_address,
3040                         Address plt_address,
3041                         Address got_base,
3042                         unsigned int tlsdesc_got_offset,
3043                         unsigned int plt_offset) = 0;
3044
3045   void
3046   do_adjust_output_section(Output_section* os);
3047
3048   // Write to a map file.
3049   void
3050   do_print_to_mapfile(Mapfile* mapfile) const
3051   { mapfile->print_output_data(this, _("** PLT")); }
3052
3053  private:
3054   // Set the final size.
3055   void
3056   set_final_data_size();
3057
3058   // Write out the PLT data.
3059   void
3060   do_write(Output_file*);
3061
3062   // The reloc section.
3063   Reloc_section* rel_;
3064
3065   // The TLSDESC relocs, if necessary.  These must follow the regular
3066   // PLT relocs.
3067   Reloc_section* tlsdesc_rel_;
3068
3069   // The IRELATIVE relocs, if necessary.  These must follow the
3070   // regular PLT relocations.
3071   Reloc_section* irelative_rel_;
3072
3073   // The .got section.
3074   Output_data_got_aarch64<size, big_endian>* got_;
3075
3076   // The .got.plt section.
3077   Output_data_space* got_plt_;
3078
3079   // The part of the .got.plt section used for IRELATIVE relocs.
3080   Output_data_space* got_irelative_;
3081
3082   // The number of PLT entries.
3083   unsigned int count_;
3084
3085   // Number of PLT entries with R_AARCH64_IRELATIVE relocs.  These
3086   // follow the regular PLT entries.
3087   unsigned int irelative_count_;
3088
3089   // GOT offset of the reserved TLSDESC_GOT entry for the lazy trampoline.
3090   // Communicated to the loader via DT_TLSDESC_GOT. The magic value -1
3091   // indicates an offset is not allocated.
3092   unsigned int tlsdesc_got_offset_;
3093 };
3094
3095 // Initialize the PLT section.
3096
3097 template<int size, bool big_endian>
3098 void
3099 Output_data_plt_aarch64<size, big_endian>::init(Layout* layout)
3100 {
3101   this->rel_ = new Reloc_section(false);
3102   layout->add_output_section_data(".rela.plt", elfcpp::SHT_RELA,
3103                                   elfcpp::SHF_ALLOC, this->rel_,
3104                                   ORDER_DYNAMIC_PLT_RELOCS, false);
3105 }
3106
3107 template<int size, bool big_endian>
3108 void
3109 Output_data_plt_aarch64<size, big_endian>::do_adjust_output_section(
3110     Output_section* os)
3111 {
3112   os->set_entsize(this->get_plt_entry_size());
3113 }
3114
3115 // Add an entry to the PLT.
3116
3117 template<int size, bool big_endian>
3118 void
3119 Output_data_plt_aarch64<size, big_endian>::add_entry(Symbol_table* symtab,
3120     Layout* layout, Symbol* gsym)
3121 {
3122   gold_assert(!gsym->has_plt_offset());
3123
3124   unsigned int* pcount;
3125   unsigned int plt_reserved;
3126   Output_section_data_build* got;
3127
3128   if (gsym->type() == elfcpp::STT_GNU_IFUNC
3129       && gsym->can_use_relative_reloc(false))
3130     {
3131       pcount = &this->irelative_count_;
3132       plt_reserved = 0;
3133       got = this->got_irelative_;
3134     }
3135   else
3136     {
3137       pcount = &this->count_;
3138       plt_reserved = this->first_plt_entry_offset();
3139       got = this->got_plt_;
3140     }
3141
3142   gsym->set_plt_offset((*pcount) * this->get_plt_entry_size()
3143                        + plt_reserved);
3144
3145   ++*pcount;
3146
3147   section_offset_type got_offset = got->current_data_size();
3148
3149   // Every PLT entry needs a GOT entry which points back to the PLT
3150   // entry (this will be changed by the dynamic linker, normally
3151   // lazily when the function is called).
3152   got->set_current_data_size(got_offset + size / 8);
3153
3154   // Every PLT entry needs a reloc.
3155   this->add_relocation(symtab, layout, gsym, got_offset);
3156
3157   // Note that we don't need to save the symbol. The contents of the
3158   // PLT are independent of which symbols are used. The symbols only
3159   // appear in the relocations.
3160 }
3161
3162 // Add an entry to the PLT for a local STT_GNU_IFUNC symbol.  Return
3163 // the PLT offset.
3164
3165 template<int size, bool big_endian>
3166 unsigned int
3167 Output_data_plt_aarch64<size, big_endian>::add_local_ifunc_entry(
3168     Symbol_table* symtab,
3169     Layout* layout,
3170     Sized_relobj_file<size, big_endian>* relobj,
3171     unsigned int local_sym_index)
3172 {
3173   unsigned int plt_offset = this->irelative_count_ * this->get_plt_entry_size();
3174   ++this->irelative_count_;
3175
3176   section_offset_type got_offset = this->got_irelative_->current_data_size();
3177
3178   // Every PLT entry needs a GOT entry which points back to the PLT
3179   // entry.
3180   this->got_irelative_->set_current_data_size(got_offset + size / 8);
3181
3182   // Every PLT entry needs a reloc.
3183   Reloc_section* rela = this->rela_irelative(symtab, layout);
3184   rela->add_symbolless_local_addend(relobj, local_sym_index,
3185                                     elfcpp::R_AARCH64_IRELATIVE,
3186                                     this->got_irelative_, got_offset, 0);
3187
3188   return plt_offset;
3189 }
3190
3191 // Add the relocation for a PLT entry.
3192
3193 template<int size, bool big_endian>
3194 void
3195 Output_data_plt_aarch64<size, big_endian>::add_relocation(
3196     Symbol_table* symtab, Layout* layout, Symbol* gsym, unsigned int got_offset)
3197 {
3198   if (gsym->type() == elfcpp::STT_GNU_IFUNC
3199       && gsym->can_use_relative_reloc(false))
3200     {
3201       Reloc_section* rela = this->rela_irelative(symtab, layout);
3202       rela->add_symbolless_global_addend(gsym, elfcpp::R_AARCH64_IRELATIVE,
3203                                          this->got_irelative_, got_offset, 0);
3204     }
3205   else
3206     {
3207       gsym->set_needs_dynsym_entry();
3208       this->rel_->add_global(gsym, elfcpp::R_AARCH64_JUMP_SLOT, this->got_plt_,
3209                              got_offset, 0);
3210     }
3211 }
3212
3213 // Return where the TLSDESC relocations should go, creating it if
3214 // necessary.  These follow the JUMP_SLOT relocations.
3215
3216 template<int size, bool big_endian>
3217 typename Output_data_plt_aarch64<size, big_endian>::Reloc_section*
3218 Output_data_plt_aarch64<size, big_endian>::rela_tlsdesc(Layout* layout)
3219 {
3220   if (this->tlsdesc_rel_ == NULL)
3221     {
3222       this->tlsdesc_rel_ = new Reloc_section(false);
3223       layout->add_output_section_data(".rela.plt", elfcpp::SHT_RELA,
3224                                       elfcpp::SHF_ALLOC, this->tlsdesc_rel_,
3225                                       ORDER_DYNAMIC_PLT_RELOCS, false);
3226       gold_assert(this->tlsdesc_rel_->output_section()
3227                   == this->rel_->output_section());
3228     }
3229   return this->tlsdesc_rel_;
3230 }
3231
3232 // Return where the IRELATIVE relocations should go in the PLT.  These
3233 // follow the JUMP_SLOT and the TLSDESC relocations.
3234
3235 template<int size, bool big_endian>
3236 typename Output_data_plt_aarch64<size, big_endian>::Reloc_section*
3237 Output_data_plt_aarch64<size, big_endian>::rela_irelative(Symbol_table* symtab,
3238                                                           Layout* layout)
3239 {
3240   if (this->irelative_rel_ == NULL)
3241     {
3242       // Make sure we have a place for the TLSDESC relocations, in
3243       // case we see any later on.
3244       this->rela_tlsdesc(layout);
3245       this->irelative_rel_ = new Reloc_section(false);
3246       layout->add_output_section_data(".rela.plt", elfcpp::SHT_RELA,
3247                                       elfcpp::SHF_ALLOC, this->irelative_rel_,
3248                                       ORDER_DYNAMIC_PLT_RELOCS, false);
3249       gold_assert(this->irelative_rel_->output_section()
3250                   == this->rel_->output_section());
3251
3252       if (parameters->doing_static_link())
3253         {
3254           // A statically linked executable will only have a .rela.plt
3255           // section to hold R_AARCH64_IRELATIVE relocs for
3256           // STT_GNU_IFUNC symbols.  The library will use these
3257           // symbols to locate the IRELATIVE relocs at program startup
3258           // time.
3259           symtab->define_in_output_data("__rela_iplt_start", NULL,
3260                                         Symbol_table::PREDEFINED,
3261                                         this->irelative_rel_, 0, 0,
3262                                         elfcpp::STT_NOTYPE, elfcpp::STB_GLOBAL,
3263                                         elfcpp::STV_HIDDEN, 0, false, true);
3264           symtab->define_in_output_data("__rela_iplt_end", NULL,
3265                                         Symbol_table::PREDEFINED,
3266                                         this->irelative_rel_, 0, 0,
3267                                         elfcpp::STT_NOTYPE, elfcpp::STB_GLOBAL,
3268                                         elfcpp::STV_HIDDEN, 0, true, true);
3269         }
3270     }
3271   return this->irelative_rel_;
3272 }
3273
3274 // Return the PLT address to use for a global symbol.
3275
3276 template<int size, bool big_endian>
3277 uint64_t
3278 Output_data_plt_aarch64<size, big_endian>::address_for_global(
3279   const Symbol* gsym)
3280 {
3281   uint64_t offset = 0;
3282   if (gsym->type() == elfcpp::STT_GNU_IFUNC
3283       && gsym->can_use_relative_reloc(false))
3284     offset = (this->first_plt_entry_offset() +
3285               this->count_ * this->get_plt_entry_size());
3286   return this->address() + offset + gsym->plt_offset();
3287 }
3288
3289 // Return the PLT address to use for a local symbol.  These are always
3290 // IRELATIVE relocs.
3291
3292 template<int size, bool big_endian>
3293 uint64_t
3294 Output_data_plt_aarch64<size, big_endian>::address_for_local(
3295     const Relobj* object,
3296     unsigned int r_sym)
3297 {
3298   return (this->address()
3299           + this->first_plt_entry_offset()
3300           + this->count_ * this->get_plt_entry_size()
3301           + object->local_plt_offset(r_sym));
3302 }
3303
3304 // Set the final size.
3305
3306 template<int size, bool big_endian>
3307 void
3308 Output_data_plt_aarch64<size, big_endian>::set_final_data_size()
3309 {
3310   unsigned int count = this->count_ + this->irelative_count_;
3311   unsigned int extra_size = 0;
3312   if (this->has_tlsdesc_entry())
3313     extra_size += this->get_plt_tlsdesc_entry_size();
3314   this->set_data_size(this->first_plt_entry_offset()
3315                       + count * this->get_plt_entry_size()
3316                       + extra_size);
3317 }
3318
3319 template<int size, bool big_endian>
3320 class Output_data_plt_aarch64_standard :
3321   public Output_data_plt_aarch64<size, big_endian>
3322 {
3323  public:
3324   typedef typename elfcpp::Elf_types<size>::Elf_Addr Address;
3325   Output_data_plt_aarch64_standard(
3326       Layout* layout,
3327       Output_data_got_aarch64<size, big_endian>* got,
3328       Output_data_space* got_plt,
3329       Output_data_space* got_irelative)
3330     : Output_data_plt_aarch64<size, big_endian>(layout,
3331                                                 size == 32 ? 4 : 8,
3332                                                 got, got_plt,
3333                                                 got_irelative)
3334   { }
3335
3336  protected:
3337   // Return the offset of the first non-reserved PLT entry.
3338   virtual unsigned int
3339   do_first_plt_entry_offset() const
3340   { return this->first_plt_entry_size; }
3341
3342   // Return the size of a PLT entry
3343   virtual unsigned int
3344   do_get_plt_entry_size() const
3345   { return this->plt_entry_size; }
3346
3347   // Return the size of a tlsdesc entry
3348   virtual unsigned int
3349   do_get_plt_tlsdesc_entry_size() const
3350   { return this->plt_tlsdesc_entry_size; }
3351
3352   virtual void
3353   do_fill_first_plt_entry(unsigned char* pov,
3354                           Address got_address,
3355                           Address plt_address);
3356
3357   virtual void
3358   do_fill_plt_entry(unsigned char* pov,
3359                     Address got_address,
3360                     Address plt_address,
3361                     unsigned int got_offset,
3362                     unsigned int plt_offset);
3363
3364   virtual void
3365   do_fill_tlsdesc_entry(unsigned char* pov,
3366                         Address gotplt_address,
3367                         Address plt_address,
3368                         Address got_base,
3369                         unsigned int tlsdesc_got_offset,
3370                         unsigned int plt_offset);
3371
3372  private:
3373   // The size of the first plt entry size.
3374   static const int first_plt_entry_size = 32;
3375   // The size of the plt entry size.
3376   static const int plt_entry_size = 16;
3377   // The size of the plt tlsdesc entry size.
3378   static const int plt_tlsdesc_entry_size = 32;
3379   // Template for the first PLT entry.
3380   static const uint32_t first_plt_entry[first_plt_entry_size / 4];
3381   // Template for subsequent PLT entries.
3382   static const uint32_t plt_entry[plt_entry_size / 4];
3383   // The reserved TLSDESC entry in the PLT for an executable.
3384   static const uint32_t tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4];
3385 };
3386
3387 // The first entry in the PLT for an executable.
3388
3389 template<>
3390 const uint32_t
3391 Output_data_plt_aarch64_standard<32, false>::
3392     first_plt_entry[first_plt_entry_size / 4] =
3393 {
3394   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3395   0x90000010,   /* adrp x16, PLT_GOT+0x8  */
3396   0xb9400A11,   /* ldr w17, [x16, #PLT_GOT+0x8]  */
3397   0x11002210,   /* add w16, w16,#PLT_GOT+0x8   */
3398   0xd61f0220,   /* br x17  */
3399   0xd503201f,   /* nop */
3400   0xd503201f,   /* nop */
3401   0xd503201f,   /* nop */
3402 };
3403
3404
3405 template<>
3406 const uint32_t
3407 Output_data_plt_aarch64_standard<32, true>::
3408     first_plt_entry[first_plt_entry_size / 4] =
3409 {
3410   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3411   0x90000010,   /* adrp x16, PLT_GOT+0x8  */
3412   0xb9400A11,   /* ldr w17, [x16, #PLT_GOT+0x8]  */
3413   0x11002210,   /* add w16, w16,#PLT_GOT+0x8   */
3414   0xd61f0220,   /* br x17  */
3415   0xd503201f,   /* nop */
3416   0xd503201f,   /* nop */
3417   0xd503201f,   /* nop */
3418 };
3419
3420
3421 template<>
3422 const uint32_t
3423 Output_data_plt_aarch64_standard<64, false>::
3424     first_plt_entry[first_plt_entry_size / 4] =
3425 {
3426   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3427   0x90000010,   /* adrp x16, PLT_GOT+16  */
3428   0xf9400A11,   /* ldr x17, [x16, #PLT_GOT+0x10]  */
3429   0x91004210,   /* add x16, x16,#PLT_GOT+0x10   */
3430   0xd61f0220,   /* br x17  */
3431   0xd503201f,   /* nop */
3432   0xd503201f,   /* nop */
3433   0xd503201f,   /* nop */
3434 };
3435
3436
3437 template<>
3438 const uint32_t
3439 Output_data_plt_aarch64_standard<64, true>::
3440     first_plt_entry[first_plt_entry_size / 4] =
3441 {
3442   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3443   0x90000010,   /* adrp x16, PLT_GOT+16  */
3444   0xf9400A11,   /* ldr x17, [x16, #PLT_GOT+0x10]  */
3445   0x91004210,   /* add x16, x16,#PLT_GOT+0x10   */
3446   0xd61f0220,   /* br x17  */
3447   0xd503201f,   /* nop */
3448   0xd503201f,   /* nop */
3449   0xd503201f,   /* nop */
3450 };
3451
3452
3453 template<>
3454 const uint32_t
3455 Output_data_plt_aarch64_standard<32, false>::
3456     plt_entry[plt_entry_size / 4] =
3457 {
3458   0x90000010,   /* adrp x16, PLTGOT + n * 4  */
3459   0xb9400211,   /* ldr w17, [w16, PLTGOT + n * 4] */
3460   0x11000210,   /* add w16, w16, :lo12:PLTGOT + n * 4  */
3461   0xd61f0220,   /* br x17.  */
3462 };
3463
3464
3465 template<>
3466 const uint32_t
3467 Output_data_plt_aarch64_standard<32, true>::
3468     plt_entry[plt_entry_size / 4] =
3469 {
3470   0x90000010,   /* adrp x16, PLTGOT + n * 4  */
3471   0xb9400211,   /* ldr w17, [w16, PLTGOT + n * 4] */
3472   0x11000210,   /* add w16, w16, :lo12:PLTGOT + n * 4  */
3473   0xd61f0220,   /* br x17.  */
3474 };
3475
3476
3477 template<>
3478 const uint32_t
3479 Output_data_plt_aarch64_standard<64, false>::
3480     plt_entry[plt_entry_size / 4] =
3481 {
3482   0x90000010,   /* adrp x16, PLTGOT + n * 8  */
3483   0xf9400211,   /* ldr x17, [x16, PLTGOT + n * 8] */
3484   0x91000210,   /* add x16, x16, :lo12:PLTGOT + n * 8  */
3485   0xd61f0220,   /* br x17.  */
3486 };
3487
3488
3489 template<>
3490 const uint32_t
3491 Output_data_plt_aarch64_standard<64, true>::
3492     plt_entry[plt_entry_size / 4] =
3493 {
3494   0x90000010,   /* adrp x16, PLTGOT + n * 8  */
3495   0xf9400211,   /* ldr x17, [x16, PLTGOT + n * 8] */
3496   0x91000210,   /* add x16, x16, :lo12:PLTGOT + n * 8  */
3497   0xd61f0220,   /* br x17.  */
3498 };
3499
3500
3501 template<int size, bool big_endian>
3502 void
3503 Output_data_plt_aarch64_standard<size, big_endian>::do_fill_first_plt_entry(
3504     unsigned char* pov,
3505     Address got_address,
3506     Address plt_address)
3507 {
3508   // PLT0 of the small PLT looks like this in ELF64 -
3509   // stp x16, x30, [sp, #-16]!          Save the reloc and lr on stack.
3510   // adrp x16, PLT_GOT + 16             Get the page base of the GOTPLT
3511   // ldr  x17, [x16, #:lo12:PLT_GOT+16] Load the address of the
3512   //                                    symbol resolver
3513   // add  x16, x16, #:lo12:PLT_GOT+16   Load the lo12 bits of the
3514   //                                    GOTPLT entry for this.
3515   // br   x17
3516   // PLT0 will be slightly different in ELF32 due to different got entry
3517   // size.
3518   memcpy(pov, this->first_plt_entry, this->first_plt_entry_size);
3519   Address gotplt_2nd_ent = got_address + (size / 8) * 2;
3520
3521   // Fill in the top 21 bits for this: ADRP x16, PLT_GOT + 8 * 2.
3522   // ADRP:  (PG(S+A)-PG(P)) >> 12) & 0x1fffff.
3523   // FIXME: This only works for 64bit
3524   AArch64_relocate_functions<size, big_endian>::adrp(pov + 4,
3525       gotplt_2nd_ent, plt_address + 4);
3526
3527   // Fill in R_AARCH64_LDST8_LO12
3528   elfcpp::Swap<32, big_endian>::writeval(
3529       pov + 8,
3530       ((this->first_plt_entry[2] & 0xffc003ff)
3531        | ((gotplt_2nd_ent & 0xff8) << 7)));
3532
3533   // Fill in R_AARCH64_ADD_ABS_LO12
3534   elfcpp::Swap<32, big_endian>::writeval(
3535       pov + 12,
3536       ((this->first_plt_entry[3] & 0xffc003ff)
3537        | ((gotplt_2nd_ent & 0xfff) << 10)));
3538 }
3539
3540
3541 // Subsequent entries in the PLT for an executable.
3542 // FIXME: This only works for 64bit
3543
3544 template<int size, bool big_endian>
3545 void
3546 Output_data_plt_aarch64_standard<size, big_endian>::do_fill_plt_entry(
3547     unsigned char* pov,
3548     Address got_address,
3549     Address plt_address,
3550     unsigned int got_offset,
3551     unsigned int plt_offset)
3552 {
3553   memcpy(pov, this->plt_entry, this->plt_entry_size);
3554
3555   Address gotplt_entry_address = got_address + got_offset;
3556   Address plt_entry_address = plt_address + plt_offset;
3557
3558   // Fill in R_AARCH64_PCREL_ADR_HI21
3559   AArch64_relocate_functions<size, big_endian>::adrp(
3560       pov,
3561       gotplt_entry_address,
3562       plt_entry_address);
3563
3564   // Fill in R_AARCH64_LDST64_ABS_LO12
3565   elfcpp::Swap<32, big_endian>::writeval(
3566       pov + 4,
3567       ((this->plt_entry[1] & 0xffc003ff)
3568        | ((gotplt_entry_address & 0xff8) << 7)));
3569
3570   // Fill in R_AARCH64_ADD_ABS_LO12
3571   elfcpp::Swap<32, big_endian>::writeval(
3572       pov + 8,
3573       ((this->plt_entry[2] & 0xffc003ff)
3574        | ((gotplt_entry_address & 0xfff) <<10)));
3575
3576 }
3577
3578
3579 template<>
3580 const uint32_t
3581 Output_data_plt_aarch64_standard<32, false>::
3582     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3583 {
3584   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3585   0x90000002,   /* adrp x2, 0 */
3586   0x90000003,   /* adrp x3, 0 */
3587   0xb9400042,   /* ldr w2, [w2, #0] */
3588   0x11000063,   /* add w3, w3, 0 */
3589   0xd61f0040,   /* br x2 */
3590   0xd503201f,   /* nop */
3591   0xd503201f,   /* nop */
3592 };
3593
3594 template<>
3595 const uint32_t
3596 Output_data_plt_aarch64_standard<32, true>::
3597     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3598 {
3599   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3600   0x90000002,   /* adrp x2, 0 */
3601   0x90000003,   /* adrp x3, 0 */
3602   0xb9400042,   /* ldr w2, [w2, #0] */
3603   0x11000063,   /* add w3, w3, 0 */
3604   0xd61f0040,   /* br x2 */
3605   0xd503201f,   /* nop */
3606   0xd503201f,   /* nop */
3607 };
3608
3609 template<>
3610 const uint32_t
3611 Output_data_plt_aarch64_standard<64, false>::
3612     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3613 {
3614   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3615   0x90000002,   /* adrp x2, 0 */
3616   0x90000003,   /* adrp x3, 0 */
3617   0xf9400042,   /* ldr x2, [x2, #0] */
3618   0x91000063,   /* add x3, x3, 0 */
3619   0xd61f0040,   /* br x2 */
3620   0xd503201f,   /* nop */
3621   0xd503201f,   /* nop */
3622 };
3623
3624 template<>
3625 const uint32_t
3626 Output_data_plt_aarch64_standard<64, true>::
3627     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3628 {
3629   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3630   0x90000002,   /* adrp x2, 0 */
3631   0x90000003,   /* adrp x3, 0 */
3632   0xf9400042,   /* ldr x2, [x2, #0] */
3633   0x91000063,   /* add x3, x3, 0 */
3634   0xd61f0040,   /* br x2 */
3635   0xd503201f,   /* nop */
3636   0xd503201f,   /* nop */
3637 };
3638
3639 template<int size, bool big_endian>
3640 void
3641 Output_data_plt_aarch64_standard<size, big_endian>::do_fill_tlsdesc_entry(
3642     unsigned char* pov,
3643     Address gotplt_address,
3644     Address plt_address,
3645     Address got_base,
3646     unsigned int tlsdesc_got_offset,
3647     unsigned int plt_offset)
3648 {
3649   memcpy(pov, tlsdesc_plt_entry, plt_tlsdesc_entry_size);
3650
3651   // move DT_TLSDESC_GOT address into x2
3652   // move .got.plt address into x3
3653   Address tlsdesc_got_entry = got_base + tlsdesc_got_offset;
3654   Address plt_entry_address = plt_address + plt_offset;
3655
3656   // R_AARCH64_ADR_PREL_PG_HI21
3657   AArch64_relocate_functions<size, big_endian>::adrp(
3658       pov + 4,
3659       tlsdesc_got_entry,
3660       plt_entry_address + 4);
3661
3662   // R_AARCH64_ADR_PREL_PG_HI21
3663   AArch64_relocate_functions<size, big_endian>::adrp(
3664       pov + 8,
3665       gotplt_address,
3666       plt_entry_address + 8);
3667
3668   // R_AARCH64_LDST64_ABS_LO12
3669   elfcpp::Swap<32, big_endian>::writeval(
3670       pov + 12,
3671       ((this->tlsdesc_plt_entry[3] & 0xffc003ff)
3672        | ((tlsdesc_got_entry & 0xff8) << 7)));
3673
3674   // R_AARCH64_ADD_ABS_LO12
3675   elfcpp::Swap<32, big_endian>::writeval(
3676       pov + 16,
3677       ((this->tlsdesc_plt_entry[4] & 0xffc003ff)
3678        | ((gotplt_address & 0xfff) << 10)));
3679 }
3680
3681 // Write out the PLT.  This uses the hand-coded instructions above,
3682 // and adjusts them as needed.  This is specified by the AMD64 ABI.
3683
3684 template<int size, bool big_endian>
3685 void
3686 Output_data_plt_aarch64<size, big_endian>::do_write(Output_file* of)
3687 {
3688   const off_t offset = this->offset();
3689   const section_size_type oview_size =
3690     convert_to_section_size_type(this->data_size());
3691   unsigned char* const oview = of->get_output_view(offset, oview_size);
3692
3693   const off_t got_file_offset = this->got_plt_->offset();
3694   gold_assert(got_file_offset + this->got_plt_->data_size()
3695               == this->got_irelative_->offset());
3696
3697   const section_size_type got_size =
3698       convert_to_section_size_type(this->got_plt_->data_size()
3699                                    + this->got_irelative_->data_size());
3700   unsigned char* const got_view = of->get_output_view(got_file_offset,
3701                                                       got_size);
3702
3703   unsigned char* pov = oview;
3704
3705   // The base address of the .plt section.
3706   typename elfcpp::Elf_types<size>::Elf_Addr plt_address = this->address();
3707   // The base address of the PLT portion of the .got section.
3708   typename elfcpp::Elf_types<size>::Elf_Addr gotplt_address
3709       = this->got_plt_->address();
3710
3711   this->fill_first_plt_entry(pov, gotplt_address, plt_address);
3712   pov += this->first_plt_entry_offset();
3713
3714   // The first three entries in .got.plt are reserved.
3715   unsigned char* got_pov = got_view;
3716   memset(got_pov, 0, size / 8 * AARCH64_GOTPLT_RESERVE_COUNT);
3717   got_pov += (size / 8) * AARCH64_GOTPLT_RESERVE_COUNT;
3718
3719   unsigned int plt_offset = this->first_plt_entry_offset();
3720   unsigned int got_offset = (size / 8) * AARCH64_GOTPLT_RESERVE_COUNT;
3721   const unsigned int count = this->count_ + this->irelative_count_;
3722   for (unsigned int plt_index = 0;
3723        plt_index < count;
3724        ++plt_index,
3725          pov += this->get_plt_entry_size(),
3726          got_pov += size / 8,
3727          plt_offset += this->get_plt_entry_size(),
3728          got_offset += size / 8)
3729     {
3730       // Set and adjust the PLT entry itself.
3731       this->fill_plt_entry(pov, gotplt_address, plt_address,
3732                            got_offset, plt_offset);
3733
3734       // Set the entry in the GOT, which points to plt0.
3735       elfcpp::Swap<size, big_endian>::writeval(got_pov, plt_address);
3736     }
3737
3738   if (this->has_tlsdesc_entry())
3739     {
3740       // Set and adjust the reserved TLSDESC PLT entry.
3741       unsigned int tlsdesc_got_offset = this->get_tlsdesc_got_offset();
3742       // The base address of the .base section.
3743       typename elfcpp::Elf_types<size>::Elf_Addr got_base =
3744           this->got_->address();
3745       this->fill_tlsdesc_entry(pov, gotplt_address, plt_address, got_base,
3746                                tlsdesc_got_offset, plt_offset);
3747       pov += this->get_plt_tlsdesc_entry_size();
3748     }
3749
3750   gold_assert(static_cast<section_size_type>(pov - oview) == oview_size);
3751   gold_assert(static_cast<section_size_type>(got_pov - got_view) == got_size);
3752
3753   of->write_output_view(offset, oview_size, oview);
3754   of->write_output_view(got_file_offset, got_size, got_view);
3755 }
3756
3757 // Telling how to update the immediate field of an instruction.
3758 struct AArch64_howto
3759 {
3760   // The immediate field mask.
3761   elfcpp::Elf_Xword dst_mask;
3762
3763   // The offset to apply relocation immediate
3764   int doffset;
3765
3766   // The second part offset, if the immediate field has two parts.
3767   // -1 if the immediate field has only one part.
3768   int doffset2;
3769 };
3770
3771 static const AArch64_howto aarch64_howto[AArch64_reloc_property::INST_NUM] =
3772 {
3773   {0, -1, -1},          // DATA
3774   {0x1fffe0, 5, -1},    // MOVW  [20:5]-imm16
3775   {0xffffe0, 5, -1},    // LD    [23:5]-imm19
3776   {0x60ffffe0, 29, 5},  // ADR   [30:29]-immlo  [23:5]-immhi
3777   {0x60ffffe0, 29, 5},  // ADRP  [30:29]-immlo  [23:5]-immhi
3778   {0x3ffc00, 10, -1},   // ADD   [21:10]-imm12
3779   {0x3ffc00, 10, -1},   // LDST  [21:10]-imm12
3780   {0x7ffe0, 5, -1},     // TBZNZ [18:5]-imm14
3781   {0xffffe0, 5, -1},    // CONDB [23:5]-imm19
3782   {0x3ffffff, 0, -1},   // B     [25:0]-imm26
3783   {0x3ffffff, 0, -1},   // CALL  [25:0]-imm26
3784 };
3785
3786 // AArch64 relocate function class
3787
3788 template<int size, bool big_endian>
3789 class AArch64_relocate_functions
3790 {
3791  public:
3792   typedef enum
3793   {
3794     STATUS_OKAY,        // No error during relocation.
3795     STATUS_OVERFLOW,    // Relocation overflow.
3796     STATUS_BAD_RELOC,   // Relocation cannot be applied.
3797   } Status;
3798
3799   typedef AArch64_relocate_functions<size, big_endian> This;
3800   typedef typename elfcpp::Elf_types<size>::Elf_Addr Address;
3801   typedef Relocate_info<size, big_endian> The_relocate_info;
3802   typedef AArch64_relobj<size, big_endian> The_aarch64_relobj;
3803   typedef Reloc_stub<size, big_endian> The_reloc_stub;
3804   typedef typename The_reloc_stub::Stub_type The_reloc_stub_type;
3805   typedef Stub_table<size, big_endian> The_stub_table;
3806   typedef elfcpp::Rela<size, big_endian> The_rela;
3807   typedef typename elfcpp::Swap<size, big_endian>::Valtype AArch64_valtype;
3808
3809   // Return the page address of the address.
3810   // Page(address) = address & ~0xFFF
3811
3812   static inline AArch64_valtype
3813   Page(Address address)
3814   {
3815     return (address & (~static_cast<Address>(0xFFF)));
3816   }
3817
3818  private:
3819   // Update instruction (pointed by view) with selected bits (immed).
3820   // val = (val & ~dst_mask) | (immed << doffset)
3821
3822   template<int valsize>
3823   static inline void
3824   update_view(unsigned char* view,
3825               AArch64_valtype immed,
3826               elfcpp::Elf_Xword doffset,
3827               elfcpp::Elf_Xword dst_mask)
3828   {
3829     typedef typename elfcpp::Swap<valsize, big_endian>::Valtype Valtype;
3830     Valtype* wv = reinterpret_cast<Valtype*>(view);
3831     Valtype val = elfcpp::Swap<valsize, big_endian>::readval(wv);
3832
3833     // Clear immediate fields.
3834     val &= ~dst_mask;
3835     elfcpp::Swap<valsize, big_endian>::writeval(wv,
3836       static_cast<Valtype>(val | (immed << doffset)));
3837   }
3838
3839   // Update two parts of an instruction (pointed by view) with selected
3840   // bits (immed1 and immed2).
3841   // val = (val & ~dst_mask) | (immed1 << doffset1) | (immed2 << doffset2)
3842
3843   template<int valsize>
3844   static inline void
3845   update_view_two_parts(
3846     unsigned char* view,
3847     AArch64_valtype immed1,
3848     AArch64_valtype immed2,
3849     elfcpp::Elf_Xword doffset1,
3850     elfcpp::Elf_Xword doffset2,
3851     elfcpp::Elf_Xword dst_mask)
3852   {
3853     typedef typename elfcpp::Swap<valsize, big_endian>::Valtype Valtype;
3854     Valtype* wv = reinterpret_cast<Valtype*>(view);
3855     Valtype val = elfcpp::Swap<valsize, big_endian>::readval(wv);
3856     val &= ~dst_mask;
3857     elfcpp::Swap<valsize, big_endian>::writeval(wv,
3858       static_cast<Valtype>(val | (immed1 << doffset1) |
3859                            (immed2 << doffset2)));
3860   }
3861
3862   // Update adr or adrp instruction with immed.
3863   // In adr and adrp: [30:29] immlo   [23:5] immhi
3864
3865   static inline void
3866   update_adr(unsigned char* view, AArch64_valtype immed)
3867   {
3868     elfcpp::Elf_Xword dst_mask = (0x3 << 29) | (0x7ffff << 5);
3869     This::template update_view_two_parts<32>(
3870       view,
3871       immed & 0x3,
3872       (immed & 0x1ffffc) >> 2,
3873       29,
3874       5,
3875       dst_mask);
3876   }
3877
3878   // Update movz/movn instruction with bits immed.
3879   // Set instruction to movz if is_movz is true, otherwise set instruction
3880   // to movn.
3881
3882   static inline void
3883   update_movnz(unsigned char* view,
3884                AArch64_valtype immed,
3885                bool is_movz)
3886   {
3887     typedef typename elfcpp::Swap<32, big_endian>::Valtype Valtype;
3888     Valtype* wv = reinterpret_cast<Valtype*>(view);
3889     Valtype val = elfcpp::Swap<32, big_endian>::readval(wv);
3890
3891     const elfcpp::Elf_Xword doffset =
3892         aarch64_howto[AArch64_reloc_property::INST_MOVW].doffset;
3893     const elfcpp::Elf_Xword dst_mask =
3894         aarch64_howto[AArch64_reloc_property::INST_MOVW].dst_mask;
3895
3896     // Clear immediate fields and opc code.
3897     val &= ~(dst_mask | (0x3 << 29));
3898
3899     // Set instruction to movz or movn.
3900     // movz: [30:29] is 10   movn: [30:29] is 00
3901     if (is_movz)
3902       val |= (0x2 << 29);
3903
3904     elfcpp::Swap<32, big_endian>::writeval(wv,
3905       static_cast<Valtype>(val | (immed << doffset)));
3906   }
3907
3908   // Update selected bits in text.
3909
3910   template<int valsize>
3911   static inline typename This::Status
3912   reloc_common(unsigned char* view, Address x,
3913                 const AArch64_reloc_property* reloc_property)
3914   {
3915     // Select bits from X.
3916     Address immed = reloc_property->select_x_value(x);
3917
3918     // Update view.
3919     const AArch64_reloc_property::Reloc_inst inst =
3920       reloc_property->reloc_inst();
3921     // If it is a data relocation or instruction has 2 parts of immediate
3922     // fields, you should not call pcrela_general.
3923     gold_assert(aarch64_howto[inst].doffset2 == -1 &&
3924                 aarch64_howto[inst].doffset != -1);
3925     This::template update_view<valsize>(view, immed,
3926                                         aarch64_howto[inst].doffset,
3927                                         aarch64_howto[inst].dst_mask);
3928
3929     // Do check overflow or alignment if needed.
3930     return (reloc_property->checkup_x_value(x)
3931             ? This::STATUS_OKAY
3932             : This::STATUS_OVERFLOW);
3933   }
3934
3935  public:
3936
3937   // Do a simple rela relocation at unaligned addresses.
3938
3939   template<int valsize>
3940   static inline typename This::Status
3941   rela_ua(unsigned char* view,
3942           const Sized_relobj_file<size, big_endian>* object,
3943           const Symbol_value<size>* psymval,
3944           AArch64_valtype addend,
3945           const AArch64_reloc_property* reloc_property)
3946   {
3947     typedef typename elfcpp::Swap_unaligned<valsize, big_endian>::Valtype
3948       Valtype;
3949     typename elfcpp::Elf_types<size>::Elf_Addr x =
3950         psymval->value(object, addend);
3951     elfcpp::Swap_unaligned<valsize, big_endian>::writeval(view,
3952       static_cast<Valtype>(x));
3953     return (reloc_property->checkup_x_value(x)
3954             ? This::STATUS_OKAY
3955             : This::STATUS_OVERFLOW);
3956   }
3957
3958   // Do a simple pc-relative relocation at unaligned addresses.
3959
3960   template<int valsize>
3961   static inline typename This::Status
3962   pcrela_ua(unsigned char* view,
3963             const Sized_relobj_file<size, big_endian>* object,
3964             const Symbol_value<size>* psymval,
3965             AArch64_valtype addend,
3966             Address address,
3967             const AArch64_reloc_property* reloc_property)
3968   {
3969     typedef typename elfcpp::Swap_unaligned<valsize, big_endian>::Valtype
3970       Valtype;
3971     Address x = psymval->value(object, addend) - address;
3972     elfcpp::Swap_unaligned<valsize, big_endian>::writeval(view,
3973       static_cast<Valtype>(x));
3974     return (reloc_property->checkup_x_value(x)
3975             ? This::STATUS_OKAY
3976             : This::STATUS_OVERFLOW);
3977   }
3978
3979   // Do a simple rela relocation at aligned addresses.
3980
3981   template<int valsize>
3982   static inline typename This::Status
3983   rela(
3984     unsigned char* view,
3985     const Sized_relobj_file<size, big_endian>* object,
3986     const Symbol_value<size>* psymval,
3987     AArch64_valtype addend,
3988     const AArch64_reloc_property* reloc_property)
3989   {
3990     typedef typename elfcpp::Swap<valsize, big_endian>::Valtype Valtype;
3991     Valtype* wv = reinterpret_cast<Valtype*>(view);
3992     Address x = psymval->value(object, addend);
3993     elfcpp::Swap<valsize, big_endian>::writeval(wv,static_cast<Valtype>(x));
3994     return (reloc_property->checkup_x_value(x)
3995             ? This::STATUS_OKAY
3996             : This::STATUS_OVERFLOW);
3997   }
3998
3999   // Do relocate. Update selected bits in text.
4000   // new_val = (val & ~dst_mask) | (immed << doffset)
4001
4002   template<int valsize>
4003   static inline typename This::Status
4004   rela_general(unsigned char* view,
4005                const Sized_relobj_file<size, big_endian>* object,
4006                const Symbol_value<size>* psymval,
4007                AArch64_valtype addend,
4008                const AArch64_reloc_property* reloc_property)
4009   {
4010     // Calculate relocation.
4011     Address x = psymval->value(object, addend);
4012     return This::template reloc_common<valsize>(view, x, reloc_property);
4013   }
4014
4015   // Do relocate. Update selected bits in text.
4016   // new val = (val & ~dst_mask) | (immed << doffset)
4017
4018   template<int valsize>
4019   static inline typename This::Status
4020   rela_general(
4021     unsigned char* view,
4022     AArch64_valtype s,
4023     AArch64_valtype addend,
4024     const AArch64_reloc_property* reloc_property)
4025   {
4026     // Calculate relocation.
4027     Address x = s + addend;
4028     return This::template reloc_common<valsize>(view, x, reloc_property);
4029   }
4030
4031   // Do address relative relocate. Update selected bits in text.
4032   // new val = (val & ~dst_mask) | (immed << doffset)
4033
4034   template<int valsize>
4035   static inline typename This::Status
4036   pcrela_general(
4037     unsigned char* view,
4038     const Sized_relobj_file<size, big_endian>* object,
4039     const Symbol_value<size>* psymval,
4040     AArch64_valtype addend,
4041     Address address,
4042     const AArch64_reloc_property* reloc_property)
4043   {
4044     // Calculate relocation.
4045     Address x = psymval->value(object, addend) - address;
4046     return This::template reloc_common<valsize>(view, x, reloc_property);
4047   }
4048
4049
4050   // Calculate (S + A) - address, update adr instruction.
4051
4052   static inline typename This::Status
4053   adr(unsigned char* view,
4054       const Sized_relobj_file<size, big_endian>* object,
4055       const Symbol_value<size>* psymval,
4056       Address addend,
4057       Address address,
4058       const AArch64_reloc_property* /* reloc_property */)
4059   {
4060     AArch64_valtype x = psymval->value(object, addend) - address;
4061     // Pick bits [20:0] of X.
4062     AArch64_valtype immed = x & 0x1fffff;
4063     update_adr(view, immed);
4064     // Check -2^20 <= X < 2^20
4065     return (size == 64 && Bits<21>::has_overflow((x))
4066             ? This::STATUS_OVERFLOW
4067             : This::STATUS_OKAY);
4068   }
4069
4070   // Calculate PG(S+A) - PG(address), update adrp instruction.
4071   // R_AARCH64_ADR_PREL_PG_HI21
4072
4073   static inline typename This::Status
4074   adrp(
4075     unsigned char* view,
4076     Address sa,
4077     Address address)
4078   {
4079     AArch64_valtype x = This::Page(sa) - This::Page(address);
4080     // Pick [32:12] of X.
4081     AArch64_valtype immed = (x >> 12) & 0x1fffff;
4082     update_adr(view, immed);
4083     // Check -2^32 <= X < 2^32
4084     return (size == 64 && Bits<33>::has_overflow((x))
4085             ? This::STATUS_OVERFLOW
4086             : This::STATUS_OKAY);
4087   }
4088
4089   // Calculate PG(S+A) - PG(address), update adrp instruction.
4090   // R_AARCH64_ADR_PREL_PG_HI21
4091
4092   static inline typename This::Status
4093   adrp(unsigned char* view,
4094        const Sized_relobj_file<size, big_endian>* object,
4095        const Symbol_value<size>* psymval,
4096        Address addend,
4097        Address address,
4098        const AArch64_reloc_property* reloc_property)
4099   {
4100     Address sa = psymval->value(object, addend);
4101     AArch64_valtype x = This::Page(sa) - This::Page(address);
4102     // Pick [32:12] of X.
4103     AArch64_valtype immed = (x >> 12) & 0x1fffff;
4104     update_adr(view, immed);
4105     return (reloc_property->checkup_x_value(x)
4106             ? This::STATUS_OKAY
4107             : This::STATUS_OVERFLOW);
4108   }
4109
4110   // Update mov[n/z] instruction. Check overflow if needed.
4111   // If X >=0, set the instruction to movz and its immediate value to the
4112   // selected bits S.
4113   // If X < 0, set the instruction to movn and its immediate value to
4114   // NOT (selected bits of).
4115
4116   static inline typename This::Status
4117   movnz(unsigned char* view,
4118         AArch64_valtype x,
4119         const AArch64_reloc_property* reloc_property)
4120   {
4121     // Select bits from X.
4122     Address immed;
4123     bool is_movz;
4124     typedef typename elfcpp::Elf_types<size>::Elf_Swxword SignedW;
4125     if (static_cast<SignedW>(x) >= 0)
4126       {
4127         immed = reloc_property->select_x_value(x);
4128         is_movz = true;
4129       }
4130     else
4131       {
4132         immed = reloc_property->select_x_value(~x);;
4133         is_movz = false;
4134       }
4135
4136     // Update movnz instruction.
4137     update_movnz(view, immed, is_movz);
4138
4139     // Do check overflow or alignment if needed.
4140     return (reloc_property->checkup_x_value(x)
4141             ? This::STATUS_OKAY
4142             : This::STATUS_OVERFLOW);
4143   }
4144
4145   static inline bool
4146   maybe_apply_stub(unsigned int,
4147                    const The_relocate_info*,
4148                    const The_rela&,
4149                    unsigned char*,
4150                    Address,
4151                    const Sized_symbol<size>*,
4152                    const Symbol_value<size>*,
4153                    const Sized_relobj_file<size, big_endian>*,
4154                    section_size_type);
4155
4156 };  // End of AArch64_relocate_functions
4157
4158
4159 // For a certain relocation type (usually jump/branch), test to see if the
4160 // destination needs a stub to fulfil. If so, re-route the destination of the
4161 // original instruction to the stub, note, at this time, the stub has already
4162 // been generated.
4163
4164 template<int size, bool big_endian>
4165 bool
4166 AArch64_relocate_functions<size, big_endian>::
4167 maybe_apply_stub(unsigned int r_type,
4168                  const The_relocate_info* relinfo,
4169                  const The_rela& rela,
4170                  unsigned char* view,
4171                  Address address,
4172                  const Sized_symbol<size>* gsym,
4173                  const Symbol_value<size>* psymval,
4174                  const Sized_relobj_file<size, big_endian>* object,
4175                  section_size_type current_group_size)
4176 {
4177   if (parameters->options().relocatable())
4178     return false;
4179
4180   typename elfcpp::Elf_types<size>::Elf_Swxword addend = rela.get_r_addend();
4181   Address branch_target = psymval->value(object, 0) + addend;
4182   The_reloc_stub_type stub_type = The_reloc_stub::
4183     stub_type_for_reloc(r_type, address, branch_target);
4184   if (stub_type == The_reloc_stub::ST_NONE)
4185     return false;
4186
4187   const The_aarch64_relobj* aarch64_relobj =
4188       static_cast<const The_aarch64_relobj*>(object);
4189   The_stub_table* stub_table = aarch64_relobj->stub_table(relinfo->data_shndx);
4190   gold_assert(stub_table != NULL);
4191
4192   unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
4193   typename The_reloc_stub::Key stub_key(stub_type, gsym, object, r_sym, addend);
4194   The_reloc_stub* stub = stub_table->find_reloc_stub(stub_key);
4195   gold_assert(stub != NULL);
4196
4197   Address new_branch_target = stub_table->address() + stub->offset();
4198   typename elfcpp::Swap<size, big_endian>::Valtype branch_offset =
4199       new_branch_target - address;
4200   const AArch64_reloc_property* arp =
4201       aarch64_reloc_property_table->get_reloc_property(r_type);
4202   gold_assert(arp != NULL);
4203   typename This::Status status = This::template
4204       rela_general<32>(view, branch_offset, 0, arp);
4205   if (status != This::STATUS_OKAY)
4206     gold_error(_("Stub is too far away, try a smaller value "
4207                  "for '--stub-group-size'. The current value is 0x%lx."),
4208                static_cast<unsigned long>(current_group_size));
4209   return true;
4210 }
4211
4212
4213 // Group input sections for stub generation.
4214 //
4215 // We group input sections in an output section so that the total size,
4216 // including any padding space due to alignment is smaller than GROUP_SIZE
4217 // unless the only input section in group is bigger than GROUP_SIZE already.
4218 // Then an ARM stub table is created to follow the last input section
4219 // in group.  For each group an ARM stub table is created an is placed
4220 // after the last group.  If STUB_ALWAYS_AFTER_BRANCH is false, we further
4221 // extend the group after the stub table.
4222
4223 template<int size, bool big_endian>
4224 void
4225 Target_aarch64<size, big_endian>::group_sections(
4226     Layout* layout,
4227     section_size_type group_size,
4228     bool stubs_always_after_branch,
4229     const Task* task)
4230 {
4231   // Group input sections and insert stub table
4232   Layout::Section_list section_list;
4233   layout->get_executable_sections(&section_list);
4234   for (Layout::Section_list::const_iterator p = section_list.begin();
4235        p != section_list.end();
4236        ++p)
4237     {
4238       AArch64_output_section<size, big_endian>* output_section =
4239           static_cast<AArch64_output_section<size, big_endian>*>(*p);
4240       output_section->group_sections(group_size, stubs_always_after_branch,
4241                                      this, task);
4242     }
4243 }
4244
4245
4246 // Find the AArch64_input_section object corresponding to the SHNDX-th input
4247 // section of RELOBJ.
4248
4249 template<int size, bool big_endian>
4250 AArch64_input_section<size, big_endian>*
4251 Target_aarch64<size, big_endian>::find_aarch64_input_section(
4252     Relobj* relobj, unsigned int shndx) const
4253 {
4254   Section_id sid(relobj, shndx);
4255   typename AArch64_input_section_map::const_iterator p =
4256     this->aarch64_input_section_map_.find(sid);
4257   return (p != this->aarch64_input_section_map_.end()) ? p->second : NULL;
4258 }
4259
4260
4261 // Make a new AArch64_input_section object.
4262
4263 template<int size, bool big_endian>
4264 AArch64_input_section<size, big_endian>*
4265 Target_aarch64<size, big_endian>::new_aarch64_input_section(
4266     Relobj* relobj, unsigned int shndx)
4267 {
4268   Section_id sid(relobj, shndx);
4269
4270   AArch64_input_section<size, big_endian>* input_section =
4271       new AArch64_input_section<size, big_endian>(relobj, shndx);
4272   input_section->init();
4273
4274   // Register new AArch64_input_section in map for look-up.
4275   std::pair<typename AArch64_input_section_map::iterator,bool> ins =
4276       this->aarch64_input_section_map_.insert(
4277           std::make_pair(sid, input_section));
4278
4279   // Make sure that it we have not created another AArch64_input_section
4280   // for this input section already.
4281   gold_assert(ins.second);
4282
4283   return input_section;
4284 }
4285
4286
4287 // Relaxation hook.  This is where we do stub generation.
4288
4289 template<int size, bool big_endian>
4290 bool
4291 Target_aarch64<size, big_endian>::do_relax(
4292     int pass,
4293     const Input_objects* input_objects,
4294     Symbol_table* symtab,
4295     Layout* layout ,
4296     const Task* task)
4297 {
4298   gold_assert(!parameters->options().relocatable());
4299   if (pass == 1)
4300     {
4301       // We don't handle negative stub_group_size right now.
4302       this->stub_group_size_ = abs(parameters->options().stub_group_size());
4303       if (this->stub_group_size_ == 1)
4304         {
4305           // Leave room for 4096 4-byte stub entries. If we exceed that, then we
4306           // will fail to link.  The user will have to relink with an explicit
4307           // group size option.
4308           this->stub_group_size_ = The_reloc_stub::MAX_BRANCH_OFFSET -
4309                                    4096 * 4;
4310         }
4311       group_sections(layout, this->stub_group_size_, true, task);
4312     }
4313   else
4314     {
4315       // If this is not the first pass, addresses and file offsets have
4316       // been reset at this point, set them here.
4317       for (Stub_table_iterator sp = this->stub_tables_.begin();
4318            sp != this->stub_tables_.end(); ++sp)
4319         {
4320           The_stub_table* stt = *sp;
4321           The_aarch64_input_section* owner = stt->owner();
4322           off_t off = align_address(owner->original_size(),
4323                                     stt->addralign());
4324           stt->set_address_and_file_offset(owner->address() + off,
4325                                            owner->offset() + off);
4326         }
4327     }
4328
4329   // Scan relocs for relocation stubs
4330   for (Input_objects::Relobj_iterator op = input_objects->relobj_begin();
4331        op != input_objects->relobj_end();
4332        ++op)
4333     {
4334       The_aarch64_relobj* aarch64_relobj =
4335           static_cast<The_aarch64_relobj*>(*op);
4336       // Lock the object so we can read from it.  This is only called
4337       // single-threaded from Layout::finalize, so it is OK to lock.
4338       Task_lock_obj<Object> tl(task, aarch64_relobj);
4339       aarch64_relobj->scan_sections_for_stubs(this, symtab, layout);
4340     }
4341
4342   bool any_stub_table_changed = false;
4343   for (Stub_table_iterator siter = this->stub_tables_.begin();
4344        siter != this->stub_tables_.end() && !any_stub_table_changed; ++siter)
4345     {
4346       The_stub_table* stub_table = *siter;
4347       if (stub_table->update_data_size_changed_p())
4348         {
4349           The_aarch64_input_section* owner = stub_table->owner();
4350           uint64_t address = owner->address();
4351           off_t offset = owner->offset();
4352           owner->reset_address_and_file_offset();
4353           owner->set_address_and_file_offset(address, offset);
4354
4355           any_stub_table_changed = true;
4356         }
4357     }
4358
4359   // Do not continue relaxation.
4360   bool continue_relaxation = any_stub_table_changed;
4361   if (!continue_relaxation)
4362     for (Stub_table_iterator sp = this->stub_tables_.begin();
4363          (sp != this->stub_tables_.end());
4364          ++sp)
4365       (*sp)->finalize_stubs();
4366
4367   return continue_relaxation;
4368 }
4369
4370
4371 // Make a new Stub_table.
4372
4373 template<int size, bool big_endian>
4374 Stub_table<size, big_endian>*
4375 Target_aarch64<size, big_endian>::new_stub_table(
4376     AArch64_input_section<size, big_endian>* owner)
4377 {
4378   Stub_table<size, big_endian>* stub_table =
4379       new Stub_table<size, big_endian>(owner);
4380   stub_table->set_address(align_address(
4381       owner->address() + owner->data_size(), 8));
4382   stub_table->set_file_offset(owner->offset() + owner->data_size());
4383   stub_table->finalize_data_size();
4384
4385   this->stub_tables_.push_back(stub_table);
4386
4387   return stub_table;
4388 }
4389
4390
4391 template<int size, bool big_endian>
4392 typename elfcpp::Elf_types<size>::Elf_Addr
4393 Target_aarch64<size, big_endian>::do_reloc_addend(
4394     void* arg, unsigned int r_type,
4395     typename elfcpp::Elf_types<size>::Elf_Addr) const
4396 {
4397   gold_assert(r_type == elfcpp::R_AARCH64_TLSDESC);
4398   uintptr_t intarg = reinterpret_cast<uintptr_t>(arg);
4399   gold_assert(intarg < this->tlsdesc_reloc_info_.size());
4400   const Tlsdesc_info& ti(this->tlsdesc_reloc_info_[intarg]);
4401   const Symbol_value<size>* psymval = ti.object->local_symbol(ti.r_sym);
4402   gold_assert(psymval->is_tls_symbol());
4403   // The value of a TLS symbol is the offset in the TLS segment.
4404   return psymval->value(ti.object, 0);
4405 }
4406
4407 // Return the number of entries in the PLT.
4408
4409 template<int size, bool big_endian>
4410 unsigned int
4411 Target_aarch64<size, big_endian>::plt_entry_count() const
4412 {
4413   if (this->plt_ == NULL)
4414     return 0;
4415   return this->plt_->entry_count();
4416 }
4417
4418 // Return the offset of the first non-reserved PLT entry.
4419
4420 template<int size, bool big_endian>
4421 unsigned int
4422 Target_aarch64<size, big_endian>::first_plt_entry_offset() const
4423 {
4424   return this->plt_->first_plt_entry_offset();
4425 }
4426
4427 // Return the size of each PLT entry.
4428
4429 template<int size, bool big_endian>
4430 unsigned int
4431 Target_aarch64<size, big_endian>::plt_entry_size() const
4432 {
4433   return this->plt_->get_plt_entry_size();
4434 }
4435
4436 // Define the _TLS_MODULE_BASE_ symbol in the TLS segment.
4437
4438 template<int size, bool big_endian>
4439 void
4440 Target_aarch64<size, big_endian>::define_tls_base_symbol(
4441     Symbol_table* symtab, Layout* layout)
4442 {
4443   if (this->tls_base_symbol_defined_)
4444     return;
4445
4446   Output_segment* tls_segment = layout->tls_segment();
4447   if (tls_segment != NULL)
4448     {
4449       // _TLS_MODULE_BASE_ always points to the beginning of tls segment.
4450       symtab->define_in_output_segment("_TLS_MODULE_BASE_", NULL,
4451                                        Symbol_table::PREDEFINED,
4452                                        tls_segment, 0, 0,
4453                                        elfcpp::STT_TLS,
4454                                        elfcpp::STB_LOCAL,
4455                                        elfcpp::STV_HIDDEN, 0,
4456                                        Symbol::SEGMENT_START,
4457                                        true);
4458     }
4459   this->tls_base_symbol_defined_ = true;
4460 }
4461
4462 // Create the reserved PLT and GOT entries for the TLS descriptor resolver.
4463
4464 template<int size, bool big_endian>
4465 void
4466 Target_aarch64<size, big_endian>::reserve_tlsdesc_entries(
4467     Symbol_table* symtab, Layout* layout)
4468 {
4469   if (this->plt_ == NULL)
4470     this->make_plt_section(symtab, layout);
4471
4472   if (!this->plt_->has_tlsdesc_entry())
4473     {
4474       // Allocate the TLSDESC_GOT entry.
4475       Output_data_got_aarch64<size, big_endian>* got =
4476           this->got_section(symtab, layout);
4477       unsigned int got_offset = got->add_constant(0);
4478
4479       // Allocate the TLSDESC_PLT entry.
4480       this->plt_->reserve_tlsdesc_entry(got_offset);
4481     }
4482 }
4483
4484 // Create a GOT entry for the TLS module index.
4485
4486 template<int size, bool big_endian>
4487 unsigned int
4488 Target_aarch64<size, big_endian>::got_mod_index_entry(
4489     Symbol_table* symtab, Layout* layout,
4490     Sized_relobj_file<size, big_endian>* object)
4491 {
4492   if (this->got_mod_index_offset_ == -1U)
4493     {
4494       gold_assert(symtab != NULL && layout != NULL && object != NULL);
4495       Reloc_section* rela_dyn = this->rela_dyn_section(layout);
4496       Output_data_got_aarch64<size, big_endian>* got =
4497           this->got_section(symtab, layout);
4498       unsigned int got_offset = got->add_constant(0);
4499       rela_dyn->add_local(object, 0, elfcpp::R_AARCH64_TLS_DTPMOD64, got,
4500                           got_offset, 0);
4501       got->add_constant(0);
4502       this->got_mod_index_offset_ = got_offset;
4503     }
4504   return this->got_mod_index_offset_;
4505 }
4506
4507 // Optimize the TLS relocation type based on what we know about the
4508 // symbol.  IS_FINAL is true if the final address of this symbol is
4509 // known at link time.
4510
4511 template<int size, bool big_endian>
4512 tls::Tls_optimization
4513 Target_aarch64<size, big_endian>::optimize_tls_reloc(bool is_final,
4514                                                      int r_type)
4515 {
4516   // If we are generating a shared library, then we can't do anything
4517   // in the linker
4518   if (parameters->options().shared())
4519     return tls::TLSOPT_NONE;
4520
4521   switch (r_type)
4522     {
4523     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
4524     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
4525     case elfcpp::R_AARCH64_TLSDESC_LD_PREL19:
4526     case elfcpp::R_AARCH64_TLSDESC_ADR_PREL21:
4527     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
4528     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
4529     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
4530     case elfcpp::R_AARCH64_TLSDESC_OFF_G1:
4531     case elfcpp::R_AARCH64_TLSDESC_OFF_G0_NC:
4532     case elfcpp::R_AARCH64_TLSDESC_LDR:
4533     case elfcpp::R_AARCH64_TLSDESC_ADD:
4534     case elfcpp::R_AARCH64_TLSDESC_CALL:
4535       // These are General-Dynamic which permits fully general TLS
4536       // access.  Since we know that we are generating an executable,
4537       // we can convert this to Initial-Exec.  If we also know that
4538       // this is a local symbol, we can further switch to Local-Exec.
4539       if (is_final)
4540         return tls::TLSOPT_TO_LE;
4541       return tls::TLSOPT_TO_IE;
4542
4543     case elfcpp::R_AARCH64_TLSLD_ADR_PAGE21:
4544     case elfcpp::R_AARCH64_TLSLD_ADD_LO12_NC:
4545     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G1:
4546     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G0_NC:
4547     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_HI12:
4548     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_LO12_NC:
4549       // These are Local-Dynamic, which refer to local symbols in the
4550       // dynamic TLS block. Since we know that we generating an
4551       // executable, we can switch to Local-Exec.
4552       return tls::TLSOPT_TO_LE;
4553
4554     case elfcpp::R_AARCH64_TLSIE_MOVW_GOTTPREL_G1:
4555     case elfcpp::R_AARCH64_TLSIE_MOVW_GOTTPREL_G0_NC:
4556     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4557     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
4558     case elfcpp::R_AARCH64_TLSIE_LD_GOTTPREL_PREL19:
4559       // These are Initial-Exec relocs which get the thread offset
4560       // from the GOT. If we know that we are linking against the
4561       // local symbol, we can switch to Local-Exec, which links the
4562       // thread offset into the instruction.
4563       if (is_final)
4564         return tls::TLSOPT_TO_LE;
4565       return tls::TLSOPT_NONE;
4566
4567     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G2:
4568     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1:
4569     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
4570     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0:
4571     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
4572     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
4573     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
4574     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
4575       // When we already have Local-Exec, there is nothing further we
4576       // can do.
4577       return tls::TLSOPT_NONE;
4578
4579     default:
4580       gold_unreachable();
4581     }
4582 }
4583
4584 // Returns true if this relocation type could be that of a function pointer.
4585
4586 template<int size, bool big_endian>
4587 inline bool
4588 Target_aarch64<size, big_endian>::Scan::possible_function_pointer_reloc(
4589   unsigned int r_type)
4590 {
4591   switch (r_type)
4592     {
4593     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21:
4594     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21_NC:
4595     case elfcpp::R_AARCH64_ADD_ABS_LO12_NC:
4596     case elfcpp::R_AARCH64_ADR_GOT_PAGE:
4597     case elfcpp::R_AARCH64_LD64_GOT_LO12_NC:
4598       {
4599         return true;
4600       }
4601     }
4602   return false;
4603 }
4604
4605 // For safe ICF, scan a relocation for a local symbol to check if it
4606 // corresponds to a function pointer being taken.  In that case mark
4607 // the function whose pointer was taken as not foldable.
4608
4609 template<int size, bool big_endian>
4610 inline bool
4611 Target_aarch64<size, big_endian>::Scan::local_reloc_may_be_function_pointer(
4612   Symbol_table* ,
4613   Layout* ,
4614   Target_aarch64<size, big_endian>* ,
4615   Sized_relobj_file<size, big_endian>* ,
4616   unsigned int ,
4617   Output_section* ,
4618   const elfcpp::Rela<size, big_endian>& ,
4619   unsigned int r_type,
4620   const elfcpp::Sym<size, big_endian>&)
4621 {
4622   // When building a shared library, do not fold any local symbols.
4623   return (parameters->options().shared()
4624           || possible_function_pointer_reloc(r_type));
4625 }
4626
4627 // For safe ICF, scan a relocation for a global symbol to check if it
4628 // corresponds to a function pointer being taken.  In that case mark
4629 // the function whose pointer was taken as not foldable.
4630
4631 template<int size, bool big_endian>
4632 inline bool
4633 Target_aarch64<size, big_endian>::Scan::global_reloc_may_be_function_pointer(
4634   Symbol_table* ,
4635   Layout* ,
4636   Target_aarch64<size, big_endian>* ,
4637   Sized_relobj_file<size, big_endian>* ,
4638   unsigned int ,
4639   Output_section* ,
4640   const elfcpp::Rela<size, big_endian>& ,
4641   unsigned int r_type,
4642   Symbol* gsym)
4643 {
4644   // When building a shared library, do not fold symbols whose visibility
4645   // is hidden, internal or protected.
4646   return ((parameters->options().shared()
4647            && (gsym->visibility() == elfcpp::STV_INTERNAL
4648                || gsym->visibility() == elfcpp::STV_PROTECTED
4649                || gsym->visibility() == elfcpp::STV_HIDDEN))
4650           || possible_function_pointer_reloc(r_type));
4651 }
4652
4653 // Report an unsupported relocation against a local symbol.
4654
4655 template<int size, bool big_endian>
4656 void
4657 Target_aarch64<size, big_endian>::Scan::unsupported_reloc_local(
4658      Sized_relobj_file<size, big_endian>* object,
4659      unsigned int r_type)
4660 {
4661   gold_error(_("%s: unsupported reloc %u against local symbol"),
4662              object->name().c_str(), r_type);
4663 }
4664
4665 // We are about to emit a dynamic relocation of type R_TYPE.  If the
4666 // dynamic linker does not support it, issue an error.
4667
4668 template<int size, bool big_endian>
4669 void
4670 Target_aarch64<size, big_endian>::Scan::check_non_pic(Relobj* object,
4671                                                       unsigned int r_type)
4672 {
4673   gold_assert(r_type != elfcpp::R_AARCH64_NONE);
4674
4675   switch (r_type)
4676     {
4677     // These are the relocation types supported by glibc for AARCH64.
4678     case elfcpp::R_AARCH64_NONE:
4679     case elfcpp::R_AARCH64_COPY:
4680     case elfcpp::R_AARCH64_GLOB_DAT:
4681     case elfcpp::R_AARCH64_JUMP_SLOT:
4682     case elfcpp::R_AARCH64_RELATIVE:
4683     case elfcpp::R_AARCH64_TLS_DTPREL64:
4684     case elfcpp::R_AARCH64_TLS_DTPMOD64:
4685     case elfcpp::R_AARCH64_TLS_TPREL64:
4686     case elfcpp::R_AARCH64_TLSDESC:
4687     case elfcpp::R_AARCH64_IRELATIVE:
4688     case elfcpp::R_AARCH64_ABS32:
4689     case elfcpp::R_AARCH64_ABS64:
4690       return;
4691
4692     default:
4693       break;
4694     }
4695
4696   // This prevents us from issuing more than one error per reloc
4697   // section. But we can still wind up issuing more than one
4698   // error per object file.
4699   if (this->issued_non_pic_error_)
4700     return;
4701   gold_assert(parameters->options().output_is_position_independent());
4702   object->error(_("requires unsupported dynamic reloc; "
4703                   "recompile with -fPIC"));
4704   this->issued_non_pic_error_ = true;
4705   return;
4706 }
4707
4708 // Return whether we need to make a PLT entry for a relocation of the
4709 // given type against a STT_GNU_IFUNC symbol.
4710
4711 template<int size, bool big_endian>
4712 bool
4713 Target_aarch64<size, big_endian>::Scan::reloc_needs_plt_for_ifunc(
4714     Sized_relobj_file<size, big_endian>* object,
4715     unsigned int r_type)
4716 {
4717   const AArch64_reloc_property* arp =
4718       aarch64_reloc_property_table->get_reloc_property(r_type);
4719   gold_assert(arp != NULL);
4720
4721   int flags = arp->reference_flags();
4722   if (flags & Symbol::TLS_REF)
4723     {
4724       gold_error(_("%s: unsupported TLS reloc %s for IFUNC symbol"),
4725                  object->name().c_str(), arp->name().c_str());
4726       return false;
4727     }
4728   return flags != 0;
4729 }
4730
4731 // Scan a relocation for a local symbol.
4732
4733 template<int size, bool big_endian>
4734 inline void
4735 Target_aarch64<size, big_endian>::Scan::local(
4736     Symbol_table* symtab,
4737     Layout* layout,
4738     Target_aarch64<size, big_endian>* target,
4739     Sized_relobj_file<size, big_endian>* object,
4740     unsigned int data_shndx,
4741     Output_section* output_section,
4742     const elfcpp::Rela<size, big_endian>& rela,
4743     unsigned int r_type,
4744     const elfcpp::Sym<size, big_endian>& lsym,
4745     bool is_discarded)
4746 {
4747   if (is_discarded)
4748     return;
4749
4750   typedef Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>
4751       Reloc_section;
4752   Output_data_got_aarch64<size, big_endian>* got =
4753       target->got_section(symtab, layout);
4754   unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
4755
4756   // A local STT_GNU_IFUNC symbol may require a PLT entry.
4757   bool is_ifunc = lsym.get_st_type() == elfcpp::STT_GNU_IFUNC;
4758   if (is_ifunc && this->reloc_needs_plt_for_ifunc(object, r_type))
4759     target->make_local_ifunc_plt_entry(symtab, layout, object, r_sym);
4760
4761   switch (r_type)
4762     {
4763     case elfcpp::R_AARCH64_ABS32:
4764     case elfcpp::R_AARCH64_ABS16:
4765       if (parameters->options().output_is_position_independent())
4766         {
4767           gold_error(_("%s: unsupported reloc %u in pos independent link."),
4768                      object->name().c_str(), r_type);
4769         }
4770       break;
4771
4772     case elfcpp::R_AARCH64_ABS64:
4773       // If building a shared library or pie, we need to mark this as a dynmic
4774       // reloction, so that the dynamic loader can relocate it.
4775       if (parameters->options().output_is_position_independent())
4776         {
4777           Reloc_section* rela_dyn = target->rela_dyn_section(layout);
4778           rela_dyn->add_local_relative(object, r_sym,
4779                                        elfcpp::R_AARCH64_RELATIVE,
4780                                        output_section,
4781                                        data_shndx,
4782                                        rela.get_r_offset(),
4783                                        rela.get_r_addend(),
4784                                        is_ifunc);
4785         }
4786       break;
4787
4788     case elfcpp::R_AARCH64_PREL64:
4789     case elfcpp::R_AARCH64_PREL32:
4790     case elfcpp::R_AARCH64_PREL16:
4791       break;
4792
4793     case elfcpp::R_AARCH64_LD_PREL_LO19:        // 273
4794     case elfcpp::R_AARCH64_ADR_PREL_LO21:       // 274
4795     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21:    // 275
4796     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21_NC: // 276
4797     case elfcpp::R_AARCH64_ADD_ABS_LO12_NC:     // 277
4798     case elfcpp::R_AARCH64_LDST8_ABS_LO12_NC:   // 278
4799     case elfcpp::R_AARCH64_LDST16_ABS_LO12_NC:  // 284
4800     case elfcpp::R_AARCH64_LDST32_ABS_LO12_NC:  // 285
4801     case elfcpp::R_AARCH64_LDST64_ABS_LO12_NC:  // 286
4802     case elfcpp::R_AARCH64_LDST128_ABS_LO12_NC: // 299
4803        break;
4804
4805     // Control flow, pc-relative. We don't need to do anything for a relative
4806     // addressing relocation against a local symbol if it does not reference
4807     // the GOT.
4808     case elfcpp::R_AARCH64_TSTBR14:
4809     case elfcpp::R_AARCH64_CONDBR19:
4810     case elfcpp::R_AARCH64_JUMP26:
4811     case elfcpp::R_AARCH64_CALL26:
4812       break;
4813
4814     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4815     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
4816       {
4817         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4818           optimize_tls_reloc(!parameters->options().shared(), r_type);
4819         if (tlsopt == tls::TLSOPT_TO_LE)
4820           break;
4821
4822         layout->set_has_static_tls();
4823         // Create a GOT entry for the tp-relative offset.
4824         if (!parameters->doing_static_link())
4825           {
4826             got->add_local_with_rel(object, r_sym, GOT_TYPE_TLS_OFFSET,
4827                                     target->rela_dyn_section(layout),
4828                                     elfcpp::R_AARCH64_TLS_TPREL64);
4829           }
4830         else if (!object->local_has_got_offset(r_sym,
4831                                                GOT_TYPE_TLS_OFFSET))
4832           {
4833             got->add_local(object, r_sym, GOT_TYPE_TLS_OFFSET);
4834             unsigned int got_offset =
4835                 object->local_got_offset(r_sym, GOT_TYPE_TLS_OFFSET);
4836             const elfcpp::Elf_Xword addend = rela.get_r_addend();
4837             gold_assert(addend == 0);
4838             got->add_static_reloc(got_offset, elfcpp::R_AARCH64_TLS_TPREL64,
4839                                   object, r_sym);
4840           }
4841       }
4842       break;
4843
4844     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
4845     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
4846       {
4847         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4848             optimize_tls_reloc(!parameters->options().shared(), r_type);
4849         if (tlsopt == tls::TLSOPT_TO_LE)
4850           {
4851             layout->set_has_static_tls();
4852             break;
4853           }
4854         gold_assert(tlsopt == tls::TLSOPT_NONE);
4855
4856         got->add_local_pair_with_rel(object,r_sym, data_shndx,
4857                                      GOT_TYPE_TLS_PAIR,
4858                                      target->rela_dyn_section(layout),
4859                                      elfcpp::R_AARCH64_TLS_DTPMOD64);
4860       }
4861       break;
4862
4863     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G2:
4864     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1:
4865     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
4866     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0:
4867     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
4868     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
4869     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
4870     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
4871       {
4872         layout->set_has_static_tls();
4873         bool output_is_shared = parameters->options().shared();
4874         if (output_is_shared)
4875           gold_error(_("%s: unsupported TLSLE reloc %u in shared code."),
4876                      object->name().c_str(), r_type);
4877       }
4878       break;
4879
4880     case elfcpp::R_AARCH64_TLSLD_ADR_PAGE21:
4881     case elfcpp::R_AARCH64_TLSLD_ADD_LO12_NC:
4882       {
4883         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4884             optimize_tls_reloc(!parameters->options().shared(), r_type);
4885         if (tlsopt == tls::TLSOPT_NONE)
4886           {
4887             // Create a GOT entry for the module index.
4888             target->got_mod_index_entry(symtab, layout, object);
4889           }
4890         else if (tlsopt != tls::TLSOPT_TO_LE)
4891           unsupported_reloc_local(object, r_type);
4892       }
4893       break;
4894
4895     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G1:
4896     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G0_NC:
4897     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_HI12:
4898     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_LO12_NC:
4899       break;
4900
4901     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
4902     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
4903     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
4904       {
4905         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4906             optimize_tls_reloc(!parameters->options().shared(), r_type);
4907         target->define_tls_base_symbol(symtab, layout);
4908         if (tlsopt == tls::TLSOPT_NONE)
4909           {
4910             // Create reserved PLT and GOT entries for the resolver.
4911             target->reserve_tlsdesc_entries(symtab, layout);
4912
4913             // Generate a double GOT entry with an R_AARCH64_TLSDESC reloc.
4914             // The R_AARCH64_TLSDESC reloc is resolved lazily, so the GOT
4915             // entry needs to be in an area in .got.plt, not .got. Call
4916             // got_section to make sure the section has been created.
4917             target->got_section(symtab, layout);
4918             Output_data_got<size, big_endian>* got =
4919                 target->got_tlsdesc_section();
4920             unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
4921             if (!object->local_has_got_offset(r_sym, GOT_TYPE_TLS_DESC))
4922               {
4923                 unsigned int got_offset = got->add_constant(0);
4924                 got->add_constant(0);
4925                 object->set_local_got_offset(r_sym, GOT_TYPE_TLS_DESC,
4926                                              got_offset);
4927                 Reloc_section* rt = target->rela_tlsdesc_section(layout);
4928                 // We store the arguments we need in a vector, and use
4929                 // the index into the vector as the parameter to pass
4930                 // to the target specific routines.
4931                 uintptr_t intarg = target->add_tlsdesc_info(object, r_sym);
4932                 void* arg = reinterpret_cast<void*>(intarg);
4933                 rt->add_target_specific(elfcpp::R_AARCH64_TLSDESC, arg,
4934                                         got, got_offset, 0);
4935               }
4936           }
4937         else if (tlsopt != tls::TLSOPT_TO_LE)
4938           unsupported_reloc_local(object, r_type);
4939       }
4940       break;
4941
4942     case elfcpp::R_AARCH64_TLSDESC_CALL:
4943       break;
4944
4945     default:
4946       unsupported_reloc_local(object, r_type);
4947     }
4948 }
4949
4950
4951 // Report an unsupported relocation against a global symbol.
4952
4953 template<int size, bool big_endian>
4954 void
4955 Target_aarch64<size, big_endian>::Scan::unsupported_reloc_global(
4956     Sized_relobj_file<size, big_endian>* object,
4957     unsigned int r_type,
4958     Symbol* gsym)
4959 {
4960   gold_error(_("%s: unsupported reloc %u against global symbol %s"),
4961              object->name().c_str(), r_type, gsym->demangled_name().c_str());
4962 }
4963
4964 template<int size, bool big_endian>
4965 inline void
4966 Target_aarch64<size, big_endian>::Scan::global(
4967     Symbol_table* symtab,
4968     Layout* layout,
4969     Target_aarch64<size, big_endian>* target,
4970     Sized_relobj_file<size, big_endian> * object,
4971     unsigned int data_shndx,
4972     Output_section* output_section,
4973     const elfcpp::Rela<size, big_endian>& rela,
4974     unsigned int r_type,
4975     Symbol* gsym)
4976 {
4977   // A STT_GNU_IFUNC symbol may require a PLT entry.
4978   if (gsym->type() == elfcpp::STT_GNU_IFUNC
4979       && this->reloc_needs_plt_for_ifunc(object, r_type))
4980     target->make_plt_entry(symtab, layout, gsym);
4981
4982   typedef Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>
4983     Reloc_section;
4984   const AArch64_reloc_property* arp =
4985       aarch64_reloc_property_table->get_reloc_property(r_type);
4986   gold_assert(arp != NULL);
4987
4988   switch (r_type)
4989     {
4990     case elfcpp::R_AARCH64_ABS16:
4991     case elfcpp::R_AARCH64_ABS32:
4992     case elfcpp::R_AARCH64_ABS64:
4993       {
4994         // Make a PLT entry if necessary.
4995         if (gsym->needs_plt_entry())
4996           {
4997             target->make_plt_entry(symtab, layout, gsym);
4998             // Since this is not a PC-relative relocation, we may be
4999             // taking the address of a function. In that case we need to
5000             // set the entry in the dynamic symbol table to the address of
5001             // the PLT entry.
5002             if (gsym->is_from_dynobj() && !parameters->options().shared())
5003               gsym->set_needs_dynsym_value();
5004           }
5005         // Make a dynamic relocation if necessary.
5006         if (gsym->needs_dynamic_reloc(arp->reference_flags()))
5007           {
5008             if (!parameters->options().output_is_position_independent()
5009                 && gsym->may_need_copy_reloc())
5010               {
5011                 target->copy_reloc(symtab, layout, object,
5012                                    data_shndx, output_section, gsym, rela);
5013               }
5014             else if (r_type == elfcpp::R_AARCH64_ABS64
5015                      && gsym->type() == elfcpp::STT_GNU_IFUNC
5016                      && gsym->can_use_relative_reloc(false)
5017                      && !gsym->is_from_dynobj()
5018                      && !gsym->is_undefined()
5019                      && !gsym->is_preemptible())
5020               {
5021                 // Use an IRELATIVE reloc for a locally defined STT_GNU_IFUNC
5022                 // symbol. This makes a function address in a PIE executable
5023                 // match the address in a shared library that it links against.
5024                 Reloc_section* rela_dyn =
5025                     target->rela_irelative_section(layout);
5026                 unsigned int r_type = elfcpp::R_AARCH64_IRELATIVE;
5027                 rela_dyn->add_symbolless_global_addend(gsym, r_type,
5028                                                        output_section, object,
5029                                                        data_shndx,
5030                                                        rela.get_r_offset(),
5031                                                        rela.get_r_addend());
5032               }
5033             else if (r_type == elfcpp::R_AARCH64_ABS64
5034                      && gsym->can_use_relative_reloc(false))
5035               {
5036                 Reloc_section* rela_dyn = target->rela_dyn_section(layout);
5037                 rela_dyn->add_global_relative(gsym,
5038                                               elfcpp::R_AARCH64_RELATIVE,
5039                                               output_section,
5040                                               object,
5041                                               data_shndx,
5042                                               rela.get_r_offset(),
5043                                               rela.get_r_addend(),
5044                                               false);
5045               }
5046             else
5047               {
5048                 check_non_pic(object, r_type);
5049                 Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>*
5050                     rela_dyn = target->rela_dyn_section(layout);
5051                 rela_dyn->add_global(
5052                   gsym, r_type, output_section, object,
5053                   data_shndx, rela.get_r_offset(),rela.get_r_addend());
5054               }
5055           }
5056       }
5057       break;
5058
5059     case elfcpp::R_AARCH64_PREL16:
5060     case elfcpp::R_AARCH64_PREL32:
5061     case elfcpp::R_AARCH64_PREL64:
5062       // This is used to fill the GOT absolute address.
5063       if (gsym->needs_plt_entry())
5064         {
5065           target->make_plt_entry(symtab, layout, gsym);
5066         }
5067       break;
5068
5069     case elfcpp::R_AARCH64_LD_PREL_LO19:        // 273
5070     case elfcpp::R_AARCH64_ADR_PREL_LO21:       // 274
5071     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21:    // 275
5072     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21_NC: // 276
5073     case elfcpp::R_AARCH64_ADD_ABS_LO12_NC:     // 277
5074     case elfcpp::R_AARCH64_LDST8_ABS_LO12_NC:   // 278
5075     case elfcpp::R_AARCH64_LDST16_ABS_LO12_NC:  // 284
5076     case elfcpp::R_AARCH64_LDST32_ABS_LO12_NC:  // 285
5077     case elfcpp::R_AARCH64_LDST64_ABS_LO12_NC:  // 286
5078     case elfcpp::R_AARCH64_LDST128_ABS_LO12_NC: // 299
5079       {
5080         if (gsym->needs_plt_entry())
5081           target->make_plt_entry(symtab, layout, gsym);
5082         // Make a dynamic relocation if necessary.
5083         if (gsym->needs_dynamic_reloc(arp->reference_flags()))
5084           {
5085             if (parameters->options().output_is_executable()
5086                 && gsym->may_need_copy_reloc())
5087               {
5088                 target->copy_reloc(symtab, layout, object,
5089                                    data_shndx, output_section, gsym, rela);
5090               }
5091           }
5092         break;
5093       }
5094
5095     case elfcpp::R_AARCH64_ADR_GOT_PAGE:
5096     case elfcpp::R_AARCH64_LD64_GOT_LO12_NC:
5097       {
5098         // This pair of relocations is used to access a specific GOT entry.
5099         // Note a GOT entry is an *address* to a symbol.
5100         // The symbol requires a GOT entry
5101         Output_data_got_aarch64<size, big_endian>* got =
5102           target->got_section(symtab, layout);
5103         if (gsym->final_value_is_known())
5104           {
5105             // For a STT_GNU_IFUNC symbol we want the PLT address.
5106             if (gsym->type() == elfcpp::STT_GNU_IFUNC)
5107               got->add_global_plt(gsym, GOT_TYPE_STANDARD);
5108             else
5109               got->add_global(gsym, GOT_TYPE_STANDARD);
5110           }
5111         else
5112           {
5113             // If this symbol is not fully resolved, we need to add a dynamic
5114             // relocation for it.
5115             Reloc_section* rela_dyn = target->rela_dyn_section(layout);
5116
5117             // Use a GLOB_DAT rather than a RELATIVE reloc if:
5118             //
5119             // 1) The symbol may be defined in some other module.
5120             // 2) We are building a shared library and this is a protected
5121             // symbol; using GLOB_DAT means that the dynamic linker can use
5122             // the address of the PLT in the main executable when appropriate
5123             // so that function address comparisons work.
5124             // 3) This is a STT_GNU_IFUNC symbol in position dependent code,
5125             // again so that function address comparisons work.
5126             if (gsym->is_from_dynobj()
5127                 || gsym->is_undefined()
5128                 || gsym->is_preemptible()
5129                 || (gsym->visibility() == elfcpp::STV_PROTECTED
5130                     && parameters->options().shared())
5131                 || (gsym->type() == elfcpp::STT_GNU_IFUNC
5132                     && parameters->options().output_is_position_independent()))
5133               got->add_global_with_rel(gsym, GOT_TYPE_STANDARD,
5134                                        rela_dyn, elfcpp::R_AARCH64_GLOB_DAT);
5135             else
5136               {
5137                 // For a STT_GNU_IFUNC symbol we want to write the PLT
5138                 // offset into the GOT, so that function pointer
5139                 // comparisons work correctly.
5140                 bool is_new;
5141                 if (gsym->type() != elfcpp::STT_GNU_IFUNC)
5142                   is_new = got->add_global(gsym, GOT_TYPE_STANDARD);
5143                 else
5144                   {
5145                     is_new = got->add_global_plt(gsym, GOT_TYPE_STANDARD);
5146                     // Tell the dynamic linker to use the PLT address
5147                     // when resolving relocations.
5148                     if (gsym->is_from_dynobj()
5149                         && !parameters->options().shared())
5150                       gsym->set_needs_dynsym_value();
5151                   }
5152                 if (is_new)
5153                   {
5154                     rela_dyn->add_global_relative(
5155                         gsym, elfcpp::R_AARCH64_RELATIVE,
5156                         got,
5157                         gsym->got_offset(GOT_TYPE_STANDARD),
5158                         0,
5159                         false);
5160                   }
5161               }
5162           }
5163         break;
5164       }
5165
5166     case elfcpp::R_AARCH64_TSTBR14:
5167     case elfcpp::R_AARCH64_CONDBR19:
5168     case elfcpp::R_AARCH64_JUMP26:
5169     case elfcpp::R_AARCH64_CALL26:
5170       {
5171         if (gsym->final_value_is_known())
5172           break;
5173
5174         if (gsym->is_defined() &&
5175             !gsym->is_from_dynobj() &&
5176             !gsym->is_preemptible())
5177           break;
5178
5179         // Make plt entry for function call.
5180         target->make_plt_entry(symtab, layout, gsym);
5181         break;
5182       }
5183
5184     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
5185     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:  // General dynamic
5186       {
5187         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
5188             optimize_tls_reloc(gsym->final_value_is_known(), r_type);
5189         if (tlsopt == tls::TLSOPT_TO_LE)
5190           {
5191             layout->set_has_static_tls();
5192             break;
5193           }
5194         gold_assert(tlsopt == tls::TLSOPT_NONE);
5195
5196         // General dynamic.
5197         Output_data_got_aarch64<size, big_endian>* got =
5198             target->got_section(symtab, layout);
5199         // Create 2 consecutive entries for module index and offset.
5200         got->add_global_pair_with_rel(gsym, GOT_TYPE_TLS_PAIR,
5201                                       target->rela_dyn_section(layout),
5202                                       elfcpp::R_AARCH64_TLS_DTPMOD64,
5203                                       elfcpp::R_AARCH64_TLS_DTPREL64);
5204       }
5205       break;
5206
5207     case elfcpp::R_AARCH64_TLSLD_ADR_PAGE21:
5208     case elfcpp::R_AARCH64_TLSLD_ADD_LO12_NC:  // Local dynamic
5209       {
5210         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
5211             optimize_tls_reloc(!parameters->options().shared(), r_type);
5212         if (tlsopt == tls::TLSOPT_NONE)
5213           {
5214             // Create a GOT entry for the module index.
5215             target->got_mod_index_entry(symtab, layout, object);
5216           }
5217         else if (tlsopt != tls::TLSOPT_TO_LE)
5218           unsupported_reloc_local(object, r_type);
5219       }
5220       break;
5221
5222     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G1:
5223     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G0_NC:
5224     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_HI12:
5225     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_LO12_NC:  // Other local dynamic
5226       break;
5227
5228     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
5229     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:  // Initial executable
5230       {
5231         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
5232           optimize_tls_reloc(gsym->final_value_is_known(), r_type);
5233         if (tlsopt == tls::TLSOPT_TO_LE)
5234           break;
5235
5236         layout->set_has_static_tls();
5237         // Create a GOT entry for the tp-relative offset.
5238         Output_data_got_aarch64<size, big_endian>* got
5239           = target->got_section(symtab, layout);
5240         if (!parameters->doing_static_link())
5241           {
5242             got->add_global_with_rel(
5243               gsym, GOT_TYPE_TLS_OFFSET,
5244               target->rela_dyn_section(layout),
5245               elfcpp::R_AARCH64_TLS_TPREL64);
5246           }
5247         if (!gsym->has_got_offset(GOT_TYPE_TLS_OFFSET))
5248           {
5249             got->add_global(gsym, GOT_TYPE_TLS_OFFSET);
5250             unsigned int got_offset =
5251               gsym->got_offset(GOT_TYPE_TLS_OFFSET);
5252             const elfcpp::Elf_Xword addend = rela.get_r_addend();
5253             gold_assert(addend == 0);
5254             got->add_static_reloc(got_offset,
5255                                   elfcpp::R_AARCH64_TLS_TPREL64, gsym);
5256           }
5257       }
5258       break;
5259
5260     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G2:
5261     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1:
5262     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
5263     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0:
5264     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
5265     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
5266     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
5267     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:  // Local executable
5268       layout->set_has_static_tls();
5269       if (parameters->options().shared())
5270         gold_error(_("%s: unsupported TLSLE reloc type %u in shared objects."),
5271                    object->name().c_str(), r_type);
5272       break;
5273
5274     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
5275     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
5276     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:  // TLS descriptor
5277       {
5278         target->define_tls_base_symbol(symtab, layout);
5279         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
5280             optimize_tls_reloc(gsym->final_value_is_known(), r_type);
5281         if (tlsopt == tls::TLSOPT_NONE)
5282           {
5283             // Create reserved PLT and GOT entries for the resolver.
5284             target->reserve_tlsdesc_entries(symtab, layout);
5285
5286             // Create a double GOT entry with an R_AARCH64_TLSDESC
5287             // relocation. The R_AARCH64_TLSDESC is resolved lazily, so the GOT
5288             // entry needs to be in an area in .got.plt, not .got. Call
5289             // got_section to make sure the section has been created.
5290             target->got_section(symtab, layout);
5291             Output_data_got<size, big_endian>* got =
5292                 target->got_tlsdesc_section();
5293             Reloc_section* rt = target->rela_tlsdesc_section(layout);
5294             got->add_global_pair_with_rel(gsym, GOT_TYPE_TLS_DESC, rt,
5295                                           elfcpp::R_AARCH64_TLSDESC, 0);
5296           }
5297         else if (tlsopt == tls::TLSOPT_TO_IE)
5298           {
5299             // Create a GOT entry for the tp-relative offset.
5300             Output_data_got<size, big_endian>* got
5301                 = target->got_section(symtab, layout);
5302             got->add_global_with_rel(gsym, GOT_TYPE_TLS_OFFSET,
5303                                      target->rela_dyn_section(layout),
5304                                      elfcpp::R_AARCH64_TLS_TPREL64);
5305           }
5306         else if (tlsopt != tls::TLSOPT_TO_LE)
5307           unsupported_reloc_global(object, r_type, gsym);
5308       }
5309       break;
5310
5311     case elfcpp::R_AARCH64_TLSDESC_CALL:
5312       break;
5313
5314     default:
5315       gold_error(_("%s: unsupported reloc type in global scan"),
5316                  aarch64_reloc_property_table->
5317                  reloc_name_in_error_message(r_type).c_str());
5318     }
5319   return;
5320 }  // End of Scan::global
5321
5322
5323 // Create the PLT section.
5324 template<int size, bool big_endian>
5325 void
5326 Target_aarch64<size, big_endian>::make_plt_section(
5327   Symbol_table* symtab, Layout* layout)
5328 {
5329   if (this->plt_ == NULL)
5330     {
5331       // Create the GOT section first.
5332       this->got_section(symtab, layout);
5333
5334       this->plt_ = this->make_data_plt(layout, this->got_, this->got_plt_,
5335                                        this->got_irelative_);
5336
5337       layout->add_output_section_data(".plt", elfcpp::SHT_PROGBITS,
5338                                       (elfcpp::SHF_ALLOC
5339                                        | elfcpp::SHF_EXECINSTR),
5340                                       this->plt_, ORDER_PLT, false);
5341
5342       // Make the sh_info field of .rela.plt point to .plt.
5343       Output_section* rela_plt_os = this->plt_->rela_plt()->output_section();
5344       rela_plt_os->set_info_section(this->plt_->output_section());
5345     }
5346 }
5347
5348 // Return the section for TLSDESC relocations.
5349
5350 template<int size, bool big_endian>
5351 typename Target_aarch64<size, big_endian>::Reloc_section*
5352 Target_aarch64<size, big_endian>::rela_tlsdesc_section(Layout* layout) const
5353 {
5354   return this->plt_section()->rela_tlsdesc(layout);
5355 }
5356
5357 // Create a PLT entry for a global symbol.
5358
5359 template<int size, bool big_endian>
5360 void
5361 Target_aarch64<size, big_endian>::make_plt_entry(
5362     Symbol_table* symtab,
5363     Layout* layout,
5364     Symbol* gsym)
5365 {
5366   if (gsym->has_plt_offset())
5367     return;
5368
5369   if (this->plt_ == NULL)
5370     this->make_plt_section(symtab, layout);
5371
5372   this->plt_->add_entry(symtab, layout, gsym);
5373 }
5374
5375 // Make a PLT entry for a local STT_GNU_IFUNC symbol.
5376
5377 template<int size, bool big_endian>
5378 void
5379 Target_aarch64<size, big_endian>::make_local_ifunc_plt_entry(
5380     Symbol_table* symtab, Layout* layout,
5381     Sized_relobj_file<size, big_endian>* relobj,
5382     unsigned int local_sym_index)
5383 {
5384   if (relobj->local_has_plt_offset(local_sym_index))
5385     return;
5386   if (this->plt_ == NULL)
5387     this->make_plt_section(symtab, layout);
5388   unsigned int plt_offset = this->plt_->add_local_ifunc_entry(symtab, layout,
5389                                                               relobj,
5390                                                               local_sym_index);
5391   relobj->set_local_plt_offset(local_sym_index, plt_offset);
5392 }
5393
5394 template<int size, bool big_endian>
5395 void
5396 Target_aarch64<size, big_endian>::gc_process_relocs(
5397     Symbol_table* symtab,
5398     Layout* layout,
5399     Sized_relobj_file<size, big_endian>* object,
5400     unsigned int data_shndx,
5401     unsigned int sh_type,
5402     const unsigned char* prelocs,
5403     size_t reloc_count,
5404     Output_section* output_section,
5405     bool needs_special_offset_handling,
5406     size_t local_symbol_count,
5407     const unsigned char* plocal_symbols)
5408 {
5409   if (sh_type == elfcpp::SHT_REL)
5410     {
5411       return;
5412     }
5413
5414   gold::gc_process_relocs<
5415     size, big_endian,
5416     Target_aarch64<size, big_endian>,
5417     elfcpp::SHT_RELA,
5418     typename Target_aarch64<size, big_endian>::Scan,
5419     typename Target_aarch64<size, big_endian>::Relocatable_size_for_reloc>(
5420     symtab,
5421     layout,
5422     this,
5423     object,
5424     data_shndx,
5425     prelocs,
5426     reloc_count,
5427     output_section,
5428     needs_special_offset_handling,
5429     local_symbol_count,
5430     plocal_symbols);
5431 }
5432
5433 // Scan relocations for a section.
5434
5435 template<int size, bool big_endian>
5436 void
5437 Target_aarch64<size, big_endian>::scan_relocs(
5438     Symbol_table* symtab,
5439     Layout* layout,
5440     Sized_relobj_file<size, big_endian>* object,
5441     unsigned int data_shndx,
5442     unsigned int sh_type,
5443     const unsigned char* prelocs,
5444     size_t reloc_count,
5445     Output_section* output_section,
5446     bool needs_special_offset_handling,
5447     size_t local_symbol_count,
5448     const unsigned char* plocal_symbols)
5449 {
5450   if (sh_type == elfcpp::SHT_REL)
5451     {
5452       gold_error(_("%s: unsupported REL reloc section"),
5453                  object->name().c_str());
5454       return;
5455     }
5456   gold::scan_relocs<size, big_endian, Target_aarch64, elfcpp::SHT_RELA, Scan>(
5457     symtab,
5458     layout,
5459     this,
5460     object,
5461     data_shndx,
5462     prelocs,
5463     reloc_count,
5464     output_section,
5465     needs_special_offset_handling,
5466     local_symbol_count,
5467     plocal_symbols);
5468 }
5469
5470 // Return the value to use for a dynamic which requires special
5471 // treatment.  This is how we support equality comparisons of function
5472 // pointers across shared library boundaries, as described in the
5473 // processor specific ABI supplement.
5474
5475 template<int size, bool big_endian>
5476 uint64_t
5477 Target_aarch64<size, big_endian>::do_dynsym_value(const Symbol* gsym) const
5478 {
5479   gold_assert(gsym->is_from_dynobj() && gsym->has_plt_offset());
5480   return this->plt_address_for_global(gsym);
5481 }
5482
5483
5484 // Finalize the sections.
5485
5486 template<int size, bool big_endian>
5487 void
5488 Target_aarch64<size, big_endian>::do_finalize_sections(
5489     Layout* layout,
5490     const Input_objects*,
5491     Symbol_table* symtab)
5492 {
5493   const Reloc_section* rel_plt = (this->plt_ == NULL
5494                                   ? NULL
5495                                   : this->plt_->rela_plt());
5496   layout->add_target_dynamic_tags(false, this->got_plt_, rel_plt,
5497                                   this->rela_dyn_, true, false);
5498
5499   // Emit any relocs we saved in an attempt to avoid generating COPY
5500   // relocs.
5501   if (this->copy_relocs_.any_saved_relocs())
5502     this->copy_relocs_.emit(this->rela_dyn_section(layout));
5503
5504   // Fill in some more dynamic tags.
5505   Output_data_dynamic* const odyn = layout->dynamic_data();
5506   if (odyn != NULL)
5507     {
5508       if (this->plt_ != NULL
5509           && this->plt_->output_section() != NULL
5510           && this->plt_ ->has_tlsdesc_entry())
5511         {
5512           unsigned int plt_offset = this->plt_->get_tlsdesc_plt_offset();
5513           unsigned int got_offset = this->plt_->get_tlsdesc_got_offset();
5514           this->got_->finalize_data_size();
5515           odyn->add_section_plus_offset(elfcpp::DT_TLSDESC_PLT,
5516                                         this->plt_, plt_offset);
5517           odyn->add_section_plus_offset(elfcpp::DT_TLSDESC_GOT,
5518                                         this->got_, got_offset);
5519         }
5520     }
5521
5522   // Set the size of the _GLOBAL_OFFSET_TABLE_ symbol to the size of
5523   // the .got.plt section.
5524   Symbol* sym = this->global_offset_table_;
5525   if (sym != NULL)
5526     {
5527       uint64_t data_size = this->got_plt_->current_data_size();
5528       symtab->get_sized_symbol<size>(sym)->set_symsize(data_size);
5529
5530       // If the .got section is more than 0x8000 bytes, we add
5531       // 0x8000 to the value of _GLOBAL_OFFSET_TABLE_, so that 16
5532       // bit relocations have a greater chance of working.
5533       if (data_size >= 0x8000)
5534         symtab->get_sized_symbol<size>(sym)->set_value(
5535           symtab->get_sized_symbol<size>(sym)->value() + 0x8000);
5536     }
5537
5538   if (parameters->doing_static_link()
5539       && (this->plt_ == NULL || !this->plt_->has_irelative_section()))
5540     {
5541       // If linking statically, make sure that the __rela_iplt symbols
5542       // were defined if necessary, even if we didn't create a PLT.
5543       static const Define_symbol_in_segment syms[] =
5544         {
5545           {
5546             "__rela_iplt_start",        // name
5547             elfcpp::PT_LOAD,            // segment_type
5548             elfcpp::PF_W,               // segment_flags_set
5549             elfcpp::PF(0),              // segment_flags_clear
5550             0,                          // value
5551             0,                          // size
5552             elfcpp::STT_NOTYPE,         // type
5553             elfcpp::STB_GLOBAL,         // binding
5554             elfcpp::STV_HIDDEN,         // visibility
5555             0,                          // nonvis
5556             Symbol::SEGMENT_START,      // offset_from_base
5557             true                        // only_if_ref
5558           },
5559           {
5560             "__rela_iplt_end",          // name
5561             elfcpp::PT_LOAD,            // segment_type
5562             elfcpp::PF_W,               // segment_flags_set
5563             elfcpp::PF(0),              // segment_flags_clear
5564             0,                          // value
5565             0,                          // size
5566             elfcpp::STT_NOTYPE,         // type
5567             elfcpp::STB_GLOBAL,         // binding
5568             elfcpp::STV_HIDDEN,         // visibility
5569             0,                          // nonvis
5570             Symbol::SEGMENT_START,      // offset_from_base
5571             true                        // only_if_ref
5572           }
5573         };
5574
5575       symtab->define_symbols(layout, 2, syms,
5576                              layout->script_options()->saw_sections_clause());
5577     }
5578
5579   return;
5580 }
5581
5582 // Perform a relocation.
5583
5584 template<int size, bool big_endian>
5585 inline bool
5586 Target_aarch64<size, big_endian>::Relocate::relocate(
5587     const Relocate_info<size, big_endian>* relinfo,
5588     Target_aarch64<size, big_endian>* target,
5589     Output_section* ,
5590     size_t relnum,
5591     const elfcpp::Rela<size, big_endian>& rela,
5592     unsigned int r_type,
5593     const Sized_symbol<size>* gsym,
5594     const Symbol_value<size>* psymval,
5595     unsigned char* view,
5596     typename elfcpp::Elf_types<size>::Elf_Addr address,
5597     section_size_type /* view_size */)
5598 {
5599   if (view == NULL)
5600     return true;
5601
5602   typedef AArch64_relocate_functions<size, big_endian> Reloc;
5603
5604   const AArch64_reloc_property* reloc_property =
5605       aarch64_reloc_property_table->get_reloc_property(r_type);
5606
5607   if (reloc_property == NULL)
5608     {
5609       std::string reloc_name =
5610           aarch64_reloc_property_table->reloc_name_in_error_message(r_type);
5611       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5612                              _("cannot relocate %s in object file"),
5613                              reloc_name.c_str());
5614       return true;
5615     }
5616
5617   const Sized_relobj_file<size, big_endian>* object = relinfo->object;
5618
5619   // Pick the value to use for symbols defined in the PLT.
5620   Symbol_value<size> symval;
5621   if (gsym != NULL
5622       && gsym->use_plt_offset(reloc_property->reference_flags()))
5623     {
5624       symval.set_output_value(target->plt_address_for_global(gsym));
5625       psymval = &symval;
5626     }
5627   else if (gsym == NULL && psymval->is_ifunc_symbol())
5628     {
5629       unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5630       if (object->local_has_plt_offset(r_sym))
5631         {
5632           symval.set_output_value(target->plt_address_for_local(object, r_sym));
5633           psymval = &symval;
5634         }
5635     }
5636
5637   const elfcpp::Elf_Xword addend = rela.get_r_addend();
5638
5639   // Get the GOT offset if needed.
5640   // For aarch64, the GOT pointer points to the start of the GOT section.
5641   bool have_got_offset = false;
5642   int got_offset = 0;
5643   int got_base = (target->got_ != NULL
5644                   ? (target->got_->current_data_size() >= 0x8000
5645                      ? 0x8000 : 0)
5646                   : 0);
5647   switch (r_type)
5648     {
5649     case elfcpp::R_AARCH64_MOVW_GOTOFF_G0:
5650     case elfcpp::R_AARCH64_MOVW_GOTOFF_G0_NC:
5651     case elfcpp::R_AARCH64_MOVW_GOTOFF_G1:
5652     case elfcpp::R_AARCH64_MOVW_GOTOFF_G1_NC:
5653     case elfcpp::R_AARCH64_MOVW_GOTOFF_G2:
5654     case elfcpp::R_AARCH64_MOVW_GOTOFF_G2_NC:
5655     case elfcpp::R_AARCH64_MOVW_GOTOFF_G3:
5656     case elfcpp::R_AARCH64_GOTREL64:
5657     case elfcpp::R_AARCH64_GOTREL32:
5658     case elfcpp::R_AARCH64_GOT_LD_PREL19:
5659     case elfcpp::R_AARCH64_LD64_GOTOFF_LO15:
5660     case elfcpp::R_AARCH64_ADR_GOT_PAGE:
5661     case elfcpp::R_AARCH64_LD64_GOT_LO12_NC:
5662     case elfcpp::R_AARCH64_LD64_GOTPAGE_LO15:
5663       if (gsym != NULL)
5664         {
5665           gold_assert(gsym->has_got_offset(GOT_TYPE_STANDARD));
5666           got_offset = gsym->got_offset(GOT_TYPE_STANDARD) - got_base;
5667         }
5668       else
5669         {
5670           unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5671           gold_assert(object->local_has_got_offset(r_sym, GOT_TYPE_STANDARD));
5672           got_offset = (object->local_got_offset(r_sym, GOT_TYPE_STANDARD)
5673                         - got_base);
5674         }
5675       have_got_offset = true;
5676       break;
5677
5678     default:
5679       break;
5680     }
5681
5682   typename Reloc::Status reloc_status = Reloc::STATUS_OKAY;
5683   typename elfcpp::Elf_types<size>::Elf_Addr value;
5684   switch (r_type)
5685     {
5686     case elfcpp::R_AARCH64_NONE:
5687       break;
5688
5689     case elfcpp::R_AARCH64_ABS64:
5690       reloc_status = Reloc::template rela_ua<64>(
5691         view, object, psymval, addend, reloc_property);
5692       break;
5693
5694     case elfcpp::R_AARCH64_ABS32:
5695       reloc_status = Reloc::template rela_ua<32>(
5696         view, object, psymval, addend, reloc_property);
5697       break;
5698
5699     case elfcpp::R_AARCH64_ABS16:
5700       reloc_status = Reloc::template rela_ua<16>(
5701         view, object, psymval, addend, reloc_property);
5702       break;
5703
5704     case elfcpp::R_AARCH64_PREL64:
5705       reloc_status = Reloc::template pcrela_ua<64>(
5706         view, object, psymval, addend, address, reloc_property);
5707       break;
5708
5709     case elfcpp::R_AARCH64_PREL32:
5710       reloc_status = Reloc::template pcrela_ua<32>(
5711         view, object, psymval, addend, address, reloc_property);
5712       break;
5713
5714     case elfcpp::R_AARCH64_PREL16:
5715       reloc_status = Reloc::template pcrela_ua<16>(
5716         view, object, psymval, addend, address, reloc_property);
5717       break;
5718
5719     case elfcpp::R_AARCH64_LD_PREL_LO19:
5720       reloc_status = Reloc::template pcrela_general<32>(
5721           view, object, psymval, addend, address, reloc_property);
5722       break;
5723
5724     case elfcpp::R_AARCH64_ADR_PREL_LO21:
5725       reloc_status = Reloc::adr(view, object, psymval, addend,
5726                                 address, reloc_property);
5727       break;
5728
5729     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21_NC:
5730     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21:
5731       reloc_status = Reloc::adrp(view, object, psymval, addend, address,
5732                                  reloc_property);
5733       break;
5734
5735     case elfcpp::R_AARCH64_LDST8_ABS_LO12_NC:
5736     case elfcpp::R_AARCH64_LDST16_ABS_LO12_NC:
5737     case elfcpp::R_AARCH64_LDST32_ABS_LO12_NC:
5738     case elfcpp::R_AARCH64_LDST64_ABS_LO12_NC:
5739     case elfcpp::R_AARCH64_LDST128_ABS_LO12_NC:
5740     case elfcpp::R_AARCH64_ADD_ABS_LO12_NC:
5741       reloc_status = Reloc::template rela_general<32>(
5742         view, object, psymval, addend, reloc_property);
5743       break;
5744
5745     case elfcpp::R_AARCH64_CALL26:
5746       if (this->skip_call_tls_get_addr_)
5747         {
5748           // Double check that the TLSGD insn has been optimized away.
5749           typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
5750           Insntype insn = elfcpp::Swap<32, big_endian>::readval(
5751               reinterpret_cast<Insntype*>(view));
5752           gold_assert((insn & 0xff000000) == 0x91000000);
5753
5754           reloc_status = Reloc::STATUS_OKAY;
5755           this->skip_call_tls_get_addr_ = false;
5756           // Return false to stop further processing this reloc.
5757           return false;
5758         }
5759       // Fallthrough
5760     case elfcpp::R_AARCH64_JUMP26:
5761       if (Reloc::maybe_apply_stub(r_type, relinfo, rela, view, address,
5762                                   gsym, psymval, object,
5763                                   target->stub_group_size_))
5764         break;
5765       // Fallthrough
5766     case elfcpp::R_AARCH64_TSTBR14:
5767     case elfcpp::R_AARCH64_CONDBR19:
5768       reloc_status = Reloc::template pcrela_general<32>(
5769         view, object, psymval, addend, address, reloc_property);
5770       break;
5771
5772     case elfcpp::R_AARCH64_ADR_GOT_PAGE:
5773       gold_assert(have_got_offset);
5774       value = target->got_->address() + got_base + got_offset;
5775       reloc_status = Reloc::adrp(view, value + addend, address);
5776       break;
5777
5778     case elfcpp::R_AARCH64_LD64_GOT_LO12_NC:
5779       gold_assert(have_got_offset);
5780       value = target->got_->address() + got_base + got_offset;
5781       reloc_status = Reloc::template rela_general<32>(
5782         view, value, addend, reloc_property);
5783       break;
5784
5785     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
5786     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
5787     case elfcpp::R_AARCH64_TLSLD_ADR_PAGE21:
5788     case elfcpp::R_AARCH64_TLSLD_ADD_LO12_NC:
5789     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G1:
5790     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G0_NC:
5791     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_HI12:
5792     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_LO12_NC:
5793     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
5794     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
5795     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G2:
5796     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1:
5797     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
5798     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0:
5799     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
5800     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
5801     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
5802     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
5803     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
5804     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
5805     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
5806     case elfcpp::R_AARCH64_TLSDESC_CALL:
5807       reloc_status = relocate_tls(relinfo, target, relnum, rela, r_type,
5808                                   gsym, psymval, view, address);
5809       break;
5810
5811     // These are dynamic relocations, which are unexpected when linking.
5812     case elfcpp::R_AARCH64_COPY:
5813     case elfcpp::R_AARCH64_GLOB_DAT:
5814     case elfcpp::R_AARCH64_JUMP_SLOT:
5815     case elfcpp::R_AARCH64_RELATIVE:
5816     case elfcpp::R_AARCH64_IRELATIVE:
5817     case elfcpp::R_AARCH64_TLS_DTPREL64:
5818     case elfcpp::R_AARCH64_TLS_DTPMOD64:
5819     case elfcpp::R_AARCH64_TLS_TPREL64:
5820     case elfcpp::R_AARCH64_TLSDESC:
5821       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5822                              _("unexpected reloc %u in object file"),
5823                              r_type);
5824       break;
5825
5826     default:
5827       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5828                              _("unsupported reloc %s"),
5829                              reloc_property->name().c_str());
5830       break;
5831     }
5832
5833   // Report any errors.
5834   switch (reloc_status)
5835     {
5836     case Reloc::STATUS_OKAY:
5837       break;
5838     case Reloc::STATUS_OVERFLOW:
5839       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5840                              _("relocation overflow in %s"),
5841                              reloc_property->name().c_str());
5842       break;
5843     case Reloc::STATUS_BAD_RELOC:
5844       gold_error_at_location(
5845           relinfo,
5846           relnum,
5847           rela.get_r_offset(),
5848           _("unexpected opcode while processing relocation %s"),
5849           reloc_property->name().c_str());
5850       break;
5851     default:
5852       gold_unreachable();
5853     }
5854
5855   return true;
5856 }
5857
5858
5859 template<int size, bool big_endian>
5860 inline
5861 typename AArch64_relocate_functions<size, big_endian>::Status
5862 Target_aarch64<size, big_endian>::Relocate::relocate_tls(
5863     const Relocate_info<size, big_endian>* relinfo,
5864     Target_aarch64<size, big_endian>* target,
5865     size_t relnum,
5866     const elfcpp::Rela<size, big_endian>& rela,
5867     unsigned int r_type, const Sized_symbol<size>* gsym,
5868     const Symbol_value<size>* psymval,
5869     unsigned char* view,
5870     typename elfcpp::Elf_types<size>::Elf_Addr address)
5871 {
5872   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
5873   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
5874
5875   Output_segment* tls_segment = relinfo->layout->tls_segment();
5876   const elfcpp::Elf_Xword addend = rela.get_r_addend();
5877   const AArch64_reloc_property* reloc_property =
5878       aarch64_reloc_property_table->get_reloc_property(r_type);
5879   gold_assert(reloc_property != NULL);
5880
5881   const bool is_final = (gsym == NULL
5882                          ? !parameters->options().shared()
5883                          : gsym->final_value_is_known());
5884   tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
5885       optimize_tls_reloc(is_final, r_type);
5886
5887   Sized_relobj_file<size, big_endian>* object = relinfo->object;
5888   int tls_got_offset_type;
5889   switch (r_type)
5890     {
5891     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
5892     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:  // Global-dynamic
5893       {
5894         if (tlsopt == tls::TLSOPT_TO_LE)
5895           {
5896             if (tls_segment == NULL)
5897               {
5898                 gold_assert(parameters->errors()->error_count() > 0
5899                             || issue_undefined_symbol_error(gsym));
5900                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5901               }
5902             return tls_gd_to_le(relinfo, target, rela, r_type, view,
5903                                 psymval);
5904           }
5905         else if (tlsopt == tls::TLSOPT_NONE)
5906           {
5907             tls_got_offset_type = GOT_TYPE_TLS_PAIR;
5908             // Firstly get the address for the got entry.
5909             typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address;
5910             if (gsym != NULL)
5911               {
5912                 gold_assert(gsym->has_got_offset(tls_got_offset_type));
5913                 got_entry_address = target->got_->address() +
5914                                     gsym->got_offset(tls_got_offset_type);
5915               }
5916             else
5917               {
5918                 unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5919                 gold_assert(
5920                   object->local_has_got_offset(r_sym, tls_got_offset_type));
5921                 got_entry_address = target->got_->address() +
5922                   object->local_got_offset(r_sym, tls_got_offset_type);
5923               }
5924
5925             // Relocate the address into adrp/ld, adrp/add pair.
5926             switch (r_type)
5927               {
5928               case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
5929                 return aarch64_reloc_funcs::adrp(
5930                   view, got_entry_address + addend, address);
5931
5932                 break;
5933
5934               case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
5935                 return aarch64_reloc_funcs::template rela_general<32>(
5936                   view, got_entry_address, addend, reloc_property);
5937                 break;
5938
5939               default:
5940                 gold_unreachable();
5941               }
5942           }
5943         gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5944                                _("unsupported gd_to_ie relaxation on %u"),
5945                                r_type);
5946       }
5947       break;
5948
5949     case elfcpp::R_AARCH64_TLSLD_ADR_PAGE21:
5950     case elfcpp::R_AARCH64_TLSLD_ADD_LO12_NC:  // Local-dynamic
5951       {
5952         if (tlsopt == tls::TLSOPT_TO_LE)
5953           {
5954             if (tls_segment == NULL)
5955               {
5956                 gold_assert(parameters->errors()->error_count() > 0
5957                             || issue_undefined_symbol_error(gsym));
5958                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5959               }
5960             return this->tls_ld_to_le(relinfo, target, rela, r_type, view,
5961                                       psymval);
5962           }
5963
5964         gold_assert(tlsopt == tls::TLSOPT_NONE);
5965         // Relocate the field with the offset of the GOT entry for
5966         // the module index.
5967         typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address;
5968         got_entry_address = (target->got_mod_index_entry(NULL, NULL, NULL) +
5969                              target->got_->address());
5970
5971         switch (r_type)
5972           {
5973           case elfcpp::R_AARCH64_TLSLD_ADR_PAGE21:
5974             return aarch64_reloc_funcs::adrp(
5975               view, got_entry_address + addend, address);
5976             break;
5977
5978           case elfcpp::R_AARCH64_TLSLD_ADD_LO12_NC:
5979             return aarch64_reloc_funcs::template rela_general<32>(
5980               view, got_entry_address, addend, reloc_property);
5981             break;
5982
5983           default:
5984             gold_unreachable();
5985           }
5986       }
5987       break;
5988
5989     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G1:
5990     case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G0_NC:
5991     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_HI12:
5992     case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_LO12_NC:  // Other local-dynamic
5993       {
5994         AArch64_address value = psymval->value(object, 0);
5995         if (tlsopt == tls::TLSOPT_TO_LE)
5996           {
5997             if (tls_segment == NULL)
5998               {
5999                 gold_assert(parameters->errors()->error_count() > 0
6000                             || issue_undefined_symbol_error(gsym));
6001                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6002               }
6003           }
6004         switch (r_type)
6005           {
6006           case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G1:
6007             return aarch64_reloc_funcs::movnz(view, value + addend,
6008                                               reloc_property);
6009             break;
6010
6011           case elfcpp::R_AARCH64_TLSLD_MOVW_DTPREL_G0_NC:
6012           case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_HI12:
6013           case elfcpp::R_AARCH64_TLSLD_ADD_DTPREL_LO12_NC:
6014             return aarch64_reloc_funcs::template rela_general<32>(
6015                 view, value, addend, reloc_property);
6016             break;
6017
6018           default:
6019             gold_unreachable();
6020           }
6021         // We should never reach here.
6022       }
6023       break;
6024
6025     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
6026     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:  // Initial-exec
6027       {
6028         if (tlsopt == tls::TLSOPT_TO_LE)
6029           {
6030             if (tls_segment == NULL)
6031               {
6032                 gold_assert(parameters->errors()->error_count() > 0
6033                             || issue_undefined_symbol_error(gsym));
6034                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6035               }
6036             return tls_ie_to_le(relinfo, target, rela, r_type, view,
6037                                 psymval);
6038           }
6039         tls_got_offset_type = GOT_TYPE_TLS_OFFSET;
6040
6041         // Firstly get the address for the got entry.
6042         typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address;
6043         if (gsym != NULL)
6044           {
6045             gold_assert(gsym->has_got_offset(tls_got_offset_type));
6046             got_entry_address = target->got_->address() +
6047                                 gsym->got_offset(tls_got_offset_type);
6048           }
6049         else
6050           {
6051             unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
6052             gold_assert(
6053                 object->local_has_got_offset(r_sym, tls_got_offset_type));
6054             got_entry_address = target->got_->address() +
6055                 object->local_got_offset(r_sym, tls_got_offset_type);
6056           }
6057         // Relocate the address into adrp/ld, adrp/add pair.
6058         switch (r_type)
6059           {
6060           case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
6061             return aarch64_reloc_funcs::adrp(view, got_entry_address + addend,
6062                                              address);
6063             break;
6064           case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
6065             return aarch64_reloc_funcs::template rela_general<32>(
6066               view, got_entry_address, addend, reloc_property);
6067           default:
6068             gold_unreachable();
6069           }
6070       }
6071       // We shall never reach here.
6072       break;
6073
6074     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G2:
6075     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1:
6076     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
6077     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0:
6078     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
6079     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
6080     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
6081     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
6082       {
6083         gold_assert(tls_segment != NULL);
6084         AArch64_address value = psymval->value(object, 0);
6085
6086         if (!parameters->options().shared())
6087           {
6088             AArch64_address aligned_tcb_size =
6089                 align_address(target->tcb_size(),
6090                               tls_segment->maximum_alignment());
6091             value += aligned_tcb_size;
6092             switch (r_type)
6093               {
6094               case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G2:
6095               case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1:
6096               case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0:
6097                 return aarch64_reloc_funcs::movnz(view, value + addend,
6098                                                   reloc_property);
6099               default:
6100                 return aarch64_reloc_funcs::template
6101                   rela_general<32>(view,
6102                                    value,
6103                                    addend,
6104                                    reloc_property);
6105               }
6106           }
6107         else
6108           gold_error(_("%s: unsupported reloc %u "
6109                        "in non-static TLSLE mode."),
6110                      object->name().c_str(), r_type);
6111       }
6112       break;
6113
6114     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
6115     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
6116     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
6117     case elfcpp::R_AARCH64_TLSDESC_CALL:
6118       {
6119         if (tlsopt == tls::TLSOPT_TO_LE)
6120           {
6121             if (tls_segment == NULL)
6122               {
6123                 gold_assert(parameters->errors()->error_count() > 0
6124                             || issue_undefined_symbol_error(gsym));
6125                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6126               }
6127             return tls_desc_gd_to_le(relinfo, target, rela, r_type,
6128                                      view, psymval);
6129           }
6130         else
6131           {
6132             tls_got_offset_type = (tlsopt == tls::TLSOPT_TO_IE
6133                                    ? GOT_TYPE_TLS_OFFSET
6134                                    : GOT_TYPE_TLS_DESC);
6135             unsigned int got_tlsdesc_offset = 0;
6136             if (r_type != elfcpp::R_AARCH64_TLSDESC_CALL
6137                 && tlsopt == tls::TLSOPT_NONE)
6138               {
6139                 // We created GOT entries in the .got.tlsdesc portion of the
6140                 // .got.plt section, but the offset stored in the symbol is the
6141                 // offset within .got.tlsdesc.
6142                 got_tlsdesc_offset = (target->got_->data_size()
6143                                       + target->got_plt_section()->data_size());
6144               }
6145             typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address;
6146             if (gsym != NULL)
6147               {
6148                 gold_assert(gsym->has_got_offset(tls_got_offset_type));
6149                 got_entry_address = target->got_->address()
6150                                     + got_tlsdesc_offset
6151                                     + gsym->got_offset(tls_got_offset_type);
6152               }
6153             else
6154               {
6155                 unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
6156                 gold_assert(
6157                     object->local_has_got_offset(r_sym, tls_got_offset_type));
6158                 got_entry_address = target->got_->address() +
6159                   got_tlsdesc_offset +
6160                   object->local_got_offset(r_sym, tls_got_offset_type);
6161               }
6162             if (tlsopt == tls::TLSOPT_TO_IE)
6163               {
6164                 if (tls_segment == NULL)
6165                   {
6166                     gold_assert(parameters->errors()->error_count() > 0
6167                                 || issue_undefined_symbol_error(gsym));
6168                     return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6169                   }
6170                 return tls_desc_gd_to_ie(relinfo, target, rela, r_type,
6171                                          view, psymval, got_entry_address,
6172                                          address);
6173               }
6174
6175             // Now do tlsdesc relocation.
6176             switch (r_type)
6177               {
6178               case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
6179                 return aarch64_reloc_funcs::adrp(view,
6180                                                  got_entry_address + addend,
6181                                                  address);
6182                 break;
6183               case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
6184               case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
6185                 return aarch64_reloc_funcs::template rela_general<32>(
6186                   view, got_entry_address, addend, reloc_property);
6187                 break;
6188               case elfcpp::R_AARCH64_TLSDESC_CALL:
6189                 return aarch64_reloc_funcs::STATUS_OKAY;
6190                 break;
6191               default:
6192                 gold_unreachable();
6193               }
6194           }
6195         }
6196       break;
6197
6198     default:
6199       gold_error(_("%s: unsupported TLS reloc %u."),
6200                  object->name().c_str(), r_type);
6201     }
6202   return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6203 }  // End of relocate_tls.
6204
6205
6206 template<int size, bool big_endian>
6207 inline
6208 typename AArch64_relocate_functions<size, big_endian>::Status
6209 Target_aarch64<size, big_endian>::Relocate::tls_gd_to_le(
6210              const Relocate_info<size, big_endian>* relinfo,
6211              Target_aarch64<size, big_endian>* target,
6212              const elfcpp::Rela<size, big_endian>& rela,
6213              unsigned int r_type,
6214              unsigned char* view,
6215              const Symbol_value<size>* psymval)
6216 {
6217   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
6218   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
6219   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
6220
6221   Insntype* ip = reinterpret_cast<Insntype*>(view);
6222   Insntype insn1 = elfcpp::Swap<32, big_endian>::readval(ip);
6223   Insntype insn2 = elfcpp::Swap<32, big_endian>::readval(ip + 1);
6224   Insntype insn3 = elfcpp::Swap<32, big_endian>::readval(ip + 2);
6225
6226   if (r_type == elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC)
6227     {
6228       // This is the 2nd relocs, optimization should already have been
6229       // done.
6230       gold_assert((insn1 & 0xfff00000) == 0x91400000);
6231       return aarch64_reloc_funcs::STATUS_OKAY;
6232     }
6233
6234   // The original sequence is -
6235   //   90000000        adrp    x0, 0 <main>
6236   //   91000000        add     x0, x0, #0x0
6237   //   94000000        bl      0 <__tls_get_addr>
6238   // optimized to sequence -
6239   //   d53bd040        mrs     x0, tpidr_el0
6240   //   91400000        add     x0, x0, #0x0, lsl #12
6241   //   91000000        add     x0, x0, #0x0
6242
6243   // Unlike tls_ie_to_le, we change the 3 insns in one function call when we
6244   // encounter the first relocation "R_AARCH64_TLSGD_ADR_PAGE21". Because we
6245   // have to change "bl tls_get_addr", which does not have a corresponding tls
6246   // relocation type. So before proceeding, we need to make sure compiler
6247   // does not change the sequence.
6248   if(!(insn1 == 0x90000000      // adrp x0,0
6249        && insn2 == 0x91000000   // add x0, x0, #0x0
6250        && insn3 == 0x94000000)) // bl 0
6251     {
6252       // Ideally we should give up gd_to_le relaxation and do gd access.
6253       // However the gd_to_le relaxation decision has been made early
6254       // in the scan stage, where we did not allocate any GOT entry for
6255       // this symbol. Therefore we have to exit and report error now.
6256       gold_error(_("unexpected reloc insn sequence while relaxing "
6257                    "tls gd to le for reloc %u."), r_type);
6258       return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6259     }
6260
6261   // Write new insns.
6262   insn1 = 0xd53bd040;  // mrs x0, tpidr_el0
6263   insn2 = 0x91400000;  // add x0, x0, #0x0, lsl #12
6264   insn3 = 0x91000000;  // add x0, x0, #0x0
6265   elfcpp::Swap<32, big_endian>::writeval(ip, insn1);
6266   elfcpp::Swap<32, big_endian>::writeval(ip + 1, insn2);
6267   elfcpp::Swap<32, big_endian>::writeval(ip + 2, insn3);
6268
6269   // Calculate tprel value.
6270   Output_segment* tls_segment = relinfo->layout->tls_segment();
6271   gold_assert(tls_segment != NULL);
6272   AArch64_address value = psymval->value(relinfo->object, 0);
6273   const elfcpp::Elf_Xword addend = rela.get_r_addend();
6274   AArch64_address aligned_tcb_size =
6275       align_address(target->tcb_size(), tls_segment->maximum_alignment());
6276   AArch64_address x = value + aligned_tcb_size;
6277
6278   // After new insns are written, apply TLSLE relocs.
6279   const AArch64_reloc_property* rp1 =
6280       aarch64_reloc_property_table->get_reloc_property(
6281           elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12);
6282   const AArch64_reloc_property* rp2 =
6283       aarch64_reloc_property_table->get_reloc_property(
6284           elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12);
6285   gold_assert(rp1 != NULL && rp2 != NULL);
6286
6287   typename aarch64_reloc_funcs::Status s1 =
6288       aarch64_reloc_funcs::template rela_general<32>(view + 4,
6289                                                      x,
6290                                                      addend,
6291                                                      rp1);
6292   if (s1 != aarch64_reloc_funcs::STATUS_OKAY)
6293     return s1;
6294
6295   typename aarch64_reloc_funcs::Status s2 =
6296       aarch64_reloc_funcs::template rela_general<32>(view + 8,
6297                                                      x,
6298                                                      addend,
6299                                                      rp2);
6300
6301   this->skip_call_tls_get_addr_ = true;
6302   return s2;
6303 }  // End of tls_gd_to_le
6304
6305
6306 template<int size, bool big_endian>
6307 inline
6308 typename AArch64_relocate_functions<size, big_endian>::Status
6309 Target_aarch64<size, big_endian>::Relocate::tls_ld_to_le(
6310              const Relocate_info<size, big_endian>* relinfo,
6311              Target_aarch64<size, big_endian>* target,
6312              const elfcpp::Rela<size, big_endian>& rela,
6313              unsigned int r_type,
6314              unsigned char* view,
6315              const Symbol_value<size>* psymval)
6316 {
6317   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
6318   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
6319   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
6320
6321   Insntype* ip = reinterpret_cast<Insntype*>(view);
6322   Insntype insn1 = elfcpp::Swap<32, big_endian>::readval(ip);
6323   Insntype insn2 = elfcpp::Swap<32, big_endian>::readval(ip + 1);
6324   Insntype insn3 = elfcpp::Swap<32, big_endian>::readval(ip + 2);
6325
6326   if (r_type == elfcpp::R_AARCH64_TLSLD_ADD_LO12_NC)
6327     {
6328       // This is the 2nd relocs, optimization should already have been
6329       // done.
6330       gold_assert((insn1 & 0xfff00000) == 0x91400000);
6331       return aarch64_reloc_funcs::STATUS_OKAY;
6332     }
6333
6334   // The original sequence is -
6335   //   90000000        adrp    x0, 0 <main>
6336   //   91000000        add     x0, x0, #0x0
6337   //   94000000        bl      0 <__tls_get_addr>
6338   // optimized to sequence -
6339   //   d53bd040        mrs     x0, tpidr_el0
6340   //   91400000        add     x0, x0, #0x0, lsl #12
6341   //   91000000        add     x0, x0, #0x0
6342
6343   // Unlike tls_ie_to_le, we change the 3 insns in one function call when we
6344   // encounter the first relocation "R_AARCH64_TLSLD_ADR_PAGE21". Because we
6345   // have to change "bl tls_get_addr", which does not have a corresponding tls
6346   // relocation type. So before proceeding, we need to make sure compiler
6347   // does not change the sequence.
6348   if(!(insn1 == 0x90000000      // adrp x0,0
6349        && insn2 == 0x91000000   // add x0, x0, #0x0
6350        && insn3 == 0x94000000)) // bl 0
6351     {
6352       // Ideally we should give up gd_to_le relaxation and do gd access.
6353       // However the gd_to_le relaxation decision has been made early
6354       // in the scan stage, where we did not allocate any GOT entry for
6355       // this symbol. Therefore we have to exit and report error now.
6356       gold_error(_("unexpected reloc insn sequence while relaxing "
6357                    "tls gd to le for reloc %u."), r_type);
6358       return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6359     }
6360
6361   // Write new insns.
6362   insn1 = 0xd53bd040;  // mrs x0, tpidr_el0
6363   insn2 = 0x91400000;  // add x0, x0, #0x0, lsl #12
6364   insn3 = 0x91000000;  // add x0, x0, #0x0
6365   elfcpp::Swap<32, big_endian>::writeval(ip, insn1);
6366   elfcpp::Swap<32, big_endian>::writeval(ip + 1, insn2);
6367   elfcpp::Swap<32, big_endian>::writeval(ip + 2, insn3);
6368
6369   // Calculate tprel value.
6370   Output_segment* tls_segment = relinfo->layout->tls_segment();
6371   gold_assert(tls_segment != NULL);
6372   AArch64_address value = psymval->value(relinfo->object, 0);
6373   const elfcpp::Elf_Xword addend = rela.get_r_addend();
6374   AArch64_address aligned_tcb_size =
6375       align_address(target->tcb_size(), tls_segment->maximum_alignment());
6376   AArch64_address x = value + aligned_tcb_size;
6377
6378   // After new insns are written, apply TLSLE relocs.
6379   const AArch64_reloc_property* rp1 =
6380       aarch64_reloc_property_table->get_reloc_property(
6381           elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12);
6382   const AArch64_reloc_property* rp2 =
6383       aarch64_reloc_property_table->get_reloc_property(
6384           elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12);
6385   gold_assert(rp1 != NULL && rp2 != NULL);
6386
6387   typename aarch64_reloc_funcs::Status s1 =
6388       aarch64_reloc_funcs::template rela_general<32>(view + 4,
6389                                                      x,
6390                                                      addend,
6391                                                      rp1);
6392   if (s1 != aarch64_reloc_funcs::STATUS_OKAY)
6393     return s1;
6394
6395   typename aarch64_reloc_funcs::Status s2 =
6396       aarch64_reloc_funcs::template rela_general<32>(view + 8,
6397                                                      x,
6398                                                      addend,
6399                                                      rp2);
6400
6401   this->skip_call_tls_get_addr_ = true;
6402   return s2;
6403
6404 }  // End of tls_ld_to_le
6405
6406 template<int size, bool big_endian>
6407 inline
6408 typename AArch64_relocate_functions<size, big_endian>::Status
6409 Target_aarch64<size, big_endian>::Relocate::tls_ie_to_le(
6410              const Relocate_info<size, big_endian>* relinfo,
6411              Target_aarch64<size, big_endian>* target,
6412              const elfcpp::Rela<size, big_endian>& rela,
6413              unsigned int r_type,
6414              unsigned char* view,
6415              const Symbol_value<size>* psymval)
6416 {
6417   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
6418   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
6419   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
6420
6421   AArch64_address value = psymval->value(relinfo->object, 0);
6422   Output_segment* tls_segment = relinfo->layout->tls_segment();
6423   AArch64_address aligned_tcb_address =
6424       align_address(target->tcb_size(), tls_segment->maximum_alignment());
6425   const elfcpp::Elf_Xword addend = rela.get_r_addend();
6426   AArch64_address x = value + addend + aligned_tcb_address;
6427   // "x" is the offset to tp, we can only do this if x is within
6428   // range [0, 2^32-1]
6429   if (!(size == 32 || (size == 64 && (static_cast<uint64_t>(x) >> 32) == 0)))
6430     {
6431       gold_error(_("TLS variable referred by reloc %u is too far from TP."),
6432                  r_type);
6433       return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6434     }
6435
6436   Insntype* ip = reinterpret_cast<Insntype*>(view);
6437   Insntype insn = elfcpp::Swap<32, big_endian>::readval(ip);
6438   unsigned int regno;
6439   Insntype newinsn;
6440   if (r_type == elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21)
6441     {
6442       // Generate movz.
6443       regno = (insn & 0x1f);
6444       newinsn = (0xd2a00000 | regno) | (((x >> 16) & 0xffff) << 5);
6445     }
6446   else if (r_type == elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC)
6447     {
6448       // Generate movk.
6449       regno = (insn & 0x1f);
6450       gold_assert(regno == ((insn >> 5) & 0x1f));
6451       newinsn = (0xf2800000 | regno) | ((x & 0xffff) << 5);
6452     }
6453   else
6454     gold_unreachable();
6455
6456   elfcpp::Swap<32, big_endian>::writeval(ip, newinsn);
6457   return aarch64_reloc_funcs::STATUS_OKAY;
6458 }  // End of tls_ie_to_le
6459
6460
6461 template<int size, bool big_endian>
6462 inline
6463 typename AArch64_relocate_functions<size, big_endian>::Status
6464 Target_aarch64<size, big_endian>::Relocate::tls_desc_gd_to_le(
6465              const Relocate_info<size, big_endian>* relinfo,
6466              Target_aarch64<size, big_endian>* target,
6467              const elfcpp::Rela<size, big_endian>& rela,
6468              unsigned int r_type,
6469              unsigned char* view,
6470              const Symbol_value<size>* psymval)
6471 {
6472   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
6473   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
6474   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
6475
6476   // TLSDESC-GD sequence is like:
6477   //   adrp  x0, :tlsdesc:v1
6478   //   ldr   x1, [x0, #:tlsdesc_lo12:v1]
6479   //   add   x0, x0, :tlsdesc_lo12:v1
6480   //   .tlsdesccall    v1
6481   //   blr   x1
6482   // After desc_gd_to_le optimization, the sequence will be like:
6483   //   movz  x0, #0x0, lsl #16
6484   //   movk  x0, #0x10
6485   //   nop
6486   //   nop
6487
6488   // Calculate tprel value.
6489   Output_segment* tls_segment = relinfo->layout->tls_segment();
6490   gold_assert(tls_segment != NULL);
6491   Insntype* ip = reinterpret_cast<Insntype*>(view);
6492   const elfcpp::Elf_Xword addend = rela.get_r_addend();
6493   AArch64_address value = psymval->value(relinfo->object, addend);
6494   AArch64_address aligned_tcb_size =
6495       align_address(target->tcb_size(), tls_segment->maximum_alignment());
6496   AArch64_address x = value + aligned_tcb_size;
6497   // x is the offset to tp, we can only do this if x is within range
6498   // [0, 2^32-1]. If x is out of range, fail and exit.
6499   if (size == 64 && (static_cast<uint64_t>(x) >> 32) != 0)
6500     {
6501       gold_error(_("TLS variable referred by reloc %u is too far from TP. "
6502                    "We Can't do gd_to_le relaxation.\n"), r_type);
6503       return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6504     }
6505   Insntype newinsn;
6506   switch (r_type)
6507     {
6508     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
6509     case elfcpp::R_AARCH64_TLSDESC_CALL:
6510       // Change to nop
6511       newinsn = 0xd503201f;
6512       break;
6513
6514     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
6515       // Change to movz.
6516       newinsn = 0xd2a00000 | (((x >> 16) & 0xffff) << 5);
6517       break;
6518
6519     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
6520       // Change to movk.
6521       newinsn = 0xf2800000 | ((x & 0xffff) << 5);
6522       break;
6523
6524     default:
6525       gold_error(_("unsupported tlsdesc gd_to_le optimization on reloc %u"),
6526                  r_type);
6527       gold_unreachable();
6528     }
6529   elfcpp::Swap<32, big_endian>::writeval(ip, newinsn);
6530   return aarch64_reloc_funcs::STATUS_OKAY;
6531 }  // End of tls_desc_gd_to_le
6532
6533
6534 template<int size, bool big_endian>
6535 inline
6536 typename AArch64_relocate_functions<size, big_endian>::Status
6537 Target_aarch64<size, big_endian>::Relocate::tls_desc_gd_to_ie(
6538              const Relocate_info<size, big_endian>* /* relinfo */,
6539              Target_aarch64<size, big_endian>* /* target */,
6540              const elfcpp::Rela<size, big_endian>& rela,
6541              unsigned int r_type,
6542              unsigned char* view,
6543              const Symbol_value<size>* /* psymval */,
6544              typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address,
6545              typename elfcpp::Elf_types<size>::Elf_Addr address)
6546 {
6547   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
6548   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
6549
6550   // TLSDESC-GD sequence is like:
6551   //   adrp  x0, :tlsdesc:v1
6552   //   ldr   x1, [x0, #:tlsdesc_lo12:v1]
6553   //   add   x0, x0, :tlsdesc_lo12:v1
6554   //   .tlsdesccall    v1
6555   //   blr   x1
6556   // After desc_gd_to_ie optimization, the sequence will be like:
6557   //   adrp  x0, :tlsie:v1
6558   //   ldr   x0, [x0, :tlsie_lo12:v1]
6559   //   nop
6560   //   nop
6561
6562   Insntype* ip = reinterpret_cast<Insntype*>(view);
6563   const elfcpp::Elf_Xword addend = rela.get_r_addend();
6564   Insntype newinsn;
6565   switch (r_type)
6566     {
6567     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
6568     case elfcpp::R_AARCH64_TLSDESC_CALL:
6569       // Change to nop
6570       newinsn = 0xd503201f;
6571       elfcpp::Swap<32, big_endian>::writeval(ip, newinsn);
6572       break;
6573
6574     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
6575       {
6576         return aarch64_reloc_funcs::adrp(view, got_entry_address + addend,
6577                                          address);
6578       }
6579       break;
6580
6581     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
6582       {
6583        // Set ldr target register to be x0.
6584        Insntype insn = elfcpp::Swap<32, big_endian>::readval(ip);
6585        insn &= 0xffffffe0;
6586        elfcpp::Swap<32, big_endian>::writeval(ip, insn);
6587        // Do relocation.
6588         const AArch64_reloc_property* reloc_property =
6589             aarch64_reloc_property_table->get_reloc_property(
6590               elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC);
6591         return aarch64_reloc_funcs::template rela_general<32>(
6592                  view, got_entry_address, addend, reloc_property);
6593       }
6594       break;
6595
6596     default:
6597       gold_error(_("Don't support tlsdesc gd_to_ie optimization on reloc %u"),
6598                  r_type);
6599       gold_unreachable();
6600     }
6601   return aarch64_reloc_funcs::STATUS_OKAY;
6602 }  // End of tls_desc_gd_to_ie
6603
6604 // Relocate section data.
6605
6606 template<int size, bool big_endian>
6607 void
6608 Target_aarch64<size, big_endian>::relocate_section(
6609     const Relocate_info<size, big_endian>* relinfo,
6610     unsigned int sh_type,
6611     const unsigned char* prelocs,
6612     size_t reloc_count,
6613     Output_section* output_section,
6614     bool needs_special_offset_handling,
6615     unsigned char* view,
6616     typename elfcpp::Elf_types<size>::Elf_Addr address,
6617     section_size_type view_size,
6618     const Reloc_symbol_changes* reloc_symbol_changes)
6619 {
6620   gold_assert(sh_type == elfcpp::SHT_RELA);
6621   typedef typename Target_aarch64<size, big_endian>::Relocate AArch64_relocate;
6622   gold::relocate_section<size, big_endian, Target_aarch64, elfcpp::SHT_RELA,
6623                          AArch64_relocate, gold::Default_comdat_behavior>(
6624     relinfo,
6625     this,
6626     prelocs,
6627     reloc_count,
6628     output_section,
6629     needs_special_offset_handling,
6630     view,
6631     address,
6632     view_size,
6633     reloc_symbol_changes);
6634 }
6635
6636 // Return the size of a relocation while scanning during a relocatable
6637 // link.
6638
6639 template<int size, bool big_endian>
6640 unsigned int
6641 Target_aarch64<size, big_endian>::Relocatable_size_for_reloc::
6642 get_size_for_reloc(
6643     unsigned int ,
6644     Relobj* )
6645 {
6646   // We will never support SHT_REL relocations.
6647   gold_unreachable();
6648   return 0;
6649 }
6650
6651 // Scan the relocs during a relocatable link.
6652
6653 template<int size, bool big_endian>
6654 void
6655 Target_aarch64<size, big_endian>::scan_relocatable_relocs(
6656     Symbol_table* symtab,
6657     Layout* layout,
6658     Sized_relobj_file<size, big_endian>* object,
6659     unsigned int data_shndx,
6660     unsigned int sh_type,
6661     const unsigned char* prelocs,
6662     size_t reloc_count,
6663     Output_section* output_section,
6664     bool needs_special_offset_handling,
6665     size_t local_symbol_count,
6666     const unsigned char* plocal_symbols,
6667     Relocatable_relocs* rr)
6668 {
6669   gold_assert(sh_type == elfcpp::SHT_RELA);
6670
6671   typedef gold::Default_scan_relocatable_relocs<elfcpp::SHT_RELA,
6672     Relocatable_size_for_reloc> Scan_relocatable_relocs;
6673
6674   gold::scan_relocatable_relocs<size, big_endian, elfcpp::SHT_RELA,
6675       Scan_relocatable_relocs>(
6676     symtab,
6677     layout,
6678     object,
6679     data_shndx,
6680     prelocs,
6681     reloc_count,
6682     output_section,
6683     needs_special_offset_handling,
6684     local_symbol_count,
6685     plocal_symbols,
6686     rr);
6687 }
6688
6689 // Relocate a section during a relocatable link.
6690
6691 template<int size, bool big_endian>
6692 void
6693 Target_aarch64<size, big_endian>::relocate_relocs(
6694     const Relocate_info<size, big_endian>* relinfo,
6695     unsigned int sh_type,
6696     const unsigned char* prelocs,
6697     size_t reloc_count,
6698     Output_section* output_section,
6699     typename elfcpp::Elf_types<size>::Elf_Off offset_in_output_section,
6700     const Relocatable_relocs* rr,
6701     unsigned char* view,
6702     typename elfcpp::Elf_types<size>::Elf_Addr view_address,
6703     section_size_type view_size,
6704     unsigned char* reloc_view,
6705     section_size_type reloc_view_size)
6706 {
6707   gold_assert(sh_type == elfcpp::SHT_RELA);
6708
6709   gold::relocate_relocs<size, big_endian, elfcpp::SHT_RELA>(
6710     relinfo,
6711     prelocs,
6712     reloc_count,
6713     output_section,
6714     offset_in_output_section,
6715     rr,
6716     view,
6717     view_address,
6718     view_size,
6719     reloc_view,
6720     reloc_view_size);
6721 }
6722
6723
6724 // The selector for aarch64 object files.
6725
6726 template<int size, bool big_endian>
6727 class Target_selector_aarch64 : public Target_selector
6728 {
6729  public:
6730   Target_selector_aarch64();
6731
6732   virtual Target*
6733   do_instantiate_target()
6734   { return new Target_aarch64<size, big_endian>(); }
6735 };
6736
6737 template<>
6738 Target_selector_aarch64<32, true>::Target_selector_aarch64()
6739   : Target_selector(elfcpp::EM_AARCH64, 32, true,
6740                     "elf32-bigaarch64", "aarch64_elf32_be_vec")
6741 { }
6742
6743 template<>
6744 Target_selector_aarch64<32, false>::Target_selector_aarch64()
6745   : Target_selector(elfcpp::EM_AARCH64, 32, false,
6746                     "elf32-littleaarch64", "aarch64_elf32_le_vec")
6747 { }
6748
6749 template<>
6750 Target_selector_aarch64<64, true>::Target_selector_aarch64()
6751   : Target_selector(elfcpp::EM_AARCH64, 64, true,
6752                     "elf64-bigaarch64", "aarch64_elf64_be_vec")
6753 { }
6754
6755 template<>
6756 Target_selector_aarch64<64, false>::Target_selector_aarch64()
6757   : Target_selector(elfcpp::EM_AARCH64, 64, false,
6758                     "elf64-littleaarch64", "aarch64_elf64_le_vec")
6759 { }
6760
6761 Target_selector_aarch64<32, true> target_selector_aarch64elf32b;
6762 Target_selector_aarch64<32, false> target_selector_aarch64elf32;
6763 Target_selector_aarch64<64, true> target_selector_aarch64elfb;
6764 Target_selector_aarch64<64, false> target_selector_aarch64elf;
6765
6766 } // End anonymous namespace.