Skip to content

Commit

Permalink
Take load offset into account in entryPoints implementations (#10)
Browse files Browse the repository at this point in the history
This change stores load options with the loaded binary and uses those
options to properly calculate entry point addresses such that they
include the offset the binary was loaded at.
  • Loading branch information
bboston7 authored Mar 17, 2022
1 parent f69f3a8 commit 7e26fbe
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 12 deletions.
8 changes: 5 additions & 3 deletions macaw-loader-aarch32/src/Data/Macaw/BinaryLoader/AArch32.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import qualified Data.Macaw.Memory as MM
import qualified Data.Macaw.Memory.ElfLoader as EL
import qualified Data.Macaw.Memory.LoadCommon as LC
import qualified Data.Map.Strict as Map
import Data.Maybe ( mapMaybe )
import Data.Maybe ( fromMaybe, mapMaybe )

import qualified Data.Macaw.ARM as MA

Expand Down Expand Up @@ -57,10 +57,11 @@ aarch32EntryPoints loadedBinary =
Just entryPoint ->
return (entryPoint DLN.:| mapMaybe (BLE.resolveAbsoluteAddress mem) symbols)
where
offset = fromMaybe 0 (LC.loadOffset (MBL.loadOptions loadedBinary))
mem = MBL.memoryImage loadedBinary
addr = MM.memWord (fromIntegral (EE.headerEntry (EE.header (elf (MBL.binaryFormatData loadedBinary)))))
addr = MM.memWord (offset + fromIntegral (EE.headerEntry (EE.header (elf (MBL.binaryFormatData loadedBinary)))))
elfData = elf (MBL.binaryFormatData loadedBinary)
symbols = [ MM.memWord (fromIntegral (EE.steValue entry))
symbols = [ MM.memWord (offset + (fromIntegral (EE.steValue entry)))
| Just (Right st) <- [EE.decodeHeaderSymtab elfData]
, entry <- F.toList (EE.symtabEntries st)
, EE.steType entry == EE.STT_FUNC
Expand All @@ -85,6 +86,7 @@ loadAArch32Binary lopts e =
, MBL.loadDiagnostics = warnings
, MBL.binaryRepr = MBL.Elf32Repr
, MBL.originalBinary = e
, MBL.loadOptions = lopts
}

indexSymbols :: [EL.MemSymbol 32] -> Map.Map (MM.MemAddr 32) BS.ByteString
Expand Down
16 changes: 10 additions & 6 deletions macaw-loader-ppc/src/Data/Macaw/BinaryLoader/PPC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import qualified Data.Macaw.Memory as MM
import qualified Data.Macaw.Memory.ElfLoader as EL
import qualified Data.Macaw.Memory.LoadCommon as LC
import qualified Data.Map.Strict as Map
import Data.Maybe ( mapMaybe )
import Data.Maybe ( fromMaybe, mapMaybe )
import qualified SemMC.Architecture.PPC32 as PPC32
import qualified SemMC.Architecture.PPC64 as PPC64

Expand Down Expand Up @@ -78,13 +78,14 @@ ppc64EntryPoints :: (X.MonadThrow m, MC.ArchAddrWidth PPC64.PPC ~ 64)
ppc64EntryPoints loadedBinary = do
entryAddr <- liftMemErr PPCElfMemoryError
(MC.readAddr mem (BL.memoryEndianness loadedBinary) tocEntryAbsAddr)
absEntryAddr <- liftMaybe (PPCInvalidAbsoluteAddress entryAddr) (MC.asSegmentOff mem entryAddr)
let otherEntries = mapMaybe (MC.asSegmentOff mem) (TOC.entryPoints toc)
absEntryAddr <- liftMaybe (PPCInvalidAbsoluteAddress entryAddr) (MC.asSegmentOff mem (MC.incAddr (fromIntegral offset) entryAddr))
let otherEntries = mapMaybe (MC.asSegmentOff mem . MM.incAddr (fromIntegral offset)) (TOC.entryPoints toc)
return (absEntryAddr NEL.:| otherEntries)
where
offset = fromMaybe 0 (LC.loadOffset (BL.loadOptions loadedBinary))
tocEntryAddr = E.headerEntry $ E.header (elf (BL.binaryFormatData loadedBinary))
tocEntryAbsAddr :: EL.MemWidth w => MC.MemAddr w
tocEntryAbsAddr = MC.absoluteAddr (MC.memWord (fromIntegral tocEntryAddr))
tocEntryAbsAddr = MC.absoluteAddr (MC.memWord (fromIntegral (offset + tocEntryAddr)))
toc = BL.archBinaryData loadedBinary
mem = BL.memoryImage loadedBinary

Expand All @@ -109,10 +110,11 @@ ppc32EntryPoints loadedBinary =
Nothing -> X.throwM (InvalidEntryPoint entryAddr)
Just entryPoint -> return (entryPoint NEL.:| mapMaybe (BLE.resolveAbsoluteAddress mem) symbols)
where
offset = fromMaybe 0 (LC.loadOffset (BL.loadOptions loadedBinary))
mem = BL.memoryImage loadedBinary
entryAddr = MM.memWord (fromIntegral (E.headerEntry (E.header (elf (BL.binaryFormatData loadedBinary)))))
entryAddr = MM.memWord (offset + fromIntegral (E.headerEntry (E.header (elf (BL.binaryFormatData loadedBinary)))))
elfData = elf (BL.binaryFormatData loadedBinary)
symbols = [ MM.memWord (fromIntegral (E.steValue entry))
symbols = [ MM.memWord (offset + (fromIntegral (E.steValue entry)))
| Just (Right st) <- [E.decodeHeaderSymtab elfData]
, entry <- F.toList (E.symtabEntries st)
, E.steType entry == E.STT_FUNC
Expand All @@ -138,6 +140,7 @@ loadPPC32Binary lopts e =
, BL.loadDiagnostics = warnings
, BL.binaryRepr = BL.Elf32Repr
, BL.originalBinary = e
, BL.loadOptions = lopts
}
where
index32 = F.foldl' doIndex Map.empty
Expand Down Expand Up @@ -166,6 +169,7 @@ loadPPC64Binary lopts e = do
, BL.loadDiagnostics = warnings
, BL.binaryRepr = BL.Elf64Repr
, BL.originalBinary = e
, BL.loadOptions = lopts
}

indexSymbols :: (Foldable t)
Expand Down
8 changes: 5 additions & 3 deletions macaw-loader-x86/src/Data/Macaw/BinaryLoader/X86.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import qualified Data.Macaw.Memory as MM
import qualified Data.Macaw.Memory.ElfLoader as EL
import qualified Data.Macaw.Memory.LoadCommon as LC
import qualified Data.Map.Strict as Map
import Data.Maybe ( mapMaybe )
import Data.Maybe ( fromMaybe, mapMaybe )

import qualified Data.Macaw.X86 as MX

Expand Down Expand Up @@ -56,10 +56,11 @@ x86EntryPoints loadedBinary = do
Just entryPoint -> return (entryPoint NEL.:| mapMaybe (BLE.resolveAbsoluteAddress mem) symbolWords)
Nothing -> X.throwM (InvalidEntryPoint addrWord)
where
offset = fromMaybe 0 (LC.loadOffset (BL.loadOptions loadedBinary))
mem = BL.memoryImage loadedBinary
addrWord = MM.memWord (fromIntegral (E.headerEntry (E.header (elf (BL.binaryFormatData loadedBinary)))))
addrWord = MM.memWord (offset + (fromIntegral (E.headerEntry (E.header (elf (BL.binaryFormatData loadedBinary))))))
elfData = elf (BL.binaryFormatData loadedBinary)
symbolWords = [ MM.memWord (fromIntegral (E.steValue entry))
symbolWords = [ MM.memWord (fromIntegral (offset + (E.steValue entry)))
| Just (Right st) <- [E.decodeHeaderSymtab elfData]
, entry <- F.toList (E.symtabEntries st)
, E.steType entry == E.STT_FUNC
Expand All @@ -84,6 +85,7 @@ loadX86Binary lopts e = do
, BL.loadDiagnostics = warnings
, BL.binaryRepr = BL.Elf64Repr
, BL.originalBinary = e
, BL.loadOptions = lopts
}

indexSymbols :: [EL.MemSymbol 64] -> Map.Map (MM.MemAddr 64) BS.ByteString
Expand Down
1 change: 1 addition & 0 deletions macaw-loader/src/Data/Macaw/BinaryLoader.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ data LoadedBinary arch binFmt =
, loadDiagnostics :: [Diagnostic arch binFmt]
, binaryRepr :: BinaryRepr binFmt
, originalBinary :: binFmt
, loadOptions :: LC.LoadOptions
}

-- | A class for architecture and binary container independent binary loading
Expand Down

0 comments on commit 7e26fbe

Please sign in to comment.