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

Safe HaskellSafe
LanguageHaskell98

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

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

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

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

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 somehow a generalization of lines and words. But note the differences:

Prelude Data.List.HT> words "a  a"
["a","a"]
Prelude Data.List.HT> chop (' '==) "a  a"
["a","","a"]
Prelude Data.List.HT> lines "a\n\na"
["a","","a"]
Prelude Data.List.HT> chop ('\n'==) "a\n\na"
["a","","a"]
Prelude Data.List.HT> lines "a\n"
["a"]
Prelude Data.List.HT> chop ('\n'==) "a\n"
["a",""]

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

Like break, but splits after the matching element.

takeUntil :: (a -> Bool) -> [a] -> [a] Source #

Take all elements until one matches. The matching element is returned, too. This is the key difference to takeWhile (not . p). It holds takeUntil p xs == fst (breakAfter p xs).

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. See package non-empty for more precise result type.

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. See package non-empty for more precise result type.

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

Data.List.HT Data.Char> segmentAfterMaybe (\c -> toMaybe (isLetter c) (toUpper c)) "123a5345b---"
([("123",'A'),("5345",'B')],"---")

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

Data.List.HT Data.Char> segmentBeforeMaybe (\c -> toMaybe (isLetter c) (toUpper c)) "123a5345b---"
("123",[('A',"5345"),('B',"---")])

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.

See also the proposal http://www.haskell.org/pipermail/libraries/2008-February/009270.html

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

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

Deprecated: use viewR instead

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

Should be prefered to head and tail.

switchR :: b -> ([a] -> a -> b) -> [a] -> b Source #

Should be prefered to init and last.

List processing starting at the end

dropRev :: Int -> [a] -> [a] Source #

dropRev n is like reverse . drop n . reverse but it is lazy enough to work for infinite lists, too.

takeRev :: Int -> [a] -> [a] Source #

takeRev n is like reverse . take n . reverse but it is lazy enough to work for infinite lists, too.

splitAtRev :: Int -> [a] -> ([a], [a]) Source #

splitAtRev n xs == (dropRev n xs, takeRev n xs). It holds xs == uncurry (++) (splitAtRev n xs)

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

Deprecated: Use dropWhile from Data.List.Reverse.StrictElement or Data.List.Reverse.StrictSpine instead

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

Deprecated: Use takeWhile from Data.List.Reverse.StrictElement or Data.List.Reverse.StrictSpine instead

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. It is the same as stripPrefix.

maybeSuffixOf :: Eq a => [a] -> [a] -> Maybe [a] Source #

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 #

keep every k-th value from the list

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

rotate left

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

isAscending :: Ord a => [a] -> Bool Source #

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.

mapAdjacent1 :: (a -> a -> b -> c) -> a -> [(a, b)] -> [c] Source #

mapAdjacent f a0 [(a1,b1), (a2,b2), (a3,b3)]
==
[f a0 a1 b1, f a1 a2 b2, f a2 a3 b3]

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.