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

Morley.Client.TezosClient.Impl

Description

Interface to the tezos-client executable expressed in Haskell types.

Synopsis

Documentation

data TezosClientError Source #

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

Constructors

UnexpectedClientFailure

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

Fields

UnknownAddressAlias

Could not find an address with given name.

Fields

  • Text

    Name of address which is eventually used

UnknownAddress

Could not find an address.

Fields

  • Address

    Address that is not present in local tezos cache

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 tezos-client fails from time to time.

ConfigParseError String

A parse error occurred during config parsing.

TezosClientCryptoParseError Text CryptoParseError

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

TezosClientParseAddressError Text ParseAddressError

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

TezosClientParseFeeError Text Text

tezos-client produced invalid output for parsing baker fee

TezosClientUnexpectedOutputFormat Text

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

tezos-client sign bytes produced unexpected output format

TezosClientParseEncryptionTypeError Text Text

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

tezos-client api

signBytes :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => ImplicitAddressOrAlias -> Maybe ScrubbedBytes -> ByteString -> m Signature Source #

Sign an arbtrary bytestring using tezos-client. Secret key of the address corresponding to give AddressOrAlias must be known.

rememberContract :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => Bool -> ContractAddress -> ContractAlias -> m () Source #

Save a contract with given address and alias. If replaceExisting is False and a contract with given alias already exists, this function does nothing.

importKey :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => Bool -> ImplicitAlias -> SecretKey -> m ImplicitAlias Source #

genKey :: (MonadThrow m, MonadCatch m, WithClientLog env m, HasTezosClientEnv env, MonadIO m, HasTezosClient m) => ImplicitAlias -> m ImplicitAddress Source #

Generate a new secret key and save it with given alias. If an address with given alias already exists, it will be returned and no state will be changed.

genFreshKey :: (MonadThrow m, MonadCatch m, WithClientLog env m, HasTezosClientEnv env, MonadIO m, HasTezosClient m) => ImplicitAlias -> m ImplicitAddress Source #

Generate a new secret key and save it with given alias. If an address with given alias already exists, it will be removed and replaced with a fresh one.

revealKey :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => ImplicitAlias -> Maybe ScrubbedBytes -> m () Source #

Reveal public key corresponding to the given alias. Fails if it's already revealed.

resolveAddressMaybe :: forall env m kind. (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => AddressOrAlias kind -> m (Maybe (KindedAddress kind)) Source #

Return KindedAddress corresponding to given AddressOrAlias, covered in Maybe. Return Nothing if address alias is unknown

resolveAddress :: (MonadThrow m, HasTezosClient m) => AddressOrAlias kind -> m (KindedAddress kind) Source #

Return KindedAddress corresponding to given AddressOrAlias.

getAlias :: forall kind env m. (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m, L1AddressKind kind) => AddressOrAlias kind -> m (Alias kind) Source #

Return Alias corresponding to given AddressOrAlias.

getPublicKey :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => ImplicitAddressOrAlias -> m PublicKey Source #

Return PublicKey corresponding to given AddressOrAlias.

getSecretKey :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => ImplicitAddressOrAlias -> m SecretKey Source #

Return SecretKey corresponding to given AddressOrAlias.

getTezosClientConfig :: FilePath -> Maybe FilePath -> IO TezosClientConfig Source #

Read tezos-client configuration.

calcTransferFee :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => AddressOrAlias kind -> Maybe ScrubbedBytes -> TezosInt64 -> [CalcTransferFeeData] -> m [TezosMutez] Source #

Calc baker fee for transfer using tezos-client.

calcOriginationFee :: (UntypedValScope st, WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => CalcOriginationFeeData cp st -> m TezosMutez Source #

Calc baker fee for origination using tezos-client.

calcRevealFee :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => ImplicitAlias -> Maybe ScrubbedBytes -> TezosInt64 -> m TezosMutez Source #

Calc baker fee for revealing using tezos-client.

Note that tezos-client does not support passing an address here, at least at the moment of writing.

getKeyPassword :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadMask m) => ImplicitAddress -> m (Maybe ScrubbedBytes) Source #

Get password for secret key associated with given address in case this key is password-protected

registerDelegate :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => ImplicitAlias -> Maybe ScrubbedBytes -> m () Source #

Register alias as delegate

Internals

callTezosClient :: forall env m. (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => (Text -> Text -> IO Bool) -> [String] -> CallMode -> Maybe ScrubbedBytes -> m Text Source #

Call tezos-client with given arguments. Arguments defined by config are added automatically. The second argument specifies what should be done in failure case. It takes stdout and stderr output. Possible handling:

  1. Parse a specific error and throw it.
  2. Parse an expected error that shouldn't cause a failure. Return True in this case.
  3. Detect an unexpected error, return False. In this case UnexpectedClientFailure will be throw.

callTezosClientStrict :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => [String] -> CallMode -> Maybe ScrubbedBytes -> m Text Source #

Call tezos-client and expect success.