infinite-list-0.1: Infinite lists
Copyright(c) 2022 Bodigrim
LicenseBSD3
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.List.Infinite

Description

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

Construction

data Infinite a Source #

Type of infinite lists.

Constructors

a :< (Infinite a) infixr 5 

Instances

Instances details
Applicative Infinite Source #

This instance operates pointwise, similar to ZipList.

Instance details

Defined in Data.List.Infinite

Methods

pure :: a -> Infinite a #

(<*>) :: Infinite (a -> b) -> Infinite a -> Infinite b #

liftA2 :: (a -> b -> c) -> Infinite a -> Infinite b -> Infinite c #

(*>) :: Infinite a -> Infinite b -> Infinite b #

(<*) :: Infinite a -> Infinite b -> Infinite a #

Functor Infinite Source #

Just a pointwise map.

Instance details

Defined in Data.List.Infinite

Methods

fmap :: (a -> b) -> Infinite a -> Infinite b #

(<$) :: a -> Infinite b -> Infinite a #

Monad Infinite Source #

ZipList cannot be made a lawful Monad, but Infinite, being a Representable, can. Namely, join picks up a diagonal of an infinite matrix of Infinite (Infinite a). This is mostly useful for parallel list comprehensions once {-# LANGUAGE MonadComprehensions #-} is enabled.

Instance details

Defined in Data.List.Infinite

Methods

(>>=) :: Infinite a -> (a -> Infinite b) -> Infinite b #

(>>) :: Infinite a -> Infinite b -> Infinite b #

return :: a -> Infinite a #

Elimination

head :: Infinite a -> a Source #

Get the first elements of an infinite list.

tail :: Infinite a -> Infinite a Source #

Get the elements of an infinite list after the first one.

uncons :: Infinite a -> (a, Infinite a) Source #

Split an infinite list into its head and tail.

toList :: Infinite a -> [a] Source #

Convert to a list. Use cycle to go in another direction.

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 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)

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 #

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 #

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 #

If you are looking how to traverse with a state, look no further:

mapAccumL f acc0 (x1 :< x2 :< ...) =
  let (acc1, y1) = f acc0 x1 in
    let (acc2, y2) = f acc1 x2 in
      ...
        y1 :< y2 :< ...

Transformations

concat :: Infinite (NonEmpty a) -> Infinite a Source #

Flatten out an infinite list of non-empty lists.

concatMap :: (a -> NonEmpty b) -> Infinite a -> Infinite b Source #

First map every element, then concat.

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.

interleave :: Infinite a -> Infinite a -> Infinite a Source #

Interleave two infinite lists.

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 Source #

Generate infinite sequences, 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]

(....) :: Enum a => (a, a) -> Infinite a Source #

Generate infinite sequences, 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]

iterate :: (a -> a) -> a -> Infinite a Source #

Generate an infinite list of repeated applications.

iterate' :: (a -> a) -> a -> Infinite a Source #

Same as iterate, but strict in accumulator.

unfoldr :: (b -> (a, b)) -> b -> Infinite a Source #

Build an infinite list from a seed value.

tabulate :: (Word -> a) -> Infinite a Source #

Generate an infinite list of f 0, f 1, f 2...

tabulate and (!!) witness that Infinite is Representable.

repeat :: a -> Infinite a Source #

Repeat the same element ad infinitum.

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.

Sublists

prependList :: [a] -> Infinite a -> Infinite a Source #

Prepend a list to an infinite list.

take :: Int -> Infinite a -> [a] Source #

Take a prefix of given length.

drop :: Int -> Infinite a -> Infinite a Source #

Drop a prefix of given length.

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.

dropWhile :: (a -> Bool) -> Infinite a -> Infinite a Source #

Drop the longest prefix satisfying a predicate.

This function isn't productive (e. g., head . dropWhile f won't terminate), if all elements of the input list satisfy the predicate.

span :: (a -> Bool) -> Infinite a -> ([a], Infinite a) Source #

Split an infinite list into the longest prefix satisfying a predicate and the rest.

This function isn't productive in the second component of the tuple (e. g., head . snd . span f won't terminate), if all elements of the input list satisfy the predicate.

break :: (a -> Bool) -> Infinite a -> ([a], Infinite a) Source #

Split an infinite list into the longest prefix not satisfying a predicate and the rest.

This function isn't productive in the second component of the tuple (e. g., head . snd . break f won't terminate), if no elements of the input list satisfy the predicate.

group :: Eq a => Infinite a -> Infinite (NonEmpty a) Source #

Group consecutive equal elements.

inits :: Infinite a -> Infinite [a] Source #

Generate all prefixes of an infinite list.

inits1 :: Infinite a -> Infinite (NonEmpty a) Source #

Generate all non-empty prefixes of an infinite list.

tails :: Infinite a -> Infinite (Infinite a) Source #

Generate all suffixes 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

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.

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.

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

zip :: Infinite a -> Infinite b -> Infinite (a, b) Source #

Zip two infinite lists.

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.

unzip :: Infinite (a, b) -> (Infinite a, Infinite b) Source #

Unzip an infinite list of tuples.

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

lines :: Infinite Char -> Infinite [Char] Source #

Split an infinite string into lines, by \n.

words :: Infinite Char -> Infinite (NonEmpty Char) Source #

Split an infinite string into words, by any isSpace symbol.

unlines :: Infinite [Char] -> Infinite Char Source #

Concatenate lines together with \n.

unwords :: Infinite (NonEmpty Char) -> Infinite Char Source #

Concatenate words together with a space.

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

nubBy :: (a -> a -> Bool) -> Infinite a -> Infinite a Source #

Overloaded version of nub.

deleteBy :: (a -> b -> Bool) -> a -> Infinite b -> Infinite b Source #

Overloaded version of delete.

deleteFirstsBy :: (a -> b -> Bool) -> Infinite b -> [a] -> Infinite b Source #

Overloaded version of (\\).

unionBy :: (a -> a -> Bool) -> [a] -> Infinite a -> Infinite a Source #

Overloaded version of union.

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.

genericDrop :: Integral i => i -> Infinite a -> Infinite a Source #

Drop 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 ZipList.

Instance details

Methods

pure :: a -> Infinite a #

(<*>) :: Infinite (a -> b) -> Infinite a -> Infinite b #

liftA2 :: (a -> b -> c) -> Infinite a -> Infinite b -> Infinite c #

(*>) :: Infinite a -> Infinite b -> Infinite b #

(<*) :: Infinite a -> Infinite b -> Infinite a #

Functor Infinite Source #

Just a pointwise map.

Instance details

Methods

fmap :: (a -> b) -> Infinite a -> Infinite b #

(<$) :: a -> Infinite b -> Infinite a #

Monad Infinite Source #

ZipList cannot be made a lawful Monad, but Infinite, being a Representable, can. Namely, join picks up a diagonal of an infinite matrix of Infinite (Infinite a). This is mostly useful for parallel list comprehensions once {-# LANGUAGE MonadComprehensions #-} is enabled.

Instance details

Methods

(>>=) :: Infinite a -> (a -> Infinite b) -> Infinite b #

(>>) :: Infinite a -> Infinite b -> Infinite b #

return :: a -> Infinite a #