-- SPDX-FileCopyrightText: 2022 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Functions to reveal keys via node RPC. module Morley.Client.Action.Reveal ( RevealData (..) , revealKey , revealKeyWithFee , revealKeyUnlessRevealed , revealKeyUnlessRevealedWithFee , revealKeyOp , revealKeyUnlessRevealedOp ) where import Fmt ((|+)) import Morley.Client.Action.Common import Morley.Client.Action.Operation import Morley.Client.Logging import Morley.Client.RPC.Class import Morley.Client.RPC.Error import Morley.Client.RPC.Getters import Morley.Client.RPC.Types import Morley.Client.TezosClient.Class (HasTezosClient(getPublicKey)) import Morley.Client.TezosClient.Impl (getAlias) import Morley.Client.Types import Morley.Tezos.Address import Morley.Tezos.Address.Alias (AddressOrAlias(..)) import Morley.Tezos.Core (Mutez) import Morley.Tezos.Crypto (PublicKey) -- | Resolve the public key of an implicit address and reveal it. revealKey :: (HasTezosRpc m, HasTezosClient m, WithClientLog env m) => ImplicitAddressWithAlias -> m OperationHash revealKey = (`revealKeyWithFee` Nothing) -- | Version of 'revealKey' with explicit fee. revealKeyWithFee :: (HasTezosRpc m, HasTezosClient m, WithClientLog env m) => ImplicitAddressWithAlias -> Maybe Mutez -> m OperationHash revealKeyWithFee sender mbFee = do pk <- getPublicKey sender runRevealOperationRaw sender pk mbFee -- | Resolve the public key of an implicit address and reveal it, unless already -- revealed. revealKeyUnlessRevealed :: (HasTezosRpc m, HasTezosClient m, WithClientLog env m) => ImplicitAddressWithAlias -> m () revealKeyUnlessRevealed = (`revealKeyUnlessRevealedWithFee` Nothing) -- | Version of 'revealKeyUnlessRevealed' with explicit fee. revealKeyUnlessRevealedWithFee :: (HasTezosRpc m, HasTezosClient m, WithClientLog env m) => ImplicitAddressWithAlias -> Maybe Mutez -> m () revealKeyUnlessRevealedWithFee sender mbFee = do pk <- getPublicKey sender handleAlreadyRevealed (flip (runRevealOperationRaw sender) mbFee) pk -- | Reveal given key. -- -- Note that sender is implicitly defined by the key being revealed, as you can -- only reveal your own key. -- -- This is a variation of key revealing method that tries to use solely RPC. revealKeyOp -- TODO [#873] remove HasTezosClient dependency :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => PublicKey -> Maybe Mutez -> m OperationHash revealKeyOp pk mbFee = do senderAlias <- getAlias $ AddressResolved senderAddress runRevealOperationRaw (AddressWithAlias senderAddress senderAlias) pk mbFee where senderAddress = mkKeyAddress pk {-# DEPRECATED revealKeyOp "Prefer using 'revealKeyWithFee', as it's a lot more efficient" #-} -- | Reveal given key. -- -- Note that sender is implicitly defined by the key being revealed, as you can -- only reveal your own key. revealKeyUnlessRevealedOp -- TODO [#873] remove HasTezosClient dependency :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => PublicKey -> Maybe Mutez -> m () revealKeyUnlessRevealedOp key mbFee = handleAlreadyRevealed (flip revealKeyOp mbFee) key {-# DEPRECATED revealKeyUnlessRevealedOp "Prefer using 'revealKeyUnlessRevealedWithFee', as it's a lot more efficient" #-} -- Internals handleAlreadyRevealed :: (HasTezosRpc m, WithClientLog env m) => (PublicKey -> m a) -> PublicKey -> m () handleAlreadyRevealed doReveal key = do let sender = mkKeyAddress key -- An optimization for the average case, but we can't rely on it in -- distributed environment getManagerKey sender >>= \case Just _ -> logDebug $ sender |+ " address has already revealed key" Nothing -> ignoreAlreadyRevealedError . void $ doReveal key where ignoreAlreadyRevealedError = flip catch \case RunCodeErrors [PreviouslyRevealedKey _] -> pass e -> throwM e -- | Note that sender and rdPublicKey must be consistent, otherwise network will -- reject the operation runRevealOperationRaw :: (HasTezosRpc m, HasTezosClient m, WithClientLog env m) => ImplicitAddressWithAlias -> PublicKey -> Maybe Mutez -> m OperationHash runRevealOperationRaw sender rdPublicKey rdMbFee = fmap fst . runOperationsNonEmpty sender . one $ OpReveal RevealData{..}