@@ -18,6 +18,7 @@ module Act.HEVM where
1818import Prelude hiding (GT , LT )
1919
2020import qualified Data.Map as M
21+ import qualified Data.Set as S
2122import Data.List
2223import Data.Containers.ListUtils (nubOrd )
2324import qualified Data.Text as T
@@ -658,8 +659,9 @@ getInitContractState solvers iface pointers preconds cmap = do
658659 (cmaps, checks) <- unzip <$> mapM getContractState (fmap nub casts')
659660
660661 let finalmap = M. unions (cmap: cmaps)
662+
661663 check <- checkAliasing finalmap cmaps
662- pure (finalmap, check <* sequenceA_ checks)
664+ pure (finalmap, check <* sequenceA_ checks <* checkUniqueAddr (cmap : cmaps) )
663665
664666 where
665667
@@ -710,7 +712,15 @@ getInitContractState solvers iface pointers preconds cmap = do
710712
711713 msg = " \x1b [1mThe following addresses cannot be proved distinct:\x1b [m"
712714
715+ -- currently we check that all symbolic addresses are globaly unique, and fail otherwise
716+ -- (this is required for aliasing check to be sound when merging graphs
717+ -- In the future, we should implement an internal renaming of variables to ensure global
718+ -- uniqueness of symbolic a)ddresses.
713719
720+ checkUniqueAddr :: [ContractMap ] -> Error String ()
721+ checkUniqueAddr cmaps =
722+ let pairs = comb cmaps in
723+ assert (nowhere, " Names of symbolic adresses must be unique" ) (foldl (\ b (c1, c2) -> S. disjoint (M. keysSet c1) (M. keysSet c2) && b) True pairs)
714724
715725checkConstructors :: App m => SolverGroup -> ByteString -> ByteString -> Contract -> ActT m (Error String ContractMap )
716726checkConstructors solvers initcode runtimecode (Contract ctor@ (Constructor _ iface pointers preconds _ _ _) _) = do
0 commit comments