[GHC] #15704: Different saturations of the same polymorphic-kinded type constructor aren't seen as apart types

GHC ghc-devs at haskell.org
Thu Oct 4 05:38:13 UTC 2018


#15704: Different saturations of the same polymorphic-kinded type constructor
aren't seen as apart types
-------------------------------------+-------------------------------------
           Reporter:  mniip          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.6.1
  (Type checker)                     |
           Keywords:  TypeFamilies   |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# LANGUAGE TypeFamilies, PolyKinds #-}

 module A where

 data family D :: k

 type family F (a :: k) :: *

 type instance F (D Int) = Int
 type instance F (f a b) = Char
 type instance F (D Int Bool) = Char
 }}}

 The last equation, even though a specialization of the middle one, trips
 up the equality consistency check:
 {{{#!hs
 a.hs:9:15: error:
     Conflicting family instance declarations:
       F (D Int) = Int -- Defined at a.hs:9:15
       F (D Int Bool) = Char -- Defined at a.hs:10:15
   |
 9 | type instance F (D Int) = Int
   |               ^
 }}}

 So GHC is able to infer that `D Int ~/~ f a b` because `D ~/~ f a`, but
 for some reason the same reasoning doesn't work for `D ~/~ D a`.

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


More information about the ghc-tickets mailing list