{-# LANGUAGE CPP #-}
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#if defined(MIN_VERSION_hashable) || __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE Trustworthy #-}
#else
{-# LANGUAGE Safe #-}
#endif
#endif
#ifdef __GLASGOW_HASKELL__
#define LANGUAGE_DeriveDataTypeable
{-# LANGUAGE DeriveDataTypeable #-}
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 704
#define LANGUAGE_DeriveGeneric
{-# LANGUAGE DeriveGeneric #-}
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE TypeFamilies #-}
#endif
#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif
module Data.List.NonEmpty (
NonEmpty(..)
, map
, intersperse
, scanl
, scanr
, scanl1
, scanr1
, transpose
, sortBy
, sortWith
, length
, head
, tail
, last
, init
, (<|), cons
, uncons
, unfoldr
, sort
, reverse
, inits
, tails
, iterate
, repeat
, cycle
, unfold
, insert
, some1
, take
, drop
, splitAt
, takeWhile
, dropWhile
, span
, break
, filter
, partition
, group
, groupBy
, groupWith
, groupAllWith
, group1
, groupBy1
, groupWith1
, groupAllWith1
, isPrefixOf
, nub
, nubBy
, (!!)
, zip
, zipWith
, unzip
, fromList
, toList
, nonEmpty
, xor
) where
import qualified Prelude
import Prelude hiding
( head, tail, map, reverse
, scanl, scanl1, scanr, scanr1
, iterate, take, drop, takeWhile
, dropWhile, repeat, cycle, filter
, (!!), zip, unzip, zipWith, words
, unwords, lines, unlines, break, span
, splitAt, foldr, foldl, last, init
, length
)
import Control.Applicative
#ifdef MIN_VERSION_deepseq
import Control.DeepSeq (NFData(..))
#endif
import Control.Monad
import Control.Monad.Fix
#if MIN_VERSION_base(4,4,0)
import Control.Monad.Zip (MonadZip(..))
#endif
#ifdef LANGUAGE_DeriveDataTypeable
import Data.Data
#endif
#if MIN_VERSION_base(4,8,0)
import Data.Foldable hiding (toList, length)
#else
import Data.Foldable hiding (toList)
import Data.Monoid (mappend)
import Data.Traversable
#endif
import qualified Data.Foldable as Foldable
import Data.Function (on)
#ifdef MIN_VERSION_hashable
import Data.Hashable
#endif
import qualified Data.List as List
import Data.Ord (comparing)
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts
#endif
#ifdef LANGUAGE_DeriveGeneric
import GHC.Generics
#endif
infixr 5 :|, <|
data NonEmpty a = a :| [a] deriving
( Eq, Ord, Show, Read
#ifdef LANGUAGE_DeriveDataTypeable
, Data, Typeable
#endif
#ifdef LANGUAGE_DeriveGeneric
, Generic
#if __GLASGOW_HASKELL__ >= 706
, Generic1
#endif
#endif
)
#ifdef MIN_VERSION_hashable
instance Hashable a => Hashable (NonEmpty a) where
#if MIN_VERSION_hashable(1,2,0)
hashWithSalt p (a :| as) = p `hashWithSalt` a `hashWithSalt` as
#else
hash (a :| as) = hash a `combine` hash as
#endif
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 708
instance Exts.IsList (NonEmpty a) where
type Item (NonEmpty a) = a
fromList = fromList
toList = toList
#endif
#ifdef MIN_VERSION_deepseq
instance NFData a => NFData (NonEmpty a) where
rnf (x :| xs) = rnf x `seq` rnf xs
#endif
instance MonadFix NonEmpty where
mfix f = case fix (f . head) of
~(x :| _) -> x :| mfix (tail . f)
#if MIN_VERSION_base(4,4,0)
instance MonadZip NonEmpty where
mzip = zip
mzipWith = zipWith
munzip = unzip
#endif
length :: NonEmpty a -> Int
length (_ :| xs) = 1 + Prelude.length xs
{-# INLINE length #-}
xor :: NonEmpty Bool -> Bool
xor (x :| xs) = foldr xor' x xs
where xor' True y = not y
xor' False y = y
unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b
unfold f a = case f a of
(b, Nothing) -> b :| []
(b, Just c) -> b <| unfold f c
nonEmpty :: [a] -> Maybe (NonEmpty a)
nonEmpty [] = Nothing
nonEmpty (a:as) = Just (a :| as)
{-# INLINE nonEmpty #-}
uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
uncons ~(a :| as) = (a, nonEmpty as)
{-# INLINE uncons #-}
unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
unfoldr f a = case f a of
(b, mc) -> b :| maybe [] go mc
where
go c = case f c of
(d, me) -> d : maybe [] go me
instance Functor NonEmpty where
fmap f ~(a :| as) = f a :| fmap f as
#if MIN_VERSION_base(4,2,0)
b <$ ~(_ :| as) = b :| (b <$ as)
#endif
instance Applicative NonEmpty where
pure a = a :| []
(<*>) = ap
instance Monad NonEmpty where
return a = a :| []
~(a :| as) >>= f = b :| (bs ++ bs')
where b :| bs = f a
bs' = as >>= toList . f
instance Traversable NonEmpty where
traverse f ~(a :| as) = (:|) <$> f a <*> traverse f as
instance Foldable NonEmpty where
foldr f z ~(a :| as) = f a (foldr f z as)
foldl f z ~(a :| as) = foldl f (f z a) as
foldl1 f ~(a :| as) = foldl f a as
foldMap f ~(a :| as) = f a `mappend` foldMap f as
fold ~(m :| ms) = m `mappend` fold ms
head :: NonEmpty a -> a
head ~(a :| _) = a
{-# INLINE head #-}
tail :: NonEmpty a -> [a]
tail ~(_ :| as) = as
{-# INLINE tail #-}
last :: NonEmpty a -> a
last ~(a :| as) = List.last (a : as)
{-# INLINE last #-}
init :: NonEmpty a -> [a]
init ~(a :| as) = List.init (a : as)
{-# INLINE init #-}
(<|) :: a -> NonEmpty a -> NonEmpty a
a <| ~(b :| bs) = a :| b : bs
{-# INLINE (<|) #-}
cons :: a -> NonEmpty a -> NonEmpty a
cons = (<|)
{-# INLINE cons #-}
sort :: Ord a => NonEmpty a -> NonEmpty a
sort = lift List.sort
{-# INLINE sort #-}
fromList :: [a] -> NonEmpty a
fromList (a:as) = a :| as
fromList [] = error "NonEmpty.fromList: empty list"
{-# INLINE fromList #-}
toList :: NonEmpty a -> [a]
toList ~(a :| as) = a : as
{-# INLINE toList #-}
lift :: Foldable f => ([a] -> [b]) -> f a -> NonEmpty b
lift f = fromList . f . Foldable.toList
{-# INLINE lift #-}
map :: (a -> b) -> NonEmpty a -> NonEmpty b
map f ~(a :| as) = f a :| fmap f as
{-# INLINE map #-}
inits :: Foldable f => f a -> NonEmpty [a]
inits = fromList . List.inits . Foldable.toList
{-# INLINE inits #-}
tails :: Foldable f => f a -> NonEmpty [a]
tails = fromList . List.tails . Foldable.toList
{-# INLINE tails #-}
insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
insert a = fromList . List.insert a . Foldable.toList
{-# INLINE insert #-}
some1 :: Alternative f => f a -> f (NonEmpty a)
some1 x = (:|) <$> x <*> many x
{-# INLINE some1 #-}
scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
scanl f z = fromList . List.scanl f z . Foldable.toList
{-# INLINE scanl #-}
scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
scanr f z = fromList . List.scanr f z . Foldable.toList
{-# INLINE scanr #-}
scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
scanl1 f ~(a :| as) = fromList (List.scanl f a as)
{-# INLINE scanl1 #-}
scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
scanr1 f ~(a :| as) = fromList (List.scanr1 f (a:as))
{-# INLINE scanr1 #-}
intersperse :: a -> NonEmpty a -> NonEmpty a
intersperse a ~(b :| bs) = b :| case bs of
[] -> []
_ -> a : List.intersperse a bs
{-# INLINE intersperse #-}
iterate :: (a -> a) -> a -> NonEmpty a
iterate f a = a :| List.iterate f (f a)
{-# INLINE iterate #-}
cycle :: NonEmpty a -> NonEmpty a
cycle = fromList . List.cycle . toList
{-# INLINE cycle #-}
reverse :: NonEmpty a -> NonEmpty a
reverse = lift List.reverse
{-# INLINE reverse #-}
repeat :: a -> NonEmpty a
repeat a = a :| List.repeat a
{-# INLINE repeat #-}
take :: Int -> NonEmpty a -> [a]
take n = List.take n . toList
{-# INLINE take #-}
drop :: Int -> NonEmpty a -> [a]
drop n = List.drop n . toList
{-# INLINE drop #-}
splitAt :: Int -> NonEmpty a -> ([a],[a])
splitAt n = List.splitAt n . toList
{-# INLINE splitAt #-}
takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
takeWhile p = List.takeWhile p . toList
{-# INLINE takeWhile #-}
dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
dropWhile p = List.dropWhile p . toList
{-# INLINE dropWhile #-}
span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
span p = List.span p . toList
{-# INLINE span #-}
break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
break p = span (not . p)
{-# INLINE break #-}
filter :: (a -> Bool) -> NonEmpty a -> [a]
filter p = List.filter p . toList
{-# INLINE filter #-}
partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
partition p = List.partition p . toList
{-# INLINE partition #-}
group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
group = groupBy (==)
{-# INLINE group #-}
groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
groupBy eq0 = go eq0 . Foldable.toList
where
go _ [] = []
go eq (x : xs) = (x :| ys) : groupBy eq zs
where (ys, zs) = List.span (eq x) xs
groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
groupWith f = groupBy ((==) `on` f)
{-# INLINE groupWith #-}
groupAllWith :: (Ord b) => (a -> b) -> [a] -> [NonEmpty a]
groupAllWith f = groupWith f . List.sortBy (compare `on` f)
{-# INLINE groupAllWith #-}
group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
group1 = groupBy1 (==)
{-# INLINE group1 #-}
groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupBy1 eq (x :| xs) = (x :| ys) :| groupBy eq zs
where (ys, zs) = List.span (eq x) xs
{-# INLINE groupBy1 #-}
groupWith1 :: (Eq b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupWith1 f = groupBy1 ((==) `on` f)
{-# INLINE groupWith1 #-}
groupAllWith1 :: (Ord b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupAllWith1 f = groupWith1 f . sortWith f
{-# INLINE groupAllWith1 #-}
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
isPrefixOf [] _ = True
isPrefixOf (y:ys) (x :| xs) = (y == x) && List.isPrefixOf ys xs
{-# INLINE isPrefixOf #-}
(!!) :: NonEmpty a -> Int -> a
(!!) ~(x :| xs) n
| n == 0 = x
| n > 0 = xs List.!! (n - 1)
| otherwise = error "NonEmpty.!! negative argument"
{-# INLINE (!!) #-}
zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a,b)
zip ~(x :| xs) ~(y :| ys) = (x, y) :| List.zip xs ys
{-# INLINE zip #-}
zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
zipWith f ~(x :| xs) ~(y :| ys) = f x y :| List.zipWith f xs ys
{-# INLINE zipWith #-}
unzip :: Functor f => f (a,b) -> (f a, f b)
unzip xs = (fst <$> xs, snd <$> xs)
{-# INLINE unzip #-}
nub :: Eq a => NonEmpty a -> NonEmpty a
nub = nubBy (==)
nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
nubBy eq (a :| as) = a :| List.nubBy eq (List.filter (\b -> not (eq a b)) as)
transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
transpose = fmap fromList
. fromList . List.transpose . Foldable.toList
. fmap Foldable.toList
sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
sortBy f = lift (List.sortBy f)
sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
sortWith = sortBy . comparing