Skip to content

Commit

Permalink
Merge pull request #150 from ethereum/no-warnings
Browse files Browse the repository at this point in the history
ci: enforce no warnings in ci
  • Loading branch information
d-xo authored Dec 27, 2022
2 parents c611276 + 62c1773 commit f42ec15
Show file tree
Hide file tree
Showing 8 changed files with 32 additions and 18 deletions.
2 changes: 1 addition & 1 deletion flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@
}))
(haskell.lib.compose.addTestToolDepends [ solc z3 cvc5 ])
(haskell.lib.compose.appendConfigureFlags (
[ "--ghc-option=-O2" ]
[ "--ghc-option=-O2" "-fci" ]
++ lib.optionals stdenv.isLinux [
"--enable-executable-static"
"--extra-lib-dirs=${gmp.override { withStatic = true; }}/lib"
Expand Down
9 changes: 9 additions & 0 deletions hevm.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,11 +40,18 @@ extra-source-files:
test/contracts/fail/dsProveFail.sol
test/contracts/fail/invariantFail.sol

flag ci
description: Sets flags for compilation in CI
default: False
manual: True

source-repository head
type: git
location: https://github.com/ethereum/hevm.git

common shared
if flag(ci)
ghc-options: -Werror
default-language:
Haskell2010
default-extensions:
Expand Down Expand Up @@ -287,6 +294,8 @@ common test-common
test-base
build-depends:
test-utils
other-modules:
EVM.TestUtils
if os(darwin)
extra-libraries: c++
-- https://gitlab.haskell.org/ghc/ghc/-/issues/11829
Expand Down
2 changes: 1 addition & 1 deletion src/EVM/Dapp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ dappInfo root solcByName sources =
let
solcs = Map.elems solcByName
astIds = astIdMap $ snd <$> toList (view sourceAsts sources)
immutables = filter ((/=) mempty . _immutableReferences) solcs
immutables = filter ((/=) mempty . (view immutableReferences)) solcs

in DappInfo
{ _dappRoot = root
Expand Down
23 changes: 13 additions & 10 deletions src/EVM/Flatten.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# Language TupleSections #-}

module EVM.Flatten (flatten) where

-- This module concatenates all the imported dependencies
Expand Down Expand Up @@ -33,12 +35,12 @@ import qualified Data.Graph.Inductive.Query.DFS as Fgl
import Data.SemVer (SemVerRange, parseSemVerRange)
import qualified Data.SemVer as SemVer

import Control.Monad (forM)
import Control.Monad (forM, (>=>))
import Data.ByteString (ByteString)
import Data.Foldable (foldl', toList)
import Data.List (sort, nub, (\\))
import Data.Map (Map, (!), (!?))
import Data.Maybe (mapMaybe, isJust, catMaybes, fromMaybe)
import Data.Maybe (mapMaybe, isJust, fromMaybe)
import Data.Text (Text, unpack, pack, intercalate)
import Data.Text.Encoding (encodeUtf8, decodeUtf8)
import Text.Read (readMaybe)
Expand Down Expand Up @@ -210,7 +212,7 @@ flatten dapp target = do

joinLicenses :: [Value] -> Text
joinLicenses asts =
case nub $ mapMaybe (\ast -> getAttribute "license" ast >>= preview _String) asts of
case nub $ mapMaybe (getAttribute "license" >=> preview _String) asts of
[] -> ""
x -> "// SPDX-License-Identifier: " <> intercalate " AND " x

Expand Down Expand Up @@ -248,9 +250,9 @@ maximalPragma asts = (
ps = filter (nodeIs "PragmaDirective") (universe ast)

components :: [[Value]]
components = catMaybes $
fmap
((fmap toList) . (\x -> getAttribute "literals" x >>= preview _Array))
components = mapMaybe
((fmap toList)
. (getAttribute "literals" >=> preview _Array))
ps

-- Simple way to combine many SemVer ranges. We don't actually
Expand Down Expand Up @@ -400,9 +402,9 @@ prefixContractAst castr cs bso ast = prefixAstNodes
+ (BS.length $ fst $ BS.breakSubstring name' bs')
+ (BS.length name')
in
fmap ((,) pos) $ id' v
fmap (pos,) $ id' v
| t `elem` ["UserDefinedTypeName", "Identifier"] =
fmap ((,) end) $ refDec v
fmap (end,) $ refDec v
| otherwise =
error $ "internal error: not a contract reference: " ++ show t

Expand Down Expand Up @@ -450,15 +452,16 @@ repeated :: Eq a => [a] -> [a]
repeated = fmap fst $ foldl' f ([], [])
where
f (acc, seen) x =
( if (x `elem` seen) && (not $ x `elem` acc)
( if (x `elem` seen) && (x `notElem` acc)
then x : acc
else acc
, x : seen
)

indexed :: [(Integer, Text)] -> [(Integer, Text)]
indexed = fst . foldl' f ([], Map.empty) -- (zip (fmap snd xs) $ replicate (length xs) 0) xs
indexed = fst . foldl' f ([], (Map.empty :: Map Text Integer))
where
f :: (Show v, Num v, Ord k) => ([(a, Text)], Map k v) -> (a, k) -> ([(a, Text)], Map k v)
f (acc, seen) (id', n) =
let
count = (fromMaybe 0 $ seen !? n) + 1
Expand Down
7 changes: 3 additions & 4 deletions src/EVM/SMT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,6 @@ import Language.SMT2.Syntax (SpecConstant(..), GeneralRes(..), Term(..), QualIde
import Data.Word
import Numeric (readHex)
import Data.ByteString (ByteString)
import Data.Maybe (fromMaybe)

import qualified Data.ByteString as BS
import qualified Data.List as List
Expand Down Expand Up @@ -785,10 +784,10 @@ parseFrameCtx name = case TS.unpack name of
t -> error $ "Internal Error: cannot parse " <> t <> " into an Expr"

getVars :: (TS.Text -> Expr EWord) -> SolverInstance -> [TS.Text] -> IO (Map (Expr EWord) W256)
getVars parseFn inst names = Map.mapKeys parseFn <$> foldM getVar mempty names
getVars parseFn inst names = Map.mapKeys parseFn <$> foldM getOne mempty names
where
getVar :: Map TS.Text W256 -> TS.Text -> IO (Map TS.Text W256)
getVar acc name = do
getOne :: Map TS.Text W256 -> TS.Text -> IO (Map TS.Text W256)
getOne acc name = do
raw <- getValue inst (T.fromStrict name)
let
parsed = case parseCommentFreeFileMsg getValueRes (T.toStrict raw) of
Expand Down
1 change: 1 addition & 0 deletions src/EVM/Solidity.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ module EVM.Solidity
, sourceFiles
, sourceLines
, sourceAsts
, immutableReferences
, stripBytecodeMetadata
, stripBytecodeMetadataSym
, signature
Expand Down
4 changes: 3 additions & 1 deletion src/EVM/SymExec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -528,9 +528,11 @@ equivalenceCheck solvers bytecodeA bytecodeB opts signature' = do
(Revert _ a, Revert _ b) -> if a==b then PBool False else a ./= b
(Revert _ _, _) -> PBool True
(_, Revert _ _) -> PBool True
(Failure _ erra, Failure _ errb) -> if erra==errb then PBool False else PBool True
(GVar _, _) -> error "Expressions cannot contain global vars"
(_ , GVar _) -> error "Expressions cannot contain global vars"
(Failure _ (TmpErr s), _) -> error $ "Unhandled error: " <> s
(_, Failure _ (TmpErr s)) -> error $ "Unhandled error: " <> s
(Failure _ erra, Failure _ errb) -> if erra==errb then PBool False else PBool True
(ITE _ _ _, _ ) -> error "Expressions must be flattened"
(_, ITE _ _ _) -> error "Expressions must be flattened"

Expand Down
2 changes: 1 addition & 1 deletion src/EVM/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,7 @@ instance FromJSON Transaction where
toAddr <- addrFieldMaybe val "to"
v <- wordField val "v"
value <- wordField val "value"
txType <- fmap read <$> (val JSON..:? "type")
txType <- fmap (read :: String -> Int) <$> (val JSON..:? "type")
case txType of
Just 0x00 -> return $ Transaction tdata gasLimit gasPrice nonce r s toAddr v value LegacyTransaction [] Nothing Nothing
Just 0x01 -> do
Expand Down

0 comments on commit f42ec15

Please sign in to comment.