harpy-0.2: Runtime code generation for x86 machine codeContentsIndex
Harpy.X86CGCombinators
Portabilityportable (but generated code non-portable)
Stabilityquite experimental
Maintainer{magr,klee}@cs.tu-berlin.de
Contents
Types
Combinators
Description

This module exports several combinators for writing loops, conditionals and function prolog/epilog code.

Note: this module is under heavy development and the exported API is definitely not yet stable.

Synopsis
data UserState = UserState {
usedRegs :: Int
}
data UserEnv = UserEnv {
bindings :: [(String, CodeGen UserEnv UserState ())]
dataDest :: DataDest
ctrlDest :: CtrlDest
}
data CtrlDest
= FallThrough
| Return
| Goto Label
| Branch CtrlDest CtrlDest
data DataDest
= RegDest Word8
| StackDest
| MemBaseDest Word8 Word32
| Ignore
ifThenElse :: CodeGen UserEnv s r -> CodeGen UserEnv s a -> CodeGen UserEnv s a1 -> CodeGen UserEnv s ()
doWhile :: CodeGen UserEnv s r -> CodeGen UserEnv s a -> CodeGen UserEnv s ()
continue :: CodeGen UserEnv s ()
continueBranch :: Int -> Bool -> CodeGen UserEnv s ()
withDataDest :: DataDest -> CodeGen UserEnv s r -> CodeGen UserEnv s r
withCtrlDest :: CtrlDest -> CodeGen UserEnv s r -> CodeGen UserEnv s r
withDest :: DataDest -> CtrlDest -> CodeGen UserEnv s r -> CodeGen UserEnv s r
function :: CodeGen UserEnv s r -> CodeGen UserEnv s r
withRegister :: (Word8 -> CodeGen e UserState t) -> CodeGen e UserState ()
Types
data UserState
User state is used to maintain bitmask of registers currently in use.
Constructors
UserState
usedRegs :: Int
data UserEnv
User environment stores code generators for accessing specific variables as well as the current data and control destinations
Constructors
UserEnv
bindings :: [(String, CodeGen UserEnv UserState ())]
dataDest :: DataDest
ctrlDest :: CtrlDest
data CtrlDest
Destination for control transfers
Constructors
FallThroughGo to next instruction
ReturnReturn from current functio
Goto LabelGo to specific label
Branch CtrlDest CtrlDestGo to one of the given labels depending on outcome of test
data DataDest
Destination for a calculated value.
Constructors
RegDest Word8Store into specific register
StackDestPush onto stack
MemBaseDest Word8 Word32Store at memory address
IgnoreThrow result away.
Combinators
ifThenElse :: CodeGen UserEnv s r -> CodeGen UserEnv s a -> CodeGen UserEnv s a1 -> CodeGen UserEnv s ()
doWhile :: CodeGen UserEnv s r -> CodeGen UserEnv s a -> CodeGen UserEnv s ()
continue :: CodeGen UserEnv s ()
continueBranch :: Int -> Bool -> CodeGen UserEnv s ()
withDataDest :: DataDest -> CodeGen UserEnv s r -> CodeGen UserEnv s r
Set the data destinations to the given values while running the code generator.
withCtrlDest :: CtrlDest -> CodeGen UserEnv s r -> CodeGen UserEnv s r
Set the control destinations to the given values while running the code generator.
withDest :: DataDest -> CtrlDest -> CodeGen UserEnv s r -> CodeGen UserEnv s r
Set the data and control destinations to the given values while running the code generator.
function :: CodeGen UserEnv s r -> CodeGen UserEnv s r
Emit the necessary function prolog and epilog code and invoke the given code generator for the code inbetween.
withRegister :: (Word8 -> CodeGen e UserState t) -> CodeGen e UserState ()
Apply the given cg to a register, which is reserved while the generator is running.
Produced by Haddock version 0.8