Zora-1.1.11: Graphing library wrapper + assorted useful functions

Portabilityportable
Stabilityexperimental
Maintainerbgwines@cs.stanford.edu
Safe HaskellSafe-Inferred

Zora.List

Contents

Description

Assorted functions on lists.

Synopsis

Partitioning

partition_with_block_size :: Int -> [a] -> [[a]]Source

O(n) Partitions the given list into blocks of the specified length. Truncation behaves as follows:

 partition_with_block_size 3 [1..10] == [[1,2,3],[4,5,6],[7,8,9],[10]]

partition_into_k :: Int -> [a] -> [[a]]Source

O(n) Partitions the given list into k blocks. Truncation behavior is best described by example:

 partition_into_k  3 [1..9]  == [[1,2,3],[4,5,6],[7,8,9]]
 partition_into_k  3 [1..10] == [[1,2,3,4],[5,6,7,8],[9,10]]
 partition_into_k  3 [1..11] == [[1,2,3,4],[5,6,7,8],[9,10,11]]
 partition_into_k  3 [1..12] == [[1,2,3,4],[5,6,7,8],[9,10,11,12]]
 partition_into_k  3 [1..13] == [[1,2,3,4,5],[6,7,8,9,10],[11,12,13]]

powerpartition :: [a] -> [[[a]]]Source

O(B(n)), where B(n) is the n^th Bell number. Computes all partitions of the given list. For example,

 powerpartition [1..3] == [[[1],[2],[3]], [[1,2],[3]], [[2],[1,3]], [[1],[2,3]], [[1,2,3]]]

List transformations

uniqueify :: Ord a => [a] -> [a]Source

O(n log(n)) Removes duplicate elements. Like nub, but for Ord types, so it can be faster.

pairify :: [a] -> [(a, a)]Source

O(n) Zips the list up into pairs. For example,

 pairify [1..6] == [(1,2), (3,4), (5,6)]
 pairify [1..5] == [(1,2), (3,4)]

decyclify :: Eq a => [a] -> [a]Source

O(l m), where l is the cycle length and m is the index of the start of the cycle. If the list contains no cycles, then the runtime is O(n).

NOTE: this function will only find cycles in a list can be the output of an iterated function -- that is, no element may be succeeded by two separate elements (e.g. [2,3,2,4]).

shuffle :: forall a. Eq a => [a] -> Integer -> [a]Source

O(n log(n)) Shuffles the given list. The second parameter is the seed for the random number generator that backs the shuffle.

Permutations, combinations, and cycles

powerset :: [a] -> [[a]]Source

O(2^n) Computes the powerset of the given list.

permutations :: [a] -> [[a]]Source

O(n!) Computes all permutations of the given list.

subsets_of_size :: [a] -> Integer -> [[a]]Source

O(2^k) Generates all subsets of the given list of size k.

subsets_of_size_with_replacement :: Integer -> [a] -> [[a]]Source

O(n^m) Computes all sets comprised of elements in the given list, where the elements may be used multiple times, where n is the size of the given list and m is the size of the sets to generate. For example,

 subsets_of_size_with_replacement 3 [1,2] == [[1,1,1],[2,1,1],[1,2,1],[2,2,1],[1,1,2],[2,1,2],[1,2,2],[2,2,2]]

cycles :: Eq a => [a] -> [[a]]Source

O(n) Generates all cycles of a given list. For example,

 cycles [1..3] == [[2,3,1],[3,1,2],[1,2,3]]

has_cycles :: Eq a => [a] -> BoolSource

O(l m), where l is the cycle length and m is the index of the start of the cycle. If the list contains no cycles, then the runtime is O(n).

Operations with two lists

diff_infinite :: Ord a => [a] -> [a] -> [a]Source

Given two infinite sorted lists, generates a list of elements in the first but not the second. Implementation from http://en.literateprograms.org/Sieve_of_Eratosthenes_(Haskell).

merge :: Ord a => [a] -> [a] -> [a]Source

O(max(n, m)) Merges the two given sorted lists of respective lengths n and m. A special case of merge_by where the comparison function is compare.

merge_by :: Ord a => (a -> a -> Ordering) -> [a] -> [a] -> [a]Source

O(max(n, m)) Merges the two given sorted lists of respective lengths n and m, comparing elements in between the two lists with the given comparator function.

zip_while :: (a -> b -> Bool) -> [a] -> [b] -> [(a, b)]Source

O(min(n, m)) Zips the two given lists of respective lengths n and m as long as the pairs satisfy the given predicate function.

Sublists

remove_at_index :: Integer -> [a] -> [a]Source

O(n) Removes an element at the specified index in the given list.

subseq :: Integer -> Integer -> [a] -> [a]Source

O(n) Returns the subsequence of the given length at starting at index i of length m. For example,

 subseq 4 5 [1..20] == [5,6,7,8,9]

take_while_keep_last :: (a -> Bool) -> [a] -> [a]Source

(O(n)) Identical to takeWhile, but also contains the first element to satisfy the given predicate function. For example:

 take_while_keep_last (<3) [1..] == [1,2,3]

take_while_and_rest :: (a -> Bool) -> [a] -> ([a], [a])Source

(O(n)) Returns a pair where the first element is identical to what takeWhile returns and the second element is the rest of the list

 take_while_and_rest (<3) [1..10] == ([1,2],[3,4,5,6,7,8,9,10])

find_and_rest :: (a -> Bool) -> [a] -> Maybe (a, [a])Source

O(n) Like Data.List.Find, but returns a Maybe 2-tuple, instead, where the second element of the pair is the elements in the list after the first element of the pair.

 (find_and_rest ((==) 3) [1..10]) == Just (3, [4..10])

subsequences :: [a] -> [[a]]Source

(O(2^n)) Returns all subsequences (contiguous and noncontiguous)

contiguous_subsequences :: [a] -> [[a]]Source

(O(n^2)) Returns all contiguous subsequences.

Sorting

is_sorted :: Ord a => [a] -> BoolSource

O(n) Returns whether the given list is sorted.

mergesort :: Ord a => [a] -> [a]Source

O(n log(n)) Sorts the given list.

Predicates

is_palindrome :: Eq e => [e] -> BoolSource

O(n) Returns whether the given list is a palindrome.

contains_duplicates :: forall a. Ord a => [a] -> BoolSource

O(n log(n)) Returns whether the given list contains any element more than once.

Assorted functions

bsearch :: (Integer -> Ordering) -> Maybe IntegerSource

O(f log k), where k is the returnvalue, and f is the runtime of the input function on the lowest power of 2 above the returnvalue.

bsearch_1st_geq :: (Integer -> Ordering) -> Maybe IntegerSource

O(f log k), where k is the returnvalue, and f is the runtime of the input function on the lowest power of 2 above the returnvalue.

elem_counts :: Ord a => [a] -> [(a, Integer)]Source

O(nlog(n)) Counts the number of time each element appears in the given list. For example:

 elem_counts [1,2,1,4] == [(1,2),(2,1),(4,1)]

running_bests :: forall a. Ord a => [a] -> [a]Source

O(n) Returns the noncontiguous sublist of elements greater than all previous elements. For example:

 running_bests [1,3,2,4,6,5] == [1,3,4,6]

running_bests_by :: forall a. Ord a => (a -> a -> Ordering) -> [a] -> [a]Source

O(n) Returns the noncontiguous sublist of elements greater than all previous elements, where greater is determined by the provided comparison function. For example:

 running_bests_by (Data.Ord.comparing length) [[1],[3,3,3],[2,2]] == [[1],[3,3,3]]

(<$*>) :: Applicative f => (a -> a -> b) -> f a -> f bSource

Shorthand for applicative functors:

 f <$*> l = f <$> l <*> l

interleave :: [a] -> [a] -> [a]Source

O(min(n, m)) Interleaves elements from the two given lists of respective lengths n and m in an alternating fashion. For example:

 interleave [1,3,5,7] [2,4,6,8] == [1,2,3,4,5,6,7,8]
 interleave [1,3,5,7] [2,4,6] == [1,2,3,4,5,6,7]
 interleave [1,3,5] [2,4,6,8] == [1,2,3,4,5,6,8]

count :: (a -> Bool) -> [a] -> IntegerSource

O(n) counts the number of elements in a list that satisfy a given predicate function.

map_keep :: (a -> b) -> [a] -> [(a, b)]Source

O(n) Maps the given function over the list while keeping the original list. For example:

 map_keep chr [97..100] == [(97,'a'),(98,'b'),(99,'c'),(100,'d')]

maximum_with_index :: Ord a => [a] -> (a, Integer)Source

O(n) Finds the maximum element of the given list and returns a pair of it and the index at which it occurs (if the maximum element occurs multiple times, behavior is identical to that of maximumBy). The list must be finite and non-empty.

minimum_with_index :: Ord a => [a] -> (a, Integer)Source

O(n) Finds the minimum element of the given list and returns a pair of it and the index at which it occurs (if the minimum element occurs multiple times, behavior is identical to that of minimumBy). The list must be finite and non-empty.

minima_by :: (a -> a -> Ordering) -> [a] -> [a]Source

length' :: [a] -> IntegerSource

Like length, but returns an integer.

drop' :: Integer -> [a] -> [a]Source

Like drop, but takes an integer.

take' :: Integer -> [a] -> [a]Source

Like take, but takes an integer.

cons :: a -> [a] -> [a]Source

List pre-pending.

snoc :: a -> [a] -> [a]Source

List appending.

 snoc 4 [1,2,3] == [1,2,3,4]

Tuples

map_fst :: (a -> c) -> (a, b) -> (c, b)Source

Applies the given function to the first element of the tuple.

map_snd :: (b -> c) -> (a, b) -> (a, c)Source

Applies the given function to the second element of the tuple.

map_pair :: (a -> c) -> (b -> d) -> (a, b) -> (c, d)Source

Applies the given two functions to the respective first and second elements of the tuple.

fst3 :: (a, b, c) -> aSource

Extracts the first element of a 3-tuple.

snd3 :: (a, b, c) -> bSource

Extracts the second element of a 3-tuple.

trd3 :: (a, b, c) -> cSource

Extracts the third element of a 3-tuple.

pair_op :: (a -> b -> c) -> (a, b) -> cSource

Applies the given binary function to both elements of the given tuple.

triple_op :: (a -> b -> c -> d) -> (a, b, c) -> dSource

Applies the given ternary function to all three elements of the given tuple.