| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Morley.Client.RPC.Types
Description
This module contains various types which are used in tezos-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 {
- arConsumedGas :: TezosInt64
 - arStorageSize :: TezosInt64
 - arPaidStorageDiff :: TezosInt64
 - arOriginatedContracts :: [Address]
 - 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 {
- boHash :: Text
 - boContents :: [OperationResp]
 
 - data CommonOperationData = CommonOperationData {
- codSource :: Address
 - codFee :: TezosMutez
 - codCounter :: TezosInt64
 - codGasLimit :: TezosInt64
 - codStorageLimit :: TezosInt64
 
 - data ForgeOperation = ForgeOperation {}
 - data GetBigMap = GetBigMap {}
 - data GetBigMapResult
- = GetBigMapResult Expression
 - | GetBigMapNotFound
 
 - newtype InternalOperation = InternalOperation {}
 - data OperationContent = OperationContent RunMetadata
 - newtype OperationHash = OperationHash {}
 - data OperationInput = OperationInput {}
 - data OperationResp
 - data OperationResult
 - data OriginationOperation = OriginationOperation {
- ooBalance :: TezosMutez
 - ooScript :: OriginationScript
 
 - data OriginationScript = OriginationScript {}
 - data ParametersInternal = ParametersInternal {
- piEntrypoint :: Text
 - piValue :: Expression
 
 - data PreApplyOperation = PreApplyOperation {
- paoProtocol :: Text
 - paoBranch :: Text
 - paoContents :: NonEmpty OperationInput
 - paoSignature :: Signature
 
 - data ProtocolParameters = ProtocolParameters {
- ppOriginationSize :: Int
 - ppHardGasLimitPerOperation :: TezosInt64
 - ppHardStorageLimitPerOperation :: TezosInt64
 - ppMinimalBlockDelay :: TezosNat
 - ppCostPerByte :: TezosMutez
 
 - data RevealOperation = RevealOperation {
- roPublicKey :: PublicKey
 
 - data RunCode = RunCode {}
 - data RunCodeResult = RunCodeResult {
- rcrStorage :: Expression
 
 - data RunMetadata = RunMetadata {}
 - data RunOperation = RunOperation {}
 - data RunOperationInternal = RunOperationInternal {
- roiBranch :: Text
 - roiContents :: NonEmpty OperationInput
 - roiSignature :: Signature
 
 - data RunOperationResult = RunOperationResult {}
 - data RPCInput
 - data TransactionOperation = TransactionOperation {
- toAmount :: TezosMutez
 - toDestination :: Address
 - toParameters :: ParametersInternal
 
 - combineResults :: OperationResult -> OperationResult -> OperationResult
 - mkCommonOperationData :: Address -> TezosInt64 -> ProtocolParameters -> CommonOperationData
 - data RunError
- = RuntimeError Address
 - | 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 Address
 - | ScriptOverflow
 - | GasExhaustedOperation
 - | MutezAdditionOverflow [TezosInt64]
 - | MutezSubtractionUnderflow [TezosInt64]
 - | MutezMultiplicationOverflow TezosInt64 TezosInt64
 - | CantPayStorageFee
 - | BalanceTooLow ("balance" :! Mutez) ("required" :! Mutez)
 - | PreviouslyRevealedKey Address
 - | NonExistingContract Address
 
 - data InternalError
- = CounterInThePast Address ("expected" :! Word) ("found" :! Word)
 - | UnrevealedKey Address
 - | Failure Text
 
 - _RuntimeError :: Prism' RunError Address
 - _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 Address
 - _ScriptOverflow :: Prism' RunError ()
 - _PreviouslyRevealedKey :: Prism' RunError Address
 - _GasExhaustedOperation :: Prism' RunError ()
 - oiCommonDataL :: Lens' OperationInput CommonOperationData
 
Documentation
data AppliedResult Source #
Constructors
| AppliedResult | |
Fields 
  | |
Instances
| Show AppliedResult Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> AppliedResult -> ShowS # show :: AppliedResult -> String # showList :: [AppliedResult] -> ShowS #  | |
| Semigroup AppliedResult Source # | |
Defined in Morley.Client.RPC.Types Methods (<>) :: AppliedResult -> AppliedResult -> AppliedResult # sconcat :: NonEmpty AppliedResult -> AppliedResult # stimes :: Integral b => b -> AppliedResult -> AppliedResult #  | |
| Monoid AppliedResult Source # | |
Defined in Morley.Client.RPC.Types Methods mempty :: AppliedResult # mappend :: AppliedResult -> AppliedResult -> AppliedResult # mconcat :: [AppliedResult] -> AppliedResult #  | |
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 
  | |
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
| ToJSON BlockHeader Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: BlockHeader -> Value # toEncoding :: BlockHeader -> Encoding # toJSONList :: [BlockHeader] -> Value # toEncodingList :: [BlockHeader] -> Encoding #  | |
| FromJSON BlockHeader Source # | |
Defined in Morley.Client.RPC.Types  | |
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 Text | Idenfitier referring to a block by its hash in Base58Check notation.  | 
| AtDepthId Natural | Identifier of a block at specific depth relative to   | 
Instances
| Eq BlockId Source # | |
| Show BlockId Source # | |
| Buildable BlockId Source # | |
Defined in Morley.Client.RPC.Types  | |
| 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  | |
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
| ToJSON CommonOperationData Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: CommonOperationData -> Value # toEncoding :: CommonOperationData -> Encoding # toJSONList :: [CommonOperationData] -> Value # toEncodingList :: [CommonOperationData] -> Encoding #  | |
| FromJSON CommonOperationData Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser CommonOperationData # parseJSONList :: Value -> Parser [CommonOperationData] #  | |
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 #  | |
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] #  | |
newtype 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 OperationContent Source #
Constructors
| OperationContent RunMetadata | 
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
| Eq OperationHash Source # | |
Defined in Morley.Client.RPC.Types Methods (==) :: OperationHash -> OperationHash -> Bool # (/=) :: OperationHash -> OperationHash -> Bool #  | |
| Show OperationHash Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> OperationHash -> ShowS # show :: OperationHash -> String # showList :: [OperationHash] -> ShowS #  | |
| FromJSON OperationHash Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OperationHash # parseJSONList :: Value -> Parser [OperationHash] #  | |
| Buildable OperationHash Source # | |
Defined in Morley.Client.RPC.Types Methods build :: OperationHash -> Builder #  | |
| CmdArg OperationHash Source # | |
Defined in Morley.Client.TezosClient.Types Methods toCmdArg :: OperationHash -> String Source #  | |
data OperationInput Source #
Constructors
| OperationInput | |
Fields  | |
Instances
| ToJSON OperationInput Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: OperationInput -> Value # toEncoding :: OperationInput -> Encoding # toJSONList :: [OperationInput] -> Value # toEncodingList :: [OperationInput] -> Encoding #  | |
data OperationResp Source #
Contents of an operation that can appear in RPC responses.
Constructors
| TransactionOpResp TransactionOperation | Operation with kind   | 
| OtherOpResp | Operation with kind that we don't support yet (but need to parse to something).  | 
Instances
| FromJSON OperationResp Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OperationResp # parseJSONList :: Value -> Parser [OperationResp] #  | |
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
| ToJSON OriginationOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: OriginationOperation -> Value # toEncoding :: OriginationOperation -> Encoding # toJSONList :: [OriginationOperation] -> Value # toEncodingList :: [OriginationOperation] -> Encoding #  | |
data OriginationScript Source #
Constructors
| OriginationScript | |
Instances
| ToJSON OriginationScript Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: OriginationScript -> Value # toEncoding :: OriginationScript -> Encoding # toJSONList :: [OriginationScript] -> Value # toEncodingList :: [OriginationScript] -> Encoding #  | |
| FromJSON OriginationScript Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser OriginationScript # parseJSONList :: Value -> Parser [OriginationScript] #  | |
data ParametersInternal Source #
Constructors
| ParametersInternal | |
Fields 
  | |
Instances
| ToJSON ParametersInternal Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: ParametersInternal -> Value # toEncoding :: ParametersInternal -> Encoding # toJSONList :: [ParametersInternal] -> Value # toEncodingList :: [ParametersInternal] -> Encoding #  | |
| FromJSON ParametersInternal Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser ParametersInternal # parseJSONList :: Value -> Parser [ParametersInternal] #  | |
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
| ToJSON RevealOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: RevealOperation -> Value # toEncoding :: RevealOperation -> Encoding # toJSONList :: [RevealOperation] -> Value # toEncodingList :: [RevealOperation] -> Encoding #  | |
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 OriginationInfo RPCInput Source # type RevealInfo RPCInput Source #  | |
| ToJSON (OperationInfo RPCInput) Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: OperationInfo RPCInput -> Value # toEncoding :: OperationInfo RPCInput -> Encoding # toJSONList :: [OperationInfo RPCInput] -> Value # toEncodingList :: [OperationInfo RPCInput] -> Encoding #  | |
| type TransferInfo 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  | |
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
| ToJSON TransactionOperation Source # | |
Defined in Morley.Client.RPC.Types Methods toJSON :: TransactionOperation -> Value # toEncoding :: TransactionOperation -> Encoding # toJSONList :: [TransactionOperation] -> Value # toEncodingList :: [TransactionOperation] -> Encoding #  | |
| FromJSON TransactionOperation Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser TransactionOperation # parseJSONList :: Value -> Parser [TransactionOperation] #  | |
mkCommonOperationData :: Address -> TezosInt64 -> ProtocolParameters -> CommonOperationData Source #
Create CommonOperationData based on current blockchain protocol parameters
 and sender info. This data is used for operation simulation.
Fee isn't accounted during operation simulation, so it's safe to use zero amount. Real operation fee is calculated later using 'tezos-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
| RuntimeError Address | |
| 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 | Transfer of 0 to an implicit account.  | 
Fields 
  | |
| ScriptOverflow | A contract failed due to the detection of an overflow. It seems to happen if a too big value is passed to shift instructions (as second argument).  | 
| GasExhaustedOperation | |
| MutezAdditionOverflow [TezosInt64] | |
| MutezSubtractionUnderflow [TezosInt64] | |
| MutezMultiplicationOverflow TezosInt64 TezosInt64 | |
| CantPayStorageFee | |
| BalanceTooLow ("balance" :! Mutez) ("required" :! Mutez) | |
| PreviouslyRevealedKey Address | |
| NonExistingContract Address | |
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
| Show InternalError Source # | |
Defined in Morley.Client.RPC.Types Methods showsPrec :: Int -> InternalError -> ShowS # show :: InternalError -> String # showList :: [InternalError] -> ShowS #  | |
| FromJSON InternalError Source # | |
Defined in Morley.Client.RPC.Types Methods parseJSON :: Value -> Parser InternalError # parseJSONList :: Value -> Parser [InternalError] #  | |
| Buildable InternalError Source # | |
Defined in Morley.Client.RPC.Types Methods build :: InternalError -> Builder #  | |
Prisms
_RuntimeError :: Prism' RunError Address 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 Address Source #
_ScriptOverflow :: Prism' RunError () Source #
_PreviouslyRevealedKey :: Prism' RunError Address Source #