streamly: Beautiful Streaming, Concurrent and Reactive Composition

[ array, bsd3, concurrency, dataflow, filesystem, library, list, logic, network, non-determinism, parsing, pipes, reactivity, streaming, streamly, time, unicode ] [ Propose Tags ]

Streamly, short for streaming concurrently, provides monadic streams, with a simple API, almost identical to standard lists, and an in-built support for concurrency. By using stream-style combinators on stream composition, streams can be generated, merged, chained, mapped, zipped, and consumed concurrently – providing a generalized high level programming framework unifying streaming and concurrency. Controlled concurrency allows even infinite streams to be evaluated concurrently. Concurrency is auto scaled based on feedback from the stream consumer. The programmer does not have to be aware of threads, locking or synchronization to write scalable concurrent programs.

The basic streaming functionality of streamly is equivalent to that provided by streaming libraries like vector, streaming, pipes, and conduit. In addition to providing streaming functionality, streamly subsumes the functionality of list transformer libraries like pipes or list-t and also the logic programming library logict. On the concurrency side, it subsumes the functionality of the async package. Because it supports streaming with concurrency we can write FRP applications similar in concept to Yampa or reflex.

For file IO, currently the library provides only one API to stream the lines in the file as Strings. Future versions will provide better streaming file IO options. Streamly interworks with the popular streaming libraries, see the interworking section in Streamly.Tutorial.

Why use streamly?

  • Simplicity: Simple list like streaming API, if you know how to use lists then you know how to use streamly. This library is built with simplicity and ease of use as a primary design goal.

  • Concurrency: Simple, powerful, and scalable concurrency. Concurrency is built-in, and not intrusive, concurrent programs are written exactly the same way as non-concurrent ones.

  • Generality: Unifies functionality provided by several disparate packages (streaming, concurrency, list transformer, logic programming, reactive programming) in a concise API.

  • Performance: Streamly is designed for high performance. It employs stream fusion optimizations for best possible performance. Serial peformance is equivalent to the venerable vector library in most cases and even better in some cases. Concurrent performance is unbeatable. See streaming-benchmarks for a comparison of popular streaming libraries on micro-benchmarks.

Where to find more information:

  • README shipped with the package for a quick overview

  • Streamly.Tutorial module in the haddock documentation for a detailed introduction

  • examples directory in the package for some simple practical examples


[Skip to Readme]

Flags

Manual Flags

NameDescriptionDefault
diag

Diagnostics build

Disabled
dev

Development build

Disabled
no-fusion

Disable rewrite rules

Disabled
streamk

Use CPS style streams when possible

Disabled
examples

Build including examples

Disabled
examples-sdl

Build including SDL examples

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0, 0.1.1, 0.1.2, 0.2.0, 0.2.1, 0.3.0, 0.4.0, 0.4.1, 0.5.0, 0.5.1, 0.5.2, 0.6.0, 0.6.1, 0.7.0, 0.7.1, 0.7.2, 0.7.3, 0.7.3.1, 0.7.3.2, 0.8.0, 0.8.1, 0.8.1.1, 0.8.2, 0.8.3, 0.9.0, 0.10.0, 0.10.1
Change log Changelog.md
Dependencies atomic-primops (>=0.8 && <0.9), base (>=4.8 && <5), clock (>=0.7.1 && <0.8), containers (>=0.5 && <0.7), exceptions (>=0.8 && <0.11), ghc-prim (>=0.2 && <0.6), heaps (>=0.3 && <0.4), lockfree-queue (>=0.2.3 && <0.3), monad-control (>=1.0 && <2), mtl (>=2.2 && <3), semigroups (>=0.18 && <0.19), transformers (>=0.4 && <0.6), transformers-base (>=0.4 && <0.5) [details]
License BSD-3-Clause
Copyright 2017 Harendra Kumar
Author Harendra Kumar
Maintainer harendra.kumar@gmail.com
Category Control, Concurrency, Streaming, Reactivity
Home page https://github.com/composewell/streamly
Bug tracker https://github.com/composewell/streamly/issues
Source repo head: git clone https://github.com/composewell/streamly
Uploaded by harendra at 2018-09-12T18:10:41Z
Distributions LTSHaskell:0.10.1, NixOS:0.10.1, Stackage:0.10.1
Reverse Dependencies 33 direct, 4 indirect [details]
Executables CirclingSquare, AcidRain, MergeSort, ListDir, SearchQuery, chart-nested, chart-linear
Downloads 16764 total (307 in the last 30 days)
Rating 2.5 (votes: 6) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-09-12 [all 1 reports]

Readme for streamly-0.5.1

[back to package description]

Streamly

Streaming Concurrently

Streamly, short for streaming concurrently, provides monadic streams, with a simple API, almost identical to standard lists and vector, and an in-built support for concurrency. By using stream-style combinators on stream composition, streams can be generated, merged, chained, mapped, zipped, and consumed concurrently – providing a generalized high level programming framework unifying streaming and concurrency. Controlled concurrency allows even infinite streams to be evaluated concurrently. Concurrency is auto scaled based on feedback from the stream consumer. The programmer does not have to be aware of threads, locking or synchronization to write scalable concurrent programs.

The basic streaming functionality of streamly is equivalent to that provided by streaming libraries like vector, streaming, pipes, and conduit. In addition to providing streaming functionality, streamly subsumes the functionality of list transformer libraries like pipes or list-t, and also the logic programming library logict. On the concurrency side, it subsumes the functionality of the async package, and provides even higher level concurrent composition. Because it supports streaming with concurrency we can write FRP applications similar in concept to Yampa or reflex.

Why use streamly?

  • Simplicity: Simple list like streaming API, if you know how to use lists then you know how to use streamly. This library is built with simplicity and ease of use as a design goal.
  • Concurrency: Simple, powerful, and scalable concurrency. Concurrency is built-in, and not intrusive, concurrent programs are written exactly the same way as non-concurrent ones.
  • Generality: Unifies functionality provided by several disparate packages (streaming, concurrency, list transformer, logic programming, reactive programming) in a concise API.
  • Performance: Streamly is designed for high performance. It employs stream fusion optimizations for best possible performance. Serial peformance is equivalent to the venerable vector library in most cases and even better in some cases. Concurrent performance is unbeatable. See streaming-benchmarks for a comparison of popular streaming libraries on micro-benchmarks.

The following chart shows a summary of the cost of key streaming operations processing a million elements. The timings for streamly and vector are in the 600-700 microseconds range and therefore can barely be seen in the graph.

Streaming Operations at a Glance

Streaming Pipelines

Unlike pipes or conduit and like vector and streaming, streamly composes stream data instead of stream processors (functions). A stream is just like a list and is explicitly passed around to functions that process the stream. Therefore, no special operator is needed to join stages in a streaming pipeline, just the standard function application ($) or reverse function application (&) operator is enough. Combinators are provided in Streamly.Prelude to transform or fold streams.

The following snippet provides a simple stream composition example that reads numbers from stdin, prints the squares of even numbers and exits if an even number more than 9 is entered.

import Streamly
import qualified Streamly.Prelude as S
import Data.Function ((&))

main = runStream $
       S.repeatM getLine
     & fmap read
     & S.filter even
     & S.takeWhile (<= 9)
     & fmap (\x -> x * x)
     & S.mapM print

Concurrent Stream Generation

Monadic construction and generation functions e.g. consM, unfoldrM, replicateM, repeatM, iterateM and fromFoldableM etc. work concurrently when used with appropriate stream type combinator (e.g. asyncly, aheadly or parallely).

The following code finishes in 3 seconds (6 seconds when serial):

> let p n = threadDelay (n * 1000000) >> return n
> S.toList $ aheadly $ p 3 |: p 2 |: p 1 |: S.nil
[3,2,1]

> S.toList $ parallely $ p 3 |: p 2 |: p 1 |: S.nil
[1,2,3]

The following finishes in 10 seconds (100 seconds when serial):

runStream $ asyncly $ S.replicateM 10 $ p 10

Concurrent Streaming Pipelines

Use |& or |$ to apply stream processing functions concurrently. The following example prints a "hello" every second; if you use & instead of |& you will see that the delay doubles to 2 seconds instead because of serial application.

main = runStream $
      S.repeatM (threadDelay 1000000 >> return "hello")
   |& S.mapM (\x -> threadDelay 1000000 >> putStrLn x)

Mapping Concurrently

We can use mapM or sequence functions concurrently on a stream.

> let p n = threadDelay (n * 1000000) >> return n
> runStream $ aheadly $ S.mapM (\x -> p 1 >> print x) (serially $ repeatM (p 1))

Serial and Concurrent Merging

Semigroup and Monoid instances can be used to fold streams serially or concurrently. In the following example we compose ten actions in the stream, each with a delay of 1 to 10 seconds, respectively. Since all the actions are concurrent we see one output printed every second:

import Streamly
import qualified Streamly.Prelude as S
import Control.Concurrent (threadDelay)

main = S.toList $ parallely $ foldMap delay [1..10]
 where delay n = S.yieldM $ threadDelay (n * 1000000) >> print n

Streams can be combined together in many ways. We provide some examples below, see the tutorial for more ways. We use the following delay function in the examples to demonstrate the concurrency aspects:

import Streamly
import qualified Streamly.Prelude as S
import Control.Concurrent

delay n = S.yieldM $ do
    threadDelay (n * 1000000)
    tid <- myThreadId
    putStrLn (show tid ++ ": Delay " ++ show n)

Serial

main = runStream $ delay 3 <> delay 2 <> delay 1
ThreadId 36: Delay 3
ThreadId 36: Delay 2
ThreadId 36: Delay 1

Parallel

main = runStream . parallely $ delay 3 <> delay 2 <> delay 1
ThreadId 42: Delay 1
ThreadId 41: Delay 2
ThreadId 40: Delay 3

Nested Loops (aka List Transformer)

The monad instance composes like a list monad.

import Streamly
import qualified Streamly.Prelude as S

loops = do
    x <- S.fromFoldable [1,2]
    y <- S.fromFoldable [3,4]
    S.yieldM $ putStrLn $ show (x, y)

main = runStream loops
(1,3)
(1,4)
(2,3)
(2,4)

Concurrent Nested Loops

To run the above code with, lookahead style concurrency i.e. each iteration in the loop can run run concurrently by but the results are presented in the same order as serial execution:

main = runStream $ aheadly $ loops

To run it with depth first concurrency yielding results asynchronously in the same order as they become available (deep async composition):

main = runStream $ asyncly $ loops

To run it with breadth first concurrency and yeilding results asynchronously (wide async composition):

main = runStream $ wAsyncly $ loops

The above streams provide lazy/demand-driven concurrency which is automatically scaled as per demand and is controlled/bounded so that it can be used on infinite streams. The following combinator provides strict, unbounded concurrency irrespective of demand:

main = runStream $ parallely $ loops

To run it serially but interleaving the outer and inner loop iterations (breadth first serial):

main = runStream $ wSerially $ loops

Magical Concurrency

Streams can perform semigroup (<>) and monadic bind (>>=) operations concurrently using combinators like asyncly, parallelly. For example, to concurrently generate squares of a stream of numbers and then concurrently sum the square roots of all combinations of two streams:

import Streamly
import qualified Streamly.Prelude as S

main = do
    s <- S.sum $ asyncly $ do
        -- Each square is performed concurrently, (<>) is concurrent
        x2 <- foldMap (\x -> return $ x * x) [1..100]
        y2 <- foldMap (\y -> return $ y * y) [1..100]
        -- Each addition is performed concurrently, monadic bind is concurrent
        return $ sqrt (x2 + y2)
    print s

Of course, the actions running in parallel could be arbitrary IO actions. For example, to concurrently list the contents of a directory tree recursively:

import Path.IO (listDir, getCurrentDir)
import Streamly
import qualified Streamly.Prelude as S

main = runStream $ aheadly $ getCurrentDir >>= readdir
   where readdir d = do
            (dirs, files) <- S.yieldM $ listDir d
            S.yieldM $ mapM_ putStrLn $ map show files
            -- read the subdirs concurrently, (<>) is concurrent
            foldMap readdir dirs

In the above examples we do not think in terms of threads, locking or synchronization, rather we think in terms of what can run in parallel, the rest is taken care of automatically. When using aheadly the programmer does not have to worry about how many threads are to be created, they are automatically adjusted based on the demand of the consumer.

The concurrency facilities provided by streamly can be compared with OpenMP and Cilk but with a more declarative expression.

Rate Limiting

For bounded concurrent streams, stream yield rate can be specified. For example, to print hello once every second you can simply write this:

import Streamly
import Streamly.Prelude as S

main = runStream $ asyncly $ avgRate 1 $ S.repeatM $ putStrLn "hello"

For some practical uses of rate control, see AcidRain.hs and CirclingSquare.hs . Concurrency of the stream is automatically controlled to match the specified rate. Rate control works precisely even at throughputs as high as millions of yields per second. For more sophisticated rate control see the haddock documentation.

Reactive Programming (FRP)

Streamly is a foundation for first class reactive programming as well by virtue of integrating concurrency and streaming. See AcidRain.hs for a console based FRP game example and CirclingSquare.hs for an SDL based animation example.

Further Reading

For more information, see:

Contributing

The code is available under BSD-3 license on github. Join the gitter chat channel for discussions. You can find some of the todo items on the github wiki. Please ask on the gitter channel or contact the maintainer directly for more details on each item. All contributions are welcome!

This library was originally inspired by the transient package authored by Alberto G. Corona.