{-# LANGUAGE CPP, NoImplicitPrelude #-}
module Data.List.NonEmpty.Compat (
  
    NonEmpty(..)
  
  , map
  , intersperse
  , scanl
  , scanr
  , scanl1
  , scanr1
  , transpose
  , sortBy
  , sortWith
  
  , length
  , compareLength
  , head
  , tail
  , last
  , init
  , singleton
  , (<|), cons
  , uncons
  , unfoldr
  , sort
  , sortOn
  , reverse
  , inits
  , inits1
  , tails
  , tails1
  , append
  , appendList
  , prependList
  
  , iterate
  , repeat
  , cycle
  , unfold
  , insert
  , some1
  
  , take
  , drop
  , splitAt
  , takeWhile
  , dropWhile
  , span
  , break
  , filter
  , partition
  , group
  , groupBy
  , groupWith
  , groupAllWith
  , group1
  , groupBy1
  , groupWith1
  , groupAllWith1
  , permutations
  , permutations1
  
  , isPrefixOf
  
  , nub
  , nubBy
  
  , (!!)
  
  , zip
  , zipWith
  , unzip
  
  , fromList
  , toList
  , nonEmpty
  , xor
) where
import Data.List.NonEmpty
#if !(MIN_VERSION_base(4,20,0))
import qualified Prelude.Compat as Prelude
import Prelude.Compat ((.))
import qualified Data.List.Compat as List
#endif
#if !(MIN_VERSION_base(4,21,0))
import Prelude.Compat (Int, Num(..), Ord(..), Ordering(..), otherwise)
import qualified Data.Foldable.Compat as Foldable
#endif
#if !(MIN_VERSION_base(4,15,0))
singleton :: a -> NonEmpty a
singleton a = a :| []
#endif
#if !(MIN_VERSION_base(4,16,0))
append :: NonEmpty a -> NonEmpty a -> NonEmpty a
append = (Prelude.<>)
appendList :: NonEmpty a -> [a] -> NonEmpty a
appendList (x :| xs) ys = x :| xs Prelude.<> ys
prependList :: [a] -> NonEmpty a -> NonEmpty a
prependList ls ne = case ls of
  [] -> ne
  (x : xs) -> x :| xs Prelude.<> toList ne
#endif
#if !(MIN_VERSION_base(4,18,0))
inits1 :: NonEmpty a -> NonEmpty (NonEmpty a)
inits1 =
  
  
  
  
  
  
  
  fromList . Prelude.map fromList . List.tail . List.inits . Foldable.toList
tails1 :: NonEmpty a -> NonEmpty (NonEmpty a)
tails1 =
  
  
  
  
  
  
  
  fromList . Prelude.map fromList . List.init . List.tails . Foldable.toList
#endif
#if !(MIN_VERSION_base(4,20,0))
permutations            :: [a] -> NonEmpty [a]
permutations :: forall a. [a] -> NonEmpty [a]
permutations [a]
xs0        =  [a]
xs0 [a] -> [[a]] -> NonEmpty [a]
forall a. a -> [a] -> NonEmpty a
:| [a] -> [a] -> [[a]]
forall {a}. [a] -> [a] -> [[a]]
perms [a]
xs0 []
  where
    perms :: [a] -> [a] -> [[a]]
perms []     [a]
_  = []
    perms (a
t:[a]
ts) [a]
is = ([a] -> [[a]] -> [[a]]) -> [[a]] -> NonEmpty [a] -> [[a]]
forall a b. (a -> b -> b) -> b -> NonEmpty a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
List.foldr [a] -> [[a]] -> [[a]]
interleave ([a] -> [a] -> [[a]]
perms [a]
ts (a
ta -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
is)) ([a] -> NonEmpty [a]
forall a. [a] -> NonEmpty [a]
permutations [a]
is)
      where interleave :: [a] -> [[a]] -> [[a]]
interleave    [a]
xs     [[a]]
r = let ([a]
_,[[a]]
zs) = ([a] -> [a]) -> [a] -> [[a]] -> ([a], [[a]])
forall {a}. ([a] -> a) -> [a] -> [a] -> ([a], [a])
interleave' [a] -> [a]
forall a. a -> a
Prelude.id [a]
xs [[a]]
r in [[a]]
zs
            interleave' :: ([a] -> a) -> [a] -> [a] -> ([a], [a])
interleave' [a] -> a
_ []     [a]
r = ([a]
ts, [a]
r)
            interleave' [a] -> a
f (a
y:[a]
ys) [a]
r = let ([a]
us,[a]
zs) = ([a] -> a) -> [a] -> [a] -> ([a], [a])
interleave' ([a] -> a
f ([a] -> a) -> ([a] -> [a]) -> [a] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:)) [a]
ys [a]
r
                                     in  (a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
us, [a] -> a
f (a
ta -> [a] -> [a]
forall a. a -> [a] -> [a]
:a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
us) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
zs)
permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a)
permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
permutations1 NonEmpty a
xs = [a] -> NonEmpty a
forall a. HasCallStack => [a] -> NonEmpty a
fromList ([a] -> NonEmpty a) -> NonEmpty [a] -> NonEmpty (NonEmpty a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> [a] -> NonEmpty [a]
forall a. [a] -> NonEmpty [a]
permutations (NonEmpty a -> [a]
forall a. NonEmpty a -> [a]
toList NonEmpty a
xs)
sortOn :: Prelude.Ord b => (a -> b) -> NonEmpty a -> NonEmpty a
sortOn :: forall b a. Ord b => (a -> b) -> NonEmpty a -> NonEmpty a
sortOn a -> b
f = ([a] -> [a]) -> NonEmpty a -> NonEmpty a
forall (f :: * -> *) a b.
Foldable f =>
([a] -> [b]) -> f a -> NonEmpty b
lift ((a -> b) -> [a] -> [a]
forall b a. Ord b => (a -> b) -> [a] -> [a]
List.sortOn a -> b
f)
lift :: Foldable.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 = [b] -> NonEmpty b
forall a. HasCallStack => [a] -> NonEmpty a
fromList ([b] -> NonEmpty b) -> (f a -> [b]) -> f a -> NonEmpty b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [b]
f ([a] -> [b]) -> (f a -> [a]) -> f a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [a]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList
#endif
#if !(MIN_VERSION_base(4,21,0))
compareLength :: NonEmpty a -> Int -> Ordering
compareLength :: forall a. NonEmpty a -> Int -> Ordering
compareLength NonEmpty a
xs Int
n
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = Ordering
GT
  | Bool
otherwise = (a -> (Int -> Ordering) -> Int -> Ordering)
-> (Int -> Ordering) -> NonEmpty a -> Int -> Ordering
forall a b. (a -> b -> b) -> b -> NonEmpty a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr
    (\a
_ Int -> Ordering
f Int
m -> if Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int -> Ordering
f (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) else Ordering
GT)
    (\Int
m -> if Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Ordering
LT else Ordering
EQ)
    NonEmpty a
xs
    Int
n
#endif