PROPOSAL: Restrict the type of (^), (^^), and add genericPower, genericPower'

Hi all, This got a warm reception when I mentioned it in http://www.haskell.org/pipermail/haskell-cafe/2007-June/027557.html so I'm formally proposing it now. It's trac #1902: http://hackage.haskell.org/trac/ghc/ticket/1902 Note that this is a divergence from Haskell 98 (but the libraries already have a handful of small divergences, and Haskell' is just around the corner...). In my opinion, (^) has the wrong type. Just as we have, for example, (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -> b -> a we should also have (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a (or some other function name). The same goes for (^^) (genericPower'). In my experience this would remove 99.9% of all defaulting (mostly where you write things like x^12 and 8^12), which means it's easier to get -Wall clean without having to put :: Int annotations everywhere. The impact to GHC's bootlibs and extralibs is minimal. In most cases we have things like 2^15, where Int is clearly fine, although it happens to be defaulted to Integer currently. In Data.Complex we have 2 cases of e^(2::Int) which can now be beautified. There are several cases where the type is inferred to be Int anyway. There are 3 files where we really do have an Integer, and it does matter. They are all for parsing numbers of the form 18e43, in base/Text/Read/Lex.hs, parsec/Text/ParserCombinators/Parsec/Token.hs and haskell-src/Language/Haskell/Lexer.hs. Initial deadline: 1 Dec 2007. Thanks Ian

On Sat, 17 Nov 2007, Ian Lynagh wrote:
Hi all,
This got a warm reception when I mentioned it in http://www.haskell.org/pipermail/haskell-cafe/2007-June/027557.html so I'm formally proposing it now. It's trac #1902: http://hackage.haskell.org/trac/ghc/ticket/1902
Note that this is a divergence from Haskell 98 (but the libraries already have a handful of small divergences, and Haskell' is just around the corner...).
In my opinion, (^) has the wrong type. Just as we have, for example, (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -> b -> a we should also have (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a (or some other function name). The same goes for (^^) (genericPower').
I vote for this proposal. In order not to overuse the prime, I propose genericFractionalPower or genericFracPower for (^^). In my code, the exponent is most oftenly 2.

On 17/11/2007, Ian Lynagh
Hi all,
This got a warm reception when I mentioned it in http://www.haskell.org/pipermail/haskell-cafe/2007-June/027557.html so I'm formally proposing it now. It's trac #1902: http://hackage.haskell.org/trac/ghc/ticket/1902
Note that this is a divergence from Haskell 98 (but the libraries already have a handful of small divergences, and Haskell' is just around the corner...).
In my opinion, (^) has the wrong type. Just as we have, for example, (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -> b -> a we should also have (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a (or some other function name). The same goes for (^^) (genericPower').
In my experience this would remove 99.9% of all defaulting (mostly where you write things like x^12 and 8^12), which means it's easier to get -Wall clean without having to put :: Int annotations everywhere.
The impact to GHC's bootlibs and extralibs is minimal. In most cases we have things like 2^15, where Int is clearly fine, although it happens to be defaulted to Integer currently. In Data.Complex we have 2 cases of e^(2::Int) which can now be beautified. There are several cases where the type is inferred to be Int anyway.
There are 3 files where we really do have an Integer, and it does matter. They are all for parsing numbers of the form 18e43, in base/Text/Read/Lex.hs, parsec/Text/ParserCombinators/Parsec/Token.hs and haskell-src/Language/Haskell/Lexer.hs.
Initial deadline: 1 Dec 2007.
Thanks Ian
This is a move in the opposite direction from what I'd really like to see. The Int type is usually a premature optimisation, and I usually prefer to work with Integer as much as possible, but this just means more fromIntegral conversions (or the use of the awkwardly named general version). I would much prefer for length, !!, etc. to have more general types, not less general (with compiler specialisation on Int of course). This change would be annoying. - Cale

Cale Gibbard wrote:
[...] The Int type is usually a premature optimisation,
[...] I would much prefer for length, !!, etc. to have more general types, not less general (with compiler specialisation on Int of course).
Yes! Best regards, Johannes Waldmann.

On Sat, Nov 17, 2007 at 11:45:52AM -0500, Cale Gibbard wrote:
On 17/11/2007, Ian Lynagh
wrote: (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a
This is a move in the opposite direction from what I'd really like to see. The Int type is usually a premature optimisation, and I usually prefer to work with Integer as much as possible, but this just means more fromIntegral conversions (or the use of the awkwardly named general version).
I would much prefer for length, !!, etc. to have more general types, not less general (with compiler specialisation on Int of course).
This proposal is about making (^) and (^^) consistent with everything else. Making everything use Integer rather than Int is an orthogonal question. Someone could also make a Prelude.Integer module, that exports foo :: ... Integer ... foo = genericFoo for various foo which are specialised to Int in Prelude, and reexports all other functions from Prelude. Getting rid of implicit Prelude imports would help too. Thanks Ian

On 17/11/2007, Ian Lynagh
On Sat, Nov 17, 2007 at 11:45:52AM -0500, Cale Gibbard wrote:
On 17/11/2007, Ian Lynagh
wrote: (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a
This is a move in the opposite direction from what I'd really like to see. The Int type is usually a premature optimisation, and I usually prefer to work with Integer as much as possible, but this just means more fromIntegral conversions (or the use of the awkwardly named general version).
I would much prefer for length, !!, etc. to have more general types, not less general (with compiler specialisation on Int of course).
This proposal is about making (^) and (^^) consistent with everything else. Making everything use Integer rather than Int is an orthogonal question.
Someone could also make a Prelude.Integer module, that exports foo :: ... Integer ... foo = genericFoo for various foo which are specialised to Int in Prelude, and reexports all other functions from Prelude. Getting rid of implicit Prelude imports would help too.
Thanks Ian
I don't want the types specialised to Integer either though. I'd want to have the types be as generic as possible, but include appropriate pragmas to tell GHC how to optimise when they're applied monomorphically.

On Sat, 17 Nov 2007, Cale Gibbard wrote:
On 17/11/2007, Ian Lynagh
wrote: This proposal is about making (^) and (^^) consistent with everything else. Making everything use Integer rather than Int is an orthogonal question.
Someone could also make a Prelude.Integer module, that exports foo :: ... Integer ... foo = genericFoo for various foo which are specialised to Int in Prelude, and reexports all other functions from Prelude. Getting rid of implicit Prelude imports would help too.
Thanks Ian
I don't want the types specialised to Integer either though. I'd want to have the types be as generic as possible, but include appropriate pragmas to tell GHC how to optimise when they're applied monomorphically.
As Ian pointed to, general types for exponents are rarely used in the code he explored. This is also my experience from doing math with Haskell. Did you make a different experience? The proposal isn't about removing the polymorphism of (^), but to shift it to an alphanumerically named function. I find "to have the types be as generic as possible" isn't always a good design strategy, especially in this case, where the type of the exponent cannot be infered from other operands. Thus in many cases the compiler has to choose a default type. It's just like I find (*) :: (Multiplyable a b c) => a -> b -> c not a good idea, say for various multiplications in linear algebra, because of lost type inference.

On Sat, Nov 17, 2007 at 01:00:51PM -0500, Cale Gibbard wrote:
On 17/11/2007, Ian Lynagh
wrote: On Sat, Nov 17, 2007 at 11:45:52AM -0500, Cale Gibbard wrote:
On 17/11/2007, Ian Lynagh
wrote: (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a
This is a move in the opposite direction from what I'd really like to see. The Int type is usually a premature optimisation, and I usually prefer to work with Integer as much as possible, but this just means more fromIntegral conversions (or the use of the awkwardly named general version).
I would much prefer for length, !!, etc. to have more general types, not less general (with compiler specialisation on Int of course).
This proposal is about making (^) and (^^) consistent with everything else. Making everything use Integer rather than Int is an orthogonal question.
Someone could also make a Prelude.Integer module, that exports foo :: ... Integer ... foo = genericFoo for various foo which are specialised to Int in Prelude, and reexports all other functions from Prelude. Getting rid of implicit Prelude imports would help too.
I don't want the types specialised to Integer either though. I'd want to have the types be as generic as possible, but include appropriate pragmas to tell GHC how to optimise when they're applied monomorphically.
You can also make Prelude.Generic foo :: Integral a => ... a ... foo = genericFoo Or we could just remove the genericFoo functions and have Prelude.Generic.foo be the canonical name. If possible, I would like to separate what we should do /in general/ from whether we should make (^) and (^^) consistent with the rest of the libraries, though. If someone wants to propose a change to the general scheme /now/ then I don't mind this proposal waiting until that is either resolved or fizzles out. Thanks Ian

On Sat, 17 Nov 2007, Cale Gibbard wrote:
On 17/11/2007, Ian Lynagh
wrote: Hi all,
This got a warm reception when I mentioned it in http://www.haskell.org/pipermail/haskell-cafe/2007-June/027557.html so I'm formally proposing it now. It's trac #1902: http://hackage.haskell.org/trac/ghc/ticket/1902
Note that this is a divergence from Haskell 98 (but the libraries already have a handful of small divergences, and Haskell' is just around the corner...).
In my opinion, (^) has the wrong type. Just as we have, for example, (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -> b -> a we should also have (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a (or some other function name). The same goes for (^^) (genericPower').
In my experience this would remove 99.9% of all defaulting (mostly where you write things like x^12 and 8^12), which means it's easier to get -Wall clean without having to put :: Int annotations everywhere.
The impact to GHC's bootlibs and extralibs is minimal. In most cases we have things like 2^15, where Int is clearly fine, although it happens to be defaulted to Integer currently. In Data.Complex we have 2 cases of e^(2::Int) which can now be beautified. There are several cases where the type is inferred to be Int anyway.
There are 3 files where we really do have an Integer, and it does matter. They are all for parsing numbers of the form 18e43, in base/Text/Read/Lex.hs, parsec/Text/ParserCombinators/Parsec/Token.hs and haskell-src/Language/Haskell/Lexer.hs.
Initial deadline: 1 Dec 2007.
Thanks Ian
This is a move in the opposite direction from what I'd really like to see. The Int type is usually a premature optimisation,
Accepted, but then I prefer fixed type 'Integer' as exponent and some guarantee, that powers with small constant exponents are converted to products by the optimizer.

"Cale Gibbard"
On 17/11/2007, Ian Lynagh
wrote: In my opinion, (^) has the wrong type. Just as we have, for example, (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -> b -> a we should also have (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a (or some other function name). The same goes for (^^) (genericPower').
This is a move in the opposite direction from what I'd really like to see. The Int type is usually a premature optimisation,
Hear, hear.
I would much prefer for length, !!, etc. to have more general types, not less general (with compiler specialisation on Int of course).
This change would be annoying.
Agreed. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

I vote against this proposal.
On 11/17/07, Ian Lynagh
In my experience this would remove 99.9% of all defaulting (mostly where you write things like x^12 and 8^12), which means it's easier to get -Wall clean without having to put :: Int annotations everywhere.
I agree that is a benefit (making it easier to avoid warnings), but in my opinion it is a tiny benefit. I don't see any other benefits to this proposal. And I am strongly against making the standard library more complicated by adding multiple functions that do the same thing (^ and genericPower). The inverse proposal has the same benefit, and doesn't require a change to GHC: just add intPower to your own code, and use it wherever you want. If you are unhappy with the idea of using intPower, perhaps you understand why I'm unhappy with the prospect of having to use genericPower.

On Sat, 17 Nov 2007, David Benbennick wrote:
I vote against this proposal.
On 11/17/07, Ian Lynagh
wrote: In my experience this would remove 99.9% of all defaulting (mostly where you write things like x^12 and 8^12), which means it's easier to get -Wall clean without having to put :: Int annotations everywhere.
I agree that is a benefit (making it easier to avoid warnings), but in my opinion it is a tiny benefit.
Let me guess - you don't use -Wall. :-) Warnings are not the problem, warnings point to a problem. The problem here is, that the compiler has to guess a type, because it cannot be infered from other operands.
The inverse proposal has the same benefit, and doesn't require a change to GHC: just add intPower to your own code, and use it wherever you want. If you are unhappy with the idea of using intPower, perhaps you understand why I'm unhappy with the prospect of having to use genericPower.
Question: How often did you need the genericity of Haskell 98 (^) ? That is, how often do you call (^) with a non-constant exponent and how often is the exponent constant? If I have (^) with variable exponents too often in the code, I suspect that I missed some optimizations like (iterate (x*) 1). I have done (semi-automatically) some statistics on my mathematical stuff in Haskell, namely http://darcs.haskell.org/htam/src (^^) used with exponents (1-j) (n2-1) n pred n (^) used with variable exponents i j m n n n n degree xs degree xs degree ys (n2-1) mod n 2 mod (p+1) 2 (^) used with constant exponents 2: 169 times 3: 31 times 4: 9 times 5: 10 times 6: 3 times 7: 2 times 8: 1 times 9: 1 times If I search for '::Int', the most results are exponents of (^), others are from enumerations like [(0::Int)..].

I thought of two more reasons I'm against this proposal:
2) It isn't backwards compatible. It will cause some existing Haskell
code to not compile.
3) It makes things more difficult in GHCI. Under this proposal, you'd
have the following:
Prelude> let x = 2
Prelude> 6 ^ x
<interactive>:
Couldn't match expected type `Int' against inferred type `Integer'
On 11/17/07, Henning Thielemann
Let me guess - you don't use -Wall. :-) Warnings are not the problem, warnings point to a problem. The problem here is, that the compiler has to guess a type, because it cannot be infered from other operands.
I don't see how that's a problem. Have you ever had a case where defaulting to Integer produced the wrong behavior?

On Sat, Nov 17, 2007 at 02:46:56PM -0800, David Benbennick wrote:
I thought of two more reasons I'm against this proposal:
2) It isn't backwards compatible. It will cause some existing Haskell code to not compile.
That is true, and is why I checked all the bootlibs and corelibs in my original message. I don't believe many programs/libraries will be affected, but I'm willing to be proven wrong! (The fix is trivial anyway, of course. The only annoying bit is checking that you weren't relying on any cases being defaulted to Integer, but you should be able to check for that easily by compiling with -fwarn-type-defaults).
3) It makes things more difficult in GHCI. Under this proposal, you'd have the following:
Prelude> let x = 2 Prelude> 6 ^ x <interactive>: Couldn't match expected type `Int' against inferred type `Integer'
This is true, just as you currently get: Prelude> let x = 2 Prelude> take x [1..] <interactive>:1:5: Couldn't match expected type `Int' against inferred type `Integer' and likewise for (!!) etc. I hadn't really noticed that the default defaulting conflicts with the use of Int in the standard functions in this way. I guess in ghci is the only time it comes up, though.
On 11/17/07, Henning Thielemann
wrote: Let me guess - you don't use -Wall. :-) Warnings are not the problem, warnings point to a problem. The problem here is, that the compiler has to guess a type, because it cannot be infered from other operands.
I don't see how that's a problem. Have you ever had a case where defaulting to Integer produced the wrong behavior?
Unintentional defaulting can mean significant performance loss. If you leave intentional defaulting in the code then you will get warnings when you compile with -Wall, and if you always get warnings when you compile then you just ignore all warnings. This means that warnings don't help you to find bugs in your code. Thanks Ian

Hello,
I also think that this proposal is not a good idea, David Benbennick
gave a number of good reasons why, and a perfectly valid solution if
you are worried about the defaulting issue.
By the way, defaulting to Integer should not loose any performance in
the (presumably very common) case when the second argument is a
statically known constant. If it does, then we should look at GHC and
fix the problem there.
-Iavor
On Nov 17, 2007 4:20 PM, Ian Lynagh
On Sat, Nov 17, 2007 at 02:46:56PM -0800, David Benbennick wrote:
I thought of two more reasons I'm against this proposal:
2) It isn't backwards compatible. It will cause some existing Haskell code to not compile.
That is true, and is why I checked all the bootlibs and corelibs in my original message. I don't believe many programs/libraries will be affected, but I'm willing to be proven wrong!
(The fix is trivial anyway, of course. The only annoying bit is checking that you weren't relying on any cases being defaulted to Integer, but you should be able to check for that easily by compiling with -fwarn-type-defaults).
3) It makes things more difficult in GHCI. Under this proposal, you'd have the following:
Prelude> let x = 2 Prelude> 6 ^ x <interactive>: Couldn't match expected type `Int' against inferred type `Integer'
This is true, just as you currently get:
Prelude> let x = 2 Prelude> take x [1..] <interactive>:1:5: Couldn't match expected type `Int' against inferred type `Integer'
and likewise for (!!) etc.
I hadn't really noticed that the default defaulting conflicts with the use of Int in the standard functions in this way. I guess in ghci is the only time it comes up, though.
On 11/17/07, Henning Thielemann
wrote: Let me guess - you don't use -Wall. :-) Warnings are not the problem, warnings point to a problem. The problem here is, that the compiler has to guess a type, because it cannot be infered from other operands.
I don't see how that's a problem. Have you ever had a case where defaulting to Integer produced the wrong behavior?
Unintentional defaulting can mean significant performance loss.
If you leave intentional defaulting in the code then you will get warnings when you compile with -Wall, and if you always get warnings when you compile then you just ignore all warnings. This means that warnings don't help you to find bugs in your code.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I think this proposal goes the wrong way. We should not make types more
specific, but more general.
Instead of ruining ^ and ^^, lets make the type of length, take, etc more
general.
-- Lennart
On Nov 17, 2007 2:02 PM, Ian Lynagh
Hi all,
This got a warm reception when I mentioned it in http://www.haskell.org/pipermail/haskell-cafe/2007-June/027557.html so I'm formally proposing it now. It's trac #1902: http://hackage.haskell.org/trac/ghc/ticket/1902
Note that this is a divergence from Haskell 98 (but the libraries already have a handful of small divergences, and Haskell' is just around the corner...).
In my opinion, (^) has the wrong type. Just as we have, for example, (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -> b -> a we should also have (^) :: (Num a) => a -> Int -> a genericPower :: (Num a, Integral b) => a -> b -> a (or some other function name). The same goes for (^^) (genericPower').
In my experience this would remove 99.9% of all defaulting (mostly where you write things like x^12 and 8^12), which means it's easier to get -Wall clean without having to put :: Int annotations everywhere.
The impact to GHC's bootlibs and extralibs is minimal. In most cases we have things like 2^15, where Int is clearly fine, although it happens to be defaulted to Integer currently. In Data.Complex we have 2 cases of e^(2::Int) which can now be beautified. There are several cases where the type is inferred to be Int anyway.
There are 3 files where we really do have an Integer, and it does matter. They are all for parsing numbers of the form 18e43, in base/Text/Read/Lex.hs, parsec/Text/ParserCombinators/Parsec/Token.hs and haskell-src/Language/Haskell/Lexer.hs.
Initial deadline: 1 Dec 2007.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (8)
-
Cale Gibbard
-
David Benbennick
-
Henning Thielemann
-
Ian Lynagh
-
Iavor Diatchki
-
Johannes Waldmann
-
Jon Fairbairn
-
Lennart Augustsson