Skip to content

Commit 5d39721

Browse files
committed
Allow skipping snapshot checksum check
1 parent 7c8d483 commit 5d39721

File tree

8 files changed

+101
-29
lines changed

8 files changed

+101
-29
lines changed

ouroboros-consensus-cardano/app/DBAnalyser/Parsers.hs

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
1-
{-# LANGUAGE ApplicativeDo #-}
2-
{-# LANGUAGE CPP #-}
3-
{-# LANGUAGE LambdaCase #-}
1+
{-# LANGUAGE ApplicativeDo #-}
2+
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE LambdaCase #-}
4+
{-# LANGUAGE PatternSynonyms #-}
45

56
module DBAnalyser.Parsers (
67
BlockType (..)
@@ -21,6 +22,7 @@ import Options.Applicative
2122
import Ouroboros.Consensus.Block
2223
import Ouroboros.Consensus.Byron.Node (PBftSignatureThreshold (..))
2324
import Ouroboros.Consensus.Shelley.Node (Nonce (..))
25+
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots (pattern DiskSnapshotChecksum, pattern NoDiskSnapshotChecksum)
2426

2527
{-------------------------------------------------------------------------------
2628
Parsing
@@ -44,6 +46,10 @@ parseDBAnalyserConfig = DBAnalyserConfig
4446
<*> parseValidationPolicy
4547
<*> parseAnalysis
4648
<*> parseLimit
49+
<*> flag NoDiskSnapshotChecksum DiskSnapshotChecksum (mconcat [
50+
long "disk-snapshot-checksum"
51+
, help "Check the '.checksum' file if reading a ledger snapshot"
52+
])
4753

4854
parseSelectDB :: Parser SelectDB
4955
parseSelectDB =

ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/DBAnalyser/Run.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE GADTs #-}
33
{-# LANGUAGE LambdaCase #-}
44
{-# LANGUAGE NamedFieldPuns #-}
5+
{-# LANGUAGE PatternSynonyms #-}
56
{-# LANGUAGE RankNTypes #-}
67
{-# LANGUAGE ScopedTypeVariables #-}
78

@@ -51,7 +52,7 @@ analyse ::
5152
=> DBAnalyserConfig
5253
-> Args blk
5354
-> IO (Maybe AnalysisResult)
54-
analyse DBAnalyserConfig{analysis, confLimit, dbDir, selectDB, validation, verbose} args =
55+
analyse DBAnalyserConfig{analysis, confLimit, dbDir, selectDB, validation, verbose, diskSnapshotChecksum} args =
5556
withRegistry $ \registry -> do
5657
lock <- newMVar ()
5758
chainDBTracer <- mkTracer lock verbose
@@ -92,6 +93,7 @@ analyse DBAnalyserConfig{analysis, confLimit, dbDir, selectDB, validation, verbo
9293
ledgerDbFS
9394
(decodeDiskExtLedgerState $ configCodec cfg)
9495
decode
96+
diskSnapshotChecksum
9597
(DiskSnapshot slot (Just "db-analyser"))
9698
-- TODO @readSnapshot@ has type @ExceptT ReadIncrementalErr m
9799
-- (ExtLedgerState blk)@ but it also throws exceptions! This makes

ouroboros-consensus-cardano/src/unstable-cardano-tools/Cardano/Tools/DBAnalyser/Types.hs

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,23 @@
1+
{-# LANGUAGE DataKinds #-}
12
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
23

34
module Cardano.Tools.DBAnalyser.Types (module Cardano.Tools.DBAnalyser.Types) where
45

56
import Data.Word
67
import Ouroboros.Consensus.Block
8+
import Ouroboros.Consensus.Util (Flag)
79

810
data SelectDB =
911
SelectImmutableDB (WithOrigin SlotNo)
1012

1113
data DBAnalyserConfig = DBAnalyserConfig {
12-
dbDir :: FilePath
13-
, verbose :: Bool
14-
, selectDB :: SelectDB
15-
, validation :: Maybe ValidateBlocks
16-
, analysis :: AnalysisName
17-
, confLimit :: Limit
14+
dbDir :: FilePath
15+
, verbose :: Bool
16+
, selectDB :: SelectDB
17+
, validation :: Maybe ValidateBlocks
18+
, analysis :: AnalysisName
19+
, confLimit :: Limit
20+
, diskSnapshotChecksum :: Flag "DiskSnapshotChecksum"
1821
}
1922

2023
data AnalysisName =

ouroboros-consensus-cardano/test/tools-test/Main.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE PatternSynonyms #-}
2+
13
module Main (main) where
24

35
import qualified Cardano.Tools.DBAnalyser.Block.Cardano as Cardano
@@ -8,6 +10,8 @@ import qualified Cardano.Tools.DBSynthesizer.Run as DBSynthesizer
810
import Cardano.Tools.DBSynthesizer.Types
911
import Ouroboros.Consensus.Block
1012
import Ouroboros.Consensus.Cardano.Block
13+
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
14+
(pattern NoDiskSnapshotChecksum)
1115
import qualified Test.Cardano.Tools.Headers
1216
import Test.Tasty
1317
import Test.Tasty.HUnit
@@ -68,6 +72,7 @@ testAnalyserConfig =
6872
, validation = Just ValidateAllBlocks
6973
, analysis = CountBlocks
7074
, confLimit = Unlimited
75+
, diskSnapshotChecksum = NoDiskSnapshotChecksum
7176
}
7277

7378
testBlockArgs :: Cardano.Args (CardanoBlock StandardCrypto)

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

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE PatternSynonyms #-}
2+
13
-- | The Ledger DB is responsible for the following tasks:
24
--
35
-- - __Maintaining the in-memory ledger state at the tip__: When we try to
@@ -135,6 +137,8 @@ module Ouroboros.Consensus.Storage.LedgerDB (
135137
, diskSnapshotIsTemporary
136138
, listSnapshots
137139
, readSnapshot
140+
, pattern DiskSnapshotChecksum
141+
, pattern NoDiskSnapshotChecksum
138142
-- ** Write to disk
139143
, takeSnapshot
140144
, trimSnapshots
@@ -174,8 +178,10 @@ import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
174178
(DiskSnapshot (..), SnapshotFailure (..),
175179
TraceSnapshotEvent (..), decodeSnapshotBackwardsCompatible,
176180
deleteSnapshot, diskSnapshotIsTemporary, encodeSnapshot,
177-
listSnapshots, readSnapshot, snapshotToFileName,
178-
snapshotToPath, takeSnapshot, trimSnapshots, writeSnapshot)
181+
listSnapshots, readSnapshot,
182+
pattern DiskSnapshotChecksum, pattern NoDiskSnapshotChecksum,
183+
snapshotToFileName, snapshotToPath, takeSnapshot, trimSnapshots,
184+
writeSnapshot)
179185
import Ouroboros.Consensus.Storage.LedgerDB.Update
180186
(AnnLedgerError (..), AnnLedgerError', Ap (..),
181187
ExceededRollback (..), PushGoal (..), PushStart (..),

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

Lines changed: 20 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE DataKinds #-}
23
{-# LANGUAGE DeriveGeneric #-}
34
{-# LANGUAGE RankNTypes #-}
45
{-# LANGUAGE ScopedTypeVariables #-}
@@ -35,6 +36,7 @@ import Ouroboros.Consensus.Storage.LedgerDB.LedgerDB
3536
import Ouroboros.Consensus.Storage.LedgerDB.Query
3637
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
3738
import Ouroboros.Consensus.Storage.LedgerDB.Update
39+
import Ouroboros.Consensus.Util (Flag)
3840
import Ouroboros.Consensus.Util.IOLike
3941
import Ouroboros.Network.Block (Point (Point))
4042
import System.FS.API
@@ -112,12 +114,13 @@ initLedgerDB replayTracer
112114
getGenesisLedger
113115
stream = do
114116
snapshots <- listSnapshots hasFS
115-
tryNewestFirst id snapshots
117+
tryNewestFirst DiskSnapshotChecksum id snapshots
116118
where
117-
tryNewestFirst :: (InitLog blk -> InitLog blk)
119+
tryNewestFirst :: Flag "DiskSnapshotChecksum"
120+
-> (InitLog blk -> InitLog blk)
118121
-> [DiskSnapshot]
119122
-> m (InitLog blk, LedgerDB' blk, Word64)
120-
tryNewestFirst acc [] = do
123+
tryNewestFirst _ acc [] = do
121124
-- We're out of snapshots. Start at genesis
122125
traceWith replayTracer ReplayFromGenesis
123126
initDb <- ledgerDbWithAnchor <$> getGenesisLedger
@@ -126,8 +129,7 @@ initLedgerDB replayTracer
126129
case ml of
127130
Left _ -> error "invariant violation: invalid current chain"
128131
Right (l, replayed) -> return (acc InitFromGenesis, l, replayed)
129-
tryNewestFirst acc (s:ss) = do
130-
-- If we fail to use this snapshot, delete it and try an older one
132+
tryNewestFirst doChecksum acc allSnapshot@(s:ss) = do
131133
ml <- runExceptT $ initFromSnapshot
132134
replayTracer
133135
hasFS
@@ -136,14 +138,23 @@ initLedgerDB replayTracer
136138
cfg
137139
stream
138140
s
141+
doChecksum
139142
case ml of
143+
-- If a checksum file is missing for a snapshot,
144+
-- issue a warning and retry the same snapshot
145+
-- ignoring the checksum
146+
Left (InitFailureRead ReadSnapshotNoChecksumFile{}) -> do
147+
traceWith tracer $ SnapshotMissingChecksum s
148+
tryNewestFirst NoDiskSnapshotChecksum acc allSnapshot
149+
-- If we fail to use this snapshot for any other reason, delete it and try an older one
140150
Left err -> do
141151
when (diskSnapshotIsTemporary s) $
142152
-- We don't delete permanent snapshots, even if we couldn't parse
143153
-- them
144154
deleteSnapshot hasFS s
145155
traceWith tracer $ InvalidSnapshot s err
146-
tryNewestFirst (acc . InitFailure s err) ss
156+
-- always reset checksum flag after failure
157+
tryNewestFirst DiskSnapshotChecksum (acc . InitFailure s err) ss
147158
Right (r, l, replayed) ->
148159
return (acc (InitFromSnapshot s r), l, replayed)
149160

@@ -170,10 +181,11 @@ initFromSnapshot ::
170181
-> LedgerDbCfg (ExtLedgerState blk)
171182
-> StreamAPI m blk blk
172183
-> DiskSnapshot
184+
-> Flag "DiskSnapshotChecksum"
173185
-> ExceptT (SnapshotFailure blk) m (RealPoint blk, LedgerDB' blk, Word64)
174-
initFromSnapshot tracer hasFS decLedger decHash cfg stream ss = do
186+
initFromSnapshot tracer hasFS decLedger decHash cfg stream ss doChecksum = do
175187
initSS <- withExceptT InitFailureRead $
176-
readSnapshot hasFS decLedger decHash ss
188+
readSnapshot hasFS decLedger decHash doChecksum ss
177189
let replayStart = castPoint $ getTip initSS
178190
case pointToWithOriginRealPoint replayStart of
179191
Origin -> throwError InitFailureGenesis

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

Lines changed: 29 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,12 @@
11
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE DataKinds #-}
23
{-# LANGUAGE DeriveGeneric #-}
34
{-# LANGUAGE FlexibleContexts #-}
45
{-# LANGUAGE FlexibleInstances #-}
56
{-# LANGUAGE KindSignatures #-}
6-
{-# LANGUAGE LambdaCase #-}
77
{-# LANGUAGE MultiParamTypeClasses #-}
88
{-# LANGUAGE NamedFieldPuns #-}
9+
{-# LANGUAGE PatternSynonyms #-}
910
{-# LANGUAGE RankNTypes #-}
1011
{-# LANGUAGE RecordWildCards #-}
1112
{-# LANGUAGE ScopedTypeVariables #-}
@@ -14,9 +15,12 @@
1415
module Ouroboros.Consensus.Storage.LedgerDB.Snapshots (
1516
DiskSnapshot (..)
1617
-- * Read from disk
18+
, ReadSnapshotErr (..)
1719
, SnapshotFailure (..)
1820
, diskSnapshotIsTemporary
1921
, listSnapshots
22+
, pattern DiskSnapshotChecksum
23+
, pattern NoDiskSnapshotChecksum
2024
, readSnapshot
2125
-- * Write to disk
2226
, takeSnapshot
@@ -44,6 +48,7 @@ import qualified Data.ByteString.Builder as BS
4448
import qualified Data.ByteString.Char8 as BSC
4549
import qualified Data.ByteString.Lazy as BSL
4650
import Data.Char (ord)
51+
import Data.Coerce (coerce)
4752
import Data.Functor.Contravariant ((>$<))
4853
import qualified Data.List as List
4954
import Data.Maybe (isJust, mapMaybe)
@@ -57,6 +62,7 @@ import Ouroboros.Consensus.Block
5762
import Ouroboros.Consensus.Ledger.Abstract
5863
import Ouroboros.Consensus.Ledger.Extended
5964
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy
65+
import Ouroboros.Consensus.Util (Flag (..))
6066
import Ouroboros.Consensus.Util.CBOR (ReadIncrementalErr,
6167
decodeWithOrigin, readIncremental)
6268
import Ouroboros.Consensus.Util.Enclose
@@ -90,7 +96,9 @@ data TraceSnapshotEvent blk
9096
| TookSnapshot DiskSnapshot (RealPoint blk) EnclosingTimed
9197
-- ^ A snapshot was written to disk.
9298
| DeletedSnapshot DiskSnapshot
93-
-- ^ An old or invalid on-disk snapshot was deleted
99+
-- ^ An old or invalid on-disk snapshot was deleted.
100+
| SnapshotMissingChecksum DiskSnapshot
101+
-- ^ The checksum file for a snapshot was missing and was not checked
94102
deriving (Generic, Eq, Show)
95103

96104
-- | Take a snapshot of the /oldest ledger state/ in the ledger DB
@@ -206,6 +214,10 @@ data ReadSnapshotErr =
206214
| ReadSnapshotInvalidChecksumFile FsPath
207215
deriving (Eq, Show)
208216

217+
pattern DiskSnapshotChecksum, NoDiskSnapshotChecksum :: Flag "DiskSnapshotChecksum"
218+
pattern DiskSnapshotChecksum = Flag True
219+
pattern NoDiskSnapshotChecksum = Flag False
220+
209221
-- | Read snapshot from disk.
210222
--
211223
-- Fail on data corruption, i.e. when the checksum of the read data differs
@@ -215,15 +227,23 @@ readSnapshot ::
215227
=> SomeHasFS m
216228
-> (forall s. Decoder s (ExtLedgerState blk))
217229
-> (forall s. Decoder s (HeaderHash blk))
230+
-> Flag "DiskSnapshotChecksum"
218231
-> DiskSnapshot
219232
-> ExceptT ReadSnapshotErr m (ExtLedgerState blk)
220-
readSnapshot someHasFS decLedger decHash snapshotName = do
221-
!snapshotCRC <- readCRC someHasFS (snapshotToChecksumPath snapshotName)
222-
(ledgerState, checksumAsRead) <- withExceptT ReadSnapshotFailed . ExceptT $
223-
readIncremental someHasFS decoder (snapshotToPath snapshotName)
224-
if checksumAsRead /= snapshotCRC
225-
then throwError ReadSnapshotDataCorruption
226-
else pure ledgerState
233+
readSnapshot someHasFS decLedger decHash doChecksum snapshotName = do
234+
if coerce doChecksum then do
235+
!snapshotCRC <- readCRC someHasFS (snapshotToChecksumPath snapshotName)
236+
(ledgerState, checksumAsRead) <- withExceptT ReadSnapshotFailed . ExceptT $
237+
readIncremental someHasFS decoder (snapshotToPath snapshotName)
238+
if checksumAsRead /= snapshotCRC
239+
then throwError ReadSnapshotDataCorruption
240+
else pure ledgerState
241+
else do
242+
-- TODO: consider threading the doChecksum flag into readIncremental
243+
-- to skip the checksum computation
244+
(ledgerState, _) <- withExceptT ReadSnapshotFailed . ExceptT $
245+
readIncremental someHasFS decoder (snapshotToPath snapshotName)
246+
pure ledgerState
227247
where
228248
decoder :: Decoder s (ExtLedgerState blk)
229249
decoder = decodeSnapshotBackwardsCompatible (Proxy @blk) decLedger decHash

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Util.hs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE BangPatterns #-}
22
{-# LANGUAGE ConstraintKinds #-}
3+
{-# LANGUAGE DataKinds #-}
34
{-# LANGUAGE DeriveAnyClass #-}
45
{-# LANGUAGE DeriveGeneric #-}
56
{-# LANGUAGE DerivingStrategies #-}
@@ -77,6 +78,8 @@ module Ouroboros.Consensus.Util (
7778
, electric
7879
, newFuse
7980
, withFuse
81+
-- * Type-safe boolean flags
82+
, Flag (..)
8083
) where
8184

8285
import Cardano.Crypto.Hash (Hash, HashAlgorithm, hashFromBytes,
@@ -102,6 +105,7 @@ import Data.Void
102105
import Data.Word (Word64)
103106
import GHC.Generics (Generic)
104107
import GHC.Stack
108+
import GHC.TypeLits (Symbol)
105109
import Ouroboros.Consensus.Util.IOLike
106110
import Ouroboros.Network.Protocol.LocalStateQuery.Codec (Some (..))
107111
import Ouroboros.Network.Util.ShowProxy (ShowProxy (..))
@@ -450,3 +454,17 @@ withFuse (Fuse name m) (Electric io) = do
450454
newtype FuseBlownException = FuseBlownException Text
451455
deriving (Show)
452456
deriving anyclass (Exception)
457+
458+
{-------------------------------------------------------------------------------
459+
Type-safe boolean flags
460+
-------------------------------------------------------------------------------}
461+
462+
-- | Type-safe boolean flags with type level tags
463+
--
464+
-- It is recommended to create pattern synonyms for the true and false values.
465+
-- Use 'coerce' to unwrap for use in e.g. if-statements.
466+
--
467+
-- See 'Ouroboros.Consensus.Storage.LedgerDB.Snapshots.DiskSnapshotChecksum'
468+
-- for an example.
469+
newtype Flag (name :: Symbol) = Flag Bool
470+
deriving (Eq, Show, Generic)

0 commit comments

Comments
 (0)