[GHC] #10009: type inference regression when faking injective type families

GHC ghc-devs at haskell.org
Tue Jan 20 16:40:04 UTC 2015


#10009: type inference regression when faking injective type families
-------------------------------------+-------------------------------------
              Reporter:  aavogt      |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.10.1-rc1
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |        Blocked By:
             Test Case:              |   Related Tickets:
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 ghc-7.10.0.20141222 does not accept the program unless I uncomment the
 type signature (a :: a). ghc-7.8 accepts it as-is.

 {{{#!hs
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}

 class (UnF (F a) ~ a, Show a) => C a where
     type F a
     f :: F a -> a

 type family UnF a

 g :: forall a. C a => a -> String
 g _ = show a
   where a = f (undefined :: F a) -- :: a
 }}}

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


More information about the ghc-tickets mailing list