From 732fd17f060818d16f5199a9031da412e3cfe50d Mon Sep 17 00:00:00 2001 From: Joris Dral Date: Wed, 7 May 2025 17:36:29 +0200 Subject: [PATCH 1/4] Add a missing codec roundtrip test --- test/Test/Database/LSMTree/Internal/Snapshot/Codec.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/test/Test/Database/LSMTree/Internal/Snapshot/Codec.hs b/test/Test/Database/LSMTree/Internal/Snapshot/Codec.hs index 5bca699ac..0c72e716b 100644 --- a/test/Test/Database/LSMTree/Internal/Snapshot/Codec.hs +++ b/test/Test/Database/LSMTree/Internal/Snapshot/Codec.hs @@ -181,6 +181,7 @@ testAll test = [ , test (Proxy @TreeMergeType) , test (Proxy @(SnapMergingTree SnapshotRun)) , test (Proxy @(SnapMergingTreeState SnapshotRun)) + , test (Proxy @(SnapMergingRun TreeMergeType SnapshotRun)) , test (Proxy @(SnapPendingMerge SnapshotRun)) , test (Proxy @(SnapPreExistingRun SnapshotRun)) ] From 7e304ddd3a48a9c1420b2f543ce20f5ff30022b3 Mon Sep 17 00:00:00 2001 From: Joris Dral Date: Thu, 8 May 2025 11:38:39 +0200 Subject: [PATCH 2/4] Rework golden tests Previously, we were encoding each snapshot type in the context of a full metadata type. However, if one field somewhere down in the snapshot metadata changes, then the encoding of the full metadata stays the same except for that one field further down. As such, this commit changes the test setup so that we now encode (and golden-test) each type involved in the snapshot metadata separately. We also add a new `EnumGolden` class for enumerating values of snapshot types. With the more direct tests and `EnumGolden`, it's easier to prevent combinatorial explosion. --- .../LSMTree/Internal/Snapshot/Codec/Golden.hs | 754 ++++++++++-------- 1 file changed, 440 insertions(+), 314 deletions(-) diff --git a/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs b/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs index 6084f84f3..5e005e036 100644 --- a/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs +++ b/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs @@ -1,24 +1,25 @@ -{-# LANGUAGE OverloadedStrings #-} -module Test.Database.LSMTree.Internal.Snapshot.Codec.Golden - (tests) where +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE UndecidableInstances #-} + +module Test.Database.LSMTree.Internal.Snapshot.Codec.Golden ( + tests + , EnumGolden (..) + , Annotation + ) where import Codec.CBOR.Write (toLazyByteString) import Control.Monad (when) -import Data.Bifunctor (second) import qualified Data.ByteString.Lazy as BSL (writeFile) -import Data.Foldable (fold) -import qualified Data.List as List -import Data.Vector (Vector) +import Data.Typeable import qualified Data.Vector as V import Database.LSMTree.Internal.Config (BloomFilterAlloc (..), DiskCachePolicy (..), FencePointerIndexType (..), MergePolicy (..), MergeSchedule (..), SizeRatio (..), - TableConfig (..), WriteBufferAlloc (..), - defaultTableConfig) + TableConfig (..), WriteBufferAlloc (..)) import Database.LSMTree.Internal.MergeSchedule (MergePolicyForLevel (..), NominalCredits (..), NominalDebt (..)) -import qualified Database.LSMTree.Internal.MergingRun as MR +import Database.LSMTree.Internal.MergingRun as MR import Database.LSMTree.Internal.RunBuilder (IndexType (..), RunBloomFilterAlloc (..), RunDataCaching (..)) import Database.LSMTree.Internal.RunNumber (RunNumber (..)) @@ -29,328 +30,453 @@ import System.FS.API.Types (FsPath, MountPoint (..), fsToFilePath, mkFsPath, (<.>)) import System.FS.IO (HandleIO, ioHasFS) import qualified Test.Tasty as Tasty -import Test.Tasty (TestName, TestTree, testGroup) +import Test.Tasty (TestTree, testGroup) import qualified Test.Tasty.Golden as Au --- | Compare the serialization of snapshot metadata with a known reference file. tests :: TestTree -tests = handleOutputFiles . testGroup - "Test.Database.LSMTree.Internal.Snapshot.Codec.Golden" $ - [ testCodecSnapshotLabel - , testCodecTableConfig - , testCodecSnapLevels - , testCodecMergingTree - ] +tests = + handleOutputFiles $ + testGroup "Test.Database.LSMTree.Internal.Snapshot.Codec.Golden" $ + concat (forallSnapshotTypes snapshotCodecGoldenTest) + +{------------------------------------------------------------------------------- + Configuration +-------------------------------------------------------------------------------} + +-- | The location of the golden file data directory relative to the project root. +goldenDataFilePath :: FilePath +goldenDataFilePath = "test/golden-file-data/snapshot-codec" --- | The mount point is defined as the location of the golden file data directory --- relative to the project root. goldenDataMountPoint :: MountPoint -goldenDataMountPoint = MountPoint "test/golden-file-data/snapshot-codec" +goldenDataMountPoint = MountPoint goldenDataFilePath -- | Delete output files on test-case success. -- Change the option here if this is undesirable. handleOutputFiles :: TestTree -> TestTree handleOutputFiles = Tasty.localOption Au.OnPass --- | Internally, the function will infer the correct filepath names. -snapshotCodecTest :: - String -- ^ Name of the test - -> SnapshotMetaData -- ^ Data to be serialized - -> TestTree -snapshotCodecTest name datum = - let -- Various paths - -- - -- There are three paths for both the checksum and the snapshot files: - -- 1. The filepath of type @FsPath@ to which data is written. - -- 2. The filepath of type @FilePath@ from which data is read. - -- 3. The filepath of type @FilePath@ against which the data is compared. - -- - -- These file types' bindings have the following infix annotations, respectively: - -- 1. (Fs) for FsPath - -- 2. (Hs) for "Haskell" path - -- 3. (Au) for "Golden file" path - snapshotFsPath = mkFsPath [name] <.> "snapshot" - snapshotHsPath = fsToFilePath goldenDataMountPoint snapshotFsPath - snapshotAuPath = snapshotHsPath <> ".golden" - - -- IO actions - runnerIO :: FS.HasFS IO HandleIO - runnerIO = ioHasFS goldenDataMountPoint - removeIfExists :: FsPath -> IO () - removeIfExists fp = - FS.doesFileExist runnerIO fp >>= (`when` (FS.removeFile runnerIO fp)) - outputAction :: IO () - outputAction = do - -- Ensure that if the output file already exists, we remove it and - -- re-write out the serialized data. This ensures that there are no - -- false-positives, false-negatives, or irrelevant I/O exceptions. - removeIfExists snapshotFsPath - BSL.writeFile snapshotHsPath . toLazyByteString $ encode datum - - in Au.goldenVsFile name snapshotAuPath snapshotHsPath outputAction - -testCodecSnapshotLabel :: TestTree -testCodecSnapshotLabel = - let assembler (tagA, valA) = - let (tagC, valC) = basicTableConfig - valD = basicRunNumber - (tagE, valE) = basicSnapLevels - (tagF, valF) = basicSnapMergingTree - in (fuseAnnotations [tagA, tagC, tagE, tagF ], SnapshotMetaData valA valC valD valE valF) - in testCodecBuilder "SnapshotLabels" $ assembler <$> enumerateSnapshotLabel - -testCodecTableConfig :: TestTree -testCodecTableConfig = - let assembler (tagC, valC) = - let (tagA, valA) = basicSnapshotLabel - valD = basicRunNumber - (tagE, valE) = basicSnapLevels - (tagF, valF) = basicSnapMergingTree - in (fuseAnnotations [tagA, tagC, tagE, tagF ], SnapshotMetaData valA valC valD valE valF) - in testCodecBuilder "SnapshotConfig" $ assembler <$> enumerateTableConfig - -testCodecSnapLevels :: TestTree -testCodecSnapLevels = - let assembler (tagE, valE) = - let (tagA, valA) = basicSnapshotLabel - (tagC, valC) = basicTableConfig - valD = basicRunNumber - (tagF, valF) = basicSnapMergingTree - in (fuseAnnotations [tagA, tagC, tagE, tagF ], SnapshotMetaData valA valC valD valE valF) - in testCodecBuilder "SnapshotLevels" $ assembler <$> enumerateSnapLevels - -testCodecMergingTree :: TestTree -testCodecMergingTree = - let assembler (tagF, valF) = - let (tagA, valA) = basicSnapshotLabel - (tagC, valC) = basicTableConfig - valD = basicRunNumber - (tagE, valE) = basicSnapLevels - in (fuseAnnotations [tagA, tagC, tagE, tagF ], SnapshotMetaData valA valC valD valE valF) - in testCodecBuilder "SnapshotMergingTree" $ assembler <$> enumerateSnapMergingTree - -testCodecBuilder :: TestName -> [(ComponentAnnotation, SnapshotMetaData)] -> TestTree -testCodecBuilder tName metadata = - testGroup tName $ uncurry snapshotCodecTest <$> metadata - -type ComponentAnnotation = String - -fuseAnnotations :: [ComponentAnnotation] -> ComponentAnnotation -fuseAnnotations = List.intercalate "-" - -blank :: ComponentAnnotation -blank = "__" - -{---------------- -Defaults used when the SnapshotMetaData sub-component is not under test -----------------} - -basicSnapshotLabel :: (ComponentAnnotation, SnapshotLabel) -basicSnapshotLabel = head enumerateSnapshotLabel - -basicTableConfig :: (ComponentAnnotation, TableConfig) -basicTableConfig = ( fuseAnnotations $ "T0" : replicate 4 blank - , defaultTableConfig {confFencePointerIndex = CompactIndex} - ) - -basicRunNumber :: RunNumber -basicRunNumber = enumerateRunNumbers - -basicSnapLevels :: (ComponentAnnotation, SnapLevels SnapshotRun) -basicSnapLevels = head enumerateSnapLevels - -basicSnapMergingTree :: (ComponentAnnotation, Maybe (SnapMergingTree SnapshotRun)) -basicSnapMergingTree = head enumerateSnapMergingTree - -{---------------- -Enumeration of SnapshotMetaData sub-components -----------------} - -enumerateSnapshotLabel :: [(ComponentAnnotation, SnapshotLabel)] -enumerateSnapshotLabel = - [ ("B0", SnapshotLabel "UserProvidedLabel") - , ("B1", SnapshotLabel "") - ] - -enumerateTableConfig :: [(ComponentAnnotation, TableConfig)] -enumerateTableConfig = - [ ( fuseAnnotations [ "T1", d, e, f, g ] - , TableConfig - policy - ratio - allocs - bloom - fence - cache - merge - ) - | (_, policy) <- [(blank, LazyLevelling)] - , (_, ratio ) <- [(blank, Four)] - , (_, allocs) <- fmap AllocNumEntries <$> [(blank, magicNumber1)] - , (d, bloom ) <- enumerateBloomFilterAlloc - , (e, fence ) <- [("I0", CompactIndex), ("I1", OrdinaryIndex)] - , (f, cache ) <- enumerateDiskCachePolicy - , (g, merge ) <- [("G0", OneShot), ("G1", Incremental)] +{------------------------------------------------------------------------------- + Golden tests +-------------------------------------------------------------------------------} + +-- | Compare the serialization of snapshot metadata with a known reference file. +snapshotCodecGoldenTest :: + forall a. (Typeable a, EnumGolden a, Encode a) + => Proxy a + -> [TestTree] +snapshotCodecGoldenTest proxy = [ + go (nameGolden proxy annotation) datum + | (annotation, datum) <- enumGoldenAnnotated' proxy + ] + where + go name datum = + let -- Various paths + -- + -- There are three paths for both the checksum and the snapshot files: + -- 1. The filepath of type @FsPath@ to which data is written. + -- 2. The filepath of type @FilePath@ from which data is read. + -- 3. The filepath of type @FilePath@ against which the data is compared. + -- + -- These file types' bindings have the following infix annotations, respectively: + -- 1. (Fs) for FsPath + -- 2. (Hs) for "Haskell" path + -- 3. (Au) for "Golden file" path + snapshotFsPath = mkFsPath [name] <.> "snapshot" + snapshotHsPath = fsToFilePath goldenDataMountPoint snapshotFsPath + snapshotAuPath = snapshotHsPath <> ".golden" + + -- IO actions + runnerIO :: FS.HasFS IO HandleIO + runnerIO = ioHasFS goldenDataMountPoint + removeIfExists :: FsPath -> IO () + removeIfExists fp = + FS.doesFileExist runnerIO fp >>= (`when` (FS.removeFile runnerIO fp)) + outputAction :: IO () + outputAction = do + -- Ensure that if the output file already exists, we remove it and + -- re-write out the serialized data. This ensures that there are no + -- false-positives, false-negatives, or irrelevant I/O exceptions. + removeIfExists snapshotFsPath + BSL.writeFile snapshotHsPath . toLazyByteString $ encode datum + + in Au.goldenVsFile name snapshotAuPath snapshotHsPath outputAction + +{------------------------------------------------------------------------------- + Mapping +-------------------------------------------------------------------------------} + +type Constraints a = (Typeable a, Encode a, EnumGolden a) + +-- | Do something for all snapshot types and collect the results +forallSnapshotTypes :: + (forall a. Constraints a => Proxy a -> b) + -> [b] +forallSnapshotTypes f = [ + -- SnapshotMetaData + f (Proxy @SnapshotMetaData) + , f (Proxy @SnapshotLabel) + , f (Proxy @SnapshotRun) + -- TableConfig + , f (Proxy @TableConfig) + , f (Proxy @MergePolicy) + , f (Proxy @SizeRatio) + , f (Proxy @WriteBufferAlloc) + , f (Proxy @BloomFilterAlloc) + , f (Proxy @FencePointerIndexType) + , f (Proxy @DiskCachePolicy) + , f (Proxy @MergeSchedule) + -- SnapLevels + , f (Proxy @(SnapLevels SnapshotRun)) + , f (Proxy @(SnapLevel SnapshotRun)) + , f (Proxy @(V.Vector SnapshotRun)) + , f (Proxy @RunNumber) + , f (Proxy @(SnapIncomingRun SnapshotRun)) + , f (Proxy @MergePolicyForLevel) + , f (Proxy @RunDataCaching) + , f (Proxy @RunBloomFilterAlloc) + , f (Proxy @IndexType) + , f (Proxy @RunParams) + , f (Proxy @(SnapMergingRun LevelMergeType SnapshotRun)) + , f (Proxy @MergeDebt) + , f (Proxy @MergeCredits) + , f (Proxy @NominalDebt) + , f (Proxy @NominalCredits) + , f (Proxy @LevelMergeType) + , f (Proxy @TreeMergeType) + , f (Proxy @(SnapMergingTree SnapshotRun)) + , f (Proxy @(SnapMergingTreeState SnapshotRun)) + , f (Proxy @(SnapMergingRun TreeMergeType SnapshotRun)) + , f (Proxy @(SnapPendingMerge SnapshotRun)) + , f (Proxy @(SnapPreExistingRun SnapshotRun)) ] -enumerateSnapLevels :: [(ComponentAnnotation, SnapLevels SnapshotRun)] -enumerateSnapLevels = fmap (SnapLevels . V.singleton) <$> enumerateSnapLevel - -{---------------- -Enumeration of SnapLevel sub-components -----------------} - -enumerateSnapLevel :: [(ComponentAnnotation, SnapLevel SnapshotRun)] -enumerateSnapLevel = do - (a, run) <- enumerateSnapIncomingRun - (b, vec) <- enumerateVectorRunInfo - [( fuseAnnotations [ a, b ], SnapLevel run vec)] - -enumerateSnapIncomingRun :: [(ComponentAnnotation, SnapIncomingRun SnapshotRun)] -enumerateSnapIncomingRun = - let - inSnaps = - [ (fuseAnnotations ["R1", a, b], - SnapIncomingMergingRun policy nominalDebt nominalCredits sState) - | (a, policy ) <- [("P0", LevelTiering), ("P1", LevelLevelling)] - , nominalDebt <- NominalDebt <$> [ magicNumber2 ] - , nominalCredits <- NominalCredits <$> [ magicNumber1 ] - , (b, sState ) <- enumerateSnapMergingRun enumerateLevelMergeType - ] - in fold - [ [(fuseAnnotations $ "R0" : replicate 4 blank, - SnapIncomingSingleRun enumerateOpenRunInfo)] - , inSnaps +{------------------------------------------------------------------------------- + Enumeration class +-------------------------------------------------------------------------------} + +-- | Enumerate values of type @a@ for golden tests +-- +-- To prevent combinatorial explosion, the enumeration should generally be +-- /shallow/: the different constructors for type @a@ should be enumerated +-- without recursively enumerating the constructors' fields. For example, +-- enumerating @Maybe Int@ should give us something like: +-- +-- > enumGolden @(Maybe Int) = [ Just 17, Nothing ] +-- +-- This is generally a suitable approach, since the snapshot encodings do not +-- encode types differently depending on values in the constructor fields. +-- +-- Example (recursive) instances that prevent combinatorial explosion: +-- +-- @ +-- instance EnumGolden a => EnumGolden (Maybe a) where +-- enumGolden = [ Just (singGolden @a), Nothing ] +-- instance EnumGolden Int where +-- enumGolden = [17, -72] -- singGolden = 17 +-- @ +-- +-- If there are encoders that do require more elaborate (recursive) +-- enumerations, then it is okay to deviate from shallow enumerations, but take +-- care not to explode the combinatorics ;) +class EnumGolden a where + {-# MINIMAL enumGolden | enumGoldenAnnotated | singGolden #-} + + -- | Enumerated values. The enumeration should be /shallow/. + -- + -- The default implementation is to return a singleton list containing + -- 'singGolden'. + enumGolden :: [a] + enumGolden = [ singGolden ] + + -- | Enumerated values with an annotation for naming purposes. The enumeration + -- should be /shallow/, and the annotations should be unique. + -- + -- The default implementation is to annotate 'enumGolden' with capital letters + -- starting with @\'A\'@. + enumGoldenAnnotated :: [(Annotation, a)] + enumGoldenAnnotated = zip [[c] | c <- ['A' .. 'Z']] enumGolden + + -- | A singleton enumerated value. This is mainly useful for superclass + -- instances. + -- + -- The default implementation is to take the 'head' of 'enumGoldenAnnotated'. + singGolden :: a + singGolden = snd $ head enumGoldenAnnotated + +type Annotation = String + +enumGoldenAnnotated' :: EnumGolden a => Proxy a -> [(Annotation, a)] +enumGoldenAnnotated' _ = enumGoldenAnnotated + +{------------------------------------------------------------------------------- + Enumeration class: names and file paths +-------------------------------------------------------------------------------} + +nameGolden :: Typeable a => Proxy a -> Annotation -> String +nameGolden p ann = map spaceToUnderscore (show $ typeRep p) ++ "." ++ ann + +spaceToUnderscore :: Char -> Char +spaceToUnderscore ' ' = '_' +spaceToUnderscore c = c + +{------------------------------------------------------------------------------- + Enumeration class: instances +-------------------------------------------------------------------------------} + +instance EnumGolden SnapshotMetaData where + singGolden = SnapshotMetaData singGolden singGolden singGolden singGolden singGolden + where + _coveredAllCases = \case + SnapshotMetaData{} -> () + +instance EnumGolden SnapshotLabel where + enumGolden = [ + SnapshotLabel "UserProvidedLabel" + , SnapshotLabel "" ] - -enumerateSnapMergingRun :: - [(ComponentAnnotation, t)] - -> [(ComponentAnnotation, SnapMergingRun t SnapshotRun)] -enumerateSnapMergingRun mTypes = - [ (fuseAnnotations ["C0", blank, blank], - SnapCompletedMerge mergeDebt enumerateOpenRunInfo) - | mergeDebt <- (MR.MergeDebt. MR.MergeCredits) <$> [ magicNumber2 ] - ] - ++ [ (fuseAnnotations ["C1", a, b], - SnapOngoingMerge runParams mergeCredits runVec mType) - | let runParams = enumerateRunParams - , mergeCredits <- MR.MergeCredits <$> [ magicNumber2 ] - , (a, runVec ) <- enumerateVectorRunInfo - , (b, mType ) <- mTypes + where + _coveredAllCases = \case + SnapshotLabel{} -> () + +instance EnumGolden TableConfig where + singGolden = TableConfig singGolden singGolden singGolden singGolden singGolden singGolden singGolden + where + _coveredAllCases = \case + TableConfig{} -> () + +instance EnumGolden MergePolicy where + singGolden = LazyLevelling + where + _coveredAllCases = \case + LazyLevelling{} -> () + + +instance EnumGolden SizeRatio where + singGolden = Four + where + _coveredAllCases = \case + Four{} -> () + +instance EnumGolden WriteBufferAlloc where + singGolden = AllocNumEntries magicNumber2 + where + _coveredAllCases = \case + AllocNumEntries{} -> () + +instance EnumGolden BloomFilterAlloc where + enumGolden = [ AllocFixed magicNumber3, AllocRequestFPR pi ] + where + _coveredAllCases = \case + AllocFixed{} -> () + AllocRequestFPR{} -> () + +instance EnumGolden FencePointerIndexType where + enumGolden = [ CompactIndex, OrdinaryIndex ] + where + _coveredAllCases = \case + CompactIndex{} -> () + OrdinaryIndex{} -> () + +instance EnumGolden DiskCachePolicy where + enumGolden = [ DiskCacheAll, DiskCacheLevelsAtOrBelow magicNumber3, DiskCacheNone ] + where + _coveredAllCases = \case + DiskCacheAll{} -> () + DiskCacheLevelsAtOrBelow{} -> () + DiskCacheNone{} -> () + +instance EnumGolden MergeSchedule where + enumGolden = [ OneShot, Incremental ] + where + _coveredAllCases = \case + OneShot{} -> () + Incremental{} -> () + +instance EnumGolden (SnapLevels SnapshotRun) where + singGolden = SnapLevels singGolden + where + _coveredAllCases = \case + SnapLevels{} -> () + +instance EnumGolden (SnapLevel SnapshotRun) where + singGolden = SnapLevel singGolden singGolden + where + _coveredAllCases = \case + SnapLevel{} -> () + +instance EnumGolden (SnapIncomingRun SnapshotRun) where + enumGolden = [ + SnapIncomingMergingRun singGolden singGolden singGolden singGolden + , SnapIncomingSingleRun singGolden + ] + where + _coveredAllCases = \case + SnapIncomingMergingRun{} -> () + SnapIncomingSingleRun{} -> () + +instance EnumGolden MergePolicyForLevel where + enumGolden = [ LevelTiering, LevelLevelling ] + where + _coveredAllCases = \case + LevelTiering -> () + LevelLevelling -> () + +instance EnumGolden LevelMergeType where + enumGolden = [ MergeMidLevel, MergeLastLevel ] + where + _coveredAllCases = \case + MergeMidLevel{} -> () + MergeLastLevel{} -> () + +instance EnumGolden (SnapMergingTree SnapshotRun) where + singGolden = SnapMergingTree singGolden + where + _coveredAllCases = \case + SnapMergingTree{} -> () + +instance EnumGolden (SnapMergingTreeState SnapshotRun) where + enumGolden = [ + SnapCompletedTreeMerge singGolden + , SnapPendingTreeMerge singGolden + , SnapOngoingTreeMerge singGolden + ] + where + _coveredAllCases = \case + SnapCompletedTreeMerge{} -> () + SnapPendingTreeMerge{} -> () + SnapOngoingTreeMerge{} -> () + +instance EnumGolden (SnapPendingMerge SnapshotRun) where + enumGolden = [ + SnapPendingLevelMerge singGolden singGolden + , SnapPendingUnionMerge singGolden + ] + where + _coveredAllCases = \case + SnapPendingLevelMerge{} -> () + SnapPendingUnionMerge{} -> () + +instance EnumGolden (SnapPreExistingRun SnapshotRun) where + enumGolden = [ + SnapPreExistingRun singGolden + , SnapPreExistingMergingRun singGolden + ] + where + _coveredAllCases = \case + SnapPreExistingRun{} -> () + SnapPreExistingMergingRun{} -> () + +instance EnumGolden TreeMergeType where + enumGolden = [ MergeLevel, MergeUnion ] + where + _coveredAllCases = \case + MergeLevel{} -> () + MergeUnion{} -> () + +instance EnumGolden a => EnumGolden (Maybe a) where + enumGolden = [ Just singGolden, Nothing ] + where + _coveredAllCases = \case + Just{} -> () + Nothing{} -> () + +instance EnumGolden a => EnumGolden (V.Vector a) where + enumGolden = [ + V.fromList [ singGolden, singGolden ] + , mempty + , V.fromList [ singGolden ] ] -enumerateLevelMergeType :: [(ComponentAnnotation, MR.LevelMergeType)] -enumerateLevelMergeType = - [("L0", MR.MergeMidLevel), ("L1", MR.MergeLastLevel)] - -enumerateVectorRunInfo :: [(ComponentAnnotation, Vector SnapshotRun)] -enumerateVectorRunInfo = - [ ("V0", mempty) - , ("V1", V.fromList [enumerateOpenRunInfo]) - , ("V2", V.fromList [enumerateOpenRunInfo, - enumerateOpenRunInfo { - snapRunNumber = RunNumber magicNumber2 - } ]) - ] - -{---------------- -Enumeration of SnapMergingTree sub-components -----------------} - -enumerateSnapMergingTree :: [(ComponentAnnotation, Maybe (SnapMergingTree SnapshotRun))] -enumerateSnapMergingTree = - let noneTrees = (fuseAnnotations $ "M0" : replicate 11 blank, Nothing) - someTrees = reannotate <$> enumerateSnapMergingTreeState True - reannotate (tag, val) = (fuseAnnotations ["M1", tag], Just val) - in noneTrees : someTrees - -enumerateSnapMergingTreeState :: Bool -> [(ComponentAnnotation, SnapMergingTree SnapshotRun)] -enumerateSnapMergingTreeState expandable = - let s0 = [ (fuseAnnotations $ "S0" : replicate 10 blank, SnapCompletedTreeMerge enumerateOpenRunInfo) ] - s1 = do - (tagX, valX) <- enumerateSnapPendingMerge expandable - [ (fuseAnnotations ["S1", tagX], SnapPendingTreeMerge valX) ] - s2 = do - (tagX, valX) <- enumerateSnapOngoingTreeMerge - [ (fuseAnnotations ["S2", tagX], valX) ] - in second SnapMergingTree <$> fold [ s0, s1, s2 ] - -enumerateSnapOngoingTreeMerge :: [(ComponentAnnotation, SnapMergingTreeState SnapshotRun)] -enumerateSnapOngoingTreeMerge = do - (tagX, valX) <- enumerateSnapMergingRun enumerateTreeMergeType - let value = SnapOngoingTreeMerge valX - pure ( fuseAnnotations $ ["G0", blank, tagX] <> replicate 5 blank, value ) - -enumerateSnapPendingMerge :: Bool -> [(ComponentAnnotation, SnapPendingMerge SnapshotRun)] -enumerateSnapPendingMerge expandable = - let (tagTrees, subTrees) - | not expandable = ("M0", []) - | otherwise = ("M1", snd <$> enumerateSnapMergingTreeState False) - headMay [] = Nothing - headMay (x:_) = Just x - prefix = do - extra <- [False, True ] - (tagPre, valPre) <- enumerateSnapPreExistingRun - (tagExt, valExt) <- - if extra - then second pure <$> enumerateSnapPreExistingRun - else [(fuseAnnotations $ replicate 4 blank, [])] - let preValues = [ valPre ] <> valExt - pure (fuseAnnotations [ "P0", tagPre, tagExt, tagTrees], SnapPendingLevelMerge preValues $ headMay subTrees) - in prefix <> [(fuseAnnotations $ fold [["P1"], replicate 8 blank, [tagTrees]], SnapPendingUnionMerge subTrees)] - -enumerateSnapPreExistingRun :: [(ComponentAnnotation, SnapPreExistingRun SnapshotRun)] -enumerateSnapPreExistingRun = - ( fuseAnnotations ("E0" : replicate 3 blank), SnapPreExistingRun enumerateOpenRunInfo) - : [ (fuseAnnotations ["E1", tagX], SnapPreExistingMergingRun valX) - | (tagX, valX) <- enumerateSnapMergingRun enumerateLevelMergeType +instance EnumGolden a => EnumGolden [a] where + enumGolden = [ + [singGolden, singGolden] + , [] + , [singGolden] ] -enumerateTreeMergeType :: [(ComponentAnnotation, MR.TreeMergeType)] -enumerateTreeMergeType = - [("T0", MR.MergeLevel), ("T1", MR.MergeUnion)] - -{---------------- -Enumeration of SnapshotMetaData sub-sub-components and so on... -----------------} - -enumerateBloomFilterAlloc :: [(ComponentAnnotation, BloomFilterAlloc)] -enumerateBloomFilterAlloc = - [ ("A0",AllocFixed magicNumber3) - , ("A1",AllocRequestFPR pi) - ] - -enumerateDiskCachePolicy :: [(ComponentAnnotation, DiskCachePolicy)] -enumerateDiskCachePolicy = - [ ("D0", DiskCacheAll) - , ("D1", DiskCacheNone) - , ("D2", DiskCacheLevelsAtOrBelow 1) - ] - -enumerateRunNumbers :: RunNumber -enumerateRunNumbers = RunNumber magicNumber2 - ---TODO: use a proper enumeration, but don't cause a combinatorial explosion. -enumerateRunParams :: MR.RunParams -enumerateRunParams = - MR.RunParams { - MR.runParamCaching = NoCacheRunData, - MR.runParamAlloc = RunAllocFixed 10, - MR.runParamIndex = Compact - } - ---TODO: use a proper enumeration, but don't cause a combinatorial explosion of --- golden tests. Perhaps do all combos as a direct golden test, but then where --- it is embedded, just use one combo. -enumerateOpenRunInfo :: SnapshotRun -enumerateOpenRunInfo = - SnapshotRun { - snapRunNumber = enumerateRunNumbers, - snapRunCaching = CacheRunData, - snapRunIndex = Compact - } - --- Randomly chosen numbers +instance EnumGolden RunParams where + singGolden = RunParams singGolden singGolden singGolden + where + _coveredAllCases = \case + RunParams{} -> () + +instance EnumGolden t => EnumGolden (SnapMergingRun t SnapshotRun) where + enumGolden = [ + SnapCompletedMerge singGolden singGolden + , SnapOngoingMerge singGolden singGolden singGolden singGolden + ] + where + _coveredAllCases = \case + SnapCompletedMerge{} -> () + SnapOngoingMerge{} -> () + +instance EnumGolden RunBloomFilterAlloc where + enumGolden = [ + RunAllocFixed magicNumber3 + , RunAllocRequestFPR pi + ] + where + _coveredAllCases = \case + RunAllocFixed{} -> () + RunAllocRequestFPR{} -> () + +instance EnumGolden RunNumber where + singGolden = RunNumber magicNumber3 + where + _coveredAllCases = \case + RunNumber{} -> () + +instance EnumGolden IndexType where + enumGolden = [ + Compact + , Ordinary + ] + where + _coveredAllCases = \case + Compact{} -> () + Ordinary{} -> () + +instance EnumGolden RunDataCaching where + enumGolden = [ + CacheRunData + , NoCacheRunData + ] + where + _coveredAllCases = \case + CacheRunData{} -> () + NoCacheRunData{} -> () + +instance EnumGolden SnapshotRun where + singGolden = SnapshotRun singGolden singGolden singGolden + where + _coveredAllCases = \case + SnapshotRun{} -> () + +instance EnumGolden MergeDebt where + singGolden = MergeDebt magicNumber2 + where + _coveredAllCases = \case + MergeDebt{} -> () + +instance EnumGolden MergeCredits where + singGolden = MergeCredits magicNumber2 + where + _coveredAllCases = \case + MergeCredits{} -> () + +instance EnumGolden NominalDebt where + singGolden = NominalDebt magicNumber2 + where + _coveredAllCases = \case + NominalDebt{} -> () + +instance EnumGolden NominalCredits where + singGolden = NominalCredits magicNumber1 + where + _coveredAllCases = \case + NominalCredits{} -> () + + -- Randomly chosen numbers magicNumber1, magicNumber2, magicNumber3 :: Enum e => e magicNumber1 = toEnum 42 magicNumber2 = toEnum 88 From 72c7b27f9eac29cfc4aa90432292652751086f00 Mon Sep 17 00:00:00 2001 From: Joris Dral Date: Thu, 8 May 2025 10:53:16 +0200 Subject: [PATCH 3/4] Regenerate golden files --- ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 48 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...P0-E0-__-__-__-E0-__-__-__-M1.snapshot.golden | Bin 76 -> 0 bytes ...P0-E0-__-__-__-E1-C0-__-__-M1.snapshot.golden | Bin 80 -> 0 bytes ...P0-E0-__-__-__-E1-C1-V0-L0-M1.snapshot.golden | Bin 83 -> 0 bytes ...P0-E0-__-__-__-E1-C1-V0-L1-M1.snapshot.golden | Bin 83 -> 0 bytes ...P0-E0-__-__-__-E1-C1-V1-L0-M1.snapshot.golden | Bin 89 -> 0 bytes ...P0-E0-__-__-__-E1-C1-V1-L1-M1.snapshot.golden | Bin 89 -> 0 bytes ...P0-E0-__-__-__-E1-C1-V2-L0-M1.snapshot.golden | Bin 95 -> 0 bytes ...P0-E0-__-__-__-E1-C1-V2-L1-M1.snapshot.golden | Bin 95 -> 0 bytes ...P0-E0-__-__-__-__-__-__-__-M1.snapshot.golden | Bin 68 -> 0 bytes ...P0-E1-C0-__-__-E0-__-__-__-M1.snapshot.golden | Bin 80 -> 0 bytes ...P0-E1-C0-__-__-E1-C0-__-__-M1.snapshot.golden | Bin 84 -> 0 bytes ...P0-E1-C0-__-__-E1-C1-V0-L0-M1.snapshot.golden | Bin 87 -> 0 bytes ...P0-E1-C0-__-__-E1-C1-V0-L1-M1.snapshot.golden | Bin 87 -> 0 bytes ...P0-E1-C0-__-__-E1-C1-V1-L0-M1.snapshot.golden | Bin 93 -> 0 bytes ...P0-E1-C0-__-__-E1-C1-V1-L1-M1.snapshot.golden | Bin 93 -> 0 bytes ...P0-E1-C0-__-__-E1-C1-V2-L0-M1.snapshot.golden | Bin 99 -> 0 bytes ...P0-E1-C0-__-__-E1-C1-V2-L1-M1.snapshot.golden | Bin 99 -> 0 bytes ...P0-E1-C0-__-__-__-__-__-__-M1.snapshot.golden | Bin 72 -> 0 bytes ...P0-E1-C1-V0-L0-E0-__-__-__-M1.snapshot.golden | Bin 83 -> 0 bytes ...P0-E1-C1-V0-L0-E1-C0-__-__-M1.snapshot.golden | Bin 87 -> 0 bytes ...P0-E1-C1-V0-L0-E1-C1-V0-L0-M1.snapshot.golden | Bin 90 -> 0 bytes ...P0-E1-C1-V0-L0-E1-C1-V0-L1-M1.snapshot.golden | Bin 90 -> 0 bytes ...P0-E1-C1-V0-L0-E1-C1-V1-L0-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V0-L0-E1-C1-V1-L1-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V0-L0-E1-C1-V2-L0-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V0-L0-E1-C1-V2-L1-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V0-L0-__-__-__-__-M1.snapshot.golden | Bin 75 -> 0 bytes ...P0-E1-C1-V0-L1-E0-__-__-__-M1.snapshot.golden | Bin 83 -> 0 bytes ...P0-E1-C1-V0-L1-E1-C0-__-__-M1.snapshot.golden | Bin 87 -> 0 bytes ...P0-E1-C1-V0-L1-E1-C1-V0-L0-M1.snapshot.golden | Bin 90 -> 0 bytes ...P0-E1-C1-V0-L1-E1-C1-V0-L1-M1.snapshot.golden | Bin 90 -> 0 bytes ...P0-E1-C1-V0-L1-E1-C1-V1-L0-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V0-L1-E1-C1-V1-L1-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V0-L1-E1-C1-V2-L0-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V0-L1-E1-C1-V2-L1-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V0-L1-__-__-__-__-M1.snapshot.golden | Bin 75 -> 0 bytes ...P0-E1-C1-V1-L0-E0-__-__-__-M1.snapshot.golden | Bin 89 -> 0 bytes ...P0-E1-C1-V1-L0-E1-C0-__-__-M1.snapshot.golden | Bin 93 -> 0 bytes ...P0-E1-C1-V1-L0-E1-C1-V0-L0-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V1-L0-E1-C1-V0-L1-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V1-L0-E1-C1-V1-L0-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V1-L0-E1-C1-V1-L1-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V1-L0-E1-C1-V2-L0-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V1-L0-E1-C1-V2-L1-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V1-L0-__-__-__-__-M1.snapshot.golden | Bin 81 -> 0 bytes ...P0-E1-C1-V1-L1-E0-__-__-__-M1.snapshot.golden | Bin 89 -> 0 bytes ...P0-E1-C1-V1-L1-E1-C0-__-__-M1.snapshot.golden | Bin 93 -> 0 bytes ...P0-E1-C1-V1-L1-E1-C1-V0-L0-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V1-L1-E1-C1-V0-L1-M1.snapshot.golden | Bin 96 -> 0 bytes ...P0-E1-C1-V1-L1-E1-C1-V1-L0-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V1-L1-E1-C1-V1-L1-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V1-L1-E1-C1-V2-L0-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V1-L1-E1-C1-V2-L1-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V1-L1-__-__-__-__-M1.snapshot.golden | Bin 81 -> 0 bytes ...P0-E1-C1-V2-L0-E0-__-__-__-M1.snapshot.golden | Bin 95 -> 0 bytes ...P0-E1-C1-V2-L0-E1-C0-__-__-M1.snapshot.golden | Bin 99 -> 0 bytes ...P0-E1-C1-V2-L0-E1-C1-V0-L0-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V2-L0-E1-C1-V0-L1-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V2-L0-E1-C1-V1-L0-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V2-L0-E1-C1-V1-L1-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V2-L0-E1-C1-V2-L0-M1.snapshot.golden | Bin 114 -> 0 bytes ...P0-E1-C1-V2-L0-E1-C1-V2-L1-M1.snapshot.golden | Bin 114 -> 0 bytes ...P0-E1-C1-V2-L0-__-__-__-__-M1.snapshot.golden | Bin 87 -> 0 bytes ...P0-E1-C1-V2-L1-E0-__-__-__-M1.snapshot.golden | Bin 95 -> 0 bytes ...P0-E1-C1-V2-L1-E1-C0-__-__-M1.snapshot.golden | Bin 99 -> 0 bytes ...P0-E1-C1-V2-L1-E1-C1-V0-L0-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V2-L1-E1-C1-V0-L1-M1.snapshot.golden | Bin 102 -> 0 bytes ...P0-E1-C1-V2-L1-E1-C1-V1-L0-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V2-L1-E1-C1-V1-L1-M1.snapshot.golden | Bin 108 -> 0 bytes ...P0-E1-C1-V2-L1-E1-C1-V2-L0-M1.snapshot.golden | Bin 114 -> 0 bytes ...P0-E1-C1-V2-L1-E1-C1-V2-L1-M1.snapshot.golden | Bin 114 -> 0 bytes ...P0-E1-C1-V2-L1-__-__-__-__-M1.snapshot.golden | Bin 87 -> 0 bytes ...P1-__-__-__-__-__-__-__-__-M1.snapshot.golden | Bin 3118 -> 0 bytes ...G0-__-C0-__-__-__-__-__-__-__.snapshot.golden | Bin 59 -> 0 bytes ...G0-__-C1-V0-T0-__-__-__-__-__.snapshot.golden | Bin 62 -> 0 bytes ...G0-__-C1-V0-T1-__-__-__-__-__.snapshot.golden | Bin 62 -> 0 bytes ...G0-__-C1-V1-T0-__-__-__-__-__.snapshot.golden | Bin 68 -> 0 bytes ...G0-__-C1-V1-T1-__-__-__-__-__.snapshot.golden | Bin 68 -> 0 bytes ...G0-__-C1-V2-T0-__-__-__-__-__.snapshot.golden | Bin 74 -> 0 bytes ...G0-__-C1-V2-T1-__-__-__-__-__.snapshot.golden | Bin 74 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 54 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 60 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 57 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 63 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 69 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 60 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 60 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 84 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 84 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 57 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 63 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 69 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 60 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 60 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 66 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 84 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 72 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 78 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 84 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 50 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 50 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 49 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 50 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 50 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 56 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 56 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 55 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 56 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 56 -> 0 bytes ...__-__-__-__-__-__-__-__-__-__.snapshot.golden | Bin 31 -> 0 bytes .../BloomFilterAlloc.A.snapshot.golden | Bin 0 -> 5 bytes .../BloomFilterAlloc.B.snapshot.golden | 1 + .../DiskCachePolicy.A.snapshot.golden | Bin 0 -> 2 bytes .../DiskCachePolicy.B.snapshot.golden | Bin 0 -> 5 bytes .../DiskCachePolicy.C.snapshot.golden | 1 + .../FencePointerIndexType.A.snapshot.golden | Bin 0 -> 1 bytes .../FencePointerIndexType.B.snapshot.golden | 1 + .../snapshot-codec/IndexType.A.snapshot.golden | 1 + .../snapshot-codec/IndexType.B.snapshot.golden | Bin 0 -> 1 bytes .../LevelMergeType.A.snapshot.golden | Bin 0 -> 1 bytes .../LevelMergeType.B.snapshot.golden | 1 + .../MergeCredits.A.snapshot.golden | 1 + .../snapshot-codec/MergeDebt.A.snapshot.golden | 1 + .../snapshot-codec/MergePolicy.A.snapshot.golden | Bin 0 -> 1 bytes .../MergePolicyForLevel.A.snapshot.golden | Bin 0 -> 1 bytes .../MergePolicyForLevel.B.snapshot.golden | 1 + .../MergeSchedule.A.snapshot.golden | Bin 0 -> 1 bytes .../MergeSchedule.B.snapshot.golden | 1 + .../NominalCredits.A.snapshot.golden | 1 + .../snapshot-codec/NominalDebt.A.snapshot.golden | 1 + .../RunBloomFilterAlloc.A.snapshot.golden | Bin 0 -> 5 bytes .../RunBloomFilterAlloc.B.snapshot.golden | 1 + .../RunDataCaching.A.snapshot.golden | Bin 0 -> 1 bytes .../RunDataCaching.B.snapshot.golden | 1 + .../snapshot-codec/RunNumber.A.snapshot.golden | Bin 0 -> 3 bytes .../snapshot-codec/RunParams.A.snapshot.golden | Bin 0 -> 9 bytes .../snapshot-codec/SizeRatio.A.snapshot.golden | 1 + ...SnapIncomingRun_SnapshotRun.A.snapshot.golden | Bin 0 -> 18 bytes ...SnapIncomingRun_SnapshotRun.B.snapshot.golden | Bin 0 -> 9 bytes .../SnapLevel_SnapshotRun.A.snapshot.golden | Bin 0 -> 34 bytes .../SnapLevels_SnapshotRun.A.snapshot.golden | Bin 0 -> 69 bytes ..._LevelMergeType_SnapshotRun.A.snapshot.golden | Bin 0 -> 11 bytes ..._LevelMergeType_SnapshotRun.B.snapshot.golden | Bin 0 -> 29 bytes ...n_TreeMergeType_SnapshotRun.A.snapshot.golden | Bin 0 -> 11 bytes ...n_TreeMergeType_SnapshotRun.B.snapshot.golden | Bin 0 -> 29 bytes ...ergingTreeState_SnapshotRun.A.snapshot.golden | Bin 0 -> 9 bytes ...ergingTreeState_SnapshotRun.B.snapshot.golden | Bin 0 -> 32 bytes ...ergingTreeState_SnapshotRun.C.snapshot.golden | Bin 0 -> 13 bytes ...SnapMergingTree_SnapshotRun.A.snapshot.golden | Bin 0 -> 9 bytes ...napPendingMerge_SnapshotRun.A.snapshot.golden | Bin 0 -> 30 bytes ...napPendingMerge_SnapshotRun.B.snapshot.golden | Bin 0 -> 21 bytes ...pPreExistingRun_SnapshotRun.A.snapshot.golden | Bin 0 -> 9 bytes ...pPreExistingRun_SnapshotRun.B.snapshot.golden | Bin 0 -> 13 bytes .../SnapshotLabel.A.snapshot.golden | 1 + .../SnapshotLabel.B.snapshot.golden | 1 + .../SnapshotMetaData.A.snapshot.golden | Bin 0 -> 116 bytes .../snapshot-codec/SnapshotRun.A.snapshot.golden | Bin 0 -> 7 bytes .../snapshot-codec/TableConfig.A.snapshot.golden | Bin 0 -> 16 bytes .../TreeMergeType.A.snapshot.golden | 1 + .../TreeMergeType.B.snapshot.golden | 1 + .../Vector_SnapshotRun.A.snapshot.golden | Bin 0 -> 15 bytes .../Vector_SnapshotRun.B.snapshot.golden | 1 + .../Vector_SnapshotRun.C.snapshot.golden | Bin 0 -> 8 bytes .../WriteBufferAlloc.A.snapshot.golden | Bin 0 -> 4 bytes 205 files changed, 19 insertions(+) delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S0-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L0-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V0-L1-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E0-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C0-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V0-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V0-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V1-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V1-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V2-L0-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V2-L1-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P1-__-__-__-__-__-__-__-__-M1.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C0-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V0-T0-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V0-T1-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V1-T0-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V1-T1-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V2-T0-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V2-T1-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C0-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C0-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C0-__-__-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I0-D0-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I0-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I0-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I0-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I0-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I0-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I1-D0-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I1-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I1-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I1-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I1-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A0-I1-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D0-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D0-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden delete mode 100644 test/golden-file-data/snapshot-codec/B1-T0-__-__-__-__-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/BloomFilterAlloc.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/BloomFilterAlloc.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/DiskCachePolicy.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/DiskCachePolicy.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/DiskCachePolicy.C.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/FencePointerIndexType.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/FencePointerIndexType.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/IndexType.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/IndexType.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/LevelMergeType.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/LevelMergeType.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/MergeCredits.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/MergeDebt.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/MergePolicy.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/MergePolicyForLevel.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/MergePolicyForLevel.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/MergeSchedule.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/MergeSchedule.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/NominalCredits.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/NominalDebt.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/RunBloomFilterAlloc.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/RunBloomFilterAlloc.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/RunDataCaching.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/RunDataCaching.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/RunNumber.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/RunParams.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SizeRatio.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapIncomingRun_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapIncomingRun_SnapshotRun.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapLevel_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapLevels_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingRun_LevelMergeType_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingRun_LevelMergeType_SnapshotRun.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingRun_TreeMergeType_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingRun_TreeMergeType_SnapshotRun.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.C.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapMergingTree_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapPendingMerge_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapPendingMerge_SnapshotRun.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapPreExistingRun_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapPreExistingRun_SnapshotRun.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapshotLabel.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapshotLabel.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapshotMetaData.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/TableConfig.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/TreeMergeType.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/TreeMergeType.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/Vector_SnapshotRun.A.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/Vector_SnapshotRun.B.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/Vector_SnapshotRun.C.snapshot.golden create mode 100644 test/golden-file-data/snapshot-codec/WriteBufferAlloc.A.snapshot.golden diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index d6d23502ce6e6bac777c91427b49b8d1e49c5e9d..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 48 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlZ1@HM DiaZXs diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S0-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S0-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index ee9489c6cf5dc30b0831b642934f1214946fbe1d..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nPD FFaYuw4>te+ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E0-__-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E0-__-__-__-M1.snapshot.golden deleted file mode 100644 index b800d62276af4f38de3451132bcd11d0a1ee5533..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 76 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ MW@u_+fbh_10C1QStpET3 diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C0-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C0-__-__-M1.snapshot.golden deleted file mode 100644 index aa3c71239802e406ef70a033e5a893e970f4a304..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 80 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ SW@u_+fbc*Zi3lhgDh2?>jTE5( diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V0-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V0-L0-M1.snapshot.golden deleted file mode 100644 index 2404678bbe6693fba7f50771d9ec18587ef9e069..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 83 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ YW@u_+fbg0aTY=(?Ky^Sx4Gb`000h<*K>z>% diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V0-L1-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V0-L1-M1.snapshot.golden deleted file mode 100644 index 9015506ccc3a81569c8688a14d013400e1ae6988..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 83 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ ZW@u_+fbg0aTY=(?Ky^Sx4L}+q3;+b*6+!?2 diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V1-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V1-L0-M1.snapshot.golden deleted file mode 100644 index 2266abf9e38be645eaea3e493bc28df88fa90cef..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 89 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ ZW@u_+fbg0aTY=(?Ky@HR5HSXrBmjuO7B>I@ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V1-L1-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V1-L1-M1.snapshot.golden deleted file mode 100644 index e19ef9f072e86de1416e3a5bce990924cc0bed9a..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 89 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ aW@u_+fbg0aTY=(?Ky@HR5HTPR!T$rd;O diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V2-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V2-L0-M1.snapshot.golden deleted file mode 100644 index 94b902a4bd22de65fcfccaae0e53f2e14fe34126..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 95 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ cW@u_+fbg0aTY=(?Ky^SxO%O2%$pBLV01|^2EdT%j diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V2-L1-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-E1-C1-V2-L1-M1.snapshot.golden deleted file mode 100644 index dce33bf574cb71a34cb1a8feb7934f93f560f3ef..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 95 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ cW@u_+fbg0aTY=(?Ky^SxO%O2%2^51c01}KBE&u=k diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-__-__-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E0-__-__-__-__-__-__-__-M1.snapshot.golden deleted file mode 100644 index bfc4181c698aca5084d7acba72e52ff29e34653b..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 68 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ MW@v0;fbd{60M<7WH2?qr diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E0-__-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E0-__-__-__-M1.snapshot.golden deleted file mode 100644 index 99599d8f9a97601cd0234c3682ea5b781e95f327..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 80 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ QW&rY6_o%0 diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V0-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V0-L0-M1.snapshot.golden deleted file mode 100644 index ebdd37aca62734a8188579257aa564ec0e543790..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 87 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ cW&rY4vx diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V1-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V1-L0-M1.snapshot.golden deleted file mode 100644 index ddebc9624bef8541af489fe42d551c140eb98134..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 93 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ dW&rY*g0M diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V2-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C0-__-__-E1-C1-V2-L0-M1.snapshot.golden deleted file mode 100644 index ebd0afb8180d15341c3abaf48885325b77047997..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 99 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ fW&rY3o0U`?k!!H=Y diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V1-L1-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L0-E1-C1-V1-L1-M1.snapshot.golden deleted file mode 100644 index 62bf1c237f1a46c9ea588c19251dd3f164e86b6f..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 102 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ YW&rY9fqX`wJV+8E!+=c?s01Pl0K+&K!T diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V2-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V2-L0-M1.snapshot.golden deleted file mode 100644 index 29a38f7d9fd5104b6387334da64c3664c86d524c..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 108 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ dW&rY9fqX`wJV+8E!-yi-1QCRg3{4CW1^`@A8Mpud diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V2-L1-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-E1-C1-V2-L1-M1.snapshot.golden deleted file mode 100644 index 2493c4ba5d6341ae26c8c5f2b83d1e1395ca834e..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 108 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ bW&rY9fqX`wJV+8E!-yi-1QCQuF+dmqTw58r diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-__-__-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V1-L1-__-__-__-__-M1.snapshot.golden deleted file mode 100644 index ab3856111088455c6001887235c585138bfbc216..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 81 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ WW@v0;Yz6Wef$|_phzyViVE_QzP!zxb diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E0-__-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E0-__-__-__-M1.snapshot.golden deleted file mode 100644 index e3c7215717a0b50b4e7706a9bf8bea8e98f881a2..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 95 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ aW&rY9fqX`wJW#R;A_E~AniwDq7!3dtt`{u; diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C0-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C0-__-__-M1.snapshot.golden deleted file mode 100644 index 0947e5f4968a3c8d77252f4a4863bf56dea9a917..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 99 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ eW&rY9fqX`wJW#R;A_E~AK=Kk15Ka>Vga!b0qZlCo diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V0-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V0-L0-M1.snapshot.golden deleted file mode 100644 index b124eb86b0fcad54f2f90646d9d6d27397ed95d1..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 102 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ cW&rY9fqX`wJW#R;A_E~AP^20dniwGB0KZ)r!2kdN diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V0-L1-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V0-L1-M1.snapshot.golden deleted file mode 100644 index a8159791a8b1d76b3cfd4e21943b5019df1930fa..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 102 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ bW&rY9fqX`wJW#R;A_E~AP^21wN+99@zh)T1 diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V1-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V1-L0-M1.snapshot.golden deleted file mode 100644 index 15de1b4043bbe5a2a731d8ea09f06f8e692b1914..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 108 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ cW&rY9fqX`wJW#R;A_E~AP^21Rf(#G_09aNTw*UYD diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V1-L1-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L0-E1-C1-V1-L1-M1.snapshot.golden deleted file mode 100644 index 96340a30b9a3c5e00719460dac5e3ba3780a7119..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 108 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ dW&rY9fqX`wJW#R;A_E~AP^20mfVga!b0xELY; diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V0-L0-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P0-E1-C1-V2-L1-E1-C1-V0-L0-M1.snapshot.golden deleted file mode 100644 index 5120beea76172f2e77e0f1608f45f4158743fd8e..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 102 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO^ cW&rY9fqX`wJW#R;A_E~AQKT9eniwGB0Kat@!TAwg3PC diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P1-__-__-__-__-__-__-__-__-M1.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S1-P1-__-__-__-__-__-__-__-__-M1.snapshot.golden deleted file mode 100644 index 4c62e48fbdb0728225f751a47c70774878e562fd..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 3118 zcmbtWK~BUl3`{CcyrA585JGT3>J_v-AR!?ZiF0dM?H70{X9B4=9^<&FI6>_3*q%(I zJ-pn#j{BSa^V{QY++E#2j8DgKM&aW6lEQhIL+po{D1L-~2yvoF@$;5KK2m%SGatV4 zDTVqWr#W&+)iJRpswr5(XawiXVd0mQRYkd~UJHQCK)eC}{hg*n^+qD|ce6@TcZ#AC zHnrUDr*-2cyFo#`u^77HSIlo!_? diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C0-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C0-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 7c1ec65e591a4569106306cf91970b5a32a353a9..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 59 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO? I1~MQV05ggZEC2ui diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V0-T0-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V0-T0-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 6b02b65a29f07cff6f1ae25b90d3ba3555c1ecff..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 62 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO? N1u_|dQb6$rMgU~X5X}Gp diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V0-T1-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V0-T1-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 967d71b0bf3a9d7a8b19198edfdd25c2c9e398ee..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 62 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO? N1u_|dQb6$rCIDp25Y7Mq diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V1-T0-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V1-T0-__-__-__-__-__.snapshot.golden deleted file mode 100644 index f0e7d8977671d53ca9c53f2e94cb0d695e653b02..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 68 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO? O1u_|dQXp}NAR_?J5fQ@x diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V1-T1-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V1-T1-__-__-__-__-__.snapshot.golden deleted file mode 100644 index e18612f5e65833366b6d77717a6fd51016c467e5..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 68 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO? O1u_|dQXp}NAQJ%35)s4z diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V2-T0-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V2-T0-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 29098a47decfa7113027876bebe96a46de95db5f..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 74 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO? R1u_|dQb6%0h#-Vy1OPuU61e~X diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V2-T1-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V0-M1-S2-G0-__-C1-V2-T1-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 54c6b2e595556eae5886f9dc8052998b4e169795..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 74 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY-nO? R1u_|dQb6%0h#-Vy0sucT61o5Y diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 9888c65650ac4f2d58636677fa3d010584ac9968..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 54 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY=ltX E0OC3itN;K2 diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R0-__-__-__-__-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 7159742ba687bba35547781e9adb27c3c40db959..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 60 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGQ0*kcePlY=Te_ G@*4m^5fGvP diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C0-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C0-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 65046afb475ea42cc9089520c752552a061d4227..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 57 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~29hm6 J%)r?24FC;W5M2NO diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C0-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C0-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 242b6064f0e7f877339b251db449e2055d4e3e85..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 63 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~29hm6 L%)r*}~29hm6 M%)r*}~Wo%(! N1PTMi8W*}~Wo%(! R1PTMi8W*}~Wo%(! U1PTMi8W@^dfMN_l5fJ$e01Y(~=>Px# diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V0-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index ce3f8c9b157d939293ac2a86f1ec17fefbc8c6ac..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 60 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! N1PTMi8W*}~Wo%(! R1PTMi8W*}~Wo%(! U1PTMi8W@{efMN_l5fJ$e01ZSE>Hq)$ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 06b610ad237a7ccbfe4b9c67a9fd01d97bf7a3e7..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 66 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! Q1PX)1T7V)9j0_Fm0HB}|^8f$< diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index f340a6bec91871eed3751383632eb1f194cb1078..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! R1PX)1T7V)9j0{lv8vqO&66pW{ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index d00905cba5b0e5cab160529d686d5c6f3fddc050..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 78 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! U1PX)1T7V)9j0{Z>8bW>p0DVyt-v9sr diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index a23cc6f3deab31e2e02e48f9e27a5c59ca4a4516..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 66 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! Q1PX)1T7V)9jEoK60HC80^Z)<= diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 46d7e0685bf8fb059b1a86accf49597c2b808a47..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! R1PX)1T7V)9jEqqF8vqO>66yc| diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V1-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 99200ae1c792fa02de766a59a26c6cae6d62e654..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 78 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! U1PX)1T7V)9jEqeX8bW>p0DWK+-~a#s diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 60f11febbc69f9fabd693fc978888196ce6b0634..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! U1PTMinp%J&3_w1JWN7#X01FKg=>Px# diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 772a747dccba4caa5c2d7f1a3f5be0e08bbb87da..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 78 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! V1PTMinp%J&3_w1JWN3uY-vE3)6W;&; diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 7ed810dba55e24f4b9cd3338856436c9c1c4ff42..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 84 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! V1PTMinp%J&3_w1JWI*A40|4_k6x9F# diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 4e89832f757c8610cde515ae72de4f1780e7e4b2..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! U1PTMinp%J&3_w1JWNi2b01FTj>Hq)$ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 524e2f6ffb7e82acc69f5f0451acf46e948a598b..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 78 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! V1PTMinp%J&3_w1JWNd`c-vE3@6W{;< diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P0-C1-V2-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index ffe745c9e5e2bea1562ad757a4e45546f4b68bd3..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 84 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-YGq)Mh>*}~Wo%(! V1PTMinp%J&3_w1JWJKY80|4_z6xIL$ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 11920a23948ae6c254eeddcd499af08dff5fb49d..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 57 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTFnd+5iLN> Iz}WB&01a#qUH||9 diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 1ef3b81acbca00f0e87682ab5b7adbf1d5ab385d..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 63 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTFnd+5iLN> Kz}N_(z5xJlS`kzL diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C0-__-__-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index d21d1b115f037def3d5ed230f50ca32f1194cb32..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 69 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTFnd+5iLN> Lz}N(#Amldy*Afy+ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 880078a922414630e712fba2fcfd012b80b39db6..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 60 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw KAg6($;Tr%vAQ1il diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index f9d65959ca092b34368e563ff2c85224c41d95e5..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 66 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw QAg6($v4ue*f`RcH0HMwi^Z)<= diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index ff33c11a27ff3426b35c1585fca567340660de8a..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw TAg6($sf9rzf&nN3BEJCu4OJ5A diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 68e9646c7b4bf7e22858764e9594654ffc17cef6..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 60 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw KAg6(`;Tr%vBM|=p diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 8eef0a4290656e377280fa884982736abe38fbed..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 66 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw QAg6(`v4ue*f`RcH0HN0r^#A|> diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V0-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 34d55a82d6ea95c6ce262151da82f941d498dc62..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw TAg6(`sf9rzf&nN3BEJCu4P+AQ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index fab4c60b0d701ef6c201f8d6ac4a30d242e33f89..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 66 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw PkXQ?YL<9pPL&G-!pt=$C diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 52783b5af1741eb2121fd2cfe4f44a93f6a3da6b..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw QkXQ?YL<9pP1C;&-01P`4>Hq)$ diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index cfd9ac6a50efbb1087497bafbffbb0eb19bdbb01..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 78 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw SkXQ?YL<9pPLlcCCklz4(cN5?M diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 9da182036d2693e2710c7ae66c05a1066d565cc1..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 66 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw PkXQ?YL<9pPW5YK9puG|G diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index c20ba3ba1c765b071138152bdf4fff3e3d631fb1..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw QkXQ?YL<9pPBb5FI01QMD>i_@% diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V1-L1-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index f4049648c9d6c8ff3cf397b96754a6020ab52881..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 78 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw SkXQ?YL<9pPV-tjiklz4(h7;ic diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index cce3823880fc1b1a3a7f557a6323630b2cf198b6..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 72 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw SAg8H?K_Y?y$On-O4c`C@EfVSg diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V1-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index fc62ebc29265400683de8003300279359707a137..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 78 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw UAg8H?K_Y?y$On-OjS%`90DNN;-~a#s diff --git a/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T0-__-__-__-__-R1-P1-C1-V2-L0-V2-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 70d2b8ef5acd85f72016685bbaec60fa298f4cc1..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 84 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0G{Q)pt~VrXPwl!$0-Y6VdeTCI#N42(cw TAg8H?K_Y?y$On-OD7BBHUWiLnJp JGcY!M0{|2|5u^YB diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 714b4fdda6a74d21d239cae11c372f3bcdb9abfe..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vp^<@6BBHUWiLr%2 KB7%Xj;Tr%HN)e?1 diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index c218603087a11df8659b85d01c408255cc01995f..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vp^=F}BBHUWiLnJp JGcY!M0{|3T5vBkD diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 0dd26fae76e136847320bc61e5eb191a3462b727..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vp^=GEBBHUWiLr%2 KB7%Xj;Tr%HY7wUZ diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 3b55b2be57c69f0aa370d46074c368dd463b1517..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 56 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vp^1@^K_a5Dsfn=# KNHZ`td;u@R>L diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I0-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 7cb3b00a87591ab4c595e0c9e50f281aa96236d4..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 56 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vp^1@^Q6i$Tsfn?L LK_Y^IvEds4A;1x+ diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D0-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D0-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 90a152e9405b0c6c49c6dc0c1e48776df2d60c80..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vv5|p6BBHUWiLnJp JGcY!M0{|3F5v2eC diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D0-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index b69f3e78651cd5e11a6a661d69fb1da49f88b51b..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vv5|pMBBHUWiLr%2 KB7%Xj;Tr%HToI-K diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D1-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 01e88a520387b40634b7af2f028944d0e282d2a2..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vv5|>EBBHUWiLnJp JGcY!M0{|3l5vKqE diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D1-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 90f8beaa344d2d90bd54be7b4aaaf13d3a2eff68..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 55 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vv5|>UBBHUWiLr%2 KB7%Xj;Tr%Hd=aPs diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D2-G0-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 7061c0b765afdf6e510ea5f140aacf8ec5e1c459..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 56 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vv5Aq9K_a5Dsfn=# KNHZ`td;#1W_f diff --git a/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B0-T1-A1-I1-D2-G1-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index bb55b4302647a407c46817bc0376ae5978c6a67b..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 56 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0GjYGVBDz^V8<#6?$vv5Aq9Q6i$Tsfn?L LK_Y^IvEds4A=445 diff --git a/test/golden-file-data/snapshot-codec/B1-T0-__-__-__-__-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden b/test/golden-file-data/snapshot-codec/B1-T0-__-__-__-__-R0-__-__-__-__-V0-M0-__-__-__-__-__-__-__-__-__-__-__.snapshot.golden deleted file mode 100644 index 0fa7e0a88c16dc7f4d7c0cd89b443f14118179b5..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 31 mcmZooXlGz)VvzJxXky@EXk=iNh-hqTVr*fMh+trB_yz!XZwKiB diff --git a/test/golden-file-data/snapshot-codec/BloomFilterAlloc.A.snapshot.golden b/test/golden-file-data/snapshot-codec/BloomFilterAlloc.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..0123f4f6300903df45cb72bdedbb16b87143a880 GIT binary patch literal 5 McmZo-kYr&100QCwpa1{> literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/BloomFilterAlloc.B.snapshot.golden b/test/golden-file-data/snapshot-codec/BloomFilterAlloc.B.snapshot.golden new file mode 100644 index 000000000..51182ace4 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/BloomFilterAlloc.B.snapshot.golden @@ -0,0 +1 @@ +��@ !�TD- \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/DiskCachePolicy.A.snapshot.golden b/test/golden-file-data/snapshot-codec/DiskCachePolicy.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..8b040ead36e9d32df7a5d8dfc594b6130bf3fc4a GIT binary patch literal 2 JcmZo<000350D=Gj literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/DiskCachePolicy.B.snapshot.golden b/test/golden-file-data/snapshot-codec/DiskCachePolicy.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..9478b3348f240302173a8b3e6499d16ef858385c GIT binary patch literal 5 McmZo-lw@H500QO!p#T5? literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/DiskCachePolicy.C.snapshot.golden b/test/golden-file-data/snapshot-codec/DiskCachePolicy.C.snapshot.golden new file mode 100644 index 000000000..02b41ff4e --- /dev/null +++ b/test/golden-file-data/snapshot-codec/DiskCachePolicy.C.snapshot.golden @@ -0,0 +1 @@ +� \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/FencePointerIndexType.A.snapshot.golden b/test/golden-file-data/snapshot-codec/FencePointerIndexType.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..f76dd238ade08917e6712764a16a22005a50573d GIT binary patch literal 1 IcmZPo000310RR91 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/FencePointerIndexType.B.snapshot.golden b/test/golden-file-data/snapshot-codec/FencePointerIndexType.B.snapshot.golden new file mode 100644 index 000000000..6b2aaa764 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/FencePointerIndexType.B.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/IndexType.A.snapshot.golden b/test/golden-file-data/snapshot-codec/IndexType.A.snapshot.golden new file mode 100644 index 000000000..6b2aaa764 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/IndexType.A.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/IndexType.B.snapshot.golden b/test/golden-file-data/snapshot-codec/IndexType.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..f76dd238ade08917e6712764a16a22005a50573d GIT binary patch literal 1 IcmZPo000310RR91 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/LevelMergeType.A.snapshot.golden b/test/golden-file-data/snapshot-codec/LevelMergeType.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..f76dd238ade08917e6712764a16a22005a50573d GIT binary patch literal 1 IcmZPo000310RR91 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/LevelMergeType.B.snapshot.golden b/test/golden-file-data/snapshot-codec/LevelMergeType.B.snapshot.golden new file mode 100644 index 000000000..6b2aaa764 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/LevelMergeType.B.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/MergeCredits.A.snapshot.golden b/test/golden-file-data/snapshot-codec/MergeCredits.A.snapshot.golden new file mode 100644 index 000000000..a850a922c --- /dev/null +++ b/test/golden-file-data/snapshot-codec/MergeCredits.A.snapshot.golden @@ -0,0 +1 @@ +X \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/MergeDebt.A.snapshot.golden b/test/golden-file-data/snapshot-codec/MergeDebt.A.snapshot.golden new file mode 100644 index 000000000..a850a922c --- /dev/null +++ b/test/golden-file-data/snapshot-codec/MergeDebt.A.snapshot.golden @@ -0,0 +1 @@ +X \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/MergePolicy.A.snapshot.golden b/test/golden-file-data/snapshot-codec/MergePolicy.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..f76dd238ade08917e6712764a16a22005a50573d GIT binary patch literal 1 IcmZPo000310RR91 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/MergePolicyForLevel.A.snapshot.golden b/test/golden-file-data/snapshot-codec/MergePolicyForLevel.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..f76dd238ade08917e6712764a16a22005a50573d GIT binary patch literal 1 IcmZPo000310RR91 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/MergePolicyForLevel.B.snapshot.golden b/test/golden-file-data/snapshot-codec/MergePolicyForLevel.B.snapshot.golden new file mode 100644 index 000000000..6b2aaa764 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/MergePolicyForLevel.B.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/MergeSchedule.A.snapshot.golden b/test/golden-file-data/snapshot-codec/MergeSchedule.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..f76dd238ade08917e6712764a16a22005a50573d GIT binary patch literal 1 IcmZPo000310RR91 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/MergeSchedule.B.snapshot.golden b/test/golden-file-data/snapshot-codec/MergeSchedule.B.snapshot.golden new file mode 100644 index 000000000..6b2aaa764 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/MergeSchedule.B.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/NominalCredits.A.snapshot.golden b/test/golden-file-data/snapshot-codec/NominalCredits.A.snapshot.golden new file mode 100644 index 000000000..d9ba7315a --- /dev/null +++ b/test/golden-file-data/snapshot-codec/NominalCredits.A.snapshot.golden @@ -0,0 +1 @@ +* \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/NominalDebt.A.snapshot.golden b/test/golden-file-data/snapshot-codec/NominalDebt.A.snapshot.golden new file mode 100644 index 000000000..a850a922c --- /dev/null +++ b/test/golden-file-data/snapshot-codec/NominalDebt.A.snapshot.golden @@ -0,0 +1 @@ +X \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/RunBloomFilterAlloc.A.snapshot.golden b/test/golden-file-data/snapshot-codec/RunBloomFilterAlloc.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..0123f4f6300903df45cb72bdedbb16b87143a880 GIT binary patch literal 5 McmZo-kYr&100QCwpa1{> literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/RunBloomFilterAlloc.B.snapshot.golden b/test/golden-file-data/snapshot-codec/RunBloomFilterAlloc.B.snapshot.golden new file mode 100644 index 000000000..51182ace4 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/RunBloomFilterAlloc.B.snapshot.golden @@ -0,0 +1 @@ +��@ !�TD- \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/RunDataCaching.A.snapshot.golden b/test/golden-file-data/snapshot-codec/RunDataCaching.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..f76dd238ade08917e6712764a16a22005a50573d GIT binary patch literal 1 IcmZPo000310RR91 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/RunDataCaching.B.snapshot.golden b/test/golden-file-data/snapshot-codec/RunDataCaching.B.snapshot.golden new file mode 100644 index 000000000..6b2aaa764 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/RunDataCaching.B.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/RunNumber.A.snapshot.golden b/test/golden-file-data/snapshot-codec/RunNumber.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..912f823fa811bbce28445b08cc596f84816f33f2 GIT binary patch literal 3 Kcmb1SVE_OCRsbFV literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/RunParams.A.snapshot.golden b/test/golden-file-data/snapshot-codec/RunParams.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..9a9bca30cf0279f53cbe762ec9a4c5bd817c935c GIT binary patch literal 9 QcmZo+U}$2HWMN(^b literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SizeRatio.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SizeRatio.A.snapshot.golden new file mode 100644 index 000000000..45a8ca02b --- /dev/null +++ b/test/golden-file-data/snapshot-codec/SizeRatio.A.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/SnapIncomingRun_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapIncomingRun_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..faaa76a549a2f5201e6053b6997e7ef6b7d2f489 GIT binary patch literal 18 XcmZo=V33HA&}s&fEew(@3=E6_AU6Wd literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapIncomingRun_SnapshotRun.B.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapIncomingRun_SnapshotRun.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..2349a199b436d69a71abde697f6f833ac620b6f0 GIT binary patch literal 9 QcmZo-Y+;aOVPIec00_+iCIA2c literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapLevel_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapLevel_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..cefd88665e03b42e923058e0a6a661f6fc3567e3 GIT binary patch literal 34 dcmZo_WnhqqkkD!dk}V99EDQ{cO;8$20RV5`1r-1Q literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapLevels_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapLevels_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..5caceeea0c920b7cdebfe297ec06a4ab2327701a GIT binary patch literal 69 gcmZo_YGq)Mh>*}~29hldk}M1ij7?A)#wDl%0Iz@ws{jB1 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingRun_LevelMergeType_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingRun_LevelMergeType_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..c5e3a478e1ab246b3e835ef420a034b8a09f5316 GIT binary patch literal 11 ScmZo>kcenukYr(CU<3dSZUL46 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingRun_LevelMergeType_SnapshotRun.B.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingRun_LevelMergeType_SnapshotRun.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..99b1068248c1984927995265782d4d5a5c914a32 GIT binary patch literal 29 dcmZo=Y++z%VvuBEV3dexY5_4AfI?u30RTy%1K|Jw literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingRun_TreeMergeType_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingRun_TreeMergeType_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..c5e3a478e1ab246b3e835ef420a034b8a09f5316 GIT binary patch literal 11 ScmZo>kcenukYr(CU<3dSZUL46 literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingRun_TreeMergeType_SnapshotRun.B.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingRun_TreeMergeType_SnapshotRun.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..1a9a1e30a0299737aafd2f7e6552e28cec9b8b18 GIT binary patch literal 29 dcmZo=Y++z%VvuBEV3dexY5_4AfI?u35dcY|1L6Px literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..5d414b1ccde2c97198a85afb324197d17c7f27c8 GIT binary patch literal 9 QcmZo-Xkn0KVPIec00_kaB>(^b literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.B.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..dfbec2ab17fee413876e0bea9c7f2e83126996b7 GIT binary patch literal 32 XcmZo-Y-VU`VrXHIWMN=n#AE;fXAuPT literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.C.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingTreeState_SnapshotRun.C.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..1518556e937be2b10b5e0a2c51b0b1b34cb31851 GIT binary patch literal 13 UcmZo-YG#m#Xkn0KVPIec02Cqu8UO$Q literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapMergingTree_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapMergingTree_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..5d414b1ccde2c97198a85afb324197d17c7f27c8 GIT binary patch literal 9 QcmZo-Xkn0KVPIec00_kaB>(^b literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapPendingMerge_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapPendingMerge_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..6b7ddb15e0f7a4cefd95cf3ea661fcbb4429cd1a GIT binary patch literal 30 VcmZo>Xli0;VUT2DU|_^#003671abfX literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapPendingMerge_SnapshotRun.B.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapPendingMerge_SnapshotRun.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..906de5599898076b2c81cfa8ab5e11ba684bfa33 GIT binary patch literal 21 UcmZo-Y-(a?VUT2DU|@tZ05CNJP5=M^ literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapPreExistingRun_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapPreExistingRun_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..5d414b1ccde2c97198a85afb324197d17c7f27c8 GIT binary patch literal 9 QcmZo-Xkn0KVPIec00_kaB>(^b literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapPreExistingRun_SnapshotRun.B.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapPreExistingRun_SnapshotRun.B.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..e228e9c1677c1af53a703377c5bad7f2d59701f7 GIT binary patch literal 13 UcmZo-Y-W&%Xkn0KVPIec02CGi82|tP literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapshotLabel.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapshotLabel.A.snapshot.golden new file mode 100644 index 000000000..97651bcee --- /dev/null +++ b/test/golden-file-data/snapshot-codec/SnapshotLabel.A.snapshot.golden @@ -0,0 +1 @@ +qUserProvidedLabel \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/SnapshotLabel.B.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapshotLabel.B.snapshot.golden new file mode 100644 index 000000000..64845fb76 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/SnapshotLabel.B.snapshot.golden @@ -0,0 +1 @@ +` \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/SnapshotMetaData.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapshotMetaData.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..0861071ca5a36da3c68233861f417438e614f247 GIT binary patch literal 116 zcmZoI3@uJA3Mk4i%S=g4@kvZd&1q*~X=0FwXkw6LVPI%v08vd%tqedR39V)z*#eee OY=Y7-E@2f6P^AD#Y!*8J literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..3a5ea0e7e6499b7341aec70e305948f822443a06 GIT binary patch literal 7 OcmZo+kYr(CU<3dJF#w|g literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/TableConfig.A.snapshot.golden b/test/golden-file-data/snapshot-codec/TableConfig.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..31ab6b930f72d61245b1b4c3a0e6070b78001028 GIT binary patch literal 16 XcmZo?U}<8Ih-hMvWMN=vWMBXQ8m0oC literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/TreeMergeType.A.snapshot.golden b/test/golden-file-data/snapshot-codec/TreeMergeType.A.snapshot.golden new file mode 100644 index 000000000..6b2aaa764 --- /dev/null +++ b/test/golden-file-data/snapshot-codec/TreeMergeType.A.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/TreeMergeType.B.snapshot.golden b/test/golden-file-data/snapshot-codec/TreeMergeType.B.snapshot.golden new file mode 100644 index 000000000..25cb955ba --- /dev/null +++ b/test/golden-file-data/snapshot-codec/TreeMergeType.B.snapshot.golden @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/Vector_SnapshotRun.A.snapshot.golden b/test/golden-file-data/snapshot-codec/Vector_SnapshotRun.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..ba21b1a85a797494879eff98b8feb3f35415fccb GIT binary patch literal 15 QcmZo_VUT2DU|@t&02FTl#{d8T literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/Vector_SnapshotRun.B.snapshot.golden b/test/golden-file-data/snapshot-codec/Vector_SnapshotRun.B.snapshot.golden new file mode 100644 index 000000000..5416677bc --- /dev/null +++ b/test/golden-file-data/snapshot-codec/Vector_SnapshotRun.B.snapshot.golden @@ -0,0 +1 @@ +� \ No newline at end of file diff --git a/test/golden-file-data/snapshot-codec/Vector_SnapshotRun.C.snapshot.golden b/test/golden-file-data/snapshot-codec/Vector_SnapshotRun.C.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..c21c447d1aa71a649390080e3299c5e60152132b GIT binary patch literal 8 PcmZo{VUT2DU|<9Q2s!~I literal 0 HcmV?d00001 diff --git a/test/golden-file-data/snapshot-codec/WriteBufferAlloc.A.snapshot.golden b/test/golden-file-data/snapshot-codec/WriteBufferAlloc.A.snapshot.golden new file mode 100644 index 0000000000000000000000000000000000000000..ce1e271e26691c7ca6d4c8fa286fa3720d2db9c7 GIT binary patch literal 4 LcmZo-kca>P0+ayr literal 0 HcmV?d00001 From 66d80ec755cf811bc79309ee83abff3f9c457eac Mon Sep 17 00:00:00 2001 From: Joris Dral Date: Thu, 8 May 2025 10:53:27 +0200 Subject: [PATCH 4/4] Test that there are no missing or unexpected golden files MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Example output when there is an unexpected file: ``` ❯ cabal run lsm-tree-test -- -p "prop_noUnexpectedOrMissingGoldenFiles" lsm-tree Test.Database.LSMTree.Internal.Snapshot.Codec.Golden prop_noUnexpectedOrMissingGoldenFiles: FAIL *** Failed! Falsified (after 1 test): Found unexpected files: fromList ["unexpected"] Delete the unexpected files manually from test/golden-file-data/snapshot-codec Use --quickcheck-replay="(SMGen 1489992322676650058 4671765810150648345,0)" to reproduce. 1 out of 1 tests failed (0.01s) ``` Example output when there is a missing file: ``` ❯ cabal run lsm-tree-test -- -p "prop_noUnexpectedOrMissingGoldenFiles" lsm-tree Test.Database.LSMTree.Internal.Snapshot.Codec.Golden prop_noUnexpectedOrMissingGoldenFiles: FAIL *** Failed! Falsified (after 1 test): Missing expected files: fromList ["NominalCredits.A.snapshot.golden"] Run the golden tests to regenerate the missing files Use --quickcheck-replay="(SMGen 11771750078239108519 7040896247146249591,0)" to reproduce. 1 out of 1 tests failed (0.01s) ``` --- .../LSMTree/Internal/Snapshot/Codec/Golden.hs | 37 +++++++++++++++++++ 1 file changed, 37 insertions(+) diff --git a/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs b/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs index 5e005e036..99c8bfe6a 100644 --- a/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs +++ b/test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs @@ -10,6 +10,7 @@ module Test.Database.LSMTree.Internal.Snapshot.Codec.Golden ( import Codec.CBOR.Write (toLazyByteString) import Control.Monad (when) import qualified Data.ByteString.Lazy as BSL (writeFile) +import qualified Data.Set as Set import Data.Typeable import qualified Data.Vector as V import Database.LSMTree.Internal.Config (BloomFilterAlloc (..), @@ -29,15 +30,19 @@ import qualified System.FS.API as FS import System.FS.API.Types (FsPath, MountPoint (..), fsToFilePath, mkFsPath, (<.>)) import System.FS.IO (HandleIO, ioHasFS) +import Test.QuickCheck (Property, counterexample, ioProperty, once, + (.&&.)) import qualified Test.Tasty as Tasty import Test.Tasty (TestTree, testGroup) import qualified Test.Tasty.Golden as Au +import Test.Tasty.QuickCheck (testProperty) tests :: TestTree tests = handleOutputFiles $ testGroup "Test.Database.LSMTree.Internal.Snapshot.Codec.Golden" $ concat (forallSnapshotTypes snapshotCodecGoldenTest) + ++ [testProperty "prop_noUnexpectedOrMissingGoldenFiles" prop_noUnexpectedOrMissingGoldenFiles] {------------------------------------------------------------------------------- Configuration @@ -101,6 +106,29 @@ snapshotCodecGoldenTest proxy = [ in Au.goldenVsFile name snapshotAuPath snapshotHsPath outputAction +-- | Check that are no missing or unexpected files in the output directory +prop_noUnexpectedOrMissingGoldenFiles :: Property +prop_noUnexpectedOrMissingGoldenFiles = once $ ioProperty $ do + let expectedFiles = Set.fromList $ concat $ forallSnapshotTypes filePathsGolden + + + let hfs = ioHasFS goldenDataMountPoint + actualDirectoryEntries <- FS.listDirectory hfs (FS.mkFsPath []) + + let missingFiles = expectedFiles Set.\\ actualDirectoryEntries + propMissing = + counterexample ("Missing expected files: " ++ show missingFiles) + $ counterexample ("Run the golden tests to regenerate the missing files") + $ (Set.null missingFiles) + + let unexpectedFiles = actualDirectoryEntries Set.\\ expectedFiles + propUnexpected = + counterexample ("Found unexpected files: " ++ show unexpectedFiles) + $ counterexample ("Delete the unexpected files manually from " ++ goldenDataFilePath) + (Set.null unexpectedFiles) + + pure $ propMissing .&&. propUnexpected + {------------------------------------------------------------------------------- Mapping -------------------------------------------------------------------------------} @@ -219,6 +247,15 @@ spaceToUnderscore :: Char -> Char spaceToUnderscore ' ' = '_' spaceToUnderscore c = c +filePathsGolden :: (EnumGolden a, Typeable a) => Proxy a -> [String] +filePathsGolden p = [ + filePathGolden p annotation + | (annotation, _) <- enumGoldenAnnotated' p + ] + +filePathGolden :: Typeable a => Proxy a -> String -> String +filePathGolden p ann = nameGolden p ann ++ ".snapshot.golden" + {------------------------------------------------------------------------------- Enumeration class: instances -------------------------------------------------------------------------------}