-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Functions to submit transactions via @octez-client@ and node RPC. module Morley.Client.Action.Transaction ( runTransactions , lRunTransactions -- * Transfer , transfer , lTransfer , transferTicket -- Datatypes for batch transactions , TD (..) , LTransactionData (..) , TransactionData (..) , TransferTicketData (..) ) where import Lorentz.Constraints import Morley.Client.Action.Common import Morley.Client.Action.Operation import Morley.Client.Logging import Morley.Client.RPC.Class import Morley.Client.RPC.Types import Morley.Client.TezosClient.Class import Morley.Client.Types import Morley.Michelson.Typed qualified as T import Morley.Michelson.Typed.Scope import Morley.Michelson.Untyped.Entrypoints import Morley.Tezos.Address import Morley.Tezos.Core (Mutez) -- | Perform sequence of transactions to the contract. Returns operation hash -- and a list of RPC responses, or 'Nothing' in case an empty list was provided. runTransactions :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => ImplicitAddressWithAlias -> [TransactionData] -> m (Maybe (OperationHash, [OperationInfo Result])) runTransactions sender transactions = runMaybeT do ts <- hoistMaybe $ nonEmpty transactions lift $ second toList <$> runTransactionsNonEmpty sender ts -- | Perform sequence of transactions to the contract. Returns operation hash -- and a list of RPC responses. runTransactionsNonEmpty :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => ImplicitAddressWithAlias -> NonEmpty TransactionData -> m (OperationHash, NonEmpty (OperationInfo Result)) runTransactionsNonEmpty sender = runOperationsNonEmpty sender . map OpTransfer -- | Lorentz version of 'TransactionData'. data LTransactionData where LTransactionData :: forall (t :: Type). NiceParameter t => TD t -> LTransactionData -- | Lorentz version of 'runTransactions' lRunTransactions :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => ImplicitAddressWithAlias -> [LTransactionData] -> m (Maybe (OperationHash, [OperationInfo Result])) lRunTransactions sender transactions = runTransactions sender $ map convertLTransactionData transactions where convertLTransactionData :: LTransactionData -> TransactionData convertLTransactionData (LTransactionData TD{tdParam=T.toVal -> tdParam, ..}) = TransactionData TD{..} transfer :: forall m t env kind. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m , ParameterScope t , L1AddressKind kind ) => ImplicitAddressWithAlias -> KindedAddress kind -> Mutez -> EpName -> T.Value t -> Maybe Mutez -> m (OperationHash, [IntOpEvent]) transfer from (Constrained -> tdReceiver) tdAmount tdEpName tdParam tdMbFee = (fmap . second) (getEvents . toList) . runTransactionsNonEmpty from . one $ TransactionData TD{..} where getEvents = concatMap \case OpTransfer i -> i _ -> [] transferTicket :: forall m t env kind. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m , ParameterScope t , Comparable t ) => ImplicitAddressWithAlias -- ^ Sender -> KindedAddress kind -- ^ Destination -> ContractAddress -- ^ Ticketer -> T.Value t -- ^ Ticket value -> Natural -- ^ Ticket amount -> EpName -- ^ Destination entrypoint -> Maybe Mutez -- ^ Fee -> m (OperationHash, [IntOpEvent]) transferTicket from (Constrained -> ttdDestination) (Constrained -> ttdTicketTicketer) ttdTicketContents ttdTicketAmount ttdEntrypoint ttdMbFee = (fmap . second) (getEvents . toList) . runOperationsNonEmpty from . one . OpTransferTicket $ TransferTicketData{..} where getEvents = concatMap \case OpTransferTicket i -> i _ -> [] lTransfer :: forall m t env kind. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m , NiceParameter t , L1AddressKind kind ) => ImplicitAddressWithAlias -> KindedAddress kind -> Mutez -> EpName -> t -> Maybe Mutez -> m (OperationHash, [IntOpEvent]) lTransfer from to amount epName = transfer from to amount epName . T.toVal