Skip to content

Commit

Permalink
Upgrade cardano-base dependency
Browse files Browse the repository at this point in the history
  • Loading branch information
tdammers authored and lehins committed Oct 31, 2024
1 parent 5faaf09 commit 3f163c7
Show file tree
Hide file tree
Showing 15 changed files with 89 additions and 278 deletions.
22 changes: 21 additions & 1 deletion cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,18 @@ source-repository-package
-- points to a commit in `MAlonzo-code` if you were fiddling with the SRP
-- as part of your PR.

source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-base
tag: 5d87496a4748726d8c3fe122871c072a70e14c60
--sha256: sha256-oW+msm9TfnUFpFzKdPN7oqjeJXbaqhrpsSk94peyH28=
subdir:
-- cardano-binary
cardano-crypto-class
cardano-crypto-tests
cardano-crypto-praos
cardano-mempool

index-state:
-- Bump this if you need newer packages from Hackage
, hackage.haskell.org 2024-10-30T00:00:00Z
Expand Down Expand Up @@ -88,7 +100,7 @@ packages:
libs/cardano-ledger-conformance
libs/cardano-ledger-test
libs/plutus-preprocessor
libs/ledger-state
-- libs/ledger-state
libs/constrained-generators
libs/cardano-ledger-repl-environment

Expand All @@ -110,6 +122,14 @@ package cardano-ledger-mary
package cardano-ledger-conway
flags: +asserts

allow-newer:
-- Plutus-core has an upper bound on cardano-crypto-class that would prevent
-- us from depending on the updated KES API; however, these changes to
-- cardano-crypto-class are inconsequential for plutus-core, so until the
-- dependency from plutus-core to cardano-crypto-class is updated, we will
-- have to add this exemption.
plutus-core:cardano-crypto-class

-- Always write GHC env files, because they are needed for repl and by the doctests.
write-ghc-environment-files: always

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Test.Cardano.Ledger.Shelley.Examples.Consensus where

import Cardano.Crypto.DSIGN as DSIGN
import Cardano.Crypto.Hash as Hash
import Cardano.Crypto.KES as KES
import Cardano.Crypto.Seed as Seed
import qualified Cardano.Crypto.VRF as VRF
import Cardano.Ledger.AuxiliaryData
Expand Down Expand Up @@ -181,7 +182,7 @@ exampleShelleyLedgerBlock tx = Block blockHeader blockBody
KeyPair vKeyCold _ = aikCold keys

blockHeader :: BHeader (EraCrypto era)
blockHeader = BHeader blockHeaderBody (signedKES () 0 blockHeaderBody hotKey)
blockHeader = BHeader blockHeaderBody (unsoundPureSignedKES () 0 blockHeaderBody hotKey)

blockHeaderBody :: BHBody (EraCrypto era)
blockHeaderBody =
Expand Down
11 changes: 6 additions & 5 deletions eras/shelley/test-suite/src/Test/Cardano/Ledger/Shelley/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,9 +48,9 @@ import Cardano.Crypto.Hash (
hashToBytes,
)
import Cardano.Crypto.KES (
KESAlgorithm (..),
deriveVerKeyKES,
genKeyKES,
UnsoundPureKESAlgorithm (..),
unsoundPureDeriveVerKeyKES,
unsoundPureGenKeyKES,
)
import Cardano.Crypto.Seed (Seed, mkSeedFromBytes)
import Cardano.Crypto.VRF (
Expand Down Expand Up @@ -210,10 +210,11 @@ mkCertifiedVRF a sk =
-- | For testing purposes, generate a deterministic KES key pair given a seed.
mkKESKeyPair :: Crypto c => RawSeed -> KESKeyPair c
mkKESKeyPair seed =
let sk = genKeyKES $ mkSeedFromWords seed
let sk = unsoundPureGenKeyKES (mkSeedFromWords seed)
vk = unsoundPureDeriveVerKeyKES sk
in KESKeyPair
{ kesSignKey = sk
, kesVerKey = deriveVerKeyKES sk
, kesVerKey = vk
}

runShelleyBase :: ShelleyBase a -> a
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
module Test.Cardano.Ledger.Shelley.Serialisation.Golden.Encoding (tests) where

import qualified Cardano.Crypto.Hash as Monomorphic
import Cardano.Crypto.KES (SignedKES)
import Cardano.Crypto.KES (SignedKES, unsoundPureSignedKES)
import Cardano.Crypto.VRF (CertifiedVRF)
import Cardano.Ledger.Address (Addr (..), RewardAccount (..))
import Cardano.Ledger.BaseTypes (
Expand Down Expand Up @@ -76,7 +76,6 @@ import Cardano.Ledger.Keys (
hashKey,
hashVerKeyVRF,
signedDSIGN,
signedKES,
)
import Cardano.Ledger.PoolParams (
PoolMetadata (..),
Expand Down Expand Up @@ -382,7 +381,7 @@ testBHBSigTokens ::
testBHBSigTokens = e
where
s =
signedKES @(KES (EraCrypto era))
unsoundPureSignedKES @(KES (EraCrypto era))
()
0
(testBHB @era)
Expand Down Expand Up @@ -990,7 +989,7 @@ tests =
)
, -- checkEncodingCBOR "block_header"
let sig :: (SignedKES (KES C_Crypto) (BHBody C_Crypto))
sig = signedKES () 0 (testBHB @C) (kesSignKey $ testKESKeys @C_Crypto)
sig = unsoundPureSignedKES () 0 (testBHB @C) (kesSignKey $ testKESKeys @C_Crypto)
in checkEncodingCBORAnnotated
shelleyProtVer
"block_header"
Expand All @@ -1001,7 +1000,7 @@ tests =
)
, -- checkEncodingCBOR "empty_block"
let sig :: (SignedKES (KES C_Crypto) (BHBody C_Crypto))
sig = signedKES () 0 (testBHB @C) (kesSignKey $ testKESKeys @C_Crypto)
sig = unsoundPureSignedKES () 0 (testBHB @C) (kesSignKey $ testKESKeys @C_Crypto)
bh = BHeader (testBHB @C) sig
txns = ShelleyTxSeq StrictSeq.Empty
in checkEncodingCBORAnnotated
Expand All @@ -1014,7 +1013,7 @@ tests =
)
, -- checkEncodingCBOR "rich_block"
let sig :: SignedKES (KES C_Crypto) (BHBody C_Crypto)
sig = signedKES () 0 (testBHB @C) (kesSignKey $ testKESKeys @C_Crypto)
sig = unsoundPureSignedKES () 0 (testBHB @C) (kesSignKey $ testKESKeys @C_Crypto)
bh = BHeader (testBHB @C) sig
tout = StrictSeq.singleton $ ShelleyTxOut @C testAddrE (Coin 2)
txb :: Word64 -> ShelleyTxBody C
Expand Down
2 changes: 1 addition & 1 deletion libs/cardano-ledger-binary/.ghcid
Original file line number Diff line number Diff line change
@@ -1 +1 @@
--command="cabal repl --repl-options='-isrc -fwarn-unused-binds -fwarn-unused-imports -fno-code -fobject-code -g2 -fno-break-on-exception -fno-break-on-error -ferror-spans -j -Wno-unused-packages'" --clear --no-height-limit --reverse-errors --reload=../../ --outputfile=/tmp/cardano-ledger-binary-ghcid.txt
--command="cabal repl --repl-options='-isrc -fwarn-unused-binds -fwarn-unused-imports -fno-code -fobject-code -g2 -fno-break-on-exception -fno-break-on-error -ferror-spans -j -Wno-unused-packages'" --clear --no-height-limit --reverse-errors --reload=../../ --outputfile=/tmp/cardano-ledger-binary-ghcid.txt
10 changes: 0 additions & 10 deletions libs/cardano-ledger-binary/src/Cardano/Ledger/Binary/Crypto.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,6 @@ module Cardano.Ledger.Binary.Crypto (
-- * KES
encodeVerKeyKES,
decodeVerKeyKES,
encodeSignKeyKES,
decodeSignKeyKES,
encodeSigKES,
decodeSigKES,
encodeSignedKES,
Expand Down Expand Up @@ -85,14 +83,6 @@ decodeVerKeyKES :: C.KESAlgorithm v => Decoder s (C.VerKeyKES v)
decodeVerKeyKES = fromPlainDecoder C.decodeVerKeyKES
{-# INLINE decodeVerKeyKES #-}

encodeSignKeyKES :: C.KESAlgorithm v => C.SignKeyKES v -> Encoding
encodeSignKeyKES = fromPlainEncoding . C.encodeSignKeyKES
{-# INLINE encodeSignKeyKES #-}

decodeSignKeyKES :: C.KESAlgorithm v => Decoder s (C.SignKeyKES v)
decodeSignKeyKES = fromPlainDecoder C.decodeSignKeyKES
{-# INLINE decodeSignKeyKES #-}

encodeSigKES :: C.KESAlgorithm v => C.SigKES v -> Encoding
encodeSigKES = fromPlainEncoding . C.encodeSigKES
{-# INLINE encodeSigKES #-}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -23,20 +23,13 @@ where
import qualified Cardano.Binary as Plain (Decoder, FromCBOR (..))
import Cardano.Crypto.DSIGN.Class (
DSIGNAlgorithm,
SeedSizeDSIGN,
SigDSIGN,
SignKeyDSIGN,
SignedDSIGN,
VerKeyDSIGN,
)
import Cardano.Crypto.Hash.Class (Hash, HashAlgorithm)
import Cardano.Crypto.KES.Class (KESAlgorithm, OptimizedKESAlgorithm, SigKES, SignKeyKES, VerKeyKES)
import Cardano.Crypto.KES.CompactSingle (CompactSingleKES)
import Cardano.Crypto.KES.CompactSum (CompactSumKES)
import Cardano.Crypto.KES.Mock (MockKES)
import Cardano.Crypto.KES.Simple (SimpleKES)
import Cardano.Crypto.KES.Single (SingleKES)
import Cardano.Crypto.KES.Sum (SumKES)
import Cardano.Crypto.KES.Class (KESAlgorithm, SigKES, VerKeyKES)
import Cardano.Crypto.VRF.Class (
CertVRF,
CertifiedVRF (..),
Expand Down Expand Up @@ -92,7 +85,6 @@ import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU
import Data.Void (Void)
import Data.Word (Word16, Word32, Word64, Word8)
import GHC.TypeNats (KnownNat, type (*))
import Numeric.Natural (Natural)
import qualified PlutusLedgerApi.V1 as PV1
import qualified PlutusLedgerApi.V2 as PV2
Expand Down Expand Up @@ -487,93 +479,11 @@ instance (HashAlgorithm h, Typeable a) => DecCBOR (Hash h a)
-- KES
--------------------------------------------------------------------------------

instance
(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) =>
DecCBOR (VerKeyKES (SimpleKES d t))
where
decCBOR = decodeVerKeyKES
{-# INLINE decCBOR #-}

instance
(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) =>
DecCBOR (SignKeyKES (SimpleKES d t))
where
decCBOR = decodeSignKeyKES
{-# INLINE decCBOR #-}

instance
(DSIGNAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t)) =>
DecCBOR (SigKES (SimpleKES d t))
where
decCBOR = decodeSigKES
{-# INLINE decCBOR #-}

instance (KESAlgorithm d, HashAlgorithm h) => DecCBOR (VerKeyKES (SumKES h d)) where
decCBOR = decodeVerKeyKES
{-# INLINE decCBOR #-}

instance (KESAlgorithm d, HashAlgorithm h) => DecCBOR (SignKeyKES (SumKES h d)) where
decCBOR = decodeSignKeyKES
{-# INLINE decCBOR #-}

instance (KESAlgorithm d, HashAlgorithm h) => DecCBOR (SigKES (SumKES h d)) where
decCBOR = decodeSigKES
{-# INLINE decCBOR #-}

instance DSIGNAlgorithm d => DecCBOR (VerKeyKES (CompactSingleKES d)) where
decCBOR = decodeVerKeyKES
{-# INLINE decCBOR #-}

instance DSIGNAlgorithm d => DecCBOR (SignKeyKES (CompactSingleKES d)) where
decCBOR = decodeSignKeyKES
{-# INLINE decCBOR #-}

instance DSIGNAlgorithm d => DecCBOR (SigKES (CompactSingleKES d)) where
decCBOR = decodeSigKES
{-# INLINE decCBOR #-}

instance
(OptimizedKESAlgorithm d, HashAlgorithm h) =>
DecCBOR (VerKeyKES (CompactSumKES h d))
where
instance KESAlgorithm k => DecCBOR (VerKeyKES k) where
decCBOR = decodeVerKeyKES
{-# INLINE decCBOR #-}

instance
(OptimizedKESAlgorithm d, HashAlgorithm h) =>
DecCBOR (SignKeyKES (CompactSumKES h d))
where
decCBOR = decodeSignKeyKES
{-# INLINE decCBOR #-}

instance
(OptimizedKESAlgorithm d, HashAlgorithm h) =>
DecCBOR (SigKES (CompactSumKES h d))
where
decCBOR = decodeSigKES
{-# INLINE decCBOR #-}

instance DSIGNAlgorithm d => DecCBOR (VerKeyKES (SingleKES d)) where
decCBOR = decodeVerKeyKES
{-# INLINE decCBOR #-}

instance DSIGNAlgorithm d => DecCBOR (SignKeyKES (SingleKES d)) where
decCBOR = decodeSignKeyKES
{-# INLINE decCBOR #-}

instance DSIGNAlgorithm d => DecCBOR (SigKES (SingleKES d)) where
decCBOR = decodeSigKES
{-# INLINE decCBOR #-}

instance KnownNat t => DecCBOR (VerKeyKES (MockKES t)) where
decCBOR = decodeVerKeyKES
{-# INLINE decCBOR #-}

instance KnownNat t => DecCBOR (SignKeyKES (MockKES t)) where
decCBOR = decodeSignKeyKES
{-# INLINE decCBOR #-}

instance KnownNat t => DecCBOR (SigKES (MockKES t)) where
instance KESAlgorithm k => DecCBOR (SigKES k) where
decCBOR = decodeSigKES
{-# INLINE decCBOR #-}

Expand Down
Loading

0 comments on commit 3f163c7

Please sign in to comment.