1919-- A set of /hashable/ values. A set cannot contain duplicate items.
2020-- A 'HashSet' makes no guarantees as to the order of its elements.
2121--
22- -- The implementation is based on /hash array mapped trie /. A
22+ -- The implementation is based on /hash array mapped tries /. A
2323-- 'HashSet' is often faster than other tree-based set types,
2424-- especially when value comparison is expensive, as in the case of
2525-- strings.
@@ -259,63 +259,51 @@ fromListConstr = mkConstr hashSetDataType "fromList" [] Prefix
259259hashSetDataType :: DataType
260260hashSetDataType = mkDataType " Data.HashSet.Base.HashSet" [fromListConstr]
261261
262- -- | Construct an empty set.
262+ -- | /O(1)/ Construct an empty set.
263263--
264264-- >>> HashSet.empty
265265-- fromList []
266- --
267- -- __Complexity:__ /O(1)/
268266empty :: HashSet a
269267empty = HashSet H. empty
270268
271- -- | Construct a set with a single element.
269+ -- | /O(1)/ Construct a set with a single element.
272270--
273271-- >>> HashSet.singleton 1
274272-- fromList [1]
275- --
276- -- __Complexity:__ /O(1)/
277273singleton :: Hashable a => a -> HashSet a
278274singleton a = HashSet (H. singleton a () )
279275{-# INLINABLE singleton #-}
280276
281- -- | Convert to set to the equivalent 'HashMap' with @()@ values.
277+ -- | /O(1)/ Convert to set to the equivalent 'HashMap' with @()@ values.
282278--
283279-- >>> HashSet.toMap (HashSet.singleton 1)
284280-- fromList [(1,())]
285- --
286- -- /Complexity:/ /O(1)/
287281toMap :: HashSet a -> HashMap a ()
288282toMap = asMap
289283
290- -- | Convert from the equivalent 'HashMap' with @()@ values.
284+ -- | /O(1)/ Convert from the equivalent 'HashMap' with @()@ values.
291285--
292286-- >>> HashSet.fromMap (HashMap.singleton 1 ())
293287-- fromList [1]
294- --
295- -- /Complexity:/ /O(1)/
296288fromMap :: HashMap a () -> HashSet a
297289fromMap = HashSet
298290
299- -- | Produce a 'HashSet' of all the keys in the given 'HashMap'.
291+ -- | /O(n)/ Produce a 'HashSet' of all the keys in the given 'HashMap'.
300292--
301293-- >>> HashSet.keysSet (HashMap.fromList [(1, "a"), (2, "b")]
302294-- fromList [1,2]
303295--
304- -- /Complexity:/ /O(n)/
305- --
306296-- @since 0.2.10.0
307297keysSet :: HashMap k a -> HashSet k
308298keysSet m = fromMap (() <$ m)
309299
310- -- | Construct a set containing all elements from both sets.
300+ -- | /O(n+m)/ Construct a set containing all elements from both sets.
311301--
312302-- To obtain good performance, the smaller set must be presented as
313303-- the first argument.
314304--
315305-- >>> union (fromList [1,2]) (fromList [2,3])
316306-- fromList [1,2,3]
317- --
318- -- __Complexity:__ /O(n+m)/
319307union :: (Eq a , Hashable a ) => HashSet a -> HashSet a -> HashSet a
320308union s1 s2 = HashSet $ H. union (asMap s1) (asMap s2)
321309{-# INLINE union #-}
@@ -327,165 +315,134 @@ unions :: (Eq a, Hashable a) => [HashSet a] -> HashSet a
327315unions = List. foldl' union empty
328316{-# INLINE unions #-}
329317
330- -- | Return 'True' if this set is empty, 'False' otherwise.
318+ -- | /O(1)/ Return 'True' if this set is empty, 'False' otherwise.
331319--
332320-- >>> HashSet.null HashSet.empty
333321-- True
334322-- >>> HashSet.null (HashSet.singleton 1)
335323-- False
336- --
337- -- __Complexity:__ /O(1)/
338324null :: HashSet a -> Bool
339325null = H. null . asMap
340326{-# INLINE null #-}
341327
342- -- | Return the number of elements in this set.
328+ -- | /O(n)/ Return the number of elements in this set.
343329--
344330-- >>> HashSet.size HashSet.empty
345331-- 0
346332-- >>> HashSet.size (HashSet.fromList [1,2,3])
347333-- 3
348- --
349- -- __Complexity:__ /O(n)/ - The implementation of @HashSet@ does not save the
350- -- size in a field so must traverse the entire data structure on each call.
351334size :: HashSet a -> Int
352335size = H. size . asMap
353336{-# INLINE size #-}
354337
355- -- | Return 'True' if the given value is present in this
338+ -- | /O(log n)/ Return 'True' if the given value is present in this
356339-- set, 'False' otherwise.
357340--
358341-- >>> HashSet.member 1 (Hashset.fromList [1,2,3])
359342-- True
360343-- >>> HashSet.member 1 (Hashset.fromList [4,5,6])
361344-- False
362- --
363- -- __Complexity:__ /O(log n)/
364345member :: (Eq a , Hashable a ) => a -> HashSet a -> Bool
365346member a s = case H. lookup a (asMap s) of
366347 Just _ -> True
367348 _ -> False
368349{-# INLINABLE member #-}
369350
370- -- | Add the specified value to this set.
351+ -- | /O(log n)/ Add the specified value to this set.
371352--
372353-- >>> HashSet.insert 1 HashSet.empty
373354-- fromList [1]
374- --
375- -- __Complexity:__ /O(log n)/
376355insert :: (Eq a , Hashable a ) => a -> HashSet a -> HashSet a
377356insert a = HashSet . H. insert a () . asMap
378357{-# INLINABLE insert #-}
379358
380- -- | Remove the specified value from this set if present.
359+ -- | /O(log n)/ Remove the specified value from this set if present.
381360--
382361-- >>> HashSet.delete 1 (HashSet.fromList [1,2,3])
383362-- fromList [2,3]
384363-- >>> HashSet.delete 1 (HashSet.fromList [4,5,6])
385364-- fromList [4,5,6]
386- --
387- -- __Complexity:__ /O(log n)/
388365delete :: (Eq a , Hashable a ) => a -> HashSet a -> HashSet a
389366delete a = HashSet . H. delete a . asMap
390367{-# INLINABLE delete #-}
391368
392- -- | Transform this set by applying a function to every value.
369+ -- | /O(n)/ Transform this set by applying a function to every value.
393370-- The resulting set may be smaller than the source.
394371--
395372-- >>> HashSet.map show (HashSet.fromList [1,2,3])
396373-- HashSet.fromList ["1","2","3"]
397- --
398- -- __Complexity:__ /O(n)/
399374map :: (Hashable b , Eq b ) => (a -> b ) -> HashSet a -> HashSet b
400375map f = fromList . List. map f . toList
401376{-# INLINE map #-}
402377
403- -- | Difference of two sets. Return elements of the first set
378+ -- | /O(n)/ Difference of two sets. Return elements of the first set
404379-- not existing in the second.
405380--
406381-- >>> HashSet.difference (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])
407382-- fromList [1]
408- --
409- -- __Complexity:__ /O(n)/
410383difference :: (Eq a , Hashable a ) => HashSet a -> HashSet a -> HashSet a
411384difference (HashSet a) (HashSet b) = HashSet (H. difference a b)
412385{-# INLINABLE difference #-}
413386
414- -- | Intersection of two sets. Return elements present in both
387+ -- | /O(n)/ Intersection of two sets. Return elements present in both
415388-- the first set and the second.
416389--
417390-- >>> HashSet.intersection (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])
418391-- fromList [2,3]
419- --
420- -- __Complexity:__ /O(n)/
421392intersection :: (Eq a , Hashable a ) => HashSet a -> HashSet a -> HashSet a
422393intersection (HashSet a) (HashSet b) = HashSet (H. intersection a b)
423394{-# INLINABLE intersection #-}
424395
425- -- | Reduce this set by applying a binary operator to all
396+ -- | /O(n)/ Reduce this set by applying a binary operator to all
426397-- elements, using the given starting value (typically the
427398-- left-identity of the operator). Each application of the operator
428399-- is evaluated before before using the result in the next
429400-- application. This function is strict in the starting value.
430- --
431- -- __Complexity:__ /O(n)/
432401foldl' :: (a -> b -> a ) -> a -> HashSet b -> a
433402foldl' f z0 = H. foldlWithKey' g z0 . asMap
434403 where g z k _ = f z k
435404{-# INLINE foldl' #-}
436405
437- -- | Reduce this set by applying a binary operator to all
406+ -- | /O(n)/ Reduce this set by applying a binary operator to all
438407-- elements, using the given starting value (typically the
439408-- right-identity of the operator). Each application of the operator
440409-- is evaluated before before using the result in the next
441410-- application. This function is strict in the starting value.
442- --
443- -- __Complexity:__ /O(n)/
444411foldr' :: (b -> a -> a ) -> a -> HashSet b -> a
445412foldr' f z0 = H. foldrWithKey' g z0 . asMap
446413 where g k _ z = f k z
447414{-# INLINE foldr' #-}
448415
449- -- | Reduce this set by applying a binary operator to all
416+ -- | /O(n)/ Reduce this set by applying a binary operator to all
450417-- elements, using the given starting value (typically the
451418-- right-identity of the operator).
452- --
453- -- __Complexity:__ /O(n)/
454419foldr :: (b -> a -> a ) -> a -> HashSet b -> a
455420foldr f z0 = foldrWithKey g z0 . asMap
456421 where g k _ z = f k z
457422{-# INLINE foldr #-}
458423
459- -- | Reduce this set by applying a binary operator to all
424+ -- | /O(n)/ Reduce this set by applying a binary operator to all
460425-- elements, using the given starting value (typically the
461426-- left-identity of the operator).
462- --
463- -- __Complexity:__ /O(n)/
464427foldl :: (a -> b -> a ) -> a -> HashSet b -> a
465428foldl f z0 = foldlWithKey g z0 . asMap
466429 where g z k _ = f z k
467430{-# INLINE foldl #-}
468431
469- -- | Filter this set by retaining only elements satisfying a
432+ -- | /O(n)/ Filter this set by retaining only elements satisfying a
470433-- predicate.
471- --
472- -- /Complexity:/ /O(n)/
473434filter :: (a -> Bool ) -> HashSet a -> HashSet a
474435filter p = HashSet . H. filterWithKey q . asMap
475436 where q k _ = p k
476437{-# INLINE filter #-}
477438
478- -- | Return a list of this set's elements. The list is
439+ -- | /O(n)/ Return a list of this set's elements. The list is
479440-- produced lazily.
480- --
481- -- /Complexity:/ /O(n)/
482441toList :: HashSet a -> [a ]
483442toList t = build (\ c z -> foldrWithKey ((const . ) c) z (asMap t))
484443{-# INLINE toList #-}
485444
486- -- | Construct a set from a list of elements.
487- --
488- -- /Complexity:/ /O(n*min(W, n))/
445+ -- | /O(n*min(W, n))/ Construct a set from a list of elements.
489446fromList :: (Eq a , Hashable a ) => [a ] -> HashSet a
490447fromList = HashSet . List. foldl' (\ m k -> H. insert k () m) H. empty
491448{-# INLINE fromList #-}
0 commit comments