[GHC] #8567: Poor error message when GeneralizedNewtypeDeriving fails
GHC
ghc-devs at haskell.org
Tue Nov 26 15:25:54 UTC 2013
#8567: Poor error message when GeneralizedNewtypeDeriving fails
------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
Say I try to compile this silly module:
{{{
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
module Bug where
class C a where
meth :: a -> F a
type family F a
type instance F Int = Bool
type instance F Age = Char
instance C Int where
meth = (> 0)
newtype Age = MkAge Int
deriving C
}}}
Then, I get this output:
{{{
Bug.hs:16:12:
No instance for (GHC.Types.Coercible Bool Char)
because ‛Bool’ and ‛Char’ are different types.
arising from a use of ‛GHC.Prim.coerce’
In the expression:
GHC.Prim.coerce (meth :: Int -> F Int) :: Age -> F Age
In an equation for ‛meth’:
meth = GHC.Prim.coerce (meth :: Int -> F Int) :: Age -> F Age
In the instance declaration for ‛C Age’
}}}
What a confusing error message! Of the 9 lines of error, only 3 make
sense: the line number (which is correct, at the line number of my
`deriving` statement), saying that `Bool` and `Char` are different, and
the conclusion that we're in an instance declaration.
This might be better:
{{{
Bug.hs:16:12:
Cannot coerce from ‛Bool’ to ‛Char’
because ‛Bool’ and ‛Char’ are different types
arising from the need to coerce ‛Int -> F Int’ to ‛Age -> F Age’
In the instance declaration for ‛C Age’
generated automatically through GeneralizedNewtypeDeriving
To see the code I am typechecking, use -ddump-deriv
}}}
I actually went ahead and tried to fix this myself, but it's unclear to me
what the best implementation plan for such an error message is. The code
in !TcDeriv generates `HsSyn RdrName` and then renames it to `HsSyn Name`,
but that code then gets sent through the normal type-checking pipeline.
That pipeline builds up the error-reporting context without much heed to
the fact that GHC itself generated the code. So, while I'm sure I could
hack away long enough to get the error message to come out right, I'm
equally sure that the resulting code would make people want to cry. Any
advice? Or does someone with a better perspective want to take a stab?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8567>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list