Skip to content

Commit 795e24a

Browse files
committed
blockio: refactor and document the Sim module
1 parent a5ce645 commit 795e24a

File tree

5 files changed

+154
-20
lines changed

5 files changed

+154
-20
lines changed

blockio/src-sim/System/FS/BlockIO/Sim.hs

Lines changed: 148 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,18 @@
1+
-- | Simulated instances of 'HasBlockIO' and 'HasFS'.
12
module System.FS.BlockIO.Sim (
2-
fromHasFS
3-
-- * Initialisation helpers
3+
-- * Implementation details #impl#
4+
-- $impl
5+
6+
-- * Runners
7+
runSimHasBlockIO
8+
, runSimErrorHasBlockIO
9+
-- * Initialisation
410
, simHasBlockIO
511
, simHasBlockIO'
612
, simErrorHasBlockIO
713
, simErrorHasBlockIO'
14+
-- ** Unsafe
15+
, unsafeFromHasFS
816
) where
917

1018
import Control.Concurrent.Class.MonadMVar
@@ -24,11 +32,54 @@ import System.FS.Sim.Error
2432
import System.FS.Sim.MockFS hiding (hClose, hOpen)
2533
import System.FS.Sim.STM
2634

27-
fromHasFS ::
35+
{- $impl
36+
37+
We include below some documentation about the effects of calling the interface
38+
functions on the simulated instance of the 'HasBlockIO' interface.
39+
40+
[IO context]: For uniform behaviour across implementations, the simulation
41+
creates and stores a mocked IO context that has the open/closed behaviour
42+
that is specified by the interface.
43+
44+
['close']: Close the mocked context
45+
46+
['submitIO']: Submit a batch of I/O operations using serial I/O using a 'HasFS'
47+
48+
['hSetNoCache']: No-op
49+
50+
['hAdvise']: No-op
51+
52+
['hAllocate']: No-op
53+
54+
['tryLockFile']: Simulate a lock by putting the lock state into the file
55+
contents
56+
57+
['hSynchronise']: No-op
58+
59+
['synchroniseDirectory']: No-op
60+
61+
['createHardLink']: Copy all file contents from the source path to the target
62+
path. Therefore, this is currently only correctly simulating hard links
63+
for /immutable/ files.
64+
-}
65+
66+
-- | Simulate a 'HasBlockIO' using the given 'HasFS'.
67+
--
68+
-- === Unsafe
69+
--
70+
-- You will probably want to use one of the safe functions like
71+
-- 'runSimHasBlockIO' or 'simErrorHasBlockIO' instead.
72+
--
73+
-- Only a simulated 'HasFS', like the 'simHasFS' and 'simErrorHasFS'
74+
-- simulations, should be passed to 'unsafeFromHasFS'. Technically, one could
75+
-- pass a 'HasFS' for the /real/ file system, but then the resulting
76+
-- 'HasBlockIO' would contain a mix of simulated functions and real functions,
77+
-- which is probably not what you want.
78+
unsafeFromHasFS ::
2879
forall m. (MonadCatch m, MonadMVar m, PrimMonad m)
2980
=> HasFS m HandleMock
3081
-> m (HasBlockIO m HandleMock)
31-
fromHasFS hfs =
82+
unsafeFromHasFS hfs =
3283
serialHasBlockIO
3384
hSetNoCache
3485
hAdvise
@@ -142,43 +193,131 @@ simCreateHardLink hfs sourcePath targetPath =
142193
void $ API.hPutAll hfs targetHandle bs
143194

144195
{-------------------------------------------------------------------------------
145-
Initialisation helpers
196+
Runners
146197
-------------------------------------------------------------------------------}
147198

199+
-- | @'runSimHasBlockIO' mockFS action@ runs an @action@ using a pair of
200+
-- simulated 'HasFS' and 'HasBlockIO'.
201+
--
202+
-- The pair of interfaces share the same mocked file system. The initial state
203+
-- of the mocked file system is set to @mockFs@. The final state of the mocked
204+
-- file system is returned with the result of @action@.
205+
--
206+
-- If you want to have access to the current state of the mocked file system
207+
-- or stream of errors, use 'simHasBlockIO' instead.
208+
runSimHasBlockIO ::
209+
(MonadSTM m, PrimMonad m, MonadCatch m, MonadMVar m)
210+
=> MockFS
211+
-> (HasFS m HandleMock -> HasBlockIO m HandleMock -> m a)
212+
-> m (a, MockFS)
213+
runSimHasBlockIO mockFS k = do
214+
runSimFS mockFS $ \hfs -> do
215+
hbio <- unsafeFromHasFS hfs
216+
k hfs hbio
217+
218+
-- | @'runSimErrorHasBlockIO' mockFS errors action@ runs an @action@ using a
219+
-- pair of simulated 'HasFS' and 'HasBlockIO' that allow fault injection.
220+
--
221+
-- The pair of interfaces share the same mocked file system. The initial state
222+
-- of the mocked file system is set to @mockFs@. The final state of the mocked
223+
-- file system is returned with the result of @action.
224+
--
225+
-- The pair of interfaces share the same stream of errors. The initial state of
226+
-- the stream of errors is set to @errors@. The final state of the stream of
227+
-- errors is returned with the result of @action@.
228+
--
229+
-- If you want to have access to the current state of the mocked file system
230+
-- or stream of errors, use 'simErrorHasBlockIO' instead.
231+
runSimErrorHasBlockIO ::
232+
(MonadSTM m, PrimMonad m, MonadCatch m, MonadMVar m)
233+
=> MockFS
234+
-> Errors
235+
-> (HasFS m HandleMock -> HasBlockIO m HandleMock -> m a)
236+
-> m (a, MockFS, Errors)
237+
runSimErrorHasBlockIO mockFS errs k = do
238+
fsVar <- newTMVarIO mockFS
239+
errorsVar <- newTVarIO errs
240+
(hfs, hbio) <- simErrorHasBlockIO fsVar errorsVar
241+
a <- k hfs hbio
242+
fs' <- atomically $ takeTMVar fsVar
243+
errs' <- readTVarIO errorsVar
244+
pure (a, fs', errs')
245+
246+
{-------------------------------------------------------------------------------
247+
Initialisation
248+
-------------------------------------------------------------------------------}
249+
250+
-- | @'simHasBlockIO' mockFsVar@ creates a pair of simulated 'HasFS' and
251+
-- 'HasBlockIO'.
252+
--
253+
-- The pair of interfaces share the same mocked file system, which is stored in
254+
-- @mockFsVar@. The current state of the mocked file system can be accessed by
255+
-- the user by reading @mockFsVar@, but note that the user should not leave
256+
-- @mockFsVar@ empty.
148257
simHasBlockIO ::
149258
(MonadCatch m, MonadMVar m, PrimMonad m, MonadSTM m)
150259
=> StrictTMVar m MockFS
151260
-> m (HasFS m HandleMock, HasBlockIO m HandleMock)
152261
simHasBlockIO var = do
153262
let hfs = simHasFS var
154-
hbio <- fromHasFS hfs
263+
hbio <- unsafeFromHasFS hfs
155264
pure (hfs, hbio)
156265

266+
-- | @'simHasBlockIO' mockFs@ creates a pair of simulated 'HasFS' and
267+
-- 'HasBlockIO' that allow fault injection.
268+
--
269+
-- The pair of interfaces share the same mocked file system. The initial state
270+
-- of the mocked file system is set to @mockFs@.
271+
--
272+
-- If you want to have access to the current state of the mocked file system
273+
-- or stream of errors, use 'simHasBlockIO' instead.
157274
simHasBlockIO' ::
158275
(MonadCatch m, MonadMVar m, PrimMonad m, MonadSTM m)
159276
=> MockFS
160277
-> m (HasFS m HandleMock, HasBlockIO m HandleMock)
161278
simHasBlockIO' mockFS = do
162279
hfs <- simHasFS' mockFS
163-
hbio <- fromHasFS hfs
280+
hbio <- unsafeFromHasFS hfs
164281
pure (hfs, hbio)
165282

283+
-- | @'simErrorHasBlockIO' mockFsVar errorsVar@ creates a pair of simulated
284+
-- 'HasFS' and 'HasBlockIO' that allow fault injection.
285+
--
286+
-- The pair of interfaces share the same mocked file system, which is stored in
287+
-- @mockFsVar@. The current state of the mocked file system can be accessed by
288+
-- the user by reading @mockFsVar@, but note that the user should not leave
289+
-- @mockFsVar@ empty.
290+
--
291+
-- The pair of interfaces share the same stream of errors, which is stored in
292+
-- @errorsVar@. The current state of the stream of errors can be accessed by the
293+
-- user by reading @errorsVar@.
166294
simErrorHasBlockIO ::
167295
forall m. (MonadCatch m, MonadMVar m, PrimMonad m, MonadSTM m)
168296
=> StrictTMVar m MockFS
169297
-> StrictTVar m Errors
170298
-> m (HasFS m HandleMock, HasBlockIO m HandleMock)
171299
simErrorHasBlockIO fsVar errorsVar = do
172300
let hfs = simErrorHasFS fsVar errorsVar
173-
hbio <- fromHasFS hfs
301+
hbio <- unsafeFromHasFS hfs
174302
pure (hfs, hbio)
175303

304+
-- | @'simErrorHasBlockIO' mockFs errors@ creates a pair of simulated 'HasFS'
305+
-- and 'HasBlockIO' that allow fault injection.
306+
--
307+
-- The pair of interfaces share the same mocked file system. The initial state
308+
-- of the mocked file system is set to @mockFs@.
309+
--
310+
-- The pair of interfaces share the same stream of errors. The initial state of
311+
-- the stream of errors is set to @errors@.
312+
--
313+
-- If you want to have access to the current state of the mocked file system
314+
-- or stream of errors, use 'simErrorHasBlockIO' instead.
176315
simErrorHasBlockIO' ::
177316
(MonadCatch m, MonadMVar m, PrimMonad m, MonadSTM m)
178317
=> MockFS
179318
-> Errors
180319
-> m (HasFS m HandleMock, HasBlockIO m HandleMock)
181320
simErrorHasBlockIO' mockFS errs = do
182321
hfs <- simErrorHasFS' mockFS errs
183-
hbio <- fromHasFS hfs
322+
hbio <- unsafeFromHasFS hfs
184323
pure (hfs, hbio)

test/Test/Database/LSMTree/Internal/Merge.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -51,10 +51,7 @@ tests = testGroup "Test.Database.LSMTree.Internal.Merge"
5151
=> (FS.HasFS IO FsSim.HandleMock -> FS.HasBlockIO IO FsSim.HandleMock -> IO p)
5252
-> Property
5353
ioPropertyWithMockFS prop = ioProperty $ do
54-
(res, mockFS) <-
55-
FsSim.runSimErrorFS FsSim.empty FsSim.emptyErrors $ \_ fs -> do
56-
hbio <- FsSim.fromHasFS fs
57-
prop fs hbio
54+
(res, mockFS, _) <- FsSim.runSimErrorHasBlockIO FsSim.empty FsSim.emptyErrors prop
5855
pure $ res
5956
.&&. counterexample "open handles"
6057
(FsSim.numOpenHandles mockFS === 0)

test/Test/Database/LSMTree/Internal/Readers.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,6 @@ import qualified System.FS.API as FS
3838
import qualified System.FS.BlockIO.API as FS
3939
import qualified System.FS.BlockIO.Sim as FsSim
4040
import qualified System.FS.Sim.MockFS as MockFS
41-
import qualified System.FS.Sim.STM as FsSim
4241
import qualified Test.QuickCheck as QC
4342
import Test.Tasty (TestTree, testGroup)
4443
import Test.Tasty.QuickCheck
@@ -54,8 +53,7 @@ tests = testGroup "Database.LSMTree.Internal.Readers"
5453
[ testProperty "prop_lockstep" $
5554
Lockstep.runActionsBracket (Proxy @ReadersState)
5655
mempty mempty $ \act () -> do
57-
(prop, mockFS) <- FsSim.runSimFS MockFS.empty $ \hfs -> do
58-
hbio <- FsSim.fromHasFS hfs
56+
(prop, mockFS) <- FsSim.runSimHasBlockIO MockFS.empty $ \hfs hbio -> do
5957
(prop, RealState _ mCtx) <- runRealMonad hfs hbio
6058
(RealState 0 Nothing) act
6159
traverse_ closeReadersCtx mCtx -- close current readers

test/Test/Util/FS.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@ import System.FS.API as FS
7575
import qualified System.FS.API.Lazy as FSL
7676
import System.FS.BlockIO.API
7777
import System.FS.BlockIO.IO hiding (unsafeFromHasFS)
78-
import System.FS.BlockIO.Sim (fromHasFS)
78+
import System.FS.BlockIO.Sim (unsafeFromHasFS)
7979
import System.FS.IO
8080
import System.FS.Sim.Error
8181
import System.FS.Sim.MockFS (HandleMock, MockFS, numOpenHandles,
@@ -136,7 +136,7 @@ withSimHasBlockIO ::
136136
-> m Property
137137
withSimHasBlockIO post fs k = do
138138
withSimHasFS post fs $ \hfs fsVar -> do
139-
hbio <- fromHasFS hfs
139+
hbio <- unsafeFromHasFS hfs
140140
k hfs hbio fsVar
141141

142142
{-------------------------------------------------------------------------------
@@ -180,7 +180,7 @@ withSimErrorHasBlockIO ::
180180
-> m Property
181181
withSimErrorHasBlockIO post fs errs k =
182182
withSimErrorHasFS post fs errs $ \hfs fsVar errsVar -> do
183-
hbio <- fromHasFS hfs
183+
hbio <- unsafeFromHasFS hfs
184184
k hfs hbio fsVar errsVar
185185

186186
{-------------------------------------------------------------------------------

test/Test/Util/FS/Error.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -114,7 +114,7 @@ simErrorHasBlockIOLogged ::
114114
-> m (HasFS m HandleMock, HasBlockIO m HandleMock)
115115
simErrorHasBlockIOLogged fsVar errorsVar logVar = do
116116
let hfs = simErrorHasFSLogged fsVar errorsVar logVar
117-
hbio <- fromHasFS hfs
117+
hbio <- unsafeFromHasFS hfs
118118
pure (hfs, hbio)
119119

120120
-- | Produce a simulated file system with injected errors and a logger for those

0 commit comments

Comments
 (0)