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

Commit

Permalink
[CO-410] Add golden decode only test for Configuration
Browse files Browse the repository at this point in the history
  • Loading branch information
Jimbo4350 committed Oct 12, 2018
1 parent fc4b583 commit dcb500b
Show file tree
Hide file tree
Showing 13 changed files with 411 additions and 11 deletions.
2 changes: 1 addition & 1 deletion chain/src/Pos/Chain/Block/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ data BlockConfiguration = BlockConfiguration
-- | Chain quality will be also calculated for this amount of seconds.
, ccFixedTimeCQ :: !Second

} deriving (Show, Generic)
} deriving (Eq, Generic, Show)

This comment has been minimized.

Copy link
@Jimbo4350

Jimbo4350 Oct 12, 2018

Author Contributor

All subtypes of Configuration require an Eq instance for the decoding test.

instance ToJSON BlockConfiguration where
toJSON = genericToJSON defaultOptions
Expand Down
4 changes: 2 additions & 2 deletions chain/src/Pos/Chain/Genesis/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,9 +148,9 @@ instance FromJSON StaticConfig where
avvmBalanceFactor
useHeavyDlg
seed)
| otherwise = fail "Incorrect JSON encoding for GenesisConfiguration"
| otherwise = fail "Incorrect JSON encoding for StaticConfig"

This comment has been minimized.

Copy link
@Jimbo4350

Jimbo4350 Oct 12, 2018

Author Contributor

GenesisConfiguration was renamed to StaticConfig. These changes reflect that.

parseJSON invalid = typeMismatch "GenesisConfiguration" invalid
parseJSON invalid = typeMismatch "StaticConfig" invalid

--------------------------------------------------------------------------------
-- Config
Expand Down
2 changes: 1 addition & 1 deletion chain/src/Pos/Chain/Ssc/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ data SscConfiguration = SscConfiguration
-- | Don't print “SSC couldn't compute seed” for the first epoch.
, ccNoReportNoSecretsForEpoch1 :: !Bool
}
deriving (Show, Generic)
deriving (Eq, Generic, Show)

instance FromJSON SscConfiguration where
parseJSON = genericParseJSON defaultOptions
Expand Down
2 changes: 1 addition & 1 deletion chain/src/Pos/Chain/Update/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ data UpdateConfiguration = UpdateConfiguration
-- | System tag.
, ccSystemTag :: !SystemTag
}
deriving (Show, Generic)
deriving (Eq, Generic, Show)

instance ToJSON UpdateConfiguration where
toJSON = genericToJSON defaultOptions
Expand Down
2 changes: 2 additions & 0 deletions lib/cardano-sl.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -283,6 +283,7 @@ test-suite cardano-test
Test.Pos.Diffusion.BlockSpec
Test.Pos.Genesis.CanonicalSpec
Test.Pos.Launcher.ConfigurationSpec
Test.Pos.Launcher.Json
Test.Pos.MerkleSpec
Test.Pos.Infra.Slotting.TypesSpec
Test.Pos.Types.Identity.SafeCopySpec
Expand Down Expand Up @@ -322,6 +323,7 @@ test-suite cardano-test
, filelock
, formatting
, generic-arbitrary
, hedgehog
, hspec
, lens
, network-transport
Expand Down
2 changes: 1 addition & 1 deletion lib/src/Pos/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ data NodeConfiguration = NodeConfiguration
, ccExplorerExtendedApi :: !Bool
-- ^ Enable explorer extended API for fetching more
-- info about addresses (like utxos) and bulk endpoints
} deriving (Show, Generic)
} deriving (Eq, Generic, Show)

instance ToJSON NodeConfiguration where
toJSON = genericToJSON defaultOptions
Expand Down
6 changes: 3 additions & 3 deletions lib/src/Pos/Launcher/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ data Configuration = Configuration
, ccNode :: !NodeConfiguration
, ccWallet :: !WalletConfiguration
, ccReqNetMagic :: !RequiresNetworkMagic
} deriving (Show, Generic)
} deriving (Eq, Generic , Show)

instance FromJSON Configuration where
parseJSON = withObject "Configuration" $ \o -> do
Expand Down Expand Up @@ -114,7 +114,7 @@ instance ToJSON Configuration where

data WalletConfiguration = WalletConfiguration
{ ccThrottle :: !(Maybe ThrottleSettings)
} deriving (Show, Generic)
} deriving (Eq, Generic, Show)

defaultWalletConfiguration :: WalletConfiguration
defaultWalletConfiguration = WalletConfiguration
Expand All @@ -131,7 +131,7 @@ data ThrottleSettings = ThrottleSettings
{ tsRate :: !Word64
, tsPeriod :: !Word64
, tsBurst :: !Word64
} deriving (Show, Generic)
} deriving (Eq, Generic, Show)

defaultThrottleSettings :: ThrottleSettings
defaultThrottleSettings = ThrottleSettings
Expand Down
3 changes: 3 additions & 0 deletions lib/test/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,11 @@ import Test.Hspec (hspec)
import Spec (spec)

import Test.Pos.Configuration (defaultTestConf)
import qualified Test.Pos.Launcher.Json
import Test.Pos.Util.Tripping (runTests)

main :: IO ()
main = do
putText $ "default configuration: " <> show defaultTestConf
hspec spec
runTests [ Test.Pos.Launcher.Json.tests ]
158 changes: 158 additions & 0 deletions lib/test/Test/Pos/Launcher/Json.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,158 @@
{-# LANGUAGE TemplateHaskell #-}

module Test.Pos.Launcher.Json
( tests
) where

import Universum

import qualified Data.HashMap.Strict as HM
import qualified Data.Set as S
import Hedgehog (Property)
import qualified Hedgehog as H

import Ntp.Client (NtpConfiguration (..))
import Pos.Chain.Block (BlockConfiguration (..))
import Pos.Chain.Delegation (DlgConfiguration (..))
import Pos.Chain.Genesis (FakeAvvmOptions (..),
GenesisAvvmBalances (..), GenesisDelegation (..),
GenesisInitializer (..), GenesisProtocolConstants (..),
GenesisSpec (..), StaticConfig (..),
TestnetBalanceOptions (..))
import Pos.Chain.Ssc (SscConfiguration (..))
import Pos.Chain.Txp (TxpConfiguration (..))
import Pos.Chain.Update
import Pos.Configuration (NodeConfiguration (..))
import Pos.Core.Common (Coeff (..), CoinPortion (..), SharedSeed (..),
TxFeePolicy (..), TxSizeLinear (..))
import Pos.Core.ProtocolConstants (VssMaxTTL (..), VssMinTTL (..))
import Pos.Core.Slotting (EpochIndex (..))
import Pos.Crypto.Configuration (ProtocolMagic (..),
ProtocolMagicId (..), RequiresNetworkMagic (..))
import Pos.Launcher.Configuration (Configuration (..),
WalletConfiguration (..))

import Test.Pos.Util.Golden (discoverGolden, goldenTestJSONDec)
--------------------------------------------------------------------------------
-- Configuration
--------------------------------------------------------------------------------

-- Decode-only golden tests for ensuring that, when decoding the legacy
-- `Configuration` JSON format, the `RequiresNetworkMagic` field defaults to
-- the correct `RequiresNetworkMagic`.

golden_Configuration_Legacy_NoNetworkMagicField :: Property
golden_Configuration_Legacy_NoNetworkMagicField =
goldenTestJSONDec
testGoldenConf_NoNetworkMagicField
"test/golden/json/Configuration_Legacy_NoNetworkMagicField"

testGoldenConf_NoNetworkMagicField :: Configuration
testGoldenConf_NoNetworkMagicField = Configuration
{ ccGenesis = GCSpec
( UnsafeGenesisSpec
{ gsAvvmDistr = GenesisAvvmBalances (HM.fromList [])
, gsFtsSeed = SharedSeed "skovoroda Ggurda boroda provoda "
, gsHeavyDelegation = UnsafeGenesisDelegation (HM.fromList [])
, gsBlockVersionData = BlockVersionData
{ bvdScriptVersion = 0
, bvdSlotDuration = 7000
, bvdMaxBlockSize = 2000000
, bvdMaxHeaderSize = 2000000
, bvdMaxTxSize = 4096
, bvdMaxProposalSize = 700
, bvdMpcThd = CoinPortion 100000000000000
, bvdHeavyDelThd = CoinPortion 100000000000000
, bvdUpdateVoteThd = CoinPortion 100000000000000
, bvdUpdateProposalThd = CoinPortion 100000000000000
, bvdUpdateImplicit = 10
, bvdSoftforkRule = SoftforkRule
{ srInitThd = CoinPortion 100000000000000
, srMinThd = CoinPortion 100000000000000
, srThdDecrement = CoinPortion 100000000000000
}
, bvdTxFeePolicy =
TxFeePolicyTxSizeLinear
(TxSizeLinear
(Coeff 155381.000000000) (Coeff 43.946000000))
, bvdUnlockStakeEpoch = EpochIndex 1844
}
, gsProtocolConstants = GenesisProtocolConstants
{ gpcK = 2
, gpcProtocolMagic = ProtocolMagic
(ProtocolMagicId 55550001) RequiresMagic
, gpcVssMaxTTL = VssMaxTTL 6
, gpcVssMinTTL = VssMinTTL 2
}
, gsInitializer = GenesisInitializer
{ giTestBalance = TestnetBalanceOptions
{ tboPoors = 12
, tboRichmen = 4
, tboTotalBalance = 600000000000000000
, tboRichmenShare = 0.99
, tboUseHDAddresses = True
}
, giFakeAvvmBalance = FakeAvvmOptions
{ faoCount = 10
, faoOneBalance = 100000
}
, giAvvmBalanceFactor = CoinPortion 100000000000000
, giUseHeavyDlg = True
, giSeed = 0
}
}
)
, ccNtp = NtpConfiguration
{ ntpcServers =
[ "0.pool.ntp.org"
, "2.pool.ntp.org"
, "3.pool.ntp.org"
]
, ntpcResponseTimeout = 30000000
, ntpcPollDelay = 1800000000
}
, ccUpdate = UpdateConfiguration
{ ccApplicationName = ApplicationName "cardano-sl"
, ccLastKnownBlockVersion = BlockVersion 0 0 0
, ccApplicationVersion = 0
, ccSystemTag = SystemTag "linux64"
}
, ccSsc = SscConfiguration
{ ccMpcSendInterval = 10
, ccMdNoCommitmentsEpochThreshold = 3
, ccNoReportNoSecretsForEpoch1 = False
}
, ccDlg = DlgConfiguration
{ ccDlgCacheParam = 500
, ccMessageCacheTimeout = 30
}
, ccTxp = TxpConfiguration
{ ccMemPoolLimitTx = 200
, tcAssetLockedSrcAddrs = S.fromList []
}
, ccBlock = BlockConfiguration
{ ccNetworkDiameter = 3
, ccRecoveryHeadersMessage = 20
, ccStreamWindow = 2048
, ccNonCriticalCQBootstrap = 0.95
, ccCriticalCQBootstrap = 0.8888
, ccNonCriticalCQ = 0.8
, ccCriticalCQ = 0.654321
, ccCriticalForkThreshold = 2
, ccFixedTimeCQ = 10
}
, ccNode = NodeConfiguration
{ ccNetworkConnectionTimeout = 15000
, ccConversationEstablishTimeout = 30000
, ccBlockRetrievalQueueSize = 100
, ccPendingTxResubmissionPeriod = 7
, ccWalletProductionApi = False
, ccWalletTxCreationDisabled = False
, ccExplorerExtendedApi = False
}
, ccWallet = WalletConfiguration { ccThrottle = Nothing }
, ccReqNetMagic = RequiresNoMagic
}

tests :: IO Bool
tests = H.checkSequential $$discoverGolden
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
{"core":{"genesis":{"spec":{"initializer":{"testBalance":{"poors":12,"richmen":4,"richmenShare":0.99,"useHDAddresses":true,"totalBalance":600000000000000000},"fakeAvvmBalance":{"count":10,"oneBalance":100000},"avvmBalanceFactor":0.1,"useHeavyDlg":true,"seed":0},"blockVersionData":{"scriptVersion":0,"slotDuration":7000,"maxBlockSize":2000000,"maxHeaderSize":2000000,"maxTxSize":4096,"maxProposalSize":700,"mpcThd":0.1,"heavyDelThd":0.1,"updateVoteThd":0.1,"updateProposalThd":0.1,"updateImplicit":10,"softforkRule":{"initThd":0.1,"minThd":0.1,"thdDecrement":0.1},"txFeePolicy":{"txSizeLinear":{"a":155381,"b":43.946}},"unlockStakeEpoch":1844},"protocolConstants":{"k":2,"protocolMagic":55550001,"vssMinTTL":2,"vssMaxTTL":6},"ftsSeed":"c2tvdm9yb2RhIEdndXJkYSBib3JvZGEgcHJvdm9kYSA=","heavyDelegation":{},"avvmDistr":{}}},"requiresNetworkMagic":"RequiresNoMagic","dbSerializeVersion":0},"ntp":{"responseTimeout":30000000,"pollDelay":1800000000,"servers":["0.pool.ntp.org","2.pool.ntp.org","3.pool.ntp.org"]},"update":{"applicationName":"cardano-sl","applicationVersion":0,"lastKnownBlockVersion":{"bvMajor":0,"bvMinor":0,"bvAlt":0}},"ssc":{"mpcSendInterval":10,"mdNoCommitmentsEpochThreshold":3,"noReportNoSecretsForEpoch1":false},"txp":{"memPoolLimitTx":200,"assetLockedSrcAddrs":[]},"dlg":{"dlgCacheParam":500,"messageCacheTimeout":30},"block":{"networkDiameter":3,"recoveryHeadersMessage":20,"streamWindow":2048,"nonCriticalCQBootstrap":0.95,"criticalCQBootstrap":0.8888,"nonCriticalCQ":0.8,"criticalCQ":0.654321,"criticalForkThreshold":2,"fixedTimeCQ":10},"node":{"networkConnectionTimeout":15000,"conversationEstablishTimeout":30000,"blockRetrievalQueueSize":100,"pendingTxResubmissionPeriod":7,"walletProductionApi":false,"walletTxCreationDisabled":false,"explorerExtendedApi":false},"wallet":{"throttle":null}}
106 changes: 106 additions & 0 deletions lib/test/golden/json/Prettified_Haskell_Value_Configuration
Original file line number Diff line number Diff line change
@@ -0,0 +1,106 @@
This is the prettified version of `testGoldenConf_NoNetworkMagicField` for reference purposes.

Configuration
{ ccGenesis = GCSpec
( UnsafeGenesisSpec
{ gsAvvmDistr = GenesisAvvmBalances { getGenesisAvvmBalances = fromList [] }
, gsFtsSeed = SharedSeed { getSharedSeed = "skovoroda Ggurda boroda provoda " }
, gsHeavyDelegation = UnsafeGenesisDelegation { unGenesisDelegation = fromList [] }
, gsBlockVersionData = BlockVersionData
{ bvdScriptVersion = 0
, bvdSlotDuration = 7000ms
, bvdMaxBlockSize = Byte 2000000
, bvdMaxHeaderSize = Byte 2000000
, bvdMaxTxSize = Byte 4096
, bvdMaxProposalSize = Byte 700
, bvdMpcThd = CoinPortion { getCoinPortion = 10000000000000 }
, bvdHeavyDelThd = CoinPortion { getCoinPortion = 5000000000000 }
, bvdUpdateVoteThd = CoinPortion { getCoinPortion = 1000000000000 }
, bvdUpdateProposalThd = CoinPortion { getCoinPortion = 100000000000000 }
, bvdUpdateImplicit = 10
, bvdSoftforkRule = SoftforkRule
{ srInitThd = CoinPortion { getCoinPortion = 900000000000000 }
, srMinThd = CoinPortion { getCoinPortion = 600000000000000 }
, srThdDecrement = CoinPortion { getCoinPortion = 50000000000000 }
}
, bvdTxFeePolicy = TxFeePolicyTxSizeLinear ( TxSizeLinear ( Coeff 155381.000000000 ) ( Coeff 43.946000000 ) )
, bvdUnlockStakeEpoch = EpochIndex { getEpochIndex = 18446744073709551615 }
}
, gsProtocolConstants = GenesisProtocolConstants
{ gpcK = 10
, gpcProtocolMagic = ProtocolMagic
{ getProtocolMagicId = ProtocolMagicId { unProtocolMagicId = 55550001 }
, getRequiresNetworkMagic = RequiresMagic
}
, gpcVssMaxTTL = VssMaxTTL { getVssMaxTTL = 6 }
, gpcVssMinTTL = VssMinTTL { getVssMinTTL = 2 }
}
, gsInitializer = GenesisInitializer
{ giTestBalance = TestnetBalanceOptions
{ tboPoors = 12
, tboRichmen = 4
, tboTotalBalance = 600000000000000000
, tboRichmenShare = 0.99
, tboUseHDAddresses = True
}
, giFakeAvvmBalance = FakeAvvmOptions
{ faoCount = 10
, faoOneBalance = 100000
}
, giAvvmBalanceFactor = CoinPortion { getCoinPortion = 1000000000000000 }
, giUseHeavyDlg = True
, giSeed = 0
}
}
)
, ccNtp = NtpConfiguration
{ ntpcServers =
[ "0.pool.ntp.org"
, "2.pool.ntp.org"
, "3.pool.ntp.org"
]
, ntpcResponseTimeout = 30000000
, ntpcPollDelay = 1800000000
}
, ccUpdate = UpdateConfiguration
{ ccApplicationName = ApplicationName { getApplicationName = "cardano-sl" }
, ccLastKnownBlockVersion = 0.0.0
, ccApplicationVersion = 0
, ccSystemTag = SystemTag { getSystemTag = "linux64" }
}
, ccSsc = SscConfiguration
{ ccMpcSendInterval = 10
, ccMdNoCommitmentsEpochThreshold = 3
, ccNoReportNoSecretsForEpoch1 = False
}
, ccDlg = DlgConfiguration
{ ccDlgCacheParam = 500
, ccMessageCacheTimeout = 30
}
, ccTxp = TxpConfiguration
{ ccMemPoolLimitTx = 200
, tcAssetLockedSrcAddrs = fromList []
}
, ccBlock = BlockConfiguration
{ ccNetworkDiameter = 3
, ccRecoveryHeadersMessage = 20
, ccStreamWindow = 2048
, ccNonCriticalCQBootstrap = 0.95
, ccCriticalCQBootstrap = 0.8888
, ccNonCriticalCQ = 0.8
, ccCriticalCQ = 0.654321
, ccCriticalForkThreshold = 2
, ccFixedTimeCQ = 10s
}
, ccNode = NodeConfiguration
{ ccNetworkConnectionTimeout = 15000
, ccConversationEstablishTimeout = 30000
, ccBlockRetrievalQueueSize = 100
, ccPendingTxResubmissionPeriod = 7
, ccWalletProductionApi = False
, ccWalletTxCreationDisabled = False
, ccExplorerExtendedApi = False
}
, ccWallet = WalletConfiguration { ccThrottle = Nothing }
, ccReqNetMagic = RequiresNoMagic
}
Loading

0 comments on commit dcb500b

Please sign in to comment.