Copyright | (c) 2022 Bodigrim |
---|---|
License | BSD3 |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Modern lightweight library for infinite lists with fusion:
- API similar to Data.List.
- No non-boot dependencies.
- Top performance, driven by fusion.
- Avoid dangerous instances like
Foldable
. - Use
NonEmpty
where applicable. - Use
Word
for indices. - Be lazy, but not too lazy.
{-# LANGUAGE PostfixOperators #-} import Data.List.Infinite (Infinite(..), (...), (....)) import qualified Data.List.Infinite as Inf
Synopsis
- data Infinite a = a :< (Infinite a)
- head :: Infinite a -> a
- tail :: Infinite a -> Infinite a
- uncons :: Infinite a -> (a, Infinite a)
- toList :: Infinite a -> [a]
- foldr :: (a -> b -> b) -> Infinite a -> b
- map :: (a -> b) -> Infinite a -> Infinite b
- scanl :: (b -> a -> b) -> b -> Infinite a -> Infinite b
- scanl' :: (b -> a -> b) -> b -> Infinite a -> Infinite b
- scanl1 :: (a -> a -> a) -> Infinite a -> Infinite a
- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> Infinite x -> Infinite y
- concat :: Infinite (NonEmpty a) -> Infinite a
- concatMap :: (a -> NonEmpty b) -> Infinite a -> Infinite b
- intersperse :: a -> Infinite a -> Infinite a
- intercalate :: NonEmpty a -> Infinite [a] -> Infinite a
- interleave :: Infinite a -> Infinite a -> Infinite a
- transpose :: Functor f => f (Infinite a) -> Infinite (f a)
- subsequences :: Infinite a -> Infinite [a]
- subsequences1 :: Infinite a -> Infinite (NonEmpty a)
- permutations :: Infinite a -> Infinite (Infinite a)
- (...) :: Enum a => a -> Infinite a
- (....) :: Enum a => (a, a) -> Infinite a
- iterate :: (a -> a) -> a -> Infinite a
- iterate' :: (a -> a) -> a -> Infinite a
- unfoldr :: (b -> (a, b)) -> b -> Infinite a
- tabulate :: (Word -> a) -> Infinite a
- repeat :: a -> Infinite a
- cycle :: NonEmpty a -> Infinite a
- prependList :: [a] -> Infinite a -> Infinite a
- take :: Int -> Infinite a -> [a]
- drop :: Int -> Infinite a -> Infinite a
- splitAt :: Int -> Infinite a -> ([a], Infinite a)
- takeWhile :: (a -> Bool) -> Infinite a -> [a]
- dropWhile :: (a -> Bool) -> Infinite a -> Infinite a
- span :: (a -> Bool) -> Infinite a -> ([a], Infinite a)
- break :: (a -> Bool) -> Infinite a -> ([a], Infinite a)
- group :: Eq a => Infinite a -> Infinite (NonEmpty a)
- inits :: Infinite a -> Infinite [a]
- inits1 :: Infinite a -> Infinite (NonEmpty a)
- tails :: Infinite a -> Infinite (Infinite a)
- isPrefixOf :: Eq a => [a] -> Infinite a -> Bool
- stripPrefix :: Eq a => [a] -> Infinite a -> Maybe (Infinite a)
- filter :: (a -> Bool) -> Infinite a -> Infinite a
- lookup :: Eq a => a -> Infinite (a, b) -> b
- find :: (a -> Bool) -> Infinite a -> a
- mapMaybe :: (a -> Maybe b) -> Infinite a -> Infinite b
- catMaybes :: Infinite (Maybe a) -> Infinite a
- partition :: (a -> Bool) -> Infinite a -> (Infinite a, Infinite a)
- mapEither :: (a -> Either b c) -> Infinite a -> (Infinite b, Infinite c)
- partitionEithers :: Infinite (Either a b) -> (Infinite a, Infinite b)
- (!!) :: Infinite a -> Word -> a
- elemIndex :: Eq a => a -> Infinite a -> Word
- elemIndices :: Eq a => a -> Infinite a -> Infinite Word
- findIndex :: (a -> Bool) -> Infinite a -> Word
- findIndices :: (a -> Bool) -> Infinite a -> Infinite Word
- zip :: Infinite a -> Infinite b -> Infinite (a, b)
- zipWith :: (a -> b -> c) -> Infinite a -> Infinite b -> Infinite c
- zip3 :: Infinite a -> Infinite b -> Infinite c -> Infinite (a, b, c)
- zipWith3 :: (a -> b -> c -> d) -> Infinite a -> Infinite b -> Infinite c -> Infinite d
- zip4 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite (a, b, c, d)
- zipWith4 :: (a -> b -> c -> d -> e) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e
- zip5 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite (a, b, c, d, e)
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f
- zip6 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite (a, b, c, d, e, f)
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g
- zip7 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g -> Infinite (a, b, c, d, e, f, g)
- zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g -> Infinite h
- unzip :: Infinite (a, b) -> (Infinite a, Infinite b)
- unzip3 :: Infinite (a, b, c) -> (Infinite a, Infinite b, Infinite c)
- unzip4 :: Infinite (a, b, c, d) -> (Infinite a, Infinite b, Infinite c, Infinite d)
- unzip5 :: Infinite (a, b, c, d, e) -> (Infinite a, Infinite b, Infinite c, Infinite d, Infinite e)
- unzip6 :: Infinite (a, b, c, d, e, f) -> (Infinite a, Infinite b, Infinite c, Infinite d, Infinite e, Infinite f)
- unzip7 :: Infinite (a, b, c, d, e, f, g) -> (Infinite a, Infinite b, Infinite c, Infinite d, Infinite e, Infinite f, Infinite g)
- lines :: Infinite Char -> Infinite [Char]
- words :: Infinite Char -> Infinite (NonEmpty Char)
- unlines :: Infinite [Char] -> Infinite Char
- unwords :: Infinite (NonEmpty Char) -> Infinite Char
- nub :: Eq a => Infinite a -> Infinite a
- delete :: Eq a => a -> Infinite a -> Infinite a
- (\\) :: Eq a => Infinite a -> [a] -> Infinite a
- union :: Eq a => [a] -> Infinite a -> Infinite a
- intersect :: Eq a => Infinite a -> [a] -> Infinite a
- insert :: Ord a => a -> Infinite a -> Infinite a
- nubBy :: (a -> a -> Bool) -> Infinite a -> Infinite a
- deleteBy :: (a -> b -> Bool) -> a -> Infinite b -> Infinite b
- deleteFirstsBy :: (a -> b -> Bool) -> Infinite b -> [a] -> Infinite b
- unionBy :: (a -> a -> Bool) -> [a] -> Infinite a -> Infinite a
- intersectBy :: (a -> b -> Bool) -> Infinite a -> [b] -> Infinite a
- groupBy :: (a -> a -> Bool) -> Infinite a -> Infinite (NonEmpty a)
- insertBy :: (a -> a -> Ordering) -> a -> Infinite a -> Infinite a
- genericTake :: Integral i => i -> Infinite a -> [a]
- genericDrop :: Integral i => i -> Infinite a -> Infinite a
- genericSplitAt :: Integral i => i -> Infinite a -> ([a], Infinite a)
Construction
Type of infinite lists.
In terms of recursion schemes, Infinite
a
is a fix point of the base functor (a,)
,
foldr
is a catamorphism and unfoldr
is an anamorphism.
Instances
Applicative Infinite Source # | This instance operates pointwise, similar to |
Functor Infinite Source # | Just a pointwise |
Monad Infinite Source # |
|
Elimination
foldr :: (a -> b -> b) -> Infinite a -> b Source #
Right-associative fold of an infinite list, necessarily lazy in the accumulator. Any unconditional attempt to force the accumulator even to the weak head normal form (WHNF) will hang the computation. E. g., the following definition isn't productive:
import Data.List.NonEmpty (NonEmpty(..)) toNonEmpty = foldr (\a (x :| xs) -> a :| x : xs) :: Infinite a -> NonEmpty a
One should use lazy patterns, e. g.,
toNonEmpty = foldr (\a ~(x :| xs) -> a :| x : xs)
This is a catamorphism on infinite lists.
Traversals
map :: (a -> b) -> Infinite a -> Infinite b Source #
Apply a function to every element of an infinite list.
scanl :: (b -> a -> b) -> b -> Infinite a -> Infinite b Source #
Fold an infinite list from the left and return a list of successive reductions, starting from the initial accumulator:
scanl f acc (x1 :< x2 :< ...) = acc :< f acc x1 :< f (f acc x1) x2 :< ...
scanl' :: (b -> a -> b) -> b -> Infinite a -> Infinite b Source #
Same as scanl
, but strict in accumulator.
scanl1 :: (a -> a -> a) -> Infinite a -> Infinite a Source #
Fold an infinite list from the left and return a list of successive reductions, starting from the first element:
scanl1 f (x0 :< x1 :< x2 :< ...) = x0 :< f x0 x1 :< f (f x0 x1) x2 :< ...
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> Infinite x -> Infinite y Source #
Fold an infinite list from the left and return a list of successive reductions, keeping accumulator in a state:
mapAccumL f acc0 (x1 :< x2 :< ...) = let (acc1, y1) = f acc0 x1 in let (acc2, y2) = f acc1 x2 in ... y1 :< y2 :< ...
If you are looking how to traverse with a state, look no further.
Transformations
intersperse :: a -> Infinite a -> Infinite a Source #
Insert an element between adjacent elements of an infinite list.
intercalate :: NonEmpty a -> Infinite [a] -> Infinite a Source #
Insert a non-empty list between adjacent elements of an infinite list, and subsequently flatten it out.
The peculiar type with NonEmpty
is to guarantee that intercalate
is productive and results in an infinite list. If separator is an empty list,
concatenation of infinitely many [a]
could still be a finite list.
transpose :: Functor f => f (Infinite a) -> Infinite (f a) Source #
Transpose rows and columns of an argument.
This is actually distribute
from
Distributive
type class in disguise.
subsequences :: Infinite a -> Infinite [a] Source #
Generate an infinite list of all subsequences of the argument.
subsequences1 :: Infinite a -> Infinite (NonEmpty a) Source #
Generate an infinite list of all non-empty subsequences of the argument.
permutations :: Infinite a -> Infinite (Infinite a) Source #
Generate an infinite list of all permutations of the argument.
Building
(...) :: Enum a => a -> Infinite a infix 0 Source #
Generate an infinite progression, starting from a given element,
similar to [x..]
.
For better user experience consider enabling {-# LANGUAGE PostfixOperators #-}
:
>>>
:set -XPostfixOperators
>>>
Data.List.Infinite.take 10 (0...)
[0,1,2,3,4,5,6,7,8,9]
Beware that for finite types (...)
applies cycle
atop of [x..]
:
>>>
:set -XPostfixOperators
>>>
Data.List.Infinite.take 10 (EQ...)
[EQ,GT,EQ,GT,EQ,GT,EQ,GT,EQ,GT]
Remember that Int
is a finite type as well. One is unlikely to hit this
on a 64-bit architecture, but on a 32-bit machine it's fairly possible to traverse
((0 ::
far enough to encounter Int
) ...)0
again.
(....) :: Enum a => (a, a) -> Infinite a infix 0 Source #
Generate an infinite arithmetic progression, starting from given elements,
similar to [x,y..]
.
For better user experience consider enabling {-# LANGUAGE PostfixOperators #-}
:
>>>
:set -XPostfixOperators
>>>
Data.List.Infinite.take 10 ((1,3)....)
[1,3,5,7,9,11,13,15,17,19]
Beware that for finite types (....)
applies cycle
atop of [x,y..]
:
>>>
:set -XPostfixOperators
>>>
Data.List.Infinite.take 10 ((EQ,GT)....)
[EQ,GT,EQ,GT,EQ,GT,EQ,GT,EQ,GT]
Remember that Int
is a finite type as well: for a sufficiently large
step of progression y - x
one may observe ((x :: Int, y)....)
cycling back
to emit x
fairly soon.
unfoldr :: (b -> (a, b)) -> b -> Infinite a Source #
Build an infinite list from a seed value.
This is an anamorphism on infinite lists.
tabulate :: (Word -> a) -> Infinite a Source #
Generate an infinite list of f
0, f
1, f
2...
tabulate
and (!!)
witness that Infinite
is
Representable
.
cycle :: NonEmpty a -> Infinite a Source #
Repeat a non-empty list ad infinitum.
If you were looking for something like fromList :: [a] -> Infinite a
,
look no further.
It would be less annoying to take [a]
instead of NonEmpty
a
,
but we strive to avoid partial functions.
Sublists
prependList :: [a] -> Infinite a -> Infinite a Source #
Prepend a list to an infinite list.
splitAt :: Int -> Infinite a -> ([a], Infinite a) Source #
Split an infinite list into a prefix of given length and the rest.
takeWhile :: (a -> Bool) -> Infinite a -> [a] Source #
Take the longest prefix satisfying a predicate.
inits1 :: Infinite a -> Infinite (NonEmpty a) Source #
Generate all non-empty prefixes of an infinite list.
isPrefixOf :: Eq a => [a] -> Infinite a -> Bool Source #
Check whether a list is a prefix of an infinite list.
stripPrefix :: Eq a => [a] -> Infinite a -> Maybe (Infinite a) Source #
If a list is a prefix of an infinite list, strip it and return the rest.
Otherwise return Nothing
.
Searching
filter :: (a -> Bool) -> Infinite a -> Infinite a Source #
Filter an infinite list, removing elements which does not satisfy a predicate.
This function isn't productive (e. g., head
. filter
f
won't terminate),
if no elements of the input list satisfy the predicate.
A common objection is that since it could happen that no elements of the input
satisfy the predicate, the return type should be [a]
instead of Infinite
a
.
This would not however make filter
any more productive. Note that such
hypothetical filter
could not ever generate []
constructor, only (:)
, so
we would just have a more lax type gaining nothing instead. Same reasoning applies
to other filtering / partitioning / searching functions.
lookup :: Eq a => a -> Infinite (a, b) -> b Source #
Find the first pair, whose first component is equal to the first argument, and return the second component. If there is nothing to be found, this function will hang indefinitely.
find :: (a -> Bool) -> Infinite a -> a Source #
Find the first element, satisfying a predicate. If there is nothing to be found, this function will hang indefinitely.
partition :: (a -> Bool) -> Infinite a -> (Infinite a, Infinite a) Source #
Split an infinite list into two infinite lists: the first one contains elements, satisfying a predicate, and the second one the rest.
This function isn't productive in the first component of the tuple
(e. g., head
. fst
. partition
f
won't terminate),
if no elements of the input list satisfy the predicate.
Same for the second component,
if all elements of the input list satisfy the predicate.
Indexing
(!!) :: Infinite a -> Word -> a infixl 9 Source #
Return n-th element of an infinite list.
On contrary to Data.List.
!!
, this function takes Word
instead of Int
to avoid error
on negative arguments.
This is actually index
from
Representable
type class in disguise.
elemIndex :: Eq a => a -> Infinite a -> Word Source #
Return an index of the first element, equal to a given. If there is nothing to be found, this function will hang indefinitely.
elemIndices :: Eq a => a -> Infinite a -> Infinite Word Source #
Return indices of all elements, equal to a given.
This function isn't productive (e. g., head
. elemIndices
f
won't terminate),
if no elements of the input list are equal the given one.
findIndex :: (a -> Bool) -> Infinite a -> Word Source #
Return an index of the first element, satisfying a predicate. If there is nothing to be found, this function will hang indefinitely.
findIndices :: (a -> Bool) -> Infinite a -> Infinite Word Source #
Return indices of all elements, satisfying a predicate.
This function isn't productive (e. g., head
. elemIndices
f
won't terminate),
if no elements of the input list satisfy the predicate.
Zipping
zipWith :: (a -> b -> c) -> Infinite a -> Infinite b -> Infinite c Source #
Zip two infinite lists with a given function.
zip3 :: Infinite a -> Infinite b -> Infinite c -> Infinite (a, b, c) Source #
Zip three infinite lists.
zipWith3 :: (a -> b -> c -> d) -> Infinite a -> Infinite b -> Infinite c -> Infinite d Source #
Zip three infinite lists with a given function.
zip4 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite (a, b, c, d) Source #
Zip four infinite lists.
zipWith4 :: (a -> b -> c -> d -> e) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e Source #
Zip four infinite lists with a given function.
zip5 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite (a, b, c, d, e) Source #
Zip five infinite lists.
zipWith5 :: (a -> b -> c -> d -> e -> f) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f Source #
Zip five infinite lists with a given function.
zip6 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite (a, b, c, d, e, f) Source #
Zip six infinite lists.
zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g Source #
Zip six infinite lists with a given function.
zip7 :: Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g -> Infinite (a, b, c, d, e, f, g) Source #
Zip seven infinite lists.
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> Infinite a -> Infinite b -> Infinite c -> Infinite d -> Infinite e -> Infinite f -> Infinite g -> Infinite h Source #
Zip seven infinite lists with a given function.
unzip3 :: Infinite (a, b, c) -> (Infinite a, Infinite b, Infinite c) Source #
Unzip an infinite list of triples.
unzip4 :: Infinite (a, b, c, d) -> (Infinite a, Infinite b, Infinite c, Infinite d) Source #
Unzip an infinite list of quadruples.
unzip5 :: Infinite (a, b, c, d, e) -> (Infinite a, Infinite b, Infinite c, Infinite d, Infinite e) Source #
Unzip an infinite list of quintuples.
unzip6 :: Infinite (a, b, c, d, e, f) -> (Infinite a, Infinite b, Infinite c, Infinite d, Infinite e, Infinite f) Source #
Unzip an infinite list of sextuples.
unzip7 :: Infinite (a, b, c, d, e, f, g) -> (Infinite a, Infinite b, Infinite c, Infinite d, Infinite e, Infinite f, Infinite g) Source #
Unzip an infinite list of septuples.
Functions on strings
words :: Infinite Char -> Infinite (NonEmpty Char) Source #
Split an infinite string into words, by any isSpace
symbol.
Leading spaces are removed and, as underlined by the return type,
repeated spaces are treated as a single delimiter.
unwords :: Infinite (NonEmpty Char) -> Infinite Char Source #
Concatenate words together with a space.
The function is meant to be a counterpart of with words
.
If you need to concatenate together Infinite
[
Char
]
,
use intercalate
(
pure
' ')
.
Set operations
nub :: Eq a => Infinite a -> Infinite a Source #
Remove duplicate from a list, keeping only the first occurrence of each element.
delete :: Eq a => a -> Infinite a -> Infinite a Source #
Remove all occurrences of an element from an infinite list.
(\\) :: Eq a => Infinite a -> [a] -> Infinite a Source #
Take an infinite list and remove the first occurrence of every element of a finite list.
union :: Eq a => [a] -> Infinite a -> Infinite a Source #
Union of a finite and an infinite list. It contains the finite list as a prefix and afterwards all non-duplicate elements of the infinite list, which are not members of the finite list.
intersect :: Eq a => Infinite a -> [a] -> Infinite a Source #
Return all elements of an infinite list, which are simultaneously members of a finite list.
Ordered lists
insert :: Ord a => a -> Infinite a -> Infinite a Source #
Insert an element at the first position where it is less than or equal to the next one. If the input was sorted, the output remains sorted as well.
Generalized functions
deleteFirstsBy :: (a -> b -> Bool) -> Infinite b -> [a] -> Infinite b Source #
Overloaded version of (\\)
.
intersectBy :: (a -> b -> Bool) -> Infinite a -> [b] -> Infinite a Source #
Overloaded version of intersect
.
groupBy :: (a -> a -> Bool) -> Infinite a -> Infinite (NonEmpty a) Source #
Overloaded version of group
.
insertBy :: (a -> a -> Ordering) -> a -> Infinite a -> Infinite a Source #
Overloaded version of insert
.
genericTake :: Integral i => i -> Infinite a -> [a] Source #
Take a prefix of given length.
genericSplitAt :: Integral i => i -> Infinite a -> ([a], Infinite a) Source #
Split an infinite list into a prefix of given length and the rest.
Orphan instances
Applicative Infinite Source # | This instance operates pointwise, similar to |
Functor Infinite Source # | Just a pointwise |
Monad Infinite Source # |
|