[GHC] #15558: Locally handling an empty constraint
GHC
ghc-devs at haskell.org
Thu Aug 23 14:01:58 UTC 2018
#15558: Locally handling an empty constraint
-------------------------------------+-------------------------------------
Reporter: Ericson2314 | Owner: (none)
Type: task | Status: new
Priority: normal | Milestone: ⊥
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
error/warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
You're right, there's definitely something fishy going on with this
warning. Here's a simplified example:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
module Bug where
data T a where
MkT :: T Int
data Foo a = MkFoo ((a ~ Bool) => ())
f :: T a -> Foo a
f MkT = MkFoo ()
g :: Foo Int
g = f MkT
}}}
{{{
$ /opt/ghc/8.6.1/bin/ghci Bug.hs
GHCi, version 8.6.0.20180810: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:11:3: warning: [-Winaccessible-code]
• Couldn't match type ‘Int’ with ‘Bool’
Inaccessible code in
a pattern with constructor: MkT :: T Int, in an equation for ‘f’
• In the pattern: MkT
In an equation for ‘f’: f MkT = MkFoo ()
|
11 | f MkT = MkFoo ()
| ^^^
}}}
While there //is// inaccessible code here, the warning is highlighting the
wrong spot: it should be the argument to `MkFoo`, not the argument to `f`.
(The fact that `g` typechecks at all is a testament to this fact.) I
suspect that we're using the wrong `SrcSpan` somewhere in GHC, which
causes the reported location to be incorrect.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15558#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list