Movatterモバイル変換
[0]ホーム
{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables, MagicHash, BangPatterns #-}------------------------------------------------------------------------------- |-- Module : Data.List-- Copyright : (c) The University of Glasgow 2001-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : stable-- Portability : portable---- Operations on lists.-------------------------------------------------------------------------------moduleData.OldList(-- * Basic functions(++),head,last,tail,init,uncons,null,length-- * List transformations,map,reverse,intersperse,intercalate,transpose,subsequences,permutations-- * Reducing lists (folds),foldl,foldl',foldl1,foldl1',foldr,foldr1-- ** Special folds,concat,concatMap,and,or,any,all,sum,product,maximum,minimum-- * Building lists-- ** Scans,scanl,scanl',scanl1,scanr,scanr1-- ** Accumulating maps,mapAccumL,mapAccumR-- ** Infinite lists,iterate,iterate',repeat,replicate,cycle-- ** Unfolding,unfoldr-- * Sublists-- ** Extracting sublists,take,drop,splitAt,takeWhile,dropWhile,dropWhileEnd,span,break,stripPrefix,group,inits,tails-- ** Predicates,isPrefixOf,isSuffixOf,isInfixOf-- * Searching lists-- ** Searching by equality,elem,notElem,lookup-- ** Searching with a predicate,find,filter,partition-- * Indexing lists-- | These functions treat a list @xs@ as a indexed collection,-- with indices ranging from 0 to @'length' xs - 1@.,(!!),elemIndex,elemIndices,findIndex,findIndices-- * Zipping and unzipping lists,zip,zip3,zip4,zip5,zip6,zip7,zipWith,zipWith3,zipWith4,zipWith5,zipWith6,zipWith7,unzip,unzip3,unzip4,unzip5,unzip6,unzip7-- * Special lists-- ** Functions on strings,lines,words,unlines,unwords-- ** \"Set\" operations,nub,delete,(\\),union,intersect-- ** Ordered lists,sort,sortOn,insert-- * 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 with-- 'Data.Function.on', for instance @'sortBy' ('compare'-- \`on\` 'fst')@.-- *** User-supplied equality (replacing an @Eq@ context)-- | The predicate is assumed to define an equivalence.,nubBy,deleteBy,deleteFirstsBy,unionBy,intersectBy,groupBy-- *** User-supplied comparison (replacing an @Ord@ context)-- | The function is assumed to define a total ordering.,sortBy,insertBy,maximumBy,minimumBy-- ** The \"@generic@\" operations-- | The prefix \`@generic@\' indicates an overloaded function that-- is a generalized version of a "Prelude" function.,genericLength,genericTake,genericDrop,genericSplitAt,genericIndex,genericReplicate)whereimportData.MaybeimportData.Bits((.&.))importData.Char(isSpace)importData.Ord(comparing)importData.Tuple(fst,snd)importGHC.NumimportGHC.RealimportGHC.ListimportGHC.Baseinfix5\\-- comment to fool cpp: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/phases.html#cpp-and-string-gaps-- ------------------------------------------------------------------------------- List functions-- | 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 4.5.0.0dropWhileEnd::(a->Bool)->[a]->[a]dropWhileEnd :: (a -> Bool) -> [a] -> [a]dropWhileEnda -> Boolp=(a -> [a] -> [a]) -> [a] -> [a] -> [a]forall a b. (a -> b -> b) -> b -> [a] -> bfoldr(\ax[a]xs->ifa -> BoolpaxBool -> Bool -> Bool&&[a] -> Boolforall a. [a] -> Boolnull[a]xsthen[]elseaxa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]xs)[]-- | \(\mathcal{O}(\min(m,n))\). 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"-- NothingstripPrefix::Eqa=>[a]->[a]->Maybe[a]stripPrefix :: [a] -> [a] -> Maybe [a]stripPrefix[][a]ys=[a] -> Maybe [a]forall a. a -> Maybe aJust[a]ysstripPrefix(ax:[a]xs)(ay:[a]ys)|axa -> a -> Boolforall a. Eq a => a -> a -> Bool==ay=[a] -> [a] -> Maybe [a]forall a. Eq a => [a] -> [a] -> Maybe [a]stripPrefix[a]xs[a]ysstripPrefix[a]_[a]_=Maybe [a]forall a. Maybe aNothing-- | The 'elemIndex' function returns the index of the first element-- in the given list which is equal (by '==') to the query element,-- or 'Nothing' if there is no such element.---- >>> elemIndex 4 [0..]-- Just 4elemIndex::Eqa=>a->[a]->MaybeIntelemIndex :: a -> [a] -> Maybe IntelemIndexax=(a -> Bool) -> [a] -> Maybe Intforall a. (a -> Bool) -> [a] -> Maybe IntfindIndex(axa -> a -> Boolforall a. Eq a => a -> a -> Bool==)-- | 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]elemIndices::Eqa=>a->[a]->[Int]elemIndices :: a -> [a] -> [Int]elemIndicesax=(a -> Bool) -> [a] -> [Int]forall a. (a -> Bool) -> [a] -> [Int]findIndices(axa -> a -> Boolforall a. Eq a => a -> a -> Bool==)-- | The 'find' function takes a predicate and a list and returns the-- first element in the list matching the predicate, or 'Nothing' if-- there is no such element.---- >>> find (> 4) [1..]-- Just 5---- >>> find (< 0) [1..10]-- Nothingfind::(a->Bool)->[a]->Maybeafind :: (a -> Bool) -> [a] -> Maybe afinda -> Boolp=[a] -> Maybe aforall a. [a] -> Maybe alistToMaybe([a] -> Maybe a) -> ([a] -> [a]) -> [a] -> Maybe aforall b c a. (b -> c) -> (a -> b) -> a -> c.(a -> Bool) -> [a] -> [a]forall a. (a -> Bool) -> [a] -> [a]filtera -> Boolp-- | The 'findIndex' function takes a predicate and a list and returns-- the index of the first element in the list satisfying the predicate,-- or 'Nothing' if there is no such element.---- >>> findIndex isSpace "Hello World!"-- Just 5findIndex::(a->Bool)->[a]->MaybeIntfindIndex :: (a -> Bool) -> [a] -> Maybe IntfindIndexa -> Boolp=[Int] -> Maybe Intforall a. [a] -> Maybe alistToMaybe([Int] -> Maybe Int) -> ([a] -> [Int]) -> [a] -> Maybe Intforall b c a. (b -> c) -> (a -> b) -> a -> c.(a -> Bool) -> [a] -> [Int]forall a. (a -> Bool) -> [a] -> [Int]findIndicesa -> Boolp-- | 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]findIndices::(a->Bool)->[a]->[Int]#if defined(USE_REPORT_PRELUDE)findIndicespxs=[i|(x,i)<-zipxs[0..],px]#else-- Efficient definition, adapted from Data.Sequence-- (Note that making this INLINABLE instead of INLINE allows-- 'findIndex' to fuse, fixing #15426.){-# INLINABLEfindIndices#-}findIndices :: (a -> Bool) -> [a] -> [Int]findIndicesa -> Boolp[a]ls=(forall b. (Int -> b -> b) -> b -> b) -> [Int]forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]build((forall b. (Int -> b -> b) -> b -> b) -> [Int])-> (forall b. (Int -> b -> b) -> b -> b) -> [Int]forall a b. (a -> b) -> a -> b$\Int -> b -> bcbn->letgo :: a -> (Int# -> b) -> Int# -> bgoaxInt# -> brInt#k|a -> Boolpax=Int# -> IntI#Int#kInt -> b -> b`c`Int# -> br(Int#kInt# -> Int# -> Int#+#Int#1#)|Boolotherwise=Int# -> br(Int#kInt# -> Int# -> Int#+#Int#1#)in(a -> (Int# -> b) -> Int# -> b) -> (Int# -> b) -> [a] -> Int# -> bforall a b. (a -> b -> b) -> b -> [a] -> bfoldra -> (Int# -> b) -> Int# -> bgo(\Int#_->bn)[a]lsInt#0##endif /* USE_REPORT_PRELUDE */-- | \(\mathcal{O}(\min(m,n))\). 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!"-- FalseisPrefixOf::(Eqa)=>[a]->[a]->BoolisPrefixOf :: [a] -> [a] -> BoolisPrefixOf[][a]_=BoolTrueisPrefixOf[a]_[]=BoolFalseisPrefixOf(ax:[a]xs)(ay:[a]ys)=axa -> a -> Boolforall a. Eq a => a -> a -> Bool==ayBool -> Bool -> Bool&&[a] -> [a] -> Boolforall a. Eq a => [a] -> [a] -> BoolisPrefixOf[a]xs[a]ys-- | 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!"-- FalseisSuffixOf::(Eqa)=>[a]->[a]->Bool[a]nsisSuffixOf :: [a] -> [a] -> Bool`isSuffixOf`[a]hs=Bool -> (Bool -> Bool) -> Maybe Bool -> Boolforall b a. b -> (a -> b) -> Maybe a -> bmaybeBoolFalseBool -> Boolforall a. a -> aid(Maybe Bool -> Bool) -> Maybe Bool -> Boolforall a b. (a -> b) -> a -> b$do[a]delta<-[a] -> [a] -> Maybe [a]forall a b. [a] -> [b] -> Maybe [b]dropLengthMaybe[a]ns[a]hsBool -> Maybe Boolforall (m :: * -> *) a. Monad m => a -> m areturn(Bool -> Maybe Bool) -> Bool -> Maybe Boolforall a b. (a -> b) -> a -> b$[a]ns[a] -> [a] -> Boolforall a. Eq a => a -> a -> Bool==[a] -> [a] -> [a]forall a b. [a] -> [b] -> [b]dropLength[a]delta[a]hs-- Since dropLengthMaybe ns hs succeeded, we know that (if hs is finite)-- length ns + length delta = length hs-- so dropping the length of delta from hs will yield a suffix exactly-- the length of ns.-- A version of drop that drops the length of the first argument from the-- second argument. If xs is longer than ys, xs will not be traversed in its-- entirety. dropLength is also generally faster than (drop . length)-- Both this and dropLengthMaybe could be written as folds over their first-- arguments, but this reduces clarity with no benefit to isSuffixOf.---- >>> dropLength "Hello" "Holla world"-- " world"---- >>> dropLength [1..] [1,2,3]-- []dropLength::[a]->[b]->[b]dropLength :: [a] -> [b] -> [b]dropLength[][b]y=[b]ydropLength[a]_[]=[]dropLength(a_:[a]x')(b_:[b]y')=[a] -> [b] -> [b]forall a b. [a] -> [b] -> [b]dropLength[a]x'[b]y'-- A version of dropLength that returns Nothing if the second list runs out of-- elements before the first.---- >>> dropLengthMaybe [1..] [1,2,3]-- NothingdropLengthMaybe::[a]->[b]->Maybe[b]dropLengthMaybe :: [a] -> [b] -> Maybe [b]dropLengthMaybe[][b]y=[b] -> Maybe [b]forall a. a -> Maybe aJust[b]ydropLengthMaybe[a]_[]=Maybe [b]forall a. Maybe aNothingdropLengthMaybe(a_:[a]x')(b_:[b]y')=[a] -> [b] -> Maybe [b]forall a b. [a] -> [b] -> Maybe [b]dropLengthMaybe[a]x'[b]y'-- | The 'isInfixOf' function takes two lists and returns 'True'-- 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."-- FalseisInfixOf::(Eqa)=>[a]->[a]->BoolisInfixOf :: [a] -> [a] -> BoolisInfixOf[a]needle[a]haystack=([a] -> Bool) -> [[a]] -> Boolforall a. (a -> Bool) -> [a] -> Boolany([a] -> [a] -> Boolforall a. Eq a => [a] -> [a] -> BoolisPrefixOf[a]needle)([a] -> [[a]]forall a. [a] -> [[a]]tails[a]haystack)-- | \(\mathcal{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]nub::(Eqa)=>[a]->[a]nub :: [a] -> [a]nub=(a -> a -> Bool) -> [a] -> [a]forall a. (a -> a -> Bool) -> [a] -> [a]nubBya -> a -> Boolforall a. Eq a => a -> a -> Bool(==)-- | The 'nubBy' function behaves just like 'nub', 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]nubBy::(a->a->Bool)->[a]->[a]#if defined(USE_REPORT_PRELUDE)nubByeq[]=[]nubByeq(x:xs)=x:nubByeq(filter(\y->not(eqxy))xs)#else-- stolen from HBCnubBy :: (a -> a -> Bool) -> [a] -> [a]nubBya -> a -> Booleq[a]l=[a] -> [a] -> [a]nubBy'[a]l[]wherenubBy' :: [a] -> [a] -> [a]nubBy'[][a]_=[]nubBy'(ay:[a]ys)[a]xs|(a -> a -> Bool) -> a -> [a] -> Boolforall a. (a -> a -> Bool) -> a -> [a] -> Boolelem_bya -> a -> Booleqay[a]xs=[a] -> [a] -> [a]nubBy'[a]ys[a]xs|Boolotherwise=aya -> [a] -> [a]forall a. a -> [a] -> [a]:[a] -> [a] -> [a]nubBy'[a]ys(aya -> [a] -> [a]forall a. a -> [a] -> [a]:[a]xs)-- Not exported:-- Note that we keep the call to `eq` with arguments in the-- same order as in the reference (prelude) implementation,-- and that this order is different from how `elem` calls (==).-- See #2528, #3280 and #7913.-- 'xs' is the list of things we've seen so far,-- 'y' is the potential new elementelem_by::(a->a->Bool)->a->[a]->Boolelem_by :: (a -> a -> Bool) -> a -> [a] -> Boolelem_bya -> a -> Bool_a_[]=BoolFalseelem_bya -> a -> Booleqay(ax:[a]xs)=axa -> a -> Bool`eq`ayBool -> Bool -> Bool||(a -> a -> Bool) -> a -> [a] -> Boolforall a. (a -> a -> Bool) -> a -> [a] -> Boolelem_bya -> a -> Booleqay[a]xs#endif-- | \(\mathcal{O}(n)\). 'delete' @x@ removes the first occurrence of @x@ from-- its list argument. For example,---- >>> delete 'a' "banana"-- "bnana"---- It is a special case of 'deleteBy', which allows the programmer to-- supply their own equality test.delete::(Eqa)=>a->[a]->[a]delete :: a -> [a] -> [a]delete=(a -> a -> Bool) -> a -> [a] -> [a]forall a. (a -> a -> Bool) -> a -> [a] -> [a]deleteBya -> a -> Boolforall a. Eq a => a -> a -> Bool(==)-- | \(\mathcal{O}(n)\). The 'deleteBy' function behaves like 'delete', but-- takes a user-supplied equality predicate.---- >>> deleteBy (<=) 4 [1..10]-- [1,2,3,5,6,7,8,9,10]deleteBy::(a->a->Bool)->a->[a]->[a]deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a]deleteBya -> a -> Bool_a_[]=[]deleteBya -> a -> Booleqax(ay:[a]ys)=ifaxa -> a -> Bool`eq`aythen[a]yselseaya -> [a] -> [a]forall a. a -> [a] -> [a]:(a -> a -> Bool) -> a -> [a] -> [a]forall a. (a -> a -> Bool) -> a -> [a] -> [a]deleteBya -> a -> Booleqax[a]ys-- | 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.(\\)::(Eqa)=>[a]->[a]->[a]\\ :: [a] -> [a] -> [a](\\)=([a] -> a -> [a]) -> [a] -> [a] -> [a]forall a b. (b -> a -> b) -> b -> [a] -> bfoldl((a -> [a] -> [a]) -> [a] -> a -> [a]forall a b c. (a -> b -> c) -> b -> a -> cflipa -> [a] -> [a]forall a. Eq a => a -> [a] -> [a]delete)-- | 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.union::(Eqa)=>[a]->[a]->[a]union :: [a] -> [a] -> [a]union=(a -> a -> Bool) -> [a] -> [a] -> [a]forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]unionBya -> a -> Boolforall a. Eq a => a -> a -> Bool(==)-- | The 'unionBy' function is the non-overloaded version of 'union'.unionBy::(a->a->Bool)->[a]->[a]->[a]unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]unionBya -> a -> Booleq[a]xs[a]ys=[a]xs[a] -> [a] -> [a]forall a. [a] -> [a] -> [a]++([a] -> a -> [a]) -> [a] -> [a] -> [a]forall a b. (b -> a -> b) -> b -> [a] -> bfoldl((a -> [a] -> [a]) -> [a] -> a -> [a]forall a b c. (a -> b -> c) -> b -> a -> cflip((a -> a -> Bool) -> a -> [a] -> [a]forall a. (a -> a -> Bool) -> a -> [a] -> [a]deleteBya -> a -> Booleq))((a -> a -> Bool) -> [a] -> [a]forall a. (a -> a -> Bool) -> [a] -> [a]nubBya -> a -> Booleq[a]ys)[a]xs-- | 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.intersect::(Eqa)=>[a]->[a]->[a]intersect :: [a] -> [a] -> [a]intersect=(a -> a -> Bool) -> [a] -> [a] -> [a]forall a. (a -> a -> Bool) -> [a] -> [a] -> [a]intersectBya -> a -> Boolforall a. Eq a => a -> a -> Bool(==)-- | The 'intersectBy' function is the non-overloaded version of 'intersect'.intersectBy::(a->a->Bool)->[a]->[a]->[a]intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]intersectBya -> a -> Bool_[][a]_=[]intersectBya -> a -> Bool_[a]_[]=[]intersectBya -> a -> Booleq[a]xs[a]ys=[ax|ax<-[a]xs,(a -> Bool) -> [a] -> Boolforall a. (a -> Bool) -> [a] -> Boolany(a -> a -> Booleqax)[a]ys]-- | \(\mathcal{O}(n)\). 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"intersperse::a->[a]->[a]intersperse :: a -> [a] -> [a]interspersea_[]=[]intersperseasep(ax:[a]xs)=axa -> [a] -> [a]forall a. a -> [a] -> [a]:a -> [a] -> [a]forall a. a -> [a] -> [a]prependToAllasep[a]xs-- Not exported:-- We want to make every element in the 'intersperse'd list available-- as soon as possible to avoid space leaks. Experiments suggested that-- a separate top-level helper is more efficient than a local worker.prependToAll::a->[a]->[a]prependToAll :: a -> [a] -> [a]prependToAlla_[]=[]prependToAllasep(ax:[a]xs)=asepa -> [a] -> [a]forall a. a -> [a] -> [a]:axa -> [a] -> [a]forall a. a -> [a] -> [a]:a -> [a] -> [a]forall a. a -> [a] -> [a]prependToAllasep[a]xs-- | 'intercalate' @xs xss@ is equivalent to @('concat' ('intersperse' xs xss))@.-- It inserts the list @xs@ in between the lists in @xss@ and concatenates the-- result.---- >>> intercalate ", " ["Lorem", "ipsum", "dolor"]-- "Lorem, ipsum, dolor"intercalate::[a]->[[a]]->[a]intercalate :: [a] -> [[a]] -> [a]intercalate[a]xs[[a]]xss=[[a]] -> [a]forall a. [[a]] -> [a]concat([a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]intersperse[a]xs[[a]]xss)-- | 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]]transpose::[[a]]->[[a]]transpose :: [[a]] -> [[a]]transpose[]=[]transpose([]:[[a]]xss)=[[a]] -> [[a]]forall a. [[a]] -> [[a]]transpose[[a]]xsstranspose((ax:[a]xs):[[a]]xss)=(axa -> [a] -> [a]forall a. a -> [a] -> [a]:[ah|(ah:[a]_)<-[[a]]xss])[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[[a]] -> [[a]]forall a. [[a]] -> [[a]]transpose([a]xs[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[[a]t|(a_:[a]t)<-[[a]]xss])-- | 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!")partition::(a->Bool)->[a]->([a],[a]){-# INLINEpartition#-}partition :: (a -> Bool) -> [a] -> ([a], [a])partitiona -> Boolp[a]xs=(a -> ([a], [a]) -> ([a], [a])) -> ([a], [a]) -> [a] -> ([a], [a])forall a b. (a -> b -> b) -> b -> [a] -> bfoldr((a -> Bool) -> a -> ([a], [a]) -> ([a], [a])forall a. (a -> Bool) -> a -> ([a], [a]) -> ([a], [a])selecta -> Boolp)([],[])[a]xsselect::(a->Bool)->a->([a],[a])->([a],[a])select :: (a -> Bool) -> a -> ([a], [a]) -> ([a], [a])selecta -> Boolpax~([a]ts,[a]fs)|a -> Boolpax=(axa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]ts,[a]fs)|Boolotherwise=([a]ts,axa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]fs)-- | The 'mapAccumL' function behaves like a combination of 'map' and-- 'foldl'; 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.mapAccumL::(acc->x->(acc,y))-- Function of elt of input list-- and accumulator, returning new-- accumulator and elt of result list->acc-- Initial accumulator->[x]-- Input list->(acc,[y])-- Final accumulator and result list{-# NOINLINE[1]mapAccumL#-}mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])mapAccumLacc -> x -> (acc, y)_accs[]=(accs,[])mapAccumLacc -> x -> (acc, y)faccs(xx:[x]xs)=(accs'',yyy -> [y] -> [y]forall a. a -> [a] -> [a]:[y]ys)where(accs',yy)=acc -> x -> (acc, y)faccsxx(accs'',[y]ys)=(acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])forall acc x y. (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])mapAccumLacc -> x -> (acc, y)faccs'[x]xs{-# RULES"mapAccumL"[~1]forallfsxs.mapAccumLfsxs=foldr(mapAccumLFf)pairWithNilxss"mapAccumLList"[1]forallfsxs.foldr(mapAccumLFf)pairWithNilxss=mapAccumLfsxs#-}pairWithNil::acc->(acc,[y]){-# INLINE[0]pairWithNil#-}pairWithNil :: acc -> (acc, [y])pairWithNilaccx=(accx,[])mapAccumLF::(acc->x->(acc,y))->x->(acc->(acc,[y]))->acc->(acc,[y]){-# INLINE[0]mapAccumLF#-}mapAccumLF :: (acc -> x -> (acc, y))-> x -> (acc -> (acc, [y])) -> acc -> (acc, [y])mapAccumLFacc -> x -> (acc, y)f=\xxacc -> (acc, [y])r->(acc -> (acc, [y])) -> acc -> (acc, [y])oneShot(\accs->let(accs',yy)=acc -> x -> (acc, y)faccsxx(accs'',[y]ys)=acc -> (acc, [y])raccs'in(accs'',yyy -> [y] -> [y]forall a. a -> [a] -> [a]:[y]ys))-- See Note [Left folds via right fold]-- | The 'mapAccumR' function behaves like a combination of 'map' and-- 'foldr'; 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.mapAccumR::(acc->x->(acc,y))-- Function of elt of input list-- and accumulator, returning new-- accumulator and elt of result list->acc-- Initial accumulator->[x]-- Input list->(acc,[y])-- Final accumulator and result listmapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])mapAccumRacc -> x -> (acc, y)_accs[]=(accs,[])mapAccumRacc -> x -> (acc, y)faccs(xx:[x]xs)=(accs'',yyy -> [y] -> [y]forall a. a -> [a] -> [a]:[y]ys)where(accs'',yy)=acc -> x -> (acc, y)faccs'xx(accs',[y]ys)=(acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])forall acc x y. (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])mapAccumRacc -> x -> (acc, y)faccs[x]xs-- | \(\mathcal{O}(n)\). 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]insert::Orda=>a->[a]->[a]insert :: a -> [a] -> [a]insertae[a]ls=(a -> a -> Ordering) -> a -> [a] -> [a]forall a. (a -> a -> Ordering) -> a -> [a] -> [a]insertBy(a -> a -> Orderingforall a. Ord a => a -> a -> Orderingcompare)ae[a]ls-- | \(\mathcal{O}(n)\). The non-overloaded version of 'insert'.insertBy::(a->a->Ordering)->a->[a]->[a]insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]insertBya -> a -> Ordering_ax[]=[ax]insertBya -> a -> Orderingcmpaxys :: [a]ys@(ay:[a]ys')=casea -> a -> OrderingcmpaxayofOrderingGT->aya -> [a] -> [a]forall a. a -> [a] -> [a]:(a -> a -> Ordering) -> a -> [a] -> [a]forall a. (a -> a -> Ordering) -> a -> [a] -> [a]insertBya -> a -> Orderingcmpax[a]ys'Ordering_->axa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]ys-- | The 'maximumBy' 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"maximumBy::(a->a->Ordering)->[a]->amaximumBy :: (a -> a -> Ordering) -> [a] -> amaximumBya -> a -> Ordering_[]=[Char] -> aforall a. [Char] -> aerrorWithoutStackTrace[Char]"List.maximumBy: empty list"maximumBya -> a -> Orderingcmp[a]xs=(a -> a -> a) -> [a] -> aforall a. (a -> a -> a) -> [a] -> afoldl1a -> a -> amaxBy[a]xswheremaxBy :: a -> a -> amaxByaxay=casea -> a -> OrderingcmpaxayofOrderingGT->axOrdering_->ay-- | The 'minimumBy' 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"]-- "!"minimumBy::(a->a->Ordering)->[a]->aminimumBy :: (a -> a -> Ordering) -> [a] -> aminimumBya -> a -> Ordering_[]=[Char] -> aforall a. [Char] -> aerrorWithoutStackTrace[Char]"List.minimumBy: empty list"minimumBya -> a -> Orderingcmp[a]xs=(a -> a -> a) -> [a] -> aforall a. (a -> a -> a) -> [a] -> afoldl1a -> a -> aminBy[a]xswhereminBy :: a -> a -> aminByaxay=casea -> a -> OrderingcmpaxayofOrderingGT->ayOrdering_->ax-- | \(\mathcal{O}(n)\). 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'.---- >>> genericLength [1, 2, 3] :: Int-- 3-- >>> genericLength [1, 2, 3] :: Float-- 3.0genericLength::(Numi)=>[a]->i{-# NOINLINE[1]genericLength#-}genericLength :: [a] -> igenericLength[]=i0genericLength(a_:[a]l)=i1i -> i -> iforall a. Num a => a -> a -> a+[a] -> iforall i a. Num i => [a] -> igenericLength[a]l{-# RULES"genericLengthInt"genericLength=(strictGenericLength::[a]->Int);"genericLengthInteger"genericLength=(strictGenericLength::[a]->Integer);#-}strictGenericLength::(Numi)=>[b]->istrictGenericLength :: [b] -> istrictGenericLength[b]l=[b] -> i -> iforall t a. Num t => [a] -> t -> tgl[b]li0wheregl :: [a] -> t -> tgl[]ta=tagl(a_:[a]xs)ta=leta' :: ta'=tat -> t -> tforall a. Num a => a -> a -> a+t1inta't -> t -> t`seq`[a] -> t -> tgl[a]xsta'-- | The 'genericTake' function is an overloaded version of 'take', which-- accepts any 'Integral' value as the number of elements to take.genericTake::(Integrali)=>i->[a]->[a]genericTake :: i -> [a] -> [a]genericTakein[a]_|ini -> i -> Boolforall a. Ord a => a -> a -> Bool<=i0=[]genericTakei_[]=[]genericTakein(ax:[a]xs)=axa -> [a] -> [a]forall a. a -> [a] -> [a]:i -> [a] -> [a]forall i a. Integral i => i -> [a] -> [a]genericTake(ini -> i -> iforall a. Num a => a -> a -> a-i1)[a]xs-- | The 'genericDrop' function is an overloaded version of 'drop', which-- accepts any 'Integral' value as the number of elements to drop.genericDrop::(Integrali)=>i->[a]->[a]genericDrop :: i -> [a] -> [a]genericDropin[a]xs|ini -> i -> Boolforall a. Ord a => a -> a -> Bool<=i0=[a]xsgenericDropi_[]=[]genericDropin(a_:[a]xs)=i -> [a] -> [a]forall i a. Integral i => i -> [a] -> [a]genericDrop(ini -> i -> iforall a. Num a => a -> a -> a-i1)[a]xs-- | The 'genericSplitAt' function is an overloaded version of 'splitAt', which-- accepts any 'Integral' value as the position at which to split.genericSplitAt::(Integrali)=>i->[a]->([a],[a])genericSplitAt :: i -> [a] -> ([a], [a])genericSplitAtin[a]xs|ini -> i -> Boolforall a. Ord a => a -> a -> Bool<=i0=([],[a]xs)genericSplitAti_[]=([],[])genericSplitAtin(ax:[a]xs)=(axa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]xs',[a]xs'')where([a]xs',[a]xs'')=i -> [a] -> ([a], [a])forall i a. Integral i => i -> [a] -> ([a], [a])genericSplitAt(ini -> i -> iforall a. Num a => a -> a -> a-i1)[a]xs-- | The 'genericIndex' function is an overloaded version of '!!', which-- accepts any 'Integral' value as the index.genericIndex::(Integrali)=>[a]->i->agenericIndex :: [a] -> i -> agenericIndex(ax:[a]_)i0=axgenericIndex(a_:[a]xs)in|ini -> i -> Boolforall a. Ord a => a -> a -> Bool>i0=[a] -> i -> aforall i a. Integral i => [a] -> i -> agenericIndex[a]xs(ini -> i -> iforall a. Num a => a -> a -> a-i1)|Boolotherwise=[Char] -> aforall a. [Char] -> aerrorWithoutStackTrace[Char]"List.genericIndex: negative argument."genericIndex[a]_i_=[Char] -> aforall a. [Char] -> aerrorWithoutStackTrace[Char]"List.genericIndex: index too large."-- | The 'genericReplicate' function is an overloaded version of 'replicate',-- which accepts any 'Integral' value as the number of repetitions to make.genericReplicate::(Integrali)=>i->a->[a]genericReplicate :: i -> a -> [a]genericReplicateinax=i -> [a] -> [a]forall i a. Integral i => i -> [a] -> [a]genericTakein(a -> [a]forall a. a -> [a]repeatax)-- | The 'zip4' function takes four lists and returns a list of-- quadruples, analogous to 'zip'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# INLINEzip4#-}zip4::[a]->[b]->[c]->[d]->[(a,b,c,d)]zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]zip4=(a -> b -> c -> d -> (a, b, c, d))-> [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]forall a b c d e.(a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]zipWith4(,,,)-- | The 'zip5' function takes five lists and returns a list of-- five-tuples, analogous to 'zip'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# INLINEzip5#-}zip5::[a]->[b]->[c]->[d]->[e]->[(a,b,c,d,e)]zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]zip5=(a -> b -> c -> d -> e -> (a, b, c, d, e))-> [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]forall a b c d e f.(a -> b -> c -> d -> e -> f)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f]zipWith5(,,,,)-- | The 'zip6' function takes six lists and returns a list of six-tuples,-- analogous to 'zip'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# INLINEzip6#-}zip6::[a]->[b]->[c]->[d]->[e]->[f]->[(a,b,c,d,e,f)]zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]zip6=(a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]forall a b c d e f g.(a -> b -> c -> d -> e -> f -> g)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]zipWith6(,,,,,)-- | The 'zip7' function takes seven lists and returns a list of-- seven-tuples, analogous to 'zip'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# INLINEzip7#-}zip7::[a]->[b]->[c]->[d]->[e]->[f]->[g]->[(a,b,c,d,e,f,g)]zip7 :: [a]-> [b]-> [c]-> [d]-> [e]-> [f]-> [g]-> [(a, b, c, d, e, f, g)]zip7=(a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))-> [a]-> [b]-> [c]-> [d]-> [e]-> [f]-> [g]-> [(a, b, c, d, e, f, g)]forall a b c d e f g h.(a -> b -> c -> d -> e -> f -> g -> h)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]zipWith7(,,,,,,)-- | The 'zipWith4' function takes a function which combines four-- elements, as well as four lists and returns a list of their point-wise-- combination, analogous to 'zipWith'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# NOINLINE[1]zipWith4#-}zipWith4::(a->b->c->d->e)->[a]->[b]->[c]->[d]->[e]zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]zipWith4a -> b -> c -> d -> ez(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)=a -> b -> c -> d -> ezaabbccdde -> [e] -> [e]forall a. a -> [a] -> [a]:(a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]forall a b c d e.(a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]zipWith4a -> b -> c -> d -> ez[a]as[b]bs[c]cs[d]dszipWith4a -> b -> c -> d -> e_[a]_[b]_[c]_[d]_=[]-- | The 'zipWith5' function takes a function which combines five-- elements, as well as five lists and returns a list of their point-wise-- combination, analogous to 'zipWith'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# NOINLINE[1]zipWith5#-}zipWith5::(a->b->c->d->e->f)->[a]->[b]->[c]->[d]->[e]->[f]zipWith5 :: (a -> b -> c -> d -> e -> f)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f]zipWith5a -> b -> c -> d -> e -> fz(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)=a -> b -> c -> d -> e -> fzaabbccddeef -> [f] -> [f]forall a. a -> [a] -> [a]:(a -> b -> c -> d -> e -> f)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f]forall a b c d e f.(a -> b -> c -> d -> e -> f)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f]zipWith5a -> b -> c -> d -> e -> fz[a]as[b]bs[c]cs[d]ds[e]eszipWith5a -> b -> c -> d -> e -> f_[a]_[b]_[c]_[d]_[e]_=[]-- | The 'zipWith6' function takes a function which combines six-- elements, as well as six lists and returns a list of their point-wise-- combination, analogous to 'zipWith'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# NOINLINE[1]zipWith6#-}zipWith6::(a->b->c->d->e->f->g)->[a]->[b]->[c]->[d]->[e]->[f]->[g]zipWith6 :: (a -> b -> c -> d -> e -> f -> g)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]zipWith6a -> b -> c -> d -> e -> f -> gz(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)(ff:[f]fs)=a -> b -> c -> d -> e -> f -> gzaabbccddeeffg -> [g] -> [g]forall a. a -> [a] -> [a]:(a -> b -> c -> d -> e -> f -> g)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]forall a b c d e f g.(a -> b -> c -> d -> e -> f -> g)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]zipWith6a -> b -> c -> d -> e -> f -> gz[a]as[b]bs[c]cs[d]ds[e]es[f]fszipWith6a -> b -> c -> d -> e -> f -> g_[a]_[b]_[c]_[d]_[e]_[f]_=[]-- | The 'zipWith7' function takes a function which combines seven-- elements, as well as seven lists and returns a list of their point-wise-- combination, analogous to 'zipWith'.-- It is capable of list fusion, but it is restricted to its-- first list argument and its resulting list.{-# NOINLINE[1]zipWith7#-}zipWith7::(a->b->c->d->e->f->g->h)->[a]->[b]->[c]->[d]->[e]->[f]->[g]->[h]zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]zipWith7a -> b -> c -> d -> e -> f -> g -> hz(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)(ff:[f]fs)(gg:[g]gs)=a -> b -> c -> d -> e -> f -> g -> hzaabbccddeeffggh -> [h] -> [h]forall a. a -> [a] -> [a]:(a -> b -> c -> d -> e -> f -> g -> h)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]forall a b c d e f g h.(a -> b -> c -> d -> e -> f -> g -> h)-> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]zipWith7a -> b -> c -> d -> e -> f -> g -> hz[a]as[b]bs[c]cs[d]ds[e]es[f]fs[g]gszipWith7a -> b -> c -> d -> e -> f -> g -> h_[a]_[b]_[c]_[d]_[e]_[f]_[g]_=[]{-Functions and rules for fusion of zipWith4, zipWith5, zipWith6 and zipWith7.The principle is the same as for zip and zipWith in GHC.List:Turn zipWithX into a version in which the first argument and the resultcan be fused. Turn it back into the original function if no fusion happens.-}{-# INLINE[0]zipWith4FB#-}-- See Note [Inline FB functions]zipWith4FB::(e->xs->xs')->(a->b->c->d->e)->a->b->c->d->xs->xs'zipWith4FB :: (e -> xs -> xs')-> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> xs -> xs'zipWith4FBe -> xs -> xs'consa -> b -> c -> d -> efunc=\aabbccddxsr->(a -> b -> c -> d -> efuncaabbccdd)e -> xs -> xs'`cons`xsr{-# INLINE[0]zipWith5FB#-}-- See Note [Inline FB functions]zipWith5FB::(f->xs->xs')->(a->b->c->d->e->f)->a->b->c->d->e->xs->xs'zipWith5FB :: (f -> xs -> xs')-> (a -> b -> c -> d -> e -> f)-> a-> b-> c-> d-> e-> xs-> xs'zipWith5FBf -> xs -> xs'consa -> b -> c -> d -> e -> ffunc=\aabbccddeexsr->(a -> b -> c -> d -> e -> ffuncaabbccddee)f -> xs -> xs'`cons`xsr{-# INLINE[0]zipWith6FB#-}-- See Note [Inline FB functions]zipWith6FB::(g->xs->xs')->(a->b->c->d->e->f->g)->a->b->c->d->e->f->xs->xs'zipWith6FB :: (g -> xs -> xs')-> (a -> b -> c -> d -> e -> f -> g)-> a-> b-> c-> d-> e-> f-> xs-> xs'zipWith6FBg -> xs -> xs'consa -> b -> c -> d -> e -> f -> gfunc=\aabbccddeeffxsr->(a -> b -> c -> d -> e -> f -> gfuncaabbccddeeff)g -> xs -> xs'`cons`xsr{-# INLINE[0]zipWith7FB#-}-- See Note [Inline FB functions]zipWith7FB::(h->xs->xs')->(a->b->c->d->e->f->g->h)->a->b->c->d->e->f->g->xs->xs'zipWith7FB :: (h -> xs -> xs')-> (a -> b -> c -> d -> e -> f -> g -> h)-> a-> b-> c-> d-> e-> f-> g-> xs-> xs'zipWith7FBh -> xs -> xs'consa -> b -> c -> d -> e -> f -> g -> hfunc=\aabbccddeeffggxsr->(a -> b -> c -> d -> e -> f -> g -> hfuncaabbccddeeffgg)h -> xs -> xs'`cons`xsr{-# INLINE[0]foldr4#-}foldr4::(a->b->c->d->e->e)->e->[a]->[b]->[c]->[d]->efoldr4 :: (a -> b -> c -> d -> e -> e) -> e -> [a] -> [b] -> [c] -> [d] -> efoldr4a -> b -> c -> d -> e -> ekez=[a] -> [b] -> [c] -> [d] -> egowherego :: [a] -> [b] -> [c] -> [d] -> ego(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)=a -> b -> c -> d -> e -> ekaabbccdd([a] -> [b] -> [c] -> [d] -> ego[a]as[b]bs[c]cs[d]ds)go[a]_[b]_[c]_[d]_=ez{-# INLINE[0]foldr5#-}foldr5::(a->b->c->d->e->f->f)->f->[a]->[b]->[c]->[d]->[e]->ffoldr5 :: (a -> b -> c -> d -> e -> f -> f)-> f -> [a] -> [b] -> [c] -> [d] -> [e] -> ffoldr5a -> b -> c -> d -> e -> f -> fkfz=[a] -> [b] -> [c] -> [d] -> [e] -> fgowherego :: [a] -> [b] -> [c] -> [d] -> [e] -> fgo(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)=a -> b -> c -> d -> e -> f -> fkaabbccddee([a] -> [b] -> [c] -> [d] -> [e] -> fgo[a]as[b]bs[c]cs[d]ds[e]es)go[a]_[b]_[c]_[d]_[e]_=fz{-# INLINE[0]foldr6#-}foldr6::(a->b->c->d->e->f->g->g)->g->[a]->[b]->[c]->[d]->[e]->[f]->gfoldr6 :: (a -> b -> c -> d -> e -> f -> g -> g)-> g -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> gfoldr6a -> b -> c -> d -> e -> f -> g -> gkgz=[a] -> [b] -> [c] -> [d] -> [e] -> [f] -> ggowherego :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> ggo(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)(ff:[f]fs)=a -> b -> c -> d -> e -> f -> g -> gkaabbccddeeff([a] -> [b] -> [c] -> [d] -> [e] -> [f] -> ggo[a]as[b]bs[c]cs[d]ds[e]es[f]fs)go[a]_[b]_[c]_[d]_[e]_[f]_=gz{-# INLINE[0]foldr7#-}foldr7::(a->b->c->d->e->f->g->h->h)->h->[a]->[b]->[c]->[d]->[e]->[f]->[g]->hfoldr7 :: (a -> b -> c -> d -> e -> f -> g -> h -> h)-> h -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> hfoldr7a -> b -> c -> d -> e -> f -> g -> h -> hkhz=[a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> hgowherego :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> hgo(aa:[a]as)(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)(ff:[f]fs)(gg:[g]gs)=a -> b -> c -> d -> e -> f -> g -> h -> hkaabbccddeeffgg([a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> hgo[a]as[b]bs[c]cs[d]ds[e]es[f]fs[g]gs)go[a]_[b]_[c]_[d]_[e]_[f]_[g]_=hzfoldr4_left::(a->b->c->d->e->f)->f->a->([b]->[c]->[d]->e)->[b]->[c]->[d]->ffoldr4_left :: (a -> b -> c -> d -> e -> f)-> f -> a -> ([b] -> [c] -> [d] -> e) -> [b] -> [c] -> [d] -> ffoldr4_lefta -> b -> c -> d -> e -> fkf_zaa[b] -> [c] -> [d] -> er(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)=a -> b -> c -> d -> e -> fkaabbccdd([b] -> [c] -> [d] -> er[b]bs[c]cs[d]ds)foldr4_lefta -> b -> c -> d -> e -> f_fza_[b] -> [c] -> [d] -> e_[b]_[c]_[d]_=fzfoldr5_left::(a->b->c->d->e->f->g)->g->a->([b]->[c]->[d]->[e]->f)->[b]->[c]->[d]->[e]->gfoldr5_left :: (a -> b -> c -> d -> e -> f -> g)-> g-> a-> ([b] -> [c] -> [d] -> [e] -> f)-> [b]-> [c]-> [d]-> [e]-> gfoldr5_lefta -> b -> c -> d -> e -> f -> gkg_zaa[b] -> [c] -> [d] -> [e] -> fr(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)=a -> b -> c -> d -> e -> f -> gkaabbccddee([b] -> [c] -> [d] -> [e] -> fr[b]bs[c]cs[d]ds[e]es)foldr5_lefta -> b -> c -> d -> e -> f -> g_gza_[b] -> [c] -> [d] -> [e] -> f_[b]_[c]_[d]_[e]_=gzfoldr6_left::(a->b->c->d->e->f->g->h)->h->a->([b]->[c]->[d]->[e]->[f]->g)->[b]->[c]->[d]->[e]->[f]->hfoldr6_left :: (a -> b -> c -> d -> e -> f -> g -> h)-> h-> a-> ([b] -> [c] -> [d] -> [e] -> [f] -> g)-> [b]-> [c]-> [d]-> [e]-> [f]-> hfoldr6_lefta -> b -> c -> d -> e -> f -> g -> hkh_zaa[b] -> [c] -> [d] -> [e] -> [f] -> gr(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)(ff:[f]fs)=a -> b -> c -> d -> e -> f -> g -> hkaabbccddeeff([b] -> [c] -> [d] -> [e] -> [f] -> gr[b]bs[c]cs[d]ds[e]es[f]fs)foldr6_lefta -> b -> c -> d -> e -> f -> g -> h_hza_[b] -> [c] -> [d] -> [e] -> [f] -> g_[b]_[c]_[d]_[e]_[f]_=hzfoldr7_left::(a->b->c->d->e->f->g->h->i)->i->a->([b]->[c]->[d]->[e]->[f]->[g]->h)->[b]->[c]->[d]->[e]->[f]->[g]->ifoldr7_left :: (a -> b -> c -> d -> e -> f -> g -> h -> i)-> i-> a-> ([b] -> [c] -> [d] -> [e] -> [f] -> [g] -> h)-> [b]-> [c]-> [d]-> [e]-> [f]-> [g]-> ifoldr7_lefta -> b -> c -> d -> e -> f -> g -> h -> iki_zaa[b] -> [c] -> [d] -> [e] -> [f] -> [g] -> hr(bb:[b]bs)(cc:[c]cs)(dd:[d]ds)(ee:[e]es)(ff:[f]fs)(gg:[g]gs)=a -> b -> c -> d -> e -> f -> g -> h -> ikaabbccddeeffgg([b] -> [c] -> [d] -> [e] -> [f] -> [g] -> hr[b]bs[c]cs[d]ds[e]es[f]fs[g]gs)foldr7_lefta -> b -> c -> d -> e -> f -> g -> h -> i_iza_[b] -> [c] -> [d] -> [e] -> [f] -> [g] -> h_[b]_[c]_[d]_[e]_[f]_[g]_=iz{-# RULES"foldr4/left"forallkz(g::forallb.(a->b->b)->b->b).foldr4kz(buildg)=g(foldr4_leftkz)(\___->z)"foldr5/left"forallkz(g::forallb.(a->b->b)->b->b).foldr5kz(buildg)=g(foldr5_leftkz)(\____->z)"foldr6/left"forallkz(g::forallb.(a->b->b)->b->b).foldr6kz(buildg)=g(foldr6_leftkz)(\_____->z)"foldr7/left"forallkz(g::forallb.(a->b->b)->b->b).foldr7kz(buildg)=g(foldr7_leftkz)(\______->z)"zipWith4"[~1]forallfasbscsds.zipWith4fasbscsds=build(\cn->foldr4(zipWith4FBcf)nasbscsds)"zipWith5"[~1]forallfasbscsdses.zipWith5fasbscsdses=build(\cn->foldr5(zipWith5FBcf)nasbscsdses)"zipWith6"[~1]forallfasbscsdsesfs.zipWith6fasbscsdsesfs=build(\cn->foldr6(zipWith6FBcf)nasbscsdsesfs)"zipWith7"[~1]forallfasbscsdsesfsgs.zipWith7fasbscsdsesfsgs=build(\cn->foldr7(zipWith7FBcf)nasbscsdsesfsgs)"zipWith4List"[1]forallf.foldr4(zipWith4FB(:)f)[]=zipWith4f"zipWith5List"[1]forallf.foldr5(zipWith5FB(:)f)[]=zipWith5f"zipWith6List"[1]forallf.foldr6(zipWith6FB(:)f)[]=zipWith6f"zipWith7List"[1]forallf.foldr7(zipWith7FB(:)f)[]=zipWith7f#-}{-Note [Inline @unzipN@ functions]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~The inline principle for @unzip{4,5,6,7}@ is the same as 'unzip'/'unzip3' in"GHC.List".The 'unzip'/'unzip3' functions are inlined so that the `foldr` with which theyare defined has an opportunity to fuse.As such, since there are not any differences between 2/3-ary 'unzip' and itsn-ary counterparts below aside from the number of arguments, the `INLINE`pragma should be replicated in the @unzipN@ functions below as well.-}-- | The 'unzip4' function takes a list of quadruples and returns four-- lists, analogous to 'unzip'.{-# INLINEunzip4#-}-- Inline so that fusion with `foldr` has an opportunity to fire.-- See Note [Inline @unzipN@ functions] above.unzip4::[(a,b,c,d)]->([a],[b],[c],[d])unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])unzip4=((a, b, c, d) -> ([a], [b], [c], [d]) -> ([a], [b], [c], [d]))-> ([a], [b], [c], [d]) -> [(a, b, c, d)] -> ([a], [b], [c], [d])forall a b. (a -> b -> b) -> b -> [a] -> bfoldr(\(aa,bb,cc,dd)~([a]as,[b]bs,[c]cs,[d]ds)->(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]as,bbb -> [b] -> [b]forall a. a -> [a] -> [a]:[b]bs,ccc -> [c] -> [c]forall a. a -> [a] -> [a]:[c]cs,ddd -> [d] -> [d]forall a. a -> [a] -> [a]:[d]ds))([],[],[],[])-- | The 'unzip5' function takes a list of five-tuples and returns five-- lists, analogous to 'unzip'.{-# INLINEunzip5#-}-- Inline so that fusion with `foldr` has an opportunity to fire.-- See Note [Inline @unzipN@ functions] above.unzip5::[(a,b,c,d,e)]->([a],[b],[c],[d],[e])unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])unzip5=((a, b, c, d, e) -> ([a], [b], [c], [d], [e]) -> ([a], [b], [c], [d], [e]))-> ([a], [b], [c], [d], [e])-> [(a, b, c, d, e)]-> ([a], [b], [c], [d], [e])forall a b. (a -> b -> b) -> b -> [a] -> bfoldr(\(aa,bb,cc,dd,ee)~([a]as,[b]bs,[c]cs,[d]ds,[e]es)->(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]as,bbb -> [b] -> [b]forall a. a -> [a] -> [a]:[b]bs,ccc -> [c] -> [c]forall a. a -> [a] -> [a]:[c]cs,ddd -> [d] -> [d]forall a. a -> [a] -> [a]:[d]ds,eee -> [e] -> [e]forall a. a -> [a] -> [a]:[e]es))([],[],[],[],[])-- | The 'unzip6' function takes a list of six-tuples and returns six-- lists, analogous to 'unzip'.{-# INLINEunzip6#-}-- Inline so that fusion with `foldr` has an opportunity to fire.-- See Note [Inline @unzipN@ functions] above.unzip6::[(a,b,c,d,e,f)]->([a],[b],[c],[d],[e],[f])unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])unzip6=((a, b, c, d, e, f) -> ([a], [b], [c], [d], [e], [f]) -> ([a], [b], [c], [d], [e], [f]))-> ([a], [b], [c], [d], [e], [f])-> [(a, b, c, d, e, f)]-> ([a], [b], [c], [d], [e], [f])forall a b. (a -> b -> b) -> b -> [a] -> bfoldr(\(aa,bb,cc,dd,ee,ff)~([a]as,[b]bs,[c]cs,[d]ds,[e]es,[f]fs)->(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]as,bbb -> [b] -> [b]forall a. a -> [a] -> [a]:[b]bs,ccc -> [c] -> [c]forall a. a -> [a] -> [a]:[c]cs,ddd -> [d] -> [d]forall a. a -> [a] -> [a]:[d]ds,eee -> [e] -> [e]forall a. a -> [a] -> [a]:[e]es,fff -> [f] -> [f]forall a. a -> [a] -> [a]:[f]fs))([],[],[],[],[],[])-- | The 'unzip7' function takes a list of seven-tuples and returns-- seven lists, analogous to 'unzip'.{-# INLINEunzip7#-}-- Inline so that fusion with `foldr` has an opportunity to fire.-- See Note [Inline @unzipN@ functions] above.unzip7::[(a,b,c,d,e,f,g)]->([a],[b],[c],[d],[e],[f],[g])unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])unzip7=((a, b, c, d, e, f, g) -> ([a], [b], [c], [d], [e], [f], [g]) -> ([a], [b], [c], [d], [e], [f], [g]))-> ([a], [b], [c], [d], [e], [f], [g])-> [(a, b, c, d, e, f, g)]-> ([a], [b], [c], [d], [e], [f], [g])forall a b. (a -> b -> b) -> b -> [a] -> bfoldr(\(aa,bb,cc,dd,ee,ff,gg)~([a]as,[b]bs,[c]cs,[d]ds,[e]es,[f]fs,[g]gs)->(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]as,bbb -> [b] -> [b]forall a. a -> [a] -> [a]:[b]bs,ccc -> [c] -> [c]forall a. a -> [a] -> [a]:[c]cs,ddd -> [d] -> [d]forall a. a -> [a] -> [a]:[d]ds,eee -> [e] -> [e]forall a. a -> [a] -> [a]:[e]es,fff -> [f] -> [f]forall a. a -> [a] -> [a]:[f]fs,ggg -> [g] -> [g]forall a. a -> [a] -> [a]:[g]gs))([],[],[],[],[],[],[])-- | 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.deleteFirstsBy::(a->a->Bool)->[a]->[a]->[a]deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]deleteFirstsBya -> a -> Booleq=([a] -> a -> [a]) -> [a] -> [a] -> [a]forall a b. (b -> a -> b) -> b -> [a] -> bfoldl((a -> [a] -> [a]) -> [a] -> a -> [a]forall a b c. (a -> b -> c) -> b -> a -> cflip((a -> a -> Bool) -> a -> [a] -> [a]forall a. (a -> a -> Bool) -> a -> [a] -> [a]deleteBya -> a -> Booleq))-- | 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.group::Eqa=>[a]->[[a]]group :: [a] -> [[a]]group=(a -> a -> Bool) -> [a] -> [[a]]forall a. (a -> a -> Bool) -> [a] -> [[a]]groupBya -> a -> Boolforall a. Eq a => a -> a -> Bool(==)-- | The 'groupBy' function is the non-overloaded version of 'group'.groupBy::(a->a->Bool)->[a]->[[a]]groupBy :: (a -> a -> Bool) -> [a] -> [[a]]groupBya -> a -> Bool_[]=[]groupBya -> a -> Booleq(ax:[a]xs)=(axa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]ys)[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:(a -> a -> Bool) -> [a] -> [[a]]forall a. (a -> a -> Bool) -> [a] -> [[a]]groupBya -> a -> Booleq[a]zswhere([a]ys,[a]zs)=(a -> Bool) -> [a] -> ([a], [a])forall a. (a -> Bool) -> [a] -> ([a], [a])span(a -> a -> Booleqax)[a]xs-- | The 'inits' function returns all initial segments of the argument,-- shortest first. For example,---- >>> inits "abc"-- ["","a","ab","abc"]---- Note that 'inits' has the following strictness property:-- @inits (xs ++ _|_) = inits xs ++ _|_@---- In particular,-- @inits _|_ = [] : _|_@inits::[a]->[[a]]inits :: [a] -> [[a]]inits=(SnocBuilder a -> [a]) -> [SnocBuilder a] -> [[a]]forall a b. (a -> b) -> [a] -> [b]mapSnocBuilder a -> [a]forall a. SnocBuilder a -> [a]toListSB([SnocBuilder a] -> [[a]])-> ([a] -> [SnocBuilder a]) -> [a] -> [[a]]forall b c a. (b -> c) -> (a -> b) -> a -> c.(SnocBuilder a -> a -> SnocBuilder a)-> SnocBuilder a -> [a] -> [SnocBuilder a]forall b a. (b -> a -> b) -> b -> [a] -> [b]scanl'SnocBuilder a -> a -> SnocBuilder aforall a. SnocBuilder a -> a -> SnocBuilder asnocSBSnocBuilder aforall a. SnocBuilder aemptySB{-# NOINLINEinits#-}-- We do not allow inits to inline, because it plays havoc with Call Arity-- if it fuses with a consumer, and it would generally lead to serious-- loss of sharing if allowed to fuse with a producer.-- | \(\mathcal{O}(n)\). The 'tails' function returns all final segments of the-- argument, longest first. For example,---- >>> tails "abc"-- ["abc","bc","c",""]---- Note that 'tails' has the following strictness property:-- @tails _|_ = _|_ : _|_@tails::[a]->[[a]]{-# INLINABLEtails#-}tails :: [a] -> [[a]]tails[a]lst=(forall b. ([a] -> b -> b) -> b -> b) -> [[a]]forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]build(\[a] -> b -> bcbn->lettailsGo :: [a] -> btailsGo[a]xs=[a]xs[a] -> b -> b`c`case[a]xsof[]->bn_:xs'->[a] -> btailsGo[a]xs'in[a] -> btailsGo[a]lst)-- | The 'subsequences' function returns the list of all subsequences of the argument.---- >>> subsequences "abc"-- ["","a","b","ab","c","ac","bc","abc"]subsequences::[a]->[[a]]subsequences :: [a] -> [[a]]subsequences[a]xs=[][a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[a] -> [[a]]forall a. [a] -> [[a]]nonEmptySubsequences[a]xs-- | The 'nonEmptySubsequences' function returns the list of all subsequences of the argument,-- except for the empty list.---- >>> nonEmptySubsequences "abc"-- ["a","b","ab","c","ac","bc","abc"]nonEmptySubsequences::[a]->[[a]]nonEmptySubsequences :: [a] -> [[a]]nonEmptySubsequences[]=[]nonEmptySubsequences(ax:[a]xs)=[ax][a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:([a] -> [[a]] -> [[a]]) -> [[a]] -> [[a]] -> [[a]]forall a b. (a -> b -> b) -> b -> [a] -> bfoldr[a] -> [[a]] -> [[a]]f[]([a] -> [[a]]forall a. [a] -> [[a]]nonEmptySubsequences[a]xs)wheref :: [a] -> [[a]] -> [[a]]f[a]ys[[a]]r=[a]ys[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:(axa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]ys)[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[[a]]r-- | The 'permutations' function returns the list of all permutations of the argument.---- >>> permutations "abc"-- ["abc","bac","cba","bca","cab","acb"]permutations::[a]->[[a]]permutations :: [a] -> [[a]]permutations[a]xs0=[a]xs0[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[a] -> [a] -> [[a]]forall a. [a] -> [a] -> [[a]]perms[a]xs0[]whereperms :: [a] -> [a] -> [[a]]perms[][a]_=[]perms(at:[a]ts)[a]is=([a] -> [[a]] -> [[a]]) -> [[a]] -> [[a]] -> [[a]]forall a b. (a -> b -> b) -> b -> [a] -> bfoldr[a] -> [[a]] -> [[a]]interleave([a] -> [a] -> [[a]]perms[a]ts(ata -> [a] -> [a]forall a. a -> [a] -> [a]:[a]is))([a] -> [[a]]forall a. [a] -> [[a]]permutations[a]is)whereinterleave :: [a] -> [[a]] -> [[a]]interleave[a]xs[[a]]r=let([a]_,[[a]]zs)=([a] -> [a]) -> [a] -> [[a]] -> ([a], [[a]])forall c. ([a] -> c) -> [a] -> [c] -> ([a], [c])interleave'[a] -> [a]forall a. a -> aid[a]xs[[a]]rin[[a]]zsinterleave' :: ([a] -> c) -> [a] -> [c] -> ([a], [c])interleave'[a] -> c_[][c]r=([a]ts,[c]r)interleave'[a] -> cf(ay:[a]ys)[c]r=let([a]us,[c]zs)=([a] -> c) -> [a] -> [c] -> ([a], [c])interleave'([a] -> cf([a] -> c) -> ([a] -> [a]) -> [a] -> cforall b c a. (b -> c) -> (a -> b) -> a -> c.(aya -> [a] -> [a]forall a. a -> [a] -> [a]:))[a]ys[c]rin(aya -> [a] -> [a]forall a. a -> [a] -> [a]:[a]us,[a] -> cf(ata -> [a] -> [a]forall a. a -> [a] -> [a]:aya -> [a] -> [a]forall a. a -> [a] -> [a]:[a]us)c -> [c] -> [c]forall a. a -> [a] -> [a]:[c]zs)-------------------------------------------------------------------------------- Quick Sort algorithm taken from HBC's QSort library.-- | 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 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]sort::(Orda)=>[a]->[a]-- | The 'sortBy' function is the non-overloaded version of 'sort'.---- >>> sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")]-- [(1,"Hello"),(2,"world"),(4,"!")]sortBy::(a->a->Ordering)->[a]->[a]#if defined(USE_REPORT_PRELUDE)sort=sortBycomparesortBycmp=foldr(insertBycmp)[]#else{-GHC's mergesort replaced by a better implementation, 24/12/2009.This code originally contributed to the nhc12 compiler by Thomas Nordinin 2002. Rumoured to have been based on code by Lennart Augustsson, e.g. http://www.mail-archive.com/haskell@haskell.org/msg01822.htmland possibly to bear similarities to a 1982 paper by Richard O'Keefe:"A smooth applicative merge sort".Benchmarks show it to be often 2x the speed of the previous implementation.Fixes ticket https://gitlab.haskell.org/ghc/ghc/issues/2143-}sort :: [a] -> [a]sort=(a -> a -> Ordering) -> [a] -> [a]forall a. (a -> a -> Ordering) -> [a] -> [a]sortBya -> a -> Orderingforall a. Ord a => a -> a -> OrderingcomparesortBy :: (a -> a -> Ordering) -> [a] -> [a]sortBya -> a -> Orderingcmp=[[a]] -> [a]mergeAll([[a]] -> [a]) -> ([a] -> [[a]]) -> [a] -> [a]forall b c a. (b -> c) -> (a -> b) -> a -> c.[a] -> [[a]]sequenceswheresequences :: [a] -> [[a]]sequences(aa:ab:[a]xs)|aaa -> a -> Ordering`cmp`abOrdering -> Ordering -> Boolforall a. Eq a => a -> a -> Bool==OrderingGT=a -> [a] -> [a] -> [[a]]descendingab[aa][a]xs|Boolotherwise=a -> ([a] -> [a]) -> [a] -> [[a]]ascendingab(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:)[a]xssequences[a]xs=[[a]xs]descending :: a -> [a] -> [a] -> [[a]]descendingaa[a]as(ab:[a]bs)|aaa -> a -> Ordering`cmp`abOrdering -> Ordering -> Boolforall a. Eq a => a -> a -> Bool==OrderingGT=a -> [a] -> [a] -> [[a]]descendingab(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]as)[a]bsdescendingaa[a]as[a]bs=(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]as)[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[a] -> [[a]]sequences[a]bsascending :: a -> ([a] -> [a]) -> [a] -> [[a]]ascendingaa[a] -> [a]as(ab:[a]bs)|aaa -> a -> Ordering`cmp`abOrdering -> Ordering -> Boolforall a. Eq a => a -> a -> Bool/=OrderingGT=a -> ([a] -> [a]) -> [a] -> [[a]]ascendingab(\[a]ys->[a] -> [a]as(aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]ys))[a]bsascendingaa[a] -> [a]as[a]bs=let!x :: [a]x=[a] -> [a]as[aa]in[a]x[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[a] -> [[a]]sequences[a]bsmergeAll :: [[a]] -> [a]mergeAll[[a]x]=[a]xmergeAll[[a]]xs=[[a]] -> [a]mergeAll([[a]] -> [[a]]mergePairs[[a]]xs)mergePairs :: [[a]] -> [[a]]mergePairs([a]a:[a]b:[[a]]xs)=let!x :: [a]x=[a] -> [a] -> [a]merge[a]a[a]bin[a]x[a] -> [[a]] -> [[a]]forall a. a -> [a] -> [a]:[[a]] -> [[a]]mergePairs[[a]]xsmergePairs[[a]]xs=[[a]]xsmerge :: [a] -> [a] -> [a]mergeas :: [a]as@(aa:[a]as')bs :: [a]bs@(ab:[a]bs')|aaa -> a -> Ordering`cmp`abOrdering -> Ordering -> Boolforall a. Eq a => a -> a -> Bool==OrderingGT=aba -> [a] -> [a]forall a. a -> [a] -> [a]:[a] -> [a] -> [a]merge[a]as[a]bs'|Boolotherwise=aaa -> [a] -> [a]forall a. a -> [a] -> [a]:[a] -> [a] -> [a]merge[a]as'[a]bsmerge[][a]bs=[a]bsmerge[a]as[]=[a]as{-sortBy cmp l = mergesort cmp lsort l = mergesort compare lQuicksort replaced by mergesort, 14/5/2002.From: Ian Lynagh <igloo@earth.li>I am curious as to why the List.sort implementation in GHC is aquicksort algorithm rather than an algorithm that guarantees n log ntime in the worst case? I have attached a mergesort implementation alongwith a few scripts to time it's performance, the results of which areshown below (* means it didn't finish successfully - in all cases thiswas due to a stack overflow).If I heap profile the random_list case with only 10000 then I seerandom_list peaks at using about 2.5M of memory, whereas in the sameprogram using List.sort it uses only 100k.Input style Input length Sort data Sort alg User timestdin 10000 random_list sort 2.82stdin 10000 random_list mergesort 2.96stdin 10000 sorted sort 31.37stdin 10000 sorted mergesort 1.90stdin 10000 revsorted sort 31.21stdin 10000 revsorted mergesort 1.88stdin 100000 random_list sort *stdin 100000 random_list mergesort *stdin 100000 sorted sort *stdin 100000 sorted mergesort *stdin 100000 revsorted sort *stdin 100000 revsorted mergesort *func 10000 random_list sort 0.31func 10000 random_list mergesort 0.91func 10000 sorted sort 19.09func 10000 sorted mergesort 0.15func 10000 revsorted sort 19.17func 10000 revsorted mergesort 0.16func 100000 random_list sort 3.85func 100000 random_list mergesort *func 100000 sorted sort 5831.47func 100000 sorted mergesort 2.23func 100000 revsorted sort 5872.34func 100000 revsorted mergesort 2.24mergesort :: (a -> a -> Ordering) -> [a] -> [a]mergesort cmp = mergesort' cmp . map wrapmergesort' :: (a -> a -> Ordering) -> [[a]] -> [a]mergesort' _ [] = []mergesort' _ [xs] = xsmergesort' cmp xss = mergesort' cmp (merge_pairs cmp xss)merge_pairs :: (a -> a -> Ordering) -> [[a]] -> [[a]]merge_pairs _ [] = []merge_pairs _ [xs] = [xs]merge_pairs cmp (xs:ys:xss) = merge cmp xs ys : merge_pairs cmp xssmerge :: (a -> a -> Ordering) -> [a] -> [a] -> [a]merge _ [] ys = ysmerge _ xs [] = xsmerge cmp (x:xs) (y:ys) = case x `cmp` y of GT -> y : merge cmp (x:xs) ys _ -> x : merge cmp xs (y:ys)wrap :: a -> [a]wrap x = [x]OLDER: qsort version-- qsort is stable and does not concatenate.qsort :: (a -> a -> Ordering) -> [a] -> [a] -> [a]qsort _ [] r = rqsort _ [x] r = x:rqsort cmp (x:xs) r = qpart cmp x xs [] [] r-- qpart partitions and sorts the sublistsqpart :: (a -> a -> Ordering) -> a -> [a] -> [a] -> [a] -> [a] -> [a]qpart cmp x [] rlt rge r = -- rlt and rge are in reverse order and must be sorted with an -- anti-stable sorting rqsort cmp rlt (x:rqsort cmp rge r)qpart cmp x (y:ys) rlt rge r = case cmp x y of GT -> qpart cmp x ys (y:rlt) rge r _ -> qpart cmp x ys rlt (y:rge) r-- rqsort is as qsort but anti-stable, i.e. reverses equal elementsrqsort :: (a -> a -> Ordering) -> [a] -> [a] -> [a]rqsort _ [] r = rrqsort _ [x] r = x:rrqsort cmp (x:xs) r = rqpart cmp x xs [] [] rrqpart :: (a -> a -> Ordering) -> a -> [a] -> [a] -> [a] -> [a] -> [a]rqpart cmp x [] rle rgt r = qsort cmp rle (x:qsort cmp rgt r)rqpart cmp x (y:ys) rle rgt r = case cmp y x of GT -> rqpart cmp x ys rle (y:rgt) r _ -> rqpart cmp x ys (y:rle) rgt r-}#endif /* USE_REPORT_PRELUDE */-- | 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 4.8.0.0sortOn::Ordb=>(a->b)->[a]->[a]sortOn :: (a -> b) -> [a] -> [a]sortOna -> bf=((b, a) -> a) -> [(b, a)] -> [a]forall a b. (a -> b) -> [a] -> [b]map(b, a) -> aforall a b. (a, b) -> bsnd([(b, a)] -> [a]) -> ([a] -> [(b, a)]) -> [a] -> [a]forall b c a. (b -> c) -> (a -> b) -> a -> c.((b, a) -> (b, a) -> Ordering) -> [(b, a)] -> [(b, a)]forall a. (a -> a -> Ordering) -> [a] -> [a]sortBy(((b, a) -> b) -> (b, a) -> (b, a) -> Orderingforall a b. Ord a => (b -> a) -> b -> b -> Orderingcomparing(b, a) -> bforall a b. (a, b) -> afst)([(b, a)] -> [(b, a)]) -> ([a] -> [(b, a)]) -> [a] -> [(b, a)]forall b c a. (b -> c) -> (a -> b) -> a -> c.(a -> (b, a)) -> [a] -> [(b, a)]forall a b. (a -> b) -> [a] -> [b]map(\ax->lety :: by=a -> bfaxinbyb -> (b, a) -> (b, a)`seq`(by,ax))-- | 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]---- Note [INLINE unfoldr]-- We treat unfoldr a little differently from some other forms for list fusion-- for two reasons:---- 1. We don't want to use a rule to rewrite a basic form to a fusible-- form because this would inline before constant floating. As Simon Peyton--- Jones and others have pointed out, this could reduce sharing in some cases-- where sharing is beneficial. Thus we simply INLINE it, which is, for-- example, how enumFromTo::Int becomes eftInt. Unfortunately, we don't seem-- to get enough of an inlining discount to get a version of eftInt based on-- unfoldr to inline as readily as the usual one. We know that all the Maybe-- nonsense will go away, but the compiler does not.---- 2. The benefit of inlining unfoldr is likely to be huge in many common cases,-- even apart from list fusion. In particular, inlining unfoldr often-- allows GHC to erase all the Maybes. This appears to be critical if unfoldr-- is to be used in high-performance code. A small increase in code size-- in the relatively rare cases when this does not happen looks like a very-- small price to pay.---- Doing a back-and-forth dance doesn't seem to accomplish anything if the-- final form has to be inlined in any case.unfoldr::(b->Maybe(a,b))->b->[a]{-# INLINEunfoldr#-}-- See Note [INLINE unfoldr]unfoldr :: (b -> Maybe (a, b)) -> b -> [a]unfoldrb -> Maybe (a, b)fbb0=(forall b. (a -> b -> b) -> b -> b) -> [a]forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]build(\a -> b -> bcbn->letgo :: b -> bgobb=caseb -> Maybe (a, b)fbbofJust(aa,bnew_b)->aaa -> b -> b`c`b -> bgobnew_bMaybe (a, b)Nothing->bninb -> bgobb0)-- ------------------------------------------------------------------------------- Functions on strings-- | '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 @'lines' s@ contains at least as many elements as newlines in @s@.lines::String->[String]lines :: [Char] -> [[Char]]lines[Char]""=[]-- Somehow GHC doesn't detect the selector thunks in the below code,-- so s' keeps a reference to the first line via the pair and we have-- a space leak (cf. #4334).-- So we need to make GHC see the selector thunks with a trick.lines[Char]s=([Char], [[Char]]) -> [[Char]]forall a. (a, [a]) -> [a]cons(case(Char -> Bool) -> [Char] -> ([Char], [Char])forall a. (a -> Bool) -> [a] -> ([a], [a])break(Char -> Char -> Boolforall a. Eq a => a -> a -> Bool==Char'\n')[Char]sof([Char]l,[Char]s')->([Char]l,case[Char]s'of[]->[]Char_:[Char]s''->[Char] -> [[Char]]lines[Char]s''))wherecons :: (a, [a]) -> [a]cons~(ah,[a]t)=aha -> [a] -> [a]forall a. a -> [a] -> [a]:[a]t-- | 'unlines' is an inverse operation to 'lines'.-- It joins lines, after appending a terminating newline to each.---- >>> unlines ["Hello", "World", "!"]-- "Hello\nWorld\n!\n"unlines::[String]->String#if defined(USE_REPORT_PRELUDE)unlines=concatMap(++"\n")#else-- HBC version (stolen)-- here's a more efficient versionunlines :: [[Char]] -> [Char]unlines[]=[]unlines([Char]l:[[Char]]ls)=[Char]l[Char] -> [Char] -> [Char]forall a. [a] -> [a] -> [a]++Char'\n'Char -> [Char] -> [Char]forall a. a -> [a] -> [a]:[[Char]] -> [Char]unlines[[Char]]ls#endif-- | 'words' breaks a string up into a list of words, which were delimited-- by white space.---- >>> words "Lorem ipsum\ndolor"-- ["Lorem","ipsum","dolor"]words::String->[String]{-# NOINLINE[1]words#-}words :: [Char] -> [[Char]]words[Char]s=case(Char -> Bool) -> [Char] -> [Char]forall a. (a -> Bool) -> [a] -> [a]dropWhile{-partain:Char.-}Char -> BoolisSpace[Char]sof[Char]""->[][Char]s'->[Char]w[Char] -> [[Char]] -> [[Char]]forall a. a -> [a] -> [a]:[Char] -> [[Char]]words[Char]s''where([Char]w,[Char]s'')=(Char -> Bool) -> [Char] -> ([Char], [Char])forall a. (a -> Bool) -> [a] -> ([a], [a])break{-partain:Char.-}Char -> BoolisSpace[Char]s'{-# RULES"words"[~1]foralls.wordss=build(\cn->wordsFBcns)"wordsList"[1]wordsFB(:)[]=words#-}wordsFB::([Char]->b->b)->b->String->b{-# INLINE[0]wordsFB#-}-- See Note [Inline FB functions] in GHC.ListwordsFB :: ([Char] -> b -> b) -> b -> [Char] -> bwordsFB[Char] -> b -> bcbn=[Char] -> bgowherego :: [Char] -> bgo[Char]s=case(Char -> Bool) -> [Char] -> [Char]forall a. (a -> Bool) -> [a] -> [a]dropWhileChar -> BoolisSpace[Char]sof[Char]""->bn[Char]s'->[Char]w[Char] -> b -> b`c`[Char] -> bgo[Char]s''where([Char]w,[Char]s'')=(Char -> Bool) -> [Char] -> ([Char], [Char])forall a. (a -> Bool) -> [a] -> ([a], [a])breakChar -> BoolisSpace[Char]s'-- | 'unwords' is an inverse operation to 'words'.-- It joins words with separating spaces.---- >>> unwords ["Lorem", "ipsum", "dolor"]-- "Lorem ipsum dolor"unwords::[String]->String#if defined(USE_REPORT_PRELUDE)unwords[]=""unwordsws=foldr1(\ws->w++' ':s)ws#else-- Here's a lazier version that can get the last element of a-- _|_-terminated list.{-# NOINLINE[1]unwords#-}unwords :: [[Char]] -> [Char]unwords[]=[Char]""unwords([Char]w:[[Char]]ws)=[Char]w[Char] -> [Char] -> [Char]forall a. [a] -> [a] -> [a]++[[Char]] -> [Char]go[[Char]]wswherego :: [[Char]] -> [Char]go[]=[Char]""go([Char]v:[[Char]]vs)=Char' 'Char -> [Char] -> [Char]forall a. a -> [a] -> [a]:([Char]v[Char] -> [Char] -> [Char]forall a. [a] -> [a] -> [a]++[[Char]] -> [Char]go[[Char]]vs)-- In general, the foldr-based version is probably slightly worse-- than the HBC version, because it adds an extra space and then takes-- it back off again. But when it fuses, it reduces allocation. How much-- depends entirely on the average word length--it's most effective when-- the words are on the short side.{-# RULES"unwords"[~1]forallws.unwordsws=tailUnwords(foldrunwordsFB""ws)"unwordsList"[1]forallws.tailUnwords(foldrunwordsFB""ws)=unwordsws#-}{-# INLINE[0]tailUnwords#-}tailUnwords::String->StringtailUnwords :: [Char] -> [Char]tailUnwords[]=[]tailUnwords(Char_:[Char]xs)=[Char]xs{-# INLINE[0]unwordsFB#-}unwordsFB::String->String->StringunwordsFB :: [Char] -> [Char] -> [Char]unwordsFB[Char]w[Char]r=Char' 'Char -> [Char] -> [Char]forall a. a -> [a] -> [a]:[Char]w[Char] -> [Char] -> [Char]forall a. [a] -> [a] -> [a]++[Char]r#endif{- A "SnocBuilder" is a version of Chris Okasaki's banker's queue that supportstoListSB instead of uncons. In single-threaded use, its performancecharacteristics are similar to John Hughes's functional difference lists, butlikely somewhat worse. In heavily persistent settings, however, it does muchbetter, because it takes advantage of sharing. The banker's queue guarantees(amortized) O(1) snoc and O(1) uncons, meaning that we can think of toListSB asan O(1) conversion to a list-like structure a constant factor slower thannormal lists--we pay the O(n) cost incrementally as we consume the list. Usingfunctional difference lists, on the other hand, we would have to pay the wholecost up front for each output list. -}{- We store a front list, a rear list, and the length of the queue. Because weonly snoc onto the queue and never uncons, we know it's time to rotate when thelength of the queue plus 1 is a power of 2. Note that we rely on the value ofthe length field only for performance. In the unlikely event of overflow, theperformance will suffer but the semantics will remain correct. -}dataSnocBuildera=SnocBuilder{-# UNPACK#-}!Word[a][a]{- Smart constructor that rotates the builder when lp is one minus a power of2. Does not rotate very small builders because doing so is not worth thetrouble. The lp < 255 test goes first because the power-of-2 test gives awfulbranch prediction for very small n (there are 5 powers of 2 between 1 and16). Putting the well-predicted lp < 255 test first avoids branching on thepower-of-2 test until powers of 2 have become sufficiently rare to be predictedwell. -}{-# INLINEsb#-}sb::Word->[a]->[a]->SnocBuilderasb :: Word -> [a] -> [a] -> SnocBuilder asbWordlp[a]f[a]r|WordlpWord -> Word -> Boolforall a. Ord a => a -> a -> Bool<Word255Bool -> Bool -> Bool||(WordlpWord -> Word -> Wordforall a. Bits a => a -> a -> a.&.(WordlpWord -> Word -> Wordforall a. Num a => a -> a -> a+Word1))Word -> Word -> Boolforall a. Eq a => a -> a -> Bool/=Word0=Word -> [a] -> [a] -> SnocBuilder aforall a. Word -> [a] -> [a] -> SnocBuilder aSnocBuilderWordlp[a]f[a]r|Boolotherwise=Word -> [a] -> [a] -> SnocBuilder aforall a. Word -> [a] -> [a] -> SnocBuilder aSnocBuilderWordlp([a]f[a] -> [a] -> [a]forall a. [a] -> [a] -> [a]++[a] -> [a]forall a. [a] -> [a]reverse[a]r)[]-- The empty builderemptySB::SnocBuilderaemptySB :: SnocBuilder aemptySB=Word -> [a] -> [a] -> SnocBuilder aforall a. Word -> [a] -> [a] -> SnocBuilder aSnocBuilderWord0[][]-- Add an element to the end of a queue.snocSB::SnocBuildera->a->SnocBuilderasnocSB :: SnocBuilder a -> a -> SnocBuilder asnocSB(SnocBuilderWordlp[a]f[a]r)ax=Word -> [a] -> [a] -> SnocBuilder aforall a. Word -> [a] -> [a] -> SnocBuilder asb(WordlpWord -> Word -> Wordforall a. Num a => a -> a -> a+Word1)[a]f(axa -> [a] -> [a]forall a. a -> [a] -> [a]:[a]r)-- Convert a builder to a listtoListSB::SnocBuildera->[a]toListSB :: SnocBuilder a -> [a]toListSB(SnocBuilderWord_[a]f[a]r)=[a]f[a] -> [a] -> [a]forall a. [a] -> [a] -> [a]++[a] -> [a]forall a. [a] -> [a]reverse[a]r
[8]ページ先頭