Skip to content

Commit d03a1b9

Browse files
committed
Formatting and cleanup
1 parent 3faa545 commit d03a1b9

File tree

11 files changed

+36
-49
lines changed

11 files changed

+36
-49
lines changed

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

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -53,16 +53,12 @@ import qualified Cardano.Ledger.Babbage.Translation as Babbage
5353
import Cardano.Ledger.BaseTypes
5454
import Cardano.Ledger.Binary (DecCBOR, EncCBOR)
5555
import Cardano.Ledger.Conway (ConwayEra)
56-
import Cardano.Ledger.Conway.Genesis
5756
import qualified Cardano.Ledger.Conway.Governance as CG
5857
import qualified Cardano.Ledger.Conway.Rules as Conway
5958
import qualified Cardano.Ledger.Conway.Rules as SL
6059
(ConwayLedgerPredFailure (..))
6160
import qualified Cardano.Ledger.Conway.Translation as Conway
6261
import Cardano.Ledger.Core as Core
63-
import Cardano.Ledger.Crypto (StandardCrypto)
64-
import Cardano.Ledger.Genesis
65-
import Cardano.Ledger.Keys (DSignable, Hash)
6662
import Cardano.Ledger.Mary (MaryEra)
6763
import Cardano.Ledger.Mary.Translation ()
6864
import Cardano.Ledger.Shelley (ShelleyEra)
@@ -71,17 +67,15 @@ import Cardano.Ledger.Shelley.Core as Core
7167
import qualified Cardano.Ledger.Shelley.LedgerState as SL
7268
import qualified Cardano.Ledger.Shelley.Rules as SL
7369
import qualified Cardano.Ledger.Shelley.Transition as SL
74-
import Cardano.Ledger.Shelley.Translation
75-
import Cardano.Protocol.Crypto (StandardCrypto)
7670
import qualified Cardano.Protocol.TPraos.API as SL
7771
import Control.Monad.Except
7872
import Control.State.Transition (PredicateFailure)
7973
import Data.Data (Proxy (Proxy))
8074
import Data.List.NonEmpty (NonEmpty ((:|)))
81-
import Data.Typeable (Typeable)
8275
import NoThunks.Class (NoThunks)
8376
import Ouroboros.Consensus.Ledger.SupportsMempool
8477
(WhetherToIntervene (..))
78+
import Ouroboros.Consensus.Protocol.TPraos (StandardCrypto)
8579

8680
{-------------------------------------------------------------------------------
8781
Eras instantiated with standard crypto

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

Lines changed: 4 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@ import Cardano.Ledger.BaseTypes
1616
import Cardano.Ledger.Core (fromEraCBOR, toEraCBOR)
1717
import qualified Cardano.Ledger.Core as SL
1818
import qualified Cardano.Ledger.Shelley.API as SL
19-
import qualified Cardano.Protocol.TPraos.API as SL
2019
import Cardano.Slotting.EpochInfo (epochInfoSize,
2120
epochInfoSlotToRelativeTime, fixedEpochInfo,
2221
hoistEpochInfo)
@@ -169,27 +168,6 @@ instance ShelleyCompatible proto era
169168
encodeNodeToClient _ _ = wrapCBORinCBOR encodeShelleyBlock
170169
decodeNodeToClient _ _ = unwrapCBORinCBOR decodeShelleyBlock
171170

172-
--------------------------------------------------------------------------------
173-
-- ↓↓↓ REMOVE ↓↓↓
174-
--
175-
-- This code fills the holes from
176-
-- https://github.com/IntersectMBO/cardano-ledger/issues/4893 and must
177-
-- be removed before merging!!
178-
--------------------------------------------------------------------------------
179-
180-
instance FromCBOR ActiveSlotCoeff where
181-
fromCBOR = undefined
182-
instance FromCBOR Network where
183-
fromCBOR = undefined
184-
instance ToCBOR ActiveSlotCoeff where
185-
toCBOR = undefined
186-
instance ToCBOR Network where
187-
toCBOR = undefined
188-
189-
--------------------------------------------------------------------------------
190-
-- ↑↑↑ REMOVE ↑↑↑
191-
--------------------------------------------------------------------------------
192-
193171
-- | This instance uses the invariant that the 'EpochInfo' in a
194172
-- 'ShelleyLedgerConfig' is fixed i.e. has a constant 'EpochSize' and
195173
-- 'SlotLength'. This is not true in the case of the HFC in a
@@ -239,13 +217,13 @@ instance ShelleyBasedEra era
239217
enforceSize "ShelleyPartialLedgerConfig era" 14
240218
ShelleyPartialLedgerConfig
241219
<$> ( ShelleyLedgerConfig
242-
<$> fromCBOR @(CompactGenesis (EraCrypto era))
220+
<$> fromCBOR @CompactGenesis
243221
<*> (SL.Globals
244222
(hoistEpochInfo (Right . runIdentity) $ toPureEpochInfo dummyEpochInfo)
245223
<$> fromCBOR @Word64
246224
<*> fromCBOR @Word64
247225
<*> fromCBOR @Word64
248-
<*> fromCBOR @Word64
226+
<*> fromCBOR @(NonZero Word64)
249227
<*> fromCBOR @Word64
250228
<*> fromCBOR @Word64
251229
<*> fromCBOR @Word64
@@ -279,11 +257,11 @@ instance ShelleyBasedEra era
279257
triggerHardFork
280258
)
281259
= encodeListLen 14
282-
<> toCBOR @(CompactGenesis (EraCrypto era)) myCompactGenesis
260+
<> toCBOR @CompactGenesis myCompactGenesis
283261
<> toCBOR @Word64 slotsPerKESPeriod'
284262
<> toCBOR @Word64 stabilityWindow'
285263
<> toCBOR @Word64 randomnessStabilisationWindow'
286-
<> toCBOR @Word64 securityParameter'
264+
<> toCBOR @(NonZero Word64) securityParameter'
287265
<> toCBOR @Word64 maxKESEvo'
288266
<> toCBOR @Word64 quorum'
289267
<> toCBOR @Word64 maxLovelaceSupply'

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ combineEras perEraExamples = Examples {
107107
$ himap (\ix -> K . inj ix . getExamples) perEraExamplesPrefixed
108108
where
109109
inj :: forall blk. Index (CardanoEras Crypto) blk -> Labelled (f blk) -> Labelled (f (CardanoBlock Crypto))
110-
inj idx = fmap (fmap (inject exampleStartBounds idx))
110+
inj idx = fmap (fmap (inject $ oracularInjectionIndex exampleStartBounds idx))
111111

112112
perEraExamplesPrefixed :: NP Examples (CardanoEras Crypto)
113113
perEraExamplesPrefixed = hzipWith (\(K eraName) es -> prefixExamples eraName es) perEraNames perEraExamples

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

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ module Test.Consensus.Shelley.Examples (
2222

2323
import qualified Cardano.Ledger.Block as SL
2424
import Cardano.Ledger.Core
25-
import Cardano.Ledger.Crypto (Crypto)
2625
import qualified Cardano.Ledger.Shelley.API as SL
2726
import Cardano.Protocol.Crypto (StandardCrypto)
2827
import qualified Cardano.Protocol.TPraos.BHeader as SL
@@ -267,11 +266,11 @@ examplesBabbage = fromShelleyLedgerExamplesPraos ledgerExamplesBabbage
267266
examplesConway :: Examples StandardConwayBlock
268267
examplesConway = fromShelleyLedgerExamplesPraos ledgerExamplesConway
269268

270-
exampleShelleyLedgerConfig :: forall era. ShelleyBasedEra era => TranslationContext era -> ShelleyLedgerConfig era
269+
exampleShelleyLedgerConfig :: TranslationContext era -> ShelleyLedgerConfig era
271270
exampleShelleyLedgerConfig translationContext = ShelleyLedgerConfig {
272271
shelleyLedgerCompactGenesis = compactGenesis testShelleyGenesis
273272
, shelleyLedgerGlobals = SL.mkShelleyGlobals
274-
(testShelleyGenesis @(EraCrypto era))
273+
testShelleyGenesis
275274
epochInfo
276275
, shelleyLedgerTranslationContext = translationContext
277276
}

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

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@
1111
module Test.Consensus.Shelley.Generators (SomeResult (..)) where
1212

1313
import Cardano.Ledger.Core (TranslationContext, toTxSeq)
14-
import Cardano.Ledger.Crypto (Crypto)
1514
import Cardano.Ledger.Genesis
1615
import qualified Cardano.Ledger.Shelley.API as SL
1716
import Cardano.Ledger.Shelley.Translation
@@ -223,16 +222,14 @@ instance ShelleyBasedEra era
223222

224223
-- | Generate a 'ShelleyLedgerConfig' with a fixed 'EpochInfo' (see
225224
-- 'arbitraryGlobalsWithFixedEpochInfo').
226-
instance ( Crypto (EraCrypto era)
227-
, Arbitrary (TranslationContext era)
225+
instance ( Arbitrary (TranslationContext era)
228226
) => Arbitrary (ShelleyLedgerConfig era) where
229227
arbitrary = ShelleyLedgerConfig
230228
<$> arbitrary
231229
<*> arbitraryGlobalsWithFixedEpochInfo
232230
<*> arbitrary
233231

234-
instance ( Crypto c
235-
) => Arbitrary (CompactGenesis c) where
232+
instance Arbitrary CompactGenesis where
236233
arbitrary = compactGenesis <$> arbitrary
237234

238235
-- | Generate 'Globals' with a fixed 'EpochInfo'. A fixed 'EpochInfo' is
@@ -258,7 +255,7 @@ arbitraryFixedEpochInfo = fixedEpochInfo <$> arbitrary <*> arbitrary
258255
instance Arbitrary (NoGenesis era) where
259256
arbitrary = pure NoGenesis
260257

261-
instance Crypto c => Arbitrary (FromByronTranslationContext c) where
258+
instance Arbitrary FromByronTranslationContext where
262259
arbitrary = FromByronTranslationContext <$> arbitrary <*> arbitrary <*> arbitrary
263260

264261
{-------------------------------------------------------------------------------

ouroboros-consensus-cardano/test/shelley-test/Test/ThreadNet/Shelley.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ import qualified Ouroboros.Consensus.Shelley.Ledger as Shelley
3131
import Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol ()
3232
import Ouroboros.Consensus.Shelley.Node
3333
import Ouroboros.Consensus.Shelley.ShelleyHFC ()
34-
import Test.Consensus.Shelley.MockCrypto (MockCrypto, MockShelley)
34+
import Test.Consensus.Shelley.MockCrypto (MockCrypto)
3535
import Test.QuickCheck
3636
import Test.Tasty
3737
import Test.Tasty.QuickCheck

ouroboros-consensus-diffusion/test/consensus-test/Test/Consensus/HardFork/Combinator/A.hs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ module Test.Consensus.HardFork.Combinator.A (
3838
, TxId (..)
3939
) where
4040

41-
import Cardano.Ledger.BaseTypes (unNonZero)
41+
import Cardano.Ledger.BaseTypes.NonZero
4242
import Cardano.Slotting.EpochInfo
4343
import Codec.Serialise
4444
import Control.Monad (guard)
@@ -201,6 +201,13 @@ data PartialLedgerConfigA = LCfgA {
201201
deriving Serialise
202202

203203
deriving newtype instance Serialise SecurityParam
204+
instance (HasZero a, Serialise a) => Serialise (NonZero a) where
205+
encode = encode . unNonZero
206+
decode = do
207+
a <- decode
208+
case nonZero a of
209+
Nothing -> fail "Expected non zero but found zero!"
210+
Just a' -> pure a'
204211

205212
type instance LedgerCfg (LedgerState BlockA) =
206213
(EpochInfo Identity, PartialLedgerConfigA)

ouroboros-consensus/ouroboros-consensus.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -391,8 +391,8 @@ library unstable-consensus-testlib
391391
bytestring,
392392
cardano-binary:testlib,
393393
cardano-crypto-class,
394-
cardano-ledger-core,
395394
cardano-ledger-binary:testlib,
395+
cardano-ledger-core,
396396
cardano-prelude,
397397
cardano-slotting:testlib,
398398
cardano-strict-containers,

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Config/SecurityParam.hs

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,10 +2,12 @@
22
{-# LANGUAGE DerivingVia #-}
33
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
44

5+
{-# OPTIONS_GHC -Wno-orphans #-}
6+
57
module Ouroboros.Consensus.Config.SecurityParam (SecurityParam (..)) where
68

79
import Cardano.Binary
8-
import Cardano.Ledger.BaseTypes (NonZero)
10+
import Cardano.Ledger.BaseTypes.NonZero
911
import Data.Word
1012
import GHC.Generics (Generic)
1113
import NoThunks.Class (NoThunks)
@@ -23,3 +25,13 @@ import Quiet
2325
newtype SecurityParam = SecurityParam { maxRollbacks :: NonZero Word64 }
2426
deriving (Eq, Generic, NoThunks, ToCBOR, FromCBOR)
2527
deriving Show via Quiet SecurityParam
28+
29+
instance ToCBOR a => ToCBOR (NonZero a) where
30+
toCBOR = toCBOR . unNonZero
31+
32+
instance (HasZero a, FromCBOR a) => FromCBOR (NonZero a) where
33+
fromCBOR = do
34+
a <- fromCBOR
35+
case nonZero a of
36+
Nothing -> fail "Non zero expected but zero found!"
37+
Just a' -> pure a'

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/Combinator/Embed/Nary.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -165,7 +165,7 @@ instance Inject I where
165165
inject = injectNS' (Proxy @I) . forgetInjectionIndex
166166

167167
instance Inject (K a) where
168-
inject _ _ (K a) = K a
168+
inject _ (K a) = K a
169169

170170
instance Inject Header where
171171
inject = injectNS' (Proxy @Header) . forgetInjectionIndex

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Ledger/Query/Version.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,4 +27,4 @@ nodeToClientVersionToQueryVersion x = case x of
2727
NodeToClientV_17 -> QueryVersion2
2828
NodeToClientV_18 -> QueryVersion2
2929
NodeToClientV_19 -> QueryVersion2
30-
NodeToClienvV_20 -> QueryVersion3
30+
NodeToClientV_20 -> QueryVersion3

0 commit comments

Comments
 (0)