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

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

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

import Data.ByteArray (ScrubbedBytes)

import Morley.Client.TezosClient.Types
import Morley.Client.Types
import Morley.Client.Types.AliasesAndAddresses
import Morley.Tezos.Address
import Morley.Tezos.Address.Alias
import Morley.Tezos.Crypto

-- | Type class that provides interaction with @octez-client@ binary
class (Monad m) => HasTezosClient m where
  signBytes
    :: ImplicitAddressWithAlias
    -> Maybe ScrubbedBytes
    -> ByteString
    -> m Signature
  -- ^ Sign an operation with @octez-client@.
  genKey :: ImplicitAlias -> m ImplicitAddressWithAlias
  -- ^ 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 :: ImplicitAlias -> m ImplicitAddressWithAlias
  -- ^ Generate a secret key and store it with given alias.
  -- Unlike 'genKey' this function overwrites
  -- the existing key when given alias is already stored.
  rememberContract :: AliasBehavior -> ContractAddress -> ContractAlias -> m ()
  -- ^ Associate the given contract with alias.
  -- The 'Bool' variable indicates whether or not we should replace already
  -- existing contract alias or not.
  getAliasesAndAddresses :: m AliasesAndAddresses
  -- ^ Retrieves a list with all known aliases and respective addresses.
  --
  -- Note that an alias can be ambiguous: it can refer to BOTH a contract and an implicit account.
  -- In that case, the map will contain entries for both.
  getKeyPassword :: ImplicitAddressWithAlias -> 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.
  getPublicKey :: ImplicitAddressWithAlias -> m PublicKey
  -- ^ Get a public key for an implicit address or alias.