extra-0.5.1: Extra functions I use.

Safe HaskellSafe-Inferred

Data.List.Extra

Contents

Description

This module extends Data.List with extra functions of a similar nature. The package also exports the existing Data.List functions. Some of the names and semantics were inspired by the text package.

Synopsis

Documentation

module Data.List

String operations

lower :: String -> StringSource

Convert a string to lower case.

 lower "This is A TEST" == "this is a test"
 lower "" == ""

upper :: String -> StringSource

Convert a string to upper case.

 upper "This is A TEST" == "THIS IS A TEST"
 upper "" == ""

trim :: String -> StringSource

Remove spaces from either side of a string. A combination of trimEnd and trimStart.

 trim      "  hello   " == "hello"
 trimStart "  hello   " == "hello   "
 trimEnd   "  hello   " == "  hello"
 \s -> trim s == trimEnd (trimStart s)

trimStart :: String -> StringSource

Remove spaces from the start of a string, see trim.

trimEnd :: String -> StringSource

Remove spaces from the end of a string, see trim.

word1 :: String -> (String, String)Source

Split the first word off a string. Useful for when starting to parse the beginning of a string, but you want to accurately perserve whitespace in the rest of the string.

 word1 "" == ("", "")
 word1 "keyword rest of string" == ("keyword","rest of string")
 word1 "  keyword\n  rest of string" == ("keyword","rest of string")
 \s -> fst (word1 s) == concat (take 1 $ words s)
 \s -> words (snd $ word1 s) == drop 1 (words s)

Splitting

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

Drop a number of elements from the end of the list.

 dropEnd 3 "hello"  == "he"
 dropEnd 5 "bye"    == ""
 dropEnd (-1) "bye" == "bye"
 \i xs -> dropEnd i xs `isPrefixOf` xs
 \i xs -> length (dropEnd i xs) == max 0 (length xs - max 0 i)
 \i -> take 3 (dropEnd 5 [i..]) == take 3 [i..]

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

Take a number of elements from the end of the list.

 takeEnd 3 "hello"  == "llo"
 takeEnd 5 "bye"    == "bye"
 takeEnd (-1) "bye" == ""
 \i xs -> takeEnd i xs `isSuffixOf` xs
 \i xs -> length (takeEnd i xs) == min (max 0 i) (length xs)

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

Break, but from the end.

 breakEnd isLower "youRE" == ("you","RE")
 breakEnd isLower "youre" == ("youre","")
 breakEnd isLower "YOURE" == ("","YOURE")

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

Span, but from the end.

 spanEnd isUpper "youRE" == ("you","RE")
 spanEnd (not . isSpace) "x y z" == ("x y ","z")
 \f xs-> spanEnd f xs == swap (both reverse (span f (reverse xs)))

dropWhileEnd :: (a -> Bool) -> [a] -> [a]

The dropWhileEnd function drops the largest suffix of a list in which the given predicate holds for all elements. For example:

 dropWhileEnd isSpace "foo\n" == "foo"
 dropWhileEnd isSpace "foo bar" == "foo bar"
 dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined

dropWhileEnd' :: (a -> Bool) -> [a] -> [a]Source

A version of dropWhileEnd but with different strictness properties. The function dropWhileEnd can be used on an infinite list and tests the property on each character. In contrast, dropWhileEnd' is strict in the spine of the list but only tests the trailing suffix. This version usually outperforms dropWhileEnd if the list is short or the test is expensive. Note the tests below cover both the prime and non-prime variants.

 dropWhileEnd  isSpace "ab cde  " == "ab cde"
 dropWhileEnd' isSpace "ab cde  " == "ab cde"
 last (dropWhileEnd  even [undefined,3]) == undefined
 last (dropWhileEnd' even [undefined,3]) == 3
 head (dropWhileEnd  even (3:undefined)) == 3
 head (dropWhileEnd' even (3:undefined)) == undefined

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

A version of takeWhile operating from the end.

 takeWhileEnd even [2,3,4,6] == [4,6]

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

Return the prefix of the second string if its suffix matches the entire first string.

Examples:

 stripSuffix "bar" "foobar" == Just "foo"
 stripSuffix ""    "baz"    == Just "baz"
 stripSuffix "foo" "quux"   == Nothing

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

A variant of words with a custom test. In particular, adjacent separators are discarded, as are leading or trailing separators.

 wordsBy (== ':') "::xyz:abc::123::" == ["xyz","abc","123"]
 \s -> wordsBy isSpace s == words s

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

A variant of lines with a custom test. In particular, if there is a trailing separator it will be discarded.

 linesBy (== ':') "::xyz:abc::123::" == ["","","xyz","abc","","123",""]
 \s -> linesBy (== '\n') s == lines s
 linesBy (== ';') "my;list;here;" == ["my","list","here"]

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

Find the first instance of needle in haystack. The first element of the returned tuple is the prefix of haystack before needle is matched. The second is the remainder of haystack, starting with the match.

 breakOn "::" "a::b::c" == ("a", "::b::c")
 breakOn "/" "foobar"   == ("foobar", "")
 \needle haystack -> let (prefix,match) = breakOn needle haystack in prefix ++ match == haystack

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

Similar to breakOn, but searches from the end of the string.

The first element of the returned tuple is the prefix of haystack up to and including the last match of needle. The second is the remainder of haystack, following the match.

 breakOnEnd "::" "a::b::c" == ("a::b::", "c")

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

Break a list into pieces separated by the first list argument, consuming the delimiter. An empty delimiter is invalid, and will cause an error to be raised.

 splitOn "\r\n" "a\r\nb\r\nd\r\ne" == ["a","b","d","e"]
 splitOn "aaa"  "aaaXaaaXaaaXaaa"  == ["","X","X","X",""]
 splitOn "x"    "x"                == ["",""]
 splitOn "x"    ""                 == [""]
 \s x -> s /= "" ==> intercalate s (splitOn s x) == x
 \c x -> splitOn [c] x                           == split (==c) x

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

Splits a list into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output.

 split (== 'a') "aabbaca" == ["","","bb","c",""]
 split (== 'a') ""        == [""]
 split (== ':') "::xyz:abc::123::" == ["","","xyz","abc","","123","",""]
 split (== ',') "my,list,here" == ["my","list","here"]

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

Split a list into chunks of a given size. The last chunk may contain fewer than n elements. The chunk size must be positive.

 chunksOf 3 "my test" == ["my ","tes","t"]
 chunksOf 3 "mytest"  == ["myt","est"]
 chunksOf 8 ""        == []
 chunksOf 0 "test"    == undefined

Basics

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

Non-recursive transform over a list, like maybe.

 list 1 (\v _ -> v - 2) [5,6,7] == 3
 list 1 (\v _ -> v - 2) []      == 1
 \nil cons xs -> maybe nil (uncurry cons) (uncons xs) == list nil cons xs

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

If the list is empty returns Nothing, otherwise returns the head and the tail.

 uncons "test" == Just ('t',"est")
 uncons ""     == Nothing
 \xs -> uncons xs == if null xs then Nothing else Just (head xs, tail xs)

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

If the list is empty returns Nothing, otherwise returns the init and the last.

 unsnoc "test" == Just ("tes",'t')
 unsnoc ""     == Nothing
 \xs -> unsnoc xs == if null xs then Nothing else Just (init xs, last xs)

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

Append an element to the start of a list, an alias for '(:)'.

 cons 't' "est" == "test"
 \x xs -> uncons (cons x xs) == Just (x,xs)

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

Append an element to the end of a list, takes O(n) time.

 snoc "tes" 't' == "test"
 \xs x -> unsnoc (snoc xs x) == Just (xs,x)

drop1 :: [a] -> [a]Source

Equivalent to drop 1, but likely to be faster and a single lexeme.

 drop1 ""         == ""
 drop1 "test"     == "est"
 \xs -> drop 1 xs == drop1 xs

List operations

groupSort :: Ord k => [(k, v)] -> [(k, [v])]Source

A combination of group and sort.

 groupSort [(1,'t'),(3,'t'),(2,'e'),(2,'s')] == [(1,"t"),(2,"es"),(3,"t")]
 \xs -> map fst (groupSort xs) == sort (nub (map fst xs))
 \xs -> concatMap snd (groupSort xs) == map snd (sortOn fst xs)

nubOn :: Eq b => (a -> b) -> [a] -> [a]Source

A version of nub where the equality is done on some extracted value. nubOn f is equivalent to nubBy ((==) on f), but has the performance advantage of only evaluating f once for each element in the input list.

groupOn :: Eq b => (a -> b) -> [a] -> [[a]]Source

A version of group where the equality is done on some extracted value.

sortOn :: Ord b => (a -> b) -> [a] -> [a]Source

Sort a list by comparing the results of a key function applied to each element. sortOn f is equivalent to sortBy (comparing f), but has the performance advantage of only evaluating f once for each element in the input list. This is called the decorate-sort-undecorate paradigm, or Schwartzian transform.

 sortOn fst [(3,"z"),(1,""),(3,"a")] == [(1,""),(3,"z"),(3,"a")]

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

Are two lists disjoint, with no elements in common.

 disjoint [1,2,3] [4,5] == True
 disjoint [1,2,3] [4,1] == False

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

Are all elements the same.

 allSame [1,1,2] == False
 allSame [1,1,1] == True
 allSame [1]     == True
 allSame []      == True
 allSame (1:1:2:undefined) == False
 \xs -> allSame xs == (length (nub xs) <= 1)

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

Is there any element which occurs more than once.

 anySame [1,1,2] == True
 anySame [1,2,3] == False
 anySame (1:2:1:undefined) == True
 anySame [] == False
 \xs -> anySame xs == (length (nub xs) < length xs)

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

Apply some operation repeatedly, producing an element of output and the remainder of the list.

 \xs -> repeatedly (splitAt 3) xs  == chunksOf 3 xs
 \xs -> repeatedly word1 (trim xs) == words xs

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

Flipped version of map.

 for [1,2,3] (+1) == [2,3,4]

firstJust :: (a -> Maybe b) -> [a] -> Maybe bSource

Find the first element of a list for which the operation returns Just, along with the result of the operation. Like find but useful where the function also computes some expensive information that can be reused. Particular useful when the function is monadic, see firstJustM.

 firstJust id [Nothing,Just 3]  == Just 3
 firstJust id [Nothing,Nothing] == Nothing

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

A merging of unzip and concat.

 concatUnzip [("a","AB"),("bc","C")] == ("abc","ABC")

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

A merging of unzip3 and concat.

 concatUnzip3 [("a","AB",""),("bc","C","123")] == ("abc","ABC","123")

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

Replace a subsequence everywhere it occurs. The first argument must not be the empty list.

 replace "el" "_" "Hello Bella" == "H_lo B_la"
 replace "el" "e" "Hello"       == "Helo"
 replace "" "e" "Hello"         == undefined
 \xs ys -> not (null xs) ==> replace xs xs ys == ys

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

Merge two lists which are assumed to be ordered.

 merge "ace" "bd" == "abcde"
 \xs ys -> merge (sort xs) (sort ys) == sort (xs ++ ys)

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

Like merge, but with a custom ordering function.