[GHC] #10177: Typeable solver regression

GHC ghc-devs at haskell.org
Sat Mar 21 20:53:54 UTC 2015


#10177: Typeable solver regression
-------------------------------------+-------------------------------------
              Reporter:  glguy       |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  highest     |         Milestone:  7.10.1
             Component:  Compiler    |           Version:  7.10.1-rc3
  (Type checker)                     |  Operating System:  Unknown/Multiple
              Keywords:              |   Type of failure:  GHC rejects
          Architecture:              |  valid program
  Unknown/Multiple                   |        Blocked By:
             Test Case:              |   Related Tickets:
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 This bug is known and fixed in master. Simon and Austin and Iavor are all
 aware of it. This ticket exists to ensure that the fix doesn't get lost.

 This code breaks under the Typeable solver in 7.10.1-rc3 and is fixed in
 master.

 The relevant commit in master is 3a0019e3672097761e7ce09c811018f774febfd2
 : Improve `Typeable` solver.

 {{{
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE FlexibleContexts #-}
 module Bug where

 import Data.Typeable

 newtype V n a = V [a]

 class    Typeable a                   => C a
 instance (Typeable (V n), Typeable a) => C (V n a)

 -- Bug.hs:13:10:
 --  Could not deduce (Typeable (V n a))
 --    arising from the superclasses of an instance declaration
 --  from the context (Typeable (V n), Typeable a)
 --    bound by the instance declaration at Bug.hs:13:10-50
 --  In the instance declaration for ‘C (V n a)’
 }}}

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


More information about the ghc-tickets mailing list