Skip to content

Commit

Permalink
Rebase on master and add make converter work for Conway era
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Mar 27, 2023
1 parent 786d06c commit dd1ec95
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 12 deletions.
Expand Up @@ -3,7 +3,7 @@
module CardanoLedgerStateConverter.Parsers (parseCmdLine) where

import Options.Applicative
import Ouroboros.Consensus.Storage.LedgerDB.OnDisk (DiskSnapshot (..))
import Ouroboros.Consensus.Storage.LedgerDB (DiskSnapshot (..))
import Cardano.Tools.CardanoLedgerStateConverter.Types


Expand Down
Expand Up @@ -17,7 +17,7 @@ import Ouroboros.Consensus.Util.Orphans ()
import qualified Ouroboros.Consensus.Storage.ChainDB as ChainDB
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy
(SnapshotInterval (..), defaultDiskPolicy)
import Ouroboros.Consensus.Storage.LedgerDB.OnDisk (readSnapshot, DiskSnapshot (..))
import Ouroboros.Consensus.Storage.LedgerDB (readSnapshot, DiskSnapshot (..))

import Cardano.Tools.CardanoLedgerStateConverter.Types

Expand All @@ -29,7 +29,7 @@ import qualified Ouroboros.Consensus.Ledger.Extended as Consensus
import Ouroboros.Consensus.Shelley.Ledger (shelleyLedgerState)
import Ouroboros.Consensus.Shelley.Ledger.Config (CodecConfig (ShelleyCodecConfig))
import Ouroboros.Consensus.Byron.Ledger.Config (CodecConfig (ByronCodecConfig))
import Cardano.Binary (serialize')
import Cardano.Ledger.Binary.Plain (serialize')
import Cardano.Chain.Slotting (EpochSlots(..))
import qualified Data.ByteString as BS
import Cardano.Tools.DBAnalyser.Block.Cardano ()
Expand All @@ -47,6 +47,7 @@ projectNewEpochState extLedgerState =
Cardano.LedgerStateMary x -> f MaryEra x
Cardano.LedgerStateAlonzo x -> f AlonzoEra x
Cardano.LedgerStateBabbage x -> f BabbageEra x
Cardano.LedgerStateConway x -> f ConwayEra x
where
ledgerState :: Consensus.LedgerState (CardanoBlock StandardCrypto)
Consensus.ExtLedgerState {Consensus.ledgerState} = extLedgerState
Expand All @@ -67,7 +68,7 @@ convert Config{dbDir, snapShot} = do
Just ls -> BS.writeFile outputFilename (serialize' ls)

where
decodeExtLedgerState' :: forall s .Decoder s (ExtLedgerState (CardanoBlock StandardCrypto))
decodeExtLedgerState' :: forall s. Decoder s (ExtLedgerState (CardanoBlock StandardCrypto))
decodeExtLedgerState' =
let ccfg =
Cardano.CardanoCodecConfig
Expand All @@ -77,6 +78,7 @@ convert Config{dbDir, snapShot} = do
ShelleyCodecConfig
ShelleyCodecConfig
ShelleyCodecConfig
ShelleyCodecConfig
in decodeExtLedgerState
(decodeDisk @(CardanoBlock StandardCrypto) ccfg)
(decodeDisk @(CardanoBlock StandardCrypto) ccfg)
Expand Down
@@ -1,27 +1,29 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GADTs #-}

module Cardano.Tools.CardanoLedgerStateConverter.Types
( AnyShelleyEra (..)
, SomeNewEpochState (..)
module Cardano.Tools.CardanoLedgerStateConverter.Types (
AnyShelleyEra (..)
, Config (..)
, SomeNewEpochState (..)
) where

import Cardano.Binary (ToCBOR (..))
import qualified Cardano.Ledger.Allegra as SL
import qualified Cardano.Ledger.Alonzo as SL
import qualified Cardano.Ledger.Babbage as SL
import Cardano.Ledger.Binary (ToCBOR (..))
import qualified Cardano.Ledger.Conway as SL
import Cardano.Ledger.Crypto (StandardCrypto)
import qualified Cardano.Ledger.Mary as SL
import qualified Cardano.Ledger.Shelley as SL
import qualified Cardano.Ledger.Shelley.API as SL
import Ouroboros.Consensus.Storage.LedgerDB.OnDisk (DiskSnapshot)
import Ouroboros.Consensus.Storage.LedgerDB (DiskSnapshot)

data AnyShelleyEra c era where
ShelleyEra :: AnyShelleyEra c (SL.ShelleyEra c)
AllegraEra :: AnyShelleyEra c (SL.AllegraEra c)
MaryEra :: AnyShelleyEra c (SL.MaryEra c)
AlonzoEra :: AnyShelleyEra c (SL.AlonzoEra c)
BabbageEra :: AnyShelleyEra c (SL.BabbageEra c)
ConwayEra :: AnyShelleyEra c (SL.ConwayEra c)

data SomeNewEpochState where
SomeNewEpochState ::
Expand All @@ -35,9 +37,10 @@ instance ToCBOR SomeNewEpochState where
toCBOR (SomeNewEpochState MaryEra nes) = toCBOR nes
toCBOR (SomeNewEpochState AlonzoEra nes) = toCBOR nes
toCBOR (SomeNewEpochState BabbageEra nes) = toCBOR nes
toCBOR (SomeNewEpochState ConwayEra nes) = toCBOR nes


data Config = Config {
dbDir :: FilePath
, snapShot :: DiskSnapshot
dbDir :: FilePath
, snapShot :: DiskSnapshot
}

0 comments on commit dd1ec95

Please sign in to comment.