Copyright | 2011 Bryan O'Sullivan |
---|---|
License | BSD-style |
Maintainer | johan.tibell@gmail.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Introduction
HashSet
allows you to store unique elements, providing efficient insertion,
lookups, and deletion. A HashSet
makes no guarantees as to the order of its
elements.
If you are storing sets of Data.Ints consider using Data.IntSet from the containers package.
Examples
All the examples below assume HashSet
is imported qualified, and uses the following dataStructures
set.
>>>
import qualified Data.HashSet as HashSet
>>>
let dataStructures = HashSet.fromList ["Set", "Map", "Graph", "Sequence"]
Basic Operations
Check membership in a set:
>>>
-- Check if "Map" and "Trie" are in the set of data structures.
>>>
HashSet.member "Map" dataStructures
True>>>
HashSet.member "Trie" dataStructures
False
Add a new entry to the set:
>>>
let moreDataStructures = HashSet.insert "Trie" dataStructures
>>>
HashSet.member "Trie" moreDataStructures
> True
Remove the "Graph"
entry from the set of data structures.
>>>
let fewerDataStructures = HashSet.delete "Graph" dataStructures
>>>
HashSet.toList fewerDataStructures
["Map","Set","Sequence"]
Create a new set and combine it with our original set.
>>>
let unorderedDataStructures = HashSet.fromList ["HashSet", "HashMap"]
>>>
HashSet.union dataStructures unorderedDataStructures
fromList ["Map","HashSet","Graph","HashMap","Set","Sequence"]
Using custom data with HashSet
To create a HashSet
of your custom type, the type must have instances for
Eq
and Hashable
. The Hashable
typeclass is defined in the
hashable package, see the
documentation for information on how to make your type an instance of
Hashable
.
We'll start by setting up our custom data type:
>>>
:set -XDeriveGeneric
>>>
import GHC.Generics (Generic)
>>>
import Data.Hashable
>>>
data Person = Person { name :: String, likesDogs :: Bool } deriving (Show, Eq, Generic)
>>>
instance Hashable Person
And now we'll use it!
>>>
let people = HashSet.fromList [Person "Lana" True, Person "Joe" False, Person "Simon" True]
>>>
HashSet.filter likesDogs people
fromList [Person {name = "Simon", likesDogs = True},Person {name = "Lana", likesDogs = True}]
Performance
The implementation is based on hash array mapped tries. A
HashSet
is often faster than other Ord
-based set types,
especially when value comparisons are 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) so in practice these operations are constant time.
Synopsis
- data HashSet a
- empty :: HashSet a
- singleton :: Hashable a => a -> HashSet a
- union :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
- unions :: (Eq a, Hashable a) => [HashSet a] -> HashSet a
- null :: HashSet a -> Bool
- size :: HashSet a -> Int
- member :: (Eq a, Hashable a) => a -> HashSet a -> Bool
- insert :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a
- delete :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a
- isSubsetOf :: (Eq a, Hashable a) => HashSet a -> HashSet a -> Bool
- map :: (Hashable b, Eq b) => (a -> b) -> HashSet a -> HashSet b
- difference :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
- intersection :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
- foldl' :: (a -> b -> a) -> a -> HashSet b -> a
- foldr :: (b -> a -> a) -> a -> HashSet b -> a
- filter :: (a -> Bool) -> HashSet a -> HashSet a
- toList :: HashSet a -> [a]
- fromList :: (Eq a, Hashable a) => [a] -> HashSet a
- toMap :: HashSet a -> HashMap a ()
- fromMap :: HashMap a () -> HashSet a
Documentation
A set of values. A set cannot contain duplicate values.
Instances
Foldable HashSet Source # | |
Defined in Data.HashSet.Internal fold :: Monoid m => HashSet m -> m # foldMap :: Monoid m => (a -> m) -> HashSet a -> m # foldMap' :: Monoid m => (a -> m) -> HashSet a -> m # foldr :: (a -> b -> b) -> b -> HashSet a -> b # foldr' :: (a -> b -> b) -> b -> HashSet a -> b # foldl :: (b -> a -> b) -> b -> HashSet a -> b # foldl' :: (b -> a -> b) -> b -> HashSet a -> b # foldr1 :: (a -> a -> a) -> HashSet a -> a # foldl1 :: (a -> a -> a) -> HashSet a -> a # elem :: Eq a => a -> HashSet a -> Bool # maximum :: Ord a => HashSet a -> a # minimum :: Ord a => HashSet a -> a # | |
Eq1 HashSet Source # | |
Ord1 HashSet Source # | |
Defined in Data.HashSet.Internal | |
Show1 HashSet Source # | |
NFData1 HashSet Source # | Since: 0.2.14.0 |
Defined in Data.HashSet.Internal | |
Hashable1 HashSet Source # | |
Defined in Data.HashSet.Internal | |
Lift a => Lift (HashSet a :: Type) Source # | Since: 0.2.17.0 |
(Eq a, Hashable a) => IsList (HashSet a) Source # | |
Eq a => Eq (HashSet a) Source # | Note that, in the presence of hash collisions, equal
In general, the lack of substitutivity can be observed with any function that depends on the key ordering, such as folds and traversals. |
(Data a, Eq a, Hashable a) => Data (HashSet a) Source # | |
Defined in Data.HashSet.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashSet a -> c (HashSet a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashSet a) # toConstr :: HashSet a -> Constr # dataTypeOf :: HashSet a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashSet a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashSet a)) # gmapT :: (forall b. Data b => b -> b) -> HashSet a -> HashSet a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQ :: (forall d. Data d => d -> u) -> HashSet a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashSet a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # | |
Ord a => Ord (HashSet a) Source # | |
Defined in Data.HashSet.Internal | |
(Eq a, Hashable a, Read a) => Read (HashSet a) Source # | |
Show a => Show (HashSet a) Source # | |
(Hashable a, Eq a) => Semigroup (HashSet a) Source # | O(n+m) To obtain good performance, the smaller set must be presented as the first argument. Examples
|
(Hashable a, Eq a) => Monoid (HashSet a) Source # | O(n+m) To obtain good performance, the smaller set must be presented as the first argument. Examples
|
NFData a => NFData (HashSet a) Source # | |
Defined in Data.HashSet.Internal | |
Hashable a => Hashable (HashSet a) Source # | |
Defined in Data.HashSet.Internal | |
type Item (HashSet a) Source # | |
Defined in Data.HashSet.Internal |
Construction
singleton :: Hashable a => a -> HashSet a Source #
O(1) Construct a set with a single element.
>>>
HashSet.singleton 1
fromList [1]
Combine
union :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a Source #
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]
unions :: (Eq a, Hashable a) => [HashSet a] -> HashSet a Source #
Construct a set containing all elements from a list of sets.
Basic interface
size :: HashSet a -> Int Source #
O(n) Return the number of elements in this set.
>>>
HashSet.size HashSet.empty
0>>>
HashSet.size (HashSet.fromList [1,2,3])
3
insert :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a Source #
O(log n) Add the specified value to this set.
>>>
HashSet.insert 1 HashSet.empty
fromList [1]
delete :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a Source #
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]
isSubsetOf :: (Eq a, Hashable a) => HashSet a -> HashSet a -> Bool Source #
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.12
Transformations
map :: (Hashable b, Eq b) => (a -> b) -> HashSet a -> HashSet b Source #
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"]
Difference and intersection
difference :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a Source #
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]
intersection :: (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a Source #
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]
Folds
foldl' :: (a -> b -> a) -> a -> HashSet b -> a Source #
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.
foldr :: (b -> a -> a) -> a -> HashSet b -> a Source #
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).
Filter
filter :: (a -> Bool) -> HashSet a -> HashSet a Source #
O(n) Filter this set by retaining only elements satisfying a predicate.
Conversions
Lists
toList :: HashSet a -> [a] Source #
O(n) Return a list of this set's elements. The list is produced lazily.
fromList :: (Eq a, Hashable a) => [a] -> HashSet a Source #
O(n*min(W, n)) Construct a set from a list of elements.