streamly-core-0.1.0: Streaming, parsers, arrays and more
Copyright(c) 2020 Composewell Technologies and Contributors
(c) Roman Leshchinskiy 2008-2010
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Stream.StreamD.Generate

Description

 
Synopsis

Primitives

nil :: Applicative m => Stream m a Source #

A stream that terminates without producing any output or side effect.

>>> Stream.fold Fold.toList Stream.nil
[]

nilM :: Applicative m => m b -> Stream m a Source #

A stream that terminates without producing any output, but produces a side effect.

>>> Stream.fold Fold.toList (Stream.nilM (print "nil"))
"nil"
[]

Pre-release

cons :: Applicative m => a -> Stream m a -> Stream m a Source #

Fuse a pure value at the head of an existing stream::

>>> s = 1 `Stream.cons` Stream.fromList [2,3]
>>> Stream.fold Fold.toList s
[1,2,3]

This function should not be used to dynamically construct a stream. If a stream is constructed by successive use of this function it would take O(n^2) time to consume the stream.

This function should only be used to statically fuse an element with a stream. Do not use this recursively or where it cannot be inlined.

See Streamly.Data.StreamK for a cons that can be used to construct a stream recursively.

Definition:

>>> cons x xs = return x `Stream.consM` xs

consM :: Applicative m => m a -> Stream m a -> Stream m a Source #

Like cons but fuses an effect instead of a pure value.

From Unfold

unfold :: Applicative m => Unfold m a b -> a -> Stream m b Source #

Convert an Unfold into a stream by supplying it an input seed.

>>> s = Stream.unfold Unfold.replicateM (3, putStrLn "hello")
>>> Stream.fold Fold.drain s
hello
hello
hello

Unfolding

unfoldr :: Monad m => (s -> Maybe (a, s)) -> s -> Stream m a Source #

>>> :{
unfoldr step s =
    case step s of
        Nothing -> Stream.nil
        Just (a, b) -> a `Stream.cons` unfoldr step b
:}

Build a stream by unfolding a pure step function step starting from a seed s. 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 > 2
        then Nothing
        else Just (b, b + 1)
in Stream.fold Fold.toList $ Stream.unfoldr f 0
:}
[0,1,2]

unfoldrM :: Monad m => (s -> m (Maybe (a, s))) -> s -> Stream 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 > 2
        then return Nothing
        else return (Just (b, b + 1))
in Stream.fold Fold.toList $ Stream.unfoldrM f 0
:}
[0,1,2]

From Values

fromPure :: Applicative m => a -> Stream m a Source #

Create a singleton stream from a pure value.

>>> fromPure a = a `Stream.cons` Stream.nil
>>> fromPure = pure
>>> fromPure = Stream.fromEffect . pure

fromEffect :: Applicative m => m a -> Stream m a Source #

Create a singleton stream from a monadic action.

>>> fromEffect m = m `Stream.consM` Stream.nil
>>> fromEffect = Stream.sequence . Stream.fromPure
>>> Stream.fold Fold.drain $ Stream.fromEffect (putStrLn "hello")
hello

repeat :: Monad m => a -> Stream m a Source #

Generate an infinite stream by repeating a pure value.

>>> repeat x = Stream.repeatM (pure x)

repeatM :: Monad m => m a -> Stream m a Source #

>>> repeatM = Stream.sequence . Stream.repeat
>>> repeatM = fix . Stream.consM
>>> repeatM = cycle1 . Stream.fromEffect

Generate a stream by repeatedly executing a monadic action forever.

>>> :{
repeatAction =
       Stream.repeatM (threadDelay 1000000 >> print 1)
     & Stream.take 10
     & Stream.fold Fold.drain
:}

replicate :: Monad m => Int -> a -> Stream m a Source #

>>> replicate n = Stream.take n . Stream.repeat
>>> replicate n x = Stream.replicateM n (pure x)

Generate a stream of length n by repeating a value n times.

replicateM :: Monad m => Int -> m a -> Stream m a Source #

>>> replicateM n = Stream.sequence . Stream.replicate n

Generate a stream by performing a monadic action n times.

Enumeration

Enumerating Num Types

enumerateFromStepNum :: (Monad m, Num a) => a -> a -> Stream m a Source #

For floating point numbers if the increment is less than the precision then it just gets lost. Therefore we cannot always increment it correctly by just repeated addition. 9007199254740992 + 1 + 1 :: Double => 9.007199254740992e15 9007199254740992 + 2 :: Double => 9.007199254740994e15

Instead we accumulate the increment counter and compute the increment every time before adding it to the starting number.

This works for Integrals as well as floating point numbers, but enumerateFromStepIntegral is faster for integrals.

enumerateFromNum :: (Monad m, Num a) => a -> Stream m a Source #

enumerateFromThenNum :: (Monad m, Num a) => a -> a -> Stream m a Source #

Enumerating Bounded Enum Types

enumerate :: (Monad m, Bounded a, Enumerable a) => Stream m a Source #

enumerate = enumerateFrom minBound

Enumerate a Bounded type from its minBound to maxBound

enumerateTo :: (Monad m, Bounded a, Enumerable a) => a -> Stream m a Source #

>>> enumerateTo = Stream.enumerateFromTo minBound

Enumerate a Bounded type from its minBound to specified value.

enumerateFromBounded :: (Monad m, Enumerable a, Bounded a) => a -> Stream m a Source #

>>> enumerateFromBounded from = Stream.enumerateFromTo from maxBound

enumerateFrom for Bounded Enum types.

Enumerating Enum Types not larger than Int

enumerateFromToSmall :: (Monad m, Enum a) => a -> a -> Stream m a Source #

enumerateFromTo for Enum types not larger than Int.

enumerateFromThenToSmall :: (Monad m, Enum a) => a -> a -> a -> Stream m a Source #

enumerateFromThenTo for Enum types not larger than Int.

enumerateFromThenSmallBounded :: (Monad m, Enumerable a, Bounded a) => a -> a -> Stream m a Source #

enumerateFromThen for Enum types not larger than Int.

Note: We convert the Enum to Int and enumerate the Int. If a type is bounded but does not have a Bounded instance then we can go on enumerating it beyond the legal values of the type, resulting in the failure of toEnum when converting back to Enum. Therefore we require a Bounded instance for this function to be safely used.

Enumerating Bounded Integral Types

enumerateFromIntegral :: (Monad m, Integral a, Bounded a) => a -> Stream m a Source #

Enumerate an Integral type. enumerateFromIntegral from generates a stream whose first element is from and the successive elements are in increments of 1. The stream is bounded by the size of the Integral type.

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromIntegral (0 :: Int)
[0,1,2,3]

enumerateFromThenIntegral :: (Monad m, Integral a, Bounded a) => a -> a -> Stream m a Source #

Enumerate an Integral type in steps. enumerateFromThenIntegral from then generates a stream whose first element is from, the second element is then and the successive elements are in increments of then - from. The stream is bounded by the size of the Integral type.

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromThenIntegral (0 :: Int) 2
[0,2,4,6]
>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromThenIntegral (0 :: Int) (-2)
[0,-2,-4,-6]

Enumerating Integral Types

enumerateFromToIntegral :: (Monad m, Integral a) => a -> a -> Stream m a Source #

Enumerate an Integral type up to a given limit. enumerateFromToIntegral from to generates a finite stream whose first element is from and successive elements are in increments of 1 up to to.

>>> Stream.fold Fold.toList $ Stream.enumerateFromToIntegral 0 4
[0,1,2,3,4]

enumerateFromThenToIntegral :: (Monad m, Integral a) => a -> a -> a -> Stream m a Source #

Enumerate an Integral type in steps up to a given limit. enumerateFromThenToIntegral from then to generates a finite stream whose first element is from, the second element is then and the successive elements are in increments of then - from up to to.

>>> Stream.fold Fold.toList $ Stream.enumerateFromThenToIntegral 0 2 6
[0,2,4,6]
>>> Stream.fold Fold.toList $ Stream.enumerateFromThenToIntegral 0 (-2) (-6)
[0,-2,-4,-6]

Enumerating unbounded Integral Types

enumerateFromStepIntegral :: (Integral a, Monad m) => a -> a -> Stream m a Source #

enumerateFromStepIntegral from step generates an infinite stream whose first element is from and the successive elements are in increments of step.

CAUTION: This function is not safe for finite integral types. It does not check for overflow, underflow or bounds.

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromStepIntegral 0 2
[0,2,4,6]
>>> Stream.fold Fold.toList $ Stream.take 3 $ Stream.enumerateFromStepIntegral 0 (-2)
[0,-2,-4]

Enumerating Fractional Types

enumerateFromFractional :: (Monad m, Fractional a) => a -> Stream m a Source #

Numerically stable enumeration from a Fractional number in steps of size 1. enumerateFromFractional from generates a stream whose first element is from and the successive elements are in increments of 1. No overflow or underflow checks are performed.

This is the equivalent to enumFrom for Fractional types. For example:

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromFractional 1.1
[1.1,2.1,3.1,4.1]

enumerateFromToFractional :: (Monad m, Fractional a, Ord a) => a -> a -> Stream m a Source #

Numerically stable enumeration from a Fractional number to a given limit. enumerateFromToFractional from to generates a finite stream whose first element is from and successive elements are in increments of 1 up to to.

This is the equivalent of enumFromTo for Fractional types. For example:

>>> Stream.fold Fold.toList $ Stream.enumerateFromToFractional 1.1 4
[1.1,2.1,3.1,4.1]
>>> Stream.fold Fold.toList $ Stream.enumerateFromToFractional 1.1 4.6
[1.1,2.1,3.1,4.1,5.1]

Notice that the last element is equal to the specified to value after rounding to the nearest integer.

enumerateFromThenFractional :: (Monad m, Fractional a) => a -> a -> Stream m a Source #

Numerically stable enumeration from a Fractional number in steps. enumerateFromThenFractional from then generates a stream whose first element is from, the second element is then and the successive elements are in increments of then - from. No overflow or underflow checks are performed.

This is the equivalent of enumFromThen for Fractional types. For example:

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromThenFractional 1.1 2.1
[1.1,2.1,3.1,4.1]
>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromThenFractional 1.1 (-2.1)
[1.1,-2.1,-5.300000000000001,-8.500000000000002]

enumerateFromThenToFractional :: (Monad m, Fractional a, Ord a) => a -> a -> a -> Stream m a Source #

Numerically stable enumeration from a Fractional number in steps up to a given limit. enumerateFromThenToFractional from then to generates a finite stream whose first element is from, the second element is then and the successive elements are in increments of then - from up to to.

This is the equivalent of enumFromThenTo for Fractional types. For example:

>>> Stream.fold Fold.toList $ Stream.enumerateFromThenToFractional 0.1 2 6
[0.1,2.0,3.9,5.799999999999999]
>>> Stream.fold Fold.toList $ Stream.enumerateFromThenToFractional 0.1 (-2) (-6)
[0.1,-2.0,-4.1000000000000005,-6.200000000000001]

Enumerable Type Class

class Enum a => Enumerable a where Source #

Types that can be enumerated as a stream. The operations in this type class are equivalent to those in the Enum type class, except that these generate a stream instead of a list. Use the functions in Streamly.Internal.Data.Stream.Enumeration module to define new instances.

Methods

enumerateFrom :: Monad m => a -> Stream m a Source #

enumerateFrom from generates a stream starting with the element from, enumerating up to maxBound when the type is Bounded or generating an infinite stream when the type is not Bounded.

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFrom (0 :: Int)
[0,1,2,3]

For Fractional types, enumeration is numerically stable. However, no overflow or underflow checks are performed.

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFrom 1.1
[1.1,2.1,3.1,4.1]

enumerateFromTo :: Monad m => a -> a -> Stream m a Source #

Generate a finite stream starting with the element from, enumerating the type up to the value to. If to is smaller than from then an empty stream is returned.

>>> Stream.fold Fold.toList $ Stream.enumerateFromTo 0 4
[0,1,2,3,4]

For Fractional types, the last element is equal to the specified to value after rounding to the nearest integral value.

>>> Stream.fold Fold.toList $ Stream.enumerateFromTo 1.1 4
[1.1,2.1,3.1,4.1]
>>> Stream.fold Fold.toList $ Stream.enumerateFromTo 1.1 4.6
[1.1,2.1,3.1,4.1,5.1]

enumerateFromThen :: Monad m => a -> a -> Stream m a Source #

enumerateFromThen from then generates a stream whose first element is from, the second element is then and the successive elements are in increments of then - from. Enumeration can occur downwards or upwards depending on whether then comes before or after from. For Bounded types the stream ends when maxBound is reached, for unbounded types it keeps enumerating infinitely.

>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 2
[0,2,4,6]
>>> Stream.fold Fold.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 (-2)
[0,-2,-4,-6]

enumerateFromThenTo :: Monad m => a -> a -> a -> Stream m a Source #

enumerateFromThenTo from then to generates a finite stream whose first element is from, the second element is then and the successive elements are in increments of then - from up to to. Enumeration can occur downwards or upwards depending on whether then comes before or after from.

>>> Stream.fold Fold.toList $ Stream.enumerateFromThenTo 0 2 6
[0,2,4,6]
>>> Stream.fold Fold.toList $ Stream.enumerateFromThenTo 0 (-2) (-6)
[0,-2,-4,-6]

Instances

Instances details
Enumerable Int16 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Int16 -> Stream m Int16 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Int16 -> Int16 -> Stream m Int16 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Int16 -> Int16 -> Stream m Int16 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Int16 -> Int16 -> Int16 -> Stream m Int16 Source #

Enumerable Int32 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Int32 -> Stream m Int32 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Int32 -> Int32 -> Stream m Int32 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Int32 -> Int32 -> Stream m Int32 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Int32 -> Int32 -> Int32 -> Stream m Int32 Source #

Enumerable Int64 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Int64 -> Stream m Int64 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Int64 -> Int64 -> Stream m Int64 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Int64 -> Int64 -> Stream m Int64 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Int64 -> Int64 -> Int64 -> Stream m Int64 Source #

Enumerable Int8 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Int8 -> Stream m Int8 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Int8 -> Int8 -> Stream m Int8 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Int8 -> Int8 -> Stream m Int8 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Int8 -> Int8 -> Int8 -> Stream m Int8 Source #

Enumerable Word16 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Word16 -> Stream m Word16 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Word16 -> Word16 -> Stream m Word16 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Word16 -> Word16 -> Stream m Word16 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Word16 -> Word16 -> Word16 -> Stream m Word16 Source #

Enumerable Word32 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Word32 -> Stream m Word32 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Word32 -> Word32 -> Stream m Word32 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Word32 -> Word32 -> Stream m Word32 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Word32 -> Word32 -> Word32 -> Stream m Word32 Source #

Enumerable Word64 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Word64 -> Stream m Word64 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Word64 -> Word64 -> Stream m Word64 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Word64 -> Word64 -> Stream m Word64 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Word64 -> Word64 -> Word64 -> Stream m Word64 Source #

Enumerable Word8 Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Word8 -> Stream m Word8 Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Word8 -> Word8 -> Stream m Word8 Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Word8 -> Word8 -> Stream m Word8 Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Word8 -> Word8 -> Word8 -> Stream m Word8 Source #

Enumerable Ordering Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Ordering -> Stream m Ordering Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Ordering -> Ordering -> Stream m Ordering Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Ordering -> Ordering -> Stream m Ordering Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Ordering -> Ordering -> Ordering -> Stream m Ordering Source #

Enumerable Integer Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Integer -> Stream m Integer Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Integer -> Integer -> Stream m Integer Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Integer -> Integer -> Stream m Integer Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Integer -> Integer -> Integer -> Stream m Integer Source #

Enumerable Natural Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Natural -> Stream m Natural Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Natural -> Natural -> Stream m Natural Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Natural -> Natural -> Stream m Natural Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Natural -> Natural -> Natural -> Stream m Natural Source #

Enumerable () Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => () -> Stream m () Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => () -> () -> Stream m () Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => () -> () -> Stream m () Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => () -> () -> () -> Stream m () Source #

Enumerable Bool Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Bool -> Stream m Bool Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Bool -> Bool -> Stream m Bool Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Bool -> Bool -> Stream m Bool Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Bool -> Bool -> Bool -> Stream m Bool Source #

Enumerable Char Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Char -> Stream m Char Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Char -> Char -> Stream m Char Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Char -> Char -> Stream m Char Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Char -> Char -> Char -> Stream m Char Source #

Enumerable Double Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Double -> Stream m Double Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Double -> Double -> Stream m Double Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Double -> Double -> Stream m Double Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Double -> Double -> Double -> Stream m Double Source #

Enumerable Float Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Float -> Stream m Float Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Float -> Float -> Stream m Float Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Float -> Float -> Stream m Float Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Float -> Float -> Float -> Stream m Float Source #

Enumerable Int Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Int -> Stream m Int Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Int -> Int -> Stream m Int Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Int -> Int -> Stream m Int Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Int -> Int -> Int -> Stream m Int Source #

Enumerable Word Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Word -> Stream m Word Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Word -> Word -> Stream m Word Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Word -> Word -> Stream m Word Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Word -> Word -> Word -> Stream m Word Source #

Enumerable a => Enumerable (Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Identity a -> Stream m (Identity a) Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Identity a -> Identity a -> Stream m (Identity a) Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Identity a -> Identity a -> Stream m (Identity a) Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Identity a -> Identity a -> Identity a -> Stream m (Identity a) Source #

Integral a => Enumerable (Ratio a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Ratio a -> Stream m (Ratio a) Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Ratio a -> Ratio a -> Stream m (Ratio a) Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Ratio a -> Ratio a -> Stream m (Ratio a) Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Ratio a -> Ratio a -> Ratio a -> Stream m (Ratio a) Source #

HasResolution a => Enumerable (Fixed a) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Generate

Methods

enumerateFrom :: forall (m :: Type -> Type). Monad m => Fixed a -> Stream m (Fixed a) Source #

enumerateFromTo :: forall (m :: Type -> Type). Monad m => Fixed a -> Fixed a -> Stream m (Fixed a) Source #

enumerateFromThen :: forall (m :: Type -> Type). Monad m => Fixed a -> Fixed a -> Stream m (Fixed a) Source #

enumerateFromThenTo :: forall (m :: Type -> Type). Monad m => Fixed a -> Fixed a -> Fixed a -> Stream m (Fixed a) Source #

Time Enumeration

times :: MonadIO m => Stream m (AbsTime, RelTime64) Source #

times returns a stream of time value tuples with clock of 10 ms granularity. The first component of the tuple is an absolute time reference (epoch) denoting the start of the stream and the second component is a time relative to the reference.

>>> f = Fold.drainMapM (\x -> print x >> threadDelay 1000000)
>>> Stream.fold f $ Stream.take 3 $ Stream.times
(AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
(AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
(AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))

Note: This API is not safe on 32-bit machines.

Pre-release

timesWith :: MonadIO m => Double -> Stream m (AbsTime, RelTime64) Source #

timesWith g returns a stream of time value tuples. The first component of the tuple is an absolute time reference (epoch) denoting the start of the stream and the second component is a time relative to the reference.

The argument g specifies the granularity of the relative time in seconds. A lower granularity clock gives higher precision but is more expensive in terms of CPU usage. Any granularity lower than 1 ms is treated as 1 ms.

>>> import Control.Concurrent (threadDelay)
>>> f = Fold.drainMapM (\x -> print x >> threadDelay 1000000)
>>> Stream.fold f $ Stream.take 3 $ Stream.timesWith 0.01
(AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
(AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
(AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))

Note: This API is not safe on 32-bit machines.

Pre-release

absTimes :: MonadIO m => Stream m AbsTime Source #

absTimes returns a stream of absolute timestamps using a clock of 10 ms granularity.

>>> f = Fold.drainMapM print
>>> Stream.fold f $ Stream.delayPre 1 $ Stream.take 3 $ Stream.absTimes
AbsTime (TimeSpec {sec = ..., nsec = ...})
AbsTime (TimeSpec {sec = ..., nsec = ...})
AbsTime (TimeSpec {sec = ..., nsec = ...})

Note: This API is not safe on 32-bit machines.

Pre-release

absTimesWith :: MonadIO m => Double -> Stream m AbsTime Source #

absTimesWith g returns a stream of absolute timestamps using a clock of granularity g specified in seconds. A low granularity clock is more expensive in terms of CPU usage. Any granularity lower than 1 ms is treated as 1 ms.

>>> f = Fold.drainMapM print
>>> Stream.fold f $ Stream.delayPre 1 $ Stream.take 3 $ Stream.absTimesWith 0.01
AbsTime (TimeSpec {sec = ..., nsec = ...})
AbsTime (TimeSpec {sec = ..., nsec = ...})
AbsTime (TimeSpec {sec = ..., nsec = ...})

Note: This API is not safe on 32-bit machines.

Pre-release

relTimes :: MonadIO m => Stream m RelTime64 Source #

relTimes returns a stream of relative time values starting from 0, using a clock of granularity 10 ms.

>>> f = Fold.drainMapM print
>>> Stream.fold f $ Stream.delayPre 1 $ Stream.take 3 $ Stream.relTimes
RelTime64 (NanoSecond64 ...)
RelTime64 (NanoSecond64 ...)
RelTime64 (NanoSecond64 ...)

Note: This API is not safe on 32-bit machines.

Pre-release

relTimesWith :: MonadIO m => Double -> Stream m RelTime64 Source #

relTimesWith g returns a stream of relative time values starting from 0, using a clock of granularity g specified in seconds. A low granularity clock is more expensive in terms of CPU usage. Any granularity lower than 1 ms is treated as 1 ms.

>>> f = Fold.drainMapM print
>>> Stream.fold f $ Stream.delayPre 1 $ Stream.take 3 $ Stream.relTimesWith 0.01
RelTime64 (NanoSecond64 ...)
RelTime64 (NanoSecond64 ...)
RelTime64 (NanoSecond64 ...)

Note: This API is not safe on 32-bit machines.

Pre-release

durations :: Double -> t m RelTime64 Source #

durations g returns a stream of relative time values measuring the time elapsed since the immediate predecessor element of the stream was generated. The first element of the stream is always 0. durations uses a clock of granularity g specified in seconds. A low granularity clock is more expensive in terms of CPU usage. The minimum granularity is 1 millisecond. Durations lower than 1 ms will be 0.

Note: This API is not safe on 32-bit machines.

Unimplemented

timeout :: AbsTime -> t m () Source #

Generate a singleton event at or after the specified absolute time. Note that this is different from a threadDelay, a threadDelay starts from the time when the action is evaluated, whereas if we use AbsTime based timeout it will immediately expire if the action is evaluated too late.

Unimplemented

From Generators

Generate a monadic stream from a seed.

fromIndices :: Monad m => (Int -> a) -> Stream m a Source #

fromIndicesM :: Monad m => (Int -> m a) -> Stream m a Source #

generate :: Monad m => Int -> (Int -> a) -> Stream m a Source #

generateM :: Monad m => Int -> (Int -> m a) -> Stream m a Source #

Iteration

iterate :: Monad m => (a -> a) -> a -> Stream m a Source #

>>> iterate f x = x `Stream.cons` iterate f x

Generate an infinite stream with x as the first element and each successive element derived by applying the function f on the previous element.

>>> Stream.fold Fold.toList $ Stream.take 5 $ Stream.iterate (+1) 1
[1,2,3,4,5]

iterateM :: Monad m => (a -> m a) -> m a -> Stream m a Source #

>>> iterateM f m = m >>= \a -> return a `Stream.consM` iterateM f (f a)

Generate an infinite stream with the first element generated by the action m and each successive element derived by applying the monadic function f on the previous element.

>>> :{
Stream.iterateM (\x -> print x >> return (x + 1)) (return 0)
    & Stream.take 3
    & Stream.fold Fold.toList
:}
0
1
[0,1,2]

From Containers

Transform an input structure into a stream.

fromList :: Applicative m => [a] -> Stream m a Source #

Construct a stream from a list of pure values.

fromListM :: Monad m => [m a] -> Stream m a Source #

Convert a list of monadic actions to a Stream

fromFoldable :: (Monad m, Foldable f) => f a -> Stream m a Source #

>>> fromFoldable = Prelude.foldr Stream.cons Stream.nil

Construct a stream from a Foldable containing pure values:

/WARNING: O(n^2), suitable only for a small number of elements in the stream/

fromFoldableM :: (Monad m, Foldable f) => f (m a) -> Stream m a Source #

>>> fromFoldableM = Prelude.foldr Stream.consM Stream.nil

Construct a stream from a Foldable containing pure values:

/WARNING: O(n^2), suitable only for a small number of elements in the stream/

From Pointers

fromPtr :: forall m a. (MonadIO m, Storable a) => Ptr a -> Stream m a Source #

Keep reading Storable elements from Ptr onwards.

Unsafe: The caller is responsible for safe addressing.

Pre-release

fromPtrN :: (MonadIO m, Storable a) => Int -> Ptr a -> Stream m a Source #

Take n Storable elements starting from Ptr onwards.

>>> fromPtrN n = Stream.take n . Stream.fromPtr

Unsafe: The caller is responsible for safe addressing.

Pre-release

fromByteStr# :: MonadIO m => Addr# -> Stream m Word8 Source #

Read bytes from an Addr# until a 0 byte is encountered, the 0 byte is not included in the stream.

>>> :set -XMagicHash
>>> fromByteStr# addr = Stream.takeWhile (/= 0) $ Stream.fromPtr $ Ptr addr

Unsafe: The caller is responsible for safe addressing.

Note that this is completely safe when reading from Haskell string literals because they are guaranteed to be NULL terminated:

>>> Stream.fold Fold.toList $ Stream.fromByteStr# "\1\2\3\0"#
[1,2,3]

Conversions

fromStreamK :: Applicative m => StreamK m a -> Stream m a Source #

Convert a CPS encoded StreamK to direct style step encoded StreamD

toStreamK :: Monad m => Stream m a -> StreamK m a Source #

Convert a direct style step encoded StreamD to a CPS encoded StreamK