[GHC] #14113: Error message carets point at the wrong places in the presence of CPP macros

#14113: Error message carets point at the wrong places in the presence of CPP macros -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | 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: -------------------------------------+------------------------------------- Here's a program which doesn't typecheck: {{{#!hs {-# LANGUAGE CPP #-} module Bug where #define FOO putStrLn 4 main :: IO () main = FOO }}} The error message it gives looks kind of strange, however: {{{ GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ryanglscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:7:17: error: • No instance for (Num String) arising from the literal ‘4’ • In the first argument of ‘putStrLn’, namely ‘4’ In the expression: putStrLn 4 In an equation for ‘main’: main = putStrLn 4 | 7 | main = FOO | ^ }}} That caret seems to be pointing as if `FOO` had been replaced by `putStrLn 4` in the diagnostic, but since it hadn't, it just points off into space. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14113 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14113: Error message carets point at the wrong places in the presence of CPP macros -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: 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 Rufflewind): The issue is similar to #13388 but, unlike hsc2hs, my understanding is that cpp doesn't fall under the purview of the GHC project (yet?), so it's not possible to coerce it into outputting column information. One could prevent the caret from pointing past the actual line, but that only masks the problem under certain circumstances. Another option is to simply not show the caret if cpp is involved. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14113#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14113: Error message carets point at the wrong places in the presence of CPP macros -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: 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): Replying to [comment:1 Rufflewind]:
One could prevent the caret from pointing past the actual line, but that only masks the problem under certain circumstances.
What do you mean by "masks the problem"? I'd be content with a solution similar to how `gcc` handles CPP macros when displaying carets: {{{#!c #define FOO return "wat"; int main() { FOO } }}} {{{ $ gcc wat.c wat.c: In function ‘main’: wat.c:1:20: warning: return makes integer from pointer without a cast [-Wint-conversion] #define FOO return "wat"; ^ wat.c:4:3: note: in expansion of macro ‘FOO’ FOO ^~~ }}} But I'm not familiar with how tightly integrated `gcc` and `cpp` are (as opposed to GHC and `cpp`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14113#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14113: Error message carets point at the wrong places in the presence of CPP macros -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: 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 Rufflewind):
What do you mean by "masks the problem"?
As in it will only hide the problem when the column number is obviously wrong (exceeds the length of the original line).
I'd be content with a solution similar to how `gcc` handles CPP macros when displaying carets:
I think gcc has some internal magic with its cpp (and same for clang). If you compile using `gcc -E wat.c | gcc -x c -` you will run into exactly the same bug here. {{{ wat.c: In function ‘main’: wat.c:4:12: warning: return makes integer from pointer without a cast [-Wint-conversion] FOO ^ }}} cpp simply does not provide ghc with adequate line information to determine the correct column. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14113#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

I think gcc has some internal magic with its cpp (and same for clang). If you compile using `gcc -E wat.c | gcc -x c -` you will run into exactly
#14113: Error message carets point at the wrong places in the presence of CPP macros -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: 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): Replying to [comment:3 Rufflewind]: the same bug here.
{{{ wat.c: In function ‘main’: wat.c:4:12: warning: return makes integer from pointer without a cast
[-Wint-conversion]
FOO ^ }}}
cpp simply does not provide ghc with adequate line information to
determine the correct column. Urk, I was afraid of that. Well, if there isn't a reliable way to obtain this information, I suppose there isn't much we can do here. You mentioned that we could suppress the caret if CPP is involved, although I don't know if it's possible to reliably detect that. Alternatively, we could not do anything and close this as wontfix. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14113#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14113: Error message carets point at the wrong places in the presence of CPP macros -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: 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 Rufflewind): I feel that suppressing carets for CPPed files could hurt usability in the cases where the bug doesn't occur. I'd say this should be filed under: https://ghc.haskell.org/trac/ghc/wiki/Proposal/NativeCpp If that proposal makes progress, then we could resolve this much more easily. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14113#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14113: Error message carets point at the wrong places in the presence of CPP macros -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: cpp 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => cpp -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14113#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC