Z-IO-0.1.5.0: Simple and high performance IO toolkit for Haskell

Copyright(c) Dong Han 2017-2018
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.Buffered

Contents

Description

This module provide buffered IO interface.

Synopsis

Input & Output device

class Input i where Source #

Input device

readInput should return 0 on EOF.

Methods

readInput :: HasCallStack => i -> Ptr Word8 -> Int -> IO Int Source #

Instances
Input FilePtr Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

readInput :: FilePtr -> Ptr Word8 -> Int -> IO Int Source #

Input File Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

readInput :: File -> Ptr Word8 -> Int -> IO Int Source #

Input StdStream Source # 
Instance details

Defined in Z.IO.StdStream

Input FilePtrT Source # 
Instance details

Defined in Z.IO.FileSystem.Threaded

Methods

readInput :: FilePtrT -> Ptr Word8 -> Int -> IO Int Source #

Input FileT Source # 
Instance details

Defined in Z.IO.FileSystem.Threaded

Methods

readInput :: FileT -> Ptr Word8 -> Int -> IO Int Source #

Input UVStream Source # 
Instance details

Defined in Z.IO.UV.UVStream

Methods

readInput :: UVStream -> Ptr Word8 -> Int -> IO Int Source #

class Output o where Source #

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 FilePtr Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

writeOutput :: FilePtr -> Ptr Word8 -> Int -> IO () Source #

Output File Source # 
Instance details

Defined in Z.IO.FileSystem

Methods

writeOutput :: File -> Ptr Word8 -> Int -> IO () Source #

Output StdStream Source # 
Instance details

Defined in Z.IO.StdStream

Methods

writeOutput :: StdStream -> Ptr Word8 -> Int -> IO () Source #

Output FilePtrT Source # 
Instance details

Defined in Z.IO.FileSystem.Threaded

Methods

writeOutput :: FilePtrT -> Ptr Word8 -> Int -> IO () Source #

Output FileT Source # 
Instance details

Defined in Z.IO.FileSystem.Threaded

Methods

writeOutput :: FileT -> Ptr Word8 -> Int -> IO () Source #

Output UVStream Source # 
Instance details

Defined in Z.IO.UV.UVStream

Methods

writeOutput :: UVStream -> Ptr Word8 -> Int -> IO () Source #

Buffered Input

data BufferedInput i 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 single BufferedInput, If multiple BufferedInput s are opened on a same Input device, the behaviour is undefined.

newBufferedInput :: i -> IO (BufferedInput i) Source #

Open a new buffered input with defaultChunkSize as buffer size.

newBufferedInput' Source #

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 '\r\n'), 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 '\r\n'), 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!

newBufferedOutput :: o -> IO (BufferedOutput o) Source #

Open a new buffered output with defaultChunkSize as buffer size.

newBufferedOutput' Source #

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 Source a = IO (Maybe a) Source #

Type alias for input stream, Nothing indicate EOF.

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.

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.

zipSource :: Source a -> Source b -> Source (a, b) Source #

Zip two streams into one.

(>>>>=) Source #

Arguments

:: Source a

stream to write

-> Sink a 
-> IO () 

Loop read stream and write to output, when input ends flush the output.

Exceptions

common buffer size

defaultChunkSize :: Int #

The chunk size used for I/O. Currently set to 32k-chunkOverhead

smallChunkSize :: Int #

The recommended chunk size. Currently set to 4k - chunkOverhead.