linear-base-0.5.0: Standard library for linear types.
Safe HaskellNone
LanguageHaskell2010

Streaming.Prelude.Linear

Description

The names exported by this module are closely modeled on those in Prelude and Data.List, but also on Pipes.Prelude, Pipes.Group and Pipes.Parse. The module may be said to give independent expression to the conception of Producer / Source / Generator manipulation articulated in the latter two modules. Because we dispense with piping and conduiting, the distinction between all of these modules collapses. Some things are lost but much is gained: on the one hand, everything comes much closer to ordinary beginning Haskell programming and, on the other, acquires the plasticity of programming directly with a general free monad type. The leading type, Stream (Of a) m r is chosen to permit an api that is as close as possible to that of Data.List and the Prelude.

Import qualified thus:

import Streaming
import qualified Streaming.Prelude as S

For the examples below, one sometimes needs

import Streaming.Prelude (each, yield, next, mapped, stdoutLn, stdinLn)
import Data.Function ((&))

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

Documentation

data Stream (f :: Type -> Type) (m :: Type -> Type) r where Source #

Constructors

Step :: forall (f :: Type -> Type) (m :: Type -> Type) r. !(f (Stream f m r)) -> Stream f m r 
Effect :: forall (m :: Type -> Type) (f :: Type -> Type) r. m (Stream f m r) -> Stream f m r 
Return :: forall r (f :: Type -> Type) (m :: Type -> Type). r -> Stream f m r 

Instances

Instances details
Functor f => MonadTrans (Stream f) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

lift :: Monad m => m a %1 -> Stream f m a Source #

(Functor m, Functor f) => Applicative (Stream f m) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

pure :: a %1 -> Stream f m a Source #

(<*>) :: Stream f m (a %1 -> b) %1 -> Stream f m a %1 -> Stream f m b Source #

liftA2 :: (a %1 -> b %1 -> c) %1 -> Stream f m a %1 -> Stream f m b %1 -> Stream f m c Source #

(Functor m, Functor f) => Functor (Stream f m) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

fmap :: (a %1 -> b) %1 -> Stream f m a %1 -> Stream f m b Source #

(Functor m, Functor f) => Monad (Stream f m) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

(>>=) :: Stream f m a %1 -> (a %1 -> Stream f m b) %1 -> Stream f m b Source #

(>>) :: Stream f m () %1 -> Stream f m a %1 -> Stream f m a Source #

(Functor m, Functor f) => Applicative (Stream f m) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

pure :: a -> Stream f m a Source #

(<*>) :: Stream f m (a %1 -> b) %1 -> Stream f m a %1 -> Stream f m b Source #

liftA2 :: (a %1 -> b %1 -> c) -> Stream f m a %1 -> Stream f m b %1 -> Stream f m c Source #

(Functor m, Functor f) => Functor (Stream f m) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

fmap :: (a %1 -> b) -> Stream f m a %1 -> Stream f m b Source #

data Of a b where Source #

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

Constructors

(:>) :: forall a b. !a -> b -> Of a b infixr 5 

Instances

Instances details
Functor (Of a) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

fmap :: (a0 %1 -> b) %1 -> Of a a0 %1 -> Of a b Source #

Functor (Of a) Source # 
Instance details

Defined in Streaming.Linear.Internal.Type

Methods

fmap :: (a0 %1 -> b) -> Of a a0 %1 -> Of a b Source #

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

Convert an effectful Stream into a list alongside the return value

 mapped toList :: Stream (Stream (Of a) m) m r %1-> Stream (Of [a]) m r

Like toList_, toList breaks streaming; unlike toList_ it preserves the return value and thus is frequently useful with e.g. mapped

>>> S.print $ mapped S.toList $ chunksOf 3 $ each' [1..9]
[1,2,3]
[4,5,6]
[7,8,9]
>>> S.print $ mapped S.toList $ chunksOf 2 $ S.replicateM 4 getLine
sEnter
tEnter
["s","t"]
uEnter
vEnter
["u","v"]

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

Fold streamed items into their monoidal sum

print :: Show a => Stream (Of a) IO r %1 -> IO r Source #

Print the elements of a stream as they arise.

head :: Monad m => Stream (Of a) m r %1 -> m (Of (Maybe a) r) Source #

Note that head exhausts the rest of the stream following the first element, performing all monadic effects via effects

last :: Monad m => Stream (Of a) m r %1 -> m (Of (Maybe a) r) Source #

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

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

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

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

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

 mapped S.sum :: Stream (Stream (Of Int)) m r %1-> Stream (Of Int) m r
>>> S.sum $ each' [1..10]
55 :> ()
>>> (n :> rest)  <- S.sum $ S.splitAt 3 $ each' [1..10]
>>> System.IO.print n
6
>>> (m :> rest') <- S.sum $ S.splitAt 3 rest
>>> System.IO.print m
15
>>> S.print rest'
7
8
9
10

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

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

 mapped product :: Stream (Stream (Of Int)) m r -> Stream (Of Int) m r

maximum :: (Monad m, Ord a) => Stream (Of a) m r %1 -> m (Of (Maybe a) r) Source #

minimum :: (Monad m, Ord a) => Stream (Of a) m r %1 -> m (Of (Maybe a) r) Source #

any :: Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> m (Of Bool r) Source #

Note: does not short circuit

all :: Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> m (Of Bool r) Source #

Note: does not short circuit

elem :: forall a m r. (Monad m, Eq a) => a -> Stream (Of a) m r %1 -> m (Of Bool r) infix 4 Source #

notElem :: (Monad m, Eq a) => a -> Stream (Of a) m r %1 -> m (Of Bool r) Source #

Exhaust a stream deciding whether a was an element.

fold :: forall x a b m r. Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r %1 -> m (Of b r) Source #

Strict fold of a Stream of elements that preserves the return value. This does not short circuit and all effects are performed. The third parameter will often be id where a fold is written by hand:

>>> S.fold (+) 0 id $ each' [1..10]
55 :> ()
>>> S.fold (*) 1 id $ S.fold (+) 0 id $ S.copy $ each' [1..10]
3628800 :> (55 :> ())

It can be used to replace a standard Haskell type with one more suited to writing a strict accumulation function. It is also crucial to the Applicative instance for Control.Foldl.Fold We can apply such a fold purely

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

Thus, specializing a bit:

L.purely S.fold L.sum :: Stream (Of Int) Int r %1-> m (Of Int r)
mapped (L.purely S.fold L.sum) :: Stream (Stream (Of Int)) IO r %1-> Stream (Of Int) IO r

Here we use the Applicative instance for Control.Foldl.Fold to stream three-item segments of a stream together with their sums and products.

>>> S.print $ mapped (L.purely S.fold (liftA3 (,,) L.list L.product L.sum)) $ chunksOf 3 $ each' 1..10
([4,5,6],120,15)
([7,8,9],504,24)
([10],10,10)

foldrM :: forall a m r. Monad m => (a -> m r %1 -> m r) -> Stream (Of a) m r %1 -> 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

mapM_ :: forall a m b r. (Consumable b, Monad m) => (a -> m b) -> Stream (Of a) m r %1 -> m r Source #

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

>>> S.mapM_ Prelude.print $ each' [1..3]
1
2
3
>>> rest <- S.mapM_ Prelude.print $ S.splitAt 3 $ each' [1..10]
1
2
3
>>> S.sum rest
49 :> ()

writeFile :: FilePath -> Stream (Of Text) RIO r %1 -> RIO r Source #

Write a stream of text as lines as lines to a file

foldM :: forall x a m b r. Monad m => (x %1 -> a -> m x) -> m x -> (x %1 -> m b) -> Stream (Of a) m r %1 -> m (b, r) Source #

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

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

Thus to accumulate the elements of a stream as a vector, together with a random element we might write:

>>> L.impurely S.foldM (liftA2 (,) L.vectorM L.random) $ each' [1..10::Int] :: IO (Of (Vector Int, Maybe Int) ())
([1,2,3,4,5,6,7,8,9,10],Just 9) :> ()

foldM_ :: forall a m x b r. (Monad m, Consumable r) => (x %1 -> a -> m x) -> m x -> (x %1 -> m b) -> Stream (Of a) m r %1 -> m b Source #

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

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

stdoutLn :: Stream (Of Text) IO () %1 -> IO () Source #

Write Strings to stdout using putStrLn; terminates on a broken output pipe (The name and implementation are modelled on the Pipes.Prelude stdoutLn).

>>> withLinearIO $ Control.fmap move $ S.stdoutLn $ S.each $ words "one two three" one two three

stdoutLn' :: Stream (Of Text) IO r %1 -> IO r Source #

Like stdoutLn but with an arbitrary return value

toHandle :: Handle %1 -> Stream (Of Text) RIO r %1 -> RIO (r, Handle) Source #

Write a stream to a handle and return the handle.

effects :: forall a m r. Monad m => Stream (Of a) m r %1 -> m r Source #

Reduce a stream, performing its actions but ignoring its elements.

>>> rest <- S.effects $ S.splitAt 2 $ each' [1..5]
>>> S.print rest
3
4
5

effects should be understood together with copy and is subject to the rules

S.effects . S.copy       = id
hoist S.effects . S.copy = id

The similar effects and copy operations in Data.ByteString.Streaming obey the same rules.

erase :: forall a (m :: Type -> Type) r. Monad m => Stream (Of a) m r %1 -> Stream Identity m r Source #

Remove the elements from a stream of values, retaining the structure of layers.

drained :: forall (m :: Type -> Type) t a r. (Monad m, Monad (t m), Functor (t m), MonadTrans t) => t m (Stream (Of a) m r) %1 -> 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 :: Control.Monad m => Stream (Of a) m (Stream (Of b) m r) -> Stream (Of a) m r
drained = Control.join . Control.fmap (Control.lift . effects)

Here, for example, we split a stream in two places and throw out the middle segment:

>>> rest <- S.print $ S.drained $ S.splitAt 2 $ S.splitAt 5 $ each' [1..7]
1
2
>>> S.print rest
6
7

fold_ :: forall x a b m r. (Monad m, Consumable r) => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r %1 -> m b Source #

Strict fold of a Stream of elements, preserving only the result of the fold, not the return value of the stream. This does not short circuit and all effects are performed. The third parameter will often be id where a fold is written by hand:

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

It can be used to replace a standard Haskell type with one more suited to writing a strict accumulation function. It is also crucial to the Applicative instance for Control.Foldl.Fold

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

all_ :: (Consumable r, Monad m) => (a -> Bool) -> Stream (Of a) m r %1 -> m Bool Source #

Note: does not short circuit

any_ :: (Consumable r, Monad m) => (a -> Bool) -> Stream (Of a) m r %1 -> m Bool Source #

Note: does not short circuit

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

Fold a Stream of numbers into their sum

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

Fold a Stream of numbers into their product

head_ :: (Consumable r, Monad m) => Stream (Of a) m r %1 -> m (Maybe a) Source #

Note that head exhausts the rest of the stream following the first element, performing all monadic effects via effects

last_ :: (Consumable r, Monad m) => Stream (Of a) m r %1 -> m (Maybe a) Source #

elem_ :: forall a m r. (Consumable r, Monad m, Eq a) => a -> Stream (Of a) m r %1 -> m Bool Source #

notElem_ :: (Consumable r, Monad m, Eq a) => a -> Stream (Of a) m r %1 -> m Bool Source #

length_ :: (Consumable r, Monad m) => Stream (Of a) m r %1 -> m Int Source #

Run a stream, remembering only its length:

>>> runIdentity $ S.length_ (S.each [1..10] :: Stream (Of Int) Identity ())
10

toList_ :: Monad m => Stream (Of a) m () %1 -> 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 Prelude mapM which, like replicateM, sequence and similar operations on traversable containers is a leading cause of space leaks.

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

minimum_ :: (Consumable r, Monad m, Ord a) => Stream (Of a) m r %1 -> m (Maybe a) Source #

maximum_ :: (Consumable r, Monad m, Ord a) => Stream (Of a) m r %1 -> m (Maybe a) Source #

foldrT :: forall a t (m :: Type -> Type) r. (Monad m, MonadTrans t, Monad (t m)) => (a -> t m r %1 -> t m r) -> Stream (Of a) m r %1 -> 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 -> Streaming.yield a >> p) = id

reread :: Monad m => (s -> m (Ur (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 ()

zip :: forall (m :: Type -> Type) a r1 b r2. Monad m => Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of (a, b)) m (r1, r2) Source #

zip zips two streams exhausing the remainder of the longer stream and consuming its effects.

zip3 :: forall (m :: Type -> Type) a r1 b r2 c r3. Monad m => Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of c) m r3 %1 -> Stream (Of (a, b, c)) m (r1, r2, r3) Source #

Like zipR but with three streams.

zipWith :: forall (m :: Type -> Type) a b c r1 r2. Monad m => (a -> b -> c) -> Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of c) m (r1, r2) Source #

zipWith3 :: forall (m :: Type -> Type) a b c d r1 r2 r3. Monad m => (a -> b -> c -> d) -> Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of c) m r3 %1 -> Stream (Of d) m (r1, r2, r3) Source #

Like zipWith but with three streams

unzip :: forall (m :: Type -> Type) a b r. Monad m => Stream (Of (a, b)) m r %1 -> Stream (Of a) (Stream (Of b) m) r Source #

The type

Data.List.unzip     :: [(a,b)] -> ([a],[b])

might lead us to expect

Streaming.unzip :: Stream (Of (a,b)) m r -> Stream (Of a) m (Stream (Of b) m r)

which would not stream, since it would have to accumulate the second stream (of bs). Of course, Data.List unzip doesn't stream either.

This unzip does stream, though of course you can spoil this by using e.g. toList:

>>> let xs = Prelude.map (x -> (x, Prelude.show x)) [1..5 :: Int]

>>> S.toList $ S.toList $ S.unzip (S.each' xs)
["1","2","3","4","5"] :> ([1,2,3,4,5] :> ())

>>> Prelude.unzip xs
([1,2,3,4,5],["1","2","3","4","5"])

Note the difference of order in the results. It may be of some use to think why. The first application of toList was applied to a stream of integers:

>>> :t S.unzip $ S.each' xs
S.unzip $ S.each' xs :: Control.Monad m => Stream (Of Int) (Stream (Of String) m) ()

Like any fold, toList takes no notice of the monad of effects.

toList :: Control.Monad m => Stream (Of a) m r %1-> m (Of [a] r)

In the case at hand (since I am in ghci) m = Stream (Of String) IO. So when I apply toList, I exhaust that stream of integers, folding it into a list:

>>> :t S.toList $ S.unzip $ S.each' xs
S.toList $ S.unzip $ S.each' xs
 :: Control.Monad m => Stream (Of String) m (Of [Int] ())

When I apply toList to this, I reduce everything to an ordinary action in IO, and return a list of strings:

>>> S.toList $ S.toList $ S.unzip (S.each' xs)
["1","2","3","4","5"] :> ([1,2,3,4,5] :> ())

unzip can be considered a special case of either unzips or expand:

 unzip = unzips . maps (((a,b) :> x) -> Compose (a :> b :> x))
 unzip = expand $ p ((a,b) :> abs) -> b :> p (a :> abs)

merge :: forall (m :: Type -> Type) a r s. (Monad m, Ord a) => Stream (Of a) m r %1 -> Stream (Of a) m s %1 -> Stream (Of a) m (r, s) Source #

Merge two streams of elements ordered with their Ord instance.

The return values of both streams are returned.

>>> S.print $ merge (each [1,3,5]) (each [2,4])
1
2
3
4
5
((), ())

mergeBy :: forall (m :: Type -> Type) a r s. Monad m => (a -> a -> Ordering) -> Stream (Of a) m r %1 -> Stream (Of a) m s %1 -> Stream (Of a) m (r, s) Source #

Merge two streams, ordering the elements using the given comparison function.

The return values of both streams are returned.

type ZipResidual a b (m :: Type -> Type) r1 r2 = Either3 (r1, r2) (r1, Stream (Of b) m r2) (Stream (Of a) m r1, r2) Source #

The remainder of zipping two streams

type ZipResidual3 a b c (m :: Type -> Type) r1 r2 r3 = (Either r1 (Stream (Of a) m r1), Either r2 (Stream (Of b) m r2), Either r3 (Stream (Of c) m r3)) Source #

The (liberal) remainder of zipping three streams. This has the downside that the possibility of three remainders is allowed, though it will never occur.

zipR :: forall (m :: Type -> Type) a r1 b r2. Monad m => Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of (a, b)) m (ZipResidual a b m r1 r2) Source #

zipR zips two streams keeping the remainder if there is one.

zipWithR :: forall (m :: Type -> Type) a b c r1 r2. Monad m => (a -> b -> c) -> Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of c) m (ZipResidual a b m r1 r2) Source #

zipWithR zips two streams applying a function along the way, keeping the remainder of zipping if there is one. Note. If two streams have the same length, but one needs to perform some effects to obtain the end-of-stream result, that stream is treated as a residual.

zip3R :: forall (m :: Type -> Type) a r1 b r2 c r3. Monad m => Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of c) m r3 %1 -> Stream (Of (a, b, c)) m (ZipResidual3 a b c m r1 r2 r3) Source #

Like zipR but with three streams.

zipWith3R :: forall (m :: Type -> Type) a b c d r1 r2 r3. Monad m => (a -> b -> c -> d) -> Stream (Of a) m r1 %1 -> Stream (Of b) m r2 %1 -> Stream (Of c) m r3 %1 -> Stream (Of d) m (ZipResidual3 a b c m r1 r2 r3) Source #

Like zipWithR but with three streams.

data Either3 a b c where Source #

Constructors

Left3 :: forall a b c. a -> Either3 a b c 
Middle3 :: forall b a c. b -> Either3 a b c 
Right3 :: forall c a b. c -> Either3 a b c 

mergeOn :: forall (m :: Type -> Type) b a r s. (Monad m, Ord b) => (a -> b) -> Stream (Of a) m r %1 -> Stream (Of a) m s %1 -> Stream (Of a) m (r, s) Source #

Merge two streams, ordering them by applying the given function to each element before comparing.

The return values of both streams are returned.

store :: forall (m :: Type -> Type) a r t. Monad m => (Stream (Of a) (Stream (Of a) m) r %1 -> t) -> Stream (Of a) m r %1 -> t Source #

Store the result of any suitable fold over a stream, keeping the stream for further manipulation. store f = f . copy :

>>> S.print $ S.store S.product $ each' [1..4]
1
2
3
4
24 :> ()
>>> S.print $ S.store S.sum $ S.store S.product $ each' [1..4]
1
2
3
4
10 :> (24 :> ())

Here the sum (10) and the product (24) have been 'stored' for use when finally we have traversed the stream with print . Needless to say, a second pass is excluded conceptually, so the folds that you apply successively with store are performed simultaneously, and in constant memory -- as they would be if, say, you linked them together with Control.Fold:

>>> L.impurely S.foldM (liftA3 (a b c -> (b, c)) (L.sink Prelude.print) (L.generalize L.sum) (L.generalize L.product)) $ each' [1..4]
1
2
3
4
(10,24) :> ()

Fusing folds after the fashion of Control.Foldl will generally be a bit faster than the corresponding succession of uses of store, but by constant factor that will be completely dwarfed when any IO is at issue.

But store / copy is much more powerful, as you can see by reflecting on uses like this:

>>> S.sum $ S.store (S.sum . mapped S.product . chunksOf 2) $ S.store (S.product . mapped S.sum . chunksOf 2) $ each' [1..6]
21 :> (44 :> (231 :> ()))

It will be clear that this cannot be reproduced with any combination of lenses, Control.Fold folds, or the like. (See also the discussion of copy.)

It would conceivably be clearer to import a series of specializations of store. It is intended to be used at types like this:

storeM ::  (forall s m . Control.Monad m => Stream (Of a) m s %1-> m (Of b s))
        -> (Control.Monad n => Stream (Of a) n r %1-> Stream (Of a) n (Of b r))
storeM = store

It is clear from this type that we are just using the general instance:

instance (Control.Functor f, Control.Monad m)   => Control.Monad (Stream f m)

We thus can't be touching the elements of the stream, or the final return value. It is the same with other constraints that Stream (Of a) inherits from the underlying monad. Thus I can independently filter and write to one file, but nub and write to another, or interact with a database and a logfile and the like:

>>> (S.writeFile "hello2.txt" . S.nubOrd) $ store (S.writeFile "hello.txt" . S.filter (/= "world")) $ each' ["hello", "world", "goodbye", "world"]
>>> :! cat hello.txt
hello
goodbye
>>> :! cat hello2.txt
hello
world
goodbye

split :: forall a (m :: Type -> Type) r. (Eq a, Monad m) => a -> Stream (Of a) m r %1 -> 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 $ mapped S.toList $ S.split ' ' $ each' "hello world  "
hello
world

delay :: Double -> Stream (Of a) IO r %1 -> Stream (Of a) IO r Source #

Interpolate a delay of n seconds between yields.

map :: forall (m :: Type -> Type) a b r. Monad m => (a -> b) -> Stream (Of a) m r %1 -> Stream (Of b) m r Source #

Standard map on the elements of a stream.

>>> S.stdoutLn $ S.map reverse $ each' (words "alpha beta")
ahpla
ateb

filter :: forall a (m :: Type -> Type) r. Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

Skip elements of a stream that fail a predicate

sequence :: forall a m r. Monad m => Stream (Of (m (Ur a))) m r %1 -> 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 :: Control.Monad m => Stream (Of (m a)) m r %1-> Stream (Of a) m r

mapM :: Monad m => (a -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r Source #

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

>>> S.print $ S.mapM readIORef $ S.chain (ior -> modifyIORef ior (*100)) $ S.mapM newIORef $ each' [1..6]
100
200
300
400
500
600

See also chain for a variant of this which ignores the return value of the function and just uses the side effects.

catMaybes :: forall (m :: Type -> Type) a r. Monad m => Stream (Of (Maybe a)) m r %1 -> Stream (Of a) m r Source #

The catMaybes function takes a Stream of Maybes and returns a Stream of all of the Just values. concat has the same behavior, but is more general; it works for any foldable container type.

mapMaybe :: forall a b (m :: Type -> Type) r. Monad m => (a -> Maybe b) -> Stream (Of a) m r %1 -> Stream (Of b) m r Source #

The mapMaybe function is a version of map which can throw out elements. In particular, the functional argument returns something of type Maybe b. If this is Nothing, no element is added on to the result Stream. If it is Just b, then b is included in the result Stream.

uncons :: forall a m r. (Consumable r, Monad m) => Stream (Of a) m r %1 -> m (Maybe (a, Stream (Of a) m r)) Source #

Inspect the first item in a stream of elements, without a return value.

dropWhile :: forall a (m :: Type -> Type) r. Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

Ignore elements of a stream until a test succeeds, retaining the rest.

>>> S.print $ S.dropWhile ((< 5) . length) S.stdinLn
oneEnter
twoEnter
threeEnter
"three"
fourEnter
"four"
^CInterrupted.

drop :: forall a (m :: Type -> Type) r. (HasCallStack, Monad m) => Int -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

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

>>> S.toList $ S.drop 2 $ S.replicateM 5 getLine
aEnter
bEnter
cEnter
dEnter
eEnter
["c","d","e"] :> ()

Because it retains the final return value, drop n is a suitable argument for maps:

>>> S.toList $ concats $ maps (S.drop 4) $ chunksOf 5 $ each [1..20]
[5,10,15,20] :> ()

splitAt :: forall (f :: Type -> Type) (m :: Type -> Type) r. (Monad m, Functor f) => Int -> Stream f m r %1 -> 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 :: Control.Monad m => Int -> Stream (Of a) m r %1-> Stream (Of a) m (Stream (Of a) m r)

span :: forall (m :: Type -> Type) a r. Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r) Source #

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

break :: forall a (m :: Type -> Type) r. Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r) Source #

Break a sequence upon meeting an element that falls under a predicate, keeping it and 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

show :: forall (m :: Type -> Type) a r. (Monad m, Show a) => Stream (Of a) m r %1 -> Stream (Of String) m r Source #

partitionEithers :: forall (m :: Type -> Type) a b r. Monad m => Stream (Of (Either a b)) m r %1 -> Stream (Of a) (Stream (Of b) m) r Source #

Separate left and right values in distinct streams. (separate is a more powerful, functor-general, equivalent using Sum in place of Either).

partitionEithers = separate . maps S.eitherToSum
lefts  = hoist S.effects . partitionEithers
rights = S.effects . partitionEithers
rights = S.concat

read :: forall (m :: Type -> Type) a r. (Monad m, Read a) => Stream (Of String) m r %1 -> Stream (Of a) m r Source #

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

>>> S.sum_ $ S.read $ S.takeWhile (/= "total") S.stdinLn :: IO Int
1000Enter
2000Enter
totalEnter
3000

intersperse :: forall a (m :: Type -> Type) r. Monad m => a -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

Intersperse given value between each element of the stream.

>>> S.print $ S.intersperse 0 $ each [1,2,3]
1
0
2
0
3

partition :: forall a (m :: Type -> Type) r. Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r Source #

filter p = hoist effects (partition p)

group :: forall (m :: Type -> Type) a r. (Monad m, Eq a) => Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r Source #

Group successive equal items together

>>> S.toList $ mapped S.toList $ S.group $ each' "baaaaad"
["b","aaaaa","d"] :> ()
>>> S.toList $ concats $ maps (S.drained . S.splitAt 1) $ S.group $ each' "baaaaaaad"
"bad" :> ()

groupBy :: forall a (m :: Type -> Type) r. Monad m => (a -> a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r Source #

Group elements of a stream in accordance with the supplied comparison.

>>> S.print $ mapped S.toList $ S.groupBy (>=) $ each' [1,2,3,1,2,3,4,3,2,4,5,6,7,6,5]
[1]
[2]
[3,1,2,3]
[4,3,2,4]
[5]
[6]
[7,6,5]

with :: forall f (m :: Type -> Type) r a x. (Monad m, Functor f, Consumable x) => Stream (Of a) m r %1 -> (a -> f x) -> Stream f m r Source #

Replace each element in a stream of individual Haskell values (a Stream (Of a) m r) with an associated functorial step.

for str f  = concats (with str f)
with str f = for str (yields . f)
with str f = maps (\(a:>r) -> r <$ f a) str
with = flip subst
subst = flip with
>>> with (each' [1..3]) (yield . Prelude.show) & intercalates (yield "--") & S.stdoutLn
1
--
2
--
3

for :: forall (f :: Type -> Type) (m :: Type -> Type) r a x. (Monad m, Functor f, Consumable x) => Stream (Of a) m r %1 -> (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 control functor.

filterM :: forall a m r. Monad m => (a -> m Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

Skip elements of a stream that fail a monadic test

cons :: forall (m :: Type -> Type) a r. Monad m => a -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

The natural cons for a Stream (Of a).

cons a stream = yield a Control.>> 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.

copy :: forall a (m :: Type -> Type) r. Monad m => Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r Source #

Duplicate the content of a stream, so that it can be acted on twice in different ways, but without breaking streaming. Thus, with each' [1,2] I might do:

>>> S.print $ each' ["one","two"]
"one"
"two"
>>> S.stdoutLn $ each' ["one","two"]
one
two

With copy, I can do these simultaneously:

>>> S.print $ S.stdoutLn $ S.copy $ each' ["one","two"]
"one"
one
"two"
two

copy should be understood together with effects and is subject to the rules

S.effects . S.copy       = id
hoist S.effects . S.copy = id

The similar operations in Streaming obey the same rules.

Where the actions you are contemplating are each simple folds over the elements, or a selection of elements, then the coupling of the folds is often more straightforwardly effected with Foldl, e.g.

>>> L.purely S.fold (liftA2 (,) L.sum L.product) $ each' 1..10 :> ()

rather than

>>> S.sum $ S.product . S.copy $ each' [1..10]
55 :> (3628800 :> ())

A Control.Foldl fold can be altered to act on a selection of elements by using handles on an appropriate lens. Some such manipulations are simpler and more List-like, using copy:

>>> L.purely S.fold (liftA2 (,) (L.handles (L.filtered odd) L.sum) (L.handles (L.filtered even) L.product)) $ each' 1..10 :> ()

becomes

>>> S.sum $ S.filter odd $ S.product $ S.filter even $ S.copy' $ each' [1..10]
25 :> (3840 :> ())

or using store

>>> S.sum $ S.filter odd $ S.store (S.product . S.filter even) $ each' [1..10]
25 :> (3840 :> ())

But anything that fold of a Stream (Of a) m r into e.g. an m (Of b r) that has a constraint on m that is carried over into Stream f m - e.g. Control.Monad, Control.Functor, etc. can be used on the stream. Thus, I can fold over different groupings of the original stream:

>>>  (S.toList . mapped S.toList . chunksOf 5) $  (S.toList . mapped S.toList . chunksOf 3) $ S.copy $ each' [1..10]
[[1,2,3,4,5],[6,7,8,9,10]] :> ([[1,2,3],[4,5,6],[7,8,9],[10]] :> ())

The procedure can be iterated as one pleases, as one can see from this (otherwise unadvisable!) example:

>>>  (S.toList . mapped S.toList . chunksOf 4) $ (S.toList . mapped S.toList . chunksOf 3) $ S.copy $ (S.toList . mapped S.toList . chunksOf 2) $ S.copy $ each' [1..12]
[[1,2,3,4],[5,6,7,8],[9,10,11,12]] :> ([[1,2,3],[4,5,6],[7,8,9],[10,11,12]] :> ([[1,2],[3,4],[5,6],[7,8],[9,10],[11,12]] :> ()))

copy can be considered a special case of expand:

 copy = expand $ p (a :> as) -> a :> p (a :> as)

If Of were an instance of Comonad, then one could write

 copy = expand extend

nubOrd :: forall (m :: Type -> Type) a r. (Monad m, Ord a) => Stream (Of a) m r %1 -> Stream (Of a) m r Source #

Remove repeated elements from a Stream. nubOrd of course accumulates a Set of elements that have already been seen and should thus be used with care.

nubOrdOn :: forall (m :: Type -> Type) a b r. (Monad m, Ord b) => (a -> b) -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

Use nubOrdOn to have a custom ordering function for your elements.

nubInt :: forall (m :: Type -> Type) r. Monad m => Stream (Of Int) m r %1 -> Stream (Of Int) m r Source #

More efficient versions of above when working with Ints that use IntSet.

nubIntOn :: forall (m :: Type -> Type) a r. Monad m => (a -> Int) -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

duplicate :: forall a (m :: Type -> Type) r. Monad m => Stream (Of a) m r %1 -> Stream (Of a) (Stream (Of a) m) r Source #

An alias for copy.

next :: forall a m r. Monad m => Stream (Of a) m r %1 -> m (Either r (Ur 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    :: Control.Monad m => Stream (Of a) m r %1-> m (Either r    (a, Stream (Of a) m r))
inspect :: Control.Monad m => Stream (Of a) m r %1-> m (Either r (Of a (Stream (Of a) m r)))

chain :: forall a m r y. (Monad m, Consumable y) => (a -> m y) -> Stream (Of a) m r %1 -> Stream (Of a) m r Source #

Apply an action to all values, re-yielding each. The return value (y) of the function is ignored.

>>> S.product $ S.chain Prelude.print $ S.each' [1..5]
1
2
3
4
5
120 :> ()

See also mapM for a variant of this which uses the return value of the function to transorm the values in the stream.

mapMaybeM :: forall a m b r. Monad m => (a -> m (Maybe (Ur b))) -> Stream (Of a) m r %1 -> Stream (Of b) m r Source #

Map monadically over a stream, producing a new stream only containing the Just values.

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

Map layers of one functor to another with a transformation. Compare hoist, which has a similar effect on the monadic parameter.

maps id = id
maps f . maps g = maps (f . g)

mapsPost :: forall (m :: Type -> Type) f g r. (Monad m, Functor g) => (forall x. f x %1 -> g x) -> Stream f m r %1 -> Stream g m r Source #

Map layers of one functor to another with a transformation. Compare hoist, which has a similar effect on the monadic parameter.

mapsPost id = id
mapsPost f . mapsPost g = mapsPost (f . g)
mapsPost f = maps f

mapsPost is essentially the same as maps, but it imposes a Control.Functor constraint on its target functor rather than its source functor. It should be preferred if fmap is cheaper for the target functor than for the source functor.

mapsMPost :: forall m f g r. (Monad m, Functor g) => (forall x. f x %1 -> m (g x)) -> Stream f m r %1 -> Stream g m r Source #

Map layers of one functor to another with a transformation involving the base monad. mapsMPost is essentially the same as mapsM, but it imposes a Control.Functor constraint on its target functor rather than its source functor. It should be preferred if fmap is cheaper for the target functor than for the source functor.

mapsPost is more fundamental than mapsMPost, which is best understood as a convenience for effecting this frequent composition:

mapsMPost phi = decompose . mapsPost (Compose . phi)

The streaming prelude exports the same function under the better name mappedPost, which overlaps with the lens libraries.

mapped :: forall f g m r. (Monad m, Functor f) => (forall x. f x %1 -> m (g x)) -> Stream f m r %1 -> Stream g m r Source #

Map layers of one functor to another with a transformation involving the base monad.

This function is completely functor-general. It is often useful with the more concrete type

mapped :: (forall x. Stream (Of a) IO x -> IO (Of b x)) -> Stream (Stream (Of a) IO) IO r -> Stream (Of b) IO r

to process groups which have been demarcated in an effectful, IO-based stream by grouping functions like group, split or breaks. Summary functions like fold, foldM, mconcat or toList are often used to define the transformation argument. For example:

>>> S.toList_ $ S.mapped S.toList $ S.split c (S.each' "abcde")
["ab","de"]

maps and mapped obey these rules:

maps id              = id
mapped return        = id
maps f . maps g      = maps (f . g)
mapped f . mapped g  = mapped (f <=< g)
maps f . mapped g    = mapped (fmap f . g)
mapped f . maps g    = mapped (f <=< fmap g)

where f and g are Control.Monads

maps is more fundamental than mapped, which is best understood as a convenience for effecting this frequent composition:

mapped phi = decompose . maps (Compose . phi)

mappedPost :: forall m f g r. (Monad m, Functor g) => (forall x. f x %1 -> m (g x)) -> Stream f m r %1 -> Stream g m r Source #

A version of mapped that imposes a Control.Functor constraint on the target functor rather than the source functor. This version should be preferred if fmap on the target functor is cheaper.

separate :: forall (m :: Type -> Type) (f :: Type -> Type) (g :: Type -> Type) r. (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, leaving the other material for another treatment. It generalizes partitionEithers, but actually streams properly.

>>> let odd_even = S.maps (S.distinguish even) $ S.each' [1..10::Int]
>>> :t separate odd_even
separate odd_even
 :: Monad m => Stream (Of Int) (Stream (Of Int) m) ()

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

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

Or we can write them to separate files or whatever.

Of course, in the special case of Stream (Of a) m r, we can achieve the above effects more simply by using copy

>>> S.toList . S.filter even $ S.toList . S.filter odd $ S.copy $ each' [1..10::Int]
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())

But separate and unseparate are functor-general.

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

destroyExposed :: (Functor f, Monad m) => Stream f m r %1 -> (f b %1 -> b) -> (m b %1 -> b) -> (r %1 -> b) -> b Source #

breaks :: forall a (m :: Type -> Type) r. Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Stream (Of a) m) m r Source #

Break during periods where the predicate is not satisfied, grouping the periods when it is.

>>> S.print $ mapped S.toList $ S.breaks not $ S.each' [False,True,True,False,True,True,False]
[True,True]
[True,True]
>>> S.print $ mapped S.toList $ S.breaks id $ S.each' [False,True,True,False,True,True,False]
[False]
[False]
[False]

breakWhen :: forall (m :: Type -> Type) a x b r. Monad m => (x -> a -> x) -> x -> (x -> b) -> (b -> Bool) -> Stream (Of a) m r %1 -> 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 put after the break. This function is easiest to use with purely

>>> rest each' [1..10] & L.purely S.breakWhen L.sum (10) & S.print
1
2
3
4
>>> S.print rest
5
6
7
8
9
10

breakWhen' :: forall (m :: Type -> Type) a r. Monad m => (a -> Bool) -> Stream (Of a) m r %1 -> Stream (Of a) m (Stream (Of a) m r) Source #

Breaks on the first element to satisfy the predicate

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

switch :: forall (f :: Type -> Type) (g :: Type -> Type) r. Sum f g r -> Sum g f r Source #

Swap the order of functors in a sum of functors.

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

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

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

sumToCompose :: forall (f :: Type -> Type) r. Sum f f r -> Compose (Of Bool) f r Source #

composeToSum :: forall (f :: Type -> Type) r. Compose (Of Bool) f r -> Sum f f r Source #

hoist :: forall (f :: Type -> Type) m n r. (Monad m, Functor f) => (forall a. m a %1 -> n a) -> Stream f m r %1 -> Stream f n r Source #

Change the effects of one monad to another with a transformation. This is one of the fundamental transformations on streams. Compare with maps:

maps  :: (Control.Monad m, Control.Functor f) => (forall x. f x %1-> g x) -> Stream f m r %1-> Stream g m r
hoist :: (Control.Monad m, Control.Functor f) => (forall a. m a %1-> n a) -> Stream f m r %1-> Stream f n r

subst :: forall (m :: Type -> Type) f x a r. (Monad m, Functor f, Consumable x) => (a -> f x) -> Stream (Of a) m r %1 -> Stream f m r Source #

Replace each element in a stream of individual values with a functorial layer of any sort. subst = flip with and is more convenient in a sequence of compositions that transform a stream.

with = flip subst
for str f = concats $ subst f str
subst f = maps (\(a:>r) -> r <$ f a)
S.concat = concats . subst each

scan :: forall a x b (m :: Type -> Type) r. Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r %1 -> Stream (Of b) m r Source #

Strict left scan, streaming, e.g. successive partial results. The seed is yielded first, before any action of finding the next element is performed.

>>> S.print $ S.scan (++) "" id $ each' (words "a b c d")
""
"a"
"ab"
"abc"
"abcd"

scan is fitted for use with Control.Foldl, thus:

>>> S.print $ L.purely S.scan L.list $ each' [3..5]
[]
[3]
[3,4]
[3,4,5]

scanM :: forall a x b m r. Monad m => (x %1 -> a -> m (Ur x)) -> m (Ur x) -> (x %1 -> m (Ur b)) -> Stream (Of a) m r %1 -> Stream (Of b) m r Source #

Strict left scan, accepting a monadic function. It can be used with FoldMs from Control.Foldl using impurely. Here we yield a succession of vectors each recording

>>> let v = L.impurely scanM L.vectorM $ each' [1..4::Int] :: Stream (Of (Vector Int)) IO ()
>>> S.print v
[]
[1]
[1,2]
[1,2,3]
[1,2,3,4]

scanned :: forall a x b (m :: Type -> Type) r. Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream (Of a) m r %1 -> Stream (Of (a, b)) m r Source #

Label each element in a stream with a value accumulated according to a fold.

>>> S.print $ S.scanned (*) 1 id $ S.each' 100,200,300
(200,20000)
(300,6000000)
>>> S.print $ L.purely S.scanned' L.product $ S.each 100,200,300
(200,20000)
(300,6000000)

slidingWindow :: forall a b (m :: Type -> Type). Monad m => Int -> Stream (Of a) m b %1 -> Stream (Of (Seq a)) m b Source #

slidingWindow accumulates the first n elements of a stream, update thereafter to form a sliding window of length n. It follows the behavior of the slidingWindow function in conduit-combinators.

>>> S.print $ S.slidingWindow 4 $ S.each "123456"
fromList "1234"
fromList "2345"
fromList "3456"

wrapEffect :: forall m (f :: Type -> Type) y a r. (Monad m, Functor f, Consumable y) => m a -> (a %1 -> m y) -> Stream f m r %1 -> Stream f m r Source #

Before evaluating the monadic action returning the next step in the Stream, wrapEffect extracts the value in a monadic computation m a and passes it to a computation a -> m y.

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

Build a Stream by unfolding steps starting from a seed. In particular note that S.unfoldr S.next = id.

replicate :: forall (m :: Type -> Type) a. (HasCallStack, Monad m) => Int -> a -> Stream (Of a) m () Source #

Repeat an element several times.

yield :: forall (m :: Type -> Type) a. Monad m => a -> Stream (Of a) m () Source #

A singleton stream

>>> stdoutLn $ yield "hello"
hello
>>> S.sum $ do {yield 1; yield 2; yield 3}
6 :> ()

readFile :: FilePath -> Stream (Of Text) RIO () Source #

Read the lines of a file given the filename.

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

Repeat an action several times, streaming its results.

>>> import qualified Unsafe.Linear as Unsafe
>>> import qualified Data.Time as Time
>>> let getCurrentTime = fromSystemIO (Unsafe.coerce Time.getCurrentTime)
>>> S.print $ S.replicateM 2 getCurrentTime
2015-08-18 00:57:36.124508 UTC
2015-08-18 00:57:36.124785 UTC

iterateN :: forall (m :: Type -> Type) a. Monad m => Int -> (a -> a) -> a -> Stream (Of a) m () Source #

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

each' :: forall (m :: Type -> Type) a. Monad m => [a] -> Stream (Of a) m () Source #

Stream the elements of a pure, foldable container.

>>> S.print $ each' [1..3]
1
2
3

replicateZip :: forall (m :: Type -> Type) x r a. Monad m => Stream (Of x) m r -> a -> Stream (Of (a, x)) m r Source #

Replicate a constant element and zip it with the finite stream which is the first argument.

untilRight :: Monad m => m (Either (Ur a) r) -> Stream (Of a) m r Source #

stdinLnN :: Int -> Stream (Of Text) IO () Source #

stdinLnN n is a stream of n lines from standard input

stdinLnUntil :: (Text -> Bool) -> Stream (Of Text) IO () Source #

Provides a stream of standard input and omits the first line that satisfies the predicate

stdinLnUntilM :: (Text -> IO Bool) -> Stream (Of Text) IO () Source #

Provides a stream of standard input and omits the first line that satisfies the predicate, possibly requiring IO

stdinLnZip :: Stream (Of x) IO r %1 -> Stream (Of (x, Text)) IO r Source #

Given a finite stream, provide a stream of lines of standard input zipped with that finite stream

readLnN :: Read a => Int -> Stream (Of a) IO () Source #

readLnUntil :: Read a => (a -> Bool) -> Stream (Of a) IO () Source #

readLnUntilM :: Read a => (a -> IO Bool) -> Stream (Of a) IO () Source #

readLnZip :: Read a => Stream (Of x) IO r %1 -> Stream (Of (x, a)) IO r Source #

iterateZip :: forall (m :: Type -> Type) x r a. Monad m => Stream (Of x) m r -> (a -> a) -> a -> Stream (Of (x, a)) m r Source #

iterateMN :: Monad m => Int -> (a -> m (Ur a)) -> m (Ur a) -> Stream (Of a) m () Source #

Iterate a monadic function from a seed value, streaming the results forever.

iterateMZip :: Monad m => Stream (Of x) m r %1 -> (a -> m (Ur a)) -> m (Ur a) -> Stream (Of (x, a)) m r Source #

cycleN :: forall (m :: Type -> Type) r a. (Monad m, Consumable r) => Int -> Stream (Of a) m r -> Stream (Of a) m r Source #

Cycle a stream a finite number of times

cycleZip :: forall (m :: Type -> Type) s a r b. (Monad m, Consumable s) => Stream (Of a) m r %1 -> Stream (Of b) m s -> Stream (Of (a, b)) m (r, s) Source #

cycleZip s1 s2 will cycle s2 just enough to zip with the given finite stream s1. Note that we consume all the effects of the remainder of the cycled stream s2. That is, we consume s2 the smallest natural number of times we need to zip.

enumFromN :: forall (m :: Type -> Type) e. (Monad m, Enum e) => Int -> e -> Stream (Of e) m () Source #

Like enumFromThenN but where the next element in the enumeration is just the successor succ n for a given enum n.

enumFromZip :: forall (m :: Type -> Type) e a r. (Monad m, Enum e) => Stream (Of a) m r %1 -> e -> Stream (Of (a, e)) m r Source #

Like enumFromThenZip but where the next element in the enumeration is just the successor succ n for a given enum n.

enumFromThenN :: forall (m :: Type -> Type) e. (Monad m, Enum e) => Int -> e -> e -> Stream (Of e) m () Source #

An finite sequence of enumerable values at a fixed distance, determined by the first and second values.

>>> S.print $ S.enumFromThenN 3 100 200
100
200
300

enumFromThenZip :: forall (m :: Type -> Type) e a r. (Monad m, Enum e) => Stream (Of a) m r %1 -> e -> e -> Stream (Of (a, e)) m r Source #

A finite sequence of enumerable values at a fixed distance determined by the first and second values. The length is limited by zipping with a given finite stream, i.e., the first argument.