module Bindings.Bfd.Disasm.I386.Mnemonic where import Bindings.Bfd.Disasm.I386.CondCode import Bindings.Bfd.Disasm.I386.Order import Bindings.Bfd.Disasm.I386.Precision import Bindings.Bfd.Disasm.I386.XmmType data Mnemonic = Add { bits1 :: Int } | AddCarry { bits1 :: Int } | AddScalar { precision :: Precision } | BitAnd { bits1 :: Int } | BitAndXmm -- FIXME | BitExclOr { xmmType :: XmmType } | BitNot { bits1 :: Int } | BitOr { bits1 :: Int } | BitOrXmm -- FIXME | BitScan -- FIXME | Branch { condCode :: CondCode } | Call { bits1 :: Int } | Compare { bits1 :: Int } | CompareExchange { bits1 :: Int } | CompareString { bits1 :: Int } | CompareUnordered { precision :: Precision } | CompareXmm -- FIXME | Convert { bits1 :: Int , bits2 :: Int , isSplit :: Bool } | ConvertXmm { numElems :: Int , sourceXmmType :: XmmType , targetXmmType :: XmmType , isTruncate :: Bool } | Cpuid | Decrement { bits1 :: Int } | Direction { isSet :: Bool } | Divide { bits1 :: Int } | DivideInt { bits1 :: Int } | DivideScalar { precision :: Precision } | Exchange { bits1 :: Int } | ExchangeAdd { bits1 :: Int } | Fpu -- FIXME | FpuCopyPop { bits1 :: Int } | FpuLoadValue { bits1 :: Int } | Halt | Increment { bits1 :: Int } | Jump { mbWidth :: Maybe Int } | Leave { bits1 :: Int } | LoadEffAddr { bits1 :: Int } | LogicalExclOr | Loop | Maximum -- FIXME | Minimum -- FIXME | Move { bits1 :: Int , mbWidthSignExtend :: Maybe (Int, Bool) -- (bits, T=se,F=ze) } | MoveAligned { xmmType :: XmmType } | MoveCond { bits1 :: Int , condCode :: CondCode } | MoveNonTemp { xmmType2 :: Either Int XmmType } | MovePacked { precision :: Precision , isHigh1 :: Bool , isHigh2 :: Bool } | MoveScalar { bits1 :: Int } | MoveString { bits1 :: Int } | MoveUnaligned { precision :: Precision } | Multiply { bits1 :: Int } | MultiplyInt { bits1 :: Int } | MultiplyScalar { xmmType :: XmmType } | Negate { bits1 :: Int } | NoOp | Pause | Pop { bits1 :: Int } | Push { bits1 :: Int } | Return { bits1 :: Int } | Rotate { bits1 :: Int , isRight :: Bool } | ScanString { bits1 :: Int } | Set { condCode :: CondCode } | Shift { bits1 :: Int , isRight :: Bool , isArith :: Bool } | SquareRoot -- FIXME | StoreString { bits1 :: Int } | Subtract { bits1 :: Int } | SubtractBorrow { bits1 :: Int } | SubtractScalar { precision :: Precision } | Test { bits1 :: Int } | Unpack { order :: Order , xmmType :: XmmType , mbWidth :: Maybe Int } | FIXME deriving (Show) toMnemonic :: String -> Mnemonic toMnemonic s | s == "adcl" = AddCarry 32 | s == "addb" = Add 8 | s == "addl" = Add 32 | s == "addq" = Add 64 | s == "addsd" = AddScalar Double | s == "addss" = AddScalar Single | s == "addw" = Add 16 | s == "andb" = BitAnd 8 | s == "andl" = BitAnd 32 | s == "andnpd" = BitAndXmm | s == "andpd" = BitAndXmm | s == "andq" = BitAnd 64 | s == "andw" = BitAnd 16 | s == "bsfq" = BitScan | s == "callq" = Call 64 | s == "cbtw" = Convert 8 16 False | s == "cld" = Direction False | s == "cltd" = Convert 32 64 True | s == "cltq" = Convert 32 64 False | s == "cmovael" = MoveCond 32 AboveOrEqual | s == "cmovaeq" = MoveCond 64 AboveOrEqual | s == "cmoval" = MoveCond 32 Above | s == "cmovaq" = MoveCond 64 Above | s == "cmovbel" = MoveCond 32 BelowOrEqual | s == "cmovbeq" = MoveCond 64 BelowOrEqual | s == "cmovbl" = MoveCond 32 Below | s == "cmovbq" = MoveCond 64 Below | s == "cmovel" = MoveCond 32 Equal | s == "cmoveq" = MoveCond 64 Equal | s == "cmovgel" = MoveCond 32 GreaterOrEqual | s == "cmovgeq" = MoveCond 64 GreaterOrEqual | s == "cmovgl" = MoveCond 32 Greater | s == "cmovgq" = MoveCond 64 Greater | s == "cmovlel" = MoveCond 32 LessOrEqual | s == "cmovleq" = MoveCond 64 LessOrEqual | s == "cmovlew" = MoveCond 16 LessOrEqual | s == "cmovll" = MoveCond 32 Less | s == "cmovlq" = MoveCond 64 Less | s == "cmovnel" = MoveCond 32 NotEqual | s == "cmovneq" = MoveCond 64 NotEqual | s == "cmovnpl" = MoveCond 32 NotParity | s == "cmovnsl" = MoveCond 32 NotSigned | s == "cmovnsq" = MoveCond 64 NotSigned | s == "cmovpl" = MoveCond 32 Parity | s == "cmovpq" = MoveCond 64 Parity | s == "cmovsl" = MoveCond 32 Signed | s == "cmpb" = Compare 8 | s == "cmpeqsd" = CompareXmm | s == "cmpl" = Compare 32 | s == "cmpneqsd" = CompareXmm | s == "cmpnlesd" = CompareXmm | s == "cmpnltsd" = CompareXmm | s == "cmpsb" = CompareString 8 | s == "cmpq" = Compare 64 | s == "cmpw" = Compare 16 | s == "cmpxchgl" = CompareExchange 32 | s == "cmpxchgq" = CompareExchange 64 | s == "cpuid" = Cpuid | s == "cqto" = Convert 64 128 False -- FIXME | s == "cvtpd2ps" = ConvertXmm 16 (FloatingPt Double) (FloatingPt Single) False | s == "cvtps2pd" = ConvertXmm 16 (FloatingPt Single) (FloatingPt Double) False | s == "cvtsd2ss" = ConvertXmm 8 (FloatingPt Double) (Int 0) False -- shouldn't this have a size postfix? it doesn't... | s == "cvtsi2sdl" = ConvertXmm 8 (Int 32) (FloatingPt Double) False | s == "cvtsi2sdq" = ConvertXmm 8 (Int 64) (FloatingPt Double) False | s == "cvtsi2ssl" = ConvertXmm 8 (Int 32) (FloatingPt Single) False | s == "cvtsi2ssq" = ConvertXmm 8 (Int 64) (FloatingPt Single) False | s == "cvtss2sd" = ConvertXmm 8 (FloatingPt Single) (FloatingPt Double) False | s == "cvttsd2si" = ConvertXmm 8 (FloatingPt Double) (Int 0) True -- shouldn't this have a size postfix? it doesn't... | s == "cvttsd2siq" = ConvertXmm 8 (FloatingPt Double) (Int 8) True | s == "cvttss2siq" = ConvertXmm 8 (FloatingPt Single) (Int 8) True | s == "cwtl" = Convert 16 32 False | s == "decb" = Decrement 8 | s == "decl" = Decrement 32 | s == "decq" = Decrement 64 | s == "decw" = Decrement 16 | s == "divl" = Divide 32 | s == "divq" = Divide 64 | s == "divsd" = DivideScalar Double | s == "divss" = DivideScalar Single | s == "fchs" = Fpu | s == "fcmove" = Fpu | s == "fcmovne" = Fpu | s == "fld" = Fpu | s == "fldcw" = Fpu | s == "fldl" = FpuLoadValue 64 | s == "fnstcw" = Fpu | s == "fstp" = Fpu | s == "fstpl" = FpuCopyPop 64 | s == "fxch" = Fpu | s == "hlt" = Halt | s == "idivl" = DivideInt 32 | s == "idivq" = DivideInt 64 | s == "imull" = MultiplyInt 32 | s == "imulq" = MultiplyInt 64 | s == "incl" = Increment 32 | s == "incq" = Increment 64 | s == "incw" = Increment 16 | s == "ja" = Branch Above | s == "ja,pn" = Branch Above -- FIXME | s == "jae" = Branch AboveOrEqual | s == "jae,pn" = Branch AboveOrEqual -- FIXME | s == "jb" = Branch Below | s == "jbe" = Branch BelowOrEqual | s == "jbe,pn" = Branch BelowOrEqual -- FIXME | s == "jbe,pt" = Branch BelowOrEqual -- FIXME | s == "je" = Branch Equal | s == "je,pn" = Branch Equal -- FIXME | s == "jg" = Branch Greater | s == "jge" = Branch GreaterOrEqual | s == "jl" = Branch Less | s == "jl,pt" = Branch Less -- FIXME | s == "jle" = Branch LessOrEqual | s == "jle,pn" = Branch LessOrEqual -- FIXME | s == "jne" = Branch NotEqual | s == "jne,pn" = Branch NotEqual -- FIXME | s == "jne,pt" = Branch NotEqual -- FIXME | s == "jnp" = Branch NotParity | s == "jns" = Branch NotSigned | s == "jmp" = Jump Nothing | s == "jmpq" = Jump $ Just 64 | s == "jp" = Branch Parity | s == "jp,pn" = Branch Parity -- FIXME | s == "js" = Branch Signed | s == "js,pn" = Branch Signed -- FIXME | s == "leal" = LoadEffAddr 32 | s == "leaq" = LoadEffAddr 64 | s == "leaveq" = Leave 64 | s == "maxsd" = Maximum -- FIXME | s == "minsd" = Minimum -- FIXME | s == "movabsq" = Move 64 Nothing | s == "movapd" = MoveAligned $ FloatingPt Double | s == "movaps" = MoveAligned $ FloatingPt Single | s == "movb" = Move 8 Nothing | s == "movdqa" = MoveAligned $ Int 128 | s == "movl" = Move 32 Nothing | s == "movlpd" = MovePacked Double False False | s == "movntps" = MoveNonTemp $ Right $ FloatingPt Single | s == "movq" = Move 64 Nothing | s == "movsb" = MoveString 8 | s == "movsbl" = Move 8 $ Just (32, True) | s == "movsbq" = Move 8 $ Just (64, True) | s == "movsbw" = Move 8 $ Just (16, True) | s == "movsd" = MoveScalar 64 | s == "movslq" = Move 32 $ Just (64, True) | s == "movsq" = MoveString 64 | s == "movss" = MoveScalar 32 | s == "movswl" = Move 16 $ Just (32, True) | s == "movswq" = Move 16 $ Just (64, True) | s == "movups" = MoveUnaligned Single | s == "movw" = Move 16 Nothing | s == "movzbl" = Move 8 $ Just (32, False) | s == "movzbq" = Move 8 $ Just (64, False) | s == "movzbw" = Move 8 $ Just (16, False) | s == "movzwl" = Move 16 $ Just (32, False) | s == "movzwq" = Move 16 $ Just (64, False) | s == "mull" = Multiply 32 | s == "mulq" = Multiply 64 | s == "mulsd" = MultiplyScalar $ FloatingPt Double | s == "mulss" = MultiplyScalar $ FloatingPt Single | s == "negl" = Negate 32 | s == "negq" = Negate 64 | s == "nop" = NoOp | s == "nopl" = NoOp | s == "nopw" = NoOp | s == "notl" = BitNot 32 | s == "notq" = BitNot 64 | s == "orb" = BitOr 8 | s == "orl" = BitOr 32 | s == "orpd" = BitOrXmm | s == "orq" = BitOr 64 | s == "orw" = BitOr 16 | s == "pause" = Pause | s == "popq" = Pop 64 | s == "punpcklqdq" = Unpack Low (Int 64) (Just 128) | s == "pushq" = Push 64 | s == "pxor" = LogicalExclOr | s == "roll" = Rotate 32 False | s == "retq" = Return 64 | s == "sarl" = Shift 32 True True | s == "sarq" = Shift 64 True True | s == "sbbl" = SubtractBorrow 32 | s == "sbbq" = SubtractBorrow 64 | s == "scasb" = ScanString 8 | s == "seta" = Set Above | s == "setae" = Set AboveOrEqual | s == "setb" = Set Below | s == "setbe" = Set BelowOrEqual | s == "sete" = Set Equal | s == "setg" = Set Greater | s == "setge" = Set GreaterOrEqual | s == "setl" = Set Less | s == "setle" = Set LessOrEqual | s == "setne" = Set NotEqual | s == "setnp" = Set NotParity | s == "setp" = Set Parity | s == "shlb" = Shift 8 False False | s == "shll" = Shift 32 False False | s == "shlq" = Shift 64 False False | s == "shrb" = Shift 8 True False | s == "shrl" = Shift 32 True False | s == "shrq" = Shift 64 True False | s == "shrw" = Shift 16 True False | s == "sqrtsd" = SquareRoot | s == "stosq" = StoreString 64 | s == "subb" = Subtract 8 | s == "subl" = Subtract 32 | s == "subq" = Subtract 64 | s == "subw" = Subtract 16 | s == "subsd" = SubtractScalar Double | s == "subss" = SubtractScalar Single | s == "testb" = Test 8 | s == "testl" = Test 32 | s == "testq" = Test 64 | s == "testw" = Test 16 | s == "ucomisd" = CompareUnordered Double | s == "ucomiss" = CompareUnordered Single | s == "unpcklpd" = Unpack Low (FloatingPt Double) Nothing | s == "unpcklps" = Unpack Low (FloatingPt Single) Nothing | s == "xaddl" = ExchangeAdd 32 | s == "xaddq" = ExchangeAdd 64 | s == "xchgl" = Exchange 32 | s == "xchgq" = Exchange 64 | s == "xchgw" = Exchange 16 | s == "xorb" = BitExclOr $ Int 8 | s == "xorl" = BitExclOr $ Int 32 | s == "xorpd" = BitExclOr $ FloatingPt Double | s == "xorps" = BitExclOr $ FloatingPt Single | s == "xorq" = BitExclOr $ Int 64 | s == "xorw" = BitExclOr $ Int 16 | otherwise = error $ "toMnemonic: " ++ show s isCall :: Mnemonic -> Bool isCall (Call _) = True isCall _ = False isJump :: Mnemonic -> Bool isJump (Jump _) = True isJump _ = False isBranch :: Mnemonic -> Bool isBranch (Branch _) = True isBranch (Loop ) = True isBranch _ = False isHalt :: Mnemonic -> Bool isHalt Halt = True isHalt _ = False isReturn :: Mnemonic -> Bool isReturn (Return _) = True isReturn _ = False {- unpcklps unpack and interleave low packed single precision floating point unpcklpd unpack and interleave low packed double precision floating point unpckhps unpack and interleave high packed single precision floating point unpckhpd unpack and interleave high packed double precision floating point punpckl unpack and interleave low 1 8 1 16 2 8 2 16 4 8 4 16 8 16 -}