[GHC] #10960: Closed type families don't reduce on data family instances

GHC ghc-devs at haskell.org
Mon Oct 12 18:53:00 UTC 2015


#10960: Closed type families don't reduce on data family instances
-------------------------------------+-------------------------------------
           Reporter:  exFalso        |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  7.10.2
           Keywords:  closed type    |  Operating System:  Linux
  family data                        |
       Architecture:  x86_64         |   Type of failure:  GHC rejects
  (amd64)                            |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code doesn't compile:

 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}
 module Tmp where

 data family D a
 data instance D () = D

 type family T a where
   T () = ()
   T a = Char

 try :: T (D ()) ~ Char => ()
 try = ()

 main :: IO ()
 main = return try
 }}}

 giving

 {{{
 Tmp.hs:15:15:
     Couldn't match expected type ‘Char’ with actual type ‘T (D ())’
     In the first argument of ‘return’, namely ‘try’
     In the expression: return try
     In an equation for ‘main’: main = return try
 }}}

 Is this a known limitation of closed type families?

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


More information about the ghc-tickets mailing list