Copyright | (c) Dong Han 2017-2020 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides low level buffered IO interface, it's recommended to check higher level streaming interface Z.IO.BIO first as it provides more features.
Synopsis
- class Input i where
- class Output o where
- writeOutput :: HasCallStack => o -> Ptr Word8 -> Int -> IO ()
- data BufferedInput
- bufInput :: BufferedInput -> HasCallStack => Ptr Word8 -> Int -> IO Int
- newBufferedInput :: Input i => i -> IO BufferedInput
- newBufferedInput' :: Input i => Int -> i -> IO BufferedInput
- readBuffer :: HasCallStack => BufferedInput -> IO Bytes
- readBufferText :: HasCallStack => BufferedInput -> IO Text
- unReadBuffer :: HasCallStack => Bytes -> BufferedInput -> IO ()
- readParser :: HasCallStack => Parser a -> BufferedInput -> IO (Either ParseError a)
- readExactly :: HasCallStack => Int -> BufferedInput -> IO Bytes
- readToMagic :: HasCallStack => Word8 -> BufferedInput -> IO Bytes
- readLine :: HasCallStack => BufferedInput -> IO (Maybe Bytes)
- readAll :: HasCallStack => BufferedInput -> IO [Bytes]
- readAll' :: HasCallStack => BufferedInput -> IO Bytes
- data BufferedOutput
- bufOutput :: BufferedOutput -> HasCallStack => Ptr Word8 -> Int -> IO ()
- newBufferedOutput :: Output o => o -> IO BufferedOutput
- newBufferedOutput' :: Output o => Int -> o -> IO BufferedOutput
- writeBuffer :: HasCallStack => BufferedOutput -> Bytes -> IO ()
- writeBuilder :: HasCallStack => BufferedOutput -> Builder a -> IO ()
- flushBuffer :: HasCallStack => BufferedOutput -> IO ()
- data IncompleteInput = IncompleteInput CallStack
- defaultChunkSize :: Int
- smallChunkSize :: Int
- chunkOverhead :: Int
Input & Output device
Input device
readInput
should return 0 on EOF.
Output device
writeOutput
should not return until all data are written (may not
necessarily flushed to hardware, that should be done in device specific way).
writeOutput :: HasCallStack => o -> Ptr Word8 -> Int -> IO () Source #
Instances
Output StdStream Source # | |
Defined in Z.IO.StdStream | |
Output FilePtrT Source # | |
Defined in Z.IO.FileSystem.Threaded | |
Output File Source # | |
Defined in Z.IO.FileSystem.Threaded | |
Output FilePtr Source # | |
Defined in Z.IO.FileSystem | |
Output File Source # | |
Defined in Z.IO.FileSystem | |
Output UVStream Source # | |
Defined in Z.IO.UV.UVStream |
Buffered Input
data BufferedInput Source #
Input device with buffer, NOT THREAD SAFE!
- A
BufferedInput
should not be used in multiple threads, there's no locking mechanism to protect buffering state. - A
Input
device should only be used with a singleBufferedInput
, If multipleBufferedInput
s are opened on a sameInput
device, the behaviour is undefined.
bufInput :: BufferedInput -> HasCallStack => Ptr Word8 -> Int -> IO Int Source #
newBufferedInput :: Input i => i -> IO BufferedInput Source #
Open a new buffered input with defaultChunkSize
as buffer size.
:: Input i | |
=> Int | Input buffer size |
-> i | |
-> IO BufferedInput |
Open a new buffered input with given buffer size, e.g. defaultChunkSize
.
readBuffer :: HasCallStack => BufferedInput -> IO Bytes Source #
Request bytes chunk from BufferedInput
.
The buffering logic is quite simple:
If we have pushed back bytes, directly return it, otherwise we read using buffer size. If we read N bytes, and N is larger than half of the buffer size, then we freeze buffer and return, otherwise we copy buffer into result and reuse buffer afterward.
readBufferText :: HasCallStack => BufferedInput -> IO Text Source #
Request UTF8 Text
chunk from BufferedInput
.
The buffer size must be larger than 4 bytes to guarantee decoding progress. If there're
trailing bytes before EOF, IncompleteInput
are thrown.
unReadBuffer :: HasCallStack => Bytes -> BufferedInput -> IO () Source #
Push bytes back into buffer(if not empty).
readParser :: HasCallStack => Parser a -> BufferedInput -> IO (Either ParseError a) Source #
Read buffer and parse with Parser
.
This function will continuously draw data from input before parsing finish. Unconsumed bytes will be returned to buffer.
Either during parsing or before parsing, reach EOF will result in ParseError
.
readExactly :: HasCallStack => Int -> BufferedInput -> IO Bytes Source #
Read exactly N bytes.
If EOF reached before N bytes read, a IncompleteInput
will be thrown
readToMagic :: HasCallStack => Word8 -> BufferedInput -> IO Bytes Source #
Read until reach a magic bytes, return bytes(including the magic bytes).
Empty bytes indicate EOF. if EOF is reached before meet a magic byte, partial bytes are returned.
/----- readToMagic ----- \ /----- readToMagic -----\ ... +------------------+-------+-----------------+-------+ | ... | magic | ... | magic | ... +------------------+-------+-----------------+-------+
readLine :: HasCallStack => BufferedInput -> IO (Maybe Bytes) Source #
Read to a linefeed ('n' or 'rn'), return Bytes
before it.
Return bytes don't include linefeed, empty bytes indicate empty line, Nothing
indicate EOF.
If EOF is reached before meet a line feed, partial line is returned.
/--- readLine ---\ discarded /--- readLine ---\ discarded / ... +------------------+---------+------------------+---------+ | ... | \r\n/\n | ... | \r\n/\n | ... +------------------+---------+------------------+---------+
readAll :: HasCallStack => BufferedInput -> IO [Bytes] Source #
Read all chunks from a BufferedInput
until EOF.
This function will loop read until meet EOF(Input
device return empty
),
Useful for reading small file into memory.
readAll' :: HasCallStack => BufferedInput -> IO Bytes Source #
Read all chunks from a BufferedInput
, and concat chunks together.
This function will loop read until meet EOF(Input
device return empty
),
Useful for reading small file into memory.
Buffered Output
data BufferedOutput Source #
Output device with buffer, NOT THREAD SAFE!
- A
BufferedOutput
should not be used in multiple threads, there's no locking mechanism to protect buffering state. - A
Output
device should only be used with a singleBufferedOutput
, If multipleBufferedOutput
s are opened on a sameBufferedOutput
device, the output will be interleaved.
bufOutput :: BufferedOutput -> HasCallStack => Ptr Word8 -> Int -> IO () Source #
newBufferedOutput :: Output o => o -> IO BufferedOutput Source #
Open a new buffered output with defaultChunkSize
as buffer size.
:: Output o | |
=> Int | Output buffer size |
-> o | |
-> IO BufferedOutput |
Open a new buffered output with given buffer size, e.g. defaultChunkSize
.
writeBuffer :: HasCallStack => BufferedOutput -> Bytes -> IO () Source #
Write Bytes
into buffered handle.
- If buffer is empty and bytes are larger than half of buffer, directly write bytes, otherwise copy bytes to buffer.
- If buffer is not empty, then copy bytes to buffer if it can hold, otherwise write buffer first, then try again.
writeBuilder :: HasCallStack => BufferedOutput -> Builder a -> IO () Source #
flushBuffer :: HasCallStack => BufferedOutput -> IO () Source #
Flush the buffer into output device(if buffer is not empty).
Exceptions
data IncompleteInput Source #
Exceptions when read not enough input.
Note this exception is a sub-type of SomeIOException
.
Instances
Show IncompleteInput Source # | |
Defined in Z.IO.Buffered showsPrec :: Int -> IncompleteInput -> ShowS # show :: IncompleteInput -> String # showList :: [IncompleteInput] -> ShowS # | |
Exception IncompleteInput Source # | |
Defined in Z.IO.Buffered |
common buffer size
defaultChunkSize :: Int #
The chunk size used for I/O. Currently set to 16k - chunkOverhead
smallChunkSize :: Int #
The recommended chunk size. Currently set to 4k - chunkOverhead
.
chunkOverhead :: Int #
The memory management overhead. Currently this is tuned for GHC only.