Skip to content

Commit 63ff75a

Browse files
committed
corpus mutation to remove reverts
1 parent 73819e3 commit 63ff75a

File tree

6 files changed

+24
-16
lines changed

6 files changed

+24
-16
lines changed

lib/Echidna/Campaign.hs

+7-3
Original file line numberDiff line numberDiff line change
@@ -420,9 +420,13 @@ callseq vm txSeq = do
420420

421421
-- | Add transactions to the corpus discarding reverted ones
422422
addToCorpus :: Int -> [(Tx, (VMResult Concrete RealWorld, Gas))] -> Corpus -> Corpus
423-
addToCorpus n res corpus =
424-
if null rtxs then corpus else Set.insert (n, rtxs) corpus
425-
where rtxs = fst <$> res
423+
addToCorpus n res corpus@(corpusTxs, revertingTxSet) =
424+
if null rtxs then corpus else (Set.insert (n, rtxs) corpusTxs, Set.union revertingTxSet $ Set.fromList revertingTxsHere)
425+
where
426+
rtxs = fst <$> res
427+
revertingTxsHere = fst <$> filter (not . isSuccess . fst . snd) res
428+
isSuccess (VMSuccess _) = True
429+
isSuccess _ = False
426430

427431
-- | Execute a transaction, capturing the PC and codehash of each instruction
428432
-- executed, saving the transaction if it finds new coverage.

lib/Echidna/Mutator/Corpus.hs

+11-8
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
module Echidna.Mutator.Corpus where
22

33
import Control.Monad.Random.Strict (MonadRandom, getRandomR, weighted)
4-
import Data.Set (Set)
54
import Data.Set qualified as Set
65

76
import Echidna.Mutator.Array
@@ -11,10 +10,10 @@ import Echidna.Types.Tx (Tx)
1110
import Echidna.Types.Corpus
1211

1312
defaultMutationConsts :: Num a => MutationConsts a
14-
defaultMutationConsts = (1, 1, 1, 1)
13+
defaultMutationConsts = (1, 1, 1, 1, 1)
1514

1615
fromConsts :: Num a => MutationConsts Integer -> MutationConsts a
17-
fromConsts (a, b, c, d) = let fi = fromInteger in (fi a, fi b, fi c, fi d)
16+
fromConsts (a, b, c, d, e) = let fi = fromInteger in (fi a, fi b, fi c, fi d, fi e)
1817

1918
data TxsMutation = Identity
2019
| Shrinking
@@ -28,6 +27,7 @@ data CorpusMutation = RandomAppend TxsMutation
2827
| RandomPrepend TxsMutation
2928
| RandomSplice
3029
| RandomInterleave
30+
| RemoveReverts
3131
deriving (Eq, Ord, Show)
3232

3333
mutator :: MonadRandom m => TxsMutation -> [Tx] -> m [Tx]
@@ -63,10 +63,10 @@ selectAndCombine f ql corpus gtxs = do
6363

6464
selectFromCorpus
6565
:: MonadRandom m
66-
=> Set (Int, [Tx])
66+
=> Corpus
6767
-> m [Tx]
6868
selectFromCorpus =
69-
weighted . map (\(i, txs) -> (txs, fromIntegral i)) . Set.toDescList
69+
weighted . map (\(i, txs) -> (txs, fromIntegral i)) . Set.toDescList . fst
7070

7171
getCorpusMutation
7272
:: MonadRandom m
@@ -85,12 +85,13 @@ getCorpusMutation (RandomPrepend m) = mut (mutator m)
8585
pure . take ql $ take k gtxs ++ rtxs'
8686
getCorpusMutation RandomSplice = selectAndCombine spliceAtRandom
8787
getCorpusMutation RandomInterleave = selectAndCombine interleaveAtRandom
88+
getCorpusMutation RemoveReverts = \_ (_, revertingTxs) txs -> pure $ filter (not . flip Set.member revertingTxs) txs
8889

8990
seqMutatorsStateful
9091
:: MonadRandom m
9192
=> MutationConsts Rational
9293
-> m CorpusMutation
93-
seqMutatorsStateful (c1, c2, c3, c4) = weighted
94+
seqMutatorsStateful (c1, c2, c3, c4, c5) = weighted
9495
[(RandomAppend Identity, 800),
9596
(RandomPrepend Identity, 200),
9697

@@ -107,14 +108,16 @@ seqMutatorsStateful (c1, c2, c3, c4) = weighted
107108
(RandomPrepend Deletion, c3),
108109

109110
(RandomSplice, c4),
110-
(RandomInterleave, c4)
111+
(RandomInterleave, c4),
112+
113+
(RemoveReverts, c5)
111114
]
112115

113116
seqMutatorsStateless
114117
:: MonadRandom m
115118
=> MutationConsts Rational
116119
-> m CorpusMutation
117-
seqMutatorsStateless (c1, c2, _, _) = weighted
120+
seqMutatorsStateless (c1, c2, _, _, _) = weighted
118121
[(RandomAppend Identity, 800),
119122
(RandomPrepend Identity, 200),
120123

lib/Echidna/Types.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ instance Exception ExecException
3131

3232
type Gas = Word64
3333

34-
type MutationConsts a = (a, a, a, a)
34+
type MutationConsts a = (a, a, a, a, a)
3535

3636
-- | Transform an EVM action from HEVM to our MonadState VM
3737
fromEVM :: (MonadIO m, MonadState (VM Concrete RealWorld) m) => EVM Concrete RealWorld r -> m r

lib/Echidna/Types/Corpus.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,8 @@ module Echidna.Types.Corpus where
33
import Data.Set (Set, size)
44
import Echidna.Types.Tx (Tx)
55

6-
type Corpus = Set (Int, [Tx])
6+
-- (set of transaction sequences in corpus, set of transactions that cause reverts (used for RemoveReverts))
7+
type Corpus = (Set (Int, [Tx]), Set Tx)
78

89
corpusSize :: Corpus -> Int
9-
corpusSize = size
10+
corpusSize = size . fst

src/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@ main = withUtf8 $ withCP65001 $ do
9595
liftIO $ writeFile file (ppTestName test <> ": " <> txsPrinted)
9696

9797
measureIO cfg.solConf.quiet "Saving corpus" $ do
98-
corpus <- readIORef env.corpusRef
98+
(corpus, _) <- readIORef env.corpusRef
9999
saveTxs env (dir </> "coverage") (snd <$> Set.toList corpus)
100100

101101
-- TODO: We use the corpus dir to save coverage reports which is confusing.

tests/solidity/basic/default.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ corpusDir: null
8080
# list of file formats to save coverage reports in; default is all possible formats
8181
coverageFormats: ["txt","html","lcov"]
8282
# constants for corpus mutations (for experimentation only)
83-
mutConsts: [1, 1, 1, 1]
83+
mutConsts: [1, 1, 1, 1, 1]
8484
# maximum value to send to payable functions
8585
maxValue: 100000000000000000000 # 100 eth
8686
# URL to fetch contracts over RPC

0 commit comments

Comments
 (0)