base-4.19.1.0: Basic libraries
Copyright(c) The University of Glasgow 1994-2002
Licensesee libraries/base/LICENSE
Maintainercvs-ghc@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellTrustworthy
LanguageHaskell2010

GHC.List

Description

The List data type and its operations

Synopsis

Documentation

data List a Source #

The builtin list type, usually written in its non-prefix form [a].

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 it unsuited for operations that require \(\mathcal{O}(1)\) access. Instead, lists are intended to be traversed.

Lists are constructed recursively using the right-associative cons-operator (:) :: a -> [a] -> [a], which prepends an element to a list, and the empty list [].

(1 : 2 : 3 : []) == (1 : (2 : (3 : []))) == [1, 2, 3]

Internally and in memory, all the above are represented like this, with arrows being pointers to locations in memory.

╭───┬───┬──╮   ╭───┬───┬──╮   ╭───┬───┬──╮   ╭────╮
│(:)│   │ ─┼──>│(:)│   │ ─┼──>│(:)│   │ ─┼──>│ [] │
╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰───┴─┼─┴──╯   ╰────╯
      v              v              v
      1              2              3

As seen above, 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 []

Similarly, String literals of the form "I 💜 hs" are translated into Lists of characters, ['I', ' ', '💜', ' ', 'h', 's'].

Examples

Expand
>>> ['H', 'a', 's', 'k', 'e', 'l', 'l']
"Haskell"
>>> 1 : [4, 1, 5, 9]
[1,4,1,5,9]
>>> [] : [] : []
[[],[]]

Since: ghc-prim-0.10.0

Instances

Instances details
MonadFail [] Source #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> [a] Source #

MonadFix [] Source #

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

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

MonadZip [] Source #

Since: base-4.3.1.0

Instance details

Defined in Control.Monad.Zip

Methods

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

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

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

Foldable [] Source #

Since: base-2.1

Instance details

Defined in 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 #

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

null :: [a] -> Bool Source #

length :: [a] -> Int Source #

elem :: Eq a => a -> [a] -> Bool Source #

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

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

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

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

Eq1 [] Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> [a] -> [b] -> Bool Source #

Ord1 [] Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> [a] -> [b] -> Ordering Source #

Read1 [] Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS [a] Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [[a]] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [a] Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [[a]] Source #

Show1 [] Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [[a]] -> ShowS Source #

Traversable [] Source #

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> [a] -> f [b] Source #

sequenceA :: Applicative f => [f a] -> f [a] Source #

mapM :: Monad m => (a -> m b) -> [a] -> m [b] Source #

sequence :: Monad m => [m a] -> m [a] Source #

Alternative [] Source #

Combines lists by concatenation, starting from the empty list.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty :: [a] Source #

(<|>) :: [a] -> [a] -> [a] Source #

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

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

Applicative [] Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> [a] Source #

(<*>) :: [a -> b] -> [a] -> [b] Source #

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

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

(<*) :: [a] -> [b] -> [a] Source #

Functor [] Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

(<$) :: a -> [b] -> [a] Source #

Monad [] Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

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

return :: a -> [a] Source #

MonadPlus [] Source #

Combines lists by concatenation, starting from the empty list.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: [a] Source #

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

Generic1 [] Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 []

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from1 :: [a] -> Rep1 [] a Source #

to1 :: Rep1 [] a -> [a] Source #

Data a => Data [a] Source #

For historical reasons, the constructor name used for (:) is "(:)". In a derived instance, it would be ":".

Since: base-4.0.0.0

Instance details

Defined in 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 #

(a ~ Char) context was introduced in 4.9.0.0

Since: base-2.1

Instance details

Defined in Data.String

Methods

fromString :: String -> [a] Source #

Monoid [a] Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] Source #

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

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

Semigroup [a] Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty [a] -> [a] Source #

stimes :: Integral b => b -> [a] -> [a] Source #

Generic [a] Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a]

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: [a] -> Rep [a] x Source #

to :: Rep [a] x -> [a] Source #

IsList [a] Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item [a] 
Instance details

Defined in GHC.IsList

type Item [a] = a

Methods

fromList :: [Item [a]] -> [a] Source #

fromListN :: Int -> [Item [a]] -> [a] Source #

toList :: [a] -> [Item [a]] Source #

Read a => Read [a] Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Show a => Show [a] Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> [a] -> ShowS Source #

show :: [a] -> String Source #

showList :: [[a]] -> ShowS Source #

IsChar c => PrintfArg [c] Source #

Since: base-2.1

Instance details

Defined in Text.Printf

IsChar c => PrintfType [c] Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Methods

spr :: String -> [UPrintf] -> [c]

Eq a => Eq [a] 
Instance details

Defined in GHC.Classes

Methods

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

(/=) :: [a] -> [a] -> Bool Source #

Ord a => Ord [a] 
Instance details

Defined in GHC.Classes

Methods

compare :: [a] -> [a] -> Ordering Source #

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

(<=) :: [a] -> [a] -> Bool Source #

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

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

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

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

type Rep1 [] Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep [a] Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Item [a] Source # 
Instance details

Defined in GHC.IsList

type Item [a] = a

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

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

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

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

foldr' is a variant of foldr that begins list reduction from the last element and evaluates the accumulator strictly as it unwinds the stack back to the beginning of the list. The input list must be finite, otherwise foldr' runs out of space (diverges).

Note that if the function that combines the accumulated value with each element is strict in the accumulator, other than a possible improvement in the constant factor, you get the same \(\mathcal{O}(n)\) space cost as with just foldr.

If you want a strict right fold in constant space, you need a structure that supports faster than \(\mathcal{O}(n)\) access to the right-most element, such as Seq from the containers package.

Use of this function is a hint that the [] structure may be a poor fit for the task at hand. If the order in which the elements are combined is not important, use foldl' instead.

>>> foldr' (+) [1..4]  -- Use foldl' instead!
10
>>> foldr' (&&) [True, False, True, True] -- Use foldr instead!
False
>>> foldr' (||) [False, False, True, True] -- Use foldr instead!
True

foldr1 :: HasCallStack => (a -> a -> a) -> [a] -> a Source #

foldr1 is a variant of foldr that has no starting value argument, and thus must be applied to non-empty lists. Note that unlike foldr, the accumulated value must be of the same type as the list elements.

>>> foldr1 (+) [1..4]
10
>>> foldr1 (+) []
*** Exception: Prelude.foldr1: empty list
>>> foldr1 (-) [1..4]
-2
>>> foldr1 (&&) [True, False, True, True]
False
>>> foldr1 (||) [False, False, True, True]
True
>>> force $ foldr1 (+) [1..]
*** Exception: stack overflow

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

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

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

The list must be finite.

>>> foldl (+) 0 [1..4]
10
>>> foldl (+) 42 []
42
>>> foldl (-) 100 [1..4]
90
>>> foldl (\reversedString nextChar -> nextChar : reversedString) "foo" ['a', 'b', 'c', 'd']
"dcbafoo"
>>> foldl (+) 0 [1..]
* Hangs forever *

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

A strict version of foldl.

foldl1 :: HasCallStack => (a -> a -> a) -> [a] -> a Source #

foldl1 is a variant of foldl that has no starting value argument, and thus must be applied to non-empty lists. Note that unlike foldl, the accumulated value must be of the same type as the list elements.

>>> foldl1 (+) [1..4]
10
>>> foldl1 (+) []
*** Exception: Prelude.foldl1: empty list
>>> foldl1 (-) [1..4]
-8
>>> foldl1 (&&) [True, False, True, True]
False
>>> foldl1 (||) [False, False, True, True]
True
>>> foldl1 (+) [1..]
* Hangs forever *

null :: [a] -> Bool Source #

\(\mathcal{O}(1)\). Test whether a list is empty.

>>> null []
True
>>> null [1]
False
>>> null [1..]
False

length :: [a] -> Int Source #

\(\mathcal{O}(n)\). length returns the length of a finite list as an Int. It is an instance of the more general genericLength, the result type of which may be any kind of number.

>>> length []
0
>>> length ['a', 'b', 'c']
3
>>> length [1..]
* Hangs forever *

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

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

Examples

Expand
>>> 3 `elem` []
False
>>> 3 `elem` [1,2]
False
>>> 3 `elem` [1,2,3,4,5]
True
>>> 3 `elem` [1..]
True
>>> 3 `elem` [4..]
* Hangs forever *

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

notElem is the negation of elem.

Examples

Expand
>>> 3 `notElem` []
True
>>> 3 `notElem` [1,2]
True
>>> 3 `notElem` [1,2,3,4,5]
False
>>> 3 `notElem` [1..]
False
>>> 3 `notElem` [4..]
* Hangs forever *

maximum :: (Ord a, HasCallStack) => [a] -> a Source #

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

>>> maximum []
*** Exception: Prelude.maximum: empty list
>>> maximum [42]
42
>>> maximum [55, -12, 7, 0, -89]
55
>>> maximum [1..]
* Hangs forever *

minimum :: (Ord a, HasCallStack) => [a] -> a Source #

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

>>> minimum []
*** Exception: Prelude.minimum: empty list
>>> minimum [42]
42
>>> minimum [55, -12, 7, 0, -89]
-89
>>> minimum [1..]
* Hangs forever *

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

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

>>> sum []
0
>>> sum [42]
42
>>> sum [1..10]
55
>>> sum [4.1, 2.0, 1.7]
7.8
>>> sum [1..]
* Hangs forever *

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

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

>>> product []
1
>>> product [42]
42
>>> product [1..10]
3628800
>>> product [4.1, 2.0, 1.7]
13.939999999999998
>>> product [1..]
* Hangs forever *

and :: [Bool] -> Bool Source #

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

Examples

Expand
>>> and []
True
>>> and [True]
True
>>> and [False]
False
>>> and [True, True, False]
False
>>> and (False : repeat True) -- Infinite list [False,True,True,True,True,True,True...
False
>>> and (repeat True)
* Hangs forever *

or :: [Bool] -> Bool Source #

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

Examples

Expand
>>> or []
False
>>> or [True]
True
>>> or [False]
False
>>> or [True, True, False]
True
>>> or (True : repeat False) -- Infinite list [True,False,False,False,False,False,False...
True
>>> or (repeat False)
* Hangs forever *

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

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

Examples

Expand
>>> 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 :: (a -> Bool) -> [a] -> Bool Source #

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

Examples

Expand
>>> 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 *

foldl1' :: HasCallStack => (a -> a -> a) -> [a] -> a Source #

A strict version of foldl1.

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

Concatenate a list of lists.

Examples

Expand
>>> concat [[1,2,3], [4,5], [6], []]
[1,2,3,4,5,6]
>>> concat []
[]
>>> concat [[42]]
[42]

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

Map a function returning a list over a list and concatenate the results. concatMap can be seen as the composition of concat and map.

concatMap f xs == (concat . map f) xs

Examples

Expand
>>> concatMap (\i -> [-i,i]) []
[]
>>> concatMap (\i -> [-i, i]) [1, 2, 3]
[-1,1,-2,2,-3,3]
>>> concatMap ('replicate' 3) [0, 2, 4]
[0,0,0,2,2,2,4,4,4]

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

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

(++) :: [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

Expand

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

Expand
>>> [1, 2, 3] ++ [4, 5, 6]
[1,2,3,4,5,6]
>>> [] ++ [1, 2, 3]
[1,2,3]
>>> [3, 2, 1] ++ []
[3,2,1]

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

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

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

\(\mathcal{O}(n)\). lookup key assocs looks up a key in an association list. For the result to be Nothing, the list must be finite.

Examples

Expand
>>> lookup 2 []
Nothing
>>> lookup 2 [(1, "first")]
Nothing
>>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
Just "second"

head :: HasCallStack => [a] -> a Source #

Warning: This is a partial function, it throws an error on empty lists. Use pattern matching or Data.List.uncons instead. Consider refactoring to use Data.List.NonEmpty.

\(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.

Examples
Expand
>>> 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

Expand
>>> 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 Data.List.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.

Examples

Expand
>>> 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

Expand
>>> 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), where x is the head of the list and xs its tail.

Examples

Expand
>>> 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), where xs is the initial part of the list and x is its last element.

unsnoc is dual to uncons: for a finite list xs

unsnoc xs = (\(hd, tl) -> (reverse tl, hd)) <$> uncons (reverse xs)

Examples

Expand
>>> unsnoc []
Nothing
>>> unsnoc [1]
Just ([],1)
>>> unsnoc [1, 2, 3]
Just ([1,2],3)

Laziness

Expand
>>> 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

(!?) :: [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

Expand
>>> ['a', 'b', 'c'] !? 0
Just 'a'
>>> ['a', 'b', 'c'] !? 2
Just 'c'
>>> ['a', 'b', 'c'] !? 3
Nothing
>>> ['a', 'b', 'c'] !? (-1)
Nothing

(!!) :: 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

Expand
>>> ['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

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

Expand
>>> 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

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

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

\(\mathcal{O}(n)\). A strict version of scanl.

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

Expand
>>> 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

Expand
>>> 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

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

Expand

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

>>> take 1 $ iterate undefined 42
[42]

Examples

Expand
>>> 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 the result of each application of the function to weak head normal form (WHNF) before proceeding.

>>> take 1 $ iterate' undefined 42
*** Exception: Prelude.undefined

repeat :: a -> [a] Source #

repeat x is an infinite list, with x the value of every element.

Examples

Expand
>>> 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

Expand
>>> 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

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

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

Expand
>>> take 0 undefined
[]
>>> take 2 (1 : 2 : undefined)
[1,2]

Examples

Expand
>>> 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

Expand
>>> 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

Expand

It is equivalent to (take n xs, drop n xs) unless 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

Expand
>>> 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

Expand
>>> takeWhile (const False) undefined
*** Exception: Prelude.undefined
>>> takeWhile (const False) (undefined : undefined)
[]
>>> take 1 (takeWhile (const True) (1 : undefined))
[1]

Examples

Expand
>>> takeWhile (< 3) [1,2,3,4,1,2,3,4]
[1,2]
>>> takeWhile (< 9) [1,2,3]
[1,2,3]
>>> takeWhile (< 0) [1,2,3]
[]

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

dropWhile p xs returns the suffix remaining after takeWhile p xs.

Examples

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

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 (takeWhile p xs, dropWhile p xs), even if p is _|_.

Laziness

Expand
>>> 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

Expand
>>> 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) and consequently to (takeWhile (not . p) xs, dropWhile (not . p) xs), even if p is _|_.

Laziness

Expand
>>> 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

Expand
>>> 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],[])

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

\(\mathcal{O}(n)\). reverse xs returns the elements of xs in reverse order. xs must be finite.

Laziness

Expand

reverse is lazy in its elements.

>>> head (reverse [undefined, 1])
1
>>> reverse (1 : 2 : undefined)
*** Exception: Prelude.undefined

Examples

Expand
>>> reverse []
[]
>>> reverse [42]
[42]
>>> reverse [2,5,7]
[7,5,2]
>>> reverse [1..]
* Hangs forever *

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

Expand
>>> 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..] []
[]

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

zip3 takes three lists and returns a list of triples, analogous to zip. It is capable of list fusion, but it is restricted to its first list argument and its resulting list.

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

Expand

zipWith (+) can be applied to two lists to produce the list of corresponding sums:

>>> zipWith (+) [1, 2, 3] [4, 5, 6]
[5,7,9]
>>> zipWith (++) ["hello ", "foo"] ["world!", "bar"]
["hello world!","foobar"]

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

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

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

Expand
>>> unzip []
([],[])
>>> unzip [(1, 'a'), (2, 'b')]
([1,2],"ab")

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

The unzip3 function takes a list of triples and returns three lists of the respective components, analogous to unzip.

Examples

Expand
>>> unzip3 []
([],[],[])
>>> unzip3 [(1, 'a', True), (2, 'b', False)]
([1,2],"ab",[True,False])

GHC List fusion

augment :: (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] Source #

A list producer that can be fused with foldr. This function is merely

   augment g xs = g (:) xs

but GHC's simplifier will transform an expression of the form foldr k z (augment g xs), which may arise after inlining, to g k (foldr k z xs), which avoids producing an intermediate list.

build :: (forall b. (a -> b -> b) -> b -> b) -> [a] Source #

A list producer that can be fused with foldr. This function is merely

   build g = g (:) []

but GHC's simplifier will transform an expression of the form foldr k z (build g), which may arise after inlining, to g k z, which avoids producing an intermediate list.