> {-# LANGUAGE TypeFamilies #-} > module Data.SetClass > where Import List ----------- > import qualified Data.Set as S > import qualified Data.IntSet as IS > import Prelude hiding (null) ------------------------------------- > class Set a where > type SetElem a > toList :: a -> [SetElem a] > fromList :: [SetElem a] -> a > size :: a -> Int > intersection :: a -> a -> a > (\\) :: a -> a -> a > union :: a -> a -> a > null :: a -> Bool > empty :: a > disjunct :: a -> a -> Bool > disjunct a b = null (intersection a b) --------------------------- > instance Ord a => Set (S.Set a) where > type SetElem (S.Set a) = a > toList = S.toList > fromList = S.fromList > size = S.size > intersection = S.intersection > (\\) = (S.\\) > union = S.union > null = S.null > empty = S.empty > instance Set IS.IntSet where > type SetElem IS.IntSet = Int > toList = IS.toList > fromList = IS.fromList > size = IS.size > intersection = IS.intersection > (\\) = (IS.\\) > union = IS.union > null = IS.null > empty = IS.empty