module Blockfrost.Client.Cardano.Transactions
( getTx
, getTxUtxos
, getTxRedeemers
, getTxStakes
, getTxDelegations
, getTxWithdrawals
, getTxMirs
, getTxPoolUpdates
, getTxPoolRetiring
, getTxMetadataJSON
, getTxCBOR
, getTxMetadataCBOR
, submitTx
) where
import Blockfrost.API
import Blockfrost.Client.Types
import Blockfrost.Types hiding (MempoolTransaction(..))
transactionsClient :: MonadBlockfrost m => Project -> TransactionsAPI (AsClientT m)
transactionsClient :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient = ((((TxHash -> m Transaction)
:<|> ((TxHash -> m TransactionUtxos)
:<|> (TxHash -> m [TransactionRedeemer])))
:<|> ((TxHash -> m [TransactionStake])
:<|> ((TxHash -> m [TransactionDelegation])
:<|> (TxHash -> m [TransactionWithdrawal]))))
:<|> (((TxHash -> m [TransactionMir])
:<|> ((TxHash -> m [TransactionPoolUpdate])
:<|> (TxHash -> m [TransactionPoolRetiring])))
:<|> ((TxHash -> m [TransactionMetaJSON])
:<|> ((TxHash -> m [TransactionCBOR])
:<|> (TxHash -> m [TransactionMetaCBOR])))))
-> TransactionsAPI (AsClientT m)
ToServant TransactionsAPI (AsClientT m)
-> TransactionsAPI (AsClientT m)
forall {k} (routes :: k -> *) (mode :: k).
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant (((((TxHash -> m Transaction)
:<|> ((TxHash -> m TransactionUtxos)
:<|> (TxHash -> m [TransactionRedeemer])))
:<|> ((TxHash -> m [TransactionStake])
:<|> ((TxHash -> m [TransactionDelegation])
:<|> (TxHash -> m [TransactionWithdrawal]))))
:<|> (((TxHash -> m [TransactionMir])
:<|> ((TxHash -> m [TransactionPoolUpdate])
:<|> (TxHash -> m [TransactionPoolRetiring])))
:<|> ((TxHash -> m [TransactionMetaJSON])
:<|> ((TxHash -> m [TransactionCBOR])
:<|> (TxHash -> m [TransactionMetaCBOR])))))
-> TransactionsAPI (AsClientT m))
-> (Project
-> (((TxHash -> m Transaction)
:<|> ((TxHash -> m TransactionUtxos)
:<|> (TxHash -> m [TransactionRedeemer])))
:<|> ((TxHash -> m [TransactionStake])
:<|> ((TxHash -> m [TransactionDelegation])
:<|> (TxHash -> m [TransactionWithdrawal]))))
:<|> (((TxHash -> m [TransactionMir])
:<|> ((TxHash -> m [TransactionPoolUpdate])
:<|> (TxHash -> m [TransactionPoolRetiring])))
:<|> ((TxHash -> m [TransactionMetaJSON])
:<|> ((TxHash -> m [TransactionCBOR])
:<|> (TxHash -> m [TransactionMetaCBOR])))))
-> Project
-> TransactionsAPI (AsClientT m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoAPI (AsClientT m)
-> (((TxHash -> m Transaction)
:<|> ((TxHash -> m TransactionUtxos)
:<|> (TxHash -> m [TransactionRedeemer])))
:<|> ((TxHash -> m [TransactionStake])
:<|> ((TxHash -> m [TransactionDelegation])
:<|> (TxHash -> m [TransactionWithdrawal]))))
:<|> (((TxHash -> m [TransactionMir])
:<|> ((TxHash -> m [TransactionPoolUpdate])
:<|> (TxHash -> m [TransactionPoolRetiring])))
:<|> ((TxHash -> m [TransactionMetaJSON])
:<|> ((TxHash -> m [TransactionCBOR])
:<|> (TxHash -> m [TransactionMetaCBOR]))))
CardanoAPI (AsClientT m)
-> AsClientT m
:- ("txs"
:> (Tag "Cardano \187 Transactions"
:> ToServantApi TransactionsAPI))
forall route.
CardanoAPI route
-> route
:- ("txs"
:> (Tag "Cardano \187 Transactions"
:> ToServantApi TransactionsAPI))
_transactions (CardanoAPI (AsClientT m)
-> (((TxHash -> m Transaction)
:<|> ((TxHash -> m TransactionUtxos)
:<|> (TxHash -> m [TransactionRedeemer])))
:<|> ((TxHash -> m [TransactionStake])
:<|> ((TxHash -> m [TransactionDelegation])
:<|> (TxHash -> m [TransactionWithdrawal]))))
:<|> (((TxHash -> m [TransactionMir])
:<|> ((TxHash -> m [TransactionPoolUpdate])
:<|> (TxHash -> m [TransactionPoolRetiring])))
:<|> ((TxHash -> m [TransactionMetaJSON])
:<|> ((TxHash -> m [TransactionCBOR])
:<|> (TxHash -> m [TransactionMetaCBOR])))))
-> (Project -> CardanoAPI (AsClientT m))
-> Project
-> (((TxHash -> m Transaction)
:<|> ((TxHash -> m TransactionUtxos)
:<|> (TxHash -> m [TransactionRedeemer])))
:<|> ((TxHash -> m [TransactionStake])
:<|> ((TxHash -> m [TransactionDelegation])
:<|> (TxHash -> m [TransactionWithdrawal]))))
:<|> (((TxHash -> m [TransactionMir])
:<|> ((TxHash -> m [TransactionPoolUpdate])
:<|> (TxHash -> m [TransactionPoolRetiring])))
:<|> ((TxHash -> m [TransactionMetaJSON])
:<|> ((TxHash -> m [TransactionCBOR])
:<|> (TxHash -> m [TransactionMetaCBOR]))))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CardanoAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CardanoAPI (AsClientT m)
cardanoClient
getTx_ :: MonadBlockfrost m => Project -> TxHash -> m Transaction
getTx_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m Transaction
getTx_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Specific transaction"
:> (Description "Return content of the requested transaction."
:> (Capture "hash" TxHash :> Get '[JSON] Transaction)))
TransactionsAPI (AsClientT m) -> TxHash -> m Transaction
forall route.
TransactionsAPI route
-> route
:- (Summary "Specific transaction"
:> (Description "Return content of the requested transaction."
:> (Capture "hash" TxHash :> Get '[JSON] Transaction)))
_tx (TransactionsAPI (AsClientT m) -> TxHash -> m Transaction)
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m Transaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTx :: MonadBlockfrost m => TxHash -> m Transaction
getTx :: forall (m :: * -> *). MonadBlockfrost m => TxHash -> m Transaction
getTx TxHash
t = (Project -> m Transaction) -> m Transaction
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m Transaction
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m Transaction
`getTx_` TxHash
t)
getTxUtxos_ :: MonadBlockfrost m => Project -> TxHash -> m TransactionUtxos
getTxUtxos_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m TransactionUtxos
getTxUtxos_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction UTXOs"
:> (Description
"Return the inputs and UTXOs of the specific transaction."
:> (Capture "hash" TxHash
:> ("utxos" :> Get '[JSON] TransactionUtxos))))
TransactionsAPI (AsClientT m) -> TxHash -> m TransactionUtxos
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction UTXOs"
:> (Description
"Return the inputs and UTXOs of the specific transaction."
:> (Capture "hash" TxHash
:> ("utxos" :> Get '[JSON] TransactionUtxos))))
_txUtxos (TransactionsAPI (AsClientT m) -> TxHash -> m TransactionUtxos)
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m TransactionUtxos
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxUtxos :: MonadBlockfrost m => TxHash -> m TransactionUtxos
getTxUtxos :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m TransactionUtxos
getTxUtxos TxHash
t = (Project -> m TransactionUtxos) -> m TransactionUtxos
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m TransactionUtxos
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m TransactionUtxos
`getTxUtxos_` TxHash
t)
getTxRedeemers_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionRedeemer]
getTxRedeemers_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionRedeemer]
getTxRedeemers_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction redeemers"
:> (Description "Obtain the transaction redeemers."
:> (Capture "hash" TxHash
:> ("redeemers" :> Get '[JSON] [TransactionRedeemer]))))
TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionRedeemer]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction redeemers"
:> (Description "Obtain the transaction redeemers."
:> (Capture "hash" TxHash
:> ("redeemers" :> Get '[JSON] [TransactionRedeemer]))))
_txRedeemers (TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionRedeemer])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionRedeemer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxRedeemers :: MonadBlockfrost m => TxHash -> m [TransactionRedeemer]
getTxRedeemers :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionRedeemer]
getTxRedeemers TxHash
t = (Project -> m [TransactionRedeemer]) -> m [TransactionRedeemer]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionRedeemer]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionRedeemer]
`getTxRedeemers_` TxHash
t)
getTxStakes_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionStake]
getTxStakes_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionStake]
getTxStakes_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction stake addresses certificates "
:> (Description
"Obtain information about (de)registration of stake addresses within a transaction."
:> (Capture "hash" TxHash
:> ("stakes" :> Get '[JSON] [TransactionStake]))))
TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionStake]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction stake addresses certificates "
:> (Description
"Obtain information about (de)registration of stake addresses within a transaction."
:> (Capture "hash" TxHash
:> ("stakes" :> Get '[JSON] [TransactionStake]))))
_txStakes (TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionStake])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionStake]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxStakes :: MonadBlockfrost m => TxHash -> m [TransactionStake]
getTxStakes :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionStake]
getTxStakes TxHash
t = (Project -> m [TransactionStake]) -> m [TransactionStake]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionStake]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionStake]
`getTxStakes_` TxHash
t)
getTxDelegations_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionDelegation]
getTxDelegations_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionDelegation]
getTxDelegations_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction delegation certificates"
:> (Description
"Obtain information about delegation certificates of a specific transaction."
:> (Capture "hash" TxHash
:> ("delegations" :> Get '[JSON] [TransactionDelegation]))))
TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionDelegation]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction delegation certificates"
:> (Description
"Obtain information about delegation certificates of a specific transaction."
:> (Capture "hash" TxHash
:> ("delegations" :> Get '[JSON] [TransactionDelegation]))))
_txDelegations (TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionDelegation])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionDelegation]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxDelegations :: MonadBlockfrost m => TxHash -> m [TransactionDelegation]
getTxDelegations :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionDelegation]
getTxDelegations TxHash
t = (Project -> m [TransactionDelegation]) -> m [TransactionDelegation]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionDelegation]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionDelegation]
`getTxDelegations_` TxHash
t)
getTxWithdrawals_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionWithdrawal]
getTxWithdrawals_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionWithdrawal]
getTxWithdrawals_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction withdrawal"
:> (Description
"Obtain information about withdrawals of a specific transaction."
:> (Capture "hash" TxHash
:> ("withdrawals" :> Get '[JSON] [TransactionWithdrawal]))))
TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionWithdrawal]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction withdrawal"
:> (Description
"Obtain information about withdrawals of a specific transaction."
:> (Capture "hash" TxHash
:> ("withdrawals" :> Get '[JSON] [TransactionWithdrawal]))))
_txWithdrawals (TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionWithdrawal])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionWithdrawal]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxWithdrawals :: MonadBlockfrost m => TxHash -> m [TransactionWithdrawal]
getTxWithdrawals :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionWithdrawal]
getTxWithdrawals TxHash
t = (Project -> m [TransactionWithdrawal]) -> m [TransactionWithdrawal]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionWithdrawal]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionWithdrawal]
`getTxWithdrawals_` TxHash
t)
getTxMirs_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionMir]
getTxMirs_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionMir]
getTxMirs_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction MIRs"
:> (Description
"Obtain information about Move Instantaneous Rewards (MIRs) of a specific transaction."
:> (Capture "hash" TxHash
:> ("mirs" :> Get '[JSON] [TransactionMir]))))
TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionMir]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction MIRs"
:> (Description
"Obtain information about Move Instantaneous Rewards (MIRs) of a specific transaction."
:> (Capture "hash" TxHash
:> ("mirs" :> Get '[JSON] [TransactionMir]))))
_txMirs (TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionMir])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionMir]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxMirs :: MonadBlockfrost m => TxHash -> m [TransactionMir]
getTxMirs :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionMir]
getTxMirs TxHash
t = (Project -> m [TransactionMir]) -> m [TransactionMir]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionMir]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionMir]
`getTxMirs_` TxHash
t)
getTxPoolUpdates_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionPoolUpdate]
getTxPoolUpdates_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionPoolUpdate]
getTxPoolUpdates_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary
"Transaction stake pool registration and update certificates"
:> (Description
"Obtain information about stake pool registration and update certificates of a specific transaction."
:> (Capture "hash" TxHash
:> ("pool_updates" :> Get '[JSON] [TransactionPoolUpdate]))))
TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionPoolUpdate]
forall route.
TransactionsAPI route
-> route
:- (Summary
"Transaction stake pool registration and update certificates"
:> (Description
"Obtain information about stake pool registration and update certificates of a specific transaction."
:> (Capture "hash" TxHash
:> ("pool_updates" :> Get '[JSON] [TransactionPoolUpdate]))))
_txPoolUpdates (TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionPoolUpdate])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionPoolUpdate]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxPoolUpdates :: MonadBlockfrost m => TxHash -> m [TransactionPoolUpdate]
getTxPoolUpdates :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionPoolUpdate]
getTxPoolUpdates TxHash
t = (Project -> m [TransactionPoolUpdate]) -> m [TransactionPoolUpdate]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionPoolUpdate]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionPoolUpdate]
`getTxPoolUpdates_` TxHash
t)
getTxPoolRetiring_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionPoolRetiring]
getTxPoolRetiring_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionPoolRetiring]
getTxPoolRetiring_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction stake pool retirement certificates"
:> (Description
"Obtain information about stake pool retirements within a specific transaction."
:> (Capture "hash" TxHash
:> ("pool_retires" :> Get '[JSON] [TransactionPoolRetiring]))))
TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionPoolRetiring]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction stake pool retirement certificates"
:> (Description
"Obtain information about stake pool retirements within a specific transaction."
:> (Capture "hash" TxHash
:> ("pool_retires" :> Get '[JSON] [TransactionPoolRetiring]))))
_txPoolRetiring (TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionPoolRetiring])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionPoolRetiring]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxPoolRetiring :: MonadBlockfrost m => TxHash -> m [TransactionPoolRetiring]
getTxPoolRetiring :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionPoolRetiring]
getTxPoolRetiring TxHash
t = (Project -> m [TransactionPoolRetiring])
-> m [TransactionPoolRetiring]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionPoolRetiring]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionPoolRetiring]
`getTxPoolRetiring_` TxHash
t)
getTxMetadataJSON_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionMetaJSON]
getTxMetadataJSON_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionMetaJSON]
getTxMetadataJSON_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction metadata"
:> (Description "Obtain the transaction metadata."
:> (Capture "hash" TxHash
:> ("metadata" :> Get '[JSON] [TransactionMetaJSON]))))
TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionMetaJSON]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction metadata"
:> (Description "Obtain the transaction metadata."
:> (Capture "hash" TxHash
:> ("metadata" :> Get '[JSON] [TransactionMetaJSON]))))
_txMetadataJSON (TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionMetaJSON])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionMetaJSON]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxMetadataJSON :: MonadBlockfrost m => TxHash -> m [TransactionMetaJSON]
getTxMetadataJSON :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionMetaJSON]
getTxMetadataJSON TxHash
t = (Project -> m [TransactionMetaJSON]) -> m [TransactionMetaJSON]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionMetaJSON]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionMetaJSON]
`getTxMetadataJSON_` TxHash
t)
getTxCBOR_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionCBOR]
getTxCBOR_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionCBOR]
getTxCBOR_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction in CBOR"
:> (Description "Obtain the CBOR serialized transaction."
:> (Capture "hash" TxHash
:> ("cbor" :> Get '[JSON] [TransactionCBOR]))))
TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionCBOR]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction in CBOR"
:> (Description "Obtain the CBOR serialized transaction."
:> (Capture "hash" TxHash
:> ("cbor" :> Get '[JSON] [TransactionCBOR]))))
_txCBOR (TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionCBOR])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionCBOR]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxCBOR :: MonadBlockfrost m => TxHash -> m [TransactionCBOR]
getTxCBOR :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionCBOR]
getTxCBOR TxHash
t = (Project -> m [TransactionCBOR]) -> m [TransactionCBOR]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionCBOR]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionCBOR]
`getTxCBOR_` TxHash
t)
getTxMetadataCBOR_ :: MonadBlockfrost m => Project -> TxHash -> m [TransactionMetaCBOR]
getTxMetadataCBOR_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionMetaCBOR]
getTxMetadataCBOR_ = TransactionsAPI (AsClientT m)
-> AsClientT m
:- (Summary "Transaction metadata in CBOR"
:> (Description "Obtain the transaction metadata in CBOR."
:> (Capture "hash" TxHash
:> ("metadata" :> ("cbor" :> Get '[JSON] [TransactionMetaCBOR])))))
TransactionsAPI (AsClientT m) -> TxHash -> m [TransactionMetaCBOR]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction metadata in CBOR"
:> (Description "Obtain the transaction metadata in CBOR."
:> (Capture "hash" TxHash
:> ("metadata" :> ("cbor" :> Get '[JSON] [TransactionMetaCBOR])))))
_txMetadataCBOR (TransactionsAPI (AsClientT m)
-> TxHash -> m [TransactionMetaCBOR])
-> (Project -> TransactionsAPI (AsClientT m))
-> Project
-> TxHash
-> m [TransactionMetaCBOR]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TransactionsAPI (AsClientT m)
transactionsClient
getTxMetadataCBOR :: MonadBlockfrost m => TxHash -> m [TransactionMetaCBOR]
getTxMetadataCBOR :: forall (m :: * -> *).
MonadBlockfrost m =>
TxHash -> m [TransactionMetaCBOR]
getTxMetadataCBOR TxHash
t = (Project -> m [TransactionMetaCBOR]) -> m [TransactionMetaCBOR]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> TxHash -> m [TransactionMetaCBOR]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> TxHash -> m [TransactionMetaCBOR]
`getTxMetadataCBOR_` TxHash
t)
submitTx_ :: MonadBlockfrost m => Project -> CBORString -> m TxHash
submitTx_ :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CBORString -> m TxHash
submitTx_ = CardanoAPI (AsClientT m)
-> AsClientT m
:- (Summary "Submit a transaction"
:> (Description
"Submit an already serialized transaction to the network."
:> (Tag "Cardano \187 Transactions"
:> ("tx"
:> ("submit"
:> (ReqBody '[CBOR] CBORString :> Post '[JSON] TxHash))))))
CardanoAPI (AsClientT m) -> CBORString -> m TxHash
forall route.
CardanoAPI route
-> route
:- (Summary "Submit a transaction"
:> (Description
"Submit an already serialized transaction to the network."
:> (Tag "Cardano \187 Transactions"
:> ("tx"
:> ("submit"
:> (ReqBody '[CBOR] CBORString :> Post '[JSON] TxHash))))))
_txSubmit (CardanoAPI (AsClientT m) -> CBORString -> m TxHash)
-> (Project -> CardanoAPI (AsClientT m))
-> Project
-> CBORString
-> m TxHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CardanoAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CardanoAPI (AsClientT m)
cardanoClient
submitTx :: MonadBlockfrost m => CBORString -> m TxHash
submitTx :: forall (m :: * -> *). MonadBlockfrost m => CBORString -> m TxHash
submitTx CBORString
txCbor = (Project -> m TxHash) -> m TxHash
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go (Project -> CBORString -> m TxHash
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CBORString -> m TxHash
`submitTx_` CBORString
txCbor)