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

Safe HaskellNone
LanguageHaskell2010

CodeGen.X86

Contents

Synopsis

Byte sequences

newtype Bytes Source #

Constructors

Bytes 

Fields

Instances

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

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 #

Memory references

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

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

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

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

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

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 #

Conditions

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 #

Assembly codes

data Code where Source #

Constructors

Scope :: Code -> Code 
Up :: Code -> Code 

Instances

pattern Ret :: Code Source #

pattern Nop :: Code Source #

pattern PushF :: Code Source #

pattern PopF :: Code Source #

pattern Cmc :: Code Source #

pattern Clc :: Code Source #

pattern Stc :: Code Source #

pattern Cli :: Code Source #

pattern Sti :: Code Source #

pattern Cld :: Code Source #

pattern Std :: Code Source #

pattern Inc :: () => forall s. IsSize s => Operand RW s -> Code Source #

pattern Dec :: () => forall s. IsSize s => Operand RW s -> Code Source #

pattern Not :: () => forall s. IsSize s => Operand RW s -> Code Source #

pattern Neg :: () => forall s. IsSize s => Operand RW s -> Code Source #

pattern Add :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Or :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Adc :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Sbb :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern And :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Sub :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Xor :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Cmp :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Test :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Mov :: () => forall s r. IsSize s => Operand RW s -> Operand r s -> Code Source #

pattern Cmov :: () => forall s. IsSize s => Condition -> Operand RW s -> Operand RW s -> Code Source #

pattern Rol :: () => forall s r. IsSize s => Operand RW s -> Operand r S8 -> Code Source #

pattern Ror :: () => forall s r. IsSize s => Operand RW s -> Operand r S8 -> Code Source #

pattern Rcl :: () => forall s r. IsSize s => Operand RW s -> Operand r S8 -> Code Source #

pattern Rcr :: () => forall s r. IsSize s => Operand RW s -> Operand r S8 -> Code Source #

pattern Shl :: () => forall s r. IsSize s => Operand RW s -> Operand r S8 -> Code Source #

pattern Shr :: () => forall s r. IsSize s => Operand RW s -> Operand r S8 -> Code Source #

pattern Sar :: () => forall s r. IsSize s => Operand RW s -> Operand r S8 -> Code Source #

pattern Xchg :: () => forall s. IsSize s => Operand RW s -> Operand RW s -> Code Source #

pattern Movd :: () => forall s s' r. (IsSize s, IsSize s') => Operand RW s -> Operand r s' -> Code Source #

pattern Movq :: () => forall s s' r. (IsSize s, IsSize s') => Operand RW s -> Operand r s' -> Code Source #

pattern Movdqa :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Paddb :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Paddw :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Paddd :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Paddq :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Psubb :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Psubw :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Psubd :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Psubq :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Pxor :: () => forall r. Operand RW S128 -> Operand r S128 -> Code Source #

pattern Psllw :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Pslld :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Psllq :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Pslldq :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Psrlw :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Psrld :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Psrlq :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Psrldq :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Psraw :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Psrad :: () => forall r. Operand RW S128 -> Operand r S8 -> Code Source #

pattern Lea :: () => forall s s'. (IsSize s, IsSize s') => Operand RW s -> Operand RW s' -> Code Source #

pattern J :: Condition -> Maybe Size -> Code Source #

pattern Pop :: Operand RW S64 -> Code Source #

pattern Push :: () => forall r. Operand r S64 -> Code Source #

pattern Call :: Operand RW S64 -> Code Source #

pattern Jmpq :: Operand RW S64 -> Code Source #

pattern Jmp :: Maybe Size -> Code Source #

pattern Data :: Bytes -> Code Source #

pattern Align :: Int -> Code Source #

pattern Label :: Code Source #

Compound assembly codes

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0

(<.>) :: Code -> Code -> Code infixr 5 Source #

(<:>) :: Code -> Code -> Code infixr 5 Source #

jmp :: Code -> Code Source #

auto size jump; the extra argument is the code between the jump and the label

jmp_back :: Code Source #

auto size backward jump

jmp8 :: Code Source #

short jump

jmp32 :: Code Source #

near jump

j :: Condition -> Code -> Code Source #

auto size conditional forward jump

j8 :: Condition -> Code -> Code Source #

short conditional forward jump

j32 :: Condition -> Code -> Code Source #

near conditional forward jump

j_back :: Code -> Condition -> Code Source #

auto size conditional backward jump

j_back8 :: Code -> Condition -> Code Source #

short conditional backward jump

j_back32 :: Code -> Condition -> Code Source #

near conditional backward jump

leaData :: (HasBytes t, IsSize s) => Operand RW s -> t -> Code Source #

Compilation

class Callable a Source #

Minimal complete definition

unsafeCallForeignPtr

Instances

Callable Bool Source # 
Callable Int Source # 
Callable Int8 Source # 
Callable Int16 Source # 
Callable Int32 Source # 
Callable Int64 Source # 
Callable Word Source # 
Callable Word8 Source # 
Callable Word16 Source # 
Callable Word32 Source # 
Callable Word64 Source # 
Callable (IO ()) Source # 

Methods

unsafeCallForeignPtr :: ForeignPtr (IO ()) -> IO ()

Callable (Word64 -> Word64) Source # 
Callable (Ptr a -> Int) Source # 

Methods

unsafeCallForeignPtr :: ForeignPtr (Ptr a -> Int) -> Ptr a -> Int

Callable (Ptr a -> Int64) Source # 
Callable (Ptr a -> Word) Source # 

Methods

unsafeCallForeignPtr :: ForeignPtr (Ptr a -> Word) -> Ptr a -> Word

Callable (Ptr a -> Word64) Source # 

Calling C and Haskell from Assembly

saveNonVolatile :: Code -> Code Source #

Save the non-volatile registers

Note: R12..R15 should be preserved on both Windows and Linux. This is the responsability of the user (this won't save them).

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 #

class CallableHs a Source #

Minimal complete definition

createHsPtr

Instances

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

Misc

runTests :: IO () Source #

Run all tests

newtype CString Source #

Constructors

CString String 

Instances