{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleContexts #-} {-| 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. To derive automatically 'Simplifiable', add language extensions 'DeriveAnyClass' and 'DeriveGeneric', import 'GHC.Generics' and add 'Generic' and 'Simplifiable' to the derived typeclasses of your datatype. (For example : "data Foo a = Foo (Set a) deriving (Generic, Simplifiable)".) -} 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 Data.Int import Data.Word import GHC.Generics 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 default simplify :: (Generic a, GSimplifiable (Rep a)) => a -> a simplify a = to $ gsimplify (from a) class GSimplifiable f where gsimplify :: f a -> f a instance GSimplifiable U1 where gsimplify U1 = U1 instance (GSimplifiable a, GSimplifiable b) => GSimplifiable (a :*: b) where gsimplify (a :*: b) = (gsimplify a) :*: (gsimplify b) instance (GSimplifiable a, GSimplifiable b) => GSimplifiable (a :+: b) where gsimplify (L1 a) = L1 $ gsimplify a gsimplify (R1 b) = R1 $ gsimplify b instance (GSimplifiable a) => GSimplifiable (M1 i c a) where gsimplify (M1 a) = M1 $ gsimplify a instance (Simplifiable a) => GSimplifiable (K1 i a) where gsimplify (K1 x) = K1 $ simplify x instance Simplifiable Bool where simplify = id instance Simplifiable Char where simplify = id instance Simplifiable Double where simplify = id instance Simplifiable Float where simplify = id instance Simplifiable Int where simplify = id instance Simplifiable Int8 where simplify = id instance Simplifiable Int16 where simplify = id instance Simplifiable Int32 where simplify = id instance Simplifiable Int64 where simplify = id instance Simplifiable Integer where simplify = id instance Simplifiable Natural where simplify = id instance Simplifiable Ordering where simplify = id instance Simplifiable Word where simplify = id instance Simplifiable Word8 where simplify = id instance Simplifiable Word16 where simplify = id instance Simplifiable Word32 where simplify = id instance Simplifiable Word64 where simplify = id instance Simplifiable () 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