streaming-0.1.2.2: an elementary streaming prelude and a general monad transformer for streaming applications.

Safe HaskellNone
LanguageHaskell2010

Streaming.Prelude

Contents

Description

This module is very closely modeled on Pipes.Prelude; it attempts to simplify and optimize the conception of Producer manipulation contained in Pipes.Group, Pipes.Parse and the like. This is very simple and unmysterious; it is independent of piping and conduiting, and can be used with any rational "streaming IO" system.

Import qualified thus:

import Streaming
import qualified Streaming.Prelude as S

For the examples below, one sometimes needs

import Streaming.Prelude (each, yield, stdoutLn, stdinLn)

Other libraries that come up in passing are

import qualified Control.Foldl as L -- cabal install foldl
import qualified Pipes as P
import qualified Pipes.Prelude as P
import qualified System.IO as IO

Here are some correspondences between the types employed here and elsewhere:

              streaming             |            pipes               |       conduit       |  io-streams
-------------------------------------------------------------------------------------------------------------------
Stream (Of a) m ()                  | Producer a m ()                | Source m a          | InputStream a
                                    | ListT m a                      | ConduitM () o m ()  | Generator r ()
-------------------------------------------------------------------------------------------------------------------
Stream (Of a) m r                   | Producer a m r                 | ConduitM () o m r   | Generator a r
-------------------------------------------------------------------------------------------------------------------
Stream (Of a) m (Stream (Of a) m r) | Producer a m (Producer a m r)  |                     
--------------------------------------------------------------------------------------------------------------------
Stream (Stream (Of a) m) r          | FreeT (Producer a m) m r       |
--------------------------------------------------------------------------------------------------------------------
--------------------------------------------------------------------------------------------------------------------
ByteString m ()                     | Producer ByteString m ()       | Source m ByteString  | InputStream ByteString
--------------------------------------------------------------------------------------------------------------------

Synopsis

Types

data Of a b Source

A left-strict pair; the base functor for streams of individual elements.

Constructors

!a :> b infixr 5 

Instances

Monoid a => Monad (Of a) Source 
Functor (Of a) Source 
Monoid a => Applicative (Of a) Source 
Foldable (Of a) Source 
Traversable (Of a) Source 
Eq a => Eq1 (Of a) Source 
Ord a => Ord1 (Of a) Source 
Read a => Read1 (Of a) Source 
Show a => Show1 (Of a) Source 
(Eq a, Eq b) => Eq (Of a b) Source 
(Data a, Data b) => Data (Of a b) Source 
(Ord a, Ord b) => Ord (Of a b) Source 
(Read a, Read b) => Read (Of a b) Source 
(Show a, Show b) => Show (Of a b) Source 
(Monoid a, Monoid b) => Monoid (Of a b) Source 

Introducing streams of elements

yield :: Monad m => a -> Stream (Of a) m () Source

A singleton stream

>>> stdoutLn $ yield "hello"
hello
>>> S.sum $ do {yield 1; yield 2}
3
>>> S.sum $ do {yield 1; lift $ putStrLn "/* 1 was yielded */"; yield 2; lift $ putStrLn "/* 2 was yielded */"}
/* 1 was yielded */
/* 2 was yielded */
3
>>> let prompt :: IO Int; prompt = putStrLn "Enter a number:" >> readLn
>>> S.sum $ do {lift prompt >>= yield ; lift prompt >>= yield ; lift prompt >>= yield}
Enter a number:
3<Enter>
Enter a number:
20<Enter>
Enter a number:
100<Enter>
123

each :: (Monad m, Foldable f) => f a -> Stream (Of a) m () Source

Stream the elements of a foldable container.

>>> S.print $ S.map (*100) $ each [1..3]
100
200
300
>>> S.print $ S.map (*100) $ each [1..3] >> lift readLn >>= yield
100
200
300
4<Enter>
400

unfoldr :: Monad m => (s -> m (Either r (a, s))) -> s -> Stream (Of a) m r Source

Build a Stream by unfolding steps starting from a seed.

The seed can of course be anything, but this is one natural way to consume a pipes Producer. Consider:

>>> S.stdoutLn $ S.take 2 (S.unfoldr P.next P.stdinLn)
hello<Enter>
hello
goodbye<Enter>
goodbye
>>> S.stdoutLn $ S.unfoldr P.next (P.stdinLn P.>-> P.take 2)
hello<Enter>
hello
goodbye<Enter>
goodbye
>>> S.effects $ S.unfoldr P.next (P.stdinLn P.>-> P.take 2 P.>-> P.stdoutLn)
hello<Enter>
hello
goodbye<Enter>
goodbye

If the intended "coalgebra" is complicated it might be pleasant to write it with the state monad:

\state seed -> S.unfoldr  (runExceptT  . runStateT state) seed :: Monad m => StateT s (ExceptT r m) a -> s -> P.Producer a m r
>>> let state = do {n <- get ; if n >= 3 then lift (throwE "Got to three"); else put (n+1); return n}
>>> S.print $ S.unfoldr (runExceptT  . runStateT state) 0
0
1
2
"Got to three"

stdinLn :: MonadIO m => Stream (Of String) m () Source

repeatedly stream lines as String from stdin

>>> stdoutLn $ S.show (S.each [1..3])
1
2
3
>>> stdoutLn stdinLn
hello<Enter>
hello
world<Enter>
world
^CInterrupted.
>>> stdoutLn $ S.map reverse stdinLn
hello<Enter>
olleh
world<Enter>
dlrow
^CInterrupted.

readLn :: (MonadIO m, Read a) => Stream (Of a) m () Source

Read values from stdin, ignoring failed parses

>>> S.sum $ S.take 2 S.readLn :: IO Int
3<Enter>
#$%^&\^?<Enter>
1000<Enter>
1003

fromHandle :: MonadIO m => Handle -> Stream (Of String) m () Source

Read Strings from a Handle using hGetLine

Terminates on end of input

>>> withFile "distribute.hs" ReadMode $ stdoutLn . S.take 3 . fromHandle
import Streaming
import qualified Streaming.Prelude as S
import Control.Monad.Trans.State.Strict

iterate :: (a -> a) -> a -> Stream (Of a) m r Source

Iterate a pure function from a seed value, streaming the results forever

repeat :: a -> Stream (Of a) m r Source

Repeat an element ad inf. .

>>> S.print $ S.take 3 $ S.repeat 1
1
1
1

replicate :: Monad m => Int -> a -> Stream (Of a) m () Source

Repeat an element several times

cycle :: (Monad m, Functor f) => Stream f m r -> Stream f m s Source

Cycle repeatedly through the layers of a stream, ad inf. This function is functor-general

cycle = forever
>>> rest <- S.print $ S.splitAt 3 $ S.cycle (yield True >> yield False)
True
False
True
>>> S.print $ S.take 3 rest
False
True
False

repeatM :: Monad m => m a -> Stream (Of a) m r Source

Repeat a monadic action ad inf., streaming its results.

>>> S.toListM $ S.take 2 (repeatM getLine)
hello<Enter>
world<Enter>
["hello","world"]

replicateM :: Monad m => Int -> m a -> Stream (Of a) m () Source

Repeat an action several times, streaming the results.

>>> S.print $ S.replicateM 2 getCurrentTime
2015-08-18 00:57:36.124508 UTC
2015-08-18 00:57:36.124785 UTC

enumFrom :: (Monad m, Enum n) => n -> Stream (Of n) m r Source

An infinite stream of enumerable values, starting from a given value. Streaming.Prelude.enumFrom is more desirable that each [x..] for the infinite case, because it has a polymorphic return type.

>>> S.print $ S.take 3 $ S.enumFrom 'a'
'a'
'b'
'c'

Because their return type is polymorphic, enumFrom and enumFromThen are useful for example with zip and zipWith, which require the same return type in the zipped streams. With each [1..] the following would be impossible.

>>> rest <- S.print $  S.zip (S.enumFrom 'a') $ S.splitAt 3 $ S.enumFrom 1
('a',1)
('b',2)
('c',3)
>>> S.print $ S.take 3 rest
4
5
6

Where a final element is specified, as in each [1..10] a special combinator is unneeded, since the return type would be () anyway.

enumFromThen :: (Monad m, Enum a) => a -> a -> Stream (Of a) m r Source

An infinite sequence of enumerable values at a fixed distance, determined by the first and second values. See the discussion of enumFrom

>>> S.print $ S.take 3 $ S.enumFromThen 100 200
100
200
300

Consuming streams of elements

stdoutLn :: MonadIO m => Stream (Of String) m () -> m () Source

Write Strings to stdout using putStrLn; terminates on a broken output pipe (compare stdoutLn).

>>> S.stdoutLn $ S.show (S.each [1..3])
1
2
3

stdoutLn' :: MonadIO m => Stream (Of String) m r -> m r Source

Write Strings to stdout using putStrLn

This does not handle a broken output pipe, but has a polymorphic return value, which makes this possible:

>>> rest <- stdoutLn' $ S.show $ S.splitAt 3 (each [1..5])
1
2
3
>>> S.sum rest
9

mapM_ :: Monad m => (a -> m b) -> Stream (Of a) m r -> m r Source

Reduce a stream to its return value with a monadic action.

>>> mapM_ Prelude.print $ each [1..3] >> return True
1
2
3
True

print :: (MonadIO m, Show a) => Stream (Of a) m r -> m r Source

Print the elements of a stream as they arise.

toHandle :: MonadIO m => Handle -> Stream (Of String) m r -> m r Source

effects :: Monad m => Stream (Of a) m r -> m r Source

Reduce a stream, performing its actions but ignoring its elements. This might just be called effects or runEffects.

>>> let effect = lift (putStrLn "Effect!")
>>> let stream = do {yield 1; effect; yield 2; effect; return (2^100)}
>>> S.effects stream
Effect!
Effect!
1267650600228229401496703205376
>>> S.effects $ S.takeWhile (<2) stream
Effect!

drained :: (Monad m, Monad (t m), Functor (t m), MonadTrans t) => t m (Stream (Of a) m r) -> t m r Source

Where a transformer returns a stream, run the effects of the stream, keeping the return value. This is usually used at the type

drained :: Monad m => Stream (Of a) m (Stream (Of b) m r) -> Stream (Of a) m r
drained = join . fmap (lift . effects)
>>> let take' n = S.drained . S.splitAt n
>>> S.print $ concats $ maps (take' 1) $ S.group $ S.each "wwwwarrrrr"
'w'
'a'
'r'

Stream transformers

map :: Monad m => (a -> b) -> Stream (Of a) m r -> Stream (Of b) m r Source

Standard map on the elements of a stream.

mapM :: Monad m => (a -> m b) -> Stream (Of a) m r -> Stream (Of b) m r Source

Replace each element of a stream with the result of a monadic action

chain :: Monad m => (a -> m ()) -> Stream (Of a) m r -> Stream (Of a) m r Source

Apply an action to all values flowing downstream

>>> S.product (S.chain Prelude.print (S.each [2..4])) >>= Prelude.print
2
3
4f
24 :> ()

maps :: (Monad m, Functor f) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r Source

Map layers of one functor to another with a transformation

sequence :: Monad m => Stream (Of (m a)) m r -> Stream (Of a) m r Source

Like the sequence but streaming. The result type is a stream of a's, but is not accumulated; the effects of the elements of the original stream are interleaved in the resulting stream. Compare:

sequence :: Monad m =>       [m a]           -> m [a]
sequence :: Monad m => Stream (Of (m a)) m r -> Stream (Of a) m r

mapFoldable :: (Monad m, Foldable t) => (a -> t b) -> Stream (Of a) m r -> Stream (Of b) m r Source

For each element of a stream, stream a foldable container of elements instead; compare mapFoldable.

mapFoldable f str = for str (\a -> each (f a))
>>> S.print $ S.mapFoldable show $ yield 12
'1'
'2'

filter :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m r Source

Skip elements of a stream that fail a predicate

filterM :: Monad m => (a -> m Bool) -> Stream (Of a) m r -> Stream (Of a) m r Source

Skip elements of a stream that fail a monadic test

for :: (Monad m, Functor f) => Stream (Of a) m r -> (a -> Stream f m x) -> Stream f m r Source

for replaces each element of a stream with an associated stream. Note that the associated stream may layer any functor.

delay :: MonadIO m => Double -> Stream (Of a) m r -> Stream (Of a) m r Source

Effect each element by the supplied number of seconds. mapM :: Monad m => (a -> m b) -> Stream (Of a) m r -> Stream (Of b) m r

take :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m () Source

End a stream after n elements; the original return value is thus lost. splitAt preserves this information. Note that, like splitAt, this function is functor-general, so that, for example, you can take not just a number of items from a stream of elements, but a number of substreams and the like.

>>> S.print $ mapsM S.sum $ S.take 2 $ chunksOf 3 $ each [1..]
6   -- sum of first group of 3
15  -- sum of second group of 3

takeWhile :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m () Source

End stream when an element fails a condition; the original return value is lost span preserves this information.

drop :: Monad m => Int -> Stream (Of a) m r -> Stream (Of a) m r Source

Ignore the first n elements of a stream, but carry out the actions

dropWhile :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m r Source

Ignore elements of a stream until a test succeeds.

>>> IO.withFile "distribute.hs" IO.ReadMode $ S.stdoutLn . S.take 2 . S.dropWhile (isPrefixOf "import") . S.fromHandle
main :: IO ()
main = do

concat :: (Monad m, Foldable f) => Stream (Of (f a)) m r -> Stream (Of a) m r Source

Make a stream of traversable containers into a stream of their separate elements. This is just

concat = for str each
>>> S.print $ S.concat (each ["xy","z"])
'x'
'y'
'z'

Note that it also has the effect of catMaybes and rights

>>> S.print $ S.concat $ S.each [Just 1, Nothing, Just 2]
1
2
>>> S.print $  S.concat $ S.each [Right 1, Left "Error!", Right 2]
1
2

concat is not to be confused with the functor-general

concats :: (Monad m, Functor f) => Stream (Stream f m) m r -> Stream f m r -- specializing
>>> S.stdoutLn $ concats $ maps (<* yield "--\n--") $ chunksOf 2 $ S.show (each [1..5])
1
2
--
--
3
4
--
--
5
--
--

scan :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> Stream (Of b) m r Source

Strict left scan, streaming, e.g. successive partial results.

Control.Foldl.purely scan :: Monad m => Fold a b -> Stream (Of a) m r -> Stream (Of b) m r
>>> S.print $ L.purely S.scan L.list $ each [3..5]
[]
[3]
[3,4]
[3,4,5]

A simple way of including the scanned item with the accumulator is to use last. See also scanned

>>> let a >< b = (,) <$> a <*> b
>>> S.print $ L.purely S.scan (L.last >< L.sum) $ S.each [1..3]
(Nothing,0)
(Just 1,1)
(Just 2,3)
(Just 3,6)

scanM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream (Of a) m r -> Stream (Of b) m r Source

Strict, monadic left scan

Control.Foldl.impurely scanM :: Monad m => FoldM a m b -> Stream (Of a) m r -> Stream (Of b) m r
>>> let v =  L.impurely scanM L.vector $ each [1..4::Int] :: Stream (Of (U.Vector Int)) IO ()
>>> S.print v
fromList []
fromList [1]
fromList [1,2]
fromList [1,2,3]
fromList [1,2,3,4]

scanned :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> Stream (Of (a, b)) m r Source

read :: (Monad m, Read a) => Stream (Of String) m r -> Stream (Of a) m r Source

Make a stream of strings into a stream of parsed values, skipping bad cases

show :: (Monad m, Show a) => Stream (Of a) m r -> Stream (Of String) m r Source

cons :: Monad m => a -> Stream (Of a) m r -> Stream (Of a) m r Source

The natural cons for a Stream (Of a).

cons a stream = yield a >> stream

Useful for interoperation:

Data.Text.foldr S.cons (return ()) :: Text -> Stream (Of Char) m ()
Lazy.foldrChunks S.cons (return ()) :: Lazy.ByteString -> Stream (Of Strict.ByteString) m ()

and so on.

duplicate :: Monad m => Stream (Of a) m r -> Stream (Of a) (Stream (Of a) m) r Source

Splitting and inspecting streams of elements

next :: Monad m => Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r)) Source

The standard way of inspecting the first item in a stream of elements, if the stream is still 'running'. The Right case contains a Haskell pair, where the more general inspect would return a left-strict pair. There is no reason to prefer inspect since, if the Right case is exposed, the first element in the pair will have been evaluated to whnf.

next :: Monad m => Stream (Of a) m r -> m (Either r (a, Stream (Of a) m r))
inspect :: Monad m => Stream (Of a) m r -> m (Either r (Of a (Stream (Of a) m r)))

Interoperate with pipes producers thus:

Pipes.unfoldr Stream.next :: Stream (Of a) m r -> Producer a m r
Stream.unfoldr Pipes.next :: Producer a m r -> Stream (Of a) m r 

Similarly:

IOStreams.unfoldM (liftM (either (const Nothing) Just) . next) :: Stream (Of a) IO b -> IO (InputStream a)
Conduit.unfoldM (liftM (either (const Nothing) Just) . next)   :: Stream (Of a) m r -> Source a m r

But see uncons, which is better fitted to these unfoldMs

uncons :: Monad m => Stream (Of a) m () -> m (Maybe (a, Stream (Of a) m ())) Source

Inspect the first item in a stream of elements, without a return value. uncons provides convenient exit into another streaming type:

IOStreams.unfoldM uncons :: Stream (Of a) IO b -> IO (InputStream a)
Conduit.unfoldM uncons   :: Stream (Of a) m r -> Conduit.Source m a

splitAt :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m (Stream f m r) Source

Split a succession of layers after some number, returning a streaming or -- effectful pair. This function is the same as the splitsAt exported by the -- Streaming module, but since this module is imported qualified, it can -- usurp a Prelude name. It specializes to:

 splitAt :: (Monad m, Functor f) => Int -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r)

split :: (Eq a, Monad m) => a -> Stream (Of a) m r -> Stream (Stream (Of a) m) m r Source

Split a stream of elements wherever a given element arises. The action is like that of words.

>>> S.stdoutLn $ mapsM S.toList $ split ' ' "hello world  "
hello
world
>>> Prelude.mapM_ Prelude.putStrLn (Prelude.words "hello world  ")
hello
world

breaks :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Stream (Of a) m) m r Source

break :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r) Source

Break a sequence when a element falls under a predicate, keeping the rest of the stream as the return value.

>>> rest <- S.print $ S.break even $ each [1,1,2,3]
1
1
>>> S.print rest
2
3

breakWhen :: Monad m => (x -> a -> x) -> x -> (x -> b) -> (b -> Bool) -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r) Source

Yield elements, using a fold to maintain state, until the accumulated value satifies the supplied predicate. The fold will then be short-circuited and the element that breaks it will be included with the stream returned. This function is easiest to use with purely

>>> rest <- S.print $ L.purely S.breakWhen L.sum even $ S.each [1,2,3,4]
1
2
>>> S.print rest
3
4

span :: Monad m => (a -> Bool) -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r) Source

Stream elements until one fails the condition, return the rest.

group :: (Monad m, Eq a) => Stream (Of a) m r -> Stream (Stream (Of a) m) m r Source

groupBy :: Monad m => (a -> a -> Bool) -> Stream (Of a) m r -> Stream (Stream (Of a) m) m r Source

Group elements of a stream by comparisons on a preliminary annotation

groupedBy :: (Monad m, Functor f) => (a -> a -> Bool) -> Stream (Compose (Of a) f) m r -> Stream (Stream (Compose (Of a) f) m) m r Source

Group layers of any functor by comparisons on a preliminary annotation

timed :: MonadIO m => Double -> Stream (Of a) m r -> Stream (Of a) m (Stream (Of a) m r) Source

Sum and Compose manipulation

distinguish :: (a -> Bool) -> Of a r -> Sum (Of a) (Of a) r Source

switch :: Sum f g r -> Sum g f r Source

Swap the order of functors in a sum of functors.

>>> S.toListM' $ S.print $ separate $ maps S.switch $ maps (S.distinguish (=='a')) $ S.each "banana"
'a'
'a'
'a'
"bnn" :> ()
>>> S.toListM' $ S.print $ separate $ maps (S.distinguish (=='a')) $ S.each "banana"
'b'
'n'
'n'
"aaa" :> ()

separate :: (Monad m, Functor f, Functor g) => Stream (Sum f g) m r -> Stream f (Stream g m) r Source

Given a stream on a sum of functors, make it a stream on the left functor, with the streaming on the other functor as the governing monad. This is useful for acting on one or the other functor with a fold.

>>> let odd_even = S.maps (S.distinguish even) $ S.each [1..10]
>>> :t S.effects $ separate odd_even

Now, for example, it is convenient to fold on the left and right values separately:

>>> toListM' $ toList' (separate odd_even)
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())
>>> S.toListM' $ S.print $ separate $  odd_even
1
3
5
7
9
[2,4,6,8,10] :> ()

We can easily use this device in place of filter:

filter = S.effects . separate . maps (distinguish f)
>>> :t hoist S.effects $ separate odd_even
hoist S.effects $ separate odd_even :: Monad n => Stream (Of Int) n ()
>>> S.print $ effects $ separate odd_even
2
4
6
8
10
>>> S.print $ hoist effects $ separate odd_even
1
3
5
7
9

unseparate :: (Monad m, Functor f, Functor g) => Stream f (Stream g m) r -> Stream (Sum f g) m r Source

eitherToSum :: Of (Either a b) r -> Sum (Of a) (Of b) r Source

sumToCompose :: Sum f f r -> Compose (Of Bool) f r Source

composeToSum :: Compose (Of Bool) f r -> Sum f f r Source

Folds

Use these to fold the elements of a Stream.

>>> S.fold_ (+) 0 id $ S.each [1..0]
50

The general folds fold, fold_', foldM and foldM_ are arranged for use with Foldl

>>> L.purely fold_ L.sum $ each [1..10]
55
>>> L.purely fold_ (liftA3 (,,) L.sum L.product L.list) $ each [1..10]
(55,3628800,[1,2,3,4,5,6,7,8,9,10])

All functions marked with an underscore omit (e.g. fold_, sum_) the stream's return value in a left-strict pair. They are good for exiting streaming completely, but when you are, e.g. mapsM-ing over a Stream (Stream (Of a) m) m r, which is to be compared with [[a]]. Specializing, we have e.g.

 mapsM sum :: (Monad m, Num n) => Stream (Stream (Of Int)) IO () -> Stream (Of n) IO ()
 mapsM (fold mappend mempty id) :: Stream (Stream (Of Int)) IO () -> Stream (Of Int) IO ()
>>> S.print $ mapsM S.sum $ chunksOf 3 $ S.each [1..10]
6
15
24
10
>>> let three_folds = L.purely S.fold (liftA3 (,,) L.sum L.product L.list)
>>> S.print $ mapsM three_folds $ chunksOf 3 (each [1..10])
(6,6,[1,2,3])
(15,120,[4,5,6])
(24,504,[7,8,9])
(10,10,[10])

fold :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m (Of b r) Source

Strict fold of a Stream of elements that preserves the return value.

>>> S.sum $ each [1..10]
55 :> ()
>>> (n :> rest)  <- S.sum $ S.splitAt 3 (each [1..10])
>>> print n
6
>>> (m :> rest') <- S.sum $ S.splitAt 3 rest
>>> print m
15
>>> S.print rest'
7
8
9

The type provides for interoperation with the foldl library.

Control.Foldl.purely fold :: Monad m => Fold a b -> Stream (Of a) m r -> m (Of b r)

Thus, specializing a bit:

L.purely fold L.sum :: Stream (Of Int) Int r -> m (Of Int r)
maps (L.purely fold L.sum) :: Stream (Stream (Of Int)) IO r -> Stream (Of Int) IO r
>>> S.print $ mapsM (L.purely S.fold (liftA2 (,) L.list L.sum)) $ chunksOf 3 $ each [1..10]
([1,2,3],6)
([4,5,6],15)
([7,8,9],24)
([10],10)

fold_ :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r -> m b Source

Strict fold of a Stream of elements

Control.Foldl.purely fold :: Monad m => Fold a b -> Stream (Of a) m () -> m b

foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream (Of a) m r -> m (Of b r) Source

Strict, monadic fold of the elements of a 'Stream (Of a)'

Control.Foldl.impurely foldM' :: Monad m => FoldM a b -> Stream (Of a) m r -> m (b, r)

foldM_ :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream (Of a) m r -> m b Source

Strict, monadic fold of the elements of a 'Stream (Of a)'

Control.Foldl.impurely foldM :: Monad m => FoldM a b -> Stream (Of a) m () -> m b

sum :: (Monad m, Num a) => Stream (Of a) m r -> m (Of a r) Source

Fold a Stream of numbers into their sum with the return value

 maps' sum' :: Stream (Stream (Of Int)) m r -> Stream (Of Int) m r

sum_ :: (Monad m, Num a) => Stream (Of a) m () -> m a Source

Fold a Stream of numbers into their sum

product :: (Monad m, Num a) => Stream (Of a) m r -> m (Of a r) Source

Fold a Stream of numbers into their product with the return value

 maps' product' :: Stream (Stream (Of Int)) m r -> Stream (Of Int) m r

product_ :: (Monad m, Num a) => Stream (Of a) m () -> m a Source

Fold a Stream of numbers into their product

length :: Monad m => Stream (Of a) m r -> m (Of Int r) Source

Run a stream, keeping its length and its return value.

>>> S.print $ mapsM S.length $ chunksOf 3 $ S.each [1..10]
3
3
3
1

length_ :: Monad m => Stream (Of a) m r -> m Int Source

Run a stream, remembering only its length:

>>> S.length $ S.each [1..10]
10

toList :: Monad m => Stream (Of a) m r -> m (Of [a] r) Source

Convert an effectful Stream into a list alongside the return value

 mapsM toListM :: Stream (Stream (Of a)) m r -> Stream (Of [a]) m 

toList_ :: Monad m => Stream (Of a) m () -> m [a] Source

Convert an effectful 'Stream (Of a)' into a list of as

Note: Needless to say this function does not stream properly. It is basically the same as mapM which, like replicateM, sequence and similar operations on traversable containers is a leading cause of space leaks.

mconcat :: (Monad m, Monoid w) => Stream (Of w) m r -> m (Of w r) Source

mconcat_ :: (Monad m, Monoid w) => Stream (Of w) m r -> m w Source

foldrM :: Monad m => (a -> m r -> m r) -> Stream (Of a) m r -> m r Source

A natural right fold for consuming a stream of elements. See also the more general iterT in the Streaming module and the still more general destroy

foldrT :: (Monad m, MonadTrans t, Monad (t m)) => (a -> t m r -> t m r) -> Stream (Of a) m r -> t m r Source

A natural right fold for consuming a stream of elements. See also the more general iterTM in the Streaming module and the still more general destroy

foldrT (\a p -> Pipes.yield a >> p) :: Monad m => Stream (Of a) m r -> Producer a m r
foldrT (\a p -> Conduit.yield a >> p) :: Monad m => Stream (Of a) m r -> Conduit a m r

Zips

zip :: Monad m => Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of (a, b)) m r Source

Zip two Streamss

zipWith :: Monad m => (a -> b -> c) -> Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r Source

Zip two Streamss using the provided combining function

zip3 :: Monad m => Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r -> Stream (Of (a, b, c)) m r Source

Zip three streams together

zipWith3 :: Monad m => (a -> b -> c -> d) -> Stream (Of a) m r -> Stream (Of b) m r -> Stream (Of c) m r -> Stream (Of d) m r Source

Zip three Streams with a combining function

Pair manipulation

lazily :: Of a b -> (a, b) Source

Note that lazily, strictly, fst', and mapOf are all so-called natural transformations on the primitive Of a functor If we write

 type f ~~> g = forall x . f x -> g x

then we can restate some types as follows:

 mapOf            :: (a -> b) -> Of a ~~> Of b   -- bifunctor lmap
 lazily           ::             Of a ~~> (,) a
 Identity . fst'  ::             Of a ~~> Identity a

Manipulation of a Stream f m r by mapping often turns on recognizing natural transformations of f, thus maps is far more general the the map of the present module, which can be defined thus:

 S.map :: (a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
 S.map f = maps (mapOf f)

This rests on recognizing that mapOf is a natural transformation; note though that it results in such a transformation as well:

 S.map :: (a -> b) -> Stream (Of a) m ~> Stream (Of b) m   

strictly :: (a, b) -> Of a b Source

fst' :: Of a b -> a Source

snd' :: Of a b -> b Source

Interoperation

reread :: Monad m => (s -> m (Maybe a)) -> s -> Stream (Of a) m () Source

Read an IORef (Maybe a) or a similar device until it reads Nothing. reread provides convenient exit from the io-streams library

reread readIORef    :: IORef (Maybe a) -> Stream (Of a) IO ()
reread Streams.read :: System.IO.Streams.InputStream a -> Stream (Of a) IO ()

Basic Type

data Stream f m r Source

Instances

Functor f => MFunctor (Stream f) Source 
Functor f => MMonad (Stream f) Source 
Functor f => MonadTrans (Stream f) Source 
(Functor f, Monad m) => Monad (Stream f m) Source 
(Functor f, Monad m) => Functor (Stream f m) Source 
(Functor f, Monad m) => Applicative (Stream f m) Source 
(MonadIO m, Functor f) => MonadIO (Stream f m) Source 
(Eq r, Eq (m (Stream f m r)), Eq (f (Stream f m r))) => Eq (Stream f m r) Source 
(Typeable (* -> *) f, Typeable (* -> *) m, Data r, Data (m (Stream f m r)), Data (f (Stream f m r))) => Data (Stream f m r) Source 
(Show r, Show (m (Stream f m r)), Show (f (Stream f m r))) => Show (Stream f m r) Source