On Mon, Aug 18, 2003 at 07:33:47PM +0200, Konrad Hinsen wrote:
> Well, yes, because my original example was cut down to illustrate the problem 
> I had.  The full version of the class Vect is
> 
> class Vect v a where
>   (<+>) :: Floating a => v a -> v a -> v a
>   (<->) :: Floating a => v a -> v a -> v a
>   (<*>) :: Floating a => a -> v a -> v a
> 
> I need the parametrization on a in order to be able to define the type of 
> scalar multiplication.

Would this suffice?

module Foo where

class Vect v a | v -> a where
    (<+>), (<->)    :: Floating a => v -> v -> v
    (<*>)           :: Floating a => a -> v -> v

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

instance Vect (Vector a) a where
    (<+>)           = fzipWith (+)
    (<->)           = fzipWith (-)
    (<*>)           = fmap . (*)
    

instance Vect [Vector a] a where
    (<+>)           = zipWith (<+>)
    (<->)           = zipWith (<->)
    (<*>)           = fmap . (<*>)

instance Functor Vector where
    fmap f (Vector x y z)
                    = Vector (f x) (f y) (f z)

class Functor z => Ziptor z where
    fzipWith        :: (a -> b -> c) -> z a -> z b -> z c

instance Ziptor Vector where
    fzipWith f (Vector x1 y1 z1) (Vector x2 y2 z2)
                    = Vector (f x1 x2) (f y1 y2) (f z1 z2)

Hm, did anyone else ever want a Ziptor class? (I didn't, until now ;))

Happy hacking,

Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.

Attachment: pgp00000.pgp
Description: PGP signature

Reply via email to