hevm-0.51.0: Ethereum virtual machine evaluator
Safe HaskellSafe-Inferred
LanguageGHC2021

EVM.SMT

Description

 
Synopsis

Encoding ** ----------------------------------------------------------------------------------

data CexVars Source #

Constructors

CexVars 

Instances

Instances details
Monoid CexVars Source # 
Instance details

Defined in EVM.SMT

Semigroup CexVars Source # 
Instance details

Defined in EVM.SMT

Show CexVars Source # 
Instance details

Defined in EVM.SMT

Eq CexVars Source # 
Instance details

Defined in EVM.SMT

Methods

(==) :: CexVars -> CexVars -> Bool #

(/=) :: CexVars -> CexVars -> Bool #

data BufModel Source #

A model for a buffer, either in it's compressed form (for storing parsed models from a solver), or as a bytestring (for presentation to users)

Instances

Instances details
Show BufModel Source # 
Instance details

Defined in EVM.SMT

Eq BufModel Source # 
Instance details

Defined in EVM.SMT

data CompressedBuf Source #

This representation lets us store buffers of arbitrary length without exhausting the available memory, it closely matches the format used by smt-lib when returning models for arrays

Constructors

Base 

Fields

Write 

Fields

Instances

Instances details
Show CompressedBuf Source # 
Instance details

Defined in EVM.SMT

Eq CompressedBuf Source # 
Instance details

Defined in EVM.SMT

data SMTCex Source #

a final post shrinking cex, buffers here are all represented as concrete bytestrings

Instances

Instances details
Show SMTCex Source # 
Instance details

Defined in EVM.SMT

Eq SMTCex Source # 
Instance details

Defined in EVM.SMT

Methods

(==) :: SMTCex -> SMTCex -> Bool #

(/=) :: SMTCex -> SMTCex -> Bool #

collapse :: BufModel -> Maybe BufModel Source #

Attemps to collapse a compressed buffer representation down to a flattened one

data SMT2 Source #

Constructors

SMT2 [Builder] CexVars 

Instances

Instances details
Monoid SMT2 Source # 
Instance details

Defined in EVM.SMT

Methods

mempty :: SMT2 #

mappend :: SMT2 -> SMT2 -> SMT2 #

mconcat :: [SMT2] -> SMT2 #

Semigroup SMT2 Source # 
Instance details

Defined in EVM.SMT

Methods

(<>) :: SMT2 -> SMT2 -> SMT2 #

sconcat :: NonEmpty SMT2 -> SMT2 #

stimes :: Integral b => b -> SMT2 -> SMT2 #

Show SMT2 Source # 
Instance details

Defined in EVM.SMT

Methods

showsPrec :: Int -> SMT2 -> ShowS #

show :: SMT2 -> String #

showList :: [SMT2] -> ShowS #

Eq SMT2 Source # 
Instance details

Defined in EVM.SMT

Methods

(==) :: SMT2 -> SMT2 -> Bool #

(/=) :: SMT2 -> SMT2 -> Bool #

declareIntermediates :: BufEnv -> StoreEnv -> SMT2 Source #

Reads all intermediate variables from the builder state and produces SMT declaring them as constants

findStorageReads :: Prop -> [(Expr EWord, Expr EWord)] Source #

This function overapproximates the reads from the abstract storage. Potentially, it can return locations that do not read a slot directly from the abstract store but from subsequent writes on the store (e.g, SLoad addr idx (SStore addr idx val AbstractStore)). However, we expect that most of such reads will have been simplified away.

assertReads :: [Prop] -> BufEnv -> StoreEnv -> [Prop] Source #

Asserts that buffer reads beyond the size of the buffer are equal to zero. Looks for buffer reads in the a list of given predicates and the buffer and storage environments.

discoverMaxReads :: [Prop] -> BufEnv -> StoreEnv -> Map Text (Expr EWord) Source #

Finds the maximum read index for each abstract buffer in the input props

declareBufs :: [Prop] -> BufEnv -> StoreEnv -> SMT2 Source #

Returns an SMT2 object with all buffers referenced from the input props declared, and with the appropriate cex extraction metadata attached

Helpers ** ---------------------------------------------------------------------------------

copySlice :: Expr EWord -> Expr EWord -> Expr EWord -> Builder -> Builder -> Builder Source #

Stores a region of src into dst

expandExp :: Expr EWord -> W256 -> Builder Source #

Unrolls an exponentiation into a series of multiplications

concatBytes :: [Expr Byte] -> Builder Source #

Concatenates a list of bytes into a larger bitvector

writeBytes :: ByteString -> Expr Buf -> Builder Source #

Concatenates a list of bytes into a larger bitvector

Cex parsing ** --------------------------------------------------------------------------------

parseSC :: (Num a, Eq a) => SpecConstant -> a Source #

parseErr :: Show a => a -> b Source #

getVars :: (Text -> Expr EWord) -> (Text -> IO Text) -> [Text] -> IO (Map (Expr EWord) W256) Source #

queryMaxReads :: (Text -> IO Text) -> Map Text (Expr EWord) -> IO (Map Text W256) Source #

Queries the solver for models for each of the expressions representing the max read index for a given buffer

getBufs :: (Text -> IO Text) -> [Text] -> IO (Map (Expr Buf) BufModel) Source #

Gets the initial model for each buffer, these will often be much too large for our purposes

interpretNDArray :: (Map Symbol Term -> Term -> a) -> Map Symbol Term -> Term -> W256 -> a Source #

Interpret an N-dimensional array as a value of type a. Parameterized by an interpretation function for array values.

interpret1DArray :: Map Symbol Term -> Term -> W256 -> W256 Source #

Interpret an 1-dimensional array as a function

interpret2DArray :: Map Symbol Term -> Term -> W256 -> W256 -> W256 Source #

Interpret an 2-dimensional array as a function