pipes-bytestring-1.0.1: ByteString support for pipes

Safe HaskellNone

Pipes.ByteString

Contents

Description

This module provides pipes utilities for "byte streams", which are streams of strict BS.ByteStrings chunks. Use byte streams to interact with both Handles and lazy BS.ByteStrings.

To stream to or from Handles, use fromHandle or toHandle. For example, the following program copies data from one file to another:

 import Pipes
 import qualified Pipes.ByteString as P
 import System.IO

 main =
     withFile "inFile.txt"  ReadMode  $ \hIn  ->
     withFile "outFile.txt" WriteMode $ \hOut ->
     runEffect $ P.fromHandle hIn >-> P.toHandle hOut

You can stream to and from stdin and stdout using the predefined stdin and stdout proxies, like in the following "echo" program:

 main = runEffect $ P.stdin >-> P.stdout

You can also translate pure lazy BL.ByteStrings to and from proxies:

 import qualified Data.ByteString.Lazy.Char8 as BL

 main = runEffect $ P.fromLazy (BL.pack "Hello, world!\n") >-> P.stdout

In addition, this module provides many functions equivalent to lazy BS.ByteString functions so that you can transform or fold byte streams. For example, to stream only the first three lines of stdin to stdout you would write:

 import Pipes
 import qualified Pipes.ByteString as PB
 import qualified Pipes.Parse      as PP

 main = runEffect $ takeLines 3 PB.stdin >-> PB.stdout
   where
     takeLines n = PB.unlines . PP.takeFree n . PB.lines

The above program will never bring more than one chunk (~ 32 KB) into memory, no matter how long the lines are.

Note that functions in this library are designed to operate on streams that are insensitive to chunk boundaries. This means that they may freely split chunks into smaller chunks and discard empty chunks. However, they will never concatenate chunks in order to provide strict upper bounds on memory usage.

Synopsis

Producers

stdin :: MonadIO m => Producer' BS.ByteString m ()Source

Stream bytes from stdin

fromHandle :: MonadIO m => Handle -> Producer' BS.ByteString m ()Source

Convert a Handle into a byte stream using a default chunk size

hGetSome :: MonadIO m => Int -> Handle -> Producer' BS.ByteString m ()Source

Convert a handle into a byte stream using a maximum chunk size

hGetSome forwards input immediately as it becomes available, splitting the input into multiple chunks if it exceeds the maximum chunk size.

hGet :: MonadIO m => Int -> Handle -> Producer' BS.ByteString m ()Source

Convert a handle into a byte stream using a fixed chunk size

hGet waits until exactly the requested number of bytes are available for each chunk.

Servers

hGetSomeN :: MonadIO m => Handle -> Int -> Server' Int BS.ByteString m ()Source

Like hGetSome, except you can vary the maximum chunk size for each request

hGetN :: MonadIO m => Handle -> Int -> Server' Int BS.ByteString m ()Source

Like hGet, except you can vary the chunk size for each request

Consumers

stdout :: MonadIO m => Consumer' BS.ByteString m ()Source

Stream bytes to stdout

Unlike toHandle, stdout gracefully terminates on a broken output pipe.

Note: For best performance, use (for source (liftIO . putStr)) instead of (source >-> stdout).

toHandle :: MonadIO m => Handle -> Consumer' BS.ByteString m rSource

Convert a byte stream into a Handle

Note: For best performance, use (for source (liftIO . hPutStr handle)) instead of (source >-> toHandle handle).

Pipes

map :: Monad m => (Word8 -> Word8) -> Pipe BS.ByteString BS.ByteString m rSource

Apply a transformation to each Word8 in the stream

concatMap :: Monad m => (Word8 -> BS.ByteString) -> Pipe BS.ByteString BS.ByteString m rSource

Map a function over the byte stream and concatenate the results

take :: (Monad m, Integral a) => a -> Pipe BS.ByteString BS.ByteString m ()Source

(take n) only allows n bytes to pass

drop :: (Monad m, Integral a) => a -> Pipe BS.ByteString BS.ByteString m rSource

(dropD n) drops the first n bytes

takeWhile :: Monad m => (Word8 -> Bool) -> Pipe BS.ByteString BS.ByteString m ()Source

Take bytes until they fail the predicate

dropWhile :: Monad m => (Word8 -> Bool) -> Pipe BS.ByteString BS.ByteString m rSource

Drop bytes until they fail the predicate

filter :: Monad m => (Word8 -> Bool) -> Pipe BS.ByteString BS.ByteString m rSource

Only allows Word8s to pass if they satisfy the predicate

elemIndices :: (Monad m, Num n) => Word8 -> Pipe BS.ByteString n m rSource

Stream all indices whose elements match the given Word8

findIndices :: (Monad m, Num n) => (Word8 -> Bool) -> Pipe BS.ByteString n m rSource

Stream all indices whose elements satisfy the given predicate

scan :: Monad m => (Word8 -> Word8 -> Word8) -> Word8 -> Pipe BS.ByteString BS.ByteString m rSource

Strict left scan over the bytes

Folds

toLazyM :: Monad m => Producer BS.ByteString m () -> m BL.ByteStringSource

Fold an effectful Producer of strict BS.ByteStrings into a lazy BL.ByteString

Note: toLazyM is not an idiomatic use of pipes, but I provide it for simple testing purposes. Idiomatic pipes style consumes the chunks immediately as they are generated instead of loading them all into memory.

fold :: Monad m => (x -> Word8 -> x) -> x -> (x -> r) -> Producer BS.ByteString m () -> m rSource

Reduce the stream of bytes using a strict left fold

head :: Monad m => Producer BS.ByteString m () -> m (Maybe Word8)Source

Retrieve the first Word8

last :: Monad m => Producer BS.ByteString m () -> m (Maybe Word8)Source

Retrieve the last Word8

null :: Monad m => Producer BS.ByteString m () -> m BoolSource

Determine if the stream is empty

length :: (Monad m, Num n) => Producer BS.ByteString m () -> m nSource

Count the number of bytes

any :: Monad m => (Word8 -> Bool) -> Producer BS.ByteString m () -> m BoolSource

Fold that returns whether Any received Word8s satisfy the predicate

all :: Monad m => (Word8 -> Bool) -> Producer BS.ByteString m () -> m BoolSource

Fold that returns whether All received Word8s satisfy the predicate

maximum :: Monad m => Producer BS.ByteString m () -> m (Maybe Word8)Source

Return the maximum Word8 within a byte stream

minimum :: Monad m => Producer BS.ByteString m () -> m (Maybe Word8)Source

Return the minimum Word8 within a byte stream

elem :: Monad m => Word8 -> Producer BS.ByteString m () -> m BoolSource

Determine whether any element in the byte stream matches the given Word8

notElem :: Monad m => Word8 -> Producer BS.ByteString m () -> m BoolSource

Determine whether all elements in the byte stream do not match the given Word8

find :: Monad m => (Word8 -> Bool) -> Producer BS.ByteString m () -> m (Maybe Word8)Source

Find the first element in the stream that matches the predicate

index :: (Monad m, Integral a) => a -> Producer BS.ByteString m () -> m (Maybe Word8)Source

Index into a byte stream

elemIndex :: (Monad m, Num n) => Word8 -> Producer BS.ByteString m () -> m (Maybe n)Source

Find the index of an element that matches the given Word8

findIndex :: (Monad m, Num n) => (Word8 -> Bool) -> Producer BS.ByteString m () -> m (Maybe n)Source

Store the first index of an element that satisfies the predicate

count :: (Monad m, Num n) => Word8 -> Producer BS.ByteString m () -> m nSource

Store a tally of how many elements match the given Word8

Splitters

splitAt :: (Monad m, Integral n) => n -> Producer BS.ByteString m r -> Producer' BS.ByteString m (Producer BS.ByteString m r)Source

Splits a Producer after the given number of bytes

chunksOf :: (Monad m, Integral n) => n -> Producer BS.ByteString m r -> FreeT (Producer BS.ByteString m) m rSource

Split a byte stream into FreeT-delimited byte streams of fixed size

span :: Monad m => (Word8 -> Bool) -> Producer BS.ByteString m r -> Producer' BS.ByteString m (Producer BS.ByteString m r)Source

Split a byte stream in two, where the first byte stream is the longest consecutive group of bytes that satisfy the predicate

break :: Monad m => (Word8 -> Bool) -> Producer BS.ByteString m r -> Producer BS.ByteString m (Producer BS.ByteString m r)Source

Split a byte stream in two, where the first byte stream is the longest consecutive group of bytes that don't satisfy the predicate

splitWith :: Monad m => (Word8 -> Bool) -> Producer BS.ByteString m r -> FreeT (Producer BS.ByteString m) m rSource

Split a byte stream into sub-streams delimited by bytes that satisfy the predicate

split :: Monad m => Word8 -> Producer BS.ByteString m r -> FreeT (Producer BS.ByteString m) m rSource

Split a byte stream using the given Word8 as the delimiter

groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> Producer BS.ByteString m r -> FreeT (Producer BS.ByteString m) m rSource

Group a byte stream into FreeT-delimited byte streams using the supplied equality predicate

group :: Monad m => Producer BS.ByteString m r -> FreeT (Producer BS.ByteString m) m rSource

Group a byte stream into FreeT-delimited byte streams of identical bytes

lines :: Monad m => Producer BS.ByteString m r -> FreeT (Producer BS.ByteString m) m rSource

Split a byte stream into FreeT-delimited lines

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the upcoming pipes-text library.

words :: Monad m => Producer BS.ByteString m r -> FreeT (Producer BS.ByteString m) m rSource

Split a byte stream into FreeT-delimited words

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the upcoming pipes-text library.

Transformations

intersperse :: Monad m => Word8 -> Producer BS.ByteString m r -> Producer BS.ByteString m rSource

Intersperse a Word8 in between the bytes of the byte stream

Joiners

intercalate :: Monad m => Producer BS.ByteString m () -> FreeT (Producer BS.ByteString m) m r -> Producer BS.ByteString m rSource

intercalate concatenates the FreeT-delimited byte streams after interspersing a byte stream in between them

unlines :: Monad m => FreeT (Producer BS.ByteString m) m r -> Producer BS.ByteString m rSource

Join FreeT-delimited lines into a byte stream

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the upcoming pipes-text library.

unwords :: Monad m => FreeT (Producer BS.ByteString m) m r -> Producer BS.ByteString m rSource

Join FreeT-delimited words into a byte stream

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the upcoming pipes-text library.

Low-level Parsers

The following parsing utilities are single-byte analogs of the ones found in pipes-parse.

nextByte :: Monad m => Producer BS.ByteString m r -> m (Either r (Word8, Producer BS.ByteString m r))Source

Consume the first byte from a byte stream

next either fails with a Left if the Producer has no more bytes or succeeds with a Right providing the next byte and the remainder of the Producer.

drawByte :: Monad m => StateT (Producer BS.ByteString m r) m (Either r Word8)Source

Draw one Word8 from the underlying Producer, returning Left if the Producer is empty

unDrawByte :: Monad m => Word8 -> StateT (Producer BS.ByteString m r) m ()Source

Push back a Word8 onto the underlying Producer

peekByte :: Monad m => StateT (Producer BS.ByteString m r) m (Either r Word8)Source

peekByte checks the first Word8 in the stream, but uses unDrawByte to push the Word8 back

 peekByte = do
     x <- drawByte
     case x of
         Left  _  -> return ()
         Right w8 -> unDrawByte w8
     return x

isEndOfBytes :: Monad m => StateT (Producer BS.ByteString m r) m BoolSource

Check if the underlying Producer has no more bytes

Note that this will skip over empty BS.ByteString chunks, unlike PP.isEndOfInput from pipes-parse.

 isEndOfBytes = liftM isLeft peekByte

takeWhile' :: Monad m => (Word8 -> Bool) -> Pipe BS.ByteString BS.ByteString (StateT (Producer BS.ByteString m r) m) ()Source

Take bytes until they fail the predicate

Unlike takeWhile, this PP.unDraws unused bytes

Re-exports

Data.ByteString re-exports the BS.ByteString type.

Data.Word re-exports the Word8 type.

Pipes.Parse re-exports PP.input, PP.concat, and FreeT (the type).

module Data.Word