Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- (++) :: [a] -> [a] -> [a]
- (\\) :: Eq a => [a] -> [a] -> [a]
- allSame :: Eq a => [a] -> Bool
- anySame :: Eq a => [a] -> Bool
- break :: (a -> Bool) -> [a] -> ([a], [a])
- breakOn :: Eq a => [a] -> [a] -> ([a], [a])
- breakOnEnd :: Eq a => [a] -> [a] -> ([a], [a])
- breakEnd :: (a -> Bool) -> [a] -> ([a], [a])
- chop :: ([a] -> (b, [a])) -> [a] -> [b]
- cons :: a -> [a] -> [a]
- cycle :: [a] -> [a]
- delete :: Eq a => a -> [a] -> [a]
- deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a]
- deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- disjoint :: Eq a => [a] -> [a] -> Bool
- divvy :: Int -> Int -> [a] -> [[a]]
- drop :: Int -> [a] -> [a]
- dropEnd :: Int -> [a] -> [a]
- dropPrefix :: Eq a => [a] -> [a] -> [a]
- dropSuffix :: Eq a => [a] -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- dropWhileEnd :: (a -> Bool) -> [a] -> [a]
- elemIndex :: Eq a => a -> [a] -> Maybe Int
- elemIndices :: Eq a => a -> [a] -> [Int]
- endBy :: Eq a => [a] -> [a] -> [[a]]
- filter :: (a -> Bool) -> [a] -> [a]
- findIndex :: (a -> Bool) -> [a] -> Maybe Int
- findIndices :: (a -> Bool) -> [a] -> [Int]
- foldl1May' :: (a -> a -> a) -> [a] -> Maybe a
- foldr1May :: (a -> a -> a) -> [a] -> Maybe a
- genericDrop :: Integral i => i -> [a] -> [a]
- genericIndex :: Integral i => [a] -> i -> a
- genericLength :: Num i => [a] -> i
- genericReplicate :: Integral i => i -> a -> [a]
- genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
- genericTake :: Integral i => i -> [a] -> [a]
- group :: Eq a => [a] -> [[a]]
- groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
- groupOn :: Eq b => (a -> b) -> [a] -> [[a]]
- groupSort :: Ord k => [(k, v)] -> [(k, [v])]
- groupSortBy :: (a -> a -> Ordering) -> [a] -> [[a]]
- groupSortOn :: Ord b => (a -> b) -> [a] -> [[a]]
- iall :: (Int -> a -> Bool) -> [a] -> Bool
- iany :: (Int -> a -> Bool) -> [a] -> Bool
- iconcatMap :: (Int -> a -> [b]) -> [a] -> [b]
- idropWhile :: (Int -> a -> Bool) -> [a] -> [a]
- ifilter :: (Int -> a -> Bool) -> [a] -> [a]
- ifind :: (Int -> a -> Bool) -> [a] -> Maybe (Int, a)
- ifindIndex :: (Int -> a -> Bool) -> [a] -> Maybe Int
- ifindIndices :: (Int -> a -> Bool) -> [a] -> [Int]
- ifoldMap :: Monoid m => (Int -> a -> m) -> [a] -> m
- ifoldl' :: (b -> Int -> a -> b) -> b -> [a] -> b
- ifoldlM :: Monad m => (b -> Int -> a -> m b) -> b -> [a] -> m b
- ifoldr :: (Int -> a -> b -> b) -> b -> [a] -> b
- ifoldrM :: Monad m => (Int -> a -> b -> m b) -> b -> [a] -> m b
- ifor :: Applicative m => [a] -> (Int -> a -> m b) -> m [b]
- ifor_ :: Applicative m => [a] -> (Int -> a -> m b) -> m ()
- imap :: (Int -> a -> b) -> [a] -> [b]
- imapAccumL :: (acc -> Int -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
- imapAccumR :: (acc -> Int -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
- inits :: [a] -> [[a]]
- insert :: Ord a => a -> [a] -> [a]
- insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
- intercalate :: [a] -> [[a]] -> [a]
- intersect :: Eq a => [a] -> [a] -> [a]
- intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- intersperse :: a -> [a] -> [a]
- ipartition :: (Int -> a -> Bool) -> [a] -> ([a], [a])
- ireplicateM :: Applicative m => Int -> (Int -> m a) -> m [a]
- ireplicateM_ :: Monad m => Int -> (Int -> m a) -> m ()
- isInfixOf :: Eq a => [a] -> [a] -> Bool
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- isSubsequenceOf :: Eq a => [a] -> [a] -> Bool
- isSuffixOf :: Eq a => [a] -> [a] -> Bool
- itakeWhile :: (Int -> a -> Bool) -> [a] -> [a]
- iterate :: (a -> a) -> a -> [a]
- itraverse :: Applicative m => (Int -> a -> m b) -> [a] -> m [b]
- itraverse_ :: Applicative m => (Int -> a -> m b) -> [a] -> m ()
- iterate' :: (a -> a) -> a -> [a]
- izipWith :: (Int -> a -> b -> c) -> [a] -> [b] -> [c]
- izipWith3 :: (Int -> a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- izipWith4 :: (Int -> a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
- izipWith5 :: (Int -> a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
- izipWith6 :: (Int -> a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
- izipWith7 :: (Int -> a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- map :: (a -> b) -> [a] -> [b]
- maximumByMay :: (a -> a -> Ordering) -> [a] -> Maybe a
- maximumMay :: Ord a => [a] -> Maybe a
- minimumByMay :: (a -> a -> Ordering) -> [a] -> Maybe a
- minimumMay :: Ord a => [a] -> Maybe a
- nub :: Eq a => [a] -> [a]
- nubBy :: (a -> a -> Bool) -> [a] -> [a]
- nubOn :: Eq b => (a -> b) -> [a] -> [a]
- nubOrd :: Ord a => [a] -> [a]
- nubOrdBy :: (a -> a -> Ordering) -> [a] -> [a]
- nubOrdOn :: Ord b => (a -> b) -> [a] -> [a]
- nubSort :: Ord a => [a] -> [a]
- nubSortBy :: (a -> a -> Ordering) -> [a] -> [a]
- nubSortOn :: Ord b => (a -> b) -> [a] -> [a]
- partition :: (a -> Bool) -> [a] -> ([a], [a])
- permutations :: [a] -> [[a]]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- reverse :: [a] -> [a]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- scanl' :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- spanEnd :: (a -> Bool) -> [a] -> ([a], [a])
- split :: (a -> Bool) -> [a] -> [[a]]
- splitAt :: Int -> [a] -> ([a], [a])
- splitAtEnd :: Int -> [a] -> ([a], [a])
- splitOn :: Eq a => [a] -> [a] -> [[a]]
- snoc :: [a] -> a -> [a]
- stripInfix :: Eq a => [a] -> [a] -> Maybe ([a], [a])
- stripInfixEnd :: Eq a => [a] -> [a] -> Maybe ([a], [a])
- stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
- stripSuffix :: Eq a => [a] -> [a] -> Maybe [a]
- subsequences :: [a] -> [[a]]
- tails :: [a] -> [[a]]
- take :: Int -> [a] -> [a]
- takeEnd :: Int -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- takeWhileEnd :: (a -> Bool) -> [a] -> [a]
- transpose :: [[a]] -> [[a]]
- uncons :: [a] -> Maybe (a, [a])
- unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
- union :: Eq a => [a] -> [a] -> [a]
- unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- unsnoc :: [a] -> Maybe ([a], a)
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])
- unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
- unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
- unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
- wordsBy :: (a -> Bool) -> [a] -> [[a]]
- zip :: [a] -> [b] -> [(a, b)]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
- zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
- zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
- zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
- zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
- data Diff a
- getDiff :: Eq t => [t] -> [t] -> [Diff t]
- getDiffBy :: (t -> t -> Bool) -> [t] -> [t] -> [Diff t]
- getGroupedDiff :: Eq t => [t] -> [t] -> [Diff [t]]
- getGroupedDiffBy :: (t -> t -> Bool) -> [t] -> [t] -> [Diff [t]]
- type String = [Char]
- words :: String -> [String]
- unwords :: [String] -> String
- lines :: String -> [String]
- unlines :: [String] -> String
- lower :: String -> String
- upper :: String -> String
- trim :: String -> String
- trimStart :: String -> String
- trimEnd :: String -> String
- showString :: String -> ShowS
- lexDigits :: ReadS String
- class IsString a where
- prefixed :: Eq a => [a] -> Prism' [a] [a]
- suffixed :: Eq a => [a] -> Prism' [a] [a]
List
(++) :: [a] -> [a] -> [a] infixr 5 #
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
(\\) :: Eq a => [a] -> [a] -> [a] infix 5 #
The \\
function is list difference (non-associative).
In the result of xs
\\
ys
, the first occurrence of each element of
ys
in turn (if any) has been removed from xs
. Thus
(xs ++ ys) \\ xs == ys.
>>>
"Hello World!" \\ "ell W"
"Hoorld!"
It is a special case of deleteFirstsBy
, which allows the programmer
to supply their own equality test.
allSame :: Eq a => [a] -> Bool #
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] -> Bool #
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)
break :: (a -> Bool) -> [a] -> ([a], [a]) #
break
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
do not satisfy p
and second element is the remainder of the list:
break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) break (< 9) [1,2,3] == ([],[1,2,3]) break (> 9) [1,2,3] == ([1,2,3],[])
breakOn :: Eq a => [a] -> [a] -> ([a], [a]) #
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.
If you want the remainder without the match, use stripInfix
.
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]) #
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")
breakEnd :: (a -> Bool) -> [a] -> ([a], [a]) #
Break, but from the end.
breakEnd isLower "youRE" == ("you","RE") breakEnd isLower "youre" == ("youre","") breakEnd isLower "YOURE" == ("","YOURE") \f xs -> breakEnd (not . f) xs == spanEnd f xs
chop :: ([a] -> (b, [a])) -> [a] -> [b] #
A useful recursion pattern for processing a list to produce a new list, often used for "chopping" up the input list. Typically chop is called with some function that will consume an initial prefix of the list and produce a value and the rest of the list.
For example, many common Prelude functions can be implemented in
terms of chop
:
group :: (Eq a) => [a] -> [[a]] group = chop (\ xs@(x:_) -> span (==x) xs) words :: String -> [String] words = filter (not . null) . chop (span (not . isSpace) . dropWhile isSpace)
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)
cycle
ties a finite list into a circular one, or equivalently,
the infinite repetition of the original list. It is the identity
on infinite lists.
deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] #
The deleteFirstsBy
function takes a predicate and two lists and
returns the first list with the first occurrence of each element of
the second list removed.
disjoint :: Eq a => [a] -> [a] -> Bool #
Are two lists disjoint, with no elements in common.
disjoint [1,2,3] [4,5] == True disjoint [1,2,3] [4,1] == False
divvy :: Int -> Int -> [a] -> [[a]] #
Divides up an input list into a set of sublists, according to n
and m
input specifications you provide. Each sublist will have n
items, and the
start of each sublist will be offset by m
items from the previous one.
divvy 5 5 [1..20] == [[1,2,3,4,5],[6,7,8,9,10],[11,12,13,14,15],[16,17,18,19,20]]
In the case where a source list's trailing elements do no fill an entire sublist, those trailing elements will be dropped.
divvy 5 2 [1..10] == [[1,2,3,4,5],[3,4,5,6,7],[5,6,7,8,9]]
As an example, you can generate a moving average over a list of prices:
type Prices = [Float] type AveragePrices = [Float] average :: [Float] -> Float average xs = sum xs / (fromIntegral $ length xs) simpleMovingAverage :: Prices -> AveragePrices simpleMovingAverage priceList = map average divvyedPrices where divvyedPrices = divvy 20 1 priceList
drop
n xs
returns the suffix of xs
after the first n
elements, or []
if n >
:length
xs
drop 6 "Hello World!" == "World!" drop 3 [1,2,3,4,5] == [4,5] drop 3 [1,2] == [] drop 3 [] == [] drop (-1) [1,2] == [1,2] drop 0 [1,2] == [1,2]
It is an instance of the more general genericDrop
,
in which n
may be of any integral type.
dropEnd :: Int -> [a] -> [a] #
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..]
dropPrefix :: Eq a => [a] -> [a] -> [a] #
Drops the given prefix from a list. It returns the original sequence if the sequence doesn't start with the given prefix.
dropPrefix "Mr. " "Mr. Men" == "Men" dropPrefix "Mr. " "Dr. Men" == "Dr. Men"
dropSuffix :: Eq a => [a] -> [a] -> [a] #
Drops the given suffix from a list. It returns the original sequence if the sequence doesn't end with the given suffix.
dropSuffix "!" "Hello World!" == "Hello World" dropSuffix "!" "Hello World!!" == "Hello World!" dropSuffix "!" "Hello World." == "Hello World."
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
Since: base-4.5.0.0
elemIndices :: Eq a => a -> [a] -> [Int] #
The elemIndices
function extends elemIndex
, by returning the
indices of all elements equal to the query element, in ascending order.
>>>
elemIndices 'o' "Hello World"
[4,7]
endBy :: Eq a => [a] -> [a] -> [[a]] #
Split into chunks terminated by the given subsequence.
Equivalent to
. For example:split
. dropFinalBlank
. dropDelims
. onSublist
endBy ";" "foo;bar;baz;" == ["foo","bar","baz"]
Note also that the lines
function from Data.List is equivalent
to
.endBy
"\n"
filter :: (a -> Bool) -> [a] -> [a] #
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
findIndices :: (a -> Bool) -> [a] -> [Int] #
The findIndices
function extends findIndex
, by returning the
indices of all elements satisfying the predicate, in ascending order.
>>>
findIndices (`elem` "aeiou") "Hello World!"
[1,4,7]
foldl1May' :: (a -> a -> a) -> [a] -> Maybe a #
genericDrop :: Integral i => i -> [a] -> [a] #
The genericDrop
function is an overloaded version of drop
, which
accepts any Integral
value as the number of elements to drop.
genericIndex :: Integral i => [a] -> i -> a #
The genericIndex
function is an overloaded version of !!
, which
accepts any Integral
value as the index.
genericLength :: Num i => [a] -> i #
The genericLength
function is an overloaded version of length
. In
particular, instead of returning an Int
, it returns any type which is
an instance of Num
. It is, however, less efficient than length
.
genericReplicate :: Integral i => i -> a -> [a] #
The genericReplicate
function is an overloaded version of replicate
,
which accepts any Integral
value as the number of repetitions to make.
genericSplitAt :: Integral i => i -> [a] -> ([a], [a]) #
The genericSplitAt
function is an overloaded version of splitAt
, which
accepts any Integral
value as the position at which to split.
genericTake :: Integral i => i -> [a] -> [a] #
The genericTake
function is an overloaded version of take
, which
accepts any Integral
value as the number of elements to take.
group :: Eq a => [a] -> [[a]] #
The group
function takes a list and returns a list of lists such
that the concatenation of the result is equal to the argument. Moreover,
each sublist in the result contains only equal elements. For example,
>>>
group "Mississippi"
["M","i","ss","i","ss","i","pp","i"]
It is a special case of groupBy
, which allows the programmer to supply
their own equality test.
groupOn :: Eq b => (a -> b) -> [a] -> [[a]] #
A version of group
where the equality is done on some extracted value.
groupSortBy :: (a -> a -> Ordering) -> [a] -> [[a]] #
groupSortOn :: Ord b => (a -> b) -> [a] -> [[a]] #
iconcatMap :: (Int -> a -> [b]) -> [a] -> [b] #
idropWhile :: (Int -> a -> Bool) -> [a] -> [a] #
ifindIndices :: (Int -> a -> Bool) -> [a] -> [Int] #
ifor :: Applicative m => [a] -> (Int -> a -> m b) -> m [b] #
ifor_ :: Applicative m => [a] -> (Int -> a -> m b) -> m () #
Subject to fusion.
imapAccumL :: (acc -> Int -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) #
imapAccumR :: (acc -> Int -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) #
insert :: Ord a => a -> [a] -> [a] #
The insert
function takes an element and a list and inserts the
element into the list at the first position where it is less
than or equal to the next element. In particular, if the list
is sorted before the call, the result will also be sorted.
It is a special case of insertBy
, which allows the programmer to
supply their own comparison function.
>>>
insert 4 [1,2,3,5,6,7]
[1,2,3,4,5,6,7]
intercalate :: [a] -> [[a]] -> [a] #
intercalate
xs xss
is equivalent to (
.
It inserts the list concat
(intersperse
xs xss))xs
in between the lists in xss
and concatenates the
result.
>>>
intercalate ", " ["Lorem", "ipsum", "dolor"]
"Lorem, ipsum, dolor"
intersect :: Eq a => [a] -> [a] -> [a] #
The intersect
function takes the list intersection of two lists.
For example,
>>>
[1,2,3,4] `intersect` [2,4,6,8]
[2,4]
If the first list contains duplicates, so will the result.
>>>
[1,2,2,3,4] `intersect` [6,4,4,2]
[2,2,4]
It is a special case of intersectBy
, which allows the programmer to
supply their own equality test. If the element is found in both the first
and the second list, the element from the first list will be used.
intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] #
The intersectBy
function is the non-overloaded version of intersect
.
intersperse :: a -> [a] -> [a] #
The intersperse
function takes an element and a list and
`intersperses' that element between the elements of the list.
For example,
>>>
intersperse ',' "abcde"
"a,b,c,d,e"
ipartition :: (Int -> a -> Bool) -> [a] -> ([a], [a]) #
ireplicateM :: Applicative m => Int -> (Int -> m a) -> m [a] #
Perform a given action n
times. Behaves like for_ [0..n-1]
, but avoids space leaks.
If you want more complicated loops (e.g. counting downwards), consider the loop package.
ireplicateM_ :: Monad m => Int -> (Int -> m a) -> m () #
NB. This function intentionally uses Monad
even though Applicative
is enough. That's because the transformers
package didn't have an optimized definition of (*>
) for StateT
prior to 0.5.3.0, so for a common case of StateT
this function would be 40 times slower with the Applicative
constraint.
isPrefixOf :: Eq a => [a] -> [a] -> Bool #
The isPrefixOf
function takes two lists and returns True
iff the first list is a prefix of the second.
>>>
"Hello" `isPrefixOf` "Hello World!"
True
>>>
"Hello" `isPrefixOf` "Wello Horld!"
False
isSubsequenceOf :: Eq a => [a] -> [a] -> Bool #
The isSubsequenceOf
function takes two lists and returns True
if all
the elements of the first list occur, in order, in the second. The
elements do not have to occur consecutively.
is equivalent to isSubsequenceOf
x y
.elem
x (subsequences
y)
Examples
>>>
isSubsequenceOf "GHC" "The Glorious Haskell Compiler"
True>>>
isSubsequenceOf ['a','d'..'z'] ['a'..'z']
True>>>
isSubsequenceOf [1..10] [10,9..0]
False
Since: base-4.8.0.0
isSuffixOf :: Eq a => [a] -> [a] -> Bool #
The isSuffixOf
function takes two lists and returns True
iff
the first list is a suffix of the second. The second list must be
finite.
>>>
"ld!" `isSuffixOf` "Hello World!"
True
>>>
"World" `isSuffixOf` "Hello World!"
False
itakeWhile :: (Int -> a -> Bool) -> [a] -> [a] #
itraverse :: Applicative m => (Int -> a -> m b) -> [a] -> m [b] #
itraverse_ :: Applicative m => (Int -> a -> m b) -> [a] -> m () #
Subject to fusion.
iterate' :: (a -> a) -> a -> [a] #
'iterate\'' is the strict version of iterate
.
It ensures that the result of each application of force to weak head normal form before proceeding.
izipWith6 :: (Int -> a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] #
izipWith7 :: (Int -> a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] #
lookup :: Eq a => a -> [(a, b)] -> Maybe b #
lookup
key assocs
looks up a key in an association list.
map :: (a -> b) -> [a] -> [b] #
map
f xs
is the list obtained by applying f
to each element
of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
maximumByMay :: (a -> a -> Ordering) -> [a] -> Maybe a #
maximumMay :: Ord a => [a] -> Maybe a #
minimumByMay :: (a -> a -> Ordering) -> [a] -> Maybe a #
minimumMay :: Ord a => [a] -> Maybe a #
O(n^2). The nub
function removes duplicate elements from a list.
In particular, it keeps only the first occurrence of each element.
(The name nub
means `essence'.)
It is a special case of nubBy
, which allows the programmer to supply
their own equality test.
>>>
nub [1,2,3,4,3,2,1,2,4,3,5]
[1,2,3,4,5]
nubOrd :: Ord a => [a] -> [a] #
O(n log n). The nubOrd
function removes duplicate elements from a list.
In particular, it keeps only the first occurrence of each element.
Unlike the standard nub
operator, this version requires an Ord
instance
and consequently runs asymptotically faster.
nubOrd "this is a test" == "this ae" nubOrd (take 4 ("this" ++ undefined)) == "this" \xs -> nubOrd xs == nub xs
nubOrdBy :: (a -> a -> Ordering) -> [a] -> [a] #
A version of nubOrd
with a custom predicate.
nubOrdBy (compare `on` length) ["a","test","of","this"] == ["a","test","of"]
nubOrdOn :: Ord b => (a -> b) -> [a] -> [a] #
A version of nubOrd
which operates on a portion of the value.
nubOrdOn length ["a","test","of","this"] == ["a","test","of"]
nubSort :: Ord a => [a] -> [a] #
O(n log n). The nubSort
function sorts and removes duplicate elements from a list.
In particular, it keeps only the first occurrence of each element.
nubSort "this is a test" == " aehist" \xs -> nubSort xs == nub (sort xs)
nubSortBy :: (a -> a -> Ordering) -> [a] -> [a] #
A version of nubSort
with a custom predicate.
nubSortBy (compare `on` length) ["a","test","of","this"] == ["a","of","test"]
nubSortOn :: Ord b => (a -> b) -> [a] -> [a] #
A version of nubSort
which operates on a portion of the value.
nubSortOn length ["a","test","of","this"] == ["a","of","test"]
partition :: (a -> Bool) -> [a] -> ([a], [a]) #
The partition
function takes a predicate a list and returns
the pair of lists of elements which do and do not satisfy the
predicate, respectively; i.e.,
partition p xs == (filter p xs, filter (not . p) xs)
>>>
partition (`elem` "aeiou") "Hello World!"
("eoo","Hll Wrld!")
permutations :: [a] -> [[a]] #
The permutations
function returns the list of all permutations of the argument.
>>>
permutations "abc"
["abc","bac","cba","bca","cab","acb"]
replicate :: Int -> a -> [a] #
replicate
n x
is a list of length n
with x
the value of
every element.
It is an instance of the more general genericReplicate
,
in which n
may be of any integral type.
The sort
function implements a stable sorting algorithm.
It is a special case of sortBy
, which allows the programmer to supply
their own comparison function.
Elements are arranged from from lowest to highest, keeping duplicates in the order they appeared in the input.
>>>
sort [1,6,4,3,2,5]
[1,2,3,4,5,6]
sortOn :: Ord b => (a -> b) -> [a] -> [a] #
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.
Elements are arranged from from lowest to highest, keeping duplicates in the order they appeared in the input.
>>>
sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]
Since: base-4.8.0.0
span :: (a -> Bool) -> [a] -> ([a], [a]) #
span
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
satisfy p
and second element is the remainder of the list:
span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) span (< 9) [1,2,3] == ([1,2,3],[]) span (< 0) [1,2,3] == ([],[1,2,3])
spanEnd :: (a -> Bool) -> [a] -> ([a], [a]) #
Span, but from the end.
spanEnd isUpper "youRE" == ("you","RE") spanEnd (not . isSpace) "x y z" == ("x y ","z") \f xs -> uncurry (++) (spanEnd f xs) == xs \f xs -> spanEnd f xs == swap (both reverse (span f (reverse xs)))
split :: (a -> Bool) -> [a] -> [[a]] #
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"]
splitAt :: Int -> [a] -> ([a], [a]) #
splitAt
n xs
returns a tuple where first element is xs
prefix of
length n
and second element is the remainder of the list:
splitAt 6 "Hello World!" == ("Hello ","World!") splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) splitAt 1 [1,2,3] == ([1],[2,3]) splitAt 3 [1,2,3] == ([1,2,3],[]) splitAt 4 [1,2,3] == ([1,2,3],[]) splitAt 0 [1,2,3] == ([],[1,2,3]) splitAt (-1) [1,2,3] == ([],[1,2,3])
It is equivalent to (
when take
n xs, drop
n xs)n
is not _|_
(splitAt _|_ xs = _|_
).
splitAt
is an instance of the more general genericSplitAt
,
in which n
may be of any integral type.
splitAtEnd :: Int -> [a] -> ([a], [a]) #
returns a split where the second element tries to
contain splitAtEnd
n xsn
elements.
splitAtEnd 3 "hello" == ("he","llo") splitAtEnd 3 "he" == ("", "he") \i xs -> uncurry (++) (splitAt i xs) == xs \i xs -> splitAtEnd i xs == (dropEnd i xs, takeEnd i xs)
splitOn :: Eq a => [a] -> [a] -> [[a]] #
Split on the given sublist. Equivalent to
. For example:split
. dropDelims
. onSublist
splitOn ".." "a..b...c....d.." == ["a","b",".c","","d",""]
In some parsing combinator frameworks this is also known as
sepBy
.
Note that this is the right inverse of the intercalate
function
from Data.List, that is,
intercalate x . splitOn x === id
is the identity on
certain lists, but it is tricky to state the precise conditions
under which this holds. (For example, it is not enough to say
that splitOn
x . intercalate
xx
does not occur in any elements of the input list.
Working out why is left as an exercise for the reader.)
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)
stripInfix :: Eq a => [a] -> [a] -> Maybe ([a], [a]) #
Return the the string before and after the search string,
or Nothing
if the search string is not present.
Examples:
stripInfix "::" "a::b::c" == Just ("a", "b::c") stripInfix "/" "foobar" == Nothing
stripInfixEnd :: Eq a => [a] -> [a] -> Maybe ([a], [a]) #
Similar to stripInfix
, but searches from the end of the
string.
stripInfixEnd "::" "a::b::c" == Just ("a::b", "c")
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] #
The stripPrefix
function drops the given prefix from a list.
It returns Nothing
if the list did not start with the prefix
given, or Just
the list after the prefix, if it does.
>>>
stripPrefix "foo" "foobar"
Just "bar"
>>>
stripPrefix "foo" "foo"
Just ""
>>>
stripPrefix "foo" "barfoo"
Nothing
>>>
stripPrefix "foo" "barfoobaz"
Nothing
stripSuffix :: Eq a => [a] -> [a] -> Maybe [a] #
Return the prefix of the second list if its suffix matches the entire first list.
Examples:
stripSuffix "bar" "foobar" == Just "foo" stripSuffix "" "baz" == Just "baz" stripSuffix "foo" "quux" == Nothing
subsequences :: [a] -> [[a]] #
The subsequences
function returns the list of all subsequences of the argument.
>>>
subsequences "abc"
["","a","b","ab","c","ac","bc","abc"]
take
n
, applied to a list xs
, returns the prefix of xs
of length n
, or xs
itself if n >
:length
xs
take 5 "Hello World!" == "Hello" take 3 [1,2,3,4,5] == [1,2,3] take 3 [1,2] == [1,2] take 3 [] == [] take (-1) [1,2] == [] take 0 [1,2] == []
It is an instance of the more general genericTake
,
in which n
may be of any integral type.
takeEnd :: Int -> [a] -> [a] #
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)
takeWhile :: (a -> Bool) -> [a] -> [a] #
takeWhile
, applied to a predicate p
and a list xs
, returns the
longest prefix (possibly empty) of xs
of elements that satisfy p
:
takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] takeWhile (< 9) [1,2,3] == [1,2,3] takeWhile (< 0) [1,2,3] == []
takeWhileEnd :: (a -> Bool) -> [a] -> [a] #
A version of takeWhile
operating from the end.
takeWhileEnd even [2,3,4,6] == [4,6]
The transpose
function transposes the rows and columns of its argument.
For example,
>>>
transpose [[1,2,3],[4,5,6]]
[[1,4],[2,5],[3,6]]
If some of the rows are shorter than the following rows, their elements are skipped:
>>>
transpose [[10,11],[20],[],[30,31,32]]
[[10,20,30],[11,31],[32]]
unfoldr :: (b -> Maybe (a, b)) -> b -> [a] #
The unfoldr
function is a `dual' to foldr
: while foldr
reduces a list to a summary value, unfoldr
builds a list from
a seed value. The function takes the element and returns Nothing
if it is done producing the list or returns Just
(a,b)
, in which
case, a
is a prepended to the list and b
is used as the next
element in a recursive call. For example,
iterate f == unfoldr (\x -> Just (x, f x))
In some cases, unfoldr
can undo a foldr
operation:
unfoldr f' (foldr f z xs) == xs
if the following holds:
f' (f x y) = Just (x,y) f' z = Nothing
A simple use of unfoldr:
>>>
unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
[10,9,8,7,6,5,4,3,2,1]
union :: Eq a => [a] -> [a] -> [a] #
The union
function returns the list union of the two lists.
For example,
>>>
"dog" `union` "cow"
"dogcw"
Duplicates, and elements of the first list, are removed from the
the second list, but if the first list contains duplicates, so will
the result.
It is a special case of unionBy
, which allows the programmer to supply
their own equality test.
unzip :: [(a, b)] -> ([a], [b]) #
unzip
transforms a list of pairs into a list of first components
and a list of second components.
wordsBy :: (a -> Bool) -> [a] -> [[a]] #
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
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] #
Diff algorithm
getGroupedDiff :: Eq t => [t] -> [t] -> [Diff [t]] #
Takes two lists and returns a list of differences between them, grouped
into chunks. This is getGroupedDiffBy
with ==
used as predicate.
getGroupedDiffBy :: (t -> t -> Bool) -> [t] -> [t] -> [Diff [t]] #
String
words
breaks a string up into a list of words, which were delimited
by white space.
>>>
words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
lines
breaks a string up into a list of strings at newline
characters. The resulting strings do not contain newlines.
Note that after splitting the string at newline characters, the last part of the string is considered a line even if it doesn't end with a newline. For example,
>>>
lines ""
[]
>>>
lines "\n"
[""]
>>>
lines "one"
["one"]
>>>
lines "one\n"
["one"]
>>>
lines "one\n\n"
["one",""]
>>>
lines "one\ntwo"
["one","two"]
>>>
lines "one\ntwo\n"
["one","two"]
Thus
contains at least as many elements as newlines in lines
ss
.
Convert a string to lower case.
lower "This is A TEST" == "this is a test" lower "" == ""
Convert a string to upper case.
upper "This is A TEST" == "THIS IS A TEST" upper "" == ""
showString :: String -> ShowS #
utility function converting a String
to a show function that
simply prepends the string unchanged.
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a #
Instances
IsString ByteString | |
Defined in Data.ByteString.Internal fromString :: String -> ByteString # | |
IsString ByteString | |
Defined in Data.ByteString.Lazy.Internal fromString :: String -> ByteString # | |
IsString Builder | |
Defined in Data.Text.Internal.Builder fromString :: String -> Builder # | |
IsString Value | |
Defined in Data.Aeson.Types.Internal fromString :: String -> Value # | |
IsString ShortByteString | |
Defined in Data.ByteString.Short.Internal fromString :: String -> ShortByteString # | |
IsString Doc | |
Defined in Text.PrettyPrint.HughesPJ fromString :: String -> Doc # | |
IsString ShortText | Note: Surrogate pairs ( This matches the behaviour of |
Defined in Data.Text.Short.Internal fromString :: String -> ShortText # | |
a ~ Char => IsString [a] |
Since: base-2.1 |
Defined in Data.String fromString :: String -> [a] # | |
IsString a => IsString (Identity a) | |
Defined in Data.String fromString :: String -> Identity a # | |
(IsString s, FoldCase s) => IsString (CI s) | |
Defined in Data.CaseInsensitive.Internal fromString :: String -> CI s # | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal fromString :: String -> Seq a # | |
a ~ Char => IsString (DList a) | |
Defined in Data.DList fromString :: String -> DList a # | |
(IsString a, Hashable a) => IsString (Hashed a) | |
Defined in Data.Hashable.Class fromString :: String -> Hashed a # | |
IsString (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ fromString :: String -> Doc a # | |
IsString (Doc ann) |
This instance uses the |
Defined in Data.Text.Prettyprint.Doc.Internal fromString :: String -> Doc ann # | |
(streamType ~ STInput, res ~ ()) => IsString (StreamSpec streamType res) | This instance uses Since: typed-process-0.1.0.0 |
Defined in System.Process.Typed fromString :: String -> StreamSpec streamType res # | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b # | |
IsString a => IsString (Tagged s a) | |
Defined in Data.Tagged fromString :: String -> Tagged s a # | |
(stdin ~ (), stdout ~ (), stderr ~ ()) => IsString (ProcessConfig stdin stdout stderr) | |
Defined in System.Process.Typed fromString :: String -> ProcessConfig stdin stdout stderr # | |
(IsString t, Eq t, a ~ t) => IsString (Prod r e t a) | String literals can be interpreted as
|
Defined in Text.Earley.Grammar fromString :: String -> Prod r e t a # | |
(a ~ Tokens s, IsString a, Eq a, Stream s, Ord e) => IsString (ParsecT e s m a) | Since: megaparsec-6.3.0 |
Defined in Text.Megaparsec.Internal fromString :: String -> ParsecT e s m a # |