pull/162/head
ggrieco-tob 6 years ago
parent e32299db84
commit b69a32c4c0
  1. 6
      lib/Echidna/Solidity.hs
  2. 16
      src/test/Spec.hs

@ -8,7 +8,7 @@ module Echidna.Solidity where
import Control.Lens
import Control.Exception (Exception)
import Control.Monad (liftM2, mapM_, when)
import Control.Monad (liftM2, mapM_, when, unless)
import Control.Monad.Catch (MonadThrow(..))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader (MonadReader)
@ -89,9 +89,9 @@ contracts fp = do
selected :: (MonadIO m, MonadThrow m, MonadReader x m, Has SolConf x) => FilePath -> Maybe Text -> m SolcContract
selected fp name = do cs <- contracts fp
c <- choose cs $ ((pack fp <> ":") <>) <$> name
stfu <- view (hasLens . quiet)
q <- view (hasLens . quiet)
liftIO $ when (isNothing name && length cs > 1) $ putStrLn "Multiple contracts found in file, only analyzing the first"
liftIO $ when (not stfu) $ putStrLn $ "Analyzing contract: " <> unpack (c ^. contractName)
liftIO $ unless q $ putStrLn $ "Analyzing contract: " <> unpack (c ^. contractName)
return c
where choose [] _ = throwM NoContracts
choose (c:_) Nothing = return c

@ -1,6 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}
import Test.Tasty
import Test.Tasty.HUnit as HU
@ -74,12 +73,13 @@ solidityTests = testGroup "Solidity-HUnit"
assertBool "s2 not in solution" $ any (\case {Left ("s2", _) -> True; _ -> False;}) calls
assertBool "s3 not in solution" $ any (\case {Left ("s3", _) -> True; _ -> False;}) calls
]
where c2 = "./examples/solidity/basic/flags.sol"
c3 = "./examples/solidity/basic/revert.sol"
--c4 = "./examples/solidity/basic/payable.sol"
c5 = "./examples/solidity/basic/true.sol"
c6 = "./examples/solidity/basic/multisender.sol"
cfg6 = "./examples/solidity/basic/multisender.yaml"
where cd = "./examples/solidity/basic/"
c2 = cd ++ "flags.sol"
c3 = cd ++ "revert.sol"
--c4 = cd ++ "payable.sol"
c5 = cd ++ "true.sol"
c6 = cd ++ "multisender.sol"
cfg6 = cd ++ "multisender.yaml"
testContract :: FilePath -> Either EConfig FilePath -> (Campaign -> HU.Assertion) -> HU.Assertion
testContract file cfg f = do
@ -110,7 +110,7 @@ solve (Solved s) = s
solve _ = undefined
findtest :: Campaign -> Text -> Maybe TestState
findtest = findtest'' . (^. tests)
findtest = findtest'' . (view tests)
findtest' :: Campaign -> Text -> TestState
findtest' = (fromJust .) . findtest

Loading…
Cancel
Save