Set.intersection

Christian Maeder maeder at tzi.de
Thu Sep 15 10:51:26 EDT 2005


Christian Maeder wrote:
> Set.intersection is neither left- nor right-biased but biased towards 
> the smaller set. I think that needs to be changed (and that may require 
> a function splitLookup).

Below is my code proposal. I'm not sure if splitLookup should be 
exported. And I'm not sure if splitMember should remain as it is (more 
efficient?) or should be reimplemented using splitLookup (better reuse).

The new intersection function is left-biased and traverses the smaller 
tree also in every recursive call (but I'm not sure if that's better).
The comment "Intersection is more efficient on (bigset `intersection` 
smallset)" needs to be deleted anyway as it is already wrong for the 
current version.

Christian


-- | /O(n+m)/. The intersection of two sets.
intersection :: Ord a => Set a -> Set a -> Set a
intersection Tip t = Tip
intersection t Tip = Tip
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


splitMember :: Ord a => a -> Set a -> (Set a,Bool,Set a)
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)



More information about the Glasgow-haskell-users mailing list