Re: [Haskell-cafe] lists as instances of a class?

2006-07-10 Thread David House

On 10/07/06, Sebastian Sylvan <[EMAIL PROTECTED]> wrote:

Double is not a type variable.


I.e. [a] is okay, but [Double] isn't.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lists as instances of a class?

2006-07-10 Thread Greg Buchholz
David Roundy wrote:
> 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?

I think it is a "feature" of H98 intended to disallow any
possibility of overlapping instances.  If you have...

instance Vec [Double]

...there's nothing from stopping you from also declaring...

instance Num a => Vec [a]

...but since Double is a member of Num, which instance should the
compiler use?

> Or is there perhaps some other syntax by which I'd declare
> this instance? 

Not by the looks of section 4.3.2 of the Haskell Report (at least by
my reading).


Greg Buchholz

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lists as instances of a class?

2006-07-10 Thread Sebastian Sylvan

On 7/10/06, Bayley, Alistair <[EMAIL PROTECTED]> wrote:

> From: [EMAIL PROTECTED]
> [mailto:[EMAIL PROTECTED] On Behalf Of Spencer Janssen
>
> 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


Sorry, I'm struggling with this. Why is [] not of the form (T a b c ...)
?

I assume that [] is syntactic sugar for something like:

data List a = Cons a | Nil   ===>?  data [a] = (:) a | []

so [Double] is just sugar for List Double, which appears to me to be of
the form (T a b c ...).

What subtlety am I missing?



Double is not a type variable.


/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] lists as instances of a class?

2006-07-10 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Spencer Janssen
> 
> 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


Sorry, I'm struggling with this. Why is [] not of the form (T a b c ...)
?

I assume that [] is syntactic sugar for something like:

data List a = Cons a | Nil   ===>?  data [a] = (:) a | []

so [Double] is just sugar for List Double, which appears to me to be of
the form (T a b c ...).

What subtlety am I missing?

Thanks,
Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lists as instances of a class?

2006-07-10 Thread Spencer Janssen

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 <[EMAIL PROTECTED]> 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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lists as instances of a class?

2006-07-10 Thread Henning Thielemann

On Mon, 10 Jul 2006, David Roundy wrote:

> > class Vec v where
> >(.+.) :: v -> v -> v
>
> > instance Vec [Double] where
> >xs .+. ys = zipWith (+) xs ys
>
> > instance Vec Double where
> >x .+. y = x + y
>
>
> 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

What about

instance Vec a => Vec [a] where
   (.+.) = zipWith (.+.)

?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] lists as instances of a class?

2006-07-10 Thread David Roundy
(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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe