{-# language GeneralizedNewtypeDeriving #-}
{-# language NoMonomorphismRestriction #-}
{-# language ScopedTypeVariables #-}
{-# language StandaloneDeriving #-}
{-# language FlexibleInstances #-}
{-# language FlexibleContexts #-}
{-# language PatternSynonyms #-}
{-# language KindSignatures #-}
{-# language PatternGuards #-}
{-# language BangPatterns #-}
{-# language ViewPatterns #-}
{-# language TypeFamilies #-}
{-# language LambdaCase #-}
{-# language RankNTypes #-}
{-# language DataKinds #-}
{-# language PolyKinds #-}
{-# language GADTs #-}
{-# language CPP #-}
module CodeGen.X86.Asm where
import Numeric
import Data.List
import Data.Bits
import Data.Int
import Data.Word
import Control.Monad
import Control.Arrow
import Control.Monad.Reader
import Control.Monad.Writer
import Control.Monad.State
everyNth :: Int -> [a] -> [[a]]
everyNth Int
n [] = []
everyNth Int
n [a]
xs = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
n [a]
xs[a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: Int -> [a] -> [[a]]
everyNth Int
n (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
n [a]
xs)
showNibble :: (Integral a, Bits a) => Int -> a -> Char
showNibble :: Int -> a -> Char
showNibble Int
n a
x = Int -> Char
forall a. Enum a => Int -> a
toEnum (Int
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ if Int
b Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
10 then Int
48 else Int
87)
where b :: Int
b = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ a
x a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n) a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
0x0f
showByte :: a -> [Char]
showByte a
b = [Int -> a -> Char
forall a. (Integral a, Bits a) => Int -> a -> Char
showNibble Int
1 a
b, Int -> a -> Char
forall a. (Integral a, Bits a) => Int -> a -> Char
showNibble Int
0 a
b]
showHex' :: a -> [Char]
showHex' a
x = [Char]
"0x" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ a -> [Char] -> [Char]
forall a. (Integral a, Show a) => a -> [Char] -> [Char]
showHex a
x [Char]
""
pattern $mIntegral :: forall r a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> (b -> r) -> (Void# -> r) -> r
Integral xs <- (toIntegralSized -> Just xs)
type Bytes = [Word8]
class HasBytes a where toBytes :: a -> Bytes
instance HasBytes Word8 where
toBytes :: Word8 -> Bytes
toBytes Word8
w = [Word8
w]
instance HasBytes Word16 where
toBytes :: Word16 -> Bytes
toBytes Word16
w = [Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w, Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word8) -> Word16 -> Word8
forall a b. (a -> b) -> a -> b
$ Word16
w Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
`shiftR` Int
8]
instance HasBytes Word32 where
toBytes :: Word32 -> Bytes
toBytes Word32
w = [ Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word8) -> Word32 -> Word8
forall a b. (a -> b) -> a -> b
$ Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
n | Int
n <- [Int
0, Int
8 .. Int
24] ]
instance HasBytes Word64 where
toBytes :: Word64 -> Bytes
toBytes Word64
w = [ Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word8) -> Word64 -> Word8
forall a b. (a -> b) -> a -> b
$ Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
n | Int
n <- [Int
0, Int
8 .. Int
56] ]
instance HasBytes Int8 where
toBytes :: Int8 -> Bytes
toBytes Int8
w = Word8 -> Bytes
forall a. HasBytes a => a -> Bytes
toBytes (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
w :: Word8)
instance HasBytes Int16 where
toBytes :: Int16 -> Bytes
toBytes Int16
w = Word16 -> Bytes
forall a. HasBytes a => a -> Bytes
toBytes (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
w :: Word16)
instance HasBytes Int32 where
toBytes :: Int32 -> Bytes
toBytes Int32
w = Word32 -> Bytes
forall a. HasBytes a => a -> Bytes
toBytes (Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
w :: Word32)
instance HasBytes Int64 where
toBytes :: Int64 -> Bytes
toBytes Int64
w = Word64 -> Bytes
forall a. HasBytes a => a -> Bytes
toBytes (Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
w :: Word64)
data Size = S1 | S8 | S16 | S32 | S64 | S128
deriving (Size -> Size -> Bool
(Size -> Size -> Bool) -> (Size -> Size -> Bool) -> Eq Size
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Size -> Size -> Bool
$c/= :: Size -> Size -> Bool
== :: Size -> Size -> Bool
$c== :: Size -> Size -> Bool
Eq, Eq Size
Eq Size
-> (Size -> Size -> Ordering)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> Ord Size
Size -> Size -> Bool
Size -> Size -> Ordering
Size -> Size -> Size
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Size -> Size -> Size
$cmin :: Size -> Size -> Size
max :: Size -> Size -> Size
$cmax :: Size -> Size -> Size
>= :: Size -> Size -> Bool
$c>= :: Size -> Size -> Bool
> :: Size -> Size -> Bool
$c> :: Size -> Size -> Bool
<= :: Size -> Size -> Bool
$c<= :: Size -> Size -> Bool
< :: Size -> Size -> Bool
$c< :: Size -> Size -> Bool
compare :: Size -> Size -> Ordering
$ccompare :: Size -> Size -> Ordering
$cp1Ord :: Eq Size
Ord)
instance Show Size where
show :: Size -> [Char]
show = \case
Size
S1 -> [Char]
"bit"
Size
S8 -> [Char]
"byte"
Size
S16 -> [Char]
"word"
Size
S32 -> [Char]
"dword"
Size
S64 -> [Char]
"qword"
Size
S128 -> [Char]
"oword"
mkSize :: a -> Size
mkSize a
1 = Size
S8
mkSize a
2 = Size
S16
mkSize a
4 = Size
S32
mkSize a
8 = Size
S64
mkSize a
16 = Size
S128
sizeLen :: Size -> p
sizeLen = \case
Size
S8 -> p
1
Size
S16 -> p
2
Size
S32 -> p
4
Size
S64 -> p
8
Size
S128 -> p
16
class HasSize a where size :: a -> Size
instance HasSize Word8 where size :: Word8 -> Size
size Word8
_ = Size
S8
instance HasSize Word16 where size :: Word16 -> Size
size Word16
_ = Size
S16
instance HasSize Word32 where size :: Word32 -> Size
size Word32
_ = Size
S32
instance HasSize Word64 where size :: Word64 -> Size
size Word64
_ = Size
S64
instance HasSize Int8 where size :: Int8 -> Size
size Int8
_ = Size
S8
instance HasSize Int16 where size :: Int16 -> Size
size Int16
_ = Size
S16
instance HasSize Int32 where size :: Int32 -> Size
size Int32
_ = Size
S32
instance HasSize Int64 where size :: Int64 -> Size
size Int64
_ = Size
S64
data SSize (s :: Size) where
SSize1 :: SSize S1
SSize8 :: SSize S8
SSize16 :: SSize S16
SSize32 :: SSize S32
SSize64 :: SSize S64
SSize128 :: SSize S128
instance HasSize (SSize s) where
size :: SSize s -> Size
size = \case
SSize s
SSize1 -> Size
S1
SSize s
SSize8 -> Size
S8
SSize s
SSize16 -> Size
S16
SSize s
SSize32 -> Size
S32
SSize s
SSize64 -> Size
S64
SSize s
SSize128 -> Size
S128
class IsSize (s :: Size) where
ssize :: SSize s
instance IsSize S1 where ssize :: SSize 'S1
ssize = SSize 'S1
SSize1
instance IsSize S8 where ssize :: SSize 'S8
ssize = SSize 'S8
SSize8
instance IsSize S16 where ssize :: SSize 'S16
ssize = SSize 'S16
SSize16
instance IsSize S32 where ssize :: SSize 'S32
ssize = SSize 'S32
SSize32
instance IsSize S64 where ssize :: SSize 'S64
ssize = SSize 'S64
SSize64
instance IsSize S128 where ssize :: SSize 'S128
ssize = SSize 'S128
SSize128
data EqT s s' where
Refl :: EqT s s
sizeEqCheck :: forall s s' f g . (IsSize s, IsSize s') => f s -> g s' -> Maybe (EqT s s')
sizeEqCheck :: f s -> g s' -> Maybe (EqT s s')
sizeEqCheck f s
_ g s'
_ = case (SSize s
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s, SSize s'
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s') of
(SSize s
SSize8 , SSize s'
SSize8) -> EqT s s -> Maybe (EqT s s)
forall a. a -> Maybe a
Just EqT s s
forall k (s :: k). EqT s s
Refl
(SSize s
SSize16, SSize s'
SSize16) -> EqT s s -> Maybe (EqT s s)
forall a. a -> Maybe a
Just EqT s s
forall k (s :: k). EqT s s
Refl
(SSize s
SSize32, SSize s'
SSize32) -> EqT s s -> Maybe (EqT s s)
forall a. a -> Maybe a
Just EqT s s
forall k (s :: k). EqT s s
Refl
(SSize s
SSize64, SSize s'
SSize64) -> EqT s s -> Maybe (EqT s s)
forall a. a -> Maybe a
Just EqT s s
forall k (s :: k). EqT s s
Refl
(SSize s, SSize s')
_ -> Maybe (EqT s s')
forall a. Maybe a
Nothing
newtype Scale = Scale Word8
deriving (Scale -> Scale -> Bool
(Scale -> Scale -> Bool) -> (Scale -> Scale -> Bool) -> Eq Scale
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scale -> Scale -> Bool
$c/= :: Scale -> Scale -> Bool
== :: Scale -> Scale -> Bool
$c== :: Scale -> Scale -> Bool
Eq)
s1 :: Scale
s1 = Word8 -> Scale
Scale Word8
0x0
s2 :: Scale
s2 = Word8 -> Scale
Scale Word8
0x1
s4 :: Scale
s4 = Word8 -> Scale
Scale Word8
0x2
s8 :: Scale
s8 = Word8 -> Scale
Scale Word8
0x3
toScale :: a -> Scale
toScale = \case
a
1 -> Scale
s1
a
2 -> Scale
s2
a
4 -> Scale
s4
a
8 -> Scale
s8
scaleFactor :: Scale -> p
scaleFactor (Scale Word8
i) = case Word8
i of
Word8
0x0 -> p
1
Word8
0x1 -> p
2
Word8
0x2 -> p
4
Word8
0x3 -> p
8
data Operand :: Access -> Size -> * where
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
addr :: IsSize s => Address s -> Operand rw s'
addr :: Address s -> Operand rw s'
addr = Addr s -> Operand rw s'
forall (s' :: Size) (rw :: Access) (s :: Size).
IsSize s' =>
Addr s' -> Operand rw s
MemOp (Addr s -> Operand rw s')
-> (Address s -> Addr s) -> Address s -> Operand rw s'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address s -> Addr s
forall (s :: Size). Address s -> Addr s
makeAddr
addr8 :: IsSize s => Address s -> Operand rw S8
addr8 :: Address s -> Operand rw 'S8
addr8 = Address s -> Operand rw 'S8
forall (s :: Size) (rw :: Access) (s' :: Size).
IsSize s =>
Address s -> Operand rw s'
addr
addr16 :: IsSize s => Address s -> Operand rw S16
addr16 :: Address s -> Operand rw 'S16
addr16 = Address s -> Operand rw 'S16
forall (s :: Size) (rw :: Access) (s' :: Size).
IsSize s =>
Address s -> Operand rw s'
addr
addr32 :: IsSize s => Address s -> Operand rw S32
addr32 :: Address s -> Operand rw 'S32
addr32 = Address s -> Operand rw 'S32
forall (s :: Size) (rw :: Access) (s' :: Size).
IsSize s =>
Address s -> Operand rw s'
addr
addr64 :: IsSize s => Address s -> Operand rw S64
addr64 :: Address s -> Operand rw 'S64
addr64 = Address s -> Operand rw 'S64
forall (s :: Size) (rw :: Access) (s' :: Size).
IsSize s =>
Address s -> Operand rw s'
addr
data Immediate a
= Immediate a
| LabelRelValue Size Label
newtype Label = Label {Label -> Int
unLabel :: Int}
instance Show Label where
show :: Label -> [Char]
show (Label Int
i) = [Char]
".l" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i
data Access
= R
| RW
data Reg :: Size -> * where
NormalReg :: Word8 -> Reg s
HighReg :: Word8 -> Reg S8
XMM :: Word8 -> Reg S128
deriving instance Eq (Reg s)
deriving instance Ord (Reg s)
data Addr s = Addr
{ Addr s -> BaseReg s
baseReg :: BaseReg s
, Addr s -> Displacement
displacement :: Displacement
, Addr s -> IndexReg s
indexReg :: IndexReg s
}
deriving (Addr s -> Addr s -> Bool
(Addr s -> Addr s -> Bool)
-> (Addr s -> Addr s -> Bool) -> Eq (Addr s)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (s :: Size). Addr s -> Addr s -> Bool
/= :: Addr s -> Addr s -> Bool
$c/= :: forall (s :: Size). Addr s -> Addr s -> Bool
== :: Addr s -> Addr s -> Bool
$c== :: forall (s :: Size). Addr s -> Addr s -> Bool
Eq)
type BaseReg s = Maybe (Reg s)
data IndexReg s = NoIndex | IndexReg Scale (Reg s)
deriving (IndexReg s -> IndexReg s -> Bool
(IndexReg s -> IndexReg s -> Bool)
-> (IndexReg s -> IndexReg s -> Bool) -> Eq (IndexReg s)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (s :: Size). IndexReg s -> IndexReg s -> Bool
/= :: IndexReg s -> IndexReg s -> Bool
$c/= :: forall (s :: Size). IndexReg s -> IndexReg s -> Bool
== :: IndexReg s -> IndexReg s -> Bool
$c== :: forall (s :: Size). IndexReg s -> IndexReg s -> Bool
Eq)
type Displacement = Maybe Int32
pattern $bNoDisp :: Maybe a
$mNoDisp :: forall r a. Maybe a -> (Void# -> r) -> (Void# -> r) -> r
NoDisp = Nothing
pattern $bDisp :: a -> Maybe a
$mDisp :: forall r a. Maybe a -> (a -> r) -> (Void# -> r) -> r
Disp a = Just a
ipRel :: Label -> Operand rw s
ipRel :: Label -> Operand rw s
ipRel Label
l = Immediate Int32 -> Operand rw s
forall (rw :: Access) (s :: Size). Immediate Int32 -> Operand rw s
IPMemOp (Immediate Int32 -> Operand rw s)
-> Immediate Int32 -> Operand rw s
forall a b. (a -> b) -> a -> b
$ Size -> Label -> Immediate Int32
forall a. Size -> Label -> Immediate a
LabelRelValue Size
S32 Label
l
ipRelValue :: Label -> Operand 'R s
ipRelValue Label
l = Immediate Int64 -> Operand 'R s
forall (s :: Size). Immediate Int64 -> Operand 'R s
ImmOp (Immediate Int64 -> Operand 'R s)
-> Immediate Int64 -> Operand 'R s
forall a b. (a -> b) -> a -> b
$ Size -> Label -> Immediate Int64
forall a. Size -> Label -> Immediate a
LabelRelValue Size
S32 Label
l
ipRel8 :: Label -> Operand rw S8
ipRel8 :: Label -> Operand rw 'S8
ipRel8 = Label -> Operand rw 'S8
forall (rw :: Access) (s :: Size). Label -> Operand rw s
ipRel
instance IsSize s => Show (Reg s) where
show :: Reg s -> [Char]
show (XMM Word8
i) = [Char]
"xmm" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Word8 -> [Char]
forall a. Show a => a -> [Char]
show Word8
i
show (HighReg Word8
i) =
([[Char]
"ah", [Char]
" ch", [Char]
"dh", [Char]
"bh"] [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [Char] -> [[Char]]
forall a. a -> [a]
repeat ([Char] -> [Char]
forall a. HasCallStack => [Char] -> a
error ([Char]
"show @Reg")))
[[Char]] -> Int -> [Char]
forall a. [a] -> Int -> a
!! Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
i
show r :: Reg s
r@(NormalReg Word8
i) =
([[Char]] -> Int -> [Char]
forall a. [a] -> Int -> a
!! Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
i) ([[Char]] -> [Char])
-> ([[Char]] -> [[Char]]) -> [[Char]] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [Char] -> [[Char]]
forall a. a -> [a]
repeat ([Char] -> [Char]
forall a. HasCallStack => [Char] -> a
error ([Char]
"show @Reg"))) ([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ case Reg s -> Size
forall a. HasSize a => a -> Size
size Reg s
r of
Size
S8 ->
[[Char]
"al", [Char]
"cl", [Char]
"dl", [Char]
"bl", [Char]
"spl", [Char]
"bpl", [Char]
"sil", [Char]
"dil"] [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"b") [[Char]]
r8
Size
S16 -> [[Char]]
r0 [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"w") [[Char]]
r8
Size
S32 -> ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (Char
'e' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:) [[Char]]
r0 [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"d") [[Char]]
r8
Size
S64 -> ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (Char
'r' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:) [[Char]]
r0 [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]]
r8
where
r0 :: [[Char]]
r0 = [[Char]
"ax", [Char]
"cx", [Char]
"dx", [Char]
"bx", [Char]
"sp", [Char]
"bp", [Char]
"si", [Char]
"di"]
r8 :: [[Char]]
r8 = [[Char]
"r8", [Char]
"r9", [Char]
"r10", [Char]
"r11", [Char]
"r12", [Char]
"r13", [Char]
"r14", [Char]
"r15"]
instance IsSize s => Show (Addr s) where
show :: Addr s -> [Char]
show (Addr BaseReg s
b Displacement
d IndexReg s
i) = [(Bool, [Char])] -> [Char]
showSum ([(Bool, [Char])] -> [Char]) -> [(Bool, [Char])] -> [Char]
forall a b. (a -> b) -> a -> b
$ BaseReg s -> [(Bool, [Char])]
forall a. Show a => Maybe a -> [(Bool, [Char])]
shb BaseReg s
b [(Bool, [Char])] -> [(Bool, [Char])] -> [(Bool, [Char])]
forall a. [a] -> [a] -> [a]
++ Displacement -> [(Bool, [Char])]
forall a. (Eq a, Num a, Show a) => Maybe a -> [(Bool, [Char])]
shd Displacement
d [(Bool, [Char])] -> [(Bool, [Char])] -> [(Bool, [Char])]
forall a. [a] -> [a] -> [a]
++ IndexReg s -> [(Bool, [Char])]
forall (s :: Size). IsSize s => IndexReg s -> [(Bool, [Char])]
shi IndexReg s
i
where
shb :: Maybe a -> [(Bool, [Char])]
shb Maybe a
Nothing = []
shb (Just a
x) = [(Bool
True, a -> [Char]
forall a. Show a => a -> [Char]
show a
x)]
shd :: Maybe a -> [(Bool, [Char])]
shd Maybe a
NoDisp = []
shd (Disp a
x) = [(a -> a
forall a. Num a => a -> a
signum a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= (-a
1), a -> [Char]
forall a. Show a => a -> [Char]
show (a -> a
forall a. Num a => a -> a
abs a
x))]
shi :: IndexReg s -> [(Bool, [Char])]
shi IndexReg s
NoIndex = []
shi (IndexReg Scale
sc Reg s
x) = [(Bool
True, Integer -> [Char]
forall a. (Eq a, Num a, Show a) => a -> [Char]
show' (Scale -> Integer
forall p. Num p => Scale -> p
scaleFactor Scale
sc) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Reg s -> [Char]
forall a. Show a => a -> [Char]
show Reg s
x)]
show' :: a -> [Char]
show' a
1 = [Char]
""
show' a
n = a -> [Char]
forall a. Show a => a -> [Char]
show a
n [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" * "
showSum :: [(Bool, [Char])] -> [Char]
showSum [] = [Char]
"0"
showSum ((Bool
True , [Char]
x) : [(Bool, [Char])]
xs) = [Char]
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [(Bool, [Char])] -> [Char]
forall (t :: * -> *). Foldable t => t (Bool, [Char]) -> [Char]
g [(Bool, [Char])]
xs
showSum ((Bool
False, [Char]
x) : [(Bool, [Char])]
xs) = [Char]
"-" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [(Bool, [Char])] -> [Char]
forall (t :: * -> *). Foldable t => t (Bool, [Char]) -> [Char]
g [(Bool, [Char])]
xs
g :: t (Bool, [Char]) -> [Char]
g = ((Bool, [Char]) -> [Char]) -> t (Bool, [Char]) -> [Char]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(Bool
a, [Char]
b) -> Bool -> [Char]
f Bool
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
b)
f :: Bool -> [Char]
f Bool
True = [Char]
" + "
f Bool
False = [Char]
" - "
instance IsSize s => Show (Operand a s) where
show :: Operand a s -> [Char]
show = \case
ImmOp Immediate Int64
w -> Immediate Int64 -> [Char]
forall a. Show a => a -> [Char]
show Immediate Int64
w
RegOp Reg s
r -> Reg s -> [Char]
forall a. Show a => a -> [Char]
show Reg s
r
r :: Operand a s
r@(MemOp Addr s'
a) -> Size -> [Char]
forall a. Show a => a -> [Char]
show (Operand a s -> Size
forall a. HasSize a => a -> Size
size Operand a s
r) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" [" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Addr s' -> [Char]
forall a. Show a => a -> [Char]
show Addr s'
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"]"
r :: Operand a s
r@(IPMemOp Immediate Int32
x) -> Size -> [Char]
forall a. Show a => a -> [Char]
show (Operand a s -> Size
forall a. HasSize a => a -> Size
size Operand a s
r) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" [" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"rel " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Immediate Int32 -> [Char]
forall a. Show a => a -> [Char]
show Immediate Int32
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"]"
where
showp :: a -> [Char]
showp a
x | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 = [Char]
" - " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ a -> [Char]
forall a. Show a => a -> [Char]
show (-a
x)
showp a
x = [Char]
" + " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ a -> [Char]
forall a. Show a => a -> [Char]
show a
x
instance Show a => Show (Immediate a) where
show :: Immediate a -> [Char]
show (Immediate a
x) = a -> [Char]
forall a. Show a => a -> [Char]
show a
x
show (LabelRelValue Size
s Label
x) = Label -> [Char]
forall a. Show a => a -> [Char]
show Label
x
instance IsSize s => HasSize (Operand a s) where
size :: Operand a s -> Size
size Operand a s
_ = SSize s -> Size
forall a. HasSize a => a -> Size
size (SSize s
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s)
instance IsSize s => HasSize (Addr s) where
size :: Addr s -> Size
size Addr s
_ = SSize s -> Size
forall a. HasSize a => a -> Size
size (SSize s
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s)
instance IsSize s => HasSize (Address s) where
size :: Address s -> Size
size Address s
_ = SSize s -> Size
forall a. HasSize a => a -> Size
size (SSize s
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s)
instance IsSize s => HasSize (BaseReg s) where
size :: BaseReg s -> Size
size BaseReg s
_ = SSize s -> Size
forall a. HasSize a => a -> Size
size (SSize s
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s)
instance IsSize s => HasSize (Reg s) where
size :: Reg s -> Size
size Reg s
_ = SSize s -> Size
forall a. HasSize a => a -> Size
size (SSize s
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s)
instance IsSize s => HasSize (IndexReg s) where
size :: IndexReg s -> Size
size IndexReg s
_ = SSize s -> Size
forall a. HasSize a => a -> Size
size (SSize s
forall (s :: Size). IsSize s => SSize s
ssize :: SSize s)
instance (rw ~ R) => Num (Operand rw s) where
negate :: Operand rw s -> Operand rw s
negate (ImmOp (Immediate Int64
x)) = Immediate Int64 -> Operand 'R s
forall (s :: Size). Immediate Int64 -> Operand 'R s
ImmOp (Immediate Int64 -> Operand 'R s)
-> Immediate Int64 -> Operand 'R s
forall a b. (a -> b) -> a -> b
$ Int64 -> Immediate Int64
forall a. a -> Immediate a
Immediate (Int64 -> Immediate Int64) -> Int64 -> Immediate Int64
forall a b. (a -> b) -> a -> b
$ Int64 -> Int64
forall a. Num a => a -> a
negate Int64
x
fromInteger :: Integer -> Operand rw s
fromInteger (Integral Int64
x) = Immediate Int64 -> Operand 'R s
forall (s :: Size). Immediate Int64 -> Operand 'R s
ImmOp (Immediate Int64 -> Operand 'R s)
-> Immediate Int64 -> Operand 'R s
forall a b. (a -> b) -> a -> b
$ Int64 -> Immediate Int64
forall a. a -> Immediate a
Immediate Int64
x
fromInteger Integer
z = [Char] -> Operand rw s
forall a. HasCallStack => [Char] -> a
error ([Char] -> Operand rw s) -> [Char] -> Operand rw s
forall a b. (a -> b) -> a -> b
$ Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
z [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" does not fit into "
+ :: Operand rw s -> Operand rw s -> Operand rw s
(+) = [Char] -> Operand rw s -> Operand rw s -> Operand rw s
forall a. HasCallStack => [Char] -> a
error [Char]
"(+) @Operand"
(-) = [Char] -> Operand rw s -> Operand rw s -> Operand rw s
forall a. HasCallStack => [Char] -> a
error [Char]
"(-) @Operand"
* :: Operand rw s -> Operand rw s -> Operand rw s
(*) = [Char] -> Operand rw s -> Operand rw s -> Operand rw s
forall a. HasCallStack => [Char] -> a
error [Char]
"(*) @Operand"
abs :: Operand rw s -> Operand rw s
abs = [Char] -> Operand rw s -> Operand rw s
forall a. HasCallStack => [Char] -> a
error [Char]
"abs @Operand"
signum :: Operand rw s -> Operand rw s
signum = [Char] -> Operand rw s -> Operand rw s
forall a. HasCallStack => [Char] -> a
error [Char]
"signum @Operand"
#if MIN_VERSION_base(4,11,0)
instance Semigroup (Addr s) where
Addr BaseReg s
a Displacement
b IndexReg s
c <> :: Addr s -> Addr s -> Addr s
<> Addr BaseReg s
a' Displacement
b' IndexReg s
c' = BaseReg s -> Displacement -> IndexReg s -> Addr s
forall (s :: Size).
BaseReg s -> Displacement -> IndexReg s -> Addr s
Addr (First (Reg s) -> BaseReg s
forall a. First a -> Maybe a
getFirst (First (Reg s) -> BaseReg s) -> First (Reg s) -> BaseReg s
forall a b. (a -> b) -> a -> b
$ BaseReg s -> First (Reg s)
forall a. Maybe a -> First a
First BaseReg s
a First (Reg s) -> First (Reg s) -> First (Reg s)
forall a. Semigroup a => a -> a -> a
<> BaseReg s -> First (Reg s)
forall a. Maybe a -> First a
First BaseReg s
a') (First Int32 -> Displacement
forall a. First a -> Maybe a
getFirst (First Int32 -> Displacement) -> First Int32 -> Displacement
forall a b. (a -> b) -> a -> b
$ Displacement -> First Int32
forall a. Maybe a -> First a
First Displacement
b First Int32 -> First Int32 -> First Int32
forall a. Semigroup a => a -> a -> a
<> Displacement -> First Int32
forall a. Maybe a -> First a
First Displacement
b') (IndexReg s
c IndexReg s -> IndexReg s -> IndexReg s
forall a. Semigroup a => a -> a -> a
<> IndexReg s
c')
instance Semigroup (IndexReg s) where
IndexReg s
i <> :: IndexReg s -> IndexReg s -> IndexReg s
<> IndexReg s
NoIndex = IndexReg s
i
IndexReg s
NoIndex <> IndexReg s
i = IndexReg s
i
#endif
instance Monoid (Addr s) where
mempty :: Addr s
mempty = BaseReg s -> Displacement -> IndexReg s -> Addr s
forall (s :: Size).
BaseReg s -> Displacement -> IndexReg s -> Addr s
Addr (First (Reg s) -> BaseReg s
forall a. First a -> Maybe a
getFirst First (Reg s)
forall a. Monoid a => a
mempty) (First Int32 -> Displacement
forall a. First a -> Maybe a
getFirst First Int32
forall a. Monoid a => a
mempty) IndexReg s
forall a. Monoid a => a
mempty
#if !MIN_VERSION_base(4,11,0)
Addr a b c `mappend` Addr a' b' c' = Addr (getFirst $ First a <> First a') (getFirst $ First b <> First b') (c <> c')
#endif
instance Monoid (IndexReg s) where
mempty :: IndexReg s
mempty = IndexReg s
forall (s :: Size). IndexReg s
NoIndex
#if !MIN_VERSION_base(4,11,0)
i `mappend` NoIndex = i
NoIndex `mappend` i = i
#endif
base :: Reg s -> Addr s
base :: Reg s -> Addr s
base Reg s
x = BaseReg s -> Displacement -> IndexReg s -> Addr s
forall (s :: Size).
BaseReg s -> Displacement -> IndexReg s -> Addr s
Addr (Reg s -> BaseReg s
forall a. a -> Maybe a
Just Reg s
x) Displacement
forall a. Maybe a
NoDisp IndexReg s
forall (s :: Size). IndexReg s
NoIndex
index :: Scale -> Reg s -> Addr s
index :: Scale -> Reg s -> Addr s
index Scale
sc Reg s
x = BaseReg s -> Displacement -> IndexReg s -> Addr s
forall (s :: Size).
BaseReg s -> Displacement -> IndexReg s -> Addr s
Addr BaseReg s
forall a. Maybe a
Nothing Displacement
forall a. Maybe a
NoDisp (Scale -> Reg s -> IndexReg s
forall (s :: Size). Scale -> Reg s -> IndexReg s
IndexReg Scale
sc Reg s
x)
index' :: Int -> Reg s -> Addr s
index' :: Int -> Reg s -> Addr s
index' Int
sc Reg s
x = BaseReg s -> Displacement -> IndexReg s -> Addr s
forall (s :: Size).
BaseReg s -> Displacement -> IndexReg s -> Addr s
Addr BaseReg s
forall a. Maybe a
Nothing Displacement
forall a. Maybe a
NoDisp (Scale -> Reg s -> IndexReg s
forall (s :: Size). Scale -> Reg s -> IndexReg s
IndexReg (Int -> Scale
forall a. (Eq a, Num a) => a -> Scale
toScale Int
sc) Reg s
x)
index1 :: Reg s -> Addr s
index1 = Scale -> Reg s -> Addr s
forall (s :: Size). Scale -> Reg s -> Addr s
index Scale
s1
index2 :: Reg s -> Addr s
index2 = Scale -> Reg s -> Addr s
forall (s :: Size). Scale -> Reg s -> Addr s
index Scale
s2
index4 :: Reg s -> Addr s
index4 = Scale -> Reg s -> Addr s
forall (s :: Size). Scale -> Reg s -> Addr s
index Scale
s4
index8 :: Reg s -> Addr s
index8 = Scale -> Reg s -> Addr s
forall (s :: Size). Scale -> Reg s -> Addr s
index Scale
s8
disp :: (Bits a, Integral a) => a -> Addr s
disp :: a -> Addr s
disp (Integral Int32
x)
| Int32
x Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
== Int32
0 = Addr s
forall a. Monoid a => a
mempty
| Bool
otherwise = BaseReg s -> Displacement -> IndexReg s -> Addr s
forall (s :: Size).
BaseReg s -> Displacement -> IndexReg s -> Addr s
Addr BaseReg s
forall a. Maybe a
Nothing (Int32 -> Displacement
forall a. a -> Maybe a
Disp Int32
x) IndexReg s
forall (s :: Size). IndexReg s
NoIndex
data Address :: Size -> * where
Address :: [(Int, Reg s)] -> Int -> Address s
scaleAddress :: (Int -> Int) -> Address s -> Address s
scaleAddress :: (Int -> Int) -> Address s -> Address s
scaleAddress Int -> Int
f (Address [(Int, Reg s)]
rs Int
d) = [(Int, Reg s)] -> Int -> Address s
forall (s :: Size). [(Int, Reg s)] -> Int -> Address s
Address ((Int -> Int) -> (Int, Reg s) -> (Int, Reg s)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Int -> Int
f ((Int, Reg s) -> (Int, Reg s)) -> [(Int, Reg s)] -> [(Int, Reg s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, Reg s)]
rs) (Int -> Address s) -> Int -> Address s
forall a b. (a -> b) -> a -> b
$ Int -> Int
f Int
d
instance Num (Address s) where
fromInteger :: Integer -> Address s
fromInteger Integer
d = [(Int, Reg s)] -> Int -> Address s
forall (s :: Size). [(Int, Reg s)] -> Int -> Address s
Address [] (Int -> Address s) -> Int -> Address s
forall a b. (a -> b) -> a -> b
$ Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
d
negate :: Address s -> Address s
negate = (Int -> Int) -> Address s -> Address s
forall (s :: Size). (Int -> Int) -> Address s -> Address s
scaleAddress Int -> Int
forall a. Num a => a -> a
negate
Address [] Int
t * :: Address s -> Address s -> Address s
* Address s
a = (Int -> Int) -> Address s -> Address s
forall (s :: Size). (Int -> Int) -> Address s -> Address s
scaleAddress (Int
t Int -> Int -> Int
forall a. Num a => a -> a -> a
*) Address s
a
Address s
a * Address [] Int
t = (Int -> Int) -> Address s -> Address s
forall (s :: Size). (Int -> Int) -> Address s -> Address s
scaleAddress (Int
t Int -> Int -> Int
forall a. Num a => a -> a -> a
*) Address s
a
Address [(Int, Reg s)]
rs Int
d + :: Address s -> Address s -> Address s
+ Address [(Int, Reg s)]
rs' Int
d' = [(Int, Reg s)] -> Int -> Address s
forall (s :: Size). [(Int, Reg s)] -> Int -> Address s
Address ([(Int, Reg s)] -> [(Int, Reg s)] -> [(Int, Reg s)]
forall b a.
(Ord b, Num a, Eq a) =>
[(a, b)] -> [(a, b)] -> [(a, b)]
f [(Int, Reg s)]
rs [(Int, Reg s)]
rs') (Int
d Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
d') where
f :: [(a, b)] -> [(a, b)] -> [(a, b)]
f [] [(a, b)]
rs = [(a, b)]
rs
f [(a, b)]
rs [] = [(a, b)]
rs
f (p :: (a, b)
p@(a
t, b
r) : [(a, b)]
rs) (p' :: (a, b)
p'@(a
t', b
r') : [(a, b)]
rs') = case b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
compare b
r b
r' of
Ordering
LT -> (a, b)
p (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: [(a, b)] -> [(a, b)] -> [(a, b)]
f [(a, b)]
rs ((a, b)
p' (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: [(a, b)]
rs')
Ordering
GT -> (a, b)
p' (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: [(a, b)] -> [(a, b)] -> [(a, b)]
f ((a, b)
p (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: [(a, b)]
rs) [(a, b)]
rs'
Ordering
EQ | a
t a -> a -> a
forall a. Num a => a -> a -> a
+ a
t' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 -> [(a, b)] -> [(a, b)] -> [(a, b)]
f [(a, b)]
rs [(a, b)]
rs'
| Bool
otherwise -> (a
t a -> a -> a
forall a. Num a => a -> a -> a
+ a
t', b
r) (a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
: [(a, b)] -> [(a, b)] -> [(a, b)]
f [(a, b)]
rs [(a, b)]
rs'
abs :: Address s -> Address s
abs = [Char] -> Address s -> Address s
forall a. HasCallStack => [Char] -> a
error [Char]
"abs @Address"
signum :: Address s -> Address s
signum = [Char] -> Address s -> Address s
forall a. HasCallStack => [Char] -> a
error [Char]
"signum @Address"
makeAddr :: Address s -> Addr s
makeAddr :: Address s -> Addr s
makeAddr (Address [(Int
1, Reg s
r)] Int
d) = Reg s -> Addr s
forall (s :: Size). Reg s -> Addr s
base Reg s
r Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Int -> Addr s
forall a (s :: Size). (Bits a, Integral a) => a -> Addr s
disp Int
d
makeAddr (Address [(Int
t, Reg s
r)] Int
d) = Int -> Reg s -> Addr s
forall (s :: Size). Int -> Reg s -> Addr s
index' Int
t Reg s
r Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Int -> Addr s
forall a (s :: Size). (Bits a, Integral a) => a -> Addr s
disp Int
d
makeAddr (Address [(Int
1, Reg s
r), (Int
1, r' :: Reg s
r'@(NormalReg Word8
0x4))] Int
d) = Reg s -> Addr s
forall (s :: Size). Reg s -> Addr s
base Reg s
r' Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Reg s -> Addr s
forall (s :: Size). Reg s -> Addr s
index1 Reg s
r Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Int -> Addr s
forall a (s :: Size). (Bits a, Integral a) => a -> Addr s
disp Int
d
makeAddr (Address [(Int
1, Reg s
r), (Int
t, Reg s
r')] Int
d) = Reg s -> Addr s
forall (s :: Size). Reg s -> Addr s
base Reg s
r Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Int -> Reg s -> Addr s
forall (s :: Size). Int -> Reg s -> Addr s
index' Int
t Reg s
r' Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Int -> Addr s
forall a (s :: Size). (Bits a, Integral a) => a -> Addr s
disp Int
d
makeAddr (Address [(Int
t, Reg s
r'), (Int
1, Reg s
r)] Int
d) = Reg s -> Addr s
forall (s :: Size). Reg s -> Addr s
base Reg s
r Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Int -> Reg s -> Addr s
forall (s :: Size). Int -> Reg s -> Addr s
index' Int
t Reg s
r' Addr s -> Addr s -> Addr s
forall a. Semigroup a => a -> a -> a
<> Int -> Addr s
forall a (s :: Size). (Bits a, Integral a) => a -> Addr s
disp Int
d
class FromReg c where
fromReg :: Reg s -> c s
instance FromReg Reg where
fromReg :: Reg s -> Reg s
fromReg = Reg s -> Reg s
forall a. a -> a
id
instance FromReg (Operand r) where
fromReg :: Reg s -> Operand r s
fromReg = Reg s -> Operand r s
forall (s :: Size) (rw :: Access). Reg s -> Operand rw s
RegOp
instance FromReg Address where
fromReg :: Reg s -> Address s
fromReg Reg s
r = [(Int, Reg s)] -> Int -> Address s
forall (s :: Size). [(Int, Reg s)] -> Int -> Address s
Address [(Int
1, Reg s
r)] Int
0
reg :: Word8 -> c s
reg = Reg s -> c s
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg s -> c s) -> (Word8 -> Reg s) -> Word8 -> c s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Reg s
forall (s :: Size). Word8 -> Reg s
NormalReg
rax, rcx, rdx, rbx, rsp, rbp, rsi, rdi, r8, r9, r10, r11, r12, r13, r14, r15 :: FromReg c => c S64
rax :: c 'S64
rax = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x0
rcx :: c 'S64
rcx = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x1
rdx :: c 'S64
rdx = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x2
rbx :: c 'S64
rbx = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x3
rsp :: c 'S64
rsp = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x4
rbp :: c 'S64
rbp = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x5
rsi :: c 'S64
rsi = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x6
rdi :: c 'S64
rdi = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x7
r8 :: c 'S64
r8 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x8
r9 :: c 'S64
r9 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x9
r10 :: c 'S64
r10 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xa
r11 :: c 'S64
r11 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xb
r12 :: c 'S64
r12 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xc
r13 :: c 'S64
r13 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xd
r14 :: c 'S64
r14 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xe
r15 :: c 'S64
r15 = Word8 -> c 'S64
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xf
eax, ecx, edx, ebx, esp, ebp, esi, edi, r8d, r9d, r10d, r11d, r12d, r13d, r14d, r15d :: FromReg c => c S32
eax :: c 'S32
eax = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x0
ecx :: c 'S32
ecx = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x1
edx :: c 'S32
edx = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x2
ebx :: c 'S32
ebx = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x3
esp :: c 'S32
esp = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x4
ebp :: c 'S32
ebp = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x5
esi :: c 'S32
esi = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x6
edi :: c 'S32
edi = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x7
r8d :: c 'S32
r8d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x8
r9d :: c 'S32
r9d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x9
r10d :: c 'S32
r10d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xa
r11d :: c 'S32
r11d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xb
r12d :: c 'S32
r12d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xc
r13d :: c 'S32
r13d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xd
r14d :: c 'S32
r14d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xe
r15d :: c 'S32
r15d = Word8 -> c 'S32
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xf
ax, cx, dx, bx, sp, bp, si, di, r8w, r9w, r10w, r11w, r12w, r13w, r14w, r15w :: FromReg c => c S16
ax :: c 'S16
ax = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x0
cx :: c 'S16
cx = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x1
dx :: c 'S16
dx = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x2
bx :: c 'S16
bx = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x3
sp :: c 'S16
sp = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x4
bp :: c 'S16
bp = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x5
si :: c 'S16
si = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x6
di :: c 'S16
di = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x7
r8w :: c 'S16
r8w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x8
r9w :: c 'S16
r9w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x9
r10w :: c 'S16
r10w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xa
r11w :: c 'S16
r11w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xb
r12w :: c 'S16
r12w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xc
r13w :: c 'S16
r13w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xd
r14w :: c 'S16
r14w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xe
r15w :: c 'S16
r15w = Word8 -> c 'S16
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xf
al, cl, dl, bl, spl, bpl, sil, dil, r8b, r9b, r10b, r11b, r12b, r13b, r14b, r15b :: FromReg c => c S8
al :: c 'S8
al = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x0
cl :: c 'S8
cl = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x1
dl :: c 'S8
dl = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x2
bl :: c 'S8
bl = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x3
spl :: c 'S8
spl = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x4
bpl :: c 'S8
bpl = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x5
sil :: c 'S8
sil = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x6
dil :: c 'S8
dil = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x7
r8b :: c 'S8
r8b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x8
r9b :: c 'S8
r9b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0x9
r10b :: c 'S8
r10b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xa
r11b :: c 'S8
r11b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xb
r12b :: c 'S8
r12b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xc
r13b :: c 'S8
r13b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xd
r14b :: c 'S8
r14b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xe
r15b :: c 'S8
r15b = Word8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Word8 -> c s
reg Word8
0xf
ah, ch, dh, bh :: FromReg c => c S8
ah :: c 'S8
ah = Reg 'S8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S8 -> c 'S8) -> Reg 'S8 -> c 'S8
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S8
HighReg Word8
0x0
ch :: c 'S8
ch = Reg 'S8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S8 -> c 'S8) -> Reg 'S8 -> c 'S8
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S8
HighReg Word8
0x1
dh :: c 'S8
dh = Reg 'S8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S8 -> c 'S8) -> Reg 'S8 -> c 'S8
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S8
HighReg Word8
0x2
bh :: c 'S8
bh = Reg 'S8 -> c 'S8
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S8 -> c 'S8) -> Reg 'S8 -> c 'S8
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S8
HighReg Word8
0x3
xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7 :: FromReg c => c S128
xmm0 :: c 'S128
xmm0 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x0
xmm1 :: c 'S128
xmm1 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x1
xmm2 :: c 'S128
xmm2 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x2
xmm3 :: c 'S128
xmm3 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x3
xmm4 :: c 'S128
xmm4 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x4
xmm5 :: c 'S128
xmm5 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x5
xmm6 :: c 'S128
xmm6 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x6
xmm7 :: c 'S128
xmm7 = Reg 'S128 -> c 'S128
forall (c :: Size -> *) (s :: Size). FromReg c => Reg s -> c s
fromReg (Reg 'S128 -> c 'S128) -> Reg 'S128 -> c 'S128
forall a b. (a -> b) -> a -> b
$ Word8 -> Reg 'S128
XMM Word8
0x7
pattern $bRegA :: Operand a b
$mRegA :: forall r (a :: Access) (b :: Size).
Operand a b -> (Void# -> r) -> (Void# -> r) -> r
RegA = RegOp (NormalReg 0x0)
pattern RegCl :: Operand r S8
pattern $bRegCl :: Operand r 'S8
$mRegCl :: forall r (r :: Access).
Operand r 'S8 -> (Void# -> r) -> (Void# -> r) -> r
RegCl = RegOp (NormalReg 0x1)
resizeOperand :: IsSize s' => Operand RW s -> Operand RW s'
resizeOperand :: Operand 'RW s -> Operand 'RW s'
resizeOperand (RegOp Reg s
x) = Reg s' -> Operand 'RW s'
forall (s :: Size) (rw :: Access). Reg s -> Operand rw s
RegOp (Reg s' -> Operand 'RW s') -> Reg s' -> Operand 'RW s'
forall a b. (a -> b) -> a -> b
$ Reg s -> Reg s'
forall (s :: Size) (s' :: Size). Reg s -> Reg s'
resizeRegCode Reg s
x
resizeOperand (MemOp Addr s'
a) = Addr s' -> Operand 'RW s'
forall (s' :: Size) (rw :: Access) (s :: Size).
IsSize s' =>
Addr s' -> Operand rw s
MemOp Addr s'
a
resizeOperand (IPMemOp Immediate Int32
a) = Immediate Int32 -> Operand 'RW s'
forall (rw :: Access) (s :: Size). Immediate Int32 -> Operand rw s
IPMemOp Immediate Int32
a
resizeRegCode :: Reg s -> Reg s'
resizeRegCode :: Reg s -> Reg s'
resizeRegCode (NormalReg Word8
i) = Word8 -> Reg s'
forall (s :: Size). Word8 -> Reg s
NormalReg Word8
i
pattern $mMemLike :: forall r (a :: Access) (b :: Size).
Operand a b -> (Void# -> r) -> (Void# -> r) -> r
MemLike <- (isMemOp -> True)
isMemOp :: Operand a b -> Bool
isMemOp MemOp{} = Bool
True
isMemOp IPMemOp{} = Bool
True
isMemOp Operand a b
_ = Bool
False
newtype Condition = Condition Word8
pattern $bO :: Condition
$mO :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
O = Condition 0x0
pattern $bNO :: Condition
$mNO :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NO = Condition 0x1
pattern $bB :: Condition
$mB :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
B = Condition 0x2
pattern $bC :: Condition
$mC :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
C = Condition 0x2
pattern $bNB :: Condition
$mNB :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NB = Condition 0x3
pattern $bNC :: Condition
$mNC :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NC = Condition 0x3
pattern $bE :: Condition
$mE :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
E = Condition 0x4
pattern $bZ :: Condition
$mZ :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
Z = Condition 0x4
pattern $bNE :: Condition
$mNE :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NE = Condition 0x5
pattern $bNZ :: Condition
$mNZ :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NZ = Condition 0x5
pattern $bNA :: Condition
$mNA :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NA = Condition 0x6
pattern $bBE :: Condition
$mBE :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
BE = Condition 0x6
pattern $bA :: Condition
$mA :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
A = Condition 0x7
pattern $bNBE :: Condition
$mNBE :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NBE = Condition 0x7
pattern $bS :: Condition
$mS :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
S = Condition 0x8
pattern $bNS :: Condition
$mNS :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NS = Condition 0x9
pattern $bP :: Condition
$mP :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
P = Condition 0xa
pattern $bNP :: Condition
$mNP :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NP = Condition 0xb
pattern $bL :: Condition
$mL :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
L = Condition 0xc
pattern $bNL :: Condition
$mNL :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NL = Condition 0xd
pattern $bNG :: Condition
$mNG :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NG = Condition 0xe
pattern $bLE :: Condition
$mLE :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
LE = Condition 0xe
pattern $bG :: Condition
$mG :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
G = Condition 0xf
pattern $bNLE :: Condition
$mNLE :: forall r. Condition -> (Void# -> r) -> (Void# -> r) -> r
NLE = Condition 0xf
instance Show Condition where
show :: Condition -> [Char]
show (Condition Word8
x) = case Word8
x of
Word8
0x0 -> [Char]
"o"
Word8
0x1 -> [Char]
"no"
Word8
0x2 -> [Char]
"c"
Word8
0x3 -> [Char]
"nc"
Word8
0x4 -> [Char]
"z"
Word8
0x5 -> [Char]
"nz"
Word8
0x6 -> [Char]
"be"
Word8
0x7 -> [Char]
"nbe"
Word8
0x8 -> [Char]
"s"
Word8
0x9 -> [Char]
"ns"
Word8
0xa -> [Char]
"p"
Word8
0xb -> [Char]
"np"
Word8
0xc -> [Char]
"l"
Word8
0xd -> [Char]
"nl"
Word8
0xe -> [Char]
"le"
Word8
0xf -> [Char]
"nle"
pattern $bN :: Condition -> Condition
$mN :: forall r. Condition -> (Condition -> r) -> (Void# -> r) -> r
N cc <- (notCond -> cc)
where N = Condition -> Condition
notCond
notCond :: Condition -> Condition
notCond :: Condition -> Condition
notCond (Condition Word8
c) = Word8 -> Condition
Condition (Word8 -> Condition) -> Word8 -> Condition
forall a b. (a -> b) -> a -> b
$ Word8
c Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
`xor` Word8
1
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 :: m Label
newLabel = do
Int
i <- m Int
forall (m :: * -> *). MonadState m => m (StateType m)
get
StateType m -> m ()
forall (m :: * -> *). MonadState m => StateType m -> m ()
put (StateType m -> m ()) -> StateType m -> m ()
forall a b. (a -> b) -> a -> b
$ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
Label -> m Label
forall (m :: * -> *) a. Monad m => a -> m a
return (Label -> m Label) -> Label -> m Label
forall a b. (a -> b) -> a -> b
$ Int -> Label
Label Int
i
codeLine :: a -> m ()
codeLine a
x = WriterType m -> m ()
forall (m :: * -> *). MonadWriter m => WriterType m -> m ()
tell [a
x]
showOp0 :: a -> m ()
showOp0 a
s = a -> m ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
codeLine a
s
showOp :: [Char] -> [Char] -> m ()
showOp [Char]
s [Char]
a = [Char] -> m ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 ([Char] -> m ()) -> [Char] -> m ()
forall a b. (a -> b) -> a -> b
$ [Char]
s [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
a
showOp1 :: [Char] -> a -> m ()
showOp1 [Char]
s a
a = [Char] -> [Char] -> m ()
forall (m :: * -> *).
(MonadWriter m, WriterType m ~ [[Char]]) =>
[Char] -> [Char] -> m ()
showOp [Char]
s ([Char] -> m ()) -> [Char] -> m ()
forall a b. (a -> b) -> a -> b
$ a -> [Char]
forall a. Show a => a -> [Char]
show a
a
showOp2 :: [Char] -> a -> a -> m ()
showOp2 [Char]
s a
a a
b = [Char] -> [Char] -> m ()
forall (m :: * -> *).
(MonadWriter m, WriterType m ~ [[Char]]) =>
[Char] -> [Char] -> m ()
showOp [Char]
s ([Char] -> m ()) -> [Char] -> m ()
forall a b. (a -> b) -> a -> b
$ a -> [Char]
forall a. Show a => a -> [Char]
show a
a [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
", " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ a -> [Char]
forall a. Show a => a -> [Char]
show a
b
showCodeLine :: CodeLine -> StateT Int (Writer [String]) ()
showCodeLine :: CodeLine -> StateT Int (Writer [[Char]]) ()
showCodeLine = \case
Add_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"add" Operand 'RW s
op1 Operand r s
op2
Or_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"or" Operand 'RW s
op1 Operand r s
op2
Adc_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"adc" Operand 'RW s
op1 Operand r s
op2
Sbb_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"sbb" Operand 'RW s
op1 Operand r s
op2
And_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"and" Operand 'RW s
op1 Operand r s
op2
Sub_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"sub" Operand 'RW s
op1 Operand r s
op2
Xor_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"xor" Operand 'RW s
op1 Operand r s
op2
Cmp_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"cmp" Operand 'RW s
op1 Operand r s
op2
Test_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"test" Operand 'RW s
op1 Operand r s
op2
Bsf Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"bsf" Operand 'RW s
op1 Operand r s
op2
Bsr Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"bsr" Operand 'RW s
op1 Operand r s
op2
Bt Operand r s
op1 Operand 'RW s
op2 -> [Char]
-> Operand r s -> Operand 'RW s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"bt" Operand r s
op1 Operand 'RW s
op2
Rol_ Operand 'RW s
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW s
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"rol" Operand 'RW s
op1 Operand r 'S8
op2
Ror_ Operand 'RW s
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW s
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"ror" Operand 'RW s
op1 Operand r 'S8
op2
Rcl_ Operand 'RW s
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW s
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"rcl" Operand 'RW s
op1 Operand r 'S8
op2
Rcr_ Operand 'RW s
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW s
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"rcr" Operand 'RW s
op1 Operand r 'S8
op2
Shl_ Operand 'RW s
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW s
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"shl" Operand 'RW s
op1 Operand r 'S8
op2
Shr_ Operand 'RW s
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW s
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"shr" Operand 'RW s
op1 Operand r 'S8
op2
Sar_ Operand 'RW s
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW s
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"sar" Operand 'RW s
op1 Operand r 'S8
op2
Mov_ Operand 'RW s
op1 Operand r s
op2 -> [Char]
-> Operand 'RW s -> Operand r s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"mov" Operand 'RW s
op1 Operand r s
op2
Cmov_ Condition
cc Operand 'RW s
op1 Operand 'RW s
op2 -> [Char]
-> Operand 'RW s
-> Operand 'RW s
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 ([Char]
"cmov" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Condition -> [Char]
forall a. Show a => a -> [Char]
show Condition
cc) Operand 'RW s
op1 Operand 'RW s
op2
Lea_ Operand 'RW s
op1 Operand 'RW s'
op2 -> [Char]
-> Operand 'RW s
-> Operand 'RW s'
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"lea" Operand 'RW s
op1 Operand 'RW s'
op2
Xchg_ Operand 'RW s
op1 Operand 'RW s
op2 -> [Char]
-> Operand 'RW s
-> Operand 'RW s
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"xchg" Operand 'RW s
op1 Operand 'RW s
op2
Movd_ Operand 'RW s
op1 Operand r s'
op2 -> [Char]
-> Operand 'RW s -> Operand r s' -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"movd" Operand 'RW s
op1 Operand r s'
op2
Movq_ Operand 'RW s
op1 Operand r s'
op2 -> [Char]
-> Operand 'RW s -> Operand r s' -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"movq" Operand 'RW s
op1 Operand r s'
op2
Movdqa_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"movdqa" Operand 'RW 'S128
op1 Operand r 'S128
op2
Paddb_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"paddb" Operand 'RW 'S128
op1 Operand r 'S128
op2
Paddw_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"paddw" Operand 'RW 'S128
op1 Operand r 'S128
op2
Paddd_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"paddd" Operand 'RW 'S128
op1 Operand r 'S128
op2
Paddq_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"paddq" Operand 'RW 'S128
op1 Operand r 'S128
op2
Psubb_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psubb" Operand 'RW 'S128
op1 Operand r 'S128
op2
Psubw_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psubw" Operand 'RW 'S128
op1 Operand r 'S128
op2
Psubd_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psubd" Operand 'RW 'S128
op1 Operand r 'S128
op2
Psubq_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psubq" Operand 'RW 'S128
op1 Operand r 'S128
op2
Pxor_ Operand 'RW 'S128
op1 Operand r 'S128
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S128
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"pxor" Operand 'RW 'S128
op1 Operand r 'S128
op2
Psllw_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psllw" Operand 'RW 'S128
op1 Operand r 'S8
op2
Pslld_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"pslld" Operand 'RW 'S128
op1 Operand r 'S8
op2
Psllq_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psllq" Operand 'RW 'S128
op1 Operand r 'S8
op2
Pslldq_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"pslldq" Operand 'RW 'S128
op1 Operand r 'S8
op2
Psrlw_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psrlw" Operand 'RW 'S128
op1 Operand r 'S8
op2
Psrld_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psrld" Operand 'RW 'S128
op1 Operand r 'S8
op2
Psrlq_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psrlq" Operand 'RW 'S128
op1 Operand r 'S8
op2
Psrldq_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psrldq" Operand 'RW 'S128
op1 Operand r 'S8
op2
Psraw_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psraw" Operand 'RW 'S128
op1 Operand r 'S8
op2
Psrad_ Operand 'RW 'S128
op1 Operand r 'S8
op2 -> [Char]
-> Operand 'RW 'S128
-> Operand r 'S8
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a a.
(MonadWriter m, Show a, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> a -> m ()
showOp2 [Char]
"psrad" Operand 'RW 'S128
op1 Operand r 'S8
op2
Inc_ Operand 'RW s
op -> [Char] -> Operand 'RW s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"inc" Operand 'RW s
op
Dec_ Operand 'RW s
op -> [Char] -> Operand 'RW s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"dec" Operand 'RW s
op
Not_ Operand 'RW s
op -> [Char] -> Operand 'RW s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"not" Operand 'RW s
op
Neg_ Operand 'RW s
op -> [Char] -> Operand 'RW s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"neg" Operand 'RW s
op
Bswap Operand 'RW s
op -> [Char] -> Operand 'RW s -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"bswap" Operand 'RW s
op
Pop_ Operand 'RW 'S64
op -> [Char] -> Operand 'RW 'S64 -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"pop" Operand 'RW 'S64
op
Push_ Operand r 'S64
op -> [Char] -> Operand r 'S64 -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"push" Operand r 'S64
op
Call_ Operand r 'S64
op -> [Char] -> Operand r 'S64 -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"call" Operand r 'S64
op
Jmpq_ Operand r 'S64
op -> [Char] -> Operand r 'S64 -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, Show a, WriterType m ~ [[Char]]) =>
[Char] -> a -> m ()
showOp1 [Char]
"jmp" Operand r 'S64
op
CodeLine
Ret_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"ret"
CodeLine
Nop_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"nop"
CodeLine
PushF_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"pushf"
CodeLine
PopF_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"popf"
CodeLine
Cmc_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"cmc"
CodeLine
Clc_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"clc"
CodeLine
Stc_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"stc"
CodeLine
Cli_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"cli"
CodeLine
Sti_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"sti"
CodeLine
Cld_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"cld"
CodeLine
Std_ -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
showOp0 [Char]
"std"
Align_ Int
s -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
codeLine ([Char] -> StateT Int (Writer [[Char]]) ())
-> [Char] -> StateT Int (Writer [[Char]]) ()
forall a b. (a -> b) -> a -> b
$ [Char]
".align " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
s
Data_ Bytes
x
| Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Bytes -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ((Word8 -> Bool) -> Bytes -> Bytes
forall a. (a -> Bool) -> [a] -> [a]
filter Word8 -> Bool
forall a. (Ord a, Num a) => a -> Bool
isPrint Bytes
x) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Bytes -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Bytes
x -> [Char] -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *).
(MonadWriter m, WriterType m ~ [[Char]]) =>
[Char] -> [Char] -> m ()
showOp [Char]
"db" ([Char] -> StateT Int (Writer [[Char]]) ())
-> [Char] -> StateT Int (Writer [[Char]]) ()
forall a b. (a -> b) -> a -> b
$ [Char] -> [Char]
forall a. Show a => a -> [Char]
show (Int -> Char
forall a. Enum a => Int -> a
toEnum (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Char) -> Bytes -> [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bytes
x :: String)
| Bool
otherwise -> [Char] -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *).
(MonadWriter m, WriterType m ~ [[Char]]) =>
[Char] -> [Char] -> m ()
showOp [Char]
"db" ([Char] -> StateT Int (Writer [[Char]]) ())
-> [Char] -> StateT Int (Writer [[Char]]) ()
forall a b. (a -> b) -> a -> b
$ [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
", " (Word8 -> [Char]
forall a. Show a => a -> [Char]
show (Word8 -> [Char]) -> Bytes -> [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bytes
x)
where
isPrint :: a -> Bool
isPrint a
c = a
c a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
32 Bool -> Bool -> Bool
&& a
c a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
126
J_ Condition
cc Maybe Size
s Label
l -> [Char] -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *).
(MonadWriter m, WriterType m ~ [[Char]]) =>
[Char] -> [Char] -> m ()
showOp ([Char]
"j" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Condition -> [Char]
forall a. Show a => a -> [Char]
show Condition
cc) ([Char] -> StateT Int (Writer [[Char]]) ())
-> [Char] -> StateT Int (Writer [[Char]]) ()
forall a b. (a -> b) -> a -> b
$ (case Maybe Size
s of Just Size
S8 -> [Char]
"short "; Just Size
S32 -> [Char]
"near "; Maybe Size
_ -> [Char]
"") [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Label -> [Char]
forall a. Show a => a -> [Char]
show Label
l
Jmp_ Maybe Size
s Label
l -> [Char] -> [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *).
(MonadWriter m, WriterType m ~ [[Char]]) =>
[Char] -> [Char] -> m ()
showOp [Char]
"jmp" ([Char] -> StateT Int (Writer [[Char]]) ())
-> [Char] -> StateT Int (Writer [[Char]]) ()
forall a b. (a -> b) -> a -> b
$ (case Maybe Size
s of Just Size
S8 -> [Char]
"short "; Just Size
S32 -> [Char]
"near "; Maybe Size
_ -> [Char]
"") [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Label -> [Char]
forall a. Show a => a -> [Char]
show Label
l
CodeLine
Label_ -> StateT Int (Writer [[Char]]) Label
forall (m :: * -> *). (MonadState m, StateType m ~ Int) => m Label
newLabel StateT Int (Writer [[Char]]) Label
-> (Label -> StateT Int (Writer [[Char]]) ())
-> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Char] -> StateT Int (Writer [[Char]]) ()
forall (m :: * -> *) a.
(MonadWriter m, WriterType m ~ [a]) =>
a -> m ()
codeLine ([Char] -> StateT Int (Writer [[Char]]) ())
-> (Label -> [Char]) -> Label -> StateT Int (Writer [[Char]]) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Label -> [Char]
forall a. Show a => a -> [Char]
show