{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_HADDOCK not-home #-}
module Data.Set.NonEmpty.Internal (
NESet(..)
, nonEmptySet
, withNonEmpty
, toSet
, singleton
, fromList
, toList
, size
, union
, unions
, foldr
, foldl
, foldr'
, foldl'
, MergeNESet(..)
, merge
, valid
, insertMinSet
, insertMaxSet
, disjointSet
, powerSetSet
, disjointUnionSet
, cartesianProductSet
) where
import Control.DeepSeq
import Control.Monad
import Data.Data
import Data.Function
import Data.Functor.Classes
import Data.List.NonEmpty (NonEmpty(..))
import Data.Semigroup
import Data.Semigroup.Foldable (Foldable1)
import Data.Set.Internal (Set(..))
import Prelude hiding (foldr, foldr1, foldl, foldl1)
import Text.Read
import qualified Data.Aeson as A
import qualified Data.Foldable as F
import qualified Data.Semigroup.Foldable as F1
import qualified Data.Set as S
import qualified Data.Set.Internal as S
#if !MIN_VERSION_containers(0,5,11)
import Utils.Containers.Internal.StrictPair
#endif
data NESet a =
NESet { NESet a -> a
nesV0 :: !a
, NESet a -> Set a
nesSet :: !(Set a)
}
deriving (Typeable)
instance Eq a => Eq (NESet a) where
NESet a
t1 == :: NESet a -> NESet a -> Bool
== NESet a
t2 = Set a -> Int
forall a. Set a -> Int
S.size (NESet a -> Set a
forall a. NESet a -> Set a
nesSet NESet a
t1) Int -> Int -> Bool
forall a. Eq 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
t2)
Bool -> Bool -> Bool
&& NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList NESet a
t1 NonEmpty a -> NonEmpty a -> Bool
forall a. Eq a => a -> a -> Bool
== NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList NESet a
t2
instance Ord a => Ord (NESet a) where
compare :: NESet a -> NESet a -> Ordering
compare = NonEmpty a -> NonEmpty a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (NonEmpty a -> NonEmpty a -> Ordering)
-> (NESet a -> NonEmpty a) -> NESet a -> NESet a -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
< :: NESet a -> NESet a -> Bool
(<) = NonEmpty a -> NonEmpty a -> Bool
forall a. Ord a => a -> a -> Bool
(<) (NonEmpty a -> NonEmpty a -> Bool)
-> (NESet a -> NonEmpty a) -> NESet a -> NESet a -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
> :: NESet a -> NESet a -> Bool
(>) = NonEmpty a -> NonEmpty a -> Bool
forall a. Ord a => a -> a -> Bool
(>) (NonEmpty a -> NonEmpty a -> Bool)
-> (NESet a -> NonEmpty a) -> NESet a -> NESet a -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
<= :: NESet a -> NESet a -> Bool
(<=) = NonEmpty a -> NonEmpty a -> Bool
forall a. Ord a => a -> a -> Bool
(<=) (NonEmpty a -> NonEmpty a -> Bool)
-> (NESet a -> NonEmpty a) -> NESet a -> NESet a -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
>= :: NESet a -> NESet a -> Bool
(>=) = NonEmpty a -> NonEmpty a -> Bool
forall a. Ord a => a -> a -> Bool
(>=) (NonEmpty a -> NonEmpty a -> Bool)
-> (NESet a -> NonEmpty a) -> NESet a -> NESet a -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
instance Show a => Show (NESet a) where
showsPrec :: Int -> NESet a -> ShowS
showsPrec Int
p NESet a
xs = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"fromList (" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty a -> ShowS
forall a. Show a => a -> ShowS
shows (NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList NESet a
xs) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
")"
instance (Read a, Ord a) => Read (NESet a) where
readPrec :: ReadPrec (NESet a)
readPrec = ReadPrec (NESet a) -> ReadPrec (NESet a)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (NESet a) -> ReadPrec (NESet a))
-> ReadPrec (NESet a) -> ReadPrec (NESet a)
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec (NESet a) -> ReadPrec (NESet a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec (NESet a) -> ReadPrec (NESet a))
-> ReadPrec (NESet a) -> ReadPrec (NESet a)
forall a b. (a -> b) -> a -> b
$ do
Ident String
"fromList" <- ReadPrec Lexeme
lexP
NonEmpty a
xs <- ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a))
-> (ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a))
-> ReadPrec (NonEmpty a)
-> ReadPrec (NonEmpty a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a))
-> ReadPrec (NonEmpty a) -> ReadPrec (NonEmpty a)
forall a b. (a -> b) -> a -> b
$ ReadPrec (NonEmpty a)
forall a. Read a => ReadPrec a
readPrec
NESet a -> ReadPrec (NESet a)
forall (m :: * -> *) a. Monad m => a -> m a
return (NonEmpty a -> NESet a
forall a. Ord a => NonEmpty a -> NESet a
fromList NonEmpty a
xs)
readListPrec :: ReadPrec [NESet a]
readListPrec = ReadPrec [NESet a]
forall a. Read a => ReadPrec [a]
readListPrecDefault
instance Eq1 NESet where
liftEq :: (a -> b -> Bool) -> NESet a -> NESet b -> Bool
liftEq a -> b -> Bool
eq NESet a
m NESet b
n =
NESet a -> Int
forall a. NESet a -> Int
size NESet a
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== NESet b -> Int
forall a. NESet a -> Int
size NESet b
n Bool -> Bool -> Bool
&& (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq (NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList NESet a
m) (NESet b -> NonEmpty b
forall a. NESet a -> NonEmpty a
toList NESet b
n)
instance Ord1 NESet where
liftCompare :: (a -> b -> Ordering) -> NESet a -> NESet b -> Ordering
liftCompare a -> b -> Ordering
cmp NESet a
m NESet b
n =
(a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp (NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList NESet a
m) (NESet b -> NonEmpty b
forall a. NESet a -> NonEmpty a
toList NESet b
n)
instance Show1 NESet where
liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NESet a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d NESet a
m =
(Int -> NonEmpty a -> ShowS)
-> String -> Int -> NonEmpty a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl) String
"fromList" Int
d (NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList NESet a
m)
instance NFData a => NFData (NESet a) where
rnf :: NESet a -> ()
rnf (NESet a
x Set a
s) = a -> ()
forall a. NFData a => a -> ()
rnf a
x () -> () -> ()
`seq` Set a -> ()
forall a. NFData a => a -> ()
rnf Set a
s
instance (Data a, Ord a) => Data (NESet a) where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NESet a -> c (NESet a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z NESet a
set = (NonEmpty a -> NESet a) -> c (NonEmpty a -> NESet a)
forall g. g -> c g
z NonEmpty a -> NESet a
forall a. Ord a => NonEmpty a -> NESet a
fromList c (NonEmpty a -> NESet a) -> NonEmpty a -> c (NESet a)
forall d b. Data d => c (d -> b) -> d -> c b
`f` NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList NESet a
set
toConstr :: NESet a -> Constr
toConstr NESet a
_ = Constr
fromListConstr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NESet a)
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
Int
1 -> c (NonEmpty a -> NESet a) -> c (NESet a)
forall b r. Data b => c (b -> r) -> c r
k ((NonEmpty a -> NESet a) -> c (NonEmpty a -> NESet a)
forall r. r -> c r
z NonEmpty a -> NESet a
forall a. Ord a => NonEmpty a -> NESet a
fromList)
Int
_ -> String -> c (NESet a)
forall a. HasCallStack => String -> a
error String
"gunfold"
dataTypeOf :: NESet a -> DataType
dataTypeOf NESet a
_ = DataType
setDataType
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (NESet a))
dataCast1 forall d. Data d => c (t d)
f = c (t a) -> Maybe (c (NESet a))
forall k1 k2 (c :: k1 -> *) (t :: k2 -> k1) (t' :: k2 -> k1)
(a :: k2).
(Typeable t, Typeable t') =>
c (t a) -> Maybe (c (t' a))
gcast1 c (t a)
forall d. Data d => c (t d)
f
fromListConstr :: Constr
fromListConstr :: Constr
fromListConstr = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
setDataType String
"fromList" [] Fixity
Prefix
setDataType :: DataType
setDataType :: DataType
setDataType = String -> [Constr] -> DataType
mkDataType String
"Data.Set.NonEmpty.Internal.NESet" [Constr
fromListConstr]
instance A.ToJSON a => A.ToJSON (NESet a) where
toJSON :: NESet a -> Value
toJSON = Set a -> Value
forall a. ToJSON a => a -> Value
A.toJSON (Set a -> Value) -> (NESet a -> Set a) -> NESet a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESet a -> Set a
forall a. NESet a -> Set a
toSet
toEncoding :: NESet a -> Encoding
toEncoding = Set a -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding (Set a -> Encoding) -> (NESet a -> Set a) -> NESet a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESet a -> Set a
forall a. NESet a -> Set a
toSet
instance (A.FromJSON a, Ord a) => A.FromJSON (NESet a) where
parseJSON :: Value -> Parser (NESet a)
parseJSON = Parser (NESet a)
-> (NESet a -> Parser (NESet a)) -> Set a -> Parser (NESet a)
forall r a. r -> (NESet a -> r) -> Set a -> r
withNonEmpty (String -> Parser (NESet a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err) NESet a -> Parser (NESet a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Set a -> Parser (NESet a))
-> (Value -> Parser (Set a)) -> Value -> Parser (NESet a)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Value -> Parser (Set a)
forall a. FromJSON a => Value -> Parser a
A.parseJSON
where
err :: String
err = String
"NESet: Non-empty set expected, but empty set found"
nonEmptySet :: Set a -> Maybe (NESet a)
nonEmptySet :: Set a -> Maybe (NESet a)
nonEmptySet = (((a, Set a) -> NESet a) -> Maybe (a, Set a) -> Maybe (NESet a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((a, Set a) -> NESet a) -> Maybe (a, Set a) -> Maybe (NESet a))
-> ((a -> Set a -> NESet a) -> (a, Set a) -> NESet a)
-> (a -> Set a -> NESet a)
-> Maybe (a, Set a)
-> Maybe (NESet a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Set a -> NESet a) -> (a, Set a) -> NESet a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry) a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet (Maybe (a, Set a) -> Maybe (NESet a))
-> (Set a -> Maybe (a, Set a)) -> Set a -> Maybe (NESet 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.minView
{-# INLINE nonEmptySet #-}
withNonEmpty
:: r
-> (NESet a -> r)
-> Set a
-> r
withNonEmpty :: r -> (NESet a -> r) -> Set a -> r
withNonEmpty r
def NESet a -> r
f = r -> (NESet a -> r) -> Maybe (NESet a) -> r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe r
def NESet a -> r
f (Maybe (NESet a) -> r) -> (Set a -> Maybe (NESet a)) -> Set a -> r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> Maybe (NESet a)
forall a. Set a -> Maybe (NESet a)
nonEmptySet
{-# INLINE withNonEmpty #-}
toSet :: NESet a -> Set a
toSet :: NESet a -> Set a
toSet (NESet a
x Set a
s) = a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x Set a
s
{-# INLINE toSet #-}
singleton :: a -> NESet a
singleton :: a -> NESet a
singleton a
x = a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x Set a
forall a. Set a
S.empty
{-# INLINE singleton #-}
fromList :: Ord a => NonEmpty a -> NESet a
fromList :: NonEmpty a -> NESet a
fromList (a
x :| [a]
s) = 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 -> NESet a
forall a. Semigroup a => a -> a -> a
<> a -> NESet a
forall a. a -> NESet a
singleton 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. Ord a => [a] -> Set a
S.fromList
([a] -> NESet a) -> [a] -> NESet a
forall a b. (a -> b) -> a -> b
$ [a]
s
{-# INLINE fromList #-}
toList :: NESet a -> NonEmpty a
toList :: NESet a -> NonEmpty a
toList (NESet a
x Set a
s) = a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| Set a -> [a]
forall a. Set a -> [a]
S.toList Set a
s
{-# INLINE toList #-}
size :: NESet a -> Int
size :: NESet a -> Int
size (NESet a
_ Set a
s) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Set a -> Int
forall a. Set a -> Int
S.size Set a
s
{-# INLINE size #-}
foldr :: (a -> b -> b) -> b -> NESet a -> b
foldr :: (a -> b -> b) -> b -> NESet a -> b
foldr a -> b -> b
f b
z (NESet a
x Set a
s) = a
x a -> b -> b
`f` (a -> b -> b) -> b -> Set a -> b
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr a -> b -> b
f b
z Set a
s
{-# INLINE foldr #-}
foldr' :: (a -> b -> b) -> b -> NESet a -> b
foldr' :: (a -> b -> b) -> b -> NESet a -> b
foldr' a -> b -> b
f b
z (NESet a
x Set a
s) = a
x a -> b -> b
`f` b
y
where
!y :: b
y = (a -> b -> b) -> b -> Set a -> b
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr' a -> b -> b
f b
z Set a
s
{-# INLINE foldr' #-}
foldr1 :: (a -> a -> a) -> NESet a -> a
foldr1 :: (a -> a -> a) -> NESet a -> a
foldr1 a -> a -> a
f (NESet a
x Set a
s) = a -> ((a, Set a) -> a) -> Maybe (a, Set a) -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
x (a -> a -> a
f a
x (a -> a) -> ((a, Set a) -> a) -> (a, Set a) -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Set a -> a) -> (a, Set a) -> a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((a -> a -> a) -> a -> Set a -> a
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr a -> a -> a
f))
(Maybe (a, Set a) -> a)
-> (Set a -> Maybe (a, Set a)) -> Set a -> 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 -> a
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINE foldr1 #-}
foldl :: (a -> b -> a) -> a -> NESet b -> a
foldl :: (a -> b -> a) -> a -> NESet b -> a
foldl a -> b -> a
f a
z (NESet b
x Set b
s) = (a -> b -> a) -> a -> Set b -> a
forall a b. (a -> b -> a) -> a -> Set b -> a
S.foldl a -> b -> a
f (a -> b -> a
f a
z b
x) Set b
s
{-# INLINE foldl #-}
foldl' :: (a -> b -> a) -> a -> NESet b -> a
foldl' :: (a -> b -> a) -> a -> NESet b -> a
foldl' a -> b -> a
f a
z (NESet b
x Set b
s) = (a -> b -> a) -> a -> Set b -> a
forall a b. (a -> b -> a) -> a -> Set b -> a
S.foldl' a -> b -> a
f a
y Set b
s
where
!y :: a
y = a -> b -> a
f a
z b
x
{-# INLINE foldl' #-}
foldl1 :: (a -> a -> a) -> NESet a -> a
foldl1 :: (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 #-}
union
:: Ord a
=> NESet a
-> NESet a
-> NESet a
union :: NESet a -> NESet a -> NESet a
union 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 -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x1 (Set a -> NESet a) -> (NESet a -> Set a) -> NESet a -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
S.union Set a
s1 (Set a -> Set a) -> (NESet a -> Set a) -> NESet a -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESet a -> Set a
forall a. NESet a -> Set a
toSet (NESet a -> NESet a) -> NESet a -> NESet a
forall a b. (a -> b) -> a -> b
$ NESet a
n2
Ordering
EQ -> a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x1 (Set a -> NESet a) -> (Set a -> Set a) -> Set a -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
S.union Set a
s1 (Set a -> NESet a) -> Set a -> NESet a
forall a b. (a -> b) -> a -> b
$ Set a
s2
Ordering
GT -> a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x2 (Set a -> NESet a) -> (Set a -> Set a) -> Set a -> NESet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> Set a -> Set a
forall a. Ord a => Set a -> Set a -> Set a
S.union (NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n1) (Set a -> NESet a) -> Set a -> NESet a
forall a b. (a -> b) -> a -> b
$ Set a
s2
{-# INLINE union #-}
unions
:: (Foldable1 f, Ord a)
=> f (NESet a)
-> NESet a
unions :: f (NESet a) -> NESet a
unions (f (NESet a) -> NonEmpty (NESet a)
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
F1.toNonEmpty->(NESet a
s :| [NESet a]
ss)) = (NESet a -> NESet a -> NESet a) -> NESet a -> [NESet a] -> NESet a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' NESet a -> NESet a -> NESet a
forall a. Ord a => NESet a -> NESet a -> NESet a
union NESet a
s [NESet a]
ss
{-# INLINE unions #-}
instance Ord a => Semigroup (NESet a) where
<> :: NESet a -> NESet a -> NESet a
(<>) = NESet a -> NESet a -> NESet a
forall a. Ord a => NESet a -> NESet a -> NESet a
union
{-# INLINE (<>) #-}
sconcat :: NonEmpty (NESet a) -> NESet a
sconcat = NonEmpty (NESet a) -> NESet a
forall (f :: * -> *) a.
(Foldable1 f, Ord a) =>
f (NESet a) -> NESet a
unions
{-# INLINE sconcat #-}
instance Foldable NESet where
#if MIN_VERSION_base(4,11,0)
fold :: NESet m -> m
fold (NESet m
x Set m
s) = m
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> Set m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
F.fold Set m
s
{-# INLINE fold #-}
foldMap :: (a -> m) -> NESet a -> m
foldMap a -> m
f (NESet a
x Set a
s) = a -> m
f a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (a -> m) -> Set a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f Set a
s
{-# INLINE foldMap #-}
#else
fold (NESet x s) = x `mappend` F.fold s
{-# INLINE fold #-}
foldMap f (NESet x s) = f x `mappend` foldMap f s
{-# INLINE foldMap #-}
#endif
foldr :: (a -> b -> b) -> b -> NESet a -> b
foldr = (a -> b -> b) -> b -> NESet a -> b
forall a b. (a -> b -> b) -> b -> NESet a -> b
foldr
{-# INLINE foldr #-}
foldr' :: (a -> b -> b) -> b -> NESet a -> b
foldr' = (a -> b -> b) -> b -> NESet a -> b
forall a b. (a -> b -> b) -> b -> NESet a -> b
foldr'
{-# INLINE foldr' #-}
foldr1 :: (a -> a -> a) -> NESet a -> a
foldr1 = (a -> a -> a) -> NESet a -> a
forall a. (a -> a -> a) -> NESet a -> a
foldr1
{-# INLINE foldr1 #-}
foldl :: (b -> a -> b) -> b -> NESet a -> b
foldl = (b -> a -> b) -> b -> NESet a -> b
forall b a. (b -> a -> b) -> b -> NESet a -> b
foldl
{-# INLINE foldl #-}
foldl' :: (b -> a -> b) -> b -> NESet a -> b
foldl' = (b -> a -> b) -> b -> NESet a -> b
forall b a. (b -> a -> b) -> b -> NESet a -> b
foldl'
{-# INLINE foldl' #-}
foldl1 :: (a -> a -> a) -> NESet a -> a
foldl1 = (a -> a -> a) -> NESet a -> a
forall a. (a -> a -> a) -> NESet a -> a
foldl1
{-# INLINE foldl1 #-}
null :: NESet a -> Bool
null NESet a
_ = Bool
False
{-# INLINE null #-}
length :: NESet a -> Int
length = NESet a -> Int
forall a. NESet a -> Int
size
{-# INLINE length #-}
elem :: a -> NESet a -> Bool
elem a
x (NESet a
x0 Set a
s) = a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
F.elem a
x Set a
s
Bool -> Bool -> Bool
|| a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x0
{-# INLINE elem #-}
minimum :: NESet a -> a
minimum (NESet a
x Set a
_) = a
x
{-# INLINE minimum #-}
maximum :: NESet a -> a
maximum (NESet a
x Set a
s) = a -> ((a, Set a) -> a) -> Maybe (a, Set a) -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
x (a, Set a) -> a
forall a b. (a, b) -> a
fst (Maybe (a, Set a) -> a)
-> (Set a -> Maybe (a, Set a)) -> Set a -> 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 -> a
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINE maximum #-}
toList :: NESet a -> [a]
toList = NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList (NonEmpty a -> [a]) -> (NESet a -> NonEmpty a) -> NESet a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
{-# INLINE toList #-}
instance Foldable1 NESet where
#if MIN_VERSION_base(4,11,0)
fold1 :: NESet m -> m
fold1 (NESet m
x Set m
s) = m -> (m -> m) -> Maybe m -> m
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m
x (m
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<>)
(Maybe m -> m) -> (Set m -> Maybe m) -> Set m -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (m -> Maybe m) -> Set m -> Maybe m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap m -> Maybe m
forall a. a -> Maybe a
Just
(Set m -> m) -> Set m -> m
forall a b. (a -> b) -> a -> b
$ Set m
s
{-# INLINE fold1 #-}
foldMap1 :: (a -> m) -> NESet a -> m
foldMap1 a -> m
f (NESet a
x Set a
s) = m -> (m -> m) -> Maybe m -> m
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (a -> m
f a
x) (a -> m
f a
x m -> m -> m
forall a. Semigroup a => a -> a -> a
<>)
(Maybe m -> m) -> (Set a -> Maybe m) -> Set a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Maybe m) -> Set a -> Maybe m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap (m -> Maybe m
forall a. a -> Maybe a
Just (m -> Maybe m) -> (a -> m) -> a -> Maybe m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> m
f)
(Set a -> m) -> Set a -> m
forall a b. (a -> b) -> a -> b
$ Set a
s
{-# INLINE foldMap1 #-}
#else
fold1 (NESet x s) = option x (x <>)
. F.foldMap (Option . Just)
$ s
{-# INLINE fold1 #-}
foldMap1 f (NESet x s) = option (f x) (f x <>)
. F.foldMap (Option . Just . f)
$ s
{-# INLINE foldMap1 #-}
#endif
toNonEmpty :: NESet a -> NonEmpty a
toNonEmpty = NESet a -> NonEmpty a
forall a. NESet a -> NonEmpty a
toList
{-# INLINE toNonEmpty #-}
newtype MergeNESet a = MergeNESet { MergeNESet a -> NESet a
getMergeNESet :: NESet a }
instance Semigroup (MergeNESet a) where
MergeNESet NESet a
n1 <> :: MergeNESet a -> MergeNESet a -> MergeNESet a
<> MergeNESet NESet a
n2 = NESet a -> MergeNESet a
forall a. NESet a -> MergeNESet a
MergeNESet (NESet a -> NESet a -> NESet a
forall a. NESet a -> NESet a -> NESet a
merge NESet a
n1 NESet a
n2)
{-# INLINE (<>) #-}
merge :: NESet a -> NESet a -> NESet a
merge :: NESet a -> NESet a -> NESet a
merge (NESet a
x1 Set a
s1) NESet a
n2 = a -> Set a -> NESet a
forall a. a -> Set a -> NESet a
NESet a
x1 (Set a -> NESet a) -> Set a -> NESet a
forall a b. (a -> b) -> a -> b
$ Set a
s1 Set a -> Set a -> Set a
forall a. Set a -> Set a -> Set a
`S.merge` NESet a -> Set a
forall a. NESet a -> Set a
toSet NESet a
n2
valid :: Ord a => NESet a -> Bool
valid :: NESet a -> Bool
valid (NESet a
x Set a
s) = Set a -> Bool
forall a. Ord a => Set a -> Bool
S.valid Set a
s
Bool -> Bool -> Bool
&& ((a, Set a) -> Bool) -> Maybe (a, Set a) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<) (a -> Bool) -> ((a, Set a) -> a) -> (a, Set a) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, Set a) -> a
forall a b. (a, b) -> a
fst) (Set a -> Maybe (a, Set a)
forall a. Set a -> Maybe (a, Set a)
S.minView Set a
s)
insertMinSet :: a -> Set a -> Set a
insertMinSet :: a -> Set a -> Set a
insertMinSet a
x = \case
Set a
Tip -> a -> Set a
forall a. a -> Set a
S.singleton a
x
Bin Int
_ a
y Set a
l Set a
r -> a -> Set a -> Set a -> Set a
forall a. a -> Set a -> Set a -> Set a
balanceL a
y (a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMinSet a
x Set a
l) Set a
r
{-# INLINABLE insertMinSet #-}
insertMaxSet :: a -> Set a -> Set a
insertMaxSet :: a -> Set a -> Set a
insertMaxSet a
x = \case
Set a
Tip -> a -> Set a
forall a. a -> Set a
S.singleton a
x
Bin Int
_ a
y Set a
l Set a
r -> a -> Set a -> Set a -> Set a
forall a. a -> Set a -> Set a -> Set a
balanceR a
y Set a
l (a -> Set a -> Set a
forall a. a -> Set a -> Set a
insertMaxSet a
x Set a
r)
{-# INLINABLE insertMaxSet #-}
disjointSet :: Ord a => Set a -> Set a -> Bool
#if MIN_VERSION_containers(0,5,11)
disjointSet :: Set a -> Set a -> Bool
disjointSet = Set a -> Set a -> Bool
forall a. Ord a => Set a -> Set a -> Bool
S.disjoint
#else
disjointSet xs = S.null . S.intersection xs
#endif
{-# INLINE disjointSet #-}
powerSetSet :: Set a -> Set (Set a)
#if MIN_VERSION_containers(0,5,11)
powerSetSet :: Set a -> Set (Set a)
powerSetSet = Set a -> Set (Set a)
forall a. Set a -> Set (Set a)
S.powerSet
{-# INLINE powerSetSet #-}
#else
powerSetSet xs0 = insertMinSet S.empty (S.foldr' step' Tip xs0) where
step' x pxs = insertMinSet (S.singleton x) (insertMinSet x `S.mapMonotonic` pxs) `glue` pxs
{-# INLINABLE powerSetSet #-}
minViewSure :: a -> Set a -> Set a -> StrictPair a (Set a)
minViewSure = go
where
go x Tip r = x :*: r
go x (Bin _ xl ll lr) r =
case go xl ll lr of
xm :*: l' -> xm :*: balanceR x l' r
maxViewSure :: a -> Set a -> Set a -> StrictPair a (Set a)
maxViewSure = go
where
go x l Tip = x :*: l
go x l (Bin _ xr rl rr) =
case go xr rl rr of
xm :*: r' -> xm :*: balanceL x l r'
glue :: Set a -> Set a -> Set a
glue Tip r = r
glue l Tip = l
glue l@(Bin sl xl ll lr) r@(Bin sr xr rl rr)
| sl > sr = let !(m :*: l') = maxViewSure xl ll lr in balanceR m l' r
| otherwise = let !(m :*: r') = minViewSure xr rl rr in balanceL m l r'
#endif
disjointUnionSet :: Set a -> Set b -> Set (Either a b)
#if MIN_VERSION_containers(0,5,11)
disjointUnionSet :: Set a -> Set b -> Set (Either a b)
disjointUnionSet = Set a -> Set b -> Set (Either a b)
forall a b. Set a -> Set b -> Set (Either a b)
S.disjointUnion
#else
disjointUnionSet as bs = S.merge (S.mapMonotonic Left as) (S.mapMonotonic Right bs)
#endif
{-# INLINE disjointUnionSet #-}
cartesianProductSet :: Set a -> Set b -> Set (a, b)
#if MIN_VERSION_containers(0,5,11)
cartesianProductSet :: Set a -> Set b -> Set (a, b)
cartesianProductSet = Set a -> Set b -> Set (a, b)
forall a b. Set a -> Set b -> Set (a, b)
S.cartesianProduct
#else
cartesianProductSet as bs =
getMergeSet $ foldMap (\a -> MergeSet $ S.mapMonotonic ((,) a) bs) as
newtype MergeSet a = MergeSet { getMergeSet :: Set a }
instance Semigroup (MergeSet a) where
MergeSet xs <> MergeSet ys = MergeSet (S.merge xs ys)
instance Monoid (MergeSet a) where
mempty = MergeSet S.empty
mappend = (<>)
#endif
{-# INLINE cartesianProductSet #-}
balanceR :: a -> Set a -> Set a -> Set a
balanceR :: a -> Set a -> Set a -> Set a
balanceR a
x Set a
l Set a
r = case Set a
l of
Set a
Tip -> case Set a
r of
Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
x Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip
Bin Int
_ a
_ Set a
Tip Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
2 a
x Set a
forall a. Set a
Tip Set a
r
Bin Int
_ a
rx Set a
Tip rr :: Set a
rr@Bin{} -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
3 a
rx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
x Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip) Set a
rr
Bin Int
_ a
rx (Bin Int
_ a
rlx Set a
_ Set a
_) Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
3 a
rlx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
x Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip) (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
rx Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip)
Bin Int
rs a
rx rl :: Set a
rl@(Bin Int
rls a
rlx Set a
rll Set a
rlr) rr :: Set a
rr@(Bin Int
rrs a
_ Set a
_ Set a
_)
| Int
rls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
rrs -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
rx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rls) a
x Set a
forall a. Set a
Tip Set a
rl) Set a
rr
| Bool
otherwise -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
rlx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
rll) a
x Set a
forall a. Set a
Tip Set a
rll) (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rrsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
rlr) a
rx Set a
rlr Set a
rr)
Bin Int
ls a
_ Set a
_ Set a
_ -> case Set a
r of
Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ls) a
x Set a
l Set a
forall a. Set a
Tip
Bin Int
rs a
rx Set a
rl Set a
rr
| Int
rs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
ls -> case (Set a
rl, Set a
rr) of
(Bin Int
rls a
rlx Set a
rll Set a
rlr, Bin Int
rrs a
_ Set a
_ Set a
_)
| Int
rls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
rrs -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
rx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rls) a
x Set a
l Set a
rl) Set a
rr
| Bool
otherwise -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
rlx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
rll) a
x Set a
l Set a
rll) (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rrsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
rlr) a
rx Set a
rlr Set a
rr)
(Set a
_, Set a
_) -> String -> Set a
forall a. HasCallStack => String -> a
error String
"Failure in Data.Map.balanceR"
| Bool
otherwise -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
x Set a
l Set a
r
{-# NOINLINE balanceR #-}
balanceL :: a -> Set a -> Set a -> Set a
balanceL :: a -> Set a -> Set a -> Set a
balanceL a
x Set a
l Set a
r = case Set a
r of
Set a
Tip -> case Set a
l of
Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
x Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip
Bin Int
_ a
_ Set a
Tip Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
2 a
x Set a
l Set a
forall a. Set a
Tip
Bin Int
_ a
lx Set a
Tip (Bin Int
_ a
lrx Set a
_ Set a
_) -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
3 a
lrx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
lx Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip) (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
x Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip)
Bin Int
_ a
lx ll :: Set a
ll@Bin{} Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
3 a
lx Set a
ll (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin Int
1 a
x Set a
forall a. Set a
Tip Set a
forall a. Set a
Tip)
Bin Int
ls a
lx ll :: Set a
ll@(Bin Int
lls a
_ Set a
_ Set a
_) lr :: Set a
lr@(Bin Int
lrs a
lrx Set a
lrl Set a
lrr)
| Int
lrs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
lls -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ls) a
lx Set a
ll (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lrs) a
x Set a
lr Set a
forall a. Set a
Tip)
| Bool
otherwise -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ls) a
lrx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
llsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
lrl) a
lx Set a
ll Set a
lrl) (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
lrr) a
x Set a
lrr Set a
forall a. Set a
Tip)
Bin Int
rs a
_ Set a
_ Set a
_ -> case Set a
l of
Set a
Tip -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
x Set a
forall a. Set a
Tip Set a
r
Bin Int
ls a
lx Set a
ll Set a
lr
| Int
ls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
rs -> case (Set a
ll, Set a
lr) of
(Bin Int
lls a
_ Set a
_ Set a
_, Bin Int
lrs a
lrx Set a
lrl Set a
lrr)
| Int
lrs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
lls -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
lx Set a
ll (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lrs) a
x Set a
lr Set a
r)
| Bool
otherwise -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
lrx (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
llsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
lrl) a
lx Set a
ll Set a
lrl) (Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Set a -> Int
forall a. Set a -> Int
S.size Set a
lrr) a
x Set a
lrr Set a
r)
(Set a
_, Set a
_) -> String -> Set a
forall a. HasCallStack => String -> a
error String
"Failure in Data.Set.NonEmpty.Internal.balanceL"
| Bool
otherwise -> Int -> a -> Set a -> Set a -> Set a
forall a. Int -> a -> Set a -> Set a -> Set a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
rs) a
x Set a
l Set a
r
{-# NOINLINE balanceL #-}
delta,ratio :: Int
delta :: Int
delta = Int
3
ratio :: Int
ratio = Int
2