Skip to content

Commit a10939e

Browse files
committed
Cleanup
1 parent ab83052 commit a10939e

File tree

12 files changed

+26
-52
lines changed

12 files changed

+26
-52
lines changed

cabal.project

+8-4
Original file line numberDiff line numberDiff line change
@@ -34,10 +34,9 @@ multi-repl: True
3434

3535
import: ./asserts.cabal
3636

37-
allow-newer: plutus-core:cardano-crypto-class
38-
, bytestring
39-
, serdoc-core:tasty-quickcheck
40-
, kes-agent:base
37+
allow-newer:
38+
serdoc-core:tasty-quickcheck
39+
, kes-agent:base
4140

4241
package ouroboros-network
4342
-- Certain ThreadNet tests rely on transactions to be submitted promptly after
@@ -63,6 +62,11 @@ if impl (ghc >= 9.12)
6362
-- https://github.com/kapralVV/Unique/issues/11
6463
, Unique:hashable
6564

65+
, serdoc-core:template-haskell
66+
, serdoc-core:th-abstraction
67+
, kes-agent:containers
68+
, kes-agent:extra
69+
6670
source-repository-package
6771
type: git
6872
location: https://github.com/input-output-hk/kes-agent

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

-1
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE FlexibleInstances #-}
22
{-# LANGUAGE MultiParamTypeClasses #-}
3-
{-# LANGUAGE TypeOperators #-}
43
{-# LANGUAGE UndecidableInstances #-}
54

65
{-# OPTIONS_GHC -Wno-orphans #-}

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Protocol/Praos.hs

-1
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
{-# LANGUAGE NamedFieldPuns #-}
33
{-# LANGUAGE TypeApplications #-}
44
{-# LANGUAGE TypeFamilies #-}
5-
{-# LANGUAGE TypeOperators #-}
65

76
{-# OPTIONS_GHC -Wno-orphans #-}
87
-- See https://gitlab.haskell.org/ghc/ghc/-/issues/14630. GHC currently warns

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

-1
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
{-# LANGUAGE ScopedTypeVariables #-}
33
{-# LANGUAGE TypeApplications #-}
44
{-# LANGUAGE TypeFamilies #-}
5-
{-# LANGUAGE TypeOperators #-}
65

76
{-# OPTIONS_GHC -Wno-orphans #-}
87

ouroboros-consensus-cardano/src/unstable-cardano-testlib/Test/Consensus/Cardano/ProtocolInfo.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,7 @@ hardForkInto Conway =
144144
--
145145
mkSimpleTestProtocolInfo ::
146146
forall c
147-
. (CardanoHardForkConstraints c)
147+
. (CardanoHardForkConstraints c, KESAgentContext c IO)
148148
=> Shelley.DecentralizationParam
149149
-- ^ Network decentralization parameter.
150150
-> SecurityParam
@@ -217,7 +217,6 @@ mkTestProtocolInfo ::
217217
forall m c
218218
. ( CardanoHardForkConstraints c
219219
, KESAgentContext c m
220-
, c ~ StandardCrypto
221220
)
222221
=> (CoreNodeId, Shelley.CoreNode c)
223222
-- ^ Id of the node for which the protocol info will be elaborated.

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

-1
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,6 @@ import Ouroboros.Consensus.Storage.LedgerDB
9191
import Ouroboros.Consensus.TypeFamilyWrappers
9292
import Ouroboros.Consensus.Util (eitherToMaybe)
9393
import Ouroboros.Consensus.Util.IndexedMemPack
94-
import Ouroboros.Consensus.Util.IOLike (IOLike)
9594
import Test.ThreadNet.TxGen
9695
import Test.ThreadNet.TxGen.Shelley ()
9796

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

+3-4
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ instance HasTypeProxy UnsoundPureKesKey where
4848
instance Key UnsoundPureKesKey where
4949

5050
newtype VerificationKey UnsoundPureKesKey =
51-
KesVerificationKey (Shelley.VerKeyKES StandardCrypto)
51+
KesVerificationKey (Crypto.VerKeyKES (KES StandardCrypto))
5252
deriving stock (Eq)
5353
deriving (Show, IsString) via UsingRawBytesHex (VerificationKey UnsoundPureKesKey)
5454
deriving newtype (EncCBOR, DecCBOR, ToCBOR, FromCBOR)
@@ -104,10 +104,9 @@ instance SerialiseAsBech32 (SigningKey UnsoundPureKesKey) where
104104
bech32PrefixFor _ = "kes_sk"
105105
bech32PrefixesPermitted _ = ["kes_sk"]
106106

107-
108107
newtype instance Hash UnsoundPureKesKey =
109-
UnsoundPureKesKeyHash (Shelley.Hash StandardCrypto
110-
(Shelley.VerKeyKES StandardCrypto))
108+
UnsoundPureKesKeyHash (Crypto.Hash HASH
109+
(Crypto.VerKeyKES (KES StandardCrypto)))
111110
deriving stock (Eq, Ord)
112111
deriving (Show, IsString) via UsingRawBytesHex (Hash UnsoundPureKesKey)
113112
deriving (ToCBOR, FromCBOR) via UsingRawBytes (Hash UnsoundPureKesKey)

ouroboros-consensus-cardano/src/unstable-shelley-testlib/Test/Consensus/Shelley/MockCrypto.hs

+4-24
Original file line numberDiff line numberDiff line change
@@ -19,9 +19,7 @@ import Cardano.Crypto.KES (MockKES)
1919
import qualified Cardano.Crypto.KES as KES (Signable)
2020
import Cardano.Crypto.Util (SignableRepresentation)
2121
import Cardano.Crypto.VRF (MockVRF)
22-
import qualified Cardano.KESAgent.KES.Crypto as Agent
23-
import qualified Cardano.KESAgent.Processes.ServiceClient as Agent
24-
import qualified Cardano.KESAgent.Protocols.VersionedProtocol as Agent
22+
import Cardano.KESAgent.Protocols.StandardCrypto (MockCrypto)
2523
import Cardano.Ledger.BaseTypes (Seed)
2624
import qualified Cardano.Ledger.Shelley.API as SL
2725
import qualified Cardano.Ledger.Shelley.Core as Core
@@ -42,16 +40,8 @@ import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock,
4240
import Ouroboros.Consensus.Shelley.Protocol.Abstract (ProtoCrypto)
4341
import Test.QuickCheck (Arbitrary)
4442

45-
-- | A mock replacement for 'StandardCrypto'
46-
--
47-
-- We run the tests with this mock crypto, as it is easier to generate and
48-
-- debug things. The code is parametric in the crypto, so it shouldn't make
49-
-- much of a difference. This also has the important advantage
50-
-- that we can reuse the generators from cardano-ledger-specs.
51-
data MockCrypto
52-
5343
instance Crypto MockCrypto where
54-
type KES MockCrypto = MockKES 10
44+
type KES MockCrypto = MockKES 128
5545
type VRF MockCrypto = MockVRF
5646

5747
instance SL.PraosCrypto MockCrypto
@@ -86,15 +76,5 @@ type CanMock proto era =
8676
, Arbitrary (SL.CertState era)
8777
)
8878

89-
instance Agent.NamedCrypto (MockCrypto h) where
90-
cryptoName _ = Agent.CryptoName "Mock"
91-
92-
instance Agent.ServiceClientDrivers (MockCrypto h) where
93-
availableServiceClientDrivers = []
94-
95-
instance Agent.Crypto (MockCrypto h) where
96-
type KES (MockCrypto h) = MockKES 10
97-
type DSIGN (MockCrypto h) = MockDSIGN
98-
99-
instance HashAlgorithm h => AgentCrypto (MockCrypto h) where
100-
type ACrypto (MockCrypto h) = MockCrypto h
79+
instance AgentCrypto MockCrypto where
80+
type ACrypto MockCrypto = MockCrypto

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

+6-8
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,6 @@ module Test.ThreadNet.Infra.Shelley (
3838

3939
import Cardano.Crypto.DSIGN (DSIGNAlgorithm (..), SignKeyDSIGN,
4040
seedSizeDSIGN)
41-
import Cardano.Crypto.Hash (HashAlgorithm)
4241
import Cardano.Crypto.KES (KESAlgorithm (..),
4342
UnsoundPureKESAlgorithm (..), UnsoundPureSignKeyKES,
4443
seedSizeKES, unsoundPureDeriveVerKeyKES,
@@ -144,7 +143,7 @@ data CoreNode c = CoreNode {
144143
, cnStakingKey :: !(SignKeyDSIGN LK.DSIGN)
145144
-- ^ The hash of the corresponding verification (public) key will be
146145
-- used as the staking credential.
147-
, cnVRF :: !(SL.SignKeyVRF c)
146+
, cnVRF :: !(SignKeyVRF (VRF c))
148147
, cnKES :: !(UnsoundPureSignKeyKES (KES c))
149148
, cnOCert :: !(SL.OCert c)
150149
}
@@ -184,9 +183,9 @@ genCoreNode ::
184183
=> SL.KESPeriod
185184
-> Gen (CoreNode c)
186185
genCoreNode startKESPeriod = do
187-
genKey <- genKeyDSIGN <$> genSeed (seedSizeDSIGN (Proxy @(DSIGN c)))
188-
delKey <- genKeyDSIGN <$> genSeed (seedSizeDSIGN (Proxy @(DSIGN c)))
189-
stkKey <- genKeyDSIGN <$> genSeed (seedSizeDSIGN (Proxy @(DSIGN c)))
186+
genKey <- genKeyDSIGN <$> genSeed (seedSizeDSIGN (Proxy @LK.DSIGN))
187+
delKey <- genKeyDSIGN <$> genSeed (seedSizeDSIGN (Proxy @LK.DSIGN))
188+
stkKey <- genKeyDSIGN <$> genSeed (seedSizeDSIGN (Proxy @LK.DSIGN))
190189
vrfKey <- genKeyVRF <$> genSeed (seedSizeVRF (Proxy @(VRF c)))
191190
kesKey <- unsoundPureGenKeyKES <$> genSeed (seedSizeKES (Proxy @(KES c)))
192191
let kesPub = unsoundPureDeriveVerKeyKES kesKey
@@ -412,10 +411,9 @@ mkGenesisConfig pVer k f d maxLovelaceSupply slotLength kesCfg coreNodes =
412411
mkProtocolShelley ::
413412
forall m c.
414413
( KESAgentContext c m
415-
, PraosCrypto c
416-
, ShelleyCompatible (TPraos c) (ShelleyEra c)
414+
, ShelleyCompatible (TPraos c) ShelleyEra
417415
)
418-
=> ShelleyGenesis c
416+
=> ShelleyGenesis
419417
-> SL.Nonce
420418
-> ProtVer
421419
-> CoreNode c

ouroboros-consensus-cardano/test/cardano-test/Test/ThreadNet/Cardano.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ import Ouroboros.Consensus.Byron.Ledger.Block (ByronBlock)
4141
import Ouroboros.Consensus.Byron.Ledger.Conversions
4242
import Ouroboros.Consensus.Byron.Node
4343
import Ouroboros.Consensus.Cardano.Block
44+
import Ouroboros.Consensus.Cardano.CanHardFork
4445
import Ouroboros.Consensus.Cardano.Condense ()
4546
import Ouroboros.Consensus.Config.SecurityParam
4647
import Ouroboros.Consensus.HardFork.Combinator
@@ -438,7 +439,7 @@ prop_simple_cardano_convergence TestSetup
438439
property $ unNonZero (maxRollbacks setupK) >= finalIntersectionDepth
439440

440441
mkProtocolCardanoAndHardForkTxs ::
441-
forall c m. (KESAgentContext c m, c ~ StandardCrypto)
442+
forall c m. (CardanoHardForkConstraints c, KESAgentContext c m)
442443
-- Byron
443444
=> PBftParams
444445
-> CoreNodeId

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

-1
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@
99
{-# LANGUAGE ScopedTypeVariables #-}
1010
{-# LANGUAGE StandaloneDeriving #-}
1111
{-# LANGUAGE TypeFamilies #-}
12-
{-# LANGUAGE TypeOperators #-}
1312

1413
-- | Transitional Praos.
1514
--

ouroboros-consensus-protocol/src/unstable-protocol-testlib/Test/Consensus/Protocol/Serialisation/Generators.hs

+2-4
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
1-
{-# LANGUAGE FlexibleContexts #-}
21
{-# LANGUAGE ScopedTypeVariables #-}
3-
{-# LANGUAGE UndecidableInstances #-}
42

53
{-# OPTIONS_GHC -Wno-orphans #-}
64

@@ -29,7 +27,7 @@ import Test.QuickCheck (Arbitrary (..), Gen, choose, oneof)
2927
instance Arbitrary InputVRF where
3028
arbitrary = mkInputVRF <$> arbitrary <*> arbitrary
3129

32-
instance (Praos.PraosCrypto c) => Arbitrary (HeaderBody c) where
30+
instance Praos.PraosCrypto c => Arbitrary (HeaderBody c) where
3331
arbitrary =
3432
let ocert =
3533
OCert
@@ -57,7 +55,7 @@ instance (Praos.PraosCrypto c) => Arbitrary (HeaderBody c) where
5755
<*> ocert
5856
<*> arbitrary
5957

60-
instance (Praos.PraosCrypto c) => Arbitrary (Header c) where
58+
instance Praos.PraosCrypto c => Arbitrary (Header c) where
6159
arbitrary = do
6260
hBody <- arbitrary
6361
period <- arbitrary

0 commit comments

Comments
 (0)