x86-64bit-0.4.3: Runtime code generation for x86 64 bit machine code

Safe HaskellNone
LanguageHaskell2010

CodeGen.X86

Contents

Synopsis

Byte sequences

type Bytes = [Word8] Source #

Sizes (in bits)

data Size Source #

Constructors

S8 
S16 
S32 
S64 
S128 

Instances

Eq Size Source # 

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Ord Size Source # 

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

class HasSize a where Source #

Minimal complete definition

size

Methods

size :: a -> Size Source #

class IsSize s Source #

Minimal complete definition

ssize

Instances

IsSize S8 Source # 

Methods

ssize :: SSize S8

IsSize S16 Source # 

Methods

ssize :: SSize S16

IsSize S32 Source # 

Methods

ssize :: SSize S32

IsSize S64 Source # 

Methods

ssize :: SSize S64

IsSize S128 Source # 

Methods

ssize :: SSize S128

Registers

64 bit registers

rax :: FromReg c => c S64 Source #

rcx :: FromReg c => c S64 Source #

rdx :: FromReg c => c S64 Source #

rbx :: FromReg c => c S64 Source #

rsp :: FromReg c => c S64 Source #

rbp :: FromReg c => c S64 Source #

rsi :: FromReg c => c S64 Source #

rdi :: FromReg c => c S64 Source #

r8 :: FromReg c => c S64 Source #

r9 :: FromReg c => c S64 Source #

r10 :: FromReg c => c S64 Source #

r11 :: FromReg c => c S64 Source #

r12 :: FromReg c => c S64 Source #

r13 :: FromReg c => c S64 Source #

r14 :: FromReg c => c S64 Source #

r15 :: FromReg c => c S64 Source #

32 bit registers

eax :: FromReg c => c S32 Source #

ecx :: FromReg c => c S32 Source #

edx :: FromReg c => c S32 Source #

ebx :: FromReg c => c S32 Source #

esp :: FromReg c => c S32 Source #

ebp :: FromReg c => c S32 Source #

esi :: FromReg c => c S32 Source #

edi :: FromReg c => c S32 Source #

r8d :: FromReg c => c S32 Source #

r9d :: FromReg c => c S32 Source #

r10d :: FromReg c => c S32 Source #

r11d :: FromReg c => c S32 Source #

r12d :: FromReg c => c S32 Source #

r13d :: FromReg c => c S32 Source #

r14d :: FromReg c => c S32 Source #

r15d :: FromReg c => c S32 Source #

16 bit registers

ax :: FromReg c => c S16 Source #

cx :: FromReg c => c S16 Source #

dx :: FromReg c => c S16 Source #

bx :: FromReg c => c S16 Source #

sp :: FromReg c => c S16 Source #

bp :: FromReg c => c S16 Source #

si :: FromReg c => c S16 Source #

di :: FromReg c => c S16 Source #

r8w :: FromReg c => c S16 Source #

r9w :: FromReg c => c S16 Source #

r10w :: FromReg c => c S16 Source #

r11w :: FromReg c => c S16 Source #

r12w :: FromReg c => c S16 Source #

r13w :: FromReg c => c S16 Source #

r14w :: FromReg c => c S16 Source #

r15w :: FromReg c => c S16 Source #

8 bit low registers

al :: FromReg c => c S8 Source #

cl :: FromReg c => c S8 Source #

dl :: FromReg c => c S8 Source #

bl :: FromReg c => c S8 Source #

spl :: FromReg c => c S8 Source #

bpl :: FromReg c => c S8 Source #

sil :: FromReg c => c S8 Source #

dil :: FromReg c => c S8 Source #

r8b :: FromReg c => c S8 Source #

r9b :: FromReg c => c S8 Source #

r10b :: FromReg c => c S8 Source #

r11b :: FromReg c => c S8 Source #

r12b :: FromReg c => c S8 Source #

r13b :: FromReg c => c S8 Source #

r14b :: FromReg c => c S8 Source #

r15b :: FromReg c => c S8 Source #

8 bit high registers

ah :: FromReg c => c S8 Source #

ch :: FromReg c => c S8 Source #

dh :: FromReg c => c S8 Source #

bh :: FromReg c => c S8 Source #

SSE registers

xmm0 :: FromReg c => c S128 Source #

xmm1 :: FromReg c => c S128 Source #

xmm2 :: FromReg c => c S128 Source #

xmm3 :: FromReg c => c S128 Source #

xmm4 :: FromReg c => c S128 Source #

xmm5 :: FromReg c => c S128 Source #

xmm6 :: FromReg c => c S128 Source #

xmm7 :: FromReg c => c S128 Source #

Addresses

addr :: IsSize s => Address s -> Operand rw s' Source #

addr8 :: IsSize s => Address s -> Operand rw S8 Source #

addr with specialized type

addr16 :: IsSize s => Address s -> Operand rw S16 Source #

addr with specialized type

addr32 :: IsSize s => Address s -> Operand rw S32 Source #

addr with specialized type

addr64 :: IsSize s => Address s -> Operand rw S64 Source #

addr with specialized type

ipRel :: Label -> Operand rw s Source #

intruction pointer relative address

ipRel8 :: Label -> Operand rw S8 Source #

ipRel with specialized type

Operands

data Access Source #

Operand access modes

Constructors

R

readable operand

RW

readable and writeable operand

data Operand :: Access -> Size -> * Source #

Instances

(~) Access rw R => Num (Operand rw s) Source # 

Methods

(+) :: Operand rw s -> Operand rw s -> Operand rw s #

(-) :: Operand rw s -> Operand rw s -> Operand rw s #

(*) :: Operand rw s -> Operand rw s -> Operand rw s #

negate :: Operand rw s -> Operand rw s #

abs :: Operand rw s -> Operand rw s #

signum :: Operand rw s -> Operand rw s #

fromInteger :: Integer -> Operand rw s #

IsSize s => Show (Operand a s) Source # 

Methods

showsPrec :: Int -> Operand a s -> ShowS #

show :: Operand a s -> String #

showList :: [Operand a s] -> ShowS #

IsSize s => HasSize (Operand a s) Source # 

Methods

size :: Operand a s -> Size Source #

Conditions

pattern N :: Condition -> Condition Source #

pattern O :: Condition Source #

pattern NO :: Condition Source #

pattern B :: Condition Source #

pattern C :: Condition Source #

pattern NB :: Condition Source #

pattern NC :: Condition Source #

pattern E :: Condition Source #

pattern Z :: Condition Source #

pattern NE :: Condition Source #

pattern NZ :: Condition Source #

pattern NA :: Condition Source #

pattern BE :: Condition Source #

pattern A :: Condition Source #

pattern NBE :: Condition Source #

pattern S :: Condition Source #

pattern NS :: Condition Source #

pattern P :: Condition Source #

pattern NP :: Condition Source #

pattern L :: Condition Source #

pattern NL :: Condition Source #

pattern NG :: Condition Source #

pattern LE :: Condition Source #

pattern G :: Condition Source #

pattern NLE :: Condition Source #

Instructions

type Code = CodeM () Source #

data CodeM a Source #

Instances

Monad CodeM Source # 

Methods

(>>=) :: CodeM a -> (a -> CodeM b) -> CodeM b #

(>>) :: CodeM a -> CodeM b -> CodeM b #

return :: a -> CodeM a #

fail :: String -> CodeM a #

Functor CodeM Source # 

Methods

fmap :: (a -> b) -> CodeM a -> CodeM b #

(<$) :: a -> CodeM b -> CodeM a #

Show Code Source # 

Methods

showsPrec :: Int -> Code -> ShowS #

show :: Code -> String #

showList :: [Code] -> ShowS #

MonadFix CodeM Source # 

Methods

mfix :: (a -> CodeM a) -> CodeM a #

Applicative CodeM Source # 

Methods

pure :: a -> CodeM a #

(<*>) :: CodeM (a -> b) -> CodeM a -> CodeM b #

(*>) :: CodeM a -> CodeM b -> CodeM b #

(<*) :: CodeM a -> CodeM b -> CodeM a #

Pseudo instructions

data Label Source #

Instances

Control

Flags

cmp :: IsSize s => Operand RW s -> Operand r s -> Code Source #

test :: IsSize s => Operand RW s -> Operand r s -> Code Source #

Arithmetic

add :: IsSize s => Operand RW s -> Operand r s -> Code Source #

adc :: IsSize s => Operand RW s -> Operand r s -> Code Source #

sub :: IsSize s => Operand RW s -> Operand r s -> Code Source #

sbb :: IsSize s => Operand RW s -> Operand r s -> Code Source #

and_ :: IsSize s => Operand RW s -> Operand r s -> Code Source #

or_ :: IsSize s => Operand RW s -> Operand r s -> Code Source #

xor_ :: IsSize s => Operand RW s -> Operand r s -> Code Source #

rol :: IsSize s => Operand RW s -> Operand r S8 -> Code Source #

ror :: IsSize s => Operand RW s -> Operand r S8 -> Code Source #

rcl :: IsSize s => Operand RW s -> Operand r S8 -> Code Source #

rcr :: IsSize s => Operand RW s -> Operand r S8 -> Code Source #

shl :: IsSize s => Operand RW s -> Operand r S8 -> Code Source #

shr :: IsSize s => Operand RW s -> Operand r S8 -> Code Source #

sar :: IsSize s => Operand RW s -> Operand r S8 -> Code Source #

lea :: (IsSize s', IsSize s) => Operand RW s -> Operand RW s' -> Code Source #

Other

xchg :: IsSize s => Operand RW s -> Operand RW s -> Code Source #

mov :: IsSize s => Operand RW s -> Operand r s -> Code Source #

SSE

movd :: (IsSize s', IsSize s) => Operand RW s -> Operand r s' -> Code Source #

movq :: (IsSize s', IsSize s) => Operand RW s -> Operand r s' -> Code Source #

Compound instructions

unless :: Condition -> CodeM a -> CodeM () Source #

execute code unless condition is true

doWhile :: Condition -> CodeM a -> CodeM () Source #

do while loop construction

if_ :: Condition -> CodeM a -> CodeM a1 -> CodeM () Source #

if-then-else

leaData :: (HasBytes a, IsSize s) => Operand RW s -> a -> CodeM () Source #

Compilation

Calling convention

saveNonVolatile :: Code -> Code Source #

Save the non-volatile registers, execute the code, restore the registers and return after.

Note: R12..R15 should be preserved on both Windows and Linux (or System V convention in general). This is the responsability of the user (this function won't save them, but you can use "saveR12R15" in addition to this).

saveR12R15 :: Code -> Code Source #

Saves R12, R13, R14 and R15 (on the stack).

arg1 :: FromReg c => c S64 Source #

arg2 :: FromReg c => c S64 Source #

arg3 :: FromReg c => c S64 Source #

arg4 :: FromReg c => c S64 Source #

result :: FromReg c => c S64 Source #

Calling C and Haskell from Assembly

class (MapResult a, NFData (Result a)) => Callable a where Source #

Minimal complete definition

dynCCall

Methods

dynCCall :: FunPtr a -> a Source #

class MapResult a => CallableHs a where Source #

Minimal complete definition

createHsPtr

Methods

createHsPtr :: a -> IO (FunPtr a) Source #

hsPtr :: CallableHs a => a -> FunPtr a Source #

newtype CString Source #

Constructors

CString String 

Instances

Misc

runTests :: IO () Source #

Run all tests