neononempty-1.1.0: NonEmpty lists that look [more, like, this]
Safe HaskellTrustworthy
LanguageHaskell98

Data.List.NeoNonEmpty

Description

NonEmpty - Like base's NonEmpty but with:

  • Show and Read instance similar to `[]`
  • A completely safe API
  • added/removed/updated functions

Added functions:

Removed functions:

  • unzip (not nonempty-specific)
  • unfold (deprecated, use unfoldr)
  • xor (seemed out of place)

Changed functions:

Replaced functions:

  • s(!!)(!?)/
Synopsis

Construction

data NonEmpty a Source #

A list with one or more elements.

Instances

Instances details
MonadFix NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Methods

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

MonadZip NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Methods

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

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

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

Foldable NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

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 #

Eq1 NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Methods

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

Ord1 NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Methods

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

Read1 NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

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

Defined in Data.List.NeoNonEmpty

Methods

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

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

Applicative NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

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 #

Functor NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Methods

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

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

Monad NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Methods

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

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

return :: a -> NonEmpty a #

Generic1 NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Associated Types

type Rep1 NonEmpty :: k -> Type #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a #

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

Defined in Data.List.NeoNonEmpty

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

Semigroup (NonEmpty a) Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Methods

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

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

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

Generic (NonEmpty a) Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Associated Types

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

Methods

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

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

IsList (NonEmpty a) Source # 
Instance details

Defined in Data.List.NeoNonEmpty

Associated Types

type Item (NonEmpty 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) Source # 
Instance details

Defined in Data.List.NeoNonEmpty

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

Defined in Data.List.NeoNonEmpty

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

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

Defined in Data.List.NeoNonEmpty

Methods

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

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

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

Defined in Data.List.NeoNonEmpty

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 #

type Rep1 NonEmpty Source # 
Instance details

Defined in Data.List.NeoNonEmpty

type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "Data.List.NeoNonEmpty" "neononempty-1.1.0-inplace" 'True) (C1 ('MetaCons "NonEmpty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 NonEmpty)))
type Rep (NonEmpty a) Source # 
Instance details

Defined in Data.List.NeoNonEmpty

type Rep (NonEmpty a) = D1 ('MetaData "NonEmpty" "Data.List.NeoNonEmpty" "neononempty-1.1.0-inplace" 'True) (C1 ('MetaCons "NonEmpty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty a))))
type Item (NonEmpty a) Source # 
Instance details

Defined in Data.List.NeoNonEmpty

type Item (NonEmpty a) = a

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

Construct a NonEmpty from an element and a list.

singleton :: a -> NonEmpty a Source #

Construct a NonEmpty list from a single element.

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

Construct a NonEmpty from an element and a list.

Type annotations

aNonEmpty :: NonEmpty a -> NonEmpty a Source #

A non empty thing. Useful as a syntactically lightweight type annotation, especially when using OverloadedLists:

>>> :set -XOverloadedLists
>>> [(), ()]
    • Ambiguous type variable ‘a0’ arising from a use of ‘print’
      prevents the constraint ‘(Show a0)’ from being solved.
>>> aNonEmpty [(), ()]
[(),()]

Converting to and from base's NonEmpty

fromNonEmpty :: NonEmpty a -> NonEmpty a Source #

Converts base's NonEmpty to a NonEmpty

toNonEmpty :: NonEmpty a -> NonEmpty a Source #

Converts a NonEmpty to base's NonEmpty

Converting to and from lists

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

Converts a normal list to a NonEmpty list, given the list has at least one element

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

Converts a NonEmpty list to a normal list

Basic functions

length :: NonEmpty a -> Int Source #

Number of elements in NonEmpty list.

head :: NonEmpty a -> a Source #

Extract the first element of the nonempty stream.

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

Extract the possibly-empty tail of the nonempty stream.

last :: NonEmpty a -> a Source #

Extract the last element of the nonempty stream.

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

Extract everything except the last element of the nonempty stream.

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

Prepend an element to the nonempty stream.

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

Produces the first element of the nonempty stream, and a stream of the remaining elements.

snoc :: NonEmpty a -> a -> NonEmpty a Source #

Append an element to the back of a nonempty stream.

unsnoc :: forall a. NonEmpty a -> ([a], a) Source #

Produces all elements up to the last element, and the last element

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

Dual of foldr, see unfoldr.

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

Sort a nonempty stream.

reverse :: NonEmpty a -> NonEmpty a Source #

Reverse a nonempty stream.

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

Produces all the prefixes of a stream, 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 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a) Source #

Produces all the nonempty prefixes of a nonempty stream, starting with the shortest.

>>> inits1 [1,2,3]
[[1], [1,2], [1,2,3]]
>>> inits1 [1]
[[1]]

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

Produces all the suffixes of a stream, starting with the longest. The result is NonEmpty because the result always contains the empty list as the first element.

>>> tails [1,2,3]
[[1, 2, 3], [2, 3], [3], []]
>>> tails [1]
[[1], []]
>>> tails []
[[]]

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

Produces all the nonempty suffixes of a nonempty stream, starting with the longest.

>>> tails1 [1,2,3]
[[1, 2, 3], [2, 3], [3]]
>>> tails1 [1]
[[1]]

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

A monomorphic version of <> for NonEmpty.

>>> append [1] [2, 3]
[1, 2, 3]

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

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

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

Prepend a list to the front of a NonEmpty.

>>> prependList [] [1, 2, 3]
[1, 2, 3]
>>> prependList [negate 1, 0] [1, 2, 3]
[-1, 0, 1, 2, 3]

Stream transformations

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

Map a function over a NonEmpty stream.

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

Produces a NonEmpty which alternates between elementes of the input list, and the supplied element.

>>> intersperse 0 [1, 2, 3])
[1, 0, 2, 0, 3]
>>> intersperse 0 [1]
[1]

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

Left-associative fold, lazy in the accumulator. See foldl.

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

Left-associative fold, strict in the accumulator. See foldl'.

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

Left-associative fold, strict in the accumulator. See foldl'.

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 (+) 1 [20, 300, 4000]
[1,21,321,4321]

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

A strict version of scanl.

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 #

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
>>> scanr (+) 0 [1..4]
[10,9,7,4,0]
>>> scanr (+) 42 []
[42]
>>> scanr (-) 100 [1..4]
[98,-97,99,-96,100]

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

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

>>> scanr1 (+) [1..4]
[10,9,7,4]
>>> scanr1 (+) []
[]
>>> scanr1 (-) [1..4]
[-2,3,-1,4]

transpose :: forall a. 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

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

Behaves the same as sortBy

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

Sort a list on a projection of its elements. Projects once, then sorts, then un-projects. This is useful when the projection function is expensive. If it's not, you should probably use sortWith.

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

Sort a list on a projection of its elements. Projects during comparison. This is useful when the projection function is cheap. If it's not, you should probably use sortOn.

Building streams

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

repeat :: a -> NonEmpty a Source #

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

cycle :: NonEmpty a -> NonEmpty a Source #

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

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

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

some1 x sequences x one or more times.

Extracting sublists

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

take n xs returns the first n elements of xs.

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

drop n xs drops the first n elements from the front of the sequence 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)

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

Produces the longest prefix of the stream for which the predicate holds.

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

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

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)

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

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

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

Removes any elements of a nonempty stream that do not satisfy a predicate.

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

Produces a pair of lists, the first of elements that satisfy the given predicate, the second of elements that did not.

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

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

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.

>>> group "Mississippi"
["M", "i", "ss", "i", "ss", "i", "pp", "i"]

groupAll :: Ord a => [a] -> [NonEmpty a] Source #

Similar to group, but sorts the input 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 #

Similar to group, but uses the provided equality predicate instead of ==.

groupAllBy :: (a -> a -> Ordering) -> [a] -> [NonEmpty a] Source #

Similar to groupBy, but sorts the input 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] Source #

Similar to group, but uses the provided projection when comparing for equality.

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

Similar to groupWith, but sorts the input first so that each equivalence class has, at most, one list in the output.

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

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

groupAll1 :: Ord a => NonEmpty a -> [NonEmpty a] Source #

Similar to group1, but sorts the input first so that each equivalence class has, at most, one list in the output.

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

Similar to group1, but uses the provided equality predicate instead of ==.

groupAllBy1 :: (a -> a -> Ordering) -> [a] -> [NonEmpty a] Source #

Similar to group, but sorts the input first so that each equivalence class has, at most, one list in the output.

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

Similar to group1, but uses the provided projection when comparing for equality.

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

Similar to groupWith1, but sorts the list first so that each equivalence class has, at most, one list in the output.

Sublist predicates

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

Returns True if the first argument is a prefix of the second.

>>> isPrefixOf [1, 2, 3] [1, 2, 3, 4, 5]
True
>>> isPrefixOf "abc" "defghi"
False
>>> isPrefixOf "abc" ""
False

Set operations

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

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 #

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

Indexing streams

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

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

Zipping streams

zip :: forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b) Source #

\(\mathcal{O}(\min(m,n))\). Takes two streams and produces a stream of corresponding pairs.

>>> zip [1, 2] ['a', 'b']
[(1, 'a'),(2, 'b')]

zipWith :: forall a b c. (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

\(\mathcal{O}(\min(m,n))\). Generalises zip by zipping with the provided function, instead of a tupling function.