[GHC] #15290: QuantifiedConstraints: panic "addTcEvBind NoEvBindsVar"
GHC
ghc-devs at haskell.org
Mon Jun 25 15:19:39 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):
Actually, it turns out that the approach in comment:26 isn't feasible. It
breaks on the program in comment:15, as it generates the following code:
{{{#!hs
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module T15290b where
import Data.Coerce
class C a where
c :: Int -> forall b. b -> a
instance C Int where
c _ _ = 42
newtype Age = MkAge Int
-- deriving C
instance C Age where
c = coerce (c :: Int -> forall b. b -> Int) :: Int -> forall b. b -> Age
}}}
{{{
$ ghc Bug.hs
[1 of 1] Compiling T15290b ( Bug.hs, Bug.o )
Bug.hs:19:7: error:
• Couldn't match representation of type ‘b0’ with that of ‘b1’
arising from a use of ‘coerce’
‘b1’ is a rigid type variable bound by
a type expected by the context:
Int -> forall b1. b1 -> Age
at Bug.hs:19:50-74
• In the expression:
coerce (c :: Int -> forall b. b -> Int) ::
Int -> forall b. b -> Age
In an equation for ‘c’:
c = coerce (c :: Int -> forall b. b -> Int) ::
Int -> forall b. b -> Age
In the instance declaration for ‘C Age’
|
19 | c = coerce (c :: Int -> forall b. b -> Int) :: Int -> forall b. b
-> Age
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
Since this does typecheck with the `TypeApplications`-based approach, I'll
go with that one.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15290#comment:29>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list