@@ -109,7 +109,7 @@ import Text.Read
109
109
110
110
import qualified Data.Data as Data
111
111
import qualified Data.Foldable as Foldable
112
- import qualified Data.HashMap.Internal as HM
112
+ import qualified Data.HashMap.Internal as H
113
113
import qualified Data.List as List
114
114
import qualified GHC.Exts as Exts
115
115
import qualified Language.Haskell.TH.Syntax as TH
@@ -259,14 +259,14 @@ hashSetDataType = Data.mkDataType "Data.HashSet.Internal.HashSet" [fromListConst
259
259
-- >>> HashSet.empty
260
260
-- fromList []
261
261
empty :: HashSet a
262
- empty = HashSet HM . empty
262
+ empty = HashSet H . empty
263
263
264
264
-- | /O(1)/ Construct a set with a single element.
265
265
--
266
266
-- >>> HashSet.singleton 1
267
267
-- fromList [1]
268
268
singleton :: Hashable a => a -> HashSet a
269
- singleton a = HashSet (HM . singleton a () )
269
+ singleton a = HashSet (H . singleton a () )
270
270
{-# INLINABLE singleton #-}
271
271
272
272
-- | /O(1)/ Convert to set to the equivalent 'HashMap' with @()@ values.
@@ -304,7 +304,7 @@ keysSet m = fromMap (() <$ m)
304
304
--
305
305
-- @since 0.2.12
306
306
isSubsetOf :: (Eq a , Hashable a ) => HashSet a -> HashSet a -> Bool
307
- isSubsetOf s1 s2 = HM . isSubmapOfBy (\ _ _ -> True ) (asMap s1) (asMap s2)
307
+ isSubsetOf s1 s2 = H . isSubmapOfBy (\ _ _ -> True ) (asMap s1) (asMap s2)
308
308
309
309
-- | /O(n+m)/ Construct a set containing all elements from both sets.
310
310
--
@@ -314,7 +314,7 @@ isSubsetOf s1 s2 = HM.isSubmapOfBy (\_ _ -> True) (asMap s1) (asMap s2)
314
314
-- >>> union (fromList [1,2]) (fromList [2,3])
315
315
-- fromList [1,2,3]
316
316
union :: (Eq a , Hashable a ) => HashSet a -> HashSet a -> HashSet a
317
- union s1 s2 = HashSet $ HM . union (asMap s1) (asMap s2)
317
+ union s1 s2 = HashSet $ H . union (asMap s1) (asMap s2)
318
318
{-# INLINE union #-}
319
319
320
320
-- TODO: Figure out the time complexity of 'unions'.
@@ -331,7 +331,7 @@ unions = List.foldl' union empty
331
331
-- >>> HashSet.null (HashSet.singleton 1)
332
332
-- False
333
333
null :: HashSet a -> Bool
334
- null = HM .null . asMap
334
+ null = H .null . asMap
335
335
{-# INLINE null #-}
336
336
337
337
-- | /O(n)/ Return the number of elements in this set.
@@ -341,7 +341,7 @@ null = HM.null . asMap
341
341
-- >>> HashSet.size (HashSet.fromList [1,2,3])
342
342
-- 3
343
343
size :: HashSet a -> Int
344
- size = HM . size . asMap
344
+ size = H . size . asMap
345
345
{-# INLINE size #-}
346
346
347
347
-- | /O(log n)/ Return 'True' if the given value is present in this
@@ -352,7 +352,7 @@ size = HM.size . asMap
352
352
-- >>> HashSet.member 1 (Hashset.fromList [4,5,6])
353
353
-- False
354
354
member :: (Eq a , Hashable a ) => a -> HashSet a -> Bool
355
- member a s = case HM .lookup a (asMap s) of
355
+ member a s = case H .lookup a (asMap s) of
356
356
Just _ -> True
357
357
_ -> False
358
358
{-# INLINABLE member #-}
@@ -362,7 +362,7 @@ member a s = case HM.lookup a (asMap s) of
362
362
-- >>> HashSet.insert 1 HashSet.empty
363
363
-- fromList [1]
364
364
insert :: (Eq a , Hashable a ) => a -> HashSet a -> HashSet a
365
- insert a = HashSet . HM . insert a () . asMap
365
+ insert a = HashSet . H . insert a () . asMap
366
366
{-# INLINABLE insert #-}
367
367
368
368
-- | /O(log n)/ Remove the specified value from this set if present.
@@ -372,7 +372,7 @@ insert a = HashSet . HM.insert a () . asMap
372
372
-- >>> HashSet.delete 1 (HashSet.fromList [4,5,6])
373
373
-- fromList [4,5,6]
374
374
delete :: (Eq a , Hashable a ) => a -> HashSet a -> HashSet a
375
- delete a = HashSet . HM . delete a . asMap
375
+ delete a = HashSet . H . delete a . asMap
376
376
{-# INLINABLE delete #-}
377
377
378
378
-- | /O(n)/ Transform this set by applying a function to every value.
@@ -390,7 +390,7 @@ map f = fromList . List.map f . toList
390
390
-- >>> HashSet.difference (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])
391
391
-- fromList [1]
392
392
difference :: (Eq a , Hashable a ) => HashSet a -> HashSet a -> HashSet a
393
- difference (HashSet a) (HashSet b) = HashSet (HM . difference a b)
393
+ difference (HashSet a) (HashSet b) = HashSet (H . difference a b)
394
394
{-# INLINABLE difference #-}
395
395
396
396
-- | /O(n)/ Intersection of two sets. Return elements present in both
@@ -399,7 +399,7 @@ difference (HashSet a) (HashSet b) = HashSet (HM.difference a b)
399
399
-- >>> HashSet.intersection (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])
400
400
-- fromList [2,3]
401
401
intersection :: (Eq a , Hashable a ) => HashSet a -> HashSet a -> HashSet a
402
- intersection (HashSet a) (HashSet b) = HashSet (HM . intersection a b)
402
+ intersection (HashSet a) (HashSet b) = HashSet (H . intersection a b)
403
403
{-# INLINABLE intersection #-}
404
404
405
405
-- | /O(n)/ Reduce this set by applying a binary operator to all
@@ -408,7 +408,7 @@ intersection (HashSet a) (HashSet b) = HashSet (HM.intersection a b)
408
408
-- is evaluated before before using the result in the next
409
409
-- application. This function is strict in the starting value.
410
410
foldl' :: (a -> b -> a ) -> a -> HashSet b -> a
411
- foldl' f z0 = HM . foldlWithKey' g z0 . asMap
411
+ foldl' f z0 = H . foldlWithKey' g z0 . asMap
412
412
where g z k _ = f z k
413
413
{-# INLINE foldl' #-}
414
414
@@ -418,7 +418,7 @@ foldl' f z0 = HM.foldlWithKey' g z0 . asMap
418
418
-- is evaluated before before using the result in the next
419
419
-- application. This function is strict in the starting value.
420
420
foldr' :: (b -> a -> a ) -> a -> HashSet b -> a
421
- foldr' f z0 = HM . foldrWithKey' g z0 . asMap
421
+ foldr' f z0 = H . foldrWithKey' g z0 . asMap
422
422
where g k _ z = f k z
423
423
{-# INLINE foldr' #-}
424
424
@@ -441,7 +441,7 @@ foldl f z0 = foldlWithKey g z0 . asMap
441
441
-- | /O(n)/ Filter this set by retaining only elements satisfying a
442
442
-- predicate.
443
443
filter :: (a -> Bool ) -> HashSet a -> HashSet a
444
- filter p = HashSet . HM . filterWithKey q . asMap
444
+ filter p = HashSet . H . filterWithKey q . asMap
445
445
where q k _ = p k
446
446
{-# INLINE filter #-}
447
447
@@ -453,7 +453,7 @@ toList t = Exts.build (\ c z -> foldrWithKey ((const .) c) z (asMap t))
453
453
454
454
-- | /O(n*min(W, n))/ Construct a set from a list of elements.
455
455
fromList :: (Eq a , Hashable a ) => [a ] -> HashSet a
456
- fromList = HashSet . List. foldl' (\ m k -> HM . insert k () m) HM . empty
456
+ fromList = HashSet . List. foldl' (\ m k -> H . insert k () m) H . empty
457
457
{-# INLINE fromList #-}
458
458
459
459
instance (Eq a , Hashable a ) => Exts. IsList (HashSet a ) where
0 commit comments