-
Notifications
You must be signed in to change notification settings - Fork 5
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge pull request #22 from maestro-org/21-epochs-endpoint-support
Feat 21: Epochs endpoint support
- Loading branch information
Showing
12 changed files
with
196 additions
and
20 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file was deleted.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 | ||
} | ||
|
||
|
||
|