Partial application of type constructors?

Robin Bate Boerop robin_bb at acm.org
Fri Apr 29 12:57:30 EDT 2005


On 19-Apr-05, at 6:34 AM, John Meacham wrote:

> This seems to be such a common question, perhaps someone could write up
> something on the wiki that goes into more depth on what the issues are
> with generalized type synonyms?

I would find this useful.  More useful would be an answer not about 
type synonyms in general, but about type synonyms in the particular 
case that is bothering me, now:

The following Haskell program fails to compile with GHC:

  > module M where
  >
  > class TakesTwo tt where
  >    f :: tt a b -> Int
  >
  > data S a b = S a b
  > type T     = (->)
  > type U a b = a -> b
  >
  > instance TakesTwo S where
  >    f _ = 1
  >
  > instance TakesTwo T where
  >    f _ = 1
  >
  > instance TakesTwo U where
  >    f _ = 1

The error message is:

u.hs:16:0:
     Type synonym `U' should have 2 arguments, but has been given 0
     In the instance declaration for `TakesTwo U'

I gather that partially applied type synonyms (the "TakesTwo U" 
instance declaration) are not allowed.  (Don't fully understand why.)  
Partially applied data types are allowed, so the "TakesTwo S" instance 
declaration is okay.  But, why is the "TakesTwo T" instance declaration 
allowed?  Isn't it the same as the "TakesTwo U"?

--
Robin
http://homepage.mac.com/robin_bb/



More information about the Glasgow-haskell-users mailing list