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

Wrap posix_fadvise(2) and posix_fallocate(2)


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

 - `fileAdvise` (aka `posix_fadvise(2)`), and
 - `fileAllocate` (aka `posix_fallocate(2)`)

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

Signed-off-by: Herbert Valerio Riedel's avatarHerbert Valerio Riedel <hvr@gnu.org>
parent cbe8af7a
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CApiFFI #-}
#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE Trustworthy #-}
#endif
-----------------------------------------------------------------------------
-- |
-- Module : System.Posix.Fcntl
-- Copyright : (c) The University of Glasgow 2014
-- License : BSD-style (see the file LICENSE)
--
-- Maintainer : libraries@haskell.org
-- Stability : provisional
-- Portability : non-portable (requires POSIX)
--
-- POSIX file control support
--
-----------------------------------------------------------------------------
#include "HsUnix.h"
module System.Posix.Fcntl (
-- * File allocation
Advice(..), fileAdvise,
fileAllocate,
) where
#if HAVE_POSIX_FALLOCATE || HAVE_POSIX_FADVISE
import Foreign.C
#endif
import System.Posix.Types
#if !HAVE_POSIX_FALLOCATE
import System.IO.Error ( ioeSetLocation )
import GHC.IO.Exception ( unsupportedOperation )
#endif
-- -----------------------------------------------------------------------------
-- File control
-- | Advice parameter for 'fileAdvise' operation.
--
-- For more details, see documentation of @posix_fadvise(2)@.
data Advice
= AdviceNormal
| AdviceRandom
| AdviceSequential
| AdviceWillNeed
| AdviceDontNeed
| AdviceNoReuse
deriving Eq
-- | Performs @posix_fadvise(2)@ operation on file-descriptor.
--
-- If platform does not provide @posix_fadvise(2)@ 'fileAdvise'
-- becomes a no-op.
--
-- (use @#if HAVE_POSIX_FADVISE@ CPP guard to detect availability)
--
-- /Since: 2.7.1.0/
fileAdvise :: Fd -> FileOffset -> FileOffset -> Advice -> IO ()
#if HAVE_POSIX_FADVISE
fileAdvise fd off len adv = do
throwErrnoIfMinus1_ "fileAdvise" (c_posix_fadvise (fromIntegral fd) (fromIntegral off) (fromIntegral len) (packAdvice adv))
foreign import capi safe "fcntl.h posix_fadvise"
c_posix_fadvise :: CInt -> COff -> COff -> CInt -> IO CInt
packAdvice :: Advice -> CInt
packAdvice AdviceNormal = (#const POSIX_FADV_NORMAL)
packAdvice AdviceRandom = (#const POSIX_FADV_RANDOM)
packAdvice AdviceSequential = (#const POSIX_FADV_SEQUENTIAL)
packAdvice AdviceWillNeed = (#const POSIX_FADV_WILLNEED)
packAdvice AdviceDontNeed = (#const POSIX_FADV_DONTNEED)
packAdvice AdviceNoReuse = (#const POSIX_FADV_NOREUSE)
#else
fileAdvise _ _ _ _ = return ()
#endif
-- | Performs @posix_fallocate(2)@ operation on file-descriptor.
--
-- Throws 'IOError' (\"unsupported operation\") if platform does not
-- provide @posix_fallocate(2)@.
--
-- (use @#if HAVE_POSIX_FALLOCATE@ CPP guard to detect availability).
--
-- /Since: 2.7.1.0/
fileAllocate :: Fd -> FileOffset -> FileOffset -> IO ()
#if HAVE_POSIX_FALLOCATE
fileAllocate fd off len = do
throwErrnoIfMinus1_ "fileAllocate" (c_posix_fallocate (fromIntegral fd) (fromIntegral off) (fromIntegral len))
foreign import capi safe "fcntl.h posix_fallocate"
c_posix_fallocate :: CInt -> COff -> COff -> IO CInt
#else
{-# WARNING fileAllocate
"operation will throw 'IOError' \"unsupported operation\" (CPP guard: @#if HAVE_POSIX_FALLOCATE@)" #-}
fileAllocate _ _ _ = ioError (ioeSetLocation unsupportedOperation
"fileAllocate")
#endif
...@@ -21,6 +21,10 @@ ...@@ -21,6 +21,10 @@
- `fileSynchronise` (aka `fsync(2)`), and - `fileSynchronise` (aka `fsync(2)`), and
- `fileSynchroniseDataOnly` (aka `fdatasync(2)`) - `fileSynchroniseDataOnly` (aka `fdatasync(2)`)
* New module `System.Posix.Fcntl` providing
- `fileAdvise` (aka `posix_fadvise(2)`), and
- `fileAllocate` (aka `posix_fallocate(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
......
...@@ -69,6 +69,7 @@ AC_CHECK_FUNCS([mkstemps mkdtemp]) ...@@ -69,6 +69,7 @@ AC_CHECK_FUNCS([mkstemps mkdtemp])
# Functions for file synchronization and allocation control # Functions for file synchronization and allocation control
AC_CHECK_FUNCS([fsync fdatasync]) AC_CHECK_FUNCS([fsync fdatasync])
AC_CHECK_FUNCS([posix_fadvise posix_fallocate])
# 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
......
...@@ -96,6 +96,8 @@ library ...@@ -96,6 +96,8 @@ library
System.Posix.Env System.Posix.Env
System.Posix.Env.ByteString System.Posix.Env.ByteString
System.Posix.Fcntl
System.Posix.Process System.Posix.Process
System.Posix.Process.Internals System.Posix.Process.Internals
System.Posix.Process.ByteString System.Posix.Process.ByteString
......
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