Skip to content

Commit

Permalink
Allow not being a PBFT slot leader
Browse files Browse the repository at this point in the history
Currently the NodeConfig for PBft makes it non-optional to be a core
node, with corresponding credentials. This patch makes it optional so we
can have nodes without core node credentials.

We introduce a PBftIsLeader type that holds the various keys needed for
core nodes. We make the NodeConfig contain a Maybe one of these.

We take advantage of the IsLeader "proof" type and for PBft we make it
carry the PBftIsLeader. Of course this does not prove that n `mod` m = i
but it does at least hold all the credentials which are needed for
signing blocks. So it makes a lot of sense for checkIsLeader to return
these credentials.

The rest is just following through the consequences.
  • Loading branch information
dcoutts committed Jul 19, 2019
1 parent b2000ca commit 770556b
Show file tree
Hide file tree
Showing 5 changed files with 56 additions and 40 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -49,11 +49,11 @@ forgeBlockOrEBB
-> BlockNo -- ^ Current block number
-> ChainHash (ByronBlockOrEBB cfg) -- ^ Previous hash
-> [GenTx (ByronBlockOrEBB cfg)] -- ^ Txs to add in the block
-> () -- ^ Leader proof ('IsLeader')
-> PBftIsLeader PBftCardanoCrypto -- ^ Leader proof ('IsLeader')
-> m (ByronBlockOrEBB ByronConfig)
forgeBlockOrEBB cfg curSlot curNo prevHash txs () = case prevHash of
forgeBlockOrEBB cfg curSlot curNo prevHash txs isLeader = case prevHash of
GenesisHash -> forgeGenesisEBB cfg curSlot
BlockHash _ -> forgeBlock cfg curSlot curNo prevHash txs ()
BlockHash _ -> forgeBlock cfg curSlot curNo prevHash txs isLeader

forgeGenesisEBB
:: forall m.
Expand Down Expand Up @@ -99,11 +99,11 @@ forgeBlock
-> BlockNo -- ^ Current block number
-> ChainHash (ByronBlockOrEBB cfg) -- ^ Previous hash
-> [GenTx (ByronBlockOrEBB cfg)] -- ^ Txs to add in the block
-> () -- ^ Leader proof ('IsLeader')
-> PBftIsLeader PBftCardanoCrypto -- ^ Leader proof ('IsLeader')
-> m (ByronBlockOrEBB ByronConfig)
forgeBlock (WithEBBNodeConfig cfg) curSlot curNo prevHash txs () = do
forgeBlock (WithEBBNodeConfig cfg) curSlot curNo prevHash txs isLeader = do
ouroborosPayload <- give (VerKeyCardanoDSIGN headerGenesisKey)
$ forgePBftFields (encNodeConfigP cfg) toCBOR toSign
$ forgePBftFields isLeader toCBOR toSign
return $ forge ouroborosPayload
where
-- TODO: Might be sufficient to add 'ConfigContainsGenesis' constraint.
Expand Down Expand Up @@ -149,15 +149,15 @@ forgeBlock (WithEBBNodeConfig cfg) curSlot curNo prevHash txs () = do
}

headerGenesisKey :: Crypto.VerificationKey
VerKeyCardanoDSIGN headerGenesisKey = pbftGenVerKey $ encNodeConfigP cfg
VerKeyCardanoDSIGN headerGenesisKey = pbftGenVerKey isLeader

dlgCertificate :: CC.Delegation.Certificate
dlgCertificate = case findDelegate of
Just x -> x
Nothing -> error "Issuer is not a valid genesis key delegate."
where
dlgMap = CC.Genesis.unGenesisDelegation pbftGenesisDlg
VerKeyCardanoDSIGN delegate = pbftVerKey $ encNodeConfigP cfg
VerKeyCardanoDSIGN delegate = pbftVerKey isLeader
findDelegate = find (\crt -> CC.Delegation.delegateVK crt == delegate
&& CC.Delegation.issuerVK crt == headerGenesisKey
)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -90,9 +90,9 @@ instance ( SimpleCrypto c
) => ForgeExt (ExtNodeConfig ext (PBft c'))
c
(SimplePBftExt c c') where
forgeExt cfg () SimpleBlock{..} = do
forgeExt _cfg isLeader SimpleBlock{..} = do
ext :: SimplePBftExt c c' <- fmap SimplePBftExt $
forgePBftFields (encNodeConfigP cfg) encode $
forgePBftFields isLeader encode $
SignedSimplePBft {
signedSimplePBft = simpleHeaderStd
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ import Ouroboros.Consensus.Crypto.DSIGN.Cardano
import Ouroboros.Consensus.Ledger.Byron
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.Node.ProtocolInfo.Abstract
import Ouroboros.Consensus.NodeId (CoreNodeId (..), NodeId (..))
import Ouroboros.Consensus.NodeId (CoreNodeId (..))
import Ouroboros.Consensus.Protocol.ExtNodeConfig
import Ouroboros.Consensus.Protocol.PBFT
import Ouroboros.Consensus.Protocol.WithEBBs
Expand All @@ -50,15 +50,18 @@ protocolInfoByron (NumCoreNodes numCoreNodes) (CoreNodeId nid) params gc =
ProtocolInfo {
pInfoConfig = WithEBBNodeConfig $ EncNodeConfig {
encNodeConfigP = PBftNodeConfig {
pbftParams = params
pbftParams = params
{ pbftNumNodes = fromIntegral numCoreNodes
-- Set the signature window to be short for the demo.
, pbftSignatureWindow = 7
}
, pbftNodeId = CoreId nid
, pbftSignKey = SignKeyCardanoDSIGN (snd (lookupKey nid))
, pbftVerKey = VerKeyCardanoDSIGN (fst (lookupKey nid))
, pbftGenVerKey = VerKeyCardanoDSIGN (lookupGenKey nid)
--TODO: also allow not being a BFT leader:
, pbftIsLeader = Just PBftIsLeader {
pbftCoreNodeId = CoreNodeId nid
, pbftSignKey = SignKeyCardanoDSIGN (snd (lookupKey nid))
, pbftVerKey = VerKeyCardanoDSIGN (fst (lookupKey nid))
, pbftGenVerKey = VerKeyCardanoDSIGN (lookupGenKey nid)
}
}
, encNodeConfigExt = ByronConfig {
pbftProtocolMagic = Cardano.Genesis.configProtocolMagic gc
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import Cardano.Crypto.DSIGN
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.Ledger.Mock
import Ouroboros.Consensus.Node.ProtocolInfo.Abstract
import Ouroboros.Consensus.NodeId (CoreNodeId (..), NodeId (..))
import Ouroboros.Consensus.NodeId (CoreNodeId (..))
import Ouroboros.Consensus.Protocol.ExtNodeConfig
import Ouroboros.Consensus.Protocol.PBFT

Expand All @@ -28,11 +28,13 @@ protocolInfoMockPBFT (NumCoreNodes numCoreNodes) (CoreNodeId nid) params =
pInfoConfig = EncNodeConfig {
encNodeConfigP = PBftNodeConfig {
pbftParams = params {pbftNumNodes = fromIntegral numCoreNodes}
, pbftNodeId = CoreId nid
, pbftSignKey = SignKeyMockDSIGN nid
, pbftVerKey = VerKeyMockDSIGN nid
-- For Mock PBFT, we use our key as the genesis key.
, pbftGenVerKey = VerKeyMockDSIGN nid
, pbftIsLeader = Just PBftIsLeader {
pbftCoreNodeId = CoreNodeId nid
, pbftSignKey = SignKeyMockDSIGN nid
, pbftVerKey = VerKeyMockDSIGN nid
-- For Mock PBFT, we use our key as the genesis key.
, pbftGenVerKey = VerKeyMockDSIGN nid
}
}
, encNodeConfigExt = PBftLedgerView $
Bimap.fromList [ (VerKeyMockDSIGN n, VerKeyMockDSIGN n)
Expand Down
47 changes: 29 additions & 18 deletions ouroboros-consensus/src/Ouroboros/Consensus/Protocol/PBFT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
Expand All @@ -17,6 +18,7 @@ module Ouroboros.Consensus.Protocol.PBFT (
, PBftLedgerView(..)
, PBftFields(..)
, PBftParams(..)
, PBftIsLeader(..)
, forgePBftFields
-- * Classes
, PBftCrypto(..)
Expand Down Expand Up @@ -49,7 +51,7 @@ import Cardano.Crypto.DSIGN.Mock (MockDSIGN)
import Ouroboros.Network.Block

import Ouroboros.Consensus.Crypto.DSIGN.Cardano
import Ouroboros.Consensus.NodeId (NodeId (..))
import Ouroboros.Consensus.NodeId (CoreNodeId(..))
import Ouroboros.Consensus.Protocol.Abstract
import Ouroboros.Consensus.Protocol.Signed
import Ouroboros.Consensus.Util.Condense
Expand Down Expand Up @@ -80,11 +82,11 @@ forgePBftFields :: ( MonadRandom m
, PBftCrypto c
, Signable (PBftDSIGN c) toSign
)
=> NodeConfig (PBft c)
=> IsLeader (PBft c)
-> (toSign -> Encoding)
-> toSign
-> m (PBftFields c toSign)
forgePBftFields PBftNodeConfig{..} encodeToSign toSign = do
forgePBftFields PBftIsLeader{..} encodeToSign toSign = do
signature <- signedDSIGN encodeToSign toSign pbftSignKey
return $ PBftFields {
pbftIssuer = pbftVerKey
Expand Down Expand Up @@ -134,16 +136,24 @@ data PBftParams = PBftParams {
, pbftSignatureThreshold :: Double
}

-- | If we are a core node (i.e. a block producing node) we know which core
-- node we are, and we have the operational key pair and delegation certificate.
--
data PBftIsLeader c = PBftIsLeader {
pbftCoreNodeId :: CoreNodeId
, pbftSignKey :: SignKeyDSIGN (PBftDSIGN c)
, pbftVerKey :: VerKeyDSIGN (PBftDSIGN c)
-- Verification key for the genesis stakeholder
-- This is unfortunately needed during the Byron era
, pbftGenVerKey :: VerKeyDSIGN (PBftDSIGN c)
-- TODO: We should have a delegation certificate here.
}

instance (PBftCrypto c, Typeable c) => OuroborosTag (PBft c) where
-- | (Static) node configuration
data NodeConfig (PBft c) = PBftNodeConfig {
pbftParams :: PBftParams
, pbftNodeId :: NodeId
, pbftSignKey :: SignKeyDSIGN (PBftDSIGN c)
, pbftVerKey :: VerKeyDSIGN (PBftDSIGN c)
-- Verification key for the genesis stakeholder
-- This is unfortunately needed during the Byron era
, pbftGenVerKey :: VerKeyDSIGN (PBftDSIGN c)
, pbftIsLeader :: Maybe (PBftIsLeader c)
}

type ValidationErr (PBft c) = PBftValidationErr c
Expand All @@ -156,7 +166,7 @@ instance (PBftCrypto c, Typeable c) => OuroborosTag (PBft c) where
-- - The delegation map.
type LedgerView (PBft c) = PBftLedgerView c

type IsLeader (PBft c) = ()
type IsLeader (PBft c) = PBftIsLeader c

-- | Chain state consists of two things:
-- - a list of the last 'pbftSignatureWindow' signatures.
Expand All @@ -166,14 +176,15 @@ instance (PBftCrypto c, Typeable c) => OuroborosTag (PBft c) where

protocolSecurityParam = pbftSecurityParam . pbftParams

checkIsLeader PBftNodeConfig{..} (SlotNo n) _l _cs = do
return $ case pbftNodeId of
RelayId _ -> Nothing -- relays are never leaders
CoreId i -> if n `mod` pbftNumNodes == fromIntegral i
then Just ()
else Nothing
where
PBftParams{..} = pbftParams
checkIsLeader PBftNodeConfig{pbftIsLeader, pbftParams} (SlotNo n) _l _cs =
case pbftIsLeader of
Nothing -> return Nothing
Just credentials
| n `mod` pbftNumNodes == fromIntegral i -> return (Just credentials)
| otherwise -> return Nothing
where
PBftIsLeader{pbftCoreNodeId = CoreNodeId i} = credentials
PBftParams{pbftNumNodes} = pbftParams

applyChainState cfg@PBftNodeConfig{..} lv@(PBftLedgerView dms) (b :: hdr) chainState = do
-- Check that the issuer signature verifies, and that it's a delegate of a
Expand Down

0 comments on commit 770556b

Please sign in to comment.