Agda-2.6.2: A dependently typed functional programming language and proof assistant
Safe HaskellNone
LanguageHaskell2010

Agda.Utils.List1

Description

Non-empty lists.

Better name List1 for non-empty lists, plus missing functionality.

Import: @

{--}

import Agda.Utils.List1 (List1, pattern (:|)) import qualified Agda.Utils.List1 as List1

@

Synopsis

Documentation

initLast :: List1 a -> ([a], a) Source #

Return the last element and the rest.

singleton :: a -> List1 a Source #

Build a list with one element.

append :: List1 a -> [a] -> List1 a Source #

Append a list to a non-empty list.

prepend :: [a] -> List1 a -> List1 a Source #

Prepend a list to a non-empty list.

snoc :: [a] -> a -> List1 a Source #

More precise type for snoc.

groupBy' :: forall a. (a -> a -> Bool) -> [a] -> [List1 a] Source #

More precise type for groupBy'.

A variant of groupBy which applies the predicate to consecutive pairs. O(n).

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

Concatenate one or more non-empty lists.

union :: Eq a => List1 a -> List1 a -> List1 a Source #

Like union. Duplicates in the first list are not removed. O(nm).

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

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

unlessNull :: Null m => [a] -> (List1 a -> m) -> m Source #

allEqual :: Eq a => List1 a -> Bool Source #

Checks if all the elements in the list are equal. Assumes that the Eq instance stands for an equivalence relation. O(n).

catMaybes :: List1 (Maybe a) -> [a] Source #

Like catMaybes.

mapMaybe :: (a -> Maybe b) -> List1 a -> [b] Source #

Like filter.

lefts :: List1 (Either a b) -> [a] Source #

Like lefts.

rights :: List1 (Either a b) -> [b] Source #

Like rights.

nubM :: Monad m => (a -> a -> m Bool) -> List1 a -> m (List1 a) Source #

Non-efficient, monadic nub. O(n²).

zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c) Source #

Like zipWithM.

zipWithM_ :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m () Source #

Like zipWithM.

sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a #

sortWith for NonEmpty, behaves the same as:

sortBy . comparing

sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a #

sortBy for NonEmpty, behaves the same as sortBy

transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a) #

transpose for NonEmpty, behaves the same as transpose The rows/columns need not be the same length, in which case > transpose . transpose /= id

nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a #

The nubBy function behaves just like nub, except it uses a user-supplied equality predicate instead of the overloaded == function.

nub :: Eq a => NonEmpty a -> NonEmpty a #

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 inequality test.

unzip :: Functor f => f (a, b) -> (f a, f b) #

The unzip function is the inverse of the zip function.

zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

The zipWith function generalizes zip. Rather than tupling the elements, the elements are combined using the function passed as the first argument.

zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #

The zip function takes two streams and returns a stream of corresponding pairs.

(!!) :: NonEmpty a -> Int -> a infixl 9 #

xs !! n returns the element of the stream xs at index n. Note that the head of the stream has index 0.

Beware: a negative or out-of-bounds index will cause an error.

isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool #

The isPrefixOf function returns True if the first argument is a prefix of the second.

groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #

groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a) #

groupBy1 is to group1 as groupBy is to group.

group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a) #

group1 operates like group, but uses the knowledge that its input is non-empty to produce guaranteed non-empty output.

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

groupAllWith operates like groupWith, but sorts the list first so that each equivalence class has, at most, one list in the output

groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a] #

groupWith operates like group, but uses the provided projection when comparing for equality

groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a] #

groupBy operates like group, but uses the provided equality predicate instead of ==.

group :: (Foldable f, Eq a) => f a -> [NonEmpty a] #

The group function takes a stream and returns a list of streams such that flattening the resulting list is equal to the argument. Moreover, each stream in the resulting list contains only equal elements. For example, in list notation:

'group' $ 'cycle' "Mississippi"
  = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ...

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

The partition function takes a predicate p and a stream xs, and returns a pair of lists. The first list corresponds to the elements of xs for which p holds; the second corresponds to the elements of xs for which p does not hold.

'partition' p xs = ('filter' p xs, 'filter' (not . p) xs)

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

filter p xs removes any elements from xs that do not satisfy p.

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

The break p function is equivalent to span (not . p).

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

span p xs returns the longest prefix of xs that satisfies p, together with the remainder of the stream.

'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs)
xs == ys ++ zs where (ys, zs) = 'span' p xs

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

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

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

takeWhile p xs returns the longest prefix of the stream xs for which the predicate p holds.

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

splitAt n xs returns a pair consisting of the prefix of xs of length n and the remaining stream immediately following this prefix.

'splitAt' n xs == ('take' n xs, 'drop' n xs)
xs == ys ++ zs where (ys, zs) = 'splitAt' n xs

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

drop n xs drops the first n elements off the front of the sequence xs.

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

take n xs returns the first n elements of xs.

repeat :: a -> NonEmpty a #

repeat x returns a constant stream, where all elements are equal to x.

reverse :: NonEmpty a -> NonEmpty a #

reverse a finite NonEmpty stream.

cycle :: NonEmpty a -> NonEmpty a #

cycle xs returns the infinite repetition of xs:

cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]

iterate :: (a -> a) -> a -> NonEmpty a #

iterate f x produces the infinite sequence of repeated applications of f to x.

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

intersperse :: a -> NonEmpty a -> NonEmpty a #

'intersperse x xs' alternates elements of the list with copies of x.

intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]

scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a #

scanr1 is a variant of scanr that has no starting value argument.

scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a #

scanl1 is a variant of scanl that has no starting value argument:

scanl1 f [x1, x2, ...] == x1 :| [x1 `f` x2, x1 `f` (x2 `f` x3), ...]

scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b #

scanr is the right-to-left dual of scanl. Note that

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

scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b #

scanl is similar to foldl, but returns a stream 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.

some1 :: Alternative f => f a -> f (NonEmpty a) #

some1 x sequences x one or more times.

insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a #

insert x xs inserts x into the last position in xs where it is still less than or equal to the next element. In particular, if the list is sorted beforehand, the result will also be sorted.

tails :: Foldable f => f a -> NonEmpty [a] #

The tails function takes a stream xs and returns all the suffixes of xs.

inits :: Foldable f => f a -> NonEmpty [a] #

The inits function takes a stream xs and returns all the finite prefixes of xs.

map :: (a -> b) -> NonEmpty a -> NonEmpty b #

Map a function over a NonEmpty stream.

toList :: NonEmpty a -> [a] #

Convert a stream to a normal list efficiently.

fromList :: [a] -> NonEmpty a #

Converts a normal list to a NonEmpty stream.

Raises an error if given an empty list.

sort :: Ord a => NonEmpty a -> NonEmpty a #

Sort a stream.

cons :: a -> NonEmpty a -> NonEmpty a #

Synonym for <|.

(<|) :: a -> NonEmpty a -> NonEmpty a infixr 5 #

Prepend an element to the stream.

init :: NonEmpty a -> [a] #

Extract everything except the last element of the stream.

last :: NonEmpty a -> a #

Extract the last element of the stream.

tail :: NonEmpty a -> [a] #

Extract the possibly-empty tail of the stream.

head :: NonEmpty a -> a #

Extract the first element of the stream.

unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b #

The unfoldr function is analogous to Data.List's unfoldr operation.

uncons :: NonEmpty a -> (a, Maybe (NonEmpty a)) #

uncons produces the first element of the stream, and a stream of the remaining elements, if any.

nonEmpty :: [a] -> Maybe (NonEmpty a) #

nonEmpty efficiently turns a normal list into a NonEmpty stream, producing Nothing if the input is empty.

unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b #

unfold produces a new stream by repeatedly applying the unfolding function to the seed value to produce an element of type b and a new seed value. When the unfolding function returns Nothing instead of a new seed value, the stream ends.

xor :: NonEmpty Bool -> Bool #

Compute n-ary logic exclusive OR operation on NonEmpty list.

length :: NonEmpty a -> Int #

Number of elements in NonEmpty list.

pattern (:|) :: a -> [a] -> NonEmpty a infixr 5 #