
#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): Hm, I've hit a roadblock when trying to switch over to the scheme proposed in comment:5. Consider this code: {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -ddump-deriv #-} module Bug where import Data.Coerce class C a where c :: Int -> forall b. b -> a instance C Int where c _ _ = 42 newtype Age = MkAge Int -- This is what -- -- deriving instance C Age -- -- would generate: instance C Age where c = coerce @( Int -> forall b. b -> a) c :: forall a. Int -> forall b. b -> a }}} This fails to typecheck: {{{ $ /opt/ghc/8.4.3/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:26:7: error: • Couldn't match representation of type ‘forall b2. b2 -> a’ with that of ‘b1 -> a’ arising from a use of ‘coerce’ • In the expression: coerce @(Int -> forall b. b -> a) c :: forall a. Int -> forall b. b -> a In an equation for ‘c’: c = coerce @(Int -> forall b. b -> a) c :: forall a. Int -> forall b. b -> a In the instance declaration for ‘C Age’ | 26 | c = coerce @( Int -> forall b. b -> a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} The same error occurs if I use `InstanceSigs`. Any ideas on how to make this work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15290#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler