| Portability | GHC only |
|---|---|
| Stability | experimental |
| Maintainer | ekmett@gmail.com |
| Safe Haskell | Safe-Infered |
Numeric.RAD
Contents
Description
Reverse Mode Automatic Differentiation via overloading to perform nonstandard interpretation that replaces original numeric type with a bundle that contains a value of the original type and the tape that will be used to recover the value of the sensitivity.
This package uses StableNames internally to recover sharing information from the tape to avoid combinatorial explosion, and thus runs asymptotically faster than it could without such sharing information, but the use of side-effects contained herein is benign.
The API has been built to be close to the design of FAD from the fad package
by Barak Pearlmutter and Jeffrey Mark Siskind and contains portions of that code, with minor liberties taken.
- data RAD s a
- lift :: a -> RAD s a
- diffUU :: Num a => (forall s. RAD s a -> RAD s a) -> a -> a
- diffUF :: (Functor f, Num a) => (forall s. RAD s a -> f (RAD s a)) -> a -> f a
- diff2UU :: Num a => (forall s. RAD s a -> RAD s a) -> a -> (a, a)
- diff2UF :: (Functor f, Num a) => (forall s. RAD s a -> f (RAD s a)) -> a -> f (a, a)
- diff :: Num a => (forall s. RAD s a -> RAD s a) -> a -> a
- diff2 :: Num a => (forall s. RAD s a -> RAD s a) -> a -> (a, a)
- jacobian :: (Traversable f, Functor g, Num a) => (forall s. f (RAD s a) -> g (RAD s a)) -> f a -> g (f a)
- jacobian2 :: (Traversable f, Functor g, Num a) => (forall s. f (RAD s a) -> g (RAD s a)) -> f a -> g (a, f a)
- grad :: (Traversable f, Num a) => (forall s. f (RAD s a) -> RAD s a) -> f a -> f a
- grad2 :: (Traversable f, Num a) => (forall s. f (RAD s a) -> RAD s a) -> f a -> (a, f a)
- zeroNewton :: Fractional a => (forall s. RAD s a -> RAD s a) -> a -> [a]
- inverseNewton :: Fractional a => (forall s. RAD s a -> RAD s a) -> a -> a -> [a]
- fixedPointNewton :: Fractional a => (forall s. RAD s a -> RAD s a) -> a -> [a]
- extremumNewton :: Fractional a => (forall s t. RAD t (RAD s a) -> RAD t (RAD s a)) -> a -> [a]
- argminNaiveGradient :: (Fractional a, Ord a) => (forall s. [RAD s a] -> RAD s a) -> [a] -> [[a]]
First-Order Reverse Mode Automatic Differentiation
Instances
| Bounded a => Bounded (RAD s a) | |
| (Num a, Enum a) => Enum (RAD s a) | |
| Eq a => Eq (RAD s a) | |
| Floating a => Floating (RAD s a) | |
| Fractional a => Fractional (RAD s a) | |
| Num a => Num (RAD s a) | |
| Ord a => Ord (RAD s a) | |
| Real a => Real (RAD s a) | |
| RealFloat a => RealFloat (RAD s a) | |
| RealFrac a => RealFrac (RAD s a) | |
| Show a => Show (RAD s a) | |
| MuRef (RAD s a) |
First-Order Differentiation Operators
diffUU :: Num a => (forall s. RAD s a -> RAD s a) -> a -> aSource
The diffUU function calculates the first derivative of a
scalar-to-scalar function.
diffUF :: (Functor f, Num a) => (forall s. RAD s a -> f (RAD s a)) -> a -> f aSource
The diffUF function calculates the first derivative of
scalar-to-nonscalar function.
diff2UU :: Num a => (forall s. RAD s a -> RAD s a) -> a -> (a, a)Source
The diff2UU function calculates the value and derivative, as a
pair, of a scalar-to-scalar function.
diff2UF :: (Functor f, Num a) => (forall s. RAD s a -> f (RAD s a)) -> a -> f (a, a)Source
Note that the signature differs from that used in Numeric.FAD, because while you can always
unzip an arbitrary functor, not all functors can be zipped.
Common access patterns
jacobian :: (Traversable f, Functor g, Num a) => (forall s. f (RAD s a) -> g (RAD s a)) -> f a -> g (f a)Source
jacobian2 :: (Traversable f, Functor g, Num a) => (forall s. f (RAD s a) -> g (RAD s a)) -> f a -> g (a, f a)Source
Optimization Routines
zeroNewton :: Fractional a => (forall s. RAD s a -> RAD s a) -> a -> [a]Source
The zeroNewton 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.)
TEST CASE:
take 10 $ zeroNewton (\x->x^2-4) 1 -- converge to 2.0
TEST CASE
:module Data.Complex Numeric.RAD
take 10 $ zeroNewton ((+1).(^2)) (1 :+ 1) -- converge to (0 :+ 1)
inverseNewton :: Fractional a => (forall s. RAD s a -> RAD s a) -> a -> a -> [a]Source
The inverseNewton function inverts a scalar function using
Newton's method; its output is a stream of increasingly accurate
results. (Modulo the usual caveats.)
TEST CASE:
take 10 $ inverseNewton sqrt 1 (sqrt 10) -- converge to 10
fixedPointNewton :: Fractional a => (forall s. RAD s a -> RAD s a) -> a -> [a]Source
The fixedPointNewton 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.)
extremumNewton :: Fractional a => (forall s t. RAD t (RAD s a) -> RAD t (RAD s a)) -> a -> [a]Source
The extremumNewton function finds an extremum of a scalar
function using Newton's method; produces a stream of increasingly
accurate results. (Modulo the usual caveats.)
argminNaiveGradient :: (Fractional a, Ord a) => (forall s. [RAD s a] -> RAD s a) -> [a] -> [[a]]Source
The argminNaiveGradient function performs a multivariate
optimization, based on the naive-gradient-descent in the file
stalingrad/examples/flow-tests/pre-saddle-1a.vlad from the
VLAD compiler Stalingrad sources. Its output is a stream of
increasingly accurate results. (Modulo the usual caveats.)
This is O(n) faster than argminNaiveGradient