extra-0.3: Extra functions I use.

Safe HaskellSafe-Inferred

Data.List.Extra

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

lower :: String -> StringSource

Documentation about lowercase

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

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

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

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

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

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

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

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

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

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

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

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

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

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]

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

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

Is there any element which occurs more than once.

 anySame [1,1,2] == True
 anySame [1,2,3] == False

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

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

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

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

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. Often outperforms if the list is short or the test is expensive.

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

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

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

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

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

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

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

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

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

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

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.

Examples:

 breakOn "::" "a::b::c" == ("a", "::b::c")
 breakOn "/" "foobar"   == ("foobar", "")

Laws:

 \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.

Examples:

 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"    ""                 == [""]

and

 \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. eg.

 split (=='a') "aabbaca" == ["","","bb","c",""]
 split (=='a') ""        == [""]

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"    == error