Copyright | (c) Dong Han 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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 :: input -> Int -> 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 (ReadResult 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
- data BufferedOutput o
- newBufferedOutput :: output -> Int -> 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
Input & Output device
Input device
Laws: readInput
should return 0 on EOF.
Note: readInput
is considered not thread-safe, e.g. A Input
device
can only be used with a single BufferedInput
, If multiple BufferedInput
s
are opened on a same Input
device, the behaviour will be undefined.
Output device
Laws: 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 UVStream Source # | |
Defined in Std.IO.UV.Manager | |
Output StdStream Source # | |
Defined in Std.IO.StdStream | |
Output UVFileWriter Source # | |
Defined in Std.IO.FileSystemT writeOutput :: UVFileWriter -> Ptr Word8 -> Int -> IO () Source # | |
Output UVFile Source # | |
Defined in Std.IO.FileSystemT | |
Output UVFileWriter Source # | |
Defined in Std.IO.FileSystem writeOutput :: UVFileWriter -> Ptr Word8 -> Int -> IO () Source # | |
Output UVFile Source # | |
Defined in Std.IO.FileSystem |
Buffered Input
data BufferedInput i Source #
Input device with buffer, NOT THREAD SAFE!
:: input | |
-> Int | Input buffer size |
-> IO (BufferedInput input) |
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 (ReadResult a) Source #
Read buffer and parse with Parser
.
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 '\r\n'), 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 '\r\n'), return Bytes
before it.
If EOF reached before meet a magic byte, a ShortReadException
will be thrown.
Buffered Output
data BufferedOutput o Source #
Output device with buffer, NOT THREAD SAFE!
:: output | |
-> Int | Output buffer size |
-> IO (BufferedOutput output) |
writeBuffer :: Output o => BufferedOutput o -> Bytes -> IO () Source #
writeBuilder :: Output o => BufferedOutput o -> Builder a -> IO () Source #
flushBuffer :: Output f => BufferedOutput f -> IO () Source #
Flush the buffer(if not empty).
Exceptions
data ShortReadException Source #
Instances
Show ShortReadException Source # | |
Defined in Std.IO.Buffered showsPrec :: Int -> ShortReadException -> ShowS # show :: ShortReadException -> String # showList :: [ShortReadException] -> ShowS # | |
Exception ShortReadException Source # | |
Defined in Std.IO.Buffered |