[Haskell-cafe] lists as instances of a class?
Spencer Janssen
spencerjanssen at gmail.com
Mon Jul 10 11:01:05 EDT 2006
The problem isn't with lists specifically, but with any instance that
applies types (rather than type variables) to a type constructor
>From section 4.3.2 of The Haskell 98 Report: "The type (T u1 ... uk)
must take the form of a type constructor T applied to simple type
variables u1, ... uk". I've run into this restriction several times
myself, and I'm also curious whether this will change in Haskell'.
Spencer Janssen
On 7/10/06, David Roundy <droundy at darcs.net> wrote:
> (This email is a literate haskell program that fails to compile
> without -fglasgow-exts.)
>
> I'm sure I'm missing something lame here, but can someone tell me why
> we apparently can't declare a list to be an instance of a class in
> Haskell 98? Or is there perhaps some other syntax by which I'd declare
> this instance? If so, is this slated for fixing in Haskell'?
>
> $ ghc Test.lhs
>
> Test.lhs:6:1:
> Illegal instance declaration for `Vec [Double]'
> (The instance type must be of form (T a b c)
> where T is not a synonym, and a,b,c are distinct type variables)
> In the instance declaration for `Vec [Double]'
>
> > module Vec where
>
> > class Vec v where
> > (.+.) :: v -> v -> v
>
> > instance Vec [Double] where
> > xs .+. ys = zipWith (+) xs ys
>
> > instance Vec Double where
> > x .+. y = x + y
>
> feeling very stupid,
> David
>
> P.S. This is with ghc 6.4.1. And oddly enough, if you make the instance
>
> instance Num a => Vec [a] where
> xs .+. ys = zipWith (+) xs ys
>
> it works fine, but this strikes me as quite an ugly hack. I really
> want only Doubles to be instances of this class (which I've
> abbreviated for this email).
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list