evm-opcodes-0.2.0: Opcode types for Ethereum Virtual Machine (EVM)
Copyright2018-2024 Simon Shine
LicenseMIT
MaintainerSimon Shine <simon@simonshine.dk>
Safe HaskellSafe-Inferred
LanguageHaskell2010

EVM.Opcode

Description

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

Types

type Opcode = Opcode' () Source #

An Opcode is a plain, parameterless Ethereum VM Opcode.

data Opcode' j Source #

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.

Constructors

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

0x1b, https://eips.ethereum.org/EIPS/eip-145

SHR

0x1c, https://eips.ethereum.org/EIPS/eip-145

SAR

0x1d, https://eips.ethereum.org/EIPS/eip-145

KECCAK256

0x20, https://eips.ethereum.org/EIPS/eip-1803

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

0x3d, https://eips.ethereum.org/EIPS/eip-211

RETURNDATACOPY

0x3e, https://eips.ethereum.org/EIPS/eip-211

EXTCODEHASH

0x3f, https://eips.ethereum.org/EIPS/eip-1052

BLOCKHASH

0x40

COINBASE

0x41

TIMESTAMP

0x42

NUMBER

0x43

PREVRANDAO

0x44, https://eips.ethereum.org/EIPS/eip-4399

GASLIMIT

0x45

CHAINID

0x46, https://eips.ethereum.org/EIPS/eip-1344

SELFBALANCE

0x47, https://eips.ethereum.org/EIPS/eip-1884

BASEFEE

0x48, https://eips.ethereum.org/EIPS/eip-3198

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

0x80 - 0x8f (DUP1 - DUP16)

SWAP !Ord16

0x90 - 0x9f (SWAP1 - SWAP16)

LOG !Ord5

0xa0 - 0xa4 (LOG0 - LOG4)

CREATE

0xf0

CALL

0xf1

CALLCODE

0xf2

RETURN

0xf3

DELEGATECALL

0xf4, https://eips.ethereum.org/EIPS/eip-7

CREATE2

0xf5, https://eips.ethereum.org/EIPS/eip-1014

STATICCALL

0xfa

REVERT

0xfd, https://eips.ethereum.org/EIPS/eip-140

INVALID

0xfe, https://eips.ethereum.org/EIPS/eip-141

SELFDESTRUCT

0xff, https://eips.ethereum.org/EIPS/eip-6

Instances

Instances details
Functor Opcode' Source # 
Instance details

Defined in EVM.Opcode.Internal

Methods

fmap :: (a -> b) -> Opcode' a -> Opcode' b #

(<$) :: a -> Opcode' b -> Opcode' a #

Show a => Show (Opcode' a) Source # 
Instance details

Defined in EVM.Opcode.Internal

Methods

showsPrec :: Int -> Opcode' a -> ShowS #

show :: Opcode' a -> String #

showList :: [Opcode' a] -> ShowS #

Eq j => Eq (Opcode' j) Source # 
Instance details

Defined in EVM.Opcode.Internal

Methods

(==) :: Opcode' j -> Opcode' j -> Bool #

(/=) :: Opcode' j -> Opcode' j -> Bool #

Ord j => Ord (Opcode' j) Source # 
Instance details

Defined in EVM.Opcode.Internal

Methods

compare :: Opcode' j -> Opcode' j -> Ordering #

(<) :: Opcode' j -> Opcode' j -> Bool #

(<=) :: Opcode' j -> Opcode' j -> Bool #

(>) :: Opcode' j -> Opcode' j -> Bool #

(>=) :: Opcode' j -> Opcode' j -> Bool #

max :: Opcode' j -> Opcode' j -> Opcode' j #

min :: Opcode' j -> Opcode' j -> Opcode' j #

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 OpcodeSpecs:

--         Hex  α δ
OpcodeSpec 0x01 2 1 "add"
OpcodeSpec 0x60 0 1 "push1 255"
OpcodeSpec 0x61 0 1 "push2 256"

Constructors

OpcodeSpec 

Fields

Instances

Instances details
Show OpcodeSpec Source # 
Instance details

Defined in EVM.Opcode.Internal

Eq OpcodeSpec Source # 
Instance details

Defined in EVM.Opcode.Internal

opcodeSpec :: Opcode' j -> OpcodeSpec Source #

Given an Opcode', produce its OpcodeSpec.

For DUP, SWAP and LOG this depends on the specific variant, and for PUSH it depends on the size of the constant being pushed.

Pseudo-instructions and helper functions

jump :: Opcode Source #

jump is a plain parameterless Opcode.

jumpi :: Opcode Source #

jumpi is a plain parameterless Opcode.

jumpdest :: Opcode Source #

jumpdest is a plain parameterless Opcode.

jumpAnnot :: Opcode' a -> Maybe a Source #

Extract the a from a JUMP a or a JUMPI a.

jumpdestAnnot :: Opcode' a -> Maybe a Source #

Extract the a from a JUMPDEST a.

Conversion and printing

concrete :: Opcode' a -> Opcode' () Source #

Convert any Opcode' a into an Opcode' ().

opcodeSize :: Num i => Opcode -> i Source #

Calculate the size in bytes of an encoded opcode. The only Opcode that uses more than one byte is PUSH. Sizes are trivially determined for only Opcode with unlabelled jumps, since we cannot know e.g. where the label of a LabelledOpcode points to before code generation has completed.

toHex :: IsString s => [Opcode] -> s Source #

Convert a [Opcode] to a string of ASCII hexadecimals.

pack :: [Opcode] -> ByteString Source #

Convert a [Opcode] to bytecode.

toBytes :: Opcode -> [Word8] Source #

Convert an Opcode to a [Word8].

To convert many Opcodes to bytecode, use pack.

Parse and validate instructions

isDUP :: Word8 -> Bool Source #

Determine if a byte represents a DUP opcode (DUP1 -- DUP16).

isSWAP :: Word8 -> Bool Source #

Determine if a byte represents a SWAP opcode (SWAP1 -- SWAP16).

isLOG :: Word8 -> Bool Source #

Determine if a byte represents a LOG opcode (LOG1 -- LOG4).

isPUSH :: Word8 -> ByteString -> Bool Source #

Determine if a byte represents a PUSH opcode.

readDUP :: Word8 -> Maybe Opcode Source #

Read a DUP opcode (DUP1 -- DUP16) safely.

readSWAP :: Word8 -> Maybe Opcode Source #

Read a SWAP opcode (SWAP1 -- SWAP16) safely.

readLOG :: Word8 -> Maybe Opcode Source #

Read a LOG opcode (LOG1 -- LOG4) safely.

readPUSH :: Word8 -> ByteString -> Maybe Opcode Source #

Read a PUSH opcode safely.

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.

Pattern synonyms

pattern DUP1 :: forall j. Opcode' j Source #

Use DUP1 instead of DUP Ord16_1.

pattern DUP2 :: forall j. Opcode' j Source #

Use DUP2 instead of DUP Ord16_2.

pattern DUP3 :: forall j. Opcode' j Source #

Use DUP3 instead of DUP Ord16_3.

pattern DUP4 :: forall j. Opcode' j Source #

Use DUP4 instead of DUP Ord16_4.

pattern DUP5 :: forall j. Opcode' j Source #

Use DUP5 instead of DUP Ord16_5.

pattern DUP6 :: forall j. Opcode' j Source #

Use DUP6 instead of DUP Ord16_6.

pattern DUP7 :: forall j. Opcode' j Source #

Use DUP7 instead of DUP Ord16_7.

pattern DUP8 :: forall j. Opcode' j Source #

Use DUP8 instead of DUP Ord16_8.

pattern DUP9 :: forall j. Opcode' j Source #

Use DUP9 instead of DUP Ord16_9.

pattern DUP10 :: forall j. Opcode' j Source #

Use DUP10 instead of DUP Ord16_10.

pattern DUP11 :: forall j. Opcode' j Source #

Use DUP11 instead of DUP Ord16_11.

pattern DUP12 :: forall j. Opcode' j Source #

Use DUP12 instead of DUP Ord16_12.

pattern DUP13 :: forall j. Opcode' j Source #

Use DUP13 instead of DUP Ord16_13.

pattern DUP14 :: forall j. Opcode' j Source #

Use DUP14 instead of DUP Ord16_14.

pattern DUP15 :: forall j. Opcode' j Source #

Use DUP15 instead of DUP Ord16_15.

pattern DUP16 :: forall j. Opcode' j Source #

Use DUP16 instead of DUP Ord16_16.

pattern SWAP1 :: forall j. Opcode' j Source #

Use SWAP1 instead of SWAP Ord16_1, etc.

pattern SWAP2 :: forall j. Opcode' j Source #

Use SWAP2 instead of SWAP Ord16_2, etc.

pattern SWAP3 :: forall j. Opcode' j Source #

Use SWAP3 instead of SWAP Ord16_3, etc.

pattern SWAP4 :: forall j. Opcode' j Source #

Use SWAP4 instead of SWAP Ord16_4, etc.

pattern SWAP5 :: forall j. Opcode' j Source #

Use SWAP5 instead of SWAP Ord16_5, etc.

pattern SWAP6 :: forall j. Opcode' j Source #

Use SWAP6 instead of SWAP Ord16_6, etc.

pattern SWAP7 :: forall j. Opcode' j Source #

Use SWAP7 instead of SWAP Ord16_7, etc.

pattern SWAP8 :: forall j. Opcode' j Source #

Use SWAP8 instead of SWAP Ord16_8, etc.

pattern SWAP9 :: forall j. Opcode' j Source #

Use SWAP9 instead of SWAP Ord16_9, etc.

pattern SWAP10 :: forall j. Opcode' j Source #

Use SWAP10 instead of SWAP Ord16_10, etc.

pattern SWAP11 :: forall j. Opcode' j Source #

Use SWAP11 instead of SWAP Ord16_11, etc.

pattern SWAP12 :: forall j. Opcode' j Source #

Use SWAP12 instead of SWAP Ord16_12, etc.

pattern SWAP13 :: forall j. Opcode' j Source #

Use SWAP13 instead of SWAP Ord16_13, etc.

pattern SWAP14 :: forall j. Opcode' j Source #

Use SWAP14 instead of SWAP Ord16_14, etc.

pattern SWAP15 :: forall j. Opcode' j Source #

Use SWAP15 instead of SWAP Ord16_15, etc.

pattern SWAP16 :: forall j. Opcode' j Source #

Use SWAP16 instead of SWAP Ord16_16, etc.

pattern LOG0 :: forall j. Opcode' j Source #

Use LOG0 instead of LOG Ord5_0.

pattern LOG1 :: forall j. Opcode' j Source #

Use LOG1 instead of LOG Ord5_1.

pattern LOG2 :: forall j. Opcode' j Source #

Use LOG2 instead of LOG Ord5_2.

pattern LOG3 :: forall j. Opcode' j Source #

Use LOG3 instead of LOG Ord5_3.

pattern LOG4 :: forall j. Opcode' j Source #

Use LOG4 instead of LOG Ord5_4.