Skip to content

Commit 0d65a19

Browse files
neilmayhewjohnalotoski
authored andcommitted
cardano-ledger upgrade: accommodate the new VRFVerKeyHash type
1 parent 66f1812 commit 0d65a19

File tree

9 files changed

+25
-19
lines changed

9 files changed

+25
-19
lines changed
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
### Breaking
2+
3+
- Change the type of the `mkKeyHashVrf` function to use the new `VRFVerKeyHash` ledger type.

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Ledger/Query/Types.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,8 @@ import Cardano.Ledger.Binary (DecCBOR (..), EncCBOR (..),
2020
decodeRecordNamed, encodeListLen)
2121
import Cardano.Ledger.Crypto (Crypto)
2222
import Cardano.Ledger.Keys (Hash)
23+
import qualified Cardano.Ledger.Keys as SL
2324
import qualified Cardano.Ledger.PoolDistr as SL
24-
import qualified Cardano.Ledger.Shelley.API as SL
2525
import Data.Map.Strict (Map)
2626
import qualified Data.Map.Strict as Map
2727
import GHC.Generics (Generic)
@@ -39,7 +39,7 @@ data IndividualPoolStake c = IndividualPoolStake {
3939
fromLedgerIndividualPoolStake :: SL.IndividualPoolStake c -> IndividualPoolStake c
4040
fromLedgerIndividualPoolStake ips = IndividualPoolStake {
4141
individualPoolStake = SL.individualPoolStake ips
42-
, individualPoolStakeVrf = SL.individualPoolStakeVrf ips
42+
, individualPoolStakeVrf = SL.fromVRFVerKeyHash $ SL.individualPoolStakeVrf ips
4343
}
4444

4545
instance Crypto c => EncCBOR (IndividualPoolStake c) where

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -148,7 +148,7 @@ shelleySharedBlockForging hotKey slotToPeriod credentials =
148148

149149
forgingVRFHash :: SL.Hash c (SL.VerKeyVRF c)
150150
forgingVRFHash =
151-
SL.hashVerKeyVRF
151+
VRF.hashVerKeyVRF
152152
. VRF.deriveVerKeyVRF
153153
. praosCanBeLeaderSignKeyVRF
154154
$ canBeLeader

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -178,7 +178,7 @@ instance Key VrfKey where
178178

179179
verificationKeyHash :: VerificationKey VrfKey -> Hash VrfKey
180180
verificationKeyHash (VrfVerificationKey vkey) =
181-
VrfKeyHash (Shelley.hashVerKeyVRF vkey)
181+
VrfKeyHash (Crypto.hashVerKeyVRF vkey)
182182

183183
instance SerialiseAsRawBytes (VerificationKey VrfKey) where
184184
serialiseToRawBytes (VrfVerificationKey vk) =

ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/Headers.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -12,12 +12,11 @@ module Cardano.Tools.Headers (
1212
) where
1313

1414
import Cardano.Crypto.DSIGN (deriveVerKeyDSIGN)
15-
import Cardano.Crypto.VRF
16-
(VRFAlgorithm (deriveVerKeyVRF, hashVerKeyVRF))
15+
import Cardano.Crypto.VRF (VRFAlgorithm (deriveVerKeyVRF))
1716
import Cardano.Ledger.Api (ConwayEra, StandardCrypto)
1817
import Cardano.Ledger.Coin (Coin (..))
1918
import Cardano.Ledger.Compactible (toCompact)
20-
import Cardano.Ledger.Keys (VKey (..), hashKey)
19+
import Cardano.Ledger.Keys (VKey (..), hashKey, hashVerKeyVRF)
2120
import Cardano.Ledger.PoolDistr (IndividualPoolStake (..))
2221
import Cardano.Prelude (ExitCode (..), exitWith, forM_, hPutStrLn,
2322
stderr)

ouroboros-consensus-cardano/src/unstable-shelley-testlib/Test/ThreadNet/Infra/Shelley.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -36,18 +36,18 @@ module Test.ThreadNet.Infra.Shelley (
3636
) where
3737

3838
import Cardano.Crypto.DSIGN (DSIGNAlgorithm (..), seedSizeDSIGN)
39-
import Cardano.Crypto.Hash (Hash, HashAlgorithm)
39+
import Cardano.Crypto.Hash (HashAlgorithm)
4040
import Cardano.Crypto.KES (KESAlgorithm (..))
4141
import Cardano.Crypto.Seed (mkSeedFromBytes)
4242
import qualified Cardano.Crypto.Seed as Cardano.Crypto
43-
import Cardano.Crypto.VRF (SignKeyVRF, VRFAlgorithm, VerKeyVRF,
44-
deriveVerKeyVRF, genKeyVRF, seedSizeVRF)
43+
import Cardano.Crypto.VRF (SignKeyVRF, deriveVerKeyVRF, genKeyVRF,
44+
seedSizeVRF)
4545
import qualified Cardano.Ledger.Allegra.Scripts as SL
4646
import Cardano.Ledger.Alonzo (AlonzoEra)
4747
import Cardano.Ledger.BaseTypes (boundRational)
4848
import Cardano.Ledger.Crypto (Crypto, DSIGN, HASH, KES, VRF)
4949
import Cardano.Ledger.Hashes (EraIndependentTxBody)
50-
import qualified Cardano.Ledger.Keys
50+
import qualified Cardano.Ledger.Keys as LK
5151
import qualified Cardano.Ledger.Mary.Core as SL
5252
import Cardano.Ledger.SafeHash (HashAnnotated (..), SafeHash,
5353
hashAnnotated)
@@ -182,7 +182,7 @@ genCoreNode startKESPeriod = do
182182
vrfKey <- genKeyVRF <$> genSeed (seedSizeVRF (Proxy @(VRF c)))
183183
kesKey <- genKeyKES <$> genSeed (seedSizeKES (Proxy @(KES c)))
184184
let kesPub = deriveVerKeyKES kesKey
185-
sigma = Cardano.Ledger.Keys.signedDSIGN
185+
sigma = LK.signedDSIGN
186186
@c
187187
delKey
188188
(SL.OCertSignable kesPub certificateIssueNumber startKESPeriod)
@@ -522,9 +522,9 @@ mkVerKey = SL.VKey . deriveVerKeyDSIGN
522522
mkKeyPair :: Crypto c => SL.SignKeyDSIGN c -> TL.KeyPair r c
523523
mkKeyPair sk = TL.KeyPair { vKey = mkVerKey sk, sKey = sk }
524524

525-
mkKeyHashVrf :: (HashAlgorithm h, VRFAlgorithm vrf)
526-
=> SignKeyVRF vrf
527-
-> Hash h (VerKeyVRF vrf)
525+
mkKeyHashVrf :: Crypto c
526+
=> SignKeyVRF (VRF c)
527+
-> LK.VRFVerKeyHash (r :: LK.KeyRoleVRF) c
528528
mkKeyHashVrf = SL.hashVerKeyVRF . deriveVerKeyVRF
529529

530530
networkId :: SL.Network
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
### Patch
2+
3+
* Use the `VRFVerKeyHash` type from `cardano-ledger-core-1.16`

ouroboros-consensus-protocol/src/ouroboros-consensus-protocol/Ouroboros/Consensus/Protocol/Praos.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,6 @@ module Ouroboros.Consensus.Protocol.Praos (
3737
import Cardano.Binary (FromCBOR (..), ToCBOR (..), enforceSize)
3838
import qualified Cardano.Crypto.DSIGN as DSIGN
3939
import qualified Cardano.Crypto.KES as KES
40-
import Cardano.Crypto.VRF (hashVerKeyVRF)
4140
import qualified Cardano.Crypto.VRF as VRF
4241
import Cardano.Ledger.BaseTypes (ActiveSlotCoeff, Nonce, (⭒))
4342
import qualified Cardano.Ledger.BaseTypes as SL
@@ -548,8 +547,10 @@ doValidateVRFSignature eta0 pd f b = do
548547
case Map.lookup hk pd of
549548
Nothing -> throwError $ VRFKeyUnknown hk
550549
Just (IndividualPoolStake sigma _totalPoolStake vrfHK) -> do
551-
vrfHK == hashVerKeyVRF vrfK
552-
?! VRFKeyWrongVRFKey hk vrfHK (hashVerKeyVRF vrfK)
550+
let vrfHKStake = SL.fromVRFVerKeyHash vrfHK
551+
vrfHKBlock = VRF.hashVerKeyVRF vrfK
552+
vrfHKStake == vrfHKBlock
553+
?! VRFKeyWrongVRFKey hk vrfHKStake vrfHKBlock
553554
VRF.verifyCertified
554555
()
555556
vrfK

ouroboros-consensus-protocol/src/ouroboros-consensus-protocol/Ouroboros/Consensus/Protocol/TPraos.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -324,7 +324,7 @@ instance SL.PraosCrypto c => ConsensusProtocol (TPraos c) where
324324
-- the overlay schedule, so we could set it to whatever we
325325
-- want. We evaluate it as normal for simplicity's sake.
326326
, tpraosIsLeaderProof = coerce y
327-
, tpraosIsLeaderGenVRFHash = Just genDlgVRFHash
327+
, tpraosIsLeaderGenVRFHash = Just $ SL.fromVRFVerKeyHash genDlgVRFHash
328328
}
329329
| otherwise
330330
-> Nothing

0 commit comments

Comments
 (0)