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

GHC ghc-devs at haskell.org
Fri Jun 22 15:40:15 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 RyanGlScott):

 On the subject of the actual panic observed in this ticket, I don't think
 Simon's commit quite fixed it. I'm still observing the panic on commit
 122ba98af22c2b016561433dfa55bbabba98d972 with this program (taken from
 #14883):

 {{{#!hs
 {-# LANGUAGE ConstraintKinds #-}
 {-# LANGUAGE ImpredicativeTypes #-}
 {-# LANGUAGE InstanceSigs #-}
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# LANGUAGE QuantifiedConstraints #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeApplications #-}
 module Bug where

 import Data.Coerce
 import Data.Kind

 type Representational1 m = (forall a b. Coercible a b => Coercible (m a)
 (m b) :: Constraint)

 class Representational1 f => Functor' f where
   fmap' :: (a -> b) -> f a -> f b

 class Functor' f => Applicative' f where
   pure'  :: a -> f a
   (<*>@) :: f (a -> b) -> f a -> f b

 class Functor' t => Traversable' t where
   traverse' :: Applicative' f => (a -> f b) -> t a -> f (t b)

 -- Typechecks
 newtype T1 m a = MkT1 (m a) deriving (Functor', Traversable')
 }}}
 {{{
 $ ghc/inplace/bin/ghc-stage2 Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
 ghc-stage2: panic! (the 'impossible' happened)
   (GHC version 8.7.20180621 for x86_64-unknown-linux):
         addTcEvBind NoEvBindsVar
   [G] df_a1bF
     = \ (@ a_asM) (@ b_asN) (v_B1 :: Coercible a_asM b_asN) ->
         coercible_sel
           @ *
           @ (m_a1bn[sk:1] a_asM)
           @ (m_a1bn[sk:1] b_asN)
           (df_a1bE @ a_asM @ b_asN v_B1)
   a1bw
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1164:37 in
 ghc:Outputable
         pprPanic, called at compiler/typecheck/TcRnMonad.hs:1404:5 in
 ghc:TcRnMonad
 }}}

 The panic does not occur if I derive `Traversable'` through
 `StandaloneDeriving`.

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


More information about the ghc-tickets mailing list