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

Morley.Client.TezosClient.Impl

Description

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

Synopsis

Documentation

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.

AliasTxRollup Text (KindedAddress 'AddressKindTxRollup)

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

ResolveError ResolveError 

octez-client api

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

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

rememberContract :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => AliasBehavior -> 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.

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

class Resolve addressOrAlias where Source #

Associated Types

type ResolvedAddress addressOrAlias :: Type Source #

type ResolvedAlias addressOrAlias :: Type Source #

Methods

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

Looks up the address associated with the given addressOrAlias.

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.

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

Looks up the alias associated with the given addressOrAlias.

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 of the address with the requested kind.

The primary (and probably only) reason this function exists is that octez-client sign command only works with aliases. It was reported upstream: https://gitlab.com/tezos/tezos/-/issues/836.

Instances

Instances details
Resolve SomeAddressOrAlias Source # 
Instance details

Defined in Morley.Client.TezosClient.Impl

Associated Types

type ResolvedAddress SomeAddressOrAlias Source #

type ResolvedAlias 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 #

Resolve (AddressOrAlias kind) Source # 
Instance details

Defined in Morley.Client.TezosClient.Impl

Associated Types

type ResolvedAddress (AddressOrAlias kind) Source #

type ResolvedAlias (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 #

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.

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.

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

Return PublicKey corresponding to given AddressOrAlias.

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

Return SecretKey corresponding to given AddressOrAlias.

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

Read octez-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 octez-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 octez-client.

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

Calc baker fee for revealing using octez-client.

Note that octez-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, HasTezosClient 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

getAliasesAndAddresses :: forall m env. (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => m [(Text, Text)] Source #

Calls octez-client list known contracts and returns a list of (alias, address) pairs.

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...")

Internals

findAddress :: forall m env. (HasTezosClient m, MonadThrow m, WithClientLog env m) => Text -> m FindAddressResult Source #

Finds the implicit/contract addresses assigned to the given alias.

Note that an alias can be ambiguous: it can refer to both a contract and an implicit account. When an alias "abc" is ambiguous, octez-client list known contracts will return two entries with the following format:

abc: KT1...
key:abc: tz1...

So, in order to check whether the alias is ambiguous, we check whether both "abc" and "key:abc" are present in the output.

If only "abc" is present, then we know it's not ambiguous (and it refers to either a contract or an implicit account).

data FindAddressResult Source #

Whether an alias is associated with an implicit address, a contract address, or both.

Constructors

FARUnambiguous L1Address 
FARAmbiguous ContractAddress ImplicitAddress 
FARNone 

data CallMode Source #

Datatype that represents modes for calling node from octez-client.

Constructors

MockupMode

Mode in which octez-client doesn't perform any actual RPC calls to the node and use mock instead.

ClientMode

Normal mode in which octez-client performs all necessary RPC calls to the node.

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 octez-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 octez-client and expect success.