Re: [Haskell-cafe] ANNOUNCE: fad 1.0 -- Forward Automatic Differentiation library

2009-04-05 Thread Kalman Noel
Henning Thielemann schrieb:
 with advanced type classes:
 http://hackage.haskell.org/packages/archive/numeric-prelude/0.0.5/doc/html/MathObj-PowerSeries.html

I'll take this as another opportunity to point out that the Haddock docs
of the Numeric Prelude are highly unreadable, due to all qualified class
and type names appearing as just C or T.  I'm wondering, too, if the
Numeric Prelude could be organized more cleanly if we had a fancier
module system - does someone have sufficient experience with, say,
ML-style module systems to tell?

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: fad 1.0 -- Forward Automatic Differentiation library

2009-04-04 Thread Henning Thielemann


On Thu, 2 Apr 2009, Bjorn Buckwalter wrote:


I'm pleased to announce the initial release of the Haskell fad
library, developed by Barak A. Pearlmutter and Jeffrey Mark Siskind.
Fad provides Forward Automatic Differentiation (AD) for functions
polymorphic over instances of 'Num'. There have been many Haskell
implementations of forward AD, with varying levels of completeness,
published in papers and blog posts[1], but alarmingly few of these
have made it into hackage -- to date Conal Elliot's vector-spaces[2]
package is the only one I am aware of.


Do you count computations with power series also as Automatic 
Differentiation? I mean, arithmetic on power series is just working with 
all derivatives simultaneously.


with Haskell 98 type classes:
http://darcs.haskell.org/htam/src/PowerSeries/Taylor.hs

with advanced type classes:
http://hackage.haskell.org/packages/archive/numeric-prelude/0.0.5/doc/html/MathObj-PowerSeries.html

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: fad 1.0 -- Forward Automatic Differentiation library

2009-04-03 Thread Edward Kmett
Very nice to have!

FYI- there is at least one more quantification-based automatic
differentiation implementation in Hackage:

http://comonad.com/haskell/monoids/dist/doc/html/monoids/Data-Ring-Module-AutomaticDifferentiation.html

My implementation is/was focused upon use with monoids and other
more-limited-than-Num classes and only included the equivalent of your
'lift' and 'diffUU' operations, however.

-Edward Kmett

On Thu, Apr 2, 2009 at 10:28 PM, Bjorn Buckwalter 
bjorn.buckwal...@gmail.com wrote:

 I'm pleased to announce the initial release of the Haskell fad
 library, developed by Barak A. Pearlmutter and Jeffrey Mark Siskind.
 Fad provides Forward Automatic Differentiation (AD) for functions
 polymorphic over instances of 'Num'. There have been many Haskell
 implementations of forward AD, with varying levels of completeness,
 published in papers and blog posts[1], but alarmingly few of these
 have made it into hackage -- to date Conal Elliot's vector-spaces[2]
 package is the only one I am aware of.

 Fad is an attempt to make as comprehensive and usable a forward AD
 package as is possible in Haskell. However, correctness is given
 priority over ease of use, and this is in my opinion the defining
 quality of fad. Specifically, Fad leverages Haskell's expressive
 type system to tackle the problem of _perturbation confusion_,
 brought to light in Pearlmutter and Siskind's 2005 paper Perturbation
 Confusion and Referential Transparency[3]. Fad prevents perturbation
 confusion by employing type-level branding as proposed by myself
 in a 2007 post to haskell-cafe[4]. To the best of our knowledge all
 other forward AD implementations in Haskell are susceptible to
 perturbation confusion.

 As this library has been in the works for quite some time it is
 worth noting that it hasn't benefited from Conal's ground-breaking
 work[5] in the area. Once we wrap our heads around his beautiful
 constructs perhaps we'll be able to borrow some tricks from him.

 As mentioned already, fad was developed primarily by Barak A.
 Pearlmutter and Jeffrey Mark Siskind. My own contribution has been
 providing Haskell infrastructure support and wrapping up loose ends
 in order to get the library into a releasable state. Many thanks
 to Barak and Jeffrey for permitting me to release fad under the BSD
 license.

 Fad resides on GitHub[6] and hackage[7] and is only a cabal install
 fad away! What follows is Fad's README, refer to the haddocks for
 detailed documentation.

 Thanks,
 Bjorn Buckwalter


 [1] http://www.haskell.org/haskellwiki/Functional_differentiation
 [2] http://www.haskell.org/haskellwiki/Vector-space
 [3]:  http://www.bcl.hamilton.ie/~qobi/nesting/papers/ifl2005.pdf
 [4]: http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/
 [5]: http://conal.net/papers/beautiful-differentiation/
 [6] http://github.com/bjornbm/fad/
 [7] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fad


 

   Copyright  : 2008-2009, Barak A. Pearlmutter and Jeffrey Mark Siskind
   License: BSD3

   Maintainer : bjorn.buckwal...@gmail.com
   Stability  : experimental
   Portability: GHC only?

 Forward Automatic Differentiation via overloading to perform
 nonstandard interpretation that replaces original numeric type with
 corresponding generalized dual number type.

 Each invocation of the differentiation function introduces a
 distinct perturbation, which requires a distinct dual number type.
 In order to prevent these from being confused, tagging, called
 branding in the Haskell community, is used.  This seems to prevent
 perturbation confusion, although it would be nice to have an actual
 proof of this.  The technique does require adding invocations of
 lift at appropriate places when nesting is present.

 For more information on perturbation confusion and the solution
 employed in this library see:
 http://www.bcl.hamilton.ie/~barak/papers/ifl2005.pdf
 http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/


 Installation
 
 To install:
cabal install

 Or:
runhaskell Setup.lhs configure
runhaskell Setup.lhs build
runhaskell Setup.lhs install


 Examples
 
 Define an example function 'f':

  import Numeric.FAD
  f x = 6 - 5 * x + x ^ 2  -- Our example function

 Basic usage of the differentiation operator:

  y   = f 2  -- f(2) = 0
  y'  = diff f 2 -- First derivative f'(2) = -1
  y'' = diff (diff f) 2  -- Second derivative f''(2) = 2

 List of derivatives:

  ys = take 3 $ diffs f 2  -- [0, -1, 2]

 Example optimization method; find a zero using Newton's method:

  y_newton1 = zeroNewton f 0   -- converges to first zero at 2.0.
  y_newton2 = zeroNewton f 10  -- converges to second zero at 3.0.


 Credits
 ===
 Authors: Copyright 2008,
 Barak A. Pearlmutter ba...@cs.nuim.ie 
 Jeffrey Mark Siskind q...@purdue.edu

 Work started as stripped-down version of higher-order tower code

Re: [Haskell-cafe] ANNOUNCE: fad 1.0 -- Forward Automatic Differentiation library

2009-04-03 Thread Edward Kmett
A somewhat tricky concern is that that the extra functionality in question
depends on a bunch of primitive definitions that lie below this in the
package and the AD engine is used by a layer on top.

So moving it out would introduce a circular dependency back into the package
or require me to stratify into two packages.  When I looked into
partitioning the package for another reason I found that I couldn't do so
without introducing some orphan instances, so it'll probably be a tricky bit
of surgery to split out. That said, it's probably still worth doing.

I also agree that I should be somewhat more pedantic about the name. =)
-Edward Kmett

On Fri, Apr 3, 2009 at 10:49 AM, Barak A. Pearlmutter ba...@cs.nuim.iewrote:

 I feel silly, did not even notice that!  Thanks for the pointer.

 Would be sensible to merge the functionalities; will try to import
 functionality in Data.Ring.Module.AutomaticDifferentiation currently
 missing from Numeric.FAD.

 (One pedantic note: should really be named
 Data.Ring.Module.AutomaticDifferentiation.Forward, since it is doing
 forward-mode accumulation automatic differentiation; reverse is
 an adjoint kettle of fish.)
 --
 Barak A. Pearlmutter
  Hamilton Institute  Dept Comp Sci, NUI Maynooth, Co. Kildare, Ireland
   http://www.bcl.hamilton.ie/~barak/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: fad 1.0 -- Forward Automatic Differentiation library

2009-04-02 Thread Bjorn Buckwalter
I'm pleased to announce the initial release of the Haskell fad
library, developed by Barak A. Pearlmutter and Jeffrey Mark Siskind.
Fad provides Forward Automatic Differentiation (AD) for functions
polymorphic over instances of 'Num'. There have been many Haskell
implementations of forward AD, with varying levels of completeness,
published in papers and blog posts[1], but alarmingly few of these
have made it into hackage -- to date Conal Elliot's vector-spaces[2]
package is the only one I am aware of.

Fad is an attempt to make as comprehensive and usable a forward AD
package as is possible in Haskell. However, correctness is given
priority over ease of use, and this is in my opinion the defining
quality of fad. Specifically, Fad leverages Haskell's expressive
type system to tackle the problem of _perturbation confusion_,
brought to light in Pearlmutter and Siskind's 2005 paper Perturbation
Confusion and Referential Transparency[3]. Fad prevents perturbation
confusion by employing type-level branding as proposed by myself
in a 2007 post to haskell-cafe[4]. To the best of our knowledge all
other forward AD implementations in Haskell are susceptible to
perturbation confusion.

As this library has been in the works for quite some time it is
worth noting that it hasn't benefited from Conal's ground-breaking
work[5] in the area. Once we wrap our heads around his beautiful
constructs perhaps we'll be able to borrow some tricks from him.

As mentioned already, fad was developed primarily by Barak A.
Pearlmutter and Jeffrey Mark Siskind. My own contribution has been
providing Haskell infrastructure support and wrapping up loose ends
in order to get the library into a releasable state. Many thanks
to Barak and Jeffrey for permitting me to release fad under the BSD
license.

Fad resides on GitHub[6] and hackage[7] and is only a cabal install
fad away! What follows is Fad's README, refer to the haddocks for
detailed documentation.

Thanks,
Bjorn Buckwalter


[1] http://www.haskell.org/haskellwiki/Functional_differentiation
[2] http://www.haskell.org/haskellwiki/Vector-space
[3]:  http://www.bcl.hamilton.ie/~qobi/nesting/papers/ifl2005.pdf
[4]: http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/
[5]: http://conal.net/papers/beautiful-differentiation/
[6] http://github.com/bjornbm/fad/
[7] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fad




   Copyright  : 2008-2009, Barak A. Pearlmutter and Jeffrey Mark Siskind
   License: BSD3

   Maintainer : bjorn.buckwal...@gmail.com
   Stability  : experimental
   Portability: GHC only?

Forward Automatic Differentiation via overloading to perform
nonstandard interpretation that replaces original numeric type with
corresponding generalized dual number type.

Each invocation of the differentiation function introduces a
distinct perturbation, which requires a distinct dual number type.
In order to prevent these from being confused, tagging, called
branding in the Haskell community, is used.  This seems to prevent
perturbation confusion, although it would be nice to have an actual
proof of this.  The technique does require adding invocations of
lift at appropriate places when nesting is present.

For more information on perturbation confusion and the solution
employed in this library see:
http://www.bcl.hamilton.ie/~barak/papers/ifl2005.pdf
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/


Installation

To install:
cabal install

Or:
runhaskell Setup.lhs configure
runhaskell Setup.lhs build
runhaskell Setup.lhs install


Examples

Define an example function 'f':

 import Numeric.FAD
 f x = 6 - 5 * x + x ^ 2  -- Our example function

Basic usage of the differentiation operator:

 y   = f 2  -- f(2) = 0
 y'  = diff f 2 -- First derivative f'(2) = -1
 y'' = diff (diff f) 2  -- Second derivative f''(2) = 2

List of derivatives:

 ys = take 3 $ diffs f 2  -- [0, -1, 2]

Example optimization method; find a zero using Newton's method:

 y_newton1 = zeroNewton f 0   -- converges to first zero at 2.0.
 y_newton2 = zeroNewton f 10  -- converges to second zero at 3.0.


Credits
===
Authors: Copyright 2008,
Barak A. Pearlmutter ba...@cs.nuim.ie 
Jeffrey Mark Siskind q...@purdue.edu

Work started as stripped-down version of higher-order tower code
published by Jerzy Karczmarczuk jerzy.karczmarc...@info.unicaen.fr
which used a non-standard standard prelude.

Initial perturbation-confusing code is a modified version of
http://cdsmith.wordpress.com/2007/11/29/some-playing-with-derivatives/

Tag trick, called branding in the Haskell community, from
Bjorn Buckwalter bjorn.buckwal...@gmail.com
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/22308/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org