streamly-0.8.1.1: Dataflow programming and declarative concurrency
Copyright(c) 2019 2021 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Internal.Data.Unfold.Enumeration

Description

The functions defined in this module should be rarely needed for direct use, try to use the operations from the Enumerable type class instances instead.

This module provides an Enumerable type class to enumerate Enum types into a stream. The operations in this type class correspond to similar operations in the Enum type class, the only difference is that they produce a stream instead of a list. These operations cannot be defined generically based on the Enum type class. We provide instances for commonly used types. If instances for other types are needed convenience functions defined in this module can be used to define them. Alternatively, these functions can be used directly.

Synopsis

Documentation

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.Unfold.Enumeration module to define new instances.

Pre-release

Methods

enumerateFrom :: Monad m => Unfold m a a Source #

Unfolds from generating 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.

>>> import qualified Streamly.Prelude as Stream
>>> import qualified Streamly.Internal.Data.Unfold as Unfold
>>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFrom (0 :: Int)
[0,1,2,3]

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

>>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFrom 1.1
[1.1,2.1,3.1,4.1]

Pre-release

enumerateFromTo :: Monad m => Unfold m (a, a) a Source #

Unfolds (from, to) generating 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.

>>> import qualified Streamly.Prelude as Stream
>>> import qualified Streamly.Internal.Data.Unfold as Unfold
>>> Stream.toList $ Stream.unfold Unfold.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.toList $ Stream.unfold Unfold.enumerateFromTo (1.1, 4)
[1.1,2.1,3.1,4.1]

>>> Stream.toList $ Stream.unfold Unfold.enumerateFromTo (1.1, 4.6)
[1.1,2.1,3.1,4.1,5.1]

Pre-release

enumerateFromThen :: Monad m => Unfold m (a, a) a Source #

Unfolds (from, then) generating a stream whose first element is from and the successive elements are in increments of then. 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.

>>> import qualified Streamly.Prelude as Stream
>>> import qualified Streamly.Internal.Data.Unfold as Unfold
>>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFromThen (0, 2)
[0,2,4,6]

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

Pre-release

enumerateFromThenTo :: Monad m => Unfold m (a, a, a) a Source #

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

>>> import qualified Streamly.Prelude as Stream
>>> import qualified Streamly.Internal.Data.Unfold as Unfold
>>> Stream.toList $ Stream.unfold Unfold.enumerateFromThenTo (0, 2, 6)
[0,2,4,6]

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

Pre-release

Instances

Instances details
Enumerable Bool Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Char Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Double Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Float Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Int Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Int8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Int16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Int32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Int64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Integer Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Enumerable Natural Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Enumerable Ordering Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Enumerable Word Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Word8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Word16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Word32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable Word64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerable () Source # 
Instance details

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

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

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

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

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

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

Defined in Streamly.Internal.Data.Unfold.Enumeration

Methods

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

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

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

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

Enumerating Num Types

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

Unfolds (from, stride) generating an infinite stream starting from from and incrementing every time by stride. For Bounded types, after the value overflows it keeps enumerating in a cycle:

>>> Stream.toList $ Stream.take 10 $ Stream.unfold Unfold.enumerateFromStepNum (255::Word8,1)
[255,0,1,2,3,4,5,6,7,8]

The implementation is numerically stable for floating point values.

Note enumerateFromStepIntegral is faster for integrals.

Internal

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

Same as enumerateFromStepNum using a stride of 1:

>>> enumerateFromNum = lmap (from -> (from, 1)) Unfold.enumerateFromStepNum
>>> Stream.toList $ Stream.take 6 $ Stream.unfold enumerateFromNum (0.9)
[0.9,1.9,2.9,3.9,4.9,5.9]

Also, same as enumerateFromThenNum using a stride of 1 but see the note in enumerateFromThenNum about the loss of precision:

>>> enumerateFromNum = lmap (from -> (from, from + 1)) Unfold.enumerateFromThenNum
>>> Stream.toList $ Stream.take 6 $ Stream.unfold enumerateFromNum (0.9)
[0.9,1.9,2.9,3.8999999999999995,4.8999999999999995,5.8999999999999995]

Internal

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

Same as 'enumerateFromStepNum (from, next)' using a stride of next - from:

>>> enumerateFromThenNum = lmap ((from, next) -> (from, next - from)) Unfold.enumerateFromStepNum

Example: @ >>> Stream.toList $ Stream.take 10 $ Stream.unfold enumerateFromThenNum (255::Word8,0) [255,0,1,2,3,4,5,6,7,8]

The implementation is numerically stable for floating point values.

Note that enumerateFromThenIntegral is faster for integrals.

Note that in the strange world of floating point numbers, using

enumerateFromThenNum (from, from + 1) is almost exactly the same as enumerateFromStepNum (from, 1) but not precisely the same. Because (from + 1) - from is not exactly 1, it may lose some precision, the loss may also be aggregated in each step, if you want that precision then use enumerateFromStepNum instead.

Internal

Enumerating unbounded Integral Types

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

Can be used to enumerate unbounded integrals. This does not check for overflow or underflow for bounded integrals.

Internal

Enumerating Bounded Integral Types

Enumerating small Integral Types

Small types are always bounded.

enumerateFromSmallBounded :: (Monad m, Enum a, Bounded a) => Unfold m a a Source #

Enumerate from given starting Enum value from with stride of 1 till maxBound

Internal

enumerateFromThenSmallBounded :: forall m a. (Monad m, Enum a, Bounded a) => Unfold m (a, a) a Source #

Enumerate from given starting Enum value from and next Enum value next with stride of (fromEnum next - fromEnum from) till maxBound.

Internal

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

Enumerate from given starting Enum value from and to Enum value to with stride of 1 till to value.

Internal

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

Enumerate from given starting Enum value from and then Enum value next and to Enum value to with stride of (fromEnum next - fromEnum from) till to value.

Internal

Enumerating Fractional Types

Enumeration of Num specialized to Fractional types.

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

Same as enumerateFromStepNum with a step of 1 and enumerating up to the specified upper limit rounded to the nearest integral value:

>>> Stream.toList $ Stream.unfold Unfold.enumerateFromToFractional (0.1, 6.3)
[0.1,1.1,2.1,3.1,4.1,5.1,6.1]

Internal