Skip to content

Commit 9e9d418

Browse files
committed
ThreadNet: move the validateGenesis` helper function
1 parent ef0881d commit 9e9d418

File tree

3 files changed

+17
-14
lines changed

3 files changed

+17
-14
lines changed

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ import Ouroboros.Consensus.Protocol.TPraos
4343
import Ouroboros.Consensus.Shelley.Ledger
4444
import Ouroboros.Consensus.Shelley.Ledger.Inspect ()
4545
import Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion ()
46+
import Ouroboros.Consensus.Shelley.Node.Common (validateGenesis)
4647
import Ouroboros.Consensus.Shelley.Node.DiffusionPipelining ()
4748
import Ouroboros.Consensus.Shelley.Node.Serialisation ()
4849
import Ouroboros.Consensus.Shelley.Node.TPraos

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

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE FlexibleInstances #-}
44
{-# LANGUAGE GADTs #-}
55
{-# LANGUAGE MultiParamTypeClasses #-}
6+
{-# LANGUAGE OverloadedStrings #-}
67
{-# LANGUAGE PolyKinds #-}
78
{-# LANGUAGE TypeFamilies #-}
89
{-# LANGUAGE TypeOperators #-}
@@ -17,13 +18,16 @@ module Ouroboros.Consensus.Shelley.Node.Common
1718
, ShelleyEraWithCrypto
1819
, ShelleyLeaderCredentials (..)
1920
, shelleyBlockIssuerVKey
21+
, validateGenesis
2022
) where
2123

2224
import Cardano.Ledger.BaseTypes (unNonZero)
2325
import qualified Cardano.Ledger.Keys as SL
2426
import qualified Cardano.Ledger.Shelley.API as SL
2527
import Cardano.Ledger.Slot
28+
import Data.Bifunctor (first)
2629
import Data.Text (Text)
30+
import qualified Data.Text as Text
2731
import Ouroboros.Consensus.Block
2832
( CannotForge
2933
, ForgeStateInfo
@@ -134,3 +138,14 @@ data ProtocolParamsShelleyBased c = ProtocolParamsShelleyBased
134138
-- mutually incompatible.
135139
, shelleyBasedLeaderCredentials :: [ShelleyLeaderCredentials c]
136140
}
141+
142+
-- | Check the validity of the genesis config. To be used in conjunction with
143+
-- 'assertWithMsg'.
144+
validateGenesis :: SL.ShelleyGenesis -> Either String ()
145+
validateGenesis = first errsToString . SL.validateGenesis
146+
where
147+
errsToString :: [SL.ValidationErr] -> String
148+
errsToString errs =
149+
Text.unpack $
150+
Text.unlines
151+
("Invalid genesis config:" : map SL.describeValidationErr errs)

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

Lines changed: 1 addition & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,6 @@ module Ouroboros.Consensus.Shelley.Node.TPraos
2727
, protocolInfoTPraosShelleyBased
2828
, shelleyBlockForging
2929
, shelleySharedBlockForging
30-
, validateGenesis
3130
) where
3231

3332
import Cardano.Crypto.Hash (Hash)
@@ -44,9 +43,7 @@ import Cardano.Slotting.EpochInfo
4443
import Cardano.Slotting.Time (mkSlotLength)
4544
import Control.Monad.Except (Except)
4645
import qualified Control.Tracer as Tracer
47-
import Data.Bifunctor (first)
4846
import qualified Data.Text as T
49-
import qualified Data.Text as Text
5047
import Lens.Micro ((^.))
5148
import Ouroboros.Consensus.Block
5249
import Ouroboros.Consensus.Config
@@ -72,6 +69,7 @@ import Ouroboros.Consensus.Shelley.Node.Common
7269
, ShelleyEraWithCrypto
7370
, ShelleyLeaderCredentials (..)
7471
, shelleyBlockIssuerVKey
72+
, validateGenesis
7573
)
7674
import Ouroboros.Consensus.Shelley.Node.Serialisation ()
7775
import Ouroboros.Consensus.Shelley.Protocol.TPraos ()
@@ -154,17 +152,6 @@ shelleySharedBlockForging hotKey slotToPeriod credentials =
154152
ProtocolInfo
155153
-------------------------------------------------------------------------------}
156154

157-
-- | Check the validity of the genesis config. To be used in conjunction with
158-
-- 'assertWithMsg'.
159-
validateGenesis :: SL.ShelleyGenesis -> Either String ()
160-
validateGenesis = first errsToString . SL.validateGenesis
161-
where
162-
errsToString :: [SL.ValidationErr] -> String
163-
errsToString errs =
164-
Text.unpack $
165-
Text.unlines
166-
("Invalid genesis config:" : map SL.describeValidationErr errs)
167-
168155
protocolInfoShelley ::
169156
forall m c.
170157
( IOLike m

0 commit comments

Comments
 (0)