{-# 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'
  , getAccountAssociatedAddressesTotal
  , getAccountAssociatedAssets
  , getAccountAssociatedAssets'
    
  , getAddressInfo
  , getAddressInfoExtended
  , 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
  , getNetworkEras
    
  , listPools
  , listPools'
  , listPoolsExtended
  , listPoolsExtended'
  , listRetiredPools
  , listRetiredPools'
  , listRetiringPools
  , listRetiringPools'
  , getPool
  , getPoolHistory
  , getPoolHistory'
  , getPoolMetadata
  , getPoolRelays
  , getPoolDelegators
  , getPoolDelegators'
  , getPoolBlocks
  , getPoolBlocks'
  , getPoolUpdates
  , getPoolUpdates'
    
  , listScripts
  , listScripts'
  , getScript
  , getScriptRedeemers
  , getScriptRedeemers'
  , getScriptDatum
  , getScriptDatumCBOR
  , getScriptJSON
  , getScriptCBOR
    
  , getTx
  , getTxUtxos
  , getTxStakes
  , getTxDelegations
  , getTxWithdrawals
  , getTxMirs
  , getTxPoolUpdates
  , getTxPoolRetiring
  , getTxMetadataJSON
  , getTxMetadataCBOR
  , getTxRedeemers
  , submitTx
    
  , deriveShelleyAddress
  , txEvaluate
  , txEvaluateUTXOs
    
  , 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.Cardano.Utils
import Blockfrost.Client.IPFS
import Blockfrost.Client.NutLink
import Blockfrost.Client.Types
import Data.Text (Text)
getRoot' :: MonadBlockfrost m => Project -> m URLVersion
getRoot' :: forall (m :: * -> *). MonadBlockfrost m => Project -> m URLVersion
getRoot' = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getRoot  :: MonadBlockfrost m => m URLVersion
getRoot :: forall (m :: * -> *). MonadBlockfrost m => m URLVersion
getRoot = forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go forall (m :: * -> *). MonadBlockfrost m => Project -> m URLVersion
getRoot'
getHealth' :: MonadBlockfrost m => Project -> m Healthy
getHealth' :: forall (m :: * -> *). MonadBlockfrost m => Project -> m Healthy
getHealth' = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getHealth  :: MonadBlockfrost m => m Healthy
getHealth :: forall (m :: * -> *). MonadBlockfrost m => m Healthy
getHealth = forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go forall (m :: * -> *). MonadBlockfrost m => Project -> m Healthy
getHealth'
getClock':: MonadBlockfrost m => Project -> m ServerTime
getClock' :: forall (m :: * -> *). MonadBlockfrost m => Project -> m ServerTime
getClock' = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getClock :: MonadBlockfrost m => m ServerTime
getClock :: forall (m :: * -> *). MonadBlockfrost m => m ServerTime
getClock = forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go forall (m :: * -> *). MonadBlockfrost m => Project -> m ServerTime
getClock'
getMetrics' :: MonadBlockfrost m => Project -> m [Metric]
getMetrics' :: forall (m :: * -> *). MonadBlockfrost m => Project -> m [Metric]
getMetrics' = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getMetrics :: MonadBlockfrost m => m [Metric]
getMetrics :: forall (m :: * -> *). MonadBlockfrost m => m [Metric]
getMetrics = forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go forall (m :: * -> *). MonadBlockfrost m => Project -> m [Metric]
getMetrics'
getMetricsEndpoints' :: MonadBlockfrost m => Project -> m [(Text, Metric)]
getMetricsEndpoints' :: forall (m :: * -> *).
MonadBlockfrost m =>
Project -> m [(Text, Metric)]
getMetricsEndpoints' = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
MonadBlockfrost m =>
Project -> CommonAPI (AsClientT m)
commonClient
getMetricsEndpoints :: MonadBlockfrost m => m [(Text, Metric)]
getMetricsEndpoints :: forall (m :: * -> *). MonadBlockfrost m => m [(Text, Metric)]
getMetricsEndpoints = forall (m :: * -> *) a.
MonadBlockfrost m =>
(Project -> m a) -> m a
go forall (m :: * -> *).
MonadBlockfrost m =>
Project -> m [(Text, Metric)]
getMetricsEndpoints'