ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Data.List.NonEmpty

Synopsis

Documentation

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

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.

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

Prepend an element to the stream.

append :: NonEmpty a -> NonEmpty a -> NonEmpty a Source #

A monomorphic version of <> for NonEmpty.

>>> append (1 :| []) (2 :| [3])
1 :| [2,3]

Since: base-4.16

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

Attach a list at the end of a NonEmpty.

>>> appendList (1 :| [2,3]) []
1 :| [2,3]
>>> appendList (1 :| [2,3]) [4,5]
1 :| [2,3,4,5]

Since: base-4.16

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

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

compareLength :: NonEmpty a -> Int -> Ordering Source #

Use compareLength xs n as a safer and faster alternative to compare (length xs) n. Similarly, it's better to write compareLength xs 10 == LT instead of length xs < 10.

While length would force and traverse the entire spine of xs (which could even diverge if xs is infinite), compareLength traverses at most n elements to determine its result.

>>> compareLength ('a' :| []) 1
EQ
>>> compareLength ('a' :| ['b']) 3
LT
>>> compareLength (0 :| [1..]) 100
GT
>>> compareLength undefined 0
GT
>>> compareLength ('a' :| 'b' : undefined) 1
GT

Since: base-4.21.0.0

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

Synonym for <|.

cycle :: NonEmpty a -> NonEmpty a Source #

cycle xs returns the infinite repetition of xs:

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

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

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

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

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

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

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

fromList :: HasCallStack => [a] -> NonEmpty a Source #

Converts a normal list to a NonEmpty stream.

Raises an error if given an empty list.

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

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, and consecutive equal elements of the input end up in the same stream of the output list. For example, in list notation:

>>> group "Mississippi"
['M' :| "",'i' :| "",'s' :| "s",'i' :| "",'s' :| "s",'i' :| "",'p' :| "p",'i' :| ""]

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

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] Source #

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

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

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

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

groupBy1 is to group1 as groupBy is to group.

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

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

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

head :: NonEmpty a -> a Source #

Extract the first element of the stream.

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

Extract everything except the last element of the stream.

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

The inits function takes a stream xs and returns all the finite prefixes of xs, starting with the shortest. The result is NonEmpty because the result always contains the empty list as the first element.

inits [1,2,3] == [] :| [[1], [1,2], [1,2,3]]
inits [1] == [] :| [[1]]
inits [] == [] :| []

inits1 :: NonEmpty a -> NonEmpty (NonEmpty a) Source #

The inits1 function takes a NonEmpty stream xs and returns all the NonEmpty finite prefixes of xs, starting with the shortest.

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

Since: base-4.18

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

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.

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

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

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

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

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

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

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

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

last :: NonEmpty a -> a Source #

Extract the last element of the stream.

length :: NonEmpty a -> Int Source #

Number of elements in NonEmpty list.

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

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

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

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.

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

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

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

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)

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

The permutations function returns the list of all permutations of the argument.

Since: base-4.20.0.0

permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a) Source #

permutations1 operates like permutations, but uses the knowledge that its input is non-empty to produce output where every element is non-empty.

permutations1 = fmap fromList . permutations . toList

Since: base-4.20.0.0

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

Attach a list at the beginning of a NonEmpty.

>>> prependList [] (1 :| [2,3])
1 :| [2,3]
>>> prependList [negate 1, 0] (1 :| [2, 3])
-1 :| [0,1,2,3]

Since: base-4.16

repeat :: a -> NonEmpty a Source #

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

reverse :: NonEmpty a -> NonEmpty a Source #

reverse a finite NonEmpty stream.

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

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.

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

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 Source #

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

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

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

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

singleton :: a -> NonEmpty a Source #

Construct a NonEmpty list from a single element.

Since: base-4.15

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

some1 x sequences x one or more times.

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

Sort a stream.

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

sortBy for NonEmpty, behaves the same as sortBy

sortOn :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty a Source #

Sort a NonEmpty on a user-supplied projection of its elements. See sortOn for more detailed information.

Examples

Expand
>>> sortOn fst $ (2, "world") :| [(4, "!"), (1, "Hello")]
(1,"Hello") :| [(2,"world"),(4,"!")]
>>> sortOn List.length ("jim" :| ["creed", "pam", "michael", "dwight", "kevin"])
"jim" :| ["pam","creed","kevin","dwight","michael"]

Performance notes

Expand

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

sortWith is an alias for `sortBy . comparing`.

Since: base-4.20.0.0

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

sortWith for NonEmpty, behaves the same as:

sortBy . comparing

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

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

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

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

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

Extract the possibly-empty tail of the stream.

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

The tails function takes a stream xs and returns all the suffixes of xs, starting with the longest. The result is NonEmpty because the result always contains the empty list as the last element.

tails [1,2,3] == [1,2,3] :| [[2,3], [3], []]
tails [1] == [1] :| [[]]
tails [] == [] :| []

tails1 :: NonEmpty a -> NonEmpty (NonEmpty a) Source #

The tails1 function takes a NonEmpty stream xs and returns all the non-empty suffixes of xs, starting with the longest.

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

Since: base-4.18

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

take n xs returns the first n elements of xs.

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

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

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

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

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

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

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

Deprecated: Use unfoldr

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.

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

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

xor :: NonEmpty Bool -> Bool Source #

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

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

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

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

data NonEmpty a #

Constructors

a :| [a] 

Instances

Instances details
Foldable1 NonEmpty Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => NonEmpty m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> NonEmpty a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> NonEmpty a -> m Source #

toNonEmpty :: NonEmpty a -> NonEmpty a Source #

maximum :: Ord a => NonEmpty a -> a Source #

minimum :: Ord a => NonEmpty a -> a Source #

head :: NonEmpty a -> a Source #

last :: NonEmpty a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b Source #

Eq1 NonEmpty Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool Source #

Ord1 NonEmpty Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering Source #

Read1 NonEmpty Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Show1 NonEmpty Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

NFData1 NonEmpty Source #

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> NonEmpty a -> () Source #

MonadFix NonEmpty # 
Instance details

Defined in GHC.Internal.Control.Monad.Fix

Methods

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

Foldable NonEmpty # 
Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m #

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

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

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

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

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

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

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

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

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

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty # 
Instance details

Defined in GHC.Internal.Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Generic1 NonEmpty # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 NonEmpty 
Instance details

Defined in GHC.Internal.Generics

Methods

from1 :: NonEmpty a -> Rep1 NonEmpty a #

to1 :: Rep1 NonEmpty a -> NonEmpty a #

Lift a => Lift (NonEmpty a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NonEmpty a -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => NonEmpty a -> Code m (NonEmpty a)

Binary a => Binary (NonEmpty a) Source #

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

NFData a => NFData (NonEmpty a) Source #

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () Source #

Binary a => Binary (NonEmpty a) Source # 
Instance details

Defined in GHC.Utils.Binary

Outputable a => Outputable (NonEmpty a) Source # 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: NonEmpty a -> SDoc Source #

Eq a => Eq (NonEmpty a) # 
Instance details

Defined in GHC.Internal.Base

Methods

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

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Ord a => Ord (NonEmpty a) # 
Instance details

Defined in GHC.Internal.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

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

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

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

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

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Data a => Data (NonEmpty a) # 
Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) #

toConstr :: NonEmpty a -> Constr #

dataTypeOf :: NonEmpty a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) #

gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

Generic (NonEmpty a) # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (NonEmpty a) 
Instance details

Defined in GHC.Internal.Generics

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

IsList (NonEmpty a) # 
Instance details

Defined in GHC.Internal.IsList

Associated Types

type Item (NonEmpty a) 
Instance details

Defined in GHC.Internal.IsList

type Item (NonEmpty a) = a

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Read a => Read (NonEmpty a) # 
Instance details

Defined in GHC.Internal.Read

Show a => Show (NonEmpty a) # 
Instance details

Defined in GHC.Internal.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

type Rep1 NonEmpty # 
Instance details

Defined in GHC.Internal.Generics

type Rep (NonEmpty a) # 
Instance details

Defined in GHC.Internal.Generics

type Item (NonEmpty a) # 
Instance details

Defined in GHC.Internal.IsList

type Item (NonEmpty a) = a

mapAndUnzip :: (a -> (b, c)) -> NonEmpty a -> (NonEmpty b, NonEmpty c) Source #

mapAndUnzip3 :: (a -> (b, c, d)) -> NonEmpty a -> (NonEmpty b, NonEmpty c, NonEmpty d) Source #

unzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) Source #

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

zipWithM :: Applicative f => (a -> b -> f c) -> NonEmpty a -> NonEmpty b -> f (NonEmpty c) Source #

toList :: Foldable t => t a -> [a] #