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

GHC ghc-devs at haskell.org
Thu Jun 21 14:22:19 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:
      Blocked By:                    |             Blocking:  9123, 14883
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 I don't think your workaround is sufficient to avoid the issue. Consider
 what would happen if we had a variant of `join` with this type signature:

 {{{#!hs
 join  :: (forall b. b -> a) -> m (m a) -> m a
 }}}

 If we plug that in to our proposed scheme:

 {{{#!hs
 {-# LANGUAGE TypeApplications, ImpredicativeTypes, ScopedTypeVariables,
              QuantifiedConstraints, StandaloneDeriving,
 GeneralizedNewtypeDeriving #-}

 module T15290 where

 import Prelude hiding ( Monad(..) )
 import Data.Coerce ( Coercible, coerce )

 class Monad m where
   join  :: (forall b. b -> a) -> m (m a) -> m a

 newtype StateT s m a = StateT { runStateT :: s -> m (s, a) }

 instance Monad m => Monad (StateT s m) where

 newtype IntStateT m a = IntStateT { runIntStateT :: StateT Int m a }

 instance (Monad m, forall p q. Coercible p q => Coercible (m p) (m q))
       => Monad (IntStateT m) where

     join = coerce
           @((forall b. b -> a) -> StateT Int m (StateT Int m a) -> StateT
 Int m a)
           @((forall b. b -> a) -> IntStateT m (IntStateT m a)   ->
 IntStateT m a)
           join :: forall a. (forall b. b -> a) -> IntStateT m (IntStateT m
 a) -> IntStateT m a
 }}}

 Then that, too, will panic:

 {{{
 $ /opt/ghc/head/bin/ghc Bug.hs
 [1 of 1] Compiling T15290           ( Bug.hs, Bug.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.5.20180616 for x86_64-unknown-linux):
         addTcEvBind NoEvBindsVar
   [G] df_a1pg
     = \ (@ p_aW5) (@ q_aW6) (v_B1 :: Coercible p_aW5 q_aW6) ->
         coercible_sel
           @ *
           @ (m_a1nx[ssk:1] p_aW5)
           @ (m_a1nx[ssk:1] q_aW6)
           (df_a1nz @ p_aW5 @ q_aW6 v_B1)
   a1og
   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
 }}}

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


More information about the ghc-tickets mailing list