Skip to content

Commit 7114a77

Browse files
committed
Cleanup
1 parent b3550a5 commit 7114a77

File tree

3 files changed

+4
-10
lines changed
  • ouroboros-consensus/src
    • ouroboros-consensus-lsm/Ouroboros/Consensus/Storage/LedgerDB/V2
    • ouroboros-consensus/Ouroboros/Consensus/Storage/LedgerDB

3 files changed

+4
-10
lines changed

ouroboros-consensus/src/ouroboros-consensus-lsm/Ouroboros/Consensus/Storage/LedgerDB/V2/LSM.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
{-# LANGUAGE TypeApplications #-}
1515
{-# LANGUAGE TypeFamilies #-}
1616
{-# LANGUAGE UndecidableInstances #-}
17+
{-# LANGUAGE ViewPatterns #-}
1718
{-# OPTIONS_GHC -Wno-orphans #-}
1819

1920
-- | Implementation of the 'LedgerTablesHandle' interface with LSM trees.
@@ -72,7 +73,6 @@ import Ouroboros.Consensus.Ledger.Tables.Utils
7273
import Ouroboros.Consensus.Storage.LedgerDB.API
7374
import Ouroboros.Consensus.Storage.LedgerDB.Args
7475
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
75-
import Ouroboros.Consensus.Storage.LedgerDB.V2
7676
import Ouroboros.Consensus.Storage.LedgerDB.V2.Backend
7777
import Ouroboros.Consensus.Storage.LedgerDB.V2.LedgerSeq
7878
import Ouroboros.Consensus.Util (chunks)

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/LedgerDB/V2.hs

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
{-# LANGUAGE TypeOperators #-}
1212
{-# LANGUAGE UndecidableInstances #-}
1313

14-
module Ouroboros.Consensus.Storage.LedgerDB.V2 (mkInitDb, snapshotToStatePath) where
14+
module Ouroboros.Consensus.Storage.LedgerDB.V2 (mkInitDb) where
1515

1616
import Control.Arrow ((>>>))
1717
import qualified Control.Monad as Monad (join, void)
@@ -240,11 +240,6 @@ implIntTruncateSnapshots snapManager (SomeHasFS fs) = do
240240
\pre -> withFile fs (snapshotToStatePath pre) (AppendMode AllowExisting) $
241241
\h -> hTruncate fs h 0
242242

243-
-- | The path within the LedgerDB's filesystem to the file that contains the
244-
-- snapshot's serialized ledger state
245-
snapshotToStatePath :: DiskSnapshot -> FsPath
246-
snapshotToStatePath = mkFsPath . (\x -> [x, "state"]) . snapshotToDirName
247-
248243
implGetVolatileTip ::
249244
(MonadSTM m, GetTip l) =>
250245
LedgerDBEnv m l blk ->

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/LedgerDB/V2/InMemory.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -148,11 +148,10 @@ newInMemoryLedgerTablesHandle tracer someFS@(SomeHasFS hasFS) l = do
148148
)
149149
)
150150
, takeHandleSnapshot = \hint snapshotName -> do
151-
createDirectoryIfMissing hasFS True $ mkFsPath [snapshotName, "tables"]
152151
h <- readTVarIO tv
153152
guardClosed h $
154153
\values ->
155-
withFile hasFS (mkFsPath [snapshotName, "tables", "tvar"]) (WriteMode MustBeNew) $ \hf ->
154+
withFile hasFS (mkFsPath [snapshotName, "tables"]) (WriteMode MustBeNew) $ \hf ->
156155
fmap (Just . snd) $
157156
hPutAllCRC hasFS hf $
158157
CBOR.toLazyByteString $
@@ -265,7 +264,7 @@ loadSnapshot tracer _rr ccfg fs ds = do
265264
(valuesMKDecoder extLedgerSt)
266265
( fsPathFromList $
267266
fsPathToList (snapshotToDirPath ds)
268-
<> [fromString "tables", fromString "tvar"]
267+
<> [fromString "tables"]
269268
)
270269
let computedCRC = crcOfConcat checksumAsRead crcTables
271270
Monad.when (computedCRC /= snapshotChecksum snapshotMeta) $

0 commit comments

Comments
 (0)