Skip to content

Commit

Permalink
deduplicate fromShelleyGenesis
Browse files Browse the repository at this point in the history
  • Loading branch information
rrruko committed Dec 18, 2023
1 parent bd68a8e commit 0306ce8
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 56 deletions.
54 changes: 0 additions & 54 deletions hydra-node/src/Hydra/Chain/Offline.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
module Hydra.Chain.Offline (
withOfflineChain,
loadGlobalsFromGenesis,
loadState,
) where

Expand Down Expand Up @@ -152,56 +151,3 @@ loadState tracer persistence defaultChainState = do
pure (headState, chainStateHistory)
where
initialState = Idle IdleState{chainState = defaultChainState}

loadGlobalsFromGenesis :: Maybe FilePath -> IO Shelley.Globals
loadGlobalsFromGenesis ledgerGenesisFile = do
shelleyGenesis <- case ledgerGenesisFile of
Nothing -> pure Nothing
Just filePath -> Just <$> readJsonFileThrow (parseJSON @(Ledger.ShelleyGenesis StandardCrypto)) filePath
systemStart <- maybe (SystemStart <$> getCurrentTime) (pure . SystemStart . Ledger.sgSystemStart) shelleyGenesis

let genesisParameters = fromShelleyGenesis <$> shelleyGenesis

globals <-
maybe
(pure $ defaultGlobals{Ledger.systemStart = systemStart})
newGlobals
genesisParameters

pure globals

-- | Taken from Cardano.Api.GenesisParameters, a private module in cardano-api
fromShelleyGenesis :: Shelley.ShelleyGenesis Ledger.StandardCrypto -> GenesisParameters ShelleyEra
fromShelleyGenesis
sg@Shelley.ShelleyGenesis
{ Shelley.sgSystemStart
, Shelley.sgNetworkMagic
, Shelley.sgActiveSlotsCoeff
, Shelley.sgSecurityParam
, Shelley.sgEpochLength
, Shelley.sgSlotsPerKESPeriod
, Shelley.sgMaxKESEvolutions
, Shelley.sgSlotLength
, Shelley.sgUpdateQuorum
, Shelley.sgMaxLovelaceSupply
, Shelley.sgGenDelegs = _ -- unused, might be of interest
, Shelley.sgInitialFunds = _ -- unused, not retained by the node
, Shelley.sgStaking = _ -- unused, not retained by the node
} =
GenesisParameters
{ protocolParamSystemStart = sgSystemStart
, protocolParamNetworkId = Shelley.fromNetworkMagic $ Shelley.NetworkMagic sgNetworkMagic
, protocolParamActiveSlotsCoefficient =
Ledger.unboundRational
sgActiveSlotsCoeff
, protocolParamSecurity = fromIntegral sgSecurityParam
, protocolParamEpochLength = sgEpochLength
, protocolParamSlotLength = Shelley.fromNominalDiffTimeMicro sgSlotLength
, protocolParamSlotsPerKESPeriod = fromIntegral sgSlotsPerKESPeriod
, protocolParamMaxKESEvolutions = fromIntegral sgMaxKESEvolutions
, protocolParamUpdateQuorum = fromIntegral sgUpdateQuorum
, protocolParamMaxLovelaceSupply =
Shelley.Lovelace
(fromIntegral sgMaxLovelaceSupply)
, protocolInitialUpdateableProtocolParameters = Shelley.sgProtocolParams sg
}
22 changes: 20 additions & 2 deletions hydra-node/src/Hydra/Node/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,14 +14,17 @@ import Hydra.Cardano.Api (
GenesisParameters (..),
ProtocolParametersConversionError,
ShelleyBasedEra (..),
StandardCrypto,
SystemStart (..),
toLedgerPParams,
)
import Hydra.Cardano.Api qualified as Shelley
import Hydra.Chain (maximumNumberOfParties)
import Hydra.Chain.CardanoClient (QueryPoint (..), queryGenesisParameters)
import Hydra.Chain.Direct (loadChainContext, mkTinyWallet, withDirectChain)
import Hydra.Chain.Direct.Fixture (defaultGlobals)
import Hydra.Chain.Direct.State (initialChainState)
import Hydra.Chain.Offline (loadGlobalsFromGenesis, loadState, withOfflineChain)
import Hydra.Chain.Offline (loadState, withOfflineChain)
import Hydra.HeadId (HeadId (..))
import Hydra.HeadLogic (
Environment (..),
Expand Down Expand Up @@ -205,7 +208,22 @@ identifyNode :: RunOptions -> RunOptions
identifyNode opt@RunOptions{verbosity = Verbose "HydraNode", nodeId} = opt{OnlineOptions.verbosity = Verbose $ "HydraNode-" <> show nodeId}
identifyNode opt = opt

-- TODO: export from cardano-api
loadGlobalsFromGenesis :: Maybe FilePath -> IO Shelley.Globals
loadGlobalsFromGenesis ledgerGenesisFile = do
shelleyGenesis <- case ledgerGenesisFile of
Nothing -> pure Nothing
Just filePath -> Just <$> readJsonFileThrow (parseJSON @(Ledger.ShelleyGenesis StandardCrypto)) filePath
systemStart <- maybe (SystemStart <$> getCurrentTime) (pure . SystemStart . Ledger.sgSystemStart) shelleyGenesis

let genesisParameters = fromShelleyGenesis <$> shelleyGenesis

globals <-
maybe
(pure $ defaultGlobals{Ledger.systemStart = systemStart})
newGlobals
genesisParameters

pure globals

-- | Taken from Cardano.Api.GenesisParameters, a private module in cardano-api
fromShelleyGenesis :: Shelley.ShelleyGenesis Ledger.StandardCrypto -> GenesisParameters Shelley.ShelleyEra
Expand Down

0 comments on commit 0306ce8

Please sign in to comment.