WeakSets-1.4.0.0: Simple set types. Useful to create sets of arbitrary types and nested sets.
CopyrightGuillaume Sabbagh 2022
LicenseLGPL-3.0-or-later
Maintainerguillaumesabbagh@protonmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.WeakSet

Description

Weak sets are sets of objects which do not have to be orderable. They are homogeneous, they can only contain a single type of object.

They are more flexible than Data.Set, they are quicker at insertion but slower at retrieving elements because the datatype only assumes its components are equatable.

We use this datatype because most of the datatypes we care about are not orderable. It also allows to define a Functor, Applicative and Monad structure on sets.

Almost all Data.WeakSet functions are implemented so that you can replace a Data.Set import such as

import Data.Set (Set)
import qualified Data.Set as Set

by a Data.WeakSet import such as

import Data.WeakSet (Set)
import qualified Data.WeakSet as Set

without breaking anything in your code.

The only functions for which this would fail are the functions converting sets back into list (they require the Eq typeclass unlike in Data.Set). size is one of them.

If a function really requires the Ord typeclass to even make sense, then it is not defined in this package, you should use Data.Set.

Note that, just like in Data.Set, the implementation is generally left-biased. Functions that take two sets as arguments and combine them, such as union and intersection, prefer the entries in the first argument to those in the second.

Functions with non colliding names are defined in Data.WeakSet.Safe. Inline functions are written between pipes |.

This module is intended to be imported qualified, to avoid name clashes with Prelude functions, except for functions in Data.WeakSet.Safe, e.g.

import           Data.WeakSet         (Set)
import qualified Data.WeakSet       as Set
import           Data.WeakSet.Safe

Unlike Data.Set, we defer the removing of duplicate elements to the conversion back to a list. It is therefore a valid Functor, Applicative and Monad. This allows to create weak sets by comprehension if you include the MonadComprehensions pragma at the beginning of your file.

Beware if the set is supposed to contain a lot of duplicate elements, you should purge them yourself by transforming the set into a list and back into a set. The time complexity is always given in function of the number of elements in the set including the duplicate elements.

Synopsis

Documentation

data Set a Source #

A weak set is a list of values such that the duplicate elements and the order of the elements are disregarded.

To force these constraints, the Set constructor is abstract and is not exported. The only way to construct a set is to use the smart constructor fromList or set which ensures the previous conditions.

Instances

Instances details
Monad Set Source # 
Instance details

Defined in Data.WeakSet

Methods

(>>=) :: Set a -> (a -> Set b) -> Set b

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

return :: a -> Set a

Functor Set Source # 
Instance details

Defined in Data.WeakSet

Methods

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

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

Applicative Set Source # 
Instance details

Defined in Data.WeakSet

Methods

pure :: a -> Set a

(<*>) :: Set (a -> b) -> Set a -> Set b

liftA2 :: (a -> b -> c) -> Set a -> Set b -> Set c

(*>) :: Set a -> Set b -> Set b

(<*) :: Set a -> Set b -> Set a

Alternative Set Source # 
Instance details

Defined in Data.WeakSet

Methods

empty :: Set a

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

some :: Set a -> Set [a]

many :: Set a -> Set [a]

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

Defined in Data.WeakSet

Methods

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

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

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

Defined in Data.WeakSet

Methods

showsPrec :: Int -> Set a -> ShowS

show :: Set a -> String

showList :: [Set a] -> ShowS

Semigroup (Set a) Source # 
Instance details

Defined in Data.WeakSet

Methods

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

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

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

Monoid (Set a) Source # 
Instance details

Defined in Data.WeakSet

Methods

mempty :: Set a

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

mconcat :: [Set a] -> Set a

Construction

empty :: Set a Source #

Alias of mempty. Defined for backward compatibility with Data.Set.

singleton :: a -> Set a Source #

Alias of pure. Defined for backward compatibility with Data.Set.

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

O(1). The smart constructor of sets. This is the only way of instantiating a Set with fromList.

We prefer the smart constructor set because its name does not collide with other data structures.

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

O(1). This smart constructor is provided to allow backward compatibility with Data.Set.

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

O(1). Defined for backward compatibility with Data.Set.

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

O(1). Defined for backward compatibility with Data.Set.

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

O(1). Defined for backward compatibility with Data.Set.

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

O(1). Defined for backward compatibility with Data.Set.

powerSet :: Set a -> Set (Set a) Source #

Return the set of all subsets of a given set.

Example :

 ghci> powerSet $ set [1,2,3]
(set [(set []),(set [1]),(set [2]),(set [1,2]),(set [3]),(set [1,3]),(set [2,3]),(set [1,2,3])])

Operators

(|&|) :: Eq a => Set a -> Set a -> Set a Source #

Alias of intersection.

(|||) :: Set a -> Set a -> Set a Source #

Alias of union.

(|*|) :: Set a -> Set b -> Set (a, b) Source #

(|+|) :: Set a -> Set b -> Set (Either a b) Source #

Alias of disjointUnion.

(|-|) :: Eq a => Set a -> Set a -> Set a Source #

Alias of difference.

(|^|) :: Eq a => Set a -> Int -> Set [a] Source #

Returns the cartesian product of a set with itself n times.

Insertion

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

O(1). Insert an element in a set. If the set already contains an element equal to the given value, it is replaced with the new value.

Deletion

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

O(n). Delete an element from a set.

Generalized insertion/deletion

alterF :: (Eq a, Functor f) => (Bool -> f Bool) -> a -> Set a -> f (Set a) Source #

O(n). (alterF f x s) can delete or insert x in s depending on whether an equal element is found in s.

Note that unlike insert, alterF will not replace an element equal to the given value.

null :: Set a -> Bool Source #

O(1). Return wether the set is empty.

isIn :: Eq a => a -> Set a -> Bool Source #

O(n). Return wether an element is in a set.

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

O(n). Alias of isIn. Defined for backward compatibility with Data.Set.

notMember :: Eq a => a -> Set a -> Bool Source #

O(n). Negation of member. Defined for backward compatibility with Data.Set.

cardinal :: Eq a => Set a -> Int Source #

O(n^2). Size of a set.

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

O(n). Size of a set.

isIncludedIn :: Eq a => Set a -> Set a -> Bool Source #

O(n^2). Return a boolean indicating if a Set is included in another one.

isSubsetOf :: Eq a => Set a -> Set a -> Bool Source #

O(n^2). Return a boolean indicating if a Set is included in another one.

isProperSubsetOf :: Eq a => Set a -> Set a -> Bool Source #

O(n^2). x is a proper subset of y if x is included in y and x is different from y.

disjoint :: Eq a => Set a -> Set a -> Bool Source #

O(n^2). Check whether two sets are disjoint (i.e., their intersection is empty).

Combine

union :: Set a -> Set a -> Set a Source #

O(n). The union of two sets, preferring the first set when equal elements are encountered.

unions :: Foldable f => f (Set a) -> Set a Source #

The union of the sets in a Foldable structure.

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

O(n*m). Difference of two sets.

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

See difference.

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

O(m*n). Return the intersection of two sets. Elements of the result come from the first set.

cartesianProduct :: Set a -> Set b -> Set (a, b) Source #

O(m*n). Return the cartesian product of two sets.

disjointUnion :: Set a -> Set b -> Set (Either a b) Source #

O(n). Return the disjoint union of two sets.

Filter

filter :: (a -> Bool) -> Set a -> Set a Source #

O(n). Filter all elements that satisfy the predicate.

partition :: (a -> Bool) -> Set a -> (Set a, Set a) Source #

O(n). Partition the set into two sets, one with all elements that satisfy the predicate and one with all elements that don't satisfy the predicate. See also split.

Indexed /!\

Beware if you use these functions as a Set is not ordered, no guaranty is given on which element will be returned.

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

O(n^2). Lookup the index of an element, which is its zero-based index in the sorted sequence of elements. The index is a number from 0 up to, but not including, the size of the set.

findIndex :: Eq a => a -> Set a -> Int Source #

O(n^2). Return the index of an element, which is its zero-based index in the sorted sequence of elements. The index is a number from 0 up to, but not including, the size of the set. Calls error when the element is not a member of the set.

elemAt :: Eq a => Int -> Set a -> a Source #

O(n^2). Retrieve an element by its index, i.e. by its zero-based index in the sorted sequence of elements. If the index is out of range (less than zero, greater or equal to size of the set), error is called.

deleteAt :: Eq a => Int -> Set a -> Set a Source #

O(n). Delete the element at index, i.e. by its zero-based index in the sorted sequence of elements. If the index is out of range (less than zero, greater or equal to size of the set), error is called.

take :: Eq a => Int -> Set a -> Set a Source #

O(n^2). Take a given number of elements in order.

drop :: Eq a => Int -> Set a -> Set a Source #

O(n^2). Drop a given number of elements in order.

splitAt :: Eq a => Int -> Set a -> (Set a, Set a) Source #

O(n^2). Split a set at a particular index.

Map

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

O(n). Alias of fmap for backward compatibility with Data.Set. Note that a WeakSet is a functor.

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

O(n). Alias of fmap for backward compatibility with Data.Set.

Folds

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

O(n^2). Fold the elements in the set using the given right-associative binary operator.

Note that an Eq constraint must be added.

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

O(n^2). Fold the elements in the set using the given right-associative binary operator.

Note that an Eq constraint must be added.

Strict folds

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

Strict foldr.

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

Strict foldl.

Fold related functions

length :: Eq a => Set a -> Int Source #

O(n^2). Alias of cardinal.

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

O(n). Return wether an element is in the Set.

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

O(n). Return the maximum value of a Set.

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

O(n). Return the minimum value of a Set.

sum :: (Eq a, Num a) => Set a -> a Source #

O(n^2). Return the sum of values in a Set.

product :: (Eq a, Num a) => Set a -> a Source #

O(n^2). Return the product of values in a Set.

concat :: Eq a => Set [a] -> [a] Source #

O(n^2). Flatten a set of lists into a list.

Example : concat set [[1,2,3],[1,2,3],[1,2]] == [1,2,3,1,2]

concat2 :: Set (Set a) -> Set a Source #

O(n). Flatten a set of sets into a set.

Example : concat set [set [1,2,3], set [1,2,3], set [1,2]] == set [1,2,3]

concatMap :: Eq b => (a -> [b]) -> Set a -> [b] Source #

O(n^2). Map a function over all the elements of a Set and concatenate the resulting lists.

and :: Set Bool -> Bool Source #

O(n). Return the conjonction of a Set of booleans.

or :: Set Bool -> Bool Source #

O(n). Return the disjunction of a Set of booleans.

any :: (a -> Bool) -> Set a -> Bool Source #

O(n). Determines whether any element of the Set satisfies the predicate.

all :: (a -> Bool) -> Set a -> Bool Source #

O(n). Determines whether all elements of the Set satisfy the predicate.

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

O(n). The largest element of a non-empty Set with respect to the given comparison function.

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

O(n). The smallest element of a non-empty Set with respect to the given comparison function.

notElem :: Eq a => a -> Set a -> Bool Source #

O(n). Negation of elem.

find :: (a -> Bool) -> Set a -> Maybe a Source #

O(n). The find function takes a predicate and a Set and returns an element of the Set matching the predicate, or Nothing if there is no such element.

Conversion

List

setToList :: Eq a => Set a -> [a] Source #

O(n^2). Transform a Set back into a list, the list returned does not have duplicate elements, the order of the original list holds.

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

O(n^2). Alias of setToList for backward compatibility with Data.Set.

nubSetBy :: (a -> a -> Bool) -> Set a -> [a] Source #

O(n^2). Remove duplicates in the set using your own equality function.

Maybe interaction

setToMaybe :: Set a -> Maybe a Source #

O(1). Set version of listToMaybe.

maybeToSet :: Maybe a -> Set a Source #

O(1). Set version of maybeToList.

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

O(n). Set version of catMaybes. Only keeps the Just values of a set and extract them.

mapMaybe :: (a -> Maybe b) -> Set a -> Set b Source #

O(n). Set version of mapMaybe. A map which throws out elements which are mapped to nothing.

Either interaction

mapEither :: (a -> Either b c) -> Set a -> (Set b, Set c) Source #

O(n). Map a function to a set, return a couple composed of the set of left elements and the set of right elements.

catEither :: Set (Either a b) -> (Set a, Set b) Source #

O(n). Take a set of Either and separate Left and Right values.

Others

traverseSet :: (Applicative f, Eq a) => (a -> f b) -> Set a -> f (Set b) Source #

Set is not a Traversable because of the Eq typeclass requirement.

sequenceSet :: (Applicative f, Eq (f a)) => Set (f a) -> f (Set a) Source #

Set is not a Traversable because of the Eq typeclass requirement.

anElement :: Set a -> a Source #

O(1). Return an element of the set if it is not empty, throw an error otherwise.

cartesianProductOfSets :: (Monoid (m a), Monad m, Foldable m, Eq a) => m (Set a) -> Set (m a) Source #

Return the cartesian product of a collection of sets.