Movatterモバイル変換


[0]ホーム

URL:


base-4.12.0.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

GHC.OldList

Contents

Description

This legacy module provides access to the list-specialised operations ofData.List. This module may go away again in future GHC versions and is provided as transitional tool to access some of the list-specialised operations that had to be generalised due to the implementation of theFoldable/Traversable-in-Prelude Proposal (FTP).

If the operations needed are available inGHC.List, it's recommended to avoid importing this module and useGHC.List instead for now.

Since: 4.8.0.0

Synopsis

Basic functions

(++) :: [a] -> [a] -> [a]infixr 5Source#

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.

head :: [a] -> aSource#

Extract the first element of a list, which must be non-empty.

last :: [a] -> aSource#

Extract the last element of a list, which must be finite and non-empty.

tail :: [a] -> [a]Source#

Extract the elements after the head of a list, which must be non-empty.

init :: [a] -> [a]Source#

Return all the elements of a list except the last one. The list must be non-empty.

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

Decompose a list into its head and tail. If the list is empty, returnsNothing. If the list is non-empty, returnsJust (x, xs), wherex is the head of the list andxs its tail.

Since: 4.8.0.0

null :: [a] ->BoolSource#

Test whether a list is empty.

length :: [a] ->IntSource#

O(n).length returns the length of a finite list as anInt. It is an instance of the more generalgenericLength, the result type of which may be any kind of number.

List transformations

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

mapf xs is the list obtained by applyingf to each element ofxs, i.e.,

map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]map f [x1, x2, ...] == [f x1, f x2, ...]

reverse :: [a] -> [a]Source#

reversexs returns the elements ofxs in reverse order.xs must be finite.

intersperse :: a -> [a] -> [a]Source#

Theintersperse 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"

intercalate :: [a] -> [[a]] -> [a]Source#

intercalatexs xss is equivalent to(concat (intersperse xs xss)). It inserts the listxs in between the lists inxss and concatenates the result.

>>>intercalate ", " ["Lorem", "ipsum", "dolor"]"Lorem, ipsum, dolor"

transpose :: [[a]] -> [[a]]Source#

Thetranspose 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]]

subsequences :: [a] -> [[a]]Source#

Thesubsequences function returns the list of all subsequences of the argument.

>>>subsequences "abc"["","a","b","ab","c","ac","bc","abc"]

permutations :: [a] -> [[a]]Source#

Thepermutations function returns the list of all permutations of the argument.

>>>permutations "abc"["abc","bac","cba","bca","cab","acb"]

Reducing lists (folds)

foldl ::forall a b. (b -> a -> b) -> b -> [a] -> bSource#

foldl, applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

The list must be finite.

foldl' ::forall a b. (b -> a -> b) -> b -> [a] -> bSource#

A strict version offoldl.

foldl1 :: (a -> a -> a) -> [a] -> aSource#

foldl1 is a variant offoldl that has no starting value argument, and thus must be applied to non-empty lists.

foldl1' :: (a -> a -> a) -> [a] -> aSource#

A strict version offoldl1

foldr :: (a -> b -> b) -> b -> [a] -> bSource#

foldr, applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

foldr1 :: (a -> a -> a) -> [a] -> aSource#

foldr1 is a variant offoldr that has no starting value argument, and thus must be applied to non-empty lists.

Special folds

concat :: [[a]] -> [a]Source#

Concatenate a list of lists.

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

Map a function over a list and concatenate the results.

and :: [Bool] ->BoolSource#

and returns the conjunction of a Boolean list. For the result to beTrue, the list must be finite;False, however, results from aFalse value at a finite index of a finite or infinite list.

or :: [Bool] ->BoolSource#

or returns the disjunction of a Boolean list. For the result to beFalse, the list must be finite;True, however, results from aTrue value at a finite index of a finite or infinite list.

any :: (a ->Bool) -> [a] ->BoolSource#

Applied to a predicate and a list,any determines if any element of the list satisfies the predicate. For the result to beFalse, the list must be finite;True, however, results from aTrue value for the predicate applied to an element at a finite index of a finite or infinite list.

all :: (a ->Bool) -> [a] ->BoolSource#

Applied to a predicate and a list,all determines if all elements of the list satisfy the predicate. For the result to beTrue, the list must be finite;False, however, results from aFalse value for the predicate applied to an element at a finite index of a finite or infinite list.

sum ::Num a => [a] -> aSource#

Thesum function computes the sum of a finite list of numbers.

product ::Num a => [a] -> aSource#

Theproduct function computes the product of a finite list of numbers.

maximum ::Ord a => [a] -> aSource#

maximum returns the maximum value from a list, which must be non-empty, finite, and of an ordered type. It is a special case ofmaximumBy, which allows the programmer to supply their own comparison function.

minimum ::Ord a => [a] -> aSource#

minimum returns the minimum value from a list, which must be non-empty, finite, and of an ordered type. It is a special case ofminimumBy, which allows the programmer to supply their own comparison function.

Building lists

Scans

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

scanl is similar tofoldl, but returns a list of successive reduced values from the left:

scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]

Note that

last (scanl f z xs) == foldl f z xs.

scanl' :: (b -> a -> b) -> b -> [a] -> [b]Source#

A strictly accumulating version ofscanl

scanl1 :: (a -> a -> a) -> [a] -> [a]Source#

scanl1 is a variant ofscanl that has no starting value argument:

scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]

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

scanr is the right-to-left dual ofscanl. Note that

head (scanr f z xs) == foldr f z xs.

scanr1 :: (a -> a -> a) -> [a] -> [a]Source#

scanr1 is a variant ofscanr that has no starting value argument.

Accumulating maps

mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])Source#

ThemapAccumL function behaves like a combination ofmap andfoldl; it applies a function to each element of a list, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new list.

mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])Source#

ThemapAccumR function behaves like a combination ofmap andfoldr; it applies a function to each element of a list, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new list.

Infinite lists

iterate :: (a -> a) -> a -> [a]Source#

iteratef x returns an infinite list of repeated applications off tox:

iterate f x == [x, f x, f (f x), ...]

Note thatiterate is lazy, potentially leading to thunk build-up if the consumer doesn't force each iterate. See 'iterate\'' for a strict variant of this function.

iterate' :: (a -> a) -> a -> [a]Source#

'iterate\'' is the strict version ofiterate.

It ensures that the result of each application of force to weak head normal form before proceeding.

repeat :: a -> [a]Source#

repeatx is an infinite list, withx the value of every element.

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

replicaten x is a list of lengthn withx the value of every element. It is an instance of the more generalgenericReplicate, in whichn may be of any integral type.

cycle :: [a] -> [a]Source#

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.

Unfolding

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

Theunfoldr function is a `dual' tofoldr: whilefoldr reduces a list to a summary value,unfoldr builds a list from a seed value. The function takes the element and returnsNothing if it is done producing the list or returnsJust(a,b), in which case,a is a prepended to the list andb 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 afoldr 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]

Sublists

Extracting sublists

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

taken, applied to a listxs, returns the prefix ofxs of lengthn, orxs itself ifn >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 generalgenericTake, in whichn may be of any integral type.

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

dropn xs returns the suffix ofxs after the firstn elements, or[] ifn >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 generalgenericDrop, in whichn may be of any integral type.

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

splitAtn xs returns a tuple where first element isxs prefix of lengthn 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(take n xs,drop n xs) whenn is not_|_ (splitAt _|_ xs = _|_).splitAt is an instance of the more generalgenericSplitAt, in whichn may be of any integral type.

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

takeWhile, applied to a predicatep and a listxs, returns the longest prefix (possibly empty) ofxs of elements that satisfyp:

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

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

dropWhilep xs returns the suffix remaining aftertakeWhilep xs:

dropWhile (< 3) [1,2,3,4,5,1,2,3] == [3,4,5,1,2,3]dropWhile (< 9) [1,2,3] == []dropWhile (< 0) [1,2,3] == [1,2,3]

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

ThedropWhileEnd 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: 4.5.0.0

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

span, applied to a predicatep and a listxs, returns a tuple where first element is longest prefix (possibly empty) ofxs of elements that satisfyp 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])

spanp xs is equivalent to(takeWhile p xs,dropWhile p xs)

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

break, applied to a predicatep and a listxs, returns a tuple where first element is longest prefix (possibly empty) ofxs of elements thatdo not satisfyp 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],[])

breakp is equivalent tospan (not . p).

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

ThestripPrefix function drops the given prefix from a list. It returnsNothing if the list did not start with the prefix given, orJust 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

group ::Eq a => [a] -> [[a]]Source#

Thegroup 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 ofgroupBy, which allows the programmer to supply their own equality test.

inits :: [a] -> [[a]]Source#

Theinits function returns all initial segments of the argument, shortest first. For example,

>>>inits "abc"["","a","ab","abc"]

Note thatinits has the following strictness property:inits (xs ++ _|_) = inits xs ++ _|_

In particular,inits _|_ = [] : _|_

tails :: [a] -> [[a]]Source#

Thetails function returns all final segments of the argument, longest first. For example,

>>>tails "abc"["abc","bc","c",""]

Note thattails has the following strictness property:tails _|_ = _|_ : _|_

Predicates

isPrefixOf ::Eq a => [a] -> [a] ->BoolSource#

TheisPrefixOf function takes two lists and returnsTrue iff the first list is a prefix of the second.

>>>"Hello" `isPrefixOf` "Hello World!"True
>>>"Hello" `isPrefixOf` "Wello Horld!"False

isSuffixOf ::Eq a => [a] -> [a] ->BoolSource#

TheisSuffixOf function takes two lists and returnsTrue 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

isInfixOf ::Eq a => [a] -> [a] ->BoolSource#

TheisInfixOf function takes two lists and returnsTrue iff the first list is contained, wholly and intact, anywhere within the second.

>>>isInfixOf "Haskell" "I really like Haskell."True
>>>isInfixOf "Ial" "I really like Haskell."False

Searching lists

Searching by equality

elem ::Eq a => a -> [a] ->Boolinfix 4Source#

elem is the list membership predicate, usually written in infix form, e.g.,x `elem` xs. For the result to beFalse, the list must be finite;True, however, results from an element equal tox found at a finite index of a finite or infinite list.

notElem ::Eq a => a -> [a] ->Boolinfix 4Source#

notElem is the negation ofelem.

lookup ::Eq a => a -> [(a, b)] ->Maybe bSource#

lookupkey assocs looks up a key in an association list.

Searching with a predicate

find :: (a ->Bool) -> [a] ->Maybe aSource#

Thefind function takes a predicate and a list and returns the first element in the list matching the predicate, orNothing if there is no such element.

>>>find (> 4) [1..]Just 5
>>>find (< 0) [1..10]Nothing

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

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]

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

Thepartition 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!")

Indexing lists

These functions treat a listxs as a indexed collection, with indices ranging from 0 tolength xs - 1.

(!!) :: [a] ->Int -> ainfixl 9Source#

List index (subscript) operator, starting from 0. It is an instance of the more generalgenericIndex, which takes an index of any integral type.

elemIndex ::Eq a => a -> [a] ->MaybeIntSource#

TheelemIndex function returns the index of the first element in the given list which is equal (by==) to the query element, orNothing if there is no such element.

>>>elemIndex 4 [0..]Just 4

elemIndices ::Eq a => a -> [a] -> [Int]Source#

TheelemIndices function extendselemIndex, by returning the indices of all elements equal to the query element, in ascending order.

>>>elemIndices 'o' "Hello World"[4,7]

findIndex :: (a ->Bool) -> [a] ->MaybeIntSource#

ThefindIndex function takes a predicate and a list and returns the index of the first element in the list satisfying the predicate, orNothing if there is no such element.

>>>findIndex isSpace "Hello World!"Just 5

findIndices :: (a ->Bool) -> [a] -> [Int]Source#

ThefindIndices function extendsfindIndex, by returning the indices of all elements satisfying the predicate, in ascending order.

>>>findIndices (`elem` "aeiou") "Hello World!"[1,4,7]

Zipping and unzipping lists

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

zip takes two lists and returns a list of corresponding pairs.

zip [1, 2] ['a', 'b'] = [(1, 'a'), (2, 'b')]

If one input list is short, excess elements of the longer list are discarded:

zip [1] ['a', 'b'] = [(1, 'a')]zip [1, 2] ['a'] = [(1, 'a')]

zip is right-lazy:

zip [] _|_ = []zip _|_ [] = _|_

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

zip3 takes three lists and returns a list of triples, analogous tozip.

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

Thezip4 function takes four lists and returns a list of quadruples, analogous tozip.

zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]Source#

Thezip5 function takes five lists and returns a list of five-tuples, analogous tozip.

zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]Source#

Thezip6 function takes six lists and returns a list of six-tuples, analogous tozip.

zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]Source#

Thezip7 function takes seven lists and returns a list of seven-tuples, analogous tozip.

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

zipWith generaliseszip by zipping with the function given as the first argument, instead of a tupling function. For example,zipWith (+) is applied to two lists to produce the list of corresponding sums.

zipWith is right-lazy:

zipWith f [] _|_ = []

zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]Source#

ThezipWith3 function takes a function which combines three elements, as well as three lists and returns a list of their point-wise combination, analogous tozipWith.

zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]Source#

ThezipWith4 function takes a function which combines four elements, as well as four lists and returns a list of their point-wise combination, analogous tozipWith.

zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]Source#

ThezipWith5 function takes a function which combines five elements, as well as five lists and returns a list of their point-wise combination, analogous tozipWith.

zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]Source#

ThezipWith6 function takes a function which combines six elements, as well as six lists and returns a list of their point-wise combination, analogous tozipWith.

zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]Source#

ThezipWith7 function takes a function which combines seven elements, as well as seven lists and returns a list of their point-wise combination, analogous tozipWith.

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

unzip transforms a list of pairs into a list of first components and a list of second components.

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

Theunzip3 function takes a list of triples and returns three lists, analogous tounzip.

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

Theunzip4 function takes a list of quadruples and returns four lists, analogous tounzip.

unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])Source#

Theunzip5 function takes a list of five-tuples and returns five lists, analogous tounzip.

unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])Source#

Theunzip6 function takes a list of six-tuples and returns six lists, analogous tounzip.

unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])Source#

Theunzip7 function takes a list of seven-tuples and returns seven lists, analogous tounzip.

Special lists

Functions on strings

lines ::String -> [String]Source#

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

Thuslines s contains at least as many elements as newlines ins.

words ::String -> [String]Source#

words breaks a string up into a list of words, which were delimited by white space.

>>>words "Lorem ipsum\ndolor"["Lorem","ipsum","dolor"]

unlines :: [String] ->StringSource#

unlines is an inverse operation tolines. It joins lines, after appending a terminating newline to each.

>>>unlines ["Hello", "World", "!"]"Hello\nWorld\n!\n"

unwords :: [String] ->StringSource#

unwords is an inverse operation towords. It joins words with separating spaces.

>>>unwords ["Lorem", "ipsum", "dolor"]"Lorem ipsum dolor"

"Set" operations

nub ::Eq a => [a] -> [a]Source#

O(n^2). Thenub function removes duplicate elements from a list. In particular, it keeps only the first occurrence of each element. (The namenub means `essence'.) It is a special case ofnubBy, 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]

delete ::Eq a => a -> [a] -> [a]Source#

deletex removes the first occurrence ofx from its list argument. For example,

>>>delete 'a' "banana""bnana"

It is a special case ofdeleteBy, which allows the programmer to supply their own equality test.

(\\) ::Eq a => [a] -> [a] -> [a]infix 5Source#

The\\ function is list difference (non-associative). In the result ofxs\\ys, the first occurrence of each element ofys in turn (if any) has been removed fromxs. Thus

(xs ++ ys) \\ xs == ys.
>>>"Hello World!" \\ "ell W""Hoorld!"

It is a special case ofdeleteFirstsBy, which allows the programmer to supply their own equality test.

union ::Eq a => [a] -> [a] -> [a]Source#

Theunion 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 ofunionBy, which allows the programmer to supply their own equality test.

intersect ::Eq a => [a] -> [a] -> [a]Source#

Theintersect 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 ofintersectBy, 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.

Ordered lists

sort ::Ord a => [a] -> [a]Source#

Thesort function implements a stable sorting algorithm. It is a special case ofsortBy, 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]Source#

Sort a list by comparing the results of a key function applied to each element.sortOn f is equivalent tosortBy (comparing f), but has the performance advantage of only evaluatingf 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: 4.8.0.0

insert ::Ord a => a -> [a] -> [a]Source#

Theinsert 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 ofinsertBy, 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]

Generalized functions

The "By" operations

By convention, overloaded functions have a non-overloaded counterpart whose name is suffixed with `By'.

It is often convenient to use these functions together withon, for instancesortBy (compare `on`fst).

User-supplied equality (replacing anEq context)

The predicate is assumed to define an equivalence.

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

ThenubBy function behaves just likenub, except it uses a user-supplied equality predicate instead of the overloaded== function.

>>>nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6][1,2,6]

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

ThedeleteBy function behaves likedelete, but takes a user-supplied equality predicate.

>>>deleteBy (<=) 4 [1..10][1,2,3,5,6,7,8,9,10]

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

ThedeleteFirstsBy function takes a predicate and two lists and returns the first list with the first occurrence of each element of the second list removed.

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

TheunionBy function is the non-overloaded version ofunion.

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

TheintersectBy function is the non-overloaded version ofintersect.

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

ThegroupBy function is the non-overloaded version ofgroup.

User-supplied comparison (replacing anOrd context)

The function is assumed to define a total ordering.

sortBy :: (a -> a ->Ordering) -> [a] -> [a]Source#

ThesortBy function is the non-overloaded version ofsort.

>>>sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")][(1,"Hello"),(2,"world"),(4,"!")]

insertBy :: (a -> a ->Ordering) -> a -> [a] -> [a]Source#

The non-overloaded version ofinsert.

maximumBy :: (a -> a ->Ordering) -> [a] -> aSource#

ThemaximumBy function takes a comparison function and a list and returns the greatest element of the list by the comparison function. The list must be finite and non-empty.

We can use this to find the longest entry of a list:

>>>maximumBy (\x y -> compare (length x) (length y)) ["Hello", "World", "!", "Longest", "bar"]"Longest"

minimumBy :: (a -> a ->Ordering) -> [a] -> aSource#

TheminimumBy function takes a comparison function and a list and returns the least element of the list by the comparison function. The list must be finite and non-empty.

We can use this to find the shortest entry of a list:

>>>minimumBy (\x y -> compare (length x) (length y)) ["Hello", "World", "!", "Longest", "bar"]"!"

The "generic" operations

The prefix `generic' indicates an overloaded function that is a generalized version of aPrelude function.

genericLength ::Num i => [a] -> iSource#

ThegenericLength function is an overloaded version oflength. In particular, instead of returning anInt, it returns any type which is an instance ofNum. It is, however, less efficient thanlength.

genericTake ::Integral i => i -> [a] -> [a]Source#

ThegenericTake function is an overloaded version oftake, which accepts anyIntegral value as the number of elements to take.

genericDrop ::Integral i => i -> [a] -> [a]Source#

ThegenericDrop function is an overloaded version ofdrop, which accepts anyIntegral value as the number of elements to drop.

genericSplitAt ::Integral i => i -> [a] -> ([a], [a])Source#

ThegenericSplitAt function is an overloaded version ofsplitAt, which accepts anyIntegral value as the position at which to split.

genericIndex ::Integral i => [a] -> i -> aSource#

ThegenericIndex function is an overloaded version of!!, which accepts anyIntegral value as the index.

genericReplicate ::Integral i => i -> a -> [a]Source#

ThegenericReplicate function is an overloaded version ofreplicate, which accepts anyIntegral value as the number of repetitions to make.

Produced byHaddock version 2.20.0


[8]ページ先頭

©2009-2025 Movatter.jp