module Blockfrost.Client.Cardano.Transactions
( getTx
, getTxUtxos
, getTxRedeemers
, getTxStakes
, getTxDelegations
, getTxWithdrawals
, getTxMirs
, getTxPoolUpdates
, getTxPoolRetiring
, getTxMetadataJSON
, getTxMetadataCBOR
, submitTx
) where
import Blockfrost.API
import Blockfrost.Client.Types
import Blockfrost.Types
transactionsClient :: Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient :: Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient = ((((TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos))
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionDelegation]))))
:<|> (((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolUpdate])))
:<|> ((TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionMetaCBOR])))))
-> TransactionsAPI (AsClientT BlockfrostClient)
forall (routes :: * -> *) mode.
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant (((((TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos))
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionDelegation]))))
:<|> (((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolUpdate])))
:<|> ((TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionMetaCBOR])))))
-> TransactionsAPI (AsClientT BlockfrostClient))
-> (Project
-> (((TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos))
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionDelegation]))))
:<|> (((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolUpdate])))
:<|> ((TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionMetaCBOR])))))
-> Project
-> TransactionsAPI (AsClientT BlockfrostClient)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoAPI (AsClientT BlockfrostClient)
-> (((TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos))
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionDelegation]))))
:<|> (((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolUpdate])))
:<|> ((TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR]))))
forall route.
CardanoAPI route
-> route
:- ("txs"
:> (Tag "Cardano \187 Transactions"
:> ToServantApi TransactionsAPI))
_transactions (CardanoAPI (AsClientT BlockfrostClient)
-> (((TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos))
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionDelegation]))))
:<|> (((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolUpdate])))
:<|> ((TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionMetaCBOR])))))
-> (Project -> CardanoAPI (AsClientT BlockfrostClient))
-> Project
-> (((TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos))
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionDelegation]))))
:<|> (((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
:<|> (TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolUpdate])))
:<|> ((TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
:<|> ((TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
:<|> (TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR]))))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CardanoAPI (AsClientT BlockfrostClient)
cardanoClient
getTx_ :: Project -> TxHash -> BlockfrostClient Transaction
getTx_ :: Project
-> TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction
getTx_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) 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 BlockfrostClient)
-> TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTx :: TxHash -> BlockfrostClient Transaction
getTx :: TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction
getTx TxHash
t = (Project
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction)
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) Transaction
`getTx_` TxHash
t)
getTxUtxos_ :: Project -> TxHash -> BlockfrostClient TransactionUtxos
getTxUtxos_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos
getTxUtxos_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) 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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos)
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxUtxos :: TxHash -> BlockfrostClient TransactionUtxos
getTxUtxos :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos
getTxUtxos TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos)
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) TransactionUtxos
`getTxUtxos_` TxHash
t)
getTxRedeemers_ :: Project -> TxHash -> BlockfrostClient [TransactionRedeemer]
getTxRedeemers_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer]
getTxRedeemers_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction redeemers"
:> (Description "Obtain the transaction redeemers."
:> (Capture "hash" TxHash
:> ("redeemers" :> Get '[JSON] [TransactionRedeemer]))))
_txRedeemers (TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxRedeemers :: TxHash -> BlockfrostClient [TransactionRedeemer]
getTxRedeemers :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer]
getTxRedeemers TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionRedeemer]
`getTxRedeemers_` TxHash
t)
getTxStakes_ :: Project -> TxHash -> BlockfrostClient [TransactionStake]
getTxStakes_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake]
getTxStakes_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxStakes :: TxHash -> BlockfrostClient [TransactionStake]
getTxStakes :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake]
getTxStakes TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionStake]
`getTxStakes_` TxHash
t)
getTxDelegations_ :: Project -> TxHash -> BlockfrostClient [TransactionDelegation]
getTxDelegations_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionDelegation]
getTxDelegations_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionDelegation])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionDelegation]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxDelegations :: TxHash -> BlockfrostClient [TransactionDelegation]
getTxDelegations :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionDelegation]
getTxDelegations TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionDelegation])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionDelegation]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionDelegation]
`getTxDelegations_` TxHash
t)
getTxWithdrawals_ :: Project -> TxHash -> BlockfrostClient [TransactionWithdrawal]
getTxWithdrawals_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal]
getTxWithdrawals_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxWithdrawals :: TxHash -> BlockfrostClient [TransactionWithdrawal]
getTxWithdrawals :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal]
getTxWithdrawals TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionWithdrawal]
`getTxWithdrawals_` TxHash
t)
getTxMirs_ :: Project -> TxHash -> BlockfrostClient [TransactionMir]
getTxMirs_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir]
getTxMirs_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxMirs :: TxHash -> BlockfrostClient [TransactionMir]
getTxMirs :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir]
getTxMirs TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMir]
`getTxMirs_` TxHash
t)
getTxPoolUpdates_ :: Project -> TxHash -> BlockfrostClient [TransactionPoolUpdate]
getTxPoolUpdates_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolUpdate]
getTxPoolUpdates_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolUpdate])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolUpdate]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxPoolUpdates :: TxHash -> BlockfrostClient [TransactionPoolUpdate]
getTxPoolUpdates :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolUpdate]
getTxPoolUpdates TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolUpdate])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolUpdate]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolUpdate]
`getTxPoolUpdates_` TxHash
t)
getTxPoolRetiring_ :: Project -> TxHash -> BlockfrostClient [TransactionPoolRetiring]
getTxPoolRetiring_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolRetiring]
getTxPoolRetiring_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolRetiring]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxPoolRetiring :: TxHash -> BlockfrostClient [TransactionPoolRetiring]
getTxPoolRetiring :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolRetiring]
getTxPoolRetiring TxHash
t = (Project
-> ExceptT
BlockfrostError
(ReaderT ClientConfig IO)
[TransactionPoolRetiring])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolRetiring]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionPoolRetiring]
`getTxPoolRetiring_` TxHash
t)
getTxMetadataJSON_ :: Project -> TxHash -> BlockfrostClient [TransactionMetaJSON]
getTxMetadataJSON_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON]
getTxMetadataJSON_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON]
forall route.
TransactionsAPI route
-> route
:- (Summary "Transaction metadata"
:> (Description "Obtain the transaction metadata."
:> (Capture "hash" TxHash
:> ("metadata" :> Get '[JSON] [TransactionMetaJSON]))))
_txMetadataJSON (TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxMetadataJSON :: TxHash -> BlockfrostClient [TransactionMetaJSON]
getTxMetadataJSON :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON]
getTxMetadataJSON TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaJSON]
`getTxMetadataJSON_` TxHash
t)
getTxMetadataCBOR_ :: Project -> TxHash -> BlockfrostClient [TransactionMetaCBOR]
getTxMetadataCBOR_ :: Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR]
getTxMetadataCBOR_ = TransactionsAPI (AsClientT BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [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 BlockfrostClient)
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR])
-> (Project -> TransactionsAPI (AsClientT BlockfrostClient))
-> Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> TransactionsAPI (AsClientT BlockfrostClient)
transactionsClient
getTxMetadataCBOR :: TxHash -> BlockfrostClient [TransactionMetaCBOR]
getTxMetadataCBOR :: TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR]
getTxMetadataCBOR TxHash
t = (Project
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR])
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> TxHash
-> ExceptT
BlockfrostError (ReaderT ClientConfig IO) [TransactionMetaCBOR]
`getTxMetadataCBOR_` TxHash
t)
submitTx_ :: Project -> CBORString -> BlockfrostClient TxHash
submitTx_ :: Project -> CBORString -> BlockfrostClient TxHash
submitTx_ = CardanoAPI (AsClientT BlockfrostClient)
-> CBORString -> BlockfrostClient 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 BlockfrostClient)
-> CBORString -> BlockfrostClient TxHash)
-> (Project -> CardanoAPI (AsClientT BlockfrostClient))
-> Project
-> CBORString
-> BlockfrostClient TxHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CardanoAPI (AsClientT BlockfrostClient)
cardanoClient
submitTx :: CBORString -> BlockfrostClient TxHash
submitTx :: CBORString -> BlockfrostClient TxHash
submitTx CBORString
txCbor = (Project -> BlockfrostClient TxHash) -> BlockfrostClient TxHash
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project -> CBORString -> BlockfrostClient TxHash
`submitTx_` CBORString
txCbor)