| Copyright | (c) Edward Kmett 2015 | 
|---|---|
| License | BSD3 | 
| Maintainer | ekmett@gmail.com | 
| Stability | experimental | 
| Portability | GHC only | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Numeric.AD.Newton.Double
Description
Synopsis
- findZero :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double]
- findZeroNoEq :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double]
- inverse :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> Double -> [Double]
- inverseNoEq :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> Double -> [Double]
- fixedPoint :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double]
- fixedPointNoEq :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double]
- extremum :: (forall s. AD s (On (Forward ForwardDouble)) -> AD s (On (Forward ForwardDouble))) -> Double -> [Double]
- extremumNoEq :: (forall s. AD s (On (Forward ForwardDouble)) -> AD s (On (Forward ForwardDouble))) -> Double -> [Double]
- conjugateGradientDescent :: Traversable f => (forall s. Chosen s => f (Or s (On (Forward ForwardDouble)) (Kahn Double)) -> Or s (On (Forward ForwardDouble)) (Kahn Double)) -> f Double -> [f Double]
- conjugateGradientAscent :: Traversable f => (forall s. Chosen s => f (Or s (On (Forward ForwardDouble)) (Kahn Double)) -> Or s (On (Forward ForwardDouble)) (Kahn Double)) -> f Double -> [f Double]
Newton's Method (Forward AD)
findZero :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double] Source #
The findZero function finds a zero of a scalar function using
 Newton's method; its output is a stream of increasingly accurate
 results.  (Modulo the usual caveats.) If the stream becomes constant
 ("it converges"), no further elements are returned.
Examples:
>>>take 10 $ findZero (\x->x^2-4) 1[1.0,2.5,2.05,2.000609756097561,2.0000000929222947,2.000000000000002,2.0]
findZeroNoEq :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double] Source #
The findZeroNoEq function behaves the same as findZero except that it
 doesn't truncate the list once the results become constant.
inverse :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> Double -> [Double] Source #
The inverse function inverts a scalar function using
 Newton's method; its output is a stream of increasingly accurate
 results.  (Modulo the usual caveats.) If the stream becomes
 constant ("it converges"), no further elements are returned.
Example:
>>>last $ take 10 $ inverse sqrt 1 (sqrt 10)10.0
inverseNoEq :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> Double -> [Double] Source #
The inverseNoEq function behaves the same as inverse except that it
 doesn't truncate the list once the results become constant.
fixedPoint :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double] Source #
The fixedPoint function find a fixedpoint of a scalar
 function using Newton's method; its output is a stream of
 increasingly accurate results.  (Modulo the usual caveats.)
If the stream becomes constant ("it converges"), no further elements are returned.
>>>last $ take 10 $ fixedPoint cos 10.7390851332151607
fixedPointNoEq :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> [Double] Source #
The fixedPointNoEq function behaves the same as fixedPoint except that
 doesn't truncate the list once the results become constant.
extremum :: (forall s. AD s (On (Forward ForwardDouble)) -> AD s (On (Forward ForwardDouble))) -> Double -> [Double] Source #
The extremum function finds an extremum of a scalar
 function using Newton's method; produces a stream of increasingly
 accurate results.  (Modulo the usual caveats.) If the stream
 becomes constant ("it converges"), no further elements are returned.
>>>last $ take 10 $ extremum cos 10.0
extremumNoEq :: (forall s. AD s (On (Forward ForwardDouble)) -> AD s (On (Forward ForwardDouble))) -> Double -> [Double] Source #
The extremumNoEq function behaves the same as extremum except that it
 doesn't truncate the list once the results become constant.
Gradient Ascent/Descent (Reverse AD)
conjugateGradientDescent :: Traversable f => (forall s. Chosen s => f (Or s (On (Forward ForwardDouble)) (Kahn Double)) -> Or s (On (Forward ForwardDouble)) (Kahn Double)) -> f Double -> [f Double] Source #
Perform a conjugate gradient descent using reverse mode automatic differentiation to compute the gradient, and using forward-on-forward mode for computing extrema.
>>>let sq x = x * x>>>let rosenbrock [x,y] = sq (1 - x) + 100 * sq (y - sq x)>>>rosenbrock [0,0]1>>>rosenbrock (conjugateGradientDescent rosenbrock [0, 0] !! 5) < 0.1True
conjugateGradientAscent :: Traversable f => (forall s. Chosen s => f (Or s (On (Forward ForwardDouble)) (Kahn Double)) -> Or s (On (Forward ForwardDouble)) (Kahn Double)) -> f Double -> [f Double] Source #
Perform a conjugate gradient ascent using reverse mode automatic differentiation to compute the gradient.