Here we have the patch for gold aarch64 backend to support relaxation.
[external/binutils.git] / gold / aarch64.cc
1 // aarch64.cc -- aarch64 target support for gold.
2
3 // Copyright (C) 2014 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_assert(false);
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_(), 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   // Return the number of entries in the PLT.
1766   unsigned int
1767   plt_entry_count() const;
1768
1769   //Return the offset of the first non-reserved PLT entry.
1770   unsigned int
1771   first_plt_entry_offset() const;
1772
1773   // Return the size of each PLT entry.
1774   unsigned int
1775   plt_entry_size() const;
1776
1777   // Create a stub table.
1778   The_stub_table*
1779   new_stub_table(The_aarch64_input_section*);
1780
1781   // Create an aarch64 input section.
1782   The_aarch64_input_section*
1783   new_aarch64_input_section(Relobj*, unsigned int);
1784
1785   // Find an aarch64 input section instance for a given OBJ and SHNDX.
1786   The_aarch64_input_section*
1787   find_aarch64_input_section(Relobj*, unsigned int) const;
1788
1789   // Return the thread control block size.
1790   unsigned int
1791   tcb_size() const { return This::TCB_SIZE; }
1792
1793   // Scan a section for stub generation.
1794   void
1795   scan_section_for_stubs(const Relocate_info<size, big_endian>*, unsigned int,
1796                          const unsigned char*, size_t, Output_section*,
1797                          bool, const unsigned char*,
1798                          Address,
1799                          section_size_type);
1800
1801   // Scan a relocation section for stub.
1802   template<int sh_type>
1803   void
1804   scan_reloc_section_for_stubs(
1805       const The_relocate_info* relinfo,
1806       const unsigned char* prelocs,
1807       size_t reloc_count,
1808       Output_section* output_section,
1809       bool needs_special_offset_handling,
1810       const unsigned char* view,
1811       Address view_address,
1812       section_size_type);
1813
1814   // Relocate a single stub.
1815   void
1816   relocate_stub(The_reloc_stub*, const Relocate_info<size, big_endian>*,
1817                 Output_section*, unsigned char*, Address,
1818                 section_size_type);
1819
1820   // Get the default AArch64 target.
1821   static This*
1822   current_target()
1823   {
1824     gold_assert(parameters->target().machine_code() == elfcpp::EM_AARCH64
1825                 && parameters->target().get_size() == size
1826                 && parameters->target().is_big_endian() == big_endian);
1827     return static_cast<This*>(parameters->sized_target<size, big_endian>());
1828   }
1829
1830  protected:
1831   void
1832   do_select_as_default_target()
1833   {
1834     gold_assert(aarch64_reloc_property_table == NULL);
1835     aarch64_reloc_property_table = new AArch64_reloc_property_table();
1836   }
1837
1838   // Add a new reloc argument, returning the index in the vector.
1839   size_t
1840   add_tlsdesc_info(Sized_relobj_file<size, big_endian>* object,
1841                    unsigned int r_sym)
1842   {
1843     this->tlsdesc_reloc_info_.push_back(Tlsdesc_info(object, r_sym));
1844     return this->tlsdesc_reloc_info_.size() - 1;
1845   }
1846
1847   virtual Output_data_plt_aarch64<size, big_endian>*
1848   do_make_data_plt(Layout* layout,
1849                    Output_data_got_aarch64<size, big_endian>* got,
1850                    Output_data_space* got_plt,
1851                    Output_data_space* got_irelative)
1852   {
1853     return new Output_data_plt_aarch64_standard<size, big_endian>(
1854       layout, got, got_plt, got_irelative);
1855   }
1856
1857
1858   // do_make_elf_object to override the same function in the base class.
1859   Object*
1860   do_make_elf_object(const std::string&, Input_file*, off_t,
1861                      const elfcpp::Ehdr<size, big_endian>&);
1862
1863   Output_data_plt_aarch64<size, big_endian>*
1864   make_data_plt(Layout* layout,
1865                 Output_data_got_aarch64<size, big_endian>* got,
1866                 Output_data_space* got_plt,
1867                 Output_data_space* got_irelative)
1868   {
1869     return this->do_make_data_plt(layout, got, got_plt, got_irelative);
1870   }
1871
1872   // We only need to generate stubs, and hence perform relaxation if we are
1873   // not doing relocatable linking.
1874   virtual bool
1875   do_may_relax() const
1876   { return !parameters->options().relocatable(); }
1877
1878   // Relaxation hook.  This is where we do stub generation.
1879   virtual bool
1880   do_relax(int, const Input_objects*, Symbol_table*, Layout*, const Task*);
1881
1882   void
1883   group_sections(Layout* layout,
1884                  section_size_type group_size,
1885                  bool stubs_always_after_branch,
1886                  const Task* task);
1887
1888   void
1889   scan_reloc_for_stub(const The_relocate_info*, unsigned int,
1890                       const Sized_symbol<size>*, unsigned int,
1891                       const Symbol_value<size>*,
1892                       typename elfcpp::Elf_types<size>::Elf_Swxword,
1893                       Address Elf_Addr);
1894
1895   // Make an output section.
1896   Output_section*
1897   do_make_output_section(const char* name, elfcpp::Elf_Word type,
1898                          elfcpp::Elf_Xword flags)
1899   { return new The_aarch64_output_section(name, type, flags); }
1900
1901  private:
1902   // The class which scans relocations.
1903   class Scan
1904   {
1905   public:
1906     Scan()
1907       : issued_non_pic_error_(false)
1908     { }
1909
1910     inline void
1911     local(Symbol_table* symtab, Layout* layout, Target_aarch64* target,
1912           Sized_relobj_file<size, big_endian>* object,
1913           unsigned int data_shndx,
1914           Output_section* output_section,
1915           const elfcpp::Rela<size, big_endian>& reloc, unsigned int r_type,
1916           const elfcpp::Sym<size, big_endian>& lsym,
1917           bool is_discarded);
1918
1919     inline void
1920     global(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            Symbol* gsym);
1926
1927     inline bool
1928     local_reloc_may_be_function_pointer(Symbol_table* , Layout* ,
1929                                         Target_aarch64<size, big_endian>* ,
1930                                         Sized_relobj_file<size, big_endian>* ,
1931                                         unsigned int ,
1932                                         Output_section* ,
1933                                         const elfcpp::Rela<size, big_endian>& ,
1934                                         unsigned int r_type,
1935                                         const elfcpp::Sym<size, big_endian>&);
1936
1937     inline bool
1938     global_reloc_may_be_function_pointer(Symbol_table* , Layout* ,
1939                                          Target_aarch64<size, big_endian>* ,
1940                                          Sized_relobj_file<size, big_endian>* ,
1941                                          unsigned int ,
1942                                          Output_section* ,
1943                                          const elfcpp::Rela<size, big_endian>& ,
1944                                          unsigned int r_type,
1945                                          Symbol* gsym);
1946
1947   private:
1948     static void
1949     unsupported_reloc_local(Sized_relobj_file<size, big_endian>*,
1950                             unsigned int r_type);
1951
1952     static void
1953     unsupported_reloc_global(Sized_relobj_file<size, big_endian>*,
1954                              unsigned int r_type, Symbol*);
1955
1956     inline bool
1957     possible_function_pointer_reloc(unsigned int r_type);
1958
1959     void
1960     check_non_pic(Relobj*, unsigned int r_type);
1961
1962     // Whether we have issued an error about a non-PIC compilation.
1963     bool issued_non_pic_error_;
1964   };
1965
1966   // The class which implements relocation.
1967   class Relocate
1968   {
1969    public:
1970     Relocate()
1971       : skip_call_tls_get_addr_(false)
1972     { }
1973
1974     ~Relocate()
1975     { }
1976
1977     // Do a relocation.  Return false if the caller should not issue
1978     // any warnings about this relocation.
1979     inline bool
1980     relocate(const Relocate_info<size, big_endian>*, Target_aarch64*,
1981              Output_section*,
1982              size_t relnum, const elfcpp::Rela<size, big_endian>&,
1983              unsigned int r_type, const Sized_symbol<size>*,
1984              const Symbol_value<size>*,
1985              unsigned char*, typename elfcpp::Elf_types<size>::Elf_Addr,
1986              section_size_type);
1987
1988   private:
1989     inline typename AArch64_relocate_functions<size, big_endian>::Status
1990     relocate_tls(const Relocate_info<size, big_endian>*,
1991                  Target_aarch64<size, big_endian>*,
1992                  size_t,
1993                  const elfcpp::Rela<size, big_endian>&,
1994                  unsigned int r_type, const Sized_symbol<size>*,
1995                  const Symbol_value<size>*,
1996                  unsigned char*,
1997                  typename elfcpp::Elf_types<size>::Elf_Addr);
1998
1999     inline typename AArch64_relocate_functions<size, big_endian>::Status
2000     tls_gd_to_le(
2001                  const Relocate_info<size, big_endian>*,
2002                  Target_aarch64<size, big_endian>*,
2003                  const elfcpp::Rela<size, big_endian>&,
2004                  unsigned int,
2005                  unsigned char*,
2006                  const Symbol_value<size>*);
2007
2008     inline typename AArch64_relocate_functions<size, big_endian>::Status
2009     tls_ie_to_le(
2010                  const Relocate_info<size, big_endian>*,
2011                  Target_aarch64<size, big_endian>*,
2012                  const elfcpp::Rela<size, big_endian>&,
2013                  unsigned int,
2014                  unsigned char*,
2015                  const Symbol_value<size>*);
2016
2017     inline typename AArch64_relocate_functions<size, big_endian>::Status
2018     tls_desc_gd_to_le(
2019                  const Relocate_info<size, big_endian>*,
2020                  Target_aarch64<size, big_endian>*,
2021                  const elfcpp::Rela<size, big_endian>&,
2022                  unsigned int,
2023                  unsigned char*,
2024                  const Symbol_value<size>*);
2025
2026     inline typename AArch64_relocate_functions<size, big_endian>::Status
2027     tls_desc_gd_to_ie(
2028                  const Relocate_info<size, big_endian>*,
2029                  Target_aarch64<size, big_endian>*,
2030                  const elfcpp::Rela<size, big_endian>&,
2031                  unsigned int,
2032                  unsigned char*,
2033                  const Symbol_value<size>*,
2034                  typename elfcpp::Elf_types<size>::Elf_Addr,
2035                  typename elfcpp::Elf_types<size>::Elf_Addr);
2036
2037     bool skip_call_tls_get_addr_;
2038
2039   };  // End of class Relocate
2040
2041   // A class which returns the size required for a relocation type,
2042   // used while scanning relocs during a relocatable link.
2043   class Relocatable_size_for_reloc
2044   {
2045    public:
2046     unsigned int
2047     get_size_for_reloc(unsigned int, Relobj*);
2048   };
2049
2050   // Adjust TLS relocation type based on the options and whether this
2051   // is a local symbol.
2052   static tls::Tls_optimization
2053   optimize_tls_reloc(bool is_final, int r_type);
2054
2055   // Get the GOT section, creating it if necessary.
2056   Output_data_got_aarch64<size, big_endian>*
2057   got_section(Symbol_table*, Layout*);
2058
2059   // Get the GOT PLT section.
2060   Output_data_space*
2061   got_plt_section() const
2062   {
2063     gold_assert(this->got_plt_ != NULL);
2064     return this->got_plt_;
2065   }
2066
2067   // Get the GOT section for TLSDESC entries.
2068   Output_data_got<size, big_endian>*
2069   got_tlsdesc_section() const
2070   {
2071     gold_assert(this->got_tlsdesc_ != NULL);
2072     return this->got_tlsdesc_;
2073   }
2074
2075   // Create the PLT section.
2076   void
2077   make_plt_section(Symbol_table* symtab, Layout* layout);
2078
2079   // Create a PLT entry for a global symbol.
2080   void
2081   make_plt_entry(Symbol_table*, Layout*, Symbol*);
2082
2083   // Create a PLT entry for a local STT_GNU_IFUNC symbol.
2084   void
2085   make_local_ifunc_plt_entry(Symbol_table*, Layout*,
2086                              Sized_relobj_file<size, big_endian>* relobj,
2087                              unsigned int local_sym_index);
2088
2089   // Define the _TLS_MODULE_BASE_ symbol in the TLS segment.
2090   void
2091   define_tls_base_symbol(Symbol_table*, Layout*);
2092
2093   // Create the reserved PLT and GOT entries for the TLS descriptor resolver.
2094   void
2095   reserve_tlsdesc_entries(Symbol_table* symtab, Layout* layout);
2096
2097   // Create a GOT entry for the TLS module index.
2098   unsigned int
2099   got_mod_index_entry(Symbol_table* symtab, Layout* layout,
2100                       Sized_relobj_file<size, big_endian>* object);
2101
2102   // Get the PLT section.
2103   Output_data_plt_aarch64<size, big_endian>*
2104   plt_section() const
2105   {
2106     gold_assert(this->plt_ != NULL);
2107     return this->plt_;
2108   }
2109
2110   // Get the dynamic reloc section, creating it if necessary.
2111   Reloc_section*
2112   rela_dyn_section(Layout*);
2113
2114   // Get the section to use for TLSDESC relocations.
2115   Reloc_section*
2116   rela_tlsdesc_section(Layout*) const;
2117
2118   // Get the section to use for IRELATIVE relocations.
2119   Reloc_section*
2120   rela_irelative_section(Layout*);
2121
2122   // Add a potential copy relocation.
2123   void
2124   copy_reloc(Symbol_table* symtab, Layout* layout,
2125              Sized_relobj_file<size, big_endian>* object,
2126              unsigned int shndx, Output_section* output_section,
2127              Symbol* sym, const elfcpp::Rela<size, big_endian>& reloc)
2128   {
2129     this->copy_relocs_.copy_reloc(symtab, layout,
2130                                   symtab->get_sized_symbol<size>(sym),
2131                                   object, shndx, output_section,
2132                                   reloc, this->rela_dyn_section(layout));
2133   }
2134
2135   // Information about this specific target which we pass to the
2136   // general Target structure.
2137   static const Target::Target_info aarch64_info;
2138
2139   // The types of GOT entries needed for this platform.
2140   // These values are exposed to the ABI in an incremental link.
2141   // Do not renumber existing values without changing the version
2142   // number of the .gnu_incremental_inputs section.
2143   enum Got_type
2144   {
2145     GOT_TYPE_STANDARD = 0,      // GOT entry for a regular symbol
2146     GOT_TYPE_TLS_OFFSET = 1,    // GOT entry for TLS offset
2147     GOT_TYPE_TLS_PAIR = 2,      // GOT entry for TLS module/offset pair
2148     GOT_TYPE_TLS_DESC = 3       // GOT entry for TLS_DESC pair
2149   };
2150
2151   // This type is used as the argument to the target specific
2152   // relocation routines.  The only target specific reloc is
2153   // R_AARCh64_TLSDESC against a local symbol.
2154   struct Tlsdesc_info
2155   {
2156     Tlsdesc_info(Sized_relobj_file<size, big_endian>* a_object,
2157                  unsigned int a_r_sym)
2158       : object(a_object), r_sym(a_r_sym)
2159     { }
2160
2161     // The object in which the local symbol is defined.
2162     Sized_relobj_file<size, big_endian>* object;
2163     // The local symbol index in the object.
2164     unsigned int r_sym;
2165   };
2166
2167   // The GOT section.
2168   Output_data_got_aarch64<size, big_endian>* got_;
2169   // The PLT section.
2170   Output_data_plt_aarch64<size, big_endian>* plt_;
2171   // The GOT PLT section.
2172   Output_data_space* got_plt_;
2173   // The GOT section for IRELATIVE relocations.
2174   Output_data_space* got_irelative_;
2175   // The GOT section for TLSDESC relocations.
2176   Output_data_got<size, big_endian>* got_tlsdesc_;
2177   // The _GLOBAL_OFFSET_TABLE_ symbol.
2178   Symbol* global_offset_table_;
2179   // The dynamic reloc section.
2180   Reloc_section* rela_dyn_;
2181   // The section to use for IRELATIVE relocs.
2182   Reloc_section* rela_irelative_;
2183   // Relocs saved to avoid a COPY reloc.
2184   Copy_relocs<elfcpp::SHT_RELA, size, big_endian> copy_relocs_;
2185   // Offset of the GOT entry for the TLS module index.
2186   unsigned int got_mod_index_offset_;
2187   // We handle R_AARCH64_TLSDESC against a local symbol as a target
2188   // specific relocation. Here we store the object and local symbol
2189   // index for the relocation.
2190   std::vector<Tlsdesc_info> tlsdesc_reloc_info_;
2191   // True if the _TLS_MODULE_BASE_ symbol has been defined.
2192   bool tls_base_symbol_defined_;
2193   // List of stub_tables
2194   Stub_table_list stub_tables_;
2195   AArch64_input_section_map aarch64_input_section_map_;
2196 };  // End of Target_aarch64
2197
2198
2199 template<>
2200 const Target::Target_info Target_aarch64<64, false>::aarch64_info =
2201 {
2202   64,                   // size
2203   false,                // is_big_endian
2204   elfcpp::EM_AARCH64,   // machine_code
2205   false,                // has_make_symbol
2206   false,                // has_resolve
2207   false,                // has_code_fill
2208   true,                 // is_default_stack_executable
2209   false,                // can_icf_inline_merge_sections
2210   '\0',                 // wrap_char
2211   "/lib/ld.so.1",       // program interpreter
2212   0x400000,             // default_text_segment_address
2213   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2214   0x1000,               // common_pagesize (overridable by -z common-page-size)
2215   false,                // isolate_execinstr
2216   0,                    // rosegment_gap
2217   elfcpp::SHN_UNDEF,    // small_common_shndx
2218   elfcpp::SHN_UNDEF,    // large_common_shndx
2219   0,                    // small_common_section_flags
2220   0,                    // large_common_section_flags
2221   NULL,                 // attributes_section
2222   NULL,                 // attributes_vendor
2223   "_start"              // entry_symbol_name
2224 };
2225
2226 template<>
2227 const Target::Target_info Target_aarch64<32, false>::aarch64_info =
2228 {
2229   32,                   // size
2230   false,                // is_big_endian
2231   elfcpp::EM_AARCH64,   // machine_code
2232   false,                // has_make_symbol
2233   false,                // has_resolve
2234   false,                // has_code_fill
2235   true,                 // is_default_stack_executable
2236   false,                // can_icf_inline_merge_sections
2237   '\0',                 // wrap_char
2238   "/lib/ld.so.1",       // program interpreter
2239   0x400000,             // default_text_segment_address
2240   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2241   0x1000,               // common_pagesize (overridable by -z common-page-size)
2242   false,                // isolate_execinstr
2243   0,                    // rosegment_gap
2244   elfcpp::SHN_UNDEF,    // small_common_shndx
2245   elfcpp::SHN_UNDEF,    // large_common_shndx
2246   0,                    // small_common_section_flags
2247   0,                    // large_common_section_flags
2248   NULL,                 // attributes_section
2249   NULL,                 // attributes_vendor
2250   "_start"              // entry_symbol_name
2251 };
2252
2253 template<>
2254 const Target::Target_info Target_aarch64<64, true>::aarch64_info =
2255 {
2256   64,                   // size
2257   true,                 // is_big_endian
2258   elfcpp::EM_AARCH64,   // machine_code
2259   false,                // has_make_symbol
2260   false,                // has_resolve
2261   false,                // has_code_fill
2262   true,                 // is_default_stack_executable
2263   false,                // can_icf_inline_merge_sections
2264   '\0',                 // wrap_char
2265   "/lib/ld.so.1",       // program interpreter
2266   0x400000,             // default_text_segment_address
2267   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2268   0x1000,               // common_pagesize (overridable by -z common-page-size)
2269   false,                // isolate_execinstr
2270   0,                    // rosegment_gap
2271   elfcpp::SHN_UNDEF,    // small_common_shndx
2272   elfcpp::SHN_UNDEF,    // large_common_shndx
2273   0,                    // small_common_section_flags
2274   0,                    // large_common_section_flags
2275   NULL,                 // attributes_section
2276   NULL,                 // attributes_vendor
2277   "_start"              // entry_symbol_name
2278 };
2279
2280 template<>
2281 const Target::Target_info Target_aarch64<32, true>::aarch64_info =
2282 {
2283   32,                   // size
2284   true,                 // is_big_endian
2285   elfcpp::EM_AARCH64,   // machine_code
2286   false,                // has_make_symbol
2287   false,                // has_resolve
2288   false,                // has_code_fill
2289   true,                 // is_default_stack_executable
2290   false,                // can_icf_inline_merge_sections
2291   '\0',                 // wrap_char
2292   "/lib/ld.so.1",       // program interpreter
2293   0x400000,             // default_text_segment_address
2294   0x1000,               // abi_pagesize (overridable by -z max-page-size)
2295   0x1000,               // common_pagesize (overridable by -z common-page-size)
2296   false,                // isolate_execinstr
2297   0,                    // rosegment_gap
2298   elfcpp::SHN_UNDEF,    // small_common_shndx
2299   elfcpp::SHN_UNDEF,    // large_common_shndx
2300   0,                    // small_common_section_flags
2301   0,                    // large_common_section_flags
2302   NULL,                 // attributes_section
2303   NULL,                 // attributes_vendor
2304   "_start"              // entry_symbol_name
2305 };
2306
2307 // Get the GOT section, creating it if necessary.
2308
2309 template<int size, bool big_endian>
2310 Output_data_got_aarch64<size, big_endian>*
2311 Target_aarch64<size, big_endian>::got_section(Symbol_table* symtab,
2312                                               Layout* layout)
2313 {
2314   if (this->got_ == NULL)
2315     {
2316       gold_assert(symtab != NULL && layout != NULL);
2317
2318       // When using -z now, we can treat .got.plt as a relro section.
2319       // Without -z now, it is modified after program startup by lazy
2320       // PLT relocations.
2321       bool is_got_plt_relro = parameters->options().now();
2322       Output_section_order got_order = (is_got_plt_relro
2323                                         ? ORDER_RELRO
2324                                         : ORDER_RELRO_LAST);
2325       Output_section_order got_plt_order = (is_got_plt_relro
2326                                             ? ORDER_RELRO
2327                                             : ORDER_NON_RELRO_FIRST);
2328
2329       // Layout of .got and .got.plt sections.
2330       // .got[0] &_DYNAMIC                          <-_GLOBAL_OFFSET_TABLE_
2331       // ...
2332       // .gotplt[0] reserved for ld.so (&linkmap)   <--DT_PLTGOT
2333       // .gotplt[1] reserved for ld.so (resolver)
2334       // .gotplt[2] reserved
2335
2336       // Generate .got section.
2337       this->got_ = new Output_data_got_aarch64<size, big_endian>(symtab,
2338                                                                  layout);
2339       layout->add_output_section_data(".got", elfcpp::SHT_PROGBITS,
2340                                       (elfcpp::SHF_ALLOC | elfcpp::SHF_WRITE),
2341                                       this->got_, got_order, true);
2342       // The first word of GOT is reserved for the address of .dynamic.
2343       // We put 0 here now. The value will be replaced later in
2344       // Output_data_got_aarch64::do_write.
2345       this->got_->add_constant(0);
2346
2347       // Define _GLOBAL_OFFSET_TABLE_ at the start of the PLT.
2348       // _GLOBAL_OFFSET_TABLE_ value points to the start of the .got section,
2349       // even if there is a .got.plt section.
2350       this->global_offset_table_ =
2351         symtab->define_in_output_data("_GLOBAL_OFFSET_TABLE_", NULL,
2352                                       Symbol_table::PREDEFINED,
2353                                       this->got_,
2354                                       0, 0, elfcpp::STT_OBJECT,
2355                                       elfcpp::STB_LOCAL,
2356                                       elfcpp::STV_HIDDEN, 0,
2357                                       false, false);
2358
2359       // Generate .got.plt section.
2360       this->got_plt_ = new Output_data_space(size / 8, "** GOT PLT");
2361       layout->add_output_section_data(".got.plt", elfcpp::SHT_PROGBITS,
2362                                       (elfcpp::SHF_ALLOC
2363                                        | elfcpp::SHF_WRITE),
2364                                       this->got_plt_, got_plt_order,
2365                                       is_got_plt_relro);
2366
2367       // The first three entries are reserved.
2368       this->got_plt_->set_current_data_size(
2369         AARCH64_GOTPLT_RESERVE_COUNT * (size / 8));
2370
2371       // If there are any IRELATIVE relocations, they get GOT entries
2372       // in .got.plt after the jump slot entries.
2373       this->got_irelative_ = new Output_data_space(size / 8,
2374                                                    "** GOT IRELATIVE PLT");
2375       layout->add_output_section_data(".got.plt", elfcpp::SHT_PROGBITS,
2376                                       (elfcpp::SHF_ALLOC
2377                                        | elfcpp::SHF_WRITE),
2378                                       this->got_irelative_,
2379                                       got_plt_order,
2380                                       is_got_plt_relro);
2381
2382       // If there are any TLSDESC relocations, they get GOT entries in
2383       // .got.plt after the jump slot and IRELATIVE entries.
2384       this->got_tlsdesc_ = new Output_data_got<size, big_endian>();
2385       layout->add_output_section_data(".got.plt", elfcpp::SHT_PROGBITS,
2386                                       (elfcpp::SHF_ALLOC
2387                                        | elfcpp::SHF_WRITE),
2388                                       this->got_tlsdesc_,
2389                                       got_plt_order,
2390                                       is_got_plt_relro);
2391
2392       if (!is_got_plt_relro)
2393         {
2394           // Those bytes can go into the relro segment.
2395           layout->increase_relro(
2396             AARCH64_GOTPLT_RESERVE_COUNT * (size / 8));
2397         }
2398
2399     }
2400   return this->got_;
2401 }
2402
2403 // Get the dynamic reloc section, creating it if necessary.
2404
2405 template<int size, bool big_endian>
2406 typename Target_aarch64<size, big_endian>::Reloc_section*
2407 Target_aarch64<size, big_endian>::rela_dyn_section(Layout* layout)
2408 {
2409   if (this->rela_dyn_ == NULL)
2410     {
2411       gold_assert(layout != NULL);
2412       this->rela_dyn_ = new Reloc_section(parameters->options().combreloc());
2413       layout->add_output_section_data(".rela.dyn", elfcpp::SHT_RELA,
2414                                       elfcpp::SHF_ALLOC, this->rela_dyn_,
2415                                       ORDER_DYNAMIC_RELOCS, false);
2416     }
2417   return this->rela_dyn_;
2418 }
2419
2420 // Get the section to use for IRELATIVE relocs, creating it if
2421 // necessary.  These go in .rela.dyn, but only after all other dynamic
2422 // relocations.  They need to follow the other dynamic relocations so
2423 // that they can refer to global variables initialized by those
2424 // relocs.
2425
2426 template<int size, bool big_endian>
2427 typename Target_aarch64<size, big_endian>::Reloc_section*
2428 Target_aarch64<size, big_endian>::rela_irelative_section(Layout* layout)
2429 {
2430   if (this->rela_irelative_ == NULL)
2431     {
2432       // Make sure we have already created the dynamic reloc section.
2433       this->rela_dyn_section(layout);
2434       this->rela_irelative_ = new Reloc_section(false);
2435       layout->add_output_section_data(".rela.dyn", elfcpp::SHT_RELA,
2436                                       elfcpp::SHF_ALLOC, this->rela_irelative_,
2437                                       ORDER_DYNAMIC_RELOCS, false);
2438       gold_assert(this->rela_dyn_->output_section()
2439                   == this->rela_irelative_->output_section());
2440     }
2441   return this->rela_irelative_;
2442 }
2443
2444
2445 // do_make_elf_object to override the same function in the base class.  We need
2446 // to use a target-specific sub-class of Sized_relobj_file<size, big_endian> to
2447 // store backend specific information. Hence we need to have our own ELF object
2448 // creation.
2449
2450 template<int size, bool big_endian>
2451 Object*
2452 Target_aarch64<size, big_endian>::do_make_elf_object(
2453     const std::string& name,
2454     Input_file* input_file,
2455     off_t offset, const elfcpp::Ehdr<size, big_endian>& ehdr)
2456 {
2457   int et = ehdr.get_e_type();
2458   // ET_EXEC files are valid input for --just-symbols/-R,
2459   // and we treat them as relocatable objects.
2460   if (et == elfcpp::ET_EXEC && input_file->just_symbols())
2461     return Sized_target<size, big_endian>::do_make_elf_object(
2462         name, input_file, offset, ehdr);
2463   else if (et == elfcpp::ET_REL)
2464     {
2465       AArch64_relobj<size, big_endian>* obj =
2466         new AArch64_relobj<size, big_endian>(name, input_file, offset, ehdr);
2467       obj->setup();
2468       return obj;
2469     }
2470   else if (et == elfcpp::ET_DYN)
2471     {
2472       // Keep base implementation.
2473       Sized_dynobj<size, big_endian>* obj =
2474           new Sized_dynobj<size, big_endian>(name, input_file, offset, ehdr);
2475       obj->setup();
2476       return obj;
2477     }
2478   else
2479     {
2480       gold_error(_("%s: unsupported ELF file type %d"),
2481                  name.c_str(), et);
2482       return NULL;
2483     }
2484 }
2485
2486
2487 // Scan a relocation for stub generation.
2488
2489 template<int size, bool big_endian>
2490 void
2491 Target_aarch64<size, big_endian>::scan_reloc_for_stub(
2492     const Relocate_info<size, big_endian>* relinfo,
2493     unsigned int r_type,
2494     const Sized_symbol<size>* gsym,
2495     unsigned int r_sym,
2496     const Symbol_value<size>* psymval,
2497     typename elfcpp::Elf_types<size>::Elf_Swxword addend,
2498     Address address)
2499 {
2500   const AArch64_relobj<size, big_endian>* aarch64_relobj =
2501       static_cast<AArch64_relobj<size, big_endian>*>(relinfo->object);
2502
2503   Symbol_value<size> symval;
2504   if (gsym != NULL)
2505     {
2506       const AArch64_reloc_property* arp = aarch64_reloc_property_table->
2507         get_reloc_property(r_type);
2508       if (gsym->use_plt_offset(arp->reference_flags()))
2509         {
2510           // This uses a PLT, change the symbol value.
2511           symval.set_output_value(this->plt_section()->address()
2512                                   + gsym->plt_offset());
2513           psymval = &symval;
2514         }
2515       else if (gsym->is_undefined())
2516         // There is no need to generate a stub symbol is undefined.
2517         return;
2518     }
2519
2520   // Get the symbol value.
2521   typename Symbol_value<size>::Value value = psymval->value(aarch64_relobj, 0);
2522
2523   // Owing to pipelining, the PC relative branches below actually skip
2524   // two instructions when the branch offset is 0.
2525   Address destination = static_cast<Address>(-1);
2526   switch (r_type)
2527     {
2528     case elfcpp::R_AARCH64_CALL26:
2529     case elfcpp::R_AARCH64_JUMP26:
2530       destination = value + addend;
2531       break;
2532     default:
2533       gold_assert(false);
2534     }
2535
2536   typename The_reloc_stub::Stub_type stub_type = The_reloc_stub::
2537       stub_type_for_reloc(r_type, address, destination);
2538   if (stub_type == The_reloc_stub::ST_NONE)
2539     return ;
2540
2541   The_stub_table* stub_table = aarch64_relobj->stub_table(relinfo->data_shndx);
2542   gold_assert(stub_table != NULL);
2543
2544   The_reloc_stub_key key(stub_type, gsym, aarch64_relobj, r_sym, addend);
2545   The_reloc_stub* stub = stub_table->find_reloc_stub(key);
2546   if (stub == NULL)
2547     {
2548       stub = new The_reloc_stub(stub_type);
2549       stub_table->add_reloc_stub(stub, key);
2550     }
2551   stub->set_destination_address(destination);
2552 }  // End of Target_aarch64::scan_reloc_for_stub
2553
2554
2555 // This function scans a relocation section for stub generation.
2556 // The template parameter Relocate must be a class type which provides
2557 // a single function, relocate(), which implements the machine
2558 // specific part of a relocation.
2559
2560 // BIG_ENDIAN is the endianness of the data.  SH_TYPE is the section type:
2561 // SHT_REL or SHT_RELA.
2562
2563 // PRELOCS points to the relocation data.  RELOC_COUNT is the number
2564 // of relocs.  OUTPUT_SECTION is the output section.
2565 // NEEDS_SPECIAL_OFFSET_HANDLING is true if input offsets need to be
2566 // mapped to output offsets.
2567
2568 // VIEW is the section data, VIEW_ADDRESS is its memory address, and
2569 // VIEW_SIZE is the size.  These refer to the input section, unless
2570 // NEEDS_SPECIAL_OFFSET_HANDLING is true, in which case they refer to
2571 // the output section.
2572
2573 template<int size, bool big_endian>
2574 template<int sh_type>
2575 void inline
2576 Target_aarch64<size, big_endian>::scan_reloc_section_for_stubs(
2577     const Relocate_info<size, big_endian>* relinfo,
2578     const unsigned char* prelocs,
2579     size_t reloc_count,
2580     Output_section* /*output_section*/,
2581     bool /*needs_special_offset_handling*/,
2582     const unsigned char* /*view*/,
2583     Address view_address,
2584     section_size_type)
2585 {
2586   typedef typename Reloc_types<sh_type,size,big_endian>::Reloc Reltype;
2587
2588   const int reloc_size =
2589       Reloc_types<sh_type,size,big_endian>::reloc_size;
2590   AArch64_relobj<size, big_endian>* object =
2591       static_cast<AArch64_relobj<size, big_endian>*>(relinfo->object);
2592   unsigned int local_count = object->local_symbol_count();
2593
2594   gold::Default_comdat_behavior default_comdat_behavior;
2595   Comdat_behavior comdat_behavior = CB_UNDETERMINED;
2596
2597   for (size_t i = 0; i < reloc_count; ++i, prelocs += reloc_size)
2598     {
2599       Reltype reloc(prelocs);
2600       typename elfcpp::Elf_types<size>::Elf_WXword r_info = reloc.get_r_info();
2601       unsigned int r_sym = elfcpp::elf_r_sym<size>(r_info);
2602       unsigned int r_type = elfcpp::elf_r_type<size>(r_info);
2603       if (r_type != elfcpp::R_AARCH64_CALL26
2604           && r_type != elfcpp::R_AARCH64_JUMP26)
2605         continue;
2606
2607       section_offset_type offset =
2608           convert_to_section_size_type(reloc.get_r_offset());
2609
2610       // Get the addend.
2611       typename elfcpp::Elf_types<size>::Elf_Swxword addend =
2612           reloc.get_r_addend();
2613
2614       const Sized_symbol<size>* sym;
2615       Symbol_value<size> symval;
2616       const Symbol_value<size> *psymval;
2617       bool is_defined_in_discarded_section;
2618       unsigned int shndx;
2619       if (r_sym < local_count)
2620         {
2621           sym = NULL;
2622           psymval = object->local_symbol(r_sym);
2623
2624           // If the local symbol belongs to a section we are discarding,
2625           // and that section is a debug section, try to find the
2626           // corresponding kept section and map this symbol to its
2627           // counterpart in the kept section.  The symbol must not
2628           // correspond to a section we are folding.
2629           bool is_ordinary;
2630           shndx = psymval->input_shndx(&is_ordinary);
2631           is_defined_in_discarded_section =
2632             (is_ordinary
2633              && shndx != elfcpp::SHN_UNDEF
2634              && !object->is_section_included(shndx)
2635              && !relinfo->symtab->is_section_folded(object, shndx));
2636
2637           // We need to compute the would-be final value of this local
2638           // symbol.
2639           if (!is_defined_in_discarded_section)
2640             {
2641               typedef Sized_relobj_file<size, big_endian> ObjType;
2642               typename ObjType::Compute_final_local_value_status status =
2643                 object->compute_final_local_value(r_sym, psymval, &symval,
2644                                                   relinfo->symtab);
2645               if (status == ObjType::CFLV_OK)
2646                 {
2647                   // Currently we cannot handle a branch to a target in
2648                   // a merged section.  If this is the case, issue an error
2649                   // and also free the merge symbol value.
2650                   if (!symval.has_output_value())
2651                     {
2652                       const std::string& section_name =
2653                         object->section_name(shndx);
2654                       object->error(_("cannot handle branch to local %u "
2655                                           "in a merged section %s"),
2656                                         r_sym, section_name.c_str());
2657                     }
2658                   psymval = &symval;
2659                 }
2660               else
2661                 {
2662                   // We cannot determine the final value.
2663                   continue;
2664                 }
2665             }
2666         }
2667       else
2668         {
2669           const Symbol* gsym;
2670           gsym = object->global_symbol(r_sym);
2671           gold_assert(gsym != NULL);
2672           if (gsym->is_forwarder())
2673             gsym = relinfo->symtab->resolve_forwards(gsym);
2674
2675           sym = static_cast<const Sized_symbol<size>*>(gsym);
2676           if (sym->has_symtab_index() && sym->symtab_index() != -1U)
2677             symval.set_output_symtab_index(sym->symtab_index());
2678           else
2679             symval.set_no_output_symtab_entry();
2680
2681           // We need to compute the would-be final value of this global
2682           // symbol.
2683           const Symbol_table* symtab = relinfo->symtab;
2684           const Sized_symbol<size>* sized_symbol =
2685               symtab->get_sized_symbol<size>(gsym);
2686           Symbol_table::Compute_final_value_status status;
2687           typename elfcpp::Elf_types<size>::Elf_Addr value =
2688               symtab->compute_final_value<size>(sized_symbol, &status);
2689
2690           // Skip this if the symbol has not output section.
2691           if (status == Symbol_table::CFVS_NO_OUTPUT_SECTION)
2692             continue;
2693           symval.set_output_value(value);
2694
2695           if (gsym->type() == elfcpp::STT_TLS)
2696             symval.set_is_tls_symbol();
2697           else if (gsym->type() == elfcpp::STT_GNU_IFUNC)
2698             symval.set_is_ifunc_symbol();
2699           psymval = &symval;
2700
2701           is_defined_in_discarded_section =
2702               (gsym->is_defined_in_discarded_section()
2703                && gsym->is_undefined());
2704           shndx = 0;
2705         }
2706
2707       Symbol_value<size> symval2;
2708       if (is_defined_in_discarded_section)
2709         {
2710           if (comdat_behavior == CB_UNDETERMINED)
2711             {
2712               std::string name = object->section_name(relinfo->data_shndx);
2713               comdat_behavior = default_comdat_behavior.get(name.c_str());
2714             }
2715           if (comdat_behavior == CB_PRETEND)
2716             {
2717               bool found;
2718               typename elfcpp::Elf_types<size>::Elf_Addr value =
2719                 object->map_to_kept_section(shndx, &found);
2720               if (found)
2721                 symval2.set_output_value(value + psymval->input_value());
2722               else
2723                 symval2.set_output_value(0);
2724             }
2725           else
2726             {
2727               if (comdat_behavior == CB_WARNING)
2728                 gold_warning_at_location(relinfo, i, offset,
2729                                          _("relocation refers to discarded "
2730                                            "section"));
2731               symval2.set_output_value(0);
2732             }
2733           symval2.set_no_output_symtab_entry();
2734           psymval = &symval2;
2735         }
2736
2737       // If symbol is a section symbol, we don't know the actual type of
2738       // destination.  Give up.
2739       if (psymval->is_section_symbol())
2740         continue;
2741
2742       this->scan_reloc_for_stub(relinfo, r_type, sym, r_sym, psymval,
2743                                 addend, view_address + offset);
2744     }  // End of iterating relocs in a section
2745 }  // End of Target_aarch64::scan_reloc_section_for_stubs
2746
2747
2748 // Scan an input section for stub generation.
2749
2750 template<int size, bool big_endian>
2751 void
2752 Target_aarch64<size, big_endian>::scan_section_for_stubs(
2753     const Relocate_info<size, big_endian>* relinfo,
2754     unsigned int sh_type,
2755     const unsigned char* prelocs,
2756     size_t reloc_count,
2757     Output_section* output_section,
2758     bool needs_special_offset_handling,
2759     const unsigned char* view,
2760     Address view_address,
2761     section_size_type view_size)
2762 {
2763   gold_assert(sh_type == elfcpp::SHT_RELA);
2764   this->scan_reloc_section_for_stubs<elfcpp::SHT_RELA>(
2765       relinfo,
2766       prelocs,
2767       reloc_count,
2768       output_section,
2769       needs_special_offset_handling,
2770       view,
2771       view_address,
2772       view_size);
2773 }
2774
2775
2776 // Relocate a single stub.
2777
2778 template<int size, bool big_endian>
2779 void Target_aarch64<size, big_endian>::
2780 relocate_stub(The_reloc_stub* stub,
2781               const The_relocate_info*,
2782               Output_section*,
2783               unsigned char* view,
2784               Address address,
2785               section_size_type)
2786 {
2787   typedef AArch64_relocate_functions<size, big_endian> The_reloc_functions;
2788   typedef typename The_reloc_functions::Status The_reloc_functions_status;
2789   typedef typename elfcpp::Swap<32,big_endian>::Valtype Insntype;
2790
2791   Insntype* ip = reinterpret_cast<Insntype*>(view);
2792   int insn_number = stub->stub_insn_number();
2793   const uint32_t* insns = stub->stub_insns();
2794   // Check the insns are really those stub insns.
2795   for (int i = 0; i < insn_number; ++i)
2796     {
2797       Insntype insn = elfcpp::Swap<32,big_endian>::readval(ip + i);
2798       gold_assert(((uint32_t)insn == insns[i+1]));
2799     }
2800
2801   Address dest = stub->destination_address();
2802
2803   switch(stub->stub_type())
2804     {
2805     case The_reloc_stub::ST_ADRP_BRANCH:
2806       {
2807         // 1st reloc is ADR_PREL_PG_HI21
2808         The_reloc_functions_status status =
2809             The_reloc_functions::adrp(view, dest, address);
2810         // An error should never arise in the above step. If so, please
2811         // check 'aarch64_valid_for_adrp_p'.
2812         gold_assert(status == The_reloc_functions::STATUS_OKAY);
2813
2814         // 2nd reloc is ADD_ABS_LO12_NC
2815         const AArch64_reloc_property* arp =
2816             aarch64_reloc_property_table->get_reloc_property(
2817                 elfcpp::R_AARCH64_ADD_ABS_LO12_NC);
2818         gold_assert(arp != NULL);
2819         status = The_reloc_functions::template
2820             rela_general<32>(view + 4, dest, 0, arp);
2821         // An error should never arise, it is an "_NC" relocation.
2822         gold_assert(status == The_reloc_functions::STATUS_OKAY);
2823       }
2824       break;
2825
2826     case The_reloc_stub::ST_LONG_BRANCH_ABS:
2827       // 1st reloc is R_AARCH64_PREL64, at offset 8
2828       elfcpp::Swap<64,big_endian>::writeval(view + 8, dest);
2829       break;
2830
2831     case The_reloc_stub::ST_LONG_BRANCH_PCREL:
2832       {
2833         // "PC" calculation is the 2nd insn in the stub.
2834         uint64_t offset = dest - (address + 4);
2835         // Offset is placed at offset 4 and 5.
2836         elfcpp::Swap<64,big_endian>::writeval(view + 16, offset);
2837       }
2838       break;
2839
2840     default:
2841       gold_assert(false);
2842     }
2843 }
2844
2845
2846 // A class to handle the PLT data.
2847 // This is an abstract base class that handles most of the linker details
2848 // but does not know the actual contents of PLT entries.  The derived
2849 // classes below fill in those details.
2850
2851 template<int size, bool big_endian>
2852 class Output_data_plt_aarch64 : public Output_section_data
2853 {
2854  public:
2855   typedef Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>
2856       Reloc_section;
2857   typedef typename elfcpp::Elf_types<size>::Elf_Addr Address;
2858
2859   Output_data_plt_aarch64(Layout* layout,
2860                           uint64_t addralign,
2861                           Output_data_got_aarch64<size, big_endian>* got,
2862                           Output_data_space* got_plt,
2863                           Output_data_space* got_irelative)
2864     : Output_section_data(addralign), tlsdesc_rel_(NULL),
2865       got_(got), got_plt_(got_plt), got_irelative_(got_irelative),
2866       count_(0), irelative_count_(0), tlsdesc_got_offset_(-1U)
2867   { this->init(layout); }
2868
2869   // Initialize the PLT section.
2870   void
2871   init(Layout* layout);
2872
2873   // Add an entry to the PLT.
2874   void
2875   add_entry(Symbol* gsym);
2876
2877   // Add the reserved TLSDESC_PLT entry to the PLT.
2878   void
2879   reserve_tlsdesc_entry(unsigned int got_offset)
2880   { this->tlsdesc_got_offset_ = got_offset; }
2881
2882   // Return true if a TLSDESC_PLT entry has been reserved.
2883   bool
2884   has_tlsdesc_entry() const
2885   { return this->tlsdesc_got_offset_ != -1U; }
2886
2887   // Return the GOT offset for the reserved TLSDESC_PLT entry.
2888   unsigned int
2889   get_tlsdesc_got_offset() const
2890   { return this->tlsdesc_got_offset_; }
2891
2892   // Return the PLT offset of the reserved TLSDESC_PLT entry.
2893   unsigned int
2894   get_tlsdesc_plt_offset() const
2895   {
2896     return (this->first_plt_entry_offset() +
2897             (this->count_ + this->irelative_count_)
2898             * this->get_plt_entry_size());
2899   }
2900
2901   // Return the .rela.plt section data.
2902   Reloc_section*
2903   rela_plt()
2904   { return this->rel_; }
2905
2906   // Return where the TLSDESC relocations should go.
2907   Reloc_section*
2908   rela_tlsdesc(Layout*);
2909
2910   // Return where the IRELATIVE relocations should go in the PLT
2911   // relocations.
2912   Reloc_section*
2913   rela_irelative(Symbol_table*, Layout*);
2914
2915   // Return whether we created a section for IRELATIVE relocations.
2916   bool
2917   has_irelative_section() const
2918   { return this->irelative_rel_ != NULL; }
2919
2920   // Return the number of PLT entries.
2921   unsigned int
2922   entry_count() const
2923   { return this->count_ + this->irelative_count_; }
2924
2925   // Return the offset of the first non-reserved PLT entry.
2926   unsigned int
2927   first_plt_entry_offset() const
2928   { return this->do_first_plt_entry_offset(); }
2929
2930   // Return the size of a PLT entry.
2931   unsigned int
2932   get_plt_entry_size() const
2933   { return this->do_get_plt_entry_size(); }
2934
2935   // Return the reserved tlsdesc entry size.
2936   unsigned int
2937   get_plt_tlsdesc_entry_size() const
2938   { return this->do_get_plt_tlsdesc_entry_size(); }
2939
2940   // Return the PLT address to use for a global symbol.
2941   uint64_t
2942   address_for_global(const Symbol*);
2943
2944   // Return the PLT address to use for a local symbol.
2945   uint64_t
2946   address_for_local(const Relobj*, unsigned int symndx);
2947
2948  protected:
2949   // Fill in the first PLT entry.
2950   void
2951   fill_first_plt_entry(unsigned char* pov,
2952                        Address got_address,
2953                        Address plt_address)
2954   { this->do_fill_first_plt_entry(pov, got_address, plt_address); }
2955
2956   // Fill in a normal PLT entry.
2957   void
2958   fill_plt_entry(unsigned char* pov,
2959                  Address got_address,
2960                  Address plt_address,
2961                  unsigned int got_offset,
2962                  unsigned int plt_offset)
2963   {
2964     this->do_fill_plt_entry(pov, got_address, plt_address,
2965                             got_offset, plt_offset);
2966   }
2967
2968   // Fill in the reserved TLSDESC PLT entry.
2969   void
2970   fill_tlsdesc_entry(unsigned char* pov,
2971                      Address gotplt_address,
2972                      Address plt_address,
2973                      Address got_base,
2974                      unsigned int tlsdesc_got_offset,
2975                      unsigned int plt_offset)
2976   {
2977     this->do_fill_tlsdesc_entry(pov, gotplt_address, plt_address, got_base,
2978                                 tlsdesc_got_offset, plt_offset);
2979   }
2980
2981   virtual unsigned int
2982   do_first_plt_entry_offset() const = 0;
2983
2984   virtual unsigned int
2985   do_get_plt_entry_size() const = 0;
2986
2987   virtual unsigned int
2988   do_get_plt_tlsdesc_entry_size() const = 0;
2989
2990   virtual void
2991   do_fill_first_plt_entry(unsigned char* pov,
2992                           Address got_addr,
2993                           Address plt_addr) = 0;
2994
2995   virtual void
2996   do_fill_plt_entry(unsigned char* pov,
2997                     Address got_address,
2998                     Address plt_address,
2999                     unsigned int got_offset,
3000                     unsigned int plt_offset) = 0;
3001
3002   virtual void
3003   do_fill_tlsdesc_entry(unsigned char* pov,
3004                         Address gotplt_address,
3005                         Address plt_address,
3006                         Address got_base,
3007                         unsigned int tlsdesc_got_offset,
3008                         unsigned int plt_offset) = 0;
3009
3010   void
3011   do_adjust_output_section(Output_section* os);
3012
3013   // Write to a map file.
3014   void
3015   do_print_to_mapfile(Mapfile* mapfile) const
3016   { mapfile->print_output_data(this, _("** PLT")); }
3017
3018  private:
3019   // Set the final size.
3020   void
3021   set_final_data_size();
3022
3023   // Write out the PLT data.
3024   void
3025   do_write(Output_file*);
3026
3027   // The reloc section.
3028   Reloc_section* rel_;
3029
3030   // The TLSDESC relocs, if necessary.  These must follow the regular
3031   // PLT relocs.
3032   Reloc_section* tlsdesc_rel_;
3033
3034   // The IRELATIVE relocs, if necessary.  These must follow the
3035   // regular PLT relocations.
3036   Reloc_section* irelative_rel_;
3037
3038   // The .got section.
3039   Output_data_got_aarch64<size, big_endian>* got_;
3040
3041   // The .got.plt section.
3042   Output_data_space* got_plt_;
3043
3044   // The part of the .got.plt section used for IRELATIVE relocs.
3045   Output_data_space* got_irelative_;
3046
3047   // The number of PLT entries.
3048   unsigned int count_;
3049
3050   // Number of PLT entries with R_X86_64_IRELATIVE relocs.  These
3051   // follow the regular PLT entries.
3052   unsigned int irelative_count_;
3053
3054   // GOT offset of the reserved TLSDESC_GOT entry for the lazy trampoline.
3055   // Communicated to the loader via DT_TLSDESC_GOT. The magic value -1
3056   // indicates an offset is not allocated.
3057   unsigned int tlsdesc_got_offset_;
3058 };
3059
3060 // Initialize the PLT section.
3061
3062 template<int size, bool big_endian>
3063 void
3064 Output_data_plt_aarch64<size, big_endian>::init(Layout* layout)
3065 {
3066   this->rel_ = new Reloc_section(false);
3067   layout->add_output_section_data(".rela.plt", elfcpp::SHT_RELA,
3068                                   elfcpp::SHF_ALLOC, this->rel_,
3069                                   ORDER_DYNAMIC_PLT_RELOCS, false);
3070 }
3071
3072 template<int size, bool big_endian>
3073 void
3074 Output_data_plt_aarch64<size, big_endian>::do_adjust_output_section(
3075     Output_section* os)
3076 {
3077   os->set_entsize(this->get_plt_entry_size());
3078 }
3079
3080 // Add an entry to the PLT.
3081
3082 template<int size, bool big_endian>
3083 void
3084 Output_data_plt_aarch64<size, big_endian>::add_entry(Symbol* gsym)
3085 {
3086   gold_assert(!gsym->has_plt_offset());
3087
3088   gsym->set_plt_offset((this->count_) * this->get_plt_entry_size()
3089                        + this->first_plt_entry_offset());
3090
3091   ++this->count_;
3092
3093   section_offset_type got_offset = this->got_plt_->current_data_size();
3094
3095   // Every PLT entry needs a GOT entry which points back to the PLT
3096   // entry (this will be changed by the dynamic linker, normally
3097   // lazily when the function is called).
3098   this->got_plt_->set_current_data_size(got_offset + size / 8);
3099
3100   // Every PLT entry needs a reloc.
3101   gsym->set_needs_dynsym_entry();
3102   this->rel_->add_global(gsym, elfcpp::R_AARCH64_JUMP_SLOT,
3103                          this->got_plt_, got_offset, 0);
3104
3105   // Note that we don't need to save the symbol. The contents of the
3106   // PLT are independent of which symbols are used. The symbols only
3107   // appear in the relocations.
3108 }
3109
3110 // Return where the TLSDESC relocations should go, creating it if
3111 // necessary.  These follow the JUMP_SLOT relocations.
3112
3113 template<int size, bool big_endian>
3114 typename Output_data_plt_aarch64<size, big_endian>::Reloc_section*
3115 Output_data_plt_aarch64<size, big_endian>::rela_tlsdesc(Layout* layout)
3116 {
3117   if (this->tlsdesc_rel_ == NULL)
3118     {
3119       this->tlsdesc_rel_ = new Reloc_section(false);
3120       layout->add_output_section_data(".rela.plt", elfcpp::SHT_RELA,
3121                                       elfcpp::SHF_ALLOC, this->tlsdesc_rel_,
3122                                       ORDER_DYNAMIC_PLT_RELOCS, false);
3123       gold_assert(this->tlsdesc_rel_->output_section()
3124                   == this->rel_->output_section());
3125     }
3126   return this->tlsdesc_rel_;
3127 }
3128
3129 // Return where the IRELATIVE relocations should go in the PLT.  These
3130 // follow the JUMP_SLOT and the TLSDESC relocations.
3131
3132 template<int size, bool big_endian>
3133 typename Output_data_plt_aarch64<size, big_endian>::Reloc_section*
3134 Output_data_plt_aarch64<size, big_endian>::rela_irelative(Symbol_table* symtab,
3135                                                           Layout* layout)
3136 {
3137   if (this->irelative_rel_ == NULL)
3138     {
3139       // Make sure we have a place for the TLSDESC relocations, in
3140       // case we see any later on.
3141       this->rela_tlsdesc(layout);
3142       this->irelative_rel_ = new Reloc_section(false);
3143       layout->add_output_section_data(".rela.plt", elfcpp::SHT_RELA,
3144                                       elfcpp::SHF_ALLOC, this->irelative_rel_,
3145                                       ORDER_DYNAMIC_PLT_RELOCS, false);
3146       gold_assert(this->irelative_rel_->output_section()
3147                   == this->rel_->output_section());
3148
3149       if (parameters->doing_static_link())
3150         {
3151           // A statically linked executable will only have a .rela.plt
3152           // section to hold R_AARCH64_IRELATIVE relocs for
3153           // STT_GNU_IFUNC symbols.  The library will use these
3154           // symbols to locate the IRELATIVE relocs at program startup
3155           // time.
3156           symtab->define_in_output_data("__rela_iplt_start", NULL,
3157                                         Symbol_table::PREDEFINED,
3158                                         this->irelative_rel_, 0, 0,
3159                                         elfcpp::STT_NOTYPE, elfcpp::STB_GLOBAL,
3160                                         elfcpp::STV_HIDDEN, 0, false, true);
3161           symtab->define_in_output_data("__rela_iplt_end", NULL,
3162                                         Symbol_table::PREDEFINED,
3163                                         this->irelative_rel_, 0, 0,
3164                                         elfcpp::STT_NOTYPE, elfcpp::STB_GLOBAL,
3165                                         elfcpp::STV_HIDDEN, 0, true, true);
3166         }
3167     }
3168   return this->irelative_rel_;
3169 }
3170
3171 // Return the PLT address to use for a global symbol.
3172
3173 template<int size, bool big_endian>
3174 uint64_t
3175 Output_data_plt_aarch64<size, big_endian>::address_for_global(
3176   const Symbol* gsym)
3177 {
3178   uint64_t offset = 0;
3179   if (gsym->type() == elfcpp::STT_GNU_IFUNC
3180       && gsym->can_use_relative_reloc(false))
3181     offset = (this->first_plt_entry_offset() +
3182               this->count_ * this->get_plt_entry_size());
3183   return this->address() + offset + gsym->plt_offset();
3184 }
3185
3186 // Return the PLT address to use for a local symbol.  These are always
3187 // IRELATIVE relocs.
3188
3189 template<int size, bool big_endian>
3190 uint64_t
3191 Output_data_plt_aarch64<size, big_endian>::address_for_local(
3192     const Relobj* object,
3193     unsigned int r_sym)
3194 {
3195   return (this->address()
3196           + this->first_plt_entry_offset()
3197           + this->count_ * this->get_plt_entry_size()
3198           + object->local_plt_offset(r_sym));
3199 }
3200
3201 // Set the final size.
3202
3203 template<int size, bool big_endian>
3204 void
3205 Output_data_plt_aarch64<size, big_endian>::set_final_data_size()
3206 {
3207   unsigned int count = this->count_ + this->irelative_count_;
3208   unsigned int extra_size = 0;
3209   if (this->has_tlsdesc_entry())
3210     extra_size += this->get_plt_tlsdesc_entry_size();
3211   this->set_data_size(this->first_plt_entry_offset()
3212                       + count * this->get_plt_entry_size()
3213                       + extra_size);
3214 }
3215
3216 template<int size, bool big_endian>
3217 class Output_data_plt_aarch64_standard :
3218   public Output_data_plt_aarch64<size, big_endian>
3219 {
3220  public:
3221   typedef typename elfcpp::Elf_types<size>::Elf_Addr Address;
3222   Output_data_plt_aarch64_standard(
3223       Layout* layout,
3224       Output_data_got_aarch64<size, big_endian>* got,
3225       Output_data_space* got_plt,
3226       Output_data_space* got_irelative)
3227     : Output_data_plt_aarch64<size, big_endian>(layout,
3228                                                 size == 32 ? 4 : 8,
3229                                                 got, got_plt,
3230                                                 got_irelative)
3231   { }
3232
3233  protected:
3234   // Return the offset of the first non-reserved PLT entry.
3235   virtual unsigned int
3236   do_first_plt_entry_offset() const
3237   { return this->first_plt_entry_size; }
3238
3239   // Return the size of a PLT entry
3240   virtual unsigned int
3241   do_get_plt_entry_size() const
3242   { return this->plt_entry_size; }
3243
3244   // Return the size of a tlsdesc entry
3245   virtual unsigned int
3246   do_get_plt_tlsdesc_entry_size() const
3247   { return this->plt_tlsdesc_entry_size; }
3248
3249   virtual void
3250   do_fill_first_plt_entry(unsigned char* pov,
3251                           Address got_address,
3252                           Address plt_address);
3253
3254   virtual void
3255   do_fill_plt_entry(unsigned char* pov,
3256                     Address got_address,
3257                     Address plt_address,
3258                     unsigned int got_offset,
3259                     unsigned int plt_offset);
3260
3261   virtual void
3262   do_fill_tlsdesc_entry(unsigned char* pov,
3263                         Address gotplt_address,
3264                         Address plt_address,
3265                         Address got_base,
3266                         unsigned int tlsdesc_got_offset,
3267                         unsigned int plt_offset);
3268
3269  private:
3270   // The size of the first plt entry size.
3271   static const int first_plt_entry_size = 32;
3272   // The size of the plt entry size.
3273   static const int plt_entry_size = 16;
3274   // The size of the plt tlsdesc entry size.
3275   static const int plt_tlsdesc_entry_size = 32;
3276   // Template for the first PLT entry.
3277   static const uint32_t first_plt_entry[first_plt_entry_size / 4];
3278   // Template for subsequent PLT entries.
3279   static const uint32_t plt_entry[plt_entry_size / 4];
3280   // The reserved TLSDESC entry in the PLT for an executable.
3281   static const uint32_t tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4];
3282 };
3283
3284 // The first entry in the PLT for an executable.
3285
3286 template<>
3287 const uint32_t
3288 Output_data_plt_aarch64_standard<32, false>::
3289     first_plt_entry[first_plt_entry_size / 4] =
3290 {
3291   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3292   0x90000010,   /* adrp x16, PLT_GOT+0x8  */
3293   0xb9400A11,   /* ldr w17, [x16, #PLT_GOT+0x8]  */
3294   0x11002210,   /* add w16, w16,#PLT_GOT+0x8   */
3295   0xd61f0220,   /* br x17  */
3296   0xd503201f,   /* nop */
3297   0xd503201f,   /* nop */
3298   0xd503201f,   /* nop */
3299 };
3300
3301
3302 template<>
3303 const uint32_t
3304 Output_data_plt_aarch64_standard<32, true>::
3305     first_plt_entry[first_plt_entry_size / 4] =
3306 {
3307   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3308   0x90000010,   /* adrp x16, PLT_GOT+0x8  */
3309   0xb9400A11,   /* ldr w17, [x16, #PLT_GOT+0x8]  */
3310   0x11002210,   /* add w16, w16,#PLT_GOT+0x8   */
3311   0xd61f0220,   /* br x17  */
3312   0xd503201f,   /* nop */
3313   0xd503201f,   /* nop */
3314   0xd503201f,   /* nop */
3315 };
3316
3317
3318 template<>
3319 const uint32_t
3320 Output_data_plt_aarch64_standard<64, false>::
3321     first_plt_entry[first_plt_entry_size / 4] =
3322 {
3323   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3324   0x90000010,   /* adrp x16, PLT_GOT+16  */
3325   0xf9400A11,   /* ldr x17, [x16, #PLT_GOT+0x10]  */
3326   0x91004210,   /* add x16, x16,#PLT_GOT+0x10   */
3327   0xd61f0220,   /* br x17  */
3328   0xd503201f,   /* nop */
3329   0xd503201f,   /* nop */
3330   0xd503201f,   /* nop */
3331 };
3332
3333
3334 template<>
3335 const uint32_t
3336 Output_data_plt_aarch64_standard<64, true>::
3337     first_plt_entry[first_plt_entry_size / 4] =
3338 {
3339   0xa9bf7bf0,   /* stp x16, x30, [sp, #-16]!  */
3340   0x90000010,   /* adrp x16, PLT_GOT+16  */
3341   0xf9400A11,   /* ldr x17, [x16, #PLT_GOT+0x10]  */
3342   0x91004210,   /* add x16, x16,#PLT_GOT+0x10   */
3343   0xd61f0220,   /* br x17  */
3344   0xd503201f,   /* nop */
3345   0xd503201f,   /* nop */
3346   0xd503201f,   /* nop */
3347 };
3348
3349
3350 template<>
3351 const uint32_t
3352 Output_data_plt_aarch64_standard<32, false>::
3353     plt_entry[plt_entry_size / 4] =
3354 {
3355   0x90000010,   /* adrp x16, PLTGOT + n * 4  */
3356   0xb9400211,   /* ldr w17, [w16, PLTGOT + n * 4] */
3357   0x11000210,   /* add w16, w16, :lo12:PLTGOT + n * 4  */
3358   0xd61f0220,   /* br x17.  */
3359 };
3360
3361
3362 template<>
3363 const uint32_t
3364 Output_data_plt_aarch64_standard<32, true>::
3365     plt_entry[plt_entry_size / 4] =
3366 {
3367   0x90000010,   /* adrp x16, PLTGOT + n * 4  */
3368   0xb9400211,   /* ldr w17, [w16, PLTGOT + n * 4] */
3369   0x11000210,   /* add w16, w16, :lo12:PLTGOT + n * 4  */
3370   0xd61f0220,   /* br x17.  */
3371 };
3372
3373
3374 template<>
3375 const uint32_t
3376 Output_data_plt_aarch64_standard<64, false>::
3377     plt_entry[plt_entry_size / 4] =
3378 {
3379   0x90000010,   /* adrp x16, PLTGOT + n * 8  */
3380   0xf9400211,   /* ldr x17, [x16, PLTGOT + n * 8] */
3381   0x91000210,   /* add x16, x16, :lo12:PLTGOT + n * 8  */
3382   0xd61f0220,   /* br x17.  */
3383 };
3384
3385
3386 template<>
3387 const uint32_t
3388 Output_data_plt_aarch64_standard<64, true>::
3389     plt_entry[plt_entry_size / 4] =
3390 {
3391   0x90000010,   /* adrp x16, PLTGOT + n * 8  */
3392   0xf9400211,   /* ldr x17, [x16, PLTGOT + n * 8] */
3393   0x91000210,   /* add x16, x16, :lo12:PLTGOT + n * 8  */
3394   0xd61f0220,   /* br x17.  */
3395 };
3396
3397
3398 template<int size, bool big_endian>
3399 void
3400 Output_data_plt_aarch64_standard<size, big_endian>::do_fill_first_plt_entry(
3401     unsigned char* pov,
3402     Address got_address,
3403     Address plt_address)
3404 {
3405   // PLT0 of the small PLT looks like this in ELF64 -
3406   // stp x16, x30, [sp, #-16]!          Save the reloc and lr on stack.
3407   // adrp x16, PLT_GOT + 16             Get the page base of the GOTPLT
3408   // ldr  x17, [x16, #:lo12:PLT_GOT+16] Load the address of the
3409   //                                    symbol resolver
3410   // add  x16, x16, #:lo12:PLT_GOT+16   Load the lo12 bits of the
3411   //                                    GOTPLT entry for this.
3412   // br   x17
3413   // PLT0 will be slightly different in ELF32 due to different got entry
3414   // size.
3415   memcpy(pov, this->first_plt_entry, this->first_plt_entry_size);
3416   Address gotplt_2nd_ent = got_address + (size / 8) * 2;
3417
3418   // Fill in the top 21 bits for this: ADRP x16, PLT_GOT + 8 * 2.
3419   // ADRP:  (PG(S+A)-PG(P)) >> 12) & 0x1fffff.
3420   // FIXME: This only works for 64bit
3421   AArch64_relocate_functions<size, big_endian>::adrp(pov + 4,
3422       gotplt_2nd_ent, plt_address + 4);
3423
3424   // Fill in R_AARCH64_LDST8_LO12
3425   elfcpp::Swap<32, big_endian>::writeval(
3426       pov + 8,
3427       ((this->first_plt_entry[2] & 0xffc003ff)
3428        | ((gotplt_2nd_ent & 0xff8) << 7)));
3429
3430   // Fill in R_AARCH64_ADD_ABS_LO12
3431   elfcpp::Swap<32, big_endian>::writeval(
3432       pov + 12,
3433       ((this->first_plt_entry[3] & 0xffc003ff)
3434        | ((gotplt_2nd_ent & 0xfff) << 10)));
3435 }
3436
3437
3438 // Subsequent entries in the PLT for an executable.
3439 // FIXME: This only works for 64bit
3440
3441 template<int size, bool big_endian>
3442 void
3443 Output_data_plt_aarch64_standard<size, big_endian>::do_fill_plt_entry(
3444     unsigned char* pov,
3445     Address got_address,
3446     Address plt_address,
3447     unsigned int got_offset,
3448     unsigned int plt_offset)
3449 {
3450   memcpy(pov, this->plt_entry, this->plt_entry_size);
3451
3452   Address gotplt_entry_address = got_address + got_offset;
3453   Address plt_entry_address = plt_address + plt_offset;
3454
3455   // Fill in R_AARCH64_PCREL_ADR_HI21
3456   AArch64_relocate_functions<size, big_endian>::adrp(
3457       pov,
3458       gotplt_entry_address,
3459       plt_entry_address);
3460
3461   // Fill in R_AARCH64_LDST64_ABS_LO12
3462   elfcpp::Swap<32, big_endian>::writeval(
3463       pov + 4,
3464       ((this->plt_entry[1] & 0xffc003ff)
3465        | ((gotplt_entry_address & 0xff8) << 7)));
3466
3467   // Fill in R_AARCH64_ADD_ABS_LO12
3468   elfcpp::Swap<32, big_endian>::writeval(
3469       pov + 8,
3470       ((this->plt_entry[2] & 0xffc003ff)
3471        | ((gotplt_entry_address & 0xfff) <<10)));
3472
3473 }
3474
3475
3476 template<>
3477 const uint32_t
3478 Output_data_plt_aarch64_standard<32, false>::
3479     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3480 {
3481   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3482   0x90000002,   /* adrp x2, 0 */
3483   0x90000003,   /* adrp x3, 0 */
3484   0xb9400042,   /* ldr w2, [w2, #0] */
3485   0x11000063,   /* add w3, w3, 0 */
3486   0xd61f0040,   /* br x2 */
3487   0xd503201f,   /* nop */
3488   0xd503201f,   /* nop */
3489 };
3490
3491 template<>
3492 const uint32_t
3493 Output_data_plt_aarch64_standard<32, true>::
3494     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3495 {
3496   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3497   0x90000002,   /* adrp x2, 0 */
3498   0x90000003,   /* adrp x3, 0 */
3499   0xb9400042,   /* ldr w2, [w2, #0] */
3500   0x11000063,   /* add w3, w3, 0 */
3501   0xd61f0040,   /* br x2 */
3502   0xd503201f,   /* nop */
3503   0xd503201f,   /* nop */
3504 };
3505
3506 template<>
3507 const uint32_t
3508 Output_data_plt_aarch64_standard<64, false>::
3509     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3510 {
3511   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3512   0x90000002,   /* adrp x2, 0 */
3513   0x90000003,   /* adrp x3, 0 */
3514   0xf9400042,   /* ldr x2, [x2, #0] */
3515   0x91000063,   /* add x3, x3, 0 */
3516   0xd61f0040,   /* br x2 */
3517   0xd503201f,   /* nop */
3518   0xd503201f,   /* nop */
3519 };
3520
3521 template<>
3522 const uint32_t
3523 Output_data_plt_aarch64_standard<64, true>::
3524     tlsdesc_plt_entry[plt_tlsdesc_entry_size / 4] =
3525 {
3526   0xa9bf0fe2,   /* stp x2, x3, [sp, #-16]!  */
3527   0x90000002,   /* adrp x2, 0 */
3528   0x90000003,   /* adrp x3, 0 */
3529   0xf9400042,   /* ldr x2, [x2, #0] */
3530   0x91000063,   /* add x3, x3, 0 */
3531   0xd61f0040,   /* br x2 */
3532   0xd503201f,   /* nop */
3533   0xd503201f,   /* nop */
3534 };
3535
3536 template<int size, bool big_endian>
3537 void
3538 Output_data_plt_aarch64_standard<size, big_endian>::do_fill_tlsdesc_entry(
3539     unsigned char* pov,
3540     Address gotplt_address,
3541     Address plt_address,
3542     Address got_base,
3543     unsigned int tlsdesc_got_offset,
3544     unsigned int plt_offset)
3545 {
3546   memcpy(pov, tlsdesc_plt_entry, plt_tlsdesc_entry_size);
3547
3548   // move DT_TLSDESC_GOT address into x2
3549   // move .got.plt address into x3
3550   Address tlsdesc_got_entry = got_base + tlsdesc_got_offset;
3551   Address plt_entry_address = plt_address + plt_offset;
3552
3553   // R_AARCH64_ADR_PREL_PG_HI21
3554   AArch64_relocate_functions<size, big_endian>::adrp(
3555       pov + 4,
3556       tlsdesc_got_entry,
3557       plt_entry_address + 4);
3558
3559   // R_AARCH64_ADR_PREL_PG_HI21
3560   AArch64_relocate_functions<size, big_endian>::adrp(
3561       pov + 8,
3562       gotplt_address,
3563       plt_entry_address + 8);
3564
3565   // R_AARCH64_LDST64_ABS_LO12
3566   elfcpp::Swap<32, big_endian>::writeval(
3567       pov + 12,
3568       ((this->tlsdesc_plt_entry[3] & 0xffc003ff)
3569        | ((tlsdesc_got_entry & 0xff8) << 7)));
3570
3571   // R_AARCH64_ADD_ABS_LO12
3572   elfcpp::Swap<32, big_endian>::writeval(
3573       pov + 16,
3574       ((this->tlsdesc_plt_entry[4] & 0xffc003ff)
3575        | ((gotplt_address & 0xfff) << 10)));
3576 }
3577
3578 // Write out the PLT.  This uses the hand-coded instructions above,
3579 // and adjusts them as needed.  This is specified by the AMD64 ABI.
3580
3581 template<int size, bool big_endian>
3582 void
3583 Output_data_plt_aarch64<size, big_endian>::do_write(Output_file* of)
3584 {
3585   const off_t offset = this->offset();
3586   const section_size_type oview_size =
3587     convert_to_section_size_type(this->data_size());
3588   unsigned char* const oview = of->get_output_view(offset, oview_size);
3589
3590   const off_t got_file_offset = this->got_plt_->offset();
3591   const section_size_type got_size =
3592     convert_to_section_size_type(this->got_plt_->data_size());
3593   unsigned char* const got_view = of->get_output_view(got_file_offset,
3594                                                       got_size);
3595
3596   unsigned char* pov = oview;
3597
3598   // The base address of the .plt section.
3599   typename elfcpp::Elf_types<size>::Elf_Addr plt_address = this->address();
3600   // The base address of the PLT portion of the .got section.
3601   typename elfcpp::Elf_types<size>::Elf_Addr gotplt_address
3602       = this->got_plt_->address();
3603
3604   this->fill_first_plt_entry(pov, gotplt_address, plt_address);
3605   pov += this->first_plt_entry_offset();
3606
3607   // The first three entries in .got.plt are reserved.
3608   unsigned char* got_pov = got_view;
3609   memset(got_pov, 0, size / 8 * AARCH64_GOTPLT_RESERVE_COUNT);
3610   got_pov += (size / 8) * AARCH64_GOTPLT_RESERVE_COUNT;
3611
3612   unsigned int plt_offset = this->first_plt_entry_offset();
3613   unsigned int got_offset = (size / 8) * AARCH64_GOTPLT_RESERVE_COUNT;
3614   const unsigned int count = this->count_ + this->irelative_count_;
3615   for (unsigned int plt_index = 0;
3616        plt_index < count;
3617        ++plt_index,
3618          pov += this->get_plt_entry_size(),
3619          got_pov += size / 8,
3620          plt_offset += this->get_plt_entry_size(),
3621          got_offset += size / 8)
3622     {
3623       // Set and adjust the PLT entry itself.
3624       this->fill_plt_entry(pov, gotplt_address, plt_address,
3625                            got_offset, plt_offset);
3626
3627       // Set the entry in the GOT, which points to plt0.
3628       elfcpp::Swap<size, big_endian>::writeval(got_pov, plt_address);
3629     }
3630
3631   if (this->has_tlsdesc_entry())
3632     {
3633       // Set and adjust the reserved TLSDESC PLT entry.
3634       unsigned int tlsdesc_got_offset = this->get_tlsdesc_got_offset();
3635       // The base address of the .base section.
3636       typename elfcpp::Elf_types<size>::Elf_Addr got_base =
3637           this->got_->address();
3638       this->fill_tlsdesc_entry(pov, gotplt_address, plt_address, got_base,
3639                                tlsdesc_got_offset, plt_offset);
3640       pov += this->get_plt_tlsdesc_entry_size();
3641     }
3642
3643   gold_assert(static_cast<section_size_type>(pov - oview) == oview_size);
3644   gold_assert(static_cast<section_size_type>(got_pov - got_view) == got_size);
3645
3646   of->write_output_view(offset, oview_size, oview);
3647   of->write_output_view(got_file_offset, got_size, got_view);
3648 }
3649
3650 // Telling how to update the immediate field of an instruction.
3651 struct AArch64_howto
3652 {
3653   // The immediate field mask.
3654   elfcpp::Elf_Xword dst_mask;
3655
3656   // The offset to apply relocation immediate
3657   int doffset;
3658
3659   // The second part offset, if the immediate field has two parts.
3660   // -1 if the immediate field has only one part.
3661   int doffset2;
3662 };
3663
3664 static const AArch64_howto aarch64_howto[AArch64_reloc_property::INST_NUM] =
3665 {
3666   {0, -1, -1},          // DATA
3667   {0x1fffe0, 5, -1},    // MOVW  [20:5]-imm16
3668   {0xffffe0, 5, -1},    // LD    [23:5]-imm19
3669   {0x60ffffe0, 29, 5},  // ADR   [30:29]-immlo  [23:5]-immhi
3670   {0x60ffffe0, 29, 5},  // ADRP  [30:29]-immlo  [23:5]-immhi
3671   {0x3ffc00, 10, -1},   // ADD   [21:10]-imm12
3672   {0x3ffc00, 10, -1},   // LDST  [21:10]-imm12
3673   {0x7ffe0, 5, -1},     // TBZNZ [18:5]-imm14
3674   {0xffffe0, 5, -1},    // CONDB [23:5]-imm19
3675   {0x3ffffff, 0, -1},   // B     [25:0]-imm26
3676   {0x3ffffff, 0, -1},   // CALL  [25:0]-imm26
3677 };
3678
3679 // AArch64 relocate function class
3680
3681 template<int size, bool big_endian>
3682 class AArch64_relocate_functions
3683 {
3684  public:
3685   typedef enum
3686   {
3687     STATUS_OKAY,        // No error during relocation.
3688     STATUS_OVERFLOW,    // Relocation overflow.
3689     STATUS_BAD_RELOC,   // Relocation cannot be applied.
3690   } Status;
3691
3692   typedef AArch64_relocate_functions<size, big_endian> This;
3693   typedef typename elfcpp::Elf_types<size>::Elf_Addr Address;
3694   typedef Relocate_info<size, big_endian> The_relocate_info;
3695   typedef AArch64_relobj<size, big_endian> The_aarch64_relobj;
3696   typedef Reloc_stub<size, big_endian> The_reloc_stub;
3697   typedef typename The_reloc_stub::Stub_type The_reloc_stub_type;
3698   typedef Stub_table<size, big_endian> The_stub_table;
3699   typedef elfcpp::Rela<size, big_endian> The_rela;
3700
3701   // Return the page address of the address.
3702   // Page(address) = address & ~0xFFF
3703
3704   static inline typename elfcpp::Swap<size, big_endian>::Valtype
3705   Page(Address address)
3706   {
3707     return (address & (~static_cast<Address>(0xFFF)));
3708   }
3709
3710  private:
3711   // Update instruction (pointed by view) with selected bits (immed).
3712   // val = (val & ~dst_mask) | (immed << doffset)
3713
3714   template<int valsize>
3715   static inline void
3716   update_view(unsigned char* view,
3717               typename elfcpp::Swap<size, big_endian>::Valtype immed,
3718               elfcpp::Elf_Xword doffset,
3719               elfcpp::Elf_Xword dst_mask)
3720   {
3721     typedef typename elfcpp::Swap<valsize, big_endian>::Valtype Valtype;
3722     Valtype* wv = reinterpret_cast<Valtype*>(view);
3723     Valtype val = elfcpp::Swap<valsize, big_endian>::readval(wv);
3724
3725     // Clear immediate fields.
3726     val &= ~dst_mask;
3727     elfcpp::Swap<valsize, big_endian>::writeval(wv,
3728       static_cast<Valtype>(val | (immed << doffset)));
3729   }
3730
3731   // Update two parts of an instruction (pointed by view) with selected
3732   // bits (immed1 and immed2).
3733   // val = (val & ~dst_mask) | (immed1 << doffset1) | (immed2 << doffset2)
3734
3735   template<int valsize>
3736   static inline void
3737   update_view_two_parts(
3738     unsigned char* view,
3739     typename elfcpp::Swap<size, big_endian>::Valtype immed1,
3740     typename elfcpp::Swap<size, big_endian>::Valtype immed2,
3741     elfcpp::Elf_Xword doffset1,
3742     elfcpp::Elf_Xword doffset2,
3743     elfcpp::Elf_Xword dst_mask)
3744   {
3745     typedef typename elfcpp::Swap<valsize, big_endian>::Valtype Valtype;
3746     Valtype* wv = reinterpret_cast<Valtype*>(view);
3747     Valtype val = elfcpp::Swap<valsize, big_endian>::readval(wv);
3748     val &= ~dst_mask;
3749     elfcpp::Swap<valsize, big_endian>::writeval(wv,
3750       static_cast<Valtype>(val | (immed1 << doffset1) |
3751                            (immed2 << doffset2)));
3752   }
3753
3754   // Update adr or adrp instruction with [32:12] of X.
3755   // In adr and adrp: [30:29] immlo   [23:5] immhi
3756
3757   static inline void
3758   update_adr(unsigned char* view,
3759              typename elfcpp::Swap<size, big_endian>::Valtype x,
3760              const AArch64_reloc_property* /* reloc_property */)
3761   {
3762     elfcpp::Elf_Xword dst_mask = (0x3 << 29) | (0x7ffff << 5);
3763     typename elfcpp::Swap<32, big_endian>::Valtype immed =
3764       (x >> 12) & 0x1fffff;
3765     This::template update_view_two_parts<32>(
3766       view,
3767       immed & 0x3,
3768       (immed & 0x1ffffc) >> 2,
3769       29,
3770       5,
3771       dst_mask);
3772   }
3773
3774   // Update movz/movn instruction with bits immed.
3775   // Set instruction to movz if is_movz is true, otherwise set instruction
3776   // to movn.
3777   static inline void
3778   update_movnz(unsigned char* view,
3779                typename elfcpp::Swap<size, big_endian>::Valtype immed,
3780                bool is_movz)
3781   {
3782     typedef typename elfcpp::Swap<32, big_endian>::Valtype Valtype;
3783     Valtype* wv = reinterpret_cast<Valtype*>(view);
3784     Valtype val = elfcpp::Swap<32, big_endian>::readval(wv);
3785
3786     const elfcpp::Elf_Xword doffset =
3787         aarch64_howto[AArch64_reloc_property::INST_MOVW].doffset;
3788     const elfcpp::Elf_Xword dst_mask =
3789         aarch64_howto[AArch64_reloc_property::INST_MOVW].dst_mask;
3790
3791     // Clear immediate fields and opc code.
3792     val &= ~(dst_mask | (0x11 << 29));
3793
3794     // Set instruction to movz or movn.
3795     // movz: [30:29] is 10   movn: [30:29] is 00
3796     if (is_movz)
3797       val |= (0x10 << 29);
3798
3799     elfcpp::Swap<32, big_endian>::writeval(wv,
3800       static_cast<Valtype>(val | (immed << doffset)));
3801   }
3802
3803  public:
3804
3805   // Do a simple rela relocation at unaligned addresses.
3806
3807   template<int valsize>
3808   static inline typename This::Status
3809   rela_ua(unsigned char* view,
3810           const Sized_relobj_file<size, big_endian>* object,
3811           const Symbol_value<size>* psymval,
3812           typename elfcpp::Swap<size, big_endian>::Valtype addend,
3813           const AArch64_reloc_property* reloc_property)
3814   {
3815     typedef typename elfcpp::Swap_unaligned<valsize, big_endian>::Valtype
3816       Valtype;
3817     typename elfcpp::Elf_types<size>::Elf_Addr x =
3818         psymval->value(object, addend);
3819     elfcpp::Swap_unaligned<valsize, big_endian>::writeval(view,
3820       static_cast<Valtype>(x));
3821     return (reloc_property->checkup_x_value(x)
3822             ? This::STATUS_OKAY
3823             : This::STATUS_OVERFLOW);
3824   }
3825
3826   // Do a simple pc-relative relocation at unaligned addresses.
3827
3828   template<int valsize>
3829   static inline typename This::Status
3830   pcrela_ua(unsigned char* view,
3831             const Sized_relobj_file<size, big_endian>* object,
3832             const Symbol_value<size>* psymval,
3833             typename elfcpp::Swap<size, big_endian>::Valtype addend,
3834             Address address,
3835             const AArch64_reloc_property* reloc_property)
3836   {
3837     typedef typename elfcpp::Swap_unaligned<valsize, big_endian>::Valtype
3838       Valtype;
3839     Address x = psymval->value(object, addend) - address;
3840     elfcpp::Swap_unaligned<valsize, big_endian>::writeval(view,
3841       static_cast<Valtype>(x));
3842     return (reloc_property->checkup_x_value(x)
3843             ? This::STATUS_OKAY
3844             : This::STATUS_OVERFLOW);
3845   }
3846
3847   // Do a simple rela relocation at aligned addresses.
3848
3849   template<int valsize>
3850   static inline typename This::Status
3851   rela(
3852     unsigned char* view,
3853     const Sized_relobj_file<size, big_endian>* object,
3854     const Symbol_value<size>* psymval,
3855     typename elfcpp::Swap<size, big_endian>::Valtype addend,
3856     const AArch64_reloc_property* reloc_property)
3857   {
3858     typedef typename elfcpp::Swap<valsize, big_endian>::Valtype
3859       Valtype;
3860     Valtype* wv = reinterpret_cast<Valtype*>(view);
3861     Address x = psymval->value(object, addend);
3862     elfcpp::Swap<valsize, big_endian>::writeval(wv,
3863       static_cast<Valtype>(x));
3864     return (reloc_property->checkup_x_value(x)
3865             ? This::STATUS_OKAY
3866             : This::STATUS_OVERFLOW);
3867   }
3868
3869   // Do relocate. Update selected bits in text.
3870   // new_val = (val & ~dst_mask) | (immed << doffset)
3871
3872   template<int valsize>
3873   static inline typename This::Status
3874   rela_general(unsigned char* view,
3875                const Sized_relobj_file<size, big_endian>* object,
3876                const Symbol_value<size>* psymval,
3877                typename elfcpp::Swap<size, big_endian>::Valtype addend,
3878                const AArch64_reloc_property* reloc_property)
3879   {
3880     // Calculate relocation.
3881     Address x = psymval->value(object, addend);
3882
3883     // Select bits from X.
3884     Address immed = reloc_property->select_x_value(x);
3885
3886     // Update view.
3887     const AArch64_reloc_property::Reloc_inst inst =
3888         reloc_property->reloc_inst();
3889     // If it is a data relocation or instruction has 2 parts of immediate
3890     // fields, you should not call rela_general.
3891     gold_assert(aarch64_howto[inst].doffset2 == -1 &&
3892                 aarch64_howto[inst].doffset != -1);
3893     This::template update_view<valsize>(view, immed,
3894                                         aarch64_howto[inst].doffset,
3895                                         aarch64_howto[inst].dst_mask);
3896
3897     // Do check overflow or alignment if needed.
3898     return (reloc_property->checkup_x_value(x)
3899             ? This::STATUS_OKAY
3900             : This::STATUS_OVERFLOW);
3901   }
3902
3903   // Do relocate. Update selected bits in text.
3904   // new val = (val & ~dst_mask) | (immed << doffset)
3905
3906   template<int valsize>
3907   static inline typename This::Status
3908   rela_general(
3909     unsigned char* view,
3910     typename elfcpp::Swap<size, big_endian>::Valtype s,
3911     typename elfcpp::Swap<size, big_endian>::Valtype addend,
3912     const AArch64_reloc_property* reloc_property)
3913   {
3914     // Calculate relocation.
3915     Address x = s + addend;
3916
3917     // Select bits from X.
3918     Address immed = reloc_property->select_x_value(x);
3919
3920     // Update view.
3921     const AArch64_reloc_property::Reloc_inst inst =
3922         reloc_property->reloc_inst();
3923     // If it is a data relocation or instruction has 2 parts of immediate
3924     // fields, you should not call rela_general.
3925     gold_assert(aarch64_howto[inst].doffset2 == -1 &&
3926                 aarch64_howto[inst].doffset != -1);
3927     This::template update_view<valsize>(view, immed,
3928                                         aarch64_howto[inst].doffset,
3929                                         aarch64_howto[inst].dst_mask);
3930
3931     // Do check overflow or alignment if needed.
3932     return (reloc_property->checkup_x_value(x)
3933             ? This::STATUS_OKAY
3934             : This::STATUS_OVERFLOW);
3935   }
3936
3937   // Do address relative relocate. Update selected bits in text.
3938   // new val = (val & ~dst_mask) | (immed << doffset)
3939
3940   template<int valsize>
3941   static inline typename This::Status
3942   pcrela_general(
3943     unsigned char* view,
3944     const Sized_relobj_file<size, big_endian>* object,
3945     const Symbol_value<size>* psymval,
3946     typename elfcpp::Swap<size, big_endian>::Valtype addend,
3947     Address address,
3948     const AArch64_reloc_property* reloc_property)
3949   {
3950     // Calculate relocation.
3951     Address x = psymval->value(object, addend) - address;
3952
3953     // Select bits from X.
3954     Address immed = reloc_property->select_x_value(x);
3955
3956     // Update view.
3957     const AArch64_reloc_property::Reloc_inst inst =
3958       reloc_property->reloc_inst();
3959     // If it is a data relocation or instruction has 2 parts of immediate
3960     // fields, you should not call pcrela_general.
3961     gold_assert(aarch64_howto[inst].doffset2 == -1 &&
3962                 aarch64_howto[inst].doffset != -1);
3963     This::template update_view<valsize>(view, immed,
3964                                         aarch64_howto[inst].doffset,
3965                                         aarch64_howto[inst].dst_mask);
3966
3967     // Do check overflow or alignment if needed.
3968     return (reloc_property->checkup_x_value(x)
3969             ? This::STATUS_OKAY
3970             : This::STATUS_OVERFLOW);
3971   }
3972
3973   // Calculate PG(S+A) - PG(address), update adrp instruction.
3974   // R_AARCH64_ADR_PREL_PG_HI21
3975
3976   static inline typename This::Status
3977   adrp(
3978     unsigned char* view,
3979     Address sa,
3980     Address address)
3981   {
3982     typename elfcpp::Swap<size, big_endian>::Valtype x =
3983         This::Page(sa) - This::Page(address);
3984     update_adr(view, x, NULL);
3985     // Check -2^32 <= X < 2^32
3986     return (size == 64 && Bits<33>::has_overflow((x))
3987             ? This::STATUS_OVERFLOW
3988             : This::STATUS_OKAY);
3989   }
3990
3991   // Calculate PG(S+A) - PG(address), update adrp instruction.
3992   // R_AARCH64_ADR_PREL_PG_HI21
3993
3994   static inline typename This::Status
3995   adrp(unsigned char* view,
3996        const Sized_relobj_file<size, big_endian>* object,
3997        const Symbol_value<size>* psymval,
3998        Address addend,
3999        Address address,
4000        const AArch64_reloc_property* reloc_property)
4001   {
4002     Address sa = psymval->value(object, addend);
4003     typename elfcpp::Swap<size, big_endian>::Valtype x =
4004         This::Page(sa) - This::Page(address);
4005     update_adr(view, x, reloc_property);
4006     return (reloc_property->checkup_x_value(x)
4007             ? This::STATUS_OKAY
4008             : This::STATUS_OVERFLOW);
4009   }
4010
4011   // Update mov[n/z] instruction. Check overflow if needed.
4012   // If X >=0, set the instruction to movz and its immediate value to the
4013   // selected bits S.
4014   // If X < 0, set the instruction to movn and its immediate value to
4015   // NOT (selected bits of).
4016
4017   static inline typename This::Status
4018   movnz(unsigned char* view,
4019         typename elfcpp::Swap<size, big_endian>::Valtype x,
4020         const AArch64_reloc_property* reloc_property)
4021   {
4022     // Select bits from X.
4023     Address immed = reloc_property->select_x_value(x);
4024     bool is_movz = true;
4025     if (static_cast<int64_t>(x) < 0)
4026       {
4027         immed = ~immed;
4028         is_movz = false;
4029       }
4030
4031     // Update movnz instruction.
4032     update_movnz(view, immed, is_movz);
4033
4034     // Do check overflow or alignment if needed.
4035     return (reloc_property->checkup_x_value(x)
4036             ? This::STATUS_OKAY
4037             : This::STATUS_OVERFLOW);
4038   }
4039
4040   static inline bool
4041   maybe_apply_stub(unsigned int,
4042                    const The_relocate_info*,
4043                    const The_rela&,
4044                    unsigned char*,
4045                    Address,
4046                    const Sized_symbol<size>*,
4047                    const Symbol_value<size>*,
4048                    const Sized_relobj_file<size, big_endian>*);
4049
4050 };  // End of AArch64_relocate_functions
4051
4052
4053 // For a certain relocation type (usually jump/branch), test to see if the
4054 // destination needs a stub to fulfil. If so, re-route the destination of the
4055 // original instruction to the stub, note, at this time, the stub has already
4056 // been generated.
4057
4058 template<int size, bool big_endian>
4059 bool
4060 AArch64_relocate_functions<size, big_endian>::
4061 maybe_apply_stub(unsigned int r_type,
4062                  const The_relocate_info* relinfo,
4063                  const The_rela& rela,
4064                  unsigned char* view,
4065                  Address address,
4066                  const Sized_symbol<size>* gsym,
4067                  const Symbol_value<size>* psymval,
4068                  const Sized_relobj_file<size, big_endian>* object)
4069 {
4070   if (parameters->options().relocatable())
4071     return false;
4072
4073   typename elfcpp::Elf_types<size>::Elf_Swxword addend = rela.get_r_addend();
4074   Address branch_target = psymval->value(object, 0) + addend;
4075   The_reloc_stub_type stub_type = The_reloc_stub::
4076     stub_type_for_reloc(r_type, address, branch_target);
4077   if (stub_type == The_reloc_stub::ST_NONE)
4078     return false;
4079
4080   const The_aarch64_relobj* aarch64_relobj =
4081       static_cast<const The_aarch64_relobj*>(object);
4082   The_stub_table* stub_table = aarch64_relobj->stub_table(relinfo->data_shndx);
4083   gold_assert(stub_table != NULL);
4084
4085   unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
4086   typename The_reloc_stub::Key stub_key(stub_type, gsym, object, r_sym, addend);
4087   The_reloc_stub* stub = stub_table->find_reloc_stub(stub_key);
4088   gold_assert(stub != NULL);
4089
4090   Address new_branch_target = stub_table->address() + stub->offset();
4091   typename elfcpp::Swap<size, big_endian>::Valtype branch_offset =
4092       new_branch_target - address;
4093   const AArch64_reloc_property* arp =
4094       aarch64_reloc_property_table->get_reloc_property(r_type);
4095   gold_assert(arp != NULL);
4096   This::Status status = This::template
4097       rela_general<32>(view, branch_offset, 0, arp);
4098   if (status != This::STATUS_OKAY)
4099     gold_error(_("Stub is too far away, try a smaller value "
4100                  "for '--stub-group-size'. For example, 0x2000000."));
4101   return true;
4102 }
4103
4104
4105 // Group input sections for stub generation.
4106 //
4107 // We group input sections in an output section so that the total size,
4108 // including any padding space due to alignment is smaller than GROUP_SIZE
4109 // unless the only input section in group is bigger than GROUP_SIZE already.
4110 // Then an ARM stub table is created to follow the last input section
4111 // in group.  For each group an ARM stub table is created an is placed
4112 // after the last group.  If STUB_ALWAYS_AFTER_BRANCH is false, we further
4113 // extend the group after the stub table.
4114
4115 template<int size, bool big_endian>
4116 void
4117 Target_aarch64<size, big_endian>::group_sections(
4118     Layout* layout,
4119     section_size_type group_size,
4120     bool stubs_always_after_branch,
4121     const Task* task)
4122 {
4123   // Group input sections and insert stub table
4124   Layout::Section_list section_list;
4125   layout->get_executable_sections(&section_list);
4126   for (Layout::Section_list::const_iterator p = section_list.begin();
4127        p != section_list.end();
4128        ++p)
4129     {
4130       AArch64_output_section<size, big_endian>* output_section =
4131           static_cast<AArch64_output_section<size, big_endian>*>(*p);
4132       output_section->group_sections(group_size, stubs_always_after_branch,
4133                                      this, task);
4134     }
4135 }
4136
4137
4138 // Find the AArch64_input_section object corresponding to the SHNDX-th input
4139 // section of RELOBJ.
4140
4141 template<int size, bool big_endian>
4142 AArch64_input_section<size, big_endian>*
4143 Target_aarch64<size, big_endian>::find_aarch64_input_section(
4144     Relobj* relobj, unsigned int shndx) const
4145 {
4146   Section_id sid(relobj, shndx);
4147   typename AArch64_input_section_map::const_iterator p =
4148     this->aarch64_input_section_map_.find(sid);
4149   return (p != this->aarch64_input_section_map_.end()) ? p->second : NULL;
4150 }
4151
4152
4153 // Make a new AArch64_input_section object.
4154
4155 template<int size, bool big_endian>
4156 AArch64_input_section<size, big_endian>*
4157 Target_aarch64<size, big_endian>::new_aarch64_input_section(
4158     Relobj* relobj, unsigned int shndx)
4159 {
4160   Section_id sid(relobj, shndx);
4161
4162   AArch64_input_section<size, big_endian>* input_section =
4163       new AArch64_input_section<size, big_endian>(relobj, shndx);
4164   input_section->init();
4165
4166   // Register new AArch64_input_section in map for look-up.
4167   std::pair<typename AArch64_input_section_map::iterator,bool> ins =
4168       this->aarch64_input_section_map_.insert(
4169           std::make_pair(sid, input_section));
4170
4171   // Make sure that it we have not created another AArch64_input_section
4172   // for this input section already.
4173   gold_assert(ins.second);
4174
4175   return input_section;
4176 }
4177
4178
4179 // Relaxation hook.  This is where we do stub generation.
4180
4181 template<int size, bool big_endian>
4182 bool
4183 Target_aarch64<size, big_endian>::do_relax(
4184     int pass,
4185     const Input_objects* input_objects,
4186     Symbol_table* symtab,
4187     Layout* layout ,
4188     const Task* task)
4189 {
4190   gold_assert(!parameters->options().relocatable());
4191   if (pass == 1)
4192     {
4193       section_size_type stub_group_size =
4194           parameters->options().stub_group_size();
4195       if (stub_group_size == 1)
4196         {
4197           // Leave room for 4096 4-byte stub entries. If we exceed that, then we
4198           // will fail to link.  The user will have to relink with an explicit
4199           // group size option.
4200           stub_group_size = The_reloc_stub::MAX_BRANCH_OFFSET - 4096 * 4;
4201         }
4202       group_sections(layout, stub_group_size, true, task);
4203     }
4204   else
4205     {
4206       // If this is not the first pass, addresses and file offsets have
4207       // been reset at this point, set them here.
4208       for (Stub_table_iterator sp = this->stub_tables_.begin();
4209            sp != this->stub_tables_.end(); ++sp)
4210         {
4211           The_stub_table* stt = *sp;
4212           The_aarch64_input_section* owner = stt->owner();
4213           off_t off = align_address(owner->original_size(),
4214                                     stt->addralign());
4215           stt->set_address_and_file_offset(owner->address() + off,
4216                                            owner->offset() + off);
4217         }
4218     }
4219
4220   // Scan relocs for relocation stubs
4221   for (Input_objects::Relobj_iterator op = input_objects->relobj_begin();
4222        op != input_objects->relobj_end();
4223        ++op)
4224     {
4225       The_aarch64_relobj* aarch64_relobj =
4226           static_cast<The_aarch64_relobj*>(*op);
4227       // Lock the object so we can read from it.  This is only called
4228       // single-threaded from Layout::finalize, so it is OK to lock.
4229       Task_lock_obj<Object> tl(task, aarch64_relobj);
4230       aarch64_relobj->scan_sections_for_stubs(this, symtab, layout);
4231     }
4232
4233   bool any_stub_table_changed = false;
4234   for (Stub_table_iterator siter = this->stub_tables_.begin();
4235        siter != this->stub_tables_.end() && !any_stub_table_changed; ++siter)
4236     {
4237       The_stub_table* stub_table = *siter;
4238       if (stub_table->update_data_size_changed_p())
4239         {
4240           The_aarch64_input_section* owner = stub_table->owner();
4241           uint64_t address = owner->address();
4242           off_t offset = owner->offset();
4243           owner->reset_address_and_file_offset();
4244           owner->set_address_and_file_offset(address, offset);
4245
4246           any_stub_table_changed = true;
4247         }
4248     }
4249
4250   // Do not continue relaxation.
4251   bool continue_relaxation = any_stub_table_changed;
4252   if (!continue_relaxation)
4253     for (Stub_table_iterator sp = this->stub_tables_.begin();
4254          (sp != this->stub_tables_.end());
4255          ++sp)
4256       (*sp)->finalize_stubs();
4257
4258   return continue_relaxation;
4259 }
4260
4261
4262 // Make a new Stub_table.
4263
4264 template<int size, bool big_endian>
4265 Stub_table<size, big_endian>*
4266 Target_aarch64<size, big_endian>::new_stub_table(
4267     AArch64_input_section<size, big_endian>* owner)
4268 {
4269   Stub_table<size, big_endian>* stub_table =
4270       new Stub_table<size, big_endian>(owner);
4271   stub_table->set_address(align_address(
4272       owner->address() + owner->data_size(), 8));
4273   stub_table->set_file_offset(owner->offset() + owner->data_size());
4274   stub_table->finalize_data_size();
4275
4276   this->stub_tables_.push_back(stub_table);
4277
4278   return stub_table;
4279 }
4280
4281
4282 template<int size, bool big_endian>
4283 typename elfcpp::Elf_types<size>::Elf_Addr
4284 Target_aarch64<size, big_endian>::do_reloc_addend(
4285     void* arg, unsigned int r_type,
4286     typename elfcpp::Elf_types<size>::Elf_Addr) const
4287 {
4288   gold_assert(r_type == elfcpp::R_AARCH64_TLSDESC);
4289   uintptr_t intarg = reinterpret_cast<uintptr_t>(arg);
4290   gold_assert(intarg < this->tlsdesc_reloc_info_.size());
4291   const Tlsdesc_info& ti(this->tlsdesc_reloc_info_[intarg]);
4292   const Symbol_value<size>* psymval = ti.object->local_symbol(ti.r_sym);
4293   gold_assert(psymval->is_tls_symbol());
4294   // The value of a TLS symbol is the offset in the TLS segment.
4295   return psymval->value(ti.object, 0);
4296 }
4297
4298 // Return the number of entries in the PLT.
4299
4300 template<int size, bool big_endian>
4301 unsigned int
4302 Target_aarch64<size, big_endian>::plt_entry_count() const
4303 {
4304   if (this->plt_ == NULL)
4305     return 0;
4306   return this->plt_->entry_count();
4307 }
4308
4309 // Return the offset of the first non-reserved PLT entry.
4310
4311 template<int size, bool big_endian>
4312 unsigned int
4313 Target_aarch64<size, big_endian>::first_plt_entry_offset() const
4314 {
4315   return this->plt_->first_plt_entry_offset();
4316 }
4317
4318 // Return the size of each PLT entry.
4319
4320 template<int size, bool big_endian>
4321 unsigned int
4322 Target_aarch64<size, big_endian>::plt_entry_size() const
4323 {
4324   return this->plt_->get_plt_entry_size();
4325 }
4326
4327 // Define the _TLS_MODULE_BASE_ symbol in the TLS segment.
4328
4329 template<int size, bool big_endian>
4330 void
4331 Target_aarch64<size, big_endian>::define_tls_base_symbol(
4332     Symbol_table* symtab, Layout* layout)
4333 {
4334   if (this->tls_base_symbol_defined_)
4335     return;
4336
4337   Output_segment* tls_segment = layout->tls_segment();
4338   if (tls_segment != NULL)
4339     {
4340       bool is_exec = parameters->options().output_is_executable();
4341       symtab->define_in_output_segment("_TLS_MODULE_BASE_", NULL,
4342                                        Symbol_table::PREDEFINED,
4343                                        tls_segment, 0, 0,
4344                                        elfcpp::STT_TLS,
4345                                        elfcpp::STB_LOCAL,
4346                                        elfcpp::STV_HIDDEN, 0,
4347                                        (is_exec
4348                                         ? Symbol::SEGMENT_END
4349                                         : Symbol::SEGMENT_START),
4350                                        true);
4351     }
4352   this->tls_base_symbol_defined_ = true;
4353 }
4354
4355 // Create the reserved PLT and GOT entries for the TLS descriptor resolver.
4356
4357 template<int size, bool big_endian>
4358 void
4359 Target_aarch64<size, big_endian>::reserve_tlsdesc_entries(
4360     Symbol_table* symtab, Layout* layout)
4361 {
4362   if (this->plt_ == NULL)
4363     this->make_plt_section(symtab, layout);
4364
4365   if (!this->plt_->has_tlsdesc_entry())
4366     {
4367       // Allocate the TLSDESC_GOT entry.
4368       Output_data_got_aarch64<size, big_endian>* got =
4369           this->got_section(symtab, layout);
4370       unsigned int got_offset = got->add_constant(0);
4371
4372       // Allocate the TLSDESC_PLT entry.
4373       this->plt_->reserve_tlsdesc_entry(got_offset);
4374     }
4375 }
4376
4377 // Create a GOT entry for the TLS module index.
4378
4379 template<int size, bool big_endian>
4380 unsigned int
4381 Target_aarch64<size, big_endian>::got_mod_index_entry(
4382     Symbol_table* symtab, Layout* layout,
4383     Sized_relobj_file<size, big_endian>* object)
4384 {
4385   if (this->got_mod_index_offset_ == -1U)
4386     {
4387       gold_assert(symtab != NULL && layout != NULL && object != NULL);
4388       Reloc_section* rela_dyn = this->rela_dyn_section(layout);
4389       Output_data_got_aarch64<size, big_endian>* got =
4390           this->got_section(symtab, layout);
4391       unsigned int got_offset = got->add_constant(0);
4392       rela_dyn->add_local(object, 0, elfcpp::R_AARCH64_TLS_DTPMOD64, got,
4393                           got_offset, 0);
4394       got->add_constant(0);
4395       this->got_mod_index_offset_ = got_offset;
4396     }
4397   return this->got_mod_index_offset_;
4398 }
4399
4400 // Optimize the TLS relocation type based on what we know about the
4401 // symbol.  IS_FINAL is true if the final address of this symbol is
4402 // known at link time.
4403
4404 template<int size, bool big_endian>
4405 tls::Tls_optimization
4406 Target_aarch64<size, big_endian>::optimize_tls_reloc(bool is_final,
4407                                                      int r_type)
4408 {
4409   // If we are generating a shared library, then we can't do anything
4410   // in the linker
4411   if (parameters->options().shared())
4412     return tls::TLSOPT_NONE;
4413
4414   switch (r_type)
4415     {
4416     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
4417     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
4418     case elfcpp::R_AARCH64_TLSDESC_LD_PREL19:
4419     case elfcpp::R_AARCH64_TLSDESC_ADR_PREL21:
4420     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
4421     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
4422     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
4423     case elfcpp::R_AARCH64_TLSDESC_OFF_G1:
4424     case elfcpp::R_AARCH64_TLSDESC_OFF_G0_NC:
4425     case elfcpp::R_AARCH64_TLSDESC_LDR:
4426     case elfcpp::R_AARCH64_TLSDESC_ADD:
4427     case elfcpp::R_AARCH64_TLSDESC_CALL:
4428       // These are General-Dynamic which permits fully general TLS
4429       // access.  Since we know that we are generating an executable,
4430       // we can convert this to Initial-Exec.  If we also know that
4431       // this is a local symbol, we can further switch to Local-Exec.
4432       if (is_final)
4433         return tls::TLSOPT_TO_LE;
4434       return tls::TLSOPT_TO_IE;
4435
4436     case elfcpp::R_AARCH64_TLSIE_MOVW_GOTTPREL_G1:
4437     case elfcpp::R_AARCH64_TLSIE_MOVW_GOTTPREL_G0_NC:
4438     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4439     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
4440     case elfcpp::R_AARCH64_TLSIE_LD_GOTTPREL_PREL19:
4441       // These are Initial-Exec relocs which get the thread offset
4442       // from the GOT. If we know that we are linking against the
4443       // local symbol, we can switch to Local-Exec, which links the
4444       // thread offset into the instruction.
4445       if (is_final)
4446         return tls::TLSOPT_TO_LE;
4447       return tls::TLSOPT_NONE;
4448
4449     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G2:
4450     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1:
4451     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G1_NC:
4452     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0:
4453     case elfcpp::R_AARCH64_TLSLE_MOVW_TPREL_G0_NC:
4454     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
4455     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
4456     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
4457       // When we already have Local-Exec, there is nothing further we
4458       // can do.
4459       return tls::TLSOPT_NONE;
4460
4461     default:
4462       gold_unreachable();
4463     }
4464 }
4465
4466 // Returns true if this relocation type could be that of a function pointer.
4467
4468 template<int size, bool big_endian>
4469 inline bool
4470 Target_aarch64<size, big_endian>::Scan::possible_function_pointer_reloc(
4471   unsigned int r_type)
4472 {
4473   switch (r_type)
4474     {
4475     case elfcpp::R_AARCH64_ABS64:
4476     //TODO
4477       {
4478         return true;
4479       }
4480     }
4481   return false;
4482 }
4483
4484 // For safe ICF, scan a relocation for a local symbol to check if it
4485 // corresponds to a function pointer being taken.  In that case mark
4486 // the function whose pointer was taken as not foldable.
4487
4488 template<int size, bool big_endian>
4489 inline bool
4490 Target_aarch64<size, big_endian>::Scan::local_reloc_may_be_function_pointer(
4491   Symbol_table* ,
4492   Layout* ,
4493   Target_aarch64<size, big_endian>* ,
4494   Sized_relobj_file<size, big_endian>* ,
4495   unsigned int ,
4496   Output_section* ,
4497   const elfcpp::Rela<size, big_endian>& ,
4498   unsigned int r_type,
4499   const elfcpp::Sym<size, big_endian>&)
4500 {
4501   // When building a shared library, do not fold any local symbols as it is
4502   // not possible to distinguish pointer taken versus a call by looking at
4503   // the relocation types.
4504   return (parameters->options().shared()
4505           || possible_function_pointer_reloc(r_type));
4506 }
4507
4508 // For safe ICF, scan a relocation for a global symbol to check if it
4509 // corresponds to a function pointer being taken.  In that case mark
4510 // the function whose pointer was taken as not foldable.
4511
4512 template<int size, bool big_endian>
4513 inline bool
4514 Target_aarch64<size, big_endian>::Scan::global_reloc_may_be_function_pointer(
4515   Symbol_table* ,
4516   Layout* ,
4517   Target_aarch64<size, big_endian>* ,
4518   Sized_relobj_file<size, big_endian>* ,
4519   unsigned int ,
4520   Output_section* ,
4521   const elfcpp::Rela<size, big_endian>& ,
4522   unsigned int r_type,
4523   Symbol* gsym)
4524 {
4525   // When building a shared library, do not fold symbols whose visibility
4526   // is hidden, internal or protected.
4527   return ((parameters->options().shared()
4528            && (gsym->visibility() == elfcpp::STV_INTERNAL
4529                || gsym->visibility() == elfcpp::STV_PROTECTED
4530                || gsym->visibility() == elfcpp::STV_HIDDEN))
4531           || possible_function_pointer_reloc(r_type));
4532 }
4533
4534 // Report an unsupported relocation against a local symbol.
4535
4536 template<int size, bool big_endian>
4537 void
4538 Target_aarch64<size, big_endian>::Scan::unsupported_reloc_local(
4539      Sized_relobj_file<size, big_endian>* object,
4540      unsigned int r_type)
4541 {
4542   gold_error(_("%s: unsupported reloc %u against local symbol"),
4543              object->name().c_str(), r_type);
4544 }
4545
4546 // We are about to emit a dynamic relocation of type R_TYPE.  If the
4547 // dynamic linker does not support it, issue an error.
4548
4549 template<int size, bool big_endian>
4550 void
4551 Target_aarch64<size, big_endian>::Scan::check_non_pic(Relobj* object,
4552                                                       unsigned int r_type)
4553 {
4554   gold_assert(r_type != elfcpp::R_AARCH64_NONE);
4555
4556   switch (r_type)
4557     {
4558     // These are the relocation types supported by glibc for AARCH64.
4559     case elfcpp::R_AARCH64_NONE:
4560     case elfcpp::R_AARCH64_COPY:
4561     case elfcpp::R_AARCH64_GLOB_DAT:
4562     case elfcpp::R_AARCH64_JUMP_SLOT:
4563     case elfcpp::R_AARCH64_RELATIVE:
4564     case elfcpp::R_AARCH64_TLS_DTPREL64:
4565     case elfcpp::R_AARCH64_TLS_DTPMOD64:
4566     case elfcpp::R_AARCH64_TLS_TPREL64:
4567     case elfcpp::R_AARCH64_TLSDESC:
4568     case elfcpp::R_AARCH64_IRELATIVE:
4569     case elfcpp::R_AARCH64_ABS32:
4570     case elfcpp::R_AARCH64_ABS64:
4571       return;
4572
4573     default:
4574       break;
4575     }
4576
4577   // This prevents us from issuing more than one error per reloc
4578   // section. But we can still wind up issuing more than one
4579   // error per object file.
4580   if (this->issued_non_pic_error_)
4581     return;
4582   gold_assert(parameters->options().output_is_position_independent());
4583   object->error(_("requires unsupported dynamic reloc; "
4584                   "recompile with -fPIC"));
4585   this->issued_non_pic_error_ = true;
4586   return;
4587 }
4588
4589 // Scan a relocation for a local symbol.
4590
4591 template<int size, bool big_endian>
4592 inline void
4593 Target_aarch64<size, big_endian>::Scan::local(
4594     Symbol_table* symtab,
4595     Layout* layout,
4596     Target_aarch64<size, big_endian>* target,
4597     Sized_relobj_file<size, big_endian>* object,
4598     unsigned int data_shndx,
4599     Output_section* output_section,
4600     const elfcpp::Rela<size, big_endian>& rela,
4601     unsigned int r_type,
4602     const elfcpp::Sym<size, big_endian>& /* lsym */,
4603     bool is_discarded)
4604 {
4605   if (is_discarded)
4606     return;
4607
4608   typedef Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>
4609       Reloc_section;
4610   Output_data_got_aarch64<size, big_endian>* got =
4611       target->got_section(symtab, layout);
4612   unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
4613
4614   switch (r_type)
4615     {
4616     case elfcpp::R_AARCH64_ABS32:
4617     case elfcpp::R_AARCH64_ABS16:
4618       if (parameters->options().output_is_position_independent())
4619         {
4620           gold_error(_("%s: unsupported reloc %u in pos independent link."),
4621                      object->name().c_str(), r_type);
4622         }
4623       break;
4624
4625     case elfcpp::R_AARCH64_ABS64:
4626       // If building a shared library or pie, we need to mark this as a dynmic
4627       // reloction, so that the dynamic loader can relocate it.
4628       if (parameters->options().output_is_position_independent())
4629         {
4630           Reloc_section* rela_dyn = target->rela_dyn_section(layout);
4631           rela_dyn->add_local_relative(object, r_sym,
4632                                        elfcpp::R_AARCH64_RELATIVE,
4633                                        output_section,
4634                                        data_shndx,
4635                                        rela.get_r_offset(),
4636                                        rela.get_r_addend(),
4637                                        false /* is ifunc */);
4638         }
4639       break;
4640
4641     case elfcpp::R_AARCH64_PREL64:
4642     case elfcpp::R_AARCH64_PREL32:
4643     case elfcpp::R_AARCH64_PREL16:
4644       break;
4645
4646     case elfcpp::R_AARCH64_LD_PREL_LO19:        // 273
4647     case elfcpp::R_AARCH64_ADR_PREL_LO21:       // 274
4648     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21:    // 275
4649     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21_NC: // 276
4650     case elfcpp::R_AARCH64_ADD_ABS_LO12_NC:     // 277
4651     case elfcpp::R_AARCH64_LDST8_ABS_LO12_NC:   // 278
4652     case elfcpp::R_AARCH64_LDST16_ABS_LO12_NC:  // 284
4653     case elfcpp::R_AARCH64_LDST32_ABS_LO12_NC:  // 285
4654     case elfcpp::R_AARCH64_LDST64_ABS_LO12_NC:  // 286
4655     case elfcpp::R_AARCH64_LDST128_ABS_LO12_NC: // 299
4656        break;
4657
4658     // Control flow, pc-relative. We don't need to do anything for a relative
4659     // addressing relocation against a local symbol if it does not reference
4660     // the GOT.
4661     case elfcpp::R_AARCH64_TSTBR14:
4662     case elfcpp::R_AARCH64_CONDBR19:
4663     case elfcpp::R_AARCH64_JUMP26:
4664     case elfcpp::R_AARCH64_CALL26:
4665       break;
4666
4667     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4668     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
4669       {
4670         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4671           optimize_tls_reloc(!parameters->options().shared(), r_type);
4672         if (tlsopt == tls::TLSOPT_TO_LE)
4673           break;
4674
4675         layout->set_has_static_tls();
4676         // Create a GOT entry for the tp-relative offset.
4677         if (!parameters->doing_static_link())
4678           {
4679             got->add_local_with_rel(object, r_sym, GOT_TYPE_TLS_OFFSET,
4680                                     target->rela_dyn_section(layout),
4681                                     elfcpp::R_AARCH64_TLS_TPREL64);
4682           }
4683         else if (!object->local_has_got_offset(r_sym,
4684                                                GOT_TYPE_TLS_OFFSET))
4685           {
4686             got->add_local(object, r_sym, GOT_TYPE_TLS_OFFSET);
4687             unsigned int got_offset =
4688                 object->local_got_offset(r_sym, GOT_TYPE_TLS_OFFSET);
4689             const elfcpp::Elf_Xword addend = rela.get_r_addend();
4690             gold_assert(addend == 0);
4691             got->add_static_reloc(got_offset, elfcpp::R_AARCH64_TLS_TPREL64,
4692                                   object, r_sym);
4693           }
4694       }
4695       break;
4696
4697     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
4698     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
4699       {
4700         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4701             optimize_tls_reloc(!parameters->options().shared(), r_type);
4702         if (tlsopt == tls::TLSOPT_TO_LE)
4703           {
4704             layout->set_has_static_tls();
4705             break;
4706           }
4707         gold_assert(tlsopt == tls::TLSOPT_NONE);
4708
4709         got->add_local_pair_with_rel(object,r_sym, data_shndx,
4710                                      GOT_TYPE_TLS_PAIR,
4711                                      target->rela_dyn_section(layout),
4712                                      elfcpp::R_AARCH64_TLS_DTPMOD64);
4713       }
4714       break;
4715
4716     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
4717     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
4718     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
4719       {
4720         layout->set_has_static_tls();
4721         bool output_is_shared = parameters->options().shared();
4722         if (output_is_shared)
4723           gold_error(_("%s: unsupported TLSLE reloc %u in shared code."),
4724                      object->name().c_str(), r_type);
4725       }
4726       break;
4727
4728     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
4729     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
4730     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
4731       {
4732         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4733             optimize_tls_reloc(!parameters->options().shared(), r_type);
4734         target->define_tls_base_symbol(symtab, layout);
4735         if (tlsopt == tls::TLSOPT_NONE)
4736           {
4737             // Create reserved PLT and GOT entries for the resolver.
4738             target->reserve_tlsdesc_entries(symtab, layout);
4739
4740             // Generate a double GOT entry with an R_AARCH64_TLSDESC reloc.
4741             // The R_AARCH64_TLSDESC reloc is resolved lazily, so the GOT
4742             // entry needs to be in an area in .got.plt, not .got. Call
4743             // got_section to make sure the section has been created.
4744             target->got_section(symtab, layout);
4745             Output_data_got<size, big_endian>* got =
4746                 target->got_tlsdesc_section();
4747             unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
4748             if (!object->local_has_got_offset(r_sym, GOT_TYPE_TLS_DESC))
4749               {
4750                 unsigned int got_offset = got->add_constant(0);
4751                 got->add_constant(0);
4752                 object->set_local_got_offset(r_sym, GOT_TYPE_TLS_DESC,
4753                                              got_offset);
4754                 Reloc_section* rt = target->rela_tlsdesc_section(layout);
4755                 // We store the arguments we need in a vector, and use
4756                 // the index into the vector as the parameter to pass
4757                 // to the target specific routines.
4758                 uintptr_t intarg = target->add_tlsdesc_info(object, r_sym);
4759                 void* arg = reinterpret_cast<void*>(intarg);
4760                 rt->add_target_specific(elfcpp::R_AARCH64_TLSDESC, arg,
4761                                         got, got_offset, 0);
4762               }
4763           }
4764         else if (tlsopt != tls::TLSOPT_TO_LE)
4765           unsupported_reloc_local(object, r_type);
4766       }
4767       break;
4768
4769     case elfcpp::R_AARCH64_TLSDESC_CALL:
4770       break;
4771
4772     default:
4773       unsupported_reloc_local(object, r_type);
4774     }
4775 }
4776
4777
4778 // Report an unsupported relocation against a global symbol.
4779
4780 template<int size, bool big_endian>
4781 void
4782 Target_aarch64<size, big_endian>::Scan::unsupported_reloc_global(
4783     Sized_relobj_file<size, big_endian>* object,
4784     unsigned int r_type,
4785     Symbol* gsym)
4786 {
4787   gold_error(_("%s: unsupported reloc %u against global symbol %s"),
4788              object->name().c_str(), r_type, gsym->demangled_name().c_str());
4789 }
4790
4791 template<int size, bool big_endian>
4792 inline void
4793 Target_aarch64<size, big_endian>::Scan::global(
4794     Symbol_table* symtab,
4795     Layout* layout,
4796     Target_aarch64<size, big_endian>* target,
4797     Sized_relobj_file<size, big_endian> * object,
4798     unsigned int data_shndx,
4799     Output_section* output_section,
4800     const elfcpp::Rela<size, big_endian>& rela,
4801     unsigned int r_type,
4802     Symbol* gsym)
4803 {
4804   typedef Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>
4805     Reloc_section;
4806   const AArch64_reloc_property* arp =
4807       aarch64_reloc_property_table->get_reloc_property(r_type);
4808   gold_assert(arp != NULL);
4809
4810   switch (r_type)
4811     {
4812     case elfcpp::R_AARCH64_ABS16:
4813     case elfcpp::R_AARCH64_ABS32:
4814     case elfcpp::R_AARCH64_ABS64:
4815       {
4816         // Make a PLT entry if necessary.
4817         if (gsym->needs_plt_entry())
4818           {
4819             target->make_plt_entry(symtab, layout, gsym);
4820             // Since this is not a PC-relative relocation, we may be
4821             // taking the address of a function. In that case we need to
4822             // set the entry in the dynamic symbol table to the address of
4823             // the PLT entry.
4824             if (gsym->is_from_dynobj() && !parameters->options().shared())
4825               gsym->set_needs_dynsym_value();
4826           }
4827         // Make a dynamic relocation if necessary.
4828         if (gsym->needs_dynamic_reloc(arp->reference_flags()))
4829           {
4830             if (!parameters->options().output_is_position_independent()
4831                 && gsym->may_need_copy_reloc())
4832               {
4833                 target->copy_reloc(symtab, layout, object,
4834                                    data_shndx, output_section, gsym, rela);
4835               }
4836             else if (r_type == elfcpp::R_AARCH64_ABS64
4837                      && gsym->can_use_relative_reloc(false))
4838               {
4839                 Reloc_section* rela_dyn = target->rela_dyn_section(layout);
4840                 rela_dyn->add_global_relative(gsym,
4841                                               elfcpp::R_AARCH64_RELATIVE,
4842                                               output_section,
4843                                               object,
4844                                               data_shndx,
4845                                               rela.get_r_offset(),
4846                                               rela.get_r_addend(),
4847                                               false);
4848               }
4849             else
4850               {
4851                 check_non_pic(object, r_type);
4852                 Output_data_reloc<elfcpp::SHT_RELA, true, size, big_endian>*
4853                     rela_dyn = target->rela_dyn_section(layout);
4854                 rela_dyn->add_global(
4855                   gsym, r_type, output_section, object,
4856                   data_shndx, rela.get_r_offset(),rela.get_r_addend());
4857               }
4858           }
4859       }
4860       break;
4861
4862     case elfcpp::R_AARCH64_PREL16:
4863     case elfcpp::R_AARCH64_PREL32:
4864     case elfcpp::R_AARCH64_PREL64:
4865       // This is used to fill the GOT absolute address.
4866       if (gsym->needs_plt_entry())
4867         {
4868           target->make_plt_entry(symtab, layout, gsym);
4869         }
4870       break;
4871
4872     case elfcpp::R_AARCH64_LD_PREL_LO19:        // 273
4873     case elfcpp::R_AARCH64_ADR_PREL_LO21:       // 274
4874     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21:    // 275
4875     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21_NC: // 276
4876     case elfcpp::R_AARCH64_ADD_ABS_LO12_NC:     // 277
4877     case elfcpp::R_AARCH64_LDST8_ABS_LO12_NC:   // 278
4878     case elfcpp::R_AARCH64_LDST16_ABS_LO12_NC:  // 284
4879     case elfcpp::R_AARCH64_LDST32_ABS_LO12_NC:  // 285
4880     case elfcpp::R_AARCH64_LDST64_ABS_LO12_NC:  // 286
4881     case elfcpp::R_AARCH64_LDST128_ABS_LO12_NC: // 299
4882       {
4883         if (gsym->needs_plt_entry())
4884           target->make_plt_entry(symtab, layout, gsym);
4885         // Make a dynamic relocation if necessary.
4886         if (gsym->needs_dynamic_reloc(arp->reference_flags()))
4887           {
4888             if (parameters->options().output_is_executable()
4889                 && gsym->may_need_copy_reloc())
4890               {
4891                 target->copy_reloc(symtab, layout, object,
4892                                    data_shndx, output_section, gsym, rela);
4893               }
4894           }
4895         break;
4896       }
4897
4898     case elfcpp::R_AARCH64_ADR_GOT_PAGE:
4899     case elfcpp::R_AARCH64_LD64_GOT_LO12_NC:
4900       {
4901         // This pair of relocations is used to access a specific GOT entry.
4902         // Note a GOT entry is an *address* to a symbol.
4903         // The symbol requires a GOT entry
4904         Output_data_got_aarch64<size, big_endian>* got =
4905           target->got_section(symtab, layout);
4906         if (gsym->final_value_is_known())
4907           {
4908             got->add_global(gsym, GOT_TYPE_STANDARD);
4909           }
4910         else
4911           {
4912             Reloc_section* rela_dyn = target->rela_dyn_section(layout);
4913             if (gsym->is_from_dynobj()
4914                 || gsym->is_undefined()
4915                 || gsym->is_preemptible()
4916                 || (gsym->visibility() == elfcpp::STV_PROTECTED
4917                     && parameters->options().shared()))
4918               got->add_global_with_rel(gsym, GOT_TYPE_STANDARD,
4919                                        rela_dyn, elfcpp::R_AARCH64_GLOB_DAT);
4920             else
4921               {
4922                 if (got->add_global(gsym, GOT_TYPE_STANDARD))
4923                   {
4924                     rela_dyn->add_global_relative(
4925                         gsym, elfcpp::R_AARCH64_RELATIVE,
4926                         got,
4927                         gsym->got_offset(GOT_TYPE_STANDARD),
4928                         0,
4929                         false);
4930                   }
4931               }
4932           }
4933         break;
4934       }
4935
4936     case elfcpp::R_AARCH64_TSTBR14:
4937     case elfcpp::R_AARCH64_CONDBR19:
4938     case elfcpp::R_AARCH64_JUMP26:
4939     case elfcpp::R_AARCH64_CALL26:
4940       {
4941         if (gsym->final_value_is_known())
4942           break;
4943
4944         if (gsym->is_defined() &&
4945             !gsym->is_from_dynobj() &&
4946             !gsym->is_preemptible())
4947           break;
4948
4949         // Make plt entry for function call.
4950         target->make_plt_entry(symtab, layout, gsym);
4951         break;
4952       }
4953
4954     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
4955     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:  // General dynamic
4956       {
4957         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
4958             optimize_tls_reloc(gsym->final_value_is_known(), r_type);
4959         if (tlsopt == tls::TLSOPT_TO_LE)
4960           {
4961             layout->set_has_static_tls();
4962             break;
4963           }
4964         gold_assert(tlsopt == tls::TLSOPT_NONE);
4965
4966         // General dynamic.
4967         Output_data_got_aarch64<size, big_endian>* got =
4968             target->got_section(symtab, layout);
4969         // Create 2 consecutive entries for module index and offset.
4970         got->add_global_pair_with_rel(gsym, GOT_TYPE_TLS_PAIR,
4971                                       target->rela_dyn_section(layout),
4972                                       elfcpp::R_AARCH64_TLS_DTPMOD64,
4973                                       elfcpp::R_AARCH64_TLS_DTPREL64);
4974       }
4975       break;
4976
4977     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
4978     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:  // Initial executable
4979       {
4980         tls::Tls_optimization tlsopt =Target_aarch64<size, big_endian>::
4981           optimize_tls_reloc(gsym->final_value_is_known(), r_type);
4982         if (tlsopt == tls::TLSOPT_TO_LE)
4983           break;
4984
4985         layout->set_has_static_tls();
4986         // Create a GOT entry for the tp-relative offset.
4987         Output_data_got_aarch64<size, big_endian>* got
4988           = target->got_section(symtab, layout);
4989         if (!parameters->doing_static_link())
4990           {
4991             got->add_global_with_rel(
4992               gsym, GOT_TYPE_TLS_OFFSET,
4993               target->rela_dyn_section(layout),
4994               elfcpp::R_AARCH64_TLS_TPREL64);
4995           }
4996         if (!gsym->has_got_offset(GOT_TYPE_TLS_OFFSET))
4997           {
4998             got->add_global(gsym, GOT_TYPE_TLS_OFFSET);
4999             unsigned int got_offset =
5000               gsym->got_offset(GOT_TYPE_TLS_OFFSET);
5001             const elfcpp::Elf_Xword addend = rela.get_r_addend();
5002             gold_assert(addend == 0);
5003             got->add_static_reloc(got_offset,
5004                                   elfcpp::R_AARCH64_TLS_TPREL64, gsym);
5005           }
5006       }
5007       break;
5008
5009     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
5010     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
5011     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:  // Local executable
5012       layout->set_has_static_tls();
5013       if (parameters->options().shared())
5014         gold_error(_("%s: unsupported TLSLE reloc type %u in shared objects."),
5015                    object->name().c_str(), r_type);
5016       break;
5017
5018     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
5019     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
5020     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:  // TLS descriptor
5021       {
5022         target->define_tls_base_symbol(symtab, layout);
5023         tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
5024             optimize_tls_reloc(gsym->final_value_is_known(), r_type);
5025         if (tlsopt == tls::TLSOPT_NONE)
5026           {
5027             // Create reserved PLT and GOT entries for the resolver.
5028             target->reserve_tlsdesc_entries(symtab, layout);
5029
5030             // Create a double GOT entry with an R_AARCH64_TLSDESC
5031             // relocation. The R_AARCH64_TLSDESC is resolved lazily, so the GOT
5032             // entry needs to be in an area in .got.plt, not .got. Call
5033             // got_section to make sure the section has been created.
5034             target->got_section(symtab, layout);
5035             Output_data_got<size, big_endian>* got =
5036                 target->got_tlsdesc_section();
5037             Reloc_section* rt = target->rela_tlsdesc_section(layout);
5038             got->add_global_pair_with_rel(gsym, GOT_TYPE_TLS_DESC, rt,
5039                                           elfcpp::R_AARCH64_TLSDESC, 0);
5040           }
5041         else if (tlsopt == tls::TLSOPT_TO_IE)
5042           {
5043             // Create a GOT entry for the tp-relative offset.
5044             Output_data_got<size, big_endian>* got
5045                 = target->got_section(symtab, layout);
5046             got->add_global_with_rel(gsym, GOT_TYPE_TLS_OFFSET,
5047                                      target->rela_dyn_section(layout),
5048                                      elfcpp::R_AARCH64_TLS_TPREL64);
5049           }
5050         else if (tlsopt != tls::TLSOPT_TO_LE)
5051           unsupported_reloc_global(object, r_type, gsym);
5052       }
5053       break;
5054
5055     case elfcpp::R_AARCH64_TLSDESC_CALL:
5056       break;
5057
5058     default:
5059       gold_error(_("%s: unsupported reloc type in global scan"),
5060                  aarch64_reloc_property_table->
5061                  reloc_name_in_error_message(r_type).c_str());
5062     }
5063   return;
5064 }  // End of Scan::global
5065
5066
5067 // Create the PLT section.
5068 template<int size, bool big_endian>
5069 void
5070 Target_aarch64<size, big_endian>::make_plt_section(
5071   Symbol_table* symtab, Layout* layout)
5072 {
5073   if (this->plt_ == NULL)
5074     {
5075       // Create the GOT section first.
5076       this->got_section(symtab, layout);
5077
5078       this->plt_ = this->make_data_plt(layout, this->got_, this->got_plt_,
5079                                        this->got_irelative_);
5080
5081       layout->add_output_section_data(".plt", elfcpp::SHT_PROGBITS,
5082                                       (elfcpp::SHF_ALLOC
5083                                        | elfcpp::SHF_EXECINSTR),
5084                                       this->plt_, ORDER_PLT, false);
5085
5086       // Make the sh_info field of .rela.plt point to .plt.
5087       Output_section* rela_plt_os = this->plt_->rela_plt()->output_section();
5088       rela_plt_os->set_info_section(this->plt_->output_section());
5089     }
5090 }
5091
5092 // Return the section for TLSDESC relocations.
5093
5094 template<int size, bool big_endian>
5095 typename Target_aarch64<size, big_endian>::Reloc_section*
5096 Target_aarch64<size, big_endian>::rela_tlsdesc_section(Layout* layout) const
5097 {
5098   return this->plt_section()->rela_tlsdesc(layout);
5099 }
5100
5101 // Create a PLT entry for a global symbol.
5102
5103 template<int size, bool big_endian>
5104 void
5105 Target_aarch64<size, big_endian>::make_plt_entry(
5106     Symbol_table* symtab,
5107     Layout* layout,
5108     Symbol* gsym)
5109 {
5110   if (gsym->has_plt_offset())
5111     return;
5112
5113   if (this->plt_ == NULL)
5114     this->make_plt_section(symtab, layout);
5115
5116   this->plt_->add_entry(gsym);
5117 }
5118
5119 template<int size, bool big_endian>
5120 void
5121 Target_aarch64<size, big_endian>::gc_process_relocs(
5122     Symbol_table* symtab,
5123     Layout* layout,
5124     Sized_relobj_file<size, big_endian>* object,
5125     unsigned int data_shndx,
5126     unsigned int sh_type,
5127     const unsigned char* prelocs,
5128     size_t reloc_count,
5129     Output_section* output_section,
5130     bool needs_special_offset_handling,
5131     size_t local_symbol_count,
5132     const unsigned char* plocal_symbols)
5133 {
5134   if (sh_type == elfcpp::SHT_REL)
5135     {
5136       return;
5137     }
5138
5139   gold::gc_process_relocs<
5140     size, big_endian,
5141     Target_aarch64<size, big_endian>,
5142     elfcpp::SHT_RELA,
5143     typename Target_aarch64<size, big_endian>::Scan,
5144     typename Target_aarch64<size, big_endian>::Relocatable_size_for_reloc>(
5145     symtab,
5146     layout,
5147     this,
5148     object,
5149     data_shndx,
5150     prelocs,
5151     reloc_count,
5152     output_section,
5153     needs_special_offset_handling,
5154     local_symbol_count,
5155     plocal_symbols);
5156 }
5157
5158 // Scan relocations for a section.
5159
5160 template<int size, bool big_endian>
5161 void
5162 Target_aarch64<size, big_endian>::scan_relocs(
5163     Symbol_table* symtab,
5164     Layout* layout,
5165     Sized_relobj_file<size, big_endian>* object,
5166     unsigned int data_shndx,
5167     unsigned int sh_type,
5168     const unsigned char* prelocs,
5169     size_t reloc_count,
5170     Output_section* output_section,
5171     bool needs_special_offset_handling,
5172     size_t local_symbol_count,
5173     const unsigned char* plocal_symbols)
5174 {
5175   if (sh_type == elfcpp::SHT_REL)
5176     {
5177       gold_error(_("%s: unsupported REL reloc section"),
5178                  object->name().c_str());
5179       return;
5180     }
5181   gold::scan_relocs<size, big_endian, Target_aarch64, elfcpp::SHT_RELA, Scan>(
5182     symtab,
5183     layout,
5184     this,
5185     object,
5186     data_shndx,
5187     prelocs,
5188     reloc_count,
5189     output_section,
5190     needs_special_offset_handling,
5191     local_symbol_count,
5192     plocal_symbols);
5193 }
5194
5195 // Return the value to use for a dynamic which requires special
5196 // treatment.  This is how we support equality comparisons of function
5197 // pointers across shared library boundaries, as described in the
5198 // processor specific ABI supplement.
5199
5200 template<int size, bool big_endian>
5201 uint64_t
5202 Target_aarch64<size, big_endian>::do_dynsym_value(const Symbol* gsym) const
5203 {
5204   gold_assert(gsym->is_from_dynobj() && gsym->has_plt_offset());
5205   return this->plt_address_for_global(gsym);
5206 }
5207
5208
5209 // Finalize the sections.
5210
5211 template<int size, bool big_endian>
5212 void
5213 Target_aarch64<size, big_endian>::do_finalize_sections(
5214     Layout* layout,
5215     const Input_objects*,
5216     Symbol_table* symtab)
5217 {
5218   const Reloc_section* rel_plt = (this->plt_ == NULL
5219                                   ? NULL
5220                                   : this->plt_->rela_plt());
5221   layout->add_target_dynamic_tags(false, this->got_plt_, rel_plt,
5222                                   this->rela_dyn_, true, false);
5223
5224   // Emit any relocs we saved in an attempt to avoid generating COPY
5225   // relocs.
5226   if (this->copy_relocs_.any_saved_relocs())
5227     this->copy_relocs_.emit(this->rela_dyn_section(layout));
5228
5229   // Fill in some more dynamic tags.
5230   Output_data_dynamic* const odyn = layout->dynamic_data();
5231   if (odyn != NULL)
5232     {
5233       if (this->plt_ != NULL
5234           && this->plt_->output_section() != NULL
5235           && this->plt_ ->has_tlsdesc_entry())
5236         {
5237           unsigned int plt_offset = this->plt_->get_tlsdesc_plt_offset();
5238           unsigned int got_offset = this->plt_->get_tlsdesc_got_offset();
5239           this->got_->finalize_data_size();
5240           odyn->add_section_plus_offset(elfcpp::DT_TLSDESC_PLT,
5241                                         this->plt_, plt_offset);
5242           odyn->add_section_plus_offset(elfcpp::DT_TLSDESC_GOT,
5243                                         this->got_, got_offset);
5244         }
5245     }
5246
5247   // Set the size of the _GLOBAL_OFFSET_TABLE_ symbol to the size of
5248   // the .got.plt section.
5249   Symbol* sym = this->global_offset_table_;
5250   if (sym != NULL)
5251     {
5252       uint64_t data_size = this->got_plt_->current_data_size();
5253       symtab->get_sized_symbol<size>(sym)->set_symsize(data_size);
5254
5255       // If the .got section is more than 0x8000 bytes, we add
5256       // 0x8000 to the value of _GLOBAL_OFFSET_TABLE_, so that 16
5257       // bit relocations have a greater chance of working.
5258       if (data_size >= 0x8000)
5259         symtab->get_sized_symbol<size>(sym)->set_value(
5260           symtab->get_sized_symbol<size>(sym)->value() + 0x8000);
5261     }
5262
5263   if (parameters->doing_static_link()
5264       && (this->plt_ == NULL || !this->plt_->has_irelative_section()))
5265     {
5266       // If linking statically, make sure that the __rela_iplt symbols
5267       // were defined if necessary, even if we didn't create a PLT.
5268       static const Define_symbol_in_segment syms[] =
5269         {
5270           {
5271             "__rela_iplt_start",        // name
5272             elfcpp::PT_LOAD,            // segment_type
5273             elfcpp::PF_W,               // segment_flags_set
5274             elfcpp::PF(0),              // segment_flags_clear
5275             0,                          // value
5276             0,                          // size
5277             elfcpp::STT_NOTYPE,         // type
5278             elfcpp::STB_GLOBAL,         // binding
5279             elfcpp::STV_HIDDEN,         // visibility
5280             0,                          // nonvis
5281             Symbol::SEGMENT_START,      // offset_from_base
5282             true                        // only_if_ref
5283           },
5284           {
5285             "__rela_iplt_end",          // name
5286             elfcpp::PT_LOAD,            // segment_type
5287             elfcpp::PF_W,               // segment_flags_set
5288             elfcpp::PF(0),              // segment_flags_clear
5289             0,                          // value
5290             0,                          // size
5291             elfcpp::STT_NOTYPE,         // type
5292             elfcpp::STB_GLOBAL,         // binding
5293             elfcpp::STV_HIDDEN,         // visibility
5294             0,                          // nonvis
5295             Symbol::SEGMENT_START,      // offset_from_base
5296             true                        // only_if_ref
5297           }
5298         };
5299
5300       symtab->define_symbols(layout, 2, syms,
5301                              layout->script_options()->saw_sections_clause());
5302     }
5303
5304   return;
5305 }
5306
5307 // Perform a relocation.
5308
5309 template<int size, bool big_endian>
5310 inline bool
5311 Target_aarch64<size, big_endian>::Relocate::relocate(
5312     const Relocate_info<size, big_endian>* relinfo,
5313     Target_aarch64<size, big_endian>* target,
5314     Output_section* ,
5315     size_t relnum,
5316     const elfcpp::Rela<size, big_endian>& rela,
5317     unsigned int r_type,
5318     const Sized_symbol<size>* gsym,
5319     const Symbol_value<size>* psymval,
5320     unsigned char* view,
5321     typename elfcpp::Elf_types<size>::Elf_Addr address,
5322     section_size_type /* view_size */)
5323 {
5324   if (view == NULL)
5325     return true;
5326
5327   typedef AArch64_relocate_functions<size, big_endian> Reloc;
5328
5329   const AArch64_reloc_property* reloc_property =
5330       aarch64_reloc_property_table->get_reloc_property(r_type);
5331
5332   if (reloc_property == NULL)
5333     {
5334       std::string reloc_name =
5335           aarch64_reloc_property_table->reloc_name_in_error_message(r_type);
5336       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5337                              _("cannot relocate %s in object file"),
5338                              reloc_name.c_str());
5339       return true;
5340     }
5341
5342   const Sized_relobj_file<size, big_endian>* object = relinfo->object;
5343
5344   // Pick the value to use for symbols defined in the PLT.
5345   Symbol_value<size> symval;
5346   if (gsym != NULL
5347       && gsym->use_plt_offset(reloc_property->reference_flags()))
5348     {
5349       symval.set_output_value(target->plt_address_for_global(gsym));
5350       psymval = &symval;
5351     }
5352   else if (gsym == NULL && psymval->is_ifunc_symbol())
5353     {
5354       unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5355       if (object->local_has_plt_offset(r_sym))
5356         {
5357           symval.set_output_value(target->plt_address_for_local(object, r_sym));
5358           psymval = &symval;
5359         }
5360     }
5361
5362   const elfcpp::Elf_Xword addend = rela.get_r_addend();
5363
5364   // Get the GOT offset if needed.
5365   // For aarch64, the GOT pointer points to the start of the GOT section.
5366   bool have_got_offset = false;
5367   int got_offset = 0;
5368   int got_base = (target->got_ != NULL
5369                   ? (target->got_->current_data_size() >= 0x8000
5370                      ? 0x8000 : 0)
5371                   : 0);
5372   switch (r_type)
5373     {
5374     case elfcpp::R_AARCH64_MOVW_GOTOFF_G0:
5375     case elfcpp::R_AARCH64_MOVW_GOTOFF_G0_NC:
5376     case elfcpp::R_AARCH64_MOVW_GOTOFF_G1:
5377     case elfcpp::R_AARCH64_MOVW_GOTOFF_G1_NC:
5378     case elfcpp::R_AARCH64_MOVW_GOTOFF_G2:
5379     case elfcpp::R_AARCH64_MOVW_GOTOFF_G2_NC:
5380     case elfcpp::R_AARCH64_MOVW_GOTOFF_G3:
5381     case elfcpp::R_AARCH64_GOTREL64:
5382     case elfcpp::R_AARCH64_GOTREL32:
5383     case elfcpp::R_AARCH64_GOT_LD_PREL19:
5384     case elfcpp::R_AARCH64_LD64_GOTOFF_LO15:
5385     case elfcpp::R_AARCH64_ADR_GOT_PAGE:
5386     case elfcpp::R_AARCH64_LD64_GOT_LO12_NC:
5387     case elfcpp::R_AARCH64_LD64_GOTPAGE_LO15:
5388       if (gsym != NULL)
5389         {
5390           gold_assert(gsym->has_got_offset(GOT_TYPE_STANDARD));
5391           got_offset = gsym->got_offset(GOT_TYPE_STANDARD) - got_base;
5392         }
5393       else
5394         {
5395           unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5396           gold_assert(object->local_has_got_offset(r_sym, GOT_TYPE_STANDARD));
5397           got_offset = (object->local_got_offset(r_sym, GOT_TYPE_STANDARD)
5398                         - got_base);
5399         }
5400       have_got_offset = true;
5401       break;
5402
5403     default:
5404       break;
5405     }
5406
5407   typename Reloc::Status reloc_status = Reloc::STATUS_OKAY;
5408   typename elfcpp::Elf_types<size>::Elf_Addr value;
5409   switch (r_type)
5410     {
5411     case elfcpp::R_AARCH64_NONE:
5412       break;
5413
5414     case elfcpp::R_AARCH64_ABS64:
5415       reloc_status = Reloc::template rela_ua<64>(
5416         view, object, psymval, addend, reloc_property);
5417       break;
5418
5419     case elfcpp::R_AARCH64_ABS32:
5420       reloc_status = Reloc::template rela_ua<32>(
5421         view, object, psymval, addend, reloc_property);
5422       break;
5423
5424     case elfcpp::R_AARCH64_ABS16:
5425       reloc_status = Reloc::template rela_ua<16>(
5426         view, object, psymval, addend, reloc_property);
5427       break;
5428
5429     case elfcpp::R_AARCH64_PREL64:
5430       reloc_status = Reloc::template pcrela_ua<64>(
5431         view, object, psymval, addend, address, reloc_property);
5432       break;
5433
5434     case elfcpp::R_AARCH64_PREL32:
5435       reloc_status = Reloc::template pcrela_ua<32>(
5436         view, object, psymval, addend, address, reloc_property);
5437       break;
5438
5439     case elfcpp::R_AARCH64_PREL16:
5440       reloc_status = Reloc::template pcrela_ua<16>(
5441         view, object, psymval, addend, address, reloc_property);
5442       break;
5443
5444     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21_NC:
5445     case elfcpp::R_AARCH64_ADR_PREL_PG_HI21:
5446       reloc_status = Reloc::adrp(view, object, psymval, addend, address,
5447                                  reloc_property);
5448       break;
5449
5450     case elfcpp::R_AARCH64_LDST8_ABS_LO12_NC:
5451     case elfcpp::R_AARCH64_LDST16_ABS_LO12_NC:
5452     case elfcpp::R_AARCH64_LDST32_ABS_LO12_NC:
5453     case elfcpp::R_AARCH64_LDST64_ABS_LO12_NC:
5454     case elfcpp::R_AARCH64_LDST128_ABS_LO12_NC:
5455     case elfcpp::R_AARCH64_ADD_ABS_LO12_NC:
5456       reloc_status = Reloc::template rela_general<32>(
5457         view, object, psymval, addend, reloc_property);
5458       break;
5459
5460     case elfcpp::R_AARCH64_CALL26:
5461       if (this->skip_call_tls_get_addr_)
5462         {
5463           // Double check that the TLSGD insn has been optimized away.
5464           typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
5465           Insntype insn = elfcpp::Swap<32, big_endian>::readval(
5466               reinterpret_cast<Insntype*>(view));
5467           gold_assert((insn & 0xff000000) == 0x91000000);
5468
5469           reloc_status = Reloc::STATUS_OKAY;
5470           this->skip_call_tls_get_addr_ = false;
5471           // Return false to stop further processing this reloc.
5472           return false;
5473         }
5474       // Fallthrough
5475     case elfcpp::R_AARCH64_JUMP26:
5476       if (Reloc::maybe_apply_stub(r_type, relinfo, rela, view, address,
5477                                   gsym, psymval, object))
5478         break;
5479       // Fallthrough
5480     case elfcpp::R_AARCH64_TSTBR14:
5481     case elfcpp::R_AARCH64_CONDBR19:
5482       reloc_status = Reloc::template pcrela_general<32>(
5483         view, object, psymval, addend, address, reloc_property);
5484       break;
5485
5486     case elfcpp::R_AARCH64_ADR_GOT_PAGE:
5487       gold_assert(have_got_offset);
5488       value = target->got_->address() + got_base + got_offset;
5489       reloc_status = Reloc::adrp(view, value + addend, address);
5490       break;
5491
5492     case elfcpp::R_AARCH64_LD64_GOT_LO12_NC:
5493       gold_assert(have_got_offset);
5494       value = target->got_->address() + got_base + got_offset;
5495       reloc_status = Reloc::template rela_general<32>(
5496         view, value, addend, reloc_property);
5497       break;
5498
5499     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
5500     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
5501     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
5502     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
5503     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
5504     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
5505     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
5506     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
5507     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
5508     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
5509     case elfcpp::R_AARCH64_TLSDESC_CALL:
5510       reloc_status = relocate_tls(relinfo, target, relnum, rela, r_type,
5511                                   gsym, psymval, view, address);
5512       break;
5513
5514     // These are dynamic relocations, which are unexpected when linking.
5515     case elfcpp::R_AARCH64_COPY:
5516     case elfcpp::R_AARCH64_GLOB_DAT:
5517     case elfcpp::R_AARCH64_JUMP_SLOT:
5518     case elfcpp::R_AARCH64_RELATIVE:
5519     case elfcpp::R_AARCH64_IRELATIVE:
5520     case elfcpp::R_AARCH64_TLS_DTPREL64:
5521     case elfcpp::R_AARCH64_TLS_DTPMOD64:
5522     case elfcpp::R_AARCH64_TLS_TPREL64:
5523     case elfcpp::R_AARCH64_TLSDESC:
5524       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5525                              _("unexpected reloc %u in object file"),
5526                              r_type);
5527       break;
5528
5529     default:
5530       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5531                              _("unsupported reloc %s"),
5532                              reloc_property->name().c_str());
5533       break;
5534     }
5535
5536   // Report any errors.
5537   switch (reloc_status)
5538     {
5539     case Reloc::STATUS_OKAY:
5540       break;
5541     case Reloc::STATUS_OVERFLOW:
5542       gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5543                              _("relocation overflow in %s"),
5544                              reloc_property->name().c_str());
5545       break;
5546     case Reloc::STATUS_BAD_RELOC:
5547       gold_error_at_location(
5548           relinfo,
5549           relnum,
5550           rela.get_r_offset(),
5551           _("unexpected opcode while processing relocation %s"),
5552           reloc_property->name().c_str());
5553       break;
5554     default:
5555       gold_unreachable();
5556     }
5557
5558   return true;
5559 }
5560
5561
5562 template<int size, bool big_endian>
5563 inline
5564 typename AArch64_relocate_functions<size, big_endian>::Status
5565 Target_aarch64<size, big_endian>::Relocate::relocate_tls(
5566     const Relocate_info<size, big_endian>* relinfo,
5567     Target_aarch64<size, big_endian>* target,
5568     size_t relnum,
5569     const elfcpp::Rela<size, big_endian>& rela,
5570     unsigned int r_type, const Sized_symbol<size>* gsym,
5571     const Symbol_value<size>* psymval,
5572     unsigned char* view,
5573     typename elfcpp::Elf_types<size>::Elf_Addr address)
5574 {
5575   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
5576   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
5577
5578   Output_segment* tls_segment = relinfo->layout->tls_segment();
5579   const elfcpp::Elf_Xword addend = rela.get_r_addend();
5580   const AArch64_reloc_property* reloc_property =
5581       aarch64_reloc_property_table->get_reloc_property(r_type);
5582   gold_assert(reloc_property != NULL);
5583
5584   const bool is_final = (gsym == NULL
5585                          ? !parameters->options().shared()
5586                          : gsym->final_value_is_known());
5587   tls::Tls_optimization tlsopt = Target_aarch64<size, big_endian>::
5588       optimize_tls_reloc(is_final, r_type);
5589
5590   Sized_relobj_file<size, big_endian>* object = relinfo->object;
5591   int tls_got_offset_type;
5592   switch (r_type)
5593     {
5594     case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
5595     case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:  // Global-dynamic
5596       {
5597         if (tlsopt == tls::TLSOPT_TO_LE)
5598           {
5599             if (tls_segment == NULL)
5600               {
5601                 gold_assert(parameters->errors()->error_count() > 0
5602                             || issue_undefined_symbol_error(gsym));
5603                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5604               }
5605             return tls_gd_to_le(relinfo, target, rela, r_type, view,
5606                                 psymval);
5607           }
5608         else if (tlsopt == tls::TLSOPT_NONE)
5609           {
5610             tls_got_offset_type = GOT_TYPE_TLS_PAIR;
5611             // Firstly get the address for the got entry.
5612             typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address;
5613             if (gsym != NULL)
5614               {
5615                 gold_assert(gsym->has_got_offset(tls_got_offset_type));
5616                 got_entry_address = target->got_->address() +
5617                                     gsym->got_offset(tls_got_offset_type);
5618               }
5619             else
5620               {
5621                 unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5622                 gold_assert(
5623                   object->local_has_got_offset(r_sym, tls_got_offset_type));
5624                 got_entry_address = target->got_->address() +
5625                   object->local_got_offset(r_sym, tls_got_offset_type);
5626               }
5627
5628             // Relocate the address into adrp/ld, adrp/add pair.
5629             switch (r_type)
5630               {
5631               case elfcpp::R_AARCH64_TLSGD_ADR_PAGE21:
5632                 return aarch64_reloc_funcs::adrp(
5633                   view, got_entry_address + addend, address);
5634
5635                 break;
5636
5637               case elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC:
5638                 return aarch64_reloc_funcs::template rela_general<32>(
5639                   view, got_entry_address, addend, reloc_property);
5640                 break;
5641
5642               default:
5643                 gold_assert(false);
5644               }
5645           }
5646         gold_error_at_location(relinfo, relnum, rela.get_r_offset(),
5647                                _("unsupported gd_to_ie relaxation on %u"),
5648                                r_type);
5649       }
5650       break;
5651
5652     case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
5653     case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:  // Initial-exec
5654       {
5655         if (tlsopt == tls::TLSOPT_TO_LE)
5656           {
5657             if (tls_segment == NULL)
5658               {
5659                 gold_assert(parameters->errors()->error_count() > 0
5660                             || issue_undefined_symbol_error(gsym));
5661                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5662               }
5663             return tls_ie_to_le(relinfo, target, rela, r_type, view,
5664                                 psymval);
5665           }
5666         tls_got_offset_type = GOT_TYPE_TLS_OFFSET;
5667
5668         // Firstly get the address for the got entry.
5669         typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address;
5670         if (gsym != NULL)
5671           {
5672             gold_assert(gsym->has_got_offset(tls_got_offset_type));
5673             got_entry_address = target->got_->address() +
5674                                 gsym->got_offset(tls_got_offset_type);
5675           }
5676         else
5677           {
5678             unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5679             gold_assert(
5680                 object->local_has_got_offset(r_sym, tls_got_offset_type));
5681             got_entry_address = target->got_->address() +
5682                 object->local_got_offset(r_sym, tls_got_offset_type);
5683           }
5684         // Relocate the address into adrp/ld, adrp/add pair.
5685         switch (r_type)
5686           {
5687           case elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21:
5688             return aarch64_reloc_funcs::adrp(view, got_entry_address + addend,
5689                                              address);
5690             break;
5691           case elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC:
5692             return aarch64_reloc_funcs::template rela_general<32>(
5693               view, got_entry_address, addend, reloc_property);
5694           default:
5695             gold_assert(false);
5696           }
5697       }
5698       // We shall never reach here.
5699       break;
5700
5701     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12:
5702     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12:
5703     case elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12_NC:
5704       {
5705         gold_assert(tls_segment != NULL);
5706         AArch64_address value = psymval->value(object, 0);
5707
5708         if (!parameters->options().shared())
5709           {
5710             AArch64_address aligned_tcb_size =
5711                 align_address(target->tcb_size(),
5712                               tls_segment->maximum_alignment());
5713             return aarch64_reloc_funcs::template
5714                 rela_general<32>(view,
5715                                  value + aligned_tcb_size,
5716                                  addend,
5717                                  reloc_property);
5718           }
5719         else
5720           gold_error(_("%s: unsupported reloc %u "
5721                        "in non-static TLSLE mode."),
5722                      object->name().c_str(), r_type);
5723       }
5724       break;
5725
5726     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
5727     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
5728     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
5729     case elfcpp::R_AARCH64_TLSDESC_CALL:
5730       {
5731         if (tlsopt == tls::TLSOPT_TO_LE)
5732           {
5733             if (tls_segment == NULL)
5734               {
5735                 gold_assert(parameters->errors()->error_count() > 0
5736                             || issue_undefined_symbol_error(gsym));
5737                 return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5738               }
5739             return tls_desc_gd_to_le(relinfo, target, rela, r_type,
5740                                      view, psymval);
5741           }
5742         else
5743           {
5744             tls_got_offset_type = (tlsopt == tls::TLSOPT_TO_IE
5745                                    ? GOT_TYPE_TLS_OFFSET
5746                                    : GOT_TYPE_TLS_DESC);
5747             unsigned int got_tlsdesc_offset = 0;
5748             if (r_type != elfcpp::R_AARCH64_TLSDESC_CALL
5749                 && tlsopt == tls::TLSOPT_NONE)
5750               {
5751                 // We created GOT entries in the .got.tlsdesc portion of the
5752                 // .got.plt section, but the offset stored in the symbol is the
5753                 // offset within .got.tlsdesc.
5754                 got_tlsdesc_offset = (target->got_->data_size()
5755                                       + target->got_plt_section()->data_size());
5756               }
5757             typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address;
5758             if (gsym != NULL)
5759               {
5760                 gold_assert(gsym->has_got_offset(tls_got_offset_type));
5761                 got_entry_address = target->got_->address()
5762                                     + got_tlsdesc_offset
5763                                     + gsym->got_offset(tls_got_offset_type);
5764               }
5765             else
5766               {
5767                 unsigned int r_sym = elfcpp::elf_r_sym<size>(rela.get_r_info());
5768                 gold_assert(
5769                     object->local_has_got_offset(r_sym, tls_got_offset_type));
5770                 got_entry_address = target->got_->address() +
5771                   got_tlsdesc_offset +
5772                   object->local_got_offset(r_sym, tls_got_offset_type);
5773               }
5774             if (tlsopt == tls::TLSOPT_TO_IE)
5775               {
5776                 if (tls_segment == NULL)
5777                   {
5778                     gold_assert(parameters->errors()->error_count() > 0
5779                                 || issue_undefined_symbol_error(gsym));
5780                     return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5781                   }
5782                 return tls_desc_gd_to_ie(relinfo, target, rela, r_type,
5783                                          view, psymval, got_entry_address,
5784                                          address);
5785               }
5786
5787             // Now do tlsdesc relocation.
5788             switch (r_type)
5789               {
5790               case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
5791                 return aarch64_reloc_funcs::adrp(view,
5792                                                  got_entry_address + addend,
5793                                                  address);
5794                 break;
5795               case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
5796               case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
5797                 return aarch64_reloc_funcs::template rela_general<32>(
5798                   view, got_entry_address, addend, reloc_property);
5799                 break;
5800               case elfcpp::R_AARCH64_TLSDESC_CALL:
5801                 return aarch64_reloc_funcs::STATUS_OKAY;
5802                 break;
5803               default:
5804                 gold_unreachable();
5805               }
5806           }
5807         }
5808       break;
5809
5810     default:
5811       gold_error(_("%s: unsupported TLS reloc %u."),
5812                  object->name().c_str(), r_type);
5813     }
5814   return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5815 }  // End of relocate_tls.
5816
5817
5818 template<int size, bool big_endian>
5819 inline
5820 typename AArch64_relocate_functions<size, big_endian>::Status
5821 Target_aarch64<size, big_endian>::Relocate::tls_gd_to_le(
5822              const Relocate_info<size, big_endian>* relinfo,
5823              Target_aarch64<size, big_endian>* target,
5824              const elfcpp::Rela<size, big_endian>& rela,
5825              unsigned int r_type,
5826              unsigned char* view,
5827              const Symbol_value<size>* psymval)
5828 {
5829   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
5830   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
5831   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
5832
5833   Insntype* ip = reinterpret_cast<Insntype*>(view);
5834   Insntype insn1 = elfcpp::Swap<32, big_endian>::readval(ip);
5835   Insntype insn2 = elfcpp::Swap<32, big_endian>::readval(ip + 1);
5836   Insntype insn3 = elfcpp::Swap<32, big_endian>::readval(ip + 2);
5837
5838   if (r_type == elfcpp::R_AARCH64_TLSGD_ADD_LO12_NC)
5839     {
5840       // This is the 2nd relocs, optimization should already have been
5841       // done.
5842       gold_assert((insn1 & 0xfff00000) == 0x91400000);
5843       return aarch64_reloc_funcs::STATUS_OKAY;
5844     }
5845
5846   // The original sequence is -
5847   //   90000000        adrp    x0, 0 <main>
5848   //   91000000        add     x0, x0, #0x0
5849   //   94000000        bl      0 <__tls_get_addr>
5850   // optimized to sequence -
5851   //   d53bd040        mrs     x0, tpidr_el0
5852   //   91400000        add     x0, x0, #0x0, lsl #12
5853   //   91000000        add     x0, x0, #0x0
5854
5855   // Unlike tls_ie_to_le, we change the 3 insns in one function call when we
5856   // encounter the first relocation "R_AARCH64_TLSGD_ADR_PAGE21". Because we
5857   // have to change "bl tls_get_addr", which does not have a corresponding tls
5858   // relocation type. So before proceeding, we need to make sure compiler
5859   // does not change the sequence.
5860   if(!(insn1 == 0x90000000      // adrp x0,0
5861        && insn2 == 0x91000000   // add x0, x0, #0x0
5862        && insn3 == 0x94000000)) // bl 0
5863     {
5864       // Ideally we should give up gd_to_le relaxation and do gd access.
5865       // However the gd_to_le relaxation decision has been made early
5866       // in the scan stage, where we did not allocate any GOT entry for
5867       // this symbol. Therefore we have to exit and report error now.
5868       gold_error(_("unexpected reloc insn sequence while relaxing "
5869                    "tls gd to le for reloc %u."), r_type);
5870       return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5871     }
5872
5873   // Write new insns.
5874   insn1 = 0xd53bd040;  // mrs x0, tpidr_el0
5875   insn2 = 0x91400000;  // add x0, x0, #0x0, lsl #12
5876   insn3 = 0x91000000;  // add x0, x0, #0x0
5877   elfcpp::Swap<32, big_endian>::writeval(ip, insn1);
5878   elfcpp::Swap<32, big_endian>::writeval(ip + 1, insn2);
5879   elfcpp::Swap<32, big_endian>::writeval(ip + 2, insn3);
5880
5881   // Calculate tprel value.
5882   Output_segment* tls_segment = relinfo->layout->tls_segment();
5883   gold_assert(tls_segment != NULL);
5884   AArch64_address value = psymval->value(relinfo->object, 0);
5885   const elfcpp::Elf_Xword addend = rela.get_r_addend();
5886   AArch64_address aligned_tcb_size =
5887       align_address(target->tcb_size(), tls_segment->maximum_alignment());
5888   AArch64_address x = value + aligned_tcb_size;
5889
5890   // After new insns are written, apply TLSLE relocs.
5891   const AArch64_reloc_property* rp1 =
5892       aarch64_reloc_property_table->get_reloc_property(
5893           elfcpp::R_AARCH64_TLSLE_ADD_TPREL_HI12);
5894   const AArch64_reloc_property* rp2 =
5895       aarch64_reloc_property_table->get_reloc_property(
5896           elfcpp::R_AARCH64_TLSLE_ADD_TPREL_LO12);
5897   gold_assert(rp1 != NULL && rp2 != NULL);
5898
5899   typename aarch64_reloc_funcs::Status s1 =
5900       aarch64_reloc_funcs::template rela_general<32>(view + 4,
5901                                                      x,
5902                                                      addend,
5903                                                      rp1);
5904   if (s1 != aarch64_reloc_funcs::STATUS_OKAY)
5905     return s1;
5906
5907   typename aarch64_reloc_funcs::Status s2 =
5908       aarch64_reloc_funcs::template rela_general<32>(view + 8,
5909                                                      x,
5910                                                      addend,
5911                                                      rp2);
5912
5913   this->skip_call_tls_get_addr_ = true;
5914   return s2;
5915 }  // End of tls_gd_to_le
5916
5917
5918 template<int size, bool big_endian>
5919 inline
5920 typename AArch64_relocate_functions<size, big_endian>::Status
5921 Target_aarch64<size, big_endian>::Relocate::tls_ie_to_le(
5922              const Relocate_info<size, big_endian>* relinfo,
5923              Target_aarch64<size, big_endian>* target,
5924              const elfcpp::Rela<size, big_endian>& rela,
5925              unsigned int r_type,
5926              unsigned char* view,
5927              const Symbol_value<size>* psymval)
5928 {
5929   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
5930   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
5931   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
5932
5933   AArch64_address value = psymval->value(relinfo->object, 0);
5934   Output_segment* tls_segment = relinfo->layout->tls_segment();
5935   AArch64_address aligned_tcb_address =
5936       align_address(target->tcb_size(), tls_segment->maximum_alignment());
5937   const elfcpp::Elf_Xword addend = rela.get_r_addend();
5938   AArch64_address x = value + addend + aligned_tcb_address;
5939   // "x" is the offset to tp, we can only do this if x is within
5940   // range [0, 2^32-1]
5941   if (!(size == 32 || (size == 64 && (static_cast<uint64_t>(x) >> 32) == 0)))
5942     {
5943       gold_error(_("TLS variable referred by reloc %u is too far from TP."),
5944                  r_type);
5945       return aarch64_reloc_funcs::STATUS_BAD_RELOC;
5946     }
5947
5948   Insntype* ip = reinterpret_cast<Insntype*>(view);
5949   Insntype insn = elfcpp::Swap<32, big_endian>::readval(ip);
5950   unsigned int regno;
5951   Insntype newinsn;
5952   if (r_type == elfcpp::R_AARCH64_TLSIE_ADR_GOTTPREL_PAGE21)
5953     {
5954       // Generate movz.
5955       regno = (insn & 0x1f);
5956       newinsn = (0xd2a00000 | regno) | (((x >> 16) & 0xffff) << 5);
5957     }
5958   else if (r_type == elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC)
5959     {
5960       // Generate movk.
5961       regno = (insn & 0x1f);
5962       gold_assert(regno == ((insn >> 5) & 0x1f));
5963       newinsn = (0xf2800000 | regno) | ((x & 0xffff) << 5);
5964     }
5965   else
5966     gold_assert(false);
5967
5968   elfcpp::Swap<32, big_endian>::writeval(ip, newinsn);
5969   return aarch64_reloc_funcs::STATUS_OKAY;
5970 }  // End of tls_ie_to_le
5971
5972
5973 template<int size, bool big_endian>
5974 inline
5975 typename AArch64_relocate_functions<size, big_endian>::Status
5976 Target_aarch64<size, big_endian>::Relocate::tls_desc_gd_to_le(
5977              const Relocate_info<size, big_endian>* relinfo,
5978              Target_aarch64<size, big_endian>* target,
5979              const elfcpp::Rela<size, big_endian>& rela,
5980              unsigned int r_type,
5981              unsigned char* view,
5982              const Symbol_value<size>* psymval)
5983 {
5984   typedef typename elfcpp::Elf_types<size>::Elf_Addr AArch64_address;
5985   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
5986   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
5987
5988   // TLSDESC-GD sequence is like:
5989   //   adrp  x0, :tlsdesc:v1
5990   //   ldr   x1, [x0, #:tlsdesc_lo12:v1]
5991   //   add   x0, x0, :tlsdesc_lo12:v1
5992   //   .tlsdesccall    v1
5993   //   blr   x1
5994   // After desc_gd_to_le optimization, the sequence will be like:
5995   //   movz  x0, #0x0, lsl #16
5996   //   movk  x0, #0x10
5997   //   nop
5998   //   nop
5999
6000   // Calculate tprel value.
6001   Output_segment* tls_segment = relinfo->layout->tls_segment();
6002   gold_assert(tls_segment != NULL);
6003   Insntype* ip = reinterpret_cast<Insntype*>(view);
6004   const elfcpp::Elf_Xword addend = rela.get_r_addend();
6005   AArch64_address value = psymval->value(relinfo->object, addend);
6006   AArch64_address aligned_tcb_size =
6007       align_address(target->tcb_size(), tls_segment->maximum_alignment());
6008   AArch64_address x = value + aligned_tcb_size;
6009   // x is the offset to tp, we can only do this if x is within range
6010   // [0, 2^32-1]. If x is out of range, fail and exit.
6011   if (size == 64 && (static_cast<uint64_t>(x) >> 32) != 0)
6012     {
6013       gold_error(_("TLS variable referred by reloc %u is too far from TP. "
6014                    "We Can't do gd_to_le relaxation.\n"), r_type);
6015       return aarch64_reloc_funcs::STATUS_BAD_RELOC;
6016     }
6017   Insntype newinsn;
6018   switch (r_type)
6019     {
6020     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
6021     case elfcpp::R_AARCH64_TLSDESC_CALL:
6022       // Change to nop
6023       newinsn = 0xd503201f;
6024       break;
6025
6026     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
6027       // Change to movz.
6028       newinsn = 0xd2a00000 | (((x >> 16) & 0xffff) << 5);
6029       break;
6030
6031     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
6032       // Change to movk.
6033       newinsn = 0xf2800000 | ((x & 0xffff) << 5);
6034       break;
6035
6036     default:
6037       gold_error(_("unsupported tlsdesc gd_to_le optimization on reloc %u"),
6038                  r_type);
6039       gold_unreachable();
6040     }
6041   elfcpp::Swap<32, big_endian>::writeval(ip, newinsn);
6042   return aarch64_reloc_funcs::STATUS_OKAY;
6043 }  // End of tls_desc_gd_to_le
6044
6045
6046 template<int size, bool big_endian>
6047 inline
6048 typename AArch64_relocate_functions<size, big_endian>::Status
6049 Target_aarch64<size, big_endian>::Relocate::tls_desc_gd_to_ie(
6050              const Relocate_info<size, big_endian>* /* relinfo */,
6051              Target_aarch64<size, big_endian>* /* target */,
6052              const elfcpp::Rela<size, big_endian>& rela,
6053              unsigned int r_type,
6054              unsigned char* view,
6055              const Symbol_value<size>* /* psymval */,
6056              typename elfcpp::Elf_types<size>::Elf_Addr got_entry_address,
6057              typename elfcpp::Elf_types<size>::Elf_Addr address)
6058 {
6059   typedef typename elfcpp::Swap<32, big_endian>::Valtype Insntype;
6060   typedef AArch64_relocate_functions<size, big_endian> aarch64_reloc_funcs;
6061
6062   // TLSDESC-GD sequence is like:
6063   //   adrp  x0, :tlsdesc:v1
6064   //   ldr   x1, [x0, #:tlsdesc_lo12:v1]
6065   //   add   x0, x0, :tlsdesc_lo12:v1
6066   //   .tlsdesccall    v1
6067   //   blr   x1
6068   // After desc_gd_to_ie optimization, the sequence will be like:
6069   //   adrp  x0, :tlsie:v1
6070   //   ldr   x0, [x0, :tlsie_lo12:v1]
6071   //   nop
6072   //   nop
6073
6074   Insntype* ip = reinterpret_cast<Insntype*>(view);
6075   const elfcpp::Elf_Xword addend = rela.get_r_addend();
6076   Insntype newinsn;
6077   switch (r_type)
6078     {
6079     case elfcpp::R_AARCH64_TLSDESC_ADD_LO12:
6080     case elfcpp::R_AARCH64_TLSDESC_CALL:
6081       // Change to nop
6082       newinsn = 0xd503201f;
6083       elfcpp::Swap<32, big_endian>::writeval(ip, newinsn);
6084       break;
6085
6086     case elfcpp::R_AARCH64_TLSDESC_ADR_PAGE21:
6087       {
6088         return aarch64_reloc_funcs::adrp(view, got_entry_address + addend,
6089                                          address);
6090       }
6091       break;
6092
6093     case elfcpp::R_AARCH64_TLSDESC_LD64_LO12:
6094       {
6095         const AArch64_reloc_property* reloc_property =
6096             aarch64_reloc_property_table->get_reloc_property(
6097               elfcpp::R_AARCH64_TLSIE_LD64_GOTTPREL_LO12_NC);
6098         return aarch64_reloc_funcs::template rela_general<32>(
6099                  view, got_entry_address, addend, reloc_property);
6100       }
6101       break;
6102
6103     default:
6104       gold_error(_("Don't support tlsdesc gd_to_ie optimization on reloc %u"),
6105                  r_type);
6106       gold_unreachable();
6107     }
6108   return aarch64_reloc_funcs::STATUS_OKAY;
6109 }  // End of tls_desc_gd_to_ie
6110
6111 // Relocate section data.
6112
6113 template<int size, bool big_endian>
6114 void
6115 Target_aarch64<size, big_endian>::relocate_section(
6116     const Relocate_info<size, big_endian>* relinfo,
6117     unsigned int sh_type,
6118     const unsigned char* prelocs,
6119     size_t reloc_count,
6120     Output_section* output_section,
6121     bool needs_special_offset_handling,
6122     unsigned char* view,
6123     typename elfcpp::Elf_types<size>::Elf_Addr address,
6124     section_size_type view_size,
6125     const Reloc_symbol_changes* reloc_symbol_changes)
6126 {
6127   gold_assert(sh_type == elfcpp::SHT_RELA);
6128   typedef typename Target_aarch64<size, big_endian>::Relocate AArch64_relocate;
6129   gold::relocate_section<size, big_endian, Target_aarch64, elfcpp::SHT_RELA,
6130                          AArch64_relocate, gold::Default_comdat_behavior>(
6131     relinfo,
6132     this,
6133     prelocs,
6134     reloc_count,
6135     output_section,
6136     needs_special_offset_handling,
6137     view,
6138     address,
6139     view_size,
6140     reloc_symbol_changes);
6141 }
6142
6143 // Return the size of a relocation while scanning during a relocatable
6144 // link.
6145
6146 template<int size, bool big_endian>
6147 unsigned int
6148 Target_aarch64<size, big_endian>::Relocatable_size_for_reloc::
6149 get_size_for_reloc(
6150     unsigned int ,
6151     Relobj* )
6152 {
6153   // We will never support SHT_REL relocations.
6154   gold_unreachable();
6155   return 0;
6156 }
6157
6158 // Scan the relocs during a relocatable link.
6159
6160 template<int size, bool big_endian>
6161 void
6162 Target_aarch64<size, big_endian>::scan_relocatable_relocs(
6163     Symbol_table* symtab,
6164     Layout* layout,
6165     Sized_relobj_file<size, big_endian>* object,
6166     unsigned int data_shndx,
6167     unsigned int sh_type,
6168     const unsigned char* prelocs,
6169     size_t reloc_count,
6170     Output_section* output_section,
6171     bool needs_special_offset_handling,
6172     size_t local_symbol_count,
6173     const unsigned char* plocal_symbols,
6174     Relocatable_relocs* rr)
6175 {
6176   gold_assert(sh_type == elfcpp::SHT_RELA);
6177
6178   typedef gold::Default_scan_relocatable_relocs<elfcpp::SHT_RELA,
6179     Relocatable_size_for_reloc> Scan_relocatable_relocs;
6180
6181   gold::scan_relocatable_relocs<size, big_endian, elfcpp::SHT_RELA,
6182       Scan_relocatable_relocs>(
6183     symtab,
6184     layout,
6185     object,
6186     data_shndx,
6187     prelocs,
6188     reloc_count,
6189     output_section,
6190     needs_special_offset_handling,
6191     local_symbol_count,
6192     plocal_symbols,
6193     rr);
6194 }
6195
6196 // Relocate a section during a relocatable link.
6197
6198 template<int size, bool big_endian>
6199 void
6200 Target_aarch64<size, big_endian>::relocate_relocs(
6201     const Relocate_info<size, big_endian>* relinfo,
6202     unsigned int sh_type,
6203     const unsigned char* prelocs,
6204     size_t reloc_count,
6205     Output_section* output_section,
6206     typename elfcpp::Elf_types<size>::Elf_Off offset_in_output_section,
6207     const Relocatable_relocs* rr,
6208     unsigned char* view,
6209     typename elfcpp::Elf_types<size>::Elf_Addr view_address,
6210     section_size_type view_size,
6211     unsigned char* reloc_view,
6212     section_size_type reloc_view_size)
6213 {
6214   gold_assert(sh_type == elfcpp::SHT_RELA);
6215
6216   gold::relocate_relocs<size, big_endian, elfcpp::SHT_RELA>(
6217     relinfo,
6218     prelocs,
6219     reloc_count,
6220     output_section,
6221     offset_in_output_section,
6222     rr,
6223     view,
6224     view_address,
6225     view_size,
6226     reloc_view,
6227     reloc_view_size);
6228 }
6229
6230
6231 // The selector for aarch64 object files.
6232
6233 template<int size, bool big_endian>
6234 class Target_selector_aarch64 : public Target_selector
6235 {
6236  public:
6237   Target_selector_aarch64();
6238
6239   virtual Target*
6240   do_instantiate_target()
6241   { return new Target_aarch64<size, big_endian>(); }
6242 };
6243
6244 template<>
6245 Target_selector_aarch64<32, true>::Target_selector_aarch64()
6246   : Target_selector(elfcpp::EM_AARCH64, 32, true,
6247                     "elf32-bigaarch64", "aarch64_elf32_be_vec")
6248 { }
6249
6250 template<>
6251 Target_selector_aarch64<32, false>::Target_selector_aarch64()
6252   : Target_selector(elfcpp::EM_AARCH64, 32, false,
6253                     "elf32-littleaarch64", "aarch64_elf32_le_vec")
6254 { }
6255
6256 template<>
6257 Target_selector_aarch64<64, true>::Target_selector_aarch64()
6258   : Target_selector(elfcpp::EM_AARCH64, 64, true,
6259                     "elf64-bigaarch64", "aarch64_elf64_be_vec")
6260 { }
6261
6262 template<>
6263 Target_selector_aarch64<64, false>::Target_selector_aarch64()
6264   : Target_selector(elfcpp::EM_AARCH64, 64, false,
6265                     "elf64-littleaarch64", "aarch64_elf64_le_vec")
6266 { }
6267
6268 Target_selector_aarch64<32, true> target_selector_aarch64elf32b;
6269 Target_selector_aarch64<32, false> target_selector_aarch64elf32;
6270 Target_selector_aarch64<64, true> target_selector_aarch64elfb;
6271 Target_selector_aarch64<64, false> target_selector_aarch64elf;
6272
6273 } // End anonymous namespace.