Skip to content

Commit

Permalink
move Metadata out of Pure
Browse files Browse the repository at this point in the history
  • Loading branch information
kmcallister committed Aug 21, 2011
1 parent f70be73 commit 5888808
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 26 deletions.
12 changes: 12 additions & 0 deletions Hdis86/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ module Hdis86.IO
, getInstruction
, getLength, getOffset
, getHex, getBytes, getAssembly
, getMetadata

-- * Configuration
, setConfig
Expand Down Expand Up @@ -311,6 +312,17 @@ getAssembly :: UD -> IO String
getAssembly = flip withUDPtr $ \p ->
C.insn_asm p >>= peekCString

-- | Get all metadata about the current instruction,
-- along with the instruction itself.
getMetadata :: UD -> IO Metadata
getMetadata ud = Metadata
<$> getOffset ud
<*> getLength ud
<*> getHex ud
<*> getBytes ud
<*> getAssembly ud
<*> getInstruction ud

-- | Skip the next /n/ bytes of the input.
skip :: UD -> Word -> IO ()
skip s n = withUDPtr s $ flip C.input_skip (fromIntegral n)
Expand Down
27 changes: 1 addition & 26 deletions Hdis86/Pure.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,3 @@
{-# LANGUAGE
DeriveDataTypeable #-}

-- | Interface to the @udis86@ disassembler.
--
-- This is the simplest, most high-level interface.
Expand All @@ -19,12 +16,6 @@ import Hdis86.Types
import Hdis86.IO ( UD )
import qualified Hdis86.IO as I

import Data.Typeable ( Typeable )
import Data.Data ( Data )

import Control.Applicative
import Data.Word

import System.IO.Unsafe ( unsafePerformIO )

import qualified Data.ByteString as BS
Expand All @@ -46,24 +37,8 @@ disWith f cfg bs = unsafePerformIO $ do
disassemble :: Config -> BS.ByteString -> [Instruction]
disassemble = disWith I.getInstruction

-- | An instruction with full metadata.
data Metadata = Metadata
{ mdOffset :: Word64 -- ^ Offset of the start of this instruction
, mdLength :: Word -- ^ Length of this instruction in bytes
, mdHex :: String -- ^ Hexadecimal representation of this instruction
, mdBytes :: BS.ByteString -- ^ Bytes that make up this instruction
, mdAssembly :: String -- ^ Assembly code for this instruction
, mdInst :: Instruction -- ^ The instruction itself
} deriving (Eq, Ord, Show, Read, Typeable, Data)

-- | Disassemble machine code, with full metadata.
--
-- The output is produced lazily.
disassembleMetadata :: Config -> BS.ByteString -> [Metadata]
disassembleMetadata = disWith $ \ud -> Metadata
<$> I.getOffset ud
<*> I.getLength ud
<*> I.getHex ud
<*> I.getBytes ud
<*> I.getAssembly ud
<*> I.getInstruction ud
disassembleMetadata = disWith I.getMetadata
14 changes: 14 additions & 0 deletions Hdis86/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,9 @@ module Hdis86.Types
-- * Word sizes
, WordSize(..), wordSize, bitsInWord

-- * Instruction with metadata
, Metadata(..)

-- * Configuration
, Config(..)
, Vendor(..), CPUMode(..), Syntax(..)
Expand All @@ -38,6 +41,7 @@ import Data.Word
import Data.Int
import Control.Applicative hiding ( Const )

import qualified Data.ByteString as BS
import qualified Text.Read as R
import qualified Test.QuickCheck as Q

Expand Down Expand Up @@ -222,6 +226,16 @@ data Immediate t = Immediate
, iValue :: t -- ^ Immediate value, e.g @'Int64'@ or @'Word64'@
} deriving (Eq, Ord, Show, Read, Typeable, Data)

-- | An instruction with full metadata.
data Metadata = Metadata
{ mdOffset :: Word64 -- ^ Offset of the start of this instruction
, mdLength :: Word -- ^ Length of this instruction in bytes
, mdHex :: String -- ^ Hexadecimal representation of this instruction
, mdBytes :: BS.ByteString -- ^ Bytes that make up this instruction
, mdAssembly :: String -- ^ Assembly code for this instruction
, mdInst :: Instruction -- ^ The instruction itself
} deriving (Eq, Ord, Show, Read, Typeable, Data)

-- | CPU vendors, supporting slightly different instruction sets.
data Vendor
= Intel
Expand Down

0 comments on commit 5888808

Please sign in to comment.