Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module provides pipes
utilities for "byte streams", which are
streams of strict ByteString
s chunks. Use byte streams to interact
with both Handle
s and lazy ByteString
s.
To stream to or from Handle
s, 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
pipes, like in the following "echo" program:
main = runEffect $ P.stdin >-> P.stdout
You can also translate pure lazy ByteString
s to and from pipes:
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 Lens.Family (over) import Pipes import qualified Pipes.ByteString as PB import Pipes.Group (takes) main = runEffect $ over PB.lines (takes 3) PB.stdin >-> PB.stdout
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
- 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 ()
- hGetNonBlocking :: MonadIO m => Int -> Handle -> Producer' ByteString m ()
- hGet :: MonadIO m => Int -> Handle -> Producer' ByteString m ()
- hGetRange :: MonadIO m => Int -> 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 n) => n -> Pipe ByteString ByteString m ()
- takeWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m ()
- 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
- toLazyM' :: Monad m => Producer ByteString m a -> m (ByteString, a)
- foldBytes :: 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 n) => n -> 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
- nextByte :: Monad m => Producer ByteString m r -> m (Either r (Word8, Producer ByteString m r))
- drawByte :: Monad m => Parser ByteString m (Maybe Word8)
- unDrawByte :: Monad m => Word8 -> Parser ByteString m ()
- peekByte :: Monad m => Parser ByteString m (Maybe Word8)
- isEndOfBytes :: Monad m => Parser ByteString m Bool
- splitAt :: (Monad m, Integral n) => n -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- span :: Monad m => (Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- break :: Monad m => (Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- breakOn :: Monad m => ByteString -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- group :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- word :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- line :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))
- drop :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer ByteString m r
- dropWhile :: Monad m => (Word8 -> Bool) -> Producer ByteString m r -> Producer ByteString m r
- intersperse :: Monad m => Word8 -> Producer ByteString m r -> Producer ByteString m r
- pack :: Monad m => Lens' (Producer Word8 m x) (Producer ByteString m x)
- unpack :: Monad m => Lens' (Producer ByteString m x) (Producer Word8 m x)
- chunksOf' :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer ByteString m r
- chunksOf :: (Monad m, Integral n) => n -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
- splitsWith :: Monad m => (Word8 -> Bool) -> Producer ByteString m x -> FreeT (Producer ByteString m) m x
- splits :: Monad m => Word8 -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
- splitOn :: Monad m => ByteString -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
- groupsBy :: Monad m => (Word8 -> Word8 -> Bool) -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
- groups :: Monad m => Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
- lines :: Monad m => Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
- unlines :: Monad m => Lens' (FreeT (Producer ByteString m) m x) (Producer ByteString m x)
- words :: Monad m => Producer ByteString m x -> FreeT (Producer ByteString m) m x
- unwords :: Monad m => FreeT (Producer ByteString m) m x -> Producer ByteString m x
- data ByteString
- data Word8
- data FreeT (f :: Type -> Type) (m :: Type -> Type) a
- intercalates :: forall (m :: Type -> Type) a x. Monad m => Producer a m () -> FreeT (Producer a m) m x -> Producer a m x
- concats :: forall (m :: Type -> Type) a x. Monad m => FreeT (Producer a m) m x -> Producer a m x
- type Parser a (m :: Type -> Type) r = forall x. StateT (Producer a m x) m r
Producers
fromLazy :: Monad m => ByteString -> Producer' ByteString m () Source #
Convert a lazy ByteString
into a Producer
of strict ByteString
s
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.
hGetNonBlocking :: MonadIO m => Int -> Handle -> Producer' ByteString m () Source #
Convert a handle into a byte stream using a fixed chunk size
Similar to hGet
except that it will never block waiting for data
to become available.
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.
Like hGet
but with an extra parameter specifying an initial handle offset
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
toHandle :: MonadIO m => Handle -> Consumer' ByteString m r Source #
Convert a byte stream into a Handle
p >-> toHandle handle = for p (liftIO . hPutStr handle)
Pipes
map :: Monad m => (Word8 -> Word8) -> Pipe ByteString ByteString m r Source #
Apply a transformation to each Word8
in the stream
concatMap :: Monad m => (Word8 -> ByteString) -> Pipe ByteString ByteString m r Source #
Map a function over the byte stream and concatenate the results
take :: (Monad m, Integral n) => n -> Pipe ByteString ByteString m () Source #
(take n)
only allows n
bytes to pass
takeWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m () Source #
Take bytes until they fail the predicate
filter :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m r Source #
Only allows Word8
s to pass if they satisfy the predicate
elemIndices :: (Monad m, Num n) => Word8 -> Pipe ByteString n m r Source #
Stream all indices whose elements match the given Word8
findIndices :: (Monad m, Num n) => (Word8 -> Bool) -> Pipe ByteString n m r Source #
Stream all indices whose elements satisfy the given predicate
scan :: Monad m => (Word8 -> Word8 -> Word8) -> Word8 -> Pipe ByteString ByteString m r Source #
Strict left scan over the bytes
Folds
toLazy :: Producer ByteString Identity () -> ByteString Source #
Fold a pure Producer
of strict ByteString
s into a lazy
ByteString
toLazyM :: Monad m => Producer ByteString m () -> m ByteString Source #
Fold an effectful Producer
of strict ByteString
s 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.
toLazyM' :: Monad m => Producer ByteString m a -> m (ByteString, a) Source #
Fold an effectful Producer
of strict ByteString
s into a lazy
ByteString
alongside the return value
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.
foldBytes :: Monad m => (x -> Word8 -> x) -> x -> (x -> r) -> Producer ByteString m () -> m r Source #
Reduce the stream of bytes using a strict left fold
Note: It's more efficient to use folds from Control.Foldl.ByteString
in
conjunction with Pipes.Prelude.
when possiblefold
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 Bool Source #
Determine whether any element in the byte stream matches the given Word8
notElem :: Monad m => Word8 -> Producer ByteString m () -> m Bool Source #
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 n) => n -> 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 n Source #
Store a tally of how many elements match the given Word8
Parsing
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 -> Parser ByteString m () Source #
peekByte :: Monad m => Parser ByteString m (Maybe 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 Nothing -> return () Just w8 -> unDrawByte w8 return x
isEndOfBytes :: Monad m => Parser ByteString m Bool Source #
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 isNothing peekByte
Parsing Lenses
splitAt :: (Monad m, Integral n) => n -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
Improper lens that splits a Producer
after the given number of bytes
span :: Monad m => (Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
Improper lens that splits after the longest consecutive group of bytes that satisfy the given predicate
break :: Monad m => (Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
Improper lens that splits after the longest consecutive group of bytes that fail the given predicate
breakOn :: Monad m => ByteString -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
Improper lens that splits at the first occurrence of the pattern.
groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
Improper lens that splits after the first group of matching bytes, as defined by the given equality predicate
group :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
word :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
line :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #
Improper lens that splits a Producer
after the first line
Unlike lines
, this does not consume the newline marker, which is stored
within the inner Producer
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 pipes-text
library.
Transforming Byte Streams
drop :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer ByteString m r Source #
(drop n)
drops the first n
bytes
dropWhile :: Monad m => (Word8 -> Bool) -> Producer ByteString m r -> Producer ByteString m r Source #
Drop bytes until they fail the predicate
intersperse :: Monad m => Word8 -> Producer ByteString m r -> Producer ByteString m r Source #
Intersperse a Word8
in between the bytes of the byte stream
pack :: Monad m => Lens' (Producer Word8 m x) (Producer ByteString m x) Source #
Improper lens from unpacked Word8
s to packaged ByteString
s
unpack :: Monad m => Lens' (Producer ByteString m x) (Producer Word8 m x) Source #
Improper lens from packed ByteString
s to unpacked Word8
s
chunksOf' :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer ByteString m r Source #
Group byte stream chunks into chunks of fixed length
Note: This is the only function in this API that concatenates
ByteString
chunks, which requires allocating new ByteString
s
FreeT Transformations
chunksOf :: (Monad m, Integral n) => n -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #
Split a byte stream into FreeT
-delimited byte streams of fixed size
splitsWith :: Monad m => (Word8 -> Bool) -> Producer ByteString m x -> FreeT (Producer ByteString m) m x Source #
Split a byte stream into groups separated by bytes that satisfy the predicate
splits :: Monad m => Word8 -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #
Split a byte stream into groups separated by the given byte
splitOn :: Monad m => ByteString -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #
Split a byte stream into groups separated by the given ByteString
groupsBy :: Monad m => (Word8 -> Word8 -> Bool) -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #
Isomorphism between a byte stream and groups of identical bytes using the supplied equality predicate
groups :: Monad m => Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #
lines :: Monad m => Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #
Improper lens between a bytestream and its 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 pipes-text
library.
unlines :: Monad m => Lens' (FreeT (Producer ByteString m) m x) (Producer ByteString m x) Source #
Improper lens between lines and a bytestream
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 pipes-text
library.
words :: Monad m => Producer ByteString m x -> FreeT (Producer ByteString m) m x Source #
Convert a bytestream to 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 pipes-text
library.
unwords :: Monad m => FreeT (Producer ByteString m) m x -> Producer ByteString m x Source #
Convert delimited words back to 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 pipes-text
library.
Re-exports
Data.ByteString
re-exports the ByteString
type.
Data.Word
re-exports the Word8
type.
Pipes.Parse
re-exports Parser
.
Pipes.Group
re-exports concats
, intercalates
, and FreeT
(the type).
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
8-bit unsigned integer type
Instances
data FreeT (f :: Type -> Type) (m :: Type -> Type) a #
The "free monad transformer" for a functor f
Instances
intercalates :: forall (m :: Type -> Type) a x. Monad m => Producer a m () -> FreeT (Producer a m) m x -> Producer a m x #