
Consider the following example code: data Vector = V Float Float data Matrix = M Vector Vector liftV1 f (V x y) = V (f x) (f y) liftV2 f (V x1 y1) (V x2 y2) = V (f x1 x2) (f y1 y2) liftM1 f (M x y) = M (f x) (f y) liftM2 f (M x1 y1) (M x2 y2) = M (f x1 x2) (f y1 y2) Both pairs of lift functions have almost identical implementations. Can I merge these somehow? I know data constructors are first class values and are not types, but if I want to merge these lift functions I have to write something like lift1 f (d x y) = d (f x) (f y) lift2 f (d x1 y1) (d x2 y2) = d (f x1 x2) (f y1 y2) But this does not work, as the pattern matcher does not seem to like this. Thanks, Peter Verswyvelen PS: Of course I could define a single type like: data Pair a = P a a type Vector = Pair Float type Matrix = Pair Vector lift1 f (P x y) = P (f x) (f y) lift2 f (P x1 y1) (P x2 y2) = P (f x1 x2) (f y1 y2) But that's beside the question :)

Hi Peter,
liftV1 f (V x y) = V (f x) (f y) liftV2 f (V x1 y1) (V x2 y2) = V (f x1 x2) (f y1 y2)
liftM1 f (M x y) = M (f x) (f y) liftM2 f (M x1 y1) (M x2 y2) = M (f x1 x2) (f y1 y2)
Both pairs of lift functions have almost identical implementations. Can I merge these somehow?
Using the Uniplate library the first already has a name, its called "descend". The second does not, but could be implemented in Uniplate if you wanted. descend2 :: Biplate a b => (b -> b -> b) -> a -> a -> a descend2 f a b = a2 (zipWith f as bs) where (as, a2) = uniplate a (bs, b2) = uniplate b For full details see the website: http://www-users.cs.york.ac.uk/~ndm/uniplate/ Thanks Neil

On Tue, 21 Aug 2007, Peter Verswyvelen wrote:
Consider the following example code:
data Vector = V Float Float data Matrix = M Vector Vector
liftV1 f (V x y) = V (f x) (f y) liftV2 f (V x1 y1) (V x2 y2) = V (f x1 x2) (f y1 y2)
liftM1 f (M x y) = M (f x) (f y) liftM2 f (M x1 y1) (M x2 y2) = M (f x1 x2) (f y1 y2)
Both pairs of lift functions have almost identical implementations. Can I merge these somehow? I know data constructors are first class values and are not types, but if I want to merge these lift functions I have to write something like
Maybe you are happy with instances of Control.Applicative (GHC-6.6) http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Applicati... (untested code follows) data Vector a = Vector a a instance Functor a where fmap f (Vector x y) = Vector (f x) (f y) instance Applicative pure x = Vector x x (Vector fx fy) <*> (Vector x y) = Vector (fx x) (fy y) pure f <*> vx pure f2 <*> vx <*> vy However, I'm not convinced that your code becomes more readable or flexible by this change.

Does a general approach exist to convert any non-constant (Num a) to a Float? Not using type annotation of course. Now I wrote a Convert class that has a toFloat function which I instantiate for all different numeric types, but as all these toFloat/toInt functions disappeared a long time ago from Haskell, it feels like a bad idea to reintroduce them locally in my code... Thanks (again!) Peter Verswyvelen

How can you hope to convert an arbitrary Num to a Float?
Num contains things like complex numbers that don't have any reasonable
translation to a Float.
But anyway, realToFrac is a good conversion function.
-- Lennart
On 8/21/07, Peter Verswyvelen
Does a general approach exist to convert any non-constant (Num a) to a Float? Not using type annotation of course.
Now I wrote a Convert class that has a toFloat function which I instantiate for all different numeric types, but as all these toFloat/toInt functions disappeared a long time ago from Haskell, it feels like a bad idea to reintroduce them locally in my code...
Thanks (again!) Peter Verswyvelen
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Yes indeed, I realized that. I oversimplified my question. I'm basically trying to model 4D CG/HLSL operations (pixel/vertex shaders) in Haskell. I tried realToFrac, but that did not work. Then I tried splitting the instances into Fractional and Integral, but I kept getting errors. Maybe because I also made the Vector datatype an instance of Num, Fractional, etc, which was needed to model the CG/HLSL piecewise operations (so multiplication of two vectors is done piecewise by default in the CG model; one has special dot, cross, and mul operations for performing the other operations). Anyway, although I got something working when I enabled many GHC extensions, I dropped it for now. I notice that a lot of Haskell code uses type annotations (e.g. in HOpenGL), so I guess that's the price one has to pay. It would be nice if one could have a full predicate in the constraints section of a type class, like class ((Num a) && not (Vector4D a)) => ... But I guess this indicates bad design? Thanks, Peter lennart.augustsson@gmail.com wrote: How can you hope to convert an arbitrary Num to a Float? Num contains things like complex numbers that don't have any reasonable translation to a Float. But anyway, realToFrac is a good conversion function.

On Tue, 21 Aug 2007, Peter Verswyvelen wrote:
Yes indeed, I realized that. I oversimplified my question. I'm basically trying to model 4D CG/HLSL operations (pixel/vertex shaders) in Haskell.
I tried realToFrac, but that did not work. Then I tried splitting the instances into Fractional and Integral, but I kept getting errors. Maybe because I also made the Vector datatype an instance of Num, Fractional, etc, which was needed to model the CG/HLSL piecewise operations (so multiplication of two vectors is done piecewise by default in the CG model; one has special dot, cross, and mul operations for performing the other operations).
It would be nice if one could have a full predicate in the constraints section of a type class, like
class ((Num a) && not (Vector4D a)) => ...
But I guess this indicates bad design?
Is still don't see why you need it. I have the feeling that you abuse Num and Fractional classes just for re-use of symbols like (*) and (/) in an arbitrary way. Better don't do that. Type classes are for writing generic functions. Define new infix operators where necessary.

Is still don't see why you need it. I have the feeling that you abuse Num and Fractional classes just for re-use of symbols like (*) and (/) in an
Maybe. It is true that I had the same feeling when first using the CG language: when v and u are (4D) vectors, then -u, u+v and u-v make perfect sense, but u*v, u/v, abs u, signum u, fromInteger u, sin u, etc, don't. In CG this is just solved by applying these operators componentwise. So when u=[u1 u2], then (abs u) = [(abs u1) (abs u2)]. Maybe not really correct in the mathematical sense, but it works fine in practice. It feels silly to invent new operators and names for all of these; the code looks weird, and every function in Num, Fractional, and Floating can be lifted fine into this componentwise scheme. I just "invented" extra operators (dot, cross, mul) to specify dot product, cross product, matrix/vector and matrix/matrix multiplication etc. These clearly do not fit in the numeric classes. Anyway, I started from scratch again, and all is working fine now. As a Haskell newbie, I face this a lot: it seems I'm really stuck with something, wanting to give up on Haskell, and then next day when I start my code from scratch, then it suddenly works fine in a much more elegant way. Maybe I should always do that before asking silly questions here ;) And I should checkin every version that does NOT work, so I can see what went wrong. Now I had them same when digesting C++ templates, so it's not really related to Haskell... Thanks, Peter PS: IMHO it's also a bit problematic the way the numeric classes in Haskell are defined. It would have been nicer if it followed mathematics a bit more, as it seems to be done in the upcoming Sun Fortress language. This is just a *feeling* I'm having by quickly reading the Fortress language specs, so I might be very very wrong :) No virus found in this outgoing message. Checked by AVG Free Edition. Version: 7.5.484 / Virus Database: 269.12.1/965 - Release Date: 21/08/2007 16:02

On Wed, 22 Aug 2007, Peter Verswyvelen wrote:
PS: IMHO it's also a bit problematic the way the numeric classes in Haskell are defined.
I like to mention alternative type class hierarchies like NumericPrelude, again: http://www.haskell.org/haskellwiki/Mathematical_prelude_discussion http://www.haskell.org/haskellwiki/Applications_and_libraries/Mathematics#Ty...

On Tue, 21 Aug 2007 18:53:43 +0200, Peter Verswyvelen
Does a general approach exist to convert any non-constant (Num a) to a Float? Not using type annotation of course.
Instances of class Integral (Int and Integer) can be converted with fromIntegral. -- Met vriendelijke groet, Henk-Jan van Tuyl -- http://functor.bamikanarie.com http://Van.Tuyl.eu/ --
participants (5)
-
Henk-Jan van Tuyl
-
Henning Thielemann
-
Lennart Augustsson
-
Neil Mitchell
-
Peter Verswyvelen