Skip to content

Commit

Permalink
Add missing documentation (#1298)
Browse files Browse the repository at this point in the history
* initial documentation of shrink

* expanded documentation of generation and mutation
  • Loading branch information
ggrieco-tob authored Aug 20, 2024
1 parent 182580e commit 6956030
Show file tree
Hide file tree
Showing 2 changed files with 41 additions and 7 deletions.
20 changes: 16 additions & 4 deletions lib/Echidna/ABI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -153,14 +153,20 @@ mkDictValues =
fromValue (AbiInt _ n) = Just (fromIntegral n)
fromValue _ = Nothing

-- Generation (synthesis)

-- Generate a random integer using a pow scale:
getRandomPow :: (MonadRandom m) => Int -> m Integer
getRandomPow n = if n <= 0 then return 0 else
do
-- generate uniformly a number from 20 to n
mexp <- getRandomR (20, n)
-- generate uniformly a number from the range 2 ^ (mexp / 2) to 2 ^ mexp
getRandomR (2 ^ (mexp `div` 2), 2 ^ mexp)

-- Generate a random unsigned integer with the following distribution:
-- * 9% (2/21) uniformly from 0 to 1024
-- * 76% (16/21) uniformly from 0 to 2 ^ n - 5
-- * 9% (2/21) uniformly from 2 ^ n - 5 to 2 ^ n - 1.
-- * 4% (1/21) using the getRandomPow function
getRandomUint :: MonadRandom m => Int -> m Integer
getRandomUint n =
join $ Random.weighted
Expand All @@ -170,6 +176,9 @@ getRandomUint n =
, (getRandomPow (n - 5), 1)
]

-- | Generate a random signed integer with the following distribution:
-- * 10% uniformly from the range -1023 to 1023.
-- * 90% uniformly from the range -1 * 2 ^ n to 2 ^ (n - 1).
getRandomInt :: MonadRandom m => Int -> m Integer
getRandomInt n =
getRandomR =<< Random.weighted
Expand Down Expand Up @@ -310,8 +319,8 @@ mutateAbiValue = \case
\case 0 -> fixAbiInt n <$> mutateNum x
_ -> pure $ AbiInt n x

AbiAddress x -> pure $ AbiAddress x
AbiBool _ -> genAbiValue AbiBoolType
AbiAddress x -> pure $ AbiAddress x -- Address are not mutated at all
AbiBool _ -> genAbiValue AbiBoolType -- Booleans are regenerated
AbiBytes n b -> do fs <- replicateM n getRandom
xs <- mutateLL (Just n) (BS.pack fs) b
pure $ AbiBytes n xs
Expand All @@ -327,6 +336,7 @@ mutateAbiValue = \case
AbiFunction v -> pure $ AbiFunction v

-- | Given a 'SolCall', generate a random \"similar\" call with the same 'SolSignature'.
-- Note that this funcion will mutate a *single* argument (if any)
mutateAbiCall :: MonadRandom m => SolCall -> m SolCall
mutateAbiCall = traverse f
where f [] = pure []
Expand Down Expand Up @@ -354,13 +364,15 @@ genWithDict genDict m g t = do
Just cs -> Just <$> rElem' cs
fromMaybe <$> g t <*> maybeValM

-- | A small number of dummy addresses
pregenAdds :: [Addr]
pregenAdds = [i*0xffffffff | i <- [1 .. 3]]

pregenAbiAdds :: [AbiValue]
pregenAbiAdds = map (AbiAddress . fromIntegral) pregenAdds

-- | Synthesize a random 'AbiValue' given its 'AbiType'. Requires a dictionary.
-- Only produce lists with number of elements in the range [1, 32]
genAbiValueM :: MonadRandom m => GenDict -> AbiType -> m AbiValue
genAbiValueM genDict = genWithDict genDict genDict.constants $ \case
AbiUIntType n -> fixAbiUInt n . fromInteger <$> getRandomUint n
Expand Down
28 changes: 25 additions & 3 deletions lib/Echidna/Shrink.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ import Echidna.Types.Config
import Echidna.Types.Campaign (CampaignConf(..))
import Echidna.Test (getResultFromVM, checkETest)

-- | Top level function to shrink the complexity of the sequence of transactions once
shrinkTest
:: (MonadIO m, MonadThrow m, MonadRandom m, MonadReader Env m)
=> VM Concrete RealWorld
Expand All @@ -29,22 +30,28 @@ shrinkTest
shrinkTest vm test = do
env <- ask
case test.state of
-- If we run out of tries to shrink, return the sequence as we have them
Large i | i >= env.cfg.campaignConf.shrinkLimit && not (isOptimizationTest test) ->
pure $ Just test { state = Solved }
Large i ->
-- Start removing the reverts, if any
do repro <- removeReverts vm test.reproducer
let rr = removeUselessNoCalls $ catNoCalls repro
let rr = removeUselessNoCalls $ catNoCalls repro
-- Check if the sequence can be reduced, in practice this is almost never fails
-- since the canShrinkTx function is hard to enforce for all transaction in the sequence
if length rr > 1 || any canShrinkTx rr then do
maybeShrunk <- shrinkSeq vm (checkETest test) test.value rr
-- check if the shrinked sequence passes the test or not
pure $ case maybeShrunk of
-- the test still fails, let's create another test with the reduced sequence
Just (txs, val, vm') -> do
Just test { state = Large (i + 1)
, reproducer = txs
, vm = Just vm'
, result = getResultFromVM vm'
, value = val }
Nothing ->
-- No success with shrinking this time, just bump trials
-- The test passed, so no success with shrinking this time, just bump number of tries to shrink
Just test { state = Large (i + 1), reproducer = rr}
else
pure $ Just test { state = if isOptimizationTest test
Expand All @@ -55,10 +62,15 @@ shrinkTest vm test = do
replaceByNoCall :: Tx -> Tx
replaceByNoCall tx = tx { call = NoCall }

-- | Given a sequence of transactions, remove useless NoCalls. These
-- are when the NoCall have both zero increment in timestamp and block number.
removeUselessNoCalls :: [Tx] -> [Tx]
removeUselessNoCalls = mapMaybe f
where f tx = if isUselessNoCall tx then Nothing else Just tx

-- | Given a VM and a sequence of transactions, execute each transaction except the last one.
-- If a transaction reverts, replace it by a "NoCall" with the same parameters as the original call
-- (e.g. same block increment timestamp and number)
removeReverts :: (MonadIO m, MonadReader Env m, MonadThrow m) => VM Concrete RealWorld -> [Tx] -> m [Tx]
removeReverts vm txs = do
let (itxs, le) = (init txs, last txs)
Expand All @@ -83,10 +95,14 @@ shrinkSeq
-> [Tx]
-> m (Maybe ([Tx], TestValue, VM Concrete RealWorld))
shrinkSeq vm f v txs = do
-- apply one of the two possible simplification strategies (shrunk or shorten) with equal probability
txs' <- uniform =<< sequence [shorten, shrunk]
-- remove certain type of "no calls"
let txs'' = removeUselessNoCalls txs'
-- check if the sequence still triggers a failed transaction
(value, vm') <- check txs'' vm
-- if the test passed it means we didn't shrink successfully
-- if the test passed it means we didn't shrink successfully (returns Nothing)
-- otherwise, return a reduced sequence of transaction
pure $ case (value,v) of
(BoolValue False, _) -> Just (txs'', value, vm')
(IntValue x, IntValue y) | x >= y -> Just (txs'', value, vm')
Expand All @@ -96,9 +112,15 @@ shrinkSeq vm f v txs = do
check (x:xs') vm' = do
(_, vm'') <- execTx vm' x
check xs' vm''
-- | Simplify a sequence of transactions reducing the complexity of its arguments (using shrinkTx)
-- and then reducing its sender (using shrinkSender)
shrunk = mapM (shrinkSender <=< shrinkTx) txs
-- | Simplifiy a sequence of transactions randomly dropping one transaction (with uniform selection)
shorten = (\i -> take i txs ++ drop (i + 1) txs) <$> getRandomR (0, length txs)

-- | Given a transaction, replace the sender of the transaction by another one
-- which is simpler (e.g. it is closer to zero). Usually this means that
-- simplified transactions will try to use 0x10000 as the same caller
shrinkSender :: (MonadReader Env m, MonadRandom m) => Tx -> m Tx
shrinkSender x = do
senderSet <- asks (.cfg.solConf.sender)
Expand Down

0 comments on commit 6956030

Please sign in to comment.