rio-0.1.19.0: A standard library for Haskell

Safe HaskellSafe
LanguageHaskell2010

RIO.NonEmpty

Contents

Description

NonEmpty list. Import as:

import qualified RIO.NonEmpty as NE

This module does not export any partial functions. For those, see RIO.NonEmpty.Partial

Synopsis

The type of non-empty streams

data NonEmpty a #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 
Instances
Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

(<$) :: a -> NonEmpty b -> NonEmpty a #

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

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

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

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> 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

Since: base-4.9.0.0

Instance details

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

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

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

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

NFData1 NonEmpty

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a) :: Type #

Methods

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

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

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

Eq a => Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Data a => Data (NonEmpty a)

Since: base-4.9.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) -> 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 :: (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) #

Ord a => Ord (NonEmpty a)

Since: base-4.9.0.0

Instance details

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

Read a => Read (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

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

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

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

NFData a => NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () #

Hashable a => Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type #

Methods

from1 :: NonEmpty a -> Rep1 NonEmpty a #

to1 :: Rep1 NonEmpty a -> NonEmpty a #

Each (NonEmpty a) (NonEmpty b) a b 
Instance details

Defined in Lens.Micro.Internal

Methods

each :: Traversal (NonEmpty a) (NonEmpty b) a b #

type Rep (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

type Item (NonEmpty a) = a
type Rep1 NonEmpty

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Non-empty stream transformations

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

Map a function over a NonEmpty stream.

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]

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.

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.

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

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

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

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

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

sortBy for NonEmpty, behaves the same as sortBy

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

sortWith for NonEmpty, behaves the same as:

sortBy . comparing

Basic functions

length :: NonEmpty a -> Int #

Number of elements in NonEmpty list.

head :: NonEmpty a -> a #

Extract the first element of the stream.

tail :: NonEmpty a -> [a] #

Extract the possibly-empty tail of the stream.

last :: NonEmpty a -> a #

Extract the last element of the stream.

init :: NonEmpty a -> [a] #

Extract everything except the last element of the stream.

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

Prepend an element to the stream.

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

Synonym for <|.

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

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

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

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

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

Sort a stream.

reverse :: NonEmpty a -> NonEmpty a #

reverse a finite NonEmpty stream.

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

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

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

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

Building streams

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

repeat :: a -> NonEmpty a #

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

cycle :: NonEmpty a -> NonEmpty a #

cycle xs returns the infinite repetition of xs:

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

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.

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

some1 x sequences x one or more times.

Extracting sublists

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

take n xs returns the first n elements of xs.

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

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

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

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

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

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

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

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

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

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

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

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

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)

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" : ...

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

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

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

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

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

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.

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

groupBy1 is to group1 as groupBy is to group.

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

Sublist predicates

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

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

Set-like operations

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.

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.

Zipping and unzipping streams

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

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

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.

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

The unzip function is the inverse of the zip function.

Converting to and from a list

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

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

toList :: NonEmpty a -> [a] #

Convert a stream to a normal list efficiently.

xor :: NonEmpty Bool -> Bool #

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