{-# LANGUAGE CPP #-}
module Blockfrost.Client
  ( module Blockfrost.API
  , module Blockfrost.Env
  , module Blockfrost.Types
  , module Blockfrost.Lens
  , module Blockfrost.Client.Core
  , module Blockfrost.Client.Types
    
  , getRoot
  , getHealth
  , getClock
    
  , getMetrics
  , getMetricsEndpoints
    
  , getAccount
  , getAccountRewards
  , getAccountRewards'
  , getAccountHistory
  , getAccountHistory'
  , getAccountDelegations
  , getAccountDelegations'
  , getAccountRegistrations
  , getAccountRegistrations'
  , getAccountWithdrawals
  , getAccountWithdrawals'
  , getAccountMirs
  , getAccountMirs'
  , getAccountAssociatedAddresses
  , getAccountAssociatedAddresses'
  , getAccountAssociatedAssets
  , getAccountAssociatedAssets'
    
  , getAddressInfo
  , getAddressDetails
  , getAddressUtxos
  , getAddressUtxos'
  , getAddressUtxosAsset
  , getAddressUtxosAsset'
  , getAddressTransactions
  , getAddressTransactions'
    
  , getAssets
  , getAssets'
  , getAssetDetails
  , getAssetHistory
  , getAssetHistory'
  , getAssetTransactions
  , getAssetTransactions'
  , getAssetAddresses
  , getAssetAddresses'
  , getAssetsByPolicy
  , getAssetsByPolicy'
    
  , getLatestBlock
  , getLatestBlockTxs
  , getLatestBlockTxs'
  , getBlock
  , getBlockSlot
  , getBlockEpochSlot
  , getNextBlocks
  , getNextBlocks'
  , getPreviousBlocks
  , getPreviousBlocks'
  , getBlockTxs
  , getBlockTxs'
  , getBlockAffectedAddresses'
  , getBlockAffectedAddresses
    
  , getLatestEpoch
  , getLatestEpochProtocolParams
  , getEpoch
  , getNextEpochs
  , getNextEpochs'
  , getPreviousEpochs
  , getPreviousEpochs'
  , getEpochStake
  , getEpochStake'
  , getEpochStakeByPool
  , getEpochStakeByPool'
  , getEpochBlocks
  , getEpochBlocks'
  , getEpochBlocksByPool
  , getEpochBlocksByPool'
  , getEpochProtocolParams
    
  , getLedgerGenesis
    
  , getTxMetadataLabels
  , getTxMetadataLabels'
  , getTxMetadataByLabelJSON
  , getTxMetadataByLabelJSON'
  , getTxMetadataByLabelCBOR
  , getTxMetadataByLabelCBOR'
    
  , getNetworkInfo
    
  , listPools
  , listPools'
  , listRetiredPools
  , listRetiredPools'
  , listRetiringPools
  , listRetiringPools'
  , getPool
  , getPoolHistory
  , getPoolHistory'
  , getPoolMetadata
  , getPoolRelays
  , getPoolDelegators
  , getPoolDelegators'
  , getPoolBlocks
  , getPoolBlocks'
  , getPoolUpdates
  , getPoolUpdates'
    
  , listScripts
  , listScripts'
  , getScript
  , getScriptRedeemers
  , getScriptRedeemers'
  , getScriptDatum
  , getScriptJSON
  , getScriptCBOR
    
  , getTx
  , getTxUtxos
  , getTxStakes
  , getTxDelegations
  , getTxWithdrawals
  , getTxMirs
  , getTxPoolUpdates
  , getTxPoolRetiring
  , getTxMetadataJSON
  , getTxMetadataCBOR
  , getTxRedeemers
  , submitTx
    
  , ipfsAdd
  , ipfsGateway
  , ipfsGetPin
  , ipfsListPins
  , ipfsListPins'
  , ipfsPin
  , ipfsRemovePin
    
  , nutlinkListAddress
  , nutlinkListAddressTickers
  , nutlinkListAddressTickers'
  , nutlinkAddressTickers
  , nutlinkAddressTickers'
  , nutlinkTickers
  , nutlinkTickers'
  ) where
import Blockfrost.API
import Blockfrost.Client.Core
import Blockfrost.Env
import Blockfrost.Lens
import Blockfrost.Types
import Blockfrost.Client.Cardano.Accounts
import Blockfrost.Client.Cardano.Addresses
import Blockfrost.Client.Cardano.Assets
import Blockfrost.Client.Cardano.Blocks
import Blockfrost.Client.Cardano.Epochs
import Blockfrost.Client.Cardano.Ledger
import Blockfrost.Client.Cardano.Metadata
import Blockfrost.Client.Cardano.Network
import Blockfrost.Client.Cardano.Pools
import Blockfrost.Client.Cardano.Scripts
import Blockfrost.Client.Cardano.Transactions
import Blockfrost.Client.IPFS
import Blockfrost.Client.NutLink
import Blockfrost.Client.Types
import Data.Text (Text)
getRoot' :: MonadBlockfrost m => Project -> m URLVersion
getRoot' :: Project -> m URLVersion
getRoot' = CommonAPI (AsClientT m) -> m URLVersion
forall route.
CommonAPI route
-> route
   :- (Summary "Root endpoint"
       :> (Description
             "Root endpoint has no other function than to point end users to documentation."
           :> (Tag "Health" :> Get '[JSON] URLVersion)))
_getRoot (CommonAPI (AsClientT m) -> m URLVersion)
-> (Project -> CommonAPI (AsClientT m)) -> Project -> m URLVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getRoot  :: MonadBlockfrost m => m URLVersion
getRoot :: m URLVersion
getRoot = (Project -> m URLVersion) -> m URLVersion
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go Project -> m URLVersion
forall (m :: * -> *). MonadBlockfrost m => Project -> m URLVersion
getRoot'
getHealth' :: MonadBlockfrost m => Project -> m Healthy
getHealth' :: Project -> m Healthy
getHealth' = CommonAPI (AsClientT m) -> m Healthy
forall route.
CommonAPI route
-> route
   :- (Summary "Backend health status"
       :> (Description
             "Return backend status as a boolean. Your application should handle situations when backend for the given chain is unavailable."
           :> (Tag "Health" :> ("health" :> Get '[JSON] Healthy))))
_getHealth (CommonAPI (AsClientT m) -> m Healthy)
-> (Project -> CommonAPI (AsClientT m)) -> Project -> m Healthy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getHealth  :: MonadBlockfrost m => m Healthy
getHealth :: m Healthy
getHealth = (Project -> m Healthy) -> m Healthy
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go Project -> m Healthy
forall (m :: * -> *). MonadBlockfrost m => Project -> m Healthy
getHealth'
getClock':: MonadBlockfrost m => Project -> m ServerTime
getClock' :: Project -> m ServerTime
getClock' = CommonAPI (AsClientT m) -> m ServerTime
forall route.
CommonAPI route
-> route
   :- (Summary "Current backend time"
       :> (Description
             "This endpoint provides the current UNIX time. Your application might use this to verify if the client clock is not out of sync."
           :> (Tag "Health"
               :> ("health" :> ("clock" :> Get '[JSON] ServerTime)))))
_getClock (CommonAPI (AsClientT m) -> m ServerTime)
-> (Project -> CommonAPI (AsClientT m)) -> Project -> m ServerTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getClock :: MonadBlockfrost m => m ServerTime
getClock :: m ServerTime
getClock = (Project -> m ServerTime) -> m ServerTime
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go Project -> m ServerTime
forall (m :: * -> *). MonadBlockfrost m => Project -> m ServerTime
getClock'
getMetrics' :: MonadBlockfrost m => Project -> m [Metric]
getMetrics' :: Project -> m [Metric]
getMetrics' = CommonAPI (AsClientT m) -> m [Metric]
forall route.
CommonAPI route
-> route
   :- (Summary "Blockfrost usage metrics"
       :> (Description
             "History of your Blockfrost usage metrics in the past 30 days."
           :> (Tag "Metrics" :> ("metrics" :> Get '[JSON] [Metric]))))
_metrics (CommonAPI (AsClientT m) -> m [Metric])
-> (Project -> CommonAPI (AsClientT m)) -> Project -> m [Metric]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getMetrics :: MonadBlockfrost m => m [Metric]
getMetrics :: m [Metric]
getMetrics = (Project -> m [Metric]) -> m [Metric]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go Project -> m [Metric]
forall (m :: * -> *). MonadBlockfrost m => Project -> m [Metric]
getMetrics'
getMetricsEndpoints' :: MonadBlockfrost m => Project -> m [(Text, Metric)]
getMetricsEndpoints' :: Project -> m [(Text, Metric)]
getMetricsEndpoints' = CommonAPI (AsClientT m) -> m [(Text, Metric)]
forall route.
CommonAPI route
-> route
   :- (Summary "Blockfrost endpoint usage metrics"
       :> (Description
             "History of your Blockfrost usage metrics per endpoint in the past 30 days."
           :> (Tag "Metrics"
               :> ("metrics" :> ("endpoints" :> Get '[JSON] [(Text, Metric)])))))
_metricsEndpoints (CommonAPI (AsClientT m) -> m [(Text, Metric)])
-> (Project -> CommonAPI (AsClientT m))
-> Project
-> m [(Text, Metric)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT m)
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getMetricsEndpoints :: MonadBlockfrost m => m [(Text, Metric)]
getMetricsEndpoints :: m [(Text, Metric)]
getMetricsEndpoints = (Project -> m [(Text, Metric)]) -> m [(Text, Metric)]
forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go Project -> m [(Text, Metric)]
forall (m :: * -> *).
MonadBlockfrost m =>
Project -> m [(Text, Metric)]
getMetricsEndpoints'