@@ -23,7 +23,7 @@ module Cardano.CLI.Shelley.Run.Genesis
23
23
) where
24
24
25
25
import Cardano.Prelude hiding (unlines )
26
- import Prelude (error , id , unlines , zip3 )
26
+ import Prelude (String , error , id , unlines , zip3 )
27
27
28
28
import Data.Aeson hiding (Key )
29
29
import qualified Data.Aeson as Aeson
@@ -92,12 +92,12 @@ import Cardano.CLI.Shelley.Run.StakeAddress (ShelleyStakeAddressCmdErr
92
92
renderShelleyStakeAddressCmdError , runStakeAddressKeyGenToFile )
93
93
import Cardano.CLI.Types
94
94
95
- import Cardano.CLI.Byron.Delegation
96
- import Cardano.CLI.Byron.Genesis as Byron
97
- import qualified Cardano.CLI.Byron.Key as Byron
98
95
import qualified Cardano.Chain.Common as Byron (KeyHash , mkKnownLovelace , rationalToLovelacePortion )
99
96
import Cardano.Chain.Genesis (FakeAvvmOptions (.. ), TestnetBalanceOptions (.. ),
100
97
gdProtocolParameters , gsDlgIssuersSecrets , gsPoorSecrets , gsRichSecrets )
98
+ import Cardano.CLI.Byron.Delegation
99
+ import Cardano.CLI.Byron.Genesis as Byron
100
+ import qualified Cardano.CLI.Byron.Key as Byron
101
101
import qualified Cardano.Crypto.Signing as Byron
102
102
103
103
import Cardano.Api.SerialiseTextEnvelope (textEnvelopeToJSON )
@@ -115,8 +115,8 @@ import Data.ListMap (ListMap (..))
115
115
116
116
import qualified Cardano.CLI.IO.Lazy as Lazy
117
117
118
- import System.Random (StdGen )
119
118
import qualified System.Random as Random
119
+ import System.Random (StdGen )
120
120
121
121
data ShelleyGenesisCmdError
122
122
= ShelleyGenesisCmdAesonDecodeError ! FilePath ! Text
@@ -136,6 +136,8 @@ data ShelleyGenesisCmdError
136
136
| ShelleyGenesisCmdStakeAddressCmdError ! ShelleyStakeAddressCmdError
137
137
| ShelleyGenesisCmdCostModelsError ! FilePath
138
138
| ShelleyGenesisCmdByronError ! ByronGenesisError
139
+ | ShelleyGenesisStakePoolRelayFileError ! FilePath ! IOException
140
+ | ShelleyGenesisStakePoolRelayJsonDecodeError ! FilePath ! String
139
141
deriving Show
140
142
141
143
instance Error ShelleyGenesisCmdError where
@@ -176,6 +178,12 @@ instance Error ShelleyGenesisCmdError where
176
178
" Error: " <> Text. unpack e
177
179
ShelleyGenesisCmdGenesisFileReadError e -> displayError e
178
180
ShelleyGenesisCmdByronError e -> show e
181
+ ShelleyGenesisStakePoolRelayFileError fp e ->
182
+ " Error occurred while reading the stake pool relay specification file: " <> fp <>
183
+ " Error: " <> show e
184
+ ShelleyGenesisStakePoolRelayJsonDecodeError fp e ->
185
+ " Error occurred while decoding the stake pool relay specification file: " <> fp <>
186
+ " Error: " <> e
179
187
180
188
runGenesisCmd :: GenesisCmd -> ExceptT ShelleyGenesisCmdError IO ()
181
189
runGenesisCmd (GenesisKeyGenGenesis vk sk) = runGenesisKeyGenGenesis vk sk
@@ -187,7 +195,8 @@ runGenesisCmd (GenesisTxIn vk nw mOutFile) = runGenesisTxIn vk nw mOutFile
187
195
runGenesisCmd (GenesisAddr vk nw mOutFile) = runGenesisAddr vk nw mOutFile
188
196
runGenesisCmd (GenesisCreate gd gn un ms am nw) = runGenesisCreate gd gn un ms am nw
189
197
runGenesisCmd (GenesisCreateCardano gd gn un ms am k slotLength sc nw bg sg ag mNodeCfg) = runGenesisCreateCardano gd gn un ms am k slotLength sc nw bg sg ag mNodeCfg
190
- runGenesisCmd (GenesisCreateStaked gd gn gp gl un ms am ds nw bf bp su) = runGenesisCreateStaked gd gn gp gl un ms am ds nw bf bp su
198
+ runGenesisCmd (GenesisCreateStaked gd gn gp gl un ms am ds nw bf bp su relayJsonFp) =
199
+ runGenesisCreateStaked gd gn gp gl un ms am ds nw bf bp su relayJsonFp
191
200
runGenesisCmd (GenesisHashFile gf) = runGenesisHashFile gf
192
201
193
202
--
@@ -661,11 +670,13 @@ runGenesisCreateStaked
661
670
-> Word -- ^ bulk credential files to write
662
671
-> Word -- ^ pool credentials per bulk file
663
672
-> Word -- ^ num stuffed UTxO entries
673
+ -> Maybe FilePath -- ^ Specified stake pool relays
664
674
-> ExceptT ShelleyGenesisCmdError IO ()
665
675
runGenesisCreateStaked (GenesisDir rootdir)
666
676
genNumGenesisKeys genNumUTxOKeys genNumPools genNumStDelegs
667
677
mStart mNonDlgAmount stDlgAmount network
668
- bulkPoolCredFiles bulkPoolsPerFile numStuffedUtxo = do
678
+ numBulkPoolCredFiles bulkPoolsPerFile numStuffedUtxo
679
+ sPoolRelayFp = do
669
680
liftIO $ do
670
681
createDirectoryIfMissing False rootdir
671
682
createDirectoryIfMissing False gendir
@@ -678,31 +689,39 @@ runGenesisCreateStaked (GenesisDir rootdir)
678
689
alonzoGenesis <- readAlonzoGenesis (rootdir </> " genesis.alonzo.spec.json" )
679
690
680
691
forM_ [ 1 .. genNumGenesisKeys ] $ \ index -> do
681
- createGenesisKeys gendir index
692
+ createGenesisKeys gendir index
682
693
createDelegateKeys deldir index
683
694
684
695
forM_ [ 1 .. genNumUTxOKeys ] $ \ index ->
685
696
createUtxoKeys utxodir index
686
697
687
- pools <- forM [ 1 .. genNumPools ] $ \ index -> do
698
+ mayStakePoolRelays
699
+ <- forM sPoolRelayFp $
700
+ \ fp -> do
701
+ relaySpecJsonBs <-
702
+ handleIOExceptT (ShelleyGenesisStakePoolRelayFileError fp) (LBS. readFile fp)
703
+ firstExceptT (ShelleyGenesisStakePoolRelayJsonDecodeError fp)
704
+ . hoistEither $ Aeson. eitherDecode relaySpecJsonBs
705
+
706
+ poolParams <- forM [ 1 .. genNumPools ] $ \ index -> do
688
707
createPoolCredentials pooldir index
689
- buildPool network pooldir index
708
+ buildPoolParams network pooldir index (fromMaybe mempty mayStakePoolRelays)
690
709
691
- when (bulkPoolCredFiles * bulkPoolsPerFile > genNumPools) $
692
- left $ ShelleyGenesisCmdTooFewPoolsForBulkCreds genNumPools bulkPoolCredFiles bulkPoolsPerFile
710
+ when (numBulkPoolCredFiles * bulkPoolsPerFile > genNumPools) $
711
+ left $ ShelleyGenesisCmdTooFewPoolsForBulkCreds genNumPools numBulkPoolCredFiles bulkPoolsPerFile
693
712
-- We generate the bulk files for the last pool indices,
694
713
-- so that all the non-bulk pools have stable indices at beginning:
695
- let bulkOffset = fromIntegral $ genNumPools - bulkPoolCredFiles * bulkPoolsPerFile
714
+ let bulkOffset = fromIntegral $ genNumPools - numBulkPoolCredFiles * bulkPoolsPerFile
696
715
bulkIndices :: [Word ] = [ 1 + bulkOffset .. genNumPools ]
697
716
bulkSlices :: [[Word ]] = List. chunksOf (fromIntegral bulkPoolsPerFile) bulkIndices
698
- forM_ (zip [ 1 .. bulkPoolCredFiles ] bulkSlices) $
717
+ forM_ (zip [ 1 .. numBulkPoolCredFiles ] bulkSlices) $
699
718
uncurry (writeBulkPoolCredentials pooldir)
700
719
701
720
let (delegsPerPool, delegsRemaining) = divMod genNumStDelegs genNumPools
702
721
delegsForPool poolIx = if delegsRemaining /= 0 && poolIx == genNumPools
703
722
then delegsPerPool
704
723
else delegsPerPool + delegsRemaining
705
- distribution = [pool | (pool, poolIx) <- zip pools [1 .. ], _ <- [1 .. delegsForPool poolIx]]
724
+ distribution = [pool | (pool, poolIx) <- zip poolParams [1 .. ], _ <- [1 .. delegsForPool poolIx]]
706
725
707
726
g <- Random. getStdGen
708
727
@@ -718,7 +737,7 @@ runGenesisCreateStaked (GenesisDir rootdir)
718
737
stuffedUtxoAddrs <- liftIO $ Lazy. replicateM (fromIntegral numStuffedUtxo) genStuffedAddress
719
738
720
739
let stake = second Ledger. _poolId . mkDelegationMapEntry <$> delegations
721
- stakePools = [ (Ledger. _poolId poolParams, poolParams) | poolParams <- snd . mkDelegationMapEntry <$> delegations ]
740
+ stakePools = [ (Ledger. _poolId poolParams' , poolParams' ) | poolParams' <- snd . mkDelegationMapEntry <$> delegations ]
722
741
delegAddrs = dInitialUtxoAddr <$> delegations
723
742
! shelleyGenesis =
724
743
updateCreateStakedOutputTemplate
@@ -741,13 +760,13 @@ runGenesisCreateStaked (GenesisDir rootdir)
741
760
] ++
742
761
[ mconcat
743
762
[ " , "
744
- , textShow bulkPoolCredFiles , " bulk pool credential files, "
763
+ , textShow numBulkPoolCredFiles , " bulk pool credential files, "
745
764
, textShow bulkPoolsPerFile, " pools per bulk credential file, indices starting from "
746
765
, textShow bulkOffset, " , "
747
766
, textShow $ length bulkIndices, " total pools in bulk nodes, each bulk node having this many entries: "
748
767
, textShow $ length <$> bulkSlices
749
768
]
750
- | bulkPoolCredFiles * bulkPoolsPerFile > 0 ]
769
+ | numBulkPoolCredFiles * bulkPoolsPerFile > 0 ]
751
770
752
771
where
753
772
adjustTemplate t = t { sgNetworkMagic = unNetworkMagic (toNetworkMagic network) }
@@ -861,19 +880,24 @@ data Delegation = Delegation
861
880
}
862
881
deriving (Generic , NFData )
863
882
864
- buildPool :: NetworkId -> FilePath -> Word -> ExceptT ShelleyGenesisCmdError IO (Ledger. PoolParams StandardCrypto )
865
- buildPool nw dir index = do
866
- StakePoolVerificationKey poolColdVK <- firstExceptT (ShelleyGenesisCmdPoolCmdError
867
- . ShelleyPoolCmdReadFileError )
868
- . newExceptT
869
- $ readFileTextEnvelope (AsVerificationKey AsStakePoolKey ) poolColdVKF
870
- VrfVerificationKey poolVrfVK <- firstExceptT (ShelleyGenesisCmdNodeCmdError
871
- . ShelleyNodeCmdReadFileError )
872
- . newExceptT
873
- $ readFileTextEnvelope (AsVerificationKey AsVrfKey ) poolVrfVKF
874
- rewardsSVK <- firstExceptT ShelleyGenesisCmdTextEnvReadFileError
875
- . newExceptT
876
- $ readFileTextEnvelope (AsVerificationKey AsStakeKey ) poolRewardVKF
883
+ buildPoolParams
884
+ :: NetworkId
885
+ -> FilePath -- ^ File directory where the necessary pool credentials were created
886
+ -> Word
887
+ -> Map Word [Ledger. StakePoolRelay ] -- ^ User submitted stake pool relay map
888
+ -> ExceptT ShelleyGenesisCmdError IO (Ledger. PoolParams StandardCrypto )
889
+ buildPoolParams nw dir index specifiedRelays = do
890
+ StakePoolVerificationKey poolColdVK
891
+ <- firstExceptT (ShelleyGenesisCmdPoolCmdError . ShelleyPoolCmdReadFileError )
892
+ . newExceptT $ readFileTextEnvelope (AsVerificationKey AsStakePoolKey ) poolColdVKF
893
+
894
+ VrfVerificationKey poolVrfVK
895
+ <- firstExceptT (ShelleyGenesisCmdNodeCmdError . ShelleyNodeCmdReadFileError )
896
+ . newExceptT $ readFileTextEnvelope (AsVerificationKey AsVrfKey ) poolVrfVKF
897
+ rewardsSVK
898
+ <- firstExceptT ShelleyGenesisCmdTextEnvReadFileError
899
+ . newExceptT $ readFileTextEnvelope (AsVerificationKey AsStakeKey ) poolRewardVKF
900
+
877
901
pure Ledger. PoolParams
878
902
{ Ledger. _poolId = Ledger. hashKey poolColdVK
879
903
, Ledger. _poolVrf = Ledger. hashVerKeyVRF poolVrfVK
@@ -883,10 +907,17 @@ buildPool nw dir index = do
883
907
, Ledger. _poolRAcnt =
884
908
toShelleyStakeAddr $ makeStakeAddress nw $ StakeCredentialByKey (verificationKeyHash rewardsSVK)
885
909
, Ledger. _poolOwners = mempty
886
- , Ledger. _poolRelays = Seq. empty
910
+ , Ledger. _poolRelays = lookupPoolRelay specifiedRelays
887
911
, Ledger. _poolMD = Ledger. SNothing
888
912
}
889
913
where
914
+ lookupPoolRelay
915
+ :: Map Word [Ledger. StakePoolRelay ] -> Seq. StrictSeq Ledger. StakePoolRelay
916
+ lookupPoolRelay m =
917
+ case Map. lookup index m of
918
+ Just spRelays -> Seq. fromList spRelays
919
+ Nothing -> mempty
920
+
890
921
strIndex = show index
891
922
poolColdVKF = dir </> " cold" ++ strIndex ++ " .vkey"
892
923
poolVrfVKF = dir </> " vrf" ++ strIndex ++ " .vkey"
@@ -903,12 +934,12 @@ writeBulkPoolCredentials dir bulkIx poolIxs = do
903
934
readPoolCreds :: Word -> ExceptT ShelleyGenesisCmdError IO
904
935
(TextEnvelope , TextEnvelope , TextEnvelope )
905
936
readPoolCreds ix = do
906
- (,,) <$> readEnvelope poolCert
937
+ (,,) <$> readEnvelope poolOpCert
907
938
<*> readEnvelope poolVrfSKF
908
939
<*> readEnvelope poolKesSKF
909
940
where
910
941
strIndex = show ix
911
- poolCert = dir </> " opcert" ++ strIndex ++ " .cert"
942
+ poolOpCert = dir </> " opcert" ++ strIndex ++ " .cert"
912
943
poolVrfSKF = dir </> " vrf" ++ strIndex ++ " .skey"
913
944
poolKesSKF = dir </> " kes" ++ strIndex ++ " .skey"
914
945
readEnvelope :: FilePath -> ExceptT ShelleyGenesisCmdError IO TextEnvelope
0 commit comments