derivative (S f g) ?

Zhanyong Wan zhanyong.wan@yale.edu
Tue, 21 May 2002 16:04:42 -0400


Hi Conal,

I don't have any pointers, but here's my attempt to derive the general rule
for derivatives of application of S:

  D (S f g) x
= d(S f g t) / dt | t = x
= d(f t (g t)) / dt | t = x
= D1 f t (g t) * dt/dt + D2 f t (g t) * d(g t)/dt | t = x  (#)

  where D1 and D2 are partial derivative wrt to the 1st and 2nd
  argument, respectively.

  ( since d(f G H)/dt = D1 f G H * dG/dt + D2 f G H * dH/dt )

We have

  D1 f t (g t)
= lim (e->0) (f (t + e) (g t) - f t (g t))/e
= lim (e->0) (C f (g t) (t + e) - C f (g t) t)/e

  ( since C f x y = f y x )

= D (C f (g t)) t
= D ((C f . g) t) t
= C D t ((C f . g) t)
= S (C D) (C f . g) t

and

  D2 f t (g t)
= lim (e->0) (f t (g t + e) - f t (g t))/e
= D (f t) (g t)
= (D . f) t (g t)
= S (D . f) g t

Thus

  D (S f g) x
= (#)
= S (C D) (C f . g) t + S (D . f) g t * D g t | t = x
= S (C D) (C f . g) x + S (D . f) g x * D g x

Therefore

  D (S f g)
= S (C D) (C f . g) + S (D . f) g * D g

  where "+" and "*" are pointwise lifted.

Does this look right to you?

- Zhanyong

-----Original Message-----
From: haskell-cafe-admin@haskell.org
[mailto:haskell-cafe-admin@haskell.org]On Behalf Of Conal Elliott
Sent: Tuesday, May 21, 2002 1:55 PM
To: haskell-cafe@haskell.org
Subject: derivative (S f g) ?


This isn't really a Haskell question, but I'm hoping a fellow Haskeller
might have some helpful pointers.

Has anyone seen a generalization of the chain rule for derivatives that
applies to applications of the S combinator?  The conventional chain rule
applies to the more restricted composition combinator:

  D (f . g) = (D f . g) * D g

Where D is the differentiation higher-order function, "*" is multiply lifted
pointwise to functions (\ a b x -> a x * b x), and "." is function
composition.

Thanks,

    - Conal