-- | Epoch queries

module Blockfrost.Client.Cardano.Epochs
  ( getLatestEpoch
  , getLatestEpochProtocolParams
  , getEpoch
  , getNextEpochs
  , getNextEpochs'
  , getPreviousEpochs
  , getPreviousEpochs'
  , getEpochStake
  , getEpochStake'
  , getEpochStakeByPool
  , getEpochStakeByPool'
  , getEpochBlocks
  , getEpochBlocks'
  , getEpochBlocksByPool
  , getEpochBlocksByPool'
  , getEpochProtocolParams
  ) where

import Blockfrost.API
import Blockfrost.Client.Types
import Blockfrost.Types


epochsClient :: Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient :: Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient = (((ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
   :<|> ExceptT
          BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
  :<|> ((Epoch
         -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
        :<|> ((Epoch
               -> Paged
               -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
              :<|> (Epoch
                    -> Paged
                    -> ExceptT
                         BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]))))
 :<|> (((Epoch
         -> Paged
         -> ExceptT
              BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
        :<|> (Epoch
              -> PoolId
              -> Paged
              -> ExceptT
                   BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]))
       :<|> ((Epoch
              -> Paged
              -> SortOrder
              -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
             :<|> ((Epoch
                    -> PoolId
                    -> Paged
                    -> SortOrder
                    -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                   :<|> (Epoch
                         -> ExceptT
                              BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)))))
-> EpochsAPI (AsClientT BlockfrostClient)
forall (routes :: * -> *) mode.
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant ((((ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
    :<|> ExceptT
           BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
   :<|> ((Epoch
          -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
         :<|> ((Epoch
                -> Paged
                -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
               :<|> (Epoch
                     -> Paged
                     -> ExceptT
                          BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]))))
  :<|> (((Epoch
          -> Paged
          -> ExceptT
               BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
         :<|> (Epoch
               -> PoolId
               -> Paged
               -> ExceptT
                    BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]))
        :<|> ((Epoch
               -> Paged
               -> SortOrder
               -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
              :<|> ((Epoch
                     -> PoolId
                     -> Paged
                     -> SortOrder
                     -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                    :<|> (Epoch
                          -> ExceptT
                               BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)))))
 -> EpochsAPI (AsClientT BlockfrostClient))
-> (Project
    -> ((ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
         :<|> ExceptT
                BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
        :<|> ((Epoch
               -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
              :<|> ((Epoch
                     -> Paged
                     -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
                    :<|> (Epoch
                          -> Paged
                          -> ExceptT
                               BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]))))
       :<|> (((Epoch
               -> Paged
               -> ExceptT
                    BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
              :<|> (Epoch
                    -> PoolId
                    -> Paged
                    -> ExceptT
                         BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]))
             :<|> ((Epoch
                    -> Paged
                    -> SortOrder
                    -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                   :<|> ((Epoch
                          -> PoolId
                          -> Paged
                          -> SortOrder
                          -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                         :<|> (Epoch
                               -> ExceptT
                                    BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)))))
-> Project
-> EpochsAPI (AsClientT BlockfrostClient)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoAPI (AsClientT BlockfrostClient)
-> ((ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
     :<|> ExceptT
            BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
    :<|> ((Epoch
           -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
          :<|> ((Epoch
                 -> Paged
                 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
                :<|> (Epoch
                      -> Paged
                      -> ExceptT
                           BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]))))
   :<|> (((Epoch
           -> Paged
           -> ExceptT
                BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
          :<|> (Epoch
                -> PoolId
                -> Paged
                -> ExceptT
                     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]))
         :<|> ((Epoch
                -> Paged
                -> SortOrder
                -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
               :<|> ((Epoch
                      -> PoolId
                      -> Paged
                      -> SortOrder
                      -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                     :<|> (Epoch
                           -> ExceptT
                                BlockfrostError (ReaderT ClientConfig IO) ProtocolParams))))
forall route.
CardanoAPI route
-> route
   :- ("epochs"
       :> (Tag "Cardano \187 Epochs" :> ToServantApi EpochsAPI))
_epochs (CardanoAPI (AsClientT BlockfrostClient)
 -> ((ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
      :<|> ExceptT
             BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
     :<|> ((Epoch
            -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
           :<|> ((Epoch
                  -> Paged
                  -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
                 :<|> (Epoch
                       -> Paged
                       -> ExceptT
                            BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]))))
    :<|> (((Epoch
            -> Paged
            -> ExceptT
                 BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
           :<|> (Epoch
                 -> PoolId
                 -> Paged
                 -> ExceptT
                      BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]))
          :<|> ((Epoch
                 -> Paged
                 -> SortOrder
                 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                :<|> ((Epoch
                       -> PoolId
                       -> Paged
                       -> SortOrder
                       -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                      :<|> (Epoch
                            -> ExceptT
                                 BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)))))
-> (Project -> CardanoAPI (AsClientT BlockfrostClient))
-> Project
-> ((ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
     :<|> ExceptT
            BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
    :<|> ((Epoch
           -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
          :<|> ((Epoch
                 -> Paged
                 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
                :<|> (Epoch
                      -> Paged
                      -> ExceptT
                           BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]))))
   :<|> (((Epoch
           -> Paged
           -> ExceptT
                BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
          :<|> (Epoch
                -> PoolId
                -> Paged
                -> ExceptT
                     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]))
         :<|> ((Epoch
                -> Paged
                -> SortOrder
                -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
               :<|> ((Epoch
                      -> PoolId
                      -> Paged
                      -> SortOrder
                      -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
                     :<|> (Epoch
                           -> ExceptT
                                BlockfrostError (ReaderT ClientConfig IO) ProtocolParams))))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> CardanoAPI (AsClientT BlockfrostClient)
cardanoClient

getLatestEpoch_ :: Project -> BlockfrostClient EpochInfo
getLatestEpoch_ :: Project
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
getLatestEpoch_ = EpochsAPI (AsClientT BlockfrostClient)
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
forall route.
EpochsAPI route
-> route
   :- (Summary "Latest epoch"
       :> (Description
             "Return the information about the latest, therefore current, epoch."
           :> ("latest" :> Get '[JSON] EpochInfo)))
_latestEpoch (EpochsAPI (AsClientT BlockfrostClient)
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Get the information about the latest, therefore current, epoch.
getLatestEpoch :: BlockfrostClient EpochInfo
getLatestEpoch :: ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
getLatestEpoch = (Project
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go Project
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
getLatestEpoch_

getLatestEpochProtocolParams_ :: Project -> BlockfrostClient ProtocolParams
getLatestEpochProtocolParams_ :: Project
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
getLatestEpochProtocolParams_ = EpochsAPI (AsClientT BlockfrostClient)
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
forall route.
EpochsAPI route
-> route
   :- (Summary "Latest epoch protocol parameters"
       :> (Description
             "Return the protocol parameters for the latest epoch."
           :> ("latest" :> ("parameters" :> Get '[JSON] ProtocolParams))))
_latestEpochProtocolParams (EpochsAPI (AsClientT BlockfrostClient)
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Get the protocol parameters for the latest epoch.
getLatestEpochProtocolParams :: BlockfrostClient ProtocolParams
getLatestEpochProtocolParams :: ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
getLatestEpochProtocolParams = (Project
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go Project
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
getLatestEpochProtocolParams_

getEpoch_ :: Project -> Epoch -> BlockfrostClient EpochInfo
getEpoch_ :: Project
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
getEpoch_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
forall route.
EpochsAPI route
-> route
   :- (Summary "Specific epoch"
       :> (Description "Return the content of the requested epoch."
           :> (Capture "epoch_number" Epoch :> Get '[JSON] EpochInfo)))
_getEpoch (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Get the information about specific epoch.
getEpoch :: Epoch -> BlockfrostClient EpochInfo
getEpoch :: Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
getEpoch Epoch
e = (Project
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo)
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) EpochInfo
`getEpoch_` Epoch
e)

getNextEpochs_ :: Project -> Epoch -> Paged -> BlockfrostClient [EpochInfo]
getNextEpochs_ :: Project
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getNextEpochs_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
forall route.
EpochsAPI route
-> route
   :- (Summary "List of next epochs"
       :> (Description
             "Return the list of epochs following a specific epoch."
           :> (Capture "epoch_number" Epoch
               :> ("next" :> (Pagination :> Get '[JSON] [EpochInfo])))))
_getNextEpochs (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> Paged
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Return the list of epochs following a specific epoch.
-- Allows custom paging using @Paged@.
getNextEpochs' :: Epoch -> Paged -> BlockfrostClient [EpochInfo]
getNextEpochs' :: Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getNextEpochs' Epoch
e Paged
pg = (Project
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
p -> Project
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getNextEpochs_ Project
p Epoch
e Paged
pg)

-- | Return the list of epochs following a specific epoch.
getNextEpochs :: Epoch -> BlockfrostClient [EpochInfo]
getNextEpochs :: Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getNextEpochs Epoch
e = Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getNextEpochs' Epoch
e Paged
forall a. Default a => a
def

getPreviousEpochs_ :: Project -> Epoch -> Paged -> BlockfrostClient [EpochInfo]
getPreviousEpochs_ :: Project
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getPreviousEpochs_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
forall route.
EpochsAPI route
-> route
   :- (Summary "List of previous epochs"
       :> (Description
             "Return the list of epochs preceding a specific epoch."
           :> (Capture "epoch_number" Epoch
               :> ("previous" :> (Pagination :> Get '[JSON] [EpochInfo])))))
_getPreviousEpochs (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> Paged
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Return the list of epochs preceding a specific epoch.
-- Allows custom paging using @Paged@.
getPreviousEpochs' :: Epoch -> Paged -> BlockfrostClient [EpochInfo]
getPreviousEpochs' :: Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getPreviousEpochs' Epoch
e Paged
pg = (Project
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo])
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
p -> Project
-> Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getPreviousEpochs_ Project
p Epoch
e Paged
pg)

-- | Return the list of epochs preceding a specific epoch.
getPreviousEpochs :: Epoch -> BlockfrostClient [EpochInfo]
getPreviousEpochs :: Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getPreviousEpochs Epoch
e = Epoch
-> Paged
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [EpochInfo]
getPreviousEpochs' Epoch
e Paged
forall a. Default a => a
def

getEpochStake_ :: Project -> Epoch -> Paged -> BlockfrostClient [StakeDistribution]
getEpochStake_ :: Project
-> Epoch
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStake_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
forall route.
EpochsAPI route
-> route
   :- (Summary "Stake distribution"
       :> (Description
             "Return the active stake distribution for the specified epoch."
           :> (Capture "epoch_number" Epoch
               :> ("stakes" :> (Pagination :> Get '[JSON] [StakeDistribution])))))
_getEpochStake (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> Paged
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Return the active stake distribution for the specified epoch.
-- Allows custom paging using @Paged@.
getEpochStake' :: Epoch -> Paged -> BlockfrostClient [StakeDistribution]
getEpochStake' :: Epoch
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStake' Epoch
e Paged
pg = (Project
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
p -> Project
-> Epoch
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStake_ Project
p Epoch
e Paged
pg)

-- | Return the active stake distribution for the specified epoch.
getEpochStake :: Epoch -> BlockfrostClient [StakeDistribution]
getEpochStake :: Epoch
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStake Epoch
e = Epoch
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStake' Epoch
e Paged
forall a. Default a => a
def

getEpochStakeByPool_ :: Project -> Epoch -> PoolId -> Paged -> BlockfrostClient [StakeDistribution]
getEpochStakeByPool_ :: Project
-> Epoch
-> PoolId
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStakeByPool_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> PoolId
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
forall route.
EpochsAPI route
-> route
   :- (Summary "Stake distribution by pool"
       :> (Description
             "Return the active stake distribution for the epoch specified by stake pool."
           :> (Capture "epoch_number" Epoch
               :> ("stakes"
                   :> (Capture "pool_id" PoolId
                       :> (Pagination :> Get '[JSON] [StakeDistribution]))))))
_getEpochStakeByPool (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> PoolId
 -> Paged
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> PoolId
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Return the active stake distribution for the epoch specified by stake pool.
-- Allows custom paging using @Paged@.
getEpochStakeByPool' :: Epoch -> PoolId -> Paged -> BlockfrostClient [StakeDistribution]
getEpochStakeByPool' :: Epoch
-> PoolId
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStakeByPool' Epoch
e PoolId
i Paged
pg = (Project
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution])
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
p -> Project
-> Epoch
-> PoolId
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStakeByPool_ Project
p Epoch
e PoolId
i Paged
pg)

-- | Return the active stake distribution for the epoch specified by stake pool.
getEpochStakeByPool :: Epoch -> PoolId -> BlockfrostClient [StakeDistribution]
getEpochStakeByPool :: Epoch
-> PoolId
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStakeByPool Epoch
e PoolId
i = Epoch
-> PoolId
-> Paged
-> ExceptT
     BlockfrostError (ReaderT ClientConfig IO) [StakeDistribution]
getEpochStakeByPool' Epoch
e PoolId
i Paged
forall a. Default a => a
def

getEpochBlocks_ :: Project -> Epoch -> Paged -> SortOrder -> BlockfrostClient [BlockHash]
getEpochBlocks_ :: Project
-> Epoch
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocks_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
forall route.
EpochsAPI route
-> route
   :- (Summary "Block distribution"
       :> (Description "Return the blocks minted for the epoch specified."
           :> (Capture "epoch_number" Epoch
               :> ("blocks"
                   :> (Pagination :> (Sorting :> Get '[JSON] [BlockHash]))))))
_getEpochBlocks (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> Paged
 -> SortOrder
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Return the blocks minted for the epoch specified.
-- Allows custom paging and ordering using @Paged@ and @SortOrder@.
getEpochBlocks' :: Epoch -> Paged -> SortOrder -> BlockfrostClient [BlockHash]
getEpochBlocks' :: Epoch
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocks' Epoch
e Paged
pg SortOrder
s = (Project
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
p -> Project
-> Epoch
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocks_ Project
p Epoch
e Paged
pg SortOrder
s)

-- | Return the blocks minted for the epoch specified.
getEpochBlocks :: Epoch -> BlockfrostClient [BlockHash]
getEpochBlocks :: Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocks Epoch
e = Epoch
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocks' Epoch
e Paged
forall a. Default a => a
def SortOrder
forall a. Default a => a
def

getEpochBlocksByPool_ :: Project -> Epoch -> PoolId -> Paged -> SortOrder -> BlockfrostClient [BlockHash]
getEpochBlocksByPool_ :: Project
-> Epoch
-> PoolId
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocksByPool_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> PoolId
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
forall route.
EpochsAPI route
-> route
   :- (Summary "Block distribution"
       :> (Description
             "Return the block minted for the epoch specified by stake pool."
           :> (Capture "epoch_number" Epoch
               :> ("blocks"
                   :> (Capture "pool_id" PoolId
                       :> (Pagination :> (Sorting :> Get '[JSON] [BlockHash])))))))
_getEpochBlocksByPool (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> PoolId
 -> Paged
 -> SortOrder
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> PoolId
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Return the block minted for the epoch specified by stake pool.
-- Allows custom paging and ordering using @Paged@ and @SortOrder@.
getEpochBlocksByPool' :: Epoch -> PoolId -> Paged -> SortOrder -> BlockfrostClient [BlockHash]
getEpochBlocksByPool' :: Epoch
-> PoolId
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocksByPool' Epoch
e PoolId
i Paged
pg SortOrder
s = (Project
 -> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash])
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (\Project
p -> Project
-> Epoch
-> PoolId
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocksByPool_ Project
p Epoch
e PoolId
i Paged
pg SortOrder
s)

-- | Return the block minted for the epoch specified by stake pool.
getEpochBlocksByPool :: Epoch -> PoolId -> BlockfrostClient [BlockHash]
getEpochBlocksByPool :: Epoch
-> PoolId
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocksByPool Epoch
e PoolId
i = Epoch
-> PoolId
-> Paged
-> SortOrder
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) [BlockHash]
getEpochBlocksByPool' Epoch
e PoolId
i Paged
forall a. Default a => a
def SortOrder
forall a. Default a => a
def

getEpochProtocolParams_ :: Project -> Epoch -> BlockfrostClient ProtocolParams
getEpochProtocolParams_ :: Project
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
getEpochProtocolParams_ = EpochsAPI (AsClientT BlockfrostClient)
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
forall route.
EpochsAPI route
-> route
   :- (Summary "Protocol parameters"
       :> (Description
             "Return the protocol parameters for the specified epoch."
           :> (Capture "epoch_number" Epoch
               :> ("parameters" :> Get '[JSON] ProtocolParams))))
_getEpochProtocolParams (EpochsAPI (AsClientT BlockfrostClient)
 -> Epoch
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
-> (Project -> EpochsAPI (AsClientT BlockfrostClient))
-> Project
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Project -> EpochsAPI (AsClientT BlockfrostClient)
epochsClient

-- | Return the protocol parameters for the specified epoch.
getEpochProtocolParams :: Epoch -> BlockfrostClient ProtocolParams
getEpochProtocolParams :: Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
getEpochProtocolParams Epoch
e = (Project
 -> ExceptT
      BlockfrostError (ReaderT ClientConfig IO) ProtocolParams)
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
forall a. (Project -> BlockfrostClient a) -> BlockfrostClient a
go (Project
-> Epoch
-> ExceptT BlockfrostError (ReaderT ClientConfig IO) ProtocolParams
`getEpochProtocolParams_` Epoch
e)