1+ {-# LANGUAGE OverloadedStrings #-}
2+
13-- | Tests for snapshots and their interaction with the file system
24module Test.Database.LSMTree.Internal.Snapshot.FS (tests ) where
35
46import Codec.CBOR.Read (DeserialiseFailure )
5- import Control.Exception
7+ import Control.Monad.Class.MonadThrow
8+ import Control.Monad.IOSim (runSimOrThrow )
9+ import Control.Tracer
10+ import Data.Bifunctor (Bifunctor (.. ))
11+ import Data.Maybe (fromJust )
12+ import qualified Data.Set as Set
13+ import qualified Data.Vector as V
14+ import Data.Word
15+ import Database.LSMTree.Extras (showPowersOf10 )
16+ import Database.LSMTree.Extras.Generators ()
17+ import Database.LSMTree.Internal
18+ import Database.LSMTree.Internal.Config
619import Database.LSMTree.Internal.CRC32C
20+ import Database.LSMTree.Internal.Entry
21+ import Database.LSMTree.Internal.Paths
22+ import Database.LSMTree.Internal.Serialise
723import Database.LSMTree.Internal.Snapshot
824import Database.LSMTree.Internal.Snapshot.Codec
25+ import qualified System.FS.API as FS
926import System.FS.API
1027import System.FS.Sim.Error hiding (genErrors )
1128import qualified System.FS.Sim.MockFS as MockFS
1229import Test.Database.LSMTree.Internal.Snapshot.Codec ()
30+ import Test.QuickCheck
31+ import Test.QuickCheck.Gen (genDouble )
1332import Test.Tasty
14- import Test.Tasty.QuickCheck as QC
33+ import Test.Tasty.QuickCheck
1534import Test.Util.FS
1635
1736tests :: TestTree
@@ -20,6 +39,7 @@ tests = testGroup "Test.Database.LSMTree.Internal.Snapshot.FS" [
2039 prop_fsRoundtripSnapshotMetaData
2140 , testProperty " prop_fault_fsRoundtripSnapshotMetaData"
2241 prop_fault_fsRoundtripSnapshotMetaData
42+ , testProperty " prop_flipSnapshotBit" prop_flipSnapshotBit
2343 ]
2444
2545-- | @readFileSnapshotMetaData . writeFileSnapshotMetaData = id@
@@ -56,12 +76,12 @@ prop_fault_fsRoundtripSnapshotMetaData testErrs metadata =
5676 ioProperty $
5777 withSimErrorHasFS propNoOpenHandles MockFS. empty emptyErrors $ \ hfs _fsVar errsVar -> do
5878 writeResult <-
59- try @ FsError $
79+ try @ _ @ FsError $
6080 withErrors errsVar (writeErrors testErrs) $
6181 writeFileSnapshotMetaData hfs metadataPath checksumPath metadata
6282
6383 readResult <-
64- try @ SomeException $
84+ try @ _ @ SomeException $
6585 withErrors errsVar (readErrors testErrs) $
6686 readFileSnapshotMetaData hfs metadataPath checksumPath
6787
@@ -137,3 +157,106 @@ instance Arbitrary TestErrors where
137157 [ TestErrors writeErrors' readErrors'
138158 | (writeErrors', readErrors') <- shrink (writeErrors, readErrors)
139159 ]
160+
161+ {- ------------------------------------------------------------------------------
162+ Snapshot corruption
163+ -------------------------------------------------------------------------------}
164+
165+ -- | A 'Double' in the @[0, 1)@ range.
166+ newtype Double_0_1 = Double_0_1 Double
167+ deriving stock (Show , Eq )
168+
169+ instance Arbitrary Double_0_1 where
170+ arbitrary = Double_0_1 <$> genDouble
171+ shrink (Double_0_1 x) = [Double_0_1 x' | x' <- shrink x, 0 <= x', x' < 1 ]
172+
173+ -- TODO: an alternative to generating doubles a priori is to run the monadic
174+ -- code in @PropertyM (IOSim s)@, and then we can do quantification inside the
175+ -- monadic property using @pick@. This complicates matters, however, because
176+ -- functions like @withSimHasBlockIO@ and @withTable@ would have to run in
177+ -- @PropertyM (IOSim s)@ as well. It's not clear whether the refactoring is
178+ -- worth it.
179+ prop_flipSnapshotBit ::
180+ Positive (Small Int )
181+ -> V. Vector (Word64 , Entry Word64 Word64 )
182+ -> Double_0_1 -- ^ Used to pick which file to corrupt
183+ -> Double_0_1 -- ^ Used to pick which bit to flip in the file we picked
184+ -> Property
185+ prop_flipSnapshotBit
186+ (Positive (Small bufferSize))
187+ es
188+ (Double_0_1 pickFile)
189+ (Double_0_1 pickBit) =
190+ runSimOrThrow $
191+ withSimHasBlockIO propNoOpenHandles MockFS. empty $ \ hfs hbio _fsVar ->
192+ withSession nullTracer hfs hbio root $ \ s ->
193+ withTable s conf $ \ t -> do
194+ -- Create a table, populate it, and create a snapshot
195+ updates resolve es' t
196+ createSnap t
197+
198+ -- Pick a random file from the named snapshot directory
199+ files <- listDirectoryRecursiveFiles hfs (getNamedSnapshotDir namedSnapDir)
200+ let i = round (fromIntegral (Set. size files - 1 ) * pickFile)
201+ let file = Set. elemAt i files
202+ let path = getNamedSnapshotDir namedSnapDir </> file
203+ -- Pick a random bit from the file that we want to corrupt
204+ n <- withFile hfs path ReadMode $ hGetSize hfs
205+ let j = round (fromIntegral (n * 8 - 1 ) * pickBit)
206+
207+ -- Some info for the test output
208+ let
209+ tabCorruptedFile = tabulate " Corrupted file" [show path]
210+ counterCorruptedFile = counterexample (" Corrupted file: " ++ show path)
211+ tabFlippedBit = tabulate " Flipped bit" [showPowersOf10 j]
212+ counterFlippedBit = counterexample (" Flipped bit: " ++ show j)
213+
214+ let isUncheckedFile =
215+ path == getNamedSnapshotDir namedSnapDir </> FS. mkFsPath [" 0.keyops" ]
216+ || path == getNamedSnapshotDir namedSnapDir </> FS. mkFsPath [" 0.blobs" ]
217+ || path == getNamedSnapshotDir namedSnapDir </> FS. mkFsPath [" 0.checksums" ]
218+
219+ -- TODO: remove once write buffer files have checksum verification
220+ if isUncheckedFile then
221+ pure discard
222+ else if n <= 0 then -- file is empty
223+ pure $ tabulate " Result" [" No corruption applied" ] True
224+ else do -- file is non-empty
225+
226+ -- Flip a bit and try to open the snapshot
227+ flipFileBit hfs path j
228+ t' <- try @ _ @ SomeException $ bracket (openSnap s) close $ \ _ -> pure ()
229+
230+ pure $
231+ tabCorruptedFile $ counterCorruptedFile $ tabFlippedBit $ counterFlippedBit $
232+ case t' of
233+ -- If we find an error, we detected corruption. Success!
234+ Left e ->
235+ tabulate
236+ " Result"
237+ [" Corruption detected: " <> getConstructorName e]
238+ True
239+ -- The corruption was not detected. Failure!
240+ Right _ -> property False
241+ where
242+ root = FS. mkFsPath []
243+ namedSnapDir = namedSnapshotDir (SessionRoot root) snapName
244+
245+ conf = defaultTableConfig {
246+ confWriteBufferAlloc = AllocNumEntries (NumEntries bufferSize)
247+ }
248+ es' = fmap (bimap serialiseKey (bimap serialiseValue serialiseBlob)) es
249+
250+ resolve (SerialisedValue x) (SerialisedValue y) =
251+ SerialisedValue (x <> y)
252+
253+ snapName = fromJust $ mkSnapshotName " snap"
254+ snapLabel = SnapshotLabel " label"
255+
256+ createSnap t =
257+ createSnapshot snapName snapLabel SnapFullTable t
258+
259+ openSnap s =
260+ openSnapshot s snapLabel SnapFullTable configNoOverride snapName resolve
261+
262+ getConstructorName e = takeWhile (/= ' ' ) (show e)
0 commit comments