hapstone-0.1.0.0: Capstone bindings for Haskell

Copyright(c) Inokentiy Babushkin, 2016
LicenseBSD3
MaintainerInokentiy Babushkin <inokentiy.babushkin@googlemail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Hapstone.Internal.Capstone

Contents

Description

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.

Synopsis

Datatypes

type Csh = CSize Source

capstone's weird^M^M^M^M^Mopaque handle type

data CsOption Source

options are, interestingly, represented by different types: an option

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

csSetSkipdata :: Csh -> Maybe CsSkipdataStruct -> IO CsErr Source

safely set SKIPDATA options (reset on Nothing)

Instruction representation

data ArchInfo Source

architecture specific information

Constructors

X86 CsX86

x86 architecture

Arm64 CsArm64

ARM64 architecture

Arm CsArm

ARM architecture

Mips CsMips

MIPS architecture

Ppc CsPpc

PPC architecture

Sparc CsSparc

SPARC architecture

SysZ CsSysZ

SystemZ architecture

XCore CsXCore

XCore architecture

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.

data CsDetail Source

instruction information

Constructors

CsDetail 

Fields

regsRead :: [Word8]

registers read by this instruction

regsWrite :: [Word8]

registers written by this instruction

groups :: [Word8]

instruction groups this instruction belongs to

archInfo :: Maybe ArchInfo

(optional) architecture-specific info

peekDetail :: CsArch -> Ptr CsDetail -> IO CsDetail Source

an arch-sensitive peek for cs_detail

data CsInsn Source

instructions

Constructors

CsInsn 

Fields

insnId :: Word32

instruction ID

address :: Word64

instruction's address in memory

bytes :: [Word8]

raw byte representation

mnemonic :: String

instruction's mnemonic

opStr :: String

operands

detail :: Maybe CsDetail

(optional) detailed info

peekArch :: CsArch -> Ptr CsInsn -> IO CsInsn Source

an arch-sensitive peek for cs_insn

peekArrayArch :: CsArch -> Int -> Ptr CsInsn -> IO [CsInsn] Source

an arch-sensitive peekArray for cs_insn

Capstone API

csInsnOffset :: Ptr CsInsn -> Int -> Int Source

our own port of the CS_INSN_OFFSET macro

csSupport :: Enum a => a -> Bool Source

get information on supported features

csOpen :: CsArch -> [CsMode] -> IO (CsErr, Csh) Source

open a new disassembly handle

csOption :: Enum a => Csh -> CsOption -> a -> IO CsErr Source

set an option on a handle

csErrno :: Csh -> IO CsErr Source

get the last error from a handle

csStrerror :: CsErr -> String Source

get the description of an error

csDisasm :: CsArch -> Csh -> [Word8] -> Word64 -> Int -> IO [CsInsn] Source

disassemble a buffer

csDisasmIter :: Csh -> [Word8] -> Word64 -> IO ([Word8], Word64, Either CsErr CsInsn) Source

disassemble one instruction at a time

csFree :: Ptr CsInsn -> Int -> IO () Source

free an instruction struct array

csMalloc :: Csh -> IO (Ptr CsInsn) Source

allocate space for an instruction structure

csInsnGroup :: Csh -> CsInsn -> Bool Source

check whether an instruction is member of a group

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

csOpCount :: Csh -> CsInsn -> Int -> Int Source

return the number of operands of given type an instruction has

csOpIndex :: Csh -> CsInsn -> Int -> Int -> Int Source

return the position of the first operand of given type an instruction has, given an inclusive search range