Skip to content

Commit

Permalink
Shelley/Cardano: take the initial nonce as a parameter
Browse files Browse the repository at this point in the history
Fixes #2005.

This nonce will be used to construct Shelley's initial `PrtclState`, both when
starting a fresh Shelley chain and when forking from Byron to Shelley (when
translating the Byron `ConsensusState` to the Shelley one).

We store the initial nonce in the `TPraosParams`, which is part of the
`ConsensusConfig` for `TPraos`. We need it here, at run-time, because we need
it when translating the Byron `ConsensusState` to the Shelley one.

`protocolInfoShelley` and `protocolInfoCardano` (as well as
`ProtocolReadTPraos` and `ProtocolCardano`) now take a `Nonce` argument that
will be used as the initial nonce. Typically the `Nonce` passed to these
functions (constructors) should be derived from the hash of the Shelley
Genesis config JSON file. Moreover, this allows us to choose a different
initial nonce for testing purposes, as required for #2235.

NOTE: up until now we have used `SL.NeutralNonce` as the initial nonce for
Shelley. When a different nonce is picked in `cardano-node`, i.e., one derived
from the hash of the Shelley Genesis config JSON file, it would cause a hard
fork.
  • Loading branch information
mrBliss committed Jun 26, 2020
1 parent 755d3ff commit a647b8c
Show file tree
Hide file tree
Showing 8 changed files with 50 additions and 22 deletions.
14 changes: 10 additions & 4 deletions ouroboros-consensus-cardano/src/Ouroboros/Consensus/Cardano.hs
Original file line number Diff line number Diff line change
Expand Up @@ -142,6 +142,9 @@ data Protocol (m :: * -> *) blk p where
-- | Run TPraos against the real Shelley ledger
ProtocolRealTPraos
:: ShelleyGenesis TPraosStandardCrypto
-> Nonce
-- ^ The initial nonce, typically derived from the hash of Genesis
-- config JSON file.
-> ProtVer
-> Natural -- ^ Max major protocol version
-> Maybe (TPraosLeaderCredentials TPraosStandardCrypto)
Expand All @@ -157,6 +160,9 @@ data Protocol (m :: * -> *) blk p where
-> Maybe PBftLeaderCredentials
-- Shelley
-> ShelleyGenesis TPraosStandardCrypto
-> Nonce
-- ^ The initial nonce for the Shelley era, typically derived from the
-- hash of Shelley Genesis config JSON file.
-> ProtVer -- TODO unify with 'Update.ProtocolVersion' (2 vs 3 numbers)
-> Natural -- ^ Max major protocol version
-> Maybe (TPraosLeaderCredentials TPraosStandardCrypto)
Expand Down Expand Up @@ -206,16 +212,16 @@ protocolInfo (ProtocolMockPBFT paramsPBft paramsEra nid) =
protocolInfo (ProtocolRealPBFT gc mthr prv swv mplc) =
protocolInfoByron gc mthr prv swv mplc

protocolInfo (ProtocolRealTPraos genesis protVer maxMajorPV mbLeaderCredentials) =
protocolInfoShelley genesis maxMajorPV protVer mbLeaderCredentials
protocolInfo (ProtocolRealTPraos genesis initialNonce protVer maxMajorPV mbLeaderCredentials) =
protocolInfoShelley genesis initialNonce maxMajorPV protVer mbLeaderCredentials

protocolInfo (ProtocolCardano
genesisByron mthr prv swv mbLeaderCredentialsByron
genesisShelley protVer maxMajorPV mbLeaderCredentialsShelley
genesisShelley initialNonce protVer maxMajorPV mbLeaderCredentialsShelley
mbLowerBound hardCodedTransition) =
protocolInfoCardano
genesisByron mthr prv swv mbLeaderCredentialsByron
genesisShelley protVer maxMajorPV mbLeaderCredentialsShelley
genesisShelley initialNonce protVer maxMajorPV mbLeaderCredentialsShelley
mbLowerBound hardCodedTransition

{-------------------------------------------------------------------------------
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
Expand Down Expand Up @@ -463,14 +462,17 @@ translateChainDepStateByronToShelleyWrapper
ByronBlock
(ShelleyBlock sc)
translateChainDepStateByronToShelleyWrapper =
RequireBoth $ \_ _ -> Translate $ \_ (WrapChainDepState pbftState) ->
WrapChainDepState (translateChainDepStateByronToShelley pbftState)
RequireBoth $ \_ (WrapConsensusConfig shelleyCfg) ->
Translate $ \_ (WrapChainDepState pbftState) ->
WrapChainDepState $
translateChainDepStateByronToShelley shelleyCfg pbftState

translateChainDepStateByronToShelley
:: forall bc sc.
PBftState bc
ConsensusConfig (TPraos sc)
-> PBftState bc
-> TPraosState sc
translateChainDepStateByronToShelley pbftState =
translateChainDepStateByronToShelley TPraosConfig { tpraosParams } pbftState =
TPraosState.empty (PBftState.tipSlot pbftState) $
SL.PrtclState
Map.empty
Expand All @@ -479,8 +481,7 @@ translateChainDepStateByronToShelley pbftState =
nonce
nonce
where
-- TODO use hash of Shelley genesis config as entropy?
nonce = SL.NeutralNonce
nonce = tpraosInitialNonce tpraosParams

translateLedgerViewByronToShelleyWrapper
:: forall sc.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,8 @@ import qualified Ouroboros.Consensus.Byron.Ledger.Conversions as Byron
import Ouroboros.Consensus.Byron.Ledger.NetworkProtocolVersion
import Ouroboros.Consensus.Byron.Node

import Shelley.Spec.Ledger.BaseTypes (Nonce (..))

import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock)
import qualified Ouroboros.Consensus.Shelley.Ledger as Shelley
import Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion
Expand Down Expand Up @@ -286,6 +288,9 @@ protocolInfoCardano
-> Maybe PBftLeaderCredentials
-- Shelley
-> ShelleyGenesis sc
-> Nonce
-- ^ The initial nonce for the Shelley era, typically derived from the
-- hash of Shelley Genesis config JSON file.
-> ProtVer
-> Natural
-> Maybe (TPraosLeaderCredentials sc)
Expand All @@ -294,7 +299,7 @@ protocolInfoCardano
-> TriggerHardFork
-> ProtocolInfo m (CardanoBlock sc)
protocolInfoCardano genesisByron mSigThresh pVer sVer mbCredsByron
genesisShelley protVer maxMajorPV mbCredsShelley
genesisShelley initialNonce protVer maxMajorPV mbCredsShelley
mbLowerBound triggerHardFork =
assertWithMsg (checkMaxKESEvolutions genesisShelley) $
ProtocolInfo {
Expand Down Expand Up @@ -339,7 +344,7 @@ protocolInfoCardano genesisByron mSigThresh pVer sVer mbCredsByron
-- Shelley

tpraosParams :: TPraosParams
tpraosParams = Shelley.mkTPraosParams maxMajorPV genesisShelley
tpraosParams = Shelley.mkTPraosParams maxMajorPV initialNonce genesisShelley

blockConfigShelley :: BlockConfig (ShelleyBlock sc)
blockConfigShelley = Shelley.mkShelleyBlockConfig protVer genesisShelley
Expand Down
6 changes: 5 additions & 1 deletion ouroboros-consensus-cardano/test/Test/ThreadNet/Cardano.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ import Ouroboros.Consensus.Byron.Ledger.Block (ByronBlock)
import Ouroboros.Consensus.Byron.Ledger.Conversions
import Ouroboros.Consensus.Byron.Node

import qualified Shelley.Spec.Ledger.BaseTypes as SL
import qualified Shelley.Spec.Ledger.Genesis as SL
import qualified Shelley.Spec.Ledger.OCert as SL
import qualified Shelley.Spec.Ledger.PParams as SL
Expand Down Expand Up @@ -176,6 +177,7 @@ prop_simple_cardano_convergence TestSetup
generatedSecrets
propPV
genesisShelley
SL.NeutralNonce
(coreNodes !! fromIntegral nid)
(guard setupByronLowerBound *> Just numByronEpochs)
(TriggerHardForkAtVersion shelleyMajorVersion)
Expand Down Expand Up @@ -294,14 +296,15 @@ mkProtocolCardanoAndHardForkTxs
-> CC.Update.ProtocolVersion
-- Shelley
-> ShelleyGenesis sc
-> SL.Nonce
-> Shelley.CoreNode sc
-- Hard fork
-> Maybe EpochNo
-> TriggerHardFork
-> TestNodeInitialization m (CardanoBlock sc)
mkProtocolCardanoAndHardForkTxs
pbftParams coreNodeId genesisByron generatedSecretsByron propPV
genesisShelley coreNodeShelley
genesisShelley initialNonce coreNodeShelley
mbLowerBound triggerHardFork =
TestNodeInitialization
{ tniCrucialTxs = crucialTxs
Expand Down Expand Up @@ -333,6 +336,7 @@ mkProtocolCardanoAndHardForkTxs
(Just leaderCredentialsByron)
-- Shelley
genesisShelley
initialNonce
protVerShelley
maxMajorPVShelley
(Just leaderCredentialsShelley)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -294,11 +294,13 @@ mkGenesisConfig pVer k d slotLength maxKESEvolutions coreNodes =
mkProtocolRealTPraos
:: forall m c. (IOLike m, TPraosCrypto c)
=> ShelleyGenesis c
-> SL.Nonce
-> CoreNode c
-> ProtocolInfo m (ShelleyBlock c)
mkProtocolRealTPraos genesis coreNode =
mkProtocolRealTPraos genesis initialNonce coreNode =
protocolInfoShelley
genesis
initialNonce
maxMajorPV
protVer
(Just (mkLeaderCredentials coreNode))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Test.Util.HardFork.Future (singleEraFuture)
import Test.Util.Orphans.Arbitrary ()
import Test.Util.Random

import qualified Shelley.Spec.Ledger.BaseTypes as SL
import qualified Shelley.Spec.Ledger.OCert as SL
import qualified Shelley.Spec.Ledger.PParams as SL

Expand Down Expand Up @@ -106,6 +107,7 @@ prop_simple_real_tpraos_convergence TestSetup
plainTestNodeInitialization $
mkProtocolRealTPraos
genesisConfig
SL.NeutralNonce
(coreNodes !! fromIntegral nid)
, mkRekeyM = Nothing
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module Ouroboros.Consensus.Shelley.Node (
, SL.ShelleyGenesisStaking (..)
, TPraosLeaderCredentials (..)
, SL.ProtVer
, SL.Nonce (..)
, SL.emptyGenesisStaking
, shelleyMaintainForgeState
, checkMaxKESEvolutions
Expand Down Expand Up @@ -133,11 +134,14 @@ checkMaxKESEvolutions genesis
protocolInfoShelley
:: forall m c. (IOLike m, TPraosCrypto c)
=> SL.ShelleyGenesis c
-> SL.Nonce
-- ^ The initial nonce, typically derived from the hash of Genesis config
-- JSON file.
-> Natural -- ^ Max major protocol version
-> SL.ProtVer
-> Maybe (TPraosLeaderCredentials c)
-> ProtocolInfo m (ShelleyBlock c)
protocolInfoShelley genesis maxMajorPV protVer mbCredentials =
protocolInfoShelley genesis initialNonce maxMajorPV protVer mbCredentials =
assertWithMsg (checkMaxKESEvolutions genesis) $
ProtocolInfo {
pInfoConfig = topLevelConfig
Expand Down Expand Up @@ -166,7 +170,7 @@ protocolInfoShelley genesis maxMajorPV protVer mbCredentials =
epochInfo = fixedSizeEpochInfo $ SL.sgEpochLength genesis

tpraosParams :: TPraosParams
tpraosParams = mkTPraosParams maxMajorPV genesis
tpraosParams = mkTPraosParams maxMajorPV initialNonce genesis

mkLeaderCreds :: TPraosLeaderCredentials c
-> (TPraosIsCoreNode c, MaintainForgeState m (ShelleyBlock c))
Expand Down Expand Up @@ -209,9 +213,7 @@ protocolInfoShelley genesis maxMajorPV protVer mbCredentials =
(SL.sgGenDelegs genesis)
oSched
(SL.sgProtocolParams genesis)
-- We can start without entropy, throughout the epoch(s) we'll obtain
-- entropy.
SL.NeutralNonce
initialNonce

initExtLedgerState :: ExtLedgerState (ShelleyBlock c)
initExtLedgerState = ExtLedgerState {
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -192,14 +192,19 @@ data TPraosParams = TPraosParams {
, tpraosMaxLovelaceSupply :: !Word64
-- | Testnet or mainnet?
, tpraosNetworkId :: !SL.Network
-- | Initial nonce used for the TPraos protocol state. Typically this is
-- derived from the hash of the Shelley genesis config JSON file, but
-- different values may be used for testing purposes.
, tpraosInitialNonce :: !SL.Nonce
}
deriving (Generic, NoUnexpectedThunks)

mkTPraosParams
:: Natural -- ^ Max major protocol version
:: Natural -- ^ Max major protocol version
-> SL.Nonce -- ^ Initial nonce
-> SL.ShelleyGenesis c
-> TPraosParams
mkTPraosParams maxMajorPV genesis = TPraosParams {
mkTPraosParams maxMajorPV initialNonce genesis = TPraosParams {
tpraosSlotsPerKESPeriod = SL.sgSlotsPerKESPeriod genesis
, tpraosLeaderF = SL.sgActiveSlotCoeff genesis
, tpraosMaxKESEvo = SL.sgMaxKESEvolutions genesis
Expand All @@ -208,6 +213,7 @@ mkTPraosParams maxMajorPV genesis = TPraosParams {
, tpraosNetworkId = SL.sgNetworkId genesis
, tpraosSecurityParam = securityParam
, tpraosMaxMajorPV = maxMajorPV
, tpraosInitialNonce = initialNonce
}
where
securityParam = SecurityParam $ SL.sgSecurityParam genesis
Expand Down

0 comments on commit a647b8c

Please sign in to comment.