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

2004-10-30 Thread Keean Schupke
I would have thought it would have been sensible to base floating
point maths on the IEEE spec, as thats what most hardware implements,
and there are libraries to emulate it for everything else. Does haskell use
IEEE primitives for things like sin/cos and sqrt? I am really surprised this
area seems so neglected.
I for one would like to see floats and doubles following the IEEE spec,
complete with constructors for +/- Infinity, NaN, and primitives.
   Keean
Glynn Clements wrote:
MR K P SCHUPKE wrote:
 

Double already has +Inf and -Inf; it's just that Haskell doesn't have
(AFAIK) syntax to write them as constants.
 

In the source for the GHC libraries it uses 1/0 for +Infinity
and -1/0 for -Infinity, so I assume these are the official way to do it.
Personally I would define nicer names:
positiveInfinity :: Double
positiveInfinity = 1/0
	negativeInfinity :: Double
	negativeInfinity = -1/0
   

Or just:
infinity = 1/0
and use -infinity for the negative.
One other nit: isn't the read/show syntax for Haskell98 types supposed
to valid Haskell syntax?
From http://www.haskell.org/onlinereport/derived.html#derived-text
The result of show is a syntactically correct Haskell
expression containing only constants, given the fixity
declarations in force at the point where the type is declared.
[Note: the above sentecne refers specifically to derived instances,
but induction would require that it also holds for base types.]
However:
Prelude let infinity = 1/0 :: Double
Prelude show infinity
Infinity
Prelude read (show infinity) :: Double
Infinity
Prelude Infinity

interactive:1: Data constructor not in scope: `Infinity'
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-29 Thread Keith Wansbrough
I forgot to mention:

With regard to the dangerous practice of using == (as in your `elem` 
example) on Double, every computer scientist or programmer should read 
the following paper at some point in their training:


David Goldberg, What every computer scientist should know about 
floating-point arithmetic. ACM Computing Survey Volume 23 ,  Issue 1  
(March 1991) Pages: 5 - 48.

http://portal.acm.org/citation.cfm?id=103163

--KW 8-)
-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-29 Thread Ben Rudiak-Gould
MR K P SCHUPKE wrote:
 | otherwise = contractSet (contract x0 y0:xs) ys

I think you'll find the original is correct. The first two cases deal with
non-overlapping ranges. The only remaining case is overlapping ranges,
(partial and full overlap) both these cases are dealt with by contract,
and as a result use up both the ranges at the head of both lists, sdo
the merged range is prepended to the output list and the tail is
calculated by passing the unused tails of both lists to contactSet...
Consider the case of merging [(1,2),(3,4)] and [(1,4)]. I think your 
function will produce an answer of [(1,4),(3,4)].

-- Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-29 Thread Ben Rudiak-Gould
Keith Wansbrough wrote:
Which brings me to a question: is there a better way to write -inf and
+inf in Haskell than -1/0 and 1/0?
Shouldn't (minBound :: Double) and (maxBound :: Double) work? They 
don't, but shouldn't they?

-- Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-29 Thread MR K P SCHUPKE
Keith Wansbrough wrote:

Which brings me to a question: is there a better way to write -inf and
+inf in Haskell than -1/0 and 1/0?

Why not do it with types:

data InfDbl = Dbl Double | PositiveInfinity | NegativeInfinity

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-29 Thread Brian Beckman
Very pretty, Keean, though to get it to work in Hugs Nov 2002 I had to
type the following uglier but equivalent syntax

 myInterval = Interval {
isin = (\r -
   if r == 0.6 then True else
   if r  0.7  r  1.0 then True else
   False )
} 

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Keean Schupke
Sent: Wednesday, October 27, 2004 3:53 AM
To: Stijn De Saeger
Cc: [EMAIL PROTECTED]
Subject: Re: [Haskell-cafe] Set of reals...?

I think someone else mentioned using functions earlier, rather than a
datatype why not define:

data Interval = Interval { isin :: Float - Bool }

Then each range becomes a function definition, for example:

myInterval = Interval {
   isin r
  | r == 0.6 = True
  | r  0.7  r  1.0 = True
  | otherwise = False
   }

Then you can test with:

(isin myInterval 0.6)

Keean
   



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-29 Thread Tom Pledger
Keith Wansbrough wrote:
[...]
Your data structure should be something like:
data Interval = Interval {
left :: Double,
   leftopen :: Bool,
   right :: Double,
   rightopen :: Bool
}
data Set = Set [Interval]
If you want more efficiency, you probably want a bintree datastructure 
(search Google for quadtree and octree, and make the obvious 
dimension shift).

An easy-ish special case, if you're only dealing with intervals in one 
dimension, is (untested):

   import Data.FiniteMap
   type IntervalSet k = FiniteMap k (k, Bool, Bool)
   isin :: (Ord k) = k - IntervalSet k - Bool
   k `isin` s
   = case fmToList_GE k s of
   [] - False
   ((k2, (k1, open1, open2)):_) -
   (if open1 then k  k1 else k = k1) 
   (if open2 then k  k2 else k = k2)
where each key in the finite map is the upper end of a range, and each 
element of the finite map contains the lower end of the range and the 
open/closed flags. This sort of thing seems to be the intended use of 
the _GE functions in Data.FiniteMap.

Regards,
Tom
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-29 Thread Glynn Clements

MR K P SCHUPKE wrote:

 Double already has +Inf and -Inf; it's just that Haskell doesn't have
 (AFAIK) syntax to write them as constants.
 
   In the source for the GHC libraries it uses 1/0 for +Infinity
 and -1/0 for -Infinity, so I assume these are the official way to do it.
 
 Personally I would define nicer names:
 
   positiveInfinity :: Double
   positiveInfinity = 1/0
 
   negativeInfinity :: Double
   negativeInfinity = -1/0

Or just:

infinity = 1/0

and use -infinity for the negative.

One other nit: isn't the read/show syntax for Haskell98 types supposed
to valid Haskell syntax?

From http://www.haskell.org/onlinereport/derived.html#derived-text

The result of show is a syntactically correct Haskell
expression containing only constants, given the fixity
declarations in force at the point where the type is declared.

[Note: the above sentecne refers specifically to derived instances,
but induction would require that it also holds for base types.]

However:

Prelude let infinity = 1/0 :: Double
Prelude show infinity
Infinity
Prelude read (show infinity) :: Double
Infinity
Prelude Infinity

interactive:1: Data constructor not in scope: `Infinity'

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-28 Thread Keean Schupke
erm, yes you're right - don't know why that is - seems a fairly
arbitrary decision to me... perhaps someone else knows a good
reason why normal function definiton is not allowed?
Stijn De Saeger wrote:
aha, I see. 
Seems like i still have a long way to go with functional programming. 

final question: i tried to test the code below, but it seems GHCi will
only take the `isin` functions when they are defined in lambda
notation (like isin = (\x - ...)).
Did you run this code too, or were you just sketching me the rough idea? 

Cheers for all the replies by the way, i learnt a great deal here.
stijn.
On Wed, 27 Oct 2004 14:09:36 +0100, Keean Schupke
[EMAIL PROTECTED] wrote:
 

Well, its functional of course:
   union :: Interval - Interval - Interval
   union i j = Interval {
  isin x = isin i x || isin j x
   }
   intersection :: Interval - Interval - Interval
   intersection i j = Interval {
  isin x = isin i x  isin j x
   }
   Keean.

Stijn De Saeger wrote:
   

That seems like a very clean way to define the sets indeed, but how
would you go about implementing operations like intersection,
complement etc... on those structures? define some sort of algebra
over the functions? or extend such sets by adding elements? hm...
sounds interesting,.
thanks,
stijn.
On Wed, 27 Oct 2004 11:52:54 +0100, Keean Schupke
[EMAIL PROTECTED] wrote:
 

I think someone else mentioned using functions earlier,
rather than a datatype why not define:
  data Interval = Interval { isin :: Float - Bool }
Then each range becomes a function definition, for example:
  myInterval = Interval {
 isin r
| r == 0.6 = True
| r  0.7  r  1.0 = True
| otherwise = False
 }
Then you can test with:
  (isin myInterval 0.6)
Keean

   

   

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-28 Thread Ketil Malde
Stijn De Saeger [EMAIL PROTECTED] writes:

 But, like you mentioned in your post, now I find myself needing a
 notion of subset relations, and since you obviously can't define
 equality over functions, i'm stuck again. 

Perhaps one can define an approximate equality, with an error bound?

Define the sets with a maximal boundary, and check points within the
combined boundary.  You can only be sure about the answer if it is
'False', 'True' should be interpreted as maybe :-).  

An inplementation could look something like (untested):

   data RSet = RSet {isin :: Double - Bool, bounds :: (Double,Double) }

   equals :: Double - Rset - RSet - Bool
   equals epsilon s1 s2 = and (map (equals1 s1 s2) [l,l+epsion..h]
   where l = min (fst $ bounds s1) (fst $ bounds s2)
 h = max (snd $ bounds s1) (snd $ bounds s2)

Or you could use randomly sampled values (and perhaps give a
statistical figure for confidence?), or you could try to identify the
boundaries of each set, or..

 Do you know any way around this problem, or have i hit a dead
 end...?

Simulating real numbers on discrete machinery is a mess.  Join the
club :-) 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-28 Thread Stijn De Saeger
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.1500, 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
[EMAIL PROTECTED] 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)
| e0e1 = (s0,e0):union' r0 i1 -- not overlapping
| e1e0 = (s1,e1):union' i0 r1
| s0s1  e0e1 = (s0,e0):union' i0 i1 -- complete overlap
| s1s0  e1e0 = (s1,e1):union' i0 i1
| s1s0  e0e1 = (s1,e0):union' i0 i1 -- partial overlap
| s0s1  e1e0 = (s0,e1):union' i0 i1
| otherwise = union' i0 i1
 
 And subset can be defined similarly...
 
 
 
 Keean.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-28 Thread Glynn Clements

Stijn De Saeger wrote:

 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.

As the result is a BasicSet, the accumulator would need to be a
BasicSet and the operator would need to have type:

BasicSet - Range - BasicSet

This can presumably be implemented as a fold on contract, so
contractSet would essentially be a doubly-nested fold.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Stijn De Saeger
Thanks for the swift reply,
see inline


On Wed, 27 Oct 2004 09:51:29 +0100, Graham Klyne [EMAIL PROTECTED] wrote:
 I think the first question you have to address is whether you really want
 to represent a *set* of reals or an *interval* of reals.  

A set of intervals, I would assume... 
The reason for that is that i will probably end up with 
set theoretic operations like complement, and in that case the
complement of an interval of
reals will have a hole in it somewhere. That's why i represented them
as lists of pairs (lower and upper bound of the sub-interval, so to
speak) , but that will probably get ugly before long.

 Then, some other questions follow:
 - possibly infinite sets within any given interval?

I was not explicitly thinking of  infinite sets, i just wanted to keep
the precision open for now. I would say, up to 4 decimal figures
maximum.

 - open or closed intervals?

closed intervals, but with holes. (see above)

 and probably more.
 
 #g
 --

cheers,
stijn
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Stijn De Saeger
hello

Thanks for the explanation, at first it seemed like enumFromThenTo
would indeed give me the functionality I am looking for. But then all
of GHCi started acting weird while playing around... this is a
copy-paste transcript from the terminal.

*S3 0.5 `elem` [0.0,0.1..1.0]
True
*S3 0.8 `elem` [0.6,0.7..1.0]
False
*S3 0.8 `elem` [0.6,0.7..1.0]
False
*S3 [0.6,0.7..0.9]
[0.6,0.7,0.7999,0.8999]
*S3 



in your reply you wrote :
 However, you can't specify infinitesimally small steps, nor increment
 according to the resolution of the floating point type (at least, not
 using the enumeration syntax; you *could* do it manually using integer
 enumerations and encodeFloat, but that wouldn't be particularly
 practical).

Is this what you were referring to? i wouldn't say 0.1 is an
infinitesimal small step.
why would the floating point step size work the first time but not the
second? confusing...

thanks for the help though, much appreciated.
stijn.


On Wed, 27 Oct 2004 10:31:28 +0100, Glynn Clements
[EMAIL PROTECTED] wrote:
 
 Stijn De Saeger wrote:
 
  I'm new to this list, as well as to haskell, so this question probably
  has newbie written all over it.
  I'm thinking of a way to represent a set of reals, say the reals
  between 0.0 and 1.0.  Right now I am just using a pair of Float to
  represent the lower and upper bounds of the set, but i have this dark
  throbbing feeling that there should be a more haskellish way to do
  this, using laziness.
  List comprehensions are out it seems, because they increment with
  integer steps... (obviously). In other words,  0.5 `inSet` (Set
  [0.0..1.0])   returns False.
 
 That form ([0.0..1.0]) is syntactic sugar for enumFromTo. There's also
 enumFromThenTo, for which you can use the syntax:
 
 [0.0,0.1..1.0]
 
 However, you can't specify infinitesimally small steps, nor increment
 according to the resolution of the floating point type (at least, not
 using the enumeration syntax; you *could* do it manually using integer
 enumerations and encodeFloat, but that wouldn't be particularly
 practical).
 
 The only practical way to deal with large sets of reals is to use your
 own representation and write your own operators on it (or hope that
 someone else has written such a library). Generating massive lists (or
 other structures) then testing for membership won't result in the
 lists being optimised away.
 
 --
 Glynn Clements [EMAIL PROTECTED]

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Keean Schupke
I think someone else mentioned using functions earlier,
rather than a datatype why not define:
   data Interval = Interval { isin :: Float - Bool }
Then each range becomes a function definition, for example:
   myInterval = Interval {
  isin r
 | r == 0.6 = True
 | r  0.7  r  1.0 = True
 | otherwise = False
  }
Then you can test with:
   (isin myInterval 0.6)
Keean
  


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Stijn De Saeger
That seems like a very clean way to define the sets indeed, but how
would you go about implementing operations like intersection,
complement etc... on those structures? define some sort of algebra
over the functions? or extend such sets by adding elements? hm...
sounds interesting,.

thanks,
stijn.


On Wed, 27 Oct 2004 11:52:54 +0100, Keean Schupke
[EMAIL PROTECTED] wrote:
 I think someone else mentioned using functions earlier,
 rather than a datatype why not define:
 
 data Interval = Interval { isin :: Float - Bool }
 
 Then each range becomes a function definition, for example:
 
 myInterval = Interval {
isin r
   | r == 0.6 = True
   | r  0.7  r  1.0 = True
   | otherwise = False
}
 
 Then you can test with:
 
 (isin myInterval 0.6)
 
 Keean
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Cale Gibbard
This has already been mostly answered by Ben's post, but to rephrase
this, basically you do intersection by producing the function which
returns the AND of the two functions given, and union by producing the
function which gives the OR of the two functions given. Complement is
just logical NOT. Basically, any set operation you want turns into a
logical operation using as information just a single arbitrary point,
and the two (or more) predicates given. You can also do arithmetic on
the sets by modifying the incoming point in a suitable way before
passing it on to the predicate.

 - Cale

On Wed, 27 Oct 2004 21:36:55 +0900, Stijn De Saeger
[EMAIL PROTECTED] wrote:
 That seems like a very clean way to define the sets indeed, but how
 would you go about implementing operations like intersection,
 complement etc... on those structures? define some sort of algebra
 over the functions? or extend such sets by adding elements? hm...
 sounds interesting,.
 
 thanks,
 stijn.
 
 On Wed, 27 Oct 2004 11:52:54 +0100, Keean Schupke
 
 
 [EMAIL PROTECTED] wrote:
  I think someone else mentioned using functions earlier,
  rather than a datatype why not define:
 
  data Interval = Interval { isin :: Float - Bool }
 
  Then each range becomes a function definition, for example:
 
  myInterval = Interval {
 isin r
| r == 0.6 = True
| r  0.7  r  1.0 = True
| otherwise = False
 }
 
  Then you can test with:
 
  (isin myInterval 0.6)
 
  Keean
 
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Keean Schupke
Well, its functional of course:
   union :: Interval - Interval - Interval
   union i j = Interval {
  isin x = isin i x || isin j x
   }
   intersection :: Interval - Interval - Interval
   intersection i j = Interval {
  isin x = isin i x  isin j x
   }
   Keean.
Stijn De Saeger wrote:
That seems like a very clean way to define the sets indeed, but how
would you go about implementing operations like intersection,
complement etc... on those structures? define some sort of algebra
over the functions? or extend such sets by adding elements? hm...
sounds interesting,.
thanks,
stijn.
On Wed, 27 Oct 2004 11:52:54 +0100, Keean Schupke
[EMAIL PROTECTED] wrote:
 

I think someone else mentioned using functions earlier,
rather than a datatype why not define:
   data Interval = Interval { isin :: Float - Bool }
Then each range becomes a function definition, for example:
   myInterval = Interval {
  isin r
 | r == 0.6 = True
 | r  0.7  r  1.0 = True
 | otherwise = False
  }
Then you can test with:
   (isin myInterval 0.6)
Keean
   

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Glynn Clements

Stijn De Saeger wrote:

 Thanks for the explanation, at first it seemed like enumFromThenTo
 would indeed give me the functionality I am looking for. But then all
 of GHCi started acting weird while playing around... this is a
 copy-paste transcript from the terminal.
 
 *S3 0.5 `elem` [0.0,0.1..1.0]
 True
 *S3 0.8 `elem` [0.6,0.7..1.0]
 False
 *S3 0.8 `elem` [0.6,0.7..1.0]
 False
 *S3 [0.6,0.7..0.9]
 [0.6,0.7,0.7999,0.8999]
 *S3 
 
 

Floating point has limited precision, and uses binary rather than
decimal, so you can't exactly represent multiples of 1/10 as
floating-point values. Internally, the elements of the list would
actually be out by a relative error of ~2e-16 for double-precision,
~1e-7 for single precision, but the code which converts to decimal
representation for printing rounds it.

However, Haskell does support rationals:

Prelude [6/10 :: Rational,7/10..9/10]
[3 % 5,7 % 10,4 % 5,9 % 10]
Prelude 4/5 `elem` [6/10 :: Rational,7/10..9/10]
True

 in your reply you wrote :
  However, you can't specify infinitesimally small steps, nor increment
  according to the resolution of the floating point type (at least, not
  using the enumeration syntax; you *could* do it manually using integer
  enumerations and encodeFloat, but that wouldn't be particularly
  practical).
 
 Is this what you were referring to? i wouldn't say 0.1 is an
 infinitesimal small step.

No; you could realistically use much smaller steps than that. My point
was that you can't realistically use sufficiently small steps that
values won't fall through the cracks:

Prelude 0.61 `elem` [0.6,0.7..0.9]
False

Whilst you could, without too much effort, enumerate a range of
floating-point values such that all intermediate values were included,
the resulting list would be massive. Single precision floating-point
uses a 24-bit mantissa, so an exhaustive iteration of the range
[0.5..1.0] would have 2^24+1 elements.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Stijn De Saeger
aha, I see. 
Seems like i still have a long way to go with functional programming. 

final question: i tried to test the code below, but it seems GHCi will
only take the `isin` functions when they are defined in lambda
notation (like isin = (\x - ...)).
Did you run this code too, or were you just sketching me the rough idea? 

Cheers for all the replies by the way, i learnt a great deal here.
stijn.


On Wed, 27 Oct 2004 14:09:36 +0100, Keean Schupke
[EMAIL PROTECTED] wrote:
 Well, its functional of course:
 
 union :: Interval - Interval - Interval
 union i j = Interval {
isin x = isin i x || isin j x
 }
 
 intersection :: Interval - Interval - Interval
 intersection i j = Interval {
isin x = isin i x  isin j x
 }
 
 Keean.
 
 
 
 
 Stijn De Saeger wrote:
 
 That seems like a very clean way to define the sets indeed, but how
 would you go about implementing operations like intersection,
 complement etc... on those structures? define some sort of algebra
 over the functions? or extend such sets by adding elements? hm...
 sounds interesting,.
 
 thanks,
 stijn.
 
 
 On Wed, 27 Oct 2004 11:52:54 +0100, Keean Schupke
 [EMAIL PROTECTED] wrote:
 
 
 I think someone else mentioned using functions earlier,
 rather than a datatype why not define:
 
 data Interval = Interval { isin :: Float - Bool }
 
 Then each range becomes a function definition, for example:
 
 myInterval = Interval {
isin r
   | r == 0.6 = True
   | r  0.7  r  1.0 = True
   | otherwise = False
}
 
 Then you can test with:
 
 (isin myInterval 0.6)
 
 Keean
 
 
 
 
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-10-27 Thread Stijn De Saeger
Thank you, 
I eventually tried to go with this approad, after a few people's
recommendations.
But, like you mentioned in your post, now I find myself needing a
notion of subset relations, and since you obviously can't define
equality over functions, i'm stuck again. Do you know any way around
this problem, or have i hit a dead end...?

stijn.


On Wed, 27 Oct 2004 10:50:24 +0100, Ben Rudiak-Gould
[EMAIL PROTECTED] wrote:
 One idea that might not occur to a newcomer is to represent each set by
 a function with a type like (Double - Bool), implementing the set
 membership operation. This makes set-theoretic operations easy: the
 complement of s is not.s (though watch out for NaNs!), the union of s
 and t is (\x - s x || t x), and so on. Open, closed, and half-open
 intervals are easy too. The big limitation of this representation is
 that there's no way to inspect a set except by testing particular values
 for membership, but depending on your application this may not be a problem.
 
 -- Ben
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe