uniquely-represented-sets-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Data.Set.Unique

Contents

Description

This module provides a uniquely-represented Set type.

Uniquely represented sets means that elements inserted in any order are represented by the same set. This makes it useful for type-level programming, and some security applications.

Synopsis

Set type

newtype Set a Source #

A uniquely-represented set.

Constructors

Set 

Fields

Instances

Functor Set Source # 

Methods

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

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

Foldable Set Source #

toList is O(n).

toList (fromDistinctAscList xs) === xs

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 #

Traversable Set Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Set a -> f (Set b) #

sequenceA :: Applicative f => Set (f a) -> f (Set a) #

mapM :: Monad m => (a -> m b) -> Set a -> m (Set b) #

sequence :: Monad m => Set (m a) -> m (Set a) #

Eq a => Eq (Set a) Source # 

Methods

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

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

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 #

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 #

Generic (Set a) Source # 

Associated Types

type Rep (Set a) :: * -> * #

Methods

from :: Set a -> Rep (Set a) x #

to :: Rep (Set a) x -> Set a #

NFData a => NFData (Set a) Source # 

Methods

rnf :: Set a -> () #

Generic1 * Set Source # 

Associated Types

type Rep1 Set (f :: Set -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Set f a #

to1 :: Rep1 Set f a -> f a #

type Rep (Set a) Source # 
type Rep (Set a) = D1 * (MetaData "Set" "Data.Set.Unique" "uniquely-represented-sets-0.1.0.0-DDrGJFXMqirAsu4tzMTftK" True) (C1 * (MetaCons "Set" PrefixI True) (S1 * (MetaSel (Just Symbol "tree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Braun (Braun a)))))
type Rep1 * Set Source # 
type Rep1 * Set = D1 * (MetaData "Set" "Data.Set.Unique" "uniquely-represented-sets-0.1.0.0-DDrGJFXMqirAsu4tzMTftK" True) (C1 * (MetaCons "Set" PrefixI True) (S1 * (MetaSel (Just Symbol "tree") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) * * Braun (Rec1 * Braun))))

Construction

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

O(n log n). Create a set from a list.

fromListBy :: (a -> a -> Ordering) -> [a] -> Set a Source #

O(n log n). Create a set from a list, using the supplied ordering function.

fromListBy compare xs === fromList xs

empty :: Set a Source #

The empty set.

singleton :: a -> Set a Source #

Create a set with one element.

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

O(n). Create a set from a list of ordered, distinct elements.

fromDistinctAscList (toList xs) === xs

Building

type Builder a b c = Int -> Int -> (Builder a (Braun a) -> Builder (Braun a) b -> c) -> c Source #

A type suitable for building a Set by repeated applications of consB.

consB :: a -> Builder a c d -> Builder a c d Source #

O(1). Push an element to the front of a Builder.

nilB :: Builder a b c Source #

An empty Builder.

runB :: Builder a (Braun (Braun a)) (Set a) -> Set a Source #

Convert a Builder to a Set.

Modification

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

sqrt(n log n). Insert an element into the set.

>>> toList (foldr insert empty [3,1,2,5,4,3,6])
[1,2,3,4,5,6]

insertBy :: (a -> a -> Ordering) -> a -> Set a -> Set a Source #

sqrt(n log n). Insert an element into the set, using the supplied ordering function.

insert x xs === insertBy compare x xs

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

sqrt(n log n). Delete an element from the set.

deleteBy :: (a -> a -> Ordering) -> a -> Set a -> Set a Source #

sqrt(n log n). Delete an element from the set, using the supplied ordering function.

delete x xs === deleteBy compare x xs

Querying

lookupBy :: (a -> a -> Ordering) -> a -> Set a -> Maybe a Source #

O(log^2 n). Lookup an element according to the supplied ordering function in the set.

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

O(log^2 n). Find if an element is a member of the set.

Size invariant

szfn :: Int -> Int Source #

The size invariant. The nth Braun tree in the set has size szfn n.