Portability | GHC only |
---|---|
Stability | experimental |
Maintainer | ekmett@gmail.com |
- Gradients (Reverse Mode)
- Higher Order Gradients (Sparse-on-Reverse)
- Jacobians (Sparse or Reverse)
- Higher Order Jacobian (Sparse-on-Reverse)
- Transposed Jacobians (Forward Mode)
- Hessian (Sparse-On-Reverse)
- Hessian Tensors (Sparse or Sparse-On-Reverse)
- Hessian Tensors (Sparse)
- Hessian Vector Products (Forward-On-Reverse)
- Derivatives (Forward Mode)
- Derivatives (Tower)
- Directional Derivatives (Forward Mode)
- Directional Derivatives (Tower)
- Taylor Series (Tower)
- Maclaurin Series (Tower)
- Unsafe Variadic Grad
- Exposed Types
Mixed-Mode Automatic Differentiation.
Each combinator exported from this module chooses an appropriate AD mode. The following basic operations are supported, modified as appropriate by the suffixes below:
-
grad
computes the gradient (partial derivatives) of a function at a point -
jacobian
computes the Jacobian matrix of a function at a point -
diff
computes the derivative of a function at a point -
du
computes a directional derivative of a function at a point -
hessian
compute the Hessian matrix (matrix of second partial derivatives) of a function at a point
The suffixes have the following meanings:
-
'
-- also return the answer -
With
lets the user supply a function to blend the input with the output -
F
is a version of the base function lifted to return aTraversable
(orFunctor
) result -
s
means the function returns all higher derivatives in a list or f-branchingStream
-
T
means the result is transposed with respect to the traditional formulation. -
0
means that the resulting derivative list is padded with 0s at the end.
- grad :: (Traversable f, Num a) => FU f a -> f a -> f a
- grad' :: (Traversable f, Num a) => FU f a -> f a -> (a, f a)
- gradWith :: (Traversable f, Num a) => (a -> a -> b) -> FU f a -> f a -> f b
- gradWith' :: (Traversable f, Num a) => (a -> a -> b) -> FU f a -> f a -> (a, f b)
- grads :: (Traversable f, Num a) => FU f a -> f a -> Cofree f a
- jacobian :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (f a)
- jacobian' :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (a, f a)
- jacobianWith :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (f b)
- jacobianWith' :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (a, f b)
- jacobians :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (Cofree f a)
- jacobianT :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> f (g a)
- jacobianWithT :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> f (g b)
- hessian :: (Traversable f, Num a) => FU f a -> f a -> f (f a)
- hessian' :: (Traversable f, Num a) => FU f a -> f a -> (a, f (a, f a))
- hessianF :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (f (f a))
- hessianF' :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (a, f (a, f a))
- hessianProduct :: (Traversable f, Num a) => FU f a -> f (a, a) -> f a
- hessianProduct' :: (Traversable f, Num a) => FU f a -> f (a, a) -> f (a, a)
- diff :: Num a => UU a -> a -> a
- diffF :: (Functor f, Num a) => UF f a -> a -> f a
- diff' :: Num a => UU a -> a -> (a, a)
- diffF' :: (Functor f, Num a) => UF f a -> a -> f (a, a)
- diffs :: Num a => UU a -> a -> [a]
- diffsF :: (Functor f, Num a) => UF f a -> a -> f [a]
- diffs0 :: Num a => UU a -> a -> [a]
- diffs0F :: (Functor f, Num a) => UF f a -> a -> f [a]
- du :: (Functor f, Num a) => FU f a -> f (a, a) -> a
- du' :: (Functor f, Num a) => FU f a -> f (a, a) -> (a, a)
- duF :: (Functor f, Functor g, Num a) => FF f g a -> f (a, a) -> g a
- duF' :: (Functor f, Functor g, Num a) => FF f g a -> f (a, a) -> g (a, a)
- dus :: (Functor f, Num a) => FU f a -> f [a] -> [a]
- dus0 :: (Functor f, Num a) => FU f a -> f [a] -> [a]
- dusF :: (Functor f, Functor g, Num a) => FF f g a -> f [a] -> g [a]
- dus0F :: (Functor f, Functor g, Num a) => FF f g a -> f [a] -> g [a]
- taylor :: Fractional a => UU a -> a -> a -> [a]
- taylor0 :: Fractional a => UU a -> a -> a -> [a]
- maclaurin :: Fractional a => UU a -> a -> [a]
- maclaurin0 :: Fractional a => UU a -> a -> [a]
- vgrad :: Grad i o o' a => i -> o
- vgrad' :: Grad i o o' a => i -> o'
- vgrads :: Grads i o a => i -> o
- module Numeric.AD.Types
- class Lifted t => Mode t where
- class Num a => Grad i o o' a | i -> a o o', o -> a i o', o' -> a i o
- class Num a => Grads i o a | i -> a o, o -> a i
Gradients (Reverse Mode)
grad :: (Traversable f, Num a) => FU f a -> f a -> f aSource
grad' :: (Traversable f, Num a) => FU f a -> f a -> (a, f a)Source
gradWith :: (Traversable f, Num a) => (a -> a -> b) -> FU f a -> f a -> f bSource
function calculates the gradient of a non-scalar-to-scalar function grad
g ff
with reverse-mode AD in a single pass.
The gradient is combined element-wise with the argument using the function g
.
grad == gradWith (\_ dx -> dx) id == gradWith const
gradWith' :: (Traversable f, Num a) => (a -> a -> b) -> FU f a -> f a -> (a, f b)Source
Higher Order Gradients (Sparse-on-Reverse)
Jacobians (Sparse or Reverse)
jacobian :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (f a)Source
Calculate the Jacobian of a non-scalar-to-non-scalar function, automatically choosing between forward and reverse mode AD based on the number of inputs and outputs.
If you know the relative number of inputs and outputs, consider Numeric.AD.Reverse.jacobian
or Nuneric.AD.Sparse.jacobian
.
jacobian' :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (a, f a)Source
Calculate both the answer and Jacobian of a non-scalar-to-non-scalar function, automatically choosing between forward- and reverse- mode AD based on the relative, based on the number of inputs
If you know the relative number of inputs and outputs, consider Numeric.AD.Reverse.jacobian'
or Nuneric.AD.Sparse.jacobian'
.
jacobianWith :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (f b)Source
calculates the Jacobian of a non-scalar-to-non-scalar function, automatically choosing between forward and reverse mode AD based on the number of inputs and outputs.
jacobianWith
g f
The resulting Jacobian matrix is then recombined element-wise with the input using g
.
If you know the relative number of inputs and outputs, consider Numeric.AD.Reverse.jacobianWith
or Nuneric.AD.Sparse.jacobianWith
.
jacobianWith' :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (a, f b)Source
calculates the answer and Jacobian of a non-scalar-to-non-scalar function, automatically choosing between sparse and reverse mode AD based on the number of inputs and outputs.
jacobianWith'
g f
The resulting Jacobian matrix is then recombined element-wise with the input using g
.
If you know the relative number of inputs and outputs, consider Numeric.AD.Reverse.jacobianWith'
or Nuneric.AD.Sparse.jacobianWith'
.
Higher Order Jacobian (Sparse-on-Reverse)
Transposed Jacobians (Forward Mode)
jacobianT :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> f (g a)Source
A fast, simple transposed Jacobian computed with forward-mode AD.
jacobianWithT :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> f (g b)Source
A fast, simple transposed Jacobian computed with forward-mode AD.
Hessian (Sparse-On-Reverse)
hessian :: (Traversable f, Num a) => FU f a -> f a -> f (f a)Source
Compute the Hessian via the Jacobian of the gradient. gradient is computed in reverse mode and then the Jacobian is computed in sparse (forward) mode.
hessian' :: (Traversable f, Num a) => FU f a -> f a -> (a, f (a, f a))Source
Hessian Tensors (Sparse or Sparse-On-Reverse)
hessianF :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (f (f a))Source
Compute the order 3 Hessian tensor on a non-scalar-to-non-scalar function using Sparse or Sparse-on-Reverse
Hessian Tensors (Sparse)
Hessian Vector Products (Forward-On-Reverse)
hessianProduct :: (Traversable f, Num a) => FU f a -> f (a, a) -> f aSource
computes the product of the hessian hessianProduct
f wvH
of a non-scalar-to-scalar function f
at w =
with a vector fst
$ wvv = snd $ wv
using "Pearlmutter's method" from http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.29.6143, which states:
H v = (d/dr) grad_w (w + r v) | r = 0
Or in other words, we take the directional derivative of the gradient. The gradient is calculated in reverse mode, then the directional derivative is calculated in forward mode.
hessianProduct' :: (Traversable f, Num a) => FU f a -> f (a, a) -> f (a, a)Source
computes both the gradient of a non-scalar-to-scalar hessianProduct'
f wvf
at w =
and the product of the hessian fst
$ wvH
at w
with a vector v = snd $ wv
using "Pearlmutter's method". The outputs are returned wrapped in the same functor.
H v = (d/dr) grad_w (w + r v) | r = 0
Or in other words, we return the gradient and the directional derivative of the gradient. The gradient is calculated in reverse mode, then the directional derivative is calculated in forward mode.
Derivatives (Forward Mode)
diff' :: Num a => UU a -> a -> (a, a)Source
The d'UU
function calculates the result and first derivative of scalar-to-scalar function by Forward
AD
d' sin == sin &&& cos d' f = f &&& d f
Derivatives (Tower)
Directional Derivatives (Forward Mode)
Directional Derivatives (Tower)
Taylor Series (Tower)
taylor :: Fractional a => UU a -> a -> a -> [a]Source
taylor0 :: Fractional a => UU a -> a -> a -> [a]Source
Maclaurin Series (Tower)
maclaurin :: Fractional a => UU a -> a -> [a]Source
maclaurin0 :: Fractional a => UU a -> a -> [a]Source
Unsafe Variadic Grad
Exposed Types
module Numeric.AD.Types
class Lifted t => Mode t whereSource
lift :: Num a => a -> t aSource
Embed a constant
(<+>) :: Num a => t a -> t a -> t aSource
Vector sum
(*^) :: Num a => a -> t a -> t aSource
Scalar-vector multiplication
(^*) :: Num a => t a -> a -> t aSource
Vector-scalar multiplication
(^/) :: Fractional a => t a -> a -> t aSource
Scalar division
'zero' = 'lift' 0