{-| Module : Sets Description : Homogeneous sets are sets which can contain only one type of values. They are more flexible than Data.Set because they do not require the objects contained to be orderable. Copyright : Guillaume Sabbagh 2022 License : LGPL-3.0-or-later Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable Homogeneous sets are sets which can contain only one type of values. They are more flexible than Data.Set because they do not require the objects contained to be orderable. The datatype only assumes its components are equatable, it is therefore slower than the Data.Set datatype. We use this datatype because most of the datatypes we care about are not orderable. Inline functions related to homogeneous sets are written between pipes @|@. -} module HomogeneousSet ( -- * Set datatype and smart constructor Set, -- abstract type, the smart constructor is `set` set, -- the smart constructor for `Set` -- * Set related functions setToList, isIncludedIn, cardinal, isIn, (|<$>|), (|&|), (|||), (|*|), (|+|), (|-|), powerSet, -- * Function datatype and smart constructor AssociationList(..), Function, -- abstract type, the smart constructor is `function` function, -- the smart constructor for `Function` -- * Function related functions functionToSet, domain, image, (|$|), (|!|), findWithDefault, (|.|), memorizeFunction, ) where import Data.List (intercalate, nub, nubBy, intersect, union, (\\), subsequences) -- | A homogeneous set is a list of values. -- -- The only differences are that we don't want duplicate elements and we don't need the order of the list elements. -- -- 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 `set` which ensures the previous conditions. data Set a = Set [a] -- | The smart constructor of sets. This is the only way of instantiating a `Set`. -- -- If several elements are equal, only the first element is kept. set :: (Eq a) => [a] -> Set a set xs = Set (nub xs) instance (Show a) => Show (Set a) where show (Set xs) = "(set "++show xs++")" -- | Returns 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 `elem` ys = (Set xs) `isIncludedIn` (Set ys) | otherwise = False instance (Eq a) => Eq (Set a) where x == y = x `isIncludedIn` y && y `isIncludedIn` x instance (Eq a) => Semigroup (Set a) where (Set xs) <> (Set ys) = set $ xs <> ys instance (Eq a) => Monoid (Set a) where mempty = Set [] instance Foldable Set where foldr f d (Set xs) = foldr f d xs -- | Transforms a `Set` back into a list, the list returned does not have duplicate elements, the order of the original list holds. setToList :: Set a -> [a] setToList (Set xs) = xs -- | Maps a function to every element of the set. We can't instantiate `Functor` because we would have to add a contraint @Eq@ to the type parameter of `Set`. (|<$>|) :: (Eq b) => (a -> b) -> Set a -> Set b (|<$>|) f (Set xs) = set $ f <$> xs -- | Unsafe map of a funtion to every element of a set. The function should be injective. This function is not exported. unsafeMap :: (a -> b) -> Set a -> Set b unsafeMap f (Set xs) = Set $ f <$> xs -- | Size of a set. cardinal :: Set a -> Int cardinal = length.setToList -- | Returns wether an element is in a set. isIn :: (Eq a) => a -> Set a -> Bool isIn x = (elem x).setToList -- | Returns the intersection of two sets. (|&|) :: (Eq a) => Set a -> Set a -> Set a (|&|) (Set xs) (Set ys) = Set $ xs `intersect` ys -- | Returns the union of two sets. (|||) :: (Eq a) => Set a -> Set a -> Set a (|||) (Set xs) (Set ys) = Set $ xs `union` ys -- | Unsafe union where we do not check duplicates. This function is not exported. (|!) :: Set a -> Set a -> Set a (|!) (Set xs) (Set ys) = Set $ xs ++ ys -- | Returns the cartesian product of two sets. (|*|) :: Set a -> Set b -> Set (a,b) (|*|) (Set xs) (Set ys) = Set $ [(x,y) | x <- xs, y <- ys] -- | Returns the disjoint union of two sets. (|+|) :: Set a -> Set b -> Set (Either a b) (|+|) (Set xs) (Set ys) = Set $ [Left x | x <- xs] ++ [Right y | y <- ys] -- | Returns the difference of two sets. (|-|) :: (Eq a) => Set a -> Set a -> Set a (|-|) (Set xs) (Set ys) = Set $ xs \\ ys -- | Returns the set of all subsets of a given set. powerSet :: Set a -> Set (Set a) powerSet (Set xs) = Set $ Set <$> subsequences xs -- | A function of homogeneous sets. It is a set of pairs (key,value) such that their should only be one pair with a given key. -- -- It is an abstract type, the smart constructor is `function`. data Function a b = Function (Set (a,b)) deriving (Eq) instance (Show a, Show b) => Show (Function a b) where show (Function al) = "(function "++show al++")" -- | An association list is a list of pairs (key,value). type AssociationList a b = [(a,b)] -- | The smart constructor of functions. This is the only way of instantiating a `Function`. -- -- Takes an association list and returns a function which maps to each key the value associated. -- -- If several pairs have the same keys, the first pair is kept. function :: (Eq a) => AssociationList a b -> Function a b function al = Function $ Set $ nubBy (\x y -> (fst x) == (fst y)) al -- | Transforms a function back into its underlying association list. functionToSet :: Function a b -> Set (a,b) functionToSet (Function al) = al -- | Returns the domain of a function. domain :: Function a b -> Set a domain = (unsafeMap fst).functionToSet -- | Returns the image of a function. The image of a function is the set of values which are reachable by applying the function. image :: Function a b -> Set b image = (unsafeMap snd).functionToSet -- | Apply a function to a given value. If the function is not defined on the given value returns `Nothing`, otherwise returns `Just` the image. -- -- This function is like `lookup` in Data.Map for function (the order of the argument are reversed though). (|$|) :: (Eq a) => Function a b -> a -> Maybe b (|$|) (Function (Set [])) _ = Nothing (|$|) (Function (Set ((k,v):xs))) x | x == k = Just v | otherwise = (Function (Set xs)) |$| x -- | Unsafe version of `(|$|)`. -- -- This function is like `(!)` in Data.Map for function. (|!|) :: (Eq a) => Function a b -> a -> b (|!|) (Function (Set [])) _ = error "Function applied on a value not in the domain." (|!|) (Function (Set ((k,v):xs))) x | x == k = v | otherwise = (Function (Set xs)) |!| x -- | Apply a function to a given value, if the value is in the domain returns the image, otherwise return a default value. -- -- This function is like `findWithDefault` in Data.Map for function (the order of the argument are reversed though). findWithDefault :: (Eq a) => Function a b -> b -> a -> b findWithDefault (Function (Set [])) d _ = d findWithDefault (Function (Set ((k,v):xs))) d x | x == k = v | otherwise = findWithDefault (Function (Set xs)) d x -- | Composes two functions. If the two functions are not composable, strips the functions until they can compose. (|.|) :: (Eq a, Eq b) => Function b c -> Function a b -> Function a c (|.|) f2 f1 = Function $ Set [(k,(f2 |!| (f1 |!| k))) | k <- (setToList.domain $ f1), f1 |!| k `isIn` (domain f2)] -- | Memorize a Haskell function on a given finite domain. memorizeFunction :: (a -> b) -> Set a -> Function a b memorizeFunction f (Set xs) = Function $ Set [(k, f k) | k <- xs]