Skip to content

Commit

Permalink
[no ci] wip
Browse files Browse the repository at this point in the history
  • Loading branch information
aleksey-makarov committed May 1, 2024
1 parent fa53d21 commit 3628857
Show file tree
Hide file tree
Showing 27 changed files with 171 additions and 28 deletions.
95 changes: 67 additions & 28 deletions src/Data/Internal/Elf.hs
Original file line number Diff line number Diff line change
Expand Up @@ -439,46 +439,62 @@ tail' :: [a] -> [a]
tail' [] = []
tail' (_ : xs) = xs

-- a: alignment
-- m: alignment module (a power of 2)
-- x: current address
-- returns the smallest position x' such that (x <= x') && (x' mod m == a)
nextOffset :: SingElfClassI a => WordXX a -> WordXX a -> WordXX a -> WordXX a
nextOffset _ 0 a = a
nextOffset t m a | m .&. (m - 1) /= 0 = error $ "align module is not power of two " ++ show m
| otherwise = if a' + t' < a then a' + m + t' else a' + t'
nextOffset _ 0 x = x
nextOffset a m x | m .&. (m - 1) /= 0 = error $ "align module is not power of two " ++ show m
| otherwise = if x' + a' < x then x' + m + a' else x' + a'
where
a' = a .&. complement (m - 1)
t' = t .&. (m - 1)
x' = x .&. complement (m - 1)
a' = a .&. (m - 1)

-- | bs: the contents of the ELF file
-- | rBuilders: the ELF tree that does not contain any RBuilderRawData or RBuilderRawAlign
-- | that are required to restore the original ELF file
-- | returns rBuilder's that could be restored into the original ELF file modulo section numeration
addRawData :: forall a . SingElfClassI a => BSL.ByteString -> [RBuilder a] -> [RBuilder a]
addRawData _ [] = []
addRawData bs rBuilders = snd $ addRawData' 0 (lrbie, rBuilders)
-- addRawData _ [] = []
addRawData bs rBuilders = snd $ addRawData' 0 (lrbib + lrbis, rBuilders)
where

-- e, e', ee and lrbie stand for the first occupied byte after the place being fixed
-- lrbi: last rBuilder interval (begin, size)
lrbi@(I lrbib lrbis) = rBuilderInterval $ L.last rBuilders
lrbie = if I.empty lrbi then lrbib else lrbib + lrbis
-- | the last rBuilder interval (begin, size)
(I lrbib lrbis) = rBuilderInterval $ L.last rBuilders

allEmpty :: WordXX a -> WordXX a -> Bool
allEmpty b s = BSL.all (== 0) bs'
where
bs' = cut bs (fromIntegral b) (fromIntegral s)

-- alignHint: max alignment of the container segments
-- e: the first byte after the last element of rbs
-- rbs: the content of ELF file or of a segment
-- returns (e', rbs') where rbs' is rbs with raw data inserted and
-- e' is fixed e
-- how it is fixed: there may be some data in the segment between e and the end of the
-- current segment. When that data is added into rbs,
-- the minimum e' such that all data from this position to the end
-- of the current segment is empty
addRawData' :: WordXX a -> (WordXX a, [RBuilder a]) -> (WordXX a, [RBuilder a])
addRawData' alignHint (e, rbs) = L.foldr f (e, []) $ fmap fixRBuilder rbs
where

f rb (e', rbs') =
let
i@(I b s) = rBuilderInterval rb
b' = if I.empty i then b else b + s
rbi@(I b s) = rBuilderInterval rb
b' = if I.empty rbi then b else b + s
rbs'' = addRaw b' e' rbs'
in
(b, rb : rbs'')

fixRBuilder :: RBuilder a -> RBuilder a
fixRBuilder p | I.empty $ rBuilderInterval p = p
fixRBuilder p@RBuilderSegment{..} =
fixRBuilder x | I.empty $ rBuilderInterval x = x
fixRBuilder x@RBuilderSegment{..} =
RBuilderSegment{ rbpData = addRaw b ee' rbs', ..}
where
(I b s) = rBuilderInterval p
(I b s) = rBuilderInterval x
ee = b + s
alignHint' = max (pAlign rbpHeader) alignHint
(ee', rbs') = addRawData' alignHint' (ee, rbpData)
Expand All @@ -498,24 +514,44 @@ addRawData bs rBuilders = snd $ addRawData' 0 (lrbie, rBuilders)
-- than is required by alignment rules (e')
if e' < ee && e'' == ee
then
RBuilderRawAlign ee alignHint : rbs'
RBuilderRawAlign eAddr eAlignHint : rbs'
else
rbs'
else
rbs'
where
wordSizeA = wordSize $ fromSingElfClass $ singElfClass @a
s = ee - b

eAddr = case rbs' of
(RBuilderSegment{rbpHeader = SegmentXX{..}} : _) -> pVirtAddr
_ -> 0
eAddrAlign = case rbs' of

eAlign = case rbs' of
(RBuilderSegment{rbpHeader = SegmentXX{..}} : _) -> pAlign
(RBuilderSection{rbsHeader = SectionXX{..}} : _) -> sAddrAlign
_ -> wordSize $ fromSingElfClass $ singElfClass @a
-- (RBuilderSectionTable{..} : _) -> 0
-- (RBuilderSegmentTable{..} : _) -> 0
-- _ -> wordSize $ fromSingElfClass $ singElfClass @a
_ -> 0

eAddrHint = case rbs' of
(RBuilderSegment{rbpHeader = SegmentXX{..}} : _) -> pVirtAddr
(RBuilderSection{rbsHeader = SectionXX{..}} : _) -> sAddr
_ -> 0

eAlignHint = case rbs' of
(RBuilderSegment{rbpHeader = SegmentXX{..}} : _) -> pAlign
(RBuilderSection{rbsHeader = SectionXX{..}} : _) -> sAddrAlign
(RBuilderSectionTable{} : _) -> wordSizeA
(RBuilderSegmentTable{} : _) -> wordSizeA
[] -> alignHint
_ -> 0

-- e' here is the address of the next section/segment
-- according to the regular alignment rules
e' = nextOffset eAddr eAddrAlign b
e'' = nextOffset ee alignHint b
e' = nextOffset eAddr eAlign b
e'' = nextOffset eAddrHint eAlignHint b

infix 9 !!?

Expand Down Expand Up @@ -758,8 +794,8 @@ serializeElf' elfs = do
offset' <- use wbsOffset
wbsDataReversed %= (WBuilderDataByteStream (BSL.replicate (fromIntegral $ offset' - offset) 0) :)

alignWord :: (MonadThrow n, MonadState (WBuilderState a) n) => n ()
alignWord = align 0 $ wordSize $ fromSingElfClass $ singElfClass @a
-- alignWord :: (MonadThrow n, MonadState (WBuilderState a) n) => n ()
-- alignWord = align 0 $ wordSize $ fromSingElfClass $ singElfClass @a

dataIsEmpty :: ElfSectionData c -> Bool
dataIsEmpty (ElfSectionData bs) = BSL.null bs
Expand All @@ -783,22 +819,25 @@ serializeElf' elfs = do
wbsDataReversed %= (WBuilderDataHeader :)
wbsOffset += headerSize elfClass
elf2WBuilder ElfSectionTable = do
alignWord -- FIXME: Don't hardcode this. Instead use ElfRawAlign when parsing
-- alignWord -- FIXME
use wbsOffset >>= assign wbsShOff
wbsDataReversed %= (WBuilderDataSectionTable :)
wbsOffset += (sectionN + 1) * sectionTableEntrySize elfClass
elf2WBuilder ElfSegmentTable = do
alignWord -- <- FIXME: Ditto
-- alignWord -- FIXME
use wbsOffset >>= assign wbsPhOff
wbsDataReversed %= (WBuilderDataSegmentTable :)
wbsOffset += segmentN * segmentTableEntrySize elfClass
elf2WBuilder ElfSection{esFlags = ElfSectionFlag f, ..} = do
when (f .&. fromIntegral (complement (maxBound @(WordXX a))) /= 0) do
$chainedError $ "section flags at section " ++ show esN ++ "don't fit"

-- FIXME: this should be fixed at parsing
-- I don't see any sense in aligning NOBITS section data
-- still gcc does it for .o files
when (esType /= SHT_NOBITS || (ehType header') == ET_REL) do
align 0 esAddrAlign -- <- FIXME: Don't hardcode this, use ElfRawAlign
-- when (esType /= SHT_NOBITS || (ehType header') == ET_REL) do
-- align 0 esAddrAlign -- <- FIXME: Don't hardcode this, use ElfRawAlign

(n, ns) <- uses wbsNameIndexes \case
n' : ns' -> (n', ns')
_ -> error "internal error: different number of sections in two iterations"
Expand All @@ -824,7 +863,7 @@ serializeElf' elfs = do
wbsShStrNdx .= shStrNdx
wbsNameIndexes .= ns
elf2WBuilder ElfSegment { .. } = do
align epVirtAddr epAlign
-- align epVirtAddr epAlign
offset <- use wbsOffset
void $ mapMElfList elf2WBuilder epData
offset' <- use wbsOffset
Expand Down
4 changes: 4 additions & 0 deletions tests/testdata/arm_32_lsb/arp.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -423,4 +423,8 @@ section 26 ".ARM.attributes" {
total: 53
}
string table section 27 ".shstrtab"
raw align {
Offset: 0x00000000
Align: 0x00000004
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_32_lsb/bash.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -434,4 +434,8 @@ section 26 ".ARM.attributes" {
total: 53
}
string table section 27 ".shstrtab"
raw align {
Offset: 0x00000000
Align: 0x00000004
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_64_lsb/asm_abort.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -150,4 +150,8 @@ section 8 ".rela.eh_frame" {
Data: 0x000000000000001c 0x0000000000000000 R_AARCH64_PREL32 1 ("" bind: STB_Local type: STT_Section sindex: ElfSectionIndex 1 value: 0x0000000000000000 size: 0x0000000000000000)
}
string table section 11 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_64_lsb/chmod.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -428,4 +428,8 @@ section 25 ".comment" {
total: 59
}
string table section 26 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_64_lsb/crtn.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -112,4 +112,8 @@ section 8 ".strtab" {
Data: 00 24 78 00 # .$x.
}
string table section 9 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_64_lsb/ld-2.30.so.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -410,4 +410,8 @@ section 22 ".strtab" {
total: 7310
}
string table section 23 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_64_lsb/libelf-0.177.so.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -419,4 +419,8 @@ section 25 ".comment" {
total: 59
}
string table section 26 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_64_lsb/test_bss.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -178,4 +178,8 @@ section 10 ".rela.eh_frame" {
total: 5
}
string table section 13 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/arm_64_lsb/xor-neon.ko.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -319,4 +319,8 @@ section 15 ".rela__patchable_function_entries" {
total: 4
}
string table section 25 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/nios/a.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -271,4 +271,8 @@ section 17 ".strtab" {
total: 2635
}
string table section 18 ".shstrtab"
raw align {
Offset: 0x00000000
Align: 0x00000004
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/nios/a.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -248,4 +248,8 @@ section 16 ".rela.debug_frame" {
0c 02 00 00 00 00 00 00 # ........
}
string table section 19 ".shstrtab"
raw align {
Offset: 0x00000000
Align: 0x00000004
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/orig/bloated.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -480,4 +480,8 @@ section 30 ".strtab" {
total: 891
}
string table section 28 ".shstrtab"
raw align {
Offset: 0x00000000
Align: 0x00000004
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/orig/vdso.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -268,4 +268,8 @@ section 15 ".comment" {
33 2e 30 00 # 3.0.
}
string table section 16 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/ppc/64/crt1.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -206,4 +206,8 @@ section 11 ".rela.data.rel.ro.local" {
total: 72
}
string table section 16 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/ppc/64/dladdr.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -155,4 +155,8 @@ section 9 ".rela.eh_frame" {
00 00 00 00 00 00 00 00 # ........
}
string table section 12 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/ppc/64_lsb/C-address.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -148,4 +148,8 @@ section 6 ".rela.data.rel.ro.local" {
total: 312
}
string table section 11 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/ppc/64_lsb/Mcrt1.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -61,4 +61,8 @@ section 5 ".note.GNU-stack" {
Data:
}
string table section 6 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/riscv/aio_cancel.o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -129,4 +129,8 @@ section 2 ".rela.text" {
total: 924
}
string table section 9 ".shstrtab"
raw align {
Offset: 0x00000000
Align: 0x00000004
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/riscv/bash4.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -425,4 +425,8 @@ section 26 ".gnu_debuglink" {
Data: 62 61 73 68 34 2e 64 65 62 75 67 00 7e 0c 51 7a # bash4.debug.~.Qz
}
string table section 27 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/riscv/cp.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -386,4 +386,8 @@ section 22 ".bss" {
Data: NoBits: 1508
}
string table section 23 ".shstrtab"
raw align {
Offset: 0x00000000
Align: 0x00000004
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/riscv/liblua-5.3.so.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -319,4 +319,8 @@ section 19 ".gnu_debuglink" {
62 75 67 00 d3 6b 5f 9f # bug..k_.
}
string table section 20 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
4 changes: 4 additions & 0 deletions tests/testdata/x86_64/Elf.dyn_o.elf.golden
Original file line number Diff line number Diff line change
Expand Up @@ -156,4 +156,8 @@ section 4 ".rela.data" {
total: 8688
}
string table section 11 ".shstrtab"
raw align {
Offset: 0x0000000000000000
Align: 0x0000000000000008
}
section table
Loading

0 comments on commit 3628857

Please sign in to comment.