| 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 -> i -> IO (BufferedInput i)
- readBuffer :: (Input i, HasCallStack) => BufferedInput i -> IO Bytes
- unReadBuffer :: (HasCallStack, Input i) => Bytes -> BufferedInput i -> IO ()
- readParser :: (HasCallStack, Input i) => Parser a -> BufferedInput i -> IO (Either ParseError a)
- readExactly :: (HasCallStack, Input i) => Int -> BufferedInput i -> IO Bytes
- 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 -> Source Bytes
- readLine' :: (HasCallStack, Input i) => BufferedInput i -> Source Bytes
- readAll :: (HasCallStack, Input i) => BufferedInput i -> IO [Bytes]
- readAll' :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes
- data BufferedOutput o
- newBufferedOutput :: Int -> o -> IO (BufferedOutput o)
- writeBuffer :: (HasCallStack, Output o) => BufferedOutput o -> Bytes -> IO ()
- writeBuilder :: (HasCallStack, Output o) => BufferedOutput o -> Builder a -> IO ()
- flushBuffer :: (HasCallStack, Output o) => BufferedOutput o -> IO ()
- type Source a = IO (Maybe a)
- type Sink a = (a -> IO (), IO ())
- sourceBuffer :: (HasCallStack, Input i) => BufferedInput i -> Source Bytes
- sinkBuffer :: (HasCallStack, Output o) => BufferedOutput o -> Sink Bytes
- sourceFromList :: [a] -> IO (Source a)
- (>+>) :: Source a -> Source a -> IO (Source a)
- parseSource :: HasCallStack => Parser a -> Source Bytes -> IO (Source a)
- collectSource :: Source a -> IO [a]
- concatSource :: [Source a] -> IO (Source a)
- zipSource :: Source a -> Source b -> Source (a, b)
- (>>>>=) :: Source a -> Sink a -> IO ()
- data BufferedException
- = ParseException ParseError CallStack
- | ShortReadException CallStack
- 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 |
| -> i | |
| -> IO (BufferedInput i) |
Open a new buffered input with given buffer size, e.g. defaultChunkSize.
readBuffer :: (Input i, HasCallStack) => 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(if not empty).
readParser :: (HasCallStack, Input i) => Parser a -> BufferedInput i -> 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, Input i) => Int -> BufferedInput i -> IO Bytes Source #
Read exactly N bytes
If EOF reached before N bytes read, trailing bytes will be returned.
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, return bytes(including the 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, return bytes(including the magic bytes)
If EOF is reached before meet a magic byte, a ShortReadException will be thrown.
readLine :: (HasCallStack, Input i) => BufferedInput i -> Source 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' :: (HasCallStack, Input i) => BufferedInput i -> Source 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 reached before meet a line feed, a ShortReadException will be thrown.
readAll :: (HasCallStack, Input i) => BufferedInput i -> IO [Bytes] Source #
Read all chunks from a BufferedInput.
This function will loop read until meet EOF(Input device return empty),
Useful for reading small file into memory.
readAll' :: (HasCallStack, Input i) => BufferedInput i -> 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 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 |
| -> o | |
| -> IO (BufferedOutput o) |
Open a new buffered output with given buffer size, e.g. defaultChunkSize.
writeBuffer :: (HasCallStack, Output o) => BufferedOutput o -> 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, Output o) => BufferedOutput o -> Builder a -> IO () Source #
Directly write Builder into buffered handle.
Run Builder with buffer if it can hold, write to device when buffer is full.
flushBuffer :: (HasCallStack, Output o) => BufferedOutput o -> IO () Source #
Flush the buffer into output device(if buffer is not empty).
Stream utilities
type Sink a = (a -> IO (), IO ()) Source #
Type alias for output stream, contain a write & a flush function.
sourceBuffer :: (HasCallStack, Input i) => BufferedInput i -> Source Bytes Source #
Turn a BufferedInput into Source, map EOF to Nothing.
sinkBuffer :: (HasCallStack, Output o) => BufferedOutput o -> Sink Bytes Source #
Turn a BufferedOutput into Sink.
sourceFromList :: [a] -> IO (Source a) Source #
Source a list streamly.
(>+>) :: Source a -> Source a -> IO (Source a) Source #
Connect two streams, after first reach EOF, draw element from second.
parseSource :: HasCallStack => Parser a -> Source Bytes -> IO (Source 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.
Return Nothing if reach EOF before parsing, throw ParseException if parsing fail.
collectSource :: Source a -> IO [a] Source #
Read all stream elements to a list.
concatSource :: [Source a] -> IO (Source a) Source #
Connect list of streams, after one stream reach EOF, draw element from next.
Loop read stream and write to output, when input ends flush the output.
Exceptions
data BufferedException Source #
Constructors
| ParseException ParseError CallStack | |
| ShortReadException CallStack |
Instances
| Show BufferedException Source # | |
Defined in Z.IO.Buffered Methods showsPrec :: Int -> BufferedException -> ShowS # show :: BufferedException -> String # showList :: [BufferedException] -> ShowS # | |
| Exception BufferedException Source # | |
Defined in Z.IO.Buffered Methods toException :: BufferedException -> SomeException # | |
common buffer size
defaultChunkSize :: Int #
smallChunkSize :: Int #