More type design questions

Andre Pang ozone@algorithm.com.au
Tue, 19 Aug 2003 03:10:54 +1000


On Monday, August 18, 2003, at 04:56  PM, Konrad Hinsen wrote:

> Continuing in my quest to understand type design in Haskell, here's 
> another
> episode that leaves me scratching my head:
>
> module Foo where
>
> class Vect v a where
>   (<+>) :: Floating a => v a -> v a -> v a
>
> data Vector a = Vector a a a
>
> instance Vect Vector a where
>   (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2)
>          = Vector (x1+x2) (y1+y2) (z1+z2)
>
> instance Vect [Vector a] a where
>   (<+>) l1 l2 = zipWith (<+>) l1 l2

This seems to work (with -fglasgow-exts):

module Foo where

class Vect v where
   (<+>) :: v -> v -> v

data Vector a = Vector a a a
   deriving (Show, Eq)

instance Floating a => Vect (Vector a) where
   (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2)
          = Vector (x1+x2) (y1+y2) (z1+z2)

instance Floating a => Vect [Vector a] where
   (<+>) l1 l2 = zipWith (<+>) l1 l2

*Foo> (Vector 5 6 7) <+> (Vector 1 2 3)
Vector 6.0 8.0 10.0
*Foo> [Vector 1 2 3, Vector 10 20 30] <+> [Vector 100 200 300, Vector 4 
5 6]
[Vector 101.0 202.0 303.0,Vector 14.0 25.0 36.0]

... or does example not do something which you want it to do?


-- 
% Andre Pang : trust.in.love.to.save