Skip to content

Commit 4913132

Browse files
committed
More MockFS properties
These are useful when testing with `fs-sim` errors, in which case we sould check how many open handles and/or files exist when disk faults occur.
1 parent 3a8b68d commit 4913132

File tree

2 files changed

+149
-6
lines changed

2 files changed

+149
-6
lines changed

test/Test/FS.hs

Lines changed: 110 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,26 +3,135 @@
33
-- TODO: upstream to fs-sim
44
module Test.FS (tests) where
55

6+
import Control.Concurrent.Class.MonadSTM (MonadSTM (atomically))
7+
import Control.Concurrent.Class.MonadSTM.Strict.TMVar
8+
import Control.Monad
9+
import Control.Monad.IOSim (runSimOrThrow)
10+
import Data.Char (isAsciiLower, isAsciiUpper)
11+
import qualified Data.List as List
12+
import qualified Data.Text as Text
613
import GHC.Generics (Generic)
714
import System.FS.API
815
import System.FS.Sim.Error
16+
import qualified System.FS.Sim.MockFS as MockFS
917
import qualified System.FS.Sim.Stream as S
1018
import System.FS.Sim.Stream (InternalInfo (..), Stream (..))
1119
import Test.QuickCheck
1220
import Test.QuickCheck.Classes (eqLaws)
1321
import Test.QuickCheck.Instances ()
1422
import Test.Tasty
23+
import Test.Tasty.QuickCheck (testProperty)
1524
import Test.Util.FS
1625
import Test.Util.QC
1726

1827
tests :: TestTree
1928
tests = testGroup "Test.FS" [
20-
testClassLaws "Stream" $
29+
-- * Simulated file system properties
30+
testProperty "prop_numOpenHandles" prop_numOpenHandles
31+
, testProperty "prop_numDirEntries" prop_numDirEntries
32+
-- * Equality
33+
, testClassLaws "Stream" $
2134
eqLaws (Proxy @(Stream Int))
2235
, testClassLaws "Errors" $
2336
eqLaws (Proxy @Errors)
2437
]
2538

39+
{-------------------------------------------------------------------------------
40+
Simulated file system properties
41+
-------------------------------------------------------------------------------}
42+
43+
newtype Path = Path FsPath
44+
deriving stock (Show, Eq)
45+
46+
newtype UniqueList a = UniqueList [a]
47+
deriving stock Show
48+
49+
instance (Arbitrary a, Eq a) => Arbitrary (UniqueList a) where
50+
arbitrary = do
51+
xs <- arbitrary
52+
pure (UniqueList (List.nub xs))
53+
shrink (UniqueList []) = []
54+
shrink (UniqueList xs) = UniqueList . List.nub <$> shrink xs
55+
56+
instance Arbitrary Path where
57+
arbitrary = Path . mkFsPath . (:[]) <$> ((:) <$> genChar <*> listOf genChar)
58+
where
59+
genChar = elements (['A'..'Z'] ++ ['a'..'z'])
60+
shrink (Path p) = case fsPathToList p of
61+
[] -> []
62+
t:_ -> [
63+
Path p'
64+
| t' <- shrink t
65+
, let t'' = Text.filter (\c -> isAsciiUpper c || isAsciiLower c) t'
66+
, not (Text.null t'')
67+
, let p' = fsPathFromList [t']
68+
]
69+
70+
-- | Sanity check for 'propNoOpenHandles' and 'propNumOpenHandles'
71+
prop_numOpenHandles :: UniqueList Path -> Property
72+
prop_numOpenHandles (UniqueList paths) = runSimOrThrow $
73+
withSimHasFS propTrivial MockFS.empty $ \hfs fsVar -> do
74+
-- No open handles initially
75+
fs <- atomically $ readTMVar fsVar
76+
let prop = propNoOpenHandles fs
77+
78+
-- Open n handles
79+
hs <- forM paths $ \(Path p) -> hOpen hfs p (WriteMode MustBeNew)
80+
81+
-- Now there should be precisely n open handles
82+
fs' <- atomically $ readTMVar fsVar
83+
let prop' = propNumOpenHandles n fs'
84+
85+
-- Close all previously opened handles
86+
forM_ hs $ hClose hfs
87+
88+
-- No open handles again
89+
fs'' <- atomically $ readTMVar fsVar
90+
let prop'' = propNoOpenHandles fs''
91+
92+
pure (prop .&&. prop' .&&. prop'')
93+
where
94+
n = length paths
95+
96+
-- | Sanity check for 'propNoDirEntries' and 'propNumDirEntries'
97+
prop_numDirEntries :: Path -> InfiniteList Bool -> UniqueList Path -> Property
98+
prop_numDirEntries (Path dir) isFiles (UniqueList paths) = runSimOrThrow $
99+
withSimHasFS propTrivial MockFS.empty $ \hfs fsVar -> do
100+
createDirectoryIfMissing hfs False dir
101+
102+
-- No entries initially
103+
fs <- atomically $ readTMVar fsVar
104+
let prop = propNoDirEntries dir fs
105+
106+
-- Create n entries
107+
forM_ xs $ \(isFile, Path p) ->
108+
if isFile
109+
then withFile hfs (dir </> p) (WriteMode MustBeNew) $ \_ -> pure ()
110+
else createDirectory hfs (dir </> p)
111+
112+
-- Now there should be precisely n entries
113+
fs' <- atomically $ readTMVar fsVar
114+
let prop' = propNumDirEntries dir n fs'
115+
116+
-- Remove n entries
117+
forM_ xs $ \(isFile, Path p) ->
118+
if isFile
119+
then removeFile hfs (dir </> p)
120+
else removeDirectoryRecursive hfs (dir </> p)
121+
122+
-- No entries again
123+
fs'' <- atomically $ readTMVar fsVar
124+
let prop'' = propNoDirEntries dir fs''
125+
126+
pure (prop .&&. prop' .&&. prop'')
127+
where
128+
n = length paths
129+
xs = zip (getInfiniteList isFiles) paths
130+
131+
{-------------------------------------------------------------------------------
132+
Equality
133+
-------------------------------------------------------------------------------}
134+
26135
-- | This is not a fully lawful instance, because it uses 'approximateEqStream'.
27136
instance Eq a => Eq (Stream a) where
28137
(==) = approximateEqStream

test/Test/Util/FS.hs

Lines changed: 39 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,11 @@ module Test.Util.FS (
1212
, withSimErrorHasFS
1313
, withSimErrorHasBlockIO
1414
-- * Simulated file system properties
15+
, propTrivial
16+
, propNumOpenHandles
1517
, propNoOpenHandles
18+
, propNumDirEntries
19+
, propNoDirEntries
1620
, assertNoOpenHandles
1721
, assertNumOpenHandles
1822
-- * Equality
@@ -23,9 +27,11 @@ import Control.Concurrent.Class.MonadMVar
2327
import Control.Concurrent.Class.MonadSTM.Strict
2428
import Control.Exception (assert)
2529
import Control.Monad.Class.MonadThrow (MonadCatch, MonadThrow)
30+
import Control.Monad.IOSim (runSimOrThrow)
2631
import Control.Monad.Primitive (PrimMonad)
32+
import qualified Data.Set as Set
2733
import GHC.Stack
28-
import System.FS.API
34+
import System.FS.API as FS
2935
import System.FS.BlockIO.API
3036
import System.FS.BlockIO.IO
3137
import System.FS.BlockIO.Sim (fromHasFS)
@@ -137,13 +143,41 @@ withSimErrorHasBlockIO post fs errs k =
137143
Simulated file system properties
138144
-------------------------------------------------------------------------------}
139145

146+
propTrivial :: MockFS -> Property
147+
propTrivial _ = property True
148+
149+
{-# INLINABLE propNumOpenHandles #-}
150+
propNumOpenHandles :: Int -> MockFS -> Property
151+
propNumOpenHandles expected fs =
152+
counterexample (printf "Expected %d open handles, but found %d" expected actual) $
153+
counterexample ("Open handles: " <> show (openHandles fs)) $
154+
printMockFSOnFailure fs $
155+
expected == actual
156+
where actual = numOpenHandles fs
157+
140158
{-# INLINABLE propNoOpenHandles #-}
141159
propNoOpenHandles :: MockFS -> Property
142-
propNoOpenHandles fs =
143-
counterexample ("Expected 0 open handles, but found " <> show n) $
160+
propNoOpenHandles fs = propNumOpenHandles 0 fs
161+
162+
{-# INLINABLE propNumDirEntries #-}
163+
propNumDirEntries :: FsPath -> Int -> MockFS -> Property
164+
propNumDirEntries path expected fs =
165+
counterexample
166+
(printf "Expected %d entries in the directory at %s, but found %d"
167+
expected
168+
(show path) actual) $
144169
printMockFSOnFailure fs $
145-
n == 0
146-
where n = numOpenHandles fs
170+
expected === actual
171+
where
172+
actual =
173+
let (contents, _) = runSimOrThrow $
174+
runSimFS fs $ \hfs ->
175+
FS.listDirectory hfs path
176+
in Set.size contents
177+
178+
{-# INLINABLE propNoDirEntries #-}
179+
propNoDirEntries :: FsPath -> MockFS -> Property
180+
propNoDirEntries path fs = propNumDirEntries path 0 fs
147181

148182
printMockFSOnFailure :: Testable prop => MockFS -> prop -> Property
149183
printMockFSOnFailure fs = counterexample ("Mocked file system: " <> pretty fs)

0 commit comments

Comments
 (0)