streaming-bytestring-0.1.0.1: Lazy bytestring done right

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.Streaming.Char8

Contents

Synopsis

The ByteString type

data ByteString m r Source

A space-efficient representation of a succession of Word8 vectors, supporting many efficient operations.

An effectful ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Streaming.Char8 it can be interpreted as containing 8-bit characters.

Introducing and eliminating ByteStrings

empty :: ByteString m () Source

O(1) The empty ByteString -- i.e. return ()

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

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

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

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

The unlines function restores line breaks between layers

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

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

unwordsIndividual :: Monad m => Stream (Of ByteString) m r -> ByteString m r Source

unwordsIndividual returns to a genuine bytestream by interspersing white space between a sequence of individual Data.ByteString.ByteString Distinguish the types

unwordsIndividual :: Monad m => Stream (Of B.ByteString) m r -> ByteString m r 
unwords :: Monad m => Stream (ByteString m) m r -> ByteString m r

singleton :: Monad m => Char -> ByteString m () Source

O(1) Yield a Char as a minimal ByteString

fromChunks :: Monad m => Stream (Of ByteString) m r -> ByteString m r Source

O(c) Convert a monadic stream of individual strict ByteString chunks into a byte stream.

fromLazy :: Monad m => ByteString -> ByteString m () Source

O(c) Transmute a lazy bytestring to its representation as a monadic stream of chunks.

fromStrict :: ByteString -> ByteString m () Source

O(1) yield a strict ByteString chunk.

toChunks :: Monad m => ByteString 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 => ByteString m () -> m ByteString Source

O(n) Convert a monadic byte stream into a single lazy ByteString with the same internal chunk structure.

toLazy' :: Monad m => ByteString m r -> m (Of ByteString r) Source

O(n) Convert a monadic byte stream into a single lazy ByteString with the same invisible chunk structure, retaining the original return value.

toStrict :: Monad m => ByteString m () -> 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.

toStrict' :: Monad m => ByteString 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 mapsM.

mapsM R.toStrict' :: Monad m => Stream (ByteString m) m r -> Stream (Of ByteString) m r 

It is subject to all the objections one makes to toStrict.

drain :: Monad m => ByteString m r -> m r Source

wrap :: m (ByteString m r) -> ByteString m r Source

Smart constructor for Go.

Transforming ByteStrings

map :: Monad m => (Char -> Char) -> ByteString m r -> ByteString m r Source

O(n) map f xs is the ByteString obtained by applying f to each element of xs.

intercalate :: Monad m => ByteString m () -> Stream (ByteString m) m r -> ByteString m r Source

O(n) The intercalate function takes a ByteString and a list of ByteStrings and concatenates the list after interspersing the first argument between each element of the list.

Basic interface

cons :: Monad m => Char -> ByteString m r -> ByteString m r Source

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

cons' :: Char -> ByteString m r -> ByteString 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 ByteStrings.

snoc :: Monad m => ByteString m r -> Char -> ByteString m r Source

O(n/c) Append a byte to the end of a ByteString

append :: Monad m => ByteString m r -> ByteString m s -> ByteString m s Source

O(n/c) Append two

filter :: Monad m => (Char -> Bool) -> ByteString m r -> ByteString m r Source

O(n) filter, applied to a predicate and a ByteString, returns a ByteString containing those characters that satisfy the predicate.

head :: Monad m => ByteString m r -> m Char Source

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

head' :: Monad m => ByteString m r -> m (Of (Maybe Char) r) Source

O(1) Extract the first element of a ByteString, which may be non-empty

last :: Monad m => ByteString m r -> m Char Source

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

last' :: Monad m => ByteString m r -> m (Of (Maybe Char) r) Source

null :: Monad m => ByteString m r -> m Bool Source

O(1) Test whether a ByteString is empty.

null' :: Monad m => ByteString m r -> m (Of Bool r) Source

O(1) Test whether a ByteString is empty, collecting its return value; -- this operation must check the whole length of the string.

>>> S.print $ mapsM R.null' $ Q.lines "yours,\nMeredith"
False
False

uncons :: Monad m => ByteString m r -> m (Either r (Char, ByteString m r)) Source

O(1) Extract the head and tail of a ByteString, returning Nothing if it is empty.

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

Direct chunk handling

consChunk :: ByteString -> ByteString m r -> ByteString m r Source

Smart constructor for Chunk.

chunk :: ByteString -> ByteString m () Source

Yield-style smart constructor for Chunk.

foldrChunks :: Monad m => (ByteString -> a -> a) -> a -> ByteString m r -> m a Source

Consume the chunks of an effectful ByteString with a natural right fold.

foldlChunks :: Monad m => (a -> ByteString -> a) -> a -> ByteString m r -> m (Of a r) Source

Substrings

Breaking strings

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

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

drop :: Monad m => Int64 -> ByteString m r -> ByteString m r Source

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

group :: Monad m => ByteString m r -> Stream (ByteString m) m r Source

The group function take`5s a ByteString and returns a list of ByteStrings 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.

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

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

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

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

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

take :: Monad m => Int64 -> ByteString m r -> ByteString m () Source

O(n/c) take n, applied to a ByteString xs, returns the prefix of xs of length n, or xs itself if n > length xs.

takeWhile :: Monad m => (Char -> Bool) -> ByteString m r -> ByteString m () Source

takeWhile, applied to a predicate p and a ByteString xs, returns the longest prefix (possibly empty) of xs of elements that satisfy p.

Breaking into many substrings

split :: Monad m => Char -> ByteString m r -> Stream (ByteString m) m r Source

O(n) Break a ByteString 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 ByteStrings that are slices of the original.

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

lines :: Monad m => ByteString m r -> Stream (ByteString m) m r Source

lines turns a ByteString into a connected stream of ByteStrings 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. It is crucial to distinguish its type from that of linesIndividual

linesIndividual :: Monad m => ByteString m r -> Stream (Of B.ByteString) m r
lines :: Monad m => ByteString m r -> Stream (ByteString m) m r

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

words breaks a byte stream up into a succession of byte streams corresponding to words, breaking Chars representing white space. This is the genuinely streaming words to be distinguished from wordsIndividual, which will attempt to concatenate even infinitely long words like cycle "y" in memory.

linesIndividual :: Monad m => ByteString m r -> Stream (Of ByteString) m r Source

linesIndividual breaks streaming by concatening the chunks between line breaks

linesIndividual = mapsM toStrict' . lines

wordsIndividual :: Monad m => ByteString m r -> Stream (Of ByteString) m r Source

wordsIndividual breaks a bytestream into a sequence of individual Data.ByteString.ByteStrings, delimited by Chars representing white space. It involves concatenation, of course, and is thus potentially unsafe. Distinguish the types

wordsIndividual :: Monad m => ByteString m r  -> Stream (Of B.ByteString) m r
words :: Monad m => ByteString m r -> Stream (ByteString m) m r

The latter, genuinely streaming, words can only break up chunks hidden in the stream that is given; the former potentially concatenates

wordsIndividual = mapsM toStrict' . words

Special folds

concat :: Monad m => Stream (ByteString m) m r -> ByteString m r Source

O(n) Concatenate a stream of byte streams.

Building ByteStrings

Infinite ByteStrings

repeat :: Char -> ByteString m r Source

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

iterate :: (Char -> Char) -> Char -> ByteString m r Source

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

cycle :: Monad m => ByteString m r -> ByteString m s Source

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

Unfolding ByteStrings

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

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

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

| O(n) The unfoldr function is analogous to the Stream 'unfoldr'. unfoldr builds a ByteString from a seed value. The function takes the element and returns Nothing if it is done producing the ByteString or returns Just (a,b), in which case, a is a prepending to the ByteString and b is used as the next element in a recursive call.

Folds, including support for Foldl

fold :: Monad m => (x -> Char -> x) -> x -> (x -> b) -> ByteString m () -> m b Source

fold' :: Monad m => (x -> Char -> x) -> x -> (x -> b) -> ByteString m r -> m (Of b r) Source

length :: Monad m => ByteString m r -> m Int Source

length' :: Monad m => ByteString m r -> m (Of Int r) Source

O(n/c) length returns the length of a byte stream as an Int64

count :: Monad m => Char -> ByteString m r -> m Int Source

count' :: Monad m => Char -> ByteString m r -> m (Of Int r) Source

I/O with ByteStrings

Standard input and output

getContents :: MonadIO m => ByteString m () Source

getContents. Equivalent to hGetContents stdin. Will read lazily

stdin :: MonadIO m => ByteString m () Source

Pipes-style nomenclature for getContents

stdout :: MonadIO m => ByteString m r -> m r Source

Pipes-style nomenclature for putStr

interact :: (ByteString IO () -> ByteString IO r) -> IO r Source

Similar to hPut except that it will never block. Instead it returns any tail that did not get written. This tail may be empty in the case that the whole string was written, or the whole original string if nothing was written. Partial writes are also possible.

Note: on Windows and with Haskell implementation other than GHC, this function does not work correctly; it behaves identically to hPut.

hPutNonBlocking :: MonadIO m => Handle -> ByteString m r -> ByteString m r hPutNonBlocking _ (Empty r) = Empty r hPutNonBlocking h (Go m) = Go $ liftM (hPutNonBlocking h) m hPutNonBlocking h bs@(Chunk c cs) = do c' <- lift $ S.hPutNonBlocking h c case S.length c' of l' | l' == S.length c -> hPutNonBlocking h cs 0 -> bs _ -> Chunk c' cs {--}

A synonym for hPut, for compatibility

hPutStr :: Handle -> ByteString IO r -> IO r hPutStr = hPut

  • - | Write a ByteString to stdout putStr :: ByteString IO r -> IO r putStr = hPut IO.stdout

putStr :: MonadIO m => ByteString m r -> m r Source

putStrLn :: MonadIO m => ByteString m r -> m r Source

Files

readFile :: MonadIO m => FilePath -> ByteString m () Source

Read an entire file into a chunked 'ByteString IO ()'. The Handle will be held open until EOF is encountered.

writeFile :: FilePath -> ByteString IO r -> IO r Source

Write a ByteString to a file.

appendFile :: FilePath -> ByteString IO r -> IO r Source

Append a ByteString to a file.

I/O with Handles

fromHandle :: MonadIO m => Handle -> ByteString m () Source

Pipes-style nomenclature for hGetContents

toHandle :: MonadIO m => Handle -> ByteString m r -> m r Source

Pipes nomenclature for hPut

hGet :: MonadIO m => Handle -> Int -> ByteString m () Source

Read n bytes into a ByteString, directly from the specified Handle.

hGetContents :: MonadIO m => Handle -> ByteString m () Source

Read entire handle contents lazily into a ByteString. Chunks are read on demand, using the default chunk size.

Once EOF is encountered, the Handle is closed.

Note: the Handle should be placed in binary mode with hSetBinaryMode for hGetContents to work correctly.

hGetContentsN :: MonadIO m => Int -> Handle -> ByteString m () Source

Read entire handle contents lazily into a ByteString. 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.

The handle is closed on EOF.

Note: the Handle should be placed in binary mode with hSetBinaryMode for hGetContentsN to work correctly.

hGetN :: MonadIO m => Int -> Handle -> Int -> ByteString m () Source

Read n bytes into a ByteString, directly from the specified Handle, in chunks of size k.

hGetNonBlocking :: MonadIO m => Handle -> Int -> ByteString 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 -> ByteString 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 -> ByteString m r -> m r Source

Outputs a ByteString to the specified Handle.

Etc.

distribute :: (Monad m, MonadTrans t, MFunctor t, Monad (t m), Monad (t (ByteString m))) => ByteString (t m) a -> t (ByteString m) a Source

Given a byte stream on a transformed monad, make it possible to 'run' transformer.

materialize :: (forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x) -> ByteString m r Source

Construct a succession of chunks from its Church encoding (compare GHC.Exts.build)

dematerialize :: Monad m => ByteString 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