[Haskell-cafe] Kind signatures and closed type families syntax

Gautier DI FOLCO gautier.difolco at gmail.com
Sun Nov 30 00:35:46 UTC 2014


Hello all,

I have the following code:
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}

data Branch = Left | Right

type family Product (v :: Branch) (a :: k) (b :: k) :: k where
  Product Left  l r = l
  Product Right l r = r

He is doing what I expect it to do and Product has the right Kind:
*Main> :kind Product
Product :: Branch -> k -> k -> k

But when I change the Kind signature syntax, its Kind changes:
type family Product v a b :: Branch -> k -> k -> k where
Its Kind become:
*Main> :kind Product
Product :: Branch
           -> (Branch -> k -> k -> k)
           -> (Branch -> k1 -> k1 -> k1)
           -> Branch
           -> k2
           -> k2
           -> k2

It's even worse with this syntax:
type family Product :: Branch -> k -> k -> k where
Produces:
*Main> :r
[1 of 1] Compiling Main             ( product-highkind.hs, interpreted )

product-highkind.hs:13:3:
    Number of parameters must match family declaration; expected 0
    In the equations for closed type family ‘Product’
    In the type family declaration for ‘Product’
Failed, modules loaded: none.
I don't know if I'm tired or not but in the documentation [1] these
syntaxes should be equivalent.
If not, I'll take any explanations.

Thanks in advance for your help.

[1]
https://downloads.haskell.org/~ghc/7.8.2/docs/html/users_guide/kind-polymorphism.html
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141130/ec92c9a5/attachment.html>


More information about the Haskell-Cafe mailing list