Ch. A. Herrmann wrote:
> [...] ghc-2.08 typechecker reports the following error message in the
> type definition of function "foo" which uses the instantiated "St":
> 
>   `St' should have no arguments, but has been given 1 .
> [...]
> type St = State TS
> [...]

It works if you change the above line to

   type St a = State TS a

If I read the Haskell report correctly, your version should work, too,
and this is a bug in GHC.  Section 4.2.2 says:

   [...] The kind of the new type constructor T is of the form
   k1->...->kk->k where the kinds ki of the arguments ui and k of the
   right hand side t are determined by kind inference as described in
   Section 4.6. For example, the following definition can be used to
   provide an alternative way of writing the list type constructor:

   type List = []

The following example fails in GHC, too:

   module Foo where
   type List = []
   bar :: List Char
   bar = "doesn't work in GHC"

GHC says:

   kind.hs:3: `List' should have no arguments, but has been given 1 .

-- 
Sven Panne                                        Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik                     FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen              Oettingenstr. 67
mailto:[EMAIL PROTECTED]            D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne

Reply via email to