11{-# LANGUAGE TypeFamilies #-}
22{-# LANGUAGE UnboxedTuples #-}
33
4+ -- | Abstract interface, types, and utilities.
45module System.FS.BlockIO.API (
56 -- * HasBlockIO
67 HasBlockIO (.. )
@@ -45,55 +46,80 @@ import System.FS.API (BufferOffset, FsPath, Handle (..), HasFS)
4546import System.Posix.Types (ByteCount , FileOffset )
4647import Text.Printf
4748
48- -- | Abstract interface for submitting large batches of I\/O operations.
49+ -- | Abstract interface for submitting large batches of I\/O operations. This
50+ -- interface is an extension of the 'HasFS' interface that is provided by the
51+ -- @fs-api@ package.
52+ --
53+ -- The interface tries to specify uniform behaviour, but each implementation can
54+ -- have subtly different effects for a variety of reasons. However, for the most
55+ -- part the underlying implementation of an instance of the interface should not
56+ -- affect the correctness of programs that use the interface.
57+ --
58+ -- For uniform behaviour across implementations, functions that create a new
59+ -- instance of the interface should initialise an IO context. This IO context
60+ -- may be of any shape, as long as the context has two modes: open and closed.
61+ -- This context is only important for the 'close' and 'submitIO' functions. As
62+ -- long as the IO context is open, 'submitIO' should perform batches of I\/O
63+ -- operations as expected, but 'submitIO' should throw an error as soon as the
64+ -- IO context is closed. Once the IO context is closed, it can not be re-opened
65+ -- again. Instead, the user should create a new instance of the interface.
66+ --
67+ -- Note: there are a bunch of functions in the interface that have nothing to do
68+ -- with submitting large batches of I/O operations. In fact, only 'close' and
69+ -- 'submitIO' are related to that. All other functions were put in this record
70+ -- for simplicity because the authors of the library needed them and it was more
71+ -- straightforward to add them here then to add them to @fs-api@. Still these
72+ -- unrelated functions could and should all be moved into @fs-api@ at some point
73+ -- in the future.
74+ --
75+ -- === Implementations
76+ --
77+ -- There are currently two known implementations of the interface:
78+ --
79+ -- * An implementation using the real file system, which can be found in the
80+ -- "System.FS.BlockIO.IO" module. This implementation is platform-dependent.
81+ --
82+ -- * An implementation using a simulated file system, which can be found in the
83+ -- @System.FS.BlockIO.Sim@ module of the @blockio:sim@ sublibrary. This
84+ -- implementation is uniform across platforms.
85+ --
4986data HasBlockIO m h = HasBlockIO {
50- -- | (Idempotent) close the interface.
87+ -- | (Idempotent) close the IO context that is required for running
88+ -- 'submitIO'.
89+ --
90+ -- Using 'submitIO' after 'close' throws an 'FsError' exception.
5191 --
52- -- Using 'submitIO' after 'close' should thrown an 'FsError' exception. See
53- -- 'mkClosedError'.
5492 close :: HasCallStack => m ()
93+
5594 -- | Submit a batch of I\/O operations and wait for the result.
5695 --
5796 -- Results correspond to input 'IOOp's in a pair-wise manner, i.e., one can
5897 -- match 'IOOp's with 'IOResult's by indexing into both vectors at the same
5998 -- position.
6099 --
61100 -- If any of the I\/O operations fails, an 'FsError' exception will be thrown.
101+ --
62102 , submitIO :: HasCallStack => V. Vector (IOOp (PrimState m ) h ) -> m (VU. Vector IOResult )
103+
104+ -- TODO: once file caching is disabled, subsequent reads/writes with
105+ -- misaligned byte arrays should throw an error. Preferably, this should
106+ -- happen in both the simulation and real implementation, even if the real
107+ -- implementation does not support setting the file caching mode. This would
108+ -- make the behaviour of the file caching mode more uniform across
109+ -- implementations and platforms.
110+
63111 -- | Set the file data caching mode for a file handle.
64112 --
65- -- This has different effects on different distributions.
66- -- * [Linux]: set the @O_DIRECT@ flag.
67- -- * [MacOS]: set the @F_NOCACHE@ flag.
68- -- * [Windows]: no-op.
69- --
70- -- TODO: subsequent reads/writes with misaligned byte arrays should fail
71- -- both in simulation and real implementation.
72113 , hSetNoCache :: Handle h -> Bool -> m ()
114+
73115 -- | Predeclare an access pattern for file data.
74116 --
75- -- This has different effects on different distributions.
76- -- * [Linux]: perform @posix_fadvise(2).
77- -- * [MacOS]: no-op.
78- -- * [Windows]: no-op.
79117 , hAdvise :: Handle h -> FileOffset -> FileOffset -> Advice -> m ()
118+
80119 -- | Allocate file space.
81120 --
82- -- This has different effects on different distributions.
83- -- * [Linux]: perform @posix_fallocate(2).
84- -- * [MacOS]: no-op.
85- -- * [Windows]: no-op.
86121 , hAllocate :: Handle h -> FileOffset -> FileOffset -> m ()
87- -- | Try to acquire a file lock without blocking.
88- --
89- -- This uses different locking methods on different distributions.
90- -- * [Linux]: Open file descriptor (OFD)
91- -- * [MacOS]: @flock@
92- -- * [Windows]: @LockFileEx@
93- --
94- -- This function can throw 'GHC.FileLockingNotSupported' when file locking
95- -- is not supported.
96- --
122+
97123 -- NOTE: though it would have been nicer to allow locking /file handles/
98124 -- instead of /file paths/, it would make the implementation of this
99125 -- function in 'IO' much more complex. In particular, if we want to reuse
@@ -114,35 +140,34 @@ data HasBlockIO m h = HasBlockIO {
114140 -- that allows you to use 'LockFileHandle' as a 'Handle', but only within a
115141 -- limited scope. That is, it has to fit the style of @withHandleToHANDLE ::
116142 -- Handle -> (HANDLE -> IO a) -> IO a@ from the @Win32@ package.
143+
144+ -- | Try to acquire a file lock without blocking.
145+ --
146+ -- This function throws 'GHC.FileLockingNotSupported' when file locking is
147+ -- not supported.
148+ --
117149 , tryLockFile :: FsPath -> GHC. LockMode -> m (Maybe (LockFileHandle m ))
118150
119151 -- | Synchronise file contents with the storage device.
120152 --
121- -- Ensure that all change to the file handle's contents which exist only in
122- -- memory (as buffered system cache pages) are transferred/flushed to disk.
123- -- This will also update the file handle's associated metadata.
153+ -- This ensures that all changes to the file handle's contents, which might
154+ -- exist only in memory as buffered system cache pages, are
155+ -- transferred/flushed to disk. This will also update the file handle's
156+ -- associated metadata.
124157 --
125- -- This uses different system calls on different distributions.
126- -- * [Linux]: @fsync(2)@
127- -- * [MacOS]: @fsync(2)@
128- -- * [Windows]: @flushFileBuffers@
129158 , hSynchronise :: Handle h -> m ()
130159
131160 -- | Synchronise a directory with the storage device.
132161 --
133- -- This uses different system calls on different distributions.
134- -- * [Linux]: @fsync(2)@
135- -- * [MacOS]: @fsync(2)@
136- -- * [Windows]: no-op
162+ -- This ensures that all changes to the directory, which might exist only in
163+ -- memory as buffered changes, are transferred/flushed to disk. This will
164+ -- also update the directory's associated metadata.
165+ --
137166 , synchroniseDirectory :: FsPath -> m ()
138167
139168 -- | Create a hard link for an existing file at the source path and a new
140169 -- file at the target path.
141170 --
142- -- This uses different system calls on different distributions.
143- -- * [Linux]: @link@
144- -- * [MacOS]: @link@
145- -- * [Windows]: @CreateHardLinkW@
146171 , createHardLink :: FsPath -> FsPath -> m ()
147172 }
148173
@@ -195,7 +220,7 @@ instance VUM.Unbox IOResult
195220 Advice
196221-------------------------------------------------------------------------------}
197222
198- -- | Basically "System.Posix.Fcntl.Advice" from the @unix@ package
223+ -- | Copy of "System.Posix.Fcntl.Advice" from the @unix@ package
199224data Advice =
200225 AdviceNormal
201226 | AdviceRandom
@@ -219,7 +244,7 @@ hDropCacheAll hbio h = hAdviseAll hbio h AdviceDontNeed
219244-------------------------------------------------------------------------------}
220245
221246{-# SPECIALISE synchroniseFile :: HasFS IO h -> HasBlockIO IO h -> FsPath -> IO () #-}
222- -- | Synchronise a file and its contents with the storage device.
247+ -- | Synchronise a file's contents and metadata with the storage device.
223248synchroniseFile :: MonadThrow m => HasFS m h -> HasBlockIO m h -> FsPath -> m ()
224249synchroniseFile hfs hbio path =
225250 FS. withFile hfs path (FS. ReadWriteMode FS. MustExist ) $ hSynchronise hbio
@@ -230,8 +255,8 @@ synchroniseFile hfs hbio path =
230255 -> FsPath
231256 -> IO ()
232257 #-}
233- -- | Synchronise a directory and recursively its contents with the storage
234- -- device .
258+ -- | Synchronise a directory's contents and metadata with the storage device,
259+ -- and recursively for all entries in the directory .
235260synchroniseDirectoryRecursive ::
236261 MonadThrow m
237262 => HasFS m h
0 commit comments