| Copyright | (c) Dong Han 2017-2018 |
|---|---|
| License | BSD |
| Maintainer | winterland1989@gmail.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Z.IO.Buffered
Description
This module provide buffered IO interface.
Synopsis
- class Input i where
- class Output o where
- writeOutput :: HasCallStack => o -> Ptr Word8 -> Int -> IO ()
- data BufferedInput i
- newBufferedInput :: Int -> input -> IO (BufferedInput input)
- readBuffer :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes
- unReadBuffer :: (HasCallStack, Input i) => Bytes -> BufferedInput i -> IO ()
- readParser :: (HasCallStack, Input i) => Parser a -> BufferedInput i -> IO (Bytes, Either ParseError a)
- readExactly :: (HasCallStack, Input i) => Int -> BufferedInput i -> IO Bytes
- readToMagic :: (HasCallStack, Input i) => Word8 -> BufferedInput i -> IO Bytes
- readToMagic' :: (HasCallStack, Input i) => Word8 -> BufferedInput i -> IO Bytes
- readLine :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes
- readLine' :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes
- readAll :: (HasCallStack, Input i) => BufferedInput i -> IO [Bytes]
- readAll' :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes
- data BufferedOutput o
- newBufferedOutput :: Int -> output -> IO (BufferedOutput output)
- writeBuffer :: Output o => BufferedOutput o -> Bytes -> IO ()
- writeBuilder :: Output o => BufferedOutput o -> Builder a -> IO ()
- flushBuffer :: Output f => BufferedOutput f -> IO ()
- data ShortReadException = ShortReadException IOEInfo
- defaultChunkSize :: Int
- smallChunkSize :: 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).
Methods
writeOutput :: HasCallStack => o -> Ptr Word8 -> Int -> IO () Source #
Instances
| Output File Source # | |
Defined in Z.IO.FileSystem | |
| Output UVStream Source # | |
Defined in Z.IO.UV.Manager | |
| Output StdStream Source # | |
Defined in Z.IO.StdStream | |
| Output FileT Source # | |
Defined in Z.IO.FileSystem.Threaded | |
Buffered Input
data BufferedInput i Source #
Input device with buffer, NOT THREAD SAFE!
- A
BufferedInputshould not be used in multiple threads, there's no locking mechanism to protect buffering state. - A
Inputdevice should only be used with a singleBufferedInput, If multipleBufferedInputs are opened on a sameInputdevice, the behaviour is undefined.
Arguments
| :: Int | Input buffer size |
| -> input | |
| -> IO (BufferedInput input) |
Open a new buffered input with given buffer size, e.g. defaultChunkSize.
readBuffer :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes Source #
Request bytes 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.
unReadBuffer :: (HasCallStack, Input i) => Bytes -> BufferedInput i -> IO () Source #
Push bytes back into buffer.
readParser :: (HasCallStack, Input i) => Parser a -> BufferedInput i -> IO (Bytes, Either ParseError a) Source #
Read buffer and parse with Parser.
This function will continuously draw data from input before parsing finish.
readExactly :: (HasCallStack, Input i) => Int -> BufferedInput i -> IO Bytes Source #
Read exactly N bytes
If EOF reached before N bytes read, a ShortReadException will be thrown
readToMagic :: (HasCallStack, Input i) => Word8 -> BufferedInput i -> IO Bytes Source #
Read until reach a magic bytes
If EOF is reached before meet a magic byte, partial bytes are returned.
readToMagic' :: (HasCallStack, Input i) => Word8 -> BufferedInput i -> IO Bytes Source #
Read until reach a magic bytes
If EOF is reached before meet a magic byte, a ShortReadException will be thrown.
readLine :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes Source #
Read to a linefeed ('n' or 'rn'), return Bytes before it.
If EOF is reached before meet a magic byte, partial line is returned.
readLine' :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes Source #
Read to a linefeed ('n' or 'rn'), return Bytes before it.
If EOF reached before meet a 'n', a ShortReadException will be thrown.
readAll :: (HasCallStack, Input i) => BufferedInput i -> IO [Bytes] Source #
Read all chunks from a BufferedInput.
readAll' :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes Source #
Read all chunks from a BufferedInput, and concat chunks together.
Buffered Output
data BufferedOutput o Source #
Output device with buffer, NOT THREAD SAFE!
- A
BufferedOutputshould not be used in multiple threads, there's no locking mechanism to protect buffering state. - A
Outputdevice should only be used with a singleBufferedOutput, If multipleBufferedOutputs are opened on a sameBufferedOutputdevice, the output will be interleaved.
Arguments
| :: Int | Output buffer size |
| -> output | |
| -> IO (BufferedOutput output) |
Open a new buffered output with given buffer size, e.g. defaultChunkSize.
writeBuffer :: Output o => BufferedOutput o -> Bytes -> IO () Source #
Write Bytes into buffered handle.
Copy Bytes to buffer if it can hold, otherwise
write both buffer(if not empty) and Bytes.
writeBuilder :: Output o => BufferedOutput o -> Builder a -> IO () Source #
Write Bytes into buffered handle.
Copy Bytes to buffer if it can hold, otherwise
write both buffer(if not empty) and Bytes.
flushBuffer :: Output f => BufferedOutput f -> IO () Source #
Flush the buffer into output device(if not empty).
Exceptions
data ShortReadException Source #
Constructors
| ShortReadException IOEInfo |
Instances
| Show ShortReadException Source # | |
Defined in Z.IO.Buffered Methods showsPrec :: Int -> ShortReadException -> ShowS # show :: ShortReadException -> String # showList :: [ShortReadException] -> ShowS # | |
| Exception ShortReadException Source # | |
Defined in Z.IO.Buffered Methods toException :: ShortReadException -> SomeException # fromException :: SomeException -> Maybe ShortReadException # | |
common buffer size
defaultChunkSize :: Int #
smallChunkSize :: Int #