Flesh out disassembleFn a bit more

This commit is contained in:
Tristan Ravitch 2017-10-02 13:35:51 -07:00
parent 20e5b5f00d
commit 4b6b82cd13
2 changed files with 43 additions and 3 deletions

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
@ -164,7 +165,10 @@ ppc64_linux_info = ppc_linux_info (Proxy @PPC64.PPC)
ppc32_linux_info :: MI.ArchitectureInfo PPC32.PPC
ppc32_linux_info = ppc_linux_info (Proxy @PPC32.PPC)
ppc_linux_info :: (ArchReg ppc ~ PPCReg ppc) => proxy ppc -> MI.ArchitectureInfo ppc
ppc_linux_info :: (ArchReg ppc ~ PPCReg ppc,
MM.MemWidth (RegAddrWidth (ArchReg ppc)))
=> proxy ppc
-> MI.ArchitectureInfo ppc
ppc_linux_info proxy =
MI.ArchitectureInfo { MI.withArchConstraints = undefined
, MI.archAddrWidth = undefined

View File

@ -1,6 +1,10 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Macaw.PPC.Disassemble ( disassembleFn ) where
import qualified Control.Monad.Except as ET
import Control.Monad.ST ( ST )
import Control.Monad.Trans ( lift )
import Data.Macaw.AbsDomain.AbsState as MA
import Data.Macaw.CFG
@ -8,11 +12,43 @@ import Data.Macaw.CFG.Block
import qualified Data.Macaw.Memory as MM
import qualified Data.Parameterized.Nonce as NC
disassembleFn :: proxy ppc
newtype DisM s a = DisM { unDisM :: ET.ExceptT DisassembleException (ST s) a }
deriving (Functor,
Applicative,
Monad,
ET.MonadError DisassembleException)
data DisassembleException = DisassembleException
deriving (Show)
liftST :: ST s a -> DisM s a
liftST = DisM . lift
tryDisassembleBlock :: MM.Memory (ArchAddrWidth ppc)
-> NC.NonceGenerator (ST ids) ids
-> ArchSegmentOff ppc
-> ArchAddrWord ppc
-> DisM s ([Block ppc ids], MM.MemWord (ArchAddrWidth ppc))
tryDisassembleBlock = undefined
-- | Disassemble a block from the given start address (which points into the
-- 'MM.Memory').
--
-- Return a list of disassembled blocks as well as the total number of bytes
-- occupied by those blocks.
disassembleFn :: (MM.MemWidth (RegAddrWidth (ArchReg ppc)))
=> proxy ppc
-> MM.Memory (ArchAddrWidth ppc)
-> NC.NonceGenerator (ST ids) ids
-> ArchSegmentOff ppc
-- ^ The address to disassemble from
-> ArchAddrWord ppc
-- ^ Maximum size of the block (a safeguard)
-> MA.AbsBlockState (ArchReg ppc)
-- ^ Abstract state of the processor at the start of the block
-> ST ids ([Block ppc ids], MM.MemWord (ArchAddrWidth ppc), Maybe String)
disassembleFn = undefined
disassembleFn _ mem nonceGen startAddr maxSize _ = do
mr <- ET.runExceptT (unDisM (tryDisassembleBlock mem nonceGen startAddr maxSize))
case mr of
Left exn -> return ([], 0, Just (show exn))
Right (blocks, bytes) -> return (blocks, bytes, Nothing)