Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Bytes = [Word8]
- class HasBytes a where
- data Size
- class HasSize a where
- class IsSize (s :: Size)
- data EqT s s' where
- sizeEqCheck :: forall s s' f g. (IsSize s, IsSize s') => f s -> g s' -> Maybe (EqT s s')
- data Reg :: Size -> * where
- class FromReg c where
- rax :: FromReg c => c S64
- rcx :: FromReg c => c S64
- rdx :: FromReg c => c S64
- rbx :: FromReg c => c S64
- rsp :: FromReg c => c S64
- rbp :: FromReg c => c S64
- rsi :: FromReg c => c S64
- rdi :: FromReg c => c S64
- r8 :: FromReg c => c S64
- r9 :: FromReg c => c S64
- r10 :: FromReg c => c S64
- r11 :: FromReg c => c S64
- r12 :: FromReg c => c S64
- r13 :: FromReg c => c S64
- r14 :: FromReg c => c S64
- r15 :: FromReg c => c S64
- eax :: FromReg c => c S32
- ecx :: FromReg c => c S32
- edx :: FromReg c => c S32
- ebx :: FromReg c => c S32
- esp :: FromReg c => c S32
- ebp :: FromReg c => c S32
- esi :: FromReg c => c S32
- edi :: FromReg c => c S32
- r8d :: FromReg c => c S32
- r9d :: FromReg c => c S32
- r10d :: FromReg c => c S32
- r11d :: FromReg c => c S32
- r12d :: FromReg c => c S32
- r13d :: FromReg c => c S32
- r14d :: FromReg c => c S32
- r15d :: FromReg c => c S32
- ax :: FromReg c => c S16
- cx :: FromReg c => c S16
- dx :: FromReg c => c S16
- bx :: FromReg c => c S16
- sp :: FromReg c => c S16
- bp :: FromReg c => c S16
- si :: FromReg c => c S16
- di :: FromReg c => c S16
- r8w :: FromReg c => c S16
- r9w :: FromReg c => c S16
- r10w :: FromReg c => c S16
- r11w :: FromReg c => c S16
- r12w :: FromReg c => c S16
- r13w :: FromReg c => c S16
- r14w :: FromReg c => c S16
- r15w :: FromReg c => c S16
- al :: FromReg c => c S8
- cl :: FromReg c => c S8
- dl :: FromReg c => c S8
- bl :: FromReg c => c S8
- spl :: FromReg c => c S8
- bpl :: FromReg c => c S8
- sil :: FromReg c => c S8
- dil :: FromReg c => c S8
- r8b :: FromReg c => c S8
- r9b :: FromReg c => c S8
- r10b :: FromReg c => c S8
- r11b :: FromReg c => c S8
- r12b :: FromReg c => c S8
- r13b :: FromReg c => c S8
- r14b :: FromReg c => c S8
- r15b :: FromReg c => c S8
- ah :: FromReg c => c S8
- ch :: FromReg c => c S8
- dh :: FromReg c => c S8
- bh :: FromReg c => c S8
- xmm0 :: FromReg c => c S128
- xmm1 :: FromReg c => c S128
- xmm2 :: FromReg c => c S128
- xmm3 :: FromReg c => c S128
- xmm4 :: FromReg c => c S128
- xmm5 :: FromReg c => c S128
- xmm6 :: FromReg c => c S128
- xmm7 :: FromReg c => c S128
- data Addr s = Addr {
- baseReg :: BaseReg s
- displacement :: Displacement
- indexReg :: IndexReg s
- type BaseReg s = Maybe (Reg s)
- data IndexReg s
- data Scale
- s1 :: Scale
- s2 :: Scale
- s4 :: Scale
- s8 :: Scale
- type Displacement = Maybe Int32
- data Address :: Size -> *
- addr :: IsSize s => Address s -> Operand rw s'
- addr8 :: IsSize s => Address s -> Operand rw S8
- addr16 :: IsSize s => Address s -> Operand rw S16
- addr32 :: IsSize s => Address s -> Operand rw S32
- addr64 :: IsSize s => Address s -> Operand rw S64
- ipRel :: Label -> Operand rw s
- ipRel8 :: Label -> Operand rw S8
- data Access
- data Operand :: Access -> Size -> * where
- resizeOperand :: IsSize s' => Operand RW s -> Operand RW s'
- ipRelValue :: Label -> Operand R s
- data Condition
- pattern N :: Condition -> Condition
- pattern O :: Condition
- pattern NO :: Condition
- pattern B :: Condition
- pattern C :: Condition
- pattern NB :: Condition
- pattern NC :: Condition
- pattern E :: Condition
- pattern Z :: Condition
- pattern NE :: Condition
- pattern NZ :: Condition
- pattern NA :: Condition
- pattern BE :: Condition
- pattern A :: Condition
- pattern NBE :: Condition
- pattern S :: Condition
- pattern NS :: Condition
- pattern P :: Condition
- pattern NP :: Condition
- pattern L :: Condition
- pattern NL :: Condition
- pattern NG :: Condition
- pattern LE :: Condition
- pattern G :: Condition
- pattern NLE :: Condition
- type Code = CodeM ()
- data CodeM a
- db :: Bytes -> Code
- align :: Int -> Code
- data Label
- label :: CodeM Label
- j :: Condition -> Label -> Code
- jmp :: Label -> Code
- jmpq :: Operand r S64 -> Code
- call :: Operand r S64 -> Code
- ret :: Code
- nop :: Code
- cmc :: Code
- clc :: Code
- stc :: Code
- cli :: Code
- sti :: Code
- cld :: Code
- std :: Code
- pushf :: Code
- popf :: Code
- cmp :: IsSize s => Operand RW s -> Operand r s -> Code
- test :: IsSize s => Operand RW s -> Operand r s -> Code
- bt :: IsSize s => Operand r s -> Operand RW s -> Code
- bsf :: IsSize s => Operand RW s -> Operand r s -> Code
- bsr :: IsSize s => Operand RW s -> Operand r s -> Code
- inc :: IsSize s => Operand RW s -> Code
- dec :: IsSize s => Operand RW s -> Code
- neg :: IsSize s => Operand RW s -> Code
- add :: IsSize s => Operand RW s -> Operand r s -> Code
- adc :: IsSize s => Operand RW s -> Operand r s -> Code
- sub :: IsSize s => Operand RW s -> Operand r s -> Code
- sbb :: IsSize s => Operand RW s -> Operand r s -> Code
- lea :: (IsSize s, IsSize s') => Operand RW s -> Operand RW s' -> Code
- not_ :: IsSize s => Operand RW s -> Code
- and_ :: IsSize s => Operand RW s -> Operand r s -> Code
- or_ :: IsSize s => Operand RW s -> Operand r s -> Code
- xor_ :: IsSize s => Operand RW s -> Operand r s -> Code
- rol :: IsSize s => Operand RW s -> Operand r S8 -> Code
- ror :: IsSize s => Operand RW s -> Operand r S8 -> Code
- rcl :: IsSize s => Operand RW s -> Operand r S8 -> Code
- rcr :: IsSize s => Operand RW s -> Operand r S8 -> Code
- shl :: IsSize s => Operand RW s -> Operand r S8 -> Code
- shr :: IsSize s => Operand RW s -> Operand r S8 -> Code
- sar :: IsSize s => Operand RW s -> Operand r S8 -> Code
- bswap :: IsSize s => Operand RW s -> Code
- xchg :: IsSize s => Operand RW s -> Operand RW s -> Code
- mov :: IsSize s => Operand RW s -> Operand r s -> Code
- cmov :: IsSize s => Condition -> Operand RW s -> Operand RW s -> Code
- pop :: Operand RW S64 -> Code
- push :: Operand r S64 -> Code
- movd :: (IsSize s, IsSize s') => Operand RW s -> Operand r s' -> Code
- movq :: (IsSize s, IsSize s') => Operand RW s -> Operand r s' -> Code
- movdqa :: Operand RW S128 -> Operand r S128 -> Code
- paddb :: Operand RW S128 -> Operand r S128 -> Code
- paddw :: Operand RW S128 -> Operand r S128 -> Code
- paddd :: Operand RW S128 -> Operand r S128 -> Code
- paddq :: Operand RW S128 -> Operand r S128 -> Code
- psubb :: Operand RW S128 -> Operand r S128 -> Code
- psubw :: Operand RW S128 -> Operand r S128 -> Code
- psubd :: Operand RW S128 -> Operand r S128 -> Code
- psubq :: Operand RW S128 -> Operand r S128 -> Code
- pxor :: Operand RW S128 -> Operand r S128 -> Code
- psllw :: Operand RW S128 -> Operand r S8 -> Code
- pslld :: Operand RW S128 -> Operand r S8 -> Code
- psllq :: Operand RW S128 -> Operand r S8 -> Code
- pslldq :: Operand RW S128 -> Operand r S8 -> Code
- psrlw :: Operand RW S128 -> Operand r S8 -> Code
- psrld :: Operand RW S128 -> Operand r S8 -> Code
- psrlq :: Operand RW S128 -> Operand r S8 -> Code
- psrldq :: Operand RW S128 -> Operand r S8 -> Code
- psraw :: Operand RW S128 -> Operand r S8 -> Code
- psrad :: Operand RW S128 -> Operand r S8 -> Code
- unless :: Condition -> CodeM a -> CodeM ()
- doWhile :: Condition -> CodeM a -> CodeM ()
- if_ :: Condition -> CodeM a1 -> CodeM a2 -> CodeM ()
- leaData :: (IsSize s, HasBytes a) => Operand RW s -> a -> CodeM ()
- traceReg :: IsSize s => String -> Operand RW s -> Code
- compile :: Callable a => Code -> a
- preBuild :: Code -> Code
- saveNonVolatile :: Code -> Code
- saveR12R15 :: Code -> Code
- arg1 :: FromReg c => c S64
- arg2 :: FromReg c => c S64
- arg3 :: FromReg c => c S64
- arg4 :: FromReg c => c S64
- result :: FromReg c => c S64
- class (MapResult a, NFData (Result a)) => Callable a where
- class MapResult a => CallableHs a where
- createHsPtr :: a -> IO (FunPtr a)
- callFun :: Operand RW S64 -> FunPtr a -> Code
- printf :: FunPtr a
- hsPtr :: CallableHs a => a -> FunPtr a
- newtype CString = CString String
Byte sequences
Sizes (in bits)
class HasSize a where Source #
Instances
HasSize Int8 Source # | |
HasSize Int16 Source # | |
HasSize Int32 Source # | |
HasSize Int64 Source # | |
HasSize Word8 Source # | |
HasSize Word16 Source # | |
HasSize Word32 Source # | |
HasSize Word64 Source # | |
IsSize s => HasSize (Address s) Source # | |
IsSize s => HasSize (IndexReg s) Source # | |
IsSize s => HasSize (BaseReg s) Source # | |
IsSize s => HasSize (Addr s) Source # | |
IsSize s => HasSize (Reg s) Source # | |
IsSize s => HasSize (Operand a s) Source # | |
class IsSize (s :: Size) Source #
ssize
Instances
IsSize S1 Source # | |
Defined in CodeGen.X86.Asm | |
IsSize S8 Source # | |
Defined in CodeGen.X86.Asm | |
IsSize S16 Source # | |
Defined in CodeGen.X86.Asm | |
IsSize S32 Source # | |
Defined in CodeGen.X86.Asm | |
IsSize S64 Source # | |
Defined in CodeGen.X86.Asm | |
IsSize S128 Source # | |
Defined in CodeGen.X86.Asm |
Registers
data Reg :: Size -> * where Source #
A register.
64 bit registers
32 bit registers
16 bit registers
8 bit low registers
8 bit high registers
SSE registers
Addresses
A (relative) address is made up base a base register, a displacement, and a (scaled) index.
For example in [eax+4*ecx+20]
the base register is eax
, the displacement is 20
and the
index is 4*ecx
.
Addr | |
|
The scaling of an index. (replace with Size?)
type Displacement = Maybe Int32 Source #
Operands
data Operand :: Access -> Size -> * where Source #
An operand can be an immediate, a register, a memory address or RIP-relative (memory address relative to the instruction pointer)
ImmOp :: Immediate Int64 -> Operand R s | |
RegOp :: Reg s -> Operand rw s | |
MemOp :: IsSize s' => Addr s' -> Operand rw s | |
IPMemOp :: Immediate Int32 -> Operand rw s |
Instances
FromReg (Operand r) Source # | |
rw ~ R => Num (Operand rw s) Source # | |
Defined in CodeGen.X86.Asm (+) :: 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 # | |
IsSize s => HasSize (Operand a s) Source # | |
Conditions
Instructions
Pseudo instructions
Control instructions
Flag manipulation
Conditionals
Arithmetic
Bit manipulation
Byte manipulation/move
SSE
Compound instructions
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).
Calling C and Haskell from Assembly
class MapResult a => CallableHs a where Source #
createHsPtr :: a -> IO (FunPtr a) Source #
hsPtr :: CallableHs a => a -> FunPtr a Source #