streaming-bytestring: effectful byte steams, or: bytestring io done right.

[ bsd3, data, library, pipes, streaming ] [ Propose Tags ]

This is an implementation of effectful, memory-constrained bytestrings (byte streams) and functions for streaming bytestring manipulation, adequate for non-lazy-io.

Interoperation with pipes uses this isomorphism:

Streaming.unfoldrChunks Pipes.next :: Monad m => Producer ByteString m r -> ByteString m r
Pipes.unfoldr Streaming.nextChunk  :: Monad m => ByteString m r -> Producer ByteString m r

Interoperation with io-streams is thus:

IOStreams.unfoldM Streaming.unconsChunk :: ByteString IO () -> IO (InputStream ByteString)
Streaming.reread IOStreams.read         :: InputStream ByteString -> ByteString IO ()

and similarly for other rational streaming io libraries.

Problems and questions about the library can be put as issues on the github page, or mailed to the pipes list.

A tutorial module is in the works; here, for the moment, is a sequence of simplified implementations of familiar shell utilities. The same programs are implemented at the end of the excellent io-streams tutorial. It is generally much simpler; in some case simpler than what you would write with lazy bytestrings. Here is a simple GET request that returns a byte stream.

The implementation is idiot-simple; it follows the details of Data.ByteString.Lazy and Data.ByteString.Lazy.Char8 as far as is possible, replacing the lazy bytestring type:

data ByteString     = Empty   | Chunk Strict.ByteString ByteString

with the minimal effectful variant:

data ByteString m r = Empty r | Chunk Strict.ByteString (ByteString m r) | Go (m (ByteString m r))

(Constructors are necessarily hidden in internal modules in both cases.)

That's it. As a lazy bytestring is implemented internally by a sort of list of strict bytestring chunks, a streaming bytestring is simply implemented as a producer or generator of strict bytestring chunks. Most operations are defined by simply adding a line to what we find in Data.ByteString.Lazy.

Something like this alteration of type is of course obvious and mechanical, once the idea of an effectful bytestring type is contemplated and lazy io is rejected. Indeed it seems that this is the proper expression of what was intended by lazy bytestrings to begin with. The documentation, after all, reads

  • "A key feature of lazy 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 lazy streaming style, e.g. classic pipeline composition. The default I/O chunk size is 32k, which should be good in most circumstances."

... which is very much the idea of this library: the default chunk size for hGetContents and the like follows Data.ByteString.Lazy and operations like lines and append and so on are tailored not to increase chunk size.

The present library is thus nothing but lazy bytestring done right. The authors of Data.ByteString.Lazy must have supposed that the directly monadic formulation of such their type would necessarily make things slower. This appears to be a prejudice. For example, passing a large file of short lines through this benchmark transformation

Lazy.unlines      . map    (\bs -> "!"       <> Lazy.drop 5 bs)       . Lazy.lines
Streaming.unlines . S.maps (\bs -> chunk "!" >> Streaming.drop 5 bs)  . Streaming.lines

gives pleasing results like these

$  time ./benchlines lazy >> /dev/null
real	0m2.097s
...
$  time ./benchlines streaming >> /dev/null
real	0m1.930s

For a more sophisticated operation like

Lazy.intercalate "!\n"      . Lazy.lines
Streaming.intercalate "!\n" . Streaming.lines

we get results like these:

time ./benchlines lazy >> /dev/null
real	0m1.250s
...
time ./benchlines streaming >> /dev/null
real	0m1.531s

The pipes environment would express the latter as

Pipes.intercalates (Pipes.yield "!\n") . view Pipes.lines

meaning almost exactly what we mean above, but with results like this

 time ./benchlines pipes >> /dev/null
 real	0m6.353s

The difference, however, is emphatically not intrinsic to pipes; it is just that this library depends the streaming library, which is used in place of free to express the &quot;perfectly streaming&quot; splitting and iterated division or "chunking" of byte streams.

These concepts belong to the ABCs of streaming; lines is just a textbook example, and it is of course handled correctly in Data.ByteString.Lazy. But the concepts are catastrophically mishandled in the streaming io libraries other than pipes. Already the enumerator and iteratee libraries were completely defeated by lines: see e.g. the enumerator implementation of splitWhen and lines. This will concatenate strict text forever, if that's what is coming in. The rot spreads from there. It is just a fact that in all of the general streaming io frameworks other than pipes, it becomes torture to express elementary distinctions that are transparently and immediately contained in any idea of streaming whatsoever.

Though we barely alter signatures in Data.ByteString.Lazy more than is required by the types, the point of view that emerges is very much that of pipes-bytestring and pipes-group. In particular we have these correspondences:

Lazy.splitAt      :: Int -> ByteString              -> (ByteString, ByteString)
Streaming.splitAt :: Int -> ByteString m r          -> ByteString m (ByteString m r)
Pipes.splitAt     :: Int -> Producer ByteString m r -> Producer ByteString m (Producer ByteString m r)

and

Lazy.lines      :: ByteString -> [ByteString]
Streaming.lines :: ByteString m r -> Stream (ByteString m) m r
Pipes.lines     :: Producer ByteString m r -> FreeT (Producer ByteString m) m r

where the Stream type expresses the sequencing of ByteString m _ layers with the usual 'free monad' sequencing.

If you are unfamiliar with this way of structuring material you might take a look at the tutorial for pipes-group and the examples in the documentation for the streaming library. See also simple implementations of the shell-like examples mentioned above. Or, again, put a question on the issues page or to the pipes list.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.3, 0.1.0.4, 0.1.0.5, 0.1.0.6, 0.1.0.7, 0.1.0.8, 0.1.1.0, 0.1.2.0, 0.1.2.2, 0.1.3.0, 0.1.4.0, 0.1.4.2, 0.1.4.3, 0.1.4.4, 0.1.4.5, 0.1.4.6, 0.1.5, 0.1.6, 0.1.7, 0.2.0, 0.2.1, 0.2.2, 0.2.3, 0.2.4, 0.3.0, 0.3.1, 0.3.2 (info)
Dependencies base (<4.9), bytestring, bytestring-builder, deepseq, mmorph (>=1.0 && <1.2), mtl (>=2.1 && <2.3), streaming (>0.1.0.20 && <0.1.1.2), transformers (>=0.3 && <0.5) [details]
License BSD-3-Clause
Author michaelt
Maintainer what_is_it_to_do_anything@yahoo.com
Category Data, Pipes, Streaming
Home page https://github.com/michaelt/streaming-bytestring
Bug tracker https://github.com/michaelt/streaming-bytestring/issues
Source repo head: git clone https://github.com/michaelt/streaming-bytestring
Uploaded by MichaelThompson at 2015-10-05T01:01:56Z
Distributions LTSHaskell:0.3.2, NixOS:0.3.2, Stackage:0.3.2
Reverse Dependencies 38 direct, 39 indirect [details]
Downloads 38102 total (279 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for streaming-bytestring-0.1.1.0

[back to package description]

bytestring-streaming

This package depends on the streaming library

          copy 200M file    divide it on lines, 
                            adding '!' to each 
                            
lazy      0m0.813s          0m8.597s
streaming 0m0.783s          0m9.664s
pipes     0m0.771s          0m49.176s
conduit	  0m1.068s          2m25.437s

This library is modeled as far as possible on the internal structure of Data.ByteString.Lazy. There are two changes: a chunk may be delayed by a monadic step, and the sucession of steps has a 'return' value:

data ByteString m r =
  Empty r
  | Chunk {-#UNPACK #-} !S.ByteString (ByteString m r)
  | Go (m (ByteString m r ))

unlike

data ByteString = 
  Empty 
  | Chunk {-#UNPACK #-} !S.ByteString ByteString

That's it.


Another module is planned that would correspond more closely to Pipes.Bytestring than to Data.ByteString.Lazy.
Producer ByteString m r as it is treated in pipes-bytestring as the ByteString m r type is here. The result is much faster, at least with preliminary tests. The modules integrating attoparsec and aeson are simple replicas of k0001's pipes-attoparsec and pipes-aeson. Also included is a replica of pipes-http.

It is possible that streaming-bytestring is conceptually clearer than pipes-bytestring as well - and clearer than the approach taken by conduit and io-streams. All of these are forced to integrate the conception of an amorphous succession of bytes that may be chunked anywhere - the direct result of, say, fromHandle, sourceFile and the like - and a succession of 'semantically' distinct bytestrings of interest under a single concept.


Strange as it may seem, it is arguable that the general Producer, Source, and InputStream concepts from these libraries ought not to hold ByteStrings except as conceptually separate units, e.g. the lines of a document taken as strict bytestrings, where that is legitimate. An InputStream ByteString is like an InputStream Int; a Conduit.Source m ByteString has the same type as a Source m Int; a Pipes.Producer ByteString m r has the same type as a Producer Int m r. These types are suited to the general stream transformations these libraries make possible.

We can see the strangeness in the io-streams lines

lines :: InputStream ByteString -> IO (InputStream ByteString)

and the conduit linesUnboundedAscii

linesUnboundedAscii :: (Monad m) => Conduit ByteString m ByteString

(specializing slightly). In either case, what enters on the left will be a succession of anyhow-chunked bytes; what exits on the right will be a succession of significant individual things of type ByteString.

What we find in IOStreams.lines and linesUnlimitedAscii are comparable to what we would have if bytestring defined

lines :: L.ByteString -> [S.ByteString]

or more absurdly

lines :: L.ByteString -> L.ByteString 

and exposed methods for inspecting the hitherto secret chunks contained in lazy bytestrings.

The model employed by the present package is a little different. First, the primitive lines concept is just

lines :: ByteString m r -> Stream (ByteString m) m r

as in pipes-bytestring; this corresponds precisely to

lines :: ByteString -> [ByteString]

as it appears in Data.ByteString.Lazy -- the elements of the list (stream) are themselves lazy bytestrings.

But pipes-bytestring attempts to mean by Producer ByteString m r what we express by ByteString m r - the undifferentiated byte stream. But (we are provisionally suggesting) that isn't what Producer ByteString m r means, and this is part of the reason why pipes-bytestring is difficult for people to grasp. The user frequently proposes to inspect and work with individual lines with Pipes themselves and thus needs

produceLines :: Producer ByteString m r -> Producer ByteString m r
produceLines = folds B.concat B.empty id . view Pipes.ByteString.lines

Here we would instead write a

produceLines :: ByteString m r -> Stream (Of ByteString) m r

which is transparently related to the type of lines itself

lines :: ByteString m r -> Stream (ByteString m) m r

The distinctive type of produceLines clearly express the transition from the world of amorphously chunked bytestreams to the world of significant individual values, in this case individual strict bytestrings.