
I tried to implement symbolic differentation using GHC's simplification rules. I assume that someone has already thought about this, right? I have also heard that the rules system is not strong enough for implementing a full computer algebra system. But here is a simple trial and some questions and problems which arise: 1. How to specify a type class context to which the rules have to be restricted? (see the first comment) 2. How to handle lambdas? 3. The module can only be used for compiled programs, since in GHCi optimisation is not available. {-# OPTIONS -O -fglasgow-exts #-} module SymbolicDifferentation where {- These rules need Num context. -- How to write that? "derive/const" forall y. derive (const y) = const 0 ; "derive/id" derive id = const 1 ; "derive/compos" forall f g. derive (f . g) = derive f . g .* derive g ; -} {-# RULES "derive/plus" forall f g. derive (f .+ g) = derive f .+ derive g ; "derive/minus" forall f g. derive (f .- g) = derive f .- derive g ; "derive/times" forall f g. derive (f .* g) = derive f .* g .+ f .* derive g ; "derive/divide" forall f g. derive (f ./ g) = derive f .* g .- f .* derive g ./ ((^2).g) ; "derive/power" forall n. derive ((^) n) = (n*) . (^(n-1)) ; "derive/sin" derive sin = cos ; "derive/cos" derive cos = negate . sin ; "derive/exp" derive exp = exp ; "derive/log" derive log = recip ; #-} -- lift a binary operation to the function values fop2 :: (c -> d -> e) -> (a -> c) -> (a -> d) -> (a -> e) fop2 op f g x = op (f x) (g x) infixl 6 .+, .- infixl 7 .*, ./ (.+), (.-), (.*) :: Num a => (t -> a) -> (t -> a) -> (t -> a) (./) :: Fractional a => (t -> a) -> (t -> a) -> (t -> a) (.+) = fop2 (+) (.-) = fop2 (-) (.*) = fop2 (*) (./) = fop2 (/) derive :: (t -> a) -> (t -> a) derive = error "Could not derive expression symbolically." test :: IO () test = do print (derive log 2) print (derive sin 0) print (derive cos 0.1) print (derive (cos .+ sin) (pi/4)) print (derive (\x -> exp x) 0) print (derive (\x -> x^2 + x) 0) print (derive (exp . sin) 0)