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

Stijn De Saeger stijndesaeger at gmail.com
Thu Oct 28 22:30:04 EDT 2004


Hi again,

yes, i decided to go with my first idea after all and represent
real-valued sets as a list of ranges. It went pretty ok for a while,
but then inevitably new questions come up... *sigh*. i'll get this to
work eventually... maybe. :-)

for anyone still interested in the topic, here's where i got :

so, define basic sets as a list of ranges, a range being defined as a pair
representing the lower and upper bound.

> type Range = (Float, Float)
> type BasicSet = [Range]

some test sets:

> a,b :: BasicSet
> b = [(0.0, 1.0), (3.1415, 5.8), (22.0, 54.8)]
> a = [(0.3, 0.1), (3.15000000, 3.99), (1.0,1.0), (4.0, 4.1)]

some helper functions for working with Ranges :

> inRange :: Float -> Range -> Bool
> inRange x y = (x >= (fst y) && x <= (snd y))

> intersectRange :: Range -> Range -> Range
> intersectRange x y = ((max (fst x) (fst y)), (min (snd x) (snd y)))

> subRange :: Range -> Range -> Bool
> subRange x y = (fst x) >= (fst y) && (snd x) <= (snd y)

this allows you do check for subsets pretty straightforwardly... 

> subSet :: BasicSet -> BasicSet -> Bool
> subSet [] _ = True
> subSet (x:xs) ys = if or [x `subRange` y | y <- ys] 
>	             then subSet xs ys
>		     else False

Now, for unions I tried the following: 
to take the union of two BasicSets, just append them and contract the result.
contracting meaning: merge overlapping intervals.

> contract :: Range -> Range -> BasicSet
> contract (x1,y1) (x2,y2) 
>   | x2 <= y1 = if x2 >= x1 then [(x1, (max y1 y2))] else 
>	         if y2 >= x1 then [(x2, (max y1 y2))] else [(x2,y2), (x1,y1)]
>   | x1 <= y2 = if x1 >= x2 then [(x2, (max y1 y2))] else 
>	         if y1 >= x2 then [(x1, (max y1 y2))] else [(x1,y1), (x2,y2)]
>   | x1 <= x2 = [(x1,y1), (x2, y2)]


Now generalizing this from Ranges to BasicSets is where i got stuck.
In my limited grasp of haskell and FP, this contractSet function below
is just crying for the use of a fold operation, but i can't for the
life of me see how to do it.

> contractSet :: BasicSet -> BasicSet
> contractSet [] = []
> contractSet (x:xs) = foldl contract x xs    -- this doesn't work, though...

I'll probably find a way to get around this eventually. 
I just wanted to keep the conversation going a bit longer for those
that are still interested.

cheers,
stijn

On Thu, 28 Oct 2004 11:09:36 +0100, Keean Schupke
<k.schupke at imperial.ac.uk> wrote:
> Subsets can be done like this:
> 
> myInterval = Interval {
>    isin = \n -> case n of
>       r  | r == 0.3 -> True
>          | r > 0.6 && r < 1.0 -> True
>          | otherwise -> False,
>    rangein = \(s,e) -> case (s,e) of
>       (i,j) | i==0.3 && j==0.3 -> True
>             | i>=0.6 && j<=1.0 -> True
>             | otherwise -> False,
>    subset = \s -> rangein s (0.3,0.3) && rangein s (0.6,1.0)
>    }
> 
> The problem now is how to calculate the union of two sets... you cannot
> efficiently union the two rangein functions of two sets. Its starting to
> look
> like you need to use a data representation to allow all the
> functionality you
> require. Something like a list of pairs:
> 
>     [(0.3,0.3),(0.6,1.0)]
> 
> where each pair is the beginning and end of a range (or the same)... If you
> build your functions to order the components, then you may want to protect
> things with a type:
> 
>     newtype Interval = Interval [(Double,Double)]
> 
> isin then becomes:
> 
>     contains :: Interval -> Double -> Bool
>     contains (Interval ((i,j):rs)) n
>        | i<=n && n<=j = True
>        | otherwise = contains (Interval rs) n
>     contains _ _ = False
> 
>     union :: Interval -> Interval -> Interval
>     union (Interval i0) (Interval i1) = Interval (union' i0 i1)
> 
>     union' :: [(Double,Double)] -> [(Double,Double)] -> [(Double,Double)]
>     union' i0@((s0,e0):r0) i1@((s1,e1):r1)
>        | e0<e1 = (s0,e0):union' r0 i1 -- not overlapping
>        | e1<e0 = (s1,e1):union' i0 r1
>        | s0<s1 && e0>e1 = (s0,e0):union' i0 i1 -- complete overlap
>        | s1<s0 && e1>e0 = (s1,e1):union' i0 i1
>        | s1<s0 && e0>e1 = (s1,e0):union' i0 i1 -- partial overlap
>        | s0<s1 && e1>e0 = (s0,e1):union' i0 i1
>        | otherwise = union' i0 i1
> 
> And subset can be defined similarly...
> 
> 
> 
>     Keean.
>


More information about the Haskell-Cafe mailing list