streaming-bytestring-0.3.2: Fast, effectful byte streams.
Copyright(c) Don Stewart 2006
(c) Duncan Coutts 2006-2011
(c) Michael Thompson 2015
LicenseBSD-style
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streaming.ByteString.Char8

Description

This library emulates Data.ByteString.Lazy.Char8 but includes a monadic element and thus at certain points uses a Stream/FreeT type in place of lists. See the documentation for Streaming.ByteString and the examples of of use to implement simple shell operations here. Examples of use with http-client, attoparsec, aeson, zlib etc. can be found in the 'streaming-utils' library.

Synopsis

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

Instances details
MonadTrans ByteStream Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

lift :: Monad m => m a -> ByteStream m a #

MFunctor ByteStream Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> ByteStream m b -> ByteStream n b #

MonadBase b m => MonadBase b (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

liftBase :: b α -> ByteStream m α #

MonadIO m => MonadIO (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

liftIO :: IO a -> ByteStream m a #

Monad m => Applicative (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

pure :: a -> ByteStream m a #

(<*>) :: ByteStream m (a -> b) -> ByteStream m a -> ByteStream m b #

liftA2 :: (a -> b -> c) -> ByteStream m a -> ByteStream m b -> ByteStream m c #

(*>) :: ByteStream m a -> ByteStream m b -> ByteStream m b #

(<*) :: ByteStream m a -> ByteStream m b -> ByteStream m a #

Monad m => Functor (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

fmap :: (a -> b) -> ByteStream m a -> ByteStream m b #

(<$) :: a -> ByteStream m b -> ByteStream m a #

Monad m => Monad (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

(>>=) :: ByteStream m a -> (a -> ByteStream m b) -> ByteStream m b #

(>>) :: ByteStream m a -> ByteStream m b -> ByteStream m b #

return :: a -> ByteStream m a #

MonadCatch m => MonadCatch (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

catch :: Exception e => ByteStream m a -> (e -> ByteStream m a) -> ByteStream m a #

MonadThrow m => MonadThrow (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

throwM :: Exception e => e -> ByteStream m a #

MonadResource m => MonadResource (ByteStream m) Source # 
Instance details

Defined in Streaming.ByteString.Internal

r ~ () => IsString (ByteStream m r) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

fromString :: String -> ByteStream m r #

(Monoid r, Monad m) => Monoid (ByteStream m r) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

mempty :: ByteStream m r #

mappend :: ByteStream m r -> ByteStream m r -> ByteStream m r #

mconcat :: [ByteStream m r] -> ByteStream m r #

(Semigroup r, Monad m) => Semigroup (ByteStream m r) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

(<>) :: ByteStream m r -> ByteStream m r -> ByteStream m r #

sconcat :: NonEmpty (ByteStream m r) -> ByteStream m r #

stimes :: Integral b => b -> ByteStream m r -> ByteStream m r #

(m ~ Identity, Show r) => Show (ByteStream m r) Source # 
Instance details

Defined in Streaming.ByteString.Internal

Methods

showsPrec :: Int -> ByteStream m r -> ShowS #

show :: ByteStream m r -> String #

showList :: [ByteStream m r] -> ShowS #

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 ().

pack :: Monad m => Stream (Of Char) m r -> ByteStream m r Source #

O(n) Convert a stream of separate characters into a packed byte stream.

unpack :: Monad m => ByteStream m r -> Stream (Of Char) m r Source #

Given a stream of bytes, produce a vanilla Stream of characters.

string :: String -> ByteStream m () Source #

Promote a vanilla String into a stream.

Note: Each Char is truncated to 8 bits.

unlines :: Monad m => Stream (ByteStream m) m r -> ByteStream m r Source #

The unlines function restores line breaks between layers.

Note that this is not a perfect inverse of lines:

  • lines . unlines can produce more strings than there were if some of the "lines" had embedded newlines.
  • unlines . lines will replace \r\n with \n.

unwords :: Monad m => Stream (ByteStream m) m r -> ByteStream m r Source #

The unwords function is analogous to the unlines function, on words.

singleton :: Monad m => Char -> ByteStream m () Source #

O(1) Yield a Char as a minimal ByteStream

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.

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 (())))))

fromStrict :: ByteString -> ByteStream m () Source #

O(1) Yield a strict ByteString chunk.

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.

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.

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.txt
hello
world
>>> :! cat hello1.txt
hello
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.txt
hello!
world!
>>> :! cat hello1.txt
hello

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 => (Char -> Char) -> 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 => Char -> ByteStream m r -> ByteStream m r Source #

The intersperse function takes a Char 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 => Char -> ByteStream m r -> ByteStream m r Source #

O(1) Cons a Char onto a byte stream.

cons' :: Char -> 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 lazy ByteStreams.

snoc :: Monad m => ByteStream m r -> Char -> 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 => (Char -> 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.

head :: Monad m => ByteStream m r -> m (Of (Maybe Char) r) Source #

O(1) Extract the first element of a ByteStream, if possible. Suitable for use with mapped:

S.mapped Q.head :: Stream (Q.ByteStream m) m r -> Stream (Of (Maybe Char)) m r

head_ :: Monad m => ByteStream m r -> m Char Source #

O(1) Extract the first element of a ByteStream, which must be non-empty.

last :: Monad m => ByteStream m r -> m (Of (Maybe Char) 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 Char)) m r

last_ :: Monad m => ByteStream m r -> m Char Source #

O(n/c) Extract the last element of a ByteStream, which must be finite and non-empty.

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.stdin
True
>>> :t Q.null $ Q.take 0 Q.stdin
Q.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.concat
Q.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.

uncons :: Monad m => ByteStream m r -> m (Either r (Char, 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.

nextChar :: Monad m => ByteStream m r -> m (Either r (Char, ByteStream m r)) Source #

Deprecated: Use uncons instead.

The same as uncons, will be removed in the next version.

skipSomeWS :: Monad m => ByteStream m r -> ByteStream m r Source #

Try to position the stream at the next non-whitespace input, by skipping leading whitespace. Only a reasonable quantity of whitespace will be skipped before giving up and returning the rest of the stream with any remaining whitespace. Limiting the amount of whitespace consumed is a safety mechanism to avoid looping forever on a never-ending stream of whitespace from an untrusted source. For unconditional dropping of all leading whitespace, use dropWhile with a suitable predicate.

Substrings

Breaking strings

break :: Monad m => (Char -> Bool) -> ByteStream m r -> ByteStream m (ByteStream m r) Source #

break p is equivalent to span (not . p).

drop :: Monad m => Int64 -> ByteStream m r -> ByteStream m r Source #

O(n/c) drop n xs returns the suffix of xs after the first n elements, or [] if n > length xs.

>>> Q.putStrLn $ Q.drop 6 "Wisconsin"
sin
>>> Q.putStrLn $ Q.drop 16 "Wisconsin"

dropWhile :: Monad m => (Char -> Bool) -> ByteStream m r -> ByteStream m r Source #

dropWhile p xs returns the suffix remaining after takeWhile p xs.

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 => (Char -> Char -> Bool) -> ByteStream m r -> Stream (ByteStream m) m r Source #

The groupBy function is a generalized version of group.

span :: Monad m => (Char -> Bool) -> ByteStream m r -> ByteStream m (ByteStream m r) Source #

span p xs breaks the ByteStream into two segments. It is equivalent to (takeWhile p xs, dropWhile p xs)

splitAt :: Monad m => Int64 -> ByteStream m r -> ByteStream m (ByteStream m r) Source #

O(n/c) splitAt n xs is equivalent to (take n xs, drop n xs).

>>> rest <- Q.putStrLn $ Q.splitAt 3 "therapist is a danger to good hyphenation, as Knuth notes"
the
>>> Q.putStrLn $ Q.splitAt 19 rest
rapist is a danger

splitWith :: Monad m => (Char -> Bool) -> ByteStream m r -> Stream (ByteStream m) m r Source #

Like split, but you can supply your own splitting predicate.

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 True
Is there
>>> Q.putStrLn $ "Is there a God?" >> return True
Is there a God?
True
>>> rest <- Q.putStrLn $ Q.splitAt 8 $ "Is there a God?" >> return True
Is there
>>> Q.effects  rest
True

takeWhile :: Monad m => (Char -> 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 => Char -> 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.

>>> Q.stdout $ Q.unlines $ Q.split 'n' "banana peel"
ba
a
a peel

lines :: forall m r. Monad m => ByteStream m r -> Stream (ByteStream m) m r Source #

lines turns a ByteStream into a connected stream of ByteStreams at divide at newline characters. The resulting strings do not contain newlines. This is the genuinely streaming lines which only breaks chunks, and thus never increases the use of memory.

Because ByteStreams are usually read in binary mode, with no line ending conversion, this function recognizes both \n and \r\n endings (regardless of the current platform).

lineSplit Source #

Arguments

:: forall m r. Monad m 
=> Int

number of lines per group

-> ByteStream m r

stream of bytes

-> Stream (ByteStream m) m r 

lineSplit turns a ByteStream into a connected stream of ByteStreams at divide after a fixed number of newline characters. Unlike most of the string splitting functions in this library, this function preserves newlines characters.

Like lines, this function properly handles both \n and \r\n endings regardless of the current platform. It does not support \r or \n\r line endings.

>>> let planets = ["Mercury","Venus","Earth","Mars","Saturn","Jupiter","Neptune","Uranus"]
>>> S.mapsM_ (\x -> putStrLn "Chunk" >> Q.putStrLn x) $ Q.lineSplit 3 $ Q.string $ L.unlines planets
Chunk
Mercury
Venus
Earth

Chunk Mars Saturn Jupiter

Chunk Neptune Uranus

Since all characters originally present in the stream are preserved, this function satisfies the following law:

Ɐ n bs. concat (lineSplit n bs) ≅ bs

words :: Monad m => ByteStream m r -> Stream (ByteStream m) m r Source #

words breaks a byte stream up into a succession of byte streams corresponding to words, breaking on Chars representing white space. This is the genuinely streaming words. A function that returns individual strict bytestrings would concatenate even infinitely long words like cycle "y" in memory. When the stream is known to not contain unreasonably long words, you can write mapped toStrict . words or the like, if strict bytestrings are needed.

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  aaa
10000 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 aa
10000 is a number.

Building ByteStreams

Infinite ByteStreams

repeat :: Char -> ByteStream m r Source #

repeat x is an infinite ByteStream, with x the value of every element.

iterate :: (Char -> Char) -> Char -> ByteStream m r Source #

iterate f x returns an infinite ByteStream of repeated applications of f to x:

iterate f x == [x, f x, f (f x), ...]

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

unfoldr :: (a -> Either r (Char, a)) -> a -> ByteStream m r Source #

Given some pure process that produces characters, generate a stream of bytes. The r produced by the final Left will be the return value at the end of the stream. Note also that the Char values will be truncated to 8-bits.

unfoldM :: Monad m => (a -> Maybe (Char, a)) -> a -> ByteStream m () Source #

cycle ties a finite ByteStream into a circular one, or equivalently, the infinite repetition of the original ByteStream.

| 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 Just (a,b), in which case, 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

fold :: Monad m => (x -> Char -> x) -> x -> (x -> b) -> ByteStream m r -> m (Of b r) Source #

Like fold_, but suitable for use with mapped.

fold_ :: Monad m => (x -> Char -> x) -> x -> (x -> b) -> ByteStream m () -> m b Source #

fold_ keeps the return value of the left-folded bytestring. Useful for simultaneous folds over a segmented bytestream.

length :: Monad m => ByteStream m r -> m (Of Int r) Source #

O(n/c) length returns the length of a byte stream as an Int together with the return value. This makes various maps possible.

>>> Q.length "one\ntwo\three\nfour\nfive\n"
23 :> ()
>>> S.print $ S.take 3 $ mapped Q.length $ Q.lines "one\ntwo\three\nfour\nfive\n"
3
8
4

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.

count :: Monad m => Char -> 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 'a') :: Stream (Q.ByteStream m) m r -> Stream (Of Int) m r

count_ :: Monad m => Char -> ByteStream m r -> m Int Source #

Returns the number of times its argument appears in the ByteStream.

readInt :: Monad m => ByteStream m r -> m (Compose (Of (Maybe Int)) (ByteStream m) r) Source #

Try to read an Int value from the ByteString, returning m (Compose (Just val :> str)) on success, where val is the value read and str is the rest of the input stream. If the stream of digits decodes to a value larger than can be represented by an Int, the returned value will be m (Compose (Nothing :> str)), where the content of str is the same as the original stream, but some of the monadic effects may already have taken place, so the original stream MUST NOT be used. To read the remaining data, you MUST use the returned str.

This function will not read an unreasonably long stream of leading zero digits when trying to decode a number. When reading the first non-zero digit would require requesting a new chunk and ~32KB of leading zeros have already been read, the conversion is aborted and Nothing is returned, along with the overly long run of leading zeros (and any initial explicit plus or minus sign).

readInt does not ignore leading whitespace, the value must start immediately at the beginning of the input stream. Use skipSomeWS if you want to skip a reasonable quantity of leading whitespace.

Example

Expand
>>> getCompose <$> (readInt . skipSomeWS) stream >>= \case
>>> Just n  :> rest -> print n >> gladly rest
>>> Nothing :> rest -> sadly rest

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)

putStr :: MonadIO m => ByteStream m r -> m r Source #

Print a stream of bytes to STDOUT.

putStrLn :: MonadIO m => ByteStream m r -> m r Source #

Print a stream of bytes to STDOUT, ending with a final n.

Note: The final n is not added atomically, and in certain multi-threaded scenarios might not appear where expected.

Files

readFile :: MonadResource m => FilePath -> ByteStream m () Source #

Read an entire file into a chunked ByteStream IO (). The handle will be held open until EOF is encountered. The block governed by runResourceT will end with the closing of any handles opened.

>>> :! cat hello.txt
Hello 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.txt
Hello 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.

toHandle :: MonadIO m => Handle -> ByteStream m r -> m r Source #

Pipes nomenclature for hPut.

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.