Skip to content
Snippets Groups Projects
Verified Commit a69e0dc7 authored by Moritz Angermann's avatar Moritz Angermann
Browse files

[aarch64/elf] fix note parsing

Notes appear to be 8byte aligned instead of 4 as on x86_64 :face_palm:

See: https://reviews.llvm.org/D70962

> The .note.gnu.property SHT_NOTE sections on AArch64 (a 64-bit target) should have alignment 8 to more closely match the binutils implementation where alignment is 4-bytes on 32-bit machines and 8-bytes on 64-bit machines.
> Previously LLD was using 4 for both 32-bit and 64-bit machines.
> There was a long discussion on the right alignment of the .note.gnu.property section on the binutils mailing list. The basic argument was that generic ELF requires 8-byte alignment for SHT_NOTES sections, however this hadn't been respected by other GNU notes sections. The implementation in GNU ld uses 8 and as there is no binary legacy of using 4 in LLD (BTI is only just being picked up and used) I'd like to keep LLD in line with GNU ld.
> Although at present LLD only does something useful with AArch64 properties, this also applies to X86.
parent a85d25e4
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
{-
-----------------------------------------------------------------------------
--
......@@ -14,6 +15,9 @@ module Elf (
makeElfNote
) where
#include <ghcplatform.h>
#include "HsVersions.h"
import GhcPrelude
import AsmUtils
......@@ -362,14 +366,22 @@ readElfNoteBS dflags bs sectionName noteId = action `catchIO` \_ -> do
-- read notes recursively until the one with a valid identifier is found
findNote hdr = do
#if defined(aarch64_HOST_ARCH)
align 8
#else
align 4
#endif
namesz <- gw32 hdr
descsz <- gw32 hdr
_ <- gw32 hdr -- we don't use the note type
name <- if namesz == 0
then return LBS.empty
else getLazyByteStringNul
#if defined(aarch64_HOST_ARCH)
align 8
#else
align 4
#endif
desc <- if descsz == 0
then return LBS.empty
else getLazyByteString (fromIntegral descsz)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment