Copyright | (c) 2018 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
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
perations 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
- class Enum a => Enumerable a where
- enumerateFrom :: (IsStream t, Monad m) => a -> t m a
- enumerateFromTo :: (IsStream t, Monad m) => a -> a -> t m a
- enumerateFromThen :: (IsStream t, Monad m) => a -> a -> t m a
- enumerateFromThenTo :: (IsStream t, Monad m) => a -> a -> a -> t m a
- enumerate :: (IsStream t, Monad m, Bounded a, Enumerable a) => t m a
- enumerateTo :: (IsStream t, Monad m, Bounded a, Enumerable a) => a -> t m a
- enumerateFromBounded :: (IsStream t, Monad m, Enumerable a, Bounded a) => a -> t m a
- enumerateFromToSmall :: (IsStream t, Monad m, Enum a) => a -> a -> t m a
- enumerateFromThenToSmall :: (IsStream t, Monad m, Enum a) => a -> a -> a -> t m a
- enumerateFromThenSmallBounded :: (IsStream t, Monad m, Enumerable a, Bounded a) => a -> a -> t m a
- enumerateFromIntegral :: (IsStream t, Monad m, Integral a, Bounded a) => a -> t m a
- enumerateFromThenIntegral :: (IsStream t, Monad m, Integral a, Bounded a) => a -> a -> t m a
- enumerateFromToIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> t m a
- enumerateFromThenToIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> a -> t m a
- enumerateFromStepIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> t m a
- enumerateFromFractional :: (IsStream t, Monad m, Fractional a) => a -> t m a
- enumerateFromToFractional :: (IsStream t, Monad m, Fractional a, Ord a) => a -> a -> t m a
- enumerateFromThenFractional :: (IsStream t, Monad m, Fractional a) => a -> a -> t m a
- enumerateFromThenToFractional :: (IsStream t, Monad m, Fractional a, Ord a) => a -> a -> a -> t m a
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.Stream.Enumeration module to define new instances.
Since: 0.6.0
enumerateFrom :: (IsStream t, Monad m) => a -> t 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.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.toList $ Stream.take 4 $ Stream.enumerateFrom 1.1 [1.1,2.1,3.1,4.1]
Since: 0.6.0
enumerateFromTo :: (IsStream t, Monad m) => a -> a -> t 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.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.toList $ Stream.enumerateFromTo 1.1 4 [1.1,2.1,3.1,4.1] >>> Stream.toList $ Stream.enumerateFromTo 1.1 4.6 [1.1,2.1,3.1,4.1,5.1]
Since: 0.6.0
enumerateFromThen :: (IsStream t, Monad m) => a -> a -> t 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.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 2 [0,2,4,6] >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 (-2) [0,-2,-4,-6]
Since: 0.6.0
enumerateFromThenTo :: (IsStream t, Monad m) => a -> a -> a -> t 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.toList $ Stream.enumerateFromThenTo 0 2 6 [0,2,4,6] >>> Stream.toList $ Stream.enumerateFromThenTo 0 (-2) (-6) [0,-2,-4,-6]
Since: 0.6.0
Instances
Enumerating Bounded
Enum
Types
enumerateTo :: (IsStream t, Monad m, Bounded a, Enumerable a) => a -> t m a Source #
enumerateFromBounded :: (IsStream t, Monad m, Enumerable a, Bounded a) => a -> t m a Source #
enumerateFromBounded = enumerateFromTo from maxBound
enumerateFrom
for Bounded
Enum
types.
Since: 0.6.0
Enumerating Enum
Types not larger than Int
enumerateFromToSmall :: (IsStream t, Monad m, Enum a) => a -> a -> t m a Source #
enumerateFromTo
for Enum
types not larger than Int
.
Since: 0.6.0
enumerateFromThenToSmall :: (IsStream t, Monad m, Enum a) => a -> a -> a -> t m a Source #
enumerateFromThenTo
for Enum
types not larger than Int
.
Since: 0.6.0
enumerateFromThenSmallBounded :: (IsStream t, Monad m, Enumerable a, Bounded a) => a -> a -> t 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.
Since: 0.6.0
Enumerating Bounded
Integral
Types
enumerateFromIntegral :: (IsStream t, Monad m, Integral a, Bounded a) => a -> t 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.toList $ Stream.take 4 $ Stream.enumerateFromIntegral (0 :: Int) [0,1,2,3]
Since: 0.6.0
enumerateFromThenIntegral :: (IsStream t, Monad m, Integral a, Bounded a) => a -> a -> t 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.toList $ Stream.take 4 $ Stream.enumerateFromThenIntegral (0 :: Int) 2 [0,2,4,6] >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThenIntegral (0 :: Int) (-2) [0,-2,-4,-6]
Since: 0.6.0
Enumerating Integral
Types
enumerateFromToIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> t 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.toList $ Stream.enumerateFromToIntegral 0 4 [0,1,2,3,4]
Since: 0.6.0
enumerateFromThenToIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> a -> t 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.toList $ Stream.enumerateFromThenToIntegral 0 2 6 [0,2,4,6] >>> Stream.toList $ Stream.enumerateFromThenToIntegral 0 (-2) (-6) [0,-2,-4,-6]
Since: 0.6.0
Enumerating unbounded Integral
Types
enumerateFromStepIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> t 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.toList $ Stream.take 4 $ Stream.enumerateFromStepIntegral 0 2 [0,2,4,6] >>> Stream.toList $ Stream.take 3 $ Stream.enumerateFromStepIntegral 0 (-2) [0,-2,-4]
Since: 0.6.0
Enumerating Fractional
Types
enumerateFromFractional :: (IsStream t, Monad m, Fractional a) => a -> t 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.toList $ Stream.take 4 $ Stream.enumerateFromFractional 1.1 [1.1,2.1,3.1,4.1]
Since: 0.6.0
enumerateFromToFractional :: (IsStream t, Monad m, Fractional a, Ord a) => a -> a -> t 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.toList $ Stream.enumerateFromToFractional 1.1 4 [1.1,2.1,3.1,4.1] >>> Stream.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.
Since: 0.6.0
enumerateFromThenFractional :: (IsStream t, Monad m, Fractional a) => a -> a -> t 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.toList $ Stream.take 4 $ Stream.enumerateFromThenFractional 1.1 2.1 [1.1,2.1,3.1,4.1] >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThenFractional 1.1 (-2.1) [1.1,-2.1,-5.300000000000001,-8.500000000000002]
Since: 0.6.0
enumerateFromThenToFractional :: (IsStream t, Monad m, Fractional a, Ord a) => a -> a -> a -> t 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.toList $ Stream.enumerateFromThenToFractional 0.1 2 6 [0.1,2.0,3.9,5.799999999999999] >>> Stream.toList $ Stream.enumerateFromThenToFractional 0.1 (-2) (-6) [0.1,-2.0,-4.1000000000000005,-6.200000000000001]
Since: 0.6.0