{-# LINE 1 "libraries/unix/System/Posix/Fcntl.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- 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
--
-- @since 2.7.1.0
-----------------------------------------------------------------------------



module System.Posix.Fcntl (
    -- * File allocation
    Advice(..), fileAdvise,
    fileAllocate,
  ) where


{-# LINE 29 "libraries/unix/System/Posix/Fcntl.hsc" #-}
import System.Posix.Types


{-# LINE 32 "libraries/unix/System/Posix/Fcntl.hsc" #-}
import System.IO.Error ( ioeSetLocation )
import GHC.IO.Exception ( unsupportedOperation )

{-# LINE 35 "libraries/unix/System/Posix/Fcntl.hsc" #-}

-- -----------------------------------------------------------------------------
-- File control

-- | Advice parameter for 'fileAdvise' operation.
--
-- For more details, see documentation of @posix_fadvise(2)@.
--
-- @since 2.7.1.0
data Advice
  = AdviceNormal
  | AdviceRandom
  | AdviceSequential
  | AdviceWillNeed
  | AdviceDontNeed
  | AdviceNoReuse
  deriving Advice -> Advice -> Bool
(Advice -> Advice -> Bool)
-> (Advice -> Advice -> Bool) -> Eq Advice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Advice -> Advice -> Bool
== :: Advice -> Advice -> Bool
$c/= :: Advice -> Advice -> Bool
/= :: Advice -> Advice -> Bool
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 ()

{-# LINE 77 "libraries/unix/System/Posix/Fcntl.hsc" #-}
fileAdvise :: Fd -> FileOffset -> FileOffset -> Advice -> IO ()
fileAdvise Fd
_ FileOffset
_ FileOffset
_ Advice
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{-# LINE 79 "libraries/unix/System/Posix/Fcntl.hsc" #-}

-- | 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 ()

{-# LINE 99 "libraries/unix/System/Posix/Fcntl.hsc" #-}
{-# WARNING fileAllocate
    "operation will throw 'IOError' \"unsupported operation\" (CPP guard: @#if HAVE_POSIX_FALLOCATE@)" #-}
fileAllocate :: Fd -> FileOffset -> FileOffset -> IO ()
fileAllocate Fd
_ FileOffset
_ FileOffset
_ = IOError -> IO ()
forall a. IOError -> IO a
ioError (IOError -> String -> IOError
ioeSetLocation IOError
unsupportedOperation
                              String
"fileAllocate")

{-# LINE 104 "libraries/unix/System/Posix/Fcntl.hsc" #-}