diff --git a/.github/workflows/haskell.yml b/.github/workflows/haskell.yml index 3c2d6800f..5914375a6 100644 --- a/.github/workflows/haskell.yml +++ b/.github/workflows/haskell.yml @@ -47,6 +47,25 @@ jobs: cabal-version: ${{ matrix.cabal }} cabal-update: true + - name: Install liburing (on Linux) + id: setup-liburing + if: matrix.os == 'ubuntu-latest' + run: | + sudo apt-get update + sudo apt-get -y install pkg-config + echo "PKG_CONFIG_PATH=$PKG_CONFIG_PATH" + mkdir tmp + cd tmp + git clone https://github.com/axboe/liburing.git + cd liburing + git checkout liburing-2.5 + ./configure --cc=gcc --cxx=g++ + make -j$(nproc) + sudo make install + cd ../.. + sudo rm -rf ./tmp + pkg-config --modversion liburing + - name: Configure the build run: | cabal configure --enable-tests --enable-benchmark --ghc-options="-Werror" --ghc-options="-fno-ignore-asserts" @@ -131,11 +150,7 @@ jobs: cache-name: cache-cabal-stylish with: path: ${{ steps.setup-haskell.outputs.cabal-store }} - key: ${{ runner.os }}-${{ matrix.ghc }}-${{ env.cache-name }}-${{ hashFiles('**/*.cabal') }}-${{ hashFiles('**/cabal.project') }} - restore-keys: | - ${{ runner.os }}-${{ matrix.ghc }}-${{ env.cache-name }}-${{ hashFiles('**/*.cabal') }}-${{ hashFiles('**/cabal.project') }} - ${{ runner.os }}-${{ matrix.ghc }}-${{ env.cache-name }}-${{ hashFiles('**/*.cabal') }}- - ${{ runner.os }}-${{ matrix.ghc }}-${{ env.cache-name }}- + key: ${{ runner.os }}-${{ matrix.ghc }}-${{ env.cache-name }} - name: Install stylish-haskell run: cabal install --ignore-project stylish-haskell --constraint 'stylish-haskell == 0.14.6.0' diff --git a/README.md b/README.md index b92d1cecb..7d84f886a 100644 --- a/README.md +++ b/README.md @@ -16,4 +16,7 @@ It has a number of custom features that are primarily tailored towards performan ## System requirements -This library only supports 64-bit, little-endian systems. \ No newline at end of file +This library only supports 64-bit, little-endian systems. + +Provide the -threaded flag to executables, test suites and benchmark suites if +you use this library on Linux systems. \ No newline at end of file diff --git a/cabal.project b/cabal.project index 2ebed1bd7..690df8a0d 100644 --- a/cabal.project +++ b/cabal.project @@ -38,3 +38,18 @@ package lsm-tree -- apply this to all components -- relevant mostly only for development & testing ghc-options: -fno-ignore-asserts + +if(os(linux)) + source-repository-package + type: git + location: https://github.com/well-typed/blockio-uring + tag: bbeb81130ec3eafd8ced81564cc8bd46d24aff08 + +-- fs-api with support for I/O using user-supplied buffers +source-repository-package + type: git + location: https://github.com/input-output-hk/fs-sim + tag: 6a4a456640dd1fed434ccb4cbb553482afe8e2d4 + subdir: + fs-api + fs-sim \ No newline at end of file diff --git a/fs-api-blockio/src-linux/System/FS/BlockIO/Async.hs b/fs-api-blockio/src-linux/System/FS/BlockIO/Async.hs new file mode 100644 index 000000000..f7c772665 --- /dev/null +++ b/fs-api-blockio/src-linux/System/FS/BlockIO/Async.hs @@ -0,0 +1,94 @@ +{-# LANGUAGE NamedFieldPuns #-} + +module System.FS.BlockIO.Async ( + asyncHasBlockIO + ) where + +import Control.Exception +import qualified Control.Exception as E +import Control.Monad +import Foreign.C.Error +import GHC.IO.Exception +import GHC.Stack +import System.FS.API (BufferOffset (..), FsErrorPath, Handle (..), + HasFS (..), SomeHasFS (..), ioToFsError) +import qualified System.FS.BlockIO.API as API +import System.FS.BlockIO.API (IOOp (..), IOResult (..), ioopHandle) +import System.FS.IO (HandleIO) +import System.FS.IO.Internal.Handle +import qualified System.IO.BlockIO as I +import System.IO.Error (ioeSetErrorString, isResourceVanishedError) +import System.Posix.Types + +-- | IO instantiation of 'HasBlockIO', using @blockio-uring@. +asyncHasBlockIO :: HasFS IO HandleIO -> Maybe API.IOCtxParams -> IO (API.HasBlockIO IO HandleIO) +asyncHasBlockIO hasFS ctxParams = do + ctx <- I.initIOCtx (maybe I.defaultIOCtxParams ctxParamsConv ctxParams) + pure $ API.HasBlockIO { + API.close = I.closeIOCtx ctx + , API.submitIO = submitIO hasFS ctx + } + +ctxParamsConv :: API.IOCtxParams -> I.IOCtxParams +ctxParamsConv API.IOCtxParams{API.ioctxBatchSizeLimit, API.ioctxConcurrencyLimit} = + I.IOCtxParams { + I.ioctxBatchSizeLimit = ioctxBatchSizeLimit + , I.ioctxConcurrencyLimit = ioctxConcurrencyLimit + } + +submitIO :: + HasFS IO HandleIO + -> I.IOCtx + -> [IOOp IO HandleIO] + -> IO [IOResult] +submitIO hasFS ioctx ioops = do + ioops' <- mapM ioopConv ioops + ress <- I.submitIO ioctx ioops' `catch` rethrowClosedError + zipWithM rethrowErrno ioops ress + where + rethrowClosedError :: IOError -> IO a + rethrowClosedError e@IOError{} = + -- Pattern matching on the error is brittle, because the structure of + -- the exception might change between versions of @blockio-uring@. + -- Nonetheless, it's better than nothing. + if isResourceVanishedError e && ioe_location e == "IOCtx closed" + then throwIO (API.mkClosedError (SomeHasFS hasFS) "submitIO") + else throwIO e + + rethrowErrno :: + HasCallStack + => IOOp IO HandleIO + -> I.IOResult + -> IO IOResult + rethrowErrno ioop res = do + case res of + I.IOResult c -> pure (IOResult c) + I.IOError e -> throwAsFsError e + where + throwAsFsError :: HasCallStack => Errno -> IO a + throwAsFsError errno = E.throwIO $ ioToFsError fep (fromErrno errno) + + fep :: FsErrorPath + fep = mkFsErrorPath hasFS (handlePath (ioopHandle ioop)) + + fromErrno :: Errno -> IOError + fromErrno errno = ioeSetErrorString + (errnoToIOError "submitIO" errno Nothing Nothing) + ("submitIO failed: " <> ioopType) + + ioopType :: String + ioopType = case ioop of + IOOpRead{} -> "IOOpRead" + IOOpWrite{} -> "IOOpWrite" + +ioopConv :: IOOp IO HandleIO -> IO (I.IOOp IO) +ioopConv (IOOpRead h off buf bufOff c) = handleFd h >>= \fd -> + pure (I.IOOpRead fd off buf (unBufferOffset bufOff) c) +ioopConv (IOOpWrite h off buf bufOff c) = handleFd h >>= \fd -> + pure (I.IOOpWrite fd off buf (unBufferOffset bufOff) c) + +-- This only checks whether the handle is open when we convert to an Fd. After +-- that, the handle could be closed when we're still performing blockio +-- operations. +handleFd :: Handle HandleIO -> IO Fd +handleFd h = withOpenHandle "submitIO" (handleRaw h) pure diff --git a/fs-api-blockio/src-linux/System/FS/BlockIO/Internal.hs b/fs-api-blockio/src-linux/System/FS/BlockIO/Internal.hs new file mode 100644 index 000000000..6da38a107 --- /dev/null +++ b/fs-api-blockio/src-linux/System/FS/BlockIO/Internal.hs @@ -0,0 +1,15 @@ +module System.FS.BlockIO.Internal ( + ioHasBlockIO + ) where + +import System.FS.API (HasBufFS, HasFS) +import System.FS.BlockIO.API (HasBlockIO, IOCtxParams) +import qualified System.FS.BlockIO.Async as I +import System.FS.IO (HandleIO) + +ioHasBlockIO :: + HasFS IO HandleIO + -> HasBufFS IO HandleIO + -> Maybe IOCtxParams + -> IO (HasBlockIO IO HandleIO) +ioHasBlockIO hfs _bhfs = I.asyncHasBlockIO hfs diff --git a/fs-api-blockio/src-macos/System/FS/BlockIO/Internal.hs b/fs-api-blockio/src-macos/System/FS/BlockIO/Internal.hs new file mode 100644 index 000000000..e661912b0 --- /dev/null +++ b/fs-api-blockio/src-macos/System/FS/BlockIO/Internal.hs @@ -0,0 +1,15 @@ +module System.FS.BlockIO.Internal ( + ioHasBlockIO + ) where + +import System.FS.API (HasBufFS, HasFS) +import System.FS.BlockIO.API (HasBlockIO, IOCtxParams) +import qualified System.FS.BlockIO.Serial as Serial +import System.FS.IO (HandleIO) + +ioHasBlockIO :: + HasFS IO HandleIO + -> HasBufFS IO HandleIO + -> Maybe IOCtxParams + -> IO (HasBlockIO IO HandleIO) +ioHasBlockIO hasFS hasBufFS _ = Serial.serialHasBlockIO hasFS hasBufFS diff --git a/fs-api-blockio/src-windows/System/FS/BlockIO/Internal.hs b/fs-api-blockio/src-windows/System/FS/BlockIO/Internal.hs new file mode 100644 index 000000000..e661912b0 --- /dev/null +++ b/fs-api-blockio/src-windows/System/FS/BlockIO/Internal.hs @@ -0,0 +1,15 @@ +module System.FS.BlockIO.Internal ( + ioHasBlockIO + ) where + +import System.FS.API (HasBufFS, HasFS) +import System.FS.BlockIO.API (HasBlockIO, IOCtxParams) +import qualified System.FS.BlockIO.Serial as Serial +import System.FS.IO (HandleIO) + +ioHasBlockIO :: + HasFS IO HandleIO + -> HasBufFS IO HandleIO + -> Maybe IOCtxParams + -> IO (HasBlockIO IO HandleIO) +ioHasBlockIO hasFS hasBufFS _ = Serial.serialHasBlockIO hasFS hasBufFS diff --git a/fs-api-blockio/src/System/FS/BlockIO/API.hs b/fs-api-blockio/src/System/FS/BlockIO/API.hs new file mode 100644 index 000000000..a2dad15f2 --- /dev/null +++ b/fs-api-blockio/src/System/FS/BlockIO/API.hs @@ -0,0 +1,64 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE RankNTypes #-} + +module System.FS.BlockIO.API ( + HasBlockIO (..) + , IOCtxParams (..) + , mkClosedError + , IOOp (..) + , ioopHandle + , IOResult (..) + -- * Re-exports + , ByteCount + , FileOffset + ) where + +import Control.Monad.Primitive (PrimMonad (PrimState)) +import Data.Primitive.ByteArray (MutableByteArray) +import GHC.IO.Exception (IOErrorType (ResourceVanished)) +import System.FS.API +import System.IO.Error (ioeSetErrorString, mkIOError) +import System.Posix.Types (ByteCount, FileOffset) +import Util.CallStack + +-- | Abstract interface for submitting large batches of I\/O operations. +data HasBlockIO m h = HasBlockIO { + -- | (Idempotent) close the interface. + -- + -- Using 'submitIO' after 'close' should thrown an 'FsError' exception. See + -- 'mkClosedError'. + close :: HasCallStack => m () + -- | Submit a batch of I\/O operations and wait for the result. + -- + -- Results correspond to input 'IOOp's in a pair-wise manner, i.e., one can + -- match 'IOOp's with 'IOResult's by zipping the input and output list. + -- + -- If any of the I\/O operations fails, an 'FsError' exception will be thrown. + , submitIO :: HasCallStack => [IOOp m h] -> m [IOResult] + } + +-- | Concurrency parameters for initialising a 'HasBlockIO. Can be ignored by +-- serial implementations. +data IOCtxParams = IOCtxParams { + ioctxBatchSizeLimit :: !Int, + ioctxConcurrencyLimit :: !Int + } + +mkClosedError :: HasCallStack => SomeHasFS m -> String -> FsError +mkClosedError (SomeHasFS hasFS) loc = ioToFsError (mkFsErrorPath hasFS (mkFsPath [])) ioerr + where ioerr = + ioeSetErrorString + (mkIOError ResourceVanished loc Nothing Nothing) + ("HasBlockIO closed: " <> loc) + + +data IOOp m h = + IOOpRead !(Handle h) !FileOffset !(MutableByteArray (PrimState m)) !BufferOffset !ByteCount + | IOOpWrite !(Handle h) !FileOffset !(MutableByteArray (PrimState m)) !BufferOffset !ByteCount + +ioopHandle :: IOOp m h -> Handle h +ioopHandle (IOOpRead h _ _ _ _) = h +ioopHandle (IOOpWrite h _ _ _ _) = h + +-- | Number of read/written bytes. +newtype IOResult = IOResult ByteCount diff --git a/fs-api-blockio/src/System/FS/BlockIO/IO.hs b/fs-api-blockio/src/System/FS/BlockIO/IO.hs new file mode 100644 index 000000000..2a905a60e --- /dev/null +++ b/fs-api-blockio/src/System/FS/BlockIO/IO.hs @@ -0,0 +1,16 @@ +module System.FS.BlockIO.IO ( + ioHasBlockIO + ) where + +import System.FS.API (HasBufFS, HasFS) +import System.FS.BlockIO.API (HasBlockIO, IOCtxParams) +import qualified System.FS.BlockIO.Internal as I +import System.FS.IO (HandleIO) + +-- | Platform-dependent IO instantiation of 'HasBlockIO'. +ioHasBlockIO :: + HasFS IO HandleIO + -> HasBufFS IO HandleIO + -> Maybe IOCtxParams + -> IO (HasBlockIO IO HandleIO) +ioHasBlockIO = I.ioHasBlockIO diff --git a/fs-api-blockio/src/System/FS/BlockIO/Serial.hs b/fs-api-blockio/src/System/FS/BlockIO/Serial.hs new file mode 100644 index 000000000..dee18ebc1 --- /dev/null +++ b/fs-api-blockio/src/System/FS/BlockIO/Serial.hs @@ -0,0 +1,76 @@ +{-# LANGUAGE LambdaCase #-} + +module System.FS.BlockIO.Serial ( + serialHasBlockIO + ) where + +import Control.Concurrent.Class.MonadMVar +import Control.Monad.Class.MonadThrow +import System.FS.API +import qualified System.FS.BlockIO.API as API +import System.FS.BlockIO.API (IOOp (..), IOResult (..)) + +-- | IO instantiation of 'HasBlockIO', using serialised I\/O. +serialHasBlockIO :: + (MonadThrow m, MonadMVar m, Eq h) + => HasFS m h + -> HasBufFS m h + -> m (API.HasBlockIO m h) +serialHasBlockIO hfs hbfs = do + ctx <- initIOCtx (SomeHasFS hfs) + pure $ API.HasBlockIO { + API.close = close ctx + , API.submitIO = submitIO hfs hbfs ctx + } + +data IOCtx m = IOCtx { ctxFS :: SomeHasFS m, openVar :: MVar m CtxState } + +data CtxState = Open Word | Closing Word | Closed + +addSubmitter :: (MonadMVar m, MonadThrow m) => IOCtx m -> m () +addSubmitter ctx = modifyMVar_ (openVar ctx) $ \case + Open n -> pure (Open (n+1)) + Closing _ -> throwIO (API.mkClosedError (ctxFS ctx) "submitIO") + Closed -> throwIO (API.mkClosedError (ctxFS ctx) "submitIO") + +removeSubmitter :: (MonadMVar m, MonadThrow m) => IOCtx m -> m () +removeSubmitter ctx = modifyMVar_ (openVar ctx) $ \case + Open n -> pure (Open (n-1)) + Closing n + | n - 1 == 0 -> pure Closed + | otherwise -> pure (Closing (n-1)) + Closed -> throwIO (API.mkClosedError (ctxFS ctx) "submitIO") + +initIOCtx :: MonadMVar m => SomeHasFS m -> m (IOCtx m) +initIOCtx someHasFS = IOCtx someHasFS <$> newMVar (Open 0) + +close :: MonadMVar m => IOCtx m -> m () +close ctx = modifyMVar_ (openVar ctx) $ \case + Open n -> pure (Closing n) + Closing n -> pure (Closing n) + Closed -> pure Closed + +submitIO :: + (MonadMVar m, MonadThrow m) + => HasFS m h + -> HasBufFS m h + -> IOCtx m + -> [IOOp m h] + -> m [IOResult] +submitIO hfs hbfs ctx ioops = do + addSubmitter ctx + ress <- mapM (ioop hfs hbfs) ioops + removeSubmitter ctx + pure ress + +-- | Perform the IOOp using synchronous I\/O. +ioop :: + MonadThrow m + => HasFS m h + -> HasBufFS m h + -> IOOp m h + -> m IOResult +ioop hfs hbfs (IOOpRead h off buf bufOff c) = + IOResult <$> hGetBufExactlyAt hfs hbfs h buf bufOff c (fromIntegral off) +ioop _hfs hbfs (IOOpWrite h off buf bufOff c) = + IOResult <$> hPutBufExactlyAt hbfs h buf bufOff c (fromIntegral off) diff --git a/fs-api-blockio/test/Main.hs b/fs-api-blockio/test/Main.hs new file mode 100644 index 000000000..865c5d778 --- /dev/null +++ b/fs-api-blockio/test/Main.hs @@ -0,0 +1,120 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} + +{-# OPTIONS_GHC -Wno-orphans #-} + +{- HLINT ignore "Use camelCase" -} + +module Main (main) where + +import Control.Concurrent (modifyMVar_, newMVar, threadDelay, + withMVar) +import Control.Concurrent.Async +import Control.Exception (SomeException, try) +import Control.Monad +import Control.Monad.Primitive +import Data.ByteString +import qualified Data.ByteString as BS +import qualified Data.ByteString.Short.Internal as SBS +import Data.Maybe (catMaybes) +import Data.Primitive.ByteArray +import qualified System.FS.API as FS +import System.FS.API.Strict (hPutAllStrict) +import System.FS.BlockIO.API +import qualified System.FS.BlockIO.IO as IO +import qualified System.FS.IO as IO +import System.IO.Temp +import Test.Tasty +import Test.Tasty.HUnit +import Test.Tasty.QuickCheck + +main :: IO () +main = defaultMain tests + +tests :: TestTree +tests = testGroup "fs-api-blockio" [ + testCase "example_initClose" example_initClose + , testCase "example_closeIsIdempotent" example_closeIsIdempotent + , testProperty "prop_readWrite" prop_readWrite + , testProperty "prop_submitToClosedCtx" prop_submitToClosedCtx + ] + +instance Arbitrary ByteString where + arbitrary = BS.pack <$> arbitrary + shrink = fmap BS.pack . shrink . BS.unpack + +fromByteString :: PrimMonad m => ByteString -> m (MutableByteArray (PrimState m)) +fromByteString bs = thawByteArray (ByteArray ba) 0 (SBS.length sbs) + where !sbs@(SBS.SBS ba) = SBS.toShort bs + +toByteString :: PrimMonad m => Int -> MutableByteArray (PrimState m) -> m ByteString +toByteString n mba = freezeByteArray mba 0 n >>= \(ByteArray ba) -> pure (SBS.fromShort $ SBS.SBS ba) + +example_initClose :: Assertion +example_initClose = withSystemTempDirectory "example_initClose" $ \dirPath -> do + let mount = FS.MountPoint dirPath + hfs = IO.ioHasFS mount + hbfs = IO.ioHasBufFS mount + hbio <- IO.ioHasBlockIO hfs hbfs Nothing + close hbio + +example_closeIsIdempotent :: Assertion +example_closeIsIdempotent = withSystemTempDirectory "example_closeIsIdempotent" $ \dirPath -> do + let mount = FS.MountPoint dirPath + hfs = IO.ioHasFS mount + hbfs = IO.ioHasBufFS mount + hbio <- IO.ioHasBlockIO hfs hbfs Nothing + close hbio + eith <- try @SomeException (close hbio) + case eith of + Left (e :: SomeException) -> + assertFailure ("Close on a closed context threw an error : " <> show e) + Right () -> + pure () + +prop_readWrite :: ByteString -> Property +prop_readWrite bs = ioProperty $ withSystemTempDirectory "prop_readWrite" $ \dirPath -> do + let mount = FS.MountPoint dirPath + hfs = IO.ioHasFS mount + hbfs = IO.ioHasBufFS mount + hbio <- IO.ioHasBlockIO hfs hbfs Nothing + prop <- FS.withFile hfs (FS.mkFsPath ["temp"]) (FS.WriteMode FS.MustBeNew) $ \h -> do + let n = BS.length bs + writeBuf <- fromByteString bs + [IOResult m] <- submitIO hbio [IOOpWrite h 0 writeBuf 0 (fromIntegral n)] + let writeTest = n === fromIntegral m + readBuf <- newPinnedByteArray n + [IOResult o] <- submitIO hbio [IOOpRead h 0 readBuf 0 (fromIntegral n)] + let readTest = o === m + bs' <- toByteString n readBuf + let cmpTest = bs === bs' + pure $ writeTest .&&. readTest .&&. cmpTest + close hbio + pure prop + +prop_submitToClosedCtx :: ByteString -> Property +prop_submitToClosedCtx bs = ioProperty $ withSystemTempDirectory "prop_a" $ \dir -> do + let mount = FS.MountPoint dir + hfs = IO.ioHasFS mount + hbfs = IO.ioHasBufFS mount + hbio <- IO.ioHasBlockIO hfs hbfs Nothing + + props <- FS.withFile hfs (FS.mkFsPath ["temp"]) (FS.WriteMode FS.MustBeNew) $ \h -> do + void $ hPutAllStrict hfs h bs + syncVar <- newMVar False + forConcurrently [0 .. BS.length bs - 1] $ \i -> + if i == 0 then do + threadDelay 15 + modifyMVar_ syncVar $ \_ -> do + close hbio + pure True + pure Nothing + else do + readBuf <- newPinnedByteArray (BS.length bs) + withMVar syncVar $ \b -> do + eith <- try @SomeException $ submitIO hbio [IOOpRead h 0 readBuf (fromIntegral i) 1] + pure $ case eith of + Left _ -> Just $ tabulate "submitIO successful" [show False] $ counterexample "expected failure, but got success" (b === True) + Right _ -> Just $ tabulate "submitIO successful" [show True] $ counterexample "expected success, but got failure" (b === False) + pure $ conjoin (catMaybes props) diff --git a/lsm-tree.cabal b/lsm-tree.cabal index c5a84f194..3eb8dd404 100644 --- a/lsm-tree.cabal +++ b/lsm-tree.cabal @@ -235,6 +235,8 @@ test-suite lsm-tree-test , transformers , vector + ghc-options: -fno-ignore-asserts -threaded + benchmark lsm-tree-micro-bench import: warnings, wno-x-partial default-language: Haskell2010 @@ -262,6 +264,8 @@ benchmark lsm-tree-micro-bench , QuickCheck , random + ghc-options: -threaded + benchmark lsm-tree-macro-bench import: warnings, wno-x-partial default-language: Haskell2010 @@ -279,7 +283,7 @@ benchmark lsm-tree-macro-bench , vector , wide-word - ghc-options: -rtsopts -with-rtsopts=-T + ghc-options: -rtsopts -with-rtsopts=-T -threaded library kmerge import: warnings, wno-x-partial @@ -382,3 +386,55 @@ test-suite bloomfilter-tests , random , test-framework , test-framework-quickcheck2 + +library fs-api-blockio + import: warnings, wno-x-partial + visibility: private + hs-source-dirs: fs-api-blockio/src + default-language: Haskell2010 + exposed-modules: + System.FS.BlockIO.API + System.FS.BlockIO.IO + System.FS.BlockIO.Serial + + build-depends: + , base >=4.16 && <4.20 + , fs-api ^>=0.2 + , io-classes ^>=1.3 + , primitive ^>=0.9 + + if os(linux) + hs-source-dirs: fs-api-blockio/src-linux + other-modules: + System.FS.BlockIO.Async + System.FS.BlockIO.Internal + + build-depends: blockio-uring ^>=0.1 + + elif os(osx) + hs-source-dirs: fs-api-blockio/src-macos + other-modules: System.FS.BlockIO.Internal + + elif os(windows) + hs-source-dirs: fs-api-blockio/src-windows + other-modules: System.FS.BlockIO.Internal + +test-suite fs-api-blockio-test + import: warnings, wno-x-partial + default-language: Haskell2010 + type: exitcode-stdio-1.0 + hs-source-dirs: fs-api-blockio/test + main-is: Main.hs + build-depends: + , async + , base >=4.16 && <4.20 + , bytestring + , fs-api + , lsm-tree:fs-api-blockio + , primitive + , tasty + , tasty-hunit + , tasty-quickcheck + , temporary + + ghc-options: -threaded -fno-ignore-asserts