[Haskell] Defining Cg, HLSL style vectors in Haskell

Hello, I have to define a couple of float2, float3, float4 Cg, HLSL style vectors in Haskell. At first I was tempted to make them instances of Num, Floating, RealFrac, etc. but some of the functions defined in those classes have no sense for vectors. One such example is signum from class Num. There are several workarounds for this. One may come up with some meaning for vectors of such functions, for example: instance Num Float3 where ..... signum a | a == Float3 0 0 0 = 0 | otherwise = 1 This is silly. Other option, which I prefer, is to leave such functions undefined (that is signum=undefined, not just not defining them). Is this ok? Are there any other options? Another bugging thing is that some of the functions do have meaning for vectors but they need different signatures. For example (**) :: Floating a => a -> a -> a, for vectors should be (**) :: (Floating a, Vector v) => v -> a -> v, that is (**) applied for every component of the vector. Any workarounds for that? I know that I can scrap all those Num, Floating, RealFrac, etc. classes and define class Vector from scratch, but I really don't want to come up and use different names for +, -, etc. that will bloat the code. Last question: Does haskell have something like C++ templates? For example, some time in the future I may need types like int2, short3, etc., that behave just like float2, float3, but use different types for their components. I really, really wouldn't like to copy-paste the definitions of floatn and manually change their types to intn respectfully. Cheers. -- Slavomir Kaslev

Hello Slavomir, Tuesday, November 28, 2006, 3:46:13 PM, you wrote:
Last question: Does haskell have something like C++ templates? For example, some time in the future I may need types like int2, short3, etc., that behave just like float2, float3, but use different types for their components. I really, really wouldn't like to copy-paste the definitions of floatn and manually change their types to intn respectfully.
yes, it's named parameterized types: data Vec2 a = Vec2 !a !a instance (Num a) => Num (Vec2 a) where (Vec2 a1 a2) + (Vec2 b1 b2) = Vec2 (a1+b1) (a2+b2) .... type Float2 = Vec2 Float -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 11/28/06, Bulat Ziganshin
Hello Slavomir,
Tuesday, November 28, 2006, 3:46:13 PM, you wrote:
Last question: Does haskell have something like C++ templates? For example, some time in the future I may need types like int2, short3, etc., that behave just like float2, float3, but use different types for their components. I really, really wouldn't like to copy-paste the definitions of floatn and manually change their types to intn respectfully.
yes, it's named parameterized types:
data Vec2 a = Vec2 !a !a
instance (Num a) => Num (Vec2 a) where (Vec2 a1 a2) + (Vec2 b1 b2) = Vec2 (a1+b1) (a2+b2) ....
type Float2 = Vec2 Float
I wasn't aware of parameterized types, they are sweet. Thank you very much. What about my other questions? Do you have any suggestions? I know that this is very library specific. All I am asking is for some Haskell common sense. What would you do, if you were writing this kind of library? Cheers. -- Slavomir Kaslev

On 11/28/06, Slavomir Kaslev
On 11/28/06, Bulat Ziganshin
wrote: Hello Slavomir,
Tuesday, November 28, 2006, 3:46:13 PM, you wrote:
Last question: Does haskell have something like C++ templates? For example, some time in the future I may need types like int2, short3, etc., that behave just like float2, float3, but use different types for their components. I really, really wouldn't like to copy-paste the definitions of floatn and manually change their types to intn respectfully.
yes, it's named parameterized types:
data Vec2 a = Vec2 !a !a
instance (Num a) => Num (Vec2 a) where (Vec2 a1 a2) + (Vec2 b1 b2) = Vec2 (a1+b1) (a2+b2) ....
type Float2 = Vec2 Float
I wasn't aware of parameterized types, they are sweet. Thank you very much.
What about my other questions? Do you have any suggestions? I know that this is very library specific. All I am asking is for some Haskell common sense. What would you do, if you were writing this kind of library?
Cheers.
-- Slavomir Kaslev
Err... Actually I *am* aware of parameterized types. Almost every function function from the Prelude on lists is parameterized. I was confused by you post that parameterized types have something to do with the strictness flag '!'. Sorry for that, going home embarrassed. -- Slavomir Kaslev

Slavomir Kaslev wrote:
I have to define a couple of float2, float3, float4 Cg, HLSL style vectors in Haskell. At first I was tempted to make them instances of Num, Floating, RealFrac, etc. but some of the functions defined in those classes have no sense for vectors.
I'd suggest that this implies that these classes are not suitable for Vectors.
One such example is signum from class Num.
There are several workarounds for this. One may come up with some meaning for vectors of such functions, for example:
instance Num Float3 where ..... signum a | a == Float3 0 0 0 = 0 | otherwise = 1
This looks a bit unnatural. Also, testing equality of Floats is not generally recommended.
[snip] I know that I can scrap all those Num, Floating, RealFrac, etc. classes and define class Vector from scratch, but I really don't want to come up and use different names for +, -, etc. that will bloat the code.
While it may be tempting to want to use symbolic operators like + and -, these quickly become very confusing when more distinctions need to be made (eg between cross product, dot product, and scaling, or between transforming a position versus transforming a direction) so I'd argue that for readability descriptive names are better than symbols: class Num a => Vector v a where plus :: v a -> v a -> v a minus :: v a -> v a -> v a cross :: v a -> v a -> v a dot :: v a -> v a -> a scale :: a -> v a -> v a magSquared :: v a -> a class Num a => Transform mat vec a where transformPosition :: mat a -> vec a -> vec a transformDirection :: mat a -> vec a -> vec a instance Num a => Transform Mat44 Vec4 a where -- ... If you're doing matrix transformations, you might also like to consider using separate PositionN and DirectionN types instead of VecN to make use of the type system to catch some math bugs but I haven't looked into this myself yet so I don't know whether this would be practical or not. Best regards, Brian. -- http://www.metamilk.com

On 11/28/06, Brian Hulley
Slavomir Kaslev wrote:
I have to define a couple of float2, float3, float4 Cg, HLSL style vectors in Haskell. At first I was tempted to make them instances of Num, Floating, RealFrac, etc. but some of the functions defined in those classes have no sense for vectors.
I'd suggest that this implies that these classes are not suitable for Vectors.
One such example is signum from class Num.
There are several workarounds for this. One may come up with some meaning for vectors of such functions, for example:
instance Num Float3 where ..... signum a | a == Float3 0 0 0 = 0 | otherwise = 1
This looks a bit unnatural. Also, testing equality of Floats is not generally recommended.
Agreed about the testing floats remark. The former definition was just to scratch the point that it's silly to come up with new meanings of such operations. It's not well typed either. signum is Num a => a->a, while the former is (Vector b, Num a) => b -> a. After giving some thought on signum, I got to the point, that signum should be defined so that abs x * signum x = x holds. So it can be defined as signum (Vec2 x y) = Vec 2 (signum x) (signum y). It turns out that all the functions in Num, Floating, etc. classes can be given meaningful definitions for vectors in this pattern. That is f (Vecn x1 x2 .. xn) = Vecn (f x1) ... (f xn). And all expected laws just work. One can think of that like the way SIMD processor works, it does the same operations as on floats but on four floats at parallel. So vectors can be instances of Num, Floating, etc., after all.
[snip] I know that I can scrap all those Num, Floating, RealFrac, etc. classes and define class Vector from scratch, but I really don't want to come up and use different names for +, -, etc. that will bloat the code.
While it may be tempting to want to use symbolic operators like + and -, these quickly become very confusing when more distinctions need to be made (eg between cross product, dot product, and scaling, or between transforming a position versus transforming a direction) so I'd argue that for readability descriptive names are better than symbols:
class Num a => Vector v a where plus :: v a -> v a -> v a minus :: v a -> v a -> v a cross :: v a -> v a -> v a dot :: v a -> v a -> a scale :: a -> v a -> v a magSquared :: v a -> a
As I already said, I am leaning toward making vectors instances of Num.
class Num a => Transform mat vec a where transformPosition :: mat a -> vec a -> vec a transformDirection :: mat a -> vec a -> vec a
instance Num a => Transform Mat44 Vec4 a where -- ...
If you're doing matrix transformations, you might also like to consider using separate PositionN and DirectionN types instead of VecN to make use of the type system to catch some math bugs but I haven't looked into this myself yet so I don't know whether this would be practical or not.
The point of library is to define vectors, not as mathematical entities, but just like data representation, as they are defined in Cg/HLSL. One can take other approach and differentiate vectors between positions and directions as you suggested. In Renderman shading language, for example, those two different types are called 'point' and 'normal'. Cheers -- Slavomir Kaslev

On Tue, 28 Nov 2006, Brian Hulley wrote:
While it may be tempting to want to use symbolic operators like + and -, these quickly become very confusing when more distinctions need to be made (eg between cross product, dot product, and scaling, or between transforming a position versus transforming a direction) so I'd argue that for readability descriptive names are better than symbols:
class Num a => Vector v a where plus :: v a -> v a -> v a minus :: v a -> v a -> v a cross :: v a -> v a -> v a dot :: v a -> v a -> a scale :: a -> v a -> v a magSquared :: v a -> a
I'm currently even thinking about an alternative of the multi-parameter class Vector that is Haskell 98. The problem with the multi-parameter type class is, that you cannot define instances where 'a' is a complex number type, say Num a => Vector [Complex a] (Complex a)

[snip] If you're doing matrix transformations, you might also like to consider using separate PositionN and DirectionN types instead of VecN to make use of the type system to catch some math bugs but I haven't looked into this myself yet so I don't know whether this would be practical or not.
Indeed, not only bug catching : actually, some operations on points, vectors and normals have to be done differently. Thu
Best regards, Brian.

2006/11/28, Slavomir Kaslev
Hello,
I have to define a couple of float2, float3, float4 Cg, HLSL style vectors in Haskell. At first I was tempted to make them instances of Num, Floating, RealFrac, etc. but some of the functions defined in those classes have no sense for vectors. One such example is signum from class Num.
There are several workarounds for this. One may come up with some meaning for vectors of such functions, for example:
instance Num Float3 where ..... signum a | a == Float3 0 0 0 = 0 | otherwise = 1
This is silly. Other option, which I prefer, is to leave such functions undefined (that is signum=undefined, not just not defining them). Is this ok? Are there any other options?
Another bugging thing is that some of the functions do have meaning for vectors but they need different signatures. For example (**) :: Floating a => a -> a -> a, for vectors should be (**) :: (Floating a, Vector v) => v -> a -> v, that is (**) applied for every component of the vector. Any workarounds for that? Those are the type signatures of +, ... you can't break them. So it won't be possible to use + to add two values of different types.
I know that I can scrap all those Num, Floating, RealFrac, etc. classes and define class Vector from scratch, but I really don't want to come up and use different names for +, -, etc. that will bloat the code.
Last question: Does haskell have something like C++ templates? For example, some time in the future I may need types like int2, short3, etc., that behave just like float2, float3, but use different types for their components. I really, really wouldn't like to copy-paste the definitions of floatn and manually change their types to intn respectfully.
Yep, you have to learn that you can parametrise a type (constructor). For exemple, realise that [1], ["hello"] and "hello" are values of different types, i.e. different list types. The first one is of type [Int], the second one is [String] and the third [Char] (so you see that String is simply [Char]). In your case, you would want to define something like: Data Float2 a = Float2 a a then, optionnaly type Float2Int = Fl2 Int Bye, thu
Cheers.
-- Slavomir Kaslev _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Nov 28, 2006, at 7:46 AM, Slavomir Kaslev wrote:
Hello,
I have to define a couple of float2, float3, float4 Cg, HLSL style vectors in Haskell. At first I was tempted to make them instances of Num, Floating, RealFrac, etc. but some of the functions defined in those classes have no sense for vectors. One such example is signum from class Num.
There are several workarounds for this. One may come up with some meaning for vectors of such functions, for example:
instance Num Float3 where ..... signum a | a == Float3 0 0 0 = 0 | otherwise = 1
This is silly. Other option, which I prefer, is to leave such functions undefined (that is signum=undefined, not just not defining them). Is this ok? Are there any other options?
This will work. So long as you don't call signum, all will be well.
Another bugging thing is that some of the functions do have meaning for vectors but they need different signatures. For example (**) :: Floating a => a -> a -> a, for vectors should be (**) :: (Floating a, Vector v) => v -> a -> v, that is (**) applied for every component of the vector. Any workarounds for that?
I know that I can scrap all those Num, Floating, RealFrac, etc. classes and define class Vector from scratch, but I really don't want to come up and use different names for +, -, etc. that will bloat the code.
The inflexibility of the numeric classes is one of the well-known problems with the definition of the Haskell prelude. As you say, there are a number of things for which only a subset of the operations make sense, or where more general types are needed for the operations. There have been a couple of attempts to reformulate these classes so that they are more flexible. Here is one that I know of: http://darcs.haskell.org/numericprelude/ I haven't used it, so I can't really comment, other than to say it exists. I seem to recall that there were several other attempts in a similar vein, but my brief google search didn't turn them up. Can someone else fill in? If you want to roll your own, you can still use the nice names if you explicitly import the prelude and hide names. Eg, import Prelude hiding ( (+), (-), .... etc .... ) Hope that helps.
Last question: Does haskell have something like C++ templates? For example, some time in the future I may need types like int2, short3, etc., that behave just like float2, float3, but use different types for their components. I really, really wouldn't like to copy-paste the definitions of floatn and manually change their types to intn respectfully.
Cheers.
-- Slavomir Kaslev _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Hi Slavomir,
On 11/28/06, Slavomir Kaslev
instance Num Float3 where ..... signum a | a == Float3 0 0 0 = 0 | otherwise = 1
signum has a natural generalization for vectors. signum v = vector with the same direction as v but with |v| = 1 where |v| is the absolute length of v. The problematic function in Num is abs. Ideally abs should be defined as: abs v = |v| but its type is Float3 -> Float while the Num class requires Float3 -> Float3. Cheers, Krasimir

On 11/29/06, Krasimir Angelov
Hi Slavomir,
On 11/28/06, Slavomir Kaslev
wrote: instance Num Float3 where ..... signum a | a == Float3 0 0 0 = 0 | otherwise = 1
signum has a natural generalization for vectors.
signum v = vector with the same direction as v but with |v| = 1
where |v| is the absolute length of v. The problematic function in Num is abs. Ideally abs should be defined as:
abs v = |v|
but its type is Float3 -> Float while the Num class requires Float3 -> Float3.
You mean signum = normalize? What do you think of my comments here:
After giving some thought on signum, I got to the point, that signum should be defined so that abs x * signum x = x holds. So it can be defined as signum (Vec2 x y) = Vec 2 (signum x) (signum y).
It turns out that all the functions in Num, Floating, etc. classes can be given meaningful definitions for vectors in this pattern. That is f (Vecn x1 x2 .. xn) = Vecn (f x1) ... (f xn). And all expected laws just work. One can think of that like the way SIMD processor works, it does the same operations as on floats but on four floats at parallel.
I think this is the way to define vector instances for Num, Floating, etc. For vector specific operations, such as normalize, len, dot, cross, etc. are declared in class Vector. -- Slavomir Kaslev

It is possible of course but your definition doesn't correspond to any
operation in the usual vector algebra. By the way how do you define
(*)? Isn't it 3D vector multiplication?
Krasimir
On 11/29/06, Slavomir Kaslev
You mean signum = normalize? What do you think of my comments here:
After giving some thought on signum, I got to the point, that signum should be defined so that abs x * signum x = x holds. So it can be defined as signum (Vec2 x y) = Vec 2 (signum x) (signum y).
It turns out that all the functions in Num, Floating, etc. classes can be given meaningful definitions for vectors in this pattern. That is f (Vecn x1 x2 .. xn) = Vecn (f x1) ... (f xn). And all expected laws just work. One can think of that like the way SIMD processor works, it does the same operations as on floats but on four floats at parallel.
I think this is the way to define vector instances for Num, Floating, etc. For vector specific operations, such as normalize, len, dot, cross, etc. are declared in class Vector.
-- Slavomir Kaslev

On 11/29/06, Krasimir Angelov
It is possible of course but your definition doesn't correspond to any operation in the usual vector algebra. By the way how do you define (*)? Isn't it 3D vector multiplication?
(*) is per component multiplication, as it is in Cg/HLSL. For vector to vector, vector to matrix, etc. multiplication there is mul. Cheers. -- Slavomir Kaslev

Slavomir Kaslev
On 11/29/06, Krasimir Angelov
wrote: It is possible of course but your definition doesn't correspond to any operation in the usual vector algebra. By the way how do you define (*)? Isn't it 3D vector multiplication?
(*) is per component multiplication, as it is in Cg/HLSL. For vector to vector, vector to matrix, etc. multiplication there is mul.
Cheers.
Hello, I have defined a class for vectors that I think can be interesting for you, althougt I do NOT use the Num class. I really like infix operators for vectors but using + * ... and so gets things confusing for me and have bad interaction with scalars. So I define infix operators <+> <-> <*> ... with an "<" or ">" on the side when a vector is spected, so (*>) is a scalar multiplication of a vector, (<*>) multiplication of two vectors, <.> dot product .... The class is named Vector, and I don't make distinction bewteen vectors and points. A minimalist instance of Vector class, can be defined by only two method functions, reduceComponent and combineComponent. reduceComponent is like a fold functions over the components of a vector, so for example the max component of a vector is defined as "maxComponent vec = reduceComponent (max) vec". combineComponent apply a function to every pair of components of two vectors, so an addition of two vectors is defined as "(<+>) a b = combineComponent (+) a b". Note that for Vector3 and Vector2 datatypes I define instances with reduceComponent and combineComponent, but for performance reasons I override default implementations of the most used operations. Here is the code, I hope that it makes clear what I have tried to explain. Please, feel free to criticize the code Fco. Javier Loma fjloma <at> andaluciajunta.es --begin code {-# OPTIONS_GHC -fglasgow-exts -fbang-patterns #-} module Data.Vectors where -- Use a Double for each component type VReal = Double --data Dimension = X | Y | Z | W deriving (Show, Read, Eq) data Vector3 = V3 !VReal !VReal !VReal deriving (Show, Read, Eq) class (Floating r, Ord r) => (Vector r) v | v -> r where -- minimun definition by reduceComponent and combineComponent reduceComponent :: (r -> r -> r) -> v -> r combineComponent :: (r -> r -> r) -> v -> v -> v (<+>) :: v -> v -> v (<+>) a b = combineComponent (+) a b (<->) :: v -> v -> v (<->) a b = combineComponent (-) a b (<*>) :: v -> v -> v (<*>) a b = combineComponent (*) a b (>) :: v -> v -> v (>) a b = combineComponent (/) a b (<.>) :: v -> v -> r a <.> b = reduceComponent (+) (combineComponent (*) a b) (<*) :: v -> r -> v a <* k = combineComponent (\x -> \_ -> x*k) a a () :: v -> r -> v a k = combineComponent (\x -> \_ -> x/k) a a (*>) :: r -> v -> v k *> vec = vec <* k normalize :: v -> v normalize vec = vec (vlength vec) vlength :: v -> r vlength vec = sqrt(vec <.> vec) maxComponent :: v -> r maxComponent vec = reduceComponent (max) vec minComponent :: v -> r minComponent vec = reduceComponent (min) vec middle :: v -> v -> v middle a b = (a <+> b) 2 distance :: v -> v -> r distance a b = sqrt (distance2 a b) distance2 :: v -> v -> r distance2 a b = r <.> r where r = b <-> a instance Vector VReal Vector3 where reduceComponent f (V3 a1 a2 a3) = (f a1 (f a2 a3)) combineComponent f (V3 a1 a2 a3) (V3 b1 b2 b3) = V3 (f a1 b1) (f a2 b2) (f a3 b3) (!V3 a1 a2 a3) <+> (!V3 b1 b2 b3) = V3 (a1 + b1) (a2 + b2) (a3 + b3) (!V3 a1 a2 a3) <-> (!V3 b1 b2 b3) = V3 (a1 - b1) (a2 - b2) (a3 - b3) (!V3 a1 a2 a3) <*> (!V3 b1 b2 b3) = V3 (a1 * b1) (a2 * b2) (a3 * b3) (!V3 a1 a2 a3) > (!V3 b1 b2 b3) = V3 (a1 / b1) (a2 / b2) (a3 / b3) (!V3 a1 a2 a3) <.> (!V3 b1 b2 b3) = a1 * b1 + a2 * b2 + a3 * b3 (!V3 a1 a2 a3) <* k = V3 (a1 * k) (a2 * k) (a3 * k) (!V3 a1 a2 a3) k = V3 (a1 / k) (a2 / k) (a3 / k) data Vector2 = V2 !VReal !VReal deriving (Show, Read, Eq) instance Vector VReal Vector2 where combineComponent f (V2 a1 a2) (V2 b1 b2) = V2 (f a1 b1) (f a2 b2) reduceComponent f (V2 a1 a2) = (f a1 a2) (V2 a1 a2 ) <.> (V2 b1 b2 ) = a1 * b1 + a2 * b2 (V2 a1 a2 ) <* k = V2 (a1 * k) (a2 * k) (V2 a1 a2 ) k = V2 (a1 / k) (a2 / k)
participants (8)
-
Brian Hulley
-
Bulat Ziganshin
-
Fco.Javier Loma
-
Henning Thielemann
-
Krasimir Angelov
-
minh thu
-
Robert Dockins
-
Slavomir Kaslev