Skip to content

Commit

Permalink
Remove unnecessary ViewPatterns (#925)
Browse files Browse the repository at this point in the history
  • Loading branch information
arcz committed Jan 30, 2023
1 parent 89cbbb4 commit b20d6a6
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 9 deletions.
10 changes: 6 additions & 4 deletions lib/Echidna/Campaign.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE GADTs #-}

module Echidna.Campaign where
Expand Down Expand Up @@ -55,17 +54,20 @@ instance MonadCatch m => MonadCatch (RandT g m) where
-- | Given a 'Campaign', checks if we can attempt any solves or shrinks without exceeding
-- the limits defined in our 'CampaignConf'.
isDone :: MonadReader EConfig m => Campaign -> m Bool
isDone c | null (view tests c) = do
isDone c | null c._tests = do
conf <- asks (._cConf)
pure $ c._ncallseqs * conf._seqLen >= conf._testLimit
isDone (view tests -> ts) = do
isDone c = do
conf <- asks (._cConf)
let res (Open i) = if i >= conf._testLimit then Just True else Nothing
res Passed = Just True
res (Large i) = if i >= conf._shrinkLimit then Just False else Nothing
res Solved = Just False
res (Failed _) = Just False
pure $ res . (.testState) <$> ts & if conf._stopOnFail then elem $ Just False else all isJust
let testResults = res . (.testState) <$> c._tests
let done = if conf._stopOnFail then Just False `elem` testResults
else all isJust testResults
pure done

-- | Given a 'Campaign', check if the test results should be reported as a
-- success or a failure.
Expand Down
9 changes: 4 additions & 5 deletions lib/Echidna/Transaction.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ViewPatterns #-}

module Echidna.Transaction where

Expand Down Expand Up @@ -32,11 +31,11 @@ import Echidna.Types.Campaign (Campaign(..))
hasSelfdestructed :: VM -> Addr -> Bool
hasSelfdestructed vm addr = addr `elem` vm._tx._substate._selfdestructs

-- | If half a tuple is zero, make both halves zero. Useful for generating delays, since block number
-- only goes up with timestamp
-- | If half a tuple is zero, make both halves zero. Useful for generating
-- delays, since block number only goes up with timestamp
level :: (Num a, Eq a) => (a, a) -> (a, a)
level (elemOf each 0 -> True) = (0,0)
level x = x
level (x, y) | x == 0 || y == 0 = (0, 0)
level x = x

getSignatures :: MonadRandom m => SignatureMap -> Maybe SignatureMap -> m SignatureMap
getSignatures hmm Nothing = return hmm
Expand Down

0 comments on commit b20d6a6

Please sign in to comment.