{-# LINE 1 "libraries/unix/System/Posix/IO.hsc" #-}
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.IO
-- Copyright   :  (c) The University of Glasgow 2002
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  non-portable (requires POSIX)
--
-- POSIX IO support.  These types and functions correspond to the unix
-- functions open(2), close(2), etc.  For more portable functions
-- which are more like fopen(3) and friends from stdio.h, see
-- "System.IO".
--
-----------------------------------------------------------------------------



module System.Posix.IO (
    -- * Input \/ Output

    -- ** Standard file descriptors
    stdInput, stdOutput, stdError,

    -- ** Opening and closing files
    OpenMode(..),
    OpenFileFlags(..), defaultFileFlags,
    openFd, openFdAt, createFile, createFileAt,
    closeFd,

    -- ** Reading\/writing data
    -- |Programmers using the 'fdRead' and 'fdWrite' API should be aware that
    -- EAGAIN exceptions may occur for non-blocking IO!

    fdRead, fdWrite,
    fdReadBuf, fdWriteBuf,

    -- ** Seeking
    fdSeek,

    -- ** File options
    FdOption(..),
    queryFdOption,
    setFdOption,

    -- ** Locking
    FileLock,
    LockRequest(..),
    getLock,  setLock,
    waitToSetLock,

    -- ** Pipes
    createPipe,

    -- ** Duplicating file descriptors
    dup, dupTo,

    -- ** Converting file descriptors to\/from Handles
    handleToFd,
    fdToHandle,

  ) where

import Foreign ( allocaBytes, castPtr )
import Foreign.C ( peekCStringLen, withCStringLen )

import GHC.IO.Exception ( IOErrorType(EOF) )

import System.IO.Error ( ioeSetErrorString, mkIOError )

import System.Posix.Types
import System.Posix.Error
import System.Posix.IO.Common
import System.Posix.Internals ( withFilePath )

-- |Open and optionally create this file.  See 'System.Posix.Files'
-- for information on how to use the 'FileMode' type.
openFd :: FilePath
       -> OpenMode
       -> OpenFileFlags
       -> IO Fd
openFd :: FilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFd = Maybe Fd -> FilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFdAt Maybe Fd
forall a. Maybe a
Nothing

-- | Open a file relative to an optional directory file descriptor.
--
-- Directory file descriptors can be used to avoid some race conditions when
-- navigating changing directory trees, or to retain access to a portion of the
-- directory tree that would otherwise become inaccessible after dropping
-- privileges.
openFdAt :: Maybe Fd -- ^ Optional directory file descriptor
         -> FilePath -- ^ Pathname to open
         -> OpenMode -- ^ Read-only, read-write or write-only
         -> OpenFileFlags -- ^ Append, exclusive, truncate, etc.
         -> IO Fd
openFdAt :: Maybe Fd -> FilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFdAt Maybe Fd
fdMay FilePath
name OpenMode
how OpenFileFlags
flags =
  FilePath -> (CString -> IO Fd) -> IO Fd
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
name ((CString -> IO Fd) -> IO Fd) -> (CString -> IO Fd) -> IO Fd
forall a b. (a -> b) -> a -> b
$ \CString
str ->
    FilePath -> FilePath -> IO Fd -> IO Fd
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO a
throwErrnoPathIfMinus1Retry FilePath
"openFdAt" FilePath
name (IO Fd -> IO Fd) -> IO Fd -> IO Fd
forall a b. (a -> b) -> a -> b
$
      Maybe Fd -> CString -> OpenMode -> OpenFileFlags -> IO Fd
openat_ Maybe Fd
fdMay CString
str OpenMode
how OpenFileFlags
flags

-- |Create and open this file in WriteOnly mode.  A special case of
-- 'openFd'.  See 'System.Posix.Files' for information on how to use
-- the 'FileMode' type.
createFile :: FilePath -> FileMode -> IO Fd
createFile :: FilePath -> FileMode -> IO Fd
createFile = Maybe Fd -> FilePath -> FileMode -> IO Fd
createFileAt Maybe Fd
forall a. Maybe a
Nothing

-- | Create and open a file for write-only, with default flags,
-- relative an optional directory file-descriptor.
--
-- Directory file descriptors can be used to avoid some race conditions when
-- navigating changing directory trees, or to retain access to a portion of the
-- directory tree that would otherwise become inaccessible after dropping
-- privileges.
createFileAt :: Maybe Fd -- ^ Optional directory file descriptor
             -> FilePath -- ^ Pathname to create
             -> FileMode -- ^ File permission bits (before umask)
             -> IO Fd
createFileAt :: Maybe Fd -> FilePath -> FileMode -> IO Fd
createFileAt Maybe Fd
fdMay FilePath
name FileMode
mode
  = Maybe Fd -> FilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFdAt Maybe Fd
fdMay FilePath
name OpenMode
WriteOnly OpenFileFlags
defaultFileFlags{ trunc=True, creat=(Just mode) }

{-# DEPRECATED fdRead "This function is scheduled to be dropped in favor of 'System.Posix.IO.ByteString.fdRead', because decoding e.g. UTF-8 streams partially is unsafe." #-} -- deprecated in 2.8.0.0
-- | Read data from an 'Fd' and convert it to a 'String' using the locale encoding.
-- Throws an exception if this is an invalid descriptor, or EOF has been
-- reached.
fdRead :: Fd
       -> ByteCount -- ^How many bytes to read
       -> IO (String, ByteCount) -- ^The bytes read, how many bytes were read.
fdRead :: Fd -> ByteCount -> IO (FilePath, ByteCount)
fdRead Fd
_fd ByteCount
0 = (FilePath, ByteCount) -> IO (FilePath, ByteCount)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
"", ByteCount
0)
fdRead Fd
fd ByteCount
nbytes =
  Int
-> (Ptr Word8 -> IO (FilePath, ByteCount))
-> IO (FilePath, ByteCount)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (ByteCount -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ByteCount
nbytes) ((Ptr Word8 -> IO (FilePath, ByteCount))
 -> IO (FilePath, ByteCount))
-> (Ptr Word8 -> IO (FilePath, ByteCount))
-> IO (FilePath, ByteCount)
forall a b. (a -> b) -> a -> b
$ \ Ptr Word8
buf -> do
  rc <- Fd -> Ptr Word8 -> ByteCount -> IO ByteCount
fdReadBuf Fd
fd Ptr Word8
buf ByteCount
nbytes
  case rc of
    ByteCount
0 -> IOError -> IO (FilePath, ByteCount)
forall a. IOError -> IO a
ioError (IOError -> FilePath -> IOError
ioeSetErrorString (IOErrorType
-> FilePath -> Maybe Handle -> Maybe FilePath -> IOError
mkIOError IOErrorType
EOF FilePath
"fdRead" Maybe Handle
forall a. Maybe a
Nothing Maybe FilePath
forall a. Maybe a
Nothing) FilePath
"EOF")
    ByteCount
n -> do
      s <- CStringLen -> IO FilePath
peekCStringLen (Ptr Word8 -> CString
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
buf, ByteCount -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ByteCount
n)
      return (s, n)

-- | Write a 'String' to an 'Fd' using the locale encoding.
fdWrite :: Fd -> String -> IO ByteCount
fdWrite :: Fd -> FilePath -> IO ByteCount
fdWrite Fd
fd FilePath
str =
  FilePath -> (CStringLen -> IO ByteCount) -> IO ByteCount
forall a. FilePath -> (CStringLen -> IO a) -> IO a
withCStringLen FilePath
str ((CStringLen -> IO ByteCount) -> IO ByteCount)
-> (CStringLen -> IO ByteCount) -> IO ByteCount
forall a b. (a -> b) -> a -> b
$ \ (CString
buf,Int
len) ->
    Fd -> Ptr Word8 -> ByteCount -> IO ByteCount
fdWriteBuf Fd
fd (CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
buf) (Int -> ByteCount
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)