[GHC] #15290: QuantifiedConstraints: panic "addTcEvBind NoEvBindsVar"

GHC ghc-devs at haskell.org
Mon Jun 25 10:29:36 UTC 2018


#15290: QuantifiedConstraints: panic "addTcEvBind NoEvBindsVar"
-------------------------------------+-------------------------------------
        Reporter:  goldfire          |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.4.3
      Resolution:                    |             Keywords:
                                     |  QuantifiedConstraints
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:  quantified-
                                     |  constraints/T15290, T15290a
      Blocked By:                    |             Blocking:  9123, 14883
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 Good grief -- again!  comment:17 is ghastly.  Here's what is happening.
 What we are 'really' checking is
 {{{
   bar = ((coerce @(Int -> Maybe b)
                 @(Age -> Maybe b)
                 bar)
            :: forall b. Age -> Maybe b)
         :: forall b. Age -> Maybe b
 }}}
 where

 * the outer type signature comes from checking that the type of the
   method matches the type that the class expects
 * the inner one comes from the 'deriving' patch

 Because both of those type sigs ultimately from the same source,
 both 'b's happen to have the same unique. That should be fine but it
 isn't:

 * The outer forall adds `b :-> b1[sk]` to the type environment.  That's
 fine,
   even though this outer forall b does not scope; the type envt isn't
 responsible
   for resolving lexical scoping.

 * The `forall` on the inner signature is typechecked with by the
 `HsForAllTy`
   case of `tc_hs_type`, which calls
   * `tcExplicitTKBndrs`, which calls
   * `tcHsTyVarBndr`, which calls
   * `tcHsTyVarName`, '''which has a special case for type variables
 already in scope'''

 * The in-scope handling in `tcHsTyVarName` is a very special case
   intended '''only''' for the binders in the `LHSQTyVars` of an
   associated type or type instance declaration, nested inside a class
   decl. Yet it is here being used (accidentally) for the `forall` of a
   type signature, a situation that it is utterly unsuitable for.  Even
   if the tyvar for a `forall` is already in scope, that should be
   utterly irrelevant to the type signature.

 * The net result is chaos: we end up with two different skolems that
 really
   represent the same type variable.

 Conclusion: we should radically narrow the cases in which this funny
 in-scope test applies.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15290#comment:24>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list