Skip to content

Commit 3c994f0

Browse files
committed
Use mlocked KES
1 parent c844bc2 commit 3c994f0

File tree

44 files changed

+507
-226
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

44 files changed

+507
-226
lines changed
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
### Breaking
2+
3+
- Use new mlocked KES API for all internal KES sign key handling.
4+
- Add finalizers to all block forgings (required by `ouroboros-consensus`).
5+
- Change `HotKey` to manage not only KES sign keys, but also the corresponding
6+
OpCerts. This is in preparation for KES agent connectivity: with the new
7+
design, the KES agent will provide both KES sign keys and matching OpCerts
8+
together, and we need to be able to dynamically replace them both together.
9+
- Add finalizer to `HotKey`. This takes care of securely forgetting any KES
10+
keys the HotKey may still hold, and will be called automatically when the
11+
owning block forging terminates.
12+
- Change `ShelleyLeaderCredentials` to not contain the KES sign key itself
13+
anymore. Instead, the `CanBeLeader` data structure now contains a
14+
`praosCanBeLeaderCredentialsSource` field, which specifies how to obtain the
15+
actual credentials (OpCert and KES SignKey).
16+
- The `KesKey` data type in `unstable-cardano-tools` has been renamed to
17+
`UnsoundPureKesKey`, to reflect the fact that it uses the old, unsound KES
18+
API (which does not use mlocking or secure forgetting).

ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -301,7 +301,7 @@ library unstable-shelley-testlib
301301
cardano-ledger-alonzo,
302302
cardano-ledger-alonzo-test,
303303
cardano-ledger-babbage-test,
304-
cardano-ledger-conway-test >=1.2.1,
304+
cardano-ledger-conway-test >=1.3.0,
305305
cardano-ledger-core:{cardano-ledger-core, testlib},
306306
cardano-ledger-mary,
307307
cardano-ledger-shelley:{cardano-ledger-shelley, testlib},

ouroboros-consensus-cardano/src/byron/Ouroboros/Consensus/Byron/Node.hs

+1
Original file line numberDiff line numberDiff line change
@@ -140,6 +140,7 @@ byronBlockForging creds = BlockForging {
140140
slot
141141
tickedPBftState
142142
, forgeBlock = \cfg -> return ....: forgeByronBlock cfg
143+
, finalize = pure ()
143144
}
144145
where
145146
canBeLeader = mkPBftCanBeLeader creds

ouroboros-consensus-cardano/src/ouroboros-consensus-cardano/Ouroboros/Consensus/Cardano/Node.hs

+25-22
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,9 @@ module Ouroboros.Consensus.Cardano.Node (
3838
, CardanoHardForkTriggers (.., CardanoHardForkTriggers', triggerHardForkShelley, triggerHardForkAllegra, triggerHardForkMary, triggerHardForkAlonzo, triggerHardForkBabbage, triggerHardForkConway)
3939
, CardanoProtocolParams (..)
4040
, MaxMajorProtVer (..)
41+
, ProtocolParamsByron
42+
, ProtocolParamsShelleyBased
43+
, CheckpointsMap
4144
, TriggerHardFork (..)
4245
, protocolClientInfoCardano
4346
, protocolInfoCardano
@@ -92,10 +95,8 @@ import Ouroboros.Consensus.Ledger.Extended
9295
import Ouroboros.Consensus.Node.NetworkProtocolVersion
9396
import Ouroboros.Consensus.Node.ProtocolInfo
9497
import Ouroboros.Consensus.Node.Run
95-
import qualified Ouroboros.Consensus.Protocol.Ledger.HotKey as HotKey
9698
import Ouroboros.Consensus.Protocol.Praos (Praos, PraosParams (..))
97-
import Ouroboros.Consensus.Protocol.Praos.Common
98-
(praosCanBeLeaderOpCert)
99+
import Ouroboros.Consensus.Protocol.Praos.Common (PraosCanBeLeader (..), instantiatePraosCredentials)
99100
import Ouroboros.Consensus.Protocol.TPraos (TPraos, TPraosParams (..))
100101
import qualified Ouroboros.Consensus.Protocol.TPraos as Shelley
101102
import Ouroboros.Consensus.Shelley.HFEras ()
@@ -104,9 +105,9 @@ import qualified Ouroboros.Consensus.Shelley.Ledger as Shelley
104105
import Ouroboros.Consensus.Shelley.Ledger.Block (IsShelleyBlock,
105106
ShelleyBlockLedgerEra)
106107
import Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion
108+
import qualified Ouroboros.Consensus.Protocol.Ledger.HotKey as HotKey
107109
import Ouroboros.Consensus.Shelley.Node
108-
import Ouroboros.Consensus.Shelley.Node.Common (ShelleyEraWithCrypto,
109-
shelleyBlockIssuerVKey)
110+
import Ouroboros.Consensus.Shelley.Node.Common (ShelleyEraWithCrypto, shelleyBlockIssuerVKey)
110111
import qualified Ouroboros.Consensus.Shelley.Node.Praos as Praos
111112
import qualified Ouroboros.Consensus.Shelley.Node.TPraos as TPraos
112113
import Ouroboros.Consensus.Storage.Serialisation
@@ -475,12 +476,12 @@ protocolInfoCardano paramsCardano
475476
, length credssShelleyBased > 1
476477
= error "Multiple Shelley-based credentials not allowed for mainnet"
477478
| otherwise
478-
= assertWithMsg (validateGenesis genesisShelley)
479+
= assertWithMsg (validateGenesis genesisShelley) $
479480
( ProtocolInfo {
480481
pInfoConfig = cfg
481482
, pInfoInitLedger = initExtLedgerStateCardano
482483
}
483-
, blockForging
484+
, mkBlockForgings
484485
)
485486
where
486487
CardanoProtocolParams {
@@ -827,8 +828,8 @@ protocolInfoCardano paramsCardano
827828
-- credentials. If there are multiple Shelley credentials, we merge the
828829
-- Byron credentials with the first Shelley one but still have separate
829830
-- threads for the remaining Shelley ones.
830-
blockForging :: m [BlockForging m (CardanoBlock c)]
831-
blockForging = do
831+
mkBlockForgings :: m ([BlockForging m (CardanoBlock c)])
832+
mkBlockForgings = do
832833
shelleyBased <- traverse blockForgingShelleyBased credssShelleyBased
833834
let blockForgings :: [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
834835
blockForgings = case (mBlockForgingByron, shelleyBased) of
@@ -854,24 +855,26 @@ protocolInfoCardano paramsCardano
854855
ShelleyLeaderCredentials c
855856
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c))
856857
blockForgingShelleyBased credentials = do
857-
let ShelleyLeaderCredentials
858-
{ shelleyLeaderCredentialsInitSignKey = initSignKey
859-
, shelleyLeaderCredentialsCanBeLeader = canBeLeader
860-
} = credentials
861-
862-
hotKey <- do
863-
let maxKESEvo :: Word64
864-
maxKESEvo = assert (tpraosMaxKESEvo == praosMaxKESEvo) praosMaxKESEvo
865-
866-
startPeriod :: Absolute.KESPeriod
867-
startPeriod = Absolute.ocertKESPeriod $ praosCanBeLeaderOpCert canBeLeader
868-
869-
HotKey.mkHotKey @m @c initSignKey startPeriod maxKESEvo
858+
let canBeLeader = shelleyLeaderCredentialsCanBeLeader credentials
870859

871860
let slotToPeriod :: SlotNo -> Absolute.KESPeriod
872861
slotToPeriod (SlotNo slot) = assert (tpraosSlotsPerKESPeriod == praosSlotsPerKESPeriod) $
873862
Absolute.KESPeriod $ fromIntegral $ slot `div` praosSlotsPerKESPeriod
874863

864+
(ocert, sk) <- instantiatePraosCredentials (praosCanBeLeaderCredentialsSource canBeLeader)
865+
866+
let startPeriod :: Absolute.KESPeriod
867+
startPeriod = Absolute.ocertKESPeriod ocert
868+
869+
let maxKESEvo :: Word64
870+
maxKESEvo = assert (tpraosMaxKESEvo == praosMaxKESEvo) praosMaxKESEvo
871+
872+
hotKey :: HotKey.HotKey c m <- HotKey.mkHotKey
873+
ocert
874+
sk
875+
startPeriod
876+
maxKESEvo
877+
875878
let tpraos :: forall era.
876879
ShelleyEraWithCrypto c (TPraos c) era
877880
=> BlockForging m (ShelleyBlock (TPraos c) era)

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Node.hs

+1
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ import Ouroboros.Consensus.Shelley.Ledger
4444
import Ouroboros.Consensus.Shelley.Ledger.Inspect ()
4545
import Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion ()
4646
import Ouroboros.Consensus.Shelley.Node.DiffusionPipelining ()
47+
import Ouroboros.Consensus.Shelley.Node.Common
4748
import Ouroboros.Consensus.Shelley.Node.Serialisation ()
4849
import Ouroboros.Consensus.Shelley.Node.TPraos
4950
import Ouroboros.Consensus.Shelley.Protocol.Abstract (pHeaderIssuer)

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Node/Common.hs

+1-8
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,6 @@ module Ouroboros.Consensus.Shelley.Node.Common (
2020
, shelleyBlockIssuerVKey
2121
) where
2222

23-
import Cardano.Crypto.KES (UnsoundPureSignKeyKES)
24-
import Cardano.Ledger.Crypto
2523
import qualified Cardano.Ledger.Keys as SL
2624
import qualified Cardano.Ledger.Shelley.API as SL
2725
import Cardano.Ledger.Slot
@@ -50,12 +48,7 @@ import Ouroboros.Consensus.Storage.ImmutableDB
5048
-------------------------------------------------------------------------------}
5149

5250
data ShelleyLeaderCredentials c = ShelleyLeaderCredentials
53-
{ -- | The unevolved signing KES key (at evolution 0).
54-
--
55-
-- Note that this is not inside 'ShelleyCanBeLeader' since it gets evolved
56-
-- automatically, whereas 'ShelleyCanBeLeader' does not change.
57-
shelleyLeaderCredentialsInitSignKey :: UnsoundPureSignKeyKES (KES c),
58-
shelleyLeaderCredentialsCanBeLeader :: PraosCanBeLeader c,
51+
{ shelleyLeaderCredentialsCanBeLeader :: PraosCanBeLeader c,
5952
-- | Identifier for this set of credentials.
6053
--
6154
-- Useful when the node is running with multiple sets of credentials.

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Node/Praos.hs

+8-17
Original file line numberDiff line numberDiff line change
@@ -28,8 +28,6 @@ import qualified Ouroboros.Consensus.Ledger.SupportsMempool as Mempool
2828
import qualified Ouroboros.Consensus.Protocol.Ledger.HotKey as HotKey
2929
import Ouroboros.Consensus.Protocol.Praos (Praos, PraosParams (..),
3030
praosCheckCanForge)
31-
import Ouroboros.Consensus.Protocol.Praos.Common
32-
(PraosCanBeLeader (praosCanBeLeaderOpCert))
3331
import Ouroboros.Consensus.Shelley.Eras (EraCrypto)
3432
import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock,
3533
ShelleyCompatible, forgeShelleyBlock)
@@ -51,21 +49,13 @@ praosBlockForging ::
5149
, IOLike m
5250
)
5351
=> PraosParams
52+
-> HotKey.HotKey c m
5453
-> ShelleyLeaderCredentials (EraCrypto era)
55-
-> m (BlockForging m (ShelleyBlock (Praos c) era))
56-
praosBlockForging praosParams credentials = do
57-
hotKey <- HotKey.mkHotKey @m @c initSignKey startPeriod praosMaxKESEvo
58-
pure $ praosSharedBlockForging hotKey slotToPeriod credentials
54+
-> BlockForging m (ShelleyBlock (Praos c) era)
55+
praosBlockForging praosParams hotKey credentials =
56+
praosSharedBlockForging hotKey slotToPeriod credentials
5957
where
60-
PraosParams {praosMaxKESEvo, praosSlotsPerKESPeriod} = praosParams
61-
62-
ShelleyLeaderCredentials {
63-
shelleyLeaderCredentialsInitSignKey = initSignKey
64-
, shelleyLeaderCredentialsCanBeLeader = canBeLeader
65-
} = credentials
66-
67-
startPeriod :: Absolute.KESPeriod
68-
startPeriod = SL.ocertKESPeriod $ praosCanBeLeaderOpCert canBeLeader
58+
PraosParams {praosSlotsPerKESPeriod} = praosParams
6959

7060
slotToPeriod :: SlotNo -> Absolute.KESPeriod
7161
slotToPeriod (SlotNo slot) =
@@ -90,7 +80,7 @@ praosSharedBlockForging
9080
ShelleyLeaderCredentials {
9181
shelleyLeaderCredentialsCanBeLeader = canBeLeader
9282
, shelleyLeaderCredentialsLabel = label
93-
} = do
83+
} =
9484
BlockForging
9585
{ forgeLabel = label <> "_" <> T.pack (L.eraName @era),
9686
canBeLeader = canBeLeader,
@@ -105,5 +95,6 @@ praosSharedBlockForging
10595
forgeShelleyBlock
10696
hotKey
10797
canBeLeader
108-
cfg
98+
cfg,
99+
finalize = HotKey.finalize hotKey
109100
}

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Node/TPraos.hs

+26-18
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ import Ouroboros.Consensus.Ledger.Extended
5555
import Ouroboros.Consensus.Ledger.SupportsMempool (TxLimits)
5656
import Ouroboros.Consensus.Node.ProtocolInfo
5757
import Ouroboros.Consensus.Protocol.Abstract
58-
import Ouroboros.Consensus.Protocol.Ledger.HotKey (HotKey)
58+
import Ouroboros.Consensus.Protocol.Ledger.HotKey (HotKey, mkHotKey)
5959
import qualified Ouroboros.Consensus.Protocol.Ledger.HotKey as HotKey
6060
import Ouroboros.Consensus.Protocol.Praos.Common
6161
import Ouroboros.Consensus.Protocol.TPraos
@@ -65,7 +65,8 @@ import Ouroboros.Consensus.Shelley.Ledger.Inspect ()
6565
import Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion ()
6666
import Ouroboros.Consensus.Shelley.Node.Common
6767
(ProtocolParamsShelleyBased (..), ShelleyEraWithCrypto,
68-
ShelleyLeaderCredentials (..), shelleyBlockIssuerVKey)
68+
ShelleyLeaderCredentials (..),
69+
shelleyBlockIssuerVKey)
6970
import Ouroboros.Consensus.Shelley.Node.Serialisation ()
7071
import Ouroboros.Consensus.Shelley.Protocol.TPraos ()
7172
import Ouroboros.Consensus.Util.Assert
@@ -88,21 +89,13 @@ shelleyBlockForging ::
8889
, IOLike m
8990
)
9091
=> TPraosParams
92+
-> HotKey c m
9193
-> ShelleyLeaderCredentials (EraCrypto era)
92-
-> m (BlockForging m (ShelleyBlock (TPraos c) era))
93-
shelleyBlockForging tpraosParams credentials = do
94-
hotKey <- HotKey.mkHotKey @m @c initSignKey startPeriod tpraosMaxKESEvo
95-
pure $ shelleySharedBlockForging hotKey slotToPeriod credentials
94+
-> BlockForging m (ShelleyBlock (TPraos c) era)
95+
shelleyBlockForging tpraosParams hotKey credentials = do
96+
shelleySharedBlockForging hotKey slotToPeriod credentials
9697
where
97-
TPraosParams {tpraosMaxKESEvo, tpraosSlotsPerKESPeriod} = tpraosParams
98-
99-
ShelleyLeaderCredentials {
100-
shelleyLeaderCredentialsInitSignKey = initSignKey
101-
, shelleyLeaderCredentialsCanBeLeader = canBeLeader
102-
} = credentials
103-
104-
startPeriod :: Absolute.KESPeriod
105-
startPeriod = SL.ocertKESPeriod $ praosCanBeLeaderOpCert canBeLeader
98+
TPraosParams {tpraosSlotsPerKESPeriod} = tpraosParams
10699

107100
slotToPeriod :: SlotNo -> Absolute.KESPeriod
108101
slotToPeriod (SlotNo slot) =
@@ -139,6 +132,7 @@ shelleySharedBlockForging hotKey slotToPeriod credentials =
139132
hotKey
140133
canBeLeader
141134
cfg
135+
, finalize = HotKey.finalize hotKey
142136
}
143137
where
144138
ShelleyLeaderCredentials {
@@ -216,11 +210,25 @@ protocolInfoTPraosShelleyBased ProtocolParamsShelleyBased {
216210
pInfoConfig = topLevelConfig
217211
, pInfoInitLedger = initExtLedgerState
218212
}
219-
, traverse
220-
(shelleyBlockForging tpraosParams)
221-
credentialss
213+
, traverse mkBlockForging credentialss
222214
)
223215
where
216+
mkBlockForging :: ShelleyLeaderCredentials c -> m (BlockForging m (ShelleyBlock (TPraos c) era))
217+
mkBlockForging credentials = do
218+
let canBeLeader = shelleyLeaderCredentialsCanBeLeader credentials
219+
(ocert, sk) <- instantiatePraosCredentials (praosCanBeLeaderCredentialsSource canBeLeader)
220+
221+
let startPeriod :: Absolute.KESPeriod
222+
startPeriod = SL.ocertKESPeriod ocert
223+
224+
hotKey :: HotKey c m <- mkHotKey
225+
ocert
226+
sk
227+
startPeriod
228+
(tpraosMaxKESEvo tpraosParams)
229+
230+
return $ shelleyBlockForging tpraosParams hotKey credentials
231+
224232
genesis :: SL.ShelleyGenesis c
225233
genesis = transitionCfg ^. L.tcShelleyGenesisL
226234

ouroboros-consensus-cardano/src/unstable-byron-testlib/Ouroboros/Consensus/ByronDual/Node.hs

+1
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,7 @@ dualByronBlockForging creds = BlockForging {
6666
fmap castForgeStateUpdateInfo .: updateForgeState (dualTopLevelConfigMain cfg)
6767
, checkCanForge = checkCanForge . dualTopLevelConfigMain
6868
, forgeBlock = return .....: forgeDualByronBlock
69+
, finalize = return ()
6970
}
7071
where
7172
BlockForging {..} = byronBlockForging creds

ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Api/Key.hs

+11-11
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@ module Cardano.Api.Key (
99
, CastSigningKeyRole (..)
1010
, CastVerificationKeyRole (..)
1111
, Key (..)
12-
, generateSigningKey
1312
) where
1413

1514
import Cardano.Api.Any
@@ -51,16 +50,17 @@ class (Eq (VerificationKey keyrole),
5150
verificationKeyHash :: VerificationKey keyrole -> Hash keyrole
5251

5352

54-
-- TODO: We should move this into the Key type class, with the existing impl as the default impl.
55-
-- For KES we can then override it to keep the seed and key in mlocked memory at all times.
56-
-- | Generate a 'SigningKey' using a seed from operating system entropy.
57-
--
58-
generateSigningKey :: Key keyrole => AsType keyrole -> IO (SigningKey keyrole)
59-
generateSigningKey keytype = do
60-
seed <- Crypto.readSeedFromSystemEntropy seedSize
61-
return $! deterministicSigningKey keytype seed
62-
where
63-
seedSize = deterministicSigningKeySeedSize keytype
53+
-- | Generate a 'SigningKey' using a seed from operating system entropy.
54+
generateSigningKey :: AsType keyrole -> IO (SigningKey keyrole)
55+
generateSigningKey keytype = do
56+
--
57+
-- For KES we can override this to keep the seed and key in mlocked memory
58+
-- at all times.
59+
--
60+
seed <- Crypto.readSeedFromSystemEntropy seedSize
61+
return $! deterministicSigningKey keytype seed
62+
where
63+
seedSize = deterministicSigningKeySeedSize keytype
6464

6565

6666
instance HasTypeProxy a => HasTypeProxy (VerificationKey a) where

0 commit comments

Comments
 (0)