
Hi, I need a library that provides partial derivatives for functions. The solution I came up with is based on a datatype using reversed polish notation to store the function: Type VarName = String data Fkt a = Val a | Var VarName | Add (FktElem a) (FktElem a) | Sub (FktElem a) (FktElem a) | Mul (FktElem a) (FktElem a) | ... I can then use pattern matching to compute the derivative: derivative :: VarName -> Fkt b -> Fkt b derivative name (Var n) = if n == name then Val 1.0 else Val 0.0 derivative name (Add a b) | (containsVar name a) && (containsVar name b) = Add (derivative name a) (derivative name b) | (containsVar name a) && (not(containsVar name b)) = (derivative name a) | (not(containsVar name a)) && (containsVar name b) = (derivative name b) | otherwise = Val 0.0 derivative name (Sub a b) | (containsVar name a) && (containsVar name b) = Sub (derivative name a) (derivative name b) | (containsVar name a) && (not(containsVar name b)) = (derivative name a) | (not(containsVar name a)) && (containsVar name b) = (derivative name b) | otherwise = Val 0.0 derivative name (Mul a b) | (containsVar name a) && (containsVar name b) = Add (Mul (derivative name a) b) (Mul a (derivative name b)) | (containsVar name a) && (not(containsVar name b)) = Mul (derivative name a) b | (not(containsVar name a)) && (containsVar name b) = Mul a (derivative name b) | otherwise = Val 0.0 ... Where the function containsVar :: VarName -> Fkt a -> Bool tests if a function contains the variable. The solution works but is not very elegant. The complete module is appended to the mail. Does anyone have a more elegant solution or is there a package that provides derivatives in a similar way? Thank you, Gerhard ======================================== Gerhard Navratil Teaching- And Research-Assistant Technical University Vienna, Austria Institute of Geoinformation and Cartography Gusshausstr. 27-29, 1040 Vienna Tel.: ++43 (0) 1 / 58 801 - 12712 Fax.: ++43 (0) 1 / 58 801 - 12799 Cel.: ++43 (0) 699 / 197 44 761 http://www.geoinfo.tuwien.ac.at

Gerhard Navratil wrote:
I need a library that provides partial derivatives for functions. The solution I came up with is based on a datatype using reversed polish notation to store the function:
<<lots of code>>
The solution works but is not very elegant. The complete module is appended to the mail.
Does anyone have a more elegant solution or is there a package that provides derivatives in a similar way?
A simple way to make it more ellegant is to use smart constructors, so you don't have to check to prevent zeroes everywhere:
sub :: Fkt a -> Fkt a -> Fkt a sub a b | b == 0 = a | a == 0 = Neg b | otherwise = Sub a b -- etc.
Now you can use this smart constructor instead of the real constructor without worry, like:
derivative name (Sub a b) = sub (derivative name a) (derivative name b) -- etc.
Twan

Hi, Jerzy Karczmarczuk has a nice paper about "Functional Differentiation of Computer Programs", see http://users.info.unicaen.fr/~karczma/arpap/ regards, Arjen Gerhard Navratil wrote:
Hi,
I need a library that provides partial derivatives for functions. The solution I came up with is based on a datatype using reversed polish notation to store the function:
Type VarName = String data Fkt a = Val a | Var VarName | Add (FktElem a) (FktElem a) | Sub (FktElem a) (FktElem a) | Mul (FktElem a) (FktElem a) | ...
I can then use pattern matching to compute the derivative:
derivative :: VarName -> Fkt b -> Fkt b derivative name (Var n) = if n == name then Val 1.0 else Val 0.0 derivative name (Add a b) | (containsVar name a) && (containsVar name b) = Add (derivative name a) (derivative name b) | (containsVar name a) && (not(containsVar name b)) = (derivative name a) | (not(containsVar name a)) && (containsVar name b) = (derivative name b) | otherwise = Val 0.0 derivative name (Sub a b) | (containsVar name a) && (containsVar name b) = Sub (derivative name a) (derivative name b) | (containsVar name a) && (not(containsVar name b)) = (derivative name a) | (not(containsVar name a)) && (containsVar name b) = (derivative name b) | otherwise = Val 0.0 derivative name (Mul a b) | (containsVar name a) && (containsVar name b) = Add (Mul (derivative name a) b) (Mul a (derivative name b)) | (containsVar name a) && (not(containsVar name b)) = Mul (derivative name a) b | (not(containsVar name a)) && (containsVar name b) = Mul a (derivative name b) | otherwise = Val 0.0 ...
Where the function
containsVar :: VarName -> Fkt a -> Bool
tests if a function contains the variable.
The solution works but is not very elegant. The complete module is appended to the mail.
Does anyone have a more elegant solution or is there a package that provides derivatives in a similar way?
Thank you, Gerhard
======================================== Gerhard Navratil Teaching- And Research-Assistant Technical University Vienna, Austria Institute of Geoinformation and Cartography Gusshausstr. 27-29, 1040 Vienna Tel.: ++43 (0) 1 / 58 801 - 12712 Fax.: ++43 (0) 1 / 58 801 - 12799 Cel.: ++43 (0) 699 / 197 44 761 http://www.geoinfo.tuwien.ac.at
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Gerhard Navratil wrote:
I need a library that provides partial derivatives for functions. The solution I came up with is based on a datatype using reversed polish notation to store the function:
I like Oleg Kiselyov's "Typeful symbolic differentiation of compiled functions"... http://www.haskell.org/pipermail/haskell/2004-November/014939.html
participants (4)
-
Arjen van Weelden
-
Gerhard Navratil
-
Greg Buchholz
-
Twan van Laarhoven