More type design questions

Remi Turk rturk@science.uva.nl
Mon, 18 Aug 2003 22:24:52 +0200


--ZGiS0Q5IWpPtfppv
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable

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 pro=
blem=20
> I had.  The full version of the class Vect is
>=20
> class Vect v a where
>   (<+>) :: Floating a =3D> v a -> v a -> v a
>   (<->) :: Floating a =3D> v a -> v a -> v a
>   (<*>) :: Floating a =3D> a -> v a -> v a
>=20
> I need the parametrization on a in order to be able to define the type of=
=20
> scalar multiplication.

Would this suffice?

module Foo where

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

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

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

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

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

class Functor z =3D> 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)
                    =3D 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

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

--ZGiS0Q5IWpPtfppv
Content-Type: application/pgp-signature
Content-Disposition: inline

-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.2.2 (GNU/Linux)

iD8DBQE/QTYU36VhKIVjE3sRAmkSAJ0dSXoOsOMOSBXC1pVmkHL+vlc1yACgj2Fk
xcWIHPlLcgpfPgA+tL89FMg=
=Acph
-----END PGP SIGNATURE-----

--ZGiS0Q5IWpPtfppv--