ad-0.15: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com

Numeric.AD

Contents

Description

Mixed-Mode Automatic Differentiation.

Each combinator exported from this module chooses an appropriate AD mode.

Synopsis

Gradients

grad :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> f aSource

The grad function calculates the gradient of a non-scalar-to-scalar function with Reverse AD in a single pass.

grad2 :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f a)Source

The grad2 function calculates the result and gradient of a non-scalar-to-scalar function with Reverse AD in a single pass.

gradWith :: (Traversable f, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> f bSource

grad g f function calculates the gradient of a non-scalar-to-scalar function f 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

gradWith2 :: (Traversable f, Num a) => (a -> a -> b) -> (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f b)Source

grad2 g f calculates the result and gradient of a non-scalar-to-scalar function f with Reverse AD in a single pass the gradient is combined element-wise with the argument using the function g.

 grad2 == gradWith2 (\_ dx -> dx)

Jacobians

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

jacobian2 :: (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 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, consider using jacobianT from Numeric.AD.Forward or jacobian2 from Numeric.AD.Reverse directly.

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

jacobianWith g f 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.

The resulting Jacobian matrix is then recombined element-wise with the input using g.

jacobianWith2 :: (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

jacobianWith2 g f 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.

The resulting Jacobian matrix is then recombined element-wise with the input using g.

Synonyms

diff :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> aSource

The diff2 function calculates the first derivative of scalar-to-scalar function by Forward AD

diff2 :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> (a, a)Source

The diff2 function calculates the result and first derivative of scalar-to-scalar function by Forward AD

diffs :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]Source

diffs0 :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]Source

Derivatives (Forward)

diffUU :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> aSource

The diffUU function calculates the first derivative of a scalar-to-scalar function by Forward AD

diffUF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f aSource

The diffUF function calculates the first derivative of scalar-to-nonscalar function by Forward AD

diff2UU :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> (a, a)Source

The diff2UU function calculates the result and first derivative of scalar-to-scalar function by Forward AD

diff2UF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f (a, a)Source

The diff2UF function calculates the result and first derivative of a scalar-to-non-scalar function by Forward AD

Derivatives (Reverse)

diffFU :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> f aSource

diff2FU :: (Traversable f, Num a) => (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> (a, f a)Source

Derivatives (Tower)

diffsUU :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]Source

diffsUF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f [a]Source

diffs0UU :: Num a => (forall s. Mode s => AD s a -> AD s a) -> a -> [a]Source

diffs0UF :: (Functor f, Num a) => (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f [a]Source

Taylor Series (Tower)

taylor :: Fractional a => (forall s. Mode s => AD s a -> AD s a) -> a -> a -> [a]Source

taylor0 :: Fractional a => (forall s. Mode s => AD s a -> AD s a) -> a -> a -> [a]Source

Exposed Types

newtype AD f a Source

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.

Constructors

AD 

Fields

runAD :: f a
 

Instances

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

Methods

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 :: Num a => t aSource

 'zero' = 'lift' 0