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

-- | An abstraction layer over RPC implementation.
-- The primary reason it exists is to make it possible to fake
-- RPC in tests.

module Morley.Client.RPC.Class
  ( HasTezosRpc (..)
  ) where

import Morley.Tezos.Address
import Morley.Tezos.Core (ChainId, Mutez)
import Morley.Tezos.Crypto (KeyHash, PublicKey)
import Morley.Util.ByteString

import Morley.Client.RPC.Types
import Morley.Micheline (Expression, TezosInt64)

-- | Type class that provides interaction with tezos node via RPC
class (Monad m, MonadCatch m) => HasTezosRpc m where
  getBlockHash :: BlockId -> m BlockHash
  -- ^ Get hash of the given 'BlockId', mostly used to get hash of
  -- 'HeadId'
  getCounterAtBlock :: BlockId -> ImplicitAddress -> m TezosInt64
  -- ^ Get address counter, which is required for both transaction sending
  -- and contract origination.
  getBlockHeader :: BlockId -> m BlockHeader
  -- ^ Get the whole header of a block.
  getScriptSizeAtBlock :: BlockId -> CalcSize -> m ScriptSize
  -- ^ Get the script size at block.
  getBlockConstants :: BlockId -> m BlockConstants
  -- ^ Get block constants that are required by other RPC calls.
  getBlockOperations :: BlockId -> m [[BlockOperation]]
  -- ^ Get all operations from the block with specified ID.
  getBlockOperationHashes :: BlockId -> m [[OperationHash]]
  -- ^ Get all operation hashes from the block with specified ID.
  getProtocolParametersAtBlock :: BlockId -> m ProtocolParameters
  -- ^ Get protocol parameters that are for limits calculations.
  runOperationAtBlock :: BlockId -> RunOperation -> m RunOperationResult
  -- ^ Perform operation run, this operation doesn't require proper signing.
  -- As a result it returns burned gas and storage diff (also list of originated
  -- contracts but their addresses are incorrect due to the fact that operation
  -- could be not signed properly) or indicates about operation failure.
  preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> m [RunOperationResult]
  -- ^ Preapply list of operations, each operation has to be signed with sender
  -- secret key. As a result it returns list of results each of which has information
  -- about burned gas, storage diff size and originated contracts.
  forgeOperationAtBlock :: BlockId -> ForgeOperation -> m HexJSONByteString
  -- ^ Forge operation in order to receive its hexadecimal representation.
  injectOperation :: HexJSONByteString -> m OperationHash
  -- ^ Inject operation, note that this operation has to be signed before
  -- injection. As a result it returns operation hash.
  getContractScriptAtBlock :: BlockId -> ContractAddress -> m OriginationScript
  -- ^ Get code and storage of the desired contract. Note that both code and storage
  -- are presented in low-level Micheline representation.
  -- If the storage contains a @big_map@, then the expression will contain the @big_map@'s ID,
  -- not its contents.
  getContractStorageAtBlock :: BlockId -> ContractAddress -> m Expression
  -- ^ Get storage of the desired contract at some block. Note that storage
  -- is presented in low-level Micheline representation.
  -- If the storage contains a @big_map@, then the expression will contain the @big_map@'s ID,
  -- not its contents.
  getContractBigMapAtBlock :: BlockId -> ContractAddress -> GetBigMap -> m GetBigMapResult
  -- ^ Get big map value by contract address.
  getBigMapValueAtBlock :: BlockId -> Natural -> Text -> m Expression
  -- ^ Get big map value at some block by the big map's ID and the hashed entry key.
  getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> m Expression
  -- ^ Get all big map values at some block by the big map's ID and the optional offset and length.
  getBalanceAtBlock :: BlockId -> Address -> m Mutez
  -- ^ Get balance for given address.
  getDelegateAtBlock :: BlockId -> L1Address -> m (Maybe KeyHash)
  -- ^ Get delegate for given address.
  runCodeAtBlock :: BlockId -> RunCode -> m RunCodeResult
  -- ^ Emulate contract call. This RPC endpoint does the same as
  -- @octez-client run script@ command does.
  getChainId :: m ChainId
  -- ^ Get current @ChainId@
  getManagerKeyAtBlock :: BlockId -> ImplicitAddress -> m (Maybe PublicKey)
  -- ^ Get manager key for given address.
  -- Returns @Nothing@ if this key wasn't revealed.
  waitForOperation :: m OperationHash -> m OperationHash
  -- ^ Blocks until an operation with the given hash is included into the chain.
  -- The first argument is the action that puts the operation on the chain.
  -- Returns the hash of the included operation.
  getTicketBalanceAtBlock :: BlockId -> Address -> GetTicketBalance -> m Natural
  -- ^ Access the contract's or implicit account's balance of ticket with
  -- specified ticketer, content type, and content.
  getAllTicketBalancesAtBlock
    :: BlockId
    -> ContractAddress
    -> m [GetAllTicketBalancesResponse]
  -- ^ Access the complete list of tickets owned by the given contract by
  -- scanning the contract's storage.