-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Types used for interaction with @octez-client@. module Morley.Client.TezosClient.Types ( CmdArg (..) , CalcOriginationFeeData (..) , CalcTransferFeeData (..) , TezosClientEnv (..) , HasTezosClientEnv (..) , SecretKeyEncryption (..) , AliasBehavior (..) -- * Lens , tceEndpointUrlL , tceTezosClientPathL , tceMbTezosClientDataDirL , tceAliasMapL ) where import Data.Aeson (KeyValue(..), ToJSON(..), object) import Data.ByteArray (ScrubbedBytes) import Data.Fixed (E6, Fixed(..)) import Fmt (Buildable(..), pretty, prettyText) import Morley.Util.Lens (makeLensesWith, postfixLFields) import Servant.Client (BaseUrl(..), showBaseUrl) import Text.Hex (encodeHex) import Morley.Client.RPC.Types (OperationHash) import Morley.Client.Types.AliasesAndAddresses import Morley.Client.Util import Morley.Micheline import Morley.Michelson.Printer import Morley.Michelson.Typed (Contract, EpName, Value) import Morley.Michelson.Typed qualified as T import Morley.Tezos.Address import Morley.Tezos.Address.Alias (AddressOrAlias(..), Alias) import Morley.Tezos.Core import Morley.Tezos.Crypto -- | An object that can be put as argument to a @octez-client@ command-line call. class CmdArg a where -- | Render an object as a command-line argument. toCmdArg :: a -> String default toCmdArg :: Buildable a => a -> String toCmdArg = pretty instance CmdArg Text where instance CmdArg LText where instance CmdArg Word16 where instance CmdArg SecretKey where toCmdArg = toCmdArg . formatSecretKey instance CmdArg (KindedAddress kind) where instance CmdArg Address where instance CmdArg ByteString where toCmdArg = toCmdArg . ("0x" <>) . encodeHex instance CmdArg EpName where toCmdArg = toCmdArg . epNameToTezosEp instance CmdArg Mutez where toCmdArg m = show . MkFixed @_ @E6 $ fromIntegral (unMutez m) instance T.UntypedValScope t => CmdArg (Value t) where toCmdArg = toCmdArg . printTypedValue True instance CmdArg (Contract cp st) where toCmdArg = toString . printTypedContract True instance CmdArg BaseUrl where toCmdArg = showBaseUrl instance CmdArg OperationHash instance CmdArg (Alias kind) where instance CmdArg (AddressOrAlias kind) where -- | Representation of address secret key encryption type data SecretKeyEncryption = UnencryptedKey | EncryptedKey | LedgerKey deriving stock (Eq, Show) -- | Runtime environment for @octez-client@ bindings. data TezosClientEnv = TezosClientEnv { tceEndpointUrl :: BaseUrl -- ^ URL of tezos node on which operations are performed. , tceTezosClientPath :: FilePath -- ^ Path to tezos client binary through which operations are -- performed. , tceMbTezosClientDataDir :: Maybe FilePath -- ^ Path to tezos client data directory. , tceAliasMap :: MVar (Maybe AliasesAndAddresses) -- ^ Lazy cache for the mapping between addresses and aliases. The 'Nothing' -- value signifies the cache is either yet unpopulated or was recently -- invalidated. The 'Just' value is the cached result of @octez-client list -- known contracts@. 'MVar' itself being empty/full is used for thread -- synchronization, as is usual. } makeLensesWith postfixLFields ''TezosClientEnv -- | Using this type class one can require 'MonadReader' constraint -- that holds any type with 'TezosClientEnv' inside. class HasTezosClientEnv env where tezosClientEnvL :: Lens' env TezosClientEnv -- | Data required for calculating fee for transfer operation. data CalcTransferFeeData = forall t kind. T.UntypedValScope t => CalcTransferFeeData { ctfdTo :: AddressOrAlias kind , ctfdParam :: Value t , ctfdEp :: EpName , ctfdAmount :: TezosMutez } instance ToJSON CalcTransferFeeData where toJSON CalcTransferFeeData{..} = object [ "destination" .= prettyText ctfdTo , "amount" .= (fromString @Text $ toCmdArg $ unTezosMutez ctfdAmount) , "arg" .= (fromString @Text $ toCmdArg ctfdParam) , "entrypoint" .= (fromString @Text $ toCmdArg ctfdEp) ] -- | Data required for calculating fee for origination operation. data CalcOriginationFeeData cp st = forall kind. CalcOriginationFeeData { cofdFrom :: AddressOrAlias kind , cofdBalance :: TezosMutez , cofdMbFromPassword :: Maybe ScrubbedBytes , cofdContract :: Contract cp st , cofdStorage :: Value st , cofdBurnCap :: TezosInt64 } -- | How to save the originated contract address. data AliasBehavior = 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 deriving stock (Eq, Ord, Enum)