| Copyright | (c) The University of Glasgow 2001 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
GHC.Internal.Data.List
Description
Operations on lists.
Synopsis
- data List a
- (++) :: [a] -> [a] -> [a]
- head :: HasCallStack => [a] -> a
- last :: HasCallStack => [a] -> a
- tail :: HasCallStack => [a] -> [a]
- init :: HasCallStack => [a] -> [a]
- uncons :: [a] -> Maybe (a, [a])
- unsnoc :: [a] -> Maybe ([a], a)
- singleton :: a -> [a]
- null :: Foldable t => t a -> Bool
- length :: Foldable t => t a -> Int
- map :: (a -> b) -> [a] -> [b]
- reverse :: [a] -> [a]
- intersperse :: a -> [a] -> [a]
- intercalate :: [a] -> [[a]] -> [a]
- transpose :: [[a]] -> [[a]]
- subsequences :: [a] -> [[a]]
- permutations :: [a] -> [[a]]
- foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl1 :: Foldable t => (a -> a -> a) -> t a -> a
- foldl1' :: HasCallStack => (a -> a -> a) -> [a] -> a
- foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- foldr1 :: Foldable t => (a -> a -> a) -> t a -> a
- concat :: Foldable t => t [a] -> [a]
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- and :: Foldable t => t Bool -> Bool
- or :: Foldable t => t Bool -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- sum :: (Foldable t, Num a) => t a -> a
- product :: (Foldable t, Num a) => t a -> a
- maximum :: (Foldable t, Ord a) => t a -> a
- minimum :: (Foldable t, Ord a) => t a -> a
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- scanl' :: (b -> a -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
- mapAccumR :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
- iterate :: (a -> a) -> a -> [a]
- iterate' :: (a -> a) -> a -> [a]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- cycle :: HasCallStack => [a] -> [a]
- unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- dropWhileEnd :: (a -> Bool) -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
- group :: Eq a => [a] -> [[a]]
- inits :: [a] -> [[a]]
- tails :: [a] -> [[a]]
- isPrefixOf :: Eq a => [a] -> [a] -> Bool
- isSuffixOf :: Eq a => [a] -> [a] -> Bool
- isInfixOf :: Eq a => [a] -> [a] -> Bool
- isSubsequenceOf :: Eq a => [a] -> [a] -> Bool
- elem :: (Foldable t, Eq a) => a -> t a -> Bool
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- find :: Foldable t => (a -> Bool) -> t a -> Maybe a
- filter :: (a -> Bool) -> [a] -> [a]
- partition :: (a -> Bool) -> [a] -> ([a], [a])
- (!?) :: [a] -> Int -> Maybe a
- (!!) :: HasCallStack => [a] -> Int -> a
- elemIndex :: Eq a => a -> [a] -> Maybe Int
- elemIndices :: Eq a => a -> [a] -> [Int]
- findIndex :: (a -> Bool) -> [a] -> Maybe Int
- findIndices :: (a -> Bool) -> [a] -> [Int]
- zip :: [a] -> [b] -> [(a, b)]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- zip4 :: [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
- zip5 :: [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
- zip6 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
- zip7 :: [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zipWith4 :: (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
- zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip4 :: [(a, b, c, d)] -> ([a], [b], [c], [d])
- unzip5 :: [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
- unzip6 :: [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
- unzip7 :: [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
- lines :: String -> [String]
- words :: String -> [String]
- unlines :: [String] -> String
- unwords :: [String] -> String
- nub :: Eq a => [a] -> [a]
- delete :: Eq a => a -> [a] -> [a]
- (\\) :: Eq a => [a] -> [a] -> [a]
- union :: Eq a => [a] -> [a] -> [a]
- intersect :: Eq a => [a] -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- insert :: Ord a => a -> [a] -> [a]
- nubBy :: (a -> a -> Bool) -> [a] -> [a]
- deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a]
- deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a]
- groupBy :: (a -> a -> Bool) -> [a] -> [[a]]
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]
- insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
- maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- genericLength :: Num i => [a] -> i
- genericTake :: Integral i => i -> [a] -> [a]
- genericDrop :: Integral i => i -> [a] -> [a]
- genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
- genericIndex :: Integral i => [a] -> i -> a
- genericReplicate :: Integral i => i -> a -> [a]
Documentation
The builtin linked list type.
In Haskell, lists are one of the most important data types as they are often used analogous to loops in imperative programming languages. These lists are singly linked, which makes them unsuited for operations that require \(\mathcal{O}(1)\) access. Instead, they are intended to be traversed.
You can use List a or [a] in type signatures:
length :: [a] -> Int
or
length :: List a -> Int
They are fully equivalent, and List a will be normalised to [a].
Usage
Lists are constructed recursively using the right-associative constructor operator (or cons)
 (:) :: a -> [a] -> [a], which prepends an element to a list,
 and the empty list [].
(1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]
Lists can also be constructed using list literals
 of the form [x_1, x_2, ..., x_n]
 which are syntactic sugar and, unless -XOverloadedLists is enabled,
 are translated into uses of (:) and []
String literals, like "I 💜 hs", are translated into
 Lists of characters, ['I', ' ', '💜', ' ', 'h', 's'].
Implementation
Internally and in memory, all the above are represented like this, with arrows being pointers to locations in memory.
╭───┬───┬──╮   ╭───┬───┬──╮   ╭───┬───┬──╮   ╭────╮
│(:)│   │ ─┼──>│(:)│   │ ─┼──>│(:)│   │ ─┼──>│ [] │
╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰────╯
      v              v              v
      1              2              3Examples
>>> ['H', 'a', 's', 'k', 'e', 'l', 'l'] "Haskell"
>>> 1 : [4, 1, 5, 9] [1,4,1,5,9]
>>> [] : [] : [] [[],[]]
Since: ghc-internal-0.10.0
Instances
| Alternative [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 | ||||
| Applicative [] Source # | Since: base-2.1 | ||||
| Functor [] Source # | Since: base-2.1 | ||||
| Monad [] Source # | Since: base-2.1 | ||||
| MonadPlus [] Source # | Combines lists by concatenation, starting from the empty list. Since: base-2.1 | ||||
| MonadFail [] Source # | Since: base-4.9.0.0 | ||||
| Defined in GHC.Internal.Control.Monad.Fail Methods fail :: HasCallStack => String -> [a] Source # | |||||
| MonadFix [] Source # | Since: base-2.1 | ||||
| Defined in GHC.Internal.Control.Monad.Fix | |||||
| MonadZip [] Source # | Since: ghc-internal-4.3.1.0 | ||||
| Foldable [] Source # | Since: base-2.1 | ||||
| Defined in GHC.Internal.Data.Foldable Methods fold :: Monoid m => [m] -> m Source # foldMap :: Monoid m => (a -> m) -> [a] -> m Source # foldMap' :: Monoid m => (a -> m) -> [a] -> m Source # foldr :: (a -> b -> b) -> b -> [a] -> b Source # foldr' :: (a -> b -> b) -> b -> [a] -> b Source # foldl :: (b -> a -> b) -> b -> [a] -> b Source # foldl' :: (b -> a -> b) -> b -> [a] -> b Source # foldr1 :: (a -> a -> a) -> [a] -> a Source # foldl1 :: (a -> a -> a) -> [a] -> a Source # elem :: Eq a => a -> [a] -> Bool Source # maximum :: Ord a => [a] -> a Source # minimum :: Ord a => [a] -> a Source # | |||||
| Traversable [] Source # | Since: base-2.1 | ||||
| Generic1 [] Source # | |||||
| Defined in GHC.Internal.Generics Associated Types 
 | |||||
| Lift a => Lift ([a] :: Type) Source # | |||||
| Monoid [a] Source # | Since: base-2.1 | ||||
| Semigroup [a] Source # | Since: base-4.9.0.0 | ||||
| Eq a => Eq [a] Source # | |||||
| Ord a => Ord [a] Source # | |||||
| Data a => Data [a] Source # | For historical reasons, the constructor name used for  Since: base-4.0.0.0 | ||||
| Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> [a] -> c [a] Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c [a] Source # toConstr :: [a] -> Constr Source # dataTypeOf :: [a] -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c [a]) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c [a]) Source # gmapT :: (forall b. Data b => b -> b) -> [a] -> [a] Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> [a] -> r Source # gmapQ :: (forall d. Data d => d -> u) -> [a] -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> [a] -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> [a] -> m [a] Source # | |||||
| a ~ Char => IsString [a] Source # | 
 Since: base-2.1 | ||||
| Defined in GHC.Internal.Data.String Methods fromString :: String -> [a] Source # | |||||
| Generic [a] Source # | |||||
| Defined in GHC.Internal.Generics Associated Types 
 | |||||
| IsList [a] Source # | Since: base-4.7.0.0 | ||||
| Read a => Read [a] Source # | Since: base-2.1 | ||||
| Show a => Show [a] Source # | Since: base-2.1 | ||||
| type Rep1 [] Source # | Since: base-4.6.0.0 | ||||
| Defined in GHC.Internal.Generics type Rep1 [] = D1 ('MetaData "List" "GHC.Internal.Types" "ghc-internal" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
| type Rep [a] Source # | Since: base-4.6.0.0 | ||||
| Defined in GHC.Internal.Generics type Rep [a] = D1 ('MetaData "List" "GHC.Internal.Types" "ghc-internal" 'False) (C1 ('MetaCons "[]" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |||||
| type Item [a] Source # | |||||
| Defined in GHC.Internal.IsList type Item [a] = a | |||||
Basic functions
(++) :: [a] -> [a] -> [a] infixr 5 Source #
(++) appends 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.
Performance considerations
This function takes linear time in the number of elements of the
 first list. Thus it is better to associate repeated
 applications of (++) to the right (which is the default behaviour):
 xs ++ (ys ++ zs) or simply xs ++ ys ++ zs, but not (xs ++ ys) ++ zs.
 For the same reason concat = foldr (++) []
 has linear performance, while foldl (++) [] is prone
 to quadratic slowdown
Examples
>>>[1, 2, 3] ++ [4, 5, 6][1,2,3,4,5,6]
>>>[] ++ [1, 2, 3][1,2,3]
>>>[3, 2, 1] ++ [][3,2,1]
head :: HasCallStack => [a] -> a Source #
Warning: This is a partial function, it throws an error on empty lists. Use pattern matching, uncons or listToMaybe instead. Consider refactoring to use Data.List.NonEmpty.
\(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.
To disable the warning about partiality put {-# OPTIONS_GHC -Wno-x-partial -Wno-unrecognised-warning-flags #-}
 at the top of the file. To disable it throughout a package put the same
 options into ghc-options section of Cabal file. To disable it in GHCi
 put :set -Wno-x-partial -Wno-unrecognised-warning-flags into ~/.ghci config file.
 See also the migration guide.
Examples
>>>head [1, 2, 3]1
>>>head [1..]1
>>>head []*** Exception: Prelude.head: empty list
last :: HasCallStack => [a] -> a Source #
\(\mathcal{O}(n)\). Extract the last element of a list, which must be finite and non-empty.
WARNING: This function is partial. Consider using unsnoc instead.
Examples
>>>last [1, 2, 3]3
>>>last [1..]* Hangs forever *
>>>last []*** Exception: Prelude.last: empty list
tail :: HasCallStack => [a] -> [a] Source #
Warning: This is a partial function, it throws an error on empty lists. Replace it with drop 1, or use pattern matching or uncons instead. Consider refactoring to use Data.List.NonEmpty.
\(\mathcal{O}(1)\). Extract the elements after the head of a list, which must be non-empty.
To disable the warning about partiality put {-# OPTIONS_GHC -Wno-x-partial -Wno-unrecognised-warning-flags #-}
 at the top of the file. To disable it throughout a package put the same
 options into ghc-options section of Cabal file. To disable it in GHCi
 put :set -Wno-x-partial -Wno-unrecognised-warning-flags into ~/.ghci config file.
 See also the migration guide.
Examples
>>>tail [1, 2, 3][2,3]
>>>tail [1][]
>>>tail []*** Exception: Prelude.tail: empty list
init :: HasCallStack => [a] -> [a] Source #
\(\mathcal{O}(n)\). Return all the elements of a list except the last one. The list must be non-empty.
WARNING: This function is partial. Consider using unsnoc instead.
Examples
>>>init [1, 2, 3][1,2]
>>>init [1][]
>>>init []*** Exception: Prelude.init: empty list
uncons :: [a] -> Maybe (a, [a]) Source #
\(\mathcal{O}(1)\). Decompose a list into its head and tail.
- If the list is empty, returns Nothing.
- If the list is non-empty, returns Just(x, xs)xis theheadof the list andxsitstail.
Examples
>>>uncons []Nothing
>>>uncons [1]Just (1,[])
>>>uncons [1, 2, 3]Just (1,[2,3])
Since: base-4.8.0.0
unsnoc :: [a] -> Maybe ([a], a) Source #
\(\mathcal{O}(n)\). Decompose a list into init and last.
- If the list is empty, returns Nothing.
- If the list is non-empty, returns Just(xs, x)xsis theinitial part of the list andxis itslastelement.
unsnoc is dual to uncons: for a finite list xs
unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)
Examples
>>>unsnoc []Nothing
>>>unsnoc [1]Just ([],1)
>>>unsnoc [1, 2, 3]Just ([1,2],3)
Laziness
>>>fst <$> unsnoc [undefined]Just []
>>>head . fst <$> unsnoc (1 : undefined)Just *** Exception: Prelude.undefined
>>>head . fst <$> unsnoc (1 : 2 : undefined)Just 1
Since: base-4.19.0.0
singleton :: a -> [a] Source #
Construct a list from a single element.
Examples
>>>singleton True[True]
>>>singleton [1, 2, 3][[1,2,3]]
>>>singleton 'c'"c"
Since: base-4.15.0.0
null :: Foldable t => t a -> Bool Source #
Test whether the structure is empty. The default implementation is Left-associative and lazy in both the initial element and the accumulator. Thus optimised for structures where the first element can be accessed in constant time. Structures where this is not the case should have a non-default implementation.
Examples
Basic usage:
>>>null []True
>>>null [1]False
null is expected to terminate even for infinite structures.
 The default implementation terminates provided the structure
 is bounded on the left (there is a leftmost element).
>>>null [1..]False
Since: base-4.8.0.0
length :: Foldable t => t a -> Int Source #
Returns the size/length of a finite structure as an Int.  The
 default implementation just counts elements starting with the leftmost.
 Instances for structures that can compute the element count faster
 than via element-by-element counting, should provide a specialised
 implementation.
Examples
Basic usage:
>>>length []0
>>>length ['a', 'b', 'c']3>>>length [1..]* Hangs forever *
Since: base-4.8.0.0
List transformations
map :: (a -> b) -> [a] -> [b] Source #
\(\mathcal{O}(n)\). map f xs is the list obtained by applying f to
 each element of xs, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
this means that map id == id
Examples
>>>map (+1) [1, 2, 3][2,3,4]
>>>map id [1, 2, 3][1,2,3]
>>>map (\n -> 3 * n + 1) [1, 2, 3][4,7,10]
reverse :: [a] -> [a] Source #
\(\mathcal{O}(n)\). reverse xs returns the elements of xs in reverse order.
 xs must be finite.
Laziness
reverse is lazy in its elements.
>>>head (reverse [undefined, 1])1
>>>reverse (1 : 2 : undefined)*** Exception: Prelude.undefined
Examples
>>>reverse [][]
>>>reverse [42][42]
>>>reverse [2,5,7][7,5,2]
>>>reverse [1..]* Hangs forever *
intersperse :: a -> [a] -> [a] Source #
\(\mathcal{O}(n)\). The intersperse function takes an element and a list
 and `intersperses' that element between the elements of the list.
Laziness
intersperse has the following properties
>>>take 1 (intersperse undefined ('a' : undefined))"a"
>>>take 2 (intersperse ',' ('a' : undefined))"a*** Exception: Prelude.undefined
Examples
>>>intersperse ',' "abcde""a,b,c,d,e"
>>>intersperse 1 [3, 4, 5][3,1,4,1,5]
intercalate :: [a] -> [[a]] -> [a] Source #
intercalate xs xss is equivalent to (.
 It inserts the list concat (intersperse xs xss))xs in between the lists in xss and concatenates the
 result.
Laziness
intercalate has the following properties:
>>>take 5 (intercalate undefined ("Lorem" : undefined))"Lorem"
>>>take 6 (intercalate ", " ("Lorem" : undefined))"Lorem*** Exception: Prelude.undefined
Examples
>>>intercalate ", " ["Lorem", "ipsum", "dolor"]"Lorem, ipsum, dolor"
>>>intercalate [0, 1] [[2, 3], [4, 5, 6], []][2,3,0,1,4,5,6,0,1]
>>>intercalate [1, 2, 3] [[], []][1,2,3]
transpose :: [[a]] -> [[a]] Source #
The transpose function transposes the rows and columns of its argument.
Laziness
transpose is lazy in its elements
>>>take 1 (transpose ['a' : undefined, 'b' : undefined])["ab"]
Examples
>>>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]]
For this reason the outer list must be finite; otherwise transpose hangs:
>>>transpose (repeat [])* Hangs forever *
subsequences :: [a] -> [[a]] Source #
The subsequences function returns the list of all subsequences of the argument.
Laziness
subsequences does not look ahead unless it must:
>>>take 1 (subsequences undefined)[[]]>>>take 2 (subsequences ('a' : undefined))["","a"]
Examples
>>>subsequences "abc"["","a","b","ab","c","ac","bc","abc"]
This function is productive on infinite inputs:
>>>take 8 $ subsequences ['a'..]["","a","b","ab","c","ac","bc","abc"]
permutations :: [a] -> [[a]] Source #
The permutations function returns the list of all permutations of the argument.
Note that the order of permutations is not lexicographic. It satisfies the following property:
map (take n) (take (product [1..n]) (permutations ([1..n] ++ undefined))) == permutations [1..n]
Laziness
The permutations function is maximally lazy:
 for each n, the value of permutations xstake n xsdrop n xs
Examples
>>>permutations "abc"["abc","bac","cba","bca","cab","acb"]
>>>permutations [1, 2][[1,2],[2,1]]
>>>permutations [][[]]
This function is productive on infinite inputs:
>>>take 6 $ map (take 3) $ permutations ['a'..]["abc","bac","cba","bca","cab","acb"]
Reducing lists (folds)
foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b Source #
Left-associative fold of a structure, lazy in the accumulator. This is rarely what you want, but can work well for structures with efficient right-to-left sequencing and an operator that is lazy in its left argument.
In the case of lists, foldl, when 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
Note that to produce the outermost application of the operator the
 entire input list must be traversed.  Like all left-associative folds,
 foldl will diverge if given an infinite list.
If you want an efficient strict left-fold, you probably want to use
 foldl' instead of foldl.  The reason for this is that the latter
 does not force the inner results (e.g. z `f` x1 in the above
 example) before applying them to the operator (e.g. to (`f` x2)).
 This results in a thunk chain O(n) elements long, which then must be
 evaluated from the outside-in.
For a general Foldable structure this should be semantically identical
 to:
foldl f z =foldlf z .toList
Examples
The first example is a strict fold, which in practice is best performed
 with foldl'.
>>>foldl (+) 42 [1,2,3,4]52
Though the result below is lazy, the input is reversed before prepending it to the initial accumulator, so corecursion begins only after traversing the entire input string.
>>>foldl (\acc c -> c : acc) "abcd" "efgh""hgfeabcd"
A left fold of a structure that is infinite on the right cannot terminate, even when for any finite input the fold just returns the initial accumulator:
>>>foldl (\a _ -> a) 0 $ repeat 1* Hangs forever *
WARNING: When it comes to lists, you always want to use either foldl' or foldr instead.
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b Source #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to Weak Head Normal
 Form before being applied, avoiding the collection of thunks that would
 otherwise occur.  This is often what you want to strictly reduce a
 finite structure to a single strict result (e.g. sum).
For a general Foldable structure this should be semantically identical
 to,
foldl' f z =foldl'f z .toList
Since: base-4.6.0.0
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a Source #
A variant of foldl that has no base case,
 and thus may only be applied to non-empty structures.
This function is non-total and will raise a runtime exception if the structure happens to be empty.
foldl1f =foldl1f .toList
Examples
Basic usage:
>>>foldl1 (+) [1..4]10
>>>foldl1 (+) []*** Exception: Prelude.foldl1: empty list
>>>foldl1 (+) Nothing*** Exception: foldl1: empty structure
>>>foldl1 (-) [1..4]-8
>>>foldl1 (&&) [True, False, True, True]False
>>>foldl1 (||) [False, False, True, True]True
>>>foldl1 (+) [1..]* Hangs forever *
foldl1' :: HasCallStack => (a -> a -> a) -> [a] -> a Source #
A strict version of foldl1.
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b Source #
Right-associative fold of a structure, lazy in the accumulator.
In the case of lists, foldr, when 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)...)
Note that since the head of the resulting expression is produced by an
 application of the operator to the first element of the list, given an
 operator lazy in its right argument, foldr can produce a terminating
 expression from an unbounded list.
For a general Foldable structure this should be semantically identical
 to,
foldr f z =foldrf z .toList
Examples
Basic usage:
>>>foldr (||) False [False, True, False]True
>>>foldr (||) False []False
>>>foldr (\c acc -> acc ++ [c]) "foo" ['a', 'b', 'c', 'd']"foodcba"
Infinite structures
⚠️ Applying foldr to infinite structures usually doesn't terminate.
It may still terminate under one of the following conditions:
- the folding function is short-circuiting
- the folding function is lazy on its second argument
Short-circuiting
( short-circuits on ||)True values, so the following terminates
 because there is a True value finitely far from the left side:
>>>foldr (||) False (True : repeat False)True
But the following doesn't terminate:
>>>foldr (||) False (repeat False ++ [True])* Hangs forever *
Laziness in the second argument
Applying foldr to infinite structures terminates when the operator is
 lazy in its second argument (the initial accumulator is never used in
 this case, and so could be left undefined, but [] is more clear):
>>>take 5 $ foldr (\i acc -> i : fmap (+3) acc) [] (repeat 1)[1,4,7,10,13]
foldr1 :: Foldable t => (a -> a -> a) -> t a -> a Source #
A variant of foldr that has no base case,
 and thus may only be applied to non-empty structures.
This function is non-total and will raise a runtime exception if the structure happens to be empty.
Examples
Basic usage:
>>>foldr1 (+) [1..4]10
>>>foldr1 (+) []Exception: Prelude.foldr1: empty list
>>>foldr1 (+) Nothing*** Exception: foldr1: empty structure
>>>foldr1 (-) [1..4]-2
>>>foldr1 (&&) [True, False, True, True]False
>>>foldr1 (||) [False, False, True, True]True
>>>foldr1 (+) [1..]* Hangs forever *
Special folds
concat :: Foldable t => t [a] -> [a] Source #
The concatenation of all the elements of a container of lists.
Examples
Basic usage:
>>>concat (Just [1, 2, 3])[1,2,3]
>>>concat (Left 42)[]
>>>concat [[1, 2, 3], [4, 5], [6], []][1,2,3,4,5,6]
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] Source #
Map a function over all the elements of a container and concatenate the resulting lists.
Examples
Basic usage:
>>>concatMap (take 3) [[1..], [10..], [100..], [1000..]][1,2,3,10,11,12,100,101,102,1000,1001,1002]
>>>concatMap (take 3) (Just [1..])[1,2,3]
and :: Foldable t => t Bool -> Bool Source #
and returns the conjunction of a container of Bools.  For the
 result to be True, the container must be finite; False, however,
 results from a False value finitely far from the left end.
Examples
Basic usage:
>>>and []True
>>>and [True]True
>>>and [False]False
>>>and [True, True, False]False
>>>and (False : repeat True) -- Infinite list [False,True,True,True,...False
>>>and (repeat True)* Hangs forever *
or :: Foldable t => t Bool -> Bool Source #
or returns the disjunction of a container of Bools.  For the
 result to be False, the container must be finite; True, however,
 results from a True value finitely far from the left end.
Examples
Basic usage:
>>>or []False
>>>or [True]True
>>>or [False]False
>>>or [True, True, False]True
>>>or (True : repeat False) -- Infinite list [True,False,False,False,...True
>>>or (repeat False)* Hangs forever *
any :: Foldable t => (a -> Bool) -> t a -> Bool Source #
Determines whether any element of the structure satisfies the predicate.
Examples
Basic usage:
>>>any (> 3) []False
>>>any (> 3) [1,2]False
>>>any (> 3) [1,2,3,4,5]True
>>>any (> 3) [1..]True
>>>any (> 3) [0, -1..]* Hangs forever *
all :: Foldable t => (a -> Bool) -> t a -> Bool Source #
Determines whether all elements of the structure satisfy the predicate.
Examples
Basic usage:
>>>all (> 3) []True
>>>all (> 3) [1,2]False
>>>all (> 3) [1,2,3,4,5]False
>>>all (> 3) [1..]False
>>>all (> 3) [4..]* Hangs forever *
sum :: (Foldable t, Num a) => t a -> a Source #
The sum function computes the sum of the numbers of a structure.
Examples
Basic usage:
>>>sum []0
>>>sum [42]42
>>>sum [1..10]55
>>>sum [4.1, 2.0, 1.7]7.8
>>>sum [1..]* Hangs forever *
Since: base-4.8.0.0
product :: (Foldable t, Num a) => t a -> a Source #
The product function computes the product of the numbers of a
 structure.
Examples
Basic usage:
>>>product []1
>>>product [42]42
>>>product [1..10]3628800
>>>product [4.1, 2.0, 1.7]13.939999999999998
>>>product [1..]* Hangs forever *
Since: base-4.8.0.0
maximum :: (Foldable t, Ord a) => t a -> a Source #
The largest element of a non-empty structure. This function is
 equivalent to foldr1 maxmax. For the default implementation of max (max x y = if x <= y
 then y else x), structure order is used as a tie-breaker: if there are
 multiple largest elements, the rightmost of them is chosen (this is
 equivalent to maximumBy compare
This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the maximum in faster than linear time.
Examples
Basic usage:
>>>maximum [1..10]10
>>>maximum []*** Exception: Prelude.maximum: empty list
>>>maximum Nothing*** Exception: maximum: empty structure
WARNING: This function is partial for possibly-empty structures like lists.
Since: base-4.8.0.0
minimum :: (Foldable t, Ord a) => t a -> a Source #
The least element of a non-empty structure. This function is
 equivalent to foldr1 minmin. For the default implementation of min (min x y = if x <= y
 then x else y), structure order is used as a tie-breaker: if there are
 multiple least elements, the leftmost of them is chosen (this is
 equivalent to minimumBy compare
This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the minimum in faster than linear time.
Examples
Basic usage:
>>>minimum [1..10]1
>>>minimum []*** Exception: Prelude.minimum: empty list
>>>minimum Nothing*** Exception: minimum: empty structure
WARNING: This function is partial for possibly-empty structures like lists.
Since: base-4.8.0.0
Building lists
Scans
scanl :: (b -> a -> b) -> b -> [a] -> [b] Source #
\(\mathcal{O}(n)\). scanl is similar to foldl, 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
Examples
>>>scanl (+) 0 [1..4][0,1,3,6,10]
>>>scanl (+) 42 [][42]
>>>scanl (-) 100 [1..4][100,99,97,94,90]
>>>scanl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']["foo","afoo","bafoo","cbafoo","dcbafoo"]
>>>take 10 (scanl (+) 0 [1..])[0,1,3,6,10,15,21,28,36,45]
>>>take 1 (scanl undefined 'a' undefined)"a"
scanl1 :: (a -> a -> a) -> [a] -> [a] Source #
\(\mathcal{O}(n)\). scanl1 is a variant of scanl that has no starting
 value argument:
scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
Examples
>>>scanl1 (+) [1..4][1,3,6,10]
>>>scanl1 (+) [][]
>>>scanl1 (-) [1..4][1,-1,-4,-8]
>>>scanl1 (&&) [True, False, True, True][True,False,False,False]
>>>scanl1 (||) [False, False, True, True][False,False,True,True]
>>>take 10 (scanl1 (+) [1..])[1,3,6,10,15,21,28,36,45,55]
>>>take 1 (scanl1 undefined ('a' : undefined))"a"
scanr :: (a -> b -> b) -> b -> [a] -> [b] Source #
\(\mathcal{O}(n)\). scanr is the right-to-left dual of scanl. Note that the order of parameters on the accumulating function are reversed compared to scanl.
 Also note that
head (scanr f z xs) == foldr f z xs.
Examples
>>>scanr (+) 0 [1..4][10,9,7,4,0]
>>>scanr (+) 42 [][42]
>>>scanr (-) 100 [1..4][98,-97,99,-96,100]
>>>scanr (\nextChar reversedString -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']["abcdfoo","bcdfoo","cdfoo","dfoo","foo"]
>>>force $ scanr (+) 0 [1..]*** Exception: stack overflow
scanr1 :: (a -> a -> a) -> [a] -> [a] Source #
\(\mathcal{O}(n)\). scanr1 is a variant of scanr that has no starting
 value argument.
Examples
>>>scanr1 (+) [1..4][10,9,7,4]
>>>scanr1 (+) [][]
>>>scanr1 (-) [1..4][-2,3,-1,4]
>>>scanr1 (&&) [True, False, True, True][False,False,True,True]
>>>scanr1 (||) [True, True, False, False][True,True,False,False]
>>>force $ scanr1 (+) [1..]*** Exception: stack overflow
Accumulating maps
mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #
The mapAccumL function behaves like a combination of fmap
 and foldl; it applies a function to each element of a structure,
 passing an accumulating parameter from left to right, and returning
 a final value of this accumulator together with the new structure.
Examples
Basic usage:
>>>mapAccumL (\a b -> (a + b, a)) 0 [1..10](55,[0,1,3,6,10,15,21,28,36,45])
>>>mapAccumL (\a b -> (a <> show b, a)) "0" [1..5]("012345",["0","01","012","0123","01234"])
mapAccumR :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #
The mapAccumR function behaves like a combination of fmap
 and foldr; it applies a function to each element of a structure,
 passing an accumulating parameter from right to left, and returning
 a final value of this accumulator together with the new structure.
Examples
Basic usage:
>>>mapAccumR (\a b -> (a + b, a)) 0 [1..10](55,[54,52,49,45,40,34,27,19,10,0])
>>>mapAccumR (\a b -> (a <> show b, a)) "0" [1..5]("054321",["05432","0543","054","05","0"])
Infinite lists
iterate :: (a -> a) -> a -> [a] Source #
iterate f x returns an infinite list of repeated applications
 of f to x:
iterate f x == [x, f x, f (f x), ...]
Laziness
Note that iterate is lazy, potentially leading to thunk build-up if
 the consumer doesn't force each element. See iterate' for a strict
 variant of this function.
>>>let xs = iterate (\x -> if x == 0 then undefined else x - 1) 2>>>xs[2,1,0,*** Exception: Prelude.undefined>>>length (take 10 xs)10
In xs every element following 0 is bottom, but the list itself is
 infinitely long because it is generated without forcing its elements.
Examples
>>>take 10 $ iterate not True[True,False,True,False,True,False,True,False,True,False]
>>>take 10 $ iterate (+3) 42[42,45,48,51,54,57,60,63,66,69]
iterate id == :repeat
>>>take 10 $ iterate id 1[1,1,1,1,1,1,1,1,1,1]
iterate' :: (a -> a) -> a -> [a] Source #
iterate' is the strict version of iterate.
It forces each element to weak head normal form (WHNF) before proceeding.
Laziness
>>>let xs = iterate' (\x -> if x == 0 then undefined else x - 1) 2>>>xs[2,1,0*** Exception: Prelude.undefined>>>length (take 10 xs)*** Exception: Prelude.undefined
The list xs has 3 elements followed by a tail that is bottom.
repeat x is an infinite list, with x the value of every element.
Examples
>>>take 10 $ repeat 17[17,17,17,17,17,17,17,17,17, 17]
>>>repeat undefined[*** Exception: Prelude.undefined
replicate :: Int -> a -> [a] Source #
replicate n x is a list of length n with x the value of
 every element.
 It is an instance of the more general genericReplicate,
 in which n may be of any integral type.
Examples
>>>replicate 0 True[]
>>>replicate (-1) True[]
>>>replicate 4 True[True,True,True,True]
cycle :: HasCallStack => [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.
Examples
>>>cycle []*** Exception: Prelude.cycle: empty list
>>>take 10 (cycle [42])[42,42,42,42,42,42,42,42,42,42]
>>>take 10 (cycle [2, 5, 7])[2,5,7,2,5,7,2,5,7,2]
>>>take 1 (cycle (42 : undefined))[42]
Unfolding
unfoldr :: (b -> Maybe (a, b)) -> b -> [a] Source #
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
Laziness
>>>take 1 (unfoldr (\x -> Just (x, undefined)) 'a')"a"
Examples
>>>unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10[10,9,8,7,6,5,4,3,2,1]
>>>take 10 $ unfoldr (\(x, y) -> Just (x, (y, x + y))) (0, 1)[0,1,1,2,3,5,8,13,21,54]
Sublists
Extracting sublists
take :: Int -> [a] -> [a] Source #
take n, applied to a list xs, returns the prefix of xs
 of length n, or xs itself if n >= .length xs
It is an instance of the more general genericTake,
 in which n may be of any integral type.
Laziness
>>>take 0 undefined[]>>>take 2 (1 : 2 : undefined)[1,2]
Examples
>>>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][]
drop :: Int -> [a] -> [a] Source #
drop n xs returns the suffix of xs
 after the first n elements, or [] if n >= .length xs
It is an instance of the more general genericDrop,
 in which n may be of any integral type.
Examples
>>>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]
splitAt :: Int -> [a] -> ([a], [a]) Source #
splitAt n xs returns a tuple where first element is xs prefix of
 length n and second element is the remainder of the list:
splitAt is an instance of the more general genericSplitAt,
 in which n may be of any integral type.
Laziness
It is equivalent to (
 unless take n xs, drop n xs)n is _|_:
 splitAt _|_ xs = _|_, not (_|_, _|_)).
The first component of the tuple is produced lazily:
>>>fst (splitAt 0 undefined)[]
>>>take 1 (fst (splitAt 10 (1 : undefined)))[1]
Examples
>>>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])
takeWhile :: (a -> Bool) -> [a] -> [a] Source #
takeWhile, applied to a predicate p and a list xs, returns the
 longest prefix (possibly empty) of xs of elements that satisfy p.
Laziness
>>>takeWhile (const False) undefined*** Exception: Prelude.undefined
>>>takeWhile (const False) (undefined : undefined)[]
>>>take 1 (takeWhile (const True) (1 : undefined))[1]
Examples
>>>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][]
dropWhileEnd :: (a -> Bool) -> [a] -> [a] Source #
The dropWhileEnd function drops the largest suffix of a list
 in which the given predicate holds for all elements.
Laziness
This function is lazy in spine, but strict in elements,
 which makes it different from reverse . dropWhile p . reverse,
 which is strict in spine, but lazy in elements. For instance:
>>>take 1 (dropWhileEnd (< 0) (1 : undefined))[1]
>>>take 1 (reverse $ dropWhile (< 0) $ reverse (1 : undefined))*** Exception: Prelude.undefined
but on the other hand
>>>last (dropWhileEnd (< 0) [undefined, 1])*** Exception: Prelude.undefined
>>>last (reverse $ dropWhile (< 0) $ reverse [undefined, 1])1
Examples
>>>dropWhileEnd isSpace "foo\n""foo"
>>>dropWhileEnd isSpace "foo bar""foo bar">>>dropWhileEnd (> 10) [1..20][1,2,3,4,5,6,7,8,9,10]
Since: base-4.5.0.0
span :: (a -> Bool) -> [a] -> ([a], [a]) Source #
span, applied to a predicate p and a list xs, returns a tuple where
 first element is the longest prefix (possibly empty) of xs of elements that
 satisfy p and second element is the remainder of the list:
span p xs is equivalent to (, even if takeWhile p xs, dropWhile p xs)p is _|_.
Laziness
>>>span undefined []([],[])>>>fst (span (const False) undefined)*** Exception: Prelude.undefined>>>fst (span (const False) (undefined : undefined))[]>>>take 1 (fst (span (const True) (1 : undefined)))[1]
span produces the first component of the tuple lazily:
>>>take 10 (fst (span (const True) [1..]))[1,2,3,4,5,6,7,8,9,10]
Examples
>>>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])
break :: (a -> Bool) -> [a] -> ([a], [a]) Source #
break, applied to a predicate p and a list xs, returns a tuple where
 first element is longest prefix (possibly empty) of xs of elements that
 do not satisfy p and second element is the remainder of the list:
break p is equivalent to span (not . p)(,
 even if takeWhile (not . p) xs, dropWhile (not . p) xs)p is _|_.
Laziness
>>>break undefined []([],[])
>>>fst (break (const True) undefined)*** Exception: Prelude.undefined
>>>fst (break (const True) (undefined : undefined))[]
>>>take 1 (fst (break (const False) (1 : undefined)))[1]
break produces the first component of the tuple lazily:
>>>take 10 (fst (break (const False) [1..]))[1,2,3,4,5,6,7,8,9,10]
Examples
>>>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],[])
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] Source #
\(\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.
Examples
>>>stripPrefix "foo" "foobar"Just "bar"
>>>stripPrefix "foo" "foo"Just ""
>>>stripPrefix "foo" "barfoo"Nothing
>>>stripPrefix "foo" "barfoobaz"Nothing
group :: Eq a => [a] -> [[a]] Source #
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 is non-empty, all elements are equal to the
 first one, and consecutive equal elements of the input end up in the
 same element of the output list.
group is a special case of groupBy, which allows the programmer to supply
 their own equality test.
It's often preferable to use Data.List.NonEmpty.group,
 which provides type-level guarantees of non-emptiness of inner lists.
 A common idiom to squash repeating elements map head . group
 is better served by
 map Data.List.NonEmpty.head . Data.List.NonEmpty.group
 because it avoids partial functions.
Examples
>>>group "Mississippi"["M","i","ss","i","ss","i","pp","i"]
>>>group [1, 1, 1, 2, 2, 3, 4, 5, 5][[1,1,1],[2,2],[3],[4],[5,5]]
inits :: [a] -> [[a]] Source #
The inits function returns all initial segments of the argument,
 shortest first.
inits is semantically equivalent to map reverse . scanl (flip (:)) []reverse.
Laziness
Note that inits has the following strictness property:
 inits (xs ++ _|_) = inits xs ++ _|_
In particular,
 inits _|_ = [] : _|_
Examples
>>>inits "abc"["","a","ab","abc"]
>>>inits [][[]]
inits is productive on infinite lists:
>>>take 5 $ inits [1..][[],[1],[1,2],[1,2,3],[1,2,3,4]]
tails :: [a] -> [[a]] Source #
\(\mathcal{O}(n)\). The tails function returns all final segments of the
 argument, longest first.
Laziness
Note that tails has the following strictness property:
 tails _|_ = _|_ : _|_
>>>tails undefined[*** Exception: Prelude.undefined
>>>drop 1 (tails [undefined, 1, 2])[[1, 2], [2], []]
Examples
>>>tails "abc"["abc","bc","c",""]
>>>tails [1, 2, 3][[1,2,3],[2,3],[3],[]]
>>>tails [][[]]
Predicates
isPrefixOf :: Eq a => [a] -> [a] -> Bool Source #
\(\mathcal{O}(\min(m,n))\). The isPrefixOf function takes two lists and
 returns True iff the first list is a prefix of the second.
Examples
>>>"Hello" `isPrefixOf` "Hello World!"True
>>>"Hello" `isPrefixOf` "Wello Horld!"False
For the result to be True, the first list must be finite;
 False, however, results from any mismatch:
>>>[0..] `isPrefixOf` [1..]False
>>>[0..] `isPrefixOf` [0..99]False
>>>[0..99] `isPrefixOf` [0..]True
>>>[0..] `isPrefixOf` [0..]* Hangs forever *
isPrefixOf shortcuts when the first argument is empty:
>>>isPrefixOf [] undefinedTrue
isSuffixOf :: Eq a => [a] -> [a] -> Bool Source #
The isSuffixOf function takes two lists and returns True iff
 the first list is a suffix of the second.
Examples
>>>"ld!" `isSuffixOf` "Hello World!"True
>>>"World" `isSuffixOf` "Hello World!"False
The second list must be finite; however the first list may be infinite:
>>>[0..] `isSuffixOf` [0..99]False
>>>[0..99] `isSuffixOf` [0..]* Hangs forever *
isInfixOf :: Eq a => [a] -> [a] -> Bool Source #
The isInfixOf function takes two lists and returns True
 iff the first list is contained, wholly and intact,
 anywhere within the second.
Examples
>>>isInfixOf "Haskell" "I really like Haskell."True
>>>isInfixOf "Ial" "I really like Haskell."False
For the result to be True, the first list must be finite;
 for the result to be False, the second list must be finite:
>>>[20..50] `isInfixOf` [0..]True
>>>[0..] `isInfixOf` [20..50]False
>>>[0..] `isInfixOf` [0..]* Hangs forever *
isSubsequenceOf :: Eq a => [a] -> [a] -> Bool Source #
The isSubsequenceOf function takes two lists and returns True if all
 the elements of the first list occur, in order, in the second. The
 elements do not have to occur consecutively.
isSubsequenceOf x yx `.elem` (subsequences y)
Note: isSubsequenceOf is often used in infix form.
Examples
>>>"GHC" `isSubsequenceOf` "The Glorious Haskell Compiler"True
>>>['a','d'..'z'] `isSubsequenceOf` ['a'..'z']True
>>>[1..10] `isSubsequenceOf` [10,9..0]False
For the result to be True, the first list must be finite;
 for the result to be False, the second list must be finite:
>>>[0,2..10] `isSubsequenceOf` [0..]True
>>>[0..] `isSubsequenceOf` [0,2..10]False
>>>[0,2..] `isSubsequenceOf` [0..]* Hangs forever*
Since: base-4.8.0.0
Searching lists
Searching by equality
elem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 Source #
Does the element occur in the structure?
Note: elem is often used in infix form.
Examples
Basic usage:
>>>3 `elem` []False
>>>3 `elem` [1,2]False
>>>3 `elem` [1,2,3,4,5]True
For infinite structures, the default implementation of elem
 terminates if the sought-after value exists at a finite distance
 from the left side of the structure:
>>>3 `elem` [1..]True
>>>3 `elem` ([4..] ++ [3])* Hangs forever *
Since: base-4.8.0.0
notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 Source #
notElem is the negation of elem.
Examples
Basic usage:
>>>3 `notElem` []True
>>>3 `notElem` [1,2]True
>>>3 `notElem` [1,2,3,4,5]False
For infinite structures, notElem terminates if the value exists at a
 finite distance from the left side of the structure:
>>>3 `notElem` [1..]False
>>>3 `notElem` ([4..] ++ [3])* Hangs forever *
Searching with a predicate
filter :: (a -> Bool) -> [a] -> [a] Source #
\(\mathcal{O}(n)\). 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]
Examples
>>>filter odd [1, 2, 3][1,3]
>>>filter (\l -> length l > 3) ["Hello", ", ", "World", "!"]["Hello","World"]
>>>filter (/= 3) [1, 2, 3, 4, 3, 2, 1][1,2,4,2,1]
partition :: (a -> Bool) -> [a] -> ([a], [a]) Source #
The partition function takes a predicate and 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)
Examples
>>>partition (`elem` "aeiou") "Hello World!"("eoo","Hll Wrld!")
>>>partition even [1..10]([2,4,6,8,10],[1,3,5,7,9])
>>>partition (< 5) [1..10]([1,2,3,4],[5,6,7,8,9,10])
Indexing lists
These functions treat a list xs as an indexed collection,
 with indices ranging from 0 to length xs - 1
(!?) :: [a] -> Int -> Maybe a infixl 9 Source #
List index (subscript) operator, starting from 0. Returns Nothing
 if the index is out of bounds
This is the total variant of the partial !! operator.
WARNING: This function takes linear time in the index.
Examples
>>>['a', 'b', 'c'] !? 0Just 'a'
>>>['a', 'b', 'c'] !? 2Just 'c'
>>>['a', 'b', 'c'] !? 3Nothing
>>>['a', 'b', 'c'] !? (-1)Nothing
Since: base-4.19.0.0
(!!) :: HasCallStack => [a] -> Int -> a infixl 9 Source #
List index (subscript) operator, starting from 0.
 It is an instance of the more general genericIndex,
 which takes an index of any integral type.
WARNING: This function is partial, and should only be used if you are
 sure that the indexing will not fail. Otherwise, use !?.
WARNING: This function takes linear time in the index.
Examples
>>>['a', 'b', 'c'] !! 0'a'
>>>['a', 'b', 'c'] !! 2'c'
>>>['a', 'b', 'c'] !! 3*** Exception: Prelude.!!: index too large
>>>['a', 'b', 'c'] !! (-1)*** Exception: Prelude.!!: negative index
elemIndex :: Eq a => a -> [a] -> Maybe Int Source #
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.
 For the result to be Nothing, the list must be finite.
Examples
>>>elemIndex 4 [0..]Just 4
>>>elemIndex 'o' "haskell"Nothing
>>>elemIndex 0 [1..]* hangs forever *
elemIndices :: Eq a => a -> [a] -> [Int] Source #
The elemIndices function extends elemIndex, by returning the
 indices of all elements equal to the query element, in ascending order.
Examples
>>>elemIndices 'o' "Hello World"[4,7]
>>>elemIndices 1 [1, 2, 3, 1, 2, 3][0,3]
findIndex :: (a -> Bool) -> [a] -> Maybe Int Source #
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.
 For the result to be Nothing, the list must be finite.
Examples
>>>findIndex isSpace "Hello World!"Just 5
>>>findIndex odd [0, 2, 4, 6]Nothing
>>>findIndex even [1..]Just 1
>>>findIndex odd [0, 2 ..]* hangs forever *
findIndices :: (a -> Bool) -> [a] -> [Int] Source #
The findIndices function extends findIndex, by returning the
 indices of all elements satisfying the predicate, in ascending order.
Examples
>>>findIndices (`elem` "aeiou") "Hello World!"[1,4,7]
>>>findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"][1,3]
Zipping and unzipping lists
zip :: [a] -> [b] -> [(a, b)] Source #
\(\mathcal{O}(\min(m,n))\). zip takes two lists and returns a list of
 corresponding pairs.
zip is right-lazy:
>>>zip [] undefined[]>>>zip undefined []*** Exception: Prelude.undefined ...
zip is capable of list fusion, but it is restricted to its
 first list argument and its resulting list.
Examples
>>>zip [1, 2, 3] ['a', 'b', 'c'][(1,'a'),(2,'b'),(3,'c')]
If one input list is shorter than the other, excess elements of the longer list are discarded, even if one of the lists is infinite:
>>>zip [1] ['a', 'b'][(1,'a')]
>>>zip [1, 2] ['a'][(1,'a')]
>>>zip [] [1..][]
>>>zip [1..] [][]
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #
\(\mathcal{O}(\min(m,n))\). zipWith generalises zip by zipping with the
 function given as the first argument, instead of a tupling function.
zipWith (,) xs ys == zip xs ys zipWith f [x1,x2,x3..] [y1,y2,y3..] == [f x1 y1, f x2 y2, f x3 y3..]
zipWith is right-lazy:
>>>let f = undefined>>>zipWith f [] undefined[]
zipWith is capable of list fusion, but it is restricted to its
 first list argument and its resulting list.
Examples
zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #
\(\mathcal{O}(\min(l,m,n))\). The zipWith3 function takes a function which combines three
 elements, as well as three lists and returns a list of the function applied
 to corresponding elements, analogous to zipWith.
 It is capable of list fusion, but it is restricted to its
 first list argument and its resulting list.
zipWith3 (,,) xs ys zs == zip3 xs ys zs zipWith3 f [x1,x2,x3..] [y1,y2,y3..] [z1,z2,z3..] == [f x1 y1 z1, f x2 y2 z2, f x3 y3 z3..]
Examples
>>>zipWith3 (\x y z -> [x, y, z]) "123" "abc" "xyz"["1ax","2by","3cz"]
>>>zipWith3 (\x y z -> (x * y) + z) [1, 2, 3] [4, 5, 6] [7, 8, 9][11,18,27]
zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] Source #
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h] Source #
unzip :: [(a, b)] -> ([a], [b]) Source #
unzip transforms a list of pairs into a list of first components
 and a list of second components.
Examples
>>>unzip []([],[])
>>>unzip [(1, 'a'), (2, 'b')]([1,2],"ab")
Special lists
Functions on strings
lines :: String -> [String] Source #
Splits the argument into a list of lines stripped of their terminating
 \n characters.  The \n terminator is optional in a final non-empty
 line of the argument string.
When the argument string is empty, or ends in a \n character, it can be
 recovered by passing the result of lines to the unlines function.
 Otherwise, unlines appends the missing terminating \n.  This makes
 unlines . lines idempotent:
(unlines . lines) . (unlines . lines) = (unlines . lines)
Examples
>>>lines "" -- empty input contains no lines[]
>>>lines "\n" -- single empty line[""]
>>>lines "one" -- single unterminated line["one"]
>>>lines "one\n" -- single non-empty line["one"]
>>>lines "one\n\n" -- second line is empty["one",""]
>>>lines "one\ntwo" -- second line is unterminated["one","two"]
>>>lines "one\ntwo\n" -- two non-empty lines["one","two"]
"Set" operations
nub :: Eq a => [a] -> [a] Source #
\(\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.
If there exists instance Ord a, it's faster to use nubOrd from the containers package
 (link to the latest online documentation),
 which takes only \(\mathcal{O}(n \log d)\) time where d is the number of
 distinct elements in the list.
Another approach to speed up nub is to use
 map Data.List.NonEmpty.head . Data.List.NonEmpty.group . sort,
 which takes \(\mathcal{O}(n \log n)\) time, requires instance Ord a and doesn't
 preserve the order.
Examples
>>>nub [1,2,3,4,3,2,1,2,4,3,5][1,2,3,4,5]
>>>nub "hello, world!""helo, wrd!"
delete :: Eq a => a -> [a] -> [a] Source #
\(\mathcal{O}(n)\). delete x removes the first occurrence of x from
 its list argument.
It is a special case of deleteBy, which allows the programmer to
 supply their own equality test.
Examples
>>>delete 'a' "banana""bnana"
>>>delete "not" ["haskell", "is", "not", "awesome"]["haskell","is","awesome"]
(\\) :: Eq a => [a] -> [a] -> [a] infix 5 Source #
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.
It is a special case of deleteFirstsBy, which allows the programmer
 to supply their own equality test.
Examples
>>>"Hello World!" \\ "ell W""Hoorld!"
The second list must be finite, but the first may be infinite.
>>>take 5 ([0..] \\ [2..4])[0,1,5,6,7]
>>>take 5 ([0..] \\ [2..])* Hangs forever *
union :: Eq a => [a] -> [a] -> [a] Source #
The union function returns the list union of the two lists.
 It is a special case of unionBy, which allows the programmer to supply
 their own equality test.
Examples
>>>"dog" `union` "cow""dogcw"
If equal elements are present in both lists, an element from the first list will be used. If the second list contains equal elements, only the first one will be retained:
>>>import Data.Semigroup(Arg(..))>>>union [Arg () "dog"] [Arg () "cow"][Arg () "dog"]>>>union [] [Arg () "dog", Arg () "cow"][Arg () "dog"]
However if the first list contains duplicates, so will the result:
>>>"coot" `union` "duck""cootduk">>>"duck" `union` "coot""duckot"
union is productive even if both arguments are infinite.
>>>[0, 2 ..] `union` [1, 3 ..][0,2,4,6,8,10,12..
intersect :: Eq a => [a] -> [a] -> [a] Source #
The intersect function takes the list intersection of two lists.
 It is a special case of intersectBy, which allows the programmer to
 supply their own equality test.
Examples
>>>[1,2,3,4] `intersect` [2,4,6,8][2,4]
If equal elements are present in both lists, an element from the first list will be used, and all duplicates from the second list quashed:
>>>import Data.Semigroup>>>intersect [Arg () "dog"] [Arg () "cow", Arg () "cat"][Arg () "dog"]
However if the first list contains duplicates, so will the result.
>>>"coot" `intersect` "heron""oo">>>"heron" `intersect` "coot""o"
If the second list is infinite, intersect either hangs
 or returns its first argument in full. Otherwise if the first list
 is infinite, intersect might be productive:
>>>intersect [100..] [0..][100,101,102,103...>>>intersect [0] [1..]* Hangs forever *>>>intersect [1..] [0]* Hangs forever *>>>intersect (cycle [1..3]) [2][2,2,2,2...
Ordered lists
sort :: Ord a => [a] -> [a] Source #
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.
The argument must be finite.
Examples
>>>sort [1,6,4,3,2,5][1,2,3,4,5,6]
>>>sort "haskell""aehklls"
>>>import Data.Semigroup(Arg(..))>>>sort [Arg ":)" 0, Arg ":D" 0, Arg ":)" 1, Arg ":3" 0, Arg ":D" 1][Arg ":)" 0,Arg ":)" 1,Arg ":3" 0,Arg ":D" 0,Arg ":D" 1]
sortOn :: Ord b => (a -> b) -> [a] -> [a] Source #
Sort a list by comparing the results of a key function applied to each
 element.  sortOn fsortBy (comparing f)f once for each element in the
 input list.  This is called the decorate-sort-undecorate paradigm, or
 Schwartzian transform.
Elements are arranged from lowest to highest, keeping duplicates in the order they appeared in the input.
The argument must be finite.
Examples
>>>sortOn fst [(2, "world"), (4, "!"), (1, "Hello")][(1,"Hello"),(2,"world"),(4,"!")]
>>>sortOn length ["jim", "creed", "pam", "michael", "dwight", "kevin"]["jim","pam","creed","kevin","dwight","michael"]
Performance notes
This function minimises the projections performed, by materialising the projections in an intermediate list.
For trivial projections, you should prefer using sortBy with
 comparing, for example:
>>>sortBy (comparing fst) [(3, 1), (2, 2), (1, 3)][(1,3),(2,2),(3,1)]
Or, for the exact same API as sortOn, you can use `sortBy . comparing`:
>>>(sortBy . comparing) fst [(3, 1), (2, 2), (1, 3)][(1,3),(2,2),(3,1)]
However, sortOn may still be faster for instances with a more efficient
 implementation of (>) than compare.
Since: base-4.8.0.0
insert :: Ord a => a -> [a] -> [a] Source #
\(\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.
Examples
>>>insert (-1) [1, 2, 3][-1,1,2,3]
>>>insert 'd' "abcefg""abcdefg"
>>>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 with
 on, for instance sortBy (compare
 `on` fst)
User-supplied equality (replacing an Eq context)
The predicate is assumed to define an equivalence.
nubBy :: (a -> a -> Bool) -> [a] -> [a] Source #
The nubBy function behaves just like nub, except it uses a
 user-supplied equality predicate instead of the overloaded (==)
 function.
Examples
>>>nubBy (\x y -> mod x 3 == mod y 3) [1,2,4,5,6][1,2,6]
>>>nubBy (/=) [2, 7, 1, 8, 2, 8, 1, 8, 2, 8][2,2,2]
>>>nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2][1,2,3,5,5]
deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #
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. This is the non-overloaded version of (\\).
(\\) == deleteFirstsBy (==)
The second list must be finite, but the first may be infinite.
Examples
>>>deleteFirstsBy (>) [1..10] [3, 4, 5][4,5,6,7,8,9,10]
>>>deleteFirstsBy (/=) [1..10] [1, 3, 5][4,5,6,7,8,9,10]
intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] Source #
The intersectBy function is the non-overloaded version of intersect.
 It is productive for infinite arguments only if the first one
 is a subset of the second.
groupBy :: (a -> a -> Bool) -> [a] -> [[a]] Source #
The groupBy function is the non-overloaded version of group.
When a supplied relation is not transitive, it is important to remember that equality is checked against the first element in the group, not against the nearest neighbour:
>>>groupBy (\a b -> b - a < 5) [0..19][[0,1,2,3,4],[5,6,7,8,9],[10,11,12,13,14],[15,16,17,18,19]]
It's often preferable to use Data.List.NonEmpty.groupBy,
 which provides type-level guarantees of non-emptiness of inner lists.
Examples
>>>groupBy (/=) [1, 1, 1, 2, 3, 1, 4, 4, 5][[1],[1],[1,2,3],[1,4,4,5]]
>>>groupBy (>) [1, 3, 5, 1, 4, 2, 6, 5, 4][[1],[3],[5,1,4,2],[6,5,4]]
>>>groupBy (const not) [True, False, True, False, False, False, True][[True,False],[True,False,False,False],[True]]
User-supplied comparison (replacing an Ord context)
The function is assumed to define a total ordering.
sortBy :: (a -> a -> Ordering) -> [a] -> [a] Source #
The sortBy function is the non-overloaded version of sort.
 The argument must be finite.
The supplied comparison relation is supposed to be reflexive and antisymmetric,
 otherwise, e. g., for _ _ -> GT, the ordered list simply does not exist.
 The relation is also expected to be transitive: if it is not then sortBy
 might fail to find an ordered permutation, even if it exists.
Examples
>>>sortBy (\(a,_) (b,_) -> compare a b) [(2, "world"), (4, "!"), (1, "Hello")][(1,"Hello"),(2,"world"),(4,"!")]
insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] Source #
\(\mathcal{O}(n)\). The non-overloaded version of insert.
Examples
>>>insertBy (\x y -> compare (length x) (length y)) [1, 2] [[1], [1, 2, 3], [1, 2, 3, 4]][[1],[1,2],[1,2,3],[1,2,3,4]]
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a Source #
The largest element of a non-empty structure with respect to the given comparison function. Structure order is used as a tie-breaker: if there are multiple largest elements, the rightmost of them is chosen.
Examples
Basic usage:
>>>maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]"Longest"
WARNING: This function is partial for possibly-empty structures like lists.
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a Source #
The least element of a non-empty structure with respect to the given comparison function. Structure order is used as a tie-breaker: if there are multiple least elements, the leftmost of them is chosen.
Examples
Basic usage:
>>>minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]"!"
WARNING: This function is partial for possibly-empty structures like lists.
The "generic" operations
The prefix `generic' indicates an overloaded function that
 is a generalized version of a Prelude function.
genericLength :: Num i => [a] -> i Source #
\(\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.
Examples
>>>genericLength [1, 2, 3] :: Int3>>>genericLength [1, 2, 3] :: Float3.0
Users should take care to pick a return type that is wide enough to contain
 the full length of the list. If the width is insufficient, the overflow
 behaviour will depend on the (+) implementation in the selected Num
 instance. The following example overflows because the actual list length
 of 200 lies outside of the Int8 range of -128..127.
>>>genericLength [1..200] :: Int8-56
genericTake :: Integral i => i -> [a] -> [a] Source #
The genericTake function is an overloaded version of take, which
 accepts any Integral value as the number of elements to take.
genericDrop :: Integral i => i -> [a] -> [a] Source #
The genericDrop function is an overloaded version of drop, which
 accepts any Integral value as the number of elements to drop.
genericSplitAt :: Integral i => i -> [a] -> ([a], [a]) Source #
The genericSplitAt function is an overloaded version of splitAt, which
 accepts any Integral value as the position at which to split.
genericIndex :: Integral i => [a] -> i -> a Source #
The genericIndex function is an overloaded version of !!, which
 accepts any Integral value as the index.
genericReplicate :: Integral i => i -> a -> [a] Source #
The genericReplicate function is an overloaded version of replicate,
 which accepts any Integral value as the number of repetitions to make.