Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data RpcQuery a where
- QueryAccount :: Addr -> RpcQuery (ByteString, W256, W256)
- QueryCode :: Addr -> RpcQuery ByteString
- QueryBlock :: RpcQuery Block
- QueryBalance :: Addr -> RpcQuery W256
- QueryNonce :: Addr -> RpcQuery W256
- QuerySlot :: Addr -> W256 -> RpcQuery W256
- QueryChainId :: RpcQuery W256
- data BlockNumber
- rpc :: String -> [Value] -> Scientific -> Value
- class ToRPC a where
- readText :: Read a => Text -> a
- fetchQuery :: Show a => BlockNumber -> (Value -> IO (Maybe Value)) -> RpcQuery a -> IO (Maybe a)
- parseBlock :: (AsValue s, Show s) => s -> Maybe Block
- fetchWithSession :: Text -> Session -> Value -> IO (Maybe Value)
- fetchContractWithSession :: BlockNumber -> Text -> Addr -> Session -> IO (Maybe Contract)
- fetchSlotWithSession :: BlockNumber -> Text -> Session -> Addr -> W256 -> IO (Maybe Word)
- fetchBlockWithSession :: BlockNumber -> Text -> Session -> IO (Maybe Block)
- fetchBlockFrom :: BlockNumber -> Text -> IO (Maybe Block)
- fetchContractFrom :: BlockNumber -> Text -> Addr -> IO (Maybe Contract)
- fetchSlotFrom :: BlockNumber -> Text -> Addr -> W256 -> IO (Maybe Word)
- http :: BlockNumber -> Text -> Fetcher
- zero :: Fetcher
- oracle :: Maybe State -> Maybe (BlockNumber, Text) -> Bool -> Fetcher
- type Fetcher = Query -> IO (EVM ())
- checksat :: SBool -> Query CheckSatResult
- checkBranch :: SBool -> SBool -> Bool -> Query BranchCondition
Documentation
data RpcQuery a where Source #
Abstract representation of an RPC fetch request
QueryAccount :: Addr -> RpcQuery (ByteString, W256, W256) | |
QueryCode :: Addr -> RpcQuery ByteString | |
QueryBlock :: RpcQuery Block | |
QueryBalance :: Addr -> RpcQuery W256 | |
QueryNonce :: Addr -> RpcQuery W256 | |
QuerySlot :: Addr -> W256 -> RpcQuery W256 | |
QueryChainId :: RpcQuery W256 |
data BlockNumber Source #
Instances
fetchQuery :: Show a => BlockNumber -> (Value -> IO (Maybe Value)) -> RpcQuery a -> IO (Maybe a) Source #
fetchContractWithSession :: BlockNumber -> Text -> Addr -> Session -> IO (Maybe Contract) Source #
fetchBlockWithSession :: BlockNumber -> Text -> Session -> IO (Maybe Block) Source #
fetchBlockFrom :: BlockNumber -> Text -> IO (Maybe Block) Source #
fetchContractFrom :: BlockNumber -> Text -> Addr -> IO (Maybe Contract) Source #
fetchSlotFrom :: BlockNumber -> Text -> Addr -> W256 -> IO (Maybe Word) Source #
checkBranch :: SBool -> SBool -> Bool -> Query BranchCondition Source #
Checks which branches are satisfiable, checking the pathconditions for consistency if the third argument is true. When in debug mode, we do not want to be able to navigate to dead paths, but for normal execution paths with inconsistent pathconditions will be pruned anyway.