Copyright | (c) Adrian Herrera 2016 |
---|---|
License | GPL-2 |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Keystone is a lightweight multi-platform, multi-architecture assembler framework.
Further information is available at http://www.keystone-engine.org.
Synopsis
- type Assembler a = ExceptT Error IO a
- data Engine
- data Architecture
- data Mode
- data OptionType
- data OptionValue
- runAssembler :: Assembler a -> IO (Either Error a)
- open :: Architecture -> [Mode] -> Assembler Engine
- option :: Engine -> OptionType -> OptionValue -> Assembler ()
- assemble :: Engine -> [String] -> Maybe Word64 -> Assembler (ByteString, Int)
- data Error
- = ErrOk
- | ErrNomem
- | ErrArch
- | ErrHandle
- | ErrMode
- | ErrVersion
- | ErrOptInvalid
- | ErrAsmExprToken
- | ErrAsmDirectiveValueRange
- | ErrAsmDirectiveId
- | ErrAsmDirectiveToken
- | ErrAsmDirectiveStr
- | ErrAsmDirectiveComma
- | ErrAsmDirectiveRelocName
- | ErrAsmDirectiveRelocToken
- | ErrAsmDirectiveFpoint
- | ErrAsmDirectiveUnknown
- | ErrAsmDirectiveEqu
- | ErrAsmDirectiveInvalid
- | ErrAsmVariantInvalid
- | ErrAsmExprBracket
- | ErrAsmSymbolModifier
- | ErrAsmSymbolRedefined
- | ErrAsmSymbolMissing
- | ErrAsmRparen
- | ErrAsmStatToken
- | ErrAsmUnsupported
- | ErrAsmMacroToken
- | ErrAsmMacroParen
- | ErrAsmMacroEqu
- | ErrAsmMacroArgs
- | ErrAsmMacroLevelsExceed
- | ErrAsmMacroStr
- | ErrAsmMacroInvalid
- | ErrAsmEscBackslash
- | ErrAsmEscOctal
- | ErrAsmEscSequence
- | ErrAsmEscStr
- | ErrAsmTokenInvalid
- | ErrAsmInsnUnsupported
- | ErrAsmFixupInvalid
- | ErrAsmLabelInvalid
- | ErrAsmFragmentInvalid
- | ErrAsmInvalidoperand
- | ErrAsmMissingfeature
- | ErrAsmMnemonicfail
- errno :: Engine -> Assembler Error
- strerror :: Error -> String
- version :: Int
Assembler control
type Assembler a = ExceptT Error IO a Source #
The assembler runs in the IO monad and allows for the handling of errors "under the hood".
data Architecture Source #
CPU architecture.
Instances
Bounded Architecture Source # | |
Defined in Heystone.Internal.Keystone | |
Enum Architecture Source # | |
Defined in Heystone.Internal.Keystone succ :: Architecture -> Architecture # pred :: Architecture -> Architecture # toEnum :: Int -> Architecture # fromEnum :: Architecture -> Int # enumFrom :: Architecture -> [Architecture] # enumFromThen :: Architecture -> Architecture -> [Architecture] # enumFromTo :: Architecture -> Architecture -> [Architecture] # enumFromThenTo :: Architecture -> Architecture -> Architecture -> [Architecture] # | |
Show Architecture Source # | |
Defined in Heystone.Internal.Keystone showsPrec :: Int -> Architecture -> ShowS # show :: Architecture -> String # showList :: [Architecture] -> ShowS # | |
Eq Architecture Source # | |
Defined in Heystone.Internal.Keystone (==) :: Architecture -> Architecture -> Bool # (/=) :: Architecture -> Architecture -> Bool # |
CPU hardware mode.
ModeLittleEndian | |
ModeArm | |
Mode16 | |
ModeMips32 | |
Mode32 | |
ModePpc32 | |
ModeSparc32 | |
ModeMips64 | |
Mode64 | |
ModePpc64 | |
ModeSparc64 | |
ModeThumb | |
ModeMicro | |
ModeQpx | |
ModeV9 | |
ModeMips3 | |
ModeV8 | |
ModeMips32r6 | |
ModeBigEndian |
data OptionType Source #
Runtime option types.
Instances
Bounded OptionType Source # | |
Defined in Heystone.Internal.Keystone minBound :: OptionType # maxBound :: OptionType # | |
Enum OptionType Source # | |
Defined in Heystone.Internal.Keystone succ :: OptionType -> OptionType # pred :: OptionType -> OptionType # toEnum :: Int -> OptionType # fromEnum :: OptionType -> Int # enumFrom :: OptionType -> [OptionType] # enumFromThen :: OptionType -> OptionType -> [OptionType] # enumFromTo :: OptionType -> OptionType -> [OptionType] # enumFromThenTo :: OptionType -> OptionType -> OptionType -> [OptionType] # | |
Show OptionType Source # | |
Defined in Heystone.Internal.Keystone showsPrec :: Int -> OptionType -> ShowS # show :: OptionType -> String # showList :: [OptionType] -> ShowS # | |
Eq OptionType Source # | |
Defined in Heystone.Internal.Keystone (==) :: OptionType -> OptionType -> Bool # (/=) :: OptionType -> OptionType -> Bool # |
data OptionValue Source #
Runtime option values.
Instances
Bounded OptionValue Source # | |
Defined in Heystone.Internal.Keystone minBound :: OptionValue # maxBound :: OptionValue # | |
Enum OptionValue Source # | |
Defined in Heystone.Internal.Keystone succ :: OptionValue -> OptionValue # pred :: OptionValue -> OptionValue # toEnum :: Int -> OptionValue # fromEnum :: OptionValue -> Int # enumFrom :: OptionValue -> [OptionValue] # enumFromThen :: OptionValue -> OptionValue -> [OptionValue] # enumFromTo :: OptionValue -> OptionValue -> [OptionValue] # enumFromThenTo :: OptionValue -> OptionValue -> OptionValue -> [OptionValue] # | |
Show OptionValue Source # | |
Defined in Heystone.Internal.Keystone showsPrec :: Int -> OptionValue -> ShowS # show :: OptionValue -> String # showList :: [OptionValue] -> ShowS # | |
Eq OptionValue Source # | |
Defined in Heystone.Internal.Keystone (==) :: OptionValue -> OptionValue -> Bool # (/=) :: OptionValue -> OptionValue -> Bool # |
:: Assembler a | The assembler code to execute |
-> IO (Either Error a) | A result on success, or an |
Run the Keystone assembler and return a result on success, or an Error
on failure.
:: Architecture | CPU architecture |
-> [Mode] | CPU hardware mode |
-> Assembler Engine | A Keystone engine on success, or an |
Create a new instance of the Keystone assembler.
:: Engine | Keystone engine handle |
-> OptionType | Type of option to set |
-> OptionValue | Option value corresponding with the type |
-> Assembler () | An |
:: Engine | Keystone engine handle |
-> [String] | List of statements to assemble. |
-> Maybe Word64 | Optional address of the first assembly instruction |
-> Assembler (ByteString, Int) | Returns the encoded input assembly
string and the number of statements
successfully processed. Returns an
|
Assemble a list of statements.
Error handling
Errors encountered by the Keystone API. These values are returned by
errno
.
Report the Error
number when some API function failed.
Return a string describing the given Error
.