| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
EVM
Contents
- 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
Synopsis
- blankState :: FrameState
- bytecode :: Getter Contract (Expr Buf)
- 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 => Lens s s [a] [a] -> a -> m ()
- pushToSequence :: MonadState s m => Setter s s (Seq a) (Seq a) -> a -> m ()
- getCodeLocation :: VM -> CodeLocation
- query :: Query -> EVM ()
- choose :: Choose -> EVM ()
- 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 FunctionSelector CheatAction
- 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 :: EvmError -> EVM ()
- partial :: PartialExec -> EVM ()
- wrap :: Typeable a => [Expr a] -> [SomeExpr]
- underrun :: EVM ()
- data FrameResult
- = FrameReturned (Expr Buf)
- | FrameReverted (Expr Buf)
- | FrameErrored EvmError
- finishFrame :: FrameResult -> EVM ()
- accessUnboundedMemoryRange :: Word64 -> Word64 -> EVM () -> EVM ()
- accessMemoryRange :: W256 -> W256 -> EVM () -> EVM ()
- accessMemoryWord :: 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 :: TraceData -> EVM Trace
- pushTrace :: TraceData -> EVM ()
- insertTrace :: TraceData -> EVM ()
- popTrace :: EVM ()
- zipperRootForest :: TreePos Empty a -> Forest a
- traceForest :: VM -> Forest Trace
- traceTopLog :: [Expr Log] -> EVM ()
- push :: W256 -> EVM ()
- pushSym :: Expr EWord -> EVM ()
- stackOp1 :: (?op :: Word8) => Word64 -> (Expr EWord -> Expr EWord) -> EVM ()
- stackOp2 :: (?op :: Word8) => Word64 -> ((Expr EWord, Expr EWord) -> Expr EWord) -> EVM ()
- stackOp3 :: (?op :: Word8) => Word64 -> ((Expr EWord, Expr EWord, Expr EWord) -> Expr EWord) -> EVM ()
- use' :: (VM -> a) -> EVM a
- checkJump :: Int -> [Expr EWord] -> EVM ()
- isValidJumpDest :: VM -> Int -> Bool
- opSize :: Word8 -> Int
- mkOpIxMap :: ContractCode -> Vector Int
- vmOp :: VM -> Maybe Op
- vmOpIx :: VM -> Maybe Int
- 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
- hashcode :: ContractCode -> Expr EWord
- opslen :: ContractCode -> Int
- codelen :: ContractCode -> Expr EWord
- toBuf :: ContractCode -> Expr Buf
- codeloc :: EVM CodeLocation
- ceilDiv :: (Num a, Integral a) => a -> a -> a
- allButOne64th :: (Num a, Integral a) => a -> a
- log2 :: FiniteBits b => b -> Int
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)
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 => Lens s s [a] [a] -> a -> m () Source #
pushToSequence :: MonadState s m => Setter 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
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
partial :: PartialExec -> EVM () 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
| Show FrameResult Source # | |
Defined in EVM Methods 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
Tracing
insertTrace :: TraceData -> EVM () Source #
Stack manipulation
stackOp3 :: (?op :: Word8) => 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 #
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
allButOne64th :: (Num a, Integral a) => a -> a Source #
log2 :: FiniteBits b => b -> Int Source #