Skip to content
Snippets Groups Projects
Commit 98eced86 authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing:
Browse files

Wrap fsync(2) and fdatasync(2)


This adds two new functions in `System.Posix.Unistd`

 - `fileSynchronise` (aka `fsync(2)`), and
 - `fileSynchroniseDataOnly` (aka `fdatasync(2)`)

This is based on part of #7 and has been heavily refactored from its
original patch submission by Ricardo Catalinas Jiménez.

This also bumps version to 2.7.1.0 as a minor version bump is now needed.

Signed-off-by: Herbert Valerio Riedel's avatarHerbert Valerio Riedel <hvr@gnu.org>
parent 256b1918
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE NondecreasingIndentation #-} {-# LANGUAGE NondecreasingIndentation #-}
#ifdef __GLASGOW_HASKELL__ #ifdef __GLASGOW_HASKELL__
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE Trustworthy #-}
...@@ -27,6 +28,10 @@ module System.Posix.Unistd ( ...@@ -27,6 +28,10 @@ module System.Posix.Unistd (
-- * Sleeping -- * Sleeping
sleep, usleep, nanosleep, sleep, usleep, nanosleep,
-- * File synchronisation
fileSynchronise,
fileSynchroniseDataOnly,
{- {-
ToDo from unistd.h: ToDo from unistd.h:
confstr, confstr,
...@@ -55,8 +60,14 @@ import Foreign.C.Error ...@@ -55,8 +60,14 @@ import Foreign.C.Error
import Foreign.C.String ( peekCString ) import Foreign.C.String ( peekCString )
import Foreign.C.Types import Foreign.C.Types
import Foreign import Foreign
import System.Posix.Types
import System.Posix.Internals import System.Posix.Internals
#if !(HAVE_FSYNC && HAVE_FDATASYNC)
import System.IO.Error ( ioeSetLocation )
import GHC.IO.Exception ( unsupportedOperation )
#endif
-- ----------------------------------------------------------------------------- -- -----------------------------------------------------------------------------
-- System environment (uname()) -- System environment (uname())
...@@ -206,3 +217,44 @@ sysconf n = do ...@@ -206,3 +217,44 @@ sysconf n = do
foreign import ccall unsafe "sysconf" foreign import ccall unsafe "sysconf"
c_sysconf :: CInt -> IO CLong c_sysconf :: CInt -> IO CLong
-- -----------------------------------------------------------------------------
-- File synchronization
-- | Performs @fsync(2)@ operation on file-descriptor.
--
-- Throws 'IOError' (\"unsupported operation\") if platform does not
-- provide @fsync(2)@ (use @#if HAVE_FSYNC@ CPP guard to
-- detect availability).
fileSynchronise :: Fd -> IO ()
#if HAVE_FSYNC
fileSynchronise fd = do
throwErrnoIfMinus1_ "fileSynchronise" (c_fsync fd)
foreign import capi safe "unistd.h fsync"
c_fsync :: Fd -> IO CInt
#else
{-# WARNING fileSynchronise
"operation will throw exception (CPP guard: @#if HAVE_FSYNC@)" #-}
fileSynchronise _ = ioError (ioeSetLocation unsupportedOperation
"fileSynchronise")
#endif
-- | Performs @fdatasync(2)@ operation on file-descriptor.
--
-- Throws 'IOError' (\"unsupported operation\") if platform does not
-- provide @fdatasync(2)@ (use @#if HAVE_FDATASYNC@ CPP guard to
-- detect availability).
fileSynchroniseDataOnly :: Fd -> IO ()
#if HAVE_FDATASYNC
fileSynchroniseDataOnly fd = do
throwErrnoIfMinus1_ "fileSynchroniseDataOnly" (c_fdatasync fd)
foreign import capi safe "unistd.h fdatasync"
c_fdatasync :: Fd -> IO CInt
#else
{-# WARNING fileSynchroniseDataOnly
"operation will throw exception (CPP guard: @#if HAVE_FDATASYNC@)" #-}
fileSynchroniseDataOnly _ = ioError (ioeSetLocation unsupportedOperation
"fileSynchroniseDataOnly")
#endif
# Changelog for [`unix` package](http://hackage.haskell.org/package/unix) # Changelog for [`unix` package](http://hackage.haskell.org/package/unix)
## 2.7.0.2 *TBA* ## 2.7.1.0 *Dec 2014*
* Add support for `base-4.8.0.0` * Add support for `base-4.8.0.0`
* Tighten `SafeHaskell` bounds for GHC 7.10+ * Tighten `SafeHaskell` bounds for GHC 7.10+
...@@ -17,6 +17,10 @@ ...@@ -17,6 +17,10 @@
* `executeFile`: Fix `ENOTDIR` error for entries with non-directory * `executeFile`: Fix `ENOTDIR` error for entries with non-directory
components in `PATH` (and instead skip over non-directory `PATH`-elements) components in `PATH` (and instead skip over non-directory `PATH`-elements)
* New functions in `System.Posix.Unistd`:
- `fileSynchronise` (aka `fsync(2)`), and
- `fileSynchroniseDataOnly` (aka `fdatasync(2)`)
## 2.7.0.1 *Mar 2014* ## 2.7.0.1 *Mar 2014*
* Bundled with GHC 7.8.1 * Bundled with GHC 7.8.1
......
...@@ -67,6 +67,9 @@ AC_CHECK_FUNCS([lutimes futimes]) ...@@ -67,6 +67,9 @@ AC_CHECK_FUNCS([lutimes futimes])
# Additional temp functions # Additional temp functions
AC_CHECK_FUNCS([mkstemps mkdtemp]) AC_CHECK_FUNCS([mkstemps mkdtemp])
# Functions for file synchronization and allocation control
AC_CHECK_FUNCS([fsync fdatasync])
# Avoid adding rt if absent or unneeded # Avoid adding rt if absent or unneeded
# shm_open needs -lrt on linux # shm_open needs -lrt on linux
AC_SEARCH_LIBS(shm_open, rt, [AC_CHECK_FUNCS([shm_open shm_unlink])]) AC_SEARCH_LIBS(shm_open, rt, [AC_CHECK_FUNCS([shm_open shm_unlink])])
......
name: unix name: unix
version: 2.7.0.2 version: 2.7.1.0
-- NOTE: Don't forget to update ./changelog.md -- NOTE: Don't forget to update ./changelog.md
license: BSD3 license: BSD3
license-file: LICENSE license-file: LICENSE
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment