Skip to content

Commit

Permalink
Use the real Allegra and Mary era tags
Browse files Browse the repository at this point in the history
Fixes #2668.

Previously, the Allegra and Mary eras were exactly the same as the Shelley era,
so no translations between the eras were needed.

In this commit, we use the actual, different `AllegraEra` and `ShelleyEra` tags.
This means we need translations between the eras.

In the `db-analyser`, split up `HasAnalysis` in `HasAnalysis` and
`HasProtocolInfo`. The Allegra and Mary eras have `HasAnalysis` instances, but
not yet `HasProtocolInfo` (and Allegra might never need one).
  • Loading branch information
mrBliss committed Oct 15, 2020
1 parent a09f209 commit ad7a4ac
Show file tree
Hide file tree
Showing 40 changed files with 819 additions and 626 deletions.
5 changes: 3 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -156,8 +156,8 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-ledger-specs
tag: d5eaac6c4b21a8e69dc3a5503a72e3c3bfde648e
--sha256: 1lzwfi6bc7z995s345ij6aachsrmhmrgm71060z6rvk1w97b3jqk
tag: b80714a3b6fec1128356bb2d5b196ab32356cf29
--sha256: 1nvxrk7b8zfys1n110811icl2mqfwcq9y8cxpfs61s51drvc6db4
subdir:
byron/chain/executable-spec
byron/crypto
Expand All @@ -170,6 +170,7 @@ source-repository-package
shelley/chain-and-ledger/dependencies/non-integer
shelley/chain-and-ledger/executable-spec
shelley/chain-and-ledger/shelley-spec-ledger-test
shelley-ma/impl

source-repository-package
type: git
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -196,9 +196,9 @@ codecConfig :: CardanoCodecConfig Crypto
codecConfig =
CardanoCodecConfig
Byron.codecConfig
Shelley.codecConfig
Shelley.codecConfig
Shelley.codecConfig
Shelley.ShelleyCodecConfig
Shelley.ShelleyCodecConfig
Shelley.ShelleyCodecConfig

{-------------------------------------------------------------------------------
Additional injections
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,9 @@ instance Arbitrary (CardanoBlock MockCryptoCompatByron) where
arbitrary = oneof
[ BlockByron <$> arbitrary
, BlockShelley <$> arbitrary
, BlockAllegra <$> arbitrary
-- TODO #2677 enable when the generator in the ledger supports Mary
-- , BlockMary <$> arbitrary
]

instance Arbitrary (CardanoHeader MockCryptoCompatByron) where
Expand All @@ -81,6 +84,7 @@ arbitraryHardForkState
:: forall f c a.
( Arbitrary (f ByronBlock)
, Arbitrary (f (ShelleyBlock (ShelleyEra c)))
, Arbitrary (f (ShelleyBlock (AllegraEra c)))
, Coercible a (HardForkState f (CardanoEras c))
)
=> Proxy f
Expand All @@ -96,13 +100,14 @@ arbitraryHardForkState _ = coerce <$> oneof
<*> (TS
<$> (K <$> genPast)
<*> (TZ <$> genCurrent (Proxy @(ShelleyBlock (AllegraEra c)))))
, TS
<$> (K <$> genPast)
<*> (TS
<$> (K <$> genPast)
<*> (TS
<$> (K <$> genPast)
<*> (TZ <$> genCurrent (Proxy @(ShelleyBlock (MaryEra c))))))
-- TODO #2677 enable when the generator in the ledger supports Mary
-- , TS
-- <$> (K <$> genPast)
-- <*> (TS
-- <$> (K <$> genPast)
-- <*> (TS
-- <$> (K <$> genPast)
-- <*> (TZ <$> genCurrent (Proxy @(ShelleyBlock (MaryEra c))))))
]
where
genCurrent
Expand Down Expand Up @@ -132,13 +137,19 @@ instance (CanMock (ShelleyEra c), CardanoHardForkConstraints c)
arbitrary = OneEraHash <$> oneof
[ toShortRawHash (Proxy @ByronBlock) <$> arbitrary
, toShortRawHash (Proxy @(ShelleyBlock (ShelleyEra c))) <$> arbitrary
, toShortRawHash (Proxy @(ShelleyBlock (AllegraEra c))) <$> arbitrary
-- TODO #2677 enable when the generator in the ledger supports Mary
-- , toShortRawHash (Proxy @(ShelleyBlock (MaryEra c))) <$> arbitrary
]

instance (c ~ MockCryptoCompatByron, Era (ShelleyEra c))
=> Arbitrary (AnnTip (CardanoBlock c)) where
arbitrary = oneof
[ mapAnnTip TipInfoByron <$> arbitrary @(AnnTip (ByronBlock))
, mapAnnTip TipInfoShelley <$> arbitrary @(AnnTip (ShelleyBlock (ShelleyEra c)))
, mapAnnTip TipInfoAllegra <$> arbitrary @(AnnTip (ShelleyBlock (AllegraEra c)))
-- TODO #2677 enable when the generator in the ledger supports Mary
-- , mapAnnTip TipInfoMary <$> arbitrary @(AnnTip (ShelleyBlock (MaryEra c)))
]

{-------------------------------------------------------------------------------
Expand All @@ -161,14 +172,13 @@ arbitraryNodeToNode
:: ( Arbitrary (WithVersion ByronNodeToNodeVersion byron)
, Arbitrary shelley
, Arbitrary allegra
, Arbitrary mary
)
=> (byron -> cardano)
-> (shelley -> cardano)
-> (allegra -> cardano)
-> (mary -> cardano)
-> Gen (WithVersion (HardForkNodeToNodeVersion (CardanoEras c)) cardano)
arbitraryNodeToNode injByron injShelley injAllegra injMary = oneof
arbitraryNodeToNode injByron injShelley injAllegra _injMary = oneof
-- Byron + HardFork disabled
[ (\(WithVersion versionByron b) ->
WithVersion
Expand Down Expand Up @@ -210,17 +220,18 @@ arbitraryNodeToNode injByron injShelley injAllegra injMary = oneof
:* Nil))
(injAllegra a))
<$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
-- Mary + HardFork enabled
, (\versionByron versionShelley versionAllegra (WithVersion versionMary m) ->
WithVersion
(HardForkNodeToNodeEnabled (
EraNodeToNodeEnabled versionByron
:* EraNodeToNodeEnabled versionShelley
:* EraNodeToNodeEnabled versionAllegra
:* EraNodeToNodeEnabled versionMary
:* Nil))
(injMary m))
<$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
-- TODO #2677 enable when the generator in the ledger supports Mary
-- -- Mary + HardFork enabled
-- , (\versionByron versionShelley versionAllegra (WithVersion versionMary m) ->
-- WithVersion
-- (HardForkNodeToNodeEnabled (
-- EraNodeToNodeEnabled versionByron
-- :* EraNodeToNodeEnabled versionShelley
-- :* EraNodeToNodeEnabled versionAllegra
-- :* EraNodeToNodeEnabled versionMary
-- :* Nil))
-- (injMary m))
-- <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
]

instance c ~ MockCryptoCompatByron
Expand Down Expand Up @@ -292,14 +303,13 @@ arbitraryNodeToClient
:: ( Arbitrary (WithVersion ByronNodeToClientVersion byron)
, Arbitrary shelley
, Arbitrary allegra
, Arbitrary mary
)
=> (byron -> cardano)
-> (shelley -> cardano)
-> (allegra -> cardano)
-> (mary -> cardano)
-> Gen (WithVersion (HardForkNodeToClientVersion (CardanoEras c)) cardano)
arbitraryNodeToClient injByron injShelley injAllegra injMary = oneof
arbitraryNodeToClient injByron injShelley injAllegra _injMary = oneof
-- Byron + HardFork disabled
[ (\(WithVersion versionByron b) ->
WithVersion
Expand Down Expand Up @@ -339,17 +349,18 @@ arbitraryNodeToClient injByron injShelley injAllegra injMary = oneof
:* Nil))
(injAllegra a))
<$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
-- Mary + HardFork enabled
, (\versionByron versionShelley versionAllegra (WithVersion versionMary m) ->
WithVersion
(HardForkNodeToClientEnabled (
EraNodeToClientEnabled versionByron
:* EraNodeToClientEnabled versionShelley
:* EraNodeToClientEnabled versionAllegra
:* EraNodeToClientEnabled versionMary
:* Nil))
(injMary m))
<$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
-- TODO #2677 enable when the generator in the ledger supports Mary
-- -- Mary + HardFork enabled
-- , (\versionByron versionShelley versionAllegra (WithVersion versionMary m) ->
-- WithVersion
-- (HardForkNodeToClientEnabled (
-- EraNodeToClientEnabled versionByron
-- :* EraNodeToClientEnabled versionShelley
-- :* EraNodeToClientEnabled versionAllegra
-- :* EraNodeToClientEnabled versionMary
-- :* Nil))
-- (injMary m))
-- <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
]

instance c ~ MockCryptoCompatByron
Expand Down Expand Up @@ -496,9 +507,10 @@ instance c ~ MockCryptoCompatByron
, (\(SomeResult q (_ :: result)) mismatch ->
SomeResult (QueryIfCurrentAllegra q) (Left @_ @result mismatch))
<$> arbitrary <*> arbitrary
, (\(SomeResult q (_ :: result)) mismatch ->
SomeResult (QueryIfCurrentMary q) (Left @_ @result mismatch))
<$> arbitrary <*> arbitrary
-- TODO #2677 enable when the generator in the ledger supports Mary
-- , (\(SomeResult q (_ :: result)) mismatch ->
-- SomeResult (QueryIfCurrentMary q) (Left @_ @result mismatch))
-- <$> arbitrary <*> arbitrary
]

genQueryAnytimeResultByron :: Gen (SomeResult (CardanoBlock c))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,20 +3,16 @@
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.Consensus.Cardano.MockCrypto (
BlockCompatByron
, MockShelleyCompatByron
, MockCryptoCompatByron
MockCryptoCompatByron
) where

import Cardano.Crypto.DSIGN (Ed25519DSIGN)
import Cardano.Crypto.Hash (Blake2b_224, Blake2b_256)
import Cardano.Crypto.KES (MockKES)

import Cardano.Ledger.Crypto (Crypto (..))
import Cardano.Ledger.Shelley (Shelley)
import Test.Cardano.Crypto.VRF.Fake (FakeVRF)

import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock)
import Ouroboros.Consensus.Shelley.Protocol.Crypto (TPraosCrypto)

-- | A replacement for 'Test.Consensus.Shelley.MockCrypto' that is compatible
Expand All @@ -35,8 +31,8 @@ import Ouroboros.Consensus.Shelley.Protocol.Crypto (TPraosCrypto)
-- * We can still use mock KES and mock VRF.
--
-- Note that many Shelley generators are not instantiated to 'MockShelley' but
-- are constrained by @'CanMock' era@. 'MockShelleyCompatByron' satisfies this
-- constraint, allowing us to reuse these generators for Cardano.
-- are constrained by @'CanMock' era@. @'ShelleyEra' 'MockCryptoCompatByron'@
-- satisfies this constraint, allowing us to reuse these generators for Cardano.
data MockCryptoCompatByron

instance Crypto MockCryptoCompatByron where
Expand All @@ -46,8 +42,4 @@ instance Crypto MockCryptoCompatByron where
type KES MockCryptoCompatByron = MockKES 10
type VRF MockCryptoCompatByron = FakeVRF

type MockShelleyCompatByron = Shelley MockCryptoCompatByron

instance TPraosCrypto MockShelleyCompatByron

type BlockCompatByron = ShelleyBlock MockShelleyCompatByron
instance TPraosCrypto MockCryptoCompatByron
Original file line number Diff line number Diff line change
@@ -1,11 +1,12 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.ThreadNet.TxGen.Cardano (
CardanoTxGenExtra (..),
Expand Down Expand Up @@ -65,7 +66,7 @@ import Test.ThreadNet.TxGen
data CardanoTxGenExtra c = CardanoTxGenExtra
{ ctgeByronGenesisKeys :: GeneratedSecrets
, ctgeNetworkMagic :: Byron.NetworkMagic
, ctgeShelleyCoreNodes :: [Shelley.CoreNode (ShelleyEra c)]
, ctgeShelleyCoreNodes :: [Shelley.CoreNode c]
}

instance CardanoHardForkConstraints c => TxGen (CardanoBlock c) where
Expand Down Expand Up @@ -108,19 +109,19 @@ instance CardanoHardForkConstraints c => TxGen (CardanoBlock c) where

-- Reuse the payment key as the pool key, since it's an individual
-- stake pool and the namespaces are separate.
poolSK :: SL.SignKeyDSIGN (ShelleyEra c)
poolSK :: SL.SignKeyDSIGN c
poolSK = paymentSK

-- | See 'migrateUTxO'
data MigrationInfo era = MigrationInfo
data MigrationInfo c = MigrationInfo
{ byronMagic :: Byron.NetworkMagic
-- ^ Needed for creating a Byron address.
, byronSK :: Byron.SigningKey
-- ^ The core node's Byron secret.
, paymentSK :: SL.SignKeyDSIGN era
, poolSK :: SL.SignKeyDSIGN era
, stakingSK :: SL.SignKeyDSIGN era
, vrfSK :: SL.SignKeyVRF era
, paymentSK :: SL.SignKeyDSIGN c
, poolSK :: SL.SignKeyDSIGN c
, stakingSK :: SL.SignKeyDSIGN c
, vrfSK :: SL.SignKeyVRF c
-- ^ To be re-used by the individual pool.
}

Expand All @@ -135,7 +136,7 @@ data MigrationInfo era = MigrationInfo
-- 'byronAddr' (eg if this transaction has already been applied).
migrateUTxO ::
forall c. CardanoHardForkConstraints c
=> MigrationInfo (ShelleyEra c)
=> MigrationInfo c
-> SlotNo
-> LedgerConfig (CardanoBlock c)
-> LedgerState (CardanoBlock c)
Expand Down Expand Up @@ -187,7 +188,7 @@ migrateUTxO migrationInfo curSlot lcfg lst
, SL._wdrls = SL.Wdrl Map.empty
}

bodyHash :: SL.Hash (ShelleyEra c) (SL.TxBody (ShelleyEra c))
bodyHash :: SL.Hash c (SL.TxBody (ShelleyEra c))
bodyHash = SL.hashWithSerialiser toCBOR body

-- Witness the use of bootstrap address's utxo.
Expand All @@ -197,18 +198,18 @@ migrateUTxO migrationInfo curSlot lcfg lst
Byron.addrAttributes byronAddr

-- Witness the stake delegation.
delegWit :: SL.WitVKey (ShelleyEra c) 'SL.Witness
delegWit :: SL.WitVKey 'SL.Witness (ShelleyEra c)
delegWit =
SL.WitVKey
(Shelley.mkVerKey stakingSK)
(SL.signedDSIGN @(ShelleyEra c) stakingSK bodyHash)
(SL.signedDSIGN @c stakingSK bodyHash)

-- Witness the pool registration.
poolWit :: SL.WitVKey (ShelleyEra c) 'SL.Witness
poolWit :: SL.WitVKey 'SL.Witness (ShelleyEra c)
poolWit =
SL.WitVKey
(Shelley.mkVerKey poolSK)
(SL.signedDSIGN @(ShelleyEra c) poolSK bodyHash)
(SL.signedDSIGN @c poolSK bodyHash)

in
if Map.null picked then Nothing else
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.Consensus.Cardano.Golden (tests) where

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -501,7 +501,7 @@ prop_simple_cardano_convergence TestSetup
initialKESPeriod :: SL.KESPeriod
initialKESPeriod = SL.KESPeriod 0

coreNodes :: [Shelley.CoreNode (ShelleyEra Crypto)]
coreNodes :: [Shelley.CoreNode Crypto]
coreNodes = runGen initSeed $
replicateM (fromIntegral n) $
Shelley.genCoreNode initialKESPeriod
Expand All @@ -516,7 +516,7 @@ prop_simple_cardano_convergence TestSetup
activeSlotCoeff
setupD
setupSlotLengthShelley
(Shelley.mkKesConfig (Proxy @(ShelleyEra Crypto)) numSlots)
(Shelley.mkKesConfig (Proxy @Crypto) numSlots)
coreNodes

-- the Shelley ledger is designed to use a fixed epoch size, so this test
Expand Down Expand Up @@ -710,7 +710,7 @@ mkProtocolCardanoAndHardForkTxs
-- Shelley
-> ShelleyGenesis (ShelleyEra c)
-> SL.Nonce
-> Shelley.CoreNode (ShelleyEra c)
-> Shelley.CoreNode c
-- HardForks
-> ProtocolParamsTransition
ByronBlock
Expand Down Expand Up @@ -790,7 +790,7 @@ mkProtocolCardanoAndHardForkTxs

-- Shelley

leaderCredentialsShelley :: TPraosLeaderCredentials (ShelleyEra c)
leaderCredentialsShelley :: TPraosLeaderCredentials c
leaderCredentialsShelley = Shelley.mkLeaderCredentials coreNodeShelley

{-------------------------------------------------------------------------------
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ library
, cardano-prelude
, cardano-slotting
, shelley-spec-ledger
, cardano-ledger-shelley-ma

, ouroboros-network
, ouroboros-consensus
Expand Down
Loading

0 comments on commit ad7a4ac

Please sign in to comment.