| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
CodeGen.X86.Asm
Synopsis
- everyNth :: Int -> [a] -> [[a]]
- showNibble :: (Integral a, Bits a) => Int -> a -> Char
- showByte :: (Integral a, Bits a) => a -> [Char]
- showHex' :: (Integral a, Show a) => a -> [Char]
- pattern Integral :: (Integral a, Integral b, Bits a, Bits b) => b -> a
- type Bytes = [Word8]
- class HasBytes a where
- data Size
- mkSize :: (Eq a, Num a) => a -> Size
- sizeLen :: Num a => Size -> a
- class HasSize a where
- data SSize (s :: Size) where
- class IsSize (s :: Size) where
- data EqT s s' where
- sizeEqCheck :: forall s s' f g. (IsSize s, IsSize s') => f s -> g s' -> Maybe (EqT s s')
- newtype Scale = Scale Word8
- s1 :: Scale
- s2 :: Scale
- s4 :: Scale
- s8 :: Scale
- toScale :: (Eq a, Num a) => a -> Scale
- scaleFactor :: Num a => Scale -> a
- data Operand :: Access -> Size -> * where
- 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
- data Immediate a- = Immediate a
- | LabelRelValue Size Label
 
- newtype Label = Label {}
- data Access
- data Reg :: Size -> * where
- data Addr s = Addr {- baseReg :: BaseReg s
- displacement :: Displacement
- indexReg :: IndexReg s
 
- type BaseReg s = Maybe (Reg s)
- data IndexReg s
- type Displacement = Maybe Int32
- pattern NoDisp :: Maybe a
- pattern Disp :: a -> Maybe a
- ipRel :: Label -> Operand rw s
- ipRelValue :: forall {s :: Size}. Label -> Operand 'R s
- ipRel8 :: Label -> Operand rw S8
- base :: Reg s -> Addr s
- index :: Scale -> Reg s -> Addr s
- index' :: Int -> Reg s -> Addr s
- index1 :: forall {s :: Size}. Reg s -> Addr s
- index2 :: forall {s :: Size}. Reg s -> Addr s
- index4 :: forall {s :: Size}. Reg s -> Addr s
- index8 :: forall {s :: Size}. Reg s -> Addr s
- disp :: (Bits a, Integral a) => a -> Addr s
- data Address :: Size -> * where
- scaleAddress :: (Int -> Int) -> Address s -> Address s
- makeAddr :: Address s -> Addr s
- class FromReg c where
- reg :: forall {c} {s :: Size}. FromReg c => Word8 -> c s
- 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
- pattern RegA :: Operand a b
- pattern RegCl :: Operand r S8
- resizeOperand :: IsSize s' => Operand RW s -> Operand RW s'
- resizeRegCode :: Reg s -> Reg s'
- pattern MemLike :: Operand a b
- isMemOp :: forall {a :: Access} {b :: Size}. Operand a b -> Bool
- newtype Condition = Condition Word8
- 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
- pattern N :: Condition -> Condition
- notCond :: Condition -> Condition
- data CodeLine where- Ret_, Nop_, PushF_, PopF_, Cmc_, Clc_, Stc_, Cli_, Sti_, Cld_, Std_ :: CodeLine
- Inc_, Dec_, Not_, Neg_, Bswap :: IsSize s => Operand RW s -> CodeLine
- Add_, Or_, Adc_, Sbb_, And_, Sub_, Xor_, Cmp_, Test_, Mov_, Bsf, Bsr :: IsSize s => Operand RW s -> Operand r s -> CodeLine
- Rol_, Ror_, Rcl_, Rcr_, Shl_, Shr_, Sar_ :: IsSize s => Operand RW s -> Operand r S8 -> CodeLine
- Bt :: IsSize s => Operand r s -> Operand RW s -> CodeLine
- Movdqa_, Paddb_, Paddw_, Paddd_, Paddq_, Psubb_, Psubw_, Psubd_, Psubq_, Pxor_ :: Operand RW S128 -> Operand r S128 -> CodeLine
- Psllw_, Pslld_, Psllq_, Pslldq_, Psrlw_, Psrld_, Psrlq_, Psrldq_, Psraw_, Psrad_ :: Operand RW S128 -> Operand r S8 -> CodeLine
- Movd_, Movq_ :: (IsSize s, IsSize s') => Operand RW s -> Operand r s' -> CodeLine
- Cmov_ :: IsSize s => Condition -> Operand RW s -> Operand RW s -> CodeLine
- Xchg_ :: IsSize s => Operand RW s -> Operand RW s -> CodeLine
- Lea_ :: (IsSize s, IsSize s') => Operand RW s -> Operand RW s' -> CodeLine
- Pop_ :: Operand RW S64 -> CodeLine
- Push_ :: Operand r S64 -> CodeLine
- Call_ :: Operand r S64 -> CodeLine
- Jmpq_ :: Operand r S64 -> CodeLine
- J_ :: Condition -> Maybe Size -> Label -> CodeLine
- Jmp_ :: Maybe Size -> Label -> CodeLine
- Label_ :: CodeLine
- Data_ :: Bytes -> CodeLine
- Align_ :: Int -> CodeLine
 
- newLabel :: (StateType m ~ Int, MonadState m) => m Label
- codeLine :: (WriterType m ~ [a], MonadWriter m) => a -> m ()
- showOp0 :: (WriterType m ~ [a], MonadWriter m) => a -> m ()
- showOp :: (WriterType m ~ [[Char]], MonadWriter m) => [Char] -> [Char] -> m ()
- showOp1 :: (WriterType m ~ [[Char]], MonadWriter m, Show a) => [Char] -> a -> m ()
- showOp2 :: (WriterType m ~ [[Char]], MonadWriter m, Show a, Show a) => [Char] -> a -> a -> m ()
- showCodeLine :: CodeLine -> StateT Int (Writer [String]) ()
Documentation
class HasSize a where Source #
Instances
| HasSize Int16 Source # | |
| HasSize Int32 Source # | |
| HasSize Int64 Source # | |
| HasSize Int8 Source # | |
| HasSize Word16 Source # | |
| HasSize Word32 Source # | |
| HasSize Word64 Source # | |
| HasSize Word8 Source # | |
| IsSize s => HasSize (Addr s) Source # | |
| IsSize s => HasSize (Address s) Source # | |
| IsSize s => HasSize (BaseReg s) Source # | |
| IsSize s => HasSize (IndexReg s) Source # | |
| IsSize s => HasSize (Reg s) Source # | |
| HasSize (SSize s) Source # | |
| IsSize s => HasSize (Operand a s) Source # | |
data SSize (s :: Size) where Source #
Singleton type for size
The scaling of an index. (replace with Size?)
scaleFactor :: Num a => Scale -> a Source #
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)
Constructors
| 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 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 # | |
| IsSize s => HasSize (Operand a s) Source # | |
Constructors
| Immediate a | |
| LabelRelValue Size Label | 
Operand access modes
data Reg :: Size -> * where Source #
A register.
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.
Constructors
| Addr | |
| Fields 
 | |
type Displacement = Maybe Int32 Source #
resizeRegCode :: Reg s -> Reg s' Source #
Constructors
codeLine :: (WriterType m ~ [a], MonadWriter m) => a -> m () Source #
showOp0 :: (WriterType m ~ [a], MonadWriter m) => a -> m () Source #
showOp :: (WriterType m ~ [[Char]], MonadWriter m) => [Char] -> [Char] -> m () Source #
showOp1 :: (WriterType m ~ [[Char]], MonadWriter m, Show a) => [Char] -> a -> m () Source #
showOp2 :: (WriterType m ~ [[Char]], MonadWriter m, Show a, Show a) => [Char] -> a -> a -> m () Source #