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

My applications are numerical (one goal of my current tests being to check how 
much of a performance penalty I will pay for using Haskell as opposed to 
C/C++) and involve a lot of geometry. Therefore I started by defining some 
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 => v a -> v a -> v a
  (<->) :: Floating a => v a -> v a -> v a
  (<*>) :: Floating a => a -> v a -> v a

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

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

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

cross :: Floating a => Vector a -> Vector a -> Vector a
cross (Vector x1 y1 z1) (Vector x2 y2 z2)
      = 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 
particular to postpone decisions about precision (Float, Double, eventually 
arbitrary precision arithmetic) as much as possible. Therefore the "Floating 
a" constraint. Which leads to my first question: doing it the way I did, I 
find myself having to add a "Floating a" constraint to almost every function 
specification with a vector argument. I would prefer to specify once and for 
all that vector elements need to be "Floating", everywhere. Is there a way of 
doing that?


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

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

-- Infinite universe
data InfiniteUniverse = InfiniteUniverse

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

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

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


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

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

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

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

data Universe = InfiniteUniverse | OrthorhombicUniverse a a a

the reason is that I want to leave the option of adding differently shaped 
universes later on.

Konrad.

_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to