{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
module Data.IntSet.NonEmpty (
NEIntSet,
Key,
pattern IsNonEmpty,
pattern IsEmpty,
nonEmptySet,
toSet,
withNonEmpty,
insertSet,
insertSetMin,
insertSetMax,
unsafeFromSet,
singleton,
fromList,
fromAscList,
fromDistinctAscList,
insert,
delete,
member,
notMember,
lookupLT,
lookupGT,
lookupLE,
lookupGE,
size,
isSubsetOf,
isProperSubsetOf,
disjoint,
union,
unions,
difference,
(\\),
intersection,
filter,
partition,
split,
splitMember,
splitRoot,
map,
foldr,
foldl,
foldr1,
foldl1,
foldr',
foldl',
foldr1',
foldl1',
findMin,
findMax,
deleteMin,
deleteMax,
deleteFindMin,
deleteFindMax,
elems,
toList,
toAscList,
toDescList,
valid,
) where
import Control.Applicative
import Data.Bifunctor
import Data.IntSet (IntSet)
import qualified Data.IntSet as S
import Data.IntSet.NonEmpty.Internal
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import Data.Maybe
import Data.These
import Prelude hiding (Foldable (..), filter, map)
pattern IsNonEmpty :: NEIntSet -> IntSet
pattern $mIsNonEmpty :: forall {r}. IntSet -> (NEIntSet -> r) -> ((# #) -> r) -> r
$bIsNonEmpty :: NEIntSet -> IntSet
IsNonEmpty n <- (nonEmptySet -> Just n)
where
IsNonEmpty NEIntSet
n = NEIntSet -> IntSet
toSet NEIntSet
n
pattern IsEmpty :: IntSet
pattern $mIsEmpty :: forall {r}. IntSet -> ((# #) -> r) -> ((# #) -> r) -> r
$bIsEmpty :: IntSet
IsEmpty <- (S.null -> True)
where
IsEmpty = IntSet
S.empty
{-# COMPLETE IsNonEmpty, IsEmpty #-}
insertSet :: Key -> IntSet -> NEIntSet
insertSet :: Key -> IntSet -> NEIntSet
insertSet Key
x = NEIntSet -> (NEIntSet -> NEIntSet) -> IntSet -> NEIntSet
forall r. r -> (NEIntSet -> r) -> IntSet -> r
withNonEmpty (Key -> NEIntSet
singleton Key
x) (Key -> NEIntSet -> NEIntSet
insert Key
x)
{-# INLINE insertSet #-}
insertSetMin :: Key -> IntSet -> NEIntSet
insertSetMin :: Key -> IntSet -> NEIntSet
insertSetMin = Key -> IntSet -> NEIntSet
NEIntSet
{-# INLINE insertSetMin #-}
insertSetMax :: Key -> IntSet -> NEIntSet
insertSetMax :: Key -> IntSet -> NEIntSet
insertSetMax Key
x = NEIntSet -> (NEIntSet -> NEIntSet) -> IntSet -> NEIntSet
forall r. r -> (NEIntSet -> r) -> IntSet -> r
withNonEmpty (Key -> NEIntSet
singleton Key
x) NEIntSet -> NEIntSet
go
where
go :: NEIntSet -> NEIntSet
go (NEIntSet Key
x0 IntSet
s0) = Key -> IntSet -> NEIntSet
NEIntSet Key
x0 (IntSet -> NEIntSet) -> (IntSet -> IntSet) -> IntSet -> NEIntSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> IntSet -> IntSet
insertMaxSet Key
x (IntSet -> NEIntSet) -> IntSet -> NEIntSet
forall a b. (a -> b) -> a -> b
$ IntSet
s0
{-# INLINE insertSetMax #-}
unsafeFromSet ::
IntSet ->
NEIntSet
unsafeFromSet :: IntSet -> NEIntSet
unsafeFromSet = NEIntSet -> (NEIntSet -> NEIntSet) -> IntSet -> NEIntSet
forall r. r -> (NEIntSet -> r) -> IntSet -> r
withNonEmpty NEIntSet
forall {a}. a
e NEIntSet -> NEIntSet
forall a. a -> a
id
where
e :: a
e = [Char] -> a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NEIntSet.unsafeFromSet: empty set"
{-# INLINE unsafeFromSet #-}
fromAscList :: NonEmpty Key -> NEIntSet
fromAscList :: NonEmpty Key -> NEIntSet
fromAscList = NonEmpty Key -> NEIntSet
fromDistinctAscList (NonEmpty Key -> NEIntSet)
-> (NonEmpty Key -> NonEmpty Key) -> NonEmpty Key -> NEIntSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Key -> NonEmpty Key
combineEq
{-# INLINE fromAscList #-}
fromDistinctAscList :: NonEmpty Key -> NEIntSet
fromDistinctAscList :: NonEmpty Key -> NEIntSet
fromDistinctAscList (Key
x :| [Key]
xs) =
Key -> IntSet -> NEIntSet
insertSetMin Key
x
(IntSet -> NEIntSet) -> ([Key] -> IntSet) -> [Key] -> NEIntSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Key] -> IntSet
S.fromDistinctAscList
([Key] -> NEIntSet) -> [Key] -> NEIntSet
forall a b. (a -> b) -> a -> b
$ [Key]
xs
{-# INLINE fromDistinctAscList #-}
insert :: Key -> NEIntSet -> NEIntSet
insert :: Key -> NEIntSet -> NEIntSet
insert Key
x n :: NEIntSet
n@(NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> Key -> IntSet -> NEIntSet
NEIntSet Key
x (IntSet -> NEIntSet) -> IntSet -> NEIntSet
forall a b. (a -> b) -> a -> b
$ NEIntSet -> IntSet
toSet NEIntSet
n
Ordering
EQ -> Key -> IntSet -> NEIntSet
NEIntSet Key
x IntSet
s
Ordering
GT -> Key -> IntSet -> NEIntSet
NEIntSet Key
x0 (IntSet -> NEIntSet) -> IntSet -> NEIntSet
forall a b. (a -> b) -> a -> b
$ Key -> IntSet -> IntSet
S.insert Key
x IntSet
s
{-# INLINE insert #-}
delete :: Key -> NEIntSet -> IntSet
delete :: Key -> NEIntSet -> IntSet
delete Key
x n :: NEIntSet
n@(NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> NEIntSet -> IntSet
toSet NEIntSet
n
Ordering
EQ -> IntSet
s
Ordering
GT -> Key -> IntSet -> IntSet
insertMinSet Key
x0 (IntSet -> IntSet) -> (IntSet -> IntSet) -> IntSet -> IntSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> IntSet -> IntSet
S.delete Key
x (IntSet -> IntSet) -> IntSet -> IntSet
forall a b. (a -> b) -> a -> b
$ IntSet
s
{-# INLINE delete #-}
member :: Key -> NEIntSet -> Bool
member :: Key -> NEIntSet -> Bool
member Key
x (NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> Bool
False
Ordering
EQ -> Bool
True
Ordering
GT -> Key -> IntSet -> Bool
S.member Key
x IntSet
s
{-# INLINE member #-}
notMember :: Key -> NEIntSet -> Bool
notMember :: Key -> NEIntSet -> Bool
notMember Key
x (NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> Bool
True
Ordering
EQ -> Bool
False
Ordering
GT -> Key -> IntSet -> Bool
S.notMember Key
x IntSet
s
{-# INLINE notMember #-}
lookupLT :: Key -> NEIntSet -> Maybe Key
lookupLT :: Key -> NEIntSet -> Maybe Key
lookupLT Key
x (NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> Maybe Key
forall a. Maybe a
Nothing
Ordering
EQ -> Maybe Key
forall a. Maybe a
Nothing
Ordering
GT -> Key -> IntSet -> Maybe Key
S.lookupLT Key
x IntSet
s Maybe Key -> Maybe Key -> Maybe Key
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Key -> Maybe Key
forall a. a -> Maybe a
Just Key
x0
{-# INLINE lookupLT #-}
lookupGT :: Key -> NEIntSet -> Maybe Key
lookupGT :: Key -> NEIntSet -> Maybe Key
lookupGT Key
x (NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> Key -> Maybe Key
forall a. a -> Maybe a
Just Key
x0
Ordering
EQ -> (Key, IntSet) -> Key
forall a b. (a, b) -> a
fst ((Key, IntSet) -> Key) -> Maybe (Key, IntSet) -> Maybe Key
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IntSet -> Maybe (Key, IntSet)
S.minView IntSet
s
Ordering
GT -> Key -> IntSet -> Maybe Key
S.lookupGT Key
x IntSet
s
{-# INLINE lookupGT #-}
lookupLE :: Key -> NEIntSet -> Maybe Key
lookupLE :: Key -> NEIntSet -> Maybe Key
lookupLE Key
x (NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> Maybe Key
forall a. Maybe a
Nothing
Ordering
EQ -> Key -> Maybe Key
forall a. a -> Maybe a
Just Key
x0
Ordering
GT -> Key -> IntSet -> Maybe Key
S.lookupLE Key
x IntSet
s Maybe Key -> Maybe Key -> Maybe Key
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Key -> Maybe Key
forall a. a -> Maybe a
Just Key
x0
{-# INLINE lookupLE #-}
lookupGE :: Key -> NEIntSet -> Maybe Key
lookupGE :: Key -> NEIntSet -> Maybe Key
lookupGE Key
x (NEIntSet Key
x0 IntSet
s) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> Key -> Maybe Key
forall a. a -> Maybe a
Just Key
x0
Ordering
EQ -> Key -> Maybe Key
forall a. a -> Maybe a
Just Key
x0
Ordering
GT -> Key -> IntSet -> Maybe Key
S.lookupGE Key
x IntSet
s
{-# INLINE lookupGE #-}
foldr :: (Key -> b -> b) -> b -> NEIntSet -> b
foldr :: forall b. (Key -> b -> b) -> b -> NEIntSet -> b
foldr Key -> b -> b
f b
z (NEIntSet Key
x IntSet
s) = Key
x Key -> b -> b
`f` (Key -> b -> b) -> b -> IntSet -> b
forall b. (Key -> b -> b) -> b -> IntSet -> b
S.foldr Key -> b -> b
f b
z IntSet
s
{-# INLINE foldr #-}
foldr' :: (Key -> b -> b) -> b -> NEIntSet -> b
foldr' :: forall b. (Key -> b -> b) -> b -> NEIntSet -> b
foldr' Key -> b -> b
f b
z (NEIntSet Key
x IntSet
s) = Key
x Key -> b -> b
`f` b
y
where
!y :: b
y = (Key -> b -> b) -> b -> IntSet -> b
forall b. (Key -> b -> b) -> b -> IntSet -> b
S.foldr' Key -> b -> b
f b
z IntSet
s
{-# INLINE foldr' #-}
foldr1 :: (Key -> Key -> Key) -> NEIntSet -> Key
foldr1 :: (Key -> Key -> Key) -> NEIntSet -> Key
foldr1 Key -> Key -> Key
f (NEIntSet Key
x IntSet
s) =
Key -> ((Key, IntSet) -> Key) -> Maybe (Key, IntSet) -> Key
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Key
x (Key -> Key -> Key
f Key
x (Key -> Key) -> ((Key, IntSet) -> Key) -> (Key, IntSet) -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> IntSet -> Key) -> (Key, IntSet) -> Key
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((Key -> Key -> Key) -> Key -> IntSet -> Key
forall b. (Key -> b -> b) -> b -> IntSet -> b
S.foldr Key -> Key -> Key
f))
(Maybe (Key, IntSet) -> Key)
-> (IntSet -> Maybe (Key, IntSet)) -> IntSet -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Key, IntSet)
S.maxView
(IntSet -> Key) -> IntSet -> Key
forall a b. (a -> b) -> a -> b
$ IntSet
s
{-# INLINE foldr1 #-}
foldl :: (a -> Key -> a) -> a -> NEIntSet -> a
foldl :: forall a. (a -> Key -> a) -> a -> NEIntSet -> a
foldl a -> Key -> a
f a
z (NEIntSet Key
x IntSet
s) = (a -> Key -> a) -> a -> IntSet -> a
forall a. (a -> Key -> a) -> a -> IntSet -> a
S.foldl a -> Key -> a
f (a -> Key -> a
f a
z Key
x) IntSet
s
{-# INLINE foldl #-}
foldl' :: (a -> Key -> a) -> a -> NEIntSet -> a
foldl' :: forall a. (a -> Key -> a) -> a -> NEIntSet -> a
foldl' a -> Key -> a
f a
z (NEIntSet Key
x IntSet
s) = (a -> Key -> a) -> a -> IntSet -> a
forall a. (a -> Key -> a) -> a -> IntSet -> a
S.foldl' a -> Key -> a
f a
y IntSet
s
where
!y :: a
y = a -> Key -> a
f a
z Key
x
{-# INLINE foldl' #-}
foldl1 :: (Key -> Key -> Key) -> NEIntSet -> Key
foldl1 :: (Key -> Key -> Key) -> NEIntSet -> Key
foldl1 Key -> Key -> Key
f (NEIntSet Key
x IntSet
s) = (Key -> Key -> Key) -> Key -> IntSet -> Key
forall a. (a -> Key -> a) -> a -> IntSet -> a
S.foldl Key -> Key -> Key
f Key
x IntSet
s
{-# INLINE foldl1 #-}
foldr1' :: (Key -> Key -> Key) -> NEIntSet -> Key
foldr1' :: (Key -> Key -> Key) -> NEIntSet -> Key
foldr1' Key -> Key -> Key
f (NEIntSet Key
x IntSet
s) = case IntSet -> Maybe (Key, IntSet)
S.maxView IntSet
s of
Maybe (Key, IntSet)
Nothing -> Key
x
Just (Key
y, IntSet
s') -> let !z :: Key
z = (Key -> Key -> Key) -> Key -> IntSet -> Key
forall b. (Key -> b -> b) -> b -> IntSet -> b
S.foldr' Key -> Key -> Key
f Key
y IntSet
s' in Key
x Key -> Key -> Key
`f` Key
z
{-# INLINE foldr1' #-}
foldl1' :: (Key -> Key -> Key) -> NEIntSet -> Key
foldl1' :: (Key -> Key -> Key) -> NEIntSet -> Key
foldl1' Key -> Key -> Key
f (NEIntSet Key
x IntSet
s) = (Key -> Key -> Key) -> Key -> IntSet -> Key
forall a. (a -> Key -> a) -> a -> IntSet -> a
S.foldl' Key -> Key -> Key
f Key
x IntSet
s
{-# INLINE foldl1' #-}
size :: NEIntSet -> Int
size :: NEIntSet -> Key
size (NEIntSet Key
_ IntSet
s) = Key
1 Key -> Key -> Key
forall a. Num a => a -> a -> a
+ IntSet -> Key
S.size IntSet
s
{-# INLINE size #-}
isSubsetOf ::
NEIntSet ->
NEIntSet ->
Bool
isSubsetOf :: NEIntSet -> NEIntSet -> Bool
isSubsetOf (NEIntSet Key
x IntSet
s0) (NEIntSet -> IntSet
toSet -> IntSet
s1) =
Key
x Key -> IntSet -> Bool
`S.member` IntSet
s1
Bool -> Bool -> Bool
&& IntSet
s0 IntSet -> IntSet -> Bool
`S.isSubsetOf` IntSet
s1
{-# INLINE isSubsetOf #-}
isProperSubsetOf ::
NEIntSet ->
NEIntSet ->
Bool
isProperSubsetOf :: NEIntSet -> NEIntSet -> Bool
isProperSubsetOf NEIntSet
s0 NEIntSet
s1 =
IntSet -> Key
S.size (NEIntSet -> IntSet
neisIntSet NEIntSet
s0) Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< IntSet -> Key
S.size (NEIntSet -> IntSet
neisIntSet NEIntSet
s1)
Bool -> Bool -> Bool
&& NEIntSet
s0 NEIntSet -> NEIntSet -> Bool
`isSubsetOf` NEIntSet
s1
{-# INLINE isProperSubsetOf #-}
disjoint ::
NEIntSet ->
NEIntSet ->
Bool
disjoint :: NEIntSet -> NEIntSet -> Bool
disjoint n1 :: NEIntSet
n1@(NEIntSet Key
x1 IntSet
s1) n2 :: NEIntSet
n2@(NEIntSet Key
x2 IntSet
s2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x1 Key
x2 of
Ordering
LT -> IntSet
s1 IntSet -> IntSet -> Bool
`S.disjoint` NEIntSet -> IntSet
toSet NEIntSet
n2
Ordering
EQ -> Bool
False
Ordering
GT -> NEIntSet -> IntSet
toSet NEIntSet
n1 IntSet -> IntSet -> Bool
`S.disjoint` IntSet
s2
{-# INLINE disjoint #-}
difference ::
NEIntSet ->
NEIntSet ->
IntSet
difference :: NEIntSet -> NEIntSet -> IntSet
difference n1 :: NEIntSet
n1@(NEIntSet Key
x1 IntSet
s1) n2 :: NEIntSet
n2@(NEIntSet Key
x2 IntSet
s2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x1 Key
x2 of
Ordering
LT -> Key -> IntSet -> IntSet
insertMinSet Key
x1 (IntSet -> IntSet) -> IntSet -> IntSet
forall a b. (a -> b) -> a -> b
$ IntSet
s1 IntSet -> IntSet -> IntSet
`S.difference` NEIntSet -> IntSet
toSet NEIntSet
n2
Ordering
EQ -> IntSet
s1 IntSet -> IntSet -> IntSet
`S.difference` IntSet
s2
Ordering
GT -> NEIntSet -> IntSet
toSet NEIntSet
n1 IntSet -> IntSet -> IntSet
`S.difference` IntSet
s2
{-# INLINE difference #-}
(\\) ::
NEIntSet ->
NEIntSet ->
IntSet
\\ :: NEIntSet -> NEIntSet -> IntSet
(\\) = NEIntSet -> NEIntSet -> IntSet
difference
{-# INLINE (\\) #-}
intersection ::
NEIntSet ->
NEIntSet ->
IntSet
intersection :: NEIntSet -> NEIntSet -> IntSet
intersection n1 :: NEIntSet
n1@(NEIntSet Key
x1 IntSet
s1) n2 :: NEIntSet
n2@(NEIntSet Key
x2 IntSet
s2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x1 Key
x2 of
Ordering
LT -> IntSet
s1 IntSet -> IntSet -> IntSet
`S.intersection` NEIntSet -> IntSet
toSet NEIntSet
n2
Ordering
EQ -> Key -> IntSet -> IntSet
insertMinSet Key
x1 (IntSet -> IntSet) -> IntSet -> IntSet
forall a b. (a -> b) -> a -> b
$ IntSet
s1 IntSet -> IntSet -> IntSet
`S.intersection` IntSet
s2
Ordering
GT -> NEIntSet -> IntSet
toSet NEIntSet
n1 IntSet -> IntSet -> IntSet
`S.intersection` IntSet
s2
{-# INLINE intersection #-}
filter ::
(Key -> Bool) ->
NEIntSet ->
IntSet
filter :: (Key -> Bool) -> NEIntSet -> IntSet
filter Key -> Bool
f (NEIntSet Key
x IntSet
s1)
| Key -> Bool
f Key
x = Key -> IntSet -> IntSet
insertMinSet Key
x (IntSet -> IntSet) -> (IntSet -> IntSet) -> IntSet -> IntSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> Bool) -> IntSet -> IntSet
S.filter Key -> Bool
f (IntSet -> IntSet) -> IntSet -> IntSet
forall a b. (a -> b) -> a -> b
$ IntSet
s1
| Bool
otherwise = (Key -> Bool) -> IntSet -> IntSet
S.filter Key -> Bool
f IntSet
s1
{-# INLINE filter #-}
partition ::
(Key -> Bool) ->
NEIntSet ->
These NEIntSet NEIntSet
partition :: (Key -> Bool) -> NEIntSet -> These NEIntSet NEIntSet
partition Key -> Bool
f n :: NEIntSet
n@(NEIntSet Key
x IntSet
s0) = case (IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s1, IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s2) of
(Maybe NEIntSet
Nothing, Maybe NEIntSet
Nothing)
| Key -> Bool
f Key
x -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> These a b
This NEIntSet
n
| Bool
otherwise -> NEIntSet -> These NEIntSet NEIntSet
forall a b. b -> These a b
That NEIntSet
n
(Just NEIntSet
n1, Maybe NEIntSet
Nothing)
| Key -> Bool
f Key
x -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> These a b
This NEIntSet
n
| Bool
otherwise -> NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These NEIntSet
n1 (Key -> NEIntSet
singleton Key
x)
(Maybe NEIntSet
Nothing, Just NEIntSet
n2)
| Key -> Bool
f Key
x -> NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These (Key -> NEIntSet
singleton Key
x) NEIntSet
n2
| Bool
otherwise -> NEIntSet -> These NEIntSet NEIntSet
forall a b. b -> These a b
That NEIntSet
n
(Just NEIntSet
n1, Just NEIntSet
n2)
| Key -> Bool
f Key
x -> NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These (Key -> IntSet -> NEIntSet
insertSetMin Key
x IntSet
s1) NEIntSet
n2
| Bool
otherwise -> NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These NEIntSet
n1 (Key -> IntSet -> NEIntSet
insertSetMin Key
x IntSet
s2)
where
(IntSet
s1, IntSet
s2) = (Key -> Bool) -> IntSet -> (IntSet, IntSet)
S.partition Key -> Bool
f IntSet
s0
{-# INLINEABLE partition #-}
split ::
Key ->
NEIntSet ->
Maybe (These NEIntSet NEIntSet)
split :: Key -> NEIntSet -> Maybe (These NEIntSet NEIntSet)
split Key
x n :: NEIntSet
n@(NEIntSet Key
x0 IntSet
s0) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> These NEIntSet NEIntSet
forall a b. b -> These a b
That NEIntSet
n
Ordering
EQ -> NEIntSet -> These NEIntSet NEIntSet
forall a b. b -> These a b
That (NEIntSet -> These NEIntSet NEIntSet)
-> Maybe NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s0
Ordering
GT -> case (IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s1, IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s2) of
(Maybe NEIntSet
Nothing, Maybe NEIntSet
Nothing) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> These a b
This (Key -> NEIntSet
singleton Key
x0)
(Just NEIntSet
_, Maybe NEIntSet
Nothing) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> These a b
This (Key -> IntSet -> NEIntSet
insertSetMin Key
x0 IntSet
s1)
(Maybe NEIntSet
Nothing, Just NEIntSet
n2) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These (Key -> NEIntSet
singleton Key
x0) NEIntSet
n2
(Just NEIntSet
_, Just NEIntSet
n2) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These (Key -> IntSet -> NEIntSet
insertSetMin Key
x0 IntSet
s1) NEIntSet
n2
where
(IntSet
s1, IntSet
s2) = Key -> IntSet -> (IntSet, IntSet)
S.split Key
x IntSet
s0
{-# INLINEABLE split #-}
splitMember ::
Key ->
NEIntSet ->
(Bool, Maybe (These NEIntSet NEIntSet))
splitMember :: Key -> NEIntSet -> (Bool, Maybe (These NEIntSet NEIntSet))
splitMember Key
x n :: NEIntSet
n@(NEIntSet Key
x0 IntSet
s0) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
x Key
x0 of
Ordering
LT -> (Bool
False, These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> These NEIntSet NEIntSet
forall a b. b -> These a b
That NEIntSet
n)
Ordering
EQ -> (Bool
True, NEIntSet -> These NEIntSet NEIntSet
forall a b. b -> These a b
That (NEIntSet -> These NEIntSet NEIntSet)
-> Maybe NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s0)
Ordering
GT -> (Bool
mem,) (Maybe (These NEIntSet NEIntSet)
-> (Bool, Maybe (These NEIntSet NEIntSet)))
-> Maybe (These NEIntSet NEIntSet)
-> (Bool, Maybe (These NEIntSet NEIntSet))
forall a b. (a -> b) -> a -> b
$ case (IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s1, IntSet -> Maybe NEIntSet
nonEmptySet IntSet
s2) of
(Maybe NEIntSet
Nothing, Maybe NEIntSet
Nothing) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> These a b
This (Key -> NEIntSet
singleton Key
x0)
(Just NEIntSet
_, Maybe NEIntSet
Nothing) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> These a b
This (Key -> IntSet -> NEIntSet
insertSetMin Key
x0 IntSet
s1)
(Maybe NEIntSet
Nothing, Just NEIntSet
n2) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These (Key -> NEIntSet
singleton Key
x0) NEIntSet
n2
(Just NEIntSet
_, Just NEIntSet
n2) -> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a. a -> Maybe a
Just (These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet))
-> These NEIntSet NEIntSet -> Maybe (These NEIntSet NEIntSet)
forall a b. (a -> b) -> a -> b
$ NEIntSet -> NEIntSet -> These NEIntSet NEIntSet
forall a b. a -> b -> These a b
These (Key -> IntSet -> NEIntSet
insertSetMin Key
x0 IntSet
s1) NEIntSet
n2
where
(IntSet
s1, Bool
mem, IntSet
s2) = Key -> IntSet -> (IntSet, Bool, IntSet)
S.splitMember Key
x IntSet
s0
{-# INLINEABLE splitMember #-}
splitRoot ::
NEIntSet ->
NonEmpty NEIntSet
splitRoot :: NEIntSet -> NonEmpty NEIntSet
splitRoot (NEIntSet Key
x IntSet
s) =
Key -> NEIntSet
singleton Key
x
NEIntSet -> [NEIntSet] -> NonEmpty NEIntSet
forall a. a -> [a] -> NonEmpty a
:| (IntSet -> Maybe NEIntSet) -> [IntSet] -> [NEIntSet]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe IntSet -> Maybe NEIntSet
nonEmptySet (IntSet -> [IntSet]
S.splitRoot IntSet
s)
{-# INLINE splitRoot #-}
map ::
(Key -> Key) ->
NEIntSet ->
NEIntSet
map :: (Key -> Key) -> NEIntSet -> NEIntSet
map Key -> Key
f (NEIntSet Key
x0 IntSet
s) =
NonEmpty Key -> NEIntSet
fromList
(NonEmpty Key -> NEIntSet)
-> (IntSet -> NonEmpty Key) -> IntSet -> NEIntSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> Key
f Key
x0 Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:|)
([Key] -> NonEmpty Key)
-> (IntSet -> [Key]) -> IntSet -> NonEmpty Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> [Key] -> [Key]) -> [Key] -> IntSet -> [Key]
forall b. (Key -> b -> b) -> b -> IntSet -> b
S.foldr (\Key
x [Key]
xs -> Key -> Key
f Key
x Key -> [Key] -> [Key]
forall a. a -> [a] -> [a]
: [Key]
xs) []
(IntSet -> NEIntSet) -> IntSet -> NEIntSet
forall a b. (a -> b) -> a -> b
$ IntSet
s
{-# INLINE map #-}
findMin :: NEIntSet -> Key
findMin :: NEIntSet -> Key
findMin (NEIntSet Key
x IntSet
_) = Key
x
{-# INLINE findMin #-}
findMax :: NEIntSet -> Key
findMax :: NEIntSet -> Key
findMax (NEIntSet Key
x IntSet
s) = Key -> ((Key, IntSet) -> Key) -> Maybe (Key, IntSet) -> Key
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Key
x (Key, IntSet) -> Key
forall a b. (a, b) -> a
fst (Maybe (Key, IntSet) -> Key)
-> (IntSet -> Maybe (Key, IntSet)) -> IntSet -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Key, IntSet)
S.maxView (IntSet -> Key) -> IntSet -> Key
forall a b. (a -> b) -> a -> b
$ IntSet
s
{-# INLINE findMax #-}
deleteMin :: NEIntSet -> IntSet
deleteMin :: NEIntSet -> IntSet
deleteMin (NEIntSet Key
_ IntSet
s) = IntSet
s
{-# INLINE deleteMin #-}
deleteMax :: NEIntSet -> IntSet
deleteMax :: NEIntSet -> IntSet
deleteMax (NEIntSet Key
x IntSet
s) = case IntSet -> Maybe (Key, IntSet)
S.maxView IntSet
s of
Maybe (Key, IntSet)
Nothing -> IntSet
S.empty
Just (Key
_, IntSet
s') -> Key -> IntSet -> IntSet
insertMinSet Key
x IntSet
s'
{-# INLINE deleteMax #-}
deleteFindMin :: NEIntSet -> (Key, IntSet)
deleteFindMin :: NEIntSet -> (Key, IntSet)
deleteFindMin (NEIntSet Key
x IntSet
s) = (Key
x, IntSet
s)
{-# INLINE deleteFindMin #-}
deleteFindMax :: NEIntSet -> (Key, IntSet)
deleteFindMax :: NEIntSet -> (Key, IntSet)
deleteFindMax (NEIntSet Key
x IntSet
s) =
(Key, IntSet)
-> ((Key, IntSet) -> (Key, IntSet))
-> Maybe (Key, IntSet)
-> (Key, IntSet)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Key
x, IntSet
S.empty) ((IntSet -> IntSet) -> (Key, IntSet) -> (Key, IntSet)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Key -> IntSet -> IntSet
insertMinSet Key
x))
(Maybe (Key, IntSet) -> (Key, IntSet))
-> (IntSet -> Maybe (Key, IntSet)) -> IntSet -> (Key, IntSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntSet -> Maybe (Key, IntSet)
S.maxView
(IntSet -> (Key, IntSet)) -> IntSet -> (Key, IntSet)
forall a b. (a -> b) -> a -> b
$ IntSet
s
{-# INLINE deleteFindMax #-}
elems :: NEIntSet -> NonEmpty Key
elems :: NEIntSet -> NonEmpty Key
elems = NEIntSet -> NonEmpty Key
toList
{-# INLINE elems #-}
toAscList :: NEIntSet -> NonEmpty Key
toAscList :: NEIntSet -> NonEmpty Key
toAscList = NEIntSet -> NonEmpty Key
toList
{-# INLINE toAscList #-}
toDescList :: NEIntSet -> NonEmpty Key
toDescList :: NEIntSet -> NonEmpty Key
toDescList (NEIntSet Key
x IntSet
s) = (NonEmpty Key -> Key -> NonEmpty Key)
-> NonEmpty Key -> IntSet -> NonEmpty Key
forall a. (a -> Key -> a) -> a -> IntSet -> a
S.foldl' ((Key -> NonEmpty Key -> NonEmpty Key)
-> NonEmpty Key -> Key -> NonEmpty Key
forall a b c. (a -> b -> c) -> b -> a -> c
flip Key -> NonEmpty Key -> NonEmpty Key
forall a. a -> NonEmpty a -> NonEmpty a
(NE.<|)) (Key
x Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| []) IntSet
s
{-# INLINE toDescList #-}
combineEq :: NonEmpty Key -> NonEmpty Key
combineEq :: NonEmpty Key -> NonEmpty Key
combineEq (Key
x :| [Key]
xs) = Key -> [Key] -> NonEmpty Key
forall {t}. Eq t => t -> [t] -> NonEmpty t
go Key
x [Key]
xs
where
go :: t -> [t] -> NonEmpty t
go t
z [] = t
z t -> [t] -> NonEmpty t
forall a. a -> [a] -> NonEmpty a
:| []
go t
z (t
y : [t]
ys)
| t
z t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
y = t -> [t] -> NonEmpty t
go t
z [t]
ys
| Bool
otherwise = t
z t -> NonEmpty t -> NonEmpty t
forall a. a -> NonEmpty a -> NonEmpty a
NE.<| t -> [t] -> NonEmpty t
go t
y [t]
ys