Skip to content

Commit

Permalink
Force corpus evaluation
Browse files Browse the repository at this point in the history
  • Loading branch information
arcz committed Mar 29, 2023
1 parent 206b911 commit c75c849
Show file tree
Hide file tree
Showing 3 changed files with 33 additions and 14 deletions.
3 changes: 2 additions & 1 deletion lib/Echidna/Campaign.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ import Echidna.Types.Test
import Echidna.Types.Tx (TxCall(..), Tx(..), getResult, call)
import Echidna.Types.World (World)
import Echidna.Types.Corpus (Corpus)
import qualified Control.DeepSeq as DeepSeq

instance MonadThrow m => MonadThrow (RandT g m) where
throwM = lift . throwM
Expand Down Expand Up @@ -235,7 +236,7 @@ callseq initialCorpus vm world seqLen = do
then updateGasInfo res [] camp.gasInfo
else camp.gasInfo
-- If there is new coverage, add the transaction list to the corpus
, corpus = if camp'.newCoverage
, corpus = DeepSeq.force $ if camp'.newCoverage
then addToCorpus (camp.ncallseqs + 1) res camp.corpus
else camp.corpus
-- Reset the new coverage flag
Expand Down
43 changes: 30 additions & 13 deletions lib/Echidna/Types/Tx.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}

module Echidna.Types.Tx where

Expand All @@ -15,20 +17,23 @@ import Data.Text (Text)
import Data.Word (Word64)

import EVM (VMResult(..), Error(..))
import EVM.ABI (encodeAbiValue, AbiValue(..))
import EVM.ABI (encodeAbiValue, AbiValue(..), AbiType)
import EVM.Types (Addr, W256)

import Echidna.Orphans.JSON ()
import Echidna.Types.Buffer (forceBuf)
import Echidna.Types.Signature (SolCall)
import Control.DeepSeq (NFData)
import GHC.Generics (Generic)
import Data.DoubleWord (Word256, Word128, Int256, Int128, Word160)

-- | A transaction call is either a @CREATE@, a fully instrumented 'SolCall', or
-- an abstract call consisting only of calldata.
data TxCall = SolCreate ByteString
| SolCall SolCall
| SolCalldata ByteString
data TxCall = SolCreate !ByteString
| SolCall !SolCall
| SolCalldata !ByteString
| NoCall
deriving (Show, Ord, Eq)
deriving (Show, Ord, Eq, Generic)
$(deriveJSON defaultOptions ''TxCall)

maxGasPerBlock :: Word64
Expand All @@ -51,14 +56,26 @@ initialBlockNumber = 4370000 -- Initial byzantium block

-- | A transaction is either a @CREATE@ or a regular call with an origin, destination, and value.
-- Note: I currently don't model nonces or signatures here.
data Tx = Tx { call :: TxCall -- | Call
, src :: Addr -- | Origin
, dst :: Addr -- | Destination
, gas :: Word64 -- | Gas
, gasprice :: W256 -- | Gas price
, value :: W256 -- | Value
, delay :: (W256, W256) -- | (Time, # of blocks since last call)
} deriving (Eq, Ord, Show)
data Tx = Tx { call :: !TxCall -- | Call
, src :: !Addr -- | Origin
, dst :: !Addr -- | Destination
, gas :: !Word64 -- | Gas
, gasprice :: !W256 -- | Gas price
, value :: !W256 -- | Value
, delay :: !(W256, W256) -- | (Time, # of blocks since last call)
} deriving (Eq, Ord, Show, Generic)

deriving instance NFData Tx
deriving instance NFData TxCall
deriving instance NFData AbiValue
deriving instance NFData Word256
deriving instance NFData Word128
deriving instance NFData Int256
deriving instance NFData Int128
deriving instance NFData Word160
deriving instance NFData AbiType
deriving anyclass instance NFData Addr
deriving anyclass instance NFData W256

instance ToJSON Tx where
toJSON Tx{..} = object
Expand Down
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ dependencies:
- containers
- data-bword
- data-dword
- deepseq
- extra
- directory
- exceptions
Expand Down

0 comments on commit c75c849

Please sign in to comment.