ad-0.13: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com

Numeric.AD.Reverse

Contents

Description

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.

Synopsis

Gradient

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.

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.

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

Derivatives

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

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

The diff2UU function calculates the value and derivative, as a pair, of a scalar-to-scalar function.

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

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

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

Synonyms

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

The diff function is a synonym for diffUU.

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

The diff2 function is a synonym for diff2UU.

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) 
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) 
Var (AD Reverse a) 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