Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
- Data types
- Data accessors
- Data constructors
- Opcode dispatch (exec1)
- Opcode helper actions
- How to finalize a transaction
- Substate manipulation
- Cheat codes
- General call implementation ("delegateCall")
- VM error implementation
- Memory helpers
- Tracing
- Stack manipulation
- Bytecode data functions
- Gas cost calculation helpers
- Arithmetic
- Emacs setup
Synopsis
- data Error
- = BalanceTooLow W256 W256
- | UnrecognizedOpcode Word8
- | SelfDestruction
- | StackUnderrun
- | BadJumpDestination
- | Revert (Expr Buf)
- | OutOfGas Word64 Word64
- | BadCheatCode (Maybe Word32)
- | StackLimitExceeded
- | IllegalOverflow
- | Query Query
- | Choose Choose
- | StateChangeWhileStatic
- | InvalidMemoryAccess
- | CallDepthLimitReached
- | MaxCodeSizeExceeded W256 W256
- | InvalidFormat
- | PrecompileFailure
- | forall a. UnexpectedSymbolicArg Int String [Expr a]
- | DeadPath
- | NotUnique (Expr EWord)
- | SMTTimeout
- | FFI [AbiValue]
- | NonceOverflow
- data VMResult
- data VM = VM {}
- data Trace = Trace {}
- data TraceData
- = EventTrace (Expr EWord) (Expr Buf) [Expr EWord]
- | FrameTrace FrameContext
- | QueryTrace Query
- | ErrorTrace Error
- | EntryTrace Text
- | ReturnTrace (Expr Buf) FrameContext
- data Query where
- PleaseFetchContract :: Addr -> (Contract -> EVM ()) -> Query
- PleaseFetchSlot :: Addr -> W256 -> (W256 -> EVM ()) -> Query
- PleaseAskSMT :: Expr EWord -> [Prop] -> (BranchCondition -> EVM ()) -> Query
- PleaseDoFFI :: [String] -> (ByteString -> EVM ()) -> Query
- data Choose where
- type EVM a = State VM a
- type CodeLocation = (Addr, Int)
- data BranchCondition
- = Case Bool
- | Unknown
- | Inconsistent
- data IsUnique a
- = Unique a
- | Multiple
- | InconsistentU
- | TimeoutU
- data Cache = Cache {
- _fetchedContracts :: Map Addr Contract
- _fetchedStorage :: Map W256 (Map W256 W256)
- _path :: Map (CodeLocation, Int) Bool
- data StorageBase
- data VMOpts = VMOpts {
- vmoptContract :: Contract
- vmoptCalldata :: (Expr Buf, [Prop])
- vmoptStorageBase :: StorageBase
- vmoptValue :: Expr EWord
- vmoptPriorityFee :: W256
- vmoptAddress :: Addr
- vmoptCaller :: Expr EWord
- vmoptOrigin :: Addr
- vmoptGas :: Word64
- vmoptGaslimit :: Word64
- vmoptNumber :: W256
- vmoptTimestamp :: Expr EWord
- vmoptCoinbase :: Addr
- vmoptPrevRandao :: W256
- vmoptMaxCodeSize :: W256
- vmoptBlockGaslimit :: Word64
- vmoptGasprice :: W256
- vmoptBaseFee :: W256
- vmoptSchedule :: FeeSchedule Word64
- vmoptChainId :: W256
- vmoptCreate :: Bool
- vmoptTxAccessList :: Map Addr [W256]
- vmoptAllowFFI :: Bool
- data Frame = Frame {}
- data FrameContext
- = CreationContext { }
- | CallContext { }
- data FrameState = FrameState {}
- data TxState = TxState {}
- data SubState = SubState {
- _selfdestructs :: [Addr]
- _touchedAccounts :: [Addr]
- _accessedAddresses :: Set Addr
- _accessedStorageKeys :: Set (Addr, W256)
- _refunds :: [(Addr, Word64)]
- data ContractCode
- data RuntimeCode
- data Contract = Contract {}
- data StorageModel
- data Env = Env {
- _contracts :: Map Addr Contract
- _chainId :: W256
- _storage :: Expr Storage
- _origStorage :: Map W256 (Map W256 W256)
- _sha3Crack :: Map W256 ByteString
- data Block = Block {
- _coinbase :: Addr
- _timestamp :: Expr EWord
- _number :: W256
- _prevRandao :: W256
- _gaslimit :: Word64
- _baseFee :: W256
- _maxCodeSize :: W256
- _schedule :: FeeSchedule Word64
- blankState :: FrameState
- static :: Lens' FrameState Bool
- stack :: Lens' FrameState [Expr 'EWord]
- returndata :: Lens' FrameState (Expr 'Buf)
- pc :: Lens' FrameState Int
- memorySize :: Lens' FrameState Word64
- memory :: Lens' FrameState (Expr 'Buf)
- gas :: Lens' FrameState Word64
- contract :: Lens' FrameState Addr
- codeContract :: Lens' FrameState Addr
- code :: Lens' FrameState ContractCode
- callvalue :: Lens' FrameState (Expr 'EWord)
- caller :: Lens' FrameState (Expr 'EWord)
- calldata :: Lens' FrameState (Expr 'Buf)
- frameState :: Lens' Frame FrameState
- frameContext :: Lens' Frame FrameContext
- timestamp :: Lens' Block (Expr 'EWord)
- schedule :: Lens' Block (FeeSchedule Word64)
- prevRandao :: Lens' Block W256
- number :: Lens' Block W256
- maxCodeSize :: Lens' Block W256
- gaslimit :: Lens' Block Word64
- coinbase :: Lens' Block Addr
- baseFee :: Lens' Block W256
- value :: Lens' TxState (Expr 'EWord)
- txgaslimit :: Lens' TxState Word64
- txReversion :: Lens' TxState (Map Addr Contract)
- txPriorityFee :: Lens' TxState W256
- toAddr :: Lens' TxState Addr
- substate :: Lens' TxState SubState
- origin :: Lens' TxState Addr
- isCreate :: Lens' TxState Bool
- gasprice :: Lens' TxState W256
- touchedAccounts :: Lens' SubState [Addr]
- selfdestructs :: Lens' SubState [Addr]
- refunds :: Lens' SubState [(Addr, Word64)]
- accessedStorageKeys :: Lens' SubState (Set (Addr, W256))
- accessedAddresses :: Lens' SubState (Set Addr)
- opIxMap :: Lens' Contract (Vector Int)
- nonce :: Lens' Contract W256
- external :: Lens' Contract Bool
- contractcode :: Lens' Contract ContractCode
- codehash :: Lens' Contract (Expr 'EWord)
- codeOps :: Lens' Contract (Vector (Int, Op))
- balance :: Lens' Contract W256
- storage :: Lens' Env (Expr 'Storage)
- sha3Crack :: Lens' Env (Map W256 ByteString)
- origStorage :: Lens' Env (Map W256 (Map W256 W256))
- contracts :: Lens' Env (Map Addr Contract)
- chainId :: Lens' Env W256
- path :: Lens' Cache (Map (CodeLocation, Int) Bool)
- fetchedStorage :: Lens' Cache (Map W256 (Map W256 W256))
- fetchedContracts :: Lens' Cache (Map Addr Contract)
- traceOpIx :: Lens' Trace Int
- traceData :: Lens' Trace TraceData
- traceContract :: Lens' Trace Contract
- tx :: Lens' VM TxState
- traces :: Lens' VM (TreePos Empty Trace)
- state :: Lens' VM FrameState
- result :: Lens' VM (Maybe VMResult)
- logs :: Lens' VM [Expr 'Log]
- keccakEqs :: Lens' VM [Prop]
- iterations :: Lens' VM (Map CodeLocation Int)
- frames :: Lens' VM [Frame]
- env :: Lens' VM Env
- constraints :: Lens' VM [Prop]
- cache :: Lens' VM Cache
- burned :: Lens' VM Word64
- block :: Lens' VM Block
- allowFFI :: Lens' VM Bool
- bytecode :: Getter Contract (Expr Buf)
- unifyCachedStorage :: Map W256 W256 -> Map W256 W256 -> Map W256 W256
- unifyCachedContract :: Contract -> Contract -> Contract
- currentContract :: VM -> Maybe Contract
- makeVm :: VMOpts -> VM
- initialContract :: ContractCode -> Contract
- next :: (?op :: Word8) => EVM ()
- exec1 :: EVM ()
- transfer :: Addr -> Addr -> W256 -> EVM ()
- callChecks :: (?op :: Word8) => Contract -> Word64 -> Addr -> Addr -> W256 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> (Word64 -> EVM ()) -> EVM ()
- precompiledContract :: (?op :: Word8) => Contract -> Word64 -> Addr -> Addr -> W256 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> EVM ()
- executePrecompile :: (?op :: Word8) => Addr -> Word64 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> EVM ()
- truncpadlit :: Int -> ByteString -> ByteString
- lazySlice :: W256 -> W256 -> ByteString -> ByteString
- parseModexpLength :: ByteString -> (W256, W256, W256)
- isZero :: W256 -> W256 -> ByteString -> Bool
- asInteger :: ByteString -> Integer
- noop :: Monad m => m ()
- pushTo :: MonadState s m => ASetter s s [a] [a] -> a -> m ()
- pushToSequence :: MonadState s m => ASetter s s (Seq a) (Seq a) -> a -> m ()
- getCodeLocation :: VM -> CodeLocation
- branch :: CodeLocation -> Expr EWord -> (Bool -> EVM ()) -> EVM ()
- fetchAccount :: Addr -> (Contract -> EVM ()) -> EVM ()
- accessStorage :: Addr -> Expr EWord -> (Expr EWord -> EVM ()) -> EVM ()
- accountExists :: Addr -> VM -> Bool
- accountEmpty :: Contract -> Bool
- finalize :: EVM ()
- loadContract :: Addr -> EVM ()
- limitStack :: Int -> EVM () -> EVM ()
- notStatic :: EVM () -> EVM ()
- burn :: Word64 -> EVM () -> EVM ()
- forceConcrete :: Expr EWord -> String -> (W256 -> EVM ()) -> EVM ()
- forceConcrete2 :: (Expr EWord, Expr EWord) -> String -> ((W256, W256) -> EVM ()) -> EVM ()
- forceConcrete3 :: (Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256) -> EVM ()) -> EVM ()
- forceConcrete4 :: (Expr EWord, Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256, W256) -> EVM ()) -> EVM ()
- forceConcrete5 :: (Expr EWord, Expr EWord, Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256, W256, W256) -> EVM ()) -> EVM ()
- forceConcrete6 :: (Expr EWord, Expr EWord, Expr EWord, Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256, W256, W256, W256) -> EVM ()) -> EVM ()
- forceConcreteBuf :: Expr Buf -> String -> (ByteString -> EVM ()) -> EVM ()
- refund :: Word64 -> EVM ()
- unRefund :: Word64 -> EVM ()
- touchAccount :: Addr -> EVM ()
- selfdestruct :: Addr -> EVM ()
- accessAndBurn :: Addr -> EVM () -> EVM ()
- accessAccountForGas :: Addr -> EVM Bool
- accessStorageForGas :: Addr -> Expr EWord -> EVM Bool
- cheatCode :: Addr
- cheat :: (?op :: Word8) => (W256, W256) -> (W256, W256) -> EVM ()
- type CheatAction = Expr EWord -> Expr EWord -> Expr Buf -> EVM ()
- cheatActions :: Map Word32 CheatAction
- ethsign :: PrivateKey -> Digest Keccak_256 -> Signature
- delegateCall :: (?op :: Word8) => Contract -> Word64 -> Expr EWord -> Expr EWord -> W256 -> W256 -> W256 -> W256 -> W256 -> [Expr EWord] -> (Addr -> EVM ()) -> EVM ()
- collision :: Maybe Contract -> Bool
- create :: (?op :: Word8) => Addr -> Contract -> Word64 -> W256 -> [Expr EWord] -> Addr -> Expr Buf -> EVM ()
- replaceCode :: Addr -> ContractCode -> EVM ()
- replaceCodeOfSelf :: ContractCode -> EVM ()
- resetState :: EVM ()
- vmError :: Error -> EVM ()
- underrun :: EVM ()
- data FrameResult
- = FrameReturned (Expr Buf)
- | FrameReverted (Expr Buf)
- | FrameErrored Error
- finishFrame :: FrameResult -> EVM ()
- accessUnboundedMemoryRange :: FeeSchedule Word64 -> Word64 -> Word64 -> EVM () -> EVM ()
- accessMemoryRange :: FeeSchedule Word64 -> W256 -> W256 -> EVM () -> EVM ()
- accessMemoryWord :: FeeSchedule Word64 -> W256 -> EVM () -> EVM ()
- copyBytesToMemory :: Expr Buf -> Expr EWord -> Expr EWord -> Expr EWord -> EVM ()
- copyCallBytesToMemory :: Expr Buf -> Expr EWord -> Expr EWord -> Expr EWord -> EVM ()
- readMemory :: Expr EWord -> Expr EWord -> VM -> Expr Buf
- withTraceLocation :: MonadState VM m => TraceData -> m Trace
- pushTrace :: TraceData -> EVM ()
- insertTrace :: TraceData -> EVM ()
- popTrace :: EVM ()
- zipperRootForest :: TreePos Empty a -> Forest a
- traceForest :: VM -> Forest Trace
- traceTopLog :: MonadState VM m => [Expr Log] -> m ()
- push :: W256 -> EVM ()
- pushSym :: Expr EWord -> EVM ()
- stackOp1 :: (?op :: Word8) => (Expr EWord -> Word64) -> (Expr EWord -> Expr EWord) -> EVM ()
- stackOp2 :: (?op :: Word8) => ((Expr EWord, Expr EWord) -> Word64) -> ((Expr EWord, Expr EWord) -> Expr EWord) -> EVM ()
- stackOp3 :: (?op :: Word8) => ((Expr EWord, Expr EWord, Expr EWord) -> Word64) -> ((Expr EWord, Expr EWord, Expr EWord) -> Expr EWord) -> EVM ()
- checkJump :: Int -> [Expr EWord] -> EVM ()
- opSize :: Word8 -> Int
- mkOpIxMap :: ContractCode -> Vector Int
- vmOp :: VM -> Maybe Op
- vmOpIx :: VM -> Maybe Int
- opParams :: VM -> Map String (Expr EWord)
- readOp :: Word8 -> [Expr Byte] -> Op
- mkCodeOps :: ContractCode -> Vector (Int, Op)
- costOfCall :: FeeSchedule Word64 -> Bool -> W256 -> Word64 -> Word64 -> Addr -> EVM (Word64, Word64)
- costOfCreate :: FeeSchedule Word64 -> Word64 -> W256 -> (Word64, Word64)
- concreteModexpGasFee :: ByteString -> Word64
- costOfPrecompile :: FeeSchedule Word64 -> Addr -> Expr Buf -> Word64
- memoryCost :: FeeSchedule Word64 -> Word64 -> Word64
- ceilDiv :: (Num a, Integral a) => a -> a -> a
- allButOne64th :: (Num a, Integral a) => a -> a
- log2 :: FiniteBits b => b -> Int
- hashcode :: ContractCode -> Expr EWord
- opslen :: ContractCode -> Int
- codelen :: ContractCode -> Expr EWord
- toBuf :: ContractCode -> Expr Buf
- codeloc :: EVM CodeLocation
Data types
EVM failure modes
The possible result states of a VM
The state of a stepwise EVM execution
Trace | |
|
Queries halt execution until resolved through RPC calls or SMT queries
PleaseFetchContract :: Addr -> (Contract -> EVM ()) -> Query | |
PleaseFetchSlot :: Addr -> W256 -> (W256 -> EVM ()) -> Query | |
PleaseAskSMT :: Expr EWord -> [Prop] -> (BranchCondition -> EVM ()) -> Query | |
PleaseDoFFI :: [String] -> (ByteString -> EVM ()) -> Query |
type CodeLocation = (Addr, Int) Source #
data BranchCondition Source #
The possible return values of a SMT query
Instances
Show BranchCondition Source # | |
Defined in EVM showsPrec :: Int -> BranchCondition -> ShowS # show :: BranchCondition -> String # showList :: [BranchCondition] -> ShowS # |
The possible return values of a `is unique` SMT query
The cache is data that can be persisted for efficiency: any expensive query that is constant at least within a block.
Cache | |
|
data StorageBase Source #
Instances
Show StorageBase Source # | |
Defined in EVM showsPrec :: Int -> StorageBase -> ShowS # show :: StorageBase -> String # showList :: [StorageBase] -> ShowS # | |
Eq StorageBase Source # | |
Defined in EVM (==) :: StorageBase -> StorageBase -> Bool # (/=) :: StorageBase -> StorageBase -> Bool # |
A way to specify an initial VM state
VMOpts | |
|
An entry in the VM's "call/create stack"
data FrameContext Source #
Call/create info
Instances
Show FrameContext Source # | |
Defined in EVM showsPrec :: Int -> FrameContext -> ShowS # show :: FrameContext -> String # showList :: [FrameContext] -> ShowS # |
data FrameState Source #
The "registers" of the VM along with memory and data stack
Instances
Show FrameState Source # | |
Defined in EVM showsPrec :: Int -> FrameState -> ShowS # show :: FrameState -> String # showList :: [FrameState] -> ShowS # |
The state that spans a whole transaction
The "accrued substate" across a transaction
SubState | |
|
data ContractCode Source #
A contract is either in creation (running its "constructor") or
post-creation, and code in these two modes is treated differently
by instructions like EXTCODEHASH
, so we distinguish these two
code types.
The definition follows the structure of code output by solc. We need to use some heuristics here to deal with symbolic data regions that may be present in the bytecode since the fully abstract case is impractical:
- initcode has concrete code, followed by an abstract data "section"
- runtimecode has a fixed length, but may contain fixed size symbolic regions (due to immutable)
hopefully we do not have to deal with dynamic immutable before we get a real data section...
InitCode ByteString (Expr Buf) | Constructor code, during contract creation |
RuntimeCode RuntimeCode | Instance code, after contract creation |
Instances
Show ContractCode Source # | |
Defined in EVM showsPrec :: Int -> ContractCode -> ShowS # show :: ContractCode -> String # showList :: [ContractCode] -> ShowS # | |
Eq ContractCode Source # | |
Defined in EVM (==) :: ContractCode -> ContractCode -> Bool # (/=) :: ContractCode -> ContractCode -> Bool # | |
Ord ContractCode Source # | |
Defined in EVM compare :: ContractCode -> ContractCode -> Ordering # (<) :: ContractCode -> ContractCode -> Bool # (<=) :: ContractCode -> ContractCode -> Bool # (>) :: ContractCode -> ContractCode -> Bool # (>=) :: ContractCode -> ContractCode -> Bool # max :: ContractCode -> ContractCode -> ContractCode # min :: ContractCode -> ContractCode -> ContractCode # |
data RuntimeCode Source #
We have two variants here to optimize the fully concrete case. ConcreteRuntimeCode just wraps a ByteString SymbolicRuntimeCode is a fixed length vector of potentially symbolic bytes, which lets us handle symbolic pushdata (e.g. from immutable variables in solidity).
Instances
Show RuntimeCode Source # | |
Defined in EVM showsPrec :: Int -> RuntimeCode -> ShowS # show :: RuntimeCode -> String # showList :: [RuntimeCode] -> ShowS # | |
Eq RuntimeCode Source # | |
Defined in EVM (==) :: RuntimeCode -> RuntimeCode -> Bool # (/=) :: RuntimeCode -> RuntimeCode -> Bool # | |
Ord RuntimeCode Source # | |
Defined in EVM compare :: RuntimeCode -> RuntimeCode -> Ordering # (<) :: RuntimeCode -> RuntimeCode -> Bool # (<=) :: RuntimeCode -> RuntimeCode -> Bool # (>) :: RuntimeCode -> RuntimeCode -> Bool # (>=) :: RuntimeCode -> RuntimeCode -> Bool # max :: RuntimeCode -> RuntimeCode -> RuntimeCode # min :: RuntimeCode -> RuntimeCode -> RuntimeCode # |
A contract can either have concrete or symbolic storage depending on what type of execution we are doing data Storage = Concrete (Map Word Expr EWord) | Symbolic [(Expr EWord, Expr EWord)] (SArray (WordN 256) (WordN 256)) deriving (Show)
The state of a contract
data StorageModel Source #
When doing symbolic execution, we have three different ways to model the storage of contracts. This determines not only the initial contract storage model but also how RPC or state fetched contracts will be modeled.
ConcreteS | Uses |
SymbolicS | Uses |
InitialS | Uses |
Instances
Read StorageModel Source # | |
Defined in EVM readsPrec :: Int -> ReadS StorageModel # readList :: ReadS [StorageModel] # | |
Show StorageModel Source # | |
Defined in EVM showsPrec :: Int -> StorageModel -> ShowS # show :: StorageModel -> String # showList :: [StorageModel] -> ShowS # | |
ParseField StorageModel Source # | |
Various environmental data
Env | |
|
Data about the block
Block | |
|
returndata :: Lens' FrameState (Expr 'Buf) Source #
iterations :: Lens' VM (Map CodeLocation Int) Source #
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)
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 #
truncpadlit :: Int -> ByteString -> ByteString Source #
lazySlice :: W256 -> W256 -> ByteString -> ByteString Source #
parseModexpLength :: ByteString -> (W256, W256, W256) Source #
asInteger :: ByteString -> Integer Source #
Opcode helper actions
pushTo :: MonadState s m => ASetter s s [a] [a] -> a -> m () Source #
pushToSequence :: MonadState s m => ASetter s s (Seq a) (Seq a) -> a -> m () Source #
getCodeLocation :: VM -> CodeLocation Source #
fetchAccount :: Addr -> (Contract -> EVM ()) -> EVM () Source #
Construct RPC Query and halt execution until resolved
accountEmpty :: Contract -> Bool Source #
How to finalize a transaction
loadContract :: Addr -> EVM () Source #
Loads the selected contract as the current contract to execute
forceConcrete3 :: (Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256) -> EVM ()) -> EVM () Source #
forceConcrete4 :: (Expr EWord, Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256, W256) -> EVM ()) -> EVM () Source #
forceConcrete5 :: (Expr EWord, Expr EWord, Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256, W256, W256) -> EVM ()) -> EVM () Source #
forceConcrete6 :: (Expr EWord, Expr EWord, Expr EWord, Expr EWord, Expr EWord, Expr EWord) -> String -> ((W256, W256, W256, W256, W256, W256) -> EVM ()) -> EVM () Source #
forceConcreteBuf :: Expr Buf -> String -> (ByteString -> EVM ()) -> EVM () Source #
Substate manipulation
touchAccount :: Addr -> EVM () Source #
selfdestruct :: Addr -> 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
ethsign :: PrivateKey -> Digest Keccak_256 -> Signature Source #
We don't wanna introduce the machinery needed to sign with a random nonce, so we just use the same nonce every time (420). This is obviusly very insecure, but fine for testing purposes.
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 -> 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.
replaceCodeOfSelf :: ContractCode -> EVM () Source #
resetState :: EVM () Source #
VM error implementation
data FrameResult Source #
A stack frame can be popped in three ways.
FrameReturned (Expr Buf) | STOP, RETURN, or no more code |
FrameReverted (Expr Buf) | REVERT |
FrameErrored Error | Any other error |
Instances
Show FrameResult Source # | |
Defined in EVM showsPrec :: Int -> FrameResult -> ShowS # show :: FrameResult -> String # showList :: [FrameResult] -> ShowS # |
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
accessUnboundedMemoryRange :: FeeSchedule Word64 -> Word64 -> Word64 -> EVM () -> EVM () Source #
accessMemoryRange :: FeeSchedule Word64 -> W256 -> W256 -> EVM () -> EVM () Source #
accessMemoryWord :: FeeSchedule Word64 -> W256 -> EVM () -> EVM () Source #
Tracing
withTraceLocation :: MonadState VM m => TraceData -> m Trace Source #
insertTrace :: TraceData -> EVM () Source #
traceTopLog :: MonadState VM m => [Expr Log] -> m () Source #
Stack manipulation
stackOp1 :: (?op :: Word8) => (Expr EWord -> Word64) -> (Expr EWord -> Expr EWord) -> EVM () Source #
stackOp2 :: (?op :: Word8) => ((Expr EWord, Expr EWord) -> Word64) -> ((Expr EWord, Expr EWord) -> Expr EWord) -> EVM () Source #
stackOp3 :: (?op :: Word8) => ((Expr EWord, Expr EWord, Expr EWord) -> Word64) -> ((Expr EWord, Expr EWord, Expr EWord) -> Expr EWord) -> EVM () Source #
Bytecode data functions
Gas cost calculation helpers
costOfCall :: FeeSchedule Word64 -> Bool -> W256 -> Word64 -> Word64 -> Addr -> EVM (Word64, Word64) Source #
costOfCreate :: FeeSchedule Word64 -> Word64 -> W256 -> (Word64, Word64) Source #
costOfPrecompile :: FeeSchedule Word64 -> Addr -> Expr Buf -> Word64 Source #
memoryCost :: FeeSchedule Word64 -> Word64 -> Word64 Source #
Arithmetic
allButOne64th :: (Num a, Integral a) => a -> a Source #
log2 :: FiniteBits b => b -> Int Source #
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