Portability | GHC only |
---|---|
Stability | experimental |
Maintainer | ekmett@gmail.com |
Mixed-Mode Automatic Differentiation.
For reverse mode AD we use System.Mem.StableName.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) => 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)
- 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)
- hessian :: (Traversable f, Num a) => FU f a -> f a -> f (f a)
- hessianM :: (Traversable f, Monad m, Num a) => FF f m a -> f a -> m (f (f a))
- hessianTensor :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (f (f a))
- diff :: Num a => UU a -> a -> a
- diff' :: Num a => UU a -> a -> (a, a)
- diffF :: (Functor f, Num a) => UF f a -> a -> f a
- diffF' :: (Functor f, Num a) => UF f a -> a -> f (a, a)
- diffM :: (Monad m, Num a) => UF m a -> a -> m a
- diffM' :: (Monad m, Num a) => UF m a -> a -> m (a, a)
- gradM :: (Traversable f, Monad m, Num a) => FF f m a -> f a -> m (f a)
- gradM' :: (Traversable f, Monad m, Num a) => FF f m a -> f a -> m (a, f a)
- gradWithM :: (Traversable f, Monad m, Num a) => (a -> a -> b) -> FF f m a -> f a -> m (f b)
- gradWithM' :: (Traversable f, Monad m, Num a) => (a -> a -> b) -> FF f m a -> f a -> m (a, f b)
- gradF :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (f a)
- gradF' :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (a, f a)
- gradWithF :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (f b)
- gradWithF' :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (a, f b)
- type UU a = forall s. Mode s => AD s a -> AD s a
- type UF f a = forall s. Mode s => AD s a -> f (AD s a)
- type FU f a = forall s. Mode s => f (AD s a) -> AD s a
- type FF f g a = forall s. Mode s => f (AD s a) -> g (AD s a)
- newtype AD f a = AD {
- runAD :: f a
- class Lifted t => Mode t where
Gradient
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
Jacobian
jacobian' :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (a, f a)Source
An alias for gradF'
jacobianWith :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (f b)Source
An alias for gradWithF
.
jacobianWith' :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (a, f b)Source
An alias for gradWithF'
Hessian
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 reverse mode.
However, since the 'grad f :: f a -> f a'
is square this is not as fast as using the forward-mode Jacobian of a reverse mode gradient provided by Numeric.AD.hessian
in Numeric.AD.
hessianM :: (Traversable f, Monad m, Num a) => FF f m a -> f a -> m (f (f a))Source
Compute the hessian via the reverse-mode jacobian of the reverse-mode gradient of a non-scalar-to-scalar monadic action.
While this is less efficient than Numeric.AD.hessianTensor
from Numeric.AD or Numeric.AD.Forward.hessianTensor
from Numeric.AD.Forward, the type signature is more permissive with regards to the output non-scalar, and it may be more efficient if only a few coefficients of the result are consumed.
hessianTensor :: (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 via the forward-mode Jacobian of the mixed-mode Jacobian of the function.
While this is less efficient than Numeric.AD.hessianTensor
from Numeric.AD or Numeric.AD.Forward.hessianTensor
from Numeric.AD.Forward, the type signature is more permissive with regards to the output non-scalar, and it may be more efficient if only a few coefficients of the result are consumed.
Derivatives
diff' :: Num a => UU a -> a -> (a, a)Source
The d'
function calculates the value and derivative, as a
pair, of a scalar-to-scalar function.
Monadic Combinators
gradWithM' :: (Traversable f, Monad m, Num a) => (a -> a -> b) -> FF f m a -> f a -> m (a, f b)Source
Synonyms
gradF :: (Traversable f, Functor g, Num a) => FF f g a -> f a -> g (f a)Source
The gradF
function calculates the jacobian of a non-scalar-to-non-scalar function with reverse AD lazily in m
passes for m
outputs.
gradWithF :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (f b)Source
'gradWithF 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
.
gradF == gradWithF (\_ dx -> dx) gradWithF const == (\f x -> const x <$> f x)
gradWithF' :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (a, f b)Source
gradWithF
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 gradWithF
Instead of returning the Jacobian matrix, the elements of the matrix are combined with the input using the g
.
jacobian' == gradWithF' (\_ dx -> dx)
Exposed Types
type UU a = forall s. Mode s => AD s a -> AD s aSource
A scalar-to-scalar automatically-differentiable function.
type UF f a = forall s. Mode s => AD s a -> f (AD s a)Source
A scalar-to-non-scalar automatically-differentiable function.
type FU f a = forall s. Mode s => f (AD s a) -> AD s aSource
A non-scalar-to-scalar automatically-differentiable function.
type FF f g a = forall s. Mode s => f (AD s a) -> g (AD s a)Source
A non-scalar-to-non-scalar automatically-differentiable function.
AD
serves as a common wrapper for different Mode
instances, exposing a traditional
numerical tower. Universal quantification is used to limit the actions in user code to
machinery that will return the same answers under all AD modes, allowing us to use modes
interchangeably as both the type level "brand" and dictionary, providing a common API.
Primal f => Primal (AD f) | |
Mode f => Mode (AD f) | |
Lifted f => Lifted (AD f) | |
Var (AD Reverse) | |
Iso (f a) (AD f a) | |
(Num a, Lifted f, Bounded a) => Bounded (AD f a) | |
(Num a, Lifted f, Enum a) => Enum (AD f a) | |
(Num a, Lifted f, Eq a) => Eq (AD f a) | |
(Lifted f, Floating a) => Floating (AD f a) | |
(Lifted f, Fractional a) => Fractional (AD f a) | |
(Lifted f, Num a) => Num (AD f a) | |
(Num a, Lifted f, Ord a) => Ord (AD f a) | |
(Lifted f, Real a) => Real (AD f a) | |
(Lifted f, RealFloat a) => RealFloat (AD f a) | |
(Lifted f, RealFrac a) => RealFrac (AD f a) | |
(Lifted f, Show a) => Show (AD f a) |
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