{-# LINE 1 "System/Posix/IO/ByteString.hsc" #-}{-# LANGUAGE Trustworthy #-}------------------------------------------------------------------------------- |-- Module : System.Posix.IO.ByteString-- 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".-------------------------------------------------------------------------------moduleSystem.Posix.IO.ByteString(-- * Input \/ Output-- ** Standard file descriptorsstdInput ,stdOutput ,stdError ,-- ** Opening and closing filesOpenMode (..),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 ,-- ** SeekingfdSeek ,-- ** File optionsFdOption (..),queryFdOption ,setFdOption ,-- ** LockingFileLock ,LockRequest (..),getLock ,setLock ,waitToSetLock ,-- ** PipescreatePipe ,-- ** Duplicating file descriptorsdup ,dupTo ,-- ** Converting file descriptors to\/from HandleshandleToFd ,fdToHandle ,)whereimportData.ByteString(ByteString,empty)importqualifiedData.ByteString.InternalasBIimportqualifiedData.ByteString.UnsafeasBUimportForeign(castPtr)importGHC.IO.Exception(IOErrorType(EOF))importSystem.IO.Error(ioeSetErrorString,mkIOError)importSystem.Posix.TypesimportSystem.Posix.IO.Common importSystem.Posix.ByteString.FilePath -- |Open and optionally create this file. See 'System.Posix.Files'-- for information on how to use the 'FileMode' type.openFd ::RawFilePath ->OpenMode ->OpenFileFlags ->IOFdopenFd :: RawFilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFd =Maybe Fd -> RawFilePath -> 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 ::MaybeFd-- ^ Optional directory file descriptor->RawFilePath -- ^ Pathname to open->OpenMode -- ^ Read-only, read-write or write-only->OpenFileFlags -- ^ Append, exclusive, truncate, etc.->IOFdopenFdAt :: Maybe Fd -> RawFilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFdAt Maybe Fd
fdMay RawFilePath
name OpenMode
how OpenFileFlags
flags =RawFilePath -> (CString -> IO Fd) -> IO Fd
forall a. RawFilePath -> (CString -> IO a) -> IO a
withFilePath RawFilePath
name ((CString -> IO Fd) -> IO Fd) -> (CString -> IO Fd) -> IO Fd
forall a b. (a -> b) -> a -> b
$\CString
str ->String -> RawFilePath -> IO Fd -> IO Fd
forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO a
throwErrnoPathIfMinus1Retry String
"openFdAt"RawFilePath
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 ::RawFilePath ->FileMode->IOFdcreateFile :: RawFilePath -> FileMode -> IO Fd
createFile =Maybe Fd -> RawFilePath -> 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 ::MaybeFd-- ^ Optional directory file descriptor->RawFilePath -- ^ Pathname to create->FileMode-- ^ File permission bits (before umask)->IOFdcreateFileAt :: Maybe Fd -> RawFilePath -> FileMode -> IO Fd
createFileAt Maybe Fd
fdMay RawFilePath
name FileMode
mode =Maybe Fd -> RawFilePath -> OpenMode -> OpenFileFlags -> IO Fd
openFdAt Maybe Fd
fdMay RawFilePath
name OpenMode
WriteOnly OpenFileFlags
defaultFileFlags {trunc =True,creat =(Justmode )}-- | Read data from an 'Fd' and return it as a 'ByteString'.-- Throws an exception if this is an invalid descriptor, or EOF has been-- reached.fdRead ::Fd->ByteCount-- ^How many bytes to read->IOByteString-- ^The bytes readfdRead :: Fd -> ByteCount -> IO RawFilePath
fdRead Fd
_fd ByteCount
0=RawFilePath -> IO RawFilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnRawFilePath
emptyfdRead Fd
fd ByteCount
nbytes =Int -> (Ptr Word8 -> IO Int) -> IO RawFilePath
BI.createUptoN(ByteCount -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralByteCount
nbytes )((Ptr Word8 -> IO Int) -> IO RawFilePath)
-> (Ptr Word8 -> IO Int) -> IO RawFilePath
forall a b. (a -> b) -> a -> b
$\Ptr Word8
buf ->doByteCount
rc <-Fd -> Ptr Word8 -> ByteCount -> IO ByteCount
fdReadBuf Fd
fd Ptr Word8
buf ByteCount
nbytes caseByteCount
rc ofByteCount
0->IOError -> IO Int
forall a. IOError -> IO a
ioError(IOError -> String -> IOError
ioeSetErrorString(IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOErrorIOErrorType
EOFString
"fdRead"Maybe Handle
forall a. Maybe a
NothingMaybe String
forall a. Maybe a
Nothing)String
"EOF")ByteCount
n ->Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(ByteCount -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralByteCount
n )-- | Write a 'ByteString' to an 'Fd'.fdWrite ::Fd->ByteString->IOByteCountfdWrite :: Fd -> RawFilePath -> IO ByteCount
fdWrite Fd
fd RawFilePath
bs =RawFilePath -> (CStringLen -> IO ByteCount) -> IO ByteCount
forall a. RawFilePath -> (CStringLen -> IO a) -> IO a
BU.unsafeUseAsCStringLenRawFilePath
bs ((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
castPtrCString
buf )(Int -> ByteCount
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
len )

AltStyle によって変換されたページ (->オリジナル) /