Skip to content

Commit

Permalink
Update dependencies
Browse files Browse the repository at this point in the history
  • Loading branch information
mrBliss committed Oct 23, 2020
1 parent 95c9cd2 commit a0f2ead
Show file tree
Hide file tree
Showing 43 changed files with 797 additions and 645 deletions.
13 changes: 7 additions & 6 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -131,17 +131,17 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-prelude
tag: a5519e09958ad1605ed438d26dd7aad39167d0f9
--sha256: 03v46yn5bnkmwcm1zwihjhqvma4ssh3s1s1bfdizvq18y1janwf1
tag: bec71e48b027b2022e7be1fb7dd265bbbd80490b
--sha256: 0jnxa9m84ka799a3i863sqvlygzf18941pi00d88ar45qdmzkagm
subdir:
cardano-prelude
cardano-prelude-test

source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-base
tag: 72399b18f1bb7d91b21bc9e0e3c28715cde7d124
--sha256: 014jw9jkwq3z30hl5pc0in51hzxrdys4964vpppmn1nim994bykx
tag: 6012e2fcbddc516490fcae07aad8d3e96fd729e3
--sha256: 1y64bjl83n2idrhyjwh10frmpiv7lqmbmrixaswvxg36r2iddrqk
subdir:
binary
binary/test
Expand All @@ -152,8 +152,8 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-ledger-specs
tag: d5eaac6c4b21a8e69dc3a5503a72e3c3bfde648e
--sha256: 1lzwfi6bc7z995s345ij6aachsrmhmrgm71060z6rvk1w97b3jqk
tag: 1a2d7717682f8191cf818362df28ac20fac19b83
--sha256: 136pp0653w8chk53wnz6mlkdhf0ldglrb74p1i93d1xnf6ssvjhs
subdir:
byron/chain/executable-spec
byron/crypto
Expand All @@ -166,6 +166,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 @@ -44,7 +44,6 @@ import qualified Ouroboros.Consensus.Byron.Ledger as Byron

import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock)
import qualified Ouroboros.Consensus.Shelley.Ledger as Shelley
import Ouroboros.Consensus.Shelley.Protocol (StandardCrypto)

import Ouroboros.Consensus.Cardano.Block
import Ouroboros.Consensus.Cardano.CanHardFork ()
Expand Down Expand Up @@ -196,9 +195,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,8 @@ instance Arbitrary (CardanoBlock MockCryptoCompatByron) where
arbitrary = oneof
[ BlockByron <$> arbitrary
, BlockShelley <$> arbitrary
, BlockAllegra <$> arbitrary
, BlockMary <$> arbitrary
]

instance Arbitrary (CardanoHeader MockCryptoCompatByron) where
Expand Down Expand Up @@ -114,7 +116,7 @@ arbitraryHardForkState _ = coerce <$> oneof
genPast :: Gen Past
genPast = Past <$> arbitrary <*> arbitrary

instance (c ~ MockCryptoCompatByron, Era (ShelleyEra c))
instance (c ~ MockCryptoCompatByron, ShelleyBasedEra (ShelleyEra c))
=> Arbitrary (CardanoLedgerState c) where
arbitrary = arbitraryHardForkState (Proxy @LedgerState)

Expand All @@ -132,13 +134,17 @@ 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
, toShortRawHash (Proxy @(ShelleyBlock (MaryEra c))) <$> arbitrary
]

instance (c ~ MockCryptoCompatByron, Era (ShelleyEra c))
instance (c ~ MockCryptoCompatByron, ShelleyBasedEra (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)))
, mapAnnTip TipInfoMary <$> arbitrary @(AnnTip (ShelleyBlock (MaryEra 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
Expand Up @@ -65,7 +65,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 +108,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 +135,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 +187,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 +197,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
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
Binary file not shown.
Binary file not shown.
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
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,6 @@ import Ouroboros.Consensus.Byron.Node as X

import Ouroboros.Consensus.Shelley.Ledger
import Ouroboros.Consensus.Shelley.Node as X
import Ouroboros.Consensus.Shelley.Protocol (StandardCrypto)

import Ouroboros.Consensus.Cardano.Block
import Ouroboros.Consensus.Cardano.ByronHFC
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,7 @@ type CardanoEras c =
-- > f (BlockByron b) = _
-- > f (BlockShelley s) = _
-- > f (BlockAllegra a) = _
-- > f (BlockAllegra m) = _
-- > f (BlockMary m) = _
--
type CardanoBlock c = HardForkBlock (CardanoEras c)

Expand Down
Loading

0 comments on commit a0f2ead

Please sign in to comment.