linear-base-0.3.1: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.List.Linear

Description

Linear versions of List functions.

This module only contains minimal amount of documentation; consult the original Data.List module for more detailed information.

Synopsis

Basic functions

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

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

filter :: Dupable a => (a %1 -> Bool) -> [a] %1 -> [a] Source #

filter p xs returns a list with elements satisfying the predicate.

See mapMaybe if you do not want the Dupable constraint.

head :: [a] -> a #

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

>>> head [1, 2, 3]
1
>>> head [1..]
1
>>> head []
*** Exception: Prelude.head: empty list

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

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

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

>>> tail [1, 2, 3]
[2,3]
>>> tail [1]
[]
>>> tail []
*** Exception: Prelude.tail: empty list

last :: [a] -> a #

\(\mathcal{O}(n)\). Extract the last element of a list, which must be finite and non-empty.

>>> last [1, 2, 3]
3
>>> last [1..]
* Hangs forever *
>>> last []
*** Exception: Prelude.last: empty list

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

\(\mathcal{O}(n)\). Return all the elements of a list except the last one. The list must be non-empty.

>>> init [1, 2, 3]
[1,2]
>>> init [1]
[]
>>> init []
*** Exception: Prelude.init: empty list

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

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

\(\mathcal{O}(n)\). lookup key assocs looks up a key in an association list.

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

length :: [a] %1 -> (Ur Int, [a]) Source #

Return the length of the given list alongside with the list itself.

null :: Foldable t => t a -> Bool #

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

Expand

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

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

Extracting sublists

take :: Consumable a => Int -> [a] %1 -> [a] Source #

NOTE: This does not short-circuit and always traverses the entire list to consume the rest of the elements.

drop :: Consumable a => Int -> [a] %1 -> [a] Source #

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

span :: Dupable a => (a %1 -> Bool) -> [a] %1 -> ([a], [a]) Source #

span, applied to a predicate p and a list xs, returns a tuple where first element is longest prefix (possibly empty) of xs of elements that satisfy p and second element is the remainder of the list.

partition :: Dupable a => (a %1 -> Bool) -> [a] %1 -> ([a], [a]) Source #

takeWhile :: Dupable a => (a %1 -> Bool) -> [a] %1 -> [a] Source #

NOTE: This does not short-circuit and always traverses the entire list to consume the rest of the elements.

dropWhile :: Dupable a => (a %1 -> Bool) -> [a] %1 -> [a] Source #

find :: Foldable t => (a -> Bool) -> t a -> Maybe a #

The find function takes a predicate and a structure and returns the leftmost element of the structure matching the predicate, or Nothing if there is no such element.

Examples

Expand

Basic usage:

>>> find (> 42) [0, 5..]
Just 45
>>> find (> 12) [1..7]
Nothing

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

The intersperse function takes an element and a list and intersperses that element between the elements of the list.

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

intercalate xs xss is equivalent to (concat (intersperse xs xss)). It inserts the list xs in between the lists in xss and concatenates the result.

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

The transpose function transposes the rows and columns of its argument.

Folds

foldl :: (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b Source #

foldl' :: (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> b Source #

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

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

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

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

foldMap :: Monoid m => (a %1 -> m) -> [a] %1 -> m Source #

Map each element of the structure to a monoid, and combine the results.

foldMap' :: Monoid m => (a %1 -> m) -> [a] %1 -> m Source #

A variant of foldMap that is strict in the accumulator.

Special folds

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

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

and :: [Bool] %1 -> Bool Source #

NOTE: This does not short-circuit, and always consumes the entire container.

or :: [Bool] %1 -> Bool Source #

NOTE: This does not short-circuit, and always consumes the entire container.

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

NOTE: This does not short-circuit, and always consumes the entire container.

all :: (a %1 -> Bool) -> [a] %1 -> Bool Source #

NOTE: This does not short-circuit, and always consumes the entire container.

sum :: AddIdentity a => [a] %1 -> a Source #

product :: MultIdentity a => [a] %1 -> a Source #

Building lists

scanl :: Dupable b => (b %1 -> a %1 -> b) -> b %1 -> [a] %1 -> [b] Source #

scanl1 :: Dupable a => (a %1 -> a %1 -> a) -> [a] %1 -> [a] Source #

scanr :: Dupable b => (a %1 -> b %1 -> b) -> b %1 -> [a] %1 -> [b] Source #

scanr1 :: Dupable a => (a %1 -> a %1 -> a) -> [a] %1 -> [a] Source #

repeat :: Dupable a => a %1 -> [a] Source #

replicate :: Dupable a => Int -> a %1 -> [a] Source #

cycle :: (HasCallStack, Dupable a) => [a] %1 -> [a] Source #

iterate :: Dupable a => (a %1 -> a) -> a %1 -> [a] Source #

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

Ordered lists

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

The sort function implements a stable sorting algorithm. It is a special case of sortBy, which allows the programmer to supply their own comparison function.

Elements are arranged from lowest to highest, keeping duplicates in the order they appeared in the input.

>>> sort [1,6,4,3,2,5]
[1,2,3,4,5,6]

sortOn :: Ord b => (a -> b) -> [a] -> [a] #

Sort a list by comparing the results of a key function applied to each element. sortOn f is equivalent to sortBy (comparing f), but has the performance advantage of only evaluating f once for each element in the input list. This is called the decorate-sort-undecorate paradigm, or Schwartzian transform.

Elements are arranged from lowest to highest, keeping duplicates in the order they appeared in the input.

>>> sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]

Since: base-4.8.0.0

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

\(\mathcal{O}(n)\). The insert function takes an element and a list and inserts the element into the list at the first position where it is less than or equal to the next element. In particular, if the list is sorted before the call, the result will also be sorted. It is a special case of insertBy, which allows the programmer to supply their own comparison function.

>>> insert 4 [1,2,3,5,6,7]
[1,2,3,4,5,6,7]

Zipping lists

zip :: (Consumable a, Consumable b) => [a] %1 -> [b] %1 -> [(a, b)] Source #

zip' :: [a] %1 -> [b] %1 -> ([(a, b)], Maybe (Either (NonEmpty a) (NonEmpty b))) Source #

Same as zip, but returns the leftovers instead of consuming them.

zip3 :: (Consumable a, Consumable b, Consumable c) => [a] %1 -> [b] %1 -> [c] %1 -> [(a, b, c)] Source #

zipWith :: (Consumable a, Consumable b) => (a %1 -> b %1 -> c) -> [a] %1 -> [b] %1 -> [c] Source #

zipWith' :: (a %1 -> b %1 -> c) -> [a] %1 -> [b] %1 -> ([c], Maybe (Either (NonEmpty a) (NonEmpty b))) Source #

Same as zipWith, but returns the leftovers instead of consuming them.

zipWith3 :: forall a b c d. (Consumable a, Consumable b, Consumable c) => (a %1 -> b %1 -> c %1 -> d) -> [a] %1 -> [b] %1 -> [c] %1 -> [d] Source #

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

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

Orphan instances

Monoid [a] Source # 
Instance details

Methods

mempty :: [a] Source #

Semigroup (NonEmpty a) Source # 
Instance details

Methods

(<>) :: NonEmpty a %1 -> NonEmpty a %1 -> NonEmpty a Source #

Semigroup [a] Source # 
Instance details

Methods

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