Copyright | (c) Brett Wines 2014 |
---|---|
License | BSD-style |
Maintainer | bgwines@cs.stanford.edu |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
Assorted functions on lists.
- uniqueify :: Ord a => [a] -> [a]
- pairify :: [a] -> [(a, a)]
- decyclify :: Eq a => [a] -> [a]
- shuffle :: forall a. Eq a => [a] -> Integer -> [a]
- powerset :: [a] -> [[a]]
- gen_perms :: [a] -> [[a]]
- gen_subsets_of_size :: [a] -> Integer -> [[a]]
- gen_cycles :: Eq a => [a] -> [[a]]
- has_cycles :: Eq a => [a] -> Bool
- partition_with_block_size :: Int -> [a] -> [[a]]
- partition_into_k :: Int -> [a] -> [[a]]
- powerpartition :: [a] -> [[[a]]]
- diff_infinite :: Ord a => [a] -> [a] -> [a]
- merge :: Ord a => [a] -> [a] -> [a]
- merge_by :: Ord a => (a -> a -> Ordering) -> [a] -> [a] -> [a]
- zip_while :: (a -> b -> Bool) -> [a] -> [b] -> [(a, b)]
- remove_at_index :: Integer -> [a] -> [a]
- subseq :: Integer -> Integer -> [a] -> [a]
- take_while_keep_last :: (a -> Bool) -> [a] -> [a]
- take_while_and_rest :: (a -> Bool) -> [a] -> ([a], [a])
- is_sorted :: Ord a => [a] -> Bool
- mergesort :: Ord a => [a] -> [a]
- is_palindrome :: Eq e => [e] -> Bool
- contains_duplicates :: forall a. Ord a => [a] -> Bool
- map_keep :: (a -> b) -> [a] -> [(a, b)]
- maximum_with_index :: Ord a => [a] -> (a, Integer)
- length' :: [a] -> Integer
- drop' :: Integer -> [a] -> [a]
- take' :: Integer -> [a] -> [a]
- cons :: a -> [a] -> [a]
- snoc :: a -> [a] -> [a]
List transformations
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).
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
gen_subsets_of_size :: [a] -> Integer -> [[a]] Source
O(2^k) Generates all subsets of the given list of size k.
gen_cycles :: Eq a => [a] -> [[a]] Source
O(n) Generates all cycles of a given list. For example,
gen_cycles [1..3] == [[2,3,1],[3,1,2],[1,2,3]]
has_cycles :: Eq a => [a] -> Bool 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).
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]]]
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.
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_keep_last (<3) [1..] == [1,2,3]
Sorting
Predicates
is_palindrome :: Eq e => [e] -> Bool Source
O(n^2) Returns whether the given list is a palindrome.
contains_duplicates :: forall a. Ord a => [a] -> Bool Source
O(n log(n)) Returns whether the given list contains the any element more than once.
Assorted functions
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.