[GHC] #13670: Improving Type Error Messages
GHC
ghc-devs at haskell.org
Tue May 9 16:09:05 UTC 2017
#13670: Improving Type Error Messages
-------------------------------------+-------------------------------------
Reporter: gridaphobe | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I was reading through https://medium.com/@sjsyrek/some-notes-on-haskell-
pedagogy-de43281b1a5c the other day, and noticed a pretty gnarly error
message produced by the following code
{{{
{-# LANGUAGE InstanceSigs #-}
data List a = EmptyList | ListElement a (List a)
deriving Show
instance Functor List where
fmap :: (a -> b) -> List a -> List b
fmap f xs = ListElement (f x) xs
}}}
{{{
list.hs:8:49: error:
• Couldn't match type ‘a’ with ‘b’
‘a’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List a -> List b
at list.hs:7:11
‘b’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List a -> List b
at list.hs:7:11
Expected type: List b
Actual type: List a
• In the second argument of ‘ListElement’, namely ‘xs’
In the expression: ListElement (f x) xs
In an equation for ‘fmap’:
fmap f (ListElement x xs) = ListElement (f x) xs
• Relevant bindings include
xs :: List a (bound at list.hs:8:25)
x :: a (bound at list.hs:8:23)
f :: a -> b (bound at list.hs:8:8)
fmap :: (a -> b) -> List a -> List b
(bound at list.hs:8:3)
}}}
I think there are a few things we could do better here.
1. The biggest issue IMO is that the key piece of information, the
mismatch between `List a` and `List b` is stuck right in the middle of the
error message, obscured by GHC's attempt to be helpful by pointing out the
provenance of `a` and `b`. The mismatch should be front and center, so
users see it without having to dig through a wall of text! I think just
swapping the order of the expected/actual types and the tyvar provenance
would be a big improvement.
{{{
list.hs:8:49: error:
• Couldn't match type ‘a’ with ‘b’
Expected type: List b
Actual type: List a
‘a’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List a -> List b
at list.hs:7:11
‘b’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List a -> List b
at list.hs:7:11
• In the second argument of ‘ListElement’, namely ‘xs’
In the expression: ListElement (f x) xs
In an equation for ‘fmap’:
fmap f (ListElement x xs) = ListElement (f x) xs
• Relevant bindings include
xs :: List a (bound at list.hs:8:25)
x :: a (bound at list.hs:8:23)
f :: a -> b (bound at list.hs:8:8)
fmap :: (a -> b) -> List a -> List b
(bound at list.hs:8:3)
}}}
But there's more we can do!
2. The rust compiler does this very nice thing where it attaches helpful
notes that relate to the error to other source spans. The benefit here is
that editors can then '''highlight''' multiple spans to produce a nicer
visual. In our case, the provenance of the tyvars feels like such a
helpful note, rather than a core part of the error message.
{{{
list.hs:8:49: error:
• Couldn't match type ‘a’ with ‘b’
Expected type: List b
Actual type: List a
• In the second argument of ‘ListElement’, namely ‘xs’
In the expression: ListElement (f x) xs
In an equation for ‘fmap’:
fmap f (ListElement x xs) = ListElement (f x) xs
• Relevant bindings include
xs :: List a (bound at list.hs:8:25)
x :: a (bound at list.hs:8:23)
f :: a -> b (bound at list.hs:8:8)
fmap :: (a -> b) -> List a -> List b
(bound at list.hs:8:3)
list.hs:7:11: note:
• ‘a’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List a -> List b
list.hs:7:11: note:
• ‘b’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List a -> List b
}}}
Now the editor will highlight the ill-typed `xs` in red, with a popup that
just provides the error; and the type for `fmap` in another color (usually
blue it seems), with a popup that explains the provenance of the tyvars.
(We might also want to separate the "relevant bindings" into a helpful
note.)
I believe many linter packages for editors are already setup to
distinguish between errors and helpful notes, so this would be a really
simple and free improvement.
3. Finally, I've always liked how GHC helpfully explains the context in
which the error occurs ("in the second argument ... in the expression ...
etc"), but I think we've been outclassed by other compilers that just
print the offending line with the error underlined. We could adopt this
strategy. (Related: it seems redundant to provide this context if the user
is inside their editor rather than at the command-line. What if we had a
flag `--editor-mode` to prune such redundancies?)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13670>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list