ad-1.4: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellSafe-Infered

Numeric.AD.Mode.Tower

Contents

Description

Higher order derivatives via a "dual number tower".

Synopsis

Taylor Series

taylor :: Fractional a => UU a -> a -> a -> [a]Source

taylor0 :: Fractional a => UU a -> a -> a -> [a]Source

Maclaurin Series

maclaurin :: Fractional a => UU a -> a -> [a]Source

maclaurin0 :: Fractional a => UU a -> a -> [a]Source

Derivatives

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

diff' :: Num a => UU a -> a -> (a, a)Source

diffs :: Num a => UU a -> a -> [a]Source

diffs0 :: Num a => UU a -> a -> [a]Source

diffsF :: (Functor f, Num a) => UF f a -> a -> f [a]Source

diffs0F :: (Functor f, Num a) => UF f a -> a -> f [a]Source

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

dus :: (Functor f, Num a) => FU f a -> f [a] -> [a]Source

dus0 :: (Functor f, Num a) => FU f a -> f [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

dusF :: (Functor f, Functor g, Num a) => FF f g a -> f [a] -> g [a]Source

dus0F :: (Functor f, Functor g, Num a) => FF f g a -> f [a] -> g [a]Source

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.

class Lifted t => Mode t whereSource

Methods

isKnownConstant :: t a -> BoolSource

allowed to return False for items with a zero derivative, but we'll give more NaNs than strictly necessary

isKnownZero :: Num a => t a -> BoolSource

allowed to return False for zero, but we give more NaN's than strictly necessary then

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

(<**>) :: Floating a => t a -> t a -> t aSource

Exponentiation, this should be overloaded if you can figure out anything about what is constant!

zero :: Num a => t aSource

 'zero' = 'lift' 0

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

Typeable1 f => Typeable1 (AD f) 
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) 
(Typeable1 f, Typeable a, Data (f a), Data a) => Data (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) 
(Num a, Lifted f, Show a) => Show (AD f a) 
Num a => Grad (AD Reverse a) [a] (a, [a]) a 
Num a => Grad (AD Sparse a) [a] (a, [a]) a 
Grads i o a => Grads (AD Sparse a -> i) (a -> o) a 
Num a => Grads (AD Sparse a) (Cofree [] a) a 
Grad i o o' a => Grad (AD Reverse a -> i) (a -> o) (a -> o') a 
Grad i o o' a => Grad (AD Sparse a -> i) (a -> o) (a -> o') a