Copyright | (c) Inokentiy Babushkin, 2016 |
---|---|
License | BSD3 |
Maintainer | Inokentiy Babushkin <inokentiy.babushkin@googlemail.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This module contains capstone's public API, with the necessary datatypes and functions, and some boilerplate to make it usable. Thus, it exposes an IO-based interface to capstone, which is a rough 1:1 translation of the capstone C header to Haskell. Obviously, it isn't very ideomatic to use, so a higher-level API is present in Hapstone.Capstone. The approach there is to wrap all necessary cleanup and initialization and expose an ideomatic (but heavily abstracted) interface to capstone.
This module, on the other hand, is intended to be used when performance is more critical or greater versatility is needed. This means that the abstractions introduced in the C version of the library are still present, but their use has been restricted to provide more reasonable levels of safety.
- type Csh = CSize
- data CsArch
- data CsSupport
- data CsMode
- data CsOption
- data CsOptionState
- data CsOperand
- = CsOpInvalid
- | CsOpReg
- | CsOpImm
- | CsOpMem
- | CsOpFp
- data CsGroup
- type CsSkipdataCallback = FunPtr (Ptr Word8 -> CSize -> CSize -> Ptr () -> IO CSize)
- data CsSkipdataStruct = CsSkipdataStruct String CsSkipdataCallback (Ptr ())
- csSetSkipdata :: Csh -> Maybe CsSkipdataStruct -> IO CsErr
- data ArchInfo
- data CsDetail = CsDetail {}
- peekDetail :: CsArch -> Ptr CsDetail -> IO CsDetail
- data CsInsn = CsInsn {}
- peekArch :: CsArch -> Ptr CsInsn -> IO CsInsn
- peekArrayArch :: CsArch -> Int -> Ptr CsInsn -> IO [CsInsn]
- csInsnOffset :: Ptr CsInsn -> Int -> Int
- data CsErr
- csSupport :: Enum a => a -> Bool
- csOpen :: CsArch -> [CsMode] -> IO (CsErr, Csh)
- csClose :: Csh -> IO CsErr
- csOption :: Enum a => Csh -> CsOption -> a -> IO CsErr
- csErrno :: Csh -> IO CsErr
- csStrerror :: CsErr -> String
- csDisasm :: CsArch -> Csh -> [Word8] -> Word64 -> Int -> IO [CsInsn]
- csDisasmIter :: Csh -> [Word8] -> Word64 -> IO ([Word8], Word64, Either CsErr CsInsn)
- csFree :: Ptr CsInsn -> Int -> IO ()
- csMalloc :: Csh -> IO (Ptr CsInsn)
- csRegName :: Enum e => Csh -> e -> Maybe String
- csInsnName :: Enum e => Csh -> e -> Maybe String
- csGroupName :: Enum e => Csh -> e -> Maybe String
- csInsnGroup :: Csh -> CsInsn -> Bool
- csRegRead :: Csh -> CsInsn -> Int -> Bool
- csRegWrite :: Csh -> CsInsn -> Int -> Bool
- csOpCount :: Csh -> CsInsn -> Int -> Int
- csOpIndex :: Csh -> CsInsn -> Int -> Int -> Int
Datatypes
supported architectures
support constants
working modes
options are, interestingly, represented by different types: an option
data CsOptionState Source #
... and a state of an option
arch-uniting operand type
arch-uniting instruction group type
Skipdata setup
SKIPDATA is an option supported by the capstone disassembly engine, that allows to skip data which can't be disassembled and to represent it in form of pseudo-instructions. The types and functions given here attempt to mirror capstone's setup of this option, and a more high-level interface is available in Hapstone.Capstone.
type CsSkipdataCallback = FunPtr (Ptr Word8 -> CSize -> CSize -> Ptr () -> IO CSize) Source #
callback type for user-defined SKIPDATA work
data CsSkipdataStruct Source #
user-defined SKIPDATA setup
csSetSkipdata :: Csh -> Maybe CsSkipdataStruct -> IO CsErr Source #
safely set SKIPDATA options (reset on Nothing)
Instruction representation
architecture specific information
The union holding architecture-specific info is not tagged. Thus, we have no way to determine what kind of data is stored in it without resorting to some kind of context lookup, as the corresponding C code would do. Thus, the peek implementation does not get architecture information, use peekDetail for that.
instruction information
instructions
peekArrayArch :: CsArch -> Int -> Ptr CsInsn -> IO [CsInsn] Source #
an arch-sensitive peekArray for cs_insn
Capstone API
possible error conditions
csStrerror :: CsErr -> String Source #
get the description of an error
csDisasmIter :: Csh -> [Word8] -> Word64 -> IO ([Word8], Word64, Either CsErr CsInsn) Source #
disassemble one instruction at a time
csRegRead :: Csh -> CsInsn -> Int -> Bool Source #
check whether an instruction reads from a register
csRegWrite :: Csh -> CsInsn -> Int -> Bool Source #
check whether an instruction writes to a register