| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Morley.Client.Action.Common
Description
Module with functions that used in both transaction sending and contract origination.
Synopsis
- data OperationConstants = OperationConstants {
- ocLastBlockHash :: Text
 - 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 {
- odReplaceExisting :: Bool
 - odName :: AliasHint
 - odBalance :: Mutez
 - odContract :: Contract cp st
 - odStorage :: Value st
 - odMbFee :: Maybe Mutez
 
 - data RevealData = RevealData {
- rdPublicKey :: PublicKey
 - rdMbFee :: Maybe Mutez
 
 - data ClientInput
 - addOperationPrefix :: ByteString -> ByteString
 - buildTxDataWithAlias :: Maybe Alias -> TransactionData -> Builder
 - getAppliedResults :: HasTezosRpc m => Either RunOperation PreApplyOperation -> m (NonEmpty AppliedResult)
 - 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 => Address -> 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
 - revealKeyUnlessRevealed :: (WithClientLog env m, HasTezosRpc m, HasTezosClient m) => Address -> Maybe ScrubbedBytes -> m ()
 
Documentation
data OperationConstants Source #
Datatype that contains various values required for chain operations.
Constructors
| OperationConstants | |
Fields 
  | |
Helper for TransactionData and LTransactionData.
data TransactionData where Source #
Data for a single transaction in a batch.
Constructors
| TransactionData :: forall (t :: T). ParameterScope t => TD (Value t) -> TransactionData | 
Instances
| Buildable TransactionData Source # | |
Defined in Morley.Client.Action.Common Methods build :: TransactionData -> Builder #  | |
data OriginationData Source #
Data for a single origination in a batch
Constructors
| forall cp st.(ParameterScope cp, StorageScope st) => OriginationData | |
Fields 
  | |
data RevealData Source #
Constructors
| RevealData | |
Fields 
  | |
data ClientInput Source #
Standard operation input in morley-client interface.
Instances
| OperationInfoDescriptor ClientInput Source # | |
Defined in Morley.Client.Action.Common Associated Types type TransferInfo ClientInput Source # type OriginationInfo ClientInput Source # type RevealInfo ClientInput Source #  | |
| type TransferInfo 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  | |
buildTxDataWithAlias :: Maybe Alias -> TransactionData -> Builder Source #
Builds TransactionData with additional info about receiver's alias, if present.
getAppliedResults :: HasTezosRpc m => Either RunOperation PreApplyOperation -> m (NonEmpty AppliedResult) 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 => Address -> 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 #
revealKeyUnlessRevealed :: (WithClientLog env m, HasTezosRpc m, HasTezosClient m) => Address -> Maybe ScrubbedBytes -> m () Source #
Reveal key for implicit address if necessary.
Throws an error if given address is a contract address.