harpy-0.2: Runtime code generation for x86 machine codeContentsIndex
Harpy.CodeGenMonad
Portabilityportable (but generated code non-portable)
Stabilityprovisional
Maintainer{magr,klee}@cs.tu-berlin.de
Contents
Types
Functions
General code generator monad operations
Accessing code generation internals
Access to user state and environment
Label management
Code emission
Executing code generation
Calling generated functions
Interface to disassembler
Description

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 user 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.

Synopsis
data CodeGen e s a
data RelocKind
= RelocPCRel
| RelocAbsolute
type ErrMsg = Doc
data Reloc
data Label
data FixupKind
= Fixup8
| Fixup16
| Fixup32
| Fixup32Absolute
data CodeGenConfig = CodeGenConfig {
codeBufferSize :: 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
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
data CodeGen e s a
The code generation monad, a combined reader-state-exception monad.
show/hide Instances
data RelocKind
Kind of relocation, for example PC-relative
Constructors
RelocPCRelPC-relative relocation
RelocAbsoluteAbsolute address
show/hide Instances
type ErrMsg = Doc
An error message produced by a code generation operation.
data Reloc
Relocation entry
show/hide Instances
data Label
Label
show/hide Instances
data FixupKind
Constructors
Fixup8
Fixup16
Fixup32
Fixup32Absolute
show/hide Instances
data CodeGenConfig
Configuration of the code generator.
Constructors
CodeGenConfig
codeBufferSize :: IntSize of individual code buffer blocks.
defaultCodeGenConfig :: CodeGenConfig
Functions
General code generator monad operations
failCodeGen :: Doc -> CodeGen e s a
Abort code generation with the given error message.
Accessing code generation internals
getEntryPoint :: CodeGen e s (Ptr Word8)
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
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)
Return the pointer to the start of the code buffer. {--}
getCodeBufferList :: CodeGen e s [(Ptr Word8, Int)]
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
setState :: s -> CodeGen e s ()
Set the user state to the given value.
getState :: CodeGen e s s
Return the current user state.
getEnv :: CodeGen e s e
Return the current user environment.
withEnv :: e -> CodeGen e s r -> CodeGen e s r
Set the environment to the given value and execute the given code generation in this environment.
Label management
newLabel :: CodeGen e s Label
Generate a new label to be used with the label operations emitRelocInfo, emitFixup and defineLabel.
setLabel :: CodeGen e s Label
Generate a new label and define it at once
defineLabel :: Label -> CodeGen e s ()
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
emitFixup :: Label -> Int -> FixupKind -> CodeGen e s ()
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)
Return the address of a label, fail if the label is not yet defined.
emitRelocInfo :: Int -> RelocKind -> FunPtr a -> CodeGen e s ()
Emit a relocation entry for the given offset, relocation kind and target address.
Code emission
emit8 :: Word8 -> CodeGen e s ()
Emit a byte value to the code buffer. {--}
emit8At :: Int -> Word8 -> CodeGen e s ()
Store a byte value at the given offset into the code buffer. {--}
peek8At :: Int -> CodeGen e s Word8
Return the byte value at the given offset in the code buffer. {--}
emit32 :: Word32 -> CodeGen e s ()
Like emit8, but for a 32-bit value. {--}
emit32At :: Int -> Word32 -> CodeGen e s ()
Like emit8At, but for a 32-bit value. {--}
checkBufferSize :: Int -> CodeGen e s ()
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.
ensureBufferSize :: Int -> CodeGen e s ()
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
Executing code generation
runCodeGen :: CodeGen e s a -> e -> s -> IO (s, Either ErrMsg a)
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.
runCodeGenWithConfig :: CodeGen e s a -> e -> s -> CodeGenConfig -> IO (s, Either ErrMsg a)
Calling generated functions
callDecl :: String -> Q Type -> Q [Dec]
Declare a stub function to call the code buffer. Arguments are the name of the generated function, and the type the code buffer is supposed to have. The type argument can be given using the [t| ... |] notation of Template Haskell. Allowed types are the legal types for FFI functions.
Interface to disassembler
disassemble :: CodeGen e s [Instruction]
Disassemble all code buffers.
Produced by Haddock version 0.8