Skip to content

Commit

Permalink
Merge pull request #22 from maestro-org/21-epochs-endpoint-support
Browse files Browse the repository at this point in the history
Feat 21: Epochs endpoint support
  • Loading branch information
Vardominator authored May 24, 2023
2 parents c146969 + 6d30100 commit db2d045
Show file tree
Hide file tree
Showing 12 changed files with 196 additions and 20 deletions.
13 changes: 13 additions & 0 deletions maestro-exe/Maestro/Run/Epochs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module Maestro.Run.Epochs where

import Maestro.Client.Env
import Maestro.Client.Epochs

runEpochsAPI :: MaestroEnv -> IO ()
runEpochsAPI mEnv = do
putStrLn "Fetching Current Epoch's Info ..."
currentEpochInfo <- getCurrentEpoch mEnv
putStrLn $ "Received: ⮯\n" ++ show currentEpochInfo
putStrLn "Fetching 70th Epoch's Info ..."
epochInfo <- getEpochInfo mEnv 70
putStrLn $ "Received: ⮯\n" ++ show epochInfo
2 changes: 2 additions & 0 deletions maestro-exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Main (main) where

import qualified Data.Text as T
import Maestro.Client.Env
import Maestro.Run.Epochs
import Maestro.Run.Pools
import Maestro.Run.Tx
import System.Environment (getEnv)
Expand All @@ -14,6 +15,7 @@ main = do
env <- mkMaestroEnv (T.pack apiId) Preprod
runPoolsAPI env
runTxApi env
runEpochsAPI env

where
maestroId = getEnv "MAESTRO_API_KEY"
6 changes: 5 additions & 1 deletion maestro-sdk.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -42,12 +42,14 @@ library
Maestro.API.Accounts
Maestro.API.Address
Maestro.API.Assets
Maestro.API.Epochs
Maestro.API.General
Maestro.API.Pool
Maestro.API.Transaction

Maestro.Client
Maestro.Client.Env
Maestro.Client.Epochs
Maestro.Client.Accounts
Maestro.Client.Address
Maestro.Client.Assets
Expand All @@ -60,7 +62,7 @@ library
Maestro.Types.Address
Maestro.Types.Assets
Maestro.Types.Common
Maestro.Types.Epoch
Maestro.Types.Epochs
Maestro.Types.General
Maestro.Types.Pool

Expand Down Expand Up @@ -94,6 +96,7 @@ test-suite maestro-sdk-tests
hs-source-dirs: test
main-is: Driver.hs
other-modules:
Maestro.Test.Epochs
Maestro.Test.General
Maestro.Test.Pool
Maestro.Test.Transaction
Expand All @@ -118,6 +121,7 @@ executable maestro-exe
other-modules:
Maestro.Run.Pools
Maestro.Run.Tx
Maestro.Run.Epochs
-- other-extensions:
hs-source-dirs: maestro-exe
main-is: Main.hs
Expand Down
2 changes: 2 additions & 0 deletions src/Maestro/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import Data.Proxy (Proxy (..))
import Maestro.API.Accounts
import Maestro.API.Address
import Maestro.API.Assets
import Maestro.API.Epochs
import Maestro.API.General
import Maestro.API.Pool
import Maestro.API.Transaction
Expand All @@ -17,6 +18,7 @@ data MaestroApi route = Routes
, _general :: route :- ToServantApi GeneralAPI
, _pools :: route :- "pools" :> ToServantApi PoolAPI
, _tx :: route :- ToServantApi TxAPI
, _epochs :: route :- "epochs" :> ToServantApi EpochsAPI
} deriving(Generic)

api :: Proxy (ToServantApi MaestroApi)
Expand Down
2 changes: 1 addition & 1 deletion src/Maestro/API/Accounts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ data AccountsAPI route = AccountsAPI
:: route
:- Capture "stake_addr" String
:> "history"
:> QueryParam "epoch_no" EpochNo
:> QueryParam "epoch_no" EpochNo
:> Pagination
:> Get '[JSON] [AccountsHistory]

Expand Down
20 changes: 20 additions & 0 deletions src/Maestro/API/Epochs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module Maestro.API.Epochs where

import Maestro.Types.Common (EpochNo)
import Maestro.Types.Epochs
import Servant.API
import Servant.API.Generic

data EpochsAPI route =
EpochsAPI
{
_currentEpochInfo
:: route
:- "current"
:> Get '[JSON] CurrentEpochInfo
, _epochInfo
:: route
:- Capture "epoch_no" EpochNo
:> "info"
:> Get '[JSON] EpochInfo
} deriving (Generic)
2 changes: 1 addition & 1 deletion src/Maestro/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,4 +10,4 @@ import Servant.Client
import Servant.Client.Generic

apiClient :: MaestroEnv -> MaestroApi (AsClientT IO)
apiClient MaestroEnv{..} = genericClientHoist $ \x -> runClientM x _maeClientEnv >>= either throwIO pure
apiClient MaestroEnv{..} = genericClientHoist $ \x -> runClientM x _maeClientEnv >>= either throwIO pure
23 changes: 23 additions & 0 deletions src/Maestro/Client/Epochs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
module Maestro.Client.Epochs
( getCurrentEpoch
, getEpochInfo
) where

import Maestro.API (_epochs)
import Maestro.API.Epochs
import Maestro.Client
import Maestro.Client.Env
import Maestro.Types
import Servant.API.Generic
import Servant.Client

epochsClient :: MaestroEnv -> EpochsAPI (AsClientT IO)
epochsClient = fromServant . _epochs . apiClient

-- | Get information about the current epoch.
getCurrentEpoch :: MaestroEnv -> IO CurrentEpochInfo
getCurrentEpoch = _currentEpochInfo . epochsClient

-- | Get information about a specific epoch.
getEpochInfo :: MaestroEnv -> EpochNo -> IO EpochInfo
getEpochInfo = _epochInfo . epochsClient
2 changes: 2 additions & 0 deletions src/Maestro/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Maestro.Types
( module Maestro.Types.Accounts
, module Maestro.Types.Address
, module Maestro.Types.Assets
, module Maestro.Types.Epochs
, module Maestro.Types.Common
, module Maestro.Types.General
, module Maestro.Types.Pool
Expand All @@ -13,5 +14,6 @@ import Maestro.Types.Accounts
import Maestro.Types.Address
import Maestro.Types.Assets
import Maestro.Types.Common
import Maestro.Types.Epochs
import Maestro.Types.General
import Maestro.Types.Pool
17 changes: 0 additions & 17 deletions src/Maestro/Types/Epoch.hs

This file was deleted.

60 changes: 60 additions & 0 deletions src/Maestro/Types/Epochs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
module Maestro.Types.Epochs ( EpochInfoFees (..), CurrentEpochInfo (..), EpochInfo (..) ) where

import Data.Aeson (FromJSON (parseJSON), toEncoding,
toJSON, withText)
import Data.Text (unpack)
import Data.Time.Clock.POSIX (POSIXTime)
import Data.Word (Word64)
import Deriving.Aeson
import Maestro.Types.Common
import Numeric.Natural (Natural)
import Text.Read (readMaybe)

-- | Sum of all the fees within the epoch in lovelaces.
newtype EpochInfoFees = EpochInfoFees Natural deriving newtype (Eq, Show)

instance ToJSON EpochInfoFees where
toEncoding = toEncoding . show
toJSON = toJSON . show

instance FromJSON EpochInfoFees where
parseJSON = withText "EpochInfoFees" $ \txt -> either fail pure $ textToNatural $ unpack txt
where
textToNatural :: String -> Either String EpochInfoFees
textToNatural txt = case readMaybe txt :: Maybe Natural of
Just n -> Right $ EpochInfoFees n
Nothing -> Left "Given epoch fees is not a natural number"

-- | Current epoch information.
data CurrentEpochInfo = CurrentEpochInfo
{ -- | Current epoch number.
_currentEpochInfoEpochNo :: !EpochNo
, -- | Sum of all the fees within the epoch in lovelaces.
_currentEpochInfoFees :: !EpochInfoFees
, -- | Number of transactions within the epoch.
_currentEpochInfoTxCount :: !Word64
, -- | Number of blocks within the epoch.
_currentEpochInfoBlkCount :: !Word64
, -- | Start time of the epoch in UNIX time.
_currentEpochInfoStartTime :: !POSIXTime
}
deriving stock (Show, Eq, Generic)
deriving (FromJSON, ToJSON) via CustomJSON '[FieldLabelModifier '[StripPrefix "_currentEpochInfo", CamelToSnake]] CurrentEpochInfo

-- | Epoch information.
data EpochInfo = EpochInfo
{ -- | Epoch number.
_epochInfoEpochNo :: !EpochNo
, -- | Sum of all the fees within the epoch in lovelaces.
_epochInfoFees :: !EpochInfoFees
, -- | Number of transactions within the epoch.
_epochInfoTxCount :: !Word64
, -- | Number of blocks within the epoch.
_epochInfoBlkCount :: !Word64
, -- | Start time of the epoch in UNIX time.
_epochInfoStartTime :: !POSIXTime
, -- | End time of the epoch in UNIX time.
_epochInfoEndTime :: !POSIXTime
}
deriving stock (Show, Eq, Generic)
deriving (FromJSON, ToJSON) via CustomJSON '[FieldLabelModifier '[StripPrefix "_epochInfo", CamelToSnake]] EpochInfo
67 changes: 67 additions & 0 deletions test/Maestro/Test/Epochs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,67 @@
module Maestro.Test.Epochs where

import Data.Aeson (eitherDecode)
import Test.Hspec
import Text.RawString.QQ

import Data.ByteString.Lazy (ByteString)
import Maestro.Types

spec_general :: Spec
spec_general = do

it "parsing /epochs/current sample" $ do
eitherDecode currentEpochSample
`shouldBe`
Right currentEpochExpected

it "parsing /epochs/{epoch_no}/info sample" $ do
eitherDecode epochInfoSample
`shouldBe`
Right epochInfoExpected


currentEpochSample :: ByteString
currentEpochSample = [r|
{
"epoch_no": 413,
"fees": "47553352844",
"tx_count": 127481,
"blk_count": 6488,
"start_time": 1684619256
}
|]

currentEpochExpected :: CurrentEpochInfo
currentEpochExpected = CurrentEpochInfo
{ _currentEpochInfoBlkCount = 6488
, _currentEpochInfoEpochNo = 413
, _currentEpochInfoFees = EpochInfoFees 47553352844
, _currentEpochInfoStartTime = 1684619256
, _currentEpochInfoTxCount = 127481
}

epochInfoSample :: ByteString
epochInfoSample = [r|
{
"epoch_no": 36,
"fees": "8308727733",
"tx_count": 18799,
"blk_count": 21052,
"start_time": 1669593614,
"end_time": 1670025570
}
|]

epochInfoExpected :: EpochInfo
epochInfoExpected = EpochInfo
{ _epochInfoEpochNo = 36
, _epochInfoFees = EpochInfoFees 8308727733
, _epochInfoTxCount = 18799
, _epochInfoBlkCount = 21052
, _epochInfoStartTime = 1669593614
, _epochInfoEndTime = 1670025570
}



0 comments on commit db2d045

Please sign in to comment.