99
1010------------------------------------------------------------------------
1111-- |
12- -- Module : Data.HashSet
12+ -- Module : Data.HashSet.Base
1313-- Copyright : 2011 Bryan O'Sullivan
1414-- License : BSD-style
1515-- Maintainer : johan.tibell@gmail.com
2828-- implementation uses a large base (i.e. 16) so in practice these
2929-- operations are constant time.
3030
31- module Data.HashSet
31+ module Data.HashSet.Base
3232 (
3333 HashSet
3434
@@ -70,6 +70,9 @@ module Data.HashSet
7070 -- * HashMaps
7171 , toMap
7272 , fromMap
73+
74+ -- Exported from Data.HashMap.{Strict, Lazy}
75+ , keysSet
7376 ) where
7477
7578import Control.DeepSeq (NFData (.. ))
@@ -84,7 +87,7 @@ import Data.Monoid (Monoid(..))
8487import GHC.Exts (build )
8588import Prelude hiding (filter , foldr , map , null )
8689import qualified Data.Foldable as Foldable
87- import qualified Data.HashMap.Lazy as H
90+ import qualified Data.HashMap.Base as H
8891import qualified Data.List as List
8992import Data.Typeable (Typeable )
9093import Text.Read
@@ -101,6 +104,8 @@ import Data.Functor.Classes
101104import qualified Data.Hashable.Lifted as H
102105#endif
103106
107+ import Data.Functor ((<$) )
108+
104109-- | A set of values. A set cannot contain duplicate values.
105110newtype HashSet a = HashSet {
106111 asMap :: HashMap a ()
@@ -133,7 +138,7 @@ instance Ord1 HashSet where
133138#endif
134139
135140instance Foldable. Foldable HashSet where
136- foldr = Data.HashSet. foldr
141+ foldr = Data.HashSet.Base. foldr
137142 {-# INLINE foldr #-}
138143
139144#if __GLASGOW_HASKELL__ >= 711
@@ -210,6 +215,12 @@ toMap = asMap
210215fromMap :: HashMap a () -> HashSet a
211216fromMap = HashSet
212217
218+ -- | /O(n)/ Produce a 'HashSet' of all the keys in the given 'HashMap'.
219+ --
220+ -- @since 0.2.10.0
221+ keysSet :: HashMap k a -> HashSet k
222+ keysSet m = fromMap (() <$ m)
223+
213224-- | /O(n+m)/ Construct a set containing all elements from both sets.
214225--
215226-- To obtain good performance, the smaller set must be presented as
0 commit comments