diff --git a/System/Posix/Unistd.hsc b/System/Posix/Unistd.hsc
index 0a13d6d598aa8d1fe33d17275740bbf0e3a6880f..afb8c08636475c81b4e52f32a318f055a613bad4 100644
--- a/System/Posix/Unistd.hsc
+++ b/System/Posix/Unistd.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
 {-# LANGUAGE NondecreasingIndentation #-}
 #ifdef __GLASGOW_HASKELL__
 {-# LANGUAGE Trustworthy #-}
@@ -27,6 +28,10 @@ module System.Posix.Unistd (
     -- * Sleeping
     sleep, usleep, nanosleep,
 
+    -- * File synchronisation
+    fileSynchronise,
+    fileSynchroniseDataOnly,
+
   {-
     ToDo from unistd.h:
       confstr,
@@ -55,8 +60,14 @@ import Foreign.C.Error
 import Foreign.C.String ( peekCString )
 import Foreign.C.Types
 import Foreign
+import System.Posix.Types
 import System.Posix.Internals
 
+#if !(HAVE_FSYNC && HAVE_FDATASYNC)
+import System.IO.Error ( ioeSetLocation )
+import GHC.IO.Exception ( unsupportedOperation )
+#endif
+
 -- -----------------------------------------------------------------------------
 -- System environment (uname())
 
@@ -206,3 +217,44 @@ sysconf n = do
 
 foreign import ccall unsafe "sysconf"
   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
diff --git a/changelog.md b/changelog.md
index b7dafcd4e95844a335a05d2a39115a9282edfba6..1be0f35bd1f8b7e2fa0389900fc8e26168605617 100644
--- a/changelog.md
+++ b/changelog.md
@@ -1,6 +1,6 @@
 # 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`
   * Tighten `SafeHaskell` bounds for GHC 7.10+
@@ -17,6 +17,10 @@
   * `executeFile`: Fix `ENOTDIR` error for entries with non-directory
     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*
 
   * Bundled with GHC 7.8.1
diff --git a/configure.ac b/configure.ac
index cf5a1fd2a7ab57601e81b3d4c65e8d7e621fd2ed..94d9d777b06bb2532b923aa555e2396baa5d41b7 100644
--- a/configure.ac
+++ b/configure.ac
@@ -67,6 +67,9 @@ AC_CHECK_FUNCS([lutimes futimes])
 # Additional temp functions
 AC_CHECK_FUNCS([mkstemps mkdtemp])
 
+# Functions for file synchronization and allocation control
+AC_CHECK_FUNCS([fsync fdatasync])
+
 # Avoid adding rt if absent or unneeded
 # shm_open needs -lrt on linux
 AC_SEARCH_LIBS(shm_open, rt, [AC_CHECK_FUNCS([shm_open shm_unlink])])
diff --git a/unix.cabal b/unix.cabal
index 69470ba985e2af25e1821ff477656e519125360a..7bcf0d9a8972859c707df5f1562da3b6b72eb4c1 100644
--- a/unix.cabal
+++ b/unix.cabal
@@ -1,5 +1,5 @@
 name:           unix
-version:        2.7.0.2
+version:        2.7.1.0
 -- NOTE: Don't forget to update ./changelog.md
 license:        BSD3
 license-file:   LICENSE