no non-typevariable in instance declarations

José Romildo Malaquias romildo@urano.iceb.ufop.br
Tue, 14 Nov 2000 13:22:13 -0200


--PEIAKu/WMn1b1Hv9
Content-Type: text/plain; charset=iso-8859-1
Content-Disposition: inline
Content-Transfer-Encoding: 8bit

Hello.

I found that Hugs differs from GHC 4.08.1 and from NHC98 1.00
in instance declarations where the instance head has only
type variables: Hugs accepts them while the other two rejects.

Attached is a small program that demonstrates it.

Hugs happily runs the program and outputs the list

   ["NUM","Integer","NUM"]

NHC98 spits the message

   In file ./t.hs:
   6:23 Found a but expected one of [ ( <conid>

GHC is more verbose in its message:

   t.hs:6:
     Illegal instance declaration for `C a'
        (There must be at least one non-type-variable in the instance head)

   Compilation had errors

Why GHC and NHC98 are more restrictive than Hugs?

This style of instantiation would be very helpful when
dealing with type extensions in Haskell (based on classes
to provide the interface for common operations on
the extendable type).

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

--PEIAKu/WMn1b1Hv9
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="t.hs"

module Main where

class C a where
    ty :: a -> String

instance (Num a) => C a where
    ty _ = "NUM"

instance C Integer where
    ty _ = "Integer"

main = print [ty (234::Int), ty (234::Integer), ty (234::Double)]

--PEIAKu/WMn1b1Hv9--