Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data UnitTestOptions = UnitTestOptions {
- rpcInfo :: RpcInfo
- solvers :: SolverGroup
- verbose :: Maybe Int
- maxIter :: Maybe Integer
- askSmtIters :: Integer
- smtDebug :: Bool
- maxDepth :: Maybe Int
- smtTimeout :: Maybe Natural
- solver :: Maybe Text
- covMatch :: Maybe Text
- match :: Text
- fuzzRuns :: Int
- replay :: Maybe (Text, ByteString)
- vmModifier :: VM -> VM
- dapp :: DappInfo
- testParams :: TestVMParams
- ffiAllowed :: Bool
- data TestVMParams = TestVMParams {}
- defaultGasForCreating :: Word64
- defaultGasForInvoking :: Word64
- defaultBalanceForTestContract :: W256
- defaultMaxCodeSize :: W256
- type ABIMethod = Text
- makeVeriOpts :: UnitTestOptions -> VeriOpts
- unitTest :: UnitTestOptions -> Contracts -> Maybe String -> IO Bool
- initializeUnitTest :: UnitTestOptions -> SolcContract -> Stepper ()
- runUnitTest :: UnitTestOptions -> ABIMethod -> AbiValue -> Stepper Bool
- execTestStepper :: UnitTestOptions -> ABIMethod -> AbiValue -> Stepper Bool
- exploreStep :: UnitTestOptions -> ByteString -> Stepper Bool
- checkFailures :: UnitTestOptions -> ABIMethod -> Bool -> Stepper Bool
- fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> Property
- tick :: Text -> IO ()
- data OpLocation = OpLocation {
- srcContract :: Contract
- srcOpIx :: Int
- srcMapForOpLocation :: DappInfo -> OpLocation -> Maybe SrcMap
- type CoverageState = (VM, MultiSet OpLocation)
- currentOpLocation :: VM -> OpLocation
- execWithCoverage :: StateT CoverageState IO VMResult
- runWithCoverage :: StateT CoverageState IO VM
- interpretWithCoverage :: UnitTestOptions -> Stepper a -> StateT CoverageState IO a
- coverageReport :: DappInfo -> MultiSet SrcMap -> Map FilePath (Vector (Int, ByteString))
- coverageForUnitTestContract :: UnitTestOptions -> Map Text SolcContract -> SourceCache -> (Text, [(Test, [AbiType])]) -> IO (MultiSet SrcMap)
- runUnitTestContract :: UnitTestOptions -> Map Text SolcContract -> (Text, [(Test, [AbiType])]) -> IO [(Bool, VM)]
- runTest :: UnitTestOptions -> VM -> (Test, [AbiType]) -> IO (Text, Either Text Text, VM)
- type ExploreTx = (Addr, Addr, ByteString, W256)
- decodeCalls :: ByteString -> [ExploreTx]
- initialExplorationStepper :: UnitTestOptions -> ABIMethod -> [ExploreTx] -> [Addr] -> Int -> Stepper (Bool, RLP)
- explorationStepper :: UnitTestOptions -> ABIMethod -> [ExploreTx] -> [Addr] -> RLP -> Int -> Stepper (Bool, RLP)
- getTargetContracts :: UnitTestOptions -> Stepper [Addr]
- exploreRun :: UnitTestOptions -> VM -> ABIMethod -> [ExploreTx] -> IO (Text, Either Text Text, VM)
- execTest :: UnitTestOptions -> VM -> ABIMethod -> AbiValue -> IO (Bool, VM)
- runOne :: UnitTestOptions -> VM -> ABIMethod -> AbiValue -> IO (Text, Either Text Text, VM)
- fuzzRun :: UnitTestOptions -> VM -> Text -> [AbiType] -> IO (Text, Either Text Text, VM)
- symRun :: UnitTestOptions -> VM -> Text -> [AbiType] -> IO (Text, Either Text Text, VM)
- symFailure :: UnitTestOptions -> Text -> Expr Buf -> [AbiType] -> [(Expr End, SMTCex)] -> Text
- prettyCalldata :: (?context :: DappContext) => SMTCex -> Expr Buf -> Text -> [AbiType] -> Text
- showCalldata :: (?context :: DappContext) => SMTCex -> [AbiType] -> Expr Buf -> Text
- showVal :: AbiValue -> Text
- execSymTest :: UnitTestOptions -> ABIMethod -> (Expr Buf, [Prop]) -> Stepper (Expr End)
- checkSymFailures :: UnitTestOptions -> Stepper VM
- indentLines :: Int -> Text -> Text
- passOutput :: VM -> UnitTestOptions -> Text -> Text
- failOutput :: VM -> UnitTestOptions -> Text -> Text
- formatTestLogs :: (?context :: DappContext) => Map W256 Event -> [Expr Log] -> Text
- formatTestLog :: (?context :: DappContext) => Map W256 Event -> Expr Log -> Maybe Text
- abiCall :: TestVMParams -> Either (Text, AbiValue) ByteString -> EVM ()
- makeTxCall :: TestVMParams -> (Expr Buf, [Prop]) -> EVM ()
- initialUnitTestVm :: UnitTestOptions -> SolcContract -> VM
- getParametersFromEnvironmentVariables :: Maybe Text -> IO TestVMParams
Documentation
data UnitTestOptions Source #
UnitTestOptions | |
|
data TestVMParams Source #
makeVeriOpts :: UnitTestOptions -> VeriOpts Source #
Generate VeriOpts from UnitTestOptions
unitTest :: UnitTestOptions -> Contracts -> Maybe String -> IO Bool Source #
Top level CLI endpoint for hevm test
initializeUnitTest :: UnitTestOptions -> SolcContract -> Stepper () Source #
Assuming a constructor is loaded, this stepper will run the constructor to create the test contract, give it an initial balance, and run `setUp()'.
runUnitTest :: UnitTestOptions -> ABIMethod -> AbiValue -> Stepper Bool Source #
Assuming a test contract is loaded and initialized, this stepper will run the specified test method and return whether it succeeded.
execTestStepper :: UnitTestOptions -> ABIMethod -> AbiValue -> Stepper Bool Source #
exploreStep :: UnitTestOptions -> ByteString -> Stepper Bool Source #
checkFailures :: UnitTestOptions -> ABIMethod -> Bool -> Stepper Bool Source #
fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> Property Source #
Randomly generates the calldata arguments and runs the test
data OpLocation Source #
This is like an unresolved source mapping.
OpLocation | |
|
Instances
Show OpLocation Source # | |
Defined in EVM.UnitTest showsPrec :: Int -> OpLocation -> ShowS # show :: OpLocation -> String # showList :: [OpLocation] -> ShowS # | |
Eq OpLocation Source # | |
Defined in EVM.UnitTest (==) :: OpLocation -> OpLocation -> Bool # (/=) :: OpLocation -> OpLocation -> Bool # | |
Ord OpLocation Source # | |
Defined in EVM.UnitTest compare :: OpLocation -> OpLocation -> Ordering # (<) :: OpLocation -> OpLocation -> Bool # (<=) :: OpLocation -> OpLocation -> Bool # (>) :: OpLocation -> OpLocation -> Bool # (>=) :: OpLocation -> OpLocation -> Bool # max :: OpLocation -> OpLocation -> OpLocation # min :: OpLocation -> OpLocation -> OpLocation # |
srcMapForOpLocation :: DappInfo -> OpLocation -> Maybe SrcMap Source #
type CoverageState = (VM, MultiSet OpLocation) Source #
currentOpLocation :: VM -> OpLocation Source #
interpretWithCoverage :: UnitTestOptions -> Stepper a -> StateT CoverageState IO a Source #
coverageForUnitTestContract :: UnitTestOptions -> Map Text SolcContract -> SourceCache -> (Text, [(Test, [AbiType])]) -> IO (MultiSet SrcMap) Source #
runUnitTestContract :: UnitTestOptions -> Map Text SolcContract -> (Text, [(Test, [AbiType])]) -> IO [(Bool, VM)] Source #
decodeCalls :: ByteString -> [ExploreTx] Source #
initialExplorationStepper :: UnitTestOptions -> ABIMethod -> [ExploreTx] -> [Addr] -> Int -> Stepper (Bool, RLP) Source #
Runs an invariant test, calls the invariant before execution begins
explorationStepper :: UnitTestOptions -> ABIMethod -> [ExploreTx] -> [Addr] -> RLP -> Int -> Stepper (Bool, RLP) Source #
getTargetContracts :: UnitTestOptions -> Stepper [Addr] Source #
exploreRun :: UnitTestOptions -> VM -> ABIMethod -> [ExploreTx] -> IO (Text, Either Text Text, VM) Source #
runOne :: UnitTestOptions -> VM -> ABIMethod -> AbiValue -> IO (Text, Either Text Text, VM) Source #
Define the thread spawner for normal test cases
fuzzRun :: UnitTestOptions -> VM -> Text -> [AbiType] -> IO (Text, Either Text Text, VM) Source #
Define the thread spawner for property based tests
symRun :: UnitTestOptions -> VM -> Text -> [AbiType] -> IO (Text, Either Text Text, VM) Source #
Define the thread spawner for symbolic tests
symFailure :: UnitTestOptions -> Text -> Expr Buf -> [AbiType] -> [(Expr End, SMTCex)] -> Text Source #
prettyCalldata :: (?context :: DappContext) => SMTCex -> Expr Buf -> Text -> [AbiType] -> Text Source #
showCalldata :: (?context :: DappContext) => SMTCex -> [AbiType] -> Expr Buf -> Text Source #
passOutput :: VM -> UnitTestOptions -> Text -> Text Source #
failOutput :: VM -> UnitTestOptions -> Text -> Text Source #
formatTestLogs :: (?context :: DappContext) => Map W256 Event -> [Expr Log] -> Text Source #
abiCall :: TestVMParams -> Either (Text, AbiValue) ByteString -> EVM () Source #
makeTxCall :: TestVMParams -> (Expr Buf, [Prop]) -> EVM () Source #
initialUnitTestVm :: UnitTestOptions -> SolcContract -> VM Source #