{-# LANGUAGE CPP #-}{-# LANGUAGE DeriveLift #-}{-# LANGUAGE RoleAnnotations #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE TypeFamilies #-}{-# OPTIONS_HADDOCK not-home #-}-------------------------------------------------------------------------- |-- Module : Data.HashSet.Internal-- Copyright : 2011 Bryan O'Sullivan-- License : BSD-style-- Maintainer : johan.tibell@gmail.com-- Portability : portable---- = WARNING---- This module is considered __internal__.---- The Package Versioning Policy __does not apply__.---- The contents of this module may change __in any way whatsoever__-- and __without any warning__ between minor versions of this package.---- Authors importing this module are expected to track development-- closely.---- = Description---- A set of /hashable/ values. A set cannot contain duplicate items.-- A 'HashSet' makes no guarantees as to the order of its elements.---- The implementation is based on /hash array mapped tries/. A-- 'HashSet' is often faster than other tree-based set types,-- especially when value comparison is expensive, as in the case of-- strings.---- Many operations have a average-case complexity of \(O(\log n)\). The-- implementation uses a large base (i.e. 16 or 32) so in practice these-- operations are constant time.moduleData.HashSet.Internal(HashSet (..)-- * Construction,empty ,singleton -- * Basic interface,null ,size ,member ,insert ,delete ,isSubsetOf -- * Transformations,map -- * Combine,union ,unions -- * Difference and intersection,difference ,intersection -- * Folds,foldr ,foldr' ,foldl ,foldl' -- * Filter,filter -- * Conversions-- ** Lists,toList ,fromList -- * HashMaps,toMap ,fromMap -- Exported from Data.HashMap.{Strict, Lazy},keysSet )whereimportControl.DeepSeq(NFData(..),NFData1(..),liftRnf2)importData.Data(Constr,Data(..),DataType)importData.Functor.ClassesimportData.Hashable(Hashable(hashWithSalt))importData.Hashable.Lifted(Hashable1(..),Hashable2(..))importData.HashMap.Internal (HashMap ,equalKeys ,equalKeys1 ,foldMapWithKey ,foldlWithKey ,foldrWithKey )importData.Semigroup(Semigroup(..),stimesIdempotentMonoid)importPreludehiding(Foldable(..),filter,map)importText.ReadimportqualifiedData.DataasDataimportqualifiedData.FoldableasFoldableimportqualifiedData.HashMap.Internal asHimportqualifiedData.ListasListimportqualifiedGHC.ExtsasExtsimportqualifiedLanguage.Haskell.TH.SyntaxasTH-- | A set of values. A set cannot contain duplicate values.newtypeHashSet a =HashSet {forall a. HashSet a -> HashMap a () asMap ::HashMap a ()}typeroleHashSet nominal-- | @since 0.2.17.0derivinginstanceTH.Lifta =>TH.Lift(HashSet a )instance(NFDataa )=>NFData(HashSet a )wherernf :: HashSet a -> () rnf =HashMap a () -> () forall a. NFData a => a -> () rnf(HashMap a () -> ()) -> (HashSet a -> HashMap a ()) -> HashSet a -> () forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap {-# INLINErnf#-}-- | @since 0.2.14.0instanceNFData1HashSet whereliftRnf :: forall a. (a -> ()) -> HashSet a -> () liftRnf a -> () rnf1 =(a -> ()) -> (() -> ()) -> HashMap a () -> () forall a b. (a -> ()) -> (b -> ()) -> HashMap a b -> () forall (p :: * -> * -> *) a b. NFData2 p => (a -> ()) -> (b -> ()) -> p a b -> () liftRnf2a -> () rnf1 () -> () forall a. NFData a => a -> () rnf(HashMap a () -> ()) -> (HashSet a -> HashMap a ()) -> HashSet a -> () forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap -- | Note that, in the presence of hash collisions, equal @HashSet@s may-- behave differently, i.e. extensionality may be violated:---- >>> data D = A | B deriving (Eq, Show)-- >>> instance Hashable D where hashWithSalt salt _d = salt---- >>> x = fromList [A, B]-- >>> y = fromList [B, A]---- >>> x == y-- True-- >>> toList x-- [A,B]-- >>> toList y-- [B,A]---- In general, the lack of extensionality can be observed with any function-- that depends on the key ordering, such as folds and traversals.instance(Eqa )=>Eq(HashSet a )whereHashSet HashMap a () a == :: HashSet a -> HashSet a -> Bool ==HashSet HashMap a () b =HashMap a () -> HashMap a () -> Bool forall k v v'. Eq k => HashMap k v -> HashMap k v' -> Bool equalKeys HashMap a () a HashMap a () b {-# INLINE(==)#-}instanceEq1HashSet whereliftEq :: forall a b. (a -> b -> Bool) -> HashSet a -> HashSet b -> Bool liftEq a -> b -> Bool eq (HashSet HashMap a () a )(HashSet HashMap b () b )=(a -> b -> Bool) -> HashMap a () -> HashMap b () -> Bool forall k k' v v'. (k -> k' -> Bool) -> HashMap k v -> HashMap k' v' -> Bool equalKeys1 a -> b -> Bool eq HashMap a () a HashMap b () b instance(Orda )=>Ord(HashSet a )wherecompare :: HashSet a -> HashSet a -> Ordering compare (HashSet HashMap a () a )(HashSet HashMap a () b )=HashMap a () -> HashMap a () -> Ordering forall a. Ord a => a -> a -> Ordering compareHashMap a () a HashMap a () b {-# INLINEcompare#-}instanceOrd1HashSet whereliftCompare :: forall a b. (a -> b -> Ordering) -> HashSet a -> HashSet b -> Ordering liftCompare a -> b -> Ordering c (HashSet HashMap a () a )(HashSet HashMap b () b )=(a -> b -> Ordering) -> (() -> () -> Ordering) -> HashMap a () -> HashMap b () -> Ordering forall a b c d. (a -> b -> Ordering) -> (c -> d -> Ordering) -> HashMap a c -> HashMap b d -> Ordering forall (f :: * -> * -> *) a b c d. Ord2 f => (a -> b -> Ordering) -> (c -> d -> Ordering) -> f a c -> f b d -> Ordering liftCompare2a -> b -> Ordering c () -> () -> Ordering forall a. Ord a => a -> a -> Ordering compareHashMap a () a HashMap b () b instanceFoldable.FoldableHashSet wherefoldMap :: forall m a. Monoid m => (a -> m) -> HashSet a -> m foldMap a -> m f =(a -> () -> m) -> HashMap a () -> m forall m k v. Monoid m => (k -> v -> m) -> HashMap k v -> m foldMapWithKey (\a a () _->a -> m f a a )(HashMap a () -> m) -> (HashSet a -> HashMap a ()) -> HashSet a -> m forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap foldr :: forall a b. (a -> b -> b) -> b -> HashSet a -> b foldr =(a -> b -> b) -> b -> HashSet a -> b forall a b. (a -> b -> b) -> b -> HashSet a -> b foldr {-# INLINEfoldr#-}foldl :: forall b a. (b -> a -> b) -> b -> HashSet a -> b foldl =(b -> a -> b) -> b -> HashSet a -> b forall b a. (b -> a -> b) -> b -> HashSet a -> b foldl {-# INLINEfoldl#-}foldl' :: forall b a. (b -> a -> b) -> b -> HashSet a -> b foldl' =(b -> a -> b) -> b -> HashSet a -> b forall b a. (b -> a -> b) -> b -> HashSet a -> b foldl' {-# INLINEfoldl'#-}foldr' :: forall a b. (a -> b -> b) -> b -> HashSet a -> b foldr' =(a -> b -> b) -> b -> HashSet a -> b forall a b. (a -> b -> b) -> b -> HashSet a -> b foldr' {-# INLINEfoldr'#-}toList :: forall a. HashSet a -> [a] toList =HashSet a -> [a] forall a. HashSet a -> [a] toList {-# INLINEtoList#-}null :: forall a. HashSet a -> Bool null =HashSet a -> Bool forall a. HashSet a -> Bool null {-# INLINEnull#-}length :: forall a. HashSet a -> Int length =HashSet a -> Int forall a. HashSet a -> Int size {-# INLINElength#-}-- | '<>' = 'union'---- \(O(n+m)\)---- To obtain good performance, the smaller set must be presented as-- the first argument.---- ==== __Examples__---- >>> fromList [1,2] <> fromList [2,3]-- fromList [1,2,3]instance(Hashablea ,Eqa )=>Semigroup(HashSet a )where<> :: HashSet a -> HashSet a -> HashSet a (<>)=HashSet a -> HashSet a -> HashSet a forall a. Eq a => HashSet a -> HashSet a -> HashSet a union {-# INLINE(<>)#-}stimes :: forall b. Integral b => b -> HashSet a -> HashSet a stimes =b -> HashSet a -> HashSet a forall b a. (Integral b, Monoid a) => b -> a -> a stimesIdempotentMonoid{-# INLINEstimes#-}-- | 'mempty' = 'empty'---- 'mappend' = 'union'---- \(O(n+m)\)---- To obtain good performance, the smaller set must be presented as-- the first argument.---- ==== __Examples__---- >>> mappend (fromList [1,2]) (fromList [2,3])-- fromList [1,2,3]instance(Hashablea ,Eqa )=>Monoid(HashSet a )wheremempty :: HashSet a mempty=HashSet a forall a. HashSet a empty {-# INLINEmempty#-}mappend :: HashSet a -> HashSet a -> HashSet a mappend=HashSet a -> HashSet a -> HashSet a forall a. Semigroup a => a -> a -> a (<>){-# INLINEmappend#-}instance(Eqa ,Hashablea ,Reada )=>Read(HashSet a )wherereadPrec :: ReadPrec (HashSet a) readPrec =ReadPrec (HashSet a) -> ReadPrec (HashSet a) forall a. ReadPrec a -> ReadPrec a parens(ReadPrec (HashSet a) -> ReadPrec (HashSet a)) -> ReadPrec (HashSet a) -> ReadPrec (HashSet a) forall a b. (a -> b) -> a -> b $Int -> ReadPrec (HashSet a) -> ReadPrec (HashSet a) forall a. Int -> ReadPrec a -> ReadPrec a precInt 10(ReadPrec (HashSet a) -> ReadPrec (HashSet a)) -> ReadPrec (HashSet a) -> ReadPrec (HashSet a) forall a b. (a -> b) -> a -> b $doIdentString "fromList"<-ReadPrec Lexeme lexP[a] -> HashSet a forall a. (Eq a, Hashable a) => [a] -> HashSet a fromList ([a] -> HashSet a) -> ReadPrec [a] -> ReadPrec (HashSet a) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>ReadPrec [a] forall a. Read a => ReadPrec a readPrecreadListPrec :: ReadPrec [HashSet a] readListPrec =ReadPrec [HashSet a] forall a. Read a => ReadPrec [a] readListPrecDefaultinstanceShow1HashSet whereliftShowsPrec :: forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> HashSet a -> ShowS liftShowsPrec Int -> a -> ShowS sp [a] -> ShowS sl Int d HashSet a m =(Int -> [a] -> ShowS) -> String -> Int -> [a] -> ShowS forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS showsUnaryWith((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS forall a. (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS forall (f :: * -> *) a. Show1 f => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS liftShowsPrecInt -> a -> ShowS sp [a] -> ShowS sl )String "fromList"Int d (HashSet a -> [a] forall a. HashSet a -> [a] toList HashSet a m )instance(Showa )=>Show(HashSet a )whereshowsPrec :: Int -> HashSet a -> ShowS showsPrec Int d HashSet a m =Bool -> ShowS -> ShowS showParen(Int d 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 showStringString "fromList "ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c .[a] -> ShowS forall a. Show a => a -> ShowS shows(HashSet a -> [a] forall a. HashSet a -> [a] toList HashSet a m )instance(Dataa ,Eqa ,Hashablea )=>Data(HashSet a )wheregfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashSet a -> c (HashSet a) gfoldl forall d b. Data d => c (d -> b) -> d -> c b f forall g. g -> c g z HashSet a m =([a] -> HashSet a) -> c ([a] -> HashSet a) forall g. g -> c g z [a] -> HashSet a forall a. (Eq a, Hashable a) => [a] -> HashSet a fromList c ([a] -> HashSet a) -> [a] -> c (HashSet a) forall d b. Data d => c (d -> b) -> d -> c b `f` HashSet a -> [a] forall a. HashSet a -> [a] toList HashSet a m toConstr :: HashSet a -> Constr toConstr HashSet a _=Constr fromListConstr gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashSet a) gunfold forall b r. Data b => c (b -> r) -> c r k forall r. r -> c r z Constr c =caseConstr -> Int Data.constrIndexConstr c ofInt 1->c ([a] -> HashSet a) -> c (HashSet a) forall b r. Data b => c (b -> r) -> c r k (([a] -> HashSet a) -> c ([a] -> HashSet a) forall r. r -> c r z [a] -> HashSet a forall a. (Eq a, Hashable a) => [a] -> HashSet a fromList )Int _->String -> c (HashSet a) forall a. HasCallStack => String -> a errorString "gunfold"dataTypeOf :: HashSet a -> DataType dataTypeOf HashSet a _=DataType hashSetDataType dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashSet a)) dataCast1 forall d. Data d => c (t d) f =c (t a) -> Maybe (c (HashSet 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)) Data.gcast1c (t a) forall d. Data d => c (t d) f instanceHashable1HashSet whereliftHashWithSalt :: forall a. (Int -> a -> Int) -> Int -> HashSet a -> Int liftHashWithSalt Int -> a -> Int h Int s =(Int -> a -> Int) -> (Int -> () -> Int) -> Int -> HashMap a () -> Int forall a b. (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> HashMap a b -> Int forall (t :: * -> * -> *) a b. Hashable2 t => (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> t a b -> Int liftHashWithSalt2Int -> a -> Int h Int -> () -> Int forall a. Hashable a => Int -> a -> Int hashWithSaltInt s (HashMap a () -> Int) -> (HashSet a -> HashMap a ()) -> HashSet a -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap instance(Hashablea )=>Hashable(HashSet a )wherehashWithSalt :: Int -> HashSet a -> Int hashWithSaltInt salt =Int -> HashMap a () -> Int forall a. Hashable a => Int -> a -> Int hashWithSaltInt salt (HashMap a () -> Int) -> (HashSet a -> HashMap a ()) -> HashSet a -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap fromListConstr ::ConstrfromListConstr :: Constr fromListConstr =DataType -> String -> [String] -> Fixity -> Constr Data.mkConstrDataType hashSetDataType String "fromList"[]Fixity Data.PrefixhashSetDataType ::DataTypehashSetDataType :: DataType hashSetDataType =String -> [Constr] -> DataType Data.mkDataTypeString "Data.HashSet.Internal.HashSet"[Constr fromListConstr ]-- | \(O(1)\) Construct an empty set.---- >>> HashSet.empty-- fromList []empty ::HashSet a empty :: forall a. HashSet a empty =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet HashMap a () forall k v. HashMap k v H.empty -- | \(O(1)\) Construct a set with a single element.---- >>> HashSet.singleton 1-- fromList [1]singleton ::Hashablea =>a ->HashSet a singleton :: forall a. Hashable a => a -> HashSet a singleton a a =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (a -> () -> HashMap a () forall k v. Hashable k => k -> v -> HashMap k v H.singleton a a ()){-# INLINABLEsingleton #-}-- | \(O(1)\) Convert to set to the equivalent 'HashMap' with @()@ values.---- >>> HashSet.toMap (HashSet.singleton 1)-- fromList [(1,())]toMap ::HashSet a ->HashMap a ()toMap :: forall a. HashSet a -> HashMap a () toMap =HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap -- | \(O(1)\) Convert from the equivalent 'HashMap' with @()@ values.---- >>> HashSet.fromMap (HashMap.singleton 1 ())-- fromList [1]fromMap ::HashMap a ()->HashSet a fromMap :: forall a. HashMap a () -> HashSet a fromMap =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet -- | \(O(n)\) Produce a 'HashSet' of all the keys in the given 'HashMap'.---- >>> HashSet.keysSet (HashMap.fromList [(1, "a"), (2, "b")]-- fromList [1,2]---- @since 0.2.10.0keysSet ::HashMap k a ->HashSet k keysSet :: forall k a. HashMap k a -> HashSet k keysSet HashMap k a m =HashMap k () -> HashSet k forall a. HashMap a () -> HashSet a fromMap (()() -> HashMap k a -> HashMap k () forall a b. a -> HashMap k b -> HashMap k a forall (f :: * -> *) a b. Functor f => a -> f b -> f a <$HashMap k a m )-- | \(O(n \log m)\) Inclusion of sets.---- ==== __Examples__---- >>> fromList [1,3] `isSubsetOf` fromList [1,2,3]-- True---- >>> fromList [1,2] `isSubsetOf` fromList [1,3]-- False---- @since 0.2.12isSubsetOf ::(Eqa ,Hashablea )=>HashSet a ->HashSet a ->BoolisSubsetOf :: forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> Bool isSubsetOf HashSet a s1 HashSet a s2 =(() -> () -> Bool) -> HashMap a () -> HashMap a () -> Bool forall k v1 v2. (Eq k, Hashable k) => (v1 -> v2 -> Bool) -> HashMap k v1 -> HashMap k v2 -> Bool H.isSubmapOfBy (\() _() _->Bool True)(HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap HashSet a s1 )(HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap HashSet a s2 )-- | \(O(n+m)\) Construct a set containing all elements from both sets.---- To obtain good performance, the smaller set must be presented as-- the first argument.---- >>> union (fromList [1,2]) (fromList [2,3])-- fromList [1,2,3]union ::Eqa =>HashSet a ->HashSet a ->HashSet a union :: forall a. Eq a => HashSet a -> HashSet a -> HashSet a union HashSet a s1 HashSet a s2 =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (HashMap a () -> HashSet a) -> HashMap a () -> HashSet a forall a b. (a -> b) -> a -> b $HashMap a () -> HashMap a () -> HashMap a () forall k v. Eq k => HashMap k v -> HashMap k v -> HashMap k v H.union (HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap HashSet a s1 )(HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap HashSet a s2 ){-# INLINEunion #-}-- TODO: Figure out the time complexity of 'unions'.-- | Construct a set containing all elements from a list of sets.unions ::Eqa =>[HashSet a ]->HashSet a unions :: forall a. Eq a => [HashSet a] -> HashSet a unions =(HashSet a -> HashSet a -> HashSet a) -> HashSet a -> [HashSet a] -> HashSet a forall b a. (b -> a -> b) -> b -> [a] -> b forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b List.foldl'HashSet a -> HashSet a -> HashSet a forall a. Eq a => HashSet a -> HashSet a -> HashSet a union HashSet a forall a. HashSet a empty {-# INLINEunions #-}-- | \(O(1)\) Return 'True' if this set is empty, 'False' otherwise.---- >>> HashSet.null HashSet.empty-- True-- >>> HashSet.null (HashSet.singleton 1)-- Falsenull ::HashSet a ->Boolnull :: forall a. HashSet a -> Bool null =HashMap a () -> Bool forall k v. HashMap k v -> Bool H.null (HashMap a () -> Bool) -> (HashSet a -> HashMap a ()) -> HashSet a -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap {-# INLINEnull #-}-- | \(O(n)\) Return the number of elements in this set.---- >>> HashSet.size HashSet.empty-- 0-- >>> HashSet.size (HashSet.fromList [1,2,3])-- 3size ::HashSet a ->Intsize :: forall a. HashSet a -> Int size =HashMap a () -> Int forall k v. HashMap k v -> Int H.size (HashMap a () -> Int) -> (HashSet a -> HashMap a ()) -> HashSet a -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap {-# INLINEsize #-}-- | \(O(\log n)\) Return 'True' if the given value is present in this-- set, 'False' otherwise.---- >>> HashSet.member 1 (Hashset.fromList [1,2,3])-- True-- >>> HashSet.member 1 (Hashset.fromList [4,5,6])-- Falsemember ::(Eqa ,Hashablea )=>a ->HashSet a ->Boolmember :: forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool member a a HashSet a s =casea -> HashMap a () -> Maybe () forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v H.lookup a a (HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap HashSet a s )ofJust() _->Bool TrueMaybe () _->Bool False{-# INLINABLEmember #-}-- | \(O(\log n)\) Add the specified value to this set.---- >>> HashSet.insert 1 HashSet.empty-- fromList [1]insert ::(Eqa ,Hashablea )=>a ->HashSet a ->HashSet a insert :: forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a insert a a =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (HashMap a () -> HashSet a) -> (HashSet a -> HashMap a ()) -> HashSet a -> HashSet a forall b c a. (b -> c) -> (a -> b) -> a -> c .a -> () -> HashMap a () -> HashMap a () forall k v. (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v H.insert a a ()(HashMap a () -> HashMap a ()) -> (HashSet a -> HashMap a ()) -> HashSet a -> HashMap a () forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap {-# INLINABLEinsert #-}-- | \(O(\log n)\) Remove the specified value from this set if present.---- >>> HashSet.delete 1 (HashSet.fromList [1,2,3])-- fromList [2,3]-- >>> HashSet.delete 1 (HashSet.fromList [4,5,6])-- fromList [4,5,6]delete ::(Eqa ,Hashablea )=>a ->HashSet a ->HashSet a delete :: forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a delete a a =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (HashMap a () -> HashSet a) -> (HashSet a -> HashMap a ()) -> HashSet a -> HashSet a forall b c a. (b -> c) -> (a -> b) -> a -> c .a -> HashMap a () -> HashMap a () forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v H.delete a a (HashMap a () -> HashMap a ()) -> (HashSet a -> HashMap a ()) -> HashSet a -> HashMap a () forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap {-# INLINABLEdelete #-}-- | \(O(n)\) Transform this set by applying a function to every value.-- The resulting set may be smaller than the source.---- >>> HashSet.map show (HashSet.fromList [1,2,3])-- HashSet.fromList ["1","2","3"]map ::(Hashableb ,Eqb )=>(a ->b )->HashSet a ->HashSet b map :: forall b a. (Hashable b, Eq b) => (a -> b) -> HashSet a -> HashSet b map a -> b f =[b] -> HashSet b forall a. (Eq a, Hashable a) => [a] -> HashSet a fromList ([b] -> HashSet b) -> (HashSet a -> [b]) -> HashSet a -> HashSet b forall b c a. (b -> c) -> (a -> b) -> a -> c .(a -> b) -> [a] -> [b] forall a b. (a -> b) -> [a] -> [b] List.mapa -> b f ([a] -> [b]) -> (HashSet a -> [a]) -> HashSet a -> [b] forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> [a] forall a. HashSet a -> [a] toList {-# INLINEmap #-}-- | \(O(n)\) Difference of two sets. Return elements of the first set-- not existing in the second.---- >>> HashSet.difference (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])-- fromList [1]difference ::(Eqa ,Hashablea )=>HashSet a ->HashSet a ->HashSet a difference :: forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a difference (HashSet HashMap a () a )(HashSet HashMap a () b )=HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (HashMap a () -> HashMap a () -> HashMap a () forall k v w. (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v H.difference HashMap a () a HashMap a () b ){-# INLINABLEdifference #-}-- | \(O(n)\) Intersection of two sets. Return elements present in both-- the first set and the second.---- >>> HashSet.intersection (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])-- fromList [2,3]intersection ::Eqa =>HashSet a ->HashSet a ->HashSet a intersection :: forall a. Eq a => HashSet a -> HashSet a -> HashSet a intersection (HashSet HashMap a () a )(HashSet HashMap a () b )=HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (HashMap a () -> HashMap a () -> HashMap a () forall k v w. Eq k => HashMap k v -> HashMap k w -> HashMap k v H.intersection HashMap a () a HashMap a () b ){-# INLINABLEintersection #-}-- | \(O(n)\) Reduce this set by applying a binary operator to all-- elements, using the given starting value (typically the-- left-identity of the operator). Each application of the operator-- is evaluated before before using the result in the next-- application. This function is strict in the starting value.foldl' ::(a ->b ->a )->a ->HashSet b ->a foldl' :: forall b a. (b -> a -> b) -> b -> HashSet a -> b foldl' a -> b -> a f a z0 =(a -> b -> () -> a) -> a -> HashMap b () -> a forall a k v. (a -> k -> v -> a) -> a -> HashMap k v -> a H.foldlWithKey' a -> b -> () -> a g a z0 (HashMap b () -> a) -> (HashSet b -> HashMap b ()) -> HashSet b -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet b -> HashMap b () forall a. HashSet a -> HashMap a () asMap whereg :: a -> b -> () -> a g a z b k () _=a -> b -> a f a z b k {-# INLINEfoldl' #-}-- | \(O(n)\) Reduce this set by applying a binary operator to all-- elements, using the given starting value (typically the-- right-identity of the operator). Each application of the operator-- is evaluated before before using the result in the next-- application. This function is strict in the starting value.foldr' ::(b ->a ->a )->a ->HashSet b ->a foldr' :: forall a b. (a -> b -> b) -> b -> HashSet a -> b foldr' b -> a -> a f a z0 =(b -> () -> a -> a) -> a -> HashMap b () -> a forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a H.foldrWithKey' b -> () -> a -> a g a z0 (HashMap b () -> a) -> (HashSet b -> HashMap b ()) -> HashSet b -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet b -> HashMap b () forall a. HashSet a -> HashMap a () asMap whereg :: b -> () -> a -> a g b k () _a z =b -> a -> a f b k a z {-# INLINEfoldr' #-}-- | \(O(n)\) Reduce this set by applying a binary operator to all-- elements, using the given starting value (typically the-- right-identity of the operator).foldr ::(b ->a ->a )->a ->HashSet b ->a foldr :: forall a b. (a -> b -> b) -> b -> HashSet a -> b foldr b -> a -> a f a z0 =(b -> () -> a -> a) -> a -> HashMap b () -> a forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a foldrWithKey b -> () -> a -> a g a z0 (HashMap b () -> a) -> (HashSet b -> HashMap b ()) -> HashSet b -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet b -> HashMap b () forall a. HashSet a -> HashMap a () asMap whereg :: b -> () -> a -> a g b k () _a z =b -> a -> a f b k a z {-# INLINEfoldr #-}-- | \(O(n)\) Reduce this set by applying a binary operator to all-- elements, using the given starting value (typically the-- left-identity of the operator).foldl ::(a ->b ->a )->a ->HashSet b ->a foldl :: forall b a. (b -> a -> b) -> b -> HashSet a -> b foldl a -> b -> a f a z0 =(a -> b -> () -> a) -> a -> HashMap b () -> a forall a k v. (a -> k -> v -> a) -> a -> HashMap k v -> a foldlWithKey a -> b -> () -> a g a z0 (HashMap b () -> a) -> (HashSet b -> HashMap b ()) -> HashSet b -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet b -> HashMap b () forall a. HashSet a -> HashMap a () asMap whereg :: a -> b -> () -> a g a z b k () _=a -> b -> a f a z b k {-# INLINEfoldl #-}-- | \(O(n)\) Filter this set by retaining only elements satisfying a-- predicate.filter ::(a ->Bool)->HashSet a ->HashSet a filter :: forall a. (a -> Bool) -> HashSet a -> HashSet a filter a -> Bool p =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (HashMap a () -> HashSet a) -> (HashSet a -> HashMap a ()) -> HashSet a -> HashSet a forall b c a. (b -> c) -> (a -> b) -> a -> c .(a -> () -> Bool) -> HashMap a () -> HashMap a () forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v H.filterWithKey a -> () -> Bool q (HashMap a () -> HashMap a ()) -> (HashSet a -> HashMap a ()) -> HashSet a -> HashMap a () forall b c a. (b -> c) -> (a -> b) -> a -> c .HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap whereq :: a -> () -> Bool q a k () _=a -> Bool p a k {-# INLINEfilter #-}-- | \(O(n)\) Return a list of this set's elements. The list is-- produced lazily. The order of its elements is unspecified, and it may-- change from version to version of either this package or of @hashable@.toList ::HashSet a ->[a ]toList :: forall a. HashSet a -> [a] toList HashSet a t =(forall b. (a -> b -> b) -> b -> b) -> [a] forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] Exts.build(\a -> b -> b c b z ->(a -> () -> b -> b) -> b -> HashMap a () -> b forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a foldrWithKey ((b -> b) -> () -> b -> b forall a b. a -> b -> a const((b -> b) -> () -> b -> b) -> (a -> b -> b) -> a -> () -> b -> b forall b c a. (b -> c) -> (a -> b) -> a -> c .a -> b -> b c )b z (HashSet a -> HashMap a () forall a. HashSet a -> HashMap a () asMap HashSet a t )){-# INLINEtoList #-}-- | \(O(n \min(W, n))\) Construct a set from a list of elements.fromList ::(Eqa ,Hashablea )=>[a ]->HashSet a fromList :: forall a. (Eq a, Hashable a) => [a] -> HashSet a fromList =HashMap a () -> HashSet a forall a. HashMap a () -> HashSet a HashSet (HashMap a () -> HashSet a) -> ([a] -> HashMap a ()) -> [a] -> HashSet a forall b c a. (b -> c) -> (a -> b) -> a -> c .(HashMap a () -> a -> HashMap a ()) -> HashMap a () -> [a] -> HashMap a () forall b a. (b -> a -> b) -> b -> [a] -> b forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b List.foldl'(\HashMap a () m a k ->a -> () -> HashMap a () -> HashMap a () forall k v. (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v H.insert a k ()HashMap a () m )HashMap a () forall k v. HashMap k v H.empty {-# INLINEfromList #-}instance(Eqa ,Hashablea )=>Exts.IsList(HashSet a )wheretypeItem(HashSet a )=a fromList :: [Item (HashSet a)] -> HashSet a fromList=[a] -> HashSet a [Item (HashSet a)] -> HashSet a forall a. (Eq a, Hashable a) => [a] -> HashSet a fromList toList :: HashSet a -> [Item (HashSet a)] toList=HashSet a -> [a] HashSet a -> [Item (HashSet a)] forall a. HashSet a -> [a] toList