RE: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-29 Thread Simon Peyton-Jones
| By the way, using Integer for exponents really shouldn't be less | efficient - | but it seems it is. | | The code for (^) should be something like this: | | {-# INLINE ^ #-} | n ^ m = case toInteger m of | S# i -> powerInt# n i | J# a p -> powerGmp n a p I've done something l

RE: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-27 Thread Simon Peyton-Jones
| happens because I don't want to actually use defaulting, but I would | have no objection to the warning being suppressed if someone has | explicitly given a "default" declaration (and thus, presumably, does | want to use defaulting). I'm not against this particular proposal if there's a consensu

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Brandon Michael Moore
On Mon, Jun 25, 2007 at 08:53:18AM -0700, Dave Bayer wrote: > It continues to appear to me that "ghc -Wall -Werror" doesn't support > small Int constants without a per-use penalty, measured in code length. Why not use "ghc -Wall -Werror -fno-warn-defaulting", maybe with default(Int)? It removes

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Henning Thielemann
On Mon, 25 Jun 2007, Ian Lynagh wrote: > On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote: > > > > > z = r Prelude.^ 3 > > I don't know if (^) in particular is what is causing you problems, but > IMO it has the wrong type; just as we have > (!!) :: [a]

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer
On Mon, Jun 25, 2007 at 07:31:09PM +0100, Ian Lynagh wrote: I don't know if (^) in particular is what is causing you problems, but IMO it has the wrong type; just as we have (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -> b -> a we should also ha

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread David Roundy
On Mon, Jun 25, 2007 at 07:31:09PM +0100, Ian Lynagh wrote: > I don't know if (^) in particular is what is causing you problems, but > IMO it has the wrong type; just as we have > (!!) :: [a] -> Int -> a > genericIndex :: (Integral b) => [a] -> b -> a > we should a

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Ian Lynagh
On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote: > > > z = r Prelude.^ 3 I don't know if (^) in particular is what is causing you problems, but IMO it has the wrong type; just as we have (!!) :: [a] -> Int -> a genericIndex :: (Integral b) => [a] -

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Jaap Weel
> I've been going over my code trying to get it all to compile with > "ghc -Wall -Werror" I recently ran across what may be a good reason not to use -Wall in combination with -Werror (and similar combinations in other compilers), at least not as the standard build switches for software you intend

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer
On Jun 25, 2007, at 8:15 AM, Simon Peyton-Jones wrote: i2 = 2 :: Int i3 = 3 :: Int The code {-# OPTIONS_GHC -Wall -Werror #-} module Main where i2 = 2 :: Int i3 = 3 :: Int main :: IO () main = putStrLn $ show (i2,i3) generates the errors Main.hs:5:0: Warning: Definition but no type si

RE: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Simon Peyton-Jones
| Unless I misunderstand and it is already possible, I'd now prefer a | language extension that allows the explicit declarations | | > 2,3 :: Int | | once for each affected numeric literal. i2 = 2 :: Int i3 = 3 :: Int S ___ Haskell-Cafe mailing list Has

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer
On Jun 25, 2007, at 4:48 AM, Simon Peyton-Jones wrote: The intention is that it should be straightforward to suppress warnings. Simply add a type signature for 'z', or for the naked 3 in z's definition. I constructed my example from larger modules peppered with small integer constants;

RE: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Simon Peyton-Jones
The intention is that it should be straightforward to suppress warnings. Warning about defaulting is important, because it's a place where a silent choice affects the dynamic semantics of your program. You can suppress the warning by supplying a type signature. In your example: | > main = | >

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer
On Jun 22, 2007, at 3:11 PM, Brandon S. Allbery KF8NH wrote: (1) any way to flag a pattern match as "I know this is okay", don't warn about it" without shutting off pattern match warnings completely? GHC doesn't issue warnings about patterns on the left of = For example, the following code c

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-24 Thread Henning Thielemann
On Sat, 23 Jun 2007, David Roundy wrote: > > I refuse to drink the Kool-Aid and recite precisely what I'm told a > > type is in June, 2007; I'm hoping that types will evolve by the time > > I die. For types to evolves, we need to step back a few feet and > > think more loosely what a type really

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-23 Thread David Roundy
On Fri, Jun 22, 2007 at 05:39:10PM -0700, Dave Bayer wrote: > On Jun 22, 2007, at 4:37 PM, David Roundy wrote: > > >You get strongly-typed code whether or not you enable warnings. > > In my opinion it's delusional to think one is using strong typing if > one doesn't enable warnings. All the puf

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-23 Thread David Roundy
On Fri, Jun 22, 2007 at 03:14:06PM -0700, Stefan O'Rear wrote: > On Fri, Jun 22, 2007 at 06:11:24PM -0400, Brandon S. Allbery KF8NH wrote: > > (1) any way to flag a pattern match as "I know this is okay", don't > > warn about it" without shutting off pattern match warnings completely? > > > cas

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-23 Thread Neil Mitchell
Hi > All the puffing about the advantages of > strong typing look pretty silly if code hangs up on an incomplete > pattern. Okay... people who don't worry so much about incomplete patterns believe that they get things done. There are trade offs in type systems about how much effort you want to

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Derek Elkins
On Fri, 2007-06-22 at 17:39 -0700, Dave Bayer wrote: > On Jun 22, 2007, at 4:37 PM, David Roundy wrote: > > > You get strongly-typed code whether or not you enable warnings. > > In my opinion it's delusional to think one is using strong typing if > one doesn't enable warnings. All the puffing a

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer
On Jun 22, 2007, at 4:37 PM, David Roundy wrote: You get strongly-typed code whether or not you enable warnings. In my opinion it's delusional to think one is using strong typing if one doesn't enable warnings. All the puffing about the advantages of strong typing look pretty silly if code

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 03:07:59PM -0700, Dave Bayer wrote: > On Jun 22, 2007, at 2:46 PM, David Roundy wrote: > >I think of top-level type declarations as type-checked comments, rather > >than a seat-belt. It forces you to communicate to others what a > >function does, if that function may be use

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Brandon S. Allbery KF8NH
On Jun 22, 2007, at 18:29 , Henning Thielemann wrote: If the error occurs anyway, you get a report that your believe was wrong. (Or the user gets the report, and he doesn't know how to react.) Well, that's why I included the other leg, where I'd like the compiler to catch me at compile ti

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Derek Elkins
On Sat, 2007-06-23 at 00:29 +0200, Henning Thielemann wrote: > On Fri, 22 Jun 2007, Brandon S. Allbery KF8NH wrote: > > > I have a program which I'm checking with -Wall but not -Werror, > > because it has several pattern matches which *I* know are fine but > > which ghc doesn't. (I suspect, from

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Henning Thielemann
On Fri, 22 Jun 2007, Dave Bayer wrote: > If I import a module that I don't use, then "ghc -Wall -Werror" > rightly complains. By analogy, if I use "default (Int)" to ask GHC to > default to Int but the situation never arises, then GHC should > rightly complain. Instead, if I use "default (Int)",

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Henning Thielemann
On Fri, 22 Jun 2007, Brandon S. Allbery KF8NH wrote: > I have a program which I'm checking with -Wall but not -Werror, > because it has several pattern matches which *I* know are fine but > which ghc doesn't. (I suspect, from its description, that Catch > would also recognize it's fine.) Which

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer
On Jun 22, 2007, at 12:34 PM, Dave Bayer wrote: In particular, I always want defaulting errors, because sometimes I miss the fact that numbers I can count on my fingers are defaulting to Integer. So no one took the bait to actually offer me a shorter idiom, but I thought about the above s

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Stefan O'Rear
On Fri, Jun 22, 2007 at 06:11:24PM -0400, Brandon S. Allbery KF8NH wrote: > (1) any way to flag a pattern match as "I know this is okay", don't > warn about it" without shutting off pattern match warnings completely? case scrutinee of Pattern -> alternative Pattern -> alternative _ -> err

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Brandon S. Allbery KF8NH
On Jun 22, 2007, at 17:46 , David Roundy wrote: -Wall -Werror isn't a seat belt, it's a coding-style guideline. So, as long as we're on this topic... I have a program which I'm checking with -Wall but not -Werror, because it has several pattern matches which *I* know are fine but which g

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer
On Jun 22, 2007, at 2:46 PM, David Roundy wrote: I think of top-level type declarations as type-checked comments, rather than a seat-belt. It forces you to communicate to others what a function does, if that function may be used elsewhere. I like this. Although it can be cumbersome for q

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 12:34:09PM -0700, Dave Bayer wrote: > On Jun 22, 2007, at 11:42 AM, David Roundy wrote: > > >On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote: > >>GHC issues a "Warning: Defaulting the following constraint(s) to type > >>`Int'" for the definition of z. > > > >Why

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer
On Jun 22, 2007, at 11:42 AM, David Roundy wrote: On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote: GHC issues a "Warning: Defaulting the following constraint(s) to type `Int'" for the definition of z. Why don't you just use -fno-warn-type-defaults? ... ghc -Werr -Wall is a often

Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread David Roundy
On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote: > GHC issues a "Warning: Defaulting the following constraint(s) to type > `Int'" for the definition of z. Why don't you just use -fno-warn-type-defaults? Warnings are just that: warnings. If you believe the defaulting matches what you

[Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer
Hi all, I've been going over my code trying to get it all to compile with "ghc -Wall -Werror", without introducing constructs that would make my code the laughing stock of the dynamic typing community. They already think we're nuts; my daydreams are of a more computer literate society whe