primitive-containers-0.4.0: containers backed by arrays

Safe HaskellNone
LanguageHaskell2010

Data.Set.NonEmpty.Unlifted

Contents

Synopsis

Documentation

data Set a Source #

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

Defined in Data.Set.NonEmpty.Unlifted

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.NonEmpty.Unlifted

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.NonEmpty.Unlifted

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.NonEmpty.Unlifted

Methods

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

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

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

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

Defined in Data.Set.NonEmpty.Unlifted

Methods

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

hash :: Set a -> Int #

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

Construct a set with a single element.

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.

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.

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

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

toSet :: Set a -> Set a Source #

O(0) Convert a non-empty set to a set. The resulting set shares the internal representation with the argument.

fromSet :: Set a -> Maybe (Set a) Source #

O(1) Convert a set to a non-empty set. This returns Nothing if the set is empty. The resulting non-empty set shares internal represention as the argument.

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.