utility-ht-0.0.5.1: Various small helper functions for Lists, Maybes, Tuples, Functions

Data.List.HT

Contents

Synopsis

Improved standard functions

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

This function is lazier than the one suggested in the Haskell 98 report. It is inits undefined = [] : undefined, in contrast to Data.List.inits undefined = undefined.

tails :: [a] -> [[a]]Source

This function is lazier than the one suggested in the Haskell 98 report. It is tails undefined = ([] : undefined) : undefined, in contrast to Data.List.tails undefined = undefined.

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

This function compares adjacent elements of a list. If two adjacent elements satisfy a relation then they are put into the same sublist. Example:

 groupBy (<) "abcdebcdef"  ==  ["abcde","bcdef"]

In contrast to that Data.List.groupBy compares the head of each sublist with each candidate for this sublist. This yields

 List.groupBy (<) "abcdebcdef"  ==  ["abcdebcdef"]

The second b is compared with the leading a. Thus it is put into the same sublist as a.

The sublists are never empty. Thus the more precise result type would be [(a,[a])].

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

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

Like standard unzip but more lazy. It is Data.List.unzip undefined == undefined, but unzip undefined == (undefined, undefined).

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

Data.List.partition of GHC 6.2.1 fails on infinite lists. But this one does not.

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

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

It is Data.List.span f undefined = undefined, whereas span f undefined = (undefined, undefined).

Split

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

Split the list at the occurrences of a separator into sub-lists. Remove the separators. This is a generalization of words.

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

Like break, but splits after the matching element.

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

Split the list after each occurence of a terminator. Keep the terminator. There is always a list for the part after the last terminator. It may be empty.

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

Split the list before each occurence of a leading character. Keep these characters. There is always a list for the part before the first leading character. It may be empty.

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

removeEach xs represents a list of sublists of xs, where each element of xs is removed and the removed element is separated. It seems to be much simpler to achieve with zip xs (map (flip List.delete xs) xs), but the implementation of removeEach does not need the Eq instance and thus can also be used for lists of functions.

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

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

It holds splitLast xs == (init xs, last xs), but splitLast is more efficient if the last element is accessed after the initial ones, because it avoids memoizing list.

viewL :: [a] -> Maybe (a, [a])Source

Should be prefered to head and tail.

viewR :: [a] -> Maybe ([a], a)Source

Should be prefered to init and last.

switchL :: b -> (a -> [a] -> b) -> [a] -> bSource

Should be prefered to head and tail.

switchR :: b -> ([a] -> a -> b) -> [a] -> bSource

Should be prefered to init and last.

List processing starting at the end

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

Remove the longest suffix of elements satisfying p. In contrast to reverse . dropWhile p . reverse this works for infinite lists, too.

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

Alternative version of reverse . takeWhile p . reverse.

List processing with Maybe and Either

maybePrefixOf :: Eq a => [a] -> [a] -> Maybe [a]Source

maybePrefixOf xs ys is Just zs if xs is a prefix of ys, where zs is ys without the prefix xs. Otherwise it is Nothing.

partitionMaybe :: (a -> Maybe b) -> [a] -> ([b], [a])Source

Partition a list into elements which evaluate to Just or Nothing by f.

It holds mapMaybe f == fst . partitionMaybe f and partition p == partitionMaybe ( x -> toMaybe (p x) x).

takeWhileJust :: [Maybe a] -> [a]Source

This is the cousin of takeWhile analogously to catMaybes being the cousin of filter.

Example: Keep the heads of sublists until an empty list occurs.

 takeWhileJust $ map (fmap fst . viewL) xs

unzipEithers :: [Either a b] -> ([a], [b])Source

Sieve and slice

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

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

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

Search&replace

search :: Eq a => [a] -> [a] -> [Int]Source

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

multiReplace :: Eq a => [([a], [a])] -> [a] -> [a]Source

Lists of lists

shear :: [[a]] -> [[a]]Source

Transform

 [[00,01,02,...],          [[00],
  [10,11,12,...],   -->     [10,01],
  [20,21,22,...],           [20,11,02],
  ...]                      ...]

With concat . shear you can perform a Cantor diagonalization, that is an enumeration of all elements of the sub-lists where each element is reachable within a finite number of steps. It is also useful for polynomial multiplication (convolution).

shearTranspose :: [[a]] -> [[a]]Source

Transform

 [[00,01,02,...],          [[00],
  [10,11,12,...],   -->     [01,10],
  [20,21,22,...],           [02,11,20],
  ...]                      ...]

It's like shear but the order of elements in the sub list is reversed. Its implementation seems to be more efficient than that of shear. If the order does not matter, better choose shearTranspose.

outerProduct :: (a -> b -> c) -> [a] -> [b] -> [[c]]Source

Operate on each combination of elements of the first and the second list. In contrast to the list instance of Monad.liftM2 in holds the results in a list of lists. It holds concat (outerProduct f xs ys) == liftM2 f xs ys

Miscellaneous

takeWhileMulti :: [a -> Bool] -> [a] -> [a]Source

Take while first predicate holds, then continue taking while second predicate holds, and so on.

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

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

Given two lists that are ordered (i.e. p x y holds for subsequent x and y) mergeBy them into a list that is ordered, again.

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

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

isAscendingLazy :: Ord a => [a] -> [Bool]Source

mapAdjacent :: (a -> a -> b) -> [a] -> [b]Source

This function combines every pair of neighbour elements in a list with a certain function.

range :: Num a => Int -> [a]Source

Enumerate without Enum context. For Enum equivalent to enumFrom.

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

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

iterateAssociative :: (a -> a -> a) -> a -> [a]Source

For an associative operation op this computes iterateAssociative op a = iterate (op a) a but it is even faster than map (powerAssociative op a a) [0..] since it shares temporary results.

The idea is: From the list map (powerAssociative op a a) [0,(2*n)..] we compute the list map (powerAssociative op a a) [0,n..], and iterate that until n==1.

iterateLeaky :: (a -> a -> a) -> a -> [a]Source

This is equal to iterateAssociative. The idea is the following: The list we search is the fixpoint of the function: Square all elements of the list, then spread it and fill the holes with successive numbers of their left neighbour. This also preserves log n applications per value. However it has a space leak, because for the value with index n all elements starting at div n 2 must be kept.