Add a generic interface for finding the entry points of a binary

Includes implementations for x86 and PowerPC 64/32
This commit is contained in:
Tristan Ravitch 2018-05-20 21:41:21 -07:00
parent 796e8bc29e
commit 7cbd23dbf8
3 changed files with 107 additions and 22 deletions

View File

@ -1,3 +1,5 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
@ -12,11 +14,13 @@ import GHC.TypeLits
import qualified Control.Monad.Catch as X
import qualified Data.ElfEdit as E
import qualified Data.List.NonEmpty as NEL
import qualified Data.Macaw.BinaryLoader as BL
import qualified Data.Macaw.CFG as MC
import qualified Data.Macaw.Memory.ElfLoader as EL
import qualified Data.Macaw.Memory.LoadCommon as LC
import Data.Macaw.PPC.PPCReg ()
import Data.Maybe ( mapMaybe )
import Data.Typeable ( Typeable )
import qualified SemMC.Architecture.PPC32 as PPC32
@ -25,23 +29,60 @@ import qualified SemMC.Architecture.PPC64 as PPC64
import qualified Data.Macaw.PPC.BinaryFormat.ELF as BE
import qualified Data.Macaw.PPC.TOC as TOC
data PPCElfData w = PPCElfData { elf :: E.Elf w
, secIndexMap :: EL.SectionIndexMap w
}
instance BL.BinaryLoader PPC32.PPC (E.Elf 32) where
type ArchBinaryData PPC32.PPC = TOC.TOC PPC32.PPC
type BinaryFormatData (E.Elf 32) = EL.SectionIndexMap 32
type Diagnostic (E.Elf 32) = EL.MemLoadWarning
type ArchBinaryData PPC32.PPC (E.Elf 32) = TOC.TOC PPC32.PPC
type BinaryFormatData PPC32.PPC (E.Elf 32) = PPCElfData 32
type Diagnostic PPC32.PPC (E.Elf 32) = EL.MemLoadWarning
loadBinary = loadPPCBinary BL.Elf32Repr
entryPoints = ppcEntryPoints
instance BL.BinaryLoader PPC64.PPC (E.Elf 64) where
type ArchBinaryData PPC64.PPC = TOC.TOC PPC64.PPC
type BinaryFormatData (E.Elf 64) = EL.SectionIndexMap 64
type Diagnostic (E.Elf 64) = EL.MemLoadWarning
type ArchBinaryData PPC64.PPC (E.Elf 64) = TOC.TOC PPC64.PPC
type BinaryFormatData PPC64.PPC (E.Elf 64) = PPCElfData 64
type Diagnostic PPC64.PPC (E.Elf 64) = EL.MemLoadWarning
loadBinary = loadPPCBinary BL.Elf64Repr
entryPoints = ppcEntryPoints
ppcEntryPoints :: (X.MonadThrow m,
MC.MemWidth w,
Integral (E.ElfWordType w),
w ~ MC.ArchAddrWidth ppc,
BL.ArchBinaryData ppc (E.Elf w) ~ TOC.TOC ppc,
BL.BinaryFormatData ppc (E.Elf w) ~ PPCElfData w)
=> BL.LoadedBinary ppc (E.Elf w)
-> m (NEL.NonEmpty (MC.MemSegmentOff w))
ppcEntryPoints loadedBinary = do
entryAddr <- liftMemErr PPCElfMemoryError (MC.readAddr mem MC.BigEndian tocEntryAbsAddr)
absEntryAddr <- liftMaybe (PPCInvalidAbsoluteAddress entryAddr) (MC.asSegmentOff mem entryAddr)
let otherEntries = mapMaybe (MC.asSegmentOff mem) (TOC.entryPoints toc)
return (absEntryAddr NEL.:| otherEntries)
where
tocEntryAddr = E.elfEntry (elf (BL.binaryFormatData loadedBinary))
tocEntryAbsAddr = MC.absoluteAddr (MC.memWord (fromIntegral tocEntryAddr))
toc = BL.archBinaryData loadedBinary
mem = BL.memoryImage loadedBinary
liftMaybe :: (X.Exception e, X.MonadThrow m) => e -> Maybe a -> m a
liftMaybe exn a =
case a of
Nothing -> X.throwM exn
Just res -> return res
liftMemErr :: (X.Exception e, X.MonadThrow m) => (t -> e) -> Either t a -> m a
liftMemErr exn a =
case a of
Left err -> X.throwM (exn err)
Right res -> return res
loadPPCBinary :: (w ~ MC.ArchAddrWidth ppc,
X.MonadThrow m,
BL.ArchBinaryData ppc ~ TOC.TOC ppc,
BL.BinaryFormatData (E.Elf w) ~ EL.SectionIndexMap w,
BL.Diagnostic (E.Elf w) ~ EL.MemLoadWarning,
BL.ArchBinaryData ppc (E.Elf w) ~ TOC.TOC ppc,
BL.BinaryFormatData ppc (E.Elf w) ~ PPCElfData w,
BL.Diagnostic ppc (E.Elf w) ~ EL.MemLoadWarning,
MC.MemWidth w,
Typeable ppc,
KnownNat w)
@ -58,13 +99,19 @@ loadPPCBinary binRep lopts e = do
Right toc ->
return BL.LoadedBinary { BL.memoryImage = mem
, BL.archBinaryData = toc
, BL.binaryFormatData = sim
, BL.binaryFormatData =
PPCElfData { elf = e
, secIndexMap = sim
}
, BL.loadDiagnostics = warnings
, BL.binaryRepr = binRep
}
data PPCLoadException = PPCElfLoadError String
| PPCTOCLoadError X.SomeException
deriving (Show)
| forall w . (MC.MemWidth w) => PPCElfMemoryError (MC.MemoryError w)
| forall w . (MC.MemWidth w) => PPCInvalidAbsoluteAddress (MC.MemAddr w)
deriving instance Show PPCLoadException
instance X.Exception PPCLoadException

View File

@ -11,6 +11,7 @@ module Data.Macaw.BinaryLoader (
import qualified Control.Monad.Catch as X
import qualified Data.ElfEdit as E
import qualified Data.List.NonEmpty as NEL
import qualified Data.Macaw.CFG as MC
import qualified Data.Macaw.Memory.LoadCommon as LC
import qualified Data.Parameterized.Classes as PC
@ -27,17 +28,30 @@ instance PC.TestEquality BinaryRepr where
data LoadedBinary arch binFmt =
LoadedBinary { memoryImage :: MC.Memory (MC.ArchAddrWidth arch)
, archBinaryData :: ArchBinaryData arch
, binaryFormatData :: BinaryFormatData binFmt
, loadDiagnostics :: [Diagnostic binFmt]
, archBinaryData :: ArchBinaryData arch binFmt
, binaryFormatData :: BinaryFormatData arch binFmt
, loadDiagnostics :: [Diagnostic arch binFmt]
, binaryRepr :: BinaryRepr binFmt
}
-- | A class for architecture and binary container independent binary loading
--
-- An instance is required for every arch/format pair, but the interface is more
-- accessible to callers than some alternatives.
class BinaryLoader arch binFmt where
type ArchBinaryData arch :: *
type BinaryFormatData binFmt :: *
type Diagnostic binFmt :: *
-- | Architecture-specific information extracted from the binary
type ArchBinaryData arch binFmt :: *
-- | Information specific to the binary format that might be used later.
type BinaryFormatData arch binFmt :: *
type Diagnostic arch binFmt :: *
-- | A loader for the given binary format at a caller-specified architecture
loadBinary :: (X.MonadThrow m) => LC.LoadOptions -> binFmt -> m (LoadedBinary arch binFmt)
-- | An architecture-specific function to return the entry points of a binary
--
-- This function is allowed (and encouraged) to find all possible entry points
-- based on the metadata available in a binary.
entryPoints :: (X.MonadThrow m) => LoadedBinary arch binFmt -> m (NEL.NonEmpty (MC.MemSegmentOff (MC.ArchAddrWidth arch)))
-- | Return a runtime representative of the pointer width of the architecture
addressWidth :: LoadedBinary arch binFmt -> NR.NatRepr (MC.ArchAddrWidth arch)
addressWidth = MC.memWidth . memoryImage

View File

@ -1,3 +1,5 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
@ -9,17 +11,34 @@ module Data.Macaw.BinaryLoader.X86 (
import qualified Control.Monad.Catch as X
import qualified Data.ElfEdit as E
import qualified Data.List.NonEmpty as NEL
import qualified Data.Macaw.BinaryLoader as BL
import qualified Data.Macaw.CFG as MC
import qualified Data.Macaw.Memory.ElfLoader as EL
import qualified Data.Macaw.Memory.LoadCommon as LC
import qualified Data.Macaw.X86 as MX
data X86ElfData w = X86ElfData { elf :: E.Elf w
, secIndexMap :: EL.SectionIndexMap 64
}
instance BL.BinaryLoader MX.X86_64 (E.Elf 64) where
type ArchBinaryData MX.X86_64 = ()
type BinaryFormatData (E.Elf 64) = EL.SectionIndexMap 64
type Diagnostic (E.Elf 64) = EL.MemLoadWarning
type ArchBinaryData MX.X86_64 (E.Elf 64) = ()
type BinaryFormatData MX.X86_64 (E.Elf 64) = X86ElfData 64
type Diagnostic MX.X86_64 (E.Elf 64) = EL.MemLoadWarning
loadBinary = loadX86Binary
entryPoints = x86EntryPoints
x86EntryPoints :: (X.MonadThrow m)
=> BL.LoadedBinary MX.X86_64 (E.Elf 64)
-> m (NEL.NonEmpty (MC.MemSegmentOff 64))
x86EntryPoints loadedBinary = do
case MC.asSegmentOff (BL.memoryImage loadedBinary) addr of
Just entryPoint -> return (entryPoint NEL.:| [])
Nothing -> X.throwM (InvalidEntryPoint addr)
where
addr = MC.absoluteAddr (MC.memWord (fromIntegral (E.elfEntry (elf (BL.binaryFormatData loadedBinary)))))
loadX86Binary :: (X.MonadThrow m)
=> LC.LoadOptions
@ -31,12 +50,17 @@ loadX86Binary lopts e = do
Right (sim, mem, warnings) ->
return BL.LoadedBinary { BL.memoryImage = mem
, BL.archBinaryData = ()
, BL.binaryFormatData = sim
, BL.binaryFormatData =
X86ElfData { elf = e
, secIndexMap = sim
}
, BL.loadDiagnostics = warnings
, BL.binaryRepr = BL.Elf64Repr
}
data X86LoadException = X86ElfLoadError String
deriving (Show)
| forall w . (MC.MemWidth w) => InvalidEntryPoint (MC.MemAddr w)
deriving instance Show X86LoadException
instance X.Exception X86LoadException