primitive-containers-0.4.1: containers backed by arrays

Safe HaskellNone
LanguageHaskell2010

Data.Set.Lifted

Contents

Synopsis

Documentation

data Set a Source #

Instances
Foldable Set Source # 
Instance details

Defined in Data.Set.Lifted.Internal

Methods

fold :: Monoid m => Set m -> m #

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

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

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

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

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

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

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

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

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

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

Eq1 Set Source # 
Instance details

Defined in Data.Set.Lifted.Internal

Methods

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

Show1 Set Source # 
Instance details

Defined in Data.Set.Lifted.Internal

Methods

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

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

Hashable1 Set Source # 
Instance details

Defined in Data.Set.Lifted.Internal

Methods

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

Ord a => IsList (Set a) Source # 
Instance details

Defined in Data.Set.Lifted.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)] #

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

Defined in Data.Set.Lifted.Internal

Methods

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

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

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

Defined in Data.Set.Lifted.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 #

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

Defined in Data.Set.Lifted.Internal

Methods

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

show :: Set a -> String #

showList :: [Set a] -> ShowS #

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

Defined in Data.Set.Lifted.Internal

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

Defined in Data.Set.Lifted.Internal

Methods

mempty :: Set a #

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

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

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

Defined in Data.Set.Lifted.Internal

Methods

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

hash :: Set a -> Int #

type Item (Set a) Source # 
Instance details

Defined in Data.Set.Lifted.Internal

type Item (Set a) = a

empty :: Set a Source #

The empty set.

singleton :: a -> Set a Source #

Construct a set with a single element.

null :: Set a -> Bool Source #

True if the set is empty

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

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

lookupIndex :: Ord a => a -> Set a -> Maybe Int Source #

O(log n). Lookup the index of an element, which is its zero-based index in the sorted sequence of elements.

size :: Set a -> Int Source #

The number of elements in the set.

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

The difference of two sets.

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

Infix operator for difference.

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

The intersection of two sets.

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

Is the first argument a subset of the second argument?

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

Do the two sets contain any of the same elements?

Conversion

toArray :: Set a -> Array a Source #

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

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

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

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

Convert a list to a set.

Folds

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

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

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

Strict left fold over the elements in the set.

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

Strict right fold over the elements in the set.

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

Strict monoidal fold over the elements in the set.

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

Lazy monoidal fold over the elements in the set.

Traversals

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

Traverse a set, discarding the result.

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

Traverse a set with the indices, discarding the result.