Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Utilities for resolving addresses and aliases.
Synopsis
- data ResolveError where
- REAliasNotFound :: Text -> ResolveError
- REWrongKind :: Alias expectedKind -> Address -> ResolveError
- REAddressNotFound :: KindedAddress kind -> ResolveError
- REAmbiguousAlias :: Text -> [L1Address] -> ResolveError
- class Resolve addressOrAlias where
- type ResolvedAddress addressOrAlias :: Type
- type ResolvedAlias addressOrAlias :: Type
- type ResolvedAddressAndAlias addressOrAlias :: Type
- resolveAddressEither :: HasTezosClient m => addressOrAlias -> m (Either ResolveError (ResolvedAddress addressOrAlias))
- getAliasEither :: HasTezosClient m => addressOrAlias -> m (Either ResolveError (ResolvedAlias addressOrAlias))
- resolveAddressWithAliasEither :: HasTezosClient m => addressOrAlias -> m (Either ResolveError (ResolvedAddressAndAlias addressOrAlias))
- resolveAddress :: forall addressOrAlias m. (HasTezosClient m, MonadThrow m, Resolve addressOrAlias) => addressOrAlias -> m (ResolvedAddress addressOrAlias)
- resolveAddressMaybe :: forall addressOrAlias m. (HasTezosClient m, MonadThrow m, Resolve addressOrAlias) => addressOrAlias -> m (Maybe (ResolvedAddress addressOrAlias))
- getAlias :: forall addressOrAlias m. (HasTezosClient m, MonadThrow m, Resolve addressOrAlias) => addressOrAlias -> m (ResolvedAlias addressOrAlias)
- getAliasMaybe :: forall addressOrAlias m. (HasTezosClient m, MonadThrow m, Resolve addressOrAlias) => addressOrAlias -> m (Maybe (ResolvedAlias addressOrAlias))
- getTezosClientConfig :: FilePath -> Maybe FilePath -> IO TezosClientConfig
- resolveAddressWithAlias :: forall addressOrAlias m. (HasTezosClient m, MonadThrow m, Resolve addressOrAlias) => addressOrAlias -> m (ResolvedAddressAndAlias addressOrAlias)
- resolveAddressWithAliasMaybe :: forall addressOrAlias m. (HasTezosClient m, Resolve addressOrAlias) => addressOrAlias -> m (Maybe (ResolvedAddressAndAlias addressOrAlias))
Documentation
data ResolveError where Source #
REAliasNotFound | |
| |
REWrongKind | |
| |
REAddressNotFound | |
| |
REAmbiguousAlias | |
|
Instances
Show ResolveError Source # | |
Defined in Morley.Client.TezosClient.Types.Errors showsPrec :: Int -> ResolveError -> ShowS # show :: ResolveError -> String # showList :: [ResolveError] -> ShowS # | |
Buildable ResolveError Source # | |
Defined in Morley.Client.TezosClient.Types.Errors build :: ResolveError -> Doc buildList :: [ResolveError] -> Doc |
class Resolve addressOrAlias where Source #
type ResolvedAddress addressOrAlias :: Type Source #
type ResolvedAlias addressOrAlias :: Type Source #
type ResolvedAddressAndAlias addressOrAlias :: Type Source #
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 returnREAmbiguousAlias
, unless the alias is prefixed withimplicit:
orcontract:
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 returnREAmbiguousAlias
, unless the alias is prefixed withimplicit:
orcontract:
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
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 aTezosClientError
, unless the alias is prefixed withimplicit:
orcontract:
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 aTezosClientError
, unless the alias is prefixed withimplicit:
orcontract:
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 aTezosClientError
, unless the alias is prefixed withimplicit:
orcontract:
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 aTezosClientError
, unless the alias is prefixed withimplicit:
orcontract:
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
.