Re: [Haskell-cafe] Perl-style numeric type

2007-06-19 Thread Dougal Stanton

On 19/06/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:


PS Also, did anyone get my e-mail to this list of June 8 about Template
Haskell and QuickCheck?  If you did and it's just that no one knows the
answer to my questions, no problem.  But I was subscribed in a strange way
(through the fa.haskell Google group) and I'm beginning to suspect that
perhaps my message never actually got sent over the list.  If so I could
resend it now that I'm subscribed by more conventional means.


I've heard it said before that Google Groups doesn't properly interact
with the ML. The Haskell Cafe archives for this month [1] seem to
confirm that hypothesis, as there's only one post from you: this one.

[1]: 

Cheers,

D.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-19 Thread Lennart Augustsson

I implemented a number type like that in Haskell ca 1992, called noddy
numbers (I think John Hughes named them).  I don't think I still have them,
but it would be easy to do again.  Except for the fact that there are so
many way you and none of them are quite satisfactory.

 -- Lennart

On 6/19/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:


Hi all,

I've started developing a library to support a "Perl-style" numeric type
that "does the right thing" without having to worry too much about types.
Explicit static typing of numeric types is really great most of the time,
and certainly a good idea for larger projects, but probably everyone's had
one of those experiences where you just want to write some simple, "one-off"
numeric code that ends up getting cluttered with all sorts of fromIntegers
and whatnot just to make the type checker happy.  The idea would be to
internally use either an Integer, Rational, or Double, and transparently
convert between them as necessary.  I know I would enjoy having such a
numeric type for use in, e.g. programs to solve Project Euler problems.

But before I get too far (it looks like it will be straightforward yet
tedious to implement), I thought I would throw the idea out there and see if
anyone knows of anything similar that has already been done before (a
cursory search of the wiki didn't turn up anything).  I don't want to
reinvent the wheel here.

thanks!
-Brent

PS Also, did anyone get my e-mail to this list of June 8 about Template
Haskell and QuickCheck?  If you did and it's just that no one knows the
answer to my questions, no problem.  But I was subscribed in a strange way
(through the fa.haskell Google group) and I'm beginning to suspect that
perhaps my message never actually got sent over the list.  If so I could
resend it now that I'm subscribed by more conventional means.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-19 Thread Brent Yorgey

Good to know I'm only 15 years behind the times. =)

Well, I think I'll continue with my implementation (at the very least it's
an interesting way to learn about all the numeric classes in the Prelude),
although I'll be interested in your comments when I get around to releasing
it.  I don't expect there would be any fully satisfactory way of doing it,
but I think that has less to do with Haskell than it does with the very
nature of trying to mix up numeric types (Perl's system of numeric types
isn't quite satisfactory either!).

-Brent

On 6/19/07, Lennart Augustsson <[EMAIL PROTECTED]> wrote:


I implemented a number type like that in Haskell ca 1992, called noddy
numbers (I think John Hughes named them).  I don't think I still have them,
but it would be easy to do again.  Except for the fact that there are so
many way you and none of them are quite satisfactory.

  -- Lennart

On 6/19/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:

> Hi all,
>
> I've started developing a library to support a "Perl-style" numeric type
> that "does the right thing" without having to worry too much about types.
> Explicit static typing of numeric types is really great most of the time,
> and certainly a good idea for larger projects, but probably everyone's had
> one of those experiences where you just want to write some simple, "one-off"
> numeric code that ends up getting cluttered with all sorts of fromIntegers
> and whatnot just to make the type checker happy.  The idea would be to
> internally use either an Integer, Rational, or Double, and transparently
> convert between them as necessary.  I know I would enjoy having such a
> numeric type for use in, e.g. programs to solve Project Euler problems.
>
> But before I get too far (it looks like it will be straightforward yet
> tedious to implement), I thought I would throw the idea out there and see if
> anyone knows of anything similar that has already been done before (a
> cursory search of the wiki didn't turn up anything).  I don't want to
> reinvent the wheel here.
>
> thanks!
> -Brent
>
> PS Also, did anyone get my e-mail to this list of June 8 about Template
> Haskell and QuickCheck?  If you did and it's just that no one knows the
> answer to my questions, no problem.  But I was subscribed in a strange way
> (through the fa.haskell Google group) and I'm beginning to suspect that
> perhaps my message never actually got sent over the list.  If so I could
> resend it now that I'm subscribed by more conventional means.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-19 Thread Tom Phoenix

On 6/19/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:


I've started developing a library to support a "Perl-style" numeric type
that "does the right thing" without having to worry too much about types.



But before I get too far (it looks like it will be straightforward yet
tedious to implement), I thought I would throw the idea out there and see if
anyone knows of anything similar that has already been done before


Do you know about Pugs?

   http://www.pugscode.org/

Hope this helps!

--Tom Phoenix
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Henning Thielemann

On Tue, 19 Jun 2007, Brent Yorgey wrote:

> But before I get too far (it looks like it will be straightforward yet
> tedious to implement), I thought I would throw the idea out there and see if
> anyone knows of anything similar that has already been done before (a
> cursory search of the wiki didn't turn up anything).  I don't want to
> reinvent the wheel here.

Do you have some examples, where such a data type is really superior to
strong typing? There are examples like computing the average, where a
natural number must be converted to a different type:
  average xs = sum xs / fromIntegral (length xs)
 but this one can easily replaced by
  average xs = sum xs / genericLength xs

 Thus, before you spend much time on making Haskell closer to Perl, how
about collecting such examples, work out ways how to solve them elegantly
in the presence of strong typing and set up a wiki page explaining how to
work with strongly typed numbers? I think, this topic really belongs to
  http://www.haskell.org/haskellwiki/Category:FAQ
 Strongly typed numbers are there for good reason: There is not one type
that can emulate the others. Floating point numbers are imprecise, a/b*b=a
does not hold in general. Rationals are precise but pi and sqrt 2 are not
rational. People have designed languages again and again which ignore
this, and they failed. See e.g. MatLab which emulates an integer (and even
a boolean value) by a complex valued 1x1 matrix.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Brent Yorgey

On 6/20/07, Henning Thielemann <[EMAIL PROTECTED]> wrote:



Do you have some examples, where such a data type is really superior to
strong typing? There are examples like computing the average, where a
natural number must be converted to a different type:
  average xs = sum xs / fromIntegral (length xs)
but this one can easily replaced by
  average xs = sum xs / genericLength xs

Thus, before you spend much time on making Haskell closer to Perl, how
about collecting such examples, work out ways how to solve them elegantly
in the presence of strong typing and set up a wiki page explaining how to
work with strongly typed numbers? I think, this topic really belongs to
  http://www.haskell.org/haskellwiki/Category:FAQ
Strongly typed numbers are there for good reason: There is not one type
that can emulate the others. Floating point numbers are imprecise, a/b*b=a
does not hold in general. Rationals are precise but pi and sqrt 2 are not
rational. People have designed languages again and again which ignore
this, and they failed. See e.g. MatLab which emulates an integer (and even
a boolean value) by a complex valued 1x1 matrix.



That's a good idea too, perhaps I will do that.  This would be a good thing
to have on the wiki since it's clearly an issue that people learning Haskell
struggle with (I certainly did).  I also want to make clear, though, that I
certainly appreciate the reasons for strongly typed numbers.  I am not
trying to make Haskell closer to Perl in general (God forbid!), or in any
way advocate for doing away with strongly typed numbers, but only to create
a library for working more conveniently with numeric types in small programs
where the typing is not as important.  To give a couple quick examples,
based on what I have already implemented:

*EasyNum> 1 / 3
0.
*EasyNum> 1 / 3 :: EasyNum
1/3
*EasyNum> 1 / floor pi

:1:4:
   Ambiguous type variable `t' in the constraints:
 `Integral t' arising from use of `floor' at :1:4-11
 `Fractional t' arising from use of `/' at :1:0-11
   Probable fix: add a type signature that fixes these type variable(s)
*EasyNum> 1 / floor pi :: EasyNum
1/3

I would have also put in the example of 1 / pi :: EasyNum and show it
printing out a double value instead of the rational it prints with 1 / 3,
except I haven't yet implemented the instance of Floating. =)

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Henning Thielemann

On Wed, 20 Jun 2007, Brent Yorgey wrote:

> That's a good idea too, perhaps I will do that.  This would be a good thing
> to have on the wiki since it's clearly an issue that people learning Haskell
> struggle with (I certainly did).  I also want to make clear, though, that I
> certainly appreciate the reasons for strongly typed numbers.  I am not
> trying to make Haskell closer to Perl in general (God forbid!), or in any
> way advocate for doing away with strongly typed numbers, but only to create
> a library for working more conveniently with numeric types in small programs
> where the typing is not as important.  To give a couple quick examples,
> based on what I have already implemented:
>
> *EasyNum> 1 / 3
> 0.
> *EasyNum> 1 / 3 :: EasyNum
> 1/3
> *EasyNum> 1 / floor pi
>
> :1:4:
> Ambiguous type variable `t' in the constraints:
>   `Integral t' arising from use of `floor' at :1:4-11
>   `Fractional t' arising from use of `/' at :1:0-11
> Probable fix: add a type signature that fixes these type variable(s)
> *EasyNum> 1 / floor pi :: EasyNum
> 1/3

How about
 1 % floor pi

?

Already two examples for the Wiki which I used to start the Wiki article:
  http://www.haskell.org/haskellwiki/Generic_numeric_type
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Brent Yorgey

On 6/20/07, Henning Thielemann <[EMAIL PROTECTED]> wrote:



How about
1 % floor pi

?

Already two examples for the Wiki which I used to start the Wiki article:
  http://www.haskell.org/haskellwiki/Generic_numeric_type



What about the function isSquare?

isSquare :: (Integral a) => a -> Bool
isSquare n = (floor . sqrt $ fromIntegral n) ^ 2 == n

Is there any way to write that without the fromIntegral?  If you leave out
the fromIntegral and the explicit type signature, it type checks, but the
type constraints are such that there are no actual types that you can call
it on.

As I think about it more, I guess one of my biggest goals is essentially to
have an integral type which can silently convert to a rational or floating
type when necessary (e.g. you should be able to call sqrt on an integral
type and have it implicitly convert to floating).  Perhaps this actually has
less to do with scripting-language-style numeric types than it does with
languages (e.g. Java) that do implicit type conversions in directions where
no information is lost -- e.g. you can take the sqrt of an int and get a
double, but if you want to change a double into an int you have to
explicitly truncate or round or whatever.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Henning Thielemann

On Wed, 20 Jun 2007, Brent Yorgey wrote:

> isSquare :: (Integral a) => a -> Bool
> isSquare n = (floor . sqrt $ fromIntegral n) ^ 2 == n
>
> Is there any way to write that without the fromIntegral?  If you leave out
> the fromIntegral and the explicit type signature, it type checks, but the
> type constraints are such that there are no actual types that you can call
> it on.

This is a good example: You wonder, whether fromIntegral can be avoided. I
wonder, whether fromIntegral fulfills the task at all. Actually, it does
not. It fails for big integers, because there is no Double that represents
10^1000. That is you have to rescale the number. Even below this number,
'isSquare' will fail due to rounding errors:

Prelude> isSquare ((10^100)^2)
False

 That is, 'isSquare' does not do what it promises.

Btw. I would at least use 'round' because the Double sqrt might be
slightly below the true root.

Unfortunately we don't have access to the native sqrt implementation of
the GNU multiprecision library GMP so we have to roll our own version:

(^!) :: Num a => a -> Int -> a
(^!) x n = x^n

{- |
Compute the floor of the square root of an Integer.
-}
squareRoot :: Integer -> Integer
squareRoot 0 = 0
squareRoot 1 = 1
squareRoot n =
   let twopows = iterate (^!2) 2
   (lowerRoot, lowerN) =
  last $ takeWhile ((n>=) . snd) $ zip (1:twopows) twopows
   newtonStep x = div (x + div n x) 2
   iters = iterate newtonStep (squareRoot (div n lowerN) * lowerRoot)
   isRoot r  =  r^!2 <= n && n < (r+1)^!2
   in  head $ dropWhile (not . isRoot) iters



Btw. I think that 'squareRoot' is the basic problem and I'd like to change
the Wiki article accordingly.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Henning Thielemann

On Wed, 20 Jun 2007, Henning Thielemann wrote:

> Btw. I think that 'squareRoot' is the basic problem and I'd like to
> change the Wiki article accordingly.

I see that your experience makes only sense for isSquare, so I simply add
squareRoot as another example.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe