unordered-containers-0.2.11.0: Efficient hashing-based container types
Copyright2011 Bryan O'Sullivan
LicenseBSD-style
Maintainerjohan.tibell@gmail.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.HashSet

Description

A set of hashable values. A set cannot contain duplicate items. A HashSet makes no guarantees as to the order of its elements.

The implementation is based on hash array mapped trie. A HashSet is often faster than other tree-based set types, especially when value comparison is 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

Documentation

data HashSet a Source #

A set of values. A set cannot contain duplicate values.

Instances

Instances details
Foldable HashSet Source # 
Instance details

Defined in Data.HashSet.Base

Methods

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 #

toList :: HashSet a -> [a] #

null :: HashSet a -> Bool #

length :: HashSet a -> Int #

elem :: Eq a => a -> HashSet a -> Bool #

maximum :: Ord a => HashSet a -> a #

minimum :: Ord a => HashSet a -> a #

sum :: Num a => HashSet a -> a #

product :: Num a => HashSet a -> a #

Eq1 HashSet Source # 
Instance details

Defined in Data.HashSet.Base

Methods

liftEq :: (a -> b -> Bool) -> HashSet a -> HashSet b -> Bool #

Ord1 HashSet Source # 
Instance details

Defined in Data.HashSet.Base

Methods

liftCompare :: (a -> b -> Ordering) -> HashSet a -> HashSet b -> Ordering #

Show1 HashSet Source # 
Instance details

Defined in Data.HashSet.Base

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> HashSet a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [HashSet a] -> ShowS #

Hashable1 HashSet Source # 
Instance details

Defined in Data.HashSet.Base

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> HashSet a -> Int #

(Eq a, Hashable a) => IsList (HashSet a) Source # 
Instance details

Defined in Data.HashSet.Base

Associated Types

type Item (HashSet a) #

Methods

fromList :: [Item (HashSet a)] -> HashSet a #

fromListN :: Int -> [Item (HashSet a)] -> HashSet a #

toList :: HashSet a -> [Item (HashSet a)] #

Eq a => Eq (HashSet a) Source #

Note that, in the presence of hash collisions, equal HashSets may behave differently, i.e. substitutivity may be violated:

>>> data D = A | B deriving (Eq, Show)
>>> instance Hashable D where hashWithSalt salt _d = salt
>>> x = fromList [A, B]
>>> y = fromList [B, A]
>>> x == y
True
>>> toList x
[A,B]
>>> toList y
[B,A]

In general, the lack of substitutivity can be observed with any function that depends on the key ordering, such as folds and traversals.

Instance details

Defined in Data.HashSet.Base

Methods

(==) :: HashSet a -> HashSet a -> Bool #

(/=) :: HashSet a -> HashSet a -> Bool #

(Data a, Eq a, Hashable a) => Data (HashSet a) Source # 
Instance details

Defined in Data.HashSet.Base

Methods

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 # 
Instance details

Defined in Data.HashSet.Base

Methods

compare :: HashSet a -> HashSet a -> Ordering #

(<) :: HashSet a -> HashSet a -> Bool #

(<=) :: HashSet a -> HashSet a -> Bool #

(>) :: HashSet a -> HashSet a -> Bool #

(>=) :: HashSet a -> HashSet a -> Bool #

max :: HashSet a -> HashSet a -> HashSet a #

min :: HashSet a -> HashSet a -> HashSet a #

(Eq a, Hashable a, Read a) => Read (HashSet a) Source # 
Instance details

Defined in Data.HashSet.Base

Show a => Show (HashSet a) Source # 
Instance details

Defined in Data.HashSet.Base

Methods

showsPrec :: Int -> HashSet a -> ShowS #

show :: HashSet a -> String #

showList :: [HashSet a] -> ShowS #

(Hashable a, Eq a) => Semigroup (HashSet a) Source #

<> = union

O(n+m)

To obtain good performance, the smaller set must be presented as the first argument.

Examples

Expand
>>> fromList [1,2] <> fromList [2,3]
fromList [1,2,3]
Instance details

Defined in Data.HashSet.Base

Methods

(<>) :: HashSet a -> HashSet a -> HashSet a #

sconcat :: NonEmpty (HashSet a) -> HashSet a #

stimes :: Integral b => b -> HashSet a -> HashSet a #

(Hashable a, Eq a) => Monoid (HashSet a) Source #

mempty = empty

mappend = union

O(n+m)

To obtain good performance, the smaller set must be presented as the first argument.

Examples

Expand
>>> mappend (fromList [1,2]) (fromList [2,3])
fromList [1,2,3]
Instance details

Defined in Data.HashSet.Base

Methods

mempty :: HashSet a #

mappend :: HashSet a -> HashSet a -> HashSet a #

mconcat :: [HashSet a] -> HashSet a #

NFData a => NFData (HashSet a) Source # 
Instance details

Defined in Data.HashSet.Base

Methods

rnf :: HashSet a -> () #

Hashable a => Hashable (HashSet a) Source # 
Instance details

Defined in Data.HashSet.Base

Methods

hashWithSalt :: Int -> HashSet a -> Int #

hash :: HashSet a -> Int #

type Item (HashSet a) Source # 
Instance details

Defined in Data.HashSet.Base

type Item (HashSet a) = a

Construction

empty :: HashSet a Source #

O(1) Construct an empty set.

singleton :: Hashable a => a -> HashSet a Source #

O(1) Construct a set with a single element.

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.

Examples

Expand
>>> 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

null :: HashSet a -> Bool Source #

O(1) Return True if this set is empty, False otherwise.

size :: HashSet a -> Int Source #

O(n) Return the number of elements in this set.

member :: (Eq a, Hashable a) => a -> HashSet a -> Bool Source #

O(log n) Return True if the given value is present in this set, False otherwise.

insert :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a Source #

O(log n) Add the specified value to this set.

delete :: (Eq a, Hashable a) => a -> HashSet a -> HashSet a Source #

O(log n) Remove the specified value from this set if present.

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.

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.

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.

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.

HashMaps

toMap :: HashSet a -> HashMap a () Source #

O(1) Convert to the equivalent HashMap.

fromMap :: HashMap a () -> HashSet a Source #

O(1) Convert from the equivalent HashMap.