1{-# LANGUAGE CPP, DeriveDataTypeable #-}
2#if __GLASGOW_HASKELL__ >= 708
3{-# LANGUAGE RoleAnnotations #-}
4{-# LANGUAGE TypeFamilies #-}
5#endif
6#if __GLASGOW_HASKELL__ >= 702
7{-# LANGUAGE Trustworthy #-}
8#endif
9{-# OPTIONS_HADDOCK not-home #-}
10
11------------------------------------------------------------------------
12-- |
13-- Module      :  Data.HashSet.Internal
14-- Copyright   :  2011 Bryan O'Sullivan
15-- License     :  BSD-style
16-- Maintainer  :  johan.tibell@gmail.com
17-- Portability :  portable
18--
19-- = WARNING
20--
21-- This module is considered __internal__.
22--
23-- The Package Versioning Policy __does not apply__.
24--
25-- The contents of this module may change __in any way whatsoever__
26-- and __without any warning__ between minor versions of this package.
27--
28-- Authors importing this module are expected to track development
29-- closely.
30--
31-- = Description
32--
33-- A set of /hashable/ values.  A set cannot contain duplicate items.
34-- A 'HashSet' makes no guarantees as to the order of its elements.
35--
36-- The implementation is based on /hash array mapped tries/.  A
37-- 'HashSet' is often faster than other tree-based set types,
38-- especially when value comparison is expensive, as in the case of
39-- strings.
40--
41-- Many operations have a average-case complexity of /O(log n)/.  The
42-- implementation uses a large base (i.e. 16) so in practice these
43-- operations are constant time.
44
45module Data.HashSet.Internal
46    (
47      HashSet
48
49    -- * Construction
50    , empty
51    , singleton
52
53    -- * Basic interface
54    , null
55    , size
56    , member
57    , insert
58    , delete
59    , isSubsetOf
60
61    -- * Transformations
62    , map
63
64    -- * Combine
65    , union
66    , unions
67
68      -- * Difference and intersection
69    , difference
70    , intersection
71
72    -- * Folds
73    , foldr
74    , foldr'
75    , foldl
76    , foldl'
77
78    -- * Filter
79    , filter
80
81    -- * Conversions
82
83    -- ** Lists
84    , toList
85    , fromList
86
87    -- * HashMaps
88    , toMap
89    , fromMap
90
91    -- Exported from Data.HashMap.{Strict, Lazy}
92    , keysSet
93    ) where
94
95import Control.DeepSeq (NFData(..))
96import Data.Data hiding (Typeable)
97import Data.HashMap.Internal
98  ( HashMap, foldMapWithKey, foldlWithKey, foldrWithKey
99  , equalKeys, equalKeys1)
100import Data.Hashable (Hashable(hashWithSalt))
101#if __GLASGOW_HASKELL__ >= 711
102import Data.Semigroup (Semigroup(..))
103#elif __GLASGOW_HASKELL__ < 709
104import Data.Monoid (Monoid(..))
105#endif
106import GHC.Exts (build)
107import Prelude hiding (filter, foldr, foldl, map, null)
108import qualified Data.Foldable as Foldable
109import qualified Data.HashMap.Internal as H
110import qualified Data.List as List
111import Data.Typeable (Typeable)
112import Text.Read
113
114#if __GLASGOW_HASKELL__ >= 708
115import qualified GHC.Exts as Exts
116#endif
117
118#if MIN_VERSION_base(4,9,0)
119import Data.Functor.Classes
120#endif
121
122#if MIN_VERSION_hashable(1,2,5)
123import qualified Data.Hashable.Lifted as H
124#endif
125
126#if MIN_VERSION_deepseq(1,4,3)
127import qualified Control.DeepSeq as NF
128#endif
129
130import Data.Functor ((<$))
131
132-- | A set of values.  A set cannot contain duplicate values.
133newtype HashSet a = HashSet {
134      asMap :: HashMap a ()
135    } deriving (Typeable)
136
137#if __GLASGOW_HASKELL__ >= 708
138type role HashSet nominal
139#endif
140
141instance (NFData a) => NFData (HashSet a) where
142    rnf = rnf . asMap
143    {-# INLINE rnf #-}
144
145#if MIN_VERSION_deepseq(1,4,3)
146-- | @since 0.2.14.0
147instance NF.NFData1 HashSet where
148    liftRnf rnf1 = NF.liftRnf2 rnf1 rnf . asMap
149#endif
150
151-- | Note that, in the presence of hash collisions, equal @HashSet@s may
152-- behave differently, i.e. substitutivity may be violated:
153--
154-- >>> data D = A | B deriving (Eq, Show)
155-- >>> instance Hashable D where hashWithSalt salt _d = salt
156--
157-- >>> x = fromList [A, B]
158-- >>> y = fromList [B, A]
159--
160-- >>> x == y
161-- True
162-- >>> toList x
163-- [A,B]
164-- >>> toList y
165-- [B,A]
166--
167-- In general, the lack of substitutivity can be observed with any function
168-- that depends on the key ordering, such as folds and traversals.
169instance (Eq a) => Eq (HashSet a) where
170    HashSet a == HashSet b = equalKeys a b
171    {-# INLINE (==) #-}
172
173#if MIN_VERSION_base(4,9,0)
174instance Eq1 HashSet where
175    liftEq eq (HashSet a) (HashSet b) = equalKeys1 eq a b
176#endif
177
178instance (Ord a) => Ord (HashSet a) where
179    compare (HashSet a) (HashSet b) = compare a b
180    {-# INLINE compare #-}
181
182#if MIN_VERSION_base(4,9,0)
183instance Ord1 HashSet where
184    liftCompare c (HashSet a) (HashSet b) = liftCompare2 c compare a b
185#endif
186
187instance Foldable.Foldable HashSet where
188    foldMap f = foldMapWithKey (\a _ -> f a) . asMap
189    foldr = foldr
190    {-# INLINE foldr #-}
191    foldl = foldl
192    {-# INLINE foldl #-}
193    foldl' = foldl'
194    {-# INLINE foldl' #-}
195    foldr' = foldr'
196    {-# INLINE foldr' #-}
197#if MIN_VERSION_base(4,8,0)
198    toList = toList
199    {-# INLINE toList #-}
200    null = null
201    {-# INLINE null #-}
202    length = size
203    {-# INLINE length #-}
204#endif
205
206#if __GLASGOW_HASKELL__ >= 711
207-- | '<>' = 'union'
208--
209-- /O(n+m)/
210--
211-- To obtain good performance, the smaller set must be presented as
212-- the first argument.
213--
214-- ==== __Examples__
215--
216-- >>> fromList [1,2] <> fromList [2,3]
217-- fromList [1,2,3]
218instance (Hashable a, Eq a) => Semigroup (HashSet a) where
219    (<>) = union
220    {-# INLINE (<>) #-}
221#endif
222
223-- | 'mempty' = 'empty'
224--
225-- 'mappend' = 'union'
226--
227-- /O(n+m)/
228--
229-- To obtain good performance, the smaller set must be presented as
230-- the first argument.
231--
232-- ==== __Examples__
233--
234-- >>> mappend (fromList [1,2]) (fromList [2,3])
235-- fromList [1,2,3]
236instance (Hashable a, Eq a) => Monoid (HashSet a) where
237    mempty = empty
238    {-# INLINE mempty #-}
239#if __GLASGOW_HASKELL__ >= 711
240    mappend = (<>)
241#else
242    mappend = union
243#endif
244    {-# INLINE mappend #-}
245
246instance (Eq a, Hashable a, Read a) => Read (HashSet a) where
247    readPrec = parens $ prec 10 $ do
248      Ident "fromList" <- lexP
249      xs <- readPrec
250      return (fromList xs)
251
252    readListPrec = readListPrecDefault
253
254#if MIN_VERSION_base(4,9,0)
255instance Show1 HashSet where
256    liftShowsPrec sp sl d m =
257        showsUnaryWith (liftShowsPrec sp sl) "fromList" d (toList m)
258#endif
259
260instance (Show a) => Show (HashSet a) where
261    showsPrec d m = showParen (d > 10) $
262      showString "fromList " . shows (toList m)
263
264instance (Data a, Eq a, Hashable a) => Data (HashSet a) where
265    gfoldl f z m   = z fromList `f` toList m
266    toConstr _     = fromListConstr
267    gunfold k z c  = case constrIndex c of
268        1 -> k (z fromList)
269        _ -> error "gunfold"
270    dataTypeOf _   = hashSetDataType
271    dataCast1 f    = gcast1 f
272
273#if MIN_VERSION_hashable(1,2,6)
274instance H.Hashable1 HashSet where
275    liftHashWithSalt h s = H.liftHashWithSalt2 h hashWithSalt s . asMap
276#endif
277
278instance (Hashable a) => Hashable (HashSet a) where
279    hashWithSalt salt = hashWithSalt salt . asMap
280
281fromListConstr :: Constr
282fromListConstr = mkConstr hashSetDataType "fromList" [] Prefix
283
284hashSetDataType :: DataType
285hashSetDataType = mkDataType "Data.HashSet.Internal.HashSet" [fromListConstr]
286
287-- | /O(1)/ Construct an empty set.
288--
289-- >>> HashSet.empty
290-- fromList []
291empty :: HashSet a
292empty = HashSet H.empty
293
294-- | /O(1)/ Construct a set with a single element.
295--
296-- >>> HashSet.singleton 1
297-- fromList [1]
298singleton :: Hashable a => a -> HashSet a
299singleton a = HashSet (H.singleton a ())
300{-# INLINABLE singleton #-}
301
302-- | /O(1)/ Convert to set to the equivalent 'HashMap' with @()@ values.
303--
304-- >>> HashSet.toMap (HashSet.singleton 1)
305-- fromList [(1,())]
306toMap :: HashSet a -> HashMap a ()
307toMap = asMap
308
309-- | /O(1)/ Convert from the equivalent 'HashMap' with @()@ values.
310--
311-- >>> HashSet.fromMap (HashMap.singleton 1 ())
312-- fromList [1]
313fromMap :: HashMap a () -> HashSet a
314fromMap = HashSet
315
316-- | /O(n)/ Produce a 'HashSet' of all the keys in the given 'HashMap'.
317--
318-- >>> HashSet.keysSet (HashMap.fromList [(1, "a"), (2, "b")]
319-- fromList [1,2]
320--
321-- @since 0.2.10.0
322keysSet :: HashMap k a -> HashSet k
323keysSet m = fromMap (() <$ m)
324
325-- | /O(n*log m)/ Inclusion of sets.
326--
327-- ==== __Examples__
328--
329-- >>> fromList [1,3] `isSubsetOf` fromList [1,2,3]
330-- True
331--
332-- >>> fromList [1,2] `isSubsetOf` fromList [1,3]
333-- False
334--
335-- @since 0.2.12
336isSubsetOf :: (Eq a, Hashable a) => HashSet a -> HashSet a -> Bool
337isSubsetOf s1 s2 = H.isSubmapOfBy (\_ _ -> True) (asMap s1) (asMap s2)
338
339-- | /O(n+m)/ Construct a set containing all elements from both sets.
340--
341-- To obtain good performance, the smaller set must be presented as
342-- the first argument.
343--
344-- >>> union (fromList [1,2]) (fromList [2,3])
345-- fromList [1,2,3]
346union :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
347union s1 s2 = HashSet $ H.union (asMap s1) (asMap s2)
348{-# INLINE union #-}
349
350-- TODO: Figure out the time complexity of 'unions'.
351
352-- | Construct a set containing all elements from a list of sets.
353unions :: (Eq a, Hashable a) => [HashSet a] -> HashSet a
354unions = List.foldl' union empty
355{-# INLINE unions #-}
356
357-- | /O(1)/ Return 'True' if this set is empty, 'False' otherwise.
358--
359-- >>> HashSet.null HashSet.empty
360-- True
361-- >>> HashSet.null (HashSet.singleton 1)
362-- False
363null :: HashSet a -> Bool
364null = H.null . asMap
365{-# INLINE null #-}
366
367-- | /O(n)/ Return the number of elements in this set.
368--
369-- >>> HashSet.size HashSet.empty
370-- 0
371-- >>> HashSet.size (HashSet.fromList [1,2,3])
372-- 3
373size :: HashSet a -> Int
374size = H.size . asMap
375{-# INLINE size #-}
376
377-- | /O(log n)/ Return 'True' if the given value is present in this
378-- set, 'False' otherwise.
379--
380-- >>> HashSet.member 1 (Hashset.fromList [1,2,3])
381-- True
382-- >>> HashSet.member 1 (Hashset.fromList [4,5,6])
383-- False
384member :: (Eq a, Hashable a) => a -> HashSet a -> Bool
385member a s = case H.lookup a (asMap s) of
386               Just _ -> True
387               _      -> False
388{-# INLINABLE member #-}
389
390-- | /O(log n)/ Add the specified value to this set.
391--
392-- >>> HashSet.insert 1 HashSet.empty
393-- fromList [1]
394insert :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a
395insert a = HashSet . H.insert a () . asMap
396{-# INLINABLE insert #-}
397
398-- | /O(log n)/ Remove the specified value from this set if present.
399--
400-- >>> HashSet.delete 1 (HashSet.fromList [1,2,3])
401-- fromList [2,3]
402-- >>> HashSet.delete 1 (HashSet.fromList [4,5,6])
403-- fromList [4,5,6]
404delete :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a
405delete a = HashSet . H.delete a . asMap
406{-# INLINABLE delete #-}
407
408-- | /O(n)/ Transform this set by applying a function to every value.
409-- The resulting set may be smaller than the source.
410--
411-- >>> HashSet.map show (HashSet.fromList [1,2,3])
412-- HashSet.fromList ["1","2","3"]
413map :: (Hashable b, Eq b) => (a -> b) -> HashSet a -> HashSet b
414map f = fromList . List.map f . toList
415{-# INLINE map #-}
416
417-- | /O(n)/ Difference of two sets. Return elements of the first set
418-- not existing in the second.
419--
420-- >>> HashSet.difference (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])
421-- fromList [1]
422difference :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
423difference (HashSet a) (HashSet b) = HashSet (H.difference a b)
424{-# INLINABLE difference #-}
425
426-- | /O(n)/ Intersection of two sets. Return elements present in both
427-- the first set and the second.
428--
429-- >>> HashSet.intersection (HashSet.fromList [1,2,3]) (HashSet.fromList [2,3,4])
430-- fromList [2,3]
431intersection :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
432intersection (HashSet a) (HashSet b) = HashSet (H.intersection a b)
433{-# INLINABLE intersection #-}
434
435-- | /O(n)/ Reduce this set by applying a binary operator to all
436-- elements, using the given starting value (typically the
437-- left-identity of the operator).  Each application of the operator
438-- is evaluated before before using the result in the next
439-- application.  This function is strict in the starting value.
440foldl' :: (a -> b -> a) -> a -> HashSet b -> a
441foldl' f z0 = H.foldlWithKey' g z0 . asMap
442  where g z k _ = f z k
443{-# INLINE foldl' #-}
444
445-- | /O(n)/ Reduce this set by applying a binary operator to all
446-- elements, using the given starting value (typically the
447-- right-identity of the operator). Each application of the operator
448-- is evaluated before before using the result in the next
449-- application. This function is strict in the starting value.
450foldr' :: (b -> a -> a) -> a -> HashSet b -> a
451foldr' f z0 = H.foldrWithKey' g z0 . asMap
452  where g k _ z = f k z
453{-# INLINE foldr' #-}
454
455-- | /O(n)/ Reduce this set by applying a binary operator to all
456-- elements, using the given starting value (typically the
457-- right-identity of the operator).
458foldr :: (b -> a -> a) -> a -> HashSet b -> a
459foldr f z0 = foldrWithKey g z0 . asMap
460  where g k _ z = f k z
461{-# INLINE foldr #-}
462
463-- | /O(n)/ Reduce this set by applying a binary operator to all
464-- elements, using the given starting value (typically the
465-- left-identity of the operator).
466foldl :: (a -> b -> a) -> a -> HashSet b -> a
467foldl f z0 = foldlWithKey g z0 . asMap
468  where g z k _ = f z k
469{-# INLINE foldl #-}
470
471-- | /O(n)/ Filter this set by retaining only elements satisfying a
472-- predicate.
473filter :: (a -> Bool) -> HashSet a -> HashSet a
474filter p = HashSet . H.filterWithKey q . asMap
475  where q k _ = p k
476{-# INLINE filter #-}
477
478-- | /O(n)/ Return a list of this set's elements.  The list is
479-- produced lazily.
480toList :: HashSet a -> [a]
481toList t = build (\ c z -> foldrWithKey ((const .) c) z (asMap t))
482{-# INLINE toList #-}
483
484-- | /O(n*min(W, n))/ Construct a set from a list of elements.
485fromList :: (Eq a, Hashable a) => [a] -> HashSet a
486fromList = HashSet . List.foldl' (\ m k -> H.insert k () m) H.empty
487{-# INLINE fromList #-}
488
489#if __GLASGOW_HASKELL__ >= 708
490instance (Eq a, Hashable a) => Exts.IsList (HashSet a) where
491    type Item (HashSet a) = a
492    fromList = fromList
493    toList   = toList
494#endif
495