| Copyright | (c) Don Stewart 2006 (c) Duncan Coutts 2006-2011 (c) Michael Thompson 2015 |
|---|---|
| License | BSD-style |
| Maintainer | what_is_it_to_do_anything@yahoo.com |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Streaming.ByteString
Description
See the simple examples of use here
and the ghci examples especially in Streaming.ByteString.Char8.
We begin with a slight modification of the documentation to Data.ByteString.Lazy:
A time and space-efficient implementation of effectful byte streams using a
stream of packed Word8 arrays, suitable for high performance use, both in
terms of large data quantities, or high speed requirements. Streaming
ByteStrings are encoded as streams of strict chunks of bytes.
A key feature of streaming ByteStrings is the means to manipulate large or unbounded streams of data without requiring the entire sequence to be resident in memory. To take advantage of this you have to write your functions in a streaming style, e.g. classic pipeline composition. The default I/O chunk size is 32k, which should be good in most circumstances.
Some operations, such as concat, append, and cons, have better
complexity than their Data.ByteString equivalents, due to optimisations
resulting from the list spine structure. For other operations streaming, like
lazy, ByteStrings are usually within a few percent of strict ones.
This module is intended to be imported qualified, to avoid name clashes
with Prelude functions. eg.
import qualified Streaming.ByteString as Q
Original GHC implementation by Bryan O'Sullivan. Rewritten to use
UArray by Simon Marlow. Rewritten to support slices and
use ForeignPtr by David Roundy. Rewritten again and
extended by Don Stewart and Duncan Coutts. Lazy variant by Duncan Coutts and
Don Stewart. Streaming variant by Michael Thompson, following the ideas of
Gabriel Gonzales' pipes-bytestring.
Synopsis
- data ByteStream m r
- type ByteString = ByteStream
- empty :: ByteStream m ()
- singleton :: Monad m => Word8 -> ByteStream m ()
- pack :: Monad m => Stream (Of Word8) m r -> ByteStream m r
- unpack :: Monad m => ByteStream m r -> Stream (Of Word8) m r
- fromLazy :: Monad m => ByteString -> ByteStream m ()
- toLazy :: Monad m => ByteStream m r -> m (Of ByteString r)
- toLazy_ :: Monad m => ByteStream m r -> m ByteString
- fromChunks :: Monad m => Stream (Of ByteString) m r -> ByteStream m r
- toChunks :: Monad m => ByteStream m r -> Stream (Of ByteString) m r
- fromStrict :: ByteString -> ByteStream m ()
- toStrict :: Monad m => ByteStream m r -> m (Of ByteString r)
- toStrict_ :: Monad m => ByteStream m r -> m ByteString
- effects :: Monad m => ByteStream m r -> m r
- copy :: Monad m => ByteStream m r -> ByteStream (ByteStream m) r
- drained :: (Monad m, MonadTrans t, Monad (t m)) => t m (ByteStream m r) -> t m r
- mwrap :: m (ByteStream m r) -> ByteStream m r
- map :: Monad m => (Word8 -> Word8) -> ByteStream m r -> ByteStream m r
- intercalate :: Monad m => ByteStream m () -> Stream (ByteStream m) m r -> ByteStream m r
- intersperse :: Monad m => Word8 -> ByteStream m r -> ByteStream m r
- cons :: Monad m => Word8 -> ByteStream m r -> ByteStream m r
- cons' :: Word8 -> ByteStream m r -> ByteStream m r
- snoc :: Monad m => ByteStream m r -> Word8 -> ByteStream m r
- append :: Monad m => ByteStream m r -> ByteStream m s -> ByteStream m s
- filter :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m r
- uncons :: Monad m => ByteStream m r -> m (Either r (Word8, ByteStream m r))
- nextByte :: Monad m => ByteStream m r -> m (Either r (Word8, ByteStream m r))
- break :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m (ByteStream m r)
- drop :: Monad m => Int64 -> ByteStream m r -> ByteStream m r
- dropWhile :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m r
- group :: Monad m => ByteStream m r -> Stream (ByteStream m) m r
- groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> ByteStream m r -> Stream (ByteStream m) m r
- span :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m (ByteStream m r)
- splitAt :: Monad m => Int64 -> ByteStream m r -> ByteStream m (ByteStream m r)
- splitWith :: Monad m => (Word8 -> Bool) -> ByteStream m r -> Stream (ByteStream m) m r
- take :: Monad m => Int64 -> ByteStream m r -> ByteStream m ()
- takeWhile :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m ()
- split :: Monad m => Word8 -> ByteStream m r -> Stream (ByteStream m) m r
- concat :: Monad m => Stream (ByteStream m) m r -> ByteStream m r
- denull :: Monad m => Stream (ByteStream m) m r -> Stream (ByteStream m) m r
- toStreamingByteString :: MonadIO m => Builder -> ByteStream m ()
- toStreamingByteStringWith :: MonadIO m => AllocationStrategy -> Builder -> ByteStream m ()
- toBuilder :: ByteStream IO () -> Builder
- concatBuilders :: Stream (Of Builder) IO () -> Builder
- repeat :: Word8 -> ByteStream m r
- iterate :: (Word8 -> Word8) -> Word8 -> ByteStream m r
- cycle :: Monad m => ByteStream m r -> ByteStream m s
- unfoldM :: Monad m => (a -> Maybe (Word8, a)) -> a -> ByteStream m ()
- unfoldr :: (a -> Either r (Word8, a)) -> a -> ByteStream m r
- reread :: Monad m => (s -> m (Maybe ByteString)) -> s -> ByteStream m ()
- foldr :: Monad m => (Word8 -> a -> a) -> a -> ByteStream m () -> m a
- fold :: Monad m => (x -> Word8 -> x) -> x -> (x -> b) -> ByteStream m r -> m (Of b r)
- fold_ :: Monad m => (x -> Word8 -> x) -> x -> (x -> b) -> ByteStream m () -> m b
- head :: Monad m => ByteStream m r -> m (Of (Maybe Word8) r)
- head_ :: Monad m => ByteStream m r -> m Word8
- last :: Monad m => ByteStream m r -> m (Of (Maybe Word8) r)
- last_ :: Monad m => ByteStream m r -> m Word8
- length :: Monad m => ByteStream m r -> m (Of Int r)
- length_ :: Monad m => ByteStream m r -> m Int
- null :: Monad m => ByteStream m r -> m (Of Bool r)
- null_ :: Monad m => ByteStream m r -> m Bool
- nulls :: Monad m => ByteStream m r -> m (Sum (ByteStream m) (ByteStream m) r)
- testNull :: Monad m => ByteStream m r -> m (Of Bool (ByteStream m r))
- count :: Monad m => Word8 -> ByteStream m r -> m (Of Int r)
- count_ :: Monad m => Word8 -> ByteStream m r -> m Int
- getContents :: MonadIO m => ByteStream m ()
- stdin :: MonadIO m => ByteStream m ()
- stdout :: MonadIO m => ByteStream m r -> m r
- interact :: (ByteStream IO () -> ByteStream IO r) -> IO r
- readFile :: MonadResource m => FilePath -> ByteStream m ()
- writeFile :: MonadResource m => FilePath -> ByteStream m r -> m r
- appendFile :: MonadResource m => FilePath -> ByteStream m r -> m r
- fromHandle :: MonadIO m => Handle -> ByteStream m ()
- toHandle :: MonadIO m => Handle -> ByteStream m r -> m r
- hGet :: MonadIO m => Handle -> Int -> ByteStream m ()
- hGetContents :: MonadIO m => Handle -> ByteStream m ()
- hGetContentsN :: MonadIO m => Int -> Handle -> ByteStream m ()
- hGetN :: MonadIO m => Int -> Handle -> Int -> ByteStream m ()
- hGetNonBlocking :: MonadIO m => Handle -> Int -> ByteStream m ()
- hGetNonBlockingN :: MonadIO m => Int -> Handle -> Int -> ByteStream m ()
- hPut :: MonadIO m => Handle -> ByteStream m r -> m r
- unconsChunk :: Monad m => ByteStream m r -> m (Either r (ByteString, ByteStream m r))
- nextChunk :: Monad m => ByteStream m r -> m (Either r (ByteString, ByteStream m r))
- chunk :: ByteString -> ByteStream m ()
- foldrChunks :: Monad m => (ByteString -> a -> a) -> a -> ByteStream m r -> m a
- foldlChunks :: Monad m => (a -> ByteString -> a) -> a -> ByteStream m r -> m (Of a r)
- chunkFold :: Monad m => (x -> ByteString -> x) -> x -> (x -> a) -> ByteStream m r -> m (Of a r)
- chunkFoldM :: Monad m => (x -> ByteString -> m x) -> m x -> (x -> m a) -> ByteStream m r -> m (Of a r)
- chunkMap :: Monad m => (ByteString -> ByteString) -> ByteStream m r -> ByteStream m r
- chunkMapM :: Monad m => (ByteString -> m ByteString) -> ByteStream m r -> ByteStream m r
- chunkMapM_ :: Monad m => (ByteString -> m x) -> ByteStream m r -> m r
- dematerialize :: Monad m => ByteStream m r -> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
- materialize :: (forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x) -> ByteStream m r
- distribute :: (Monad m, MonadTrans t, MFunctor t, Monad (t m), Monad (t (ByteStream m))) => ByteStream (t m) a -> t (ByteStream m) a
- zipWithStream :: Monad m => (forall x. a -> ByteStream m x -> ByteStream m x) -> [a] -> Stream (ByteStream m) m r -> Stream (ByteStream m) m r
The ByteStream type
data ByteStream m r Source #
A space-efficient representation of a succession of Word8 vectors,
supporting many efficient operations.
An effectful ByteStream contains 8-bit bytes, or by using the operations
from Streaming.ByteString.Char8 it can be interpreted as containing
8-bit characters.
Instances
type ByteString = ByteStream Source #
Deprecated: Use ByteStream instead.
A type alias for back-compatibility.
Introducing and eliminating ByteStreams
empty :: ByteStream m () Source #
O(1) The empty ByteStream -- i.e. return () Note that ByteStream m w is
generally a monoid for monoidal values of w, like ().
singleton :: Monad m => Word8 -> ByteStream m () Source #
O(1) Yield a Word8 as a minimal ByteStream.
pack :: Monad m => Stream (Of Word8) m r -> ByteStream m r Source #
O(n) Convert a monadic stream of individual Word8s into a packed byte stream.
unpack :: Monad m => ByteStream m r -> Stream (Of Word8) m r Source #
O(n) Converts a packed byte stream into a stream of individual bytes.
fromLazy :: Monad m => ByteString -> ByteStream m () Source #
O(c) Transmute a pseudo-pure lazy bytestring to its representation as a monadic stream of chunks.
>>>Q.putStrLn $ Q.fromLazy "hi"hi>>>Q.fromLazy "hi"Chunk "hi" (Empty (())) -- note: a 'show' instance works in the identity monad>>>Q.fromLazy $ BL.fromChunks ["here", "are", "some", "chunks"]Chunk "here" (Chunk "are" (Chunk "some" (Chunk "chunks" (Empty (())))))
toLazy :: Monad m => ByteStream m r -> m (Of ByteString r) Source #
O(n) Convert an effectful byte stream into a single lazy ByteString
with the same internal chunk structure, retaining the original return value.
This is the canonical way of breaking streaming (toStrict and the like are
far more demonic). Essentially one is dividing the interleaved layers of
effects and bytes into one immense layer of effects, followed by the memory
of the succession of bytes.
Because one preserves the return value, toLazy is a suitable argument for
mapped:
S.mapped Q.toLazy :: Stream (ByteStream m) m r -> Stream (Of L.ByteString) m r
>>>Q.toLazy "hello""hello" :> ()>>>S.toListM $ traverses Q.toLazy $ Q.lines "one\ntwo\nthree\nfour\nfive\n"["one","two","three","four","five",""] -- [L.ByteString]
toLazy_ :: Monad m => ByteStream m r -> m ByteString Source #
O(n) Convert an effectful byte stream into a single lazy ByteStream
with the same internal chunk structure. See toLazy which preserve
connectedness by keeping the return value of the effectful bytestring.
fromChunks :: Monad m => Stream (Of ByteString) m r -> ByteStream m r Source #
O(c) Convert a monadic stream of individual strict ByteString chunks
into a byte stream.
toChunks :: Monad m => ByteStream m r -> Stream (Of ByteString) m r Source #
O(c) Convert a byte stream into a stream of individual strict bytestrings. This of course exposes the internal chunk structure.
fromStrict :: ByteString -> ByteStream m () Source #
O(1) Yield a strict ByteString chunk.
toStrict :: Monad m => ByteStream m r -> m (Of ByteString r) Source #
O(n) Convert a monadic byte stream into a single strict ByteString,
retaining the return value of the original pair. This operation is for use
with mapped.
mapped R.toStrict :: Monad m => Stream (ByteStream m) m r -> Stream (Of ByteString) m r
It is subject to all the objections one makes to Data.ByteString.Lazy
toStrict; all of these are devastating.
toStrict_ :: Monad m => ByteStream m r -> m ByteString Source #
O(n) Convert a byte stream into a single strict ByteString.
Note that this is an expensive operation that forces the whole monadic ByteString into memory and then copies all the data. If possible, try to avoid converting back and forth between streaming and strict bytestrings.
effects :: Monad m => ByteStream m r -> m r Source #
Perform the effects contained in an effectful bytestring, ignoring the bytes.
copy :: Monad m => ByteStream m r -> ByteStream (ByteStream m) r Source #
Make the information in a bytestring available to more than one eliminating fold, e.g.
>>>Q.count 'l' $ Q.count 'o' $ Q.copy $ "hello\nworld"3 :> (2 :> ())
>>>Q.length $ Q.count 'l' $ Q.count 'o' $ Q.copy $ Q.copy "hello\nworld"11 :> (3 :> (2 :> ()))
>>>runResourceT $ Q.writeFile "hello2.txt" $ Q.writeFile "hello1.txt" $ Q.copy $ "hello\nworld\n">>>:! cat hello2.txthello world>>>:! cat hello1.txthello world
This sort of manipulation could as well be acheived by combining folds - using
Control.Foldl for example. But any sort of manipulation can be involved in
the fold. Here are a couple of trivial complications involving splitting by lines:
>>>let doubleLines = Q.unlines . maps (<* Q.chunk "\n" ) . Q.lines>>>let emphasize = Q.unlines . maps (<* Q.chunk "!" ) . Q.lines>>>runResourceT $ Q.writeFile "hello2.txt" $ emphasize $ Q.writeFile "hello1.txt" $ doubleLines $ Q.copy $ "hello\nworld">>>:! cat hello2.txthello! world!>>>:! cat hello1.txthello world
As with the parallel operations in Streaming.Prelude, we have
Q.effects . Q.copy = id hoist Q.effects . Q.copy = id
The duplication does not by itself involve the copying of bytestring chunks; it just makes two references to each chunk as it arises. This does, however double the number of constructors associated with each chunk.
drained :: (Monad m, MonadTrans t, Monad (t m)) => t m (ByteStream m r) -> t m r Source #
Perform the effects contained in the second in an effectful pair of bytestrings, ignoring the bytes. It would typically be used at the type
ByteStream m (ByteStream m r) -> ByteStream m r
mwrap :: m (ByteStream m r) -> ByteStream m r Source #
Reconceive an effect that results in an effectful bytestring as an effectful bytestring. Compare Streaming.mwrap. The closest equivalent of
>>>Streaming.wrap :: f (Stream f m r) -> Stream f m r
is here consChunk. mwrap is the smart constructor for the internal Go constructor.
Transforming ByteStreams
map :: Monad m => (Word8 -> Word8) -> ByteStream m r -> ByteStream m r Source #
O(n) map f xs is the ByteStream obtained by applying f to each
element of xs.
intercalate :: Monad m => ByteStream m () -> Stream (ByteStream m) m r -> ByteStream m r Source #
O(n) The intercalate function takes a ByteStream and a list of
ByteStreams and concatenates the list after interspersing the first
argument between each element of the list.
intersperse :: Monad m => Word8 -> ByteStream m r -> ByteStream m r Source #
The intersperse function takes a Word8 and a ByteStream and
`intersperses' that byte between the elements of the ByteStream. It is
analogous to the intersperse function on Streams.
Basic interface
cons :: Monad m => Word8 -> ByteStream m r -> ByteStream m r Source #
O(1) cons is analogous to (:) for lists.
cons' :: Word8 -> ByteStream m r -> ByteStream m r Source #
O(1) Unlike cons, 'cons'' is strict in the ByteString that we are
consing onto. More precisely, it forces the head and the first chunk. It does
this because, for space efficiency, it may coalesce the new byte onto the
first 'chunk' rather than starting a new 'chunk'.
So that means you can't use a lazy recursive contruction like this:
let xs = cons\' c xs in xs
You can however use cons, as well as repeat and cycle, to build
infinite byte streams.
snoc :: Monad m => ByteStream m r -> Word8 -> ByteStream m r Source #
O(n/c) Append a byte to the end of a ByteStream.
append :: Monad m => ByteStream m r -> ByteStream m s -> ByteStream m s Source #
O(n/c) Append two ByteStrings together.
filter :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m r Source #
O(n) filter, applied to a predicate and a ByteStream, returns a
ByteStream containing those characters that satisfy the predicate.
uncons :: Monad m => ByteStream m r -> m (Either r (Word8, ByteStream m r)) Source #
O(1) Extract the head and tail of a ByteStream, or its return value if
it is empty. This is the 'natural' uncons for an effectful byte stream.
nextByte :: Monad m => ByteStream m r -> m (Either r (Word8, ByteStream m r)) Source #
Deprecated: Use uncons instead.
The same as uncons, will be removed in the next version.
Substrings
Breaking strings
break :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m (ByteStream m r) Source #
drop :: Monad m => Int64 -> ByteStream m r -> ByteStream m r Source #
dropWhile :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m r Source #
group :: Monad m => ByteStream m r -> Stream (ByteStream m) m r Source #
The group function takes a ByteStream and returns a list of ByteStreams
such that the concatenation of the result is equal to the argument. Moreover,
each sublist in the result contains only equal elements. For example,
group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
It is a special case of groupBy, which allows the programmer to supply
their own equality test.
groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> ByteStream m r -> Stream (ByteStream m) m r Source #
span :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m (ByteStream m r) Source #
splitAt :: Monad m => Int64 -> ByteStream m r -> ByteStream m (ByteStream m r) Source #
splitWith :: Monad m => (Word8 -> Bool) -> ByteStream m r -> Stream (ByteStream m) m r Source #
O(n) Splits a ByteStream into components delimited by separators, where
the predicate returns True for a separator element. The resulting components
do not contain the separators. Two adjacent separators result in an empty
component in the output. eg.
splitWith (=='a') "aabbaca" == ["","","bb","c",""] splitWith (=='a') [] == []
take :: Monad m => Int64 -> ByteStream m r -> ByteStream m () Source #
O(n/c) take n, applied to a ByteStream xs, returns the prefix
of xs of length n, or xs itself if n > .length xs
Note that in the streaming context this drops the final return value;
splitAt preserves this information, and is sometimes to be preferred.
>>>Q.putStrLn $ Q.take 8 $ "Is there a God?" >> return TrueIs there>>>Q.putStrLn $ "Is there a God?" >> return TrueIs there a God? True>>>rest <- Q.putStrLn $ Q.splitAt 8 $ "Is there a God?" >> return TrueIs there>>>Q.effects restTrue
takeWhile :: Monad m => (Word8 -> Bool) -> ByteStream m r -> ByteStream m () Source #
takeWhile, applied to a predicate p and a ByteStream xs, returns the
longest prefix (possibly empty) of xs of elements that satisfy p.
Breaking into many substrings
split :: Monad m => Word8 -> ByteStream m r -> Stream (ByteStream m) m r Source #
O(n) Break a ByteStream into pieces separated by the byte
argument, consuming the delimiter. I.e.
split '\n' "a\nb\nd\ne" == ["a","b","d","e"] split 'a' "aXaXaXa" == ["","X","X","X",""] split 'x' "x" == ["",""]
and
intercalate [c] . split c == id split == splitWith . (==)
As for all splitting functions in this library, this function does not copy
the substrings, it just constructs new ByteStreams that are slices of the
original.
Special folds
concat :: Monad m => Stream (ByteStream m) m r -> ByteStream m r Source #
O(n) Concatenate a stream of byte streams.
denull :: Monad m => Stream (ByteStream m) m r -> Stream (ByteStream m) m r Source #
Remove empty ByteStrings from a stream of bytestrings.
Builders
toStreamingByteString :: MonadIO m => Builder -> ByteStream m () Source #
Take a builder constructed otherwise and convert it to a genuine streaming bytestring.
>>>Q.putStrLn $ Q.toStreamingByteString $ stringUtf8 "哈斯克尔" <> stringUtf8 " " <> integerDec 98哈斯克尔 98
This benchmark shows
its performance is indistinguishable from toLazyByteString
toStreamingByteStringWith :: MonadIO m => AllocationStrategy -> Builder -> ByteStream m () Source #
Take a builder and convert it to a genuine streaming bytestring, using a specific allocation strategy.
toBuilder :: ByteStream IO () -> Builder Source #
A simple construction of a builder from a ByteString.
>>>let aaa = "10000 is a number\n" :: Q.ByteString IO ()>>>hPutBuilder IO.stdout $ toBuilder aaa10000 is a number
concatBuilders :: Stream (Of Builder) IO () -> Builder Source #
Concatenate a stream of builders (not a streaming bytestring!) into a single builder.
>>>let aa = yield (integerDec 10000) >> yield (string8 " is a number.") >> yield (char8 '\n')>>>hPutBuilder IO.stdout $ concatBuilders aa10000 is a number.
Building ByteStreams
Infinite ByteStreams
repeat :: Word8 -> ByteStream m r Source #
is an infinite ByteStream, with repeat xx the value of every
element.
>>>R.stdout $ R.take 50 $ R.repeat 60<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<>>>Q.putStrLn $ Q.take 50 $ Q.repeat 'z'zzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzz
iterate :: (Word8 -> Word8) -> Word8 -> ByteStream m r Source #
returns an infinite ByteStream of repeated applications
-- of iterate f xf to x:
iterate f x == [x, f x, f (f x), ...]
>>>R.stdout $ R.take 50 $ R.iterate succ 39()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXY>>>Q.putStrLn $ Q.take 50 $ Q.iterate succ '\''()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXY
cycle :: Monad m => ByteStream m r -> ByteStream m s Source #
cycle ties a finite ByteStream into a circular one, or equivalently,
the infinite repetition of the original ByteStream. For an empty bytestring
(like return 17) it of course makes an unproductive loop
>>>Q.putStrLn $ Q.take 7 $ Q.cycle "y\n"y y y y
Unfolding ByteStreams
unfoldM :: Monad m => (a -> Maybe (Word8, a)) -> a -> ByteStream m () Source #
O(n) The unfoldM function is analogous to the Stream unfoldr.
unfoldM builds a ByteStream from a seed value. The function takes the
element and returns Nothing if it is done producing the ByteStream or
returns , in which case, Just (a,b)a is a prepending to the ByteStream
and b is used as the next element in a recursive call.
reread :: Monad m => (s -> m (Maybe ByteString)) -> s -> ByteStream m () Source #
Stream chunks from something that contains m (Maybe ByteString) until it
returns Nothing. reread is of particular use rendering io-streams input
streams as byte streams in the present sense.
import qualified Data.ByteString as B import qualified System.IO.Streams as S Q.reread S.read :: S.InputStream B.ByteString -> Q.ByteStream IO () Q.reread (liftIO . S.read) :: MonadIO m => S.InputStream B.ByteString -> Q.ByteStream m ()
The other direction here is
S.unfoldM Q.unconsChunk :: Q.ByteString IO r -> IO (S.InputStream B.ByteString)
Folds, including support for Foldl
foldr :: Monad m => (Word8 -> a -> a) -> a -> ByteStream m () -> m a Source #
foldr, applied to a binary operator, a starting value (typically the
right-identity of the operator), and a ByteStream, reduces the ByteStream
using the binary operator, from right to left.
fold :: Monad m => (x -> Word8 -> x) -> x -> (x -> b) -> ByteStream m r -> m (Of b r) Source #
fold keeps the return value of the left-folded bytestring. Useful for
simultaneous folds over a segmented bytestream.
fold_ :: Monad m => (x -> Word8 -> x) -> x -> (x -> b) -> ByteStream m () -> m b Source #
fold_, applied to a binary operator, a starting value (typically the
left-identity of the operator), and a ByteStream, reduces the ByteStream
using the binary operator, from left to right. We use the style of the foldl
library for left folds
head :: Monad m => ByteStream m r -> m (Of (Maybe Word8) r) Source #
O(c) Extract the first element of a ByteStream, if there is one.
Suitable for use with mapped:
S.mapped Q.head :: Stream (Q.ByteStream m) m r -> Stream (Of (Maybe Word8)) m r
head_ :: Monad m => ByteStream m r -> m Word8 Source #
O(1) Extract the first element of a ByteStream, which must be non-empty.
last :: Monad m => ByteStream m r -> m (Of (Maybe Word8) r) Source #
Extract the last element of a ByteStream, if possible. Suitable for use
with mapped:
S.mapped Q.last :: Streaming (ByteStream m) m r -> Stream (Of (Maybe Word8)) m r
last_ :: Monad m => ByteStream m r -> m Word8 Source #
O(n/c) Extract the last element of a ByteStream, which must be finite
and non-empty.
length_ :: Monad m => ByteStream m r -> m Int Source #
Like length, report the length in bytes of the ByteStream by running
through its contents. Since the return value is in the effect m, this is
one way to "get out" of the stream.
null :: Monad m => ByteStream m r -> m (Of Bool r) Source #
Test whether a ByteStream is empty, collecting its return value; to reach
the return value, this operation must check the whole length of the string.
>>>Q.null "one\ntwo\three\nfour\nfive\n"False :> ()>>>Q.null ""True :> ()>>>S.print $ mapped R.null $ Q.lines "yours,\nMeredith"False False
Suitable for use with mapped:
S.mapped Q.null :: Streaming (ByteStream m) m r -> Stream (Of Bool) m r
null_ :: Monad m => ByteStream m r -> m Bool Source #
O(1) Test whether a ByteStream is empty. The value is of course in the
monad of the effects.
>>>Q.null "one\ntwo\three\nfour\nfive\n"False>>>Q.null $ Q.take 0 Q.stdinTrue>>>:t Q.null $ Q.take 0 Q.stdinQ.null $ Q.take 0 Q.stdin :: MonadIO m => m Bool
nulls :: Monad m => ByteStream m r -> m (Sum (ByteStream m) (ByteStream m) r) Source #
O1 Distinguish empty from non-empty lines, while maintaining streaming; the empty ByteStrings are on the right
>>>nulls :: ByteStream m r -> m (Sum (ByteStream m) (ByteStream m) r)
There are many (generally slower) ways to remove null bytestrings from a
Stream (ByteStream m) m r (besides using denull). If we pass next to
>>>mapped nulls bs :: Stream (Sum (ByteStream m) (ByteStream m)) m r
then can then apply Streaming.separate to get
>>>separate (mapped nulls bs) :: Stream (ByteStream m) (Stream (ByteStream m) m) r
The inner monad is now made of the empty bytestrings; we act on this
with hoist , considering that
>>>:t Q.effects . Q.concatQ.effects . Q.concat :: Monad m => Stream (Q.ByteStream m) m r -> m r
we have
>>>hoist (Q.effects . Q.concat) . separate . mapped Q.nulls:: Monad n => Stream (Q.ByteStream n) n b -> Stream (Q.ByteStream n) n b
testNull :: Monad m => ByteStream m r -> m (Of Bool (ByteStream m r)) Source #
Similar to null, but yields the remainder of the ByteStream stream when
an answer has been determined.
count :: Monad m => Word8 -> ByteStream m r -> m (Of Int r) Source #
Returns the number of times its argument appears in the ByteStream.
Suitable for use with mapped:
S.mapped (Q.count 37) :: Stream (Q.ByteStream m) m r -> Stream (Of Int) m r
count_ :: Monad m => Word8 -> ByteStream m r -> m Int Source #
Returns the number of times its argument appears in the ByteStream.
count = length . elemIndices
I/O with ByteStreams
Standard input and output
getContents :: MonadIO m => ByteStream m () Source #
Equivalent to hGetContents stdin. Will read lazily.
stdin :: MonadIO m => ByteStream m () Source #
Pipes-style nomenclature for getContents.
stdout :: MonadIO m => ByteStream m r -> m r Source #
Pipes-style nomenclature for putStr.
interact :: (ByteStream IO () -> ByteStream IO r) -> IO r Source #
A synonym for hPut, for compatibility
hPutStr :: Handle -> ByteStream IO r -> IO r hPutStr = hPut
- - | Write a ByteStream to stdout putStr :: ByteStream IO r -> IO r putStr = hPut IO.stdout
The interact function takes a function of type ByteStream -> ByteStream
as its argument. The entire input from the standard input device is passed to
this function as its argument, and the resulting string is output on the
standard output device.
interact morph = stdout (morph stdin)
Files
readFile :: MonadResource m => FilePath -> ByteStream m () Source #
Read an entire file into a chunked . The handle will be
held open until EOF is encountered. The block governed by
ByteStream IO ()runResourceT will end with the closing of any
handles opened.
>>>:! cat hello.txtHello world. Goodbye world.>>>runResourceT $ Q.stdout $ Q.readFile "hello.txt"Hello world. Goodbye world.
writeFile :: MonadResource m => FilePath -> ByteStream m r -> m r Source #
Write a ByteStream to a file. Use
runResourceT to ensure that the handle is
closed.
>>>:set -XOverloadedStrings>>>runResourceT $ Q.writeFile "hello.txt" "Hello world.\nGoodbye world.\n">>>:! cat "hello.txt"Hello world. Goodbye world.>>>runResourceT $ Q.writeFile "hello2.txt" $ Q.readFile "hello.txt">>>:! cat hello2.txtHello world. Goodbye world.
appendFile :: MonadResource m => FilePath -> ByteStream m r -> m r Source #
Append a ByteStream to a file. Use
runResourceT to ensure that the handle is
closed.
>>>runResourceT $ Q.writeFile "hello.txt" "Hello world.\nGoodbye world.\n">>>runResourceT $ Q.stdout $ Q.readFile "hello.txt"Hello world. Goodbye world.>>>runResourceT $ Q.appendFile "hello.txt" "sincerely yours,\nArthur\n">>>runResourceT $ Q.stdout $ Q.readFile "hello.txt"Hello world. Goodbye world. sincerely yours, Arthur
I/O with Handles
fromHandle :: MonadIO m => Handle -> ByteStream m () Source #
Pipes-style nomenclature for hGetContents.
hGet :: MonadIO m => Handle -> Int -> ByteStream m () Source #
Read n bytes into a ByteStream, directly from the specified Handle.
hGetContents :: MonadIO m => Handle -> ByteStream m () Source #
Read entire handle contents lazily into a ByteStream. Chunks are read
on demand, using the default chunk size.
Note: the Handle should be placed in binary mode with
hSetBinaryMode for hGetContents to work correctly.
hGetContentsN :: MonadIO m => Int -> Handle -> ByteStream m () Source #
Read entire handle contents lazily into a ByteStream. Chunks are read
on demand, in at most k-sized chunks. It does not block waiting for a whole
k-sized chunk, so if less than k bytes are available then they will be
returned immediately as a smaller chunk.
Note: the Handle should be placed in binary mode with
hSetBinaryMode for hGetContentsN to work correctly.
hGetN :: MonadIO m => Int -> Handle -> Int -> ByteStream m () Source #
Read n bytes into a ByteStream, directly from the specified Handle,
in chunks of size k.
hGetNonBlocking :: MonadIO m => Handle -> Int -> ByteStream m () Source #
hGetNonBlocking is similar to hGet, except that it will never block
waiting for data to become available, instead it returns only whatever data
is available. If there is no data available to be read, hGetNonBlocking
returns empty.
Note: on Windows and with Haskell implementation other than GHC, this
function does not work correctly; it behaves identically to hGet.
hGetNonBlockingN :: MonadIO m => Int -> Handle -> Int -> ByteStream m () Source #
hGetNonBlockingN is similar to hGetContentsN, except that it will never
block waiting for data to become available, instead it returns only whatever
data is available. Chunks are read on demand, in k-sized chunks.
hPut :: MonadIO m => Handle -> ByteStream m r -> m r Source #
Outputs a ByteStream to the specified Handle.
Simple chunkwise operations
unconsChunk :: Monad m => ByteStream m r -> m (Either r (ByteString, ByteStream m r)) Source #
Like uncons, but yields the entire first ByteString chunk that the
stream is holding onto. If there wasn't one, it tries to fetch it. Yields
the final r return value when the ByteStream is empty.
nextChunk :: Monad m => ByteStream m r -> m (Either r (ByteString, ByteStream m r)) Source #
Deprecated: Use unconsChunk instead.
The same as unconsChunk, will be removed in the next version.
chunk :: ByteString -> ByteStream m () Source #
Yield-style smart constructor for Chunk.
foldrChunks :: Monad m => (ByteString -> a -> a) -> a -> ByteStream m r -> m a Source #
Consume the chunks of an effectful ByteString with a natural right fold.
foldlChunks :: Monad m => (a -> ByteString -> a) -> a -> ByteStream m r -> m (Of a r) Source #
Consume the chunks of an effectful ByteString with a left fold. Suitable
for use with mapped.
chunkFold :: Monad m => (x -> ByteString -> x) -> x -> (x -> a) -> ByteStream m r -> m (Of a r) Source #
chunkFold is preferable to foldlChunks since it is an appropriate
argument for Control.Foldl.purely which permits many folds and sinks to be
run simultaneously on one bytestream.
chunkFoldM :: Monad m => (x -> ByteString -> m x) -> m x -> (x -> m a) -> ByteStream m r -> m (Of a r) Source #
chunkFoldM is preferable to foldlChunksM since it is an appropriate
argument for impurely which permits many folds and sinks to
be run simultaneously on one bytestream.
chunkMap :: Monad m => (ByteString -> ByteString) -> ByteStream m r -> ByteStream m r Source #
Instead of mapping over each Word8 or Char, map over each strict
ByteString chunk in the stream.
chunkMapM :: Monad m => (ByteString -> m ByteString) -> ByteStream m r -> ByteStream m r Source #
Like chunkMap, but map effectfully.
chunkMapM_ :: Monad m => (ByteString -> m x) -> ByteStream m r -> m r Source #
Like chunkMapM, but discard the result of each effectful mapping.
Etc.
dematerialize :: Monad m => ByteStream m r -> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x Source #
Resolve a succession of chunks into its Church encoding; this is not a safe operation; it is equivalent to exposing the constructors
materialize :: (forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x) -> ByteStream m r Source #
Construct a succession of chunks from its Church encoding (compare GHC.Exts.build)
distribute :: (Monad m, MonadTrans t, MFunctor t, Monad (t m), Monad (t (ByteStream m))) => ByteStream (t m) a -> t (ByteStream m) a Source #
Given a byte stream on a transformed monad, make it possible to 'run' transformer.
zipWithStream :: Monad m => (forall x. a -> ByteStream m x -> ByteStream m x) -> [a] -> Stream (ByteStream m) m r -> Stream (ByteStream m) m r Source #
Zip a list and a stream-of-byte-streams together.