rational-list-1.0.0.0: finite or repeating lists

Copyright(c) Ross Paterson 2019
LicenseBSD-style
MaintainerR.Paterson@city.ac.uk
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.RationalList

Contents

Description

A rational list (a special kind of rational tree) is a list that is either finite or of the form xs ++ cycle ys where xs and ys are finite lists and ys is non-empty. (Another name is rho-lists, after the Greek letter ρ whose shape suggests cyclic repetition after some prefix.) Such lists have a useful finite representation.

Many functions in this module have the same names as functions in the Prelude, Data.Foldable and Data.List. On finite lists, these functions have the same behaviour as their list counterparts. Due to the finite representation, they are also total, even on infinite lists. Many operations on infinite lists are also substantially faster than using lists, because they exploit the repetition. For example:

>>> num_list = iterate (\n -> (n*n + 1) `mod` 100) 19
>>> num_list
fromList [19,62,45] <> cycle [26,77,30,1,2,5]
>>> toList num_list
[19,62,45,26,77,30,1,2,5,26,77,30,1,2,5,26,77,30,1,2,5,26,77,30,...
>>> maximum num_list
77
>>> elementAt 2000000000000000000 num_list
Just 5
Synopsis

Documentation

data RationalList a Source #

A list of the form fromList xs <> cycle ys where xs and ys are finite lists.

Instances
Foldable RationalList Source #

Specialized implementations of null, length, elem, maximum and minimum

Instance details

Defined in Data.RationalList

Methods

fold :: Monoid m => RationalList m -> m #

foldMap :: Monoid m => (a -> m) -> RationalList a -> m #

foldr :: (a -> b -> b) -> b -> RationalList a -> b #

foldr' :: (a -> b -> b) -> b -> RationalList a -> b #

foldl :: (b -> a -> b) -> b -> RationalList a -> b #

foldl' :: (b -> a -> b) -> b -> RationalList a -> b #

foldr1 :: (a -> a -> a) -> RationalList a -> a #

foldl1 :: (a -> a -> a) -> RationalList a -> a #

toList :: RationalList a -> [a] #

null :: RationalList a -> Bool #

length :: RationalList a -> Int #

elem :: Eq a => a -> RationalList a -> Bool #

maximum :: Ord a => RationalList a -> a #

minimum :: Ord a => RationalList a -> a #

sum :: Num a => RationalList a -> a #

product :: Num a => RationalList a -> a #

Eq a => Eq (RationalList a) Source #

Total functions testing whether lists have the same unfoldings

Instance details

Defined in Data.RationalList

Ord a => Ord (RationalList a) Source #

Total functions giving the relationship between unfoldings

Instance details

Defined in Data.RationalList

(Read a, Eq a) => Read (RationalList a) Source #

Reads the form produced by show

Instance details

Defined in Data.RationalList

Show a => Show (RationalList a) Source #

Canonical form of the list

Instance details

Defined in Data.RationalList

Eq a => Semigroup (RationalList a) Source #

<> is concatenation. In particular, if the first list is infinite, the second is ignored.

Instance details

Defined in Data.RationalList

Eq a => Monoid (RationalList a) Source #

mempty is the empty list.

Instance details

Defined in Data.RationalList

Construction

fromList :: [a] -> RationalList a Source #

fromList xs is a representation of the list xs, which must be finite.

repeat :: a -> RationalList a Source #

repeat x is the infinite repetition of a single value.

cycle :: Eq a => [a] -> RationalList a Source #

cycle xs is the infinite repetition of the list xs, which must be finite.

iterate :: Eq a => (a -> a) -> a -> RationalList a Source #

iterate f x is an infinite list of repeated applications of f to x, provided an earlier value is repeated at some point. If no repetition occurs, the computation does not terminate.

unfoldr :: (Eq a, Eq b) => (b -> Maybe (a, b)) -> b -> RationalList a Source #

unfoldr f z is a list built from a seed value z. The function f takes a seed value and returns Nothing if it is done producing the list or returns Just (a,b), in which case, a is a prepended to the list and b is used as the next seed value in a recursive call. This will not terminate unless one of these evaluations of f returns Nothing or Just (a,b) where b is a previously seen value.

Components

Any rational list xs satisfies

fromList (prefix xs) <> cycle (repetend xs) = xs

prefix :: RationalList a -> [a] Source #

prefix xs is the minimal non-repeating part at the front of xs.

repetend :: RationalList a -> [a] Source #

repetend xs is the minimal repeating part of xs, or [] if xs is finite.

Modification

map :: Eq b => (a -> b) -> RationalList a -> RationalList b Source #

map f xs is the list obtained by applying f to each element of xs.

concat :: Eq a => RationalList (RationalList a) -> RationalList a Source #

concat xss is the concatenation of all the lists in xss.

concatMap :: Eq b => (a -> RationalList b) -> RationalList a -> RationalList b Source #

concatMap f xs is the concatenation of mapping f over the elements of xs.

concatMap f xs = concat (map f xs)

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

zip xs ys is a list of corresponding pairs in xs and ys. If one input list is shorter, unmatched elements of the longer list are not included.

zipWith :: Eq c => (a -> b -> c) -> RationalList a -> RationalList b -> RationalList c Source #

zipWith f xs ys is a list of f applied to corresponding elements from xs and ys. If one input list is shorter, unmatched elements of the longer list are not included.

unzip :: (Eq a, Eq b) => RationalList (a, b) -> (RationalList a, RationalList b) Source #

unzip xys in a pair of the list of first components of xys and the list of second components.

Sublists

filter :: Eq a => (a -> Bool) -> RationalList a -> RationalList a Source #

filter p xs is the list of elements x of xs for which p x is True.

partition :: Eq a => (a -> Bool) -> RationalList a -> (RationalList a, RationalList a) Source #

partition p xs is the list of elements x of xs for which p x is True and the list of those for which it is False.

takeWhile :: Eq a => (a -> Bool) -> RationalList a -> RationalList a Source #

takeWhile p xs is the longest prefix (possibly empty) of xs of elements that satisfy p.

dropWhile :: Eq a => (a -> Bool) -> RationalList a -> RationalList a Source #

dropWhile p xs is the remainder of the list after the longest prefix (possibly empty) of xs of elements that satisfy p. If no element satisfies p, the result is an empty list.

span :: Eq a => (a -> Bool) -> RationalList a -> (RationalList a, RationalList a) Source #

span p xs is a pair whose first element is the longest prefix (possibly empty) of xs of elements that satisfy p and whose second element is the remainder of the list. If no element satisfies p, the first list is xs and the second is empty.

take :: Integral i => i -> RationalList a -> [a] Source #

take n xs is the prefix of xs of length n, or all of xs if xs is finite and n > length xs.

drop :: (Integral i, Eq a) => i -> RationalList a -> RationalList a Source #

drop n xs is the suffix of xs after the first n elements, or empty if xs is finite and n > length xs.

splitAt :: (Integral i, Eq a) => i -> RationalList a -> ([a], RationalList a) Source #

splitAt n xs is a pair whose first element is the prefix of xs of length n and whose second element is the remainder of the list.

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

tails xs is the list of final segments of xs, longest first.

Queries

These are similar to list functions, but take advantage of repetition for efficiency and to work even with infinite lists. Several more are provided by the Foldable instance.

finite :: RationalList a -> Bool Source #

finite xs is True when xs is finite.

elementAt :: Integral i => i -> RationalList a -> Maybe a Source #

elementAt i xs is the element of xs at position i (counting from zero), or Nothing if xs has fewer than i elements.

elemIndex :: Eq a => a -> RationalList a -> Maybe Int Source #

elemIndex x xs is the index of the first element in xs that is equal (by ==) to x, or Nothing if there is no such element.

find :: (a -> Bool) -> RationalList a -> Maybe a Source #

find p xs is Just x if x is the first element of xs for which p x is True, or Nothing if there is no such element.

findIndex :: (a -> Bool) -> RationalList a -> Maybe Int Source #

findIndex p xs is Just i if i is the first element x of xs for which p x is True, or Nothing if there is no such element.

any :: (a -> Bool) -> RationalList a -> Bool Source #

any p xs is True if any only if p x is True for any element of xs.

all :: (a -> Bool) -> RationalList a -> Bool Source #

all p xs is True if any only if p x is True for all elements of xs.

maximumBy :: (a -> a -> Ordering) -> RationalList a -> a Source #

maximumBy cmp xs is the greatest element of xs (which must be non-empty) with respect to the comparison function cmp.

minimumBy :: (a -> a -> Ordering) -> RationalList a -> a Source #

minimumBy cmp xs is the least element of xs (which must be non-empty) with respect to the comparison function cmp.

foldMapTake :: (Integral i, Monoid m) => (a -> m) -> i -> RationalList a -> m Source #

foldMapTake f n xs applies f to the first n elements of xs and combines the results:

foldMapTake f n = foldMap f . take n

but may be significantly faster for some monoids.

Examples

Decimal fractions

The following function takes a number 0 <= x < 1 and returns the leading digit of its decimal representation, as well as the residue:

digit :: Rational -> Maybe (Int, Rational)
digit x
  | x == 0 = Nothing
  | otherwise = Just (properFraction (x * 10))

Unfolding with this function gives decimal representations of fractions:

>>> Data.List.unfoldr digit (3/8)
[3,7,5]
>>> Data.List.unfoldr digit (3/28)
[1,0,7,1,4,2,8,5,7,1,4,2,8,5,7,1,4,2,8,5,7,1,4,2,8,5,7,1,4,2,...

The latter infinite list repeats the subsequence 7,1,4,2,8,5 indefinitely. The rational list version of unfoldr detects the repetition and yields a finite representation:

>>> unfoldr digit (3/8)
fromList [3,7,5]
>>> unfoldr digit (3/28)
fromList [1,0] <> cycle [7,1,4,2,8,5]

With this representation, several list functions can be implemented more efficiently, e.g.

>>> elementAt 1000000000 $ unfoldr digit (3/28)
Just 4

while others terminate even for infinite lists:

>>> elem 3 $ unfoldr digit (3/28)
False

Fibonacci numbers

Puzzle: what is the last digit of the 1000000000th Fibonacci number? (where the first and second Fibonacci numbers are both 1.)

The infinite list of Fibonacci numbers can be defined as

>>> Data.List.map fst $ Data.List.iterate (\ (a,b) -> (b,(a+b))) (0,1)
[0,1,1,2,3,5,8,13,21,34,55,89,144,233,377,610,987,1597,2584,4181,...

However, we only need the last digit of each number, so we can replace a+b with (a+b) `mod` 10. Then the list of pairs must repeat, since there are a finite number of possible combinations, so it can be represented as a rational list, and the solution is

>>> elementAt 1000000000 $ map fst $ iterate (\ (a,b) -> (b, (a+b) `mod` 10)) (0,1)
Just 5

Here elementAt calculates the appropriate position in the repeating part of the list and returns that, without calculating lots of numbers.