{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Set.NonEmpty (
NESet
, pattern IsNonEmpty
, pattern IsEmpty
, nonEmptySet
, toSet
, withNonEmpty
, insertSet
, insertSetMin
, insertSetMax
, unsafeFromSet
, singleton
, fromList
, fromAscList
, fromDescList
, fromDistinctAscList
, fromDistinctDescList
, powerSet
, insert
, delete
, member
, notMember
, lookupLT
, lookupGT
, lookupLE
, lookupGE
, size
, isSubsetOf
, isProperSubsetOf
, disjoint
, union
, unions
, difference
, (\\)
, intersection
, cartesianProduct
, disjointUnion
, filter
, takeWhileAntitone
, dropWhileAntitone
, spanAntitone
, partition
, split
, splitMember
, splitRoot
, lookupIndex
, findIndex
, elemAt
, deleteAt
, take
, drop
, splitAt
, map
, mapMonotonic
, foldr
, foldl
, F.foldr1
, F.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.List.NonEmpty (NonEmpty(..))
import Data.Maybe
import Data.Set (Set)
import Data.Set.NonEmpty.Internal
import Data.These
import Prelude hiding (Foldable(..), filter, map, take, drop, splitAt)
import qualified Data.Foldable as F
import qualified Data.List.NonEmpty as NE
import qualified Data.Semigroup.Foldable as F1
import qualified Data.Set as S
pattern IsNonEmpty :: NESet a -> Set a
pattern $mIsNonEmpty :: forall {r} {a}. Set a -> (NESet a -> r) -> ((# #) -> r) -> r
$bIsNonEmpty :: forall a. NESet a -> Set a
IsNonEmpty n <- (nonEmptySet->Just n)
where
IsNonEmpty NESet a
n = NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n
pattern IsEmpty :: Set a
pattern $mIsEmpty :: forall {r} {a}. Set a -> ((# #) -> r) -> ((# #) -> r) -> r
$bIsEmpty :: forall a. Set a
IsEmpty <- (S.null->True)
where
IsEmpty = Set a
forall a. Set a
S.empty
{-# COMPLETE IsNonEmpty, IsEmpty #-}
unsafeFromSet
:: Set a
-> NESet a
unsafeFromSet :: forall a. Set a -> NESet a
unsafeFromSet = NESet a -> (NESet a -> NESet a) -> Set a -> NESet a
forall r a. r -> (NESet a -> r) -> Set a -> r
withNonEmpty NESet a
forall {a}. a
e NESet a -> NESet a
forall a. a -> a
id
where
e :: a
e = [Char] -> a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NESet.unsafeFromSet: empty set"
{-# INLINE unsafeFromSet #-}
insertSet :: Ord a => a -> Set a -> NESet a
insertSet :: forall a. Ord a => a -> Set a -> NESet a
insertSet a
x = NESet a -> (NESet a -> NESet a) -> Set a -> NESet a
forall r a. r -> (NESet a -> r) -> Set a -> r
withNonEmpty (a -> NESet a
forall a. a -> NESet a
singleton a
x) (a -> NESet a -> NESet a
forall a. Ord a => a -> NESet a -> NESet a
insert a
x)
{-# INLINE insertSet #-}
insertSetMin :: a -> Set a -> NESet a
insertSetMin :: forall a. a -> Set a -> NESet a
insertSetMin = a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet
{-# INLINE insertSetMin #-}
insertSetMax :: a -> Set a -> NESet a
insertSetMax :: forall a. a -> Set a -> NESet a
insertSetMax a
x = NESet a -> (NESet a -> NESet a) -> Set a -> NESet a
forall r a. r -> (NESet a -> r) -> Set a -> r
withNonEmpty (a -> NESet a
forall a. a -> NESet a
singleton a
x) NESet a -> NESet a
go
where
go :: NESet a -> NESet a
go (NESet a
x0 Set a
s0) = a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x0 (Set a -> NESet a) -> (Set a -> Set a) -> Set a -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMaxSet a
x (Set a -> NESet a) -> Set a -> NESet a
forall a b. (a -> b) -> a -> b
$ Set a
s0
{-# INLINE insertSetMax #-}
fromAscList :: Eq a => NonEmpty a -> NESet a
fromAscList :: forall a. Eq a => NonEmpty a -> NESet a
fromAscList = NonEmpty a -> NESet a
forall a. NonEmpty a -> NESet a
fromDistinctAscList (NonEmpty a -> NESet a)
-> (NonEmpty a -> NonEmpty a) -> NonEmpty a -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty a -> NonEmpty a
forall a. Eq a => NonEmpty a -> NonEmpty a
combineEq
{-# INLINE fromAscList #-}
fromDistinctAscList :: NonEmpty a -> NESet a
fromDistinctAscList :: forall a. NonEmpty a -> NESet a
fromDistinctAscList (a
x :| [a]
xs) = a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x
(Set a -> NESet a) -> ([a] -> Set a) -> [a] -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Set a
forall a. [a] -> Set a
S.fromDistinctAscList
([a] -> NESet a) -> [a] -> NESet a
forall a b. (a -> b) -> a -> b
$ [a]
xs
{-# INLINE fromDistinctAscList #-}
fromDescList :: Eq a => NonEmpty a -> NESet a
fromDescList :: forall a. Eq a => NonEmpty a -> NESet a
fromDescList = NonEmpty a -> NESet a
forall a. NonEmpty a -> NESet a
fromDistinctDescList (NonEmpty a -> NESet a)
-> (NonEmpty a -> NonEmpty a) -> NonEmpty a -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty a -> NonEmpty a
forall a. Eq a => NonEmpty a -> NonEmpty a
combineEq
{-# INLINE fromDescList #-}
fromDistinctDescList :: NonEmpty a -> NESet a
fromDistinctDescList :: forall a. NonEmpty a -> NESet a
fromDistinctDescList (a
x :| [a]
xs) = a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMax a
x
(Set a -> NESet a) -> ([a] -> Set a) -> [a] -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Set a
forall a. [a] -> Set a
S.fromDistinctDescList
([a] -> NESet a) -> [a] -> NESet a
forall a b. (a -> b) -> a -> b
$ [a]
xs
{-# INLINE fromDistinctDescList #-}
powerSet
:: forall a. ()
=> NESet a
-> NESet (NESet a)
powerSet :: forall a. NESet a -> NESet (NESet a)
powerSet (NESet a
x Set a
s0) = case Set (NESet a) -> Maybe (NESet (NESet a))
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set (NESet a)
p1 of
Maybe (NESet (NESet a))
Nothing -> NESet a -> NESet (NESet a)
forall a. a -> NESet a
singleton (a -> NESet a
forall a. a -> NESet a
singleton a
x)
Just NESet (NESet a)
p2 -> (Set a -> NESet a) -> NESet (Set a) -> NESet (NESet a)
forall a b. (a -> b) -> NESet a -> NESet b
mapMonotonic (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x) NESet (Set a)
p0
NESet (NESet a) -> NESet (NESet a) -> NESet (NESet a)
forall a. NESet a -> NESet a -> NESet a
`merge` NESet (NESet a)
p2
where
p0 :: NESet (Set a)
p0 :: NESet (Set a)
p0@(NESet Set a
_ Set (Set a)
p0s) = Set (Set a) -> NESet (Set a)
forall a. Set a -> NESet a
forSure (Set (Set a) -> NESet (Set a)) -> Set (Set a) -> NESet (Set a)
forall a b. (a -> b) -> a -> b
$ Set a -> Set (Set a)
forall a. Set a -> Set (Set a)
powerSetSet Set a
s0
p1 :: Set (NESet a)
p1 :: Set (NESet a)
p1 = (Set a -> NESet a) -> Set (Set a) -> Set (NESet a)
forall a b. (a -> b) -> Set a -> Set b
S.mapMonotonic Set a -> NESet a
forall a. Set a -> NESet a
forSure Set (Set a)
p0s
forSure :: Set a -> NESet a
forSure = NESet a -> (NESet a -> NESet a) -> Set a -> NESet a
forall r a. r -> (NESet a -> r) -> Set a -> r
withNonEmpty ([Char] -> NESet a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NESet.powerSet: internal error")
NESet a -> NESet a
forall a. a -> a
id
{-# INLINABLE powerSet #-}
insert :: Ord a => a -> NESet a -> NESet a
insert :: forall a. Ord a => a -> NESet a -> NESet a
insert a
x n :: NESet a
n@(NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x (Set a -> NESet a) -> Set a -> NESet a
forall a b. (a -> b) -> a -> b
$ NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n
Ordering
EQ -> a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x Set a
s
Ordering
GT -> a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x0 (Set a -> NESet a) -> Set a -> NESet a
forall a b. (a -> b) -> a -> b
$ a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
S.insert a
x Set a
s
{-# INLINE insert #-}
delete :: Ord a => a -> NESet a -> Set a
delete :: forall a. Ord a => a -> NESet a -> Set a
delete a
x n :: NESet a
n@(NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n
Ordering
EQ -> Set a
s
Ordering
GT -> a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x0 (Set a -> Set a) -> (Set a -> Set a) -> Set a -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
S.delete a
x (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINE delete #-}
member :: Ord a => a -> NESet a -> Bool
member :: forall a. Ord a => a -> NESet a -> Bool
member a
x (NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> Bool
False
Ordering
EQ -> Bool
True
Ordering
GT -> a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
S.member a
x Set a
s
{-# INLINE member #-}
notMember :: Ord a => a -> NESet a -> Bool
notMember :: forall a. Ord a => a -> NESet a -> Bool
notMember a
x (NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> Bool
True
Ordering
EQ -> Bool
False
Ordering
GT -> a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
S.notMember a
x Set a
s
{-# INLINE notMember #-}
lookupLT :: Ord a => a -> NESet a -> Maybe a
lookupLT :: forall a. Ord a => a -> NESet a -> Maybe a
lookupLT a
x (NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> Maybe a
forall a. Maybe a
Nothing
Ordering
EQ -> Maybe a
forall a. Maybe a
Nothing
Ordering
GT -> a -> Set a -> Maybe a
forall a. Ord a => a -> Set a -> Maybe a
S.lookupLT a
x Set a
s Maybe a -> Maybe a -> Maybe a
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> Maybe a
forall a. a -> Maybe a
Just a
x0
{-# INLINE lookupLT #-}
lookupGT :: Ord a => a -> NESet a -> Maybe a
lookupGT :: forall a. Ord a => a -> NESet a -> Maybe a
lookupGT a
x (NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> a -> Maybe a
forall a. a -> Maybe a
Just a
x0
Ordering
EQ -> Set a -> Maybe a
forall a. Set a -> Maybe a
S.lookupMin Set a
s
Ordering
GT -> a -> Set a -> Maybe a
forall a. Ord a => a -> Set a -> Maybe a
S.lookupGT a
x Set a
s
{-# INLINE lookupGT #-}
lookupLE :: Ord a => a -> NESet a -> Maybe a
lookupLE :: forall a. Ord a => a -> NESet a -> Maybe a
lookupLE a
x (NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> Maybe a
forall a. Maybe a
Nothing
Ordering
EQ -> a -> Maybe a
forall a. a -> Maybe a
Just a
x0
Ordering
GT -> a -> Set a -> Maybe a
forall a. Ord a => a -> Set a -> Maybe a
S.lookupLE a
x Set a
s Maybe a -> Maybe a -> Maybe a
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> Maybe a
forall a. a -> Maybe a
Just a
x0
{-# INLINE lookupLE #-}
lookupGE :: Ord a => a -> NESet a -> Maybe a
lookupGE :: forall a. Ord a => a -> NESet a -> Maybe a
lookupGE a
x (NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> a -> Maybe a
forall a. a -> Maybe a
Just a
x0
Ordering
EQ -> a -> Maybe a
forall a. a -> Maybe a
Just a
x0
Ordering
GT -> a -> Set a -> Maybe a
forall a. Ord a => a -> Set a -> Maybe a
S.lookupGE a
x Set a
s
{-# INLINE lookupGE #-}
isSubsetOf
:: Ord a
=> NESet a
-> NESet a
-> Bool
isSubsetOf :: forall a. Ord a => NESet a -> NESet a -> Bool
isSubsetOf (NESet a
x Set a
s0) (NESet a -> Set a
forall a. NESet a -> Set a
toSet->Set a
s1) = a
x a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set a
s1
Bool -> Bool -> Bool
&& Set a
s0 Set a -> Set a -> Bool
forall a. Ord a => Set a -> Set a -> Bool
`S.isSubsetOf` Set a
s1
{-# INLINE isSubsetOf #-}
isProperSubsetOf
:: Ord a
=> NESet a
-> NESet a
-> Bool
isProperSubsetOf :: forall a. Ord a => NESet a -> NESet a -> Bool
isProperSubsetOf NESet a
s0 NESet a
s1 = Set a -> Int
forall a. Set a -> Int
S.size (NESet a -> Set a
forall a. NESet a -> Set a
nesSet NESet a
s0) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Set a -> Int
forall a. Set a -> Int
S.size (NESet a -> Set a
forall a. NESet a -> Set a
nesSet NESet a
s1)
Bool -> Bool -> Bool
&& NESet a
s0 NESet a -> NESet a -> Bool
forall a. Ord a => NESet a -> NESet a -> Bool
`isSubsetOf` NESet a
s1
{-# INLINE isProperSubsetOf #-}
disjoint
:: Ord a
=> NESet a
-> NESet a
-> Bool
disjoint :: forall a. Ord a => NESet a -> NESet a -> Bool
disjoint n1 :: NESet a
n1@(NESet a
x1 Set a
s1) n2 :: NESet a
n2@(NESet a
x2 Set a
s2) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x1 a
x2 of
Ordering
LT -> Set a
s1 Set a -> Set a -> Bool
forall a. Ord a => Set a -> Set a -> Bool
`disjointSet` NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n2
Ordering
EQ -> Bool
False
Ordering
GT -> NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n1 Set a -> Set a -> Bool
forall a. Ord a => Set a -> Set a -> Bool
`disjointSet` Set a
s2
{-# INLINE disjoint #-}
difference
:: Ord a
=> NESet a
-> NESet a
-> Set a
difference :: forall a. Ord a => NESet a -> NESet a -> Set a
difference n1 :: NESet a
n1@(NESet a
x1 Set a
s1) n2 :: NESet a
n2@(NESet a
x2 Set a
s2) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x1 a
x2 of
Ordering
LT -> a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x1 (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ Set a
s1 Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
`S.difference` NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n2
Ordering
EQ -> Set a
s1 Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
`S.difference` Set a
s2
Ordering
GT -> NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n1 Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
`S.difference` Set a
s2
{-# INLINE difference #-}
(\\)
:: Ord a
=> NESet a
-> NESet a
-> Set a
\\ :: forall a. Ord a => NESet a -> NESet a -> Set a
(\\) = NESet a -> NESet a -> Set a
forall a. Ord a => NESet a -> NESet a -> Set a
difference
{-# INLINE (\\) #-}
intersection
:: Ord a
=> NESet a
-> NESet a
-> Set a
intersection :: forall a. Ord a => NESet a -> NESet a -> Set a
intersection n1 :: NESet a
n1@(NESet a
x1 Set a
s1) n2 :: NESet a
n2@(NESet a
x2 Set a
s2) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x1 a
x2 of
Ordering
LT -> Set a
s1 Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
`S.intersection` NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n2
Ordering
EQ -> a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x1 (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ Set a
s1 Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
`S.intersection` Set a
s2
Ordering
GT -> NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n1 Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
`S.intersection` Set a
s2
{-# INLINE intersection #-}
cartesianProduct
:: NESet a
-> NESet b
-> NESet (a, b)
cartesianProduct :: forall a b. NESet a -> NESet b -> NESet (a, b)
cartesianProduct NESet a
n1 NESet b
n2 = MergeNESet (a, b) -> NESet (a, b)
forall a. MergeNESet a -> NESet a
getMergeNESet
(MergeNESet (a, b) -> NESet (a, b))
-> (NESet a -> MergeNESet (a, b)) -> NESet a -> NESet (a, b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> MergeNESet (a, b)) -> NESet a -> MergeNESet (a, b)
forall m a. Semigroup m => (a -> m) -> NESet a -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
F1.foldMap1 (\a
x -> NESet (a, b) -> MergeNESet (a, b)
forall a. NESet a -> MergeNESet a
MergeNESet (NESet (a, b) -> MergeNESet (a, b))
-> NESet (a, b) -> MergeNESet (a, b)
forall a b. (a -> b) -> a -> b
$ (b -> (a, b)) -> NESet b -> NESet (a, b)
forall a b. (a -> b) -> NESet a -> NESet b
mapMonotonic (a
x,) NESet b
n2)
(NESet a -> NESet (a, b)) -> NESet a -> NESet (a, b)
forall a b. (a -> b) -> a -> b
$ NESet a
n1
{-# INLINE cartesianProduct #-}
disjointUnion
:: NESet a
-> NESet b
-> NESet (Either a b)
disjointUnion :: forall a b. NESet a -> NESet b -> NESet (Either a b)
disjointUnion (NESet a
x1 Set a
s1) NESet b
n2 = Either a b -> Set (Either a b) -> NESet (Either a b)
forall a. a -> Set a -> NESet a
NESet (a -> Either a b
forall a b. a -> Either a b
Left a
x1)
(Set a
s1 Set a -> Set b -> Set (Either a b)
forall a b. Set a -> Set b -> Set (Either a b)
`disjointUnionSet` NESet b -> Set b
forall a. NESet a -> Set a
toSet NESet b
n2)
{-# INLINE disjointUnion #-}
filter
:: (a -> Bool)
-> NESet a
-> Set a
filter :: forall a. (a -> Bool) -> NESet a -> Set a
filter a -> Bool
f (NESet a
x Set a
s1)
| a -> Bool
f a
x = a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x (Set a -> Set a) -> (Set a -> Set a) -> Set a -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> Set a -> Set a
forall a. (a -> Bool) -> Set a -> Set a
S.filter a -> Bool
f (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ Set a
s1
| Bool
otherwise = (a -> Bool) -> Set a -> Set a
forall a. (a -> Bool) -> Set a -> Set a
S.filter a -> Bool
f Set a
s1
{-# INLINE filter #-}
takeWhileAntitone
:: (a -> Bool)
-> NESet a
-> Set a
takeWhileAntitone :: forall a. (a -> Bool) -> NESet a -> Set a
takeWhileAntitone a -> Bool
f (NESet a
x Set a
s)
| a -> Bool
f a
x = a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x (Set a -> Set a) -> (Set a -> Set a) -> Set a -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> Set a -> Set a
forall a. (a -> Bool) -> Set a -> Set a
S.takeWhileAntitone a -> Bool
f (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ Set a
s
| Bool
otherwise = Set a
forall a. Set a
S.empty
{-# INLINE takeWhileAntitone #-}
dropWhileAntitone
:: (a -> Bool)
-> NESet a
-> Set a
dropWhileAntitone :: forall a. (a -> Bool) -> NESet a -> Set a
dropWhileAntitone a -> Bool
f n :: NESet a
n@(NESet a
x Set a
s)
| a -> Bool
f a
x = (a -> Bool) -> Set a -> Set a
forall a. (a -> Bool) -> Set a -> Set a
S.dropWhileAntitone a -> Bool
f Set a
s
| Bool
otherwise = NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n
{-# INLINE dropWhileAntitone #-}
spanAntitone
:: (a -> Bool)
-> NESet a
-> These (NESet a) (NESet a)
spanAntitone :: forall a. (a -> Bool) -> NESet a -> These (NESet a) (NESet a)
spanAntitone a -> Bool
f n :: NESet a
n@(NESet a
x Set a
s0)
| a -> Bool
f a
x = case (Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s1, Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s2) of
(Maybe (NESet a)
Nothing, Maybe (NESet a)
Nothing) -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This NESet a
n
(Just NESet a
_ , Maybe (NESet a)
Nothing) -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This NESet a
n
(Maybe (NESet a)
Nothing, Just NESet a
n2) -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> NESet a
forall a. a -> NESet a
singleton a
x) NESet a
n2
(Just NESet a
_ , Just NESet a
n2) -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x Set a
s1) NESet a
n2
| Bool
otherwise = NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That NESet a
n
where
(Set a
s1, Set a
s2) = (a -> Bool) -> Set a -> (Set a, Set a)
forall a. (a -> Bool) -> Set a -> (Set a, Set a)
S.spanAntitone a -> Bool
f Set a
s0
{-# INLINABLE spanAntitone #-}
partition
:: (a -> Bool)
-> NESet a
-> These (NESet a) (NESet a)
partition :: forall a. (a -> Bool) -> NESet a -> These (NESet a) (NESet a)
partition a -> Bool
f n :: NESet a
n@(NESet a
x Set a
s0) = case (Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s1, Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s2) of
(Maybe (NESet a)
Nothing, Maybe (NESet a)
Nothing)
| a -> Bool
f a
x -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This NESet a
n
| Bool
otherwise -> NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That NESet a
n
(Just NESet a
n1, Maybe (NESet a)
Nothing)
| a -> Bool
f a
x -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This NESet a
n
| Bool
otherwise -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These NESet a
n1 (a -> NESet a
forall a. a -> NESet a
singleton a
x)
(Maybe (NESet a)
Nothing, Just NESet a
n2)
| a -> Bool
f a
x -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> NESet a
forall a. a -> NESet a
singleton a
x) NESet a
n2
| Bool
otherwise -> NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That NESet a
n
(Just NESet a
n1, Just NESet a
n2)
| a -> Bool
f a
x -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x Set a
s1) NESet a
n2
| Bool
otherwise -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These NESet a
n1 (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x Set a
s2)
where
(Set a
s1, Set a
s2) = (a -> Bool) -> Set a -> (Set a, Set a)
forall a. (a -> Bool) -> Set a -> (Set a, Set a)
S.partition a -> Bool
f Set a
s0
{-# INLINABLE partition #-}
split
:: Ord a
=> a
-> NESet a
-> Maybe (These (NESet a) (NESet a))
split :: forall a.
Ord a =>
a -> NESet a -> Maybe (These (NESet a) (NESet a))
split a
x n :: NESet a
n@(NESet a
x0 Set a
s0) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That NESet a
n
Ordering
EQ -> NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That (NESet a -> These (NESet a) (NESet a))
-> Maybe (NESet a) -> Maybe (These (NESet a) (NESet a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s0
Ordering
GT -> case (Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s1, Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s2) of
(Maybe (NESet a)
Nothing, Maybe (NESet a)
Nothing) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This (a -> NESet a
forall a. a -> NESet a
singleton a
x0)
(Just NESet a
_ , Maybe (NESet a)
Nothing) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x0 Set a
s1)
(Maybe (NESet a)
Nothing, Just NESet a
n2) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> NESet a
forall a. a -> NESet a
singleton a
x0) NESet a
n2
(Just NESet a
_ , Just NESet a
n2) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x0 Set a
s1) NESet a
n2
where
(Set a
s1, Set a
s2) = a -> Set a -> (Set a, Set a)
forall a. Ord a => a -> Set a -> (Set a, Set a)
S.split a
x Set a
s0
{-# INLINABLE split #-}
splitMember
:: Ord a
=> a
-> NESet a
-> (Bool, Maybe (These (NESet a) (NESet a)))
splitMember :: forall a.
Ord a =>
a -> NESet a -> (Bool, Maybe (These (NESet a) (NESet a)))
splitMember a
x n :: NESet a
n@(NESet a
x0 Set a
s0) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> (Bool
False, These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That NESet a
n)
Ordering
EQ -> (Bool
True , NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That (NESet a -> These (NESet a) (NESet a))
-> Maybe (NESet a) -> Maybe (These (NESet a) (NESet a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s0)
Ordering
GT -> (Bool
mem ,) (Maybe (These (NESet a) (NESet a))
-> (Bool, Maybe (These (NESet a) (NESet a))))
-> Maybe (These (NESet a) (NESet a))
-> (Bool, Maybe (These (NESet a) (NESet a)))
forall a b. (a -> b) -> a -> b
$ case (Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s1, Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s2) of
(Maybe (NESet a)
Nothing, Maybe (NESet a)
Nothing) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This (a -> NESet a
forall a. a -> NESet a
singleton a
x0)
(Just NESet a
_ , Maybe (NESet a)
Nothing) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x0 Set a
s1)
(Maybe (NESet a)
Nothing, Just NESet a
n2) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> NESet a
forall a. a -> NESet a
singleton a
x0) NESet a
n2
(Just NESet a
_ , Just NESet a
n2) -> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a. a -> Maybe a
Just (These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a)))
-> These (NESet a) (NESet a) -> Maybe (These (NESet a) (NESet a))
forall a b. (a -> b) -> a -> b
$ NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x0 Set a
s1) NESet a
n2
where
(Set a
s1, Bool
mem, Set a
s2) = a -> Set a -> (Set a, Bool, Set a)
forall a. Ord a => a -> Set a -> (Set a, Bool, Set a)
S.splitMember a
x Set a
s0
{-# INLINABLE splitMember #-}
splitRoot
:: NESet a
-> NonEmpty (NESet a)
splitRoot :: forall a. NESet a -> NonEmpty (NESet a)
splitRoot (NESet a
x Set a
s) = a -> NESet a
forall a. a -> NESet a
singleton a
x
NESet a -> [NESet a] -> NonEmpty (NESet a)
forall a. a -> [a] -> NonEmpty a
:| (Set a -> Maybe (NESet a)) -> [Set a] -> [NESet a]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet (Set a -> [Set a]
forall a. Set a -> [Set a]
S.splitRoot Set a
s)
{-# INLINE splitRoot #-}
lookupIndex
:: Ord a
=> a
-> NESet a
-> Maybe Int
lookupIndex :: forall a. Ord a => a -> NESet a -> Maybe Int
lookupIndex a
x (NESet a
x0 Set a
s) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
x a
x0 of
Ordering
LT -> Maybe Int
forall a. Maybe a
Nothing
Ordering
EQ -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
Ordering
GT -> (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 -> Set a -> Maybe Int
forall a. Ord a => a -> Set a -> Maybe Int
S.lookupIndex a
x Set a
s
{-# INLINE lookupIndex #-}
findIndex
:: Ord a
=> a
-> NESet a
-> Int
findIndex :: forall a. Ord a => a -> NESet a -> Int
findIndex a
k = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
forall {a}. a
e (Maybe Int -> Int) -> (NESet a -> Maybe Int) -> NESet a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> NESet a -> Maybe Int
forall a. Ord a => a -> NESet a -> Maybe Int
lookupIndex a
k
where
e :: a
e = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"NESet.findIndex: element is not in the set"
{-# INLINE findIndex #-}
elemAt
:: Int
-> NESet a
-> a
elemAt :: forall a. Int -> NESet a -> a
elemAt Int
0 (NESet a
x Set a
_) = a
x
elemAt Int
i (NESet a
_ Set a
s) = Int -> Set a -> a
forall a. Int -> Set a -> a
S.elemAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Set a
s
{-# INLINE elemAt #-}
deleteAt
:: Int
-> NESet a
-> Set a
deleteAt :: forall a. Int -> NESet a -> Set a
deleteAt Int
0 (NESet a
_ Set a
s) = Set a
s
deleteAt Int
i (NESet a
x Set a
s) = a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x (Set a -> Set a) -> (Set a -> Set a) -> Set a -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Set a -> Set a
forall a. Int -> Set a -> Set a
S.deleteAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINABLE deleteAt #-}
take
:: Int
-> NESet a
-> Set a
take :: forall a. Int -> NESet a -> Set a
take Int
0 (NESet a
_ Set a
_) = Set a
forall a. Set a
S.empty
take Int
i (NESet a
x Set a
s) = a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x (Set a -> Set a) -> (Set a -> Set a) -> Set a -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Set a -> Set a
forall a. Int -> Set a -> Set a
S.take (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Set a -> Set a) -> Set a -> Set a
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINABLE take #-}
drop
:: Int
-> NESet a
-> Set a
drop :: forall a. Int -> NESet a -> Set a
drop Int
0 NESet a
n = NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n
drop Int
n (NESet a
_ Set a
s) = Int -> Set a -> Set a
forall a. Int -> Set a -> Set a
S.drop (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Set a
s
{-# INLINABLE drop #-}
splitAt
:: Int
-> NESet a
-> These (NESet a) (NESet a)
splitAt :: forall a. Int -> NESet a -> These (NESet a) (NESet a)
splitAt Int
0 NESet a
n = NESet a -> These (NESet a) (NESet a)
forall a b. b -> These a b
That NESet a
n
splitAt Int
i n :: NESet a
n@(NESet a
x Set a
s0) = case (Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s1, Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet Set a
s2) of
(Maybe (NESet a)
Nothing, Maybe (NESet a)
Nothing) -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This (a -> NESet a
forall a. a -> NESet a
singleton a
x)
(Just NESet a
_ , Maybe (NESet a)
Nothing) -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> These a b
This NESet a
n
(Maybe (NESet a)
Nothing, Just NESet a
n2) -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> NESet a
forall a. a -> NESet a
singleton a
x) NESet a
n2
(Just NESet a
_ , Just NESet a
n2) -> NESet a -> NESet a -> These (NESet a) (NESet a)
forall a b. a -> b -> These a b
These (a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
insertSetMin a
x Set a
s1) NESet a
n2
where
(Set a
s1, Set a
s2) = Int -> Set a -> (Set a, Set a)
forall a. Int -> Set a -> (Set a, Set a)
S.splitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Set a
s0
{-# INLINABLE splitAt #-}
map :: Ord b
=> (a -> b)
-> NESet a
-> NESet b
map :: forall b a. Ord b => (a -> b) -> NESet a -> NESet b
map a -> b
f (NESet a
x0 Set a
s) = NonEmpty b -> NESet b
forall a. Ord a => NonEmpty a -> NESet a
fromList
(NonEmpty b -> NESet b)
-> (Set a -> NonEmpty b) -> Set a -> NESet b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b
f a
x0 b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
:|)
([b] -> NonEmpty b) -> (Set a -> [b]) -> Set a -> NonEmpty b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> [b] -> [b]) -> [b] -> Set a -> [b]
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr (\a
x [b]
xs -> a -> b
f a
x b -> [b] -> [b]
forall a. a -> [a] -> [a]
: [b]
xs) []
(Set a -> NESet b) -> Set a -> NESet b
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINE map #-}
mapMonotonic
:: (a -> b)
-> NESet a
-> NESet b
mapMonotonic :: forall a b. (a -> b) -> NESet a -> NESet b
mapMonotonic a -> b
f (NESet a
x Set a
s) = b -> Set b -> NESet b
forall a. a -> Set a -> NESet a
NESet (a -> b
f a
x) ((a -> b) -> Set a -> Set b
forall a b. (a -> b) -> Set a -> Set b
S.mapMonotonic a -> b
f Set a
s)
{-# INLINE mapMonotonic #-}
foldr1' :: (a -> a -> a) -> NESet a -> a
foldr1' :: forall a. (a -> a -> a) -> NESet a -> a
foldr1' a -> a -> a
f (NESet a
x Set a
s) = case Set a -> Maybe (a, Set a)
forall a. Set a -> Maybe (a, Set a)
S.maxView Set a
s of
Maybe (a, Set a)
Nothing -> a
x
Just (a
y, Set a
s') -> let !z :: a
z = (a -> a -> a) -> a -> Set a -> a
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr' a -> a -> a
f a
y Set a
s' in a
x a -> a -> a
`f` a
z
{-# INLINE foldr1' #-}
foldl1' :: (a -> a -> a) -> NESet a -> a
foldl1' :: forall a. (a -> a -> a) -> NESet a -> a
foldl1' a -> a -> a
f (NESet a
x Set a
s) = (a -> a -> a) -> a -> Set a -> a
forall a b. (a -> b -> a) -> a -> Set b -> a
S.foldl' a -> a -> a
f a
x Set a
s
{-# INLINE foldl1' #-}
findMin :: NESet a -> a
findMin :: forall a. NESet a -> a
findMin (NESet a
x Set a
_) = a
x
{-# INLINE findMin #-}
findMax :: NESet a -> a
findMax :: forall a. NESet a -> a
findMax (NESet a
x Set a
s) = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
x (Maybe a -> a) -> (Set a -> Maybe a) -> Set a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> Maybe a
forall a. Set a -> Maybe a
S.lookupMax (Set a -> a) -> Set a -> a
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINE findMax #-}
deleteMin :: NESet a -> Set a
deleteMin :: forall a. NESet a -> Set a
deleteMin (NESet a
_ Set a
s) = Set a
s
{-# INLINE deleteMin #-}
deleteMax :: NESet a -> Set a
deleteMax :: forall a. NESet a -> Set a
deleteMax (NESet a
x Set a
s) = case Set a -> Maybe (a, Set a)
forall a. Set a -> Maybe (a, Set a)
S.maxView Set a
s of
Maybe (a, Set a)
Nothing -> Set a
forall a. Set a
S.empty
Just (a
_, Set a
s') -> a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x Set a
s'
{-# INLINE deleteMax #-}
deleteFindMin :: NESet a -> (a, Set a)
deleteFindMin :: forall a. NESet a -> (a, Set a)
deleteFindMin (NESet a
x Set a
s) = (a
x, Set a
s)
{-# INLINE deleteFindMin #-}
deleteFindMax :: NESet a -> (a, Set a)
deleteFindMax :: forall a. NESet a -> (a, Set a)
deleteFindMax (NESet a
x Set a
s) = (a, Set a)
-> ((a, Set a) -> (a, Set a)) -> Maybe (a, Set a) -> (a, Set a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (a
x, Set a
forall a. Set a
S.empty) ((Set a -> Set a) -> (a, Set a) -> (a, Set a)
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 (a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x))
(Maybe (a, Set a) -> (a, Set a))
-> (Set a -> Maybe (a, Set a)) -> Set a -> (a, Set a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> Maybe (a, Set a)
forall a. Set a -> Maybe (a, Set a)
S.maxView
(Set a -> (a, Set a)) -> Set a -> (a, Set a)
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINE deleteFindMax #-}
elems :: NESet a -> NonEmpty a
elems :: forall a. NESet a -> NonEmpty a
elems = NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
{-# INLINE elems #-}
toAscList :: NESet a -> NonEmpty a
toAscList :: forall a. NESet a -> NonEmpty a
toAscList = NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
{-# INLINE toAscList #-}
toDescList :: NESet a -> NonEmpty a
toDescList :: forall a. NESet a -> NonEmpty a
toDescList (NESet a
x Set a
s) = (NonEmpty a -> a -> NonEmpty a)
-> NonEmpty a -> Set a -> NonEmpty a
forall a b. (a -> b -> a) -> a -> Set b -> a
S.foldl' ((a -> NonEmpty a -> NonEmpty a) -> NonEmpty a -> a -> NonEmpty a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> NonEmpty a -> NonEmpty a
forall a. a -> NonEmpty a -> NonEmpty a
(NE.<|)) (a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| []) Set a
s
{-# INLINE toDescList #-}
combineEq :: Eq a => NonEmpty a -> NonEmpty a
combineEq :: forall a. Eq a => NonEmpty a -> NonEmpty a
combineEq (a
x :| [a]
xs) = a -> [a] -> NonEmpty a
forall {t}. Eq t => t -> [t] -> NonEmpty t
go a
x [a]
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