[Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Barak A. Pearlmutter
In fiddling around with some numeric code in Haskell, I noticed some
issues.  Basically, you get warnings if you write

  energy mass = mass * c^2

but not if you write

  energy mass = mass * c * c

which seems a bit perverse.
Some more examples are below.

I understand the inference issues that cause this, but common innocuous
cases could---and I would argue, should---be addressed in ad-hoc ways.
--
Barak A. Pearlmutter
 Hamilton Institute  Dept Comp Sci, NUI Maynooth, Co. Kildare, Ireland
 http://www.bcl.hamilton.ie/~barak/

 transcript 

$ cat two.hs

main :: IO ()
main = do
  print 1
  print ((2::Float)^3)
  print  
  print (::Int)

-- Each of the four numeric expressions printed above gives a
-- compile-time warning.  Except the last, which is the only one that is
-- actually incorrect.  Maybe ghc could eliminate some of these warnings
-- by adding extra reasonableness guards.  E.g., if the 2nd argument of
-- (^) is a constant that fits in an Int, just do that.  Basically, if
-- used as an argument to a function which has no danger of overflow,
-- default to Int without warning.  And if a constant doesn't fit in an
-- Int, jamming it into one is an error.  Or at least a warning!

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.6.2

$ ghc -Wall two.hs
[1 of 1] Compiling Main ( two.hs, two.o )

two.hs:3:9: Warning:
Defaulting the following constraint(s) to type `Integer'
  (Num a0) arising from the literal `1' at two.hs:3:9
  (Show a0) arising from a use of `print' at two.hs:3:3-7
In the first argument of `print', namely `1'
In a stmt of a 'do' block: print 1
In the expression:
  do { print 1;
   print ((2 :: Float) ^ 3);
   print ;
   print ( :: Int) }

two.hs:4:20: Warning:
Defaulting the following constraint(s) to type `Integer'
  (Integral b0) arising from a use of `^' at two.hs:4:20
  (Num b0) arising from the literal `3' at two.hs:4:21
In the first argument of `print', namely `((2 :: Float) ^ 3)'
In a stmt of a 'do' block: print ((2 :: Float) ^ 3)
In the expression:
  do { print 1;
   print ((2 :: Float) ^ 3);
   print ;
   print ( :: Int) }

two.hs:5:10: Warning:
Defaulting the following constraint(s) to type `Integer'
  (Num a0)
arising from the literal `'
at two.hs:5:10-41
  (Show a0) arising from a use of `print' at two.hs:5:3-7
In the first argument of `print', namely
  `'
In a stmt of a 'do' block: print 
In the expression:
  do { print 1;
   print ((2 :: Float) ^ 3);
   print ;
   print ( :: Int) }
Linking two ...

$ ./two
1
8.0

-5035712355010463517

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Tom Ellis
On Wed, Apr 10, 2013 at 03:38:35PM +0100, Barak A. Pearlmutter wrote:
 In fiddling around with some numeric code in Haskell, I noticed some
 issues.  Basically, you get warnings if you write
 
   energy mass = mass * c^2
 
 but not if you write
 
   energy mass = mass * c * c

Numeric typeclasses are syntactically convenient, but are rather too
implicit for my taste.  I prefer using monomorphic versions once the code
becomes serious.  For example,

import Prelude hiding ((^))
import qualified Prelude

(^) :: Num a = a - Integer - a
(^) = (Prelude.^)

energy mass = mass * c^2

This does not solve your other issues though.

Tom

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Roman Cheplyaka
* Barak A. Pearlmutter ba...@cs.nuim.ie [2013-04-10 15:38:35+0100]
 In fiddling around with some numeric code in Haskell, I noticed some
 issues.  Basically, you get warnings if you write
 
   energy mass = mass * c^2
 
 but not if you write
 
   energy mass = mass * c * c
 
 which seems a bit perverse.
 Some more examples are below.
 
 I understand the inference issues that cause this, but common innocuous
 cases could---and I would argue, should---be addressed in ad-hoc ways.

Hi Barak,

In a sense, defaulting in Haskell *is* a mechanism to address common
innocuous cases in an ad-hoc way (although it still has a relatively
simple and easy to understand semantics).

If you'd like something even more ad-hoc, take a look at Ruby or
JavaScript: http://www.youtube.com/watch?v=kXEgk1Hdze0

Roman

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Aleksey Khudyakov
On 10 April 2013 22:25, Roman Cheplyaka r...@ro-che.info wrote:
 * Barak A. Pearlmutter ba...@cs.nuim.ie [2013-04-10 15:38:35+0100]
 In fiddling around with some numeric code in Haskell, I noticed some
 issues.  Basically, you get warnings if you write

   energy mass = mass * c^2

 but not if you write

   energy mass = mass * c * c

 which seems a bit perverse.
 Some more examples are below.

 I understand the inference issues that cause this, but common innocuous
 cases could---and I would argue, should---be addressed in ad-hoc ways.

 Hi Barak,

 In a sense, defaulting in Haskell *is* a mechanism to address common
 innocuous cases in an ad-hoc way (although it still has a relatively
 simple and easy to understand semantics).

This IS rather annoying problem for numeric code. Raising value to positive
power is quite common operation yet ^ operator generally couldn't be used
because it leads to warning about type defaulting (rightfully) and one
wants to keep code warning free. Actually it's problem with warnings and
I don't think adding some ad-hoc rules for generating warning is necessarily
bad idea

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Tom Ellis
On Wed, Apr 10, 2013 at 11:20:15PM +0400, Aleksey Khudyakov wrote:
 This IS rather annoying problem for numeric code. Raising value to positive
 power is quite common operation yet ^ operator generally couldn't be used
 because it leads to warning about type defaulting (rightfully) and one
 wants to keep code warning free. Actually it's problem with warnings and
 I don't think adding some ad-hoc rules for generating warning is necessarily
 bad idea

Like I demonstrated in my reply to Barak, there is a way around this which
does not require adding ad-hoc complexity to the compiler.

Tom

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Aleksey Khudyakov
On 10 April 2013 23:26, Tom Ellis
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:
 On Wed, Apr 10, 2013 at 11:20:15PM +0400, Aleksey Khudyakov wrote:
 This IS rather annoying problem for numeric code. Raising value to positive
 power is quite common operation yet ^ operator generally couldn't be used
 because it leads to warning about type defaulting (rightfully) and one
 wants to keep code warning free. Actually it's problem with warnings and
 I don't think adding some ad-hoc rules for generating warning is necessarily
 bad idea

 Like I demonstrated in my reply to Barak, there is a way around this which
 does not require adding ad-hoc complexity to the compiler.

Last time I checked (~2 years ago) GHC generated not very efficient code for ^.
But otherwise it's useable solution

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Roman Cheplyaka
* Aleksey Khudyakov alexey.sklad...@gmail.com [2013-04-10 23:20:15+0400]
 On 10 April 2013 22:25, Roman Cheplyaka r...@ro-che.info wrote:
  * Barak A. Pearlmutter ba...@cs.nuim.ie [2013-04-10 15:38:35+0100]
  In fiddling around with some numeric code in Haskell, I noticed some
  issues.  Basically, you get warnings if you write
 
energy mass = mass * c^2
 
  but not if you write
 
energy mass = mass * c * c
 
  which seems a bit perverse.
  Some more examples are below.
 
  I understand the inference issues that cause this, but common innocuous
  cases could---and I would argue, should---be addressed in ad-hoc ways.
 
  Hi Barak,
 
  In a sense, defaulting in Haskell *is* a mechanism to address common
  innocuous cases in an ad-hoc way (although it still has a relatively
  simple and easy to understand semantics).
 
 This IS rather annoying problem for numeric code. Raising value to positive
 power is quite common operation yet ^ operator generally couldn't be used
 because it leads to warning about type defaulting (rightfully) and one
 wants to keep code warning free. Actually it's problem with warnings and
 I don't think adding some ad-hoc rules for generating warning is necessarily
 bad idea

You can disable the warning with -fno-warn-type-defaults.

Roman

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Aleksey Khudyakov
On 11 April 2013 00:11, Roman Cheplyaka r...@ro-che.info wrote:
 * Aleksey Khudyakov alexey.sklad...@gmail.com [2013-04-10 23:20:15+0400]
 On 10 April 2013 22:25, Roman Cheplyaka r...@ro-che.info wrote:
 This IS rather annoying problem for numeric code. Raising value to positive
 power is quite common operation yet ^ operator generally couldn't be used
 because it leads to warning about type defaulting (rightfully) and one
 wants to keep code warning free. Actually it's problem with warnings and
 I don't think adding some ad-hoc rules for generating warning is necessarily
 bad idea

 You can disable the warning with -fno-warn-type-defaults.

Bu in most of the cases I do want this warnings. It's possible to get
something default to Integer when it should be Int. There are only few
cases when it's not appropriate. Only ^ and ^^ with literals I think

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Barak A. Pearlmutter
 ... in most of the cases I do want this warnings. It's possible to get
 something default to Integer when it should be Int. There are only few
 cases when it's not appropriate. Only ^ and ^^ with literals I think

There are a few other cases, albeit less annoying.  Like this:

c = fromIntegral 2 :: Int

Granted this is silly code, but the same case arises inside pretty much
any code that is generic over Integral, in which case the warning you
get is not the *right* warning.  Example:

genericTake n xs = take (fromIntegral n) xs
genericTake 44 foobar

--Barak.

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread Tom Ellis
On Thu, Apr 11, 2013 at 12:56:05AM +0100, Barak A. Pearlmutter wrote:
  ... in most of the cases I do want this warnings. It's possible to get
  something default to Integer when it should be Int. There are only few
  cases when it's not appropriate. Only ^ and ^^ with literals I think
 
 There are a few other cases, albeit less annoying.  Like this:
 
 c = fromIntegral 2 :: Int
 
 Granted this is silly code, but the same case arises inside pretty much
 any code that is generic over Integral, in which case the warning you
 get is not the *right* warning.  Example:
 
 genericTake n xs = take (fromIntegral n) xs
 genericTake 44 foobar

Hi Barak,

I don't write a lot of numeric code so I am under-educated in this area.
Could you write a more substantial example so I get a clearer idea of what's
going on?

Thanks,

Tom

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


Re: [Haskell-cafe] Numerics and Warnings

2013-04-10 Thread John Lato
The issue with this example is that you have

genericTake :: Integral a = a - [b] - [b]

where the 'a' is converted to an Int without being checked for overflow.

IMHO type defaulting is irrelevant for this one problem; evaluating

 take 44 foobar

has exactly the same result without any defaulting taking place.  Arguably
fromIntegral could have other behavior (error/exception/Maybe) when a
conversion would overflow, but that seems like a very significant change.

Aside from this example, I'm quite sympathetic to the issue.  I've more
than once defined values as

let two = 2 :: Int
 three = 3 :: Int

solely to suppress warnings about type defaulting for (^n).

Really, I'd prefer to see the Prelude export
(^) :: Num a = a - Int - a

I think that's the most common case, and it's probably never useful to
raise to a power greater than (maxBound :: Int).

John L.


On Thu, Apr 11, 2013 at 8:10 AM, Tom Ellis 
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 On Thu, Apr 11, 2013 at 12:56:05AM +0100, Barak A. Pearlmutter wrote:
   ... in most of the cases I do want this warnings. It's possible to get
   something default to Integer when it should be Int. There are only few
   cases when it's not appropriate. Only ^ and ^^ with literals I think
 
  There are a few other cases, albeit less annoying.  Like this:
 
  c = fromIntegral 2 :: Int
 
  Granted this is silly code, but the same case arises inside pretty much
  any code that is generic over Integral, in which case the warning you
  get is not the *right* warning.  Example:
 
  genericTake n xs = take (fromIntegral n) xs
  genericTake 44 foobar

 Hi Barak,

 I don't write a lot of numeric code so I am under-educated in this area.
 Could you write a more substantial example so I get a clearer idea of
 what's
 going on?

 Thanks,

 Tom

 ___
 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