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

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

Documentation

data AppliedResult Source #

Constructors

AppliedResult 

Fields

newtype BlockHash Source #

Constructors

BlockHash 

Fields

Instances

Instances details
FromJSON BlockHash Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSON BlockHash Source # 
Instance details

Defined in Morley.Client.RPC.Types

Show BlockHash Source # 
Instance details

Defined in Morley.Client.RPC.Types

Eq BlockHash Source # 
Instance details

Defined in Morley.Client.RPC.Types

Ord BlockHash Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToHttpApiData BlockHash Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable BlockHash Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: BlockHash -> Doc

buildList :: [BlockHash] -> Doc

data FeeConstants Source #

Constructors

FeeConstants 

Instances

Instances details
Default FeeConstants Source #

At the moment of writing, Tezos always uses these constants.

Instance details

Defined in Morley.Client.RPC.Types

Methods

def :: FeeConstants #

data BlockId Source #

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 head.

Instances

Instances details
Show BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Eq BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

(==) :: BlockId -> BlockId -> Bool #

(/=) :: BlockId -> BlockId -> Bool #

ToHttpApiData BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

HasCLReader BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: BlockId -> Doc

buildList :: [BlockId] -> Doc

data BlockOperation Source #

$operation in Tezos docs.

Instances

Instances details
FromJSON BlockOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

data CommonOperationData Source #

Data that is common for transaction and origination operations.

Constructors

CommonOperationData 

Fields

data DelegationOperation Source #

Constructors

DelegationOperation 

Fields

Instances

Instances details
FromJSON DelegationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSON DelegationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Generic DelegationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Associated Types

type Rep DelegationOperation :: Type -> Type #

Show DelegationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSONObject DelegationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable DelegationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep DelegationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep DelegationOperation = D1 ('MetaData "DelegationOperation" "Morley.Client.RPC.Types" "morley-client-0.4.0-inplace" 'False) (C1 ('MetaCons "DelegationOperation" 'PrefixI 'True) (S1 ('MetaSel ('Just "doDelegate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyHash))))

data GetBigMap Source #

Constructors

GetBigMap 

Fields

Instances

Instances details
ToJSON GetBigMap Source # 
Instance details

Defined in Morley.Client.RPC.Types

data CalcSize Source #

Constructors

CalcSize 

Fields

Instances

Instances details
ToJSON CalcSize Source # 
Instance details

Defined in Morley.Client.RPC.Types

newtype ScriptSize Source #

Constructors

ScriptSize 

Instances

Instances details
FromJSON ScriptSize Source # 
Instance details

Defined in Morley.Client.RPC.Types

data GetBigMapResult Source #

Constructors

GetBigMapResult Expression 
GetBigMapNotFound 

Instances

Instances details
FromJSON GetBigMapResult Source # 
Instance details

Defined in Morley.Client.RPC.Types

data WithSource a Source #

Constructors

WithSource 

Fields

Instances

Instances details
Functor WithSource Source # 
Instance details

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 # 
Instance details

Defined in Morley.Client.RPC.Types

Show a => Show (WithSource a) Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable a => Buildable (WithSource a) Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: WithSource a -> Doc

buildList :: [WithSource a] -> Doc

data OperationResp f Source #

Contents of an operation that can appear in RPC responses.

Constructors

TransactionOpResp (f TransactionOperation)

Operation with kind transaction.

TransferTicketOpResp (f TransferTicketOperation)

Operation with kind transfer_ticket.

OriginationOpResp (f OriginationOperation)

Operation with kind origination.

DelegationOpResp (f DelegationOperation)

Operation with kind delegation.

RevealOpResp (f RevealOperation)

Operation with kind reveal.

EventOpResp (f EventOperation)

Operation with kind event.

OtherOpResp Text

Response we don't handle yet.

Instances

Instances details
(forall a. FromJSON a => FromJSON (f a)) => FromJSON (OperationResp f) Source # 
Instance details

Defined in Morley.Client.RPC.Types

(forall a. Show a => Show (f a)) => Show (OperationResp f) Source # 
Instance details

Defined in Morley.Client.RPC.Types

(forall a. Buildable a => Buildable (f a)) => Buildable (OperationResp f) Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: OperationResp f -> Doc

buildList :: [OperationResp f] -> Doc

data OriginationOperation Source #

All the data needed to perform contract origination through Tezos RPC interface

Constructors

OriginationOperation 

Fields

Instances

Instances details
FromJSON OriginationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSON OriginationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Generic OriginationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Associated Types

type Rep OriginationOperation :: Type -> Type #

Show OriginationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSONObject OriginationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable OriginationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep OriginationOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep OriginationOperation = D1 ('MetaData "OriginationOperation" "Morley.Client.RPC.Types" "morley-client-0.4.0-inplace" 'False) (C1 ('MetaCons "OriginationOperation" 'PrefixI 'True) (S1 ('MetaSel ('Just "ooBalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TezosMutez) :*: (S1 ('MetaSel ('Just "ooDelegate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe KeyHash)) :*: S1 ('MetaSel ('Just "ooScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OriginationScript))))

data OriginationScript Source #

Constructors

OriginationScript 

Fields

data ParametersInternal Source #

Constructors

ParametersInternal 

Fields

Instances

Instances details
FromJSON ParametersInternal Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSON ParametersInternal Source # 
Instance details

Defined in Morley.Client.RPC.Types

Generic ParametersInternal Source # 
Instance details

Defined in Morley.Client.RPC.Types

Associated Types

type Rep ParametersInternal :: Type -> Type #

Show ParametersInternal Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable ParametersInternal Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep ParametersInternal Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep ParametersInternal = D1 ('MetaData "ParametersInternal" "Morley.Client.RPC.Types" "morley-client-0.4.0-inplace" 'False) (C1 ('MetaCons "ParametersInternal" 'PrefixI 'True) (S1 ('MetaSel ('Just "piEntrypoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "piValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Expression)))

data ProtocolParameters Source #

Protocol-wide constants.

There are more constants, but currently, we are using only these in our code.

Constructors

ProtocolParameters 

Fields

data RevealOperation Source #

All the data needed to perform key revealing through Tezos RPC interface

Constructors

RevealOperation 

Fields

Instances

Instances details
FromJSON RevealOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSON RevealOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Generic RevealOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Associated Types

type Rep RevealOperation :: Type -> Type #

Show RevealOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSONObject RevealOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable RevealOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: RevealOperation -> Doc

buildList :: [RevealOperation] -> Doc

type Rep RevealOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep RevealOperation = D1 ('MetaData "RevealOperation" "Morley.Client.RPC.Types" "morley-client-0.4.0-inplace" 'False) (C1 ('MetaCons "RevealOperation" 'PrefixI 'True) (S1 ('MetaSel ('Just "roPublicKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PublicKey)))

data RunCode Source #

Data required for calling run_code RPC endpoint.

Constructors

RunCode 

Fields

Instances

Instances details
ToJSON RunCode Source # 
Instance details

Defined in Morley.Client.RPC.Types

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

Instances details
FromJSON RunCodeResult Source # 
Instance details

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

data EventOperation Source #

Constructors

EventOperation 

Fields

Instances

Instances details
FromJSON EventOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSON EventOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Generic EventOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Associated Types

type Rep EventOperation :: Type -> Type #

Show EventOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

ToJSONObject EventOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable EventOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: EventOperation -> Doc

buildList :: [EventOperation] -> Doc

type Rep EventOperation Source # 
Instance details

Defined in Morley.Client.RPC.Types

type Rep EventOperation = D1 ('MetaData "EventOperation" "Morley.Client.RPC.Types" "morley-client-0.4.0-inplace" 'False) (C1 ('MetaCons "EventOperation" 'PrefixI 'True) (S1 ('MetaSel ('Just "eoType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Expression) :*: (S1 ('MetaSel ('Just "eoTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe MText)) :*: S1 ('MetaSel ('Just "eoPayload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Expression)))))

data GetTicketBalance Source #

Constructors

GetTicketBalance 

Fields

data PackData Source #

Constructors

PackData 

Fields

Instances

Instances details
ToJSON PackData Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable PackData Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: PackData -> Doc

buildList :: [PackData] -> Doc

data PackDataResult Source #

Constructors

PackDataResult 

Fields

Instances

Instances details
FromJSON PackDataResult Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable PackDataResult Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: PackDataResult -> Doc

buildList :: [PackDataResult] -> Doc

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

data RunError Source #

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 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

Transfer of 0 to an implicit account.

Fields

  • ImplicitAddress

    Receiver address.

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 ImplicitAddress 
NonExistingContract Address 
InvalidB58Check Text 
UnregisteredDelegate ImplicitAddress 
FailedUnDelegation ImplicitAddress 
DelegateAlreadyActive 
IllTypedContract Expression 
IllTypedData Expression Expression 
BadStack BadStackInformation 
ForbiddenZeroAmountTicket 
REEmptyImplicitContract ImplicitAddress 

Instances

Instances details
FromJSON RunError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Show RunError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable RunError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: RunError -> Doc

buildList :: [RunError] -> Doc

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.

Fields

  • ImplicitAddress

    Address whose counter is invalid.

  • ("expected" :! Word)

    Expected counter.

  • ("found" :! Word)

    Found counter.

UnrevealedKey

One tried to apply a manager operation without revealing the manager public key.

Fields

  • ImplicitAddress

    Manager address.

Failure Text

Failure reported without specific id

Instances

Instances details
FromJSON InternalError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Show InternalError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable InternalError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: InternalError -> Doc

buildList :: [InternalError] -> Doc

Prisms

_RuntimeError :: Prism' RunError ContractAddress Source #

_InvalidConstant :: Prism' RunError (Expression, Expression) Source #

_InconsistentTypes :: Prism' RunError (Expression, Expression) Source #

Lenses