This is an example of https://ghc.haskell.org/trac/ghc/ticket/12088.

 

The “type instance T List” declaration actually depends on the “type instance K List” declaration; the latter must be typechecked before the former.  But this dependency is absolutely unclear.  There’s a long discussion on the thread.  Bottom line: we don’t know a solid automated way to spot this kind of problem, so  I think we are going to ask for programmer assistance.  In this case, we’d put a “separator” after the “type instance K List” decl, to explain that it must be done first:

 

    type instance K List = Type

    ===========

    type instance T List = []

 

Currently you have to write $(return []) to get the separator, but I think we’ll add a special separator.

 

Simon

 

 

From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces@haskell.org] On Behalf Of David Menendez
Sent: 23 September 2016 05:48
To: glasgow-haskell-users@haskell.org Mailing List <Glasgow-haskell-users@haskell.org>
Subject: Type families in kind signatures with TypeInType

 

Should the code below work in GHC 8.0.1?

 

    {-# LANGUAGE TypeInType, TypeFamilies #-}

 

    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 = []

 

 

Right now, I get an error like this one:

 

min.hs:12:24: error:

    • Expected kind ‘K List -> Type’, but ‘[]’ has kind ‘* -> *’

    • In the type ‘[]’

      In the type instance declaration for ‘T’

 

which is puzzling, since K List -> Type and * -> * should be the same.

 

Obviously, TypeInType is experimental and incomplete. I’m just wondering if this sort of thing is expected to work, or if I’m doing something not yet supported or never to be supported

 

In particular, the kind signature for T is forall t -> K t -> Type, which looks like DependentHaskell.

 

--

Dave Menendez <dave@zednenem.com>
<http://www.eyrie.org/~zednenem/>