Type design question

Konrad Hinsen hinsen@cnrs-orleans.fr
Fri, 25 Jul 2003 15:01:18 +0200


I am a Haskell newbie working on my first serious test case, and I would =
like=20
some feedback from the experts to make sure I am not doing anything stupi=
d=20
;-)

My applications are numerical (one goal of my current tests being to chec=
k how=20
much of a performance penalty I will pay for using Haskell as opposed to=20
C/C++) and involve a lot of geometry. Therefore I started by defining som=
e=20
appropriate types, in particular vectors. So here we go:

-- Most general: element of a vector space.
-- Operations: addition, subtraction, and multiplication by a scalar
class Vect v 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

-- Vector space with a scalar product
-- Adds dot product and norm
class Vect v =3D> VectSProd v where
  dot :: Floating a =3D> v a -> v a -> a
  norm :: Floating a =3D> v a -> a
  norm x =3D sqrt (dot x x)
data Floating a =3D> Vector a =3D Vector !a !a !a
     deriving (Eq, Show)

-- Standard vector in 3D space
instance Vect Vector where
  (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2)
         =3D Vector (x1+x2) (y1+y2) (z1+z2)
  (<->) (Vector x1 y1 z1) (Vector x2 y2 z2)
         =3D Vector (x1-x2) (y1-y2) (z1-z2)
  (<*>) s (Vector x y z) =3D Vector (s*x) (s*y) (s*z)

instance VectSProd Vector where
  dot (Vector x1 y1 z1) (Vector x2 y2 z2) =3D x1*x2+y1*y2+z1*z2

cross :: Floating a =3D> Vector a -> Vector a -> Vector a
cross (Vector x1 y1 z1) (Vector x2 y2 z2)
      =3D Vector (y1*z2-z1*y2) (z1*x2-x1*z2) (x1*y2-y1*x2)



I would like to keep the numerical representation as general as possible,=
 in=20
particular to postpone decisions about precision (Float, Double, eventual=
ly=20
arbitrary precision arithmetic) as much as possible. Therefore the "Float=
ing=20
a" constraint. Which leads to my first question: doing it the way I did, =
I=20
find myself having to add a "Floating a" constraint to almost every funct=
ion=20
specification with a vector argument. I would prefer to specify once and =
for=20
all that vector elements need to be "Floating", everywhere. Is there a wa=
y of=20
doing that?


Next, I would like to define some stuff for simulations of atomic systems=
=2E=20
There are two kinds of environments for such simulations, infinite (no=20
boundaries) and periodic (topologically a torus surface). The essential=20
difference is the way that distances are calculated.

-- General simulation universe properties
class Universe u where
  distanceVector :: Floating a =3D> u -> (Vector a) -> (Vector a) -> (Vec=
tor a)
  distance :: Floating a =3D> u -> (Vector a) -> (Vector a) -> a
  distance u v1 v2 =3D norm (distanceVector u v1 v2)

-- Infinite universe
data InfiniteUniverse =3D InfiniteUniverse

instance Universe InfiniteUniverse where
  distanceVector u v1 v2 =3D v2 <-> v1

-- Periodic universe
data Floating a =3D> OrthorhombicUniverse a =3D OrthorhombicUniverse a a =
a

instance Floating a =3D> Universe (OrthorhombicUniverse a) where
  distanceVector (OrthorhombicUniverse a b c)
      (Vector x1 y1 z1) (Vector x2 y2 z2)
      =3D Vector (fmod (x2-x1) a) (fmod (y2-y1) b) (fmod (z2-z1) c)
        where fmod x y =3D x - y*truncate (x/y)


And here I run into a problem. The "Floating a" constraint on=20
OrthorhombicUniverse has the same purpose as for vectors, the three argum=
ents=20
are the dimensions of the box that is periodically replicated. The compil=
er=20
complains about the definition of distanceVector:

ERROR "/home/hinsen/haskell/md/Universe.hs":24 - Inferred type is not gen=
eral=20
enough
*** Expression    : distanceVector
*** Expected type : (Universe (OrthorhombicUniverse a), Floating b) =3D>=20
OrthorhombicUniverse a -> Vector b -> Vector b -> Vector b
*** Inferred type : (Universe (OrthorhombicUniverse a), Floating a) =3D>=20
OrthorhombicUniverse a -> Vector a -> Vector a -> Vector a

I do, in fact, want "Floating a" and "Floating b" to enforce the same typ=
e,=20
but how can I do that?

BTW, in case anyone wonders why I used a class for "Universe" instead of=20
simply defining

data Universe =3D InfiniteUniverse | OrthorhombicUniverse a a a

the reason is that I want to leave the option of adding differently shape=
d=20
universes later on.

Konrad.