hevm-0.51.1: Ethereum virtual machine evaluator
Safe HaskellSafe-Inferred
LanguageGHC2021

EVM

Synopsis

Documentation

bytecode :: Getter Contract (Expr Buf) Source #

An "external" view of a contract's bytecode, appropriate for e.g. EXTCODEHASH.

Data accessors

Data constructors

initialContract :: ContractCode -> Contract Source #

Initialize empty contract with given code

Opcode dispatch (exec1)

next :: (?op :: Word8) => EVM () Source #

Update program counter

exec1 :: EVM () Source #

Executes the EVM one step

transfer :: Addr -> Addr -> W256 -> EVM () Source #

callChecks :: (?op :: Word8) => Contract -> Word64 -> Addr -> Addr -> W256 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> (Word64 -> EVM ()) -> EVM () Source #

Checks a *CALL for failure; OOG, too many callframes, memory access etc.

precompiledContract :: (?op :: Word8) => Contract -> Word64 -> Addr -> Addr -> W256 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> EVM () Source #

executePrecompile :: (?op :: Word8) => Addr -> Word64 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> EVM () Source #

Opcode helper actions

noop :: Monad m => m () Source #

pushTo :: MonadState s m => Lens s s [a] [a] -> a -> m () Source #

pushToSequence :: MonadState s m => Setter s s (Seq a) (Seq a) -> a -> m () Source #

branch :: CodeLocation -> Expr EWord -> (Bool -> EVM ()) -> EVM () Source #

fetchAccount :: Addr -> (Contract -> EVM ()) -> EVM () Source #

Construct RPC Query and halt execution until resolved

accessStorage :: Addr -> Expr EWord -> (Expr EWord -> EVM ()) -> EVM () Source #

How to finalize a transaction

loadContract :: Addr -> EVM () Source #

Loads the selected contract as the current contract to execute

limitStack :: Int -> EVM () -> EVM () Source #

notStatic :: EVM () -> EVM () Source #

burn :: Word64 -> EVM () -> EVM () Source #

Burn gas, failing if insufficient gas is available

forceConcrete :: Expr EWord -> String -> (W256 -> EVM ()) -> EVM () Source #

forceConcrete2 :: (Expr EWord, Expr EWord) -> String -> ((W256, W256) -> EVM ()) -> EVM () Source #

Substate manipulation

accessAndBurn :: Addr -> EVM () -> EVM () Source #

accessAccountForGas :: Addr -> EVM Bool Source #

returns a wrapped boolean- if true, this address has been touched before in the txn (warm gas cost as in EIP 2929) otherwise cold

accessStorageForGas :: Addr -> Expr EWord -> EVM Bool Source #

returns a wrapped boolean- if true, this slot has been touched before in the txn (warm gas cost as in EIP 2929) otherwise cold

Cheat codes

cheat :: (?op :: Word8) => (W256, W256) -> (W256, W256) -> EVM () Source #

General call implementation ("delegateCall")

delegateCall :: (?op :: Word8) => Contract -> Word64 -> Expr EWord -> Expr EWord -> W256 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> (Addr -> EVM ()) -> EVM () Source #

create :: (?op :: Word8) => Addr -> Contract -> W256 -> Word64 -> W256 -> [Expr EWord] -> Addr -> Expr Buf -> EVM () Source #

replaceCode :: Addr -> ContractCode -> EVM () Source #

Replace a contract's code, like when CREATE returns from the constructor code.

VM error implementation

wrap :: Typeable a => [Expr a] -> [SomeExpr] Source #

data FrameResult Source #

A stack frame can be popped in three ways.

Constructors

FrameReturned (Expr Buf)

STOP, RETURN, or no more code

FrameReverted (Expr Buf)

REVERT

FrameErrored EvmError

Any other error

Instances

Instances details
Show FrameResult Source # 
Instance details

Defined in EVM

finishFrame :: FrameResult -> EVM () Source #

This function defines how to pop the current stack frame in either of the ways specified by FrameResult.

It also handles the case when the current stack frame is the only one; in this case, we set the final _result of the VM execution.

Memory helpers

Tracing

Stack manipulation

push :: W256 -> EVM () Source #

stackOp1 :: (?op :: Word8) => Word64 -> (Expr EWord -> Expr EWord) -> EVM () Source #

stackOp2 :: (?op :: Word8) => Word64 -> ((Expr EWord, Expr EWord) -> Expr EWord) -> EVM () Source #

stackOp3 :: (?op :: Word8) => Word64 -> ((Expr EWord, Expr EWord, Expr EWord) -> Expr EWord) -> EVM () Source #

Bytecode data functions

use' :: (VM -> a) -> EVM a Source #

Gas cost calculation helpers

opslen :: ContractCode -> Int Source #

The length of the code ignoring any constructor args. This represents the region that can contain executable opcodes

codelen :: ContractCode -> Expr EWord Source #

The length of the code including any constructor args. This can return an abstract value

Arithmetic

ceilDiv :: (Num a, Integral a) => a -> a -> a Source #

allButOne64th :: (Num a, Integral a) => a -> a Source #

log2 :: FiniteBits b => b -> Int Source #