{-# LANGUAGE Trustworthy #-} -- can't use Safe due to IsList instance
{-# LANGUAGE TypeFamilies #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.List.NonEmpty
-- Copyright   :  (C) 2011-2015 Edward Kmett,
--                (C) 2010 Tony Morris, Oliver Taylor, Eelis van der Weegen
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- A 'NonEmpty' list is one which always has at least one element, but
-- is otherwise identical to the traditional list type in complexity
-- and in terms of API. You will almost certainly want to import this
-- module @qualified@.
--
-- @since 4.9.0.0
----------------------------------------------------------------------------

module Data.List.NonEmpty (
   -- * The type of non-empty streams
     NonEmpty(..)

   -- * Non-empty stream transformations
   , map         -- :: (a -> b) -> NonEmpty a -> NonEmpty b
   , intersperse -- :: a -> NonEmpty a -> NonEmpty a
   , scanl       -- :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
   , scanr       -- :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
   , scanl1      -- :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
   , scanr1      -- :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
   , transpose   -- :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
   , sortBy      -- :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
   , sortWith      -- :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
   -- * Basic functions
   , length      -- :: NonEmpty a -> Int
   , head        -- :: NonEmpty a -> a
   , tail        -- :: NonEmpty a -> [a]
   , last        -- :: NonEmpty a -> a
   , init        -- :: NonEmpty a -> [a]
   , singleton   -- :: a -> NonEmpty a
   , (<|), cons  -- :: a -> NonEmpty a -> NonEmpty a
   , uncons      -- :: NonEmpty a -> (a, Maybe (NonEmpty a))
   , unfoldr     -- :: (a -> (b, Maybe a)) -> a -> NonEmpty b
   , sort        -- :: NonEmpty a -> NonEmpty a
   , reverse     -- :: NonEmpty a -> NonEmpty a
   , inits       -- :: Foldable f => f a -> NonEmpty a
   , tails       -- :: Foldable f => f a -> NonEmpty a
   , append      -- :: NonEmpty a -> NonEmpty a -> NonEmpty a
   , appendList  -- :: NonEmpty a -> [a] -> NonEmpty a
   , prependList -- :: [a] -> NonEmpty a -> NonEmpty a
   -- * Building streams
   , iterate     -- :: (a -> a) -> a -> NonEmpty a
   , repeat      -- :: a -> NonEmpty a
   , cycle       -- :: NonEmpty a -> NonEmpty a
   , unfold      -- :: (a -> (b, Maybe a) -> a -> NonEmpty b
   , insert      -- :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
   , some1       -- :: Alternative f => f a -> f (NonEmpty a)
   -- * Extracting sublists
   , take        -- :: Int -> NonEmpty a -> [a]
   , drop        -- :: Int -> NonEmpty a -> [a]
   , splitAt     -- :: Int -> NonEmpty a -> ([a], [a])
   , takeWhile   -- :: Int -> NonEmpty a -> [a]
   , dropWhile   -- :: Int -> NonEmpty a -> [a]
   , span        -- :: Int -> NonEmpty a -> ([a],[a])
   , break       -- :: Int -> NonEmpty a -> ([a],[a])
   , filter      -- :: (a -> Bool) -> NonEmpty a -> [a]
   , partition   -- :: (a -> Bool) -> NonEmpty a -> ([a],[a])
   , group       -- :: Foldable f => Eq a => f a -> [NonEmpty a]
   , groupBy     -- :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
   , groupWith     -- :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
   , groupAllWith  -- :: (Foldable f, Ord b) => (a -> b) -> f a -> [NonEmpty a]
   , group1      -- :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
   , groupBy1    -- :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
   , groupWith1     -- :: (Foldable f, Eq b) => (a -> b) -> f a -> NonEmpty (NonEmpty a)
   , groupAllWith1  -- :: (Foldable f, Ord b) => (a -> b) -> f a -> NonEmpty (NonEmpty a)
   -- * Sublist predicates
   , isPrefixOf  -- :: Foldable f => f a -> NonEmpty a -> Bool
   -- * \"Set\" operations
   , nub         -- :: Eq a => NonEmpty a -> NonEmpty a
   , nubBy       -- :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
   -- * Indexing streams
   , (!!)        -- :: NonEmpty a -> Int -> a
   -- * Zipping and unzipping streams
   , zip         -- :: NonEmpty a -> NonEmpty b -> NonEmpty (a,b)
   , zipWith     -- :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
   , unzip       -- :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
   -- * Converting to and from a list
   , fromList    -- :: [a] -> NonEmpty a
   , toList      -- :: NonEmpty a -> [a]
   , nonEmpty    -- :: [a] -> Maybe (NonEmpty a)
   , xor         -- :: NonEmpty a -> Bool
   ) where


import           Prelude             hiding (break, cycle, drop, dropWhile,
                                      filter, foldl, foldr, head, init, iterate,
                                      last, length, map, repeat, reverse,
                                      scanl, scanl1, scanr, scanr1, span,
                                      splitAt, tail, take, takeWhile,
                                      unzip, zip, zipWith, (!!))
import qualified Prelude

import           Control.Applicative (Applicative (..), Alternative (many))
import           Data.Foldable       hiding (length, toList)
import qualified Data.Foldable       as Foldable
import           Data.Function       (on)
import qualified Data.List           as List
import           Data.Ord            (comparing)
import           GHC.Base            (NonEmpty(..))

infixr 5 <|

-- $setup
-- >>> import Prelude (negate)

-- | Number of elements in 'NonEmpty' list.
length :: NonEmpty a -> Int
length :: forall a. NonEmpty a -> Int
length (a
_ :| [a]
xs) = Int
1 forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length [a]
xs

-- | Compute n-ary logic exclusive OR operation on 'NonEmpty' list.
xor :: NonEmpty Bool -> Bool
xor :: NonEmpty Bool -> Bool
xor (Bool
x :| [Bool]
xs)   = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Bool -> Bool -> Bool
xor' Bool
x [Bool]
xs
  where xor' :: Bool -> Bool -> Bool
xor' Bool
True Bool
y  = Bool -> Bool
not Bool
y
        xor' Bool
False Bool
y = Bool
y

-- | '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.
unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b
unfold :: forall a b. (a -> (b, Maybe a)) -> a -> NonEmpty b
unfold a -> (b, Maybe a)
f a
a = case a -> (b, Maybe a)
f a
a of
  (b
b, Maybe a
Nothing) -> b
b forall a. a -> [a] -> NonEmpty a
:| []
  (b
b, Just a
c)  -> b
b forall a. a -> NonEmpty a -> NonEmpty a
<| forall a b. (a -> (b, Maybe a)) -> a -> NonEmpty b
unfold a -> (b, Maybe a)
f a
c
{-# DEPRECATED unfold "Use unfoldr" #-}
-- Deprecated in 8.2.1, remove in 8.4

-- | 'nonEmpty' efficiently turns a normal list into a 'NonEmpty' stream,
-- producing 'Nothing' if the input is empty.
nonEmpty :: [a] -> Maybe (NonEmpty a)
nonEmpty :: forall a. [a] -> Maybe (NonEmpty a)
nonEmpty []     = forall a. Maybe a
Nothing
nonEmpty (a
a:[a]
as) = forall a. a -> Maybe a
Just (a
a forall a. a -> [a] -> NonEmpty a
:| [a]
as)

-- | 'uncons' produces the first element of the stream, and a stream of the
-- remaining elements, if any.
uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
uncons :: forall a. NonEmpty a -> (a, Maybe (NonEmpty a))
uncons ~(a
a :| [a]
as) = (a
a, forall a. [a] -> Maybe (NonEmpty a)
nonEmpty [a]
as)

-- | The 'unfoldr' function is analogous to "Data.List"'s
-- 'Data.List.unfoldr' operation.
unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
unfoldr :: forall a b. (a -> (b, Maybe a)) -> a -> NonEmpty b
unfoldr a -> (b, Maybe a)
f a
a = case a -> (b, Maybe a)
f a
a of
  (b
b, Maybe a
mc) -> b
b forall a. a -> [a] -> NonEmpty a
:| forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] a -> [b]
go Maybe a
mc
 where
    go :: a -> [b]
go a
c = case a -> (b, Maybe a)
f a
c of
      (b
d, Maybe a
me) -> b
d forall a. a -> [a] -> [a]
: forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] a -> [b]
go Maybe a
me

-- | Extract the first element of the stream.
head :: NonEmpty a -> a
head :: forall a. NonEmpty a -> a
head (a
a :| [a]
_) = a
a

-- | Extract the possibly-empty tail of the stream.
tail :: NonEmpty a -> [a]
tail :: forall a. NonEmpty a -> [a]
tail (a
_ :| [a]
as) = [a]
as

-- | Extract the last element of the stream.
last :: NonEmpty a -> a
last :: forall a. NonEmpty a -> a
last ~(a
a :| [a]
as) = forall a. [a] -> a
List.last (a
a forall a. a -> [a] -> [a]
: [a]
as)

-- | Extract everything except the last element of the stream.
init :: NonEmpty a -> [a]
init :: forall a. NonEmpty a -> [a]
init ~(a
a :| [a]
as) = forall a. [a] -> [a]
List.init (a
a forall a. a -> [a] -> [a]
: [a]
as)

-- | Construct a 'NonEmpty' list from a single element.
--
-- @since 4.15
singleton :: a -> NonEmpty a
singleton :: forall a. a -> NonEmpty a
singleton a
a = a
a forall a. a -> [a] -> NonEmpty a
:| []

-- | Prepend an element to the stream.
(<|) :: a -> NonEmpty a -> NonEmpty a
a
a <| :: forall a. a -> NonEmpty a -> NonEmpty a
<| ~(a
b :| [a]
bs) = a
a forall a. a -> [a] -> NonEmpty a
:| a
b forall a. a -> [a] -> [a]
: [a]
bs

-- | Synonym for '<|'.
cons :: a -> NonEmpty a -> NonEmpty a
cons :: forall a. a -> NonEmpty a -> NonEmpty a
cons = forall a. a -> NonEmpty a -> NonEmpty a
(<|)

-- | Sort a stream.
sort :: Ord a => NonEmpty a -> NonEmpty a
sort :: forall a. Ord a => NonEmpty a -> NonEmpty a
sort = forall (f :: * -> *) a b.
Foldable f =>
([a] -> [b]) -> f a -> NonEmpty b
lift forall a. Ord a => [a] -> [a]
List.sort

-- | Converts a normal list to a 'NonEmpty' stream.
--
-- Raises an error if given an empty list.
fromList :: [a] -> NonEmpty a
fromList :: forall a. [a] -> NonEmpty a
fromList (a
a:[a]
as) = a
a forall a. a -> [a] -> NonEmpty a
:| [a]
as
fromList [] = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NonEmpty.fromList: empty list"

-- | Convert a stream to a normal list efficiently.
toList :: NonEmpty a -> [a]
toList :: forall a. NonEmpty a -> [a]
toList ~(a
a :| [a]
as) = a
a forall a. a -> [a] -> [a]
: [a]
as

-- | Lift list operations to work on a 'NonEmpty' stream.
--
-- /Beware/: If the provided function returns an empty list,
-- this will raise an error.
lift :: Foldable f => ([a] -> [b]) -> f a -> NonEmpty b
lift :: forall (f :: * -> *) a b.
Foldable f =>
([a] -> [b]) -> f a -> NonEmpty b
lift [a] -> [b]
f = forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [b]
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList

-- | Map a function over a 'NonEmpty' stream.
map :: (a -> b) -> NonEmpty a -> NonEmpty b
map :: forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
map a -> b
f ~(a
a :| [a]
as) = a -> b
f a
a forall a. a -> [a] -> NonEmpty a
:| forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f [a]
as

-- | The 'inits' function takes a stream @xs@ and returns all the
-- finite prefixes of @xs@.
inits :: Foldable f => f a -> NonEmpty [a]
inits :: forall (f :: * -> *) a. Foldable f => f a -> NonEmpty [a]
inits = forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [[a]]
List.inits forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList

-- | The 'tails' function takes a stream @xs@ and returns all the
-- suffixes of @xs@.
tails   :: Foldable f => f a -> NonEmpty [a]
tails :: forall (f :: * -> *) a. Foldable f => f a -> NonEmpty [a]
tails = forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [[a]]
List.tails forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList

-- | @'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.
insert  :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
insert :: forall (f :: * -> *) a.
(Foldable f, Ord a) =>
a -> f a -> NonEmpty a
insert a
a = forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> [a] -> [a]
List.insert a
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList

-- | @'some1' x@ sequences @x@ one or more times.
some1 :: Alternative f => f a -> f (NonEmpty a)
some1 :: forall (f :: * -> *) a. Alternative f => f a -> f (NonEmpty a)
some1 f a
x = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. a -> [a] -> NonEmpty a
(:|) f a
x (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many f a
x)

-- | '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.
scanl   :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
scanl :: forall (f :: * -> *) b a.
Foldable f =>
(b -> a -> b) -> b -> f a -> NonEmpty b
scanl b -> a -> b
f b
z = forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. (b -> a -> b) -> b -> [a] -> [b]
List.scanl b -> a -> b
f b
z forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList

-- | 'scanr' is the right-to-left dual of 'scanl'.
-- Note that
--
-- > head (scanr f z xs) == foldr f z xs.
scanr   :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
scanr :: forall (f :: * -> *) a b.
Foldable f =>
(a -> b -> b) -> b -> f a -> NonEmpty b
scanr a -> b -> b
f b
z = forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b -> b) -> b -> [a] -> [b]
List.scanr a -> b -> b
f b
z forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList

-- | '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), ...]
scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
scanl1 :: forall a. (a -> a -> a) -> NonEmpty a -> NonEmpty a
scanl1 a -> a -> a
f ~(a
a :| [a]
as) = forall a. [a] -> NonEmpty a
fromList (forall b a. (b -> a -> b) -> b -> [a] -> [b]
List.scanl a -> a -> a
f a
a [a]
as)

-- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
scanr1 :: forall a. (a -> a -> a) -> NonEmpty a -> NonEmpty a
scanr1 a -> a -> a
f ~(a
a :| [a]
as) = forall a. [a] -> NonEmpty a
fromList (forall a. (a -> a -> a) -> [a] -> [a]
List.scanr1 a -> a -> a
f (a
aforall a. a -> [a] -> [a]
:[a]
as))

-- | 'intersperse x xs' alternates elements of the list with copies of @x@.
--
-- > intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]
intersperse :: a -> NonEmpty a -> NonEmpty a
intersperse :: forall a. a -> NonEmpty a -> NonEmpty a
intersperse a
a ~(a
b :| [a]
bs) = a
b forall a. a -> [a] -> NonEmpty a
:| case [a]
bs of
    [] -> []
    [a]
_ -> a
a forall a. a -> [a] -> [a]
: forall a. a -> [a] -> [a]
List.intersperse a
a [a]
bs

-- | @'iterate' f x@ produces the infinite sequence
-- of repeated applications of @f@ to @x@.
--
-- > iterate f x = x :| [f x, f (f x), ..]
iterate :: (a -> a) -> a -> NonEmpty a
iterate :: forall a. (a -> a) -> a -> NonEmpty a
iterate a -> a
f a
a = a
a forall a. a -> [a] -> NonEmpty a
:| forall a. (a -> a) -> a -> [a]
List.iterate a -> a
f (a -> a
f a
a)

-- | @'cycle' xs@ returns the infinite repetition of @xs@:
--
-- > cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]
cycle :: NonEmpty a -> NonEmpty a
cycle :: forall a. NonEmpty a -> NonEmpty a
cycle = forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
List.cycle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | 'reverse' a finite NonEmpty stream.
reverse :: NonEmpty a -> NonEmpty a
reverse :: forall a. NonEmpty a -> NonEmpty a
reverse = forall (f :: * -> *) a b.
Foldable f =>
([a] -> [b]) -> f a -> NonEmpty b
lift forall a. [a] -> [a]
List.reverse

-- | @'repeat' x@ returns a constant stream, where all elements are
-- equal to @x@.
repeat :: a -> NonEmpty a
repeat :: forall a. a -> NonEmpty a
repeat a
a = a
a forall a. a -> [a] -> NonEmpty a
:| forall a. a -> [a]
List.repeat a
a

-- | @'take' n xs@ returns the first @n@ elements of @xs@.
take :: Int -> NonEmpty a -> [a]
take :: forall a. Int -> NonEmpty a -> [a]
take Int
n = forall a. Int -> [a] -> [a]
List.take Int
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | @'drop' n xs@ drops the first @n@ elements off the front of
-- the sequence @xs@.
drop :: Int -> NonEmpty a -> [a]
drop :: forall a. Int -> NonEmpty a -> [a]
drop Int
n = forall a. Int -> [a] -> [a]
List.drop Int
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | @'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
splitAt :: Int -> NonEmpty a -> ([a],[a])
splitAt :: forall a. Int -> NonEmpty a -> ([a], [a])
splitAt Int
n = forall a. Int -> [a] -> ([a], [a])
List.splitAt Int
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | @'takeWhile' p xs@ returns the longest prefix of the stream
-- @xs@ for which the predicate @p@ holds.
takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
takeWhile :: forall a. (a -> Bool) -> NonEmpty a -> [a]
takeWhile a -> Bool
p = forall a. (a -> Bool) -> [a] -> [a]
List.takeWhile a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | @'dropWhile' p xs@ returns the suffix remaining after
-- @'takeWhile' p xs@.
dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
dropWhile :: forall a. (a -> Bool) -> NonEmpty a -> [a]
dropWhile a -> Bool
p = forall a. (a -> Bool) -> [a] -> [a]
List.dropWhile a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | @'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
span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
span :: forall a. (a -> Bool) -> NonEmpty a -> ([a], [a])
span a -> Bool
p = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.span a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | The @'break' p@ function is equivalent to @'span' (not . p)@.
break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
break :: forall a. (a -> Bool) -> NonEmpty a -> ([a], [a])
break a -> Bool
p = forall a. (a -> Bool) -> NonEmpty a -> ([a], [a])
span (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p)

-- | @'filter' p xs@ removes any elements from @xs@ that do not satisfy @p@.
filter :: (a -> Bool) -> NonEmpty a -> [a]
filter :: forall a. (a -> Bool) -> NonEmpty a -> [a]
filter a -> Bool
p = forall a. (a -> Bool) -> [a] -> [a]
List.filter a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | 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)
partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
partition :: forall a. (a -> Bool) -> NonEmpty a -> ([a], [a])
partition a -> Bool
p = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.partition a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList

-- | 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" : ...
group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
group :: forall (f :: * -> *) a. (Foldable f, Eq a) => f a -> [NonEmpty a]
group = forall (f :: * -> *) a.
Foldable f =>
(a -> a -> Bool) -> f a -> [NonEmpty a]
groupBy forall a. Eq a => a -> a -> Bool
(==)

-- | 'groupBy' operates like 'group', but uses the provided equality
-- predicate instead of `==`.
groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
groupBy :: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> Bool) -> f a -> [NonEmpty a]
groupBy a -> a -> Bool
eq0 = forall {a}. (a -> a -> Bool) -> [a] -> [NonEmpty a]
go a -> a -> Bool
eq0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList
  where
    go :: (a -> a -> Bool) -> [a] -> [NonEmpty a]
go a -> a -> Bool
_  [] = []
    go a -> a -> Bool
eq (a
x : [a]
xs) = (a
x forall a. a -> [a] -> NonEmpty a
:| [a]
ys) forall a. a -> [a] -> [a]
: forall (f :: * -> *) a.
Foldable f =>
(a -> a -> Bool) -> f a -> [NonEmpty a]
groupBy a -> a -> Bool
eq [a]
zs
      where ([a]
ys, [a]
zs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.span (a -> a -> Bool
eq a
x) [a]
xs

-- | 'groupWith' operates like 'group', but uses the provided projection when
-- comparing for equality
groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
groupWith :: forall (f :: * -> *) b a.
(Foldable f, Eq b) =>
(a -> b) -> f a -> [NonEmpty a]
groupWith a -> b
f = forall (f :: * -> *) a.
Foldable f =>
(a -> a -> Bool) -> f a -> [NonEmpty a]
groupBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` a -> b
f)

-- | 'groupAllWith' operates like 'groupWith', but sorts the list
-- first so that each equivalence class has, at most, one list in the
-- output
groupAllWith :: (Ord b) => (a -> b) -> [a] -> [NonEmpty a]
groupAllWith :: forall b a. Ord b => (a -> b) -> [a] -> [NonEmpty a]
groupAllWith a -> b
f = forall (f :: * -> *) b a.
(Foldable f, Eq b) =>
(a -> b) -> f a -> [NonEmpty a]
groupWith a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy (forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` a -> b
f)

-- | 'group1' operates like 'group', but uses the knowledge that its
-- input is non-empty to produce guaranteed non-empty output.
group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
group1 :: forall a. Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
group1 = forall a. (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupBy1 forall a. Eq a => a -> a -> Bool
(==)

-- | 'groupBy1' is to 'group1' as 'groupBy' is to 'group'.
groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupBy1 :: forall a. (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupBy1 a -> a -> Bool
eq (a
x :| [a]
xs) = (a
x forall a. a -> [a] -> NonEmpty a
:| [a]
ys) forall a. a -> [a] -> NonEmpty a
:| forall (f :: * -> *) a.
Foldable f =>
(a -> a -> Bool) -> f a -> [NonEmpty a]
groupBy a -> a -> Bool
eq [a]
zs
  where ([a]
ys, [a]
zs) = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.span (a -> a -> Bool
eq a
x) [a]
xs

-- | 'groupWith1' is to 'group1' as 'groupWith' is to 'group'
groupWith1 :: (Eq b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupWith1 :: forall b a. Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupWith1 a -> b
f = forall a. (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupBy1 (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` a -> b
f)

-- | 'groupAllWith1' is to 'groupWith1' as 'groupAllWith' is to 'groupWith'
groupAllWith1 :: (Ord b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupAllWith1 :: forall b a.
Ord b =>
(a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupAllWith1 a -> b
f = forall b a. Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupWith1 a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall o a. Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
sortWith a -> b
f

-- | The 'isPrefixOf' function returns 'True' if the first argument is
-- a prefix of the second.
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
isPrefixOf :: forall a. Eq a => [a] -> NonEmpty a -> Bool
isPrefixOf [] NonEmpty a
_ = Bool
True
isPrefixOf (a
y:[a]
ys) (a
x :| [a]
xs) = (a
y forall a. Eq a => a -> a -> Bool
== a
x) Bool -> Bool -> Bool
&& forall a. Eq a => [a] -> [a] -> Bool
List.isPrefixOf [a]
ys [a]
xs

-- | @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.
(!!) :: NonEmpty a -> Int -> a
!! :: forall a. NonEmpty a -> Int -> a
(!!) ~(a
x :| [a]
xs) Int
n
  | Int
n forall a. Eq a => a -> a -> Bool
== Int
0 = a
x
  | Int
n forall a. Ord a => a -> a -> Bool
> Int
0  = [a]
xs forall a. [a] -> Int -> a
List.!! (Int
n forall a. Num a => a -> a -> a
- Int
1)
  | Bool
otherwise = forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NonEmpty.!! negative argument"
infixl 9 !!

-- | The 'zip' function takes two streams and returns a stream of
-- corresponding pairs.
zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a,b)
zip :: forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
zip ~(a
x :| [a]
xs) ~(b
y :| [b]
ys) = (a
x, b
y) forall a. a -> [a] -> NonEmpty a
:| forall a b. [a] -> [b] -> [(a, b)]
List.zip [a]
xs [b]
ys

-- | The 'zipWith' function generalizes 'zip'. Rather than tupling
-- the elements, the elements are combined using the function
-- passed as the first argument.
zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
zipWith :: forall a b c.
(a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
zipWith a -> b -> c
f ~(a
x :| [a]
xs) ~(b
y :| [b]
ys) = a -> b -> c
f a
x b
y forall a. a -> [a] -> NonEmpty a
:| forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
List.zipWith a -> b -> c
f [a]
xs [b]
ys

-- | The 'unzip' function is the inverse of the 'zip' function.
unzip :: Functor f => f (a,b) -> (f a, f b)
unzip :: forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
unzip f (a, b)
xs = (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (a, b)
xs, forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (a, b)
xs)

-- | 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.
nub :: Eq a => NonEmpty a -> NonEmpty a
nub :: forall a. Eq a => NonEmpty a -> NonEmpty a
nub = forall a. (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
nubBy forall a. Eq a => a -> a -> Bool
(==)

-- | The 'nubBy' function behaves just like 'nub', except it uses a
-- user-supplied equality predicate instead of the overloaded '=='
-- function.
nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
nubBy :: forall a. (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
nubBy a -> a -> Bool
eq (a
a :| [a]
as) = a
a forall a. a -> [a] -> NonEmpty a
:| forall a. (a -> a -> Bool) -> [a] -> [a]
List.nubBy a -> a -> Bool
eq (forall a. (a -> Bool) -> [a] -> [a]
List.filter (\a
b -> Bool -> Bool
not (a -> a -> Bool
eq a
a a
b)) [a]
as)

-- | 'transpose' for 'NonEmpty', behaves the same as 'Data.List.transpose'
-- The rows/columns need not be the same length, in which case
-- > transpose . transpose /= id
transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
transpose :: forall a. NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
transpose = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. [a] -> NonEmpty a
fromList
          forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> NonEmpty a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [[a]] -> [[a]]
List.transpose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> [a]
toList
          forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. NonEmpty a -> [a]
toList

-- | 'sortBy' for 'NonEmpty', behaves the same as 'Data.List.sortBy'
sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
sortBy :: forall a. (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
sortBy a -> a -> Ordering
f = forall (f :: * -> *) a b.
Foldable f =>
([a] -> [b]) -> f a -> NonEmpty b
lift (forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy a -> a -> Ordering
f)

-- | 'sortWith' for 'NonEmpty', behaves the same as:
--
-- > sortBy . comparing
sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
sortWith :: forall o a. Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
sortWith = forall a. (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
sortBy forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing

-- | A monomorphic version of '<>' for 'NonEmpty'.
--
-- >>> append (1 :| []) (2 :| [3])
-- 1 :| [2,3]
--
-- @since 4.16
append :: NonEmpty a -> NonEmpty a -> NonEmpty a
append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a
append = forall a. Semigroup a => a -> a -> a
(<>)

-- | 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 4.16
appendList :: NonEmpty a -> [a] -> NonEmpty a
appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a
appendList (a
x :| [a]
xs) [a]
ys = a
x forall a. a -> [a] -> NonEmpty a
:| [a]
xs forall a. Semigroup a => a -> a -> a
<> [a]
ys

-- | 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 4.16
prependList :: [a] -> NonEmpty a -> NonEmpty a
prependList :: forall a. [a] -> NonEmpty a -> NonEmpty a
prependList [a]
ls NonEmpty a
ne = case [a]
ls of
  [] -> NonEmpty a
ne
  (a
x : [a]
xs) -> a
x forall a. a -> [a] -> NonEmpty a
:| [a]
xs forall a. Semigroup a => a -> a -> a
<> forall a. NonEmpty a -> [a]
toList NonEmpty a
ne