hashmap-1.3.3: Persistent containers Map and Set based on hashing.

Copyright(c) Milan Straka 2011
LicenseBSD-style
Maintainerfox@ucw.cz
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.HashSet

Contents

Description

Persistent Set based on hashing, which is defined as

  data Set e = IntMap (Some e)

is an IntMap indexed by hash values of elements, containing a value of Some e. That contains either one e or a Set e with elements of the same hash values.

The interface of a Set is a suitable subset of IntSet and can be used as a drop-in replacement of Set.

The complexity of operations is determined by the complexities of IntMap and Set operations. See the sources of Set to see which operations from containers package are used.

Synopsis

Documentation

data Set a Source #

The abstract type of a Set. Its interface is a suitable subset of IntSet.

Instances

Eq a => Eq (Set a) Source # 

Methods

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

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

(Hashable a, Ord a, Data a) => Data (Set a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) #

toConstr :: Set a -> Constr #

dataTypeOf :: Set a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) #

gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

Ord a => Ord (Set a) Source # 

Methods

compare :: Set a -> Set a -> Ordering #

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

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

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

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

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

(Hashable a, Ord a, Read a) => Read (Set a) Source # 
Show a => Show (Set a) Source # 

Methods

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

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Ord a => Semigroup (Set a) Source # 

Methods

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

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

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

Ord a => Monoid (Set a) Source # 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

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

NFData a => NFData (Set a) Source # 

Methods

rnf :: Set a -> () #

type HashSet a = Set a Source #

Deprecated: HashSet is deprecated. Please use Set instead.

The HashSet is a type synonym for Set for backward compatibility. It is deprecated and will be removed in furture releases.

Operators

(\\) :: Ord a => Set a -> Set a -> Set a Source #

Same as difference.

Query

null :: Set a -> Bool Source #

Is the set empty?

size :: Set a -> Int Source #

Number of elements in the set.

member :: (Hashable a, Ord a) => a -> Set a -> Bool Source #

Is the element a member of the set?

notMember :: (Hashable a, Ord a) => a -> Set a -> Bool Source #

Is the element not a member of the set?

isSubsetOf :: Ord a => Set a -> Set a -> Bool Source #

Is this a subset?

isProperSubsetOf :: Ord a => Set a -> Set a -> Bool Source #

Is this a proper subset? (ie. a subset but not equal).

Construction

empty :: Set a Source #

The empty set.

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

A set of one element.

insert :: (Hashable a, Ord a) => a -> Set a -> Set a Source #

Add a value to the set. When the value is already an element of the set, it is replaced by the new one, ie. insert is left-biased.

delete :: (Hashable a, Ord a) => a -> Set a -> Set a Source #

Delete a value in the set. Returns the original set when the value was not present.

Combine

union :: Ord a => Set a -> Set a -> Set a Source #

The union of two sets.

unions :: Ord a => [Set a] -> Set a Source #

The union of a list of sets.

difference :: Ord a => Set a -> Set a -> Set a Source #

Difference between two sets.

intersection :: Ord a => Set a -> Set a -> Set a Source #

The intersection of two sets.

Filter

filter :: Ord a => (a -> Bool) -> Set a -> Set a Source #

Filter all elements that satisfy some predicate.

partition :: Ord a => (a -> Bool) -> Set a -> (Set a, Set a) Source #

Partition the set according to some predicate. The first set contains all elements that satisfy the predicate, the second all elements that fail the predicate.

Map

map :: (Hashable b, Ord b) => (a -> b) -> Set a -> Set b Source #

map f s is the set obtained by applying f to each element of s.

It's worth noting that the size of the result may be smaller if, for some (x,y), x /= y && f x == f y

Fold

fold :: (a -> b -> b) -> b -> Set a -> b Source #

Fold over the elements of a set in an unspecified order.

Conversion

elems :: Set a -> [a] Source #

The elements of a set. (For sets, this is equivalent to toList).

toList :: Set a -> [a] Source #

Convert the set to a list of elements.

fromList :: (Hashable a, Ord a) => [a] -> Set a Source #

Create a set from a list of elements.