Portability | GHC only |
---|---|
Stability | experimental |
Maintainer | ekmett@gmail.com |
Safe Haskell | None |
Mixed-Mode Automatic Differentiation.
For reverse mode AD we use StableName
to recover sharing information from
the tape to avoid combinatorial explosion, and thus run asymptotically faster
than it could without such sharing information, but the use of side-effects
contained herein is benign.
- grad :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> f a
- grad' :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f a)
- gradWith :: (Traversable f, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> f b
- gradWith' :: (Traversable f, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f b)
- jacobian :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f a)
- jacobian' :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (a, f a)
- jacobianWith :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f b)
- jacobianWith' :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (a, f b)
- hessian :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> f (f a)
- hessianF :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f (f a))
- diff :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> a
- diff' :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> (a, a)
- diffF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f a
- diffF' :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f (a, a)
- vgrad :: Grad i o o' a => i -> o
- vgrad' :: Grad i o o' a => i -> o'
- class Num a => Grad i o o' a | i -> a o o', o -> a i o', o' -> a i o
Gradient
grad' :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f a)Source
gradWith :: (Traversable f, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> f bSource
gradWith' :: (Traversable f, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f b)Source
Jacobian
jacobian :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f a)Source
The jacobian
function calculates the jacobian of a non-scalar-to-non-scalar function with reverse AD lazily in m
passes for m
outputs.
>>>
jacobian (\[x,y] -> [y,x,x*y]) [2,1]
[[0,1],[1,0],[1,2]]
>>>
jacobian (\[x,y] -> [exp y,cos x,x+y]) [1,2]
[[0.0,7.38905609893065],[-0.8414709848078965,0.0],[1.0,1.0]]
jacobian' :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (a, f a)Source
The jacobian'
function calculates both the result and the Jacobian of a nonscalar-to-nonscalar function, using m
invocations of reverse AD,
where m
is the output dimensionality. Applying fmap snd
to the result will recover the result of jacobian
| An alias for gradF'
ghci> jacobian' ([x,y] -> [y,x,x*y]) [2,1] [(1,[0,1]),(2,[1,0]),(2,[1,2])]
jacobianWith :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f b)Source
'jacobianWith g f' calculates the Jacobian of a non-scalar-to-non-scalar function f
with reverse AD lazily in m
passes for m
outputs.
Instead of returning the Jacobian matrix, the elements of the matrix are combined with the input using the g
.
jacobian
=jacobianWith
(_ dx -> dx)jacobianWith
const
= (f x ->const
x<$>
f x)
jacobianWith' :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (a, f b)Source
jacobianWith
g f' calculates both the result and the Jacobian of a nonscalar-to-nonscalar function f
, using m
invocations of reverse AD,
where m
is the output dimensionality. Applying fmap snd
to the result will recover the result of jacobianWith
Instead of returning the Jacobian matrix, the elements of the matrix are combined with the input using the g
.
jacobian'
==jacobianWith'
(_ dx -> dx)
Hessian
hessian :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s 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 reverse mode.
However, since the
is square this is not as fast as using the forward-mode grad
f :: f a -> f ajacobian
of a reverse mode gradient provided by hessian
.
>>>
hessian (\[x,y] -> x*y) [1,2]
[[0,1],[1,0]]
hessianF :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f (f a))Source
Compute the order 3 Hessian tensor on a non-scalar-to-non-scalar function via the reverse-mode Jacobian of the reverse-mode Jacobian of the function.
Less efficient than hessianF
.
>>>
hessianF (\[x,y] -> [x*y,x+y,exp x*cos y]) [1,2]
[[[0.0,1.0],[1.0,0.0]],[[0.0,0.0],[0.0,0.0]],[[-1.1312043837568135,-2.4717266720048188],[-2.4717266720048188,1.1312043837568135]]]
Derivatives
diff :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> aSource
Compute the derivative of a function.
>>>
diff sin 0
1.0
>>>
cos 0
1.0
diff' :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> (a, a)Source
The diff'
function calculates the value and derivative, as a
pair, of a scalar-to-scalar function.
>>>
diff' sin 0
(0.0,1.0)
diffF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f aSource
Compute the derivatives of a function that returns a vector with regards to its single input.
>>>
diffF (\a -> [sin a, cos a]) 0
[1.0,0.0]
diffF' :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f (a, a)Source
Compute the derivatives of a function that returns a vector with regards to its single input as well as the primal answer.
>>>
diffF' (\a -> [sin a, cos a]) 0
[(0.0,1.0),(1.0,0.0)]