[GHC] #14719: Caret diagnostics for GADT constructor error message don't span the whole constructor
GHC
ghc-devs at haskell.org
Thu Jan 25 14:37:59 UTC 2018
#14719: Caret diagnostics for GADT constructor error message don't span the whole
constructor
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
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:
-------------------------------------+-------------------------------------
Inspecting the caret diagnostics in the error message for this program:
{{{#!hs
{-# LANGUAGE GADTs #-}
module Bug where
data Foo1 where
MkFoo1 :: Bool
newtype Foo2 where
MkFoo2 :: Foo2
}}}
{{{
$ /opt/ghc/8.2.2/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:5:3: error:
• Data constructor ‘MkFoo1’ returns type ‘Bool’
instead of an instance of its parent type ‘Foo1’
• In the definition of data constructor ‘MkFoo1’
In the data type declaration for ‘Foo1’
|
5 | MkFoo1 :: Bool
| ^
Bug.hs:8:3: error:
• The constructor of a newtype must have exactly one field
but ‘MkFoo2’ has none
• In the definition of data constructor ‘MkFoo2’
In the newtype declaration for ‘Foo2’
|
8 | MkFoo2 :: Foo2
| ^
}}}
We notice something fishy: the carets don't span the entirey of the
constructor! Contrast this with the carets for the error message in this
program:
{{{#!hs
{-# LANGUAGE GADTs #-}
module Bug where
data Foo where
MkFoo, MkFoo :: Foo
}}}
{{{
$ /opt/ghc/8.2.2/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:5:3: error:
Multiple declarations of ‘MkFoo’
Declared at: Bug.hs:5:3
Bug.hs:5:3
|
5 | MkFoo, MkFoo :: Foo
| ^^^^^^^^^^^^^^^^^^^
}}}
Where the carets span everything that is relevant.
I know what is causing this: patch incoming.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14719>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list