-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Types used for interaction with @tezos-client@. module Morley.Client.TezosClient.Types ( CmdArg (..) -- , addressResolved , CalcOriginationFeeData (..) , CalcTransferFeeData (..) , TezosClientConfig (..) , TezosClientEnv (..) , HasTezosClientEnv (..) , SecretKeyEncryption (..) -- * Lens , tceEndpointUrlL , tceTezosClientPathL , tceMbTezosClientDataDirL ) where import Data.Aeson (FromJSON(..), KeyValue(..), ToJSON(..), object, withObject, (.:)) import Data.ByteArray (ScrubbedBytes) import Data.Fixed (E6, Fixed(..)) import Fmt (Buildable(..), pretty) import Morley.Util.Lens (makeLensesWith, postfixLFields) import Servant.Client (BaseUrl(..), showBaseUrl) import Text.Hex (encodeHex) -- import Lorentz (ToAddress, toAddress) import Morley.Client.RPC.Types (OperationHash) 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 tezos-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.ProperUntypedValBetterErrors 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) -- | Configuration maintained by @tezos-client@, see its @config@ subcommands -- (e. g. @tezos-client config show@). -- Only the field we are interested in is present here. newtype TezosClientConfig = TezosClientConfig { tcEndpointUrl :: BaseUrl } deriving stock Show -- | For reading tezos-client config. instance FromJSON TezosClientConfig where parseJSON = withObject "node info" $ \o -> TezosClientConfig <$> o .: "endpoint" -- | Runtime environment for @tezos-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. } 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" .= pretty @_ @Text 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 }