Skip to content

Commit 66d80ec

Browse files
committed
Test that there are no missing or unexpected golden files
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) ```
1 parent 72c7b27 commit 66d80ec

File tree

1 file changed

+37
-0
lines changed
  • test/Test/Database/LSMTree/Internal/Snapshot/Codec

1 file changed

+37
-0
lines changed

test/Test/Database/LSMTree/Internal/Snapshot/Codec/Golden.hs

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Test.Database.LSMTree.Internal.Snapshot.Codec.Golden (
1010
import Codec.CBOR.Write (toLazyByteString)
1111
import Control.Monad (when)
1212
import qualified Data.ByteString.Lazy as BSL (writeFile)
13+
import qualified Data.Set as Set
1314
import Data.Typeable
1415
import qualified Data.Vector as V
1516
import Database.LSMTree.Internal.Config (BloomFilterAlloc (..),
@@ -29,15 +30,19 @@ import qualified System.FS.API as FS
2930
import System.FS.API.Types (FsPath, MountPoint (..), fsToFilePath,
3031
mkFsPath, (<.>))
3132
import System.FS.IO (HandleIO, ioHasFS)
33+
import Test.QuickCheck (Property, counterexample, ioProperty, once,
34+
(.&&.))
3235
import qualified Test.Tasty as Tasty
3336
import Test.Tasty (TestTree, testGroup)
3437
import qualified Test.Tasty.Golden as Au
38+
import Test.Tasty.QuickCheck (testProperty)
3539

3640
tests :: TestTree
3741
tests =
3842
handleOutputFiles $
3943
testGroup "Test.Database.LSMTree.Internal.Snapshot.Codec.Golden" $
4044
concat (forallSnapshotTypes snapshotCodecGoldenTest)
45+
++ [testProperty "prop_noUnexpectedOrMissingGoldenFiles" prop_noUnexpectedOrMissingGoldenFiles]
4146

4247
{-------------------------------------------------------------------------------
4348
Configuration
@@ -101,6 +106,29 @@ snapshotCodecGoldenTest proxy = [
101106

102107
in Au.goldenVsFile name snapshotAuPath snapshotHsPath outputAction
103108

109+
-- | Check that are no missing or unexpected files in the output directory
110+
prop_noUnexpectedOrMissingGoldenFiles :: Property
111+
prop_noUnexpectedOrMissingGoldenFiles = once $ ioProperty $ do
112+
let expectedFiles = Set.fromList $ concat $ forallSnapshotTypes filePathsGolden
113+
114+
115+
let hfs = ioHasFS goldenDataMountPoint
116+
actualDirectoryEntries <- FS.listDirectory hfs (FS.mkFsPath [])
117+
118+
let missingFiles = expectedFiles Set.\\ actualDirectoryEntries
119+
propMissing =
120+
counterexample ("Missing expected files: " ++ show missingFiles)
121+
$ counterexample ("Run the golden tests to regenerate the missing files")
122+
$ (Set.null missingFiles)
123+
124+
let unexpectedFiles = actualDirectoryEntries Set.\\ expectedFiles
125+
propUnexpected =
126+
counterexample ("Found unexpected files: " ++ show unexpectedFiles)
127+
$ counterexample ("Delete the unexpected files manually from " ++ goldenDataFilePath)
128+
(Set.null unexpectedFiles)
129+
130+
pure $ propMissing .&&. propUnexpected
131+
104132
{-------------------------------------------------------------------------------
105133
Mapping
106134
-------------------------------------------------------------------------------}
@@ -219,6 +247,15 @@ spaceToUnderscore :: Char -> Char
219247
spaceToUnderscore ' ' = '_'
220248
spaceToUnderscore c = c
221249

250+
filePathsGolden :: (EnumGolden a, Typeable a) => Proxy a -> [String]
251+
filePathsGolden p = [
252+
filePathGolden p annotation
253+
| (annotation, _) <- enumGoldenAnnotated' p
254+
]
255+
256+
filePathGolden :: Typeable a => Proxy a -> String -> String
257+
filePathGolden p ann = nameGolden p ann ++ ".snapshot.golden"
258+
222259
{-------------------------------------------------------------------------------
223260
Enumeration class: instances
224261
-------------------------------------------------------------------------------}

0 commit comments

Comments
 (0)