[GHC] #8979: matching type function application with type synonym application

GHC ghc-devs at haskell.org
Wed Apr 9 20:23:04 UTC 2014


#8979: matching type function application with type synonym application
-------------------------------------------+-------------------------------
       Reporter:  Lemming                  |             Owner:
           Type:  bug                      |            Status:  new
       Priority:  normal                   |         Milestone:
      Component:  Compiler (Type checker)  |           Version:  7.8.1
       Keywords:                           |  Operating System:
   Architecture:  Unknown/Multiple         |  Unknown/Multiple
     Difficulty:  Unknown                  |   Type of failure:
     Blocked By:                           |  None/Unknown
Related Tickets:                           |         Test Case:
                                           |          Blocking:
-------------------------------------------+-------------------------------
 When compiling this module:
 {{{
 {-# LANGUAGE TypeFamilies #-}

 type family F a
 type family G a

 type H a = G a

 newtype T0 a = Cons0 (F (G a))
 newtype T1 a = Cons1 (F (H a))

 f :: T0 Char -> T1 Char
 f (Cons0 a) = Cons1 a
 }}}
 I get the type error
 {{{
 MatchTypeFunction.hs:12:21:
     Couldn't match expected type ‘F (H Char)’
                 with actual type ‘F (G Char)’
     NB: ‘F’ is a type function, and may not be injective
     In the first argument of ‘Cons1’, namely ‘a’
     In the expression: Cons1 a
 }}}

 The code works with GHC-7.8 RC2 and GHC-7.4.2, but no longer with
 GHC-7.8.1.
 I guess there was some change in how deep GHC resolves type function
 application and type synonyms.

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


More information about the ghc-tickets mailing list