Skip to content

Commit

Permalink
cardano-ledger upgrade: accommodate the new VRFVerKeyHash type
Browse files Browse the repository at this point in the history
  • Loading branch information
neilmayhew committed Dec 18, 2024
1 parent 24b45c4 commit e562637
Show file tree
Hide file tree
Showing 9 changed files with 25 additions and 19 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
### Breaking

- Change the type of the `mkKeyHashVrf` function to use the new `VRFVerKeyHash` ledger type.
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,8 @@ import Cardano.Ledger.Binary (DecCBOR (..), EncCBOR (..),
decodeRecordNamed, encodeListLen)
import Cardano.Ledger.Crypto (Crypto)
import Cardano.Ledger.Keys (Hash)
import qualified Cardano.Ledger.Keys as SL
import qualified Cardano.Ledger.PoolDistr as SL
import qualified Cardano.Ledger.Shelley.API as SL
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import GHC.Generics (Generic)
Expand All @@ -39,7 +39,7 @@ data IndividualPoolStake c = IndividualPoolStake {
fromLedgerIndividualPoolStake :: SL.IndividualPoolStake c -> IndividualPoolStake c
fromLedgerIndividualPoolStake ips = IndividualPoolStake {
individualPoolStake = SL.individualPoolStake ips
, individualPoolStakeVrf = SL.individualPoolStakeVrf ips
, individualPoolStakeVrf = SL.fromVRFVerKeyHash $ SL.individualPoolStakeVrf ips
}

instance Crypto c => EncCBOR (IndividualPoolStake c) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@ shelleySharedBlockForging hotKey slotToPeriod credentials =

forgingVRFHash :: SL.Hash c (SL.VerKeyVRF c)
forgingVRFHash =
SL.hashVerKeyVRF
VRF.hashVerKeyVRF
. VRF.deriveVerKeyVRF
. praosCanBeLeaderSignKeyVRF
$ canBeLeader
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -178,7 +178,7 @@ instance Key VrfKey where

verificationKeyHash :: VerificationKey VrfKey -> Hash VrfKey
verificationKeyHash (VrfVerificationKey vkey) =
VrfKeyHash (Shelley.hashVerKeyVRF vkey)
VrfKeyHash (Crypto.hashVerKeyVRF vkey)

instance SerialiseAsRawBytes (VerificationKey VrfKey) where
serialiseToRawBytes (VrfVerificationKey vk) =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,12 +12,11 @@ module Cardano.Tools.Headers (
) where

import Cardano.Crypto.DSIGN (deriveVerKeyDSIGN)
import Cardano.Crypto.VRF
(VRFAlgorithm (deriveVerKeyVRF, hashVerKeyVRF))
import Cardano.Crypto.VRF (VRFAlgorithm (deriveVerKeyVRF))
import Cardano.Ledger.Api (ConwayEra, StandardCrypto)
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Compactible (toCompact)
import Cardano.Ledger.Keys (VKey (..), hashKey)
import Cardano.Ledger.Keys (VKey (..), hashKey, hashVerKeyVRF)
import Cardano.Ledger.PoolDistr (IndividualPoolStake (..))
import Cardano.Prelude (ExitCode (..), exitWith, forM_, hPutStrLn,
stderr)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -36,18 +36,18 @@ module Test.ThreadNet.Infra.Shelley (
) where

import Cardano.Crypto.DSIGN (DSIGNAlgorithm (..), seedSizeDSIGN)
import Cardano.Crypto.Hash (Hash, HashAlgorithm)
import Cardano.Crypto.Hash (HashAlgorithm)
import Cardano.Crypto.KES (KESAlgorithm (..))
import Cardano.Crypto.Seed (mkSeedFromBytes)
import qualified Cardano.Crypto.Seed as Cardano.Crypto
import Cardano.Crypto.VRF (SignKeyVRF, VRFAlgorithm, VerKeyVRF,
deriveVerKeyVRF, genKeyVRF, seedSizeVRF)
import Cardano.Crypto.VRF (SignKeyVRF, deriveVerKeyVRF, genKeyVRF,
seedSizeVRF)
import qualified Cardano.Ledger.Allegra.Scripts as SL
import Cardano.Ledger.Alonzo (AlonzoEra)
import Cardano.Ledger.BaseTypes (boundRational)
import Cardano.Ledger.Crypto (Crypto, DSIGN, HASH, KES, VRF)
import Cardano.Ledger.Hashes (EraIndependentTxBody)
import qualified Cardano.Ledger.Keys
import qualified Cardano.Ledger.Keys as LK
import qualified Cardano.Ledger.Mary.Core as SL
import Cardano.Ledger.SafeHash (HashAnnotated (..), SafeHash,
hashAnnotated)
Expand Down Expand Up @@ -182,7 +182,7 @@ genCoreNode startKESPeriod = do
vrfKey <- genKeyVRF <$> genSeed (seedSizeVRF (Proxy @(VRF c)))
kesKey <- genKeyKES <$> genSeed (seedSizeKES (Proxy @(KES c)))
let kesPub = deriveVerKeyKES kesKey
sigma = Cardano.Ledger.Keys.signedDSIGN
sigma = LK.signedDSIGN
@c
delKey
(SL.OCertSignable kesPub certificateIssueNumber startKESPeriod)
Expand Down Expand Up @@ -522,9 +522,9 @@ mkVerKey = SL.VKey . deriveVerKeyDSIGN
mkKeyPair :: Crypto c => SL.SignKeyDSIGN c -> TL.KeyPair r c
mkKeyPair sk = TL.KeyPair { vKey = mkVerKey sk, sKey = sk }

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

networkId :: SL.Network
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
### Patch

* Use the `VRFVerKeyHash` type from `cardano-ledger-core-1.16`
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,6 @@ module Ouroboros.Consensus.Protocol.Praos (
import Cardano.Binary (FromCBOR (..), ToCBOR (..), enforceSize)
import qualified Cardano.Crypto.DSIGN as DSIGN
import qualified Cardano.Crypto.KES as KES
import Cardano.Crypto.VRF (hashVerKeyVRF)
import qualified Cardano.Crypto.VRF as VRF
import Cardano.Ledger.BaseTypes (ActiveSlotCoeff, Nonce, (⭒))
import qualified Cardano.Ledger.BaseTypes as SL
Expand Down Expand Up @@ -548,8 +547,10 @@ doValidateVRFSignature eta0 pd f b = do
case Map.lookup hk pd of
Nothing -> throwError $ VRFKeyUnknown hk
Just (IndividualPoolStake sigma _totalPoolStake vrfHK) -> do
vrfHK == hashVerKeyVRF vrfK
?! VRFKeyWrongVRFKey hk vrfHK (hashVerKeyVRF vrfK)
let vrfHKStake = SL.fromVRFVerKeyHash vrfHK
vrfHKBlock = VRF.hashVerKeyVRF vrfK
vrfHKStake == vrfHKBlock
?! VRFKeyWrongVRFKey hk vrfHKStake vrfHKBlock
VRF.verifyCertified
()
vrfK
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -324,7 +324,7 @@ instance SL.PraosCrypto c => ConsensusProtocol (TPraos c) where
-- the overlay schedule, so we could set it to whatever we
-- want. We evaluate it as normal for simplicity's sake.
, tpraosIsLeaderProof = coerce y
, tpraosIsLeaderGenVRFHash = Just genDlgVRFHash
, tpraosIsLeaderGenVRFHash = Just $ SL.fromVRFVerKeyHash genDlgVRFHash
}
| otherwise
-> Nothing
Expand Down

0 comments on commit e562637

Please sign in to comment.