[GHC] #15678: Provide the provenance of unification variables in error messages when possible
GHC
ghc-devs at haskell.org
Wed Sep 26 12:35:39 UTC 2018
#15678: Provide the provenance of unification variables in error messages when
possible
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.6.1
(Type checker) |
Keywords: TypeErrors | Operating System: Unknown/Multiple
Architecture: | Type of failure: Poor/confusing
Unknown/Multiple | error message
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider the following code:
{{{#!hs
module Foo where
x :: Int
x = const 42 _
}}}
When compiles, this gives the following suggestion:
{{{
$ /opt/ghc/8.6.1/bin/ghc Bug.hs
[1 of 1] Compiling Foo ( Bug.hs, Bug.o )
Bug.hs:4:14: error:
• Found hole: _ :: b0
Where: ‘b0’ is an ambiguous type variable
• In the second argument of ‘const’, namely ‘_’
In the expression: const 42 _
In an equation for ‘x’: x = const 42 _
• Relevant bindings include x :: Int (bound at Bug.hs:4:1)
Valid hole fits include
x :: Int (bound at Bug.hs:4:1)
otherwise :: Bool
(imported from ‘Prelude’ at Bug.hs:1:8-10
(and originally defined in ‘GHC.Base’))
False :: Bool
(imported from ‘Prelude’ at Bug.hs:1:8-10
(and originally defined in ‘GHC.Types’))
True :: Bool
(imported from ‘Prelude’ at Bug.hs:1:8-10
(and originally defined in ‘GHC.Types’))
lines :: String -> [String]
(imported from ‘Prelude’ at Bug.hs:1:8-10
(and originally defined in ‘base-4.12.0.0:Data.OldList’))
unlines :: [String] -> String
(imported from ‘Prelude’ at Bug.hs:1:8-10
(and originally defined in ‘base-4.12.0.0:Data.OldList’))
(Some hole fits suppressed; use -fmax-valid-hole-fits=N or -fno-
max-valid-hole-fits)
|
4 | x = const 42 _
| ^
}}}
One thing that's rather ugly about this is the use of the type `b0`. What
exactly //is// `b0` anyway? The only hint that the error message gives is
that it's an ambiguous type variable. But that's not terribly helpful to
figure out where `b0` arises from. Ambiguous type variables like this one
arise quite frequently when writing Haskell code, and it can often take
some sleuthing to figure out why they pop up.
simonpj had one suggestion for making ambiguous type variables less
confusing: report their provenance whenever possible. There is one notable
example of a situation where it's simple to explain from where exactly in
the source code a unification variable originates: function applications.
In particular, the program above applies the function `const 42` to `_`,
which means that the type of `const 42` is instantiated to be `b0 -> Int`.
Let's report this! Something like:
{{{
• Found hole: _ :: b0
Where: ‘b0’ is an ambiguous type variable
Arising from an application of
(const 42 :: b0 -> Int)
In the expression: const 42 _
}}}
This would go a long way to clearing up what GHC is thinking when it
reports these ambiguous type variable errors. While we can't easily report
the provenance of //every// ambiguous type variables, those arising from
function applications are quite doable. We might be able to reuse the
`CtOrigin` machinery (or take heavy inspiration from it) to accomplish
this feat.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15678>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list