Safe Haskell | None |
---|---|
Language | Haskell2010 |
Functions useful for implementing instances of type classes from this package. Monads and actual instances are defined in separate modules.
Synopsis
- runRequestAcceptStatusImpl :: (WithClientLog env m, MonadIO m, MonadThrow m) => ClientEnv -> Maybe [Status] -> Request -> m Response
- throwClientErrorImpl :: forall m a. MonadThrow m => ClientError -> m a
- getBlockHashImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m Text
- getCounterImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m TezosInt64
- getBlockHeaderImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m BlockHeader
- getBlockConstantsImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m BlockConstants
- getBlockOperationsImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m [[BlockOperation]]
- getProtocolParametersImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m ProtocolParameters
- runOperationImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> RunOperation -> m RunOperationResult
- preApplyOperationsImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> [PreApplyOperation] -> m [RunOperationResult]
- forgeOperationImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> ForgeOperation -> m HexJSONByteString
- injectOperationImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => HexJSONByteString -> m OperationHash
- getContractScriptImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m OriginationScript
- getContractStorageAtBlockImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m Expression
- getContractBigMapImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> GetBigMap -> m GetBigMapResult
- getBigMapValueAtBlockImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Natural -> Text -> m Expression
- getBigMapValuesAtBlockImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Natural -> Maybe Natural -> Maybe Natural -> m Expression
- getBalanceImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m Mutez
- getManagerKeyImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m (Maybe PublicKey)
- runCodeImpl :: (RunClient m, MonadCatch m) => BlockId -> RunCode -> m RunCodeResult
- getChainIdImpl :: (RunClient m, MonadCatch m) => m ChainId
- getDelegateImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m (Maybe KeyHash)
- retryOnTimeout :: (MonadUnliftIO m, MonadThrow m) => Bool -> m a -> m a
- failOnTimeout :: (MonadUnliftIO m, MonadThrow m) => m a -> m a
- retryOnceOnTimeout :: (MonadUnliftIO m, MonadThrow m) => m a -> m a
- waitBeforeRetry :: (MonadIO m, HasTezosRpc m, WithClientLog env m) => m ()
- handleInvalidCounterRpc :: MonadThrow m => m a -> ClientRpcError -> m a
RunClient
runRequestAcceptStatusImpl :: (WithClientLog env m, MonadIO m, MonadThrow m) => ClientEnv -> Maybe [Status] -> Request -> m Response Source #
throwClientErrorImpl :: forall m a. MonadThrow m => ClientError -> m a Source #
HasTezosRpc
getBlockHashImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m Text Source #
getCounterImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m TezosInt64 Source #
getBlockHeaderImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m BlockHeader Source #
getBlockConstantsImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m BlockConstants Source #
getBlockOperationsImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m [[BlockOperation]] Source #
getProtocolParametersImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> m ProtocolParameters Source #
runOperationImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> RunOperation -> m RunOperationResult Source #
preApplyOperationsImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> [PreApplyOperation] -> m [RunOperationResult] Source #
forgeOperationImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> ForgeOperation -> m HexJSONByteString Source #
injectOperationImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => HexJSONByteString -> m OperationHash Source #
getContractScriptImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m OriginationScript Source #
getContractStorageAtBlockImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m Expression Source #
getContractBigMapImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> GetBigMap -> m GetBigMapResult Source #
getBigMapValueAtBlockImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Natural -> Text -> m Expression Source #
getBigMapValuesAtBlockImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Natural -> Maybe Natural -> Maybe Natural -> m Expression Source #
getBalanceImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m Mutez Source #
getManagerKeyImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m (Maybe PublicKey) Source #
Similar to getManagerKey
, but retries once on timeout.
runCodeImpl :: (RunClient m, MonadCatch m) => BlockId -> RunCode -> m RunCodeResult Source #
getChainIdImpl :: (RunClient m, MonadCatch m) => m ChainId Source #
getDelegateImpl :: (RunClient m, MonadUnliftIO m, MonadCatch m) => BlockId -> Address -> m (Maybe KeyHash) Source #
Timeouts and retries
retryOnTimeout :: (MonadUnliftIO m, MonadThrow m) => Bool -> m a -> m a Source #
Helper function that retries a monadic action in case action hasn't succeed
in timeoutInterval
. In case retry didn't help, error that indicates
timeout is thrown.
failOnTimeout :: (MonadUnliftIO m, MonadThrow m) => m a -> m a Source #
Helper function that consider action failed in case of timeout,
because it's unsafe to perform some of the actions twice. E.g. performing two injectOperation
action can lead to a situation when operation is injected twice.
retryOnceOnTimeout :: (MonadUnliftIO m, MonadThrow m) => m a -> m a Source #
Helper function that retries action once in case of timeout. If retry ended up with timeout
as well, action is considered failed. It's safe to retry read-only actions that don't update chain state
or tezos-client
config/environment.
waitBeforeRetry :: (MonadIO m, HasTezosRpc m, WithClientLog env m) => m () Source #
Wait for a reasonable amount of time before retrying an action that failed due to invalid counter. The waiting time depends on protocol parameters.
handleInvalidCounterRpc :: MonadThrow m => m a -> ClientRpcError -> m a Source #
Retry action if it failed due to invalid counter (already used one).