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

Morley.Client.TezosClient

Description

Interface to octez-client (and its implementation).

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 

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

class Resolve addressOrAlias Source #

Minimal complete definition

resolveAddressEither, getAliasEither

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 #

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 #

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

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.