X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=Data%2FSet.hs;h=04d0100132b30e2b798f1802275bae90a1e4d25c;hb=6b1a36a595eddf1e124529646afdb75c76a9966d;hp=33641de4b0fef9a7b5f37328dd8188350da8c0f1;hpb=7acdd16c9b9058c39ab2aea39e0f2ef879f8f89c;p=haskell-directory.git diff --git a/Data/Set.hs b/Data/Set.hs index 33641de..04d0100 100644 --- a/Data/Set.hs +++ b/Data/Set.hs @@ -9,10 +9,11 @@ -- -- An efficient implementation of sets. -- --- This module is intended to be imported @qualified@, to avoid name --- clashes with "Prelude" functions. eg. +-- Since many function names (but not the type name) clash with +-- "Prelude" names, this module is usually imported @qualified@, e.g. -- --- > import Data.Set as Set +-- > import Data.Set (Set) +-- > import qualified Data.Set as Set -- -- The implementation of 'Set' is based on /size balanced/ binary trees (or -- trees of /bounded balance/) as described by: @@ -26,7 +27,7 @@ -- SIAM journal of computing 2(1), March 1973. -- -- Note that the implementation is /left-biased/ -- the elements of a --- first argument are always perferred to the second, for example in +-- first argument are always preferred to the second, for example in -- 'union' or 'insert'. Of course, left-biasing can only be observed -- when equality is an equivalence relation instead of structural -- equality. @@ -43,6 +44,7 @@ module Data.Set ( , null , size , member + , notMember , isSubsetOf , isProperSubsetOf @@ -77,6 +79,8 @@ module Data.Set ( , deleteMax , deleteFindMin , deleteFindMax + , maxView + , minView -- * Conversion @@ -94,26 +98,13 @@ module Data.Set ( , showTree , showTreeWith , valid - - -- * Old interface, DEPRECATED - ,emptySet, -- :: Set a - mkSet, -- :: Ord a => [a] -> Set a - setToList, -- :: Set a -> [a] - unitSet, -- :: a -> Set a - elementOf, -- :: Ord a => a -> Set a -> Bool - isEmptySet, -- :: Set a -> Bool - cardinality, -- :: Set a -> Int - unionManySets, -- :: Ord a => [Set a] -> Set a - minusSet, -- :: Ord a => Set a -> Set a -> Set a - mapSet, -- :: Ord a => (b -> a) -> Set b -> Set a - intersect, -- :: Ord a => Set a -> Set a -> Set a - addToSet, -- :: Ord a => Set a -> a -> Set a - delFromSet, -- :: Ord a => Set a -> a -> Set a ) where import Prelude hiding (filter,foldr,null,map) import qualified Data.List as List +import Data.Monoid (Monoid(..)) import Data.Typeable +import Data.Foldable (Foldable(foldMap)) {- -- just for testing @@ -123,6 +114,7 @@ import qualified List -} #if __GLASGOW_HASKELL__ +import Text.Read import Data.Generics.Basics import Data.Generics.Instances #endif @@ -145,6 +137,15 @@ data Set a = Tip type Size = Int +instance Ord a => Monoid (Set a) where + mempty = empty + mappend = union + mconcat = unions + +instance Foldable Set where + foldMap f Tip = mempty + foldMap f (Bin _s k l r) = foldMap f l `mappend` f k `mappend` foldMap f r + #if __GLASGOW_HASKELL__ {-------------------------------------------------------------------- @@ -159,6 +160,7 @@ instance (Data a, Ord a) => Data (Set a) where toConstr _ = error "toConstr" gunfold _ _ = error "gunfold" dataTypeOf _ = mkNorepType "Data.Set.Set" + dataCast1 f = gcast1 f #endif @@ -190,6 +192,10 @@ member x t GT -> member x r EQ -> True +-- | /O(log n)/. Is the element not in the set? +notMember :: Ord a => a -> Set a -> Bool +notMember x t = not $ member x t + {-------------------------------------------------------------------- Construction --------------------------------------------------------------------} @@ -298,9 +304,7 @@ unions ts union :: Ord a => Set a -> Set a -> Set a union Tip t2 = t2 union t1 Tip = t1 -union t1 t2 - | size t1 >= size t2 = hedgeUnion (const LT) (const GT) t1 t2 - | otherwise = hedgeUnion (const LT) (const GT) t2 t1 +union t1 t2 = hedgeUnion (const LT) (const GT) t1 t2 hedgeUnion cmplo cmphi t1 Tip = t1 @@ -336,24 +340,32 @@ hedgeDiff cmplo cmphi t (Bin _ x l r) Intersection --------------------------------------------------------------------} -- | /O(n+m)/. The intersection of two sets. --- Intersection is more efficient on (bigset `intersection` smallset). +-- Elements of the result come from the first set, so for example +-- +-- > import qualified Data.Set as S +-- > data AB = A | B deriving Show +-- > instance Ord AB where compare _ _ = EQ +-- > instance Eq AB where _ == _ = True +-- > main = print (S.singleton A `S.intersection` S.singleton B, +-- > S.singleton B `S.intersection` S.singleton A) +-- +-- prints @(fromList [A],fromList [B])@. intersection :: Ord a => Set a -> Set a -> Set a intersection Tip t = Tip intersection t Tip = Tip -intersection t1 t2 - | size t1 >= size t2 = intersect' t1 t2 - | otherwise = intersect' t2 t1 - -intersect' Tip t = Tip -intersect' t Tip = Tip -intersect' t (Bin _ x l r) - | found = join x tl tr - | otherwise = merge tl tr - where - (lt,found,gt) = splitMember x t - tl = intersect' lt l - tr = intersect' gt r - +intersection t1@(Bin s1 x1 l1 r1) t2@(Bin s2 x2 l2 r2) = + if s1 >= s2 then + let (lt,found,gt) = splitLookup x2 t1 + tl = intersection lt l2 + tr = intersection gt r2 + in case found of + Just x -> join x tl tr + Nothing -> merge tl tr + else let (lt,found,gt) = splitMember x1 t2 + tl = intersection l1 lt + tr = intersection r1 gt + in if found then join x1 tl tr + else merge tl tr {-------------------------------------------------------------------- Filter and partition @@ -512,7 +524,8 @@ instance Ord a => Ord (Set a) where Show --------------------------------------------------------------------} instance Show a => Show (Set a) where - showsPrec d s = showSet (toAscList s) + showsPrec p xs = showParen (p > 10) $ + showString "fromList " . shows (toList xs) showSet :: (Show a) => [a] -> ShowS showSet [] @@ -527,17 +540,20 @@ showSet (x:xs) Read --------------------------------------------------------------------} instance (Read a, Ord a) => Read (Set a) where - readsPrec _ = readParen False $ \ r -> - [(fromList xs,t) | ("{",s) <- lex r, - (xs,t) <- readl s] - where readl s = [([],t) | ("}",t) <- lex s] ++ - [(x:xs,u) | (x,t) <- reads s - , (xs,u) <- readl' t] - readl' s = [([],t) | ("}",t) <- lex s] ++ - [(x:xs,v) | (",",t) <- lex s - , (x,u) <- reads t - , (xs,v) <- readl' u] - +#ifdef __GLASGOW_HASKELL__ + readPrec = parens $ prec 10 $ do + Ident "fromList" <- lexP + xs <- readPrec + return (fromList xs) + + readListPrec = readListPrecDefault +#else + readsPrec p = readParen (p > 10) $ \ r -> do + ("fromList",s) <- lex r + (xs,t) <- reads s + return (fromList xs,t) +#endif + {-------------------------------------------------------------------- Typeable/Data --------------------------------------------------------------------} @@ -625,12 +641,18 @@ split x (Bin sy y l r) -- | /O(log n)/. Performs a 'split' but also returns whether the pivot -- element was found in the original set. splitMember :: Ord a => a -> Set a -> (Set a,Bool,Set a) -splitMember x Tip = (Tip,False,Tip) -splitMember x (Bin sy y l r) - = case compare x y of - LT -> let (lt,found,gt) = splitMember x l in (lt,found,join y gt r) - GT -> let (lt,found,gt) = splitMember x r in (join y l lt,found,gt) - EQ -> (l,True,r) +splitMember x t = let (l,m,r) = splitLookup x t in + (l,maybe False (const True) m,r) + +-- | /O(log n)/. Performs a 'split' but also returns the pivot +-- element that was found in the original set. +splitLookup :: Ord a => a -> Set a -> (Set a,Maybe a,Set a) +splitLookup x Tip = (Tip,Nothing,Tip) +splitLookup x (Bin sy y l r) + = case compare x y of + LT -> let (lt,found,gt) = splitLookup x l in (lt,found,join y gt r) + GT -> let (lt,found,gt) = splitLookup x r in (join y l lt,found,gt) + EQ -> (l,Just y,r) {-------------------------------------------------------------------- Utility functions that maintain the balance properties of the tree. @@ -731,6 +753,18 @@ deleteFindMax t Bin _ x l r -> let (xm,r') = deleteFindMax r in (xm,balance x l r') Tip -> (error "Set.deleteFindMax: can not return the maximal element of an empty set", Tip) +-- | /O(log n)/. Retrieves the minimal key of the set, and the set stripped from that element +-- @fail@s (in the monad) when passed an empty set. +minView :: Monad m => Set a -> m (a, Set a) +minView Tip = fail "Set.minView: empty set" +minView x = return (deleteFindMin x) + +-- | /O(log n)/. Retrieves the maximal key of the set, and the set stripped from that element +-- @fail@s (in the monad) when passed an empty set. +maxView :: Monad m => Set a -> m (a, Set a) +maxView Tip = fail "Set.maxView: empty set" +maxView x = return (deleteFindMax x) + {-------------------------------------------------------------------- [balance x l r] balances two trees with value x. @@ -1113,72 +1147,3 @@ prop_List :: [Int] -> Bool prop_List xs = (sort (nub xs) == toList (fromList xs)) -} - -{-------------------------------------------------------------------- - Old Data.Set compatibility interface ---------------------------------------------------------------------} - -{-# DEPRECATED emptySet "Use empty instead" #-} --- | Obsolete equivalent of 'empty'. -emptySet :: Set a -emptySet = empty - -{-# DEPRECATED mkSet "Use fromList instead" #-} --- | Obsolete equivalent of 'fromList'. -mkSet :: Ord a => [a] -> Set a -mkSet = fromList - -{-# DEPRECATED setToList "Use elems instead." #-} --- | Obsolete equivalent of 'elems'. -setToList :: Set a -> [a] -setToList = elems - -{-# DEPRECATED unitSet "Use singleton instead." #-} --- | Obsolete equivalent of 'singleton'. -unitSet :: a -> Set a -unitSet = singleton - -{-# DEPRECATED elementOf "Use member instead." #-} --- | Obsolete equivalent of 'member'. -elementOf :: Ord a => a -> Set a -> Bool -elementOf = member - -{-# DEPRECATED isEmptySet "Use null instead." #-} --- | Obsolete equivalent of 'null'. -isEmptySet :: Set a -> Bool -isEmptySet = null - -{-# DEPRECATED cardinality "Use size instead." #-} --- | Obsolete equivalent of 'size'. -cardinality :: Set a -> Int -cardinality = size - -{-# DEPRECATED unionManySets "Use unions instead." #-} --- | Obsolete equivalent of 'unions'. -unionManySets :: Ord a => [Set a] -> Set a -unionManySets = unions - -{-# DEPRECATED minusSet "Use difference instead." #-} --- | Obsolete equivalent of 'difference'. -minusSet :: Ord a => Set a -> Set a -> Set a -minusSet = difference - -{-# DEPRECATED mapSet "Use map instead." #-} --- | Obsolete equivalent of 'map'. -mapSet :: (Ord a, Ord b) => (b -> a) -> Set b -> Set a -mapSet = map - -{-# DEPRECATED intersect "Use intersection instead." #-} --- | Obsolete equivalent of 'intersection'. -intersect :: Ord a => Set a -> Set a -> Set a -intersect = intersection - -{-# DEPRECATED addToSet "Use 'flip insert' instead." #-} --- | Obsolete equivalent of @'flip' 'insert'@. -addToSet :: Ord a => Set a -> a -> Set a -addToSet = flip insert - -{-# DEPRECATED delFromSet "Use `flip delete' instead." #-} --- | Obsolete equivalent of @'flip' 'delete'@. -delFromSet :: Ord a => Set a -> a -> Set a -delFromSet = flip delete