[project @ 2005-03-15 13:38:27 by simonmar]
[ghc-base.git] / Data / Set.hs
index b357f96..f321abf 100644 (file)
@@ -111,8 +111,7 @@ module Data.Set  (
        delFromSet,     -- :: Ord a => Set a -> a -> Set a
             ) where
 
-import Prelude hiding (filter,foldr,foldl,null,map)
-import Data.Monoid
+import Prelude hiding (filter,foldr,null,map)
 import qualified Data.List as List
 import Data.Typeable
 
@@ -146,12 +145,12 @@ data Set a    = Tip
 
 type Size     = Int
 
+#if __GLASGOW_HASKELL__
+
 {--------------------------------------------------------------------
   A Data instance  
 --------------------------------------------------------------------}
 
-#if __GLASGOW_HASKELL__
-
 -- This instance preserves data abstraction at the cost of inefficiency.
 -- We omit reflection services for the sake of data abstraction.
 
@@ -240,7 +239,7 @@ isProperSubsetOf s1 s2
 
 
 -- | /O(n+m)/. Is this a subset?
--- @(s1 `isSubsetOf` s2)@ tells whether s1 is a subset of s2.
+-- @(s1 `isSubsetOf` s2)@ tells whether @s1@ is a subset of @s2@.
 isSubsetOf :: Ord a => Set a -> Set a -> Bool
 isSubsetOf t1 t2
   = (size t1 <= size t2) && (isSubsetOfX t1 t2)
@@ -250,7 +249,7 @@ isSubsetOfX t Tip = False
 isSubsetOfX (Bin _ x l r) t
   = found && isSubsetOfX l lt && isSubsetOfX r gt
   where
-    (found,lt,gt) = splitMember x t
+    (lt,found,gt) = splitMember x t
 
 
 {--------------------------------------------------------------------
@@ -284,7 +283,7 @@ deleteMax Tip             = Tip
 {--------------------------------------------------------------------
   Union. 
 --------------------------------------------------------------------}
--- | The union of a list of sets: (@unions == foldl union empty@).
+-- | The union of a list of sets: (@'unions' == 'foldl' 'union' 'empty'@).
 unions :: Ord a => [Set a] -> Set a
 unions ts
   = foldlStrict union empty ts
@@ -347,7 +346,7 @@ intersect' t (Bin _ x l r)
   | found     = join x tl tr
   | otherwise = merge tl tr
   where
-    (found,lt,gt) = splitMember x t
+    (lt,found,gt) = splitMember x t
     tl            = intersect' lt l
     tr            = intersect' gt r
 
@@ -379,7 +378,7 @@ partition p (Bin _ x l r)
 ----------------------------------------------------------------------}
 
 -- | /O(n*log n)/. 
--- @map f s@ is the set obtained by applying @f@ to each element of @s@.
+-- @'map' f s@ is the set obtained by applying @f@ to each element of @s@.
 -- 
 -- It's worth noting that the size of the result may be smaller if,
 -- for some @(x,y)@, @x \/= y && f x == f y@
@@ -389,7 +388,7 @@ map f = fromList . List.map f . toList
 
 -- | /O(n)/. The 
 --
--- @mapMonotonic f s == 'map' f s@, but works only when @f@ is monotonic.
+-- @'mapMonotonic' f s == 'map' f s@, but works only when @f@ is monotonic.
 -- /The precondition is not checked./
 -- Semi-formally, we have:
 -- 
@@ -427,7 +426,7 @@ elems s
 {--------------------------------------------------------------------
   Lists 
 --------------------------------------------------------------------}
--- | /O(n)/. Convert the set to an ascending list of elements.
+-- | /O(n)/. Convert the set to a list of elements.
 toList :: Set a -> [a]
 toList s
   = toAscList s
@@ -506,15 +505,6 @@ instance Ord a => Ord (Set a) where
     compare s1 s2 = compare (toAscList s1) (toAscList s2) 
 
 {--------------------------------------------------------------------
-  Monoid 
---------------------------------------------------------------------}
-
-instance Ord a => Monoid (Set a) where
-    mempty = empty
-    mappend = union
-    mconcat = unions
-
-{--------------------------------------------------------------------
   Show
 --------------------------------------------------------------------}
 instance Show a => Show (Set a) where
@@ -603,7 +593,7 @@ filterLt cmp (Bin sx x l r)
 {--------------------------------------------------------------------
   Split
 --------------------------------------------------------------------}
--- | /O(log n)/. The expression (@split x set@) is a pair @(set1,set2)@
+-- | /O(log n)/. The expression (@'split' x set@) is a pair @(set1,set2)@
 -- where all elements in @set1@ are lower than @x@ and all elements in
 -- @set2@ larger than @x@. @x@ is not found in neither @set1@ nor @set2@.
 split :: Ord a => a -> Set a -> (Set a,Set a)
@@ -616,13 +606,13 @@ 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 -> (Bool,Set a,Set a)
-splitMember x Tip = (False,Tip,Tip)
+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 (found,lt,gt) = splitMember x l in (found,lt,join y gt r)
-      GT -> let (found,lt,gt) = splitMember x r in (found,join y l lt,gt)
-      EQ -> (True,l,r)
+      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)
 
 {--------------------------------------------------------------------
   Utility functions that maintain the balance properties of the tree.
@@ -831,7 +821,7 @@ showTree s
 {- | /O(n)/. The expression (@showTreeWith hang wide map@) shows
  the tree that implements the set. If @hang@ is
  @True@, a /hanging/ tree is shown otherwise a rotated tree is shown. If
- @wide@ is true, an extra wide version is shown.
+ @wide@ is 'True', an extra wide version is shown.
 
 > Set> putStrLn $ showTreeWith True False $ fromDistinctAscList [1..5]
 > 4