[GHC] #15290: QuantifiedConstraints: panic "addTcEvBind NoEvBindsVar"
GHC
ghc-devs at haskell.org
Tue Jun 19 03:21:26 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
Keywords: | Operating System: Unknown/Multiple
QuantifiedConstraints |
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I wanted to see if we're ready to put `join` into `Monad`. So I typed this
in:
{{{#!hs
{-# LANGUAGE QuantifiedConstraints, StandaloneDeriving,
GeneralizedNewtypeDeriving #-}
module Bug where
import Prelude hiding ( Monad(..) )
import Data.Coerce ( Coercible )
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
join :: m (m a) -> m a
newtype StateT s m a = StateT { runStateT :: s -> m (s, a) }
instance Monad m => Monad (StateT s m) where
ma >>= fmb = StateT $ \s -> runStateT ma s >>= \(s1, a) -> runStateT
(fmb a) s1
join ssa = StateT $ \s -> runStateT ssa s >>= \(s, sa) -> runStateT sa s
newtype IntStateT m a = IntStateT { runIntStateT :: StateT Int m a }
deriving instance (Monad m, forall p q. Coercible p q => Coercible (m p)
(m q)) => Monad (IntStateT m)
}}}
This looks like it should be accepted. But I get
{{{
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.5.20180617 for x86_64-apple-darwin):
addTcEvBind NoEvBindsVar
[G] df_a67k
= \ (@ p_a62C) (@ q_a62D) (v_B1 :: Coercible p_a62C q_a62D) ->
coercible_sel
@ *
@ (m_a64Z[ssk:1] p_a62C)
@ (m_a64Z[ssk:1] q_a62D)
(df_a651 @ p_a62C @ q_a62D v_B1)
a67c
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>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list