hevm-0.52.0: Symbolic EVM Evaluator
Safe HaskellSafe-Inferred
LanguageGHC2021

EVM

Synopsis

Documentation

bytecode :: Getter Contract (Maybe (Expr Buf)) Source #

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

Data accessors

Data constructors

makeVm :: VMOpts -> ST s (VM s) Source #

unknownContract :: Expr EAddr -> Contract Source #

Initialize an abstract contract with unknown code

abstractContract :: ContractCode -> Expr EAddr -> Contract Source #

Initialize an abstract contract with known code

emptyContract :: Contract Source #

Initialize an empty contract without code

initialContract :: ContractCode -> Contract Source #

Initialize empty contract with given code

Opcode dispatch (exec1)

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

Update program counter

exec1 :: EVM s () Source #

Executes the EVM one step

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

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

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

executePrecompile :: (?op :: Word8) => Addr -> Word64 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> EVM s () 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 #

query :: Query s -> EVM s () Source #

choose :: Choose s -> EVM s () Source #

branch :: forall s. Expr EWord -> (Bool -> EVM s ()) -> EVM s () Source #

fetchAccount :: Expr EAddr -> (Contract -> EVM s ()) -> EVM s () Source #

Construct RPC Query and halt execution until resolved

accessStorage :: Expr EAddr -> Expr EWord -> (Expr EWord -> EVM s ()) -> EVM s () Source #

How to finalize a transaction

loadContract :: Expr EAddr -> State (VM s) () Source #

Loads the selected contract as the current contract to execute

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

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

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

Burn gas, failing if insufficient gas is available

forceAddr :: Expr EWord -> String -> (Expr EAddr -> EVM s ()) -> EVM s () Source #

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

forceConcreteAddr :: Expr EAddr -> String -> (Addr -> EVM s ()) -> EVM s () Source #

forceConcreteAddr2 :: (Expr EAddr, Expr EAddr) -> String -> ((Addr, Addr) -> EVM s ()) -> EVM s () Source #

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

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

forceConcreteBuf :: Expr Buf -> String -> (ByteString -> EVM s ()) -> EVM s () Source #

Substate manipulation

refund :: Word64 -> EVM s () Source #

accessAndBurn :: Expr EAddr -> EVM s () -> EVM s () Source #

accessAccountForGas :: Expr EAddr -> EVM s 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 :: Expr EAddr -> Expr EWord -> EVM s 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 s () Source #

type CheatAction s = Expr EWord -> Expr EWord -> Expr Buf -> EVM s () Source #

General call implementation ("delegateCall")

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

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

parseInitCode :: Expr Buf -> Maybe ContractCode Source #

Parses a raw Buf into an InitCode

solidity implements constructor args by appending them to the end of the initcode. we support this internally by treating initCode as a concrete region (initCode) followed by a potentially symbolic region (arguments).

when constructing a contract that has symbolic construcor args, we need to apply some heuristics to convert the (unstructured) initcode in memory into this structured representation. The (unsound, bad, hacky) way that we do this, is by: looking for the first potentially symbolic byte in the input buffer and then splitting it there into code / data.

replaceCode :: Expr EAddr -> ContractCode -> EVM s () 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 s () 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

accessMemoryRange :: W256 -> W256 -> EVM s () -> EVM s () Source #

accessMemoryWord :: W256 -> EVM s () -> EVM s () Source #

Tracing

Stack manipulation

push :: W256 -> EVM s () Source #

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

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

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

Bytecode data functions

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

checkJump :: Int -> [Expr EWord] -> EVM s () Source #

noJumpIntoInitData :: Int -> EVM s () -> EVM s () 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 #