| Safe Haskell | None |
|---|
Pipes.ByteString
Contents
Description
This module provides pipes utilities for "byte streams", which are
streams of strict ByteStrings chunks. Use byte streams to interact
with both Handles and lazy 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 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
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.
- fromLazy :: Monad m => ByteString -> Producer' ByteString m ()
- stdin :: MonadIO m => Producer' ByteString m ()
- fromHandle :: MonadIO m => Handle -> Producer' ByteString m ()
- hGetSome :: MonadIO m => Int -> Handle -> Producer' ByteString m ()
- hGet :: MonadIO m => Int -> Handle -> Producer' ByteString m ()
- hGetSomeN :: MonadIO m => Handle -> Int -> Server' Int ByteString m ()
- hGetN :: MonadIO m => Handle -> Int -> Server' Int ByteString m ()
- stdout :: MonadIO m => Consumer' ByteString m ()
- toHandle :: MonadIO m => Handle -> Consumer' ByteString m r
- map :: Monad m => (Word8 -> Word8) -> Pipe ByteString ByteString m r
- concatMap :: Monad m => (Word8 -> ByteString) -> Pipe ByteString ByteString m r
- take :: (Monad m, Integral a) => a -> Pipe ByteString ByteString m ()
- drop :: (Monad m, Integral a) => a -> Pipe ByteString ByteString m r
- takeWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m ()
- dropWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m r
- filter :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m r
- elemIndices :: (Monad m, Num n) => Word8 -> Pipe ByteString n m r
- findIndices :: (Monad m, Num n) => (Word8 -> Bool) -> Pipe ByteString n m r
- scan :: Monad m => (Word8 -> Word8 -> Word8) -> Word8 -> Pipe ByteString ByteString m r
- toLazy :: Producer ByteString Identity () -> ByteString
- toLazyM :: Monad m => Producer ByteString m () -> m ByteString
- fold :: Monad m => (x -> Word8 -> x) -> x -> (x -> r) -> Producer ByteString m () -> m r
- head :: Monad m => Producer ByteString m () -> m (Maybe Word8)
- last :: Monad m => Producer ByteString m () -> m (Maybe Word8)
- null :: Monad m => Producer ByteString m () -> m Bool
- length :: (Monad m, Num n) => Producer ByteString m () -> m n
- any :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m Bool
- all :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m Bool
- maximum :: Monad m => Producer ByteString m () -> m (Maybe Word8)
- minimum :: Monad m => Producer ByteString m () -> m (Maybe Word8)
- elem :: Monad m => Word8 -> Producer ByteString m () -> m Bool
- notElem :: Monad m => Word8 -> Producer ByteString m () -> m Bool
- find :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m (Maybe Word8)
- index :: (Monad m, Integral a) => a -> Producer ByteString m () -> m (Maybe Word8)
- elemIndex :: (Monad m, Num n) => Word8 -> Producer ByteString m () -> m (Maybe n)
- findIndex :: (Monad m, Num n) => (Word8 -> Bool) -> Producer ByteString m () -> m (Maybe n)
- count :: (Monad m, Num n) => Word8 -> Producer ByteString m () -> m n
- splitAt :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer' ByteString m (Producer ByteString m r)
- chunksOf :: (Monad m, Integral n) => n -> Producer ByteString m r -> FreeT (Producer ByteString m) m r
- span :: Monad m => (Word8 -> Bool) -> Producer ByteString m r -> Producer' ByteString m (Producer ByteString m r)
- break :: Monad m => (Word8 -> Bool) -> Producer ByteString m r -> Producer ByteString m (Producer ByteString m r)
- splitWith :: Monad m => (Word8 -> Bool) -> Producer ByteString m r -> FreeT (Producer ByteString m) m r
- split :: Monad m => Word8 -> Producer ByteString m r -> FreeT (Producer ByteString m) m r
- groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> Producer ByteString m r -> FreeT (Producer ByteString m) m r
- group :: Monad m => Producer ByteString m r -> FreeT (Producer ByteString m) m r
- lines :: Monad m => Producer ByteString m r -> FreeT (Producer ByteString m) m r
- words :: Monad m => Producer ByteString m r -> FreeT (Producer ByteString m) m r
- intersperse :: Monad m => Word8 -> Producer ByteString m r -> Producer ByteString m r
- intercalate :: Monad m => Producer ByteString m () -> FreeT (Producer ByteString m) m r -> Producer ByteString m r
- unlines :: Monad m => FreeT (Producer ByteString m) m r -> Producer ByteString m r
- unwords :: Monad m => FreeT (Producer ByteString m) m r -> Producer ByteString m r
- nextByte :: Monad m => Producer ByteString m r -> m (Either r (Word8, Producer ByteString m r))
- drawByte :: Monad m => StateT (Producer ByteString m r) m (Either r Word8)
- unDrawByte :: Monad m => Word8 -> StateT (Producer ByteString m r) m ()
- peekByte :: Monad m => StateT (Producer ByteString m r) m (Either r Word8)
- isEndOfBytes :: Monad m => StateT (Producer ByteString m r) m Bool
- takeWhile' :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString (StateT (Producer ByteString m r) m) ()
- module Data.ByteString
- module Data.Word
- module Pipes.Parse
Producers
fromLazy :: Monad m => ByteString -> Producer' ByteString m ()Source
Convert a lazy ByteString into a Producer of strict ByteStrings
fromHandle :: MonadIO m => Handle -> Producer' ByteString m ()Source
Convert a Handle into a byte stream using a default chunk size
hGetSome :: MonadIO m => Int -> Handle -> Producer' 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' 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 ByteString m ()Source
Like hGetSome, except you can vary the maximum chunk size for each request
hGetN :: MonadIO m => Handle -> Int -> Server' Int ByteString m ()Source
Like hGet, except you can vary the chunk size for each request
Consumers
stdout :: MonadIO m => Consumer' ByteString m ()Source
toHandle :: MonadIO m => Handle -> Consumer' 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 ByteString ByteString m rSource
Apply a transformation to each Word8 in the stream
concatMap :: Monad m => (Word8 -> ByteString) -> Pipe ByteString ByteString m rSource
Map a function over the byte stream and concatenate the results
take :: (Monad m, Integral a) => a -> Pipe ByteString ByteString m ()Source
(take n) only allows n bytes to pass
drop :: (Monad m, Integral a) => a -> Pipe ByteString ByteString m rSource
(dropD n) drops the first n bytes
takeWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m ()Source
Take bytes until they fail the predicate
dropWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m rSource
Drop bytes until they fail the predicate
filter :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m rSource
Only allows Word8s to pass if they satisfy the predicate
elemIndices :: (Monad m, Num n) => Word8 -> Pipe ByteString n m rSource
Stream all indices whose elements match the given Word8
findIndices :: (Monad m, Num n) => (Word8 -> Bool) -> Pipe ByteString n m rSource
Stream all indices whose elements satisfy the given predicate
scan :: Monad m => (Word8 -> Word8 -> Word8) -> Word8 -> Pipe ByteString ByteString m rSource
Strict left scan over the bytes
Folds
toLazy :: Producer ByteString Identity () -> ByteStringSource
Fold a pure Producer of strict ByteStrings into a lazy
ByteString
toLazyM :: Monad m => Producer ByteString m () -> m ByteStringSource
Fold an effectful Producer of strict ByteStrings into a lazy
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 ByteString m () -> m rSource
Reduce the stream of bytes using a strict left fold
maximum :: Monad m => Producer ByteString m () -> m (Maybe Word8)Source
Return the maximum Word8 within a byte stream
minimum :: Monad m => Producer ByteString m () -> m (Maybe Word8)Source
Return the minimum Word8 within a byte stream
elem :: Monad m => Word8 -> Producer ByteString m () -> m BoolSource
Determine whether any element in the byte stream matches the given Word8
notElem :: Monad m => Word8 -> Producer ByteString m () -> m BoolSource
Determine whether all elements in the byte stream do not match the given
Word8
find :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m (Maybe Word8)Source
Find the first element in the stream that matches the predicate
index :: (Monad m, Integral a) => a -> Producer ByteString m () -> m (Maybe Word8)Source
Index into a byte stream
elemIndex :: (Monad m, Num n) => Word8 -> Producer 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 ByteString m () -> m (Maybe n)Source
Store the first index of an element that satisfies the predicate
count :: (Monad m, Num n) => Word8 -> Producer ByteString m () -> m nSource
Store a tally of how many elements match the given Word8
Splitters
splitAt :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer' ByteString m (Producer ByteString m r)Source
Splits a Producer after the given number of bytes
chunksOf :: (Monad m, Integral n) => n -> Producer ByteString m r -> FreeT (Producer ByteString m) m rSource
Split a byte stream into FreeT-delimited byte streams of fixed size
span :: Monad m => (Word8 -> Bool) -> Producer ByteString m r -> Producer' ByteString m (Producer 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 ByteString m r -> Producer ByteString m (Producer 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 ByteString m r -> FreeT (Producer ByteString m) m rSource
Split a byte stream into sub-streams delimited by bytes that satisfy the predicate
split :: Monad m => Word8 -> Producer ByteString m r -> FreeT (Producer ByteString m) m rSource
Split a byte stream using the given Word8 as the delimiter
groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> Producer ByteString m r -> FreeT (Producer ByteString m) m rSource
Group a byte stream into FreeT-delimited byte streams using the supplied
equality predicate
group :: Monad m => Producer ByteString m r -> FreeT (Producer ByteString m) m rSource
Group a byte stream into FreeT-delimited byte streams of identical bytes
lines :: Monad m => Producer ByteString m r -> FreeT (Producer ByteString m) m rSource
words :: Monad m => Producer ByteString m r -> FreeT (Producer ByteString m) m rSource
Transformations
intersperse :: Monad m => Word8 -> Producer ByteString m r -> Producer ByteString m rSource
Intersperse a Word8 in between the bytes of the byte stream
Joiners
intercalate :: Monad m => Producer ByteString m () -> FreeT (Producer ByteString m) m r -> Producer ByteString m rSource
intercalate concatenates the FreeT-delimited byte streams after
interspersing a byte stream in between them
unlines :: Monad m => FreeT (Producer ByteString m) m r -> Producer ByteString m rSource
unwords :: Monad m => FreeT (Producer ByteString m) m r -> Producer ByteString m rSource
Low-level Parsers
The following parsing utilities are single-byte analogs of the ones found
in pipes-parse.
nextByte :: Monad m => Producer ByteString m r -> m (Either r (Word8, Producer ByteString m r))Source
unDrawByte :: Monad m => Word8 -> StateT (Producer ByteString m r) m ()Source
peekByte :: Monad m => StateT (Producer 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 ByteString m r) m BoolSource
Check if the underlying Producer has no more bytes
Note that this will skip over empty ByteString chunks, unlike
isEndOfInput from pipes-parse.
isEndOfBytes = liftM isLeft peekByte
takeWhile' :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString (StateT (Producer ByteString m r) m) ()Source
Re-exports
Data.ByteString re-exports the ByteString type.
Data.Word re-exports the Word8 type.
module Data.ByteString
module Data.Word
module Pipes.Parse