11{-# LANGUAGE DeriveAnyClass #-}
22{-# LANGUAGE FlexibleContexts #-}
3+ {-# LANGUAGE GADTs #-}
34{-# LANGUAGE LambdaCase #-}
45{-# LANGUAGE OverloadedStrings #-}
56{-# LANGUAGE RecordWildCards #-}
7+ {-# LANGUAGE ScopedTypeVariables #-}
68{-# LANGUAGE TupleSections #-}
79{-# LANGUAGE TypeApplications #-}
810{-# LANGUAGE ViewPatterns #-}
@@ -30,11 +32,12 @@ import Ouroboros.Consensus.Config
3032import Ouroboros.Consensus.Ledger.Basics
3133import Ouroboros.Consensus.Ledger.Extended
3234import Ouroboros.Consensus.Node.ProtocolInfo
35+ import Ouroboros.Consensus.Storage.LedgerDB.API
3336import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
3437import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB as V1
38+ import Ouroboros.Consensus.Storage.LedgerDB.V2.LSM
3539import Ouroboros.Consensus.Util.CRC
36- import Ouroboros.Consensus.Util.IOLike
37- import Ouroboros.Consensus.Util.StreamingLedgerTables
40+ import Ouroboros.Consensus.Util.IOLike hiding (yield )
3841import System.Console.ANSI
3942import qualified System.Directory as D
4043import System.Exit
@@ -45,6 +48,7 @@ import System.FilePath (splitDirectories)
4548import qualified System.FilePath as F
4649import System.IO
4750import System.ProgressBar
51+ import System.Random
4852
4953data Format
5054 = Mem FilePath
@@ -215,24 +219,29 @@ instance StandardHash blk => Show (Error blk) where
215219 [" Error when reading entries in the UTxO tables: " , show df]
216220 show Cancelled = " Cancelled"
217221
218- data InEnv = InEnv
222+ data InEnv backend = InEnv
219223 { inState :: LedgerState (CardanoBlock StandardCrypto ) EmptyMK
220224 , inFilePath :: FilePath
221225 , inStream ::
222226 LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
223227 ResourceRegistry IO ->
224- IO (YieldArgs ( LedgerState ( CardanoBlock StandardCrypto )) IO )
228+ IO (SomeBackend YieldArgs )
225229 , inProgressMsg :: String
226230 , inCRC :: CRC
227231 , inSnapReadCRC :: Maybe CRC
228232 }
229233
230- data OutEnv = OutEnv
234+ data SomeBackend c where
235+ SomeBackend ::
236+ StreamingBackend IO backend (LedgerState (CardanoBlock StandardCrypto )) =>
237+ c IO backend (LedgerState (CardanoBlock StandardCrypto )) -> SomeBackend c
238+
239+ data OutEnv backend = OutEnv
231240 { outFilePath :: FilePath
232241 , outStream ::
233242 LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
234243 ResourceRegistry IO ->
235- IO (SinkArgs ( LedgerState ( CardanoBlock StandardCrypto )) IO )
244+ IO (SomeBackend SinkArgs )
236245 , outCreateExtra :: Maybe FilePath
237246 , outDeleteExtra :: Maybe FilePath
238247 , outProgressMsg :: String
@@ -356,7 +365,7 @@ main = withStdTerminalHandles $ do
356365 InEnv
357366 st
358367 fp
359- (fromInMemory (fp F. </> " tables" ))
368+ (\ a b -> SomeBackend <$> mkInMemYieldArgs (fp F. </> " tables" ) a b )
360369 (" InMemory@[" <> fp <> " ]" )
361370 c
362371 mtd
@@ -375,7 +384,7 @@ main = withStdTerminalHandles $ do
375384 InEnv
376385 st
377386 fp
378- (fromLMDB (fp F. </> " tables" ) defaultLMDBLimits)
387+ (\ a b -> SomeBackend <$> V1. mkLMDBYieldArgs (fp F. </> " tables" ) defaultLMDBLimits a b )
379388 (" LMDB@[" <> fp <> " ]" )
380389 c
381390 mtd
@@ -394,7 +403,9 @@ main = withStdTerminalHandles $ do
394403 InEnv
395404 st
396405 fp
397- (fromLSM lsmDbPath (last $ splitDirectories fp))
406+ ( \ a b ->
407+ SomeBackend <$> mkLSMYieldArgs lsmDbPath (last $ splitDirectories fp) stdMkBlockIOFS newStdGen a b
408+ )
398409 (" LSM@[" <> lsmDbPath <> " ]" )
399410 c
400411 mtd
@@ -412,7 +423,7 @@ main = withStdTerminalHandles $ do
412423 pure $
413424 OutEnv
414425 fp
415- (toInMemory (fp F. </> " tables" ))
426+ (\ a b -> SomeBackend <$> mkInMemSinkArgs (fp F. </> " tables" ) a b )
416427 (Just " tables" )
417428 (Nothing )
418429 (" InMemory@[" <> fp <> " ]" )
@@ -429,7 +440,7 @@ main = withStdTerminalHandles $ do
429440 pure $
430441 OutEnv
431442 fp
432- (toLMDB fp defaultLMDBLimits)
443+ (\ a b -> SomeBackend <$> V1. mkLMDBSinkArgs fp defaultLMDBLimits a b )
433444 Nothing
434445 Nothing
435446 (" LMDB@[" <> fp <> " ]" )
@@ -446,12 +457,32 @@ main = withStdTerminalHandles $ do
446457 pure $
447458 OutEnv
448459 fp
449- (toLSM lsmDbPath (last $ splitDirectories fp))
460+ ( \ a b ->
461+ SomeBackend <$> mkLSMSinkArgs lsmDbPath (last $ splitDirectories fp) stdMkBlockIOFS newStdGen a b
462+ )
450463 Nothing
451464 (Just lsmDbPath)
452465 (" LSM@[" <> lsmDbPath <> " ]" )
453466 UTxOHDLSMSnapshot
454467
468+ stream ::
469+ LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
470+ ( LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
471+ ResourceRegistry IO ->
472+ IO (SomeBackend YieldArgs )
473+ ) ->
474+ ( LedgerState (CardanoBlock StandardCrypto ) EmptyMK ->
475+ ResourceRegistry IO ->
476+ IO (SomeBackend SinkArgs )
477+ ) ->
478+ ExceptT DeserialiseFailure IO (Maybe CRC , Maybe CRC )
479+ stream st mYieldArgs mSinkArgs =
480+ ExceptT $
481+ withRegistry $ \ reg -> do
482+ (SomeBackend (yArgs :: YieldArgs IO backend1 l )) <- mYieldArgs st reg
483+ (SomeBackend (sArgs :: SinkArgs IO backend2 l )) <- mSinkArgs st reg
484+ runExceptT $ yield (Proxy @ backend1 ) yArgs st $ sink (Proxy @ backend2 ) sArgs st
485+
455486-- Helpers
456487
457488-- UI
0 commit comments