| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
EVM.UnitTest
Synopsis
- data UnitTestOptions = UnitTestOptions {}
- data TestVMParams = TestVMParams {- testAddress :: Addr
- testCaller :: Addr
- testOrigin :: Addr
- testGasCreate :: W256
- testGasCall :: W256
- testBalanceCreate :: W256
- testBalanceCall :: W256
- testCoinbase :: Addr
- testNumber :: W256
- testTimestamp :: W256
- testGaslimit :: W256
- testGasprice :: W256
- testMaxCodeSize :: W256
- testDifficulty :: W256
- testChainId :: W256
 
- defaultGasForCreating :: W256
- defaultGasForInvoking :: W256
- defaultBalanceForCreator :: W256
- defaultBalanceForCreated :: W256
- defaultMaxCodeSize :: W256
- type ABIMethod = Text
- initializeUnitTest :: UnitTestOptions -> SolcContract -> Stepper ()
- runUnitTest :: UnitTestOptions -> ABIMethod -> AbiValue -> Stepper Bool
- execTest :: UnitTestOptions -> ABIMethod -> AbiValue -> Stepper Bool
- checkFailures :: UnitTestOptions -> ABIMethod -> Bool -> Stepper Bool
- fuzzTest :: UnitTestOptions -> Text -> [AbiType] -> VM -> Property
- tick :: Text -> IO ()
- data OpLocation = OpLocation {- srcCodehash :: !W256
- 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 Text (Vector (Int, ByteString))
- coverageForUnitTestContract :: UnitTestOptions -> Map Text SolcContract -> SourceCache -> (Text, [(Test, [AbiType])]) -> IO (MultiSet SrcMap)
- runUnitTestContract :: UnitTestOptions -> Map Text SolcContract -> (Text, [(Test, [AbiType])]) -> Query [(Bool, VM)]
- runTest :: UnitTestOptions -> VM -> (Test, [AbiType]) -> Query (Text, Either Text Text, 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] -> Query (Text, Either Text Text, VM)
- symFailure :: UnitTestOptions -> Text -> [(VM, Text)] -> Text
- prettyCalldata :: (?context :: DappContext) => (Buffer, SymWord) -> Text -> [AbiType] -> Query Text
- execSymTest :: UnitTestOptions -> ABIMethod -> (Buffer, SymWord) -> Stepper (Bool, VM)
- checkSymFailures :: UnitTestOptions -> Stepper VM
- indentLines :: Int -> Text -> Text
- passOutput :: VM -> UnitTestOptions -> Text -> Text
- failOutput :: VM -> UnitTestOptions -> Text -> Text
- formatTestLogs :: (?context :: DappContext) => Map W256 Event -> Seq Log -> Text
- formatTestLog :: (?context :: DappContext) => Map W256 Event -> Log -> Maybe Text
- word32Bytes :: Word32 -> ByteString
- abiCall :: TestVMParams -> Text -> AbiValue -> EVM ()
- makeTxCall :: TestVMParams -> (Buffer, SymWord) -> EVM ()
- initialUnitTestVm :: UnitTestOptions -> SolcContract -> VM
- symbolify :: VM -> VM
- getParametersFromEnvironmentVariables :: Maybe Text -> IO TestVMParams
Documentation
data UnitTestOptions Source #
Constructors
| UnitTestOptions | |
data TestVMParams Source #
Constructors
| TestVMParams | |
| Fields 
 | |
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.
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.
Constructors
| OpLocation | |
| Fields 
 | |
Instances
| Eq OpLocation Source # | |
| Defined in EVM.UnitTest | |
| Ord OpLocation Source # | |
| Defined in EVM.UnitTest Methods compare :: OpLocation -> OpLocation -> Ordering # (<) :: OpLocation -> OpLocation -> Bool # (<=) :: OpLocation -> OpLocation -> Bool # (>) :: OpLocation -> OpLocation -> Bool # (>=) :: OpLocation -> OpLocation -> Bool # max :: OpLocation -> OpLocation -> OpLocation # min :: OpLocation -> OpLocation -> OpLocation # | |
| Show OpLocation Source # | |
| Defined in EVM.UnitTest Methods showsPrec :: Int -> OpLocation -> ShowS # show :: OpLocation -> String # showList :: [OpLocation] -> ShowS # | |
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])]) -> Query [(Bool, VM)] Source #
runTest :: UnitTestOptions -> VM -> (Test, [AbiType]) -> Query (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] -> Query (Text, Either Text Text, VM) Source #
Define the thread spawner for symbolic tests TODO: return a list of VM's
symFailure :: UnitTestOptions -> Text -> [(VM, Text)] -> Text Source #
prettyCalldata :: (?context :: DappContext) => (Buffer, SymWord) -> Text -> [AbiType] -> Query Text Source #
execSymTest :: UnitTestOptions -> ABIMethod -> (Buffer, SymWord) -> Stepper (Bool, VM) Source #
passOutput :: VM -> UnitTestOptions -> Text -> Text Source #
failOutput :: VM -> UnitTestOptions -> Text -> Text Source #
formatTestLogs :: (?context :: DappContext) => Map W256 Event -> Seq Log -> Text Source #
formatTestLog :: (?context :: DappContext) => Map W256 Event -> Log -> Maybe Text Source #
word32Bytes :: Word32 -> ByteString Source #
makeTxCall :: TestVMParams -> (Buffer, SymWord) -> EVM () Source #
initialUnitTestVm :: UnitTestOptions -> SolcContract -> VM Source #