[Haskell-cafe] Best idiom for avoiding Defaulting warnings with
ghc -Wall -Werror ??
Dave Bayer
bayer at cpw.math.columbia.edu
Mon Jun 25 05:25:15 EDT 2007
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 compiles just fine with ghc -Wall -
Werror, but the use of "Just m" generates a run-time exception:
> module Main where
>
> a :: [(Int,Int)]
> a = [(2*n,n) | n <- [1..100]]
>
> m :: Int
> Just m = lookup 3 a
>
> main :: IO ()
> main = putStrLn $ show m
I'd take this as a ghc feature, not a bug. When I use this construct
in practice, I have a proof in mind that the pattern match cannot
fail for my data, but I can't express the proof in Haskell's type
system. I'm ok with skipping writing that proof.
The difference here is programmer intent. While a missing pattern
case can often be an oversight, there's no way to put both cases here
to the left of =, so the programmer clearly intends this code as
written.
(An example of a language with a Turing complete type system is Qi:
http://www.lambdassociates.org/
As pointed out elsewhere in this thread, it is unreasonable/
undecidable to expect a type system to work out arbitrarily difficult
issues for you automatically. Some work is required, programming in
the type system. They extend this point of view.)
More information about the Haskell-Cafe
mailing list