{-| Module : WeakSets Description : A container may be simplified internally by the call of a function 'simplify'. This is the case for 'WeakSet's and 'WeakMap's where duplicate elements remain in the container until the end of the lifetime of the container. Calling 'simplify' on them will remove duplicate elements. Copyright : Guillaume Sabbagh 2022 License : LGPL-3.0-or-later Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable A container may be simplified internally by the call of a function 'simplify'. This is the case for 'WeakSet's and 'WeakMap's where duplicate elements remain in the container until the end of the lifetime of the container. Calling 'simplify' on them will remove duplicate elements. -} module Data.Simplifiable ( Simplifiable(..), ) where import qualified Data.WeakSet as Set import qualified Data.WeakMap as Map import Data.WeakMap.Safe import qualified Data.List as List import Numeric.Natural -- | A container may be simplified internally by the call of a function 'simplify'. This is the case for 'WeakSet's -- and 'WeakMap's where duplicate elements remain in the container until the end of the lifetime of the container. Calling --'simplify' on them will remove duplicate elements. class Simplifiable a where -- | A function to simplify a container recursively. simplify :: a -> a instance Simplifiable Bool where simplify = id instance Simplifiable Char where simplify = id instance Simplifiable Int where simplify = id instance Simplifiable Natural where simplify = id instance Simplifiable Float where simplify = id instance Simplifiable Double where simplify = id instance (Simplifiable a, Simplifiable b) => Simplifiable (a,b) where simplify (a,b) = (simplify a, simplify b) instance (Simplifiable a, Simplifiable b, Simplifiable c) => Simplifiable (a,b,c) where simplify (a,b,c) = (simplify a, simplify b, simplify c) instance (Simplifiable a, Simplifiable b, Simplifiable c, Simplifiable d) => Simplifiable (a,b,c,d) where simplify (a,b,c,d) = (simplify a, simplify b, simplify c, simplify d) instance (Simplifiable a, Simplifiable b, Simplifiable c, Simplifiable d, Simplifiable e) => Simplifiable (a,b,c,d,e) where simplify (a,b,c,d,e) = (simplify a, simplify b, simplify c, simplify d, simplify e) instance (Simplifiable a, Eq a) => Simplifiable (Set.Set a) where simplify s = Set.set $ Set.setToList $ simplify <$> s instance (Simplifiable k, Simplifiable v, Eq k) => Simplifiable (Map.Map k v) where simplify m = Map.weakMap $ Map.mapToList $ simplify <|$|> m instance (Simplifiable a) => Simplifiable [a] where simplify xs = simplify <$> xs instance (Simplifiable a) => Simplifiable (Maybe a) where simplify x = simplify <$> x instance (Simplifiable a, Simplifiable b) => Simplifiable (Either a b) where simplify (Left a) = Left $ simplify a simplify (Right a) = Right $ simplify a