| Safe Haskell | Safe-Inferred |
|---|
Data.List.Extra
Description
- lower :: String -> String
- upper :: String -> String
- trim :: String -> String
- trimStart :: String -> String
- trimEnd :: String -> String
- dropAround :: (a -> Bool) -> [a] -> [a]
- word1 :: String -> (String, String)
- drop1 :: [a] -> [a]
- list :: b -> (a -> [a] -> b) -> [a] -> b
- uncons :: [a] -> Maybe (a, [a])
- unsnoc :: [a] -> Maybe ([a], a)
- cons :: a -> [a] -> [a]
- snoc :: [a] -> a -> [a]
- groupSort :: Ord k => [(k, v)] -> [(k, [v])]
- groupSortOn :: Ord a => (k -> a) -> [(k, v)] -> [(k, [v])]
- nubOn :: Eq b => (a -> b) -> [a] -> [a]
- groupOn :: Eq b => (a -> b) -> [a] -> [[a]]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- repeatedly :: ([a] -> (b, [a])) -> [a] -> [b]
- for :: [a] -> (a -> b) -> [b]
- disjoint :: Eq a => [a] -> [a] -> Bool
- allSame :: Eq a => [a] -> Bool
- anySame :: Eq a => [a] -> Bool
- dropEnd :: Int -> [a] -> [a]
- takeEnd :: Int -> [a] -> [a]
- breakEnd :: (a -> Bool) -> [a] -> ([a], [a])
- spanEnd :: (a -> Bool) -> [a] -> ([a], [a])
- dropWhileEnd :: (a -> Bool) -> [a] -> [a]
- dropWhileEnd' :: (a -> Bool) -> [a] -> [a]
- takeWhileEnd :: (a -> Bool) -> [a] -> [a]
- stripSuffix :: Eq a => [a] -> [a] -> Maybe [a]
- concatUnzip :: [([a], [b])] -> ([a], [b])
- concatUnzip3 :: [([a], [b], [c])] -> ([a], [b], [c])
- merge :: Ord a => [a] -> [a] -> [a]
- mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
- replace :: Eq a => [a] -> [a] -> [a] -> [a]
- wordsBy :: (a -> Bool) -> [a] -> [[a]]
- linesBy :: (a -> Bool) -> [a] -> [[a]]
- firstJust :: (a -> Maybe b) -> [a] -> Maybe b
- breakOn :: Eq a => [a] -> [a] -> ([a], [a])
- breakOnEnd :: Eq a => [a] -> [a] -> ([a], [a])
- splitOn :: Eq a => [a] -> [a] -> [[a]]
- split :: (a -> Bool) -> [a] -> [[a]]
- chunksOf :: Int -> [a] -> [[a]]
Documentation
lower :: String -> StringSource
Documentation about lowercase
lower "This is A TEST" == "this is a test" lower "" == ""
dropAround :: (a -> Bool) -> [a] -> [a]Source
groupSortOn :: Ord a => (k -> a) -> [(k, v)] -> [(k, [v])]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
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
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]
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
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') "" == [""]