88{-# LANGUAGE UnboxedTuples #-}
99
1010module System.FS.BlockIO.API (
11+ -- * HasBlockIO
1112 HasBlockIO (.. )
1213 , IOCtxParams (.. )
1314 , defaultIOCtxParams
@@ -19,15 +20,19 @@ module System.FS.BlockIO.API (
1920 , ioopBufferOffset
2021 , ioopByteCount
2122 , IOResult (.. )
22- -- * Advice
23+ -- ** Advice
2324 , Advice (.. )
2425 , hAdviseAll
2526 , hDropCacheAll
26- -- * File locks
27+ -- ** File locks
2728 , GHC. LockMode (.. )
2829 , GHC. FileLockingNotSupported (.. )
2930 , LockFileHandle (.. )
31+ -- ** Storage synchronisation
32+ , synchroniseFile
33+ -- * Defaults for the real file system
3034 , tryLockFileIO
35+ , createHardLinkIO
3136 -- * Re-exports
3237 , ByteCount
3338 , FileOffset
@@ -52,7 +57,8 @@ import System.FS.API (BufferOffset, FsError (..), FsPath, Handle (..),
5257 HasFS , SomeHasFS (.. ))
5358import System.FS.IO (HandleIO )
5459import qualified System.IO as GHC
55- import System.IO.Error (ioeSetErrorString , mkIOError )
60+ import System.IO.Error (doesNotExistErrorType , ioeSetErrorString ,
61+ mkIOError )
5662import System.Posix.Types (ByteCount , FileOffset )
5763
5864-- | Abstract interface for submitting large batches of I\/O operations.
@@ -125,12 +131,42 @@ data HasBlockIO m h = HasBlockIO {
125131 -- limited scope. That is, it has to fit the style of @withHandleToHANDLE ::
126132 -- Handle -> (HANDLE -> IO a) -> IO a@ from the @Win32@ package.
127133 , tryLockFile :: FsPath -> GHC. LockMode -> m (Maybe (LockFileHandle m ))
134+
135+ -- | Synchronise file contents with the storage device.
136+ --
137+ -- Ensure that all change to the file handle's contents which exist only in
138+ -- memory (as buffered system cache pages) are transfered/flushed to disk.
139+ -- This will also update the file handle's associated metadata.
140+ --
141+ -- This uses different system calls on different distributions.
142+ -- * [Linux]: @fsync(2)@
143+ -- * [MacOS]: @fsync(2)@
144+ -- * [Windows]: @flushFileBuffers@
145+ , hSynchronise :: Handle h -> m ()
146+
147+ -- | Synchronise a directory with the storage device.
148+ --
149+ -- This uses different system calls on different distributions.
150+ -- * [Linux]: @fsync(2)@
151+ -- * [MacOS]: @fsync(2)@
152+ -- * [Windows]: no-op
153+ , synchroniseDirectory :: FsPath -> m ()
154+
155+ -- | Create a hard link for an existing file at the source path and a new
156+ -- file at the target path.
157+ --
158+ -- This uses different system calls on different distributions.
159+ -- * [Linux]: @link@
160+ -- * [MacOS]: @link@
161+ -- * [Windows]: @CreateHardLinkW@
162+ , createHardLink :: FsPath -> FsPath -> m ()
128163 }
129164
130165instance NFData (HasBlockIO m h ) where
131- rnf (HasBlockIO a b c d e f) =
166+ rnf (HasBlockIO a b c d e f g h i ) =
132167 rwhnf a `seq` rwhnf b `seq` rnf c `seq`
133- rwhnf d `seq` rwhnf e `seq` rwhnf f
168+ rwhnf d `seq` rwhnf e `seq` rwhnf f `seq`
169+ rwhnf g `seq` rwhnf h `seq` rwhnf i
134170
135171-- | Concurrency parameters for initialising a 'HasBlockIO. Can be ignored by
136172-- serial implementations.
@@ -195,6 +231,10 @@ deriving via (VU.UnboxViaPrim IOResult) instance VG.Vector VU.Vector IOResult
195231
196232instance VUM. Unbox IOResult
197233
234+ {- ------------------------------------------------------------------------------
235+ Advice
236+ -------------------------------------------------------------------------------}
237+
198238-- | Basically "System.Posix.Fcntl.Advice" from the @unix@ package
199239data Advice =
200240 AdviceNormal
@@ -214,6 +254,36 @@ hAdviseAll hbio h advice = hAdvise hbio h 0 0 advice -- len=0 implies until the
214254hDropCacheAll :: HasBlockIO m h -> Handle h -> m ()
215255hDropCacheAll hbio h = hAdviseAll hbio h AdviceDontNeed
216256
257+ {- ------------------------------------------------------------------------------
258+ Storage synchronisation
259+ -------------------------------------------------------------------------------}
260+
261+ -- TODO: currently, we perform an explicit check to see if the file exists and
262+ -- throw an error when it does not exist. We would prefer to be able to rely on
263+ -- withFile to throw an error for us that we could rethrow with an upated
264+ -- description/location. Unfortunately, we have to open te file in ReadWriteMode
265+ -- on Windows, and withFile currently does not support such errors. The only
266+ -- options are:
267+ --
268+ -- * AllowExisting: silently create a file if it does not exist
269+ -- * MustBeNew: throw an error if the file exists
270+ --
271+ -- We would need to add a third option to fs-api:
272+ --
273+ -- * MustExist: throw an error if the file *does not* exist
274+ synchroniseFile :: MonadThrow m => HasFS m h -> HasBlockIO m h -> FsPath -> m ()
275+ synchroniseFile hfs hbio path = do
276+ b <- FS. doesFileExist hfs path
277+ if b then
278+ FS. withFile hfs path (FS. ReadWriteMode FS. AllowExisting ) $ hSynchronise hbio
279+ else
280+ throwIO $ FS. ioToFsError (FS. mkFsErrorPath hfs (FS. mkFsPath [] )) ioerr
281+ where
282+ ioerr =
283+ ioeSetErrorString
284+ (mkIOError doesNotExistErrorType " synchroniseFile" Nothing Nothing )
285+ (" synchroniseFile: file does not exist" )
286+
217287{- ------------------------------------------------------------------------------
218288 File locks
219289-------------------------------------------------------------------------------}
@@ -249,3 +319,16 @@ rethrowFsErrorIO hfs fp action = do
249319 handleError :: HasCallStack => IOError -> IO a
250320 handleError ioErr =
251321 throwIO $ FS. ioToFsError (FS. mkFsErrorPath hfs fp) ioErr
322+
323+ {- ------------------------------------------------------------------------------
324+ Hard links
325+ -------------------------------------------------------------------------------}
326+
327+ createHardLinkIO ::
328+ HasFS IO HandleIO
329+ -> (FilePath -> FilePath -> IO () )
330+ -> (FsPath -> FsPath -> IO () )
331+ createHardLinkIO hfs f = \ source target -> do
332+ source' <- FS. unsafeToFilePath hfs source -- shouldn't fail because we are in IO
333+ target' <- FS. unsafeToFilePath hfs target -- shouldn't fail because we are in IO
334+ f source' target'
0 commit comments