Thanks. Yes I read this is syntactic sugar, and I actually like that approach; it automatically "encapsulates" the data fileds by functions, which from an OO programmers point of view, is a good thing. I'm doing my best to get rid of that OO view though, which is not easy after 15 years of OO and 10 years of imperative programming ;-)
However, I never understood why Haskell doesn't permit the same name for a function acting on different types, even without using type classes. Must be some deeper reason for it (currying?) Now the type class approach is interesting; it's like saying "any type that has an XXX field"... Lot's of typing, but IMHO it's worth it because it abstracts the concept of a field. I read some papers that some extensions got proposed to treat "fields" as first class values, so one could just do "get X (Vector2 1 2)". Did something like that make it into GHC? So the example becomes: module Main where -- "Vector" is a rather stupid example, because Haskell has tuples data Vector2 = Vector2 Float Float data Vector3 = Vector3 Float Float Float class HasX v where getX :: v -> Float setX :: v -> Float -> v class HasY v where getY :: v -> Float setY :: v -> Float -> v class HasZ v where getZ :: v -> Float setZ :: v -> Float -> v instance HasX Vector2 where getX (Vector2 x y) = x setX (Vector2 x y) value = Vector2 value y instance HasY Vector2 where getY (Vector2 x y) = y setY (Vector2 x y) value = Vector2 x value instance HasX Vector3 where getX (Vector3 x y z) = x setX (Vector3 x y z) value = Vector3 value y z instance HasY Vector3 where getY (Vector3 x y z) = y setY (Vector3 x y z) value = Vector3 x value z instance HasZ Vector3 where getZ (Vector3 x y z) = z setZ (Vector3 x y z) value = Vector3 x y value test v x = getY (setX v x) main = print $ test (Vector2 1 2) 3 -----Original Message----- From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Paul Johnson Sent: Saturday, June 16, 2007 12:51 AM To: Andrew Coppin Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Haskell record extension? Andrew Coppin wrote: > [EMAIL PROTECTED] wrote: >> I'm learning Haskell. >> I was surprised that the following example did not compile: >> >> data Vector2 = Vector2 { x :: Float, y :: Float } >> data Vector3 = Vector3 { x :: Float, y :: Float, z :: Float } >> >> error: "Multiple declarations of `Main.x'" >> > > AFAIK, GHC doesn't implement any fix for this. (I've been wrong before > tho...) This is a feature, not a bug. Haskell in general does not let you give two functions the same name (which is what you want to do). This is true of all functions, not just the ones implicitly defined here. Your "Vector2" type is pure syntactic sugar for: data Vector2 = Vector2 Float Float x, y :: Vector2 -> Float x (Vector2 v _) = v y (Vector2 _ v) = v So now you also want x (Vector3 v _ _) = v etc etc. And no, you can't do that because "x" on its own might refer to either version, and its not clear which one you want. Paul. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe