Skip to content

Commit

Permalink
Merge #3832
Browse files Browse the repository at this point in the history
3832: add genesis create-cardano command r=disassembler a=cleverca22

* combines generation of byron and shelley eras genesis
* auto generates a config based on a node config template
* slot timing and start time parameters override template
* generates all keys in byron era and converts to shelley era

fixed #3798 

Co-authored-by: Samuel Leathers <samuel.leathers@iohk.io>
  • Loading branch information
iohk-bors[bot] and disassembler authored May 3, 2022
2 parents 8cd2090 + 7eb2159 commit c7cd1e4
Show file tree
Hide file tree
Showing 10 changed files with 393 additions and 47 deletions.
9 changes: 7 additions & 2 deletions cardano-api/cardano-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,12 @@ common project-config
-Wredundant-constraints
-Wunused-packages

common maybe-unix
if !os(windows)
build-depends: unix

library
import: base, project-config
import: base, project-config, maybe-unix

hs-source-dirs: src

Expand All @@ -42,6 +46,7 @@ library
-- we create wrapper types for the ledger types
-- in this module
Cardano.Api.Orphans
Cardano.Api.SerialiseTextEnvelope

other-modules:
-- Splitting up the big Typed module:
Expand Down Expand Up @@ -75,7 +80,6 @@ library
Cardano.Api.SerialiseJSON
Cardano.Api.SerialiseLedgerCddl
Cardano.Api.SerialiseRaw
Cardano.Api.SerialiseTextEnvelope
Cardano.Api.SerialiseUsing
Cardano.Api.Shelley.Genesis
Cardano.Api.SpecialByron
Expand Down Expand Up @@ -124,6 +128,7 @@ library
, memory
, network
, nothunks
, optparse-applicative-fork
, ouroboros-consensus
, ouroboros-consensus-byron
, ouroboros-consensus-cardano
Expand Down
6 changes: 4 additions & 2 deletions cardano-api/src/Cardano/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -559,7 +559,7 @@ module Cardano.Api (
mkLocalNodeClientParams,
LocalChainSyncClient(..),
CardanoMode,
-- connectToRemoteNode,
-- connectToRemoteNode,

-- *** Chain sync protocol
-- | To construct a @ChainSyncClient@ see @Cardano.Api.Client@ or
Expand Down Expand Up @@ -663,7 +663,9 @@ module Cardano.Api (

chainPointToSlotNo,
chainPointToHeaderHash,
makeChainTip
makeChainTip,
parseFilePath,
writeSecrets

) where

Expand Down
50 changes: 48 additions & 2 deletions cardano-api/src/Cardano/Api/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,24 +1,44 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE CPP #-}

#if !defined(mingw32_HOST_OS)
#define UNIX
#endif

-- | Internal utils for the other Api modules
--
module Cardano.Api.Utils
( (?!)
, (?!.)
, formatParsecError
, noInlineMaybeToStrictMaybe
, runParsecParser
, failEither
, failEitherWith
, noInlineMaybeToStrictMaybe
, note
, parseFilePath
, runParsecParser
, writeSecrets
) where

import Prelude

import Control.Monad (forM_)
import qualified Data.Aeson.Types as Aeson
import qualified Data.ByteString as BS
import Data.Maybe.Strict
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Text.Parsec as Parsec
import qualified Text.Parsec.String as Parsec
import qualified Text.ParserCombinators.Parsec.Error as Parsec
import Text.Printf (printf)
import qualified Options.Applicative as Opt
import System.FilePath ((</>))
#ifdef UNIX
import System.Posix.Files (ownerReadMode, setFileMode)
#else
import System.Directory (emptyPermissions, readable, setPermissions)
#endif

(?!) :: Maybe a -> e -> Either e a
Nothing ?! e = Left e
Expand Down Expand Up @@ -50,3 +70,29 @@ failEither = either fail pure

failEitherWith :: MonadFail m => (e -> String) -> Either e a -> m a
failEitherWith f = either (fail . f) pure

note :: MonadFail m => String -> Maybe a -> m a
note msg = \case
Nothing -> fail msg
Just a -> pure a

parseFilePath :: String -> String -> Opt.Parser FilePath
parseFilePath optname desc =
Opt.strOption
( Opt.long optname
<> Opt.metavar "FILEPATH"
<> Opt.help desc
<> Opt.completer (Opt.bashCompleter "file")
)

writeSecrets :: FilePath -> [Char] -> [Char] -> (a -> BS.ByteString) -> [a] -> IO ()
writeSecrets outDir prefix suffix secretOp xs =
forM_ (zip xs [0::Int ..]) $
\(secret, nr)-> do
let filename = outDir </> prefix <> "." <> printf "%03d" nr <> "." <> suffix
BS.writeFile filename $ secretOp secret
#ifdef UNIX
setFileMode filename ownerReadMode
#else
setPermissions filename (emptyPermissions {readable = True})
#endif
2 changes: 1 addition & 1 deletion cardano-cli/cardano-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,6 @@ common maybe-Win32

library
import: base, project-config
, maybe-unix
, maybe-Win32

if flag(unexpected_thunks)
Expand Down Expand Up @@ -102,6 +101,7 @@ library
, binary
, bytestring
, base16-bytestring >= 1.0
, canonical-json
, cardano-api
, cardano-binary
, cardano-git-rev
Expand Down
26 changes: 1 addition & 25 deletions cardano-cli/src/Cardano/CLI/Byron/Genesis.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}

#if !defined(mingw32_HOST_OS)
#define UNIX
#endif

module Cardano.CLI.Byron.Genesis
( ByronGenesisError(..)
Expand All @@ -20,22 +16,14 @@ import Cardano.Prelude hiding (option, show, trace)
import Prelude (String)

import Control.Monad.Trans.Except.Extra (firstExceptT, left, right)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LB
import qualified Data.Map.Strict as Map
import Data.Text.Lazy.Builder (toLazyText)
import Data.Time (UTCTime)
import Formatting.Buildable
import Text.Printf (printf)

import System.Directory (createDirectory, doesPathExist)
import System.FilePath ((</>))
#ifdef UNIX
import System.Posix.Files (ownerReadMode, setFileMode)
#else
import System.Directory (emptyPermissions, readable, setPermissions)
#endif
import Cardano.Api (Key (..), NetworkId)
import Cardano.Api (Key (..), NetworkId, writeSecrets)
import Cardano.Api.Byron (ByronKey, SerialiseAsRawBytes (..), SigningKey (..),
toByronRequiresNetworkMagic)

Expand Down Expand Up @@ -217,15 +205,3 @@ dumpGenesis (NewDirectory outDir) genesisData gs = do

wOut :: String -> String -> (a -> ByteString) -> [a] -> IO ()
wOut = writeSecrets outDir

writeSecrets :: FilePath -> String -> String -> (a -> ByteString) -> [a] -> IO ()
writeSecrets outDir prefix suffix secretOp xs =
forM_ (zip xs [0::Int ..]) $
\(secret, nr)-> do
let filename = outDir </> prefix <> "." <> printf "%03d" nr <> "." <> suffix
BS.writeFile filename $ secretOp secret
#ifdef UNIX
setFileMode filename ownerReadMode
#else
setPermissions filename (emptyPermissions {readable = True})
#endif
9 changes: 0 additions & 9 deletions cardano-cli/src/Cardano/CLI/Byron/Parsers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -744,15 +744,6 @@ readDouble = do
when (f > 1) $ readerError "fraction must be <= 1"
return f

parseFilePath :: String -> String -> Parser FilePath
parseFilePath optname desc =
strOption
( long optname
<> metavar "FILEPATH"
<> help desc
<> completer (bashCompleter "file")
)

parseSigningKeyFile :: String -> String -> Parser SigningKeyFile
parseSigningKeyFile opt desc = SigningKeyFile <$> parseFilePath opt desc

Expand Down
3 changes: 3 additions & 0 deletions cardano-cli/src/Cardano/CLI/Shelley/Commands.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ import Cardano.CLI.Shelley.Key (PaymentVerifier, StakeVerifier, Verifi
import Cardano.CLI.Types

import Cardano.Ledger.Shelley.TxBody (MIRPot)
import Cardano.Chain.Common (BlockCount)
--
-- Shelley CLI command data types
--
Expand Down Expand Up @@ -416,6 +417,7 @@ renderTextViewCmd (TextViewInfo _ _) = "text-view decode-cbor"

data GenesisCmd
= GenesisCreate GenesisDir Word Word (Maybe SystemStart) (Maybe Lovelace) NetworkId
| GenesisCreateCardano GenesisDir Word Word (Maybe SystemStart) (Maybe Lovelace) BlockCount Word Rational NetworkId FilePath FilePath FilePath (Maybe FilePath)
| GenesisCreateStaked GenesisDir Word Word Word Word (Maybe SystemStart) (Maybe Lovelace) Lovelace NetworkId Word Word Word
| GenesisKeyGenGenesis VerificationKeyFile SigningKeyFile
| GenesisKeyGenDelegate VerificationKeyFile SigningKeyFile OpCertCounterFile
Expand All @@ -431,6 +433,7 @@ renderGenesisCmd :: GenesisCmd -> Text
renderGenesisCmd cmd =
case cmd of
GenesisCreate {} -> "genesis create"
GenesisCreateCardano {} -> "genesis create-cardano"
GenesisCreateStaked {} -> "genesis create-staked"
GenesisKeyGenGenesis {} -> "genesis key-gen-genesis"
GenesisKeyGenDelegate {} -> "genesis key-gen-delegate"
Expand Down
62 changes: 60 additions & 2 deletions cardano-cli/src/Cardano/CLI/Shelley/Parsers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ import Cardano.CLI.Shelley.Key (InputFormat (..), PaymentVerifier (..)
StakeVerifier (..), VerificationKeyOrFile (..), VerificationKeyOrHashOrFile (..),
VerificationKeyTextOrFile (..), deserialiseInput, renderInputDecodeError)
import Cardano.CLI.Types
import Cardano.Chain.Common (BlockCount(BlockCount))

{- HLINT ignore "Use <$>" -}

Expand Down Expand Up @@ -1101,6 +1102,10 @@ pGenesisCmd =
, subParser "initial-txin"
(Opt.info pGenesisTxIn $
Opt.progDesc "Get the TxIn for an initial UTxO based on the verification key")
, subParser "create-cardano"
(Opt.info pGenesisCreateCardano $
Opt.progDesc ("Create a Byron and Shelley genesis file from a genesis "
++ "template and genesis/delegation/spending keys."))
, subParser "create"
(Opt.info pGenesisCreate $
Opt.progDesc ("Create a Shelley genesis file from a genesis "
Expand Down Expand Up @@ -1144,6 +1149,28 @@ pGenesisCmd =
pGenesisTxIn =
GenesisTxIn <$> pVerificationKeyFile Input <*> pNetworkId <*> pMaybeOutputFile

pGenesisCreateCardano :: Parser GenesisCmd
pGenesisCreateCardano =
GenesisCreateCardano <$> pGenesisDir
<*> pGenesisNumGenesisKeys
<*> pGenesisNumUTxOKeys
<*> pMaybeSystemStart
<*> pInitialSupplyNonDelegated
<*> (BlockCount <$> pSecurityParam)
<*> pSlotLength
<*> pSlotCoefficient
<*> pNetworkId
<*> parseFilePath
"byron-template"
"JSON file with genesis defaults for each byron."
<*> parseFilePath
"shelley-template"
"JSON file with genesis defaults for each shelley."
<*> parseFilePath
"alonzo-template"
"JSON file with genesis defaults for each alonzo."
<*> pNodeConfigTemplate

pGenesisCreate :: Parser GenesisCmd
pGenesisCreate =
GenesisCreate <$> pGenesisDir
Expand Down Expand Up @@ -1197,10 +1224,13 @@ pGenesisCmd =
Opt.option Opt.auto
( Opt.long "gen-genesis-keys"
<> Opt.metavar "INT"
<> Opt.help "The number of genesis keys to make [default is 0]."
<> Opt.value 0
<> Opt.help "The number of genesis keys to make [default is 3]."
<> Opt.value 3
)

pNodeConfigTemplate :: Parser (Maybe FilePath)
pNodeConfigTemplate = optional $ parseFilePath "node-config-template" "the node config template"

pGenesisNumUTxOKeys :: Parser Word
pGenesisNumUTxOKeys =
Opt.option Opt.auto
Expand Down Expand Up @@ -1261,6 +1291,34 @@ pGenesisCmd =
<> Opt.value 0
)

pSecurityParam :: Parser Word64
pSecurityParam =
Opt.option Opt.auto
( Opt.long "security-param"
<> Opt.metavar "INT"
<> Opt.help "Security parameter for genesis file [default is 108]."
<> Opt.value 108
)

pSlotLength :: Parser Word
pSlotLength =
Opt.option Opt.auto
( Opt.long "slot-length"
<> Opt.metavar "INT"
<> Opt.help "slot length (ms) parameter for genesis file [default is 1000]."
<> Opt.value 1000
)


pSlotCoefficient :: Parser Rational
pSlotCoefficient =
Opt.option readRationalUnitInterval
( Opt.long "slot-coefficient"
<> Opt.metavar "RATIONAL"
<> Opt.help "Slot Coefficient for genesis file [default is .05]."
<> Opt.value 0.05
)

pBulkPoolCredFiles :: Parser Word
pBulkPoolCredFiles =
Opt.option Opt.auto
Expand Down
Loading

0 comments on commit c7cd1e4

Please sign in to comment.