Id is an operation over types yielding a type, as such it doesn't make much sense to me to have (Id a -> Id a) but rather something like (a -> Id a). One could make this compile by adding the obvious instance:
type instance Id a = a
Curiously, is this a reduction from a real world use of families? I just can't think of how a (Fam a -> Fam a) function would be of use. Cheers, Thomas Ganesh Sittampalam wrote:
The following program doesn't compile in latest GHC HEAD, although it does if I remove the signature on foo'. Is this expected?
Cheers,
Ganesh
{-# LANGUAGE TypeFamilies #-} module Test7 where
type family Id a
type instance Id Int = Int
foo :: Id a -> Id a foo = id
foo' :: Id a -> Id a foo' = foo _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe