ad-0.28: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com

Numeric.AD.Forward

Contents

Description

Forward mode automatic differentiation

Synopsis

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

gradWith' :: (Traversable f, Num a) => (a -> a -> b) -> FU f a -> f a -> (a, f b)Source

Jacobian

jacobian :: (Traversable f, Traversable g, Num a) => FF f g a -> f a -> g (f a)Source

jacobian' :: (Traversable f, Traversable g, Num a) => FF f g a -> f a -> g (a, f a)Source

jacobianWith :: (Traversable f, Traversable g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (f b)Source

jacobianWith' :: (Traversable f, Traversable g, Num a) => (a -> a -> b) -> FF f g a -> f a -> g (a, f b)Source

Transposed Jacobian

jacobianT :: (Traversable f, Functor g, Num a) => FF f g 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) -> FF f g a -> f a -> f (g b)Source

A fast, simple transposed Jacobian computed with forward-mode AD.

Hessian Product

hessianProduct :: (Traversable f, Num a) => FU f a -> f (a, a) -> f aSource

Compute the product of a vector with the Hessian using forward-on-forward-mode AD.

hessianProduct' :: (Traversable f, Num a) => FU f a -> f (a, a) -> f (a, a)Source

Compute the gradient and hessian product using forward-on-forward-mode AD.

Derivatives

diff :: Num a => UU a -> a -> aSource

The diff function calculates the first derivative of a scalar-to-scalar function by forward-mode AD

 diff sin == cos

diff' :: Num a => UU 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

diffF :: (Functor f, Num a) => UF f a -> a -> f aSource

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

diffF' :: (Functor f, Num a) => UF f a -> a -> f (a, a)Source

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

Directional Derivatives

du :: (Functor f, Num a) => FU f a -> f (a, a) -> aSource

du' :: (Functor f, Num a) => FU f a -> f (a, a) -> (a, a)Source

duF :: (Functor f, Functor g, Num a) => FF f g a -> f (a, a) -> g aSource

duF' :: (Functor f, Functor g, Num a) => FF f g a -> f (a, a) -> g (a, a)Source

Monadic Combinators

diffM :: (Monad m, Num a) => UF m 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) => UF m 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

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.

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

Instances