{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_HADDOCK not-home #-}
module Data.Sequence.NonEmpty.Internal (
NESeq(..)
, pattern (:<||)
, pattern (:||>)
, withNonEmpty
, toSeq
, singleton
, length
, fromList
, fromFunction
, replicate
, index
, (<|), (><), (|><)
, map
, foldMapWithIndex
, traverseWithIndex1
, tails
, zip
, zipWith
, unzip
, sortOnSeq
, unstableSortOnSeq
, unzipSeq
, unzipWithSeq
) where
import Control.Comonad
import Control.DeepSeq
import Control.Monad
import Control.Monad.Fix
import Control.Monad.Zip
import Data.Bifunctor
import Data.Coerce
import Data.Data
import Data.Functor.Alt
import Data.Functor.Bind
import Data.Functor.Classes
import Data.Functor.Extend
import Data.List.NonEmpty (NonEmpty(..))
import Data.Semigroup
import Data.Functor.Invariant
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import Data.Sequence (Seq(..))
import Prelude hiding (length, zipWith, unzip, zip, map, replicate)
import Text.Read
import qualified Data.Aeson as A
import qualified Data.Foldable as F
import qualified Data.Sequence as Seq
data NESeq a = NESeq { NESeq a -> a
nesHead :: a
, NESeq a -> Seq a
nesTail :: !(Seq a)
}
deriving (Functor NESeq
Foldable NESeq
Functor NESeq
-> Foldable NESeq
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NESeq a -> f (NESeq b))
-> (forall (f :: * -> *) a.
Applicative f =>
NESeq (f a) -> f (NESeq a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NESeq a -> m (NESeq b))
-> (forall (m :: * -> *) a. Monad m => NESeq (m a) -> m (NESeq a))
-> Traversable NESeq
(a -> f b) -> NESeq a -> f (NESeq b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => NESeq (m a) -> m (NESeq a)
forall (f :: * -> *) a. Applicative f => NESeq (f a) -> f (NESeq a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NESeq a -> m (NESeq b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NESeq a -> f (NESeq b)
sequence :: NESeq (m a) -> m (NESeq a)
$csequence :: forall (m :: * -> *) a. Monad m => NESeq (m a) -> m (NESeq a)
mapM :: (a -> m b) -> NESeq a -> m (NESeq b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NESeq a -> m (NESeq b)
sequenceA :: NESeq (f a) -> f (NESeq a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => NESeq (f a) -> f (NESeq a)
traverse :: (a -> f b) -> NESeq a -> f (NESeq b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NESeq a -> f (NESeq b)
$cp2Traversable :: Foldable NESeq
$cp1Traversable :: Functor NESeq
Traversable, Typeable)
pattern (:<||) :: a -> Seq a -> NESeq a
pattern x $b:<|| :: a -> Seq a -> NESeq a
$m:<|| :: forall r a. NESeq a -> (a -> Seq a -> r) -> (Void# -> r) -> r
:<|| xs = NESeq x xs
{-# COMPLETE (:<||) #-}
unsnoc :: NESeq a -> (Seq a, a)
unsnoc :: NESeq a -> (Seq a, a)
unsnoc (a
x :<|| (Seq a
xs :|> a
y)) = (a
x a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
:<| Seq a
xs, a
y)
unsnoc (a
x :<|| Seq a
Empty ) = (Seq a
forall a. Seq a
Empty , a
x)
{-# INLINE unsnoc #-}
pattern (:||>) :: Seq a -> a -> NESeq a
pattern xs $b:||> :: Seq a -> a -> NESeq a
$m:||> :: forall r a. NESeq a -> (Seq a -> a -> r) -> (Void# -> r) -> r
:||> x <- (unsnoc->(!xs, x))
where
(a
x :<| Seq a
xs) :||> a
y = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| (Seq a
xs Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
:|> a
y)
Seq a
Empty :||> a
y = a
y a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
forall a. Seq a
Empty
{-# COMPLETE (:||>) #-}
infixr 5 `NESeq`
infixr 5 :<||
infixl 5 :||>
instance Show a => Show (NESeq a) where
showsPrec :: Int -> NESeq a -> ShowS
showsPrec Int
p NESeq a
xs = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"fromList (" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty a -> ShowS
forall a. Show a => a -> ShowS
shows (NESeq a -> NonEmpty a
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq a
xs) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
")"
instance Read a => Read (NESeq a) where
readPrec :: ReadPrec (NESeq a)
readPrec = ReadPrec (NESeq a) -> ReadPrec (NESeq a)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (NESeq a) -> ReadPrec (NESeq a))
-> ReadPrec (NESeq a) -> ReadPrec (NESeq a)
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec (NESeq a) -> ReadPrec (NESeq a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec (NESeq a) -> ReadPrec (NESeq a))
-> ReadPrec (NESeq a) -> ReadPrec (NESeq a)
forall a b. (a -> b) -> a -> b
$ do
Ident String
"fromList" <- ReadPrec Lexeme
lexP
NonEmpty a
xs <- ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a))
-> (ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a))
-> ReadPrec (NonEmpty a)
-> ReadPrec (NonEmpty a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a))
-> ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a)
forall a b. (a -> b) -> a -> b
$ ReadPrec (NonEmpty a)
forall a. Read a => ReadPrec a
readPrec
NESeq a -> ReadPrec (NESeq a)
forall (m :: * -> *) a. Monad m => a -> m a
return (NonEmpty a -> NESeq a
forall a. NonEmpty a -> NESeq a
fromList NonEmpty a
xs)
readListPrec :: ReadPrec [NESeq a]
readListPrec = ReadPrec [NESeq a]
forall a. Read a => ReadPrec [a]
readListPrecDefault
instance Eq a => Eq (NESeq a) where
NESeq a
xs == :: NESeq a -> NESeq a -> Bool
== NESeq a
ys = NESeq a -> Int
forall a. NESeq a -> Int
length NESeq a
xs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== NESeq a -> Int
forall a. NESeq a -> Int
length NESeq a
ys
Bool -> Bool -> Bool
&& NESeq a -> NonEmpty a
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq a
xs NonEmpty a -> NonEmpty a -> Bool
forall a. Eq a => a -> a -> Bool
== NESeq a -> NonEmpty a
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq a
ys
instance Ord a => Ord (NESeq a) where
compare :: NESeq a -> NESeq a -> Ordering
compare NESeq a
xs NESeq a
ys = [a] -> [a] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (NESeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList NESeq a
xs) (NESeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList NESeq a
ys)
instance Show1 NESeq where
liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NESeq a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d NESeq a
m =
(Int -> NonEmpty a -> ShowS)
-> String -> Int -> NonEmpty a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl) String
"fromList" Int
d (NESeq a -> NonEmpty a
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq a
m)
instance Read1 NESeq where
liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NESeq a)
liftReadsPrec Int -> ReadS a
_rp ReadS [a]
readLst Int
p = Bool -> ReadS (NESeq a) -> ReadS (NESeq a)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ReadS (NESeq a) -> ReadS (NESeq a))
-> ReadS (NESeq a) -> ReadS (NESeq a)
forall a b. (a -> b) -> a -> b
$ \String
r -> do
(String
"fromList",String
s) <- ReadS String
lex String
r
(NonEmpty a
xs, String
t) <- (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a)
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS a
_rp ReadS [a]
readLst Int
10 String
s
(NESeq a, String) -> [(NESeq a, String)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NonEmpty a -> NESeq a
forall a. NonEmpty a -> NESeq a
fromList NonEmpty a
xs, String
t)
instance Eq1 NESeq where
liftEq :: (a -> b -> Bool) -> NESeq a -> NESeq b -> Bool
liftEq a -> b -> Bool
eq NESeq a
xs NESeq b
ys = NESeq a -> Int
forall a. NESeq a -> Int
length NESeq a
xs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== NESeq b -> Int
forall a. NESeq a -> Int
length NESeq b
ys Bool -> Bool -> Bool
&& (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq (NESeq a -> NonEmpty a
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq a
xs) (NESeq b -> NonEmpty b
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq b
ys)
instance Ord1 NESeq where
liftCompare :: (a -> b -> Ordering) -> NESeq a -> NESeq b -> Ordering
liftCompare a -> b -> Ordering
cmp NESeq a
xs NESeq b
ys = (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp (NESeq a -> NonEmpty a
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq a
xs) (NESeq b -> NonEmpty b
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
toNonEmpty NESeq b
ys)
instance Data a => Data (NESeq a) where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NESeq a -> c (NESeq a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z (a
x :<|| Seq a
xs) = (a -> Seq a -> NESeq a) -> c (a -> Seq a -> NESeq a)
forall g. g -> c g
z a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
(:<||) c (a -> Seq a -> NESeq a) -> a -> c (Seq a -> NESeq a)
forall d b. Data d => c (d -> b) -> d -> c b
`f` a
x c (Seq a -> NESeq a) -> Seq a -> c (NESeq a)
forall d b. Data d => c (d -> b) -> d -> c b
`f` Seq a
xs
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NESeq a)
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
_ = c (Seq a -> NESeq a) -> c (NESeq a)
forall b r. Data b => c (b -> r) -> c r
k (c (a -> Seq a -> NESeq a) -> c (Seq a -> NESeq a)
forall b r. Data b => c (b -> r) -> c r
k ((a -> Seq a -> NESeq a) -> c (a -> Seq a -> NESeq a)
forall r. r -> c r
z a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
(:<||)))
toConstr :: NESeq a -> Constr
toConstr NESeq a
_ = Constr
consConstr
dataTypeOf :: NESeq a -> DataType
dataTypeOf NESeq a
_ = DataType
seqDataType
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (NESeq a))
dataCast1 forall d. Data d => c (t d)
f = c (t a) -> Maybe (c (NESeq a))
forall k1 k2 (c :: k1 -> *) (t :: k2 -> k1) (t' :: k2 -> k1)
(a :: k2).
(Typeable t, Typeable t') =>
c (t a) -> Maybe (c (t' a))
gcast1 c (t a)
forall d. Data d => c (t d)
f
consConstr :: Constr
consConstr :: Constr
consConstr = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
seqDataType String
":<||" [] Fixity
Infix
seqDataType :: DataType
seqDataType :: DataType
seqDataType = String -> [Constr] -> DataType
mkDataType String
"Data.Sequence.NonEmpty.Internal.NESeq" [Constr
consConstr]
instance A.ToJSON a => A.ToJSON (NESeq a) where
toJSON :: NESeq a -> Value
toJSON = Seq a -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Seq a -> Value) -> (NESeq a -> Seq a) -> NESeq a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq
toEncoding :: NESeq a -> Encoding
toEncoding = Seq a -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding (Seq a -> Encoding) -> (NESeq a -> Seq a) -> NESeq a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq
instance A.FromJSON a => A.FromJSON (NESeq a) where
parseJSON :: Value -> Parser (NESeq a)
parseJSON = Parser (NESeq a)
-> (NESeq a -> Parser (NESeq a)) -> Seq a -> Parser (NESeq a)
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (String -> Parser (NESeq a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err) NESeq a -> Parser (NESeq a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Seq a -> Parser (NESeq a))
-> (Value -> Parser (Seq a)) -> Value -> Parser (NESeq a)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Value -> Parser (Seq a)
forall a. FromJSON a => Value -> Parser a
A.parseJSON
where
err :: String
err = String
"NESeq: Non-empty sequence expected, but empty sequence found"
withNonEmpty :: r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty :: r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty r
def NESeq a -> r
f = \case
a
x :<| Seq a
xs -> NESeq a -> r
f (a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
xs)
Seq a
Empty -> r
def
{-# INLINE withNonEmpty #-}
toSeq :: NESeq a -> Seq a
toSeq :: NESeq a -> Seq a
toSeq (a
x :<|| Seq a
xs) = a
x a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
:<| Seq a
xs
{-# INLINE toSeq #-}
singleton :: a -> NESeq a
singleton :: a -> NESeq a
singleton = (a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
forall a. Seq a
Seq.empty)
{-# INLINE singleton #-}
length :: NESeq a -> Int
length :: NESeq a -> Int
length (a
_ :<|| Seq a
xs) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Seq a -> Int
forall a. Seq a -> Int
Seq.length Seq a
xs
{-# INLINE length #-}
fromList :: NonEmpty a -> NESeq a
fromList :: NonEmpty a -> NESeq a
fromList (a
x :| [a]
xs) = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| [a] -> Seq a
forall a. [a] -> Seq a
Seq.fromList [a]
xs
{-# INLINE fromList #-}
fromFunction :: Int -> (Int -> a) -> NESeq a
fromFunction :: Int -> (Int -> a) -> NESeq a
fromFunction Int
n Int -> a
f
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = String -> NESeq a
forall a. HasCallStack => String -> a
error String
"NESeq.fromFunction: must take a positive integer argument"
| Bool
otherwise = Int -> a
f Int
0 a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Int -> (Int -> a) -> Seq a
forall a. Int -> (Int -> a) -> Seq a
Seq.fromFunction (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Int -> a
f (Int -> a) -> (Int -> Int) -> Int -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
replicate :: Int -> a -> NESeq a
replicate :: Int -> a -> NESeq a
replicate Int
n a
x
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = String -> NESeq a
forall a. HasCallStack => String -> a
error String
"NESeq.replicate: must take a positive integer argument"
| Bool
otherwise = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Int -> a -> Seq a
forall a. Int -> a -> Seq a
Seq.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) a
x
{-# INLINE replicate #-}
index :: NESeq a -> Int -> a
index :: NESeq a -> Int -> a
index (a
x :<|| Seq a
_ ) Int
0 = a
x
index (a
_ :<|| Seq a
xs) Int
i = Seq a
xs Seq a -> Int -> a
forall a. Seq a -> Int -> a
`Seq.index` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
{-# INLINE index #-}
(<|) :: a -> NESeq a -> NESeq a
a
x <| :: a -> NESeq a -> NESeq a
<| NESeq a
xs = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
xs
{-# INLINE (<|) #-}
(><) :: NESeq a -> NESeq a -> NESeq a
(a
x :<|| Seq a
xs) >< :: NESeq a -> NESeq a -> NESeq a
>< NESeq a
ys = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| (Seq a
xs Seq a -> Seq a -> Seq a
forall a. Seq a -> Seq a -> Seq a
Seq.>< NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
ys)
{-# INLINE (><) #-}
(|><) :: NESeq a -> Seq a -> NESeq a
(a
x :<|| Seq a
xs) |>< :: NESeq a -> Seq a -> NESeq a
|>< Seq a
ys = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| (Seq a
xs Seq a -> Seq a -> Seq a
forall a. Seq a -> Seq a -> Seq a
Seq.>< Seq a
ys)
{-# INLINE (|><) #-}
infixr 5 <|
infixr 5 ><
infixr 5 |><
map :: (a -> b) -> NESeq a -> NESeq b
map :: (a -> b) -> NESeq a -> NESeq b
map a -> b
f (a
x :<|| Seq a
xs) = a -> b
f a
x b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
:<|| (a -> b) -> Seq a -> Seq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Seq a
xs
{-# NOINLINE [1] map #-}
{-# RULES
"map/map" forall f g xs . map f (map g xs) = map (f . g) xs
#-}
{-# RULES
"map/coerce" map coerce = coerce
#-}
foldMapWithIndex :: Semigroup m => (Int -> a -> m) -> NESeq a -> m
#if MIN_VERSION_base(4,11,0)
foldMapWithIndex :: (Int -> a -> m) -> NESeq a -> m
foldMapWithIndex Int -> a -> m
f (a
x :<|| Seq a
xs) = m -> (m -> m) -> Maybe m -> m
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Int -> a -> m
f Int
0 a
x) (Int -> a -> m
f Int
0 a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<>)
(Maybe m -> m) -> (Seq a -> Maybe m) -> Seq a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> a -> Maybe m) -> Seq a -> Maybe m
forall m a. Monoid m => (Int -> a -> m) -> Seq a -> m
Seq.foldMapWithIndex (\Int
i -> m -> Maybe m
forall a. a -> Maybe a
Just (m -> Maybe m) -> (a -> m) -> a -> Maybe m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> m
f (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
(Seq a -> m) -> Seq a -> m
forall a b. (a -> b) -> a -> b
$ Seq a
xs
#else
foldMapWithIndex f (x :<|| xs) = option (f 0 x) (f 0 x <>)
. Seq.foldMapWithIndex (\i -> Option . Just . f (i + 1))
$ xs
#endif
{-# INLINE foldMapWithIndex #-}
traverseWithIndex1 :: Apply f => (Int -> a -> f b) -> NESeq a -> f (NESeq b)
traverseWithIndex1 :: (Int -> a -> f b) -> NESeq a -> f (NESeq b)
traverseWithIndex1 Int -> a -> f b
f (a
x :<|| Seq a
xs) = case MaybeApply f (Seq b) -> Either (f (Seq b)) (Seq b)
forall (f :: * -> *) a. MaybeApply f a -> Either (f a) a
runMaybeApply MaybeApply f (Seq b)
xs' of
Left f (Seq b)
ys -> b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
(:<||) (b -> Seq b -> NESeq b) -> f b -> f (Seq b -> NESeq b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> a -> f b
f Int
0 a
x f (Seq b -> NESeq b) -> f (Seq b) -> f (NESeq b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> f (Seq b)
ys
Right Seq b
ys -> (b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
:<|| Seq b
ys) (b -> NESeq b) -> f b -> f (NESeq b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> a -> f b
f Int
0 a
x
where
xs' :: MaybeApply f (Seq b)
xs' = (Int -> a -> MaybeApply f b) -> Seq a -> MaybeApply f (Seq b)
forall (f :: * -> *) a b.
Applicative f =>
(Int -> a -> f b) -> Seq a -> f (Seq b)
Seq.traverseWithIndex (\Int
i -> Either (f b) b -> MaybeApply f b
forall (f :: * -> *) a. Either (f a) a -> MaybeApply f a
MaybeApply (Either (f b) b -> MaybeApply f b)
-> (a -> Either (f b) b) -> a -> MaybeApply f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f b -> Either (f b) b
forall a b. a -> Either a b
Left (f b -> Either (f b) b) -> (a -> f b) -> a -> Either (f b) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> f b
f (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) Seq a
xs
{-# INLINABLE traverseWithIndex1 #-}
tails :: NESeq a -> NESeq (NESeq a)
tails :: NESeq a -> NESeq (NESeq a)
tails xs :: NESeq a
xs@(a
_ :<|| Seq a
ys) = NESeq (NESeq a)
-> (NESeq a -> NESeq (NESeq a)) -> Seq a -> NESeq (NESeq a)
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (NESeq a -> NESeq (NESeq a)
forall a. a -> NESeq a
singleton NESeq a
xs) ((NESeq a
xs NESeq a -> NESeq (NESeq a) -> NESeq (NESeq a)
forall a. a -> NESeq a -> NESeq a
<|) (NESeq (NESeq a) -> NESeq (NESeq a))
-> (NESeq a -> NESeq (NESeq a)) -> NESeq a -> NESeq (NESeq a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESeq a -> NESeq (NESeq a)
forall a. NESeq a -> NESeq (NESeq a)
tails) Seq a
ys
{-# INLINABLE tails #-}
zip :: NESeq a -> NESeq b -> NESeq (a, b)
zip :: NESeq a -> NESeq b -> NESeq (a, b)
zip (a
x :<|| Seq a
xs) (b
y :<|| Seq b
ys) = (a
x, b
y) (a, b) -> Seq (a, b) -> NESeq (a, b)
forall a. a -> Seq a -> NESeq a
:<|| Seq a -> Seq b -> Seq (a, b)
forall a b. Seq a -> Seq b -> Seq (a, b)
Seq.zip Seq a
xs Seq b
ys
{-# INLINE zip #-}
zipWith :: (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c
zipWith :: (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c
zipWith a -> b -> c
f (a
x :<|| Seq a
xs) (b
y :<|| Seq b
ys) = a -> b -> c
f a
x b
y c -> Seq c -> NESeq c
forall a. a -> Seq a -> NESeq a
:<|| (a -> b -> c) -> Seq a -> Seq b -> Seq c
forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
Seq.zipWith a -> b -> c
f Seq a
xs Seq b
ys
{-# INLINE zipWith #-}
unzip :: NESeq (a, b) -> (NESeq a, NESeq b)
unzip :: NESeq (a, b) -> (NESeq a, NESeq b)
unzip ((a
x, b
y) :<|| Seq (a, b)
xys) = (Seq a -> NESeq a)
-> (Seq b -> NESeq b) -> (Seq a, Seq b) -> (NESeq a, NESeq b)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<||) (b
y b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
:<||) ((Seq a, Seq b) -> (NESeq a, NESeq b))
-> (Seq (a, b) -> (Seq a, Seq b))
-> Seq (a, b)
-> (NESeq a, NESeq b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq (a, b) -> (Seq a, Seq b)
forall a b. Seq (a, b) -> (Seq a, Seq b)
unzipSeq (Seq (a, b) -> (NESeq a, NESeq b))
-> Seq (a, b) -> (NESeq a, NESeq b)
forall a b. (a -> b) -> a -> b
$ Seq (a, b)
xys
{-# INLINE unzip #-}
instance Semigroup (NESeq a) where
<> :: NESeq a -> NESeq a -> NESeq a
(<>) = NESeq a -> NESeq a -> NESeq a
forall a. NESeq a -> NESeq a -> NESeq a
(><)
{-# INLINE (<>) #-}
instance Functor NESeq where
fmap :: (a -> b) -> NESeq a -> NESeq b
fmap = (a -> b) -> NESeq a -> NESeq b
forall a b. (a -> b) -> NESeq a -> NESeq b
map
{-# INLINE fmap #-}
a
x <$ :: a -> NESeq b -> NESeq a
<$ NESeq b
xs = Int -> a -> NESeq a
forall a. Int -> a -> NESeq a
replicate (NESeq b -> Int
forall a. NESeq a -> Int
length NESeq b
xs) a
x
{-# INLINE (<$) #-}
instance Invariant NESeq where
invmap :: (a -> b) -> (b -> a) -> NESeq a -> NESeq b
invmap a -> b
f b -> a
_ = (a -> b) -> NESeq a -> NESeq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f
{-# INLINE invmap #-}
instance Apply NESeq where
(a -> b
f :<|| Seq (a -> b)
fs) <.> :: NESeq (a -> b) -> NESeq a -> NESeq b
<.> NESeq a
xs = NESeq b
fxs NESeq b -> Seq b -> NESeq b
forall a. NESeq a -> Seq a -> NESeq a
|>< Seq b
fsxs
where
fxs :: NESeq b
fxs = a -> b
f (a -> b) -> NESeq a -> NESeq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NESeq a
xs
fsxs :: Seq b
fsxs = Seq (a -> b)
fs Seq (a -> b) -> Seq a -> Seq b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
xs
{-# INLINABLE (<.>) #-}
instance Applicative NESeq where
pure :: a -> NESeq a
pure = a -> NESeq a
forall a. a -> NESeq a
singleton
{-# INLINE pure #-}
<*> :: NESeq (a -> b) -> NESeq a -> NESeq b
(<*>) = NESeq (a -> b) -> NESeq a -> NESeq b
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
(<.>)
{-# INLINABLE (<*>) #-}
instance Alt NESeq where
<!> :: NESeq a -> NESeq a -> NESeq a
(<!>) = NESeq a -> NESeq a -> NESeq a
forall a. NESeq a -> NESeq a -> NESeq a
(><)
{-# INLINE (<!>) #-}
instance Bind NESeq where
NESeq a
x Seq a
xs >>- :: NESeq a -> (a -> NESeq b) -> NESeq b
>>- a -> NESeq b
f = NESeq b -> (NESeq a -> NESeq b) -> Seq a -> NESeq b
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (a -> NESeq b
f a
x) ((a -> NESeq b
f a
x NESeq b -> NESeq b -> NESeq b
forall a. NESeq a -> NESeq a -> NESeq a
><) (NESeq b -> NESeq b) -> (NESeq a -> NESeq b) -> NESeq a -> NESeq b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NESeq a -> (a -> NESeq b) -> NESeq b
forall (m :: * -> *) a b. Bind m => m a -> (a -> m b) -> m b
>>- a -> NESeq b
f)) Seq a
xs
{-# INLINABLE (>>-) #-}
instance Monad NESeq where
return :: a -> NESeq a
return = a -> NESeq a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE return #-}
>>= :: NESeq a -> (a -> NESeq b) -> NESeq b
(>>=) = NESeq a -> (a -> NESeq b) -> NESeq b
forall (m :: * -> *) a b. Bind m => m a -> (a -> m b) -> m b
(>>-)
{-# INLINABLE (>>=) #-}
instance Extend NESeq where
duplicated :: NESeq a -> NESeq (NESeq a)
duplicated = NESeq a -> NESeq (NESeq a)
forall a. NESeq a -> NESeq (NESeq a)
tails
{-# INLINE duplicated #-}
extended :: (NESeq a -> b) -> NESeq a -> NESeq b
extended NESeq a -> b
f xs0 :: NESeq a
xs0@(a
_ :<|| Seq a
xs) = NESeq b -> (NESeq a -> NESeq b) -> Seq a -> NESeq b
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (b -> NESeq b
forall a. a -> NESeq a
singleton (NESeq a -> b
f NESeq a
xs0))
((NESeq a -> b
f NESeq a
xs0 b -> NESeq b -> NESeq b
forall a. a -> NESeq a -> NESeq a
<|) (NESeq b -> NESeq b) -> (NESeq a -> NESeq b) -> NESeq a -> NESeq b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NESeq a -> b) -> NESeq a -> NESeq b
forall (w :: * -> *) a b. Comonad w => (w a -> b) -> w a -> w b
extend NESeq a -> b
f)
Seq a
xs
{-# INLINE extended #-}
instance Comonad NESeq where
extract :: NESeq a -> a
extract (a
x :<|| Seq a
_) = a
x
{-# INLINE extract #-}
duplicate :: NESeq a -> NESeq (NESeq a)
duplicate = NESeq a -> NESeq (NESeq a)
forall (w :: * -> *) a. Extend w => w a -> w (w a)
duplicated
{-# INLINE duplicate #-}
extend :: (NESeq a -> b) -> NESeq a -> NESeq b
extend = (NESeq a -> b) -> NESeq a -> NESeq b
forall (w :: * -> *) a b. Extend w => (w a -> b) -> w a -> w b
extended
{-# INLINE extend #-}
instance Foldable NESeq where
#if MIN_VERSION_base(4,11,0)
fold :: NESeq m -> m
fold (m
x :<|| Seq m
xs) = m
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> Seq m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
F.fold Seq m
xs
{-# INLINE fold #-}
foldMap :: (a -> m) -> NESeq a -> m
foldMap a -> m
f (a
x :<|| Seq a
xs) = a -> m
f a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (a -> m) -> Seq a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap a -> m
f Seq a
xs
{-# INLINE foldMap #-}
#else
fold (x :<|| xs) = x `mappend` F.fold xs
{-# INLINE fold #-}
foldMap f (x :<|| xs) = f x `mappend` F.foldMap f xs
{-# INLINE foldMap #-}
#endif
foldr :: (a -> b -> b) -> b -> NESeq a -> b
foldr a -> b -> b
f b
z (a
x :<|| Seq a
xs) = a
x a -> b -> b
`f` (a -> b -> b) -> b -> Seq a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> b -> b
f b
z Seq a
xs
{-# INLINE foldr #-}
foldr' :: (a -> b -> b) -> b -> NESeq a -> b
foldr' a -> b -> b
f b
z (Seq a
xs :||> a
x) = (a -> b -> b) -> b -> Seq a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr' a -> b -> b
f b
y Seq a
xs
where
!y :: b
y = a -> b -> b
f a
x b
z
{-# INLINE foldr' #-}
foldl :: (b -> a -> b) -> b -> NESeq a -> b
foldl b -> a -> b
f b
z (Seq a
xs :||> a
x) = (b -> a -> b) -> b -> Seq a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl b -> a -> b
f b
z Seq a
xs b -> a -> b
`f` a
x
{-# INLINE foldl #-}
foldl' :: (b -> a -> b) -> b -> NESeq a -> b
foldl' b -> a -> b
f b
z (a
x :<|| Seq a
xs) = (b -> a -> b) -> b -> Seq a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' b -> a -> b
f b
y Seq a
xs
where
!y :: b
y = b -> a -> b
f b
z a
x
{-# INLINE foldl' #-}
foldr1 :: (a -> a -> a) -> NESeq a -> a
foldr1 a -> a -> a
f (Seq a
xs :||> a
x) = (a -> a -> a) -> a -> Seq a -> a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> a -> a
f a
x Seq a
xs
{-# INLINE foldr1 #-}
foldl1 :: (a -> a -> a) -> NESeq a -> a
foldl1 a -> a -> a
f (a
x :<|| Seq a
xs) = (a -> a -> a) -> a -> Seq a -> a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl a -> a -> a
f a
x Seq a
xs
{-# INLINE foldl1 #-}
null :: NESeq a -> Bool
null NESeq a
_ = Bool
False
{-# INLINE null #-}
length :: NESeq a -> Int
length = NESeq a -> Int
forall a. NESeq a -> Int
length
{-# INLINE length #-}
instance Foldable1 NESeq where
#if MIN_VERSION_base(4,11,0)
fold1 :: NESeq m -> m
fold1 (m
x :<|| Seq m
xs) = m -> (m -> m) -> Maybe m -> m
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m
x (m
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<>)
(Maybe m -> m) -> (Seq m -> Maybe m) -> Seq m -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (m -> Maybe m) -> Seq m -> Maybe m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap m -> Maybe m
forall a. a -> Maybe a
Just
(Seq m -> m) -> Seq m -> m
forall a b. (a -> b) -> a -> b
$ Seq m
xs
#else
fold1 (x :<|| xs) = option x (x <>)
. F.foldMap (Option . Just)
$ xs
#endif
{-# INLINE fold1 #-}
foldMap1 :: (a -> m) -> NESeq a -> m
foldMap1 a -> m
f = (Int -> a -> m) -> NESeq a -> m
forall m a. Semigroup m => (Int -> a -> m) -> NESeq a -> m
foldMapWithIndex ((a -> m) -> Int -> a -> m
forall a b. a -> b -> a
const a -> m
f)
{-# INLINE foldMap1 #-}
toNonEmpty :: NESeq a -> NonEmpty a
toNonEmpty (a
x :<|| Seq a
xs) = a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList Seq a
xs
{-# INLINE toNonEmpty #-}
instance Traversable1 NESeq where
traverse1 :: (a -> f b) -> NESeq a -> f (NESeq b)
traverse1 a -> f b
f = (Int -> a -> f b) -> NESeq a -> f (NESeq b)
forall (f :: * -> *) a b.
Apply f =>
(Int -> a -> f b) -> NESeq a -> f (NESeq b)
traverseWithIndex1 ((a -> f b) -> Int -> a -> f b
forall a b. a -> b -> a
const a -> f b
f)
{-# INLINE traverse1 #-}
sequence1 :: NESeq (f b) -> f (NESeq b)
sequence1 (f b
x :<|| Seq (f b)
xs) = case MaybeApply f (Seq b) -> Either (f (Seq b)) (Seq b)
forall (f :: * -> *) a. MaybeApply f a -> Either (f a) a
runMaybeApply MaybeApply f (Seq b)
xs' of
Left f (Seq b)
ys -> b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
(:<||) (b -> Seq b -> NESeq b) -> f b -> f (Seq b -> NESeq b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f b
x f (Seq b -> NESeq b) -> f (Seq b) -> f (NESeq b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> f (Seq b)
ys
Right Seq b
ys -> (b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
:<|| Seq b
ys) (b -> NESeq b) -> f b -> f (NESeq b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f b
x
where
xs' :: MaybeApply f (Seq b)
xs' = (f b -> MaybeApply f b) -> Seq (f b) -> MaybeApply f (Seq b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Either (f b) b -> MaybeApply f b
forall (f :: * -> *) a. Either (f a) a -> MaybeApply f a
MaybeApply (Either (f b) b -> MaybeApply f b)
-> (f b -> Either (f b) b) -> f b -> MaybeApply f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f b -> Either (f b) b
forall a b. a -> Either a b
Left) Seq (f b)
xs
{-# INLINABLE sequence1 #-}
instance MonadZip NESeq where
mzipWith :: (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c
mzipWith = (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c
forall a b c. (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c
zipWith
munzip :: NESeq (a, b) -> (NESeq a, NESeq b)
munzip = NESeq (a, b) -> (NESeq a, NESeq b)
forall a b. NESeq (a, b) -> (NESeq a, NESeq b)
unzip
instance MonadFix NESeq where
mfix :: (a -> NESeq a) -> NESeq a
mfix = (a -> NESeq a) -> NESeq a
forall a. (a -> NESeq a) -> NESeq a
mfixSeq
mfixSeq :: (a -> NESeq a) -> NESeq a
mfixSeq :: (a -> NESeq a) -> NESeq a
mfixSeq a -> NESeq a
f = Int -> (Int -> a) -> NESeq a
forall a. Int -> (Int -> a) -> NESeq a
fromFunction (NESeq a -> Int
forall a. NESeq a -> Int
length (a -> NESeq a
f a
forall a. a
err)) (\Int
k -> (a -> a) -> a
forall a. (a -> a) -> a
fix (\a
xk -> a -> NESeq a
f a
xk NESeq a -> Int -> a
forall a. NESeq a -> Int -> a
`index` Int
k))
where
err :: a
err = String -> a
forall a. HasCallStack => String -> a
error String
"mfix for Data.Sequence.NonEmpty.NESeq applied to strict function"
instance NFData a => NFData (NESeq a) where
rnf :: NESeq a -> ()
rnf (a
x :<|| Seq a
xs) = a -> ()
forall a. NFData a => a -> ()
rnf a
x () -> () -> ()
`seq` Seq a -> ()
forall a. NFData a => a -> ()
rnf Seq a
xs () -> () -> ()
`seq` ()
sortOnSeq :: Ord b => (a -> b) -> Seq a -> Seq a
#if MIN_VERSION_containers(0,5,11)
sortOnSeq :: (a -> b) -> Seq a -> Seq a
sortOnSeq = (a -> b) -> Seq a -> Seq a
forall b a. Ord b => (a -> b) -> Seq a -> Seq a
Seq.sortOn
#else
sortOnSeq f = Seq.sortBy (\x y -> f x `compare` f y)
#endif
{-# INLINE sortOnSeq #-}
unstableSortOnSeq :: Ord b => (a -> b) -> Seq a -> Seq a
#if MIN_VERSION_containers(0,5,11)
unstableSortOnSeq :: (a -> b) -> Seq a -> Seq a
unstableSortOnSeq = (a -> b) -> Seq a -> Seq a
forall b a. Ord b => (a -> b) -> Seq a -> Seq a
Seq.unstableSortOn
#else
unstableSortOnSeq f = Seq.unstableSortBy (\x y -> f x `compare` f y)
#endif
{-# INLINE unstableSortOnSeq #-}
unzipSeq :: Seq (a, b) -> (Seq a, Seq b)
#if MIN_VERSION_containers(0,5,11)
unzipSeq :: Seq (a, b) -> (Seq a, Seq b)
unzipSeq = Seq (a, b) -> (Seq a, Seq b)
forall a b. Seq (a, b) -> (Seq a, Seq b)
Seq.unzip
{-# INLINE unzipSeq #-}
#else
unzipSeq = \case
(x, y) :<| xys -> bimap (x :<|) (y :<|) . unzipSeq $ xys
Empty -> (Empty, Empty)
{-# INLINABLE unzipSeq #-}
#endif
unzipWithSeq :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
#if MIN_VERSION_containers(0,5,11)
unzipWithSeq :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
unzipWithSeq = (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
forall a b c. (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
Seq.unzipWith
{-# INLINE unzipWithSeq #-}
#else
unzipWithSeq f = go
where
go = \case
x :<| xs -> let ~(y, z) = f x
in bimap (y :<|) (z :<|) . go $ xs
Empty -> (Empty, Empty)
{-# INLINABLE unzipWithSeq #-}
#endif