Portability | GHC only |
---|---|
Stability | experimental |
Maintainer | ekmett@gmail.com |
- Gradients (Reverse Mode)
- Jacobians (Mixed Mode)
- Jacobians (Reverse Mode)
- Jacobians (Forward Mode)
- Derivatives (Forward Mode)
- Derivatives (Tower)
- Directional Derivatives (Forward Mode)
- Taylor Series (Tower)
- Maclaurin Series (Tower)
- Monadic Combinators (Forward Mode)
- Monadic Combinators (Reverse Mode)
- Exposed Types
Mixed-Mode Automatic Differentiation.
Each combinator exported from this module chooses an appropriate AD mode.
- 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, Traversable g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f a)
- jacobian' :: (Traversable f, Traversable g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (a, f a)
- jacobianWith :: (Traversable f, Traversable 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, Traversable g, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (a, f b)
- gradF :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (f a)
- gradF' :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g (a, f a)
- gradWithF :: (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)
- gradWithF' :: (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)
- jacobianT :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> f (g a)
- jacobianWithT :: (Traversable f, Functor g, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> f (g b)
- diff :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> a
- diffF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f 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, a)
- diffs :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]
- diffsF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f [a]
- diffs0 :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]
- diffs0F :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f [a]
- du :: (Functor f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f (a, a) -> a
- du' :: (Functor f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f (a, a) -> (a, a)
- duF :: (Functor f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f (a, a) -> g a
- duF' :: (Functor f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f (a, a) -> g (a, a)
- taylor :: Fractional a => (forall s. Mode s => AD s a -> AD s a) -> a -> a -> [a]
- taylor0 :: Fractional a => (forall s. Mode s => AD s a -> AD s a) -> a -> a -> [a]
- maclaurin :: Fractional a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]
- maclaurin0 :: Fractional a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]
- diffM :: (Monad m, Num a) => (forall s. Mode s => AD s a -> m (AD s a)) -> a -> m a
- diffM' :: (Monad m, Num a) => (forall s. Mode s => AD s a -> m (AD s a)) -> a -> m (a, a)
- gradM :: (Traversable f, Monad m, Num a) => (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (f a)
- gradM' :: (Traversable f, Monad m, Num a) => (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (a, f a)
- gradWithM :: (Traversable f, Monad m, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (f b)
- gradWithM' :: (Traversable f, Monad m, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (a, f b)
- newtype AD f a = AD {
- runAD :: f a
- class Lifted t => Mode t where
Gradients (Reverse Mode)
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
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) -> (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f b)Source
Jacobians (Mixed Mode)
jacobian :: (Traversable f, Traversable g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s 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 need to support functions where the output is only a Functor
or Monad
, consider Numeric.AD.Reverse.jacobian
or gradM
from Numeric.AD.Reverse.
jacobian' :: (Traversable f, Traversable g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s 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, number of inputs and outputs.
If you need to support functions where the output is only a Functor
or Monad
, consider Numeric.AD.Reverse.jacobian'
or gradM'
from Numeric.AD.Reverse.
jacobianWith :: (Traversable f, Traversable g, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> g (AD s 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 need to support functions where the output is only a Functor
or Monad
, consider Numeric.AD.Reverse.jacobianWith
or gradWithM
from Numeric.AD.Reverse.
jacobianWith' :: (Traversable f, Traversable 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
calculates the answer and 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 need to support functions where the output is only a Functor
or Monad
, consider Numeric.AD.Reverse.jacobianWith'
or gradWithM'
from Numeric.AD.Reverse.
Jacobians (Reverse Mode)
gradF :: (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 gradF
function calculates the jacobian of a non-scalar-to-non-scalar function with reverse AD lazily in m
passes for m
outputs.
gradF' :: (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
gradWithF :: (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
'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) -> (forall s. Mode s => f (AD s a) -> g (AD s 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)
Jacobians (Forward Mode)
jacobianT :: (Traversable f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s 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) -> (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> f (g b)Source
A fast, simple transposed Jacobian computed with forward-mode AD.
Derivatives (Forward Mode)
diff' :: Num a => (forall s. Mode s => AD s a -> AD s 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)
duF :: (Functor f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f (a, a) -> g aSource
duF' :: (Functor f, Functor g, Num a) => (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f (a, a) -> g (a, a)Source
Taylor Series (Tower)
Maclaurin Series (Tower)
maclaurin0 :: Fractional a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]Source
Monadic Combinators (Forward Mode)
diffM :: (Monad m, Num a) => (forall s. Mode s => AD s a -> m (AD s a)) -> a -> m aSource
The dUM
function calculates the first derivative of scalar-to-scalar monadic function by Forward
AD
diffM' :: (Monad m, Num a) => (forall s. Mode s => AD s a -> m (AD s a)) -> a -> m (a, a)Source
The d'UM
function calculates the result and first derivative of a scalar-to-scalar monadic function by Forward
AD
Monadic Combinators (Reverse Mode)
gradM :: (Traversable f, Monad m, Num a) => (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (f a)Source
gradM' :: (Traversable f, Monad m, Num a) => (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (a, f a)Source
gradWithM :: (Traversable f, Monad m, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (f b)Source
gradWithM' :: (Traversable f, Monad m, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> m (AD s a)) -> f a -> m (a, f b)Source
Exposed Types
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