module EVM.Op ( Op (..) , opString ) where import EVM.Types (SymWord) import Data.Word (Word8) import Numeric (showHex) data Op = OpStop | OpAdd | OpMul | OpSub | OpDiv | OpSdiv | OpMod | OpSmod | OpAddmod | OpMulmod | OpExp | OpSignextend | OpLt | OpGt | OpSlt | OpSgt | OpEq | OpIszero | OpAnd | OpOr | OpXor | OpNot | OpByte | OpShl | OpShr | OpSar | OpSha3 | OpAddress | OpBalance | OpOrigin | OpCaller | OpCallvalue | OpCalldataload | OpCalldatasize | OpCalldatacopy | OpCodesize | OpCodecopy | OpGasprice | OpExtcodesize | OpExtcodecopy | OpReturndatasize | OpReturndatacopy | OpExtcodehash | OpBlockhash | OpCoinbase | OpTimestamp | OpNumber | OpDifficulty | OpGaslimit | OpChainid | OpSelfbalance | OpPop | OpMload | OpMstore | OpMstore8 | OpSload | OpSstore | OpJump | OpJumpi | OpPc | OpMsize | OpGas | OpJumpdest | OpCreate | OpCall | OpStaticcall | OpCallcode | OpReturn | OpDelegatecall | OpCreate2 | OpRevert | OpSelfdestruct | OpDup !Word8 | OpSwap !Word8 | OpLog !Word8 | OpPush !SymWord | OpUnknown Word8 deriving (Int -> Op -> ShowS [Op] -> ShowS Op -> String (Int -> Op -> ShowS) -> (Op -> String) -> ([Op] -> ShowS) -> Show Op forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Op] -> ShowS $cshowList :: [Op] -> ShowS show :: Op -> String $cshow :: Op -> String showsPrec :: Int -> Op -> ShowS $cshowsPrec :: Int -> Op -> ShowS Show, Op -> Op -> Bool (Op -> Op -> Bool) -> (Op -> Op -> Bool) -> Eq Op forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Op -> Op -> Bool $c/= :: Op -> Op -> Bool == :: Op -> Op -> Bool $c== :: Op -> Op -> Bool Eq) opString :: (Integral a, Show a) => (a, Op) -> String opString :: (a, Op) -> String opString (a i, Op o) = let showPc :: a -> String showPc a x | a x a -> a -> Bool forall a. Ord a => a -> a -> Bool < a 0x10 = Char '0' Char -> ShowS forall a. a -> [a] -> [a] : a -> ShowS forall a. (Integral a, Show a) => a -> ShowS showHex a x String "" | Bool otherwise = a -> ShowS forall a. (Integral a, Show a) => a -> ShowS showHex a x String "" in a -> String forall a. (Integral a, Show a) => a -> String showPc a i String -> ShowS forall a. Semigroup a => a -> a -> a <> String " " String -> ShowS forall a. [a] -> [a] -> [a] ++ case Op o of Op OpStop -> String "STOP" Op OpAdd -> String "ADD" Op OpMul -> String "MUL" Op OpSub -> String "SUB" Op OpDiv -> String "DIV" Op OpSdiv -> String "SDIV" Op OpMod -> String "MOD" Op OpSmod -> String "SMOD" Op OpAddmod -> String "ADDMOD" Op OpMulmod -> String "MULMOD" Op OpExp -> String "EXP" Op OpSignextend -> String "SIGNEXTEND" Op OpLt -> String "LT" Op OpGt -> String "GT" Op OpSlt -> String "SLT" Op OpSgt -> String "SGT" Op OpEq -> String "EQ" Op OpIszero -> String "ISZERO" Op OpAnd -> String "AND" Op OpOr -> String "OR" Op OpXor -> String "XOR" Op OpNot -> String "NOT" Op OpByte -> String "BYTE" Op OpShl -> String "SHL" Op OpShr -> String "SHR" Op OpSar -> String "SAR" Op OpSha3 -> String "SHA3" Op OpAddress -> String "ADDRESS" Op OpBalance -> String "BALANCE" Op OpOrigin -> String "ORIGIN" Op OpCaller -> String "CALLER" Op OpCallvalue -> String "CALLVALUE" Op OpCalldataload -> String "CALLDATALOAD" Op OpCalldatasize -> String "CALLDATASIZE" Op OpCalldatacopy -> String "CALLDATACOPY" Op OpCodesize -> String "CODESIZE" Op OpCodecopy -> String "CODECOPY" Op OpGasprice -> String "GASPRICE" Op OpExtcodesize -> String "EXTCODESIZE" Op OpExtcodecopy -> String "EXTCODECOPY" Op OpReturndatasize -> String "RETURNDATASIZE" Op OpReturndatacopy -> String "RETURNDATACOPY" Op OpExtcodehash -> String "EXTCODEHASH" Op OpBlockhash -> String "BLOCKHASH" Op OpCoinbase -> String "COINBASE" Op OpTimestamp -> String "TIMESTAMP" Op OpNumber -> String "NUMBER" Op OpDifficulty -> String "DIFFICULTY" Op OpGaslimit -> String "GASLIMIT" Op OpChainid -> String "CHAINID" Op OpSelfbalance -> String "SELFBALANCE" Op OpPop -> String "POP" Op OpMload -> String "MLOAD" Op OpMstore -> String "MSTORE" Op OpMstore8 -> String "MSTORE8" Op OpSload -> String "SLOAD" Op OpSstore -> String "SSTORE" Op OpJump -> String "JUMP" Op OpJumpi -> String "JUMPI" Op OpPc -> String "PC" Op OpMsize -> String "MSIZE" Op OpGas -> String "GAS" Op OpJumpdest -> String "JUMPDEST" Op OpCreate -> String "CREATE" Op OpCall -> String "CALL" Op OpStaticcall -> String "STATICCALL" Op OpCallcode -> String "CALLCODE" Op OpReturn -> String "RETURN" Op OpDelegatecall -> String "DELEGATECALL" Op OpCreate2 -> String "CREATE2" Op OpSelfdestruct -> String "SELFDESTRUCT" OpDup Word8 x -> String "DUP" String -> ShowS forall a. [a] -> [a] -> [a] ++ Word8 -> String forall a. Show a => a -> String show Word8 x OpSwap Word8 x -> String "SWAP" String -> ShowS forall a. [a] -> [a] -> [a] ++ Word8 -> String forall a. Show a => a -> String show Word8 x OpLog Word8 x -> String "LOG" String -> ShowS forall a. [a] -> [a] -> [a] ++ Word8 -> String forall a. Show a => a -> String show Word8 x OpPush SymWord x -> String "PUSH " String -> ShowS forall a. [a] -> [a] -> [a] ++ SymWord -> String forall a. Show a => a -> String show SymWord x Op OpRevert -> String "REVERT" OpUnknown Word8 x -> String "UNKNOWN " String -> ShowS forall a. [a] -> [a] -> [a] ++ Word8 -> String forall a. Show a => a -> String show Word8 x