Skip to content

Commit

Permalink
Add @arcz 's suggestions
Browse files Browse the repository at this point in the history
  • Loading branch information
samalws-tob committed Jan 10, 2024
1 parent 5142202 commit 6a0e32f
Show file tree
Hide file tree
Showing 6 changed files with 11 additions and 12 deletions.
3 changes: 1 addition & 2 deletions lib/Echidna/Campaign.hs
Original file line number Diff line number Diff line change
Expand Up @@ -156,14 +156,13 @@ randseq deployedContracts world = do

let
mutConsts = env.cfg.campaignConf.mutConsts
txConf = env.cfg.txConf
seqLen = env.cfg.campaignConf.seqLen

-- TODO: include reproducer when optimizing
--let rs = filter (not . null) $ map (.testReproducer) $ ca._tests

-- Generate new random transactions
randTxs <- replicateM seqLen (genTx world txConf deployedContracts)
randTxs <- replicateM seqLen (genTx world deployedContracts)
-- Generate a random mutator
cmut <- if seqLen == 1 then seqMutatorsStateless (fromConsts mutConsts)
else seqMutatorsStateful (fromConsts mutConsts)
Expand Down
4 changes: 2 additions & 2 deletions lib/Echidna/Exec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -287,7 +287,7 @@ execTxWithCov tx = do
let (pc, opIx, depth) = currentCovLoc vm
contract = currentContract vm

maybeMetaVec <- lookupUsingCodehashOrInsert env.codehashMap contract env.dapp env.coverageRef $ do
maybeCovVec <- lookupUsingCodehashOrInsert env.codehashMap contract env.dapp env.coverageRef $ do
let size = BS.length . forceBuf . fromJust . view bytecode $ contract
if size == 0 then pure Nothing else do
-- IO for making a new vec
Expand All @@ -296,7 +296,7 @@ execTxWithCov tx = do
forM_ [0..size-1] $ \i -> VMut.write vec i (-1, 0, 0)
pure $ Just vec

case maybeMetaVec of
case maybeCovVec of
Nothing -> pure ()
Just vec -> do
-- TODO: no-op when pc is out-of-bounds. This shouldn't happen but
Expand Down
6 changes: 3 additions & 3 deletions lib/Echidna/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import Echidna.Orphans.JSON ()
import Echidna.Symbolic (forceWord, forceAddr)
import Echidna.Types (fromEVM)
import Echidna.Types.CodehashMap (lookupUsingCodehash)
import Echidna.Types.Config (Env(..))
import Echidna.Types.Config (Env(..), EConfig(..))
import Echidna.Types.Random
import Echidna.Types.Signature
(SignatureMap, SolCall, ContractA)
Expand Down Expand Up @@ -58,11 +58,11 @@ getSignatures hmm (Just lmm) =
genTx
:: (MonadIO m, MonadRandom m, MonadState WorkerState m, MonadReader Env m)
=> World
-> TxConf
-> Map (Expr EAddr) Contract
-> m Tx
genTx world txConf deployedContracts = do
genTx world deployedContracts = do
env <- ask
let txConf = env.cfg.txConf
genDict <- gets (.genDict)
sigMap <- getSignatures world.highSignatureMap world.lowSignatureMap
sender <- rElem' world.senders
Expand Down
6 changes: 3 additions & 3 deletions lib/Echidna/Types/CodehashMap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,14 +8,14 @@ import EVM.Dapp (DappInfo, findSrc)
import EVM.Solidity (SolcContract(..))
import EVM.Types (Contract(..), W256)

-- | Map from contracts' codehashes to their "real" (compile-time) codehash.
-- | Map from contracts' codehashes to their compile-time codehash.
-- This is relevant when the immutables solidity feature is used;
-- when this feature is not used, the map will just end up being an identity map.
-- `CodehashMap` is used in signature map and coverage map lookups.
type CodehashMap = IORef (Map W256 W256)

-- | Lookup a codehash in the `CodehashMap`.
-- In the case that it's not found, find the "real" (compile-time) codehash and add it to the map.
-- In the case that it's not found, find the compile-time codehash and add it to the map.
-- This is done using hevm's `findSrc` function.
lookupCodehash :: CodehashMap -> W256 -> Contract -> DappInfo -> IO W256
lookupCodehash chmap codehash contr dapp = do
Expand All @@ -29,7 +29,7 @@ lookupCodehash chmap codehash contr dapp = do

-- | Given a map from codehash to some values of type `a`, lookup a contract in the map using its codehash.
-- In current use, the `Map W256 a` will be either a `SignatureMap` or a `CoverageMap`.
-- Returns the "real" codehash, and the map entry if it is found.
-- Returns the compile-time codehash, and the map entry if it is found.
lookupUsingCodehash :: CodehashMap -> Contract -> DappInfo -> Map W256 a -> IO (W256, Maybe a)
lookupUsingCodehash chmap contr dapp mapVal =
ifNotFound codehash $ do
Expand Down
2 changes: 1 addition & 1 deletion lib/Echidna/Types/Coverage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import EVM.Types (W256)
import Echidna.Types.Tx (TxResult)

-- | Map with the coverage information needed for fuzzing and source code printing.
-- Indexed by contracts' "real" codehash; see `CodehashMap`.
-- Indexed by contracts' compile-time codehash; see `CodehashMap`.
type CoverageMap = Map W256 (IOVector CoverageInfo)

-- | Basic coverage information
Expand Down
2 changes: 1 addition & 1 deletion lib/Echidna/Types/Signature.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ type SolCall = (FunctionName, [AbiValue])
-- | A contract is just an address with an ABI (for our purposes).
type ContractA = (Addr, NonEmpty SolSignature)

-- | Indexed by contracts' "real" codehash; see `CodehashMap`.
-- | Indexed by contracts' compile-time codehash; see `CodehashMap`.
type SignatureMap = Map W256 (NonEmpty SolSignature)

knownBzzrPrefixes :: [ByteString]
Expand Down

0 comments on commit 6a0e32f

Please sign in to comment.