morley-client-0.2.1: Client to interact with the Tezos blockchain
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Client.Action.Common

Description

Module with functions that used in both transaction sending and contract origination.

Synopsis

Documentation

data OperationConstants Source #

Datatype that contains various values required for chain operations.

Constructors

OperationConstants 

Fields

data TD (t :: Type) Source #

Constructors

TD 

Fields

data TransactionData where Source #

Data for a single transaction in a batch.

Constructors

TransactionData :: forall (t :: T). ParameterScope t => TD (Value t) -> TransactionData 

Instances

Instances details
Buildable TransactionData Source # 
Instance details

Defined in Morley.Client.Action.Common

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

buildTxDataWithAlias :: Maybe Text -> TransactionData -> Builder Source #

Builds TransactionData with additional info about receiver's alias, if present.

getAppliedResults :: HasTezosRpc m => Either RunOperation PreApplyOperation -> m (NonEmpty AppliedResult, [InternalOperationData]) 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 #

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) => ImplicitAddress -> Maybe ScrubbedBytes -> m () Source #

Reveal key for implicit address if necessary.

Throws an error if given address is a contract address.

handleOperationResult :: MonadThrow m => RunOperationResult -> Int -> m (NonEmpty AppliedResult, [InternalOperationData]) 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.