Copyright | 2018 Simon Shine |
---|---|
License | MIT |
Maintainer | Simon Shine <shreddedglory@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
This module exposes the Opcode
type for expressing Ethereum VM opcodes
as extracted from the Ethereum Yellow Paper with amendments from various
EIPs. The Yellow Paper is available at:
https://ethereum.github.io/yellowpaper/paper.pdf
The list of opcodes is found in appendix H.2.
But it is not always up-to-date, so keeping track of EIPs that add or modify instructions is necessary. See comments in this module for the references to these additions.
Synopsis
- type Opcode = Opcode' ()
- data Opcode' j
- = STOP
- | ADD
- | MUL
- | SUB
- | DIV
- | SDIV
- | MOD
- | SMOD
- | ADDMOD
- | MULMOD
- | EXP
- | SIGNEXTEND
- | LT
- | GT
- | SLT
- | SGT
- | EQ
- | ISZERO
- | AND
- | OR
- | XOR
- | NOT
- | BYTE
- | SHL
- | SHR
- | SAR
- | SHA3
- | ADDRESS
- | BALANCE
- | ORIGIN
- | CALLER
- | CALLVALUE
- | CALLDATALOAD
- | CALLDATASIZE
- | CALLDATACOPY
- | CODESIZE
- | CODECOPY
- | GASPRICE
- | EXTCODESIZE
- | EXTCODECOPY
- | RETURNDATASIZE
- | RETURNDATACOPY
- | EXTCODEHASH
- | BLOCKHASH
- | COINBASE
- | TIMESTAMP
- | NUMBER
- | DIFFICULTY
- | GASLIMIT
- | CHAINID
- | SELFBALANCE
- | POP
- | MLOAD
- | MSTORE
- | MSTORE8
- | SLOAD
- | SSTORE
- | JUMP j
- | JUMPI j
- | PC
- | MSIZE
- | GAS
- | JUMPDEST j
- | PUSH !Word256
- | DUP !Ord16
- | SWAP !Ord16
- | LOG !Ord5
- | CREATE
- | CALL
- | CALLCODE
- | RETURN
- | DELEGATECALL
- | CREATE2
- | STATICCALL
- | REVERT
- | INVALID
- | SELFDESTRUCT
- data OpcodeSpec = OpcodeSpec {
- opcodeEncoding :: !Word8
- opcodeAlpha :: !Word8
- opcodeDelta :: !Word8
- opcodeName :: !Text
- opcodeSpec :: Opcode' j -> OpcodeSpec
- jump :: Opcode
- jumpi :: Opcode
- jumpdest :: Opcode
- jumpAnnot :: Opcode' a -> Maybe a
- jumpdestAnnot :: Opcode' a -> Maybe a
- concrete :: Opcode' a -> Opcode' ()
- opcodeText :: Opcode -> Text
- opcodeSize :: Num i => Opcode -> i
- toHex :: IsString s => [Opcode] -> s
- pack :: [Opcode] -> ByteString
- toBytes :: Opcode -> [Word8]
- isDUP :: Word8 -> Bool
- isSWAP :: Word8 -> Bool
- isLOG :: Word8 -> Bool
- isPUSH :: Word8 -> ByteString -> Bool
- readDUP :: Word8 -> Maybe Opcode
- readSWAP :: Word8 -> Maybe Opcode
- readLOG :: Word8 -> Maybe Opcode
- readPUSH :: Word8 -> ByteString -> Maybe Opcode
- readOp :: Word8 -> ByteString -> Maybe Opcode
- pattern DUP1 :: forall j. Opcode' j
- pattern DUP2 :: forall j. Opcode' j
- pattern DUP3 :: forall j. Opcode' j
- pattern DUP4 :: forall j. Opcode' j
- pattern DUP5 :: forall j. Opcode' j
- pattern DUP6 :: forall j. Opcode' j
- pattern DUP7 :: forall j. Opcode' j
- pattern DUP8 :: forall j. Opcode' j
- pattern DUP9 :: forall j. Opcode' j
- pattern DUP10 :: forall j. Opcode' j
- pattern DUP11 :: forall j. Opcode' j
- pattern DUP12 :: forall j. Opcode' j
- pattern DUP13 :: forall j. Opcode' j
- pattern DUP14 :: forall j. Opcode' j
- pattern DUP15 :: forall j. Opcode' j
- pattern DUP16 :: forall j. Opcode' j
- pattern SWAP1 :: forall j. Opcode' j
- pattern SWAP2 :: forall j. Opcode' j
- pattern SWAP3 :: forall j. Opcode' j
- pattern SWAP4 :: forall j. Opcode' j
- pattern SWAP5 :: forall j. Opcode' j
- pattern SWAP6 :: forall j. Opcode' j
- pattern SWAP7 :: forall j. Opcode' j
- pattern SWAP8 :: forall j. Opcode' j
- pattern SWAP9 :: forall j. Opcode' j
- pattern SWAP10 :: forall j. Opcode' j
- pattern SWAP11 :: forall j. Opcode' j
- pattern SWAP12 :: forall j. Opcode' j
- pattern SWAP13 :: forall j. Opcode' j
- pattern SWAP14 :: forall j. Opcode' j
- pattern SWAP15 :: forall j. Opcode' j
- pattern SWAP16 :: forall j. Opcode' j
- pattern LOG0 :: forall j. Opcode' j
- pattern LOG1 :: forall j. Opcode' j
- pattern LOG2 :: forall j. Opcode' j
- pattern LOG3 :: forall j. Opcode' j
- pattern LOG4 :: forall j. Opcode' j
Types
An Opcode'
is an Ethereum VM Opcode with parameterised jumps.
For a plain opcode using the basic EVM stack-based jumps, use Opcode
instead.
This type is used for defining and translating from annotated opcodes, e.g. with labelled jumps.
STOP | 0x00 |
ADD | 0x01 |
MUL | 0x02 |
SUB | 0x03 |
DIV | 0x04 |
SDIV | 0x05 |
MOD | 0x06 |
SMOD | 0x07 |
ADDMOD | 0x08 |
MULMOD | 0x09 |
EXP | 0x0a |
SIGNEXTEND | 0x0b |
LT | 0x10 |
GT | 0x11 |
SLT | 0x12 |
SGT | 0x13 |
EQ | 0x14 |
ISZERO | 0x15 |
AND | 0x16 |
OR | 0x17 |
XOR | 0x18 |
NOT | 0x19 |
BYTE | 0x1a |
SHL | |
SHR | |
SAR | |
SHA3 | 0x20 |
ADDRESS | 0x30 |
BALANCE | 0x31 |
ORIGIN | 0x32 |
CALLER | 0x33 |
CALLVALUE | 0x34 |
CALLDATALOAD | 0x35 |
CALLDATASIZE | 0x36 |
CALLDATACOPY | 0x37 |
CODESIZE | 0x38 |
CODECOPY | 0x39 |
GASPRICE | 0x3a |
EXTCODESIZE | 0x3b |
EXTCODECOPY | 0x3c |
RETURNDATASIZE | |
RETURNDATACOPY | |
EXTCODEHASH | |
BLOCKHASH | 0x40 |
COINBASE | 0x41 |
TIMESTAMP | 0x42 |
NUMBER | 0x43 |
DIFFICULTY | 0x44 |
GASLIMIT | 0x45 |
CHAINID | |
SELFBALANCE | |
POP | 0x50 |
MLOAD | 0x51 |
MSTORE | 0x52 |
MSTORE8 | 0x53 |
SLOAD | 0x54 |
SSTORE | 0x55 |
JUMP j | 0x56 |
JUMPI j | 0x57 |
PC | 0x58 |
MSIZE | 0x59 |
GAS | 0x5a |
JUMPDEST j | 0x5b |
PUSH !Word256 | 0x60 - 0x7f (PUSH1 - PUSH32) |
DUP !Ord16 | |
SWAP !Ord16 | |
LOG !Ord5 | |
CREATE | 0xf0 |
CALL | 0xf1 |
CALLCODE | 0xf2 |
RETURN | 0xf3 |
DELEGATECALL | |
CREATE2 | |
STATICCALL | 0xfa |
REVERT | |
INVALID | |
SELFDESTRUCT |
data OpcodeSpec Source #
An OpcodeSpec
for a given Opcode
contains the numeric encoding of the
opcode, the number of items that this opcode removes from the stack (α),
and the number of items added to the stack (δ). These values are documented
in the Ethereum Yellow Paper.
Examples of OpcodeSpec
s:
-- Hex α δ OpcodeSpec 0x01 2 1 "add" OpcodeSpec 0x60 0 1 "push1 255" OpcodeSpec 0x61 0 1 "push2 256"
OpcodeSpec | |
|
Instances
Eq OpcodeSpec Source # | |
Defined in EVM.Opcode.Internal (==) :: OpcodeSpec -> OpcodeSpec -> Bool # (/=) :: OpcodeSpec -> OpcodeSpec -> Bool # | |
Show OpcodeSpec Source # | |
Defined in EVM.Opcode.Internal showsPrec :: Int -> OpcodeSpec -> ShowS # show :: OpcodeSpec -> String # showList :: [OpcodeSpec] -> ShowS # |
opcodeSpec :: Opcode' j -> OpcodeSpec Source #
Pseudo-instructions and helper functions
Conversion and printing
opcodeSize :: Num i => Opcode -> i Source #
Parse and validate instructions
readOp :: Word8 -> ByteString -> Maybe Opcode Source #
Parse an Opcode
from a Word8
. In case of PUSH
instructions, read the
constant being pushed from a subsequent ByteString
.