[GHC] #12088: Type/data family instances in kind checking
GHC
ghc-devs at haskell.org
Fri Sep 23 05:42:03 UTC 2016
#12088: Type/data family instances in kind checking
-------------------------------------+-------------------------------------
Reporter: alexvieth | Owner:
Type: bug | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #11348, #12239 | Differential Rev(s): Phab:D2272
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
Here's another example of the phasing problem, this one posted by
[https://mail.haskell.org/pipermail/glasgow-haskell-
users/2016-September/026399.html Dave Menendez]:
{{{
{-# LANGUAGE TemplateHaskell, TypeInType, TypeFamilies #-}
module DH where
import Data.Kind (Type)
type family K t :: Type
type family T t :: K t -> Type
data List
type instance K List = Type
type instance T List = [] -- Error on this line
-- Error is:
-- * Expected kind K List -> Type, but [] has kind `* -> *`
-- In the type `[]`
-- In the type instance declaration for `T`
}}}
The reasson is the we need teh `K List` instance to typecheck the `T List`
instance.
Adding a separator just before the `instance T List` declaration makes it
work
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12088#comment:30>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list