Skip to content
This repository was archived by the owner on Aug 18, 2020. It is now read-only.

Commit 505e323

Browse files
committed
Extend node API to include protocol parameters
We don't want to use NodeStateAdaptor from the wallet. Therefore we are moving it here and making it accessable via the node API. In this PR the following parameters are added to the node-settings endpoint: - slotId - slotCount - maxTxSize - feePolicy - securityParameter
1 parent 11a0746 commit 505e323

File tree

14 files changed

+759
-19
lines changed

14 files changed

+759
-19
lines changed

cluster/src/Cardano/Cluster.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,7 @@ startNode (NodeName nodeIdT, _) env = do
9797
let lArgs = getLoggingArgs cArgs
9898
withCompileInfo $ launchNode nArgs cArgs lArgs $ \genC walC txpC ntpC nodC sscC resC -> do
9999
actionWithCoreNode
100-
(launchNodeServer aArgs ntpC resC updateConfiguration compileInfo)
100+
(launchNodeServer aArgs ntpC resC updateConfiguration compileInfo genC)
101101
genC walC txpC ntpC nodC sscC resC
102102
where
103103
parseApiArgs = do

core/src/Pos/Core/Slotting/SlotCount.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module Pos.Core.Slotting.SlotCount
44

55
import Universum
66

7-
import Data.Aeson (ToJSON (..))
7+
import Data.Aeson (FromJSON (..), ToJSON (..))
88
import Data.SafeCopy (base, deriveSafeCopySimple)
99
import System.Random (Random (..))
1010

@@ -19,5 +19,6 @@ instance Bi SlotCount where
1919
decode = SlotCount <$> decode
2020

2121
deriving instance ToJSON SlotCount
22+
deriving instance FromJSON SlotCount
2223

2324
deriveSafeCopySimple 0 'base ''SlotCount

lib/cardano-sl.cabal

+2
Original file line numberDiff line numberDiff line change
@@ -142,6 +142,7 @@ library
142142
Pos.Communication.Server
143143

144144
build-depends: base
145+
, base64-bytestring
145146
, aeson >= 0.11.2.1
146147
, aeson-options
147148
, ansi-terminal
@@ -153,6 +154,7 @@ library
153154
, cardano-sl-binary-test
154155
, cardano-sl-chain
155156
, cardano-sl-core
157+
, cardano-sl-core-test
156158
, cardano-sl-crypto
157159
, cardano-sl-crypto-test
158160
, cardano-sl-db

lib/src/Pos/Node/API.hs

+240-9
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE DataKinds #-}
3+
{-# LANGUAGE KindSignatures #-}
34
{-# LANGUAGE RecordWildCards #-}
45
{-# LANGUAGE TypeOperators #-}
56
{-# OPTIONS_GHC -fno-warn-orphans #-}
@@ -12,13 +13,14 @@ import Control.Lens (At, Index, IxValue, at, ix, makePrisms, (?~))
1213
import Data.Aeson
1314
import qualified Data.Aeson.Options as Aeson
1415
import Data.Aeson.TH as A
15-
import Data.Aeson.Types (Value (..), toJSONKeyText)
16+
import Data.Aeson.Types (Parser, Value (..), toJSONKeyText)
1617
import qualified Data.ByteArray as ByteArray
1718
import qualified Data.Char as C
1819
import qualified Data.Map.Strict as Map
1920
import Data.Swagger hiding (Example, example)
2021
import qualified Data.Swagger as S
2122
import Data.Swagger.Declare (Declare, look)
23+
import qualified Data.Swagger.Internal
2224
import Data.Swagger.Internal.Schema (GToSchema)
2325
import Data.Swagger.Internal.TypeShape (GenericHasSimpleShape,
2426
GenericShape)
@@ -45,10 +47,12 @@ import Pos.Util.Example
4547
import Pos.Util.Servant (APIResponse, CustomQueryFlag, Flaggable (..),
4648
HasCustomQueryFlagDescription (..), Tags, ValidJSON)
4749
import Pos.Util.UnitsOfMeasure
50+
import Pos.Util.Util (aesonError)
4851
import Serokell.Util.Text
4952

5053
-- ToJSON/FromJSON instances for NodeId
5154
import Pos.Infra.Communication.Types.Protocol ()
55+
import Test.Pos.Core.Arbitrary ()
5256

5357

5458

@@ -91,6 +95,55 @@ genericSchemaDroppingPrefix prfx extraDoc proxy = do
9195
Just (Ref ref) -> maybe err rewrap (defs ^. at (getReference ref))
9296
_ -> err
9397

98+
99+
--
100+
-- Helpers for writing instances for types with units
101+
--
102+
103+
-- Using a newtype wrapper might have been more elegant in some ways, but the
104+
-- helpers need different amounts of information.
105+
106+
-- Convert to user-presentable text for the API
107+
unitToText :: UnitOfMeasure -> Text
108+
unitToText Bytes = "bytes"
109+
unitToText LovelacePerByte = "Lovelace/byte"
110+
unitToText Lovelace = "Lovelace"
111+
unitToText Seconds = "seconds"
112+
unitToText Milliseconds = "milliseconds"
113+
unitToText Microseconds = "microseconds"
114+
unitToText Percentage100 = "percent"
115+
unitToText Blocks = "blocks"
116+
unitToText BlocksPerSecond = "blocks/second"
117+
118+
toJSONWithUnit :: ToJSON a => UnitOfMeasure -> a -> Value
119+
toJSONWithUnit u a =
120+
object
121+
[ "unit" .= unitToText u
122+
, "quantity" .= toJSON a
123+
]
124+
125+
-- This function ignores the unit, which might cause confusion.
126+
parseJSONQuantity :: FromJSON a => String -> Value -> Parser a
127+
parseJSONQuantity s = withObject s $ \o -> o .: "quantity"
128+
129+
-- assumes there is only one allowed unit
130+
toSchemaWithUnit :: (HasRequired b [a1], HasProperties b a2,
131+
Monoid b, Monoid a2, At a2, IsString a1, IsString (Index a2),
132+
ToSchema a3,
133+
HasType b (SwaggerType 'Data.Swagger.Internal.SwaggerKindSchema),
134+
IxValue a2 ~ Referenced Schema) =>
135+
UnitOfMeasure -> proxy a3 -> b
136+
toSchemaWithUnit unitOfMeasure a = (mempty
137+
& type_ .~ SwaggerObject
138+
& required .~ ["quantity"]
139+
& properties .~ (mempty
140+
& at "quantity" ?~ toSchemaRef a
141+
& at "unit" ?~ (Inline $ mempty
142+
& type_ .~ SwaggerString
143+
& enum_ ?~ [String $ unitToText unitOfMeasure]
144+
)
145+
))
146+
94147
data ForceNtpCheck
95148
= ForceNtpCheck
96149
| NoNtpCheck
@@ -431,6 +484,49 @@ instance BuildableSafeGen SlotDuration where
431484
buildSafeGen _ (SlotDuration (MeasuredIn w)) =
432485
bprint (build%"ms") w
433486

487+
newtype MaxTxSize = MaxTxSize (MeasuredIn 'Bytes Int)
488+
deriving (Show, Eq)
489+
490+
instance ToJSON MaxTxSize where
491+
toJSON (MaxTxSize (MeasuredIn s)) =
492+
object
493+
[ "quantity" .= toJSON s
494+
, "unit" .= String "bytes"
495+
]
496+
497+
instance FromJSON MaxTxSize where
498+
parseJSON = withObject "MaxTxSize" $ \o ->
499+
mkMaxTxSize <$> o .: "quantity"
500+
501+
mkMaxTxSize :: Int -> MaxTxSize
502+
mkMaxTxSize = MaxTxSize . MeasuredIn
503+
504+
instance Arbitrary MaxTxSize where
505+
arbitrary = mkMaxTxSize <$> arbitrary
506+
507+
deriveSafeBuildable ''MaxTxSize
508+
instance BuildableSafeGen MaxTxSize where
509+
buildSafeGen _ (MaxTxSize (MeasuredIn w)) =
510+
bprint (build%"bytes") w
511+
512+
instance ToSchema MaxTxSize where
513+
declareNamedSchema _ = do
514+
pure $ NamedSchema (Just "MaxTxSize") $ mempty
515+
& type_ .~ SwaggerObject
516+
& required .~ ["quantity"]
517+
& properties .~ (mempty
518+
& at "quantity" ?~ (Inline $ mempty
519+
& type_ .~ SwaggerNumber
520+
& minimum_ .~ (Just 0)
521+
)
522+
& at "unit" ?~ (Inline $ mempty
523+
& type_ .~ SwaggerString
524+
& enum_ ?~ ["bytes"]
525+
)
526+
)
527+
528+
529+
434530
-- | This deceptively-simple newtype is a wrapper to virtually @all@ the types exposed as
435531
-- part of this API. The reason is twofold:
436532
--
@@ -547,47 +643,179 @@ instance ToSchema (V1 Version) where
547643
pure $ NamedSchema (Just "V1Version") $ mempty
548644
& type_ .~ SwaggerString
549645

646+
647+
newtype SecurityParameter = SecurityParameter Int
648+
deriving (Show, Eq, Generic, ToJSON, FromJSON, Arbitrary)
649+
650+
instance Buildable SecurityParameter where
651+
build (SecurityParameter i) = bprint shown i
652+
653+
instance ToSchema SecurityParameter where
654+
declareNamedSchema _ =
655+
pure $ NamedSchema (Just "SecurityParameter") $ mempty
656+
& type_ .~ SwaggerNumber
657+
& minimum_ .~ (Just 0)
658+
659+
660+
instance ToSchema (V1 Core.SlotId) where
661+
declareNamedSchema _ = do
662+
word64Schema <- declareSchemaRef (Proxy @Word64)
663+
word16Schema <- declareSchemaRef (Proxy @Word16)
664+
return $ NamedSchema (Just "SlotId") $ mempty
665+
& type_ .~ SwaggerObject
666+
& properties .~ (mempty
667+
& at "slot" ?~ word16Schema
668+
& at "epoch" ?~ word64Schema)
669+
670+
instance ToJSON (V1 Core.SlotId) where
671+
toJSON (V1 s) =
672+
object
673+
[ "epoch" .= toJSON (Core.getEpochIndex $ Core.siEpoch s)
674+
, "slot" .= toJSON (Core.getSlotIndex $ Core.siSlot s)
675+
]
676+
677+
instance FromJSON (V1 Core.SlotId) where
678+
parseJSON = withObject "SlotId" $ \sl ->
679+
Core.SlotId
680+
<$> (fromInteger <$> sl .: "epoch")
681+
<*> (Core.UnsafeLocalSlotIndex <$> sl .: "slot")
682+
<&> V1
683+
684+
instance Arbitrary (V1 Core.SlotId) where
685+
arbitrary = fmap V1 arbitrary
686+
687+
688+
689+
instance Arbitrary (V1 Core.TxFeePolicy) where
690+
arbitrary = fmap V1 (arbitrary `suchThat` predicate)
691+
where
692+
-- Don't generate unknown feepolicies
693+
predicate (Core.TxFeePolicyTxSizeLinear _) = True
694+
predicate (Core.TxFeePolicyUnknown _ _) = False
695+
696+
instance ToJSON (V1 Core.TxFeePolicy) where
697+
toJSON (V1 p) =
698+
object $ case p of
699+
Core.TxFeePolicyTxSizeLinear (Core.TxSizeLinear a b) ->
700+
[ "tag" .= ("linear" :: String)
701+
, "a" .= toJSONWithUnit LovelacePerByte a
702+
, "b" .= toJSONWithUnit Lovelace b
703+
]
704+
Core.TxFeePolicyUnknown _ _ ->
705+
[ "tag" .= ("unknown" :: String)
706+
]
707+
708+
instance FromJSON (V1 Core.TxFeePolicy) where
709+
parseJSON j = V1 <$> (withObject "TxFeePolicy" $ \o -> do
710+
(tag :: String) <- o .: "tag"
711+
case tag of
712+
"linear" -> do
713+
a <- (o .: "a") >>= parseJSONQuantity "Coeff"
714+
b <- (o .: "b") >>= parseJSONQuantity "Coeff"
715+
return $ Core.TxFeePolicyTxSizeLinear $ Core.TxSizeLinear a b
716+
_ ->
717+
aesonError "TxFeePolicy: unknown policy name") j
718+
719+
instance ToSchema (V1 Core.TxFeePolicy) where
720+
declareNamedSchema _ = do
721+
pure $ NamedSchema (Just "Core.TxFeePolicy") $ mempty
722+
& type_ .~ SwaggerObject
723+
& required .~ ["tag"]
724+
& properties .~ (mempty
725+
& at "tag" ?~ (Inline $ mempty
726+
& type_ .~ SwaggerString
727+
& enum_ ?~ ["linear", "unknown"]
728+
)
729+
& at "a" ?~ (Inline $ toSchemaWithUnit LovelacePerByte (Proxy @Double))
730+
& at "b" ?~ (Inline $ toSchemaWithUnit Lovelace (Proxy @Double))
731+
)
732+
733+
instance Arbitrary (V1 Core.SlotCount) where
734+
arbitrary = fmap V1 arbitrary
735+
736+
instance ToSchema (V1 Core.SlotCount) where
737+
declareNamedSchema _ =
738+
pure $ NamedSchema (Just "V1Core.SlotCount") $ mempty
739+
& type_ .~ SwaggerNumber
740+
& minimum_ .~ Just 0
741+
742+
743+
744+
instance ToJSON (V1 Core.SlotCount) where
745+
toJSON (V1 (Core.SlotCount c)) = toJSON c
746+
747+
instance FromJSON (V1 Core.SlotCount) where
748+
parseJSON v = V1 . Core.SlotCount <$> parseJSON v
749+
750+
751+
550752
-- | The @static@ settings for this wallet node. In particular, we could group
551753
-- here protocol-related settings like the slot duration, the transaction max size,
552754
-- the current software version running on the node, etc.
553755
data NodeSettings = NodeSettings
554-
{ setSlotDuration :: !SlotDuration
555-
, setSoftwareInfo :: !(V1 Core.SoftwareVersion)
556-
, setProjectVersion :: !(V1 Version)
557-
, setGitRevision :: !Text
756+
{ setSlotId :: !(V1 Core.SlotId)
757+
, setSlotDuration :: !SlotDuration
758+
, setSlotCount :: !(V1 Core.SlotCount)
759+
, setSoftwareInfo :: !(V1 Core.SoftwareVersion)
760+
, setProjectVersion :: !(V1 Version)
761+
, setGitRevision :: !Text
762+
, setMaxTxSize :: !MaxTxSize
763+
, setFeePolicy :: !(V1 Core.TxFeePolicy)
764+
, setSecurityParameter :: !SecurityParameter
558765
} deriving (Show, Eq, Generic)
559766

560767
deriveJSON Aeson.defaultOptions ''NodeSettings
561768

562769
instance ToSchema NodeSettings where
563770
declareNamedSchema =
564771
genericSchemaDroppingPrefix "set" (\(--^) props -> props
565-
& ("slotDuration" --^ "Duration of a slot.")
566-
& ("softwareInfo" --^ "Various pieces of information about the current software.")
567-
& ("projectVersion" --^ "Current project's version.")
568-
& ("gitRevision" --^ "Git revision of this deployment.")
772+
& ("slotId" --^ "The current slot and epoch.")
773+
& ("slotDuration" --^ "Duration of a slot.")
774+
& ("slotCount" --^ "The number of slots per epoch.")
775+
& ("softwareInfo" --^ "Various pieces of information about the current software.")
776+
& ("projectVersion" --^ "Current project's version.")
777+
& ("gitRevision" --^ "Git revision of this deployment.")
778+
& ("maxTxSize" --^ "The largest allowed transaction size")
779+
& ("feePolicy" --^ "The fee policy.")
780+
& ("securityParameter" --^ "The security parameter.")
569781
)
570782

571783
instance Arbitrary NodeSettings where
572784
arbitrary = NodeSettings <$> arbitrary
785+
<*> arbitrary
786+
<*> arbitrary
573787
<*> arbitrary
574788
<*> arbitrary
575789
<*> pure "0e1c9322a"
790+
<*> arbitrary
791+
<*> arbitrary
792+
<*> arbitrary
576793

577794
instance Example NodeSettings
578795

579796
deriveSafeBuildable ''NodeSettings
580797
instance BuildableSafeGen NodeSettings where
581798
buildSafeGen _ NodeSettings{..} = bprint ("{"
799+
%" slotId="%build
582800
%" slotDuration="%build
801+
%" slotCount="%build
583802
%" softwareInfo="%build
584803
%" projectRevision="%build
585804
%" gitRevision="%build
805+
%" maxTxSize="%build
806+
%" feePolicy="%build
807+
%" securityParameter="%build
586808
%" }")
809+
setSlotId
587810
setSlotDuration
811+
setSlotCount
588812
setSoftwareInfo
589813
setProjectVersion
590814
setGitRevision
815+
setMaxTxSize
816+
setFeePolicy
817+
setSecurityParameter
818+
591819

592820

593821
type SettingsAPI =
@@ -620,3 +848,6 @@ type API =
620848
Summary "Restart the underlying node software."
621849
:> "restart-node"
622850
:> Post '[ValidJSON] NoContent
851+
852+
853+

lib/src/Pos/Util/UnitsOfMeasure.hs

+3
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,9 @@ data UnitOfMeasure =
1919
| Blocks
2020
-- | Number of blocks per second.
2121
| BlocksPerSecond
22+
| Bytes
23+
| Lovelace
24+
| LovelacePerByte
2225
deriving (Show, Eq)
2326

2427
data MeasuredIn (a :: UnitOfMeasure) b = MeasuredIn b deriving (Eq, Show)

nix/.stack.nix/cardano-sl-node.nix

+1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)