Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Module with functions that used in both transaction sending and contract origination.
Synopsis
- data OperationConstants = OperationConstants {
- ocLastBlockHash :: BlockHash
- ocBlockConstants :: BlockConstants
- ocFeeConstants :: FeeConstants
- ocCounter :: TezosInt64
- data TD (t :: Type) = TD {}
- data TransactionData where
- TransactionData :: forall (t :: T). ParameterScope t => TD (Value t) -> TransactionData
- data OriginationData = forall cp st.(ParameterScope cp, StorageScope st) => OriginationData {
- odAliasBehavior :: AliasBehavior
- odName :: ContractAlias
- odBalance :: Mutez
- odContract :: Contract cp st
- odStorage :: Value st
- odDelegate :: Maybe KeyHash
- odMbFee :: Maybe Mutez
- data TransferTicketData = forall t.(ParameterScope t, Comparable t) => TransferTicketData {
- ttdTicketContents :: Value t
- ttdTicketTicketer :: Address
- ttdTicketAmount :: Natural
- ttdDestination :: Address
- ttdEntrypoint :: EpName
- ttdMbFee :: Maybe Mutez
- data RevealData = RevealData {
- rdPublicKey :: PublicKey
- rdMbFee :: Maybe Mutez
- data DelegationData = DelegationData {
- ddDelegate :: Maybe KeyHash
- ddMbFee :: Maybe Mutez
- data ClientInput
- addOperationPrefix :: ByteString -> ByteString
- buildTxDataWithAlias :: Maybe SomeAlias -> TransactionData -> Doc
- buildTxTicketDataWithAlias :: Maybe SomeAlias -> TransferTicketData -> Doc
- getAppliedResults :: HasTezosRpc m => Either RunOperation PreApplyOperation -> m (NonEmpty AppliedResult, [OperationResp WithSource])
- computeFee :: FeeConstants -> Int -> TezosInt64 -> Mutez
- computeStorageLimit :: [AppliedResult] -> ProtocolParameters -> TezosInt64
- convergingFee :: forall op extra m. Monad m => (Mutez -> m op) -> (op -> m (Mutez, extra)) -> m (Mutez, op, extra)
- preProcessOperation :: HasTezosRpc m => ImplicitAddress -> m OperationConstants
- stubSignature :: Signature
- prepareOpForInjection :: ByteString -> Signature -> ByteString
- updateCommonData :: TezosInt64 -> TezosInt64 -> TezosMutez -> CommonOperationData -> CommonOperationData
- toParametersInternals :: ParameterScope t => EpName -> Value t -> ParametersInternal
- mkOriginationScript :: Contract cp st -> Value st -> OriginationScript
- handleOperationResult :: MonadThrow m => RunOperationResult -> Int -> m (NonEmpty AppliedResult, [OperationResp WithSource])
- runErrorsToClientError :: [RunError] -> Maybe ClientRpcError
Documentation
data OperationConstants Source #
Datatype that contains various values required for chain operations.
OperationConstants | |
|
Helper for TransactionData
and LTransactionData
.
data TransactionData where Source #
Data for a single transaction in a batch.
TransactionData :: forall (t :: T). ParameterScope t => TD (Value t) -> TransactionData |
Instances
Buildable TransactionData Source # | |
Defined in Morley.Client.Action.Common build :: TransactionData -> Doc buildList :: [TransactionData] -> Doc |
data OriginationData Source #
Data for a single origination in a batch
forall cp st.(ParameterScope cp, StorageScope st) => OriginationData | |
|
data TransferTicketData Source #
forall t.(ParameterScope t, Comparable t) => TransferTicketData | |
|
data RevealData Source #
RevealData | |
|
data DelegationData Source #
DelegationData | |
|
data ClientInput Source #
Standard operation input in morley-client interface.
Instances
OperationInfoDescriptor ClientInput Source # | |
Defined in Morley.Client.Action.Common type TransferInfo ClientInput Source # type TransferTicketInfo ClientInput Source # type OriginationInfo ClientInput Source # type RevealInfo ClientInput Source # type DelegationInfo ClientInput Source # | |
type DelegationInfo ClientInput Source # | |
Defined in Morley.Client.Action.Common | |
type OriginationInfo ClientInput Source # | |
Defined in Morley.Client.Action.Common | |
type RevealInfo ClientInput Source # | |
Defined in Morley.Client.Action.Common | |
type TransferInfo ClientInput Source # | |
Defined in Morley.Client.Action.Common | |
type TransferTicketInfo ClientInput Source # | |
Defined in Morley.Client.Action.Common |
buildTxDataWithAlias :: Maybe SomeAlias -> TransactionData -> Doc Source #
Builds TransactionData
with additional info about receiver's alias, if present.
buildTxTicketDataWithAlias :: Maybe SomeAlias -> TransferTicketData -> Doc Source #
Builds TransactionData
with additional info about receiver's alias, if present.
getAppliedResults :: HasTezosRpc m => Either RunOperation PreApplyOperation -> m (NonEmpty AppliedResult, [OperationResp WithSource]) Source #
Perform runOperation or preApplyOperations and combine the results.
If an error occurs, this function tries to turn errors returned by RPC
into ClientRpcError
. If it can't do the conversion, UnexpectedErrors
will be thrown.
computeFee :: FeeConstants -> Int -> TezosInt64 -> Mutez Source #
Compute fee for operation.
computeStorageLimit :: [AppliedResult] -> ProtocolParameters -> TezosInt64 Source #
Compute storage limit based on the results of the operations application
and given ProtocolParameters
.
convergingFee :: forall op extra m. Monad m => (Mutez -> m op) -> (op -> m (Mutez, extra)) -> m (Mutez, op, extra) Source #
convergingFee mkOperation countFee
tries to find the most minimal fee
F
and the respective operation Op
so that mkOperation F = Op
and
countFee Op <= F
.
preProcessOperation :: HasTezosRpc m => ImplicitAddress -> m OperationConstants Source #
Preprocess chain operation in order to get required constants.
stubSignature :: Signature Source #
prepareOpForInjection :: ByteString -> Signature -> ByteString Source #
updateCommonData :: TezosInt64 -> TezosInt64 -> TezosMutez -> CommonOperationData -> CommonOperationData Source #
Update common operation data based on preliminary run which estimates storage and gas limits and fee.
Reference implementation adds 100 gas and 20 bytes to the limits for safety.
toParametersInternals :: ParameterScope t => EpName -> Value t -> ParametersInternal Source #
mkOriginationScript :: Contract cp st -> Value st -> OriginationScript Source #
handleOperationResult :: MonadThrow m => RunOperationResult -> Int -> m (NonEmpty AppliedResult, [OperationResp WithSource]) Source #
Handle a result of an operation: throw errors if there was an error, return a nonempty list of applied results if there weren't.
runErrorsToClientError :: [RunError] -> Maybe ClientRpcError Source #
When an error happens, we will get a list of RunError
in response. This
list often contains more than one item. We tested which errors are returned
in certain scenarios and added handling of such scenarios here. We don't rely
on any specific order of errors and on the number of errors. For example, in
case of bad parameter this number can be different.