Copyright | (c) 2006-20015 Martin Grabmueller and Dirk Kleeblatt |
---|---|
License | BSD3 |
Maintainer | martin@grabmueller.de |
Stability | provisional |
Portability | portable (but generated code non-portable) |
Safe Haskell | None |
Language | Haskell98 |
Monad for generating x86 machine code at runtime.
This is a combined reader-state-exception monad which handles all the details of handling code buffers, emitting binary data, relocation etc.
All the code generation functions in module Harpy.X86CodeGen live in this monad and use its error reporting facilities as well as the internal state maintained by the monad.
The library user can pass a user environment and user state through the monad. This state is independent from the internal state and may be used by higher-level code generation libraries to maintain their own state across code generation operations. --------------------------------------------------------------------------
- data CodeGen e s a
- type ErrMsg = Doc
- data RelocKind
- data Reloc
- data Label
- data FixupKind
- data CodeGenConfig = CodeGenConfig {
- codeBufferSize :: Int
- customCodeBuffer :: Maybe (Ptr Word8, Int)
- defaultCodeGenConfig :: CodeGenConfig
- failCodeGen :: Doc -> CodeGen e s a
- getEntryPoint :: CodeGen e s (Ptr Word8)
- getCodeOffset :: CodeGen e s Int
- getBasePtr :: CodeGen e s (Ptr Word8)
- getCodeBufferList :: CodeGen e s [(Ptr Word8, Int)]
- setState :: s -> CodeGen e s ()
- getState :: CodeGen e s s
- getEnv :: CodeGen e s e
- withEnv :: e -> CodeGen e s r -> CodeGen e s r
- newLabel :: CodeGen e s Label
- newNamedLabel :: String -> CodeGen e s Label
- setLabel :: CodeGen e s Label
- defineLabel :: Label -> CodeGen e s ()
- (@@) :: Label -> CodeGen e s a -> CodeGen e s a
- emitFixup :: Label -> Int -> FixupKind -> CodeGen e s ()
- labelAddress :: Label -> CodeGen e s (Ptr a)
- emitRelocInfo :: Int -> RelocKind -> FunPtr a -> CodeGen e s ()
- emit8 :: Word8 -> CodeGen e s ()
- emit8At :: Int -> Word8 -> CodeGen e s ()
- peek8At :: Int -> CodeGen e s Word8
- emit32 :: Word32 -> CodeGen e s ()
- emit32At :: Int -> Word32 -> CodeGen e s ()
- checkBufferSize :: Int -> CodeGen e s ()
- ensureBufferSize :: Int -> CodeGen e s ()
- runCodeGen :: CodeGen e s a -> e -> s -> IO (s, Either ErrMsg a)
- runCodeGenWithConfig :: CodeGen e s a -> e -> s -> CodeGenConfig -> IO (s, Either ErrMsg a)
- callDecl :: String -> Q Type -> Q [Dec]
- disassemble :: CodeGen e s [Instruction]
Types
The code generation monad, a combined reader-state-exception monad.
Kind of relocation, for example PC-relative
RelocPCRel | PC-relative relocation |
RelocAbsolute | Absolute address |
Label
Eq Label | |
Ord Label | |
Call Label | |
Js Label | |
Jo Label | |
Jns Label | |
Jno Label | |
Jnle Label | |
Jnl Label | |
Jnge Label | |
Jng Label | |
Jle Label | |
Jl Label | |
Jge Label | |
Jg Label | |
Jz Label | |
Jpo Label | |
Jpe Label | |
Jp Label | |
Jnz Label | |
Jnp Label | |
Jne Label | |
Jnc Label | |
Jnbe Label | |
Jnb Label | |
Jnae Label | |
Jna Label | |
Je Label | |
Jc Label | |
Jbe Label | |
Jb Label | |
Jae Label | |
Ja Label | |
Jmp Label | |
Loop Label | |
Push Label | |
Mov Ind Label | |
Mov Addr Label | |
Mov Reg32 Label | |
Cmp Ind Label | |
Cmp Addr Label | |
Cmp Reg32 Label | |
Mov (Disp, Reg32) Label | |
Cmp (Disp, Reg32) Label | |
Mov (Disp, Reg32, Scale) Label | |
Mov (Reg32, Reg32, Scale) Label | |
Mov (Disp, Reg32, Reg32, Scale) Label |
Kind of a fixup entry. When a label is emitted with
defineLabel
, all prior references to this label must be fixed
up. This data type tells how to perform the fixup operation.
Fixup8 | 8-bit relative reference |
Fixup16 | 16-bit relative reference |
Fixup32 | 32-bit relative reference |
Fixup32Absolute | 32-bit absolute reference |
data CodeGenConfig Source
Configuration of the code generator. There are currently two
configuration options. The first is the number fo bytes to use for
allocating code buffers (the first as well as additional buffers
created in calls to ensureBufferSize
. The second allows to pass
in a pre-allocated code buffer and its size. When this option is
used, Harpy does not perform any code buffer resizing (calls to
ensureBufferSize
will be equivalent to calls to
checkBufferSize
).
CodeGenConfig | |
|
defaultCodeGenConfig :: CodeGenConfig Source
Default code generation configuration. The code buffer size is set to 4KB, and code buffer management is automatic. This value is intended to be used with record update syntax, for example:
runCodeGenWithConfig ... defaultCodeGenConfig{codeBufferSize = 128} ...
Functions
General code generator monad operations
failCodeGen :: Doc -> CodeGen e s a Source
Abort code generation with the given error message.
Accessing code generation internals
getEntryPoint :: CodeGen e s (Ptr Word8) Source
Return a pointer to the beginning of the first code buffer, which is normally the entry point to the generated code.
getCodeOffset :: CodeGen e s Int Source
Return the current offset in the code buffer, e.g. the offset at which the next instruction will be emitted.
getBasePtr :: CodeGen e s (Ptr Word8) Source
Return the pointer to the start of the code buffer.
getCodeBufferList :: CodeGen e s [(Ptr Word8, Int)] Source
Return a list of all code buffers and their respective size (i.e., actually used space for code, not allocated size).
Access to user state and environment
withEnv :: e -> CodeGen e s r -> CodeGen e s r Source
Set the environment to the given value and execute the given code generation in this environment.
Label management
newLabel :: CodeGen e s Label Source
Generate a new label to be used with the label operations
emitFixup
and defineLabel
.
newNamedLabel :: String -> CodeGen e s Label Source
Generate a new label to be used with the label operations
emitFixup
and defineLabel
. The given name is used for
diagnostic purposes, and will appear in the disassembly.
defineLabel :: Label -> CodeGen e s () Source
Emit a label at the current offset in the code buffer. All references to the label will be relocated to this offset.
(@@) :: Label -> CodeGen e s a -> CodeGen e s a Source
This operator gives neat syntax for defining labels. When l
is a label, the code
l @@ mov eax ebx
associates the label l with the following mov
instruction.
emitFixup :: Label -> Int -> FixupKind -> CodeGen e s () Source
Emit a fixup entry for the given label at the current offset in the code buffer (unless the label is already defined). The instruction at this offset will be patched to target the address associated with this label when it is defined later.
labelAddress :: Label -> CodeGen e s (Ptr a) Source
Return the address of a label, fail if the label is not yet defined.
emitRelocInfo :: Int -> RelocKind -> FunPtr a -> CodeGen e s () Source
Emit a relocation entry for the given offset, relocation kind and target address.
Code emission
emit8At :: Int -> Word8 -> CodeGen e s () Source
Store a byte value at the given offset into the code buffer.
peek8At :: Int -> CodeGen e s Word8 Source
Return the byte value at the given offset in the code buffer.
checkBufferSize :: Int -> CodeGen e s () Source
Check whether the code buffer has room for at least the given number of bytes. This should be called by code generators whenever it cannot be guaranteed that the code buffer is large enough to hold all the generated code. Lets the code generation monad fail when the buffer overflows.
Note: Starting with version 0.4, Harpy automatically checks for buffer overflow, so you do not need to call this function anymore.
ensureBufferSize :: Int -> CodeGen e s () Source
Make sure that the code buffer has room for at least the given number of bytes. This should be called by code generators whenever it cannot be guaranteed that the code buffer is large enough to hold all the generated code. Creates a new buffer and places a jump to the new buffer when there is not sufficient space available. When code generation was invoked with a pre-defined code buffer, code generation is aborted on overflow.
Note: Starting with version 0.4, Harpy automatically checks for buffer overflow, so you do not need to call this function anymore.
Executing code generation
runCodeGen :: CodeGen e s a -> e -> s -> IO (s, Either ErrMsg a) Source
Execute code generation, given a user environment and state. The
result is a tuple of the resulting user state and either an error
message (when code generation failed) or the result of the code
generation. This function runs runCodeGenWithConfig
with a
sensible default configuration.
runCodeGenWithConfig :: CodeGen e s a -> e -> s -> CodeGenConfig -> IO (s, Either ErrMsg a) Source
Like runCodeGen
, but allows more control over the code
generation process. In addition to a code generator and a user
environment and state, a code generation configuration must be
provided. A code generation configuration allows control over the
allocation of code buffers, for example.
Calling generated functions
Interface to disassembler
disassemble :: CodeGen e s [Instruction] Source
Disassemble all code buffers. The result is a list of
disassembled instructions which can be converted to strings using
the showIntel
or showAtt
functions from module
Harpy.X86Disassembler.