[Haskell-cafe] Set of reals...?

Ben Rudiak-Gould Benjamin.Rudiak-Gould at cl.cam.ac.uk
Fri Oct 29 07:51:19 EDT 2004


Keean Schupke wrote:

 >    contractSet :: BasicSet -> BasticSet -> BasicSet
 >    contractSet x@(x0@(sx,ex):xs) y@(y0:(sy,ey):ys)
 >        | ex < sy = x0:contractSet xs y
 >        | sy < sx = y0:contractSet x ys
 >        | otherwise = contract x0 y0:contractSet xs ys

I think the last line needs to be something like

       | otherwise = contractSet (contract x0 y0:xs) ys

I'm not sure that's correct, though.

Another option is to represent a set as an unpaired list of switchover 
points, i.e. points which are at the beginning or end of an interval. 
Then binary set ops look just like a sorted list merge, except that you 
omit result values that don't change the membership property:

    setUnion        = setOp 14
    setIntersection = setOp 8
    setDifference   = setOp 2

    setOp :: Int -> Int -> BasicSet -> BasicSet -> BasicSet

    setOp opTable = helper 0 where

      helper state (x:xs) (y:ys) =
        case compare x y of
          EQ -> stateSwitch state 3 x (helper xs ys)
          LT -> stateSwitch state 1 x (helper xs (y:ys))
          EQ -> stateSwitch state 2 y (helper (x:xs) ys)
      helper (x:xs) [] = stateSwitch state 1 x (helper xs [])
      helper [] (y:ys) = stateSwitch state 2 x (helper [] ys)

      stateSwitch state mask xy xs ys =
        let newState = state `xor` mask
            tail = helper newState xs ys
        in
          if testBit opTable state == testBit opTable newState
            then tail else xy:tail

This may be as simple as you're going to get for a range representation 
(especially given that it handles all three interesting binary set 
operations in one function).

Unfortunately this technique will not handle endpoints correctly -- e.g. 
the intersection of the range (1,2) and (2,3) will be the empty set 
instead of (2,2). We can solve this elegantly by putting the crossover 
points *between* two real numbers:

    data Side = JustBefore | JustThere | JustAfter  deriving Ord
    data Near r = Near !r !Side                     deriving Ord

JustThere is included so that you can easily compare crossover points 
with actual numbers when testing for set membership. As an added benefit 
that you get open/closed interval support for free.

You can also handle set complement easily, either by adding/removing an 
initial value that's JustBefore -infinity, or by adding a Bool to the 
set representation and using it to initialize the state parameter when 
you iterate through the list.

-- Ben



More information about the Haskell-Cafe mailing list