-- SPDX-FileCopyrightText: 2021 Oxhead Alpha
-- SPDX-License-Identifier: LicenseRef-MIT-OA

-- | Abstraction layer for @tezos-client@ functionality.
-- We use it to fake @tezos-client@ in tests.

module Morley.Client.TezosClient.Class
  ( HasTezosClient (..)
  ) where

import Data.ByteArray (ScrubbedBytes)

import Morley.Client.RPC.Types
import Morley.Client.TezosClient.Types
import Morley.Micheline
import Morley.Michelson.Typed.Scope
import Morley.Tezos.Address
import Morley.Tezos.Crypto

-- | Type class that provides interaction with @tezos-client@ binary
class (Monad m) => HasTezosClient m where
  signBytes :: AddressOrAlias -> Maybe ScrubbedBytes -> ByteString -> m Signature
  -- ^ Sign an operation with @tezos-client@.
  genKey :: AliasOrAliasHint -> m Address
  -- ^ Generate a secret key and store it with given alias.
  -- If a key with this alias already exists, the corresponding address
  -- will be returned and no state will be changed.
  genFreshKey :: AliasOrAliasHint -> m Address
  -- ^ Generate a secret key and store it with given alias.
  -- Unlike 'genKey' this function overwrites
  -- the existing key when given alias is already stored.
  revealKey :: Alias -> Maybe ScrubbedBytes -> m ()
  -- ^ Reveal public key associated with given implicit account.
  waitForOperation :: OperationHash -> m ()
  -- ^ Wait until operation known by some hash is included into the chain.
  rememberContract :: Bool -> Address -> AliasOrAliasHint -> m ()
  -- ^ Associate the given contract with alias.
  -- The 'Bool' variable indicates whether or not we should replace already
  -- existing contract alias or not.
  importKey :: Bool -> AliasOrAliasHint -> SecretKey -> m Alias
  -- ^ Saves 'SecretKey' via @tezos-client@ with given alias or hint associated.
  -- The 'Bool' variable indicates whether or not we should replace already
  -- existing alias key or not.
  -- The returned 'Alias' is the alias under which the key will be accessible.
  resolveAddressMaybe :: AddressOrAlias -> m (Maybe Address)
  -- ^ Retrieve an address from given address or alias. If address or alias does not exist
  -- returns `Nothing`
  getAlias :: AddressOrAlias -> m Alias
  -- ^ Retrieve an alias from given address using @tezos-client@.  The
  -- primary (and probably only) reason this function exists is that
  -- @tezos-client sign@ command only works with aliases. It was
  -- reported upstream: <https://gitlab.com/tezos/tezos/-/issues/836>.
  getPublicKey :: AddressOrAlias -> m PublicKey
  -- ^ Get public key for given address. Public keys are often used when interacting
  -- with the multising contracts
  registerDelegate :: AliasOrAliasHint -> Maybe ScrubbedBytes -> m ()
  -- ^ Register a given address as delegate
  getTezosClientConfig :: m TezosClientConfig
  -- ^ Retrieve the current @tezos-client@ config.
  calcTransferFee
    :: AddressOrAlias -> Maybe ScrubbedBytes -> TezosInt64 -> [CalcTransferFeeData] -> m [TezosMutez]
  -- ^ Calculate fee for transfer using `--dry-run` flag.
  calcOriginationFee
    :: UntypedValScope st => CalcOriginationFeeData cp st -> m TezosMutez
  -- ^ Calculate fee for origination using `--dry-run` flag.
  getKeyPassword :: Address -> m (Maybe ScrubbedBytes)
  -- ^ Get password for secret key associated with given address
  -- in case this key is password-protected. Obtained password is used
  -- in two places:
  --   * 1) In @signBytes@ call.
  --   * 2) in @revealKey@ call.