primitive-containers-0.4.0: containers backed by arrays

Safe HaskellNone
LanguageHaskell2010

Data.Set.Unlifted

Contents

Synopsis

Documentation

data Set a Source #

Instances
(PrimUnlifted a, Ord a) => IsList (Set a) Source #

The functions that convert a list to a Set are asymptotically better that using foldMap singleton, with a cost of O(n*log n) rather than O(n^2). If the input list is sorted, even if duplicate elements are present, the algorithm further improves to O(n). The fastest option available is calling fromListN on a presorted list and passing the correct size size of the resulting Set. However, even if an incorrect size is given to this function, it will still correctly convert the list into a Set.

Instance details

Defined in Data.Set.Unlifted.Internal

Associated Types

type Item (Set a) :: Type #

Methods

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

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

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

(PrimUnlifted a, Eq a) => Eq (Set a) Source # 
Instance details

Defined in Data.Set.Unlifted.Internal

Methods

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

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

(PrimUnlifted a, Ord a) => Ord (Set a) Source # 
Instance details

Defined in Data.Set.Unlifted.Internal

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 #

(PrimUnlifted a, Show a) => Show (Set a) Source # 
Instance details

Defined in Data.Set.Unlifted.Internal

Methods

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

show :: Set a -> String #

showList :: [Set a] -> ShowS #

(Ord a, PrimUnlifted a) => Semigroup (Set a) Source # 
Instance details

Defined in Data.Set.Unlifted.Internal

Methods

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

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

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

(PrimUnlifted a, Ord a) => Monoid (Set a) Source # 
Instance details

Defined in Data.Set.Unlifted.Internal

Methods

mempty :: Set a #

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

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

(Hashable a, PrimUnlifted a) => Hashable (Set a) Source # 
Instance details

Defined in Data.Set.Unlifted.Internal

Methods

hashWithSalt :: Int -> Set a -> Int #

hash :: Set a -> Int #

type Item (Set a) Source # 
Instance details

Defined in Data.Set.Unlifted.Internal

type Item (Set a) = a

empty :: Set a Source #

The empty set.

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

Construct a set with a single element.

null :: Set a -> Bool Source #

True if the set is empty

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

Test for membership in the set.

size :: PrimUnlifted a => Set a -> Int Source #

The number of elements in the set.

difference :: (PrimUnlifted a, Ord a) => Set a -> Set a -> Set a Source #

The difference of two sets.

intersection :: (Ord a, PrimUnlifted a) => Set a -> Set a -> Set a Source #

The intersection of two sets.

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

Do the two sets contain any of the same elements?

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

Is the first argument a subset of the second argument?

enumFromTo Source #

Arguments

:: (Enum a, Ord a, Num a, PrimUnlifted a) 
=> a

Inclusive lower bound

-> a

Inclusive upper bound

-> Set a 

The set that includes all elements from the lower bound to the upper bound.

Conversion

toArray :: Set a -> UnliftedArray a Source #

O(1) Convert a set to an array. The elements are given in ascending order. This function is zero-cost.

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

O(n) Convert a set to a list. The elements are given in ascending order.

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

O(n*log n) Convert a list to a set.

Folds

foldr :: PrimUnlifted a => (a -> b -> b) -> b -> Set a -> b Source #

Right fold over the elements in the set. This is lazy in the accumulator.

foldMap :: (PrimUnlifted a, Monoid m) => (a -> m) -> Set a -> m Source #

Monoidal fold over the elements in the set. This is lazy in the accumulator.

foldl' :: PrimUnlifted a => (b -> a -> b) -> b -> Set a -> b Source #

Strict left fold over the elements in the set.

foldr' :: PrimUnlifted a => (a -> b -> b) -> b -> Set a -> b Source #

Strict right fold over the elements in the set.

foldMap' :: (PrimUnlifted a, Monoid m) => (a -> m) -> Set a -> m Source #

Strict monoidal fold over the elements in the set.

Traversals

traverse_ :: (Applicative m, PrimUnlifted a) => (a -> m b) -> Set a -> m () Source #

Traverse a set, discarding the result.

itraverse_ :: (Applicative m, PrimUnlifted a) => (Int -> a -> m b) -> Set a -> m () Source #

Traverse a set with the indices, discarding the result.