Skip to content

Commit

Permalink
DiskSnapshotChecksum -> DoDiskSnapshotChecksum
Browse files Browse the repository at this point in the history
  • Loading branch information
geo2a committed Dec 9, 2024
1 parent 419c94a commit a24d6dc
Show file tree
Hide file tree
Showing 14 changed files with 47 additions and 47 deletions.
6 changes: 3 additions & 3 deletions ouroboros-consensus-cardano/app/DBAnalyser/Parsers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Options.Applicative
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Byron.Node (PBftSignatureThreshold (..))
import Ouroboros.Consensus.Shelley.Node (Nonce (..))
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy (pattern DiskSnapshotChecksum, pattern NoDiskSnapshotChecksum)
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy (pattern DoDiskSnapshotChecksum, pattern NoDoDiskSnapshotChecksum)

{-------------------------------------------------------------------------------
Parsing
Expand All @@ -46,8 +46,8 @@ parseDBAnalyserConfig = DBAnalyserConfig
<*> parseValidationPolicy
<*> parseAnalysis
<*> parseLimit
<*> flag NoDiskSnapshotChecksum DiskSnapshotChecksum (mconcat [
long "disk-snapshot-checksum"
<*> flag NoDoDiskSnapshotChecksum DoDiskSnapshotChecksum (mconcat [
long "do-disk-snapshot-checksum"
, help "Check the '.checksum' file if reading a ledger snapshot"
])

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ import Ouroboros.Consensus.Storage.Common (BlockComponent (..))
import Ouroboros.Consensus.Storage.ImmutableDB (ImmutableDB)
import qualified Ouroboros.Consensus.Storage.ImmutableDB as ImmutableDB
import Ouroboros.Consensus.Storage.LedgerDB (DiskSnapshot (..),
pattern NoDiskSnapshotChecksum, writeSnapshot)
pattern NoDoDiskSnapshotChecksum, writeSnapshot)
import Ouroboros.Consensus.Storage.Serialisation (encodeDisk)
import Ouroboros.Consensus.Util ((..:))
import qualified Ouroboros.Consensus.Util.IOLike as IOLike
Expand Down Expand Up @@ -423,7 +423,7 @@ storeLedgerStateAt slotNo ledgerAppMode env = do
storeLedgerState ledgerState = case pointSlot pt of
NotOrigin slot -> do
let snapshot = DiskSnapshot (unSlotNo slot) (Just "db-analyser")
writeSnapshot ledgerDbFS NoDiskSnapshotChecksum encLedger snapshot ledgerState
writeSnapshot ledgerDbFS NoDoDiskSnapshotChecksum encLedger snapshot ledgerState
traceWith tracer $ SnapshotStoredEvent slot
Origin -> pure ()
where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ data DBAnalyserConfig = DBAnalyserConfig {
, validation :: Maybe ValidateBlocks
, analysis :: AnalysisName
, confLimit :: Limit
, diskSnapshotChecksum :: Flag "DiskSnapshotChecksum"
, diskSnapshotChecksum :: Flag "DoDiskSnapshotChecksum"
}

data AnalysisName =
Expand Down
4 changes: 2 additions & 2 deletions ouroboros-consensus-cardano/test/tools-test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import Cardano.Tools.DBSynthesizer.Types
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Cardano.Block
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy
(pattern NoDiskSnapshotChecksum)
(pattern NoDoDiskSnapshotChecksum)
import qualified Test.Cardano.Tools.Headers
import Test.Tasty
import Test.Tasty.HUnit
Expand Down Expand Up @@ -72,7 +72,7 @@ testAnalyserConfig =
, validation = Just ValidateAllBlocks
, analysis = CountBlocks
, confLimit = Unlimited
, diskSnapshotChecksum = NoDiskSnapshotChecksum
, diskSnapshotChecksum = NoDoDiskSnapshotChecksum
}

testBlockArgs :: Cardano.Args (CardanoBlock StandardCrypto)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,8 @@ module Ouroboros.Consensus.Node (
, RunNodeArgs (..)
, Tracers
, Tracers' (..)
, pattern DiskSnapshotChecksum
, pattern NoDiskSnapshotChecksum
, pattern DoDiskSnapshotChecksum
, pattern NoDoDiskSnapshotChecksum
-- * Internal helpers
, mkNodeKernelArgs
, nodeKernelArgsEnforceInvariants
Expand Down Expand Up @@ -110,8 +110,8 @@ import Ouroboros.Consensus.Storage.ChainDB (ChainDB, ChainDbArgs,
import qualified Ouroboros.Consensus.Storage.ChainDB as ChainDB
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.Args as ChainDB
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy
(DiskPolicyArgs (..), pattern DiskSnapshotChecksum,
pattern NoDiskSnapshotChecksum)
(DiskPolicyArgs (..), pattern DoDiskSnapshotChecksum,
pattern NoDoDiskSnapshotChecksum)
import Ouroboros.Consensus.Util.Args
import Ouroboros.Consensus.Util.IOLike
import Ouroboros.Consensus.Util.Orphans ()
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@
- When writing a ledger state snapshot to disk, calculate the state's CRC32 checksum and write it to a separate file, which is named the same as the snapshot file, plus the `.checksum` extension.
- When reading a snapshot file in `readSnapshot`, calculate its checksum and compare it to the value in the corresponding `.checksum` file. Return an error if the checksum is different or invalid. Issue a warning if the checksum file does not exist, but still initialise the ledger DB.
- To support the previous item, change the error type of the `readSnapshot` from `ReadIncrementalErr` to the extended `ReadSnaphotErr`.
- Checksumming the snapshots is controlled via the `doChecksum :: Flag "DiskSnapshotChecksum"` parameter of `initFromSnapshot`. It is enabled by default in `initLedgerDB` by setting it to `DiskSnapshotChecksum` (i.e. `True`).
- Checksumming the snapshots is controlled via the `doChecksum :: Flag "DoDiskSnapshotChecksum"` parameter of `initFromSnapshot`. It is enabled by default in `initLedgerDB` by setting it to `DoDiskSnapshotChecksum` (i.e. `True`).

### Non-breaking

- Make `Ouroboros.Consensus.Util.CBOR.readIncremental` optionally compute the checksum of the data as it is read.
- Introduce an explicit `Ord` instance for `DiskSnapshot` that compares the values on `dsNumber`.
- Introduce a new utility newtype `Flag` to represent type-safe boolean flags. See ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Util.hs.
- Use `Flag "DiskSnapshotChecksum"` to control the check of the snapshot checksum file in `readSnapshot`
- Use `Flag "DoDiskSnapshotChecksum"` to control the check of the snapshot checksum file in `readSnapshot`
Original file line number Diff line number Diff line change
Expand Up @@ -222,7 +222,7 @@ initFromDisk ::
initFromDisk LgrDbArgs { lgrHasFS = hasFS, .. }
replayTracer
immutableDB = wrapFailure (Proxy @blk) $ do
let LedgerDB.DiskPolicyArgs _ _ doDiskSnapshotChecksum = lgrDiskPolicyArgs
let LedgerDB.DiskPolicyArgs _ _ doDiskSnapshotChecksum = lgrDiskPolicyArgs
(_initLog, db, replayed) <-
LedgerDB.initLedgerDB
replayTracer
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -136,8 +136,8 @@ module Ouroboros.Consensus.Storage.LedgerDB (
, SnapshotFailure (..)
, diskSnapshotIsTemporary
, listSnapshots
, pattern DiskSnapshotChecksum
, pattern NoDiskSnapshotChecksum
, pattern DoDiskSnapshotChecksum
, pattern NoDoDiskSnapshotChecksum
, readSnapshot
-- ** Write to disk
, takeSnapshot
Expand Down Expand Up @@ -165,8 +165,8 @@ import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy
(DiskPolicy (..), DiskPolicyArgs (..),
NumOfDiskSnapshots (..), SnapshotInterval (..),
TimeSinceLast (..), defaultDiskPolicyArgs, mkDiskPolicy,
pattern DiskSnapshotChecksum,
pattern NoDiskSnapshotChecksum)
pattern DoDiskSnapshotChecksum,
pattern NoDoDiskSnapshotChecksum)
import Ouroboros.Consensus.Storage.LedgerDB.Init (InitLog (..),
ReplayGoal (..), ReplayStart (..), TraceReplayEvent (..),
decorateReplayTracerWithGoal,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,8 @@ module Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy (
, TimeSinceLast (..)
, defaultDiskPolicyArgs
, mkDiskPolicy
, pattern DiskSnapshotChecksum
, pattern NoDiskSnapshotChecksum
, pattern DoDiskSnapshotChecksum
, pattern NoDoDiskSnapshotChecksum
-- * Re-exports
, Flag (..)
) where
Expand Down Expand Up @@ -47,11 +47,11 @@ data NumOfDiskSnapshots =
| RequestedNumOfDiskSnapshots Word
deriving stock (Eq, Generic, Show)

pattern DiskSnapshotChecksum, NoDiskSnapshotChecksum :: Flag "DiskSnapshotChecksum"
pattern DiskSnapshotChecksum = Flag True
pattern NoDiskSnapshotChecksum = Flag False
pattern DoDiskSnapshotChecksum, NoDoDiskSnapshotChecksum :: Flag "DoDiskSnapshotChecksum"
pattern DoDiskSnapshotChecksum = Flag True
pattern NoDoDiskSnapshotChecksum = Flag False

data DiskPolicyArgs = DiskPolicyArgs SnapshotInterval NumOfDiskSnapshots (Flag "DiskSnapshotChecksum")
data DiskPolicyArgs = DiskPolicyArgs SnapshotInterval NumOfDiskSnapshots (Flag "DoDiskSnapshotChecksum")

-- | On-disk policy
--
Expand Down Expand Up @@ -100,8 +100,8 @@ data DiskPolicy = DiskPolicy {
, onDiskShouldTakeSnapshot :: TimeSinceLast DiffTime -> Word64 -> Bool

-- | Whether or not to checksum the ledger snapshots to detect data corruption on disk.
-- "yes" if @'DiskSnapshotChecksum'@; "no" if @'NoDiskSnapshotChecksum'@.
, onDiskShouldChecksumSnapshots :: Flag "DiskSnapshotChecksum"
-- "yes" if @'DoDiskSnapshotChecksum'@; "no" if @'NoDoDiskSnapshotChecksum'@.
, onDiskShouldChecksumSnapshots :: Flag "DoDiskSnapshotChecksum"
}
deriving NoThunks via OnlyCheckWhnf DiskPolicy

Expand All @@ -111,7 +111,7 @@ data TimeSinceLast time = NoSnapshotTakenYet | TimeSinceLast time
-- | Default on-disk policy arguments suitable to use with cardano-node
--
defaultDiskPolicyArgs :: DiskPolicyArgs
defaultDiskPolicyArgs = DiskPolicyArgs DefaultSnapshotInterval DefaultNumOfDiskSnapshots DiskSnapshotChecksum
defaultDiskPolicyArgs = DiskPolicyArgs DefaultSnapshotInterval DefaultNumOfDiskSnapshots DoDiskSnapshotChecksum

mkDiskPolicy :: SecurityParam -> DiskPolicyArgs -> DiskPolicy
mkDiskPolicy (SecurityParam k) (DiskPolicyArgs reqInterval reqNumOfSnapshots onDiskShouldChecksumSnapshots) =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,8 @@ import Ouroboros.Consensus.Ledger.Inspect
import Ouroboros.Consensus.Ledger.SupportsProtocol
import Ouroboros.Consensus.Storage.ImmutableDB.Stream
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy
(pattern DiskSnapshotChecksum,
pattern NoDiskSnapshotChecksum)
(pattern DoDiskSnapshotChecksum,
pattern NoDoDiskSnapshotChecksum)
import Ouroboros.Consensus.Storage.LedgerDB.LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB.Query
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
Expand Down Expand Up @@ -108,7 +108,7 @@ initLedgerDB ::
-> LedgerDbCfg (ExtLedgerState blk)
-> m (ExtLedgerState blk) -- ^ Genesis ledger state
-> StreamAPI m blk blk
-> Flag "DiskSnapshotChecksum"
-> Flag "DoDiskSnapshotChecksum"
-> m (InitLog blk, LedgerDB' blk, Word64)
initLedgerDB replayTracer
tracer
Expand All @@ -118,11 +118,11 @@ initLedgerDB replayTracer
cfg
getGenesisLedger
stream
doDiskSnapshotChecksum = do
doDoDiskSnapshotChecksum = do
snapshots <- listSnapshots hasFS
tryNewestFirst doDiskSnapshotChecksum id snapshots
tryNewestFirst doDoDiskSnapshotChecksum id snapshots
where
tryNewestFirst :: Flag "DiskSnapshotChecksum"
tryNewestFirst :: Flag "DoDiskSnapshotChecksum"
-> (InitLog blk -> InitLog blk)
-> [DiskSnapshot]
-> m (InitLog blk, LedgerDB' blk, Word64)
Expand Down Expand Up @@ -151,7 +151,7 @@ initLedgerDB replayTracer
-- ignoring the checksum
Left (InitFailureRead ReadSnapshotNoChecksumFile{}) -> do
traceWith tracer $ SnapshotMissingChecksum s
tryNewestFirst NoDiskSnapshotChecksum acc allSnapshot
tryNewestFirst NoDoDiskSnapshotChecksum acc allSnapshot
-- If we fail to use this snapshot for any other reason, delete it and try an older one
Left err -> do
when (diskSnapshotIsTemporary s) $
Expand All @@ -160,7 +160,7 @@ initLedgerDB replayTracer
deleteSnapshot hasFS s
traceWith tracer $ InvalidSnapshot s err
-- always reset checksum flag after failure
tryNewestFirst DiskSnapshotChecksum (acc . InitFailure s err) ss
tryNewestFirst DoDiskSnapshotChecksum (acc . InitFailure s err) ss
Right (r, l, replayed) ->
return (acc (InitFromSnapshot s r), l, replayed)

Expand All @@ -187,7 +187,7 @@ initFromSnapshot ::
-> LedgerDbCfg (ExtLedgerState blk)
-> StreamAPI m blk blk
-> DiskSnapshot
-> Flag "DiskSnapshotChecksum"
-> Flag "DoDiskSnapshotChecksum"
-> ExceptT (SnapshotFailure blk) m (RealPoint blk, LedgerDB' blk, Word64)
initFromSnapshot tracer hasFS decLedger decHash cfg stream ss doChecksum = do
initSS <- withExceptT InitFailureRead $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,7 @@ takeSnapshot ::
forall m blk. (MonadThrow m, MonadMonotonicTime m, IsLedger (LedgerState blk))
=> Tracer m (TraceSnapshotEvent blk)
-> SomeHasFS m
-> Flag "DiskSnapshotChecksum"
-> Flag "DoDiskSnapshotChecksum"
-> (ExtLedgerState blk -> Encoding)
-> ExtLedgerState blk -> m (Maybe (DiskSnapshot, RealPoint blk))
takeSnapshot tracer hasFS doChecksum encLedger oldest =
Expand Down Expand Up @@ -219,7 +219,7 @@ readSnapshot ::
=> SomeHasFS m
-> (forall s. Decoder s (ExtLedgerState blk))
-> (forall s. Decoder s (HeaderHash blk))
-> Flag "DiskSnapshotChecksum"
-> Flag "DoDiskSnapshotChecksum"
-> DiskSnapshot
-> ExceptT ReadSnapshotErr m (ExtLedgerState blk)
readSnapshot someHasFS decLedger decHash doChecksum snapshotName = do
Expand Down Expand Up @@ -281,7 +281,7 @@ readSnapshot someHasFS decLedger decHash doChecksum snapshotName = do
writeSnapshot ::
forall m blk. MonadThrow m
=> SomeHasFS m
-> Flag "DiskSnapshotChecksum"
-> Flag "DoDiskSnapshotChecksum"
-> (ExtLedgerState blk -> Encoding)
-> DiskSnapshot
-> ExtLedgerState blk -> m ()
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ fromMinimalChainDbArgs MinimalChainDbArgs {..} = ChainDbArgs {
, volValidationPolicy = VolatileDB.ValidateAll
}
, cdbLgrDbArgs = LgrDbArgs {
lgrDiskPolicyArgs = LedgerDB.DiskPolicyArgs LedgerDB.DefaultSnapshotInterval LedgerDB.DefaultNumOfDiskSnapshots LedgerDB.DiskSnapshotChecksum
lgrDiskPolicyArgs = LedgerDB.DiskPolicyArgs LedgerDB.DefaultSnapshotInterval LedgerDB.DefaultNumOfDiskSnapshots LedgerDB.DoDiskSnapshotChecksum
-- Keep 2 ledger snapshots, and take a new snapshot at least every 2 *
-- k seconds, where k is the security parameter.
, lgrGenesis = return mcdbInitLedger
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Ouroboros.Consensus.Storage.LedgerDB (DiskPolicy (..),
TimeSinceLast (..), mkDiskPolicy)
import Ouroboros.Consensus.Storage.LedgerDB.DiskPolicy
(DiskPolicyArgs (DiskPolicyArgs),
pattern DiskSnapshotChecksum)
pattern DoDiskSnapshotChecksum)
import Test.QuickCheck
import Test.Tasty
import Test.Tasty.QuickCheck
Expand Down Expand Up @@ -51,7 +51,7 @@ toDiskPolicy :: TestSetup -> DiskPolicy
toDiskPolicy ts = mkDiskPolicy (tsK ts) diskPolicyArgs
where
diskPolicyArgs =
DiskPolicyArgs (tsSnapshotInterval ts) DefaultNumOfDiskSnapshots DiskSnapshotChecksum
DiskPolicyArgs (tsSnapshotInterval ts) DefaultNumOfDiskSnapshots DoDiskSnapshotChecksum

-- | The result of the represented call to 'onDiskShouldTakeSnapshot'
shouldTakeSnapshot :: TestSetup -> Bool
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -292,10 +292,10 @@ data Cmd ss =
| Switch Word64 [TestBlock]

-- | Take a snapshot (write to disk)
| Snap (Flag "DiskSnapshotChecksum")
| Snap (Flag "DoDiskSnapshotChecksum")

-- | Restore the DB from on-disk, then return it along with the init log
| Restore (Flag "DiskSnapshotChecksum")
| Restore (Flag "DoDiskSnapshotChecksum")

-- | Corrupt a previously taken snapshot
| Corrupt Corruption ss
Expand Down Expand Up @@ -568,7 +568,7 @@ runMock cmd initMock =
Delete -> Nothing
Truncate -> Just (ref, SnapCorrupted)
go (Drop n) mock =
go (Restore NoDiskSnapshotChecksum) $ mock {
go (Restore NoDoDiskSnapshotChecksum) $ mock {
mockLedger = drop (fromIntegral n) (mockLedger mock)
}

Expand Down Expand Up @@ -787,7 +787,7 @@ runDB standalone@DB{..} cmd =
atomically $ do
(rs, _db) <- readTVar dbState
writeTVar dbState (drop (fromIntegral n) rs, error "ledger DB not initialized")
go hasFS (Restore NoDiskSnapshotChecksum)
go hasFS (Restore NoDoDiskSnapshotChecksum)

push ::
TestBlock
Expand Down

0 comments on commit a24d6dc

Please sign in to comment.