Copyright | (c) 2017 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
To run examples in this module:
>>>
import qualified Streamly.Prelude as Stream
Synopsis
- newtype SerialT m a = SerialT {
- getSerialT :: Stream m a
- type Serial = SerialT IO
- serial :: SerialT m a -> SerialT m a -> SerialT m a
- newtype WSerialT m a = WSerialT {
- getWSerialT :: Stream m a
- type WSerial = WSerialT IO
- wSerialK :: Stream m a -> Stream m a -> Stream m a
- wSerial :: WSerialT m a -> WSerialT m a -> WSerialT m a
- wSerialFst :: WSerialT m a -> WSerialT m a -> WSerialT m a
- wSerialMin :: WSerialT m a -> WSerialT m a -> WSerialT m a
- consMWSerial :: Monad m => m a -> WSerialT m a -> WSerialT m a
- cons :: a -> SerialT m a -> SerialT m a
- consM :: Monad m => m a -> SerialT m a -> SerialT m a
- repeat :: Monad m => a -> SerialT m a
- unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> SerialT m a
- fromList :: IsList l => [Item l] -> l
- toList :: IsList l => l -> [Item l]
- map :: Monad m => (a -> b) -> SerialT m a -> SerialT m b
- mapM :: Monad m => (a -> m b) -> SerialT m a -> SerialT m b
- type StreamT = SerialT
- type InterleavedT = WSerialT
Serial appending stream
For SerialT
streams:
(<>) =serial
--Semigroup
(>>=) = flip .concatMapWith
serial
--Monad
A single Monad
bind behaves like a for
loop:
>>>
:{
Stream.toList $ do x <- Stream.fromList [1,2] -- foreach x in stream return x :} [1,2]
Nested monad binds behave like nested for
loops:
>>>
:{
Stream.toList $ do x <- Stream.fromList [1,2] -- foreach x in stream y <- Stream.fromList [3,4] -- foreach y in stream return (x, y) :} [(1,3),(1,4),(2,3),(2,4)]
Since: 0.2.0 (Streamly)
Since: 0.8.0
SerialT | |
|
Instances
Serial interleaving stream
For WSerialT
streams:
(<>) =wSerial
--Semigroup
(>>=) = flip .concatMapWith
wSerial
--Monad
Note that <>
is associative only if we disregard the ordering of elements
in the resulting stream.
A single Monad
bind behaves like a for
loop:
>>>
:{
Stream.toList $ Stream.fromWSerial $ do x <- Stream.fromList [1,2] -- foreach x in stream return x :} [1,2]
Nested monad binds behave like interleaved nested for
loops:
>>>
:{
Stream.toList $ Stream.fromWSerial $ do x <- Stream.fromList [1,2] -- foreach x in stream y <- Stream.fromList [3,4] -- foreach y in stream return (x, y) :} [(1,3),(2,3),(1,4),(2,4)]
It is a result of interleaving all the nested iterations corresponding to
element 1
in the first stream with all the nested iterations of element
2
:
>>>
import Streamly.Prelude (wSerial)
>>>
Stream.toList $ Stream.fromList [(1,3),(1,4)] `Stream.wSerial` Stream.fromList [(2,3),(2,4)]
[(1,3),(2,3),(1,4),(2,4)]
The W
in the name stands for wide
or breadth wise scheduling in
contrast to the depth wise scheduling behavior of SerialT
.
Since: 0.2.0 (Streamly)
Since: 0.8.0
WSerialT | |
|
Instances
wSerial :: WSerialT m a -> WSerialT m a -> WSerialT m a infixr 6 Source #
Interleaves two streams, yielding one element from each stream alternately. When one stream stops the rest of the other stream is used in the output stream.
Construction
repeat :: Monad m => a -> SerialT m a Source #
Generate an infinite stream by repeating a pure value.
unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> SerialT m a Source #
Build a stream by unfolding a monadic step function starting from a
seed. The step function returns the next element in the stream and the next
seed value. When it is done it returns Nothing
and the stream ends. For
example,
let f b = if b > 3 then return Nothing else print b >> return (Just (b, b + 1)) in drain $ unfoldrM f 0
0 1 2 3
Pre-release
fromList :: IsList l => [Item l] -> l #
The fromList
function constructs the structure l
from the given
list of Item l
Elimination
toList :: IsList l => l -> [Item l] #
The toList
function extracts a list of Item l
from the structure l
.
It should satisfy fromList . toList = id.
Transformation
Deprecated
type InterleavedT = WSerialT Source #
Deprecated: Please use WSerialT
instead.
Since: 0.1.0