Stijn De Saeger wrote:

>>data Bound = I Double | E Double deriving (Eq, Show, Ord) >>data Interval = Il Bound Bound | Nil Bound Bound deriving (Eq,Ord) >
>>isIn :: Double -> Interval -> Bool
>>isIn r (Nil x y) = not (isIn r (Il x y))
>>isIn r (Il (I x) (I y)) = r >= x && r <= y
>>isIn r (Il (I x) (E y)) = r >= x && r < y
>>isIn r (Il (E x) (I y)) = r > x && r <= y
>>isIn r (Il (E x) (E y)) = r > x && r < y


If performance is the main concern, I would flatten the data structure:

   data Interval = IlII Double Double
                 | IlIE Double Double
                 | IlEI Double Double
                 | IlEE Double Double
                 | NilII Double Double
                 | NilIE Double Double
                 | NilEI Double Double
                 | NilEE Double Double

   isIn :: Double -> Interval -> Bool
   isIn r (IlII x y) = r >= x && r <= y
   isIn r (IlIE x y) = r >= x && r < y
   isIn r (IlEI x y) = r > x && r <= y
   isIn r (IlEE x y) = r > x && r < y
   isIn r (NilII x y) = r < x || r > y
   isIn r (NilIE x y) = r < x || r >= y
   isIn r (NilEI x y) = r <= x || r > y
   isIn r (NilEE x y) = r <= x || r >= y

Depending on your application you might not need all of those cases.

Another neat trick you can pull is to take advantage of the fact that Double is actually a discrete type, like Int, and you can therefore get away with closed intervals only:

   data Interval = Il Double Double | Nil Double Double

   isIn :: Double -> Interval -> Bool
   isIn r (Il x y) = r >= x && r <= y
   isIn r (Nil x y) = r < x || r > y

But this requires nextLargestDouble and nextSmallestDouble functions. I don't know if Haskell provides them. Also, you could run into trouble with wider-than-Double intermediate values.

Finally, if you never do anything with intervals except pass them to isIn, you can do this:

   type Interval = Double -> Bool

   isIn r i = i r

-- Ben

_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to