| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Morley.Client.RPC.Types
Description
This module contains various types which are used in octez-node RPC API.
Documentation for RPC API can be found e. g. here (010 is the protocol, change to the desired one).
Note that errors are reported a bit inconsistently by RPC. For more information see this question and this issue.
Synopsis
- data AppliedResult = AppliedResult {
- arConsumedMilliGas :: TezosInt64
- arStorageSize :: TezosInt64
- arPaidStorageDiff :: TezosInt64
- arOriginatedContracts :: [ContractAddress]
- arAllocatedDestinationContracts :: TezosInt64
- data BlockConstants = BlockConstants {}
- newtype BlockHash = BlockHash {
- unBlockHash :: Text
- data BlockHeaderNoHash = BlockHeaderNoHash {}
- data BlockHeader = BlockHeader {}
- data FeeConstants = FeeConstants {
- fcBase :: Mutez
- fcMutezPerGas :: Milli
- fcMutezPerOpByte :: Milli
- data BlockId
- data BlockOperation = BlockOperation {}
- data CommonOperationData = CommonOperationData {
- codSource :: ImplicitAddress
- codFee :: TezosMutez
- codCounter :: TezosInt64
- codGasLimit :: TezosInt64
- codStorageLimit :: TezosInt64
- data DelegationOperation = DelegationOperation {
- doDelegate :: Maybe KeyHash
- data ForgeOperation = ForgeOperation {}
- data GetBigMap = GetBigMap {}
- data CalcSize = CalcSize {}
- newtype ScriptSize = ScriptSize {}
- data GetBigMapResult
- = GetBigMapResult Expression
- | GetBigMapNotFound
- data InternalOperation = InternalOperation {}
- data WithSource a = WithSource {
- wsSource :: Address
- wsOtherData :: a
- data OperationContent = OperationContent {}
- newtype OperationHash = OperationHash {}
- type OperationInput = WithCommonOperationData (OperationInfo RPCInput)
- data OperationResp f
- data OperationRespWithMeta = OperationRespWithMeta {}
- newtype OperationMetadata = OperationMetadata {}
- data OperationResult
- data OriginationOperation = OriginationOperation {
- ooBalance :: TezosMutez
- ooDelegate :: Maybe KeyHash
- ooScript :: OriginationScript
- data OriginationScript = OriginationScript {}
- data ParametersInternal = ParametersInternal {
- piEntrypoint :: Text
- piValue :: Expression
- data PreApplyOperation = PreApplyOperation {
- paoProtocol :: Text
- paoBranch :: BlockHash
- paoContents :: NonEmpty OperationInput
- paoSignature :: Signature
- data ProtocolParameters = ProtocolParameters {
- ppOriginationSize :: Int
- ppHardGasLimitPerOperation :: TezosInt64
- ppHardStorageLimitPerOperation :: TezosInt64
- ppMinimalBlockDelay :: TezosNat
- ppCostPerByte :: TezosMutez
- ppHardGasLimitPerBlock :: TezosInt64
- data RevealOperation = RevealOperation {
- roPublicKey :: PublicKey
- data RunCode = RunCode {}
- data RunCodeResult = RunCodeResult {
- rcrStorage :: Expression
- data RunMetadata = RunMetadata {}
- data RunOperation = RunOperation {}
- data RunOperationInternal = RunOperationInternal {
- roiBranch :: BlockHash
- roiContents :: NonEmpty OperationInput
- roiSignature :: Signature
- data RunOperationResult = RunOperationResult {}
- data RPCInput
- data TransactionOperation = TransactionOperation {
- toAmount :: TezosMutez
- toDestination :: Address
- toParameters :: ParametersInternal
- data TransferTicketOperation = TransferTicketOperation {
- ttoTicketContents :: Expression
- ttoTicketTy :: Expression
- ttoTicketTicketer :: Address
- ttoTicketAmount :: TezosNat
- ttoDestination :: Address
- ttoEntrypoint :: Text
- data WithCommonOperationData a = WithCommonOperationData {}
- data EventOperation = EventOperation {}
- data MonitorHeadsStep a
- data GetTicketBalance = GetTicketBalance {
- gtbTicketer :: ContractAddress
- gtbContentType :: Expression
- gtbContent :: Expression
- data GetAllTicketBalancesResponse = GetAllTicketBalancesResponse {
- gatbrTicketer :: ContractAddress
- gatbrContentType :: Expression
- gatbrContent :: Expression
- gatbrAmount :: TezosNat
- data PackData = PackData {}
- data PackDataResult = PackDataResult {}
- mkCommonOperationData :: ProtocolParameters -> ("sender" :! ImplicitAddress) -> ("counter" :! TezosInt64) -> ("num_operations" :? Int64) -> CommonOperationData
- data RunError
- = RuntimeError ContractAddress
- | ScriptRejected Expression
- | BadContractParameter Address
- | InvalidConstant Expression Expression
- | InvalidContract Address
- | InconsistentTypes Expression Expression
- | InvalidPrimitive [Text] Text
- | InvalidSyntacticConstantError Expression Expression
- | InvalidExpressionKind [Text] Text
- | InvalidContractNotation Text
- | UnexpectedContract
- | IllFormedType Expression
- | UnexpectedOperation
- | REEmptyTransaction ImplicitAddress
- | ScriptOverflow
- | GasExhaustedOperation
- | MutezAdditionOverflow [TezosInt64]
- | MutezSubtractionUnderflow [TezosInt64]
- | MutezMultiplicationOverflow TezosInt64 TezosInt64
- | CantPayStorageFee
- | BalanceTooLow ("balance" :! Mutez) ("required" :! Mutez)
- | PreviouslyRevealedKey ImplicitAddress
- | NonExistingContract Address
- | InvalidB58Check Text
- | UnregisteredDelegate ImplicitAddress
- | FailedUnDelegation ImplicitAddress
- | DelegateAlreadyActive
- | IllTypedContract Expression
- | IllTypedData Expression Expression
- | BadStack BadStackInformation
- | ForbiddenZeroAmountTicket
- | REEmptyImplicitContract ImplicitAddress
- data InternalError
- = CounterInThePast ImplicitAddress ("expected" :! Word) ("found" :! Word)
- | UnrevealedKey ImplicitAddress
- | Failure Text
- _RuntimeError :: Prism' RunError ContractAddress
- _ScriptRejected :: Prism' RunError Expression
- _BadContractParameter :: Prism' RunError Address
- _InvalidConstant :: Prism' RunError (Expression, Expression)
- _InconsistentTypes :: Prism' RunError (Expression, Expression)
- _InvalidPrimitive :: Prism' RunError ([Text], Text)
- _InvalidSyntacticConstantError :: Prism' RunError (Expression, Expression)
- _InvalidExpressionKind :: Prism' RunError ([Text], Text)
- _InvalidContractNotation :: Prism' RunError Text
- _UnexpectedContract :: Prism' RunError ()
- _IllFormedType :: Prism' RunError Expression
- _UnexpectedOperation :: Prism' RunError ()
- _REEmptyTransaction :: Prism' RunError ImplicitAddress
- _ScriptOverflow :: Prism' RunError ()
- _PreviouslyRevealedKey :: Prism' RunError ImplicitAddress
- _GasExhaustedOperation :: Prism' RunError ()
- _UnregisteredDelegate :: Prism' RunError ImplicitAddress
- wcoCommonDataL :: Lens' (WithCommonOperationData a) CommonOperationData
Documentation
data AppliedResult Source #
Constructors
| AppliedResult | |
Fields
| |
Instances
| Monoid AppliedResult Source # | |
Defined in Morley.Client.RPC.Types Methods mempty :: AppliedResult # mappend :: AppliedResult -> AppliedResult -> AppliedResult # mconcat :: [AppliedResult] -> AppliedResult # | |
| Semigroup AppliedResult Source # | |
Defined in Morley.Client.RPC.Types Methods (<>) :: AppliedResult -> AppliedResult -> AppliedResult # sconcat :: NonEmpty AppliedResult -> AppliedResult # stimes :: Integral b => b -> AppliedResult -> AppliedResult # | |
| Show AppliedResult Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> AppliedResult -> ShowS # show :: AppliedResult -> String # showList :: [AppliedResult] -> ShowS # | |
data BlockConstants Source #
Constructors
| BlockConstants | |
Fields
| |
Instances
| FromJSON BlockConstants Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser BlockConstants # parseJSONList :: Value -> Parser [BlockConstants] # | |
Constructors
| BlockHash | |
Fields
| |
Instances
| FromJSON BlockHash Source # | |
| ToJSON BlockHash Source # | |
Defined in Morley.Client.RPC.Types | |
| Show BlockHash Source # | |
| Eq BlockHash Source # | |
| Ord BlockHash Source # | |
| ToHttpApiData BlockHash Source # | |
Defined in Morley.Client.RPC.Types Methods toUrlPiece :: BlockHash -> Text # toEncodedUrlPiece :: BlockHash -> Builder # toHeader :: BlockHash -> ByteString # toQueryParam :: BlockHash -> Text # | |
| Buildable BlockHash Source # | |
Defined in Morley.Client.RPC.Types | |
data BlockHeaderNoHash Source #
Constructors
| BlockHeaderNoHash | |
Fields | |
Instances
| FromJSON BlockHeaderNoHash Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser BlockHeaderNoHash # parseJSONList :: Value -> Parser [BlockHeaderNoHash] # | |
data BlockHeader Source #
The whole block header.
Constructors
| BlockHeader | |
Fields
| |
Instances
| FromJSON BlockHeader Source # | |
Defined in Morley.Client.RPC.Types | |
| ToJSON BlockHeader Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: BlockHeader -> Value # toEncoding :: BlockHeader -> Encoding # toJSONList :: [BlockHeader] -> Value # toEncodingList :: [BlockHeader] -> Encoding # | |
data FeeConstants Source #
Constructors
| FeeConstants | |
Fields
| |
Instances
| Default FeeConstants Source # | At the moment of writing, Tezos always uses these constants. |
Defined in Morley.Client.RPC.Types Methods def :: FeeConstants # | |
A block identifier as submitted to RPC.
A block can be referenced by head, genesis, level or block hash
Constructors
| HeadId | Identifier referring to the head block. |
| FinalHeadId | Identifier of the most recent block guaranteed to have been finalized. See: https://web.archive.org/web/20220305165609/https://tezos.gitlab.io/protocols/tenderbake.html#operations |
| GenesisId | Identifier referring to the genesis block. |
| LevelId Natural | Identifier referring to a block by its level. |
| BlockHashId BlockHash | Idenfitier referring to a block by its hash in Base58Check notation. |
| AtDepthId Natural | Identifier of a block at specific depth relative to |
Instances
| Show BlockId Source # | |
| Eq BlockId Source # | |
| ToHttpApiData BlockId Source # | |
Defined in Morley.Client.RPC.Types Methods toUrlPiece :: BlockId -> Text # toEncodedUrlPiece :: BlockId -> Builder # toHeader :: BlockId -> ByteString # toQueryParam :: BlockId -> Text # | |
| HasCLReader BlockId Source # | |
Defined in Morley.Client.RPC.Types | |
| Buildable BlockId Source # | |
Defined in Morley.Client.RPC.Types | |
data BlockOperation Source #
$operation in Tezos docs.
Constructors
| BlockOperation | |
Fields
| |
Instances
| FromJSON BlockOperation Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser BlockOperation # parseJSONList :: Value -> Parser [BlockOperation] # | |
data CommonOperationData Source #
Data that is common for transaction and origination operations.
Constructors
| CommonOperationData | |
Fields
| |
Instances
| FromJSON CommonOperationData Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser CommonOperationData # parseJSONList :: Value -> Parser [CommonOperationData] # | |
| ToJSON CommonOperationData Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: CommonOperationData -> Value # toEncoding :: CommonOperationData -> Encoding # toJSONList :: [CommonOperationData] -> Value # toEncodingList :: [CommonOperationData] -> Encoding # | |
data DelegationOperation Source #
Constructors
| DelegationOperation | |
Fields
| |
Instances
data ForgeOperation Source #
Constructors
| ForgeOperation | |
Fields | |
Instances
| ToJSON ForgeOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: ForgeOperation -> Value # toEncoding :: ForgeOperation -> Encoding # toJSONList :: [ForgeOperation] -> Value # toEncodingList :: [ForgeOperation] -> Encoding # | |
Constructors
| CalcSize | |
newtype ScriptSize Source #
Constructors
| ScriptSize | |
Fields | |
Instances
| FromJSON ScriptSize Source # | |
Defined in Morley.Client.RPC.Types | |
data GetBigMapResult Source #
Constructors
| GetBigMapResult Expression | |
| GetBigMapNotFound |
Instances
| FromJSON GetBigMapResult Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser GetBigMapResult # parseJSONList :: Value -> Parser [GetBigMapResult] # | |
data InternalOperation Source #
Constructors
| InternalOperation | |
Fields | |
Instances
| FromJSON InternalOperation Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser InternalOperation # parseJSONList :: Value -> Parser [InternalOperation] # | |
data WithSource a Source #
Constructors
| WithSource | |
Fields
| |
Instances
| Functor WithSource Source # | |
Defined in Morley.Client.RPC.Types Methods fmap :: (a -> b) -> WithSource a -> WithSource b # (<$) :: a -> WithSource b -> WithSource a # | |
| FromJSON a => FromJSON (WithSource a) Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser (WithSource a) # parseJSONList :: Value -> Parser [WithSource a] # | |
| Show a => Show (WithSource a) Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> WithSource a -> ShowS # show :: WithSource a -> String # showList :: [WithSource a] -> ShowS # | |
| Buildable a => Buildable (WithSource a) Source # | |
Defined in Morley.Client.RPC.Types | |
data OperationContent Source #
Constructors
| OperationContent | |
Fields | |
Instances
| FromJSON OperationContent Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OperationContent # parseJSONList :: Value -> Parser [OperationContent] # | |
newtype OperationHash Source #
Constructors
| OperationHash | |
Fields | |
Instances
| FromJSON OperationHash Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OperationHash # parseJSONList :: Value -> Parser [OperationHash] # | |
| Show OperationHash Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> OperationHash -> ShowS # show :: OperationHash -> String # showList :: [OperationHash] -> ShowS # | |
| Eq OperationHash Source # | |
Defined in Morley.Client.RPC.Types Methods (==) :: OperationHash -> OperationHash -> Bool # (/=) :: OperationHash -> OperationHash -> Bool # | |
| CmdArg OperationHash Source # | |
Defined in Morley.Client.TezosClient.Types Methods toCmdArg :: OperationHash -> String Source # | |
| Buildable OperationHash Source # | |
Defined in Morley.Client.RPC.Types | |
data OperationResp f Source #
Contents of an operation that can appear in RPC responses.
Constructors
| TransactionOpResp (f TransactionOperation) | Operation with kind |
| TransferTicketOpResp (f TransferTicketOperation) | Operation with kind |
| OriginationOpResp (f OriginationOperation) | Operation with kind |
| DelegationOpResp (f DelegationOperation) | Operation with kind |
| RevealOpResp (f RevealOperation) | Operation with kind |
| EventOpResp (f EventOperation) | Operation with kind |
| OtherOpResp Text | Response we don't handle yet. |
Instances
| (forall a. FromJSON a => FromJSON (f a)) => FromJSON (OperationResp f) Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser (OperationResp f) # parseJSONList :: Value -> Parser [OperationResp f] # | |
| (forall a. Show a => Show (f a)) => Show (OperationResp f) Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> OperationResp f -> ShowS # show :: OperationResp f -> String # showList :: [OperationResp f] -> ShowS # | |
| (forall a. Buildable a => Buildable (f a)) => Buildable (OperationResp f) Source # | |
Defined in Morley.Client.RPC.Types | |
data OperationRespWithMeta Source #
Constructors
| OperationRespWithMeta | |
Instances
| FromJSON OperationRespWithMeta Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OperationRespWithMeta # parseJSONList :: Value -> Parser [OperationRespWithMeta] # | |
newtype OperationMetadata Source #
Constructors
| OperationMetadata | |
Fields | |
Instances
| FromJSON OperationMetadata Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OperationMetadata # parseJSONList :: Value -> Parser [OperationMetadata] # | |
data OperationResult Source #
Constructors
| OperationApplied AppliedResult | |
| OperationFailed [RunError] |
Instances
| FromJSON OperationResult Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OperationResult # parseJSONList :: Value -> Parser [OperationResult] # | |
data OriginationOperation Source #
All the data needed to perform contract origination through Tezos RPC interface
Constructors
| OriginationOperation | |
Fields
| |
Instances
data OriginationScript Source #
Constructors
| OriginationScript | |
Instances
data ParametersInternal Source #
Constructors
| ParametersInternal | |
Fields
| |
Instances
data PreApplyOperation Source #
Constructors
| PreApplyOperation | |
Fields
| |
Instances
| ToJSON PreApplyOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: PreApplyOperation -> Value # toEncoding :: PreApplyOperation -> Encoding # toJSONList :: [PreApplyOperation] -> Value # toEncodingList :: [PreApplyOperation] -> Encoding # | |
data ProtocolParameters Source #
Protocol-wide constants.
There are more constants, but currently, we are using only these in our code.
Constructors
| ProtocolParameters | |
Fields
| |
Instances
| FromJSON ProtocolParameters Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser ProtocolParameters # parseJSONList :: Value -> Parser [ProtocolParameters] # | |
data RevealOperation Source #
All the data needed to perform key revealing through Tezos RPC interface
Constructors
| RevealOperation | |
Fields
| |
Instances
Data required for calling run_code RPC endpoint.
Constructors
| RunCode | |
data RunCodeResult Source #
Result storage of run_code RPC endpoint call.
Actual resulting JSON has more contents, but currently we're interested only in resulting storage.
Constructors
| RunCodeResult | |
Fields
| |
Instances
| FromJSON RunCodeResult Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser RunCodeResult # parseJSONList :: Value -> Parser [RunCodeResult] # | |
data RunMetadata Source #
Constructors
| RunMetadata | |
Instances
| FromJSON RunMetadata Source # | |
Defined in Morley.Client.RPC.Types | |
data RunOperation Source #
Constructors
| RunOperation | |
Fields | |
Instances
| ToJSON RunOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: RunOperation -> Value # toEncoding :: RunOperation -> Encoding # toJSONList :: [RunOperation] -> Value # toEncodingList :: [RunOperation] -> Encoding # | |
data RunOperationInternal Source #
Constructors
| RunOperationInternal | |
Fields
| |
Instances
| ToJSON RunOperationInternal Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: RunOperationInternal -> Value # toEncoding :: RunOperationInternal -> Encoding # toJSONList :: [RunOperationInternal] -> Value # toEncodingList :: [RunOperationInternal] -> Encoding # | |
data RunOperationResult Source #
Constructors
| RunOperationResult | |
Fields | |
Instances
| FromJSON RunOperationResult Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser RunOperationResult # parseJSONList :: Value -> Parser [RunOperationResult] # | |
Designates an input RPC data that we supply to perform an operation.
Instances
| OperationInfoDescriptor RPCInput Source # | |
Defined in Morley.Client.RPC.Types Associated Types type TransferInfo RPCInput Source # type TransferTicketInfo RPCInput Source # type OriginationInfo RPCInput Source # type RevealInfo RPCInput Source # type DelegationInfo RPCInput Source # | |
| type DelegationInfo RPCInput Source # | |
Defined in Morley.Client.RPC.Types | |
| type OriginationInfo RPCInput Source # | |
Defined in Morley.Client.RPC.Types | |
| type RevealInfo RPCInput Source # | |
Defined in Morley.Client.RPC.Types | |
| type TransferInfo RPCInput Source # | |
Defined in Morley.Client.RPC.Types | |
| type TransferTicketInfo RPCInput Source # | |
Defined in Morley.Client.RPC.Types | |
data TransactionOperation Source #
All the data needed to perform a transaction through Tezos RPC interface. For additional information, please refer to RPC documentation http://tezos.gitlab.io/api/rpc.html
Constructors
| TransactionOperation | |
Fields
| |
Instances
| FromJSON TransactionOperation Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser TransactionOperation # parseJSONList :: Value -> Parser [TransactionOperation] # | |
| ToJSON TransactionOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: TransactionOperation -> Value # toEncoding :: TransactionOperation -> Encoding # toJSONList :: [TransactionOperation] -> Value # toEncodingList :: [TransactionOperation] -> Encoding # | |
| Show TransactionOperation Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> TransactionOperation -> ShowS # show :: TransactionOperation -> String # showList :: [TransactionOperation] -> ShowS # | |
| ToJSONObject TransactionOperation Source # | |
Defined in Morley.Client.RPC.Types | |
| Buildable TransactionOperation Source # | |
Defined in Morley.Client.RPC.Types | |
data TransferTicketOperation Source #
Constructors
| TransferTicketOperation | |
Fields
| |
Instances
| ToJSON TransferTicketOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: TransferTicketOperation -> Value # toEncoding :: TransferTicketOperation -> Encoding # toJSONList :: [TransferTicketOperation] -> Value # | |
| Show TransferTicketOperation Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> TransferTicketOperation -> ShowS # show :: TransferTicketOperation -> String # showList :: [TransferTicketOperation] -> ShowS # | |
| ToJSONObject TransferTicketOperation Source # | |
Defined in Morley.Client.RPC.Types | |
| Buildable TransferTicketOperation Source # | |
Defined in Morley.Client.RPC.Types | |
data WithCommonOperationData a Source #
Some operation data accompanied with common data.
Constructors
| WithCommonOperationData | |
Fields
| |
Instances
| FromJSON a => FromJSON (WithCommonOperationData a) Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser (WithCommonOperationData a) # parseJSONList :: Value -> Parser [WithCommonOperationData a] # | |
| ToJSONObject a => ToJSON (WithCommonOperationData a) Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: WithCommonOperationData a -> Value # toEncoding :: WithCommonOperationData a -> Encoding # toJSONList :: [WithCommonOperationData a] -> Value # toEncodingList :: [WithCommonOperationData a] -> Encoding # | |
data EventOperation Source #
Constructors
| EventOperation | |
Instances
data MonitorHeadsStep a Source #
Constructors
| MonitorHeadsStop a | |
| MonitorHeadsContinue |
data GetTicketBalance Source #
Constructors
| GetTicketBalance | |
Fields
| |
Instances
| ToJSON GetTicketBalance Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: GetTicketBalance -> Value # toEncoding :: GetTicketBalance -> Encoding # toJSONList :: [GetTicketBalance] -> Value # toEncodingList :: [GetTicketBalance] -> Encoding # | |
data GetAllTicketBalancesResponse Source #
Constructors
| GetAllTicketBalancesResponse | |
Fields
| |
Instances
| FromJSON GetAllTicketBalancesResponse Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser GetAllTicketBalancesResponse # parseJSONList :: Value -> Parser [GetAllTicketBalancesResponse] # | |
Instances
| ToJSON PackData Source # | |
Defined in Morley.Client.RPC.Types | |
| Buildable PackData Source # | |
Defined in Morley.Client.RPC.Types | |
data PackDataResult Source #
Constructors
| PackDataResult | |
Instances
| FromJSON PackDataResult Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser PackDataResult # parseJSONList :: Value -> Parser [PackDataResult] # | |
| Buildable PackDataResult Source # | |
Defined in Morley.Client.RPC.Types | |
mkCommonOperationData :: ProtocolParameters -> ("sender" :! ImplicitAddress) -> ("counter" :! TezosInt64) -> ("num_operations" :? Int64) -> CommonOperationData Source #
Create CommonOperationData based on current blockchain protocol parameters
and sender info. This data is used for operation simulation.
num_operations parameter can be used for smarter gas limit estimation. If
Nothing, the gas limit is set to ppHardGasLimitPerOperation, but that
puts a hard low limit on the number of operations that will fit into one
batch. If num_operations is set, then gas limit is estimated as
\[ \mathrm{min}\left(\mathbf{hard\_gas\_limit\_per\_operation}, \left\lfloor \frac{\mathbf{hard\_gas\_limit\_per\_block}} {num\_operations}\right\rfloor\right) \]
This works well enough for the case of many small operations, but will break
when there is one big one and a lot of small ones. That said, specifying
num_operations will work in all cases where not specifying it would, and
then some, so it's recommended to specify it whenever possible.
num_operations is assumed to be greater than 0, otherwise it'll be
silently ignored.
Fee isn't accounted during operation simulation, so it's safe to use zero amount.
Real operation fee is calculated later using octez-client.
Errors
Errors that are sent as part of operation result in an OK response (status 200). They are semi-formally defined as errors that can happen when a contract is executed and something goes wrong.
Constructors
data InternalError Source #
Errors that are sent as part of an "Internal Server Error" response (HTTP code 500).
We call them internal because of the HTTP code, but we shouldn't treat them as internal. They can be easily triggered by making a failing operation.
Constructors
| CounterInThePast | An operation assumed a contract counter in the past. |
| UnrevealedKey | One tried to apply a manager operation without revealing the manager public key. |
Fields
| |
| Failure Text | Failure reported without specific id |
Instances
| FromJSON InternalError Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser InternalError # parseJSONList :: Value -> Parser [InternalError] # | |
| Show InternalError Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> InternalError -> ShowS # show :: InternalError -> String # showList :: [InternalError] -> ShowS # | |
| Buildable InternalError Source # | |
Defined in Morley.Client.RPC.Types | |
Prisms
_RuntimeError :: Prism' RunError ContractAddress Source #
_ScriptRejected :: Prism' RunError Expression Source #
_BadContractParameter :: Prism' RunError Address Source #
_InvalidConstant :: Prism' RunError (Expression, Expression) Source #
_InconsistentTypes :: Prism' RunError (Expression, Expression) Source #
_InvalidSyntacticConstantError :: Prism' RunError (Expression, Expression) Source #
_UnexpectedContract :: Prism' RunError () Source #
_IllFormedType :: Prism' RunError Expression Source #
_REEmptyTransaction :: Prism' RunError ImplicitAddress Source #
_ScriptOverflow :: Prism' RunError () Source #
_PreviouslyRevealedKey :: Prism' RunError ImplicitAddress Source #
_UnregisteredDelegate :: Prism' RunError ImplicitAddress Source #