
Dear Haskell, Most of the time we get along well. But, I'm growing weary of the arguments, fights, and nitpicking when I try to implement new mathematical types and overload your operators. I don't know how to cooperate with your type systems. At moments like this, I think about getting back together with C++. I love you. But, I also love implementing complex numbers, vectors, matrices, and quaternions, and Galois fields. C++ is not nearly as elegant and beautiful as you. But, C++ doesn't complain when I try to do this. Isn't there some way we can work things out so I can implement these types with you? Seriously, I'm trying to implement a vector. I'm starting with vector addition: {- This code is works with Glasgow, ghci, with these options: -fglasgow-exts -fallow-undecidable-instances -fno-monomorphism-restriction -fallow-incoherent-instances -} data Vector a = Vector [a] deriving Show class Add a b c | a b -> c where (.+) :: a -> b -> c instance Add Int Int Int where (.+) x y = x + y instance Add Int Double Double where (.+) x y = (fromIntegral x) + y instance Add Double Int Double where (.+) x y = x + (fromIntegral y) instance Add Double Double Double where (.+) x y = x + y instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) where (.+) (Vector x) (Vector y) = Vector (zipWith (.+) x y) vi1 = Vector [(1::Int)..3] vi2 = Vector [(10::Int),15,2] vd1 = Vector [(1::Double)..3] vd2 = Vector [(10::Double),15,2] test1 = vi1 .+ vi2 test2 = vi1 .+ vd2 test3 = vd1 .+ vi2 test4 = vd1 .+ vd2 v1 = Vector [1,2,3] v2 = Vector [10,15,2] However, it is necessary to explicitly nail down the type of the Vector. v1 and v2 are more general. *Main> :t v1 v1 :: forall a. (Num a) => Vector a *Main> :t v2 v2 :: forall a. (Num a) => Vector a *Main> test2 I'd like for .+ to work with v1 and v2. So, I can use things like Vector [1,2,3] in expressions, instead of Vector[(1::Int),2,3]. However, v1 and v2 do not work with .+ in the code I produced above. Does anyone have any ideas how to make this work? I hoped defining .+ more generally for instances of Num would make my vector addition code work with v1 and v2. My failed attempt involved making the following changes . . . -- I added this instance (Num d) => Add d d d where (.+) x y = x + y -- instance Add Int Int Int where -- (.+) x y = x + y instance Add Int Double Double where (.+) x y = (fromIntegral x) + y instance Add Double Int Double where (.+) x y = x + (fromIntegral y) -- instance Add Double Double Double where -- (.+) x y = x + y When I make these changes and compile, I get the following error messages on the declaration of test1 and test4. . . Vector2.hs:38:12: Overlapping instances for Add (Vector Int) (Vector Int) (Vector Int) arising from use of `.+' at Vector2.hs:38:12-13 Matching instances: Vector2.hs:31:0: instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) Vector2.hs:15:0: instance (Num d) => Add d d d In the definition of `test1': test1 = vi1 .+ vi2 Vector2.hs:41:12: Overlapping instances for Add (Vector Double) (Vector Double) (Vector Double) arising from use of `.+' at Vector2.hs:41:12-13 Matching instances: Vector2.hs:31:0: instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) Vector2.hs:15:0: instance (Num d) => Add d d d In the definition of `test4': test4 = vd1 .+ vd2 I interpret this as saying that the compiler doesn't know if the .+ in "test1 = vi1 .+ vi2" should match the Vector instance or the Num instance. I could understand this if Vector was an instance of class Num. However, this is not the case. I figure either Glasgow has a bug or I don't really understand the error message. I'd be grateful for any suggestions or pointers to information on how to implement vectors (or other mathematical types) so they seamlessly and intuitively work with types, classes and operators already built into Haskell. Or, if someone could point to a more intermediate level book on working with the Haskell type system, that would be great.

Implicit conversion is a mess. Suppose that
test5 = v1 + v2
Now,
test5 :: (Add (Vector a) (Vector a1) (Vector c), Num a, Num a1) => Vector c
Note that a and a1 don't occur on the right hand side of the =>, so
the only way that they could be determined is if there was a
functional dependency c -> a a1, but there isn't, and furthermore,
your instances violate the addition of such a dependency.
The fundamental problem here is that there's no one way to compute
test5, even if we force it to be Vector Double. Do we perform
fromIntegrals or don't we? There's no way to tell what is desired.
On the other hand, elegant vector space libraries are possible. Here's
a short module I wrote for general inner product spaces in a small
raytracer:
{-# OPTIONS -fglasgow-exts #-}
module Space where
-- Class for an abstract inner product space
class (Floating f) => Space f v | v -> f where
vZero :: v -- representation for the zero vector
vAdd :: v -> v -> v -- addition
vMul :: f -> v -> v -- left scalar multiply
vInner :: v -> v -> f -- inner product
vNeg v = (-1) `vMul` v
v `vSub` w = v `vAdd` (vNeg w)
a `vDiv` v = recip a `vMul` v
vNorm v = sqrt (v `vInner` v)
vDistance v w = vNorm (w `vSub` v)
vNormalise v = (vNorm v) `vDiv` v
-- shorthand infix operators
-- note that the angle brackets go next to vectors
a <+> b = vAdd a b
a <-> b = vSub a b
a <*> b = vInner a b
r *> a = vMul r a
a <* r = vMul r a
r /> a = vDiv r a
a r = vDiv r a
data V3 = V3 !Double !Double !Double deriving (Eq, Show)
instance Space Double V3 where
vZero = V3 0 0 0
vAdd (V3 x y z) (V3 x' y' z') = V3 (x + x') (y + y') (z + z')
vMul a (V3 x y z) = V3 (a*x) (a*y) (a*z)
vInner (V3 x y z) (V3 x' y' z') = x*x' + y*y' + z*z'
v3Cross (V3 x y z) (V3 x' y' z') = V3 (y*z' - z*y') (z*x' - x*z') (x*y' - y*x')
squareDistance v w = let d = v <-> w in d <*> d
--- cut here
hope this helps
- Cale
On 22/12/05, Jeff.Harper@handheld.com
Dear Haskell,
Most of the time we get along well. But, I'm growing weary of the arguments, fights, and nitpicking when I try to implement new mathematical types and overload your operators. I don't know how to cooperate with your type systems. At moments like this, I think about getting back together with C++.
I love you. But, I also love implementing complex numbers, vectors, matrices, and quaternions, and Galois fields. C++ is not nearly as elegant and beautiful as you. But, C++ doesn't complain when I try to do this. Isn't there some way we can work things out so I can implement these types with you?
Seriously, I'm trying to implement a vector. I'm starting with vector addition:
{- This code is works with Glasgow, ghci, with these options: -fglasgow-exts -fallow-undecidable-instances -fno-monomorphism-restriction -fallow-incoherent-instances -}
data Vector a = Vector [a] deriving Show
class Add a b c | a b -> c where (.+) :: a -> b -> c
instance Add Int Int Int where (.+) x y = x + y
instance Add Int Double Double where (.+) x y = (fromIntegral x) + y
instance Add Double Int Double where (.+) x y = x + (fromIntegral y)
instance Add Double Double Double where (.+) x y = x + y
instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) where (.+) (Vector x) (Vector y) = Vector (zipWith (.+) x y)
vi1 = Vector [(1::Int)..3] vi2 = Vector [(10::Int),15,2] vd1 = Vector [(1::Double)..3] vd2 = Vector [(10::Double),15,2] test1 = vi1 .+ vi2 test2 = vi1 .+ vd2 test3 = vd1 .+ vi2 test4 = vd1 .+ vd2
v1 = Vector [1,2,3] v2 = Vector [10,15,2]
However, it is necessary to explicitly nail down the type of the Vector. v1 and v2 are more general.
*Main> :t v1 v1 :: forall a. (Num a) => Vector a *Main> :t v2 v2 :: forall a. (Num a) => Vector a *Main> test2
I'd like for .+ to work with v1 and v2. So, I can use things like Vector [1,2,3] in expressions, instead of Vector[(1::Int),2,3]. However, v1 and v2 do not work with .+ in the code I produced above.
Does anyone have any ideas how to make this work? I hoped defining .+ more generally for instances of Num would make my vector addition code work with v1 and v2. My failed attempt involved making the following changes . . .
-- I added this instance (Num d) => Add d d d where (.+) x y = x + y
-- instance Add Int Int Int where -- (.+) x y = x + y
instance Add Int Double Double where (.+) x y = (fromIntegral x) + y
instance Add Double Int Double where (.+) x y = x + (fromIntegral y)
-- instance Add Double Double Double where -- (.+) x y = x + y
When I make these changes and compile, I get the following error messages on the declaration of test1 and test4. . .
Vector2.hs:38:12: Overlapping instances for Add (Vector Int) (Vector Int) (Vector Int) arising from use of `.+' at Vector2.hs:38:12-13 Matching instances: Vector2.hs:31:0: instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) Vector2.hs:15:0: instance (Num d) => Add d d d In the definition of `test1': test1 = vi1 .+ vi2
Vector2.hs:41:12: Overlapping instances for Add (Vector Double) (Vector Double) (Vector Double) arising from use of `.+' at Vector2.hs:41:12-13 Matching instances: Vector2.hs:31:0: instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) Vector2.hs:15:0: instance (Num d) => Add d d d In the definition of `test4': test4 = vd1 .+ vd2
I interpret this as saying that the compiler doesn't know if the .+ in "test1 = vi1 .+ vi2" should match the Vector instance or the Num instance. I could understand this if Vector was an instance of class Num. However, this is not the case. I figure either Glasgow has a bug or I don't really understand the error message.
I'd be grateful for any suggestions or pointers to information on how to implement vectors (or other mathematical types) so they seamlessly and intuitively work with types, classes and operators already built into Haskell. Or, if someone could point to a more intermediate level book on working with the Haskell type system, that would be great.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, 22 Dec 2005 Jeff.Harper@handheld.com wrote:
Dear Haskell,
Most of the time we get along well. But, I'm growing weary of the arguments, fights, and nitpicking when I try to implement new mathematical types and overload your operators. I don't know how to cooperate with your type systems. At moments like this, I think about getting back together with C++.
I love you. But, I also love implementing complex numbers, vectors, matrices, and quaternions, and Galois fields.
quaternions and matrices are still missing, but anything else is available in: http://cvs.haskell.org/darcs/numericprelude/ For linear algebra I setup a Wiki page: http://haskell.org/hawiki/LinearAlgebra

Hello Jeff, Friday, December 23, 2005, 1:52:02 AM, you wrote: JHhc> {- JHhc> This code is works with Glasgow, ghci, with these options: JHhc> -fglasgow-exts JHhc> -fallow-undecidable-instances JHhc> -fno-monomorphism-restriction JHhc> -fallow-incoherent-instances JHhc> -} :) replace it with: {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fno-monomorphism-restriction -fallow-incoherent-instances #-} and the compiler will set this options automatically. btw, why you need to disable the monomorphism restriction? JHhc> v1 = Vector [1,2,3] JHhc> v2 = Vector [10,15,2] use instead: vector :: [Double] -> Vector Double vector = Vector v1 = vector [1,2,3] v2 = vector [10,15,2] -- Best regards, Bulat mailto:bulatz@HotPOP.com

Jeff.Harper@handheld.com wrote:
{- This code is works with Glasgow, ghci, with these options: -fglasgow-exts -fallow-undecidable-instances -fno-monomorphism-restriction -fallow-incoherent-instances -}
First off, try lighter weapons first. Be switching on all possible extensions you're also getting worse error reporting and more unexpected interactions. -fglasgow-exts and -fallow-overlapping-instances should be enough.
v1 = Vector [1,2,3] v2 = Vector [10,15,2]
I'd like for .+ to work with v1 and v2. So, I can use things like Vector [1,2,3] in expressions, instead of Vector[(1::Int),2,3].
And what do you think "work" would mean? It is unknown whether v1 and v2 contain Ints or Doubles, so it is not known how to add them. What do you expect the compiler to do? Usually the result of the addition would be known (you want a Vector Double), but with the mixed additions you defined that doesn't imply a type for v1 or v2.
Vector2.hs:38:12: Overlapping instances for Add (Vector Int) (Vector Int) (Vector Int) arising from use of `.+' at Vector2.hs:38:12-13 Matching instances: Vector2.hs:31:0: instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) Vector2.hs:15:0: instance (Num d) => Add d d d In the definition of `test1': test1 = vi1 .+ vi2
I interpret this as saying that the compiler doesn't know if the .+ in "test1 = vi1 .+ vi2" should match the Vector instance or the Num instance. I could understand this if Vector was an instance of class Num. However, this is not the case. I figure either Glasgow has a bug or I don't really understand the error message.
You don't understand the mechanism. GHC first looks at the instance head, then decides which instance to use, then tries to satisfy the context. Now try to find an instance for (Add (Vector Int) (VectorInt) (Vector Int)): Does it match (Add (Vector a) (Vector b) (Vector c))? It does. Does it match (Add d d d)? It too does. Which one is more specialized? Neither. I can't decide. You want to express a priority. This is possible, but not obvious. First, define overlapping instances in such a way than one is strictly more general: instance (Add a b c) => Add (Vector a) (Vector b) (Vector c) instance (...) => Add a b c -- see below To declare (Add d d d) you need a second class: class Add' a b c instance Num d => Add' d d d instance Add' a b c => Add a b c This should work (but I didn't test it). For three times (Vector Int), the first instance for Add is choosen, since it is strictly more specific than the second. For three times Int, only the second can match. Then the context (Add' ...) is satisfied. For three times String (which must not work), the second instance for Add matches, but the context (Add' ...) cannot be satisfied. It works a bit like Prolog written backwards and without backtracking :)
I'd be grateful for any suggestions or pointers to information on how to implement vectors (or other mathematical types) so they seamlessly and intuitively work with types, classes and operators already built into Haskell.
In general, do something more simple, as Cale suggested. The implicit conversions don't buy you much, but the type system extensions will cause lots of headaches. Udo. -- Part of any serious QA is removing Perl code the same way you go over a dilapidated building you inherit to remove chewing gum and duct tape and fix whatever was kept together for real. -- Erik Naggum

On Fri, Dec 23, 2005 at 12:12:49PM +0100, Udo Stenzel wrote:
Jeff.Harper@handheld.com wrote:
{- This code is works with Glasgow, ghci, with these options: -fglasgow-exts -fallow-undecidable-instances -fno-monomorphism-restriction -fallow-incoherent-instances -}
First off, try lighter weapons first. Be switching on all possible extensions you're also getting worse error reporting and more unexpected interactions. -fglasgow-exts and -fallow-overlapping-instances should be enough.
Indeed, I think this is a very important point, and one of the reasons I'd like to see Haskell 06 come out with a reasonable set of extensions that are known to work together well. I've gone down this path before, adding extension after extension, and it just leads to more and more confusion--since I don't understand what the extensions do, or how they change the language! -- David Roundy http://www.darcs.net
participants (6)
-
Bulat Ziganshin
-
Cale Gibbard
-
David Roundy
-
Henning Thielemann
-
Jeff.Harper@handheld.com
-
Udo Stenzel