{-| Module : WeakSets 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 but slower. Copyright : Guillaume Sabbagh 2022 License : LGPL-3.0-or-later Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable 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. -} module Data.WeakSet ( Set -- * Construction , empty , singleton , set , fromList , fromAscList , fromDescList , fromDistinctAscList , fromDistinctDescList , powerSet -- * Operators , (|&|) , (|||) , (|*|) , (|+|) , (|-|) , (|^|) -- * Insertion , insert -- * Deletion , delete -- * Generalized insertion/deletion , alterF -- -- * Query , null , isIn , member , notMember , cardinal , size , isIncludedIn , isSubsetOf , isProperSubsetOf , disjoint -- * Combine , union , unions , difference , (\\) , intersection , cartesianProduct , disjointUnion -- * Filter , filter , partition -- * Indexed /!\ -- ** Beware if you use these functions as a 'Set' is not ordered, no guaranty is given on which element will be returned. , lookupIndex , findIndex , elemAt , deleteAt , take , drop , splitAt -- * Map , map , mapMonotonic -- * Folds , foldr , foldl -- ** Strict folds , foldr' , foldl' -- * Fold related functions , length , elem , maximum , minimum , sum , product , concat , concat2 , concatMap , and , or , any , all , maximumBy , minimumBy , notElem , find -- * Conversion -- ** List , setToList , toList , nubSetBy -- * Maybe interaction , setToMaybe , maybeToSet , catMaybes , mapMaybe -- * Either interaction , mapEither , catEither -- * Others , traverseSet , sequenceSet , anElement , cartesianProductOfSet ) where import Prelude hiding (filter, splitAt, drop, take, map, foldr, foldl, length, elem, maximum, minimum, sum, product, concat, concatMap, and, or, any, all, maximumBy, minimumBy, notElem, find, null) import qualified Data.List as L import qualified Data.Maybe as M import Control.Applicative (liftA2, Alternative, (<|>)) import qualified Control.Applicative as Applicative import qualified Data.Foldable as Foldable -- | 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. data Set a = Set [a] instance (Eq a) => Eq (Set a) where x == y = x `isIncludedIn` y && y `isIncludedIn` x instance Semigroup (Set a) where (Set xs) <> (Set ys) = set $ xs <> ys instance Monoid (Set a) where mempty = Set [] instance Functor Set where fmap f (Set xs) = Set $ f <$> xs instance Applicative Set where pure x = Set [x] (<*>) (Set fs) (Set xs) = Set $ fs <*> xs instance Monad Set where (>>=) (Set xs) f = Set $ xs >>= (unsafeSetToList.f) instance Alternative Set where (<|>) = (|||) empty = mempty instance (Show a) => Show (Set a) where show (Set xs) = "(set "++show xs++")" -- Construction -- | Alias of mempty. Defined for backward compatibility with Data.Set. empty :: Set a empty = mempty -- | Alias of pure. Defined for backward compatibility with Data.Set. singleton :: a -> Set a singleton = pure -- | /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. set :: [a] -> Set a set = Set -- | /O(1)/. This smart constructor is provided to allow backward compatibility with Data.Set. fromList :: [a] -> Set a fromList = set -- | /O(1)/. Defined for backward compatibility with Data.Set. fromAscList :: [a] -> Set a fromAscList = set -- | /O(1)/. Defined for backward compatibility with Data.Set. fromDescList :: [a] -> Set a fromDescList = set -- | /O(1)/. Defined for backward compatibility with Data.Set. fromDistinctAscList :: [a] -> Set a fromDistinctAscList = set -- | /O(1)/. Defined for backward compatibility with Data.Set. fromDistinctDescList :: [a] -> Set a fromDistinctDescList = set -- | 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])]) -- @ powerSet :: Set a -> Set (Set a) powerSet (Set xs) = Set $ Set <$> L.subsequences xs -- Insertion -- | 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. insert :: a -> Set a -> Set a insert x (Set xs) = Set (x:xs) -- Deletion -- | O(n). Delete an element from a set. delete :: Eq a => a -> Set a -> Set a delete x (Set xs) = Set $ L.filter (/= x) xs -- Generalized deletion/insertion -- | 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. alterF :: (Eq a, Functor f) => (Bool -> f Bool) -> a -> Set a -> f (Set a) alterF f x s | x `isIn` s = (\b -> if b then s else delete x s) <$> (f True) | otherwise = (\b -> if b then insert x s else s) <$> (f False) -- Query -- | /O(1)/. Return wether the set is empty. null :: Set a -> Bool null (Set xs) = Foldable.null xs -- | /O(n)/. Return wether an element is in a set. isIn :: (Eq a) => a -> Set a -> Bool isIn x = (Foldable.elem x).unsafeSetToList -- | /O(n)/. Alias of `isIn`. Defined for backward compatibility with Data.Set. member :: Eq a => a -> Set a -> Bool member = isIn -- | /O(n)/. Negation of `member`. Defined for backward compatibility with Data.Set. notMember :: Eq a => a -> Set a -> Bool notMember x s = not $ member x s -- | /O(n^2)/. Size of a set. cardinal :: (Eq a) => Set a -> Int cardinal = (Foldable.length).setToList -- | /O(n)/. Size of a set. size :: (Eq a) => Set a -> Int size = cardinal -- | /O(n^2)/. Return a boolean indicating if a `Set` is included in another one. isIncludedIn :: (Eq a) => Set a -> Set a -> Bool (Set []) `isIncludedIn` _ = True (Set (x:xs)) `isIncludedIn` (Set ys) | x `Foldable.elem` ys = (Set xs) `isIncludedIn` (Set ys) | otherwise = False -- | /O(n^2)/. Return a boolean indicating if a `Set` is included in another one. isSubsetOf :: (Eq a) => Set a -> Set a -> Bool isSubsetOf = isIncludedIn -- | /O(n^2)/. x is a proper subset of y if x is included in y and x is different from y. isProperSubsetOf :: (Eq a) => Set a -> Set a -> Bool isProperSubsetOf x y = x /= y && x `isIncludedIn` y -- | /O(n^2)/. Check whether two sets are disjoint (i.e., their intersection is empty). disjoint :: (Eq a) => Set a -> Set a -> Bool disjoint x y = null $ x `intersection` y -- Combine -- | /O(n)/. The union of two sets, preferring the first set when equal elements are encountered. union :: Set a -> Set a -> Set a union (Set xs) (Set ys) = Set (xs ++ ys) -- | The union of the sets in a Foldable structure. unions :: (Foldable f) => f (Set a) -> Set a unions = L.foldl union empty -- | /O(n*m)/. Difference of two sets. difference :: (Eq a) => Set a -> Set a -> Set a difference (Set xs) y = Set $ L.filter (not.(`isIn` y)) xs -- | See difference. (\\) :: (Eq a) => Set a -> Set a -> Set a (\\) = difference -- | /O(m*n)/. Return the intersection of two sets. Elements of the result come from the first set. intersection :: (Eq a) => Set a -> Set a -> Set a intersection (Set xs) y = Set $ L.filter (`isIn` y) xs -- | /O(m*n)/. Return the cartesian product of two sets. cartesianProduct :: Set a -> Set b -> Set (a,b) cartesianProduct (Set xs) (Set ys) = Set $ [(x,y) | x <- xs, y <- ys] -- | /O(n)/. Return the disjoint union of two sets. disjointUnion :: Set a -> Set b -> Set (Either a b) disjointUnion (Set xs) (Set ys) = Set $ [Left x | x <- xs] ++ [Right y | y <- ys] -- Filter -- | O(n). Filter all elements that satisfy the predicate. filter :: (a -> Bool) -> Set a -> Set a filter p (Set xs) = Set $ L.filter p xs -- | 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`. partition :: (a -> Bool) -> Set a -> (Set a, Set a) partition p (Set xs) = (Set $ L.filter p xs, Set $ L.filter (not.p) xs) -- Indexed -- | 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. lookupIndex :: (Eq a) => a -> Set a -> Maybe Int lookupIndex k x = L.elemIndex k (setToList x) -- | 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. findIndex :: (Eq a) => a -> Set a -> Int findIndex k x | Foldable.null index = error "WeakSet.findIndex: element is not in the set" | otherwise = i where index = lookupIndex k x Just i = index -- | 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. elemAt :: (Eq a) => Int -> Set a -> a elemAt i s | i < 0 || i >= (Foldable.length xs) = error "WeakSet.elemAt: index out of range" | otherwise = (L.!!) xs i where xs = setToList s -- | 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. deleteAt :: (Eq a) => Int -> Set a -> Set a deleteAt i s = filter (/= (elemAt i s)) s -- | O(n^2). Take a given number of elements in order. take :: (Eq a) => Int -> Set a -> Set a take i s = Set $ L.take i (setToList s) -- | O(n^2). Drop a given number of elements in order. drop :: (Eq a) => Int -> Set a -> Set a drop i s = Set $ L.drop i (setToList s) -- | O(n^2). Split a set at a particular index. splitAt :: (Eq a) => Int -> Set a -> (Set a, Set a) splitAt i s = (Set x, Set y) where (x,y) = L.splitAt i (setToList s) -- Map -- | /O(n)/. Alias of `fmap` for backward compatibility with Data.Set. Note that a WeakSet is a functor. map :: (a -> b) -> Set a -> Set b map = fmap -- | /O(n)/. Alias of `fmap` for backward compatibility with Data.Set. mapMonotonic :: (a -> b) -> Set a -> Set b mapMonotonic = fmap -- Folds -- | Strict foldr. foldr' :: (a -> b -> b) -> b -> Set a -> b foldr' f d (Set xs) = Foldable.foldr' f d xs -- | Strict foldl. foldl' :: (a -> b -> a) -> a -> Set b -> a foldl' f d (Set xs) = Foldable.foldl' f d xs -- Conversion -- | /O(1)/. Gives the underlying list of a set without removing duplicates, this function is not exported. unsafeSetToList :: Set a -> [a] unsafeSetToList (Set xs) = xs -- | /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. setToList :: (Eq a) => Set a -> [a] setToList (Set xs) = L.nub xs -- | /O(n^2)/. Alias of `setToList` for backward compatibility with Data.Set. toList :: (Eq a) => Set a -> [a] toList = setToList -- Maybe interactions -- | /O(1)/. Set version of listToMaybe. setToMaybe :: Set a -> Maybe a setToMaybe = (M.listToMaybe).unsafeSetToList -- | /O(1)/. Set version of maybeToList. maybeToSet :: Maybe a -> Set a maybeToSet x = Set $ (M.maybeToList) x -- | /O(n)/. Set version of catMaybes. Only keeps the Just values of a set and extract them. catMaybes :: Set (Maybe a) -> Set a catMaybes = set.(M.catMaybes).unsafeSetToList -- | /O(n)/. Set version of mapMaybe. A map which throws out elements which are mapped to nothing. mapMaybe :: (a -> Maybe b) -> Set a -> Set b mapMaybe f = set.(M.mapMaybe f).unsafeSetToList -- Either interactions -- | /O(n)/. Map a function to a set and separate Left and Right values. catEither :: Set (Either a b) -> (Set a, Set b) catEither (Set []) = (empty,empty) catEither (Set (x:xs)) | Foldable.null x = (insert l ls, rs) | otherwise = (ls, insert r rs) where (ls,rs) = catEither (Set xs) Right r = x Left l = x -- | /O(n)/. Map a function to a set, return a couple composed of the set of left elements and the set of right elements. mapEither :: (a -> Either b c) -> Set a -> (Set b, Set c) mapEither _ (Set []) = (empty, empty) mapEither f (Set (x:xs)) | Foldable.null result = (insert l ls, rs) | otherwise = (ls, insert r rs) where (ls,rs) = mapEither f (Set xs) result = f x Left l = result Right r = result -- Other -- | /O(n^2)/. Remove duplicates in the set using your own equality function. nubSetBy :: (a -> a -> Bool) -> Set a -> [a] nubSetBy f (Set xs) = L.nubBy f xs -- Operators -- | Alias of `intersection`. (|&|) :: (Eq a) => Set a -> Set a -> Set a (|&|) = intersection -- | Alias of `union`. (|||) :: Set a -> Set a -> Set a (|||) = union -- | Alias of `cartesianProduct`. (|*|) :: Set a -> Set b -> Set (a,b) (|*|) = cartesianProduct -- | Alias of `disjointUnion`. (|+|) :: Set a -> Set b -> Set (Either a b) (|+|) = disjointUnion -- | Returns the cartesian product of a set with itself n times. (|^|) :: (Eq a) => Set a -> Int -> Set [a] (|^|) _ 0 = Set [[]] (|^|) s n = (:) <$> s <*> (s |^| (n-1)) -- | Alias of `difference`. (|-|) :: (Eq a) => Set a -> Set a -> Set a (|-|) = difference -- | Set is not a Traversable because of the Eq typeclass requirement. traverseSet :: (Applicative f, Eq a) => (a -> f b) -> Set a -> f (Set b) traverseSet f s = foldr (\x ys -> liftA2 insert (f x) ys) (pure mempty) (set.setToList $ s) -- | Set is not a Traversable because of the Eq typeclass requirement. sequenceSet :: (Applicative f, Eq (f a)) => Set (f a) -> f (Set a) sequenceSet (Set xs) = Set <$> sequenceA (L.nub xs) -- | /O(1)/. Return an element of the set if it is not empty, throw an error otherwise. anElement :: Set a -> a anElement (Set []) = error "Data.WeakSet.anElement: empty set" anElement (Set (x:xs)) = x -- | Return the cartesian product of a set of set. cartesianProductOfSet :: Set (Set a) -> Set (Set a) cartesianProductOfSet (Set []) = Set ([Set []]) cartesianProductOfSet (Set (x:xs)) = (\(y,ys) -> insert y ys) <$> x |*| (cartesianProductOfSet (Set xs)) -- | /O(n^2)/. Fold the elements in the set using the given right-associative binary operator. -- -- Note that an Eq constraint must be added. foldr :: (Eq a) => (a -> b -> b) -> b -> Set a -> b foldr f d s = Foldable.foldr f d (setToList s) -- | /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 foldl f d s = Foldable.foldl f d (setToList s) -- | /O(n^2)/. Alias of `cardinal`. length :: (Eq a) => Set a -> Int length = cardinal -- | /O(n)/. Return wether an element is in the 'Set'. elem :: (Eq a) => a -> Set a -> Bool elem a (Set xs) = Foldable.elem a xs -- | /O(n)/. Return the maximum value of a 'Set'. maximum :: (Ord a) => Set a -> a maximum = (Foldable.maximum).unsafeSetToList -- | /O(n)/. Return the minimum value of a 'Set'. minimum :: (Ord a) => Set a -> a minimum = (Foldable.minimum).unsafeSetToList -- | /O(n^2)/. Return the sum of values in a 'Set'. sum :: (Eq a, Num a) => Set a -> a sum = (Foldable.sum).setToList -- | /O(n^2)/. Return the product of values in a 'Set'. product :: (Eq a, Num a) => Set a -> a product = (Foldable.product).setToList -- | /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]@ concat :: (Eq a) => Set [a] -> [a] concat = (Foldable.concat).setToList -- | /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]@ concat2 :: Set (Set a) -> Set a concat2 (Set xs) = Set $ [x | s <- xs, x <- (unsafeSetToList s)] -- | /O(n^2)/. Map a function over all the elements of a 'Set' and concatenate the resulting lists. concatMap :: (Eq b) => (a -> [b]) -> Set a -> [b] concatMap f s = concat $ f <$> s -- | /O(n)/. Return the conjonction of a 'Set' of booleans. and :: Set Bool -> Bool and = (Foldable.and).unsafeSetToList -- | /O(n)/. Return the disjunction of a 'Set' of booleans. or :: Set Bool -> Bool or = (Foldable.or).unsafeSetToList -- | /O(n)/. Determines whether any element of the 'Set' satisfies the predicate. any :: (a -> Bool) -> Set a -> Bool any f (Set xs) = Foldable.any f (xs) -- | /O(n)/. Determines whether all elements of the 'Set' satisfy the predicate. all :: (a -> Bool) -> Set a -> Bool all f (Set xs) = Foldable.all f (xs) -- | /O(n)/. The largest element of a non-empty 'Set' with respect to the given comparison function. maximumBy :: (a -> a -> Ordering) -> Set a -> a maximumBy f (Set xs) = Foldable.maximumBy f xs -- | /O(n)/. The smallest element of a non-empty 'Set' with respect to the given comparison function. minimumBy :: (a -> a -> Ordering) -> Set a -> a minimumBy f (Set xs) = Foldable.minimumBy f xs -- | /O(n)/. Negation of 'elem'. notElem :: (Eq a) => a -> Set a -> Bool notElem x s = not $ elem x s -- | /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. find :: (a -> Bool) -> Set a -> Maybe a find f (Set xs) = Foldable.find f xs