Copyright | (c) The University of Glasgow 2008 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Buffers used in the IO system
Synopsis
- data Buffer e = Buffer {}
- data BufferState
- type CharBuffer = Buffer Char
- type CharBufElem = Char
- newByteBuffer :: Int -> BufferState -> IO (Buffer Word8)
- newCharBuffer :: Int -> BufferState -> IO CharBuffer
- newBuffer :: Int -> Int -> BufferState -> IO (Buffer e)
- emptyBuffer :: RawBuffer e -> Int -> BufferState -> Buffer e
- bufferRemove :: Int -> Buffer e -> Buffer e
- bufferAdd :: Int -> Buffer e -> Buffer e
- slideContents :: Buffer Word8 -> IO (Buffer Word8)
- bufferAdjustL :: Int -> Buffer e -> Buffer e
- bufferAddOffset :: Int -> Buffer e -> Buffer e
- bufferAdjustOffset :: Word64 -> Buffer e -> Buffer e
- isEmptyBuffer :: Buffer e -> Bool
- isFullBuffer :: Buffer e -> Bool
- isFullCharBuffer :: Buffer e -> Bool
- isWriteBuffer :: Buffer e -> Bool
- bufferElems :: Buffer e -> Int
- bufferAvailable :: Buffer e -> Int
- bufferOffset :: Buffer e -> Word64
- summaryBuffer :: Buffer a -> String
- withBuffer :: Buffer e -> (Ptr e -> IO a) -> IO a
- withRawBuffer :: RawBuffer e -> (Ptr e -> IO a) -> IO a
- checkBuffer :: Buffer a -> IO ()
- type RawBuffer e = ForeignPtr e
- readWord8Buf :: RawBuffer Word8 -> Int -> IO Word8
- writeWord8Buf :: RawBuffer Word8 -> Int -> Word8 -> IO ()
- type RawCharBuffer = RawBuffer CharBufElem
- peekCharBuf :: RawCharBuffer -> Int -> IO Char
- readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int)
- writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int
- readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int)
- writeCharBufPtr :: Ptr CharBufElem -> Int -> Char -> IO Int
- charSize :: Int
Buffers of any element
A mutable array of bytes that can be passed to foreign functions.
The buffer is represented by a record, where the record contains the raw buffer and the start/end points of the filled portion. The buffer contents itself is mutable, but the rest of the record is immutable. This is a slightly odd mix, but it turns out to be quite practical: by making all the buffer metadata immutable, we can have operations on buffer metadata outside of the IO monad.
The "live" elements of the buffer are those between the bufL
and
bufR
offsets. In an empty buffer, bufL
is equal to bufR
, but
they might not be zero: for example, the buffer might correspond to
a memory-mapped file and in which case bufL
will point to the
next location to be written, which is not necessarily the beginning
of the file.
On Posix systems the I/O manager has an implicit reliance on doing a file read moving the file pointer. However on Windows async operations the kernel object representing a file does not use the file pointer offset. Logically this makes sense since operations can be performed in any arbitrary order. OVERLAPPED operations don't respect the file pointer offset as their intention is to support arbitrary async reads to anywhere at a much lower level. As such we should explicitly keep track of the file offsets of the target in the buffer. Any operation to seek should also update this entry.
In order to keep us sane we try to uphold the invariant that any function being passed a Handle is responsible for updating the handles offset unless other behaviour is documented.
data BufferState Source #
Instances
Eq BufferState Source # | Since: base-4.2.0.0 |
Defined in GHC.IO.Buffer (==) :: BufferState -> BufferState -> Bool Source # (/=) :: BufferState -> BufferState -> Bool Source # |
type CharBuffer = Buffer Char Source #
type CharBufElem = Char Source #
Creation
newByteBuffer :: Int -> BufferState -> IO (Buffer Word8) Source #
newCharBuffer :: Int -> BufferState -> IO CharBuffer Source #
emptyBuffer :: RawBuffer e -> Int -> BufferState -> Buffer e Source #
Insertion/removal
slideContents :: Buffer Word8 -> IO (Buffer Word8) Source #
slides the contents of the buffer to the beginning
Inspecting
isEmptyBuffer :: Buffer e -> Bool Source #
isFullBuffer :: Buffer e -> Bool Source #
isFullCharBuffer :: Buffer e -> Bool Source #
isWriteBuffer :: Buffer e -> Bool Source #
bufferElems :: Buffer e -> Int Source #
bufferAvailable :: Buffer e -> Int Source #
bufferOffset :: Buffer e -> Word64 Source #
summaryBuffer :: Buffer a -> String Source #
Operating on the raw buffer as a Ptr
Assertions
checkBuffer :: Buffer a -> IO () Source #
Raw buffers
type RawBuffer e = ForeignPtr e Source #
type RawCharBuffer = RawBuffer CharBufElem Source #
peekCharBuf :: RawCharBuffer -> Int -> IO Char Source #
readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) Source #
writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int Source #
readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) Source #
writeCharBufPtr :: Ptr CharBufElem -> Int -> Char -> IO Int Source #