| Copyright | 2010--2022 wren romano | 
|---|---|
| License | BSD-3-Clause | 
| Maintainer | [email protected] | 
| Stability | experimental | 
| Portability | non-portable (POSIX.1, XPG4.2; hsc2hs, FFI) | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
System.Posix.IO.ByteString.Ext
Description
Provides a strict-ByteString file-descriptor based I/O
 API wrapping the standard C implementations of the functions
 specified by the ISO/IEC 9945-1:1990 (``POSIX.1'') and X/Open
 Portability Guide Issue 4, Version 2 (``XPG4.2'') specifications.
The API was originally designed loosely after the String based
 API in System.Posix.IO, but significantly extending that API.
 The `unix-2.8.0.0` package added a subset of our original API
 in System.Posix.IO.ByteString, so as of version 0.4.0 this
 module has been renamed in order to avoid conflicts.
Synopsis
- fdRead :: Fd -> ByteCount -> IO ByteString
- fdReadBuf :: Fd -> Ptr Word8 -> ByteCount -> IO ByteCount
- tryFdReadBuf :: Fd -> Ptr Word8 -> ByteCount -> IO (Either Errno ByteCount)
- fdReads :: (ByteCount -> a -> Maybe a) -> a -> Fd -> ByteCount -> IO ByteString
- fdReadvBuf :: Fd -> Ptr CIovec -> Int -> IO ByteCount
- tryFdReadvBuf :: Fd -> Ptr CIovec -> Int -> IO (Either Errno ByteCount)
- fdPread :: Fd -> ByteCount -> FileOffset -> IO ByteString
- fdPreadBuf :: Fd -> Ptr Word8 -> ByteCount -> FileOffset -> IO ByteCount
- tryFdPreadBuf :: Fd -> Ptr Word8 -> ByteCount -> FileOffset -> IO (Either Errno ByteCount)
- fdPreads :: (ByteCount -> a -> Maybe a) -> a -> Fd -> ByteCount -> FileOffset -> IO ByteString
- fdWrite :: Fd -> ByteString -> IO ByteCount
- fdWriteBuf :: Fd -> Ptr Word8 -> ByteCount -> IO ByteCount
- tryFdWriteBuf :: Fd -> Ptr Word8 -> ByteCount -> IO (Either Errno ByteCount)
- fdWrites :: Fd -> [ByteString] -> IO (ByteCount, ByteCount, [ByteString])
- fdWritev :: Fd -> [ByteString] -> IO ByteCount
- fdWritevBuf :: Fd -> Ptr CIovec -> Int -> IO ByteCount
- tryFdWritevBuf :: Fd -> Ptr CIovec -> Int -> IO (Either Errno ByteCount)
- fdPwrite :: Fd -> ByteString -> FileOffset -> IO ByteCount
- fdPwriteBuf :: Fd -> Ptr Word8 -> ByteCount -> FileOffset -> IO ByteCount
- tryFdPwriteBuf :: Fd -> Ptr Word8 -> ByteCount -> FileOffset -> IO (Either Errno ByteCount)
- fdSeek :: Fd -> SeekMode -> FileOffset -> IO FileOffset
- tryFdSeek :: Fd -> SeekMode -> FileOffset -> IO (Either Errno FileOffset)
I/O with file descriptors
Reading
The POSIX.1 read(2) syscall
Arguments
| :: Fd | |
| -> ByteCount | How many bytes to try to read. | 
| -> IO ByteString | The bytes read. | 
Read data from an Fd and convert it to a ByteString.
 Throws an exception if this is an invalid descriptor, or EOF has
 been reached. This is essentially equivalent to fdReadBuf; the
 differences are that we allocate a byte buffer for the ByteString,
 and that we detect EOF and throw an IOError.
Arguments
| :: Fd | |
| -> Ptr Word8 | Memory in which to put the data. | 
| -> ByteCount | How many bytes to try to read. | 
| -> IO ByteCount | How many bytes were actually read (zero for EOF). | 
Read data from an Fd into memory. This is exactly equivalent
 to the POSIX.1 read(2) system call, except that we return 0
 bytes read if the ByteCount argument is less than or equal to
 zero (instead of throwing an errno exception).
N.B., this behavior is different from the version in unix-2.4.2.0
 which only checks for equality to zero. If there are any errors,
 then they are thrown as IOError exceptions.
Since: 0.3.0
Arguments
| :: (ByteCount -> a -> Maybe a) | A stateful predicate for retrying. | 
| -> a | An initial state for the predicate. | 
| -> Fd | |
| -> ByteCount | How many bytes to try to read. | 
| -> IO ByteString | The bytes read. | 
Read data from an Fd and convert it to a ByteString.
 Throws an exception if this is an invalid descriptor, or EOF has
 been reached.
This version takes a kind of stateful predicate for whether and
 how long to keep retrying. Assume the function is called as
 fdReads f z0 fd n0. We will attempt to read n0 bytes from
 fd. If we fall short, then we will call f len z where len
 is the total number of bytes read so far and z is the current
 state (initially z0). If it returns Nothing then we will
 give up and return the current buffer; otherwise we will retry
 with the new state, continuing from where we left off.
For example, to define a function that tries up to n times,
 we can use:
fdReadUptoNTimes :: Int -> Fd -> ByteCount -> IO ByteString
fdReadUptoNTimes n0 = fdReads retry n0
    where
    retry _ 0 = Nothing
    retry _ n = Just $! n-1The benefit of doing this instead of the naive approach of calling
 fdRead repeatedly is that we only need to allocate one byte
 buffer, and trim it once at the end--- whereas the naive approach
 would allocate a buffer, trim it to the number of bytes read,
 and then concatenate with the previous one (another allocation,
 plus copying everything over) for each time around the loop.
Since: 0.2.1
The XPG4.2 readv(2) syscall
Arguments
| :: Fd | |
| -> Ptr CIovec | A C-style array of buffers to fill. | 
| -> Int | How many buffers there are. | 
| -> IO ByteCount | How many bytes were actually read (zero for EOF). | 
Read data from an Fd and scatter it into memory. This is
 exactly equivalent to the XPG4.2 readv(2) system call, except
 that we return 0 bytes read if the Int argument is less than
 or equal to zero (instead of throwing an eINVAL exception).
 If there are any errors, then they are thrown as IOError
 exceptions.
TODO: better documentation.
Since: 0.3.0
Arguments
| :: Fd | |
| -> Ptr CIovec | A C-style array of buffers to fill. | 
| -> Int | How many buffers there are. | 
| -> IO (Either Errno ByteCount) | How many bytes were actually read (zero for EOF). | 
Read data from an Fd and scatter it into memory. This is a
 variation of fdReadvBuf which returns errors with an Either
 instead of throwing exceptions.
Since: 0.3.3
The XPG4.2 pread(2) syscall
Arguments
| :: Fd | |
| -> ByteCount | How many bytes to try to read. | 
| -> FileOffset | Where to read the data from. | 
| -> IO ByteString | The bytes read. | 
Read data from a specified position in the Fd and convert
 it to a ByteString, without altering the position stored
 in the Fd. Throws an exception if this is an invalid descriptor,
 or EOF has been reached. This is essentially equivalent to
 fdPreadBuf; the differences are that we allocate a byte buffer
 for the ByteString, and that we detect EOF and throw an
 IOError.
Since: 0.3.0
Arguments
| :: Fd | |
| -> Ptr Word8 | Memory in which to put the data. | 
| -> ByteCount | How many bytes to try to read. | 
| -> FileOffset | Where to read the data from. | 
| -> IO ByteCount | How many bytes were actually read (zero for EOF). | 
Read data from a specified position in the Fd into memory,
 without altering the position stored in the Fd. This is exactly
 equivalent to the XPG4.2 pread(2) system call, except that we
 return 0 bytes read if the Int argument is less than or equal
 to zero (instead of throwing an errno exception). If there are
 any errors, then they are thrown as IOError exceptions.
Since: 0.3.0
Arguments
| :: Fd | |
| -> Ptr Word8 | Memory in which to put the data. | 
| -> ByteCount | How many bytes to try to read. | 
| -> FileOffset | Where to read the data from. | 
| -> IO (Either Errno ByteCount) | How many bytes were actually read (zero for EOF). | 
Read data from a specified position in the Fd into memory,
 without altering the position stored in the Fd. This is a
 variation of fdPreadBuf which returns errors with an Either
 instead of throwing exceptions.
Since: 0.3.3
Arguments
| :: (ByteCount -> a -> Maybe a) | A stateful predicate for retrying. | 
| -> a | An initial state for the predicate. | 
| -> Fd | |
| -> ByteCount | How many bytes to try to read. | 
| -> FileOffset | Where to read the data from. | 
| -> IO ByteString | The bytes read. | 
Read data from a specified position in the Fd and convert
 it to a ByteString, without altering the position stored
 in the Fd. Throws an exception if this is an invalid descriptor,
 or EOF has been reached. This is a fdPreadBuf based version
 of fdReads; see those functions for more details.
Since: 0.3.1
Writing
The POSIX.1 write(2) syscall
Arguments
| :: Fd | |
| -> ByteString | The string to write. | 
| -> IO ByteCount | How many bytes were actually written. | 
Write a ByteString to an Fd. The return value is the
 total number of bytes actually written. This is exactly equivalent
 to fdWriteBuf; we just convert the ByteString into its
 underlying Ptr Word8 and ByteCount components for passing
 to fdWriteBuf.
Arguments
| :: Fd | |
| -> Ptr Word8 | Memory containing the data to write. | 
| -> ByteCount | How many bytes to try to write. | 
| -> IO ByteCount | How many bytes were actually written. | 
Write data from memory to an Fd. This is exactly equivalent
 to the POSIX.1 write(2) system call, except that we return 0
 bytes written if the ByteCount argument is less than or equal
 to zero (instead of throwing an errno exception). N.B., this
 behavior is different from the version in unix-2.4.2.0 which
 doesn't check the byte count. If there are any errors, then they
 are thrown as IOError exceptions.
Since: 0.3.0
Arguments
| :: Fd | |
| -> Ptr Word8 | Memory containing the data to write. | 
| -> ByteCount | How many bytes to try to write. | 
| -> IO (Either Errno ByteCount) | How many bytes were actually read (zero for EOF). | 
Write data from memory to an Fd. This is a variation of
 fdWriteBuf which returns errors with an Either instead of
 throwing exceptions.
Since: 0.3.3
Arguments
| :: Fd | |
| -> [ByteString] | The strings to write. | 
| -> IO (ByteCount, ByteCount, [ByteString]) | The total number of bytes written, the number of bytes written from the first of the remaining strings, the remaining (unwritten) strings. | 
Write a sequence of ByteStrings to an Fd. The return
 value is a triple of: the total number of bytes written, the
 number of bytes written from the first of the remaining strings,
 and the remaining (unwritten) strings. We return this triple
 instead of a pair adjusting the head of the remaining strings
 (i.e., removing the bytes already written) in case there is some
 semantic significance to the way the input is split into chunks.
This version consumes the list lazily and will call fdWrite
 once for each ByteString, thus making O(n) system calls.
 This laziness allows the early parts of the list to be garbage
 collected and prevents needing to hold the whole list of
 ByteStrings in memory at once. Compare against fdWritev.
The XPG4.2 writev(2) syscall
Arguments
| :: Fd | |
| -> [ByteString] | The strings to write. | 
| -> IO ByteCount | How many bytes were actually written. | 
Write a sequence of ByteStrings to an Fd. The return
 value is the total number of bytes written. Unfortunately the
 writev(2) system call does not provide enough information to
 return the triple that fdWrites does.
This version will force the spine of the list, converting each
 ByteString into an iovec (see CIovec), and then call
 fdWritevBuf. This means we only make one system call, which
 reduces the overhead of performing context switches. But it also
 means that we must store the whole list of ByteStrings in
 memory at once, and that we must perform some allocation and
 conversion. Compare against fdWrites.
Arguments
| :: Fd | |
| -> Ptr CIovec | A C-style array of buffers to write. | 
| -> Int | How many buffers there are. | 
| -> IO ByteCount | How many bytes were actually written. | 
Write data from memory to an Fd. This is exactly equivalent
 to the XPG4.2 writev(2) system call, except that we return 0
 bytes written if the Int argument is less than or equal to
 zero (instead of throwing an eINVAL exception). If there are
 any errors, then they are thrown as IOError exceptions.
TODO: better documentation.
Since: 0.3.0
Arguments
| :: Fd | |
| -> Ptr CIovec | A C-style array of buffers to write. | 
| -> Int | How many buffers there are. | 
| -> IO (Either Errno ByteCount) | How many bytes were actually read (zero for EOF). | 
Write data from memory to an Fd. This is a variation of
 fdWritevBuf which returns errors with an Either instead of
 throwing exceptions.
Since: 0.3.3
The XPG4.2 pwrite(2) syscall
Arguments
| :: Fd | |
| -> ByteString | The string to write. | 
| -> FileOffset | Where to write the data to. | 
| -> IO ByteCount | How many bytes were actually written. | 
Write data from memory to a specified position in the Fd,
 but without altering the position stored in the Fd. This is
 exactly equivalent to fdPwriteBuf; we just convert the
 ByteString into its underlying Ptr Word8 and ByteCount
 components for passing to fdPwriteBuf.
Since: 0.3.0
Arguments
| :: Fd | |
| -> Ptr Word8 | Memory containing the data to write. | 
| -> ByteCount | How many bytes to try to write. | 
| -> FileOffset | Where to write the data to. | 
| -> IO ByteCount | How many bytes were actually written. | 
Write data from memory to a specified position in the Fd,
 but without altering the position stored in the Fd. This is
 exactly equivalent to the XPG4.2 pwrite(2) system call, except
 that we return 0 bytes written if the ByteCount argument is
 less than or equal to zero (instead of throwing an errno exception).
 If there are any errors, then they are thrown as IOError
 exceptions.
Since: 0.3.0
Arguments
| :: Fd | |
| -> Ptr Word8 | Memory containing the data to write. | 
| -> ByteCount | How many bytes to try to write. | 
| -> FileOffset | Where to write the data to. | 
| -> IO (Either Errno ByteCount) | How many bytes were actually written. | 
Write data from memory to a specified position in the Fd,
 but without altering the position stored in the Fd. This is a
 variation of fdPwriteBuf which returns errors with an Either
 instead of throwing exceptions.
Since: 0.3.3
Seeking
These functions are not ByteString related, but are
 provided here for API completeness.
The POSIX.1 lseek(2) syscall
fdSeek :: Fd -> SeekMode -> FileOffset -> IO FileOffset Source #
Repositions the offset of the file descriptor according to the
 offset and the seeking mode. This is exactly equivalent to the
 POSIX.1 lseek(2) system call. If there are any errors, then
 they are thrown as IOError exceptions.
This is the same as fdSeek in unix-2.6.0.1,
 but provided here for consistency.
Since: 0.3.5