primitive-containers-0.2.0

Safe HaskellNone
LanguageHaskell2010

Data.Set.Unboxed

Contents

Synopsis

Documentation

data Set a Source #

A set of elements.

Instances

(Prim 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.

Associated Types

type Item (Set a) :: * #

Methods

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

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

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

(Prim a, Eq a) => Eq (Set a) Source # 

Methods

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

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

(Prim 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 #

(Prim a, Show a) => Show (Set a) Source # 

Methods

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

show :: Set a -> String #

showList :: [Set a] -> ShowS #

(Prim a, 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 #

(Prim a, Ord a) => Monoid (Set a) Source # 

Methods

mempty :: Set a #

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

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

PrimUnlifted (Set a) Source # 
type Item (Set a) Source # 
type Item (Set a) = a

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

Construct a set with a single element.

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

Test whether or not an element is present in a set.

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

The number of elements in the set.

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

The difference of two sets.

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

Infix operator for difference.

List Conversion

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

Convert a set to a list. The elements are given in ascending order.

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

Convert a list to a set.

Folds

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

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

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

Strict left fold over the elements in the set.

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

Strict right fold over the elements in the set.

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

Strict monoidal fold over the elements in the set.