-- | Blockfrost client
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Blockfrost.Client
  ( module Blockfrost.API
  , module Blockfrost.Env
  , module Blockfrost.Types
  , module Blockfrost.Lens
  , module Blockfrost.Client.Core
  , module Blockfrost.Client.Types
    -- Common
  , getRoot
  , getHealth
  , getClock
    -- Metrics
  , getMetrics
  , getMetricsEndpoints
    -- Cardano - Accounts
  , getAccount
  , getAccountRewards
  , getAccountRewards'
  , getAccountHistory
  , getAccountHistory'
  , getAccountDelegations
  , getAccountDelegations'
  , getAccountRegistrations
  , getAccountRegistrations'
  , getAccountWithdrawals
  , getAccountWithdrawals'
  , getAccountMirs
  , getAccountMirs'
    -- Cardano - Addresses
  , getAddressInfo
  , getAddressDetails
  , getAddressUtxos
  , getAddressUtxos'
  , getAddressTransactions
  , getAddressTransactions'
    -- Cardano - Assets
  , getAssets
  , getAssets'
  , getAssetDetails
  , getAssetHistory
  , getAssetHistory'
  , getAssetTransactions
  , getAssetTransactions'
  , getAssetAddresses
  , getAssetAddresses'
  , getAssetsByPolicy
  , getAssetsByPolicy'
    -- Cardano - Blocks
  , getLatestBlock
  , getLatestBlockTxs
  , getLatestBlockTxs'
  , getBlock
  , getBlockSlot
  , getBlockEpochSlot
  , getNextBlocks
  , getNextBlocks'
  , getPreviousBlocks
  , getPreviousBlocks'
  , getBlockTxs
  , getBlockTxs'
    -- Cardano - Epochs
  , getLatestEpoch
  , getLatestEpochProtocolParams
  , getEpoch
  , getNextEpochs
  , getNextEpochs'
  , getPreviousEpochs
  , getPreviousEpochs'
  , getEpochStake
  , getEpochStake'
  , getEpochStakeByPool
  , getEpochStakeByPool'
  , getEpochBlocks
  , getEpochBlocks'
  , getEpochBlocksByPool
  , getEpochBlocksByPool'
  , getEpochProtocolParams
    -- Cardano - Ledger
  , getLedgerGenesis
    -- Cardano - Metadata
  , getTxMetadataLabels
  , getTxMetadataLabels'
  , getTxMetadataByLabelJSON
  , getTxMetadataByLabelJSON'
  , getTxMetadataByLabelCBOR
  , getTxMetadataByLabelCBOR'
    -- Cardano - Network
  , getNetworkInfo
    -- Cardano - Pools
  , listPools
  , listPools'
  , listRetiredPools
  , listRetiredPools'
  , listRetiringPools
  , listRetiringPools'
  , getPool
  , getPoolHistory
  , getPoolHistory'
  , getPoolMetadata
  , getPoolRelays
  , getPoolDelegators
  , getPoolDelegators'
  , getPoolBlocks
  , getPoolBlocks'
  , getPoolUpdates
  , getPoolUpdates'
    -- Cardano - Transactions
  , getTx
  , getTxUtxos
  , getTxStakes
  , getTxDelegations
  , getTxWithdrawals
  , getTxMirs
  , getTxPoolUpdates
  , getTxPoolRetiring
  , getTxMetadataJSON
  , getTxMetadataCBOR
  , submitTx
    -- IPFS
  , ipfsAdd
  , ipfsGateway
  , ipfsGetPin
  , ipfsListPins
  , ipfsListPins'
  , ipfsPin
  , ipfsRemovePin
    -- Nut.link
  , 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.Transactions
import Blockfrost.Client.IPFS
import Blockfrost.Client.NutLink
import Blockfrost.Client.Types

import Data.Text (Text)

-- ** Client functions
-- *** Health

getRoot' :: Project -> BlockfrostClient URLVersion
getRoot' :: Project -> BlockfrostClient URLVersion
getRoot' = CommonAPI (AsClientT BlockfrostClient)
-> BlockfrostClient 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 BlockfrostClient)
 -> BlockfrostClient URLVersion)
-> (Project -> CommonAPI (AsClientT BlockfrostClient))
-> Project
-> BlockfrostClient URLVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT BlockfrostClient)
commonClient

-- | Root endpoint has no other function than to point end users to documentation
getRoot  :: BlockfrostClient URLVersion
getRoot :: BlockfrostClient URLVersion
getRoot = (Project -> BlockfrostClient URLVersion)
-> BlockfrostClient URLVersion
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go Project -> BlockfrostClient URLVersion
getRoot'

getHealth' :: Project -> BlockfrostClient Healthy
getHealth' :: Project -> BlockfrostClient Healthy
getHealth' = CommonAPI (AsClientT BlockfrostClient) -> BlockfrostClient 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 BlockfrostClient)
 -> BlockfrostClient Healthy)
-> (Project -> CommonAPI (AsClientT BlockfrostClient))
-> Project
-> BlockfrostClient Healthy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT BlockfrostClient)
commonClient

-- | Return backend status. Your application should handle situations when backend for the given chain is unavailable.
getHealth  :: BlockfrostClient Healthy
getHealth :: BlockfrostClient Healthy
getHealth = (Project -> BlockfrostClient Healthy) -> BlockfrostClient Healthy
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go Project -> BlockfrostClient Healthy
getHealth'

getClock':: Project -> BlockfrostClient ServerTime
getClock' :: Project -> BlockfrostClient ServerTime
getClock' = CommonAPI (AsClientT BlockfrostClient)
-> BlockfrostClient 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 BlockfrostClient)
 -> BlockfrostClient ServerTime)
-> (Project -> CommonAPI (AsClientT BlockfrostClient))
-> Project
-> BlockfrostClient ServerTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT BlockfrostClient)
commonClient

-- | Get current backend time
getClock:: BlockfrostClient ServerTime
getClock :: BlockfrostClient ServerTime
getClock = (Project -> BlockfrostClient ServerTime)
-> BlockfrostClient ServerTime
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go Project -> BlockfrostClient ServerTime
getClock'

getMetrics':: Project -> BlockfrostClient [Metric]
getMetrics' :: Project -> BlockfrostClient [Metric]
getMetrics' = CommonAPI (AsClientT BlockfrostClient) -> BlockfrostClient [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 BlockfrostClient)
 -> BlockfrostClient [Metric])
-> (Project -> CommonAPI (AsClientT BlockfrostClient))
-> Project
-> BlockfrostClient [Metric]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT BlockfrostClient)
commonClient

-- | Get Blockfrost usage metrics over last 30 days
getMetrics:: BlockfrostClient [Metric]
getMetrics :: BlockfrostClient [Metric]
getMetrics = (Project -> BlockfrostClient [Metric]) -> BlockfrostClient [Metric]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go Project -> BlockfrostClient [Metric]
getMetrics'

getMetricsEndpoints':: Project -> BlockfrostClient [(Text, Metric)]
getMetricsEndpoints' :: Project -> BlockfrostClient [(Text, Metric)]
getMetricsEndpoints' = CommonAPI (AsClientT BlockfrostClient)
-> BlockfrostClient [(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 BlockfrostClient)
 -> BlockfrostClient [(Text, Metric)])
-> (Project -> CommonAPI (AsClientT BlockfrostClient))
-> Project
-> BlockfrostClient [(Text, Metric)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CommonAPI (AsClientT BlockfrostClient)
commonClient

-- | Get Blockfrost endpoint usage metrics over last 30 days
getMetricsEndpoints:: BlockfrostClient [(Text, Metric)]
getMetricsEndpoints :: BlockfrostClient [(Text, Metric)]
getMetricsEndpoints = (Project -> BlockfrostClient [(Text, Metric)])
-> BlockfrostClient [(Text, Metric)]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go Project -> BlockfrostClient [(Text, Metric)]
getMetricsEndpoints'