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

Morley.Client.TezosClient.Resolve

Description

Utilities for resolving addresses and aliases.

Synopsis

Documentation

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.

REAmbiguousAlias 

Fields

  • :: Text
     
  • -> [L1Address]
     
  • -> ResolveError

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

Instances

Instances details
Show ResolveError Source # 
Instance details

Defined in Morley.Client.TezosClient.Types.Errors

Buildable ResolveError Source # 
Instance details

Defined in Morley.Client.TezosClient.Types.Errors

Methods

build :: ResolveError -> Doc

buildList :: [ResolveError] -> Doc

class Resolve addressOrAlias where Source #

Associated Types

type ResolvedAddress addressOrAlias :: Type Source #

type ResolvedAlias addressOrAlias :: Type Source #

type ResolvedAddressAndAlias addressOrAlias :: Type Source #

Methods

resolveAddressEither :: HasTezosClient 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 return REAmbiguousAlias, unless the alias is prefixed with implicit: or contract: to disambiguate.
  • The AddressOrAlias instance will return the address with the requested kind.

getAliasEither :: HasTezosClient 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 return REAmbiguousAlias, 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.

resolveAddressWithAliasEither :: HasTezosClient m => addressOrAlias -> m (Either ResolveError (ResolvedAddressAndAlias addressOrAlias)) Source #

Resolve both address and alias at the same time

Instances

Instances details
Resolve SomeAddressOrAlias Source # 
Instance details

Defined in Morley.Client.TezosClient.Resolve

Associated Types

type ResolvedAddress SomeAddressOrAlias Source #

type ResolvedAlias SomeAddressOrAlias Source #

type ResolvedAddressAndAlias SomeAddressOrAlias Source #

Methods

resolveAddressEither :: HasTezosClient m => SomeAddressOrAlias -> m (Either ResolveError (ResolvedAddress SomeAddressOrAlias)) Source #

getAliasEither :: HasTezosClient m => SomeAddressOrAlias -> m (Either ResolveError (ResolvedAlias SomeAddressOrAlias)) Source #

resolveAddressWithAliasEither :: HasTezosClient m => SomeAddressOrAlias -> m (Either ResolveError (ResolvedAddressAndAlias SomeAddressOrAlias)) Source #

L1AddressKind kind => Resolve (KindedAddress kind) Source # 
Instance details

Defined in Morley.Client.TezosClient.Resolve

Associated Types

type ResolvedAddress (KindedAddress kind) Source #

type ResolvedAlias (KindedAddress kind) Source #

type ResolvedAddressAndAlias (KindedAddress kind) Source #

Methods

resolveAddressEither :: HasTezosClient m => KindedAddress kind -> m (Either ResolveError (ResolvedAddress (KindedAddress kind))) Source #

getAliasEither :: HasTezosClient m => KindedAddress kind -> m (Either ResolveError (ResolvedAlias (KindedAddress kind))) Source #

resolveAddressWithAliasEither :: HasTezosClient m => KindedAddress kind -> m (Either ResolveError (ResolvedAddressAndAlias (KindedAddress kind))) Source #

Resolve (AddressOrAlias kind) Source # 
Instance details

Defined in Morley.Client.TezosClient.Resolve

Associated Types

type ResolvedAddress (AddressOrAlias kind) Source #

type ResolvedAlias (AddressOrAlias kind) Source #

type ResolvedAddressAndAlias (AddressOrAlias kind) Source #

Methods

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

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

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

Resolve (Alias kind) Source # 
Instance details

Defined in Morley.Client.TezosClient.Resolve

Associated Types

type ResolvedAddress (Alias kind) Source #

type ResolvedAlias (Alias kind) Source #

type ResolvedAddressAndAlias (Alias kind) Source #

resolveAddress :: forall addressOrAlias m. (HasTezosClient m, MonadThrow 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. (HasTezosClient m, MonadThrow 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. (HasTezosClient 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. (HasTezosClient 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.

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

Read octez-client configuration.

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

Looks up the address and alias with the given addressOrAlias.

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

Looks up the address and alias with the given addressOrAlias.