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

Dave Bayer bayer at cpw.math.columbia.edu
Fri Jun 22 14:37:15 EDT 2007


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 where Jessie Helms stands up in the U.S. Senate to  
read aloud my type declarations to the derisive laughter of the Ruby  
and Lisp parties.

There's a fine line between my opinion as to how GHC should issue  
warnings, and a legitimate bug report. I've already submitted a bug  
report for the need to declare the type of the wildcard pattern,  
because I believe that the case is clear. Here, I'm seeking guidance.  
Perhaps I just don't know the most elegant construct to use?

My sample code is this:


> {-# OPTIONS_GHC -Wall -Werror #-}
>
> module Main where
>
> import Prelude hiding ((^))
> import qualified Prelude ((^))
>
> default (Int)
>
> infixr 8 ^
> (^) :: Num a => a -> Int -> a
> x ^ n = x Prelude.^ n
>
> main :: IO ()
> main =
>    let r = pi :: Double
>        x = r ^ (3 :: Int)
>        y = r ^ 3
>        z = r Prelude.^ 3
>    in  putStrLn $ show (x,y,z)
>

GHC issues a "Warning: Defaulting the following constraint(s) to type  
`Int'" for the definition of z.

The definition of y glides through, so a qualified import and  
redefinition of each ambiguous operator does provide a work-around,  
but the code is lame. (I could always encapsulate it in a module  
Qualude.)

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)", GHC complains  
about defaulting anyways. In my opinion, this is a bug, but I'd like  
guidance before reporting it. Is there a more elegant way to handle  
the numeric type classes with "ghc -Wall -Werror" ?

No one is forced to use "ghc -Wall -Werror", but it should be a  
practical choice.

I've enjoyed the recent typing discussions here. On one hand, there's  
little difference between using dynamic typing, and writing  
incomplete patterns in a strongly typed language. On the other hand,  
how is an incomplete pattern any different from code that potentially  
divides by zero? One quickly gets into decidability issues, dependent  
types, Turing-complete type systems.

My personal compromise is to use "ghc -Wall -Werror", live with the  
consequences, and get back to work. Perhaps I'll get over it, but  
that's a slippery slope back to Lisp.



More information about the Haskell-Cafe mailing list