[GHC] #15986: Poor error message source location reporting with unsaturated type family

#15986: Poor error message source location reporting with unsaturated type family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Keywords: TypeFamilies, | Operating System: Unknown/Multiple TypeErrors | Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If you compile this program: {{{#!hs {-# LANGUAGE TypeFamilies #-} module Bug where newtype WrapChar f = MkWrapChar (f Char) type family F a type family T a type instance T Int = WrapChar F }}} Then you'll get this error message: {{{ $ /opt/ghc/8.6.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:7:15: error: • The type family ‘F’ should have 1 argument, but has been given none • In the type instance declaration for ‘T’ | 7 | type instance T Int = WrapChar F | ^ }}} The thing is, the location of that caret is rather unfocused. It's pointing at `T`, but the real culprit is `F`! I know that GHC can do better here because other error messages actually get this right. For instance, if you change the `T Int` instance to this: {{{#!hs type instance T Int = F }}} Then GHC will actually point to `F` in the resulting error message: {{{ $ /opt/ghc/8.6.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:7:23: error: • Expecting one more argument to ‘F’ Expected a type, but ‘F’ has kind ‘* -> *’ • In the type ‘F’ In the type instance declaration for ‘T’ | 7 | type instance T Int = F | ^ }}} If GHC can point to the right place in the source code in this situation, then it ought to get the earlier situation right as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15986 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15986: Poor error message source location reporting with unsaturated type family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: TypeFamilies, | 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Now that I think about this some more, I'm less confident in my declaration that "I know GHC can do better here". That's because the two error messages that I pointed out in the original comments actually come from two entirely different compilation passes. The latter error message (`Expecting one more argument to ‘F’`) arises during typechecking, which works over source code—that is, where everything has a `SrcSpan` attached. The former error message (`The type family ‘F’ should have 1 argument`), however, arises //after// typechecking (during some //post hoc// validity checks in `TcValidity`) when we only have `Type`s floating around. The problem is that `Type`s don't have `SrcSpan`s attached to all of their subcomponents like `HsType GhcRn`s do, so it's harder to tell where to report errors during validity checking. Perhaps this is a sign that this bug can't reasonably be fixed until #15479 is implemented (i.e., when typechecking returns `HsType GhcTc` instead of `Type`). Unless someone can see a better path forward here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15986#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15986: Poor error message source location reporting with unsaturated type family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: duplicate | Keywords: TypeFamilies, | TypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #15479 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #15479 Comment: This is just one aspect of #15479. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15986#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC