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

Morley.Client

Description

Morley client that connects with real Tezos network through RPC and the octez-client binary. For more information please refer to README.

Synopsis

Command line parser

parserInfo :: ("usage" :! Doc) -> ("description" :! String) -> ("header" :! String) -> ("parser" :! Parser s) -> ParserInfo s #

Full client monad and environment

data MorleyClientM a Source #

Instances

Instances details
MonadIO MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

liftIO :: IO a -> MorleyClientM a #

Applicative MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Functor MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

fmap :: (a -> b) -> MorleyClientM a -> MorleyClientM b #

(<$) :: a -> MorleyClientM b -> MorleyClientM a #

Monad MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

MonadCatch MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

catch :: Exception e => MorleyClientM a -> (e -> MorleyClientM a) -> MorleyClientM a #

MonadMask MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

MonadThrow MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

throwM :: Exception e => e -> MorleyClientM a #

HasTezosRpc MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

getBlockHash :: BlockId -> MorleyClientM BlockHash Source #

getCounterAtBlock :: BlockId -> ImplicitAddress -> MorleyClientM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyClientM BlockHeader Source #

getScriptSizeAtBlock :: BlockId -> CalcSize -> MorleyClientM ScriptSize Source #

getBlockConstants :: BlockId -> MorleyClientM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyClientM [[BlockOperation]] Source #

getBlockOperationHashes :: BlockId -> MorleyClientM [[OperationHash]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyClientM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyClientM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyClientM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyClientM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyClientM OperationHash Source #

getContractScriptAtBlock :: BlockId -> ContractAddress -> MorleyClientM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> ContractAddress -> MorleyClientM Expression Source #

getContractBigMapAtBlock :: BlockId -> ContractAddress -> GetBigMap -> MorleyClientM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyClientM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyClientM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyClientM Mutez Source #

getDelegateAtBlock :: BlockId -> L1Address -> MorleyClientM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyClientM RunCodeResult Source #

getChainId :: MorleyClientM ChainId Source #

getManagerKeyAtBlock :: BlockId -> ImplicitAddress -> MorleyClientM (Maybe PublicKey) Source #

waitForOperation :: MorleyClientM OperationHash -> MorleyClientM OperationHash Source #

getTicketBalanceAtBlock :: BlockId -> Address -> GetTicketBalance -> MorleyClientM Natural Source #

getAllTicketBalancesAtBlock :: BlockId -> ContractAddress -> MorleyClientM [GetAllTicketBalancesResponse] Source #

HasTezosClient MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

RunClient MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

MonadUnliftIO MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

withRunInIO :: ((forall a. MorleyClientM a -> IO a) -> IO b) -> MorleyClientM b #

MonadReader MorleyClientEnv MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

HasLog MorleyClientEnv Message MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

data MorleyClientConfig Source #

Data necessary for morley client initialization.

Constructors

MorleyClientConfig 

Fields

Instances

Instances details
Show MorleyClientConfig Source # 
Instance details

Defined in Morley.Client.Init

runMorleyClientM :: MorleyClientEnv -> MorleyClientM a -> IO a Source #

Run MorleyClientM action within given MorleyClientEnv. Retry action in case of invalid counter error.

mkMorleyClientEnv :: MorleyClientConfig -> IO MorleyClientEnv Source #

Construct MorleyClientEnv.

Lens

Only-RPC client monad and environment

newtype MorleyOnlyRpcM a Source #

Monad that implements HasTezosClient and HasTezosRpc classes and can be used for high-level actions as an alternative to MorleyClientM.

Instances

Instances details
MonadIO MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

liftIO :: IO a -> MorleyOnlyRpcM a #

Applicative MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Functor MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

fmap :: (a -> b) -> MorleyOnlyRpcM a -> MorleyOnlyRpcM b #

(<$) :: a -> MorleyOnlyRpcM b -> MorleyOnlyRpcM a #

Monad MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

MonadCatch MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

catch :: Exception e => MorleyOnlyRpcM a -> (e -> MorleyOnlyRpcM a) -> MorleyOnlyRpcM a #

MonadMask MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

MonadThrow MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

throwM :: Exception e => e -> MorleyOnlyRpcM a #

HasTezosRpc MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

getBlockHash :: BlockId -> MorleyOnlyRpcM BlockHash Source #

getCounterAtBlock :: BlockId -> ImplicitAddress -> MorleyOnlyRpcM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyOnlyRpcM BlockHeader Source #

getScriptSizeAtBlock :: BlockId -> CalcSize -> MorleyOnlyRpcM ScriptSize Source #

getBlockConstants :: BlockId -> MorleyOnlyRpcM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyOnlyRpcM [[BlockOperation]] Source #

getBlockOperationHashes :: BlockId -> MorleyOnlyRpcM [[OperationHash]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyOnlyRpcM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyOnlyRpcM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyOnlyRpcM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyOnlyRpcM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyOnlyRpcM OperationHash Source #

getContractScriptAtBlock :: BlockId -> ContractAddress -> MorleyOnlyRpcM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> ContractAddress -> MorleyOnlyRpcM Expression Source #

getContractBigMapAtBlock :: BlockId -> ContractAddress -> GetBigMap -> MorleyOnlyRpcM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyOnlyRpcM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyOnlyRpcM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyOnlyRpcM Mutez Source #

getDelegateAtBlock :: BlockId -> L1Address -> MorleyOnlyRpcM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyOnlyRpcM RunCodeResult Source #

getChainId :: MorleyOnlyRpcM ChainId Source #

getManagerKeyAtBlock :: BlockId -> ImplicitAddress -> MorleyOnlyRpcM (Maybe PublicKey) Source #

waitForOperation :: MorleyOnlyRpcM OperationHash -> MorleyOnlyRpcM OperationHash Source #

getTicketBalanceAtBlock :: BlockId -> Address -> GetTicketBalance -> MorleyOnlyRpcM Natural Source #

getAllTicketBalancesAtBlock :: BlockId -> ContractAddress -> MorleyOnlyRpcM [GetAllTicketBalancesResponse] Source #

HasTezosClient MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

RunClient MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

MonadUnliftIO MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

withRunInIO :: ((forall a. MorleyOnlyRpcM a -> IO a) -> IO b) -> MorleyOnlyRpcM b #

MonadReader MorleyOnlyRpcEnv MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

HasLog MorleyOnlyRpcEnv Message MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

mkMorleyOnlyRpcEnv :: [SecretKey] -> BaseUrl -> Word -> IO MorleyOnlyRpcEnv Source #

Construct MorleyOnlyRpcEnv.

  • Full MorleyClientConfig is not passed because we need just 2 things from it.
  • Log action is built the same way as for MorleyClientEnv.
  • All secret keys are passed as an argument.

runMorleyOnlyRpcM :: MorleyOnlyRpcEnv -> MorleyOnlyRpcM a -> IO a Source #

Run MorleyOnlyRpcM action within given MorleyOnlyRpcEnv. Retry action in case of invalid counter error.

High-level actions

RPC

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

Buildable BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: BlockId -> Builder #

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

class (Monad m, MonadCatch m) => HasTezosRpc m where Source #

Type class that provides interaction with tezos node via RPC

Methods

getBlockHash :: BlockId -> m BlockHash Source #

Get hash of the given BlockId, mostly used to get hash of HeadId

getCounterAtBlock :: BlockId -> ImplicitAddress -> m TezosInt64 Source #

Get address counter, which is required for both transaction sending and contract origination.

getBlockHeader :: BlockId -> m BlockHeader Source #

Get the whole header of a block.

getScriptSizeAtBlock :: BlockId -> CalcSize -> m ScriptSize Source #

Get the script size at block.

getBlockConstants :: BlockId -> m BlockConstants Source #

Get block constants that are required by other RPC calls.

getBlockOperations :: BlockId -> m [[BlockOperation]] Source #

Get all operations from the block with specified ID.

getBlockOperationHashes :: BlockId -> m [[OperationHash]] Source #

Get all operation hashes from the block with specified ID.

getProtocolParametersAtBlock :: BlockId -> m ProtocolParameters Source #

Get protocol parameters that are for limits calculations.

runOperationAtBlock :: BlockId -> RunOperation -> m RunOperationResult Source #

Perform operation run, this operation doesn't require proper signing. As a result it returns burned gas and storage diff (also list of originated contracts but their addresses are incorrect due to the fact that operation could be not signed properly) or indicates about operation failure.

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> m [RunOperationResult] Source #

Preapply list of operations, each operation has to be signed with sender secret key. As a result it returns list of results each of which has information about burned gas, storage diff size and originated contracts.

forgeOperationAtBlock :: BlockId -> ForgeOperation -> m HexJSONByteString Source #

Forge operation in order to receive its hexadecimal representation.

injectOperation :: HexJSONByteString -> m OperationHash Source #

Inject operation, note that this operation has to be signed before injection. As a result it returns operation hash.

getContractScriptAtBlock :: BlockId -> ContractAddress -> m OriginationScript Source #

Get code and storage of the desired contract. Note that both code and storage are presented in low-level Micheline representation. If the storage contains a big_map, then the expression will contain the big_map's ID, not its contents.

getContractStorageAtBlock :: BlockId -> ContractAddress -> m Expression Source #

Get storage of the desired contract at some block. Note that storage is presented in low-level Micheline representation. If the storage contains a big_map, then the expression will contain the big_map's ID, not its contents.

getContractBigMapAtBlock :: BlockId -> ContractAddress -> GetBigMap -> m GetBigMapResult Source #

Get big map value by contract address.

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> m Expression Source #

Get big map value at some block by the big map's ID and the hashed entry key.

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> m Expression Source #

Get all big map values at some block by the big map's ID and the optional offset and length.

getBalanceAtBlock :: BlockId -> Address -> m Mutez Source #

Get balance for given address.

getDelegateAtBlock :: BlockId -> L1Address -> m (Maybe KeyHash) Source #

Get delegate for given address.

runCodeAtBlock :: BlockId -> RunCode -> m RunCodeResult Source #

Emulate contract call. This RPC endpoint does the same as octez-client run script command does.

getChainId :: m ChainId Source #

Get current ChainId

getManagerKeyAtBlock :: BlockId -> ImplicitAddress -> m (Maybe PublicKey) Source #

Get manager key for given address. Returns Nothing if this key wasn't revealed.

waitForOperation :: m OperationHash -> m OperationHash Source #

Blocks until an operation with the given hash is included into the chain. The first argument is the action that puts the operation on the chain. Returns the hash of the included operation.

getTicketBalanceAtBlock :: BlockId -> Address -> GetTicketBalance -> m Natural Source #

Access the contract's or implicit account's balance of ticket with specified ticketer, content type, and content.

getAllTicketBalancesAtBlock :: BlockId -> ContractAddress -> m [GetAllTicketBalancesResponse] Source #

Access the complete list of tickets owned by the given contract by scanning the contract's storage.

Instances

Instances details
HasTezosRpc MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

getBlockHash :: BlockId -> MorleyClientM BlockHash Source #

getCounterAtBlock :: BlockId -> ImplicitAddress -> MorleyClientM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyClientM BlockHeader Source #

getScriptSizeAtBlock :: BlockId -> CalcSize -> MorleyClientM ScriptSize Source #

getBlockConstants :: BlockId -> MorleyClientM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyClientM [[BlockOperation]] Source #

getBlockOperationHashes :: BlockId -> MorleyClientM [[OperationHash]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyClientM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyClientM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyClientM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyClientM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyClientM OperationHash Source #

getContractScriptAtBlock :: BlockId -> ContractAddress -> MorleyClientM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> ContractAddress -> MorleyClientM Expression Source #

getContractBigMapAtBlock :: BlockId -> ContractAddress -> GetBigMap -> MorleyClientM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyClientM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyClientM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyClientM Mutez Source #

getDelegateAtBlock :: BlockId -> L1Address -> MorleyClientM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyClientM RunCodeResult Source #

getChainId :: MorleyClientM ChainId Source #

getManagerKeyAtBlock :: BlockId -> ImplicitAddress -> MorleyClientM (Maybe PublicKey) Source #

waitForOperation :: MorleyClientM OperationHash -> MorleyClientM OperationHash Source #

getTicketBalanceAtBlock :: BlockId -> Address -> GetTicketBalance -> MorleyClientM Natural Source #

getAllTicketBalancesAtBlock :: BlockId -> ContractAddress -> MorleyClientM [GetAllTicketBalancesResponse] Source #

HasTezosRpc MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

getBlockHash :: BlockId -> MorleyOnlyRpcM BlockHash Source #

getCounterAtBlock :: BlockId -> ImplicitAddress -> MorleyOnlyRpcM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyOnlyRpcM BlockHeader Source #

getScriptSizeAtBlock :: BlockId -> CalcSize -> MorleyOnlyRpcM ScriptSize Source #

getBlockConstants :: BlockId -> MorleyOnlyRpcM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyOnlyRpcM [[BlockOperation]] Source #

getBlockOperationHashes :: BlockId -> MorleyOnlyRpcM [[OperationHash]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyOnlyRpcM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyOnlyRpcM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyOnlyRpcM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyOnlyRpcM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyOnlyRpcM OperationHash Source #

getContractScriptAtBlock :: BlockId -> ContractAddress -> MorleyOnlyRpcM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> ContractAddress -> MorleyOnlyRpcM Expression Source #

getContractBigMapAtBlock :: BlockId -> ContractAddress -> GetBigMap -> MorleyOnlyRpcM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyOnlyRpcM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyOnlyRpcM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyOnlyRpcM Mutez Source #

getDelegateAtBlock :: BlockId -> L1Address -> MorleyOnlyRpcM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyOnlyRpcM RunCodeResult Source #

getChainId :: MorleyOnlyRpcM ChainId Source #

getManagerKeyAtBlock :: BlockId -> ImplicitAddress -> MorleyOnlyRpcM (Maybe PublicKey) Source #

waitForOperation :: MorleyOnlyRpcM OperationHash -> MorleyOnlyRpcM OperationHash Source #

getTicketBalanceAtBlock :: BlockId -> Address -> GetTicketBalance -> MorleyOnlyRpcM Natural Source #

getAllTicketBalancesAtBlock :: BlockId -> ContractAddress -> MorleyOnlyRpcM [GetAllTicketBalancesResponse] Source #

getContract :: HasTezosRpc m => ContractAddress -> m Contract Source #

Get originated Contract for some address.

getImplicitContractCounter :: HasTezosRpc m => ImplicitAddress -> m TezosInt64 Source #

Get counter value for given implicit address.

getContractStorage :: HasTezosRpc m => ContractAddress -> m Expression Source #

getContractStorageAtBlock applied to the head block.

getBigMapValue :: HasTezosRpc m => Natural -> Text -> m Expression Source #

getBigMapValueAtBlock applied to the head block.

getHeadBlock :: HasTezosRpc m => m BlockHash Source #

Get hash of the current head block, this head hash is used in other RPC calls.

getCounter :: HasTezosRpc m => ImplicitAddress -> m TezosInt64 Source #

getCounterAtBlock applied to the head block.

forgeOperation :: HasTezosRpc m => ForgeOperation -> m HexJSONByteString Source #

forgeOperationAtBlock applied to the head block.

getContractScript :: HasTezosRpc m => ContractAddress -> m OriginationScript Source #

getContractScriptAtBlock applied to the head block.

getContractBigMap :: HasTezosRpc m => ContractAddress -> GetBigMap -> m GetBigMapResult Source #

getContractBigMapAtBlock applied to the head block.

getBalance :: forall kind m. (HasTezosRpc m, L1AddressKind kind) => KindedAddress kind -> m Mutez Source #

getBalanceAtBlock applied to the head block.

getDelegate :: HasTezosRpc m => L1Address -> m (Maybe KeyHash) Source #

getDelegateAtBlock applied to the head block.

runCode :: HasTezosRpc m => RunCode -> m RunCodeResult Source #

runCodeAtBlock applied to the head block.

getManagerKey :: HasTezosRpc m => ImplicitAddress -> m (Maybe PublicKey) Source #

getTicketBalance Source #

Arguments

:: HasTezosRpc m 
=> L1Address

Ticket owner

-> GetTicketBalance

Ticket description

-> m Natural 

getAllTicketBalances Source #

Arguments

:: HasTezosRpc m 
=> ContractAddress

Ticket owner

-> m [GetAllTicketBalancesResponse] 

data GetTicketBalance Source #

Constructors

GetTicketBalance 

Fields

Errors

data ClientRpcError Source #

Errors that can happen in the RPC part when a user tries to make failing actions.

Constructors

ContractFailed

Smart contract execution has failed.

Fields

  • ContractAddress

    Smart contract address.

  • Expression

    Value the contract has failed with.

BadParameter

Parameter passed to a contract does not match its type.

Fields

  • Address

    Smart or implicit contract address.

  • Expression

    Value passed as parameter.

EmptyTransaction

Transfer of 0 to an implicit account.

Fields

  • ImplicitAddress

    Receiver address.

ShiftOverflow

A smart contract execution failed due to a shift overflow.

Fields

  • ContractAddress

    Smart contract address.

GasExhaustion

A smart contract execution failed due gas exhaustion.

Fields

  • ContractAddress

    Smart contract address.

KeyAlreadyRevealed

A key has already been revealed.

Fields

  • ImplicitAddress

    The address corresponding to the key.

DelegateNotRegistered

Address not registered as delegate

Fields

  • ImplicitAddress

    The address in question.

ClientInternalError InternalError

An error that RPC considers internal occurred. These errors are considered internal by mistake, they are actually quite realistic and normally indicate bad user action. Currently we put InternalError here as is, because it's easy for a user of morley-client to work with this type. In #284 we will consider more errors and maybe some of them will need to be mapped into something more user-friendly, then we will reconsider this approach.

data IncorrectRpcResponse Source #

Errors that we can throw when we get a response from a node that doesn't match our expectations. It means that either the node we are talking to misbehaves or our code is incorrect.

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

Getters

readAllBigMapValues :: forall v k m. (NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> m [v] Source #

Read all big_map values, given it's ID. If the values are not of the expected type, a ValueDecodeFailure will be thrown.

readAllBigMapValuesMaybe :: forall v k m. (NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> m (Maybe [v]) Source #

Read all big_map values, given it's ID. If the values are not of the expected type, a ValueDecodeFailure will be thrown.

Returns Nothing if a big_map with the given ID does not exist.

readContractBigMapValue :: forall k v m. (PackedValScope k, HasTezosRpc m, SingI v) => ContractAddress -> Value k -> m (Value v) Source #

Read big_map value of given contract by key.

If the contract contains several big_maps with given key type, only one of them will be considered.

readBigMapValueMaybe :: forall v k m. (NicePackedValue k, NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> k -> m (Maybe v) Source #

Read big_map value, given it's ID and a key. If the value is not of the expected type, a ValueDecodeFailure will be thrown.

Returns Nothing if a big_map with the given ID does not exist, or it does exist but does not contain the given key.

readBigMapValue :: forall v k m. (NicePackedValue k, NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> k -> m v Source #

Read big_map value, given it's ID and a key. If the value is not of the expected type, a ValueDecodeFailure will be thrown.

octez-client

class Monad m => HasTezosClient m where Source #

Type class that provides interaction with octez-client binary

Methods

signBytes :: ImplicitAddressWithAlias -> Maybe ScrubbedBytes -> ByteString -> m Signature Source #

Sign an operation with octez-client.

genKey :: ImplicitAlias -> m ImplicitAddressWithAlias Source #

Generate a secret key and store it with given alias. If a key with this alias already exists, the corresponding address will be returned and no state will be changed.

genFreshKey :: ImplicitAlias -> m ImplicitAddressWithAlias Source #

Generate a secret key and store it with given alias. Unlike genKey this function overwrites the existing key when given alias is already stored.

rememberContract :: AliasBehavior -> ContractAddress -> ContractAlias -> m () Source #

Associate the given contract with alias. The Bool variable indicates whether or not we should replace already existing contract alias or not.

getAliasesAndAddresses :: m [(Text, Text)] Source #

Retrieves a list with all known aliases and respective addresses.

Note that an alias can be ambiguous: it can refer to BOTH a contract and an implicit account. When an alias "abc" is ambiguous, the list will contain two entries:

("abc", "KT1...")
("key:abc", "tz1...")

TODO [#910]: Cache this and turn it into a Bimap.

getKeyPassword :: ImplicitAddressWithAlias -> m (Maybe ScrubbedBytes) Source #

Get password for secret key associated with given address in case this key is password-protected. Obtained password is used in two places: * 1) In signBytes call. * 2) in revealKey call.

getPublicKey :: ImplicitAddressWithAlias -> m PublicKey Source #

Get a public key for an implicit address or alias.

class Resolve addressOrAlias Source #

Associated Types

type ResolvedAddress addressOrAlias :: Type Source #

type ResolvedAlias addressOrAlias :: Type Source #

Instances

Instances details
Resolve SomeAddressOrAlias Source # 
Instance details

Defined in Morley.Client.TezosClient.Impl

Associated Types

type ResolvedAddress SomeAddressOrAlias Source #

type ResolvedAlias SomeAddressOrAlias Source #

type ResolvedAddressAndAlias SomeAddressOrAlias Source #

Methods

resolveAddressEither :: (HasTezosClient m, MonadThrow m, WithClientLog env m) => SomeAddressOrAlias -> m (Either ResolveError (ResolvedAddress SomeAddressOrAlias)) Source #

getAliasEither :: (HasTezosClient m, MonadThrow m, WithClientLog env m) => SomeAddressOrAlias -> m (Either ResolveError (ResolvedAlias SomeAddressOrAlias)) Source #

resolveAddressWithAliasEither :: (HasTezosClient m, MonadThrow m, WithClientLog env m) => SomeAddressOrAlias -> m (Either ResolveError (ResolvedAddressAndAlias SomeAddressOrAlias)) Source #

Resolve (AddressOrAlias kind) Source # 
Instance details

Defined in Morley.Client.TezosClient.Impl

Associated Types

type ResolvedAddress (AddressOrAlias kind) Source #

type ResolvedAlias (AddressOrAlias kind) Source #

type ResolvedAddressAndAlias (AddressOrAlias kind) Source #

Methods

resolveAddressEither :: (HasTezosClient m, MonadThrow m, WithClientLog env m) => AddressOrAlias kind -> m (Either ResolveError (ResolvedAddress (AddressOrAlias kind))) Source #

getAliasEither :: (HasTezosClient m, MonadThrow m, WithClientLog env m) => AddressOrAlias kind -> m (Either ResolveError (ResolvedAlias (AddressOrAlias kind))) Source #

resolveAddressWithAliasEither :: (HasTezosClient m, MonadThrow m, WithClientLog env m) => AddressOrAlias kind -> m (Either ResolveError (ResolvedAddressAndAlias (AddressOrAlias kind))) Source #

data ResolveError where Source #

Constructors

REAliasNotFound 

Fields

REWrongKind 

Fields

  • :: Alias expectedKind
     
  • -> Address
     
  • -> ResolveError

    Expected an alias to be associated with an implicit address, but it was associated with a contract address, or vice-versa.

REAddressNotFound 

Fields

  • :: KindedAddress kind
     
  • -> ResolveError

    Could not find an alias with given address.

Instances

Instances details
Show ResolveError Source # 
Instance details

Defined in Morley.Client.TezosClient.Impl

Buildable ResolveError Source # 
Instance details

Defined in Morley.Client.TezosClient.Impl

getAlias :: forall addressOrAlias m env. (HasTezosClient m, WithClientLog env m, MonadThrow m, Resolve addressOrAlias) => addressOrAlias -> m (ResolvedAlias addressOrAlias) Source #

Looks up the alias associated with the given addressOrAlias.

Will throw a TezosClientError if addressOrAlias:

  • is an address that is not associated with any alias.
  • is an alias that does not exist.
  • is an alias that exists but its address is of the wrong kind.

When the alias is associated with both an implicit and a contract address:

  • The SomeAddressOrAlias instance will throw a TezosClientError, unless the alias is prefixed with implicit: or contract: to disambiguate.
  • The AddressOrAlias instance will return the alias.

getAliasMaybe :: forall addressOrAlias m env. (HasTezosClient m, WithClientLog env m, MonadThrow m, Resolve addressOrAlias) => addressOrAlias -> m (Maybe (ResolvedAlias addressOrAlias)) Source #

Looks up the alias associated with the given addressOrAlias.

Will return Nothing if addressOrAlias:

  • is an address that is not associated with any alias.
  • is an alias that does not exist.
  • is an alias that exists but its address is of the wrong kind.

When the alias is associated with both an implicit and a contract address:

  • The SomeAddressOrAlias instance will throw a TezosClientError, unless the alias is prefixed with implicit: or contract: to disambiguate.
  • The AddressOrAlias instance will return the alias.

resolveAddress :: forall addressOrAlias m env. (HasTezosClient m, MonadThrow m, WithClientLog env m, Resolve addressOrAlias) => addressOrAlias -> m (ResolvedAddress addressOrAlias) Source #

Looks up the address associated with the given addressOrAlias.

Will throw a TezosClientError if addressOrAlias is an alias and:

  • the alias does not exist.
  • the alias exists but its address is of the wrong kind.

When the alias is associated with both an implicit and a contract address:

  • The SomeAddressOrAlias instance will throw a TezosClientError, unless the alias is prefixed with implicit: or contract: to disambiguate.
  • The AddressOrAlias instance will return the address with the requested kind.

resolveAddressMaybe :: forall addressOrAlias m env. (HasTezosClient m, MonadThrow m, WithClientLog env m, Resolve addressOrAlias) => addressOrAlias -> m (Maybe (ResolvedAddress addressOrAlias)) Source #

Looks up the address associated with the given addressOrAlias.

Will return Nothing if addressOrAlias is an alias and:

  • the alias does not exist.
  • the alias exists but its address is of the wrong kind.

When the alias is associated with both an implicit and a contract address:

  • The SomeAddressOrAlias instance will throw a TezosClientError, unless the alias is prefixed with implicit: or contract: to disambiguate.
  • The AddressOrAlias instance will return the address with the requested kind.

resolveAddressWithAlias :: forall addressOrAlias m env. (HasTezosClient m, MonadThrow m, WithClientLog env m, Resolve addressOrAlias) => addressOrAlias -> m (ResolvedAddressAndAlias addressOrAlias) Source #

Looks up the address and alias with the given addressOrAlias.

resolveAddressWithAliasMaybe :: forall addressOrAlias m env. (HasTezosClient m, MonadThrow m, WithClientLog env m, Resolve addressOrAlias) => addressOrAlias -> m (Maybe (ResolvedAddressAndAlias addressOrAlias)) Source #

Looks up the address and alias with the given addressOrAlias.

data TezosClientError Source #

A data type for all predicatable errors that can happen during octez-client usage.

Constructors

UnexpectedClientFailure

octez-client call unexpectedly failed (returned non-zero exit code). The error contains the error code, stdout and stderr contents.

Fields

AlreadyRevealed

Public key of the given address is already revealed.

Fields

  • ImplicitAlias

    Address alias that has already revealed its key

InvalidOperationHash OperationHash

Can't wait for inclusion of operation with given hash because the hash is invalid.

CounterIsAlreadyUsed

Error that indicates when given counter is already used for given contract.

Fields

EConnreset

Network error with which octez-client fails from time to time.

ConfigParseError String

A parse error occurred during config parsing.

TezosClientCryptoParseError Text CryptoParseError

octez-client produced a cryptographic primitive that we can't parse.

TezosClientParseAddressError Text ParseAddressError

octez-client produced an address that we can't parse.

TezosClientParseFeeError Text Text

octez-client produced invalid output for parsing baker fee

TezosClientUnexpectedOutputFormat Text

octez-client printed a string that doesn't match the format we expect.

CantRevealContract

Given alias is a contract and cannot be revealed.

Fields

  • ImplicitAlias

    Address alias of implicit account

ContractSender ContractAddress Text

Given contract is a source of a transfer or origination operation.

EmptyImplicitContract

Given alias is an empty implicit contract.

Fields

  • ImplicitAlias

    Address alias of implicit contract

TezosClientUnexpectedSignatureOutput Text

octez-client sign bytes produced unexpected output format

TezosClientParseEncryptionTypeError Text Text

octez-client produced invalid output for parsing secret key encryption type.

DuplicateAlias Text

Tried to save alias, but such alias already exists.

AmbiguousAlias Text ContractAddress ImplicitAddress

Expected an alias to be associated with either an implicit address or a contract address, but it was associated with both.

ResolveError ResolveError 

data AliasBehavior Source #

How to save the originated contract address.

Constructors

DontSaveAlias

Don't save the newly originated contract address.

KeepDuplicateAlias

If an alias already exists, keep it, don't save the newly originated contract address.

OverwriteDuplicateAlias

If an alias already exists, replace it with the address of the newly originated contract.

ForbidDuplicateAlias

If an alias already exists, throw an exception without doing the origination

Util

disableAlphanetWarning :: IO () Source #

Sets the environment variable for disabling octez-client's "not a mainnet" warning

data AddressWithAlias kind Source #

Constructors

AddressWithAlias 

Fields

Instances

Instances details
ToTAddress cp vd (KindedAddress kind) => ToTAddress cp vd (AddressWithAlias kind) Source # 
Instance details

Defined in Morley.Client.Types

Methods

toTAddress :: AddressWithAlias kind -> TAddress cp vd

Show (AddressWithAlias kind) Source # 
Instance details

Defined in Morley.Client.Types

Buildable (AddressWithAlias kind) Source # 
Instance details

Defined in Morley.Client.Types

Methods

build :: AddressWithAlias kind -> Builder #

Eq (AddressWithAlias kind) Source # 
Instance details

Defined in Morley.Client.Types

ToAddress (AddressWithAlias kind) Source # 
Instance details

Defined in Morley.Client.Types

Methods

toAddress :: AddressWithAlias kind -> Address

Reexports

data ParserInfo a #

A full description for a runnable Parser for a program.

Instances

Instances details
Functor ParserInfo 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> ParserInfo a -> ParserInfo b #

(<$) :: a -> ParserInfo b -> ParserInfo a #