{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Sequence.NonEmpty (
NESeq ((:<||), (:||>))
, pattern IsNonEmpty
, pattern IsEmpty
, nonEmptySeq
, toSeq
, withNonEmpty
, unsafeFromSeq
, insertSeqAt
, singleton
, (<|)
, (|>)
, (><)
, (|><)
, (><|)
, fromList
, fromFunction
, replicate
, replicateA
, replicateA1
, replicateM
, cycleTaking
, iterateN
, unfoldr
, unfoldl
, head
, tail
, last
, init
, length
, scanl
, scanl1
, scanr
, scanr1
, tails
, inits
, chunksOf
, takeWhileL
, takeWhileR
, dropWhileL
, dropWhileR
, spanl
, spanr
, breakl
, breakr
, partition
, filter
, sort
, sortBy
, sortOn
, unstableSort
, unstableSortBy
, unstableSortOn
, lookup
, (!?)
, index
, adjust
, adjust'
, update
, take
, drop
, insertAt
, deleteAt
, splitAt
, elemIndexL
, elemIndicesL
, elemIndexR
, elemIndicesR
, findIndexL
, findIndicesL
, findIndexR
, findIndicesR
, foldMapWithIndex
, foldlWithIndex
, foldrWithIndex
, mapWithIndex
, traverseWithIndex
, traverseWithIndex1
, reverse
, intersperse
, zip
, zipWith
, zip3
, zipWith3
, zip4
, zipWith4
, unzip
, unzipWith
) where
import Control.Applicative
import Control.Monad hiding (replicateM)
import Data.Bifunctor
import Data.Functor.Apply
import Data.Sequence (Seq(..))
import Data.Sequence.NonEmpty.Internal
import Data.These
import Prelude hiding (length, scanl, scanl1, scanr, scanr1, splitAt, zip, zipWith, zip3, zipWith3, unzip, replicate, filter, reverse, lookup, take, drop, head, tail, init, last, map)
import qualified Data.Sequence as Seq
pattern IsNonEmpty :: NESeq a -> Seq a
pattern $bIsNonEmpty :: NESeq a -> Seq a
$mIsNonEmpty :: forall r a. Seq a -> (NESeq a -> r) -> (Void# -> r) -> r
IsNonEmpty n <- (nonEmptySeq->Just n)
where
IsNonEmpty NESeq a
n = NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
n
pattern IsEmpty :: Seq a
pattern $bIsEmpty :: Seq a
$mIsEmpty :: forall r a. Seq a -> (Void# -> r) -> (Void# -> r) -> r
IsEmpty <- (Seq.null->True)
where
IsEmpty = Seq a
forall a. Seq a
Seq.empty
{-# COMPLETE IsNonEmpty, IsEmpty #-}
nonEmptySeq :: Seq a -> Maybe (NESeq a)
nonEmptySeq :: Seq a -> Maybe (NESeq a)
nonEmptySeq (a
x :<| Seq a
xs) = NESeq a -> Maybe (NESeq a)
forall a. a -> Maybe a
Just (NESeq a -> Maybe (NESeq a)) -> NESeq a -> Maybe (NESeq a)
forall a b. (a -> b) -> a -> b
$ a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
xs
nonEmptySeq Seq a
Empty = Maybe (NESeq a)
forall a. Maybe a
Nothing
{-# INLINE nonEmptySeq #-}
unsafeFromSeq :: Seq a -> NESeq a
unsafeFromSeq :: Seq a -> NESeq a
unsafeFromSeq (a
x :<| Seq a
xs) = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
xs
unsafeFromSeq Seq a
Empty = [Char] -> NESeq a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NESeq.unsafeFromSeq: empty seq"
{-# INLINE unsafeFromSeq #-}
insertSeqAt :: Int -> a -> Seq a -> NESeq a
insertSeqAt :: Int -> a -> Seq a -> NESeq a
insertSeqAt Int
i a
y
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = (a
y a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<||)
| Bool
otherwise = \case
a
x :<| Seq a
xs -> a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Int -> a -> Seq a -> Seq a
forall a. Int -> a -> Seq a -> Seq a
Seq.insertAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) a
y Seq a
xs
Seq a
Empty -> a
y a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
forall a. Seq a
Seq.empty
{-# INLINE insertSeqAt #-}
(|>) :: NESeq a -> a -> NESeq a
(a
x :<|| Seq a
xs) |> :: NESeq a -> a -> NESeq a
|> 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
Seq.|> a
y)
{-# INLINE (|>) #-}
(><|) :: Seq a -> NESeq a -> NESeq a
Seq a
xs ><| :: Seq a -> NESeq a -> NESeq a
><| NESeq a
ys = NESeq a -> (NESeq a -> NESeq a) -> Seq a -> NESeq a
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty NESeq a
ys (NESeq a -> NESeq a -> NESeq a
forall a. NESeq a -> NESeq a -> NESeq a
>< NESeq a
ys) Seq a
xs
{-# INLINE (><|) #-}
infixl 5 |>
infixr 5 ><|
replicateA :: Applicative f => Int -> f a -> f (NESeq a)
replicateA :: Int -> f a -> f (NESeq a)
replicateA Int
n f a
x
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = [Char] -> f (NESeq a)
forall a. HasCallStack => [Char] -> a
error [Char]
"NESeq.replicateA: must take a positive integer argument"
| Bool
otherwise = (a -> Seq a -> NESeq a) -> f a -> f (Seq a) -> f (NESeq a)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
(:<||) f a
x (Int -> f a -> f (Seq a)
forall (f :: * -> *) a. Applicative f => Int -> f a -> f (Seq a)
Seq.replicateA (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) f a
x)
{-# INLINE replicateA #-}
replicateA1 :: Apply f => Int -> f a -> f (NESeq a)
replicateA1 :: Int -> f a -> f (NESeq a)
replicateA1 Int
n f a
x
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = [Char] -> f (NESeq a)
forall a. HasCallStack => [Char] -> a
error [Char]
"NESeq.replicateA1: must take a positive integer argument"
| Bool
otherwise = case MaybeApply f (Seq a) -> Either (f (Seq a)) (Seq a)
forall (f :: * -> *) a. MaybeApply f a -> Either (f a) a
runMaybeApply (Int -> MaybeApply f a -> MaybeApply f (Seq a)
forall (f :: * -> *) a. Applicative f => Int -> f a -> f (Seq a)
Seq.replicateA (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Either (f a) a -> MaybeApply f a
forall (f :: * -> *) a. Either (f a) a -> MaybeApply f a
MaybeApply (f a -> Either (f a) a
forall a b. a -> Either a b
Left f a
x))) of
Left f (Seq a)
xs -> a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
(:<||) (a -> Seq a -> NESeq a) -> f a -> f (Seq a -> NESeq a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
x f (Seq a -> NESeq a) -> f (Seq a) -> f (NESeq a)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> f (Seq a)
xs
Right Seq a
xs -> (a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
xs) (a -> NESeq a) -> f a -> f (NESeq a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
x
{-# INLINE replicateA1 #-}
replicateM :: Applicative m => Int -> m a -> m (NESeq a)
replicateM :: Int -> m a -> m (NESeq a)
replicateM = Int -> m a -> m (NESeq a)
forall (f :: * -> *) a. Applicative f => Int -> f a -> f (NESeq a)
replicateA
{-# INLINE replicateM #-}
cycleTaking :: Int -> NESeq a -> NESeq a
cycleTaking :: Int -> NESeq a -> NESeq a
cycleTaking Int
n xs0 :: NESeq a
xs0@(a
x :<|| Seq a
xs)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = [Char] -> NESeq a
forall a. HasCallStack => [Char] -> a
error [Char]
"NESeq.cycleTaking: must take a positive integer argument"
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Seq a -> Int
forall a. Seq a -> Int
Seq.length Seq a
xs = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
Seq.take (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
| Bool
otherwise = NESeq a
xs0 NESeq a -> Seq a -> NESeq a
forall a. NESeq a -> Seq a -> NESeq a
|>< Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
Seq.cycleTaking (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- NESeq a -> Int
forall a. NESeq a -> Int
length NESeq a
xs0) (NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
xs0)
{-# INLINE cycleTaking #-}
iterateN :: Int -> (a -> a) -> a -> NESeq a
iterateN :: Int -> (a -> a) -> a -> NESeq a
iterateN Int
n a -> a
f a
x
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = [Char] -> NESeq a
forall a. HasCallStack => [Char] -> a
error [Char]
"NESeq.iterateN: must take a positive integer argument"
| Bool
otherwise = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Int -> (a -> a) -> a -> Seq a
forall a. Int -> (a -> a) -> a -> Seq a
Seq.iterateN (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) a -> a
f (a -> a
f a
x)
{-# INLINE iterateN #-}
unfoldr :: (b -> (a, Maybe b)) -> b -> NESeq a
unfoldr :: (b -> (a, Maybe b)) -> b -> NESeq a
unfoldr b -> (a, Maybe b)
f = b -> NESeq a
go
where
go :: b -> NESeq a
go b
x0 = a
y a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a -> (b -> Seq a) -> Maybe b -> Seq a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seq a
forall a. Seq a
Seq.empty (NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq (NESeq a -> Seq a) -> (b -> NESeq a) -> b -> Seq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> NESeq a
go) Maybe b
x1
where
(a
y, Maybe b
x1) = b -> (a, Maybe b)
f b
x0
{-# INLINE unfoldr #-}
unfoldl :: (b -> (Maybe b, a)) -> b -> NESeq a
unfoldl :: (b -> (Maybe b, a)) -> b -> NESeq a
unfoldl b -> (Maybe b, a)
f = b -> NESeq a
go
where
go :: b -> NESeq a
go b
x0 = Seq a -> (b -> Seq a) -> Maybe b -> Seq a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seq a
forall a. Seq a
Seq.empty (NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq (NESeq a -> Seq a) -> (b -> NESeq a) -> b -> Seq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> NESeq a
go) Maybe b
x1 Seq a -> a -> NESeq a
forall a. Seq a -> a -> NESeq a
:||> a
y
where
(Maybe b
x1, a
y) = b -> (Maybe b, a)
f b
x0
{-# INLINE unfoldl #-}
head :: NESeq a -> a
head :: NESeq a -> a
head (a
x :<|| Seq a
_) = a
x
{-# INLINE head #-}
tail :: NESeq a -> Seq a
tail :: NESeq a -> Seq a
tail (a
_ :<|| Seq a
xs) = Seq a
xs
{-# INLINE tail #-}
last :: NESeq a -> a
last :: NESeq a -> a
last (Seq a
_ :||> a
x) = a
x
{-# INLINE last #-}
init :: NESeq a -> Seq a
init :: NESeq a -> Seq a
init (Seq a
xs :||> a
_) = Seq a
xs
{-# INLINE init #-}
scanl :: (a -> b -> a) -> a -> NESeq b -> NESeq a
scanl :: (a -> b -> a) -> a -> NESeq b -> NESeq a
scanl a -> b -> a
f a
y0 (b
x :<|| Seq b
xs) = a
y0 a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| (a -> b -> a) -> a -> Seq b -> Seq a
forall a b. (a -> b -> a) -> a -> Seq b -> Seq a
Seq.scanl a -> b -> a
f (a -> b -> a
f a
y0 b
x) Seq b
xs
{-# INLINE scanl #-}
scanl1 :: (a -> a -> a) -> NESeq a -> NESeq a
scanl1 :: (a -> a -> a) -> NESeq a -> NESeq a
scanl1 a -> a -> a
f (a
x :<|| Seq a
xs) = NESeq a -> (NESeq a -> NESeq a) -> Seq a -> NESeq a
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) ((a -> a -> a) -> a -> NESeq a -> NESeq a
forall a b. (a -> b -> a) -> a -> NESeq b -> NESeq a
scanl a -> a -> a
f a
x) Seq a
xs
{-# INLINE scanl1 #-}
scanr :: (a -> b -> b) -> b -> NESeq a -> NESeq b
scanr :: (a -> b -> b) -> b -> NESeq a -> NESeq b
scanr a -> b -> b
f b
y0 (Seq a
xs :||> a
x) = (a -> b -> b) -> b -> Seq a -> Seq b
forall a b. (a -> b -> b) -> b -> Seq a -> Seq b
Seq.scanr a -> b -> b
f (a -> b -> b
f a
x b
y0) Seq a
xs Seq b -> b -> NESeq b
forall a. Seq a -> a -> NESeq a
:||> b
y0
{-# INLINE scanr #-}
scanr1 :: (a -> a -> a) -> NESeq a -> NESeq a
scanr1 :: (a -> a -> a) -> NESeq a -> NESeq a
scanr1 a -> a -> a
f (Seq a
xs :||> a
x) = NESeq a -> (NESeq a -> NESeq a) -> Seq a -> NESeq a
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) ((a -> a -> a) -> a -> NESeq a -> NESeq a
forall a b. (a -> b -> b) -> b -> NESeq a -> NESeq b
scanr a -> a -> a
f a
x) Seq a
xs
{-# INLINE scanr1 #-}
inits :: NESeq a -> NESeq (NESeq a)
inits :: NESeq a -> NESeq (NESeq a)
inits xs :: NESeq a
xs@(Seq a
ys :||> a
_) = 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 (NESeq a) -> NESeq a -> NESeq (NESeq a)
forall a. NESeq a -> a -> NESeq a
|> NESeq a
xs) (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)
inits) Seq a
ys
{-# INLINABLE inits #-}
chunksOf :: Int -> NESeq a -> NESeq (NESeq a)
chunksOf :: Int -> NESeq a -> NESeq (NESeq a)
chunksOf Int
n = NESeq a -> NESeq (NESeq a)
forall a. NESeq a -> NESeq (NESeq a)
go
where
go :: NESeq a -> NESeq (NESeq a)
go NESeq a
xs = case Int -> NESeq a -> These (NESeq a) (NESeq a)
forall a. Int -> NESeq a -> These (NESeq a) (NESeq a)
splitAt Int
n NESeq a
xs of
This NESeq a
ys -> NESeq a -> NESeq (NESeq a)
forall a. a -> NESeq a
singleton NESeq a
ys
That NESeq a
_ -> NESeq (NESeq a)
forall a. a
e
These NESeq a
ys NESeq a
zs -> NESeq a
ys NESeq a -> NESeq (NESeq a) -> NESeq (NESeq a)
forall a. a -> NESeq a -> NESeq a
<| NESeq a -> NESeq (NESeq a)
go NESeq a
zs
e :: a
e = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"chunksOf: A non-empty sequence can only be broken up into positively-sized chunks."
{-# INLINABLE chunksOf #-}
takeWhileL :: (a -> Bool) -> NESeq a -> Seq a
takeWhileL :: (a -> Bool) -> NESeq a -> Seq a
takeWhileL a -> Bool
p (a
x :<|| Seq a
xs)
| a -> Bool
p a
x = a
x a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
Seq.<| (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.takeWhileL a -> Bool
p Seq a
xs
| Bool
otherwise = Seq a
forall a. Seq a
Seq.empty
{-# INLINE takeWhileL #-}
takeWhileR :: (a -> Bool) -> NESeq a -> Seq a
takeWhileR :: (a -> Bool) -> NESeq a -> Seq a
takeWhileR a -> Bool
p (Seq a
xs :||> a
x)
| a -> Bool
p a
x = (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.takeWhileR a -> Bool
p Seq a
xs Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
Seq.|> a
x
| Bool
otherwise = Seq a
forall a. Seq a
Seq.empty
{-# INLINE takeWhileR #-}
dropWhileL :: (a -> Bool) -> NESeq a -> Seq a
dropWhileL :: (a -> Bool) -> NESeq a -> Seq a
dropWhileL a -> Bool
p xs0 :: NESeq a
xs0@(a
x :<|| Seq a
xs)
| a -> Bool
p a
x = (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileL a -> Bool
p Seq a
xs
| Bool
otherwise = NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
xs0
{-# INLINE dropWhileL #-}
dropWhileR :: (a -> Bool) -> NESeq a -> Seq a
dropWhileR :: (a -> Bool) -> NESeq a -> Seq a
dropWhileR a -> Bool
p xs0 :: NESeq a
xs0@(Seq a
xs :||> a
x)
| a -> Bool
p a
x = (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.dropWhileR a -> Bool
p Seq a
xs
| Bool
otherwise = NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
xs0
{-# INLINE dropWhileR #-}
spanl :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanl :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanl a -> Bool
p xs0 :: NESeq a
xs0@(a
x :<|| Seq a
xs)
| a -> Bool
p a
x = case (Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
ys, Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
zs) of
(Maybe (NESeq a)
Nothing , Maybe (NESeq a)
Nothing ) -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This (a -> NESeq a
forall a. a -> NESeq a
singleton a
x)
(Just NESeq a
_ , Maybe (NESeq a)
Nothing ) -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This NESeq a
xs0
(Maybe (NESeq a)
Nothing , Just NESeq a
zs') -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) NESeq a
zs'
(Just NESeq a
ys', Just NESeq a
zs') -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
ys') NESeq a
zs'
| Bool
otherwise = NESeq a -> These (NESeq a) (NESeq a)
forall a b. b -> These a b
That NESeq a
xs0
where
(Seq a
ys, Seq a
zs) = (a -> Bool) -> Seq a -> (Seq a, Seq a)
forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
Seq.spanl a -> Bool
p Seq a
xs
{-# INLINABLE spanl #-}
spanr :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanr :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanr a -> Bool
p xs0 :: NESeq a
xs0@(Seq a
xs :||> a
x)
| a -> Bool
p a
x = case (Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
ys, Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
zs) of
(Maybe (NESeq a)
Nothing , Maybe (NESeq a)
Nothing ) -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This (a -> NESeq a
forall a. a -> NESeq a
singleton a
x)
(Just NESeq a
_ , Maybe (NESeq a)
Nothing ) -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This NESeq a
xs0
(Maybe (NESeq a)
Nothing , Just NESeq a
zs') -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) NESeq a
zs'
(Just NESeq a
ys', Just NESeq a
zs') -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (NESeq a
ys' NESeq a -> a -> NESeq a
forall a. NESeq a -> a -> NESeq a
|> a
x ) NESeq a
zs'
| Bool
otherwise = NESeq a -> These (NESeq a) (NESeq a)
forall a b. b -> These a b
That NESeq a
xs0
where
(Seq a
ys, Seq a
zs) = (a -> Bool) -> Seq a -> (Seq a, Seq a)
forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
Seq.spanr a -> Bool
p Seq a
xs
{-# INLINABLE spanr #-}
breakl :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
breakl :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
breakl a -> Bool
p = (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
forall a. (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanl (Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p)
{-# INLINE breakl #-}
breakr :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
breakr :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
breakr a -> Bool
p = (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
forall a. (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanr (Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p)
{-# INLINE breakr #-}
partition :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
partition :: (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
partition a -> Bool
p xs0 :: NESeq a
xs0@(a
x :<|| Seq a
xs) = case (Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
ys, Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
zs) of
(Maybe (NESeq a)
Nothing , Maybe (NESeq a)
Nothing )
| a -> Bool
p a
x -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This (a -> NESeq a
forall a. a -> NESeq a
singleton a
x)
| Bool
otherwise -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. b -> These a b
That (a -> NESeq a
forall a. a -> NESeq a
singleton a
x)
(Just NESeq a
ys', Maybe (NESeq a)
Nothing )
| a -> Bool
p a
x -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This NESeq a
xs0
| Bool
otherwise -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These NESeq a
ys' (a -> NESeq a
forall a. a -> NESeq a
singleton a
x)
(Maybe (NESeq a)
Nothing, Just NESeq a
zs' )
| a -> Bool
p a
x -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) NESeq a
zs'
| Bool
otherwise -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. b -> These a b
That NESeq a
xs0
(Just NESeq a
ys', Just NESeq a
zs')
| a -> Bool
p a
x -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
ys') NESeq a
zs'
| Bool
otherwise -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These NESeq a
ys' (a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
zs')
where
(Seq a
ys, Seq a
zs) = (a -> Bool) -> Seq a -> (Seq a, Seq a)
forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
Seq.partition a -> Bool
p Seq a
xs
{-# INLINABLE partition #-}
filter :: (a -> Bool) -> NESeq a -> Seq a
filter :: (a -> Bool) -> NESeq a -> Seq a
filter a -> Bool
p (a
x :<|| Seq a
xs)
| a -> Bool
p a
x = a
x a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
Seq.<| (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.filter a -> Bool
p Seq a
xs
| Bool
otherwise = (a -> Bool) -> Seq a -> Seq a
forall a. (a -> Bool) -> Seq a -> Seq a
Seq.filter a -> Bool
p Seq a
xs
{-# INLINE filter #-}
sort :: Ord a => NESeq a -> NESeq a
sort :: NESeq a -> NESeq a
sort = (a -> a -> Ordering) -> NESeq a -> NESeq a
forall a. (a -> a -> Ordering) -> NESeq a -> NESeq a
sortBy a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE sort #-}
sortBy :: (a -> a -> Ordering) -> NESeq a -> NESeq a
sortBy :: (a -> a -> Ordering) -> NESeq a -> NESeq a
sortBy a -> a -> Ordering
c (a
x :<|| Seq a
xs) = NESeq a -> (NESeq a -> NESeq a) -> Seq a -> NESeq a
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) ((a -> a -> Ordering) -> a -> NESeq a -> NESeq a
forall a. (a -> a -> Ordering) -> a -> NESeq a -> NESeq a
insertBy a -> a -> Ordering
c a
x)
(Seq a -> NESeq a) -> (Seq a -> Seq a) -> Seq a -> NESeq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> Ordering) -> Seq a -> Seq a
forall a. (a -> a -> Ordering) -> Seq a -> Seq a
Seq.sortBy a -> a -> Ordering
c
(Seq a -> NESeq a) -> Seq a -> NESeq a
forall a b. (a -> b) -> a -> b
$ Seq a
xs
{-# INLINE sortBy #-}
sortOn :: Ord b => (a -> b) -> NESeq a -> NESeq a
sortOn :: (a -> b) -> NESeq a -> NESeq a
sortOn a -> b
f (a
x :<|| Seq a
xs) = NESeq a -> (NESeq a -> NESeq a) -> Seq a -> NESeq a
forall r a. r -> (NESeq a -> r) -> Seq a -> r
withNonEmpty (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) ((a -> b) -> a -> NESeq a -> NESeq a
forall b a. Ord b => (a -> b) -> a -> NESeq a -> NESeq a
insertOn a -> b
f a
x)
(Seq a -> NESeq a) -> (Seq a -> Seq a) -> Seq a -> NESeq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> Seq a -> Seq a
forall b a. Ord b => (a -> b) -> Seq a -> Seq a
sortOnSeq a -> b
f
(Seq a -> NESeq a) -> Seq a -> NESeq a
forall a b. (a -> b) -> a -> b
$ Seq a
xs
{-# INLINE sortOn #-}
unstableSort :: Ord a => NESeq a -> NESeq a
unstableSort :: NESeq a -> NESeq a
unstableSort = (a -> a -> Ordering) -> NESeq a -> NESeq a
forall a. (a -> a -> Ordering) -> NESeq a -> NESeq a
unstableSortBy a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE unstableSort #-}
unstableSortBy :: (a -> a -> Ordering) -> NESeq a -> NESeq a
unstableSortBy :: (a -> a -> Ordering) -> NESeq a -> NESeq a
unstableSortBy a -> a -> Ordering
c = Seq a -> NESeq a
forall a. Seq a -> NESeq a
unsafeFromSeq (Seq a -> NESeq a) -> (NESeq a -> Seq a) -> NESeq a -> NESeq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> Ordering) -> Seq a -> Seq a
forall a. (a -> a -> Ordering) -> Seq a -> Seq a
Seq.unstableSortBy a -> a -> Ordering
c (Seq a -> Seq a) -> (NESeq a -> Seq a) -> NESeq a -> Seq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq
{-# INLINE unstableSortBy #-}
unstableSortOn :: Ord b => (a -> b) -> NESeq a -> NESeq a
unstableSortOn :: (a -> b) -> NESeq a -> NESeq a
unstableSortOn a -> b
f = Seq a -> NESeq a
forall a. Seq a -> NESeq a
unsafeFromSeq (Seq a -> NESeq a) -> (NESeq a -> Seq a) -> NESeq a -> NESeq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> Seq a -> Seq a
forall b a. Ord b => (a -> b) -> Seq a -> Seq a
unstableSortOnSeq a -> b
f (Seq a -> Seq a) -> (NESeq a -> Seq a) -> NESeq a -> Seq a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq
{-# INLINE unstableSortOn #-}
insertBy :: (a -> a -> Ordering) -> a -> NESeq a -> NESeq a
insertBy :: (a -> a -> Ordering) -> a -> NESeq a -> NESeq a
insertBy a -> a -> Ordering
c a
x NESeq a
xs = case (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
forall a. (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanl a -> Bool
ltx NESeq a
xs of
This NESeq a
ys -> NESeq a
ys NESeq a -> a -> NESeq a
forall a. NESeq a -> a -> NESeq a
|> a
x
That NESeq a
zs -> a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
zs
These NESeq a
ys NESeq a
zs -> NESeq a
ys NESeq a -> NESeq a -> NESeq a
forall a. NESeq a -> NESeq a -> NESeq a
>< (a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
zs)
where
ltx :: a -> Bool
ltx a
y = a -> a -> Ordering
c a
x a
y Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT
{-# INLINABLE insertBy #-}
insertOn :: Ord b => (a -> b) -> a -> NESeq a -> NESeq a
insertOn :: (a -> b) -> a -> NESeq a -> NESeq a
insertOn a -> b
f a
x NESeq a
xs = case (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
forall a. (a -> Bool) -> NESeq a -> These (NESeq a) (NESeq a)
spanl a -> Bool
ltx NESeq a
xs of
This NESeq a
ys -> NESeq a
ys NESeq a -> a -> NESeq a
forall a. NESeq a -> a -> NESeq a
|> a
x
That NESeq a
zs -> a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
zs
These NESeq a
ys NESeq a
zs -> NESeq a
ys NESeq a -> NESeq a -> NESeq a
forall a. NESeq a -> NESeq a -> NESeq a
>< (a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
zs)
where
fx :: b
fx = a -> b
f a
x
ltx :: a -> Bool
ltx a
y = b
fx b -> b -> Bool
forall a. Ord a => a -> a -> Bool
> a -> b
f a
y
{-# INLINABLE insertOn #-}
lookup :: Int -> NESeq a -> Maybe a
lookup :: Int -> NESeq a -> Maybe a
lookup Int
0 (a
x :<|| Seq a
_ ) = a -> Maybe a
forall a. a -> Maybe a
Just a
x
lookup Int
i (a
_ :<|| Seq a
xs) = Int -> Seq a -> Maybe a
forall a. Int -> Seq a -> Maybe a
Seq.lookup (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
{-# INLINE lookup #-}
(!?) :: NESeq a -> Int -> Maybe a
!? :: NESeq a -> Int -> Maybe a
(!?) = (Int -> NESeq a -> Maybe a) -> NESeq a -> Int -> Maybe a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> NESeq a -> Maybe a
forall a. Int -> NESeq a -> Maybe a
lookup
{-# INLINE (!?) #-}
adjust :: (a -> a) -> Int -> NESeq a -> NESeq a
adjust :: (a -> a) -> Int -> NESeq a -> NESeq a
adjust a -> a
f Int
0 (a
x :<|| Seq a
xs) = a -> a
f a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
xs
adjust a -> a
f Int
i (a
x :<|| Seq a
xs) = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| (a -> a) -> Int -> Seq a -> Seq a
forall a. (a -> a) -> Int -> Seq a -> Seq a
Seq.adjust a -> a
f (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
{-# INLINE adjust #-}
adjust' :: (a -> a) -> Int -> NESeq a -> NESeq a
adjust' :: (a -> a) -> Int -> NESeq a -> NESeq a
adjust' a -> a
f Int
0 (a
x :<|| Seq a
xs) = let !y :: a
y = a -> a
f a
x in a
y a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
xs
adjust' a -> a
f Int
i (a
x :<|| Seq a
xs) = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| (a -> a) -> Int -> Seq a -> Seq a
forall a. (a -> a) -> Int -> Seq a -> Seq a
Seq.adjust a -> a
f (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
{-# INLINE adjust' #-}
update :: Int -> a -> NESeq a -> NESeq a
update :: Int -> a -> NESeq a -> NESeq a
update Int
0 a
y (a
_ :<|| Seq a
xs) = a
y a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Seq a
xs
update Int
i a
y (a
x :<|| Seq a
xs) = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Int -> a -> Seq a -> Seq a
forall a. Int -> a -> Seq a -> Seq a
Seq.update (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) a
y Seq a
xs
{-# INLINE update #-}
take :: Int -> NESeq a -> Seq a
take :: Int -> NESeq a -> Seq a
take Int
i (a
x :<|| Seq a
xs)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Seq a
forall a. Seq a
Seq.empty
| Bool
otherwise = a
x a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
Seq.<| Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
Seq.take (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
{-# INLINE take #-}
drop :: Int -> NESeq a -> Seq a
drop :: Int -> NESeq a -> Seq a
drop Int
i xs0 :: NESeq a
xs0@(a
_ :<|| Seq a
xs)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
xs0
| Bool
otherwise = Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
Seq.drop (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
{-# INLINE drop #-}
insertAt :: Int -> a -> NESeq a -> NESeq a
insertAt :: Int -> a -> NESeq a -> NESeq a
insertAt Int
i a
y xs0 :: NESeq a
xs0@(a
x :<|| Seq a
xs)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = a
y a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
xs0
| Bool
otherwise = a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| Int -> a -> Seq a -> Seq a
forall a. Int -> a -> Seq a -> Seq a
Seq.insertAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) a
y Seq a
xs
{-# INLINE insertAt #-}
deleteAt :: Int -> NESeq a -> Seq a
deleteAt :: Int -> NESeq a -> Seq a
deleteAt Int
i xs0 :: NESeq a
xs0@(a
x :<|| Seq a
xs) = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
i Int
0 of
Ordering
LT -> NESeq a -> Seq a
forall a. NESeq a -> Seq a
toSeq NESeq a
xs0
Ordering
EQ -> Seq a
xs
Ordering
GT -> a
x a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
Seq.<| Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
Seq.deleteAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
{-# INLINE deleteAt #-}
splitAt :: Int -> NESeq a -> These (NESeq a) (NESeq a)
splitAt :: Int -> NESeq a -> These (NESeq a) (NESeq a)
splitAt Int
n xs0 :: NESeq a
xs0@(a
x :<|| Seq a
xs)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = NESeq a -> These (NESeq a) (NESeq a)
forall a b. b -> These a b
That NESeq a
xs0
| Bool
otherwise = case (Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
ys, Seq a -> Maybe (NESeq a)
forall a. Seq a -> Maybe (NESeq a)
nonEmptySeq Seq a
zs) of
(Maybe (NESeq a)
Nothing , Maybe (NESeq a)
Nothing ) -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This (a -> NESeq a
forall a. a -> NESeq a
singleton a
x)
(Just NESeq a
_ , Maybe (NESeq a)
Nothing ) -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> These a b
This NESeq a
xs0
(Maybe (NESeq a)
Nothing , Just NESeq a
zs') -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (a -> NESeq a
forall a. a -> NESeq a
singleton a
x) NESeq a
zs'
(Just NESeq a
ys', Just NESeq a
zs') -> NESeq a -> NESeq a -> These (NESeq a) (NESeq a)
forall a b. a -> b -> These a b
These (a
x a -> NESeq a -> NESeq a
forall a. a -> NESeq a -> NESeq a
<| NESeq a
ys') NESeq a
zs'
where
(Seq a
ys, Seq a
zs) = Int -> Seq a -> (Seq a, Seq a)
forall a. Int -> Seq a -> (Seq a, Seq a)
Seq.splitAt (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Seq a
xs
{-# INLINABLE splitAt #-}
elemIndexL :: Eq a => a -> NESeq a -> Maybe Int
elemIndexL :: a -> NESeq a -> Maybe Int
elemIndexL a
x = (a -> Bool) -> NESeq a -> Maybe Int
forall a. (a -> Bool) -> NESeq a -> Maybe Int
findIndexL (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x)
{-# INLINE elemIndexL #-}
elemIndexR :: Eq a => a -> NESeq a -> Maybe Int
elemIndexR :: a -> NESeq a -> Maybe Int
elemIndexR a
x = (a -> Bool) -> NESeq a -> Maybe Int
forall a. (a -> Bool) -> NESeq a -> Maybe Int
findIndexR (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x)
{-# INLINE elemIndexR #-}
elemIndicesL :: Eq a => a -> NESeq a -> [Int]
elemIndicesL :: a -> NESeq a -> [Int]
elemIndicesL a
x = (a -> Bool) -> NESeq a -> [Int]
forall a. (a -> Bool) -> NESeq a -> [Int]
findIndicesL (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x)
{-# INLINE elemIndicesL #-}
elemIndicesR :: Eq a => a -> NESeq a -> [Int]
elemIndicesR :: a -> NESeq a -> [Int]
elemIndicesR a
x = (a -> Bool) -> NESeq a -> [Int]
forall a. (a -> Bool) -> NESeq a -> [Int]
findIndicesR (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x)
{-# INLINE elemIndicesR #-}
findIndexL :: (a -> Bool) -> NESeq a -> Maybe Int
findIndexL :: (a -> Bool) -> NESeq a -> Maybe Int
findIndexL a -> Bool
p (a
x :<|| Seq a
xs) = Maybe Int
here_ Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Int
there_
where
here_ :: Maybe Int
here_ = Int
0 Int -> Maybe () -> Maybe Int
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (a -> Bool
p a
x)
there_ :: Maybe Int
there_ = (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int -> Int) -> Maybe Int -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> Bool) -> Seq a -> Maybe Int
forall a. (a -> Bool) -> Seq a -> Maybe Int
Seq.findIndexL a -> Bool
p Seq a
xs
{-# INLINE findIndexL #-}
findIndexR :: (a -> Bool) -> NESeq a -> Maybe Int
findIndexR :: (a -> Bool) -> NESeq a -> Maybe Int
findIndexR a -> Bool
p (Seq a
xs :||> a
x) = Maybe Int
here_ Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Int
there_
where
here_ :: Maybe Int
here_ = Seq a -> Int
forall a. Seq a -> Int
Seq.length Seq a
xs Int -> Maybe () -> Maybe Int
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (a -> Bool
p a
x)
there_ :: Maybe Int
there_ = (a -> Bool) -> Seq a -> Maybe Int
forall a. (a -> Bool) -> Seq a -> Maybe Int
Seq.findIndexR a -> Bool
p Seq a
xs
{-# INLINE findIndexR #-}
findIndicesL :: (a -> Bool) -> NESeq a -> [Int]
findIndicesL :: (a -> Bool) -> NESeq a -> [Int]
findIndicesL a -> Bool
p (a
x :<|| Seq a
xs)
| a -> Bool
p a
x = Int
0 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
ixs
| Bool
otherwise = [Int]
ixs
where
ixs :: [Int]
ixs = (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int -> Int) -> [Int] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> Bool) -> Seq a -> [Int]
forall a. (a -> Bool) -> Seq a -> [Int]
Seq.findIndicesL a -> Bool
p Seq a
xs
{-# INLINE findIndicesL #-}
findIndicesR :: (a -> Bool) -> NESeq a -> [Int]
findIndicesR :: (a -> Bool) -> NESeq a -> [Int]
findIndicesR a -> Bool
p (Seq a
xs :||> a
x)
| a -> Bool
p a
x = Seq a -> Int
forall a. Seq a -> Int
Seq.length Seq a
xs Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
ixs
| Bool
otherwise = [Int]
ixs
where
ixs :: [Int]
ixs = (a -> Bool) -> Seq a -> [Int]
forall a. (a -> Bool) -> Seq a -> [Int]
Seq.findIndicesR a -> Bool
p Seq a
xs
{-# INLINE findIndicesR #-}
foldlWithIndex :: (b -> Int -> a -> b) -> b -> NESeq a -> b
foldlWithIndex :: (b -> Int -> a -> b) -> b -> NESeq a -> b
foldlWithIndex b -> Int -> a -> b
f b
z (Seq a
xs :||> a
x) = (\b
z' -> b -> Int -> a -> b
f b
z' (Seq a -> Int
forall a. Seq a -> Int
Seq.length Seq a
xs) a
x) (b -> b) -> (Seq a -> b) -> Seq a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b -> Int -> a -> b) -> b -> Seq a -> b
forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
Seq.foldlWithIndex b -> Int -> a -> b
f b
z (Seq a -> b) -> Seq a -> b
forall a b. (a -> b) -> a -> b
$ Seq a
xs
{-# INLINE foldlWithIndex #-}
foldrWithIndex :: (Int -> a -> b -> b) -> b -> NESeq a -> b
foldrWithIndex :: (Int -> a -> b -> b) -> b -> NESeq a -> b
foldrWithIndex Int -> a -> b -> b
f b
z (a
x :<|| Seq a
xs) = Int -> a -> b -> b
f Int
0 a
x (b -> b) -> (Seq a -> b) -> Seq a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> a -> b -> b) -> b -> Seq a -> b
forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
Seq.foldrWithIndex (Int -> a -> b -> b
f (Int -> a -> b -> b) -> (Int -> Int) -> Int -> a -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) b
z (Seq a -> b) -> Seq a -> b
forall a b. (a -> b) -> a -> b
$ Seq a
xs
{-# INLINE foldrWithIndex #-}
mapWithIndex :: (Int -> a -> b) -> NESeq a -> NESeq b
mapWithIndex :: (Int -> a -> b) -> NESeq a -> NESeq b
mapWithIndex Int -> a -> b
f (a
x :<|| Seq a
xs) = Int -> a -> b
f Int
0 a
x b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
:<|| (Int -> a -> b) -> Seq a -> Seq b
forall a b. (Int -> a -> b) -> Seq a -> Seq b
Seq.mapWithIndex (Int -> a -> b
f (Int -> a -> b) -> (Int -> Int) -> Int -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) Seq a
xs
{-# NOINLINE [1] mapWithIndex #-}
{-# RULES
"mapWithIndex/mapWithIndex" forall f g xs . mapWithIndex f (mapWithIndex g xs) =
mapWithIndex (\k a -> f k (g k a)) xs
"mapWithIndex/map" forall f g xs . mapWithIndex f (map g xs) =
mapWithIndex (\k a -> f k (g a)) xs
"map/mapWithIndex" forall f g xs . map f (mapWithIndex g xs) =
mapWithIndex (\k a -> f (g k a)) xs
#-}
traverseWithIndex :: Applicative f => (Int -> a -> f b) -> NESeq a -> f (NESeq b)
traverseWithIndex :: (Int -> a -> f b) -> NESeq a -> f (NESeq b)
traverseWithIndex Int -> a -> f b
f (a
x :<|| Seq a
xs) = 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. Applicative f => f (a -> b) -> f a -> f b
<*> (Int -> a -> f b) -> Seq a -> f (Seq b)
forall (f :: * -> *) a b.
Applicative f =>
(Int -> a -> f b) -> Seq a -> f (Seq b)
Seq.traverseWithIndex (Int -> a -> f b
f (Int -> a -> f b) -> (Int -> Int) -> Int -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) Seq a
xs
{-# NOINLINE [1] traverseWithIndex #-}
{-# RULES
"travWithIndex/mapWithIndex" forall f g xs . traverseWithIndex f (mapWithIndex g xs) =
traverseWithIndex (\k a -> f k (g k a)) xs
"travWithIndex/map" forall f g xs . traverseWithIndex f (map g xs) =
traverseWithIndex (\k a -> f k (g a)) xs
#-}
reverse :: NESeq a -> NESeq a
reverse :: NESeq a -> NESeq a
reverse (a
x :<|| Seq a
xs) = Seq a -> Seq a
forall a. Seq a -> Seq a
Seq.reverse Seq a
xs Seq a -> a -> NESeq a
forall a. Seq a -> a -> NESeq a
:||> a
x
{-# NOINLINE [1] reverse #-}
mapReverse :: (a -> b) -> NESeq a -> NESeq b
mapReverse :: (a -> b) -> NESeq a -> NESeq b
mapReverse a -> b
f (a
x :<|| Seq a
xs) = (a -> b) -> Seq a -> Seq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Seq a -> Seq a
forall a. Seq a -> Seq a
Seq.reverse Seq a
xs) Seq b -> b -> NESeq b
forall a. Seq a -> a -> NESeq a
:||> a -> b
f a
x
{-# RULES
"map/reverse" forall f xs . map f (reverse xs) = mapReverse f xs
"reverse/map" forall f xs . reverse (map f xs) = mapReverse f xs
#-}
intersperse :: a -> NESeq a -> NESeq a
intersperse :: a -> NESeq a -> NESeq a
intersperse a
z nes :: NESeq a
nes@(a
x :<|| Seq a
xs) = case Seq a
xs of
a
_ Seq.:<| Seq a
_ -> a
x a -> Seq a -> NESeq a
forall a. a -> Seq a -> NESeq a
:<|| (a
z a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
Seq.<| a -> Seq a -> Seq a
forall a. a -> Seq a -> Seq a
Seq.intersperse a
z Seq a
xs)
Seq a
Seq.Empty -> NESeq a
nes
{-# INLINE intersperse #-}
zip3 :: NESeq a -> NESeq b -> NESeq c -> NESeq (a, b, c)
zip3 :: NESeq a -> NESeq b -> NESeq c -> NESeq (a, b, c)
zip3 (a
x :<|| Seq a
xs) (b
y :<|| Seq b
ys) (c
z :<|| Seq c
zs) = (a
x, b
y, c
z) (a, b, c) -> Seq (a, b, c) -> NESeq (a, b, c)
forall a. a -> Seq a -> NESeq a
:<|| Seq a -> Seq b -> Seq c -> Seq (a, b, c)
forall a b c. Seq a -> Seq b -> Seq c -> Seq (a, b, c)
Seq.zip3 Seq a
xs Seq b
ys Seq c
zs
{-# INLINE zip3 #-}
zipWith3 :: (a -> b -> c -> d) -> NESeq a -> NESeq b -> NESeq c -> NESeq d
zipWith3 :: (a -> b -> c -> d) -> NESeq a -> NESeq b -> NESeq c -> NESeq d
zipWith3 a -> b -> c -> d
f (a
x :<|| Seq a
xs) (b
y :<|| Seq b
ys) (c
z :<|| Seq c
zs) = a -> b -> c -> d
f a
x b
y c
z d -> Seq d -> NESeq d
forall a. a -> Seq a -> NESeq a
:<|| (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
forall a b c d.
(a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
Seq.zipWith3 a -> b -> c -> d
f Seq a
xs Seq b
ys Seq c
zs
{-# INLINE zipWith3 #-}
zip4 :: NESeq a -> NESeq b -> NESeq c -> NESeq d -> NESeq (a, b, c, d)
zip4 :: NESeq a -> NESeq b -> NESeq c -> NESeq d -> NESeq (a, b, c, d)
zip4 (a
x :<|| Seq a
xs) (b
y :<|| Seq b
ys) (c
z :<|| Seq c
zs) (d
r :<|| Seq d
rs) = (a
x, b
y, c
z, d
r) (a, b, c, d) -> Seq (a, b, c, d) -> NESeq (a, b, c, d)
forall a. a -> Seq a -> NESeq a
:<|| Seq a -> Seq b -> Seq c -> Seq d -> Seq (a, b, c, d)
forall a b c d.
Seq a -> Seq b -> Seq c -> Seq d -> Seq (a, b, c, d)
Seq.zip4 Seq a
xs Seq b
ys Seq c
zs Seq d
rs
{-# INLINE zip4 #-}
zipWith4 :: (a -> b -> c -> d -> e) -> NESeq a -> NESeq b -> NESeq c -> NESeq d -> NESeq e
zipWith4 :: (a -> b -> c -> d -> e)
-> NESeq a -> NESeq b -> NESeq c -> NESeq d -> NESeq e
zipWith4 a -> b -> c -> d -> e
f (a
x :<|| Seq a
xs) (b
y :<|| Seq b
ys) (c
z :<|| Seq c
zs) (d
r :<|| Seq d
rs) = a -> b -> c -> d -> e
f a
x b
y c
z d
r e -> Seq e -> NESeq e
forall a. a -> Seq a -> NESeq a
:<|| (a -> b -> c -> d -> e)
-> Seq a -> Seq b -> Seq c -> Seq d -> Seq e
forall a b c d e.
(a -> b -> c -> d -> e)
-> Seq a -> Seq b -> Seq c -> Seq d -> Seq e
Seq.zipWith4 a -> b -> c -> d -> e
f Seq a
xs Seq b
ys Seq c
zs Seq d
rs
{-# INLINE zipWith4 #-}
unzipWith :: (a -> (b, c)) -> NESeq a -> (NESeq b, NESeq c)
unzipWith :: (a -> (b, c)) -> NESeq a -> (NESeq b, NESeq c)
unzipWith a -> (b, c)
f (a
x :<|| Seq a
xs) = (Seq b -> NESeq b)
-> (Seq c -> NESeq c) -> (Seq b, Seq c) -> (NESeq b, NESeq c)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (b
y b -> Seq b -> NESeq b
forall a. a -> Seq a -> NESeq a
:<||) (c
z c -> Seq c -> NESeq c
forall a. a -> Seq a -> NESeq a
:<||) ((Seq b, Seq c) -> (NESeq b, NESeq c))
-> (Seq a -> (Seq b, Seq c)) -> Seq a -> (NESeq b, NESeq c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
forall a b c. (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
unzipWithSeq a -> (b, c)
f (Seq a -> (NESeq b, NESeq c)) -> Seq a -> (NESeq b, NESeq c)
forall a b. (a -> b) -> a -> b
$ Seq a
xs
where
~(b
y, c
z) = a -> (b, c)
f a
x
{-# NOINLINE [1] unzipWith #-}
{-# RULES
"unzipWith/map" forall f g xs. unzipWith f (map g xs) =
unzipWith (f . g) xs
#-}