ad-3.3.0.1: Automatic Differentiation

PortabilityGHC only
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Numeric.AD.Types

Contents

Description

 

Synopsis

AD modes

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

auto :: 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

Instances

AD variables

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) 
(Lifted (AD f), Mode f) => Mode (AD f) 
Lifted f => Lifted (AD f) 
(Primal (AD f), Var f) => Var (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) 
(Fractional (AD f a), Lifted f, Floating a) => Floating (AD f a) 
(Num (AD f a), Lifted f, Fractional a) => Fractional (AD f a) 
(Typeable (AD f a), Typeable1 f, Typeable a, Data (f a), Data a) => Data (AD f a) 
(Lifted f, Num a) => Num (AD f a) 
(Eq (AD f a), Num a, Lifted f, Ord a) => Ord (AD f a) 
(Num (AD f a), Ord (AD f a), Lifted f, Real a) => Real (AD f a) 
(RealFrac (AD f a), Floating (AD f a), Lifted f, RealFloat a) => RealFloat (AD f a) 
(Real (AD f a), Fractional (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 Sparse a) [a] (a, [a]) a 
Num a => Grad (AD Kahn a) [a] (a, [a]) a 
(Num a, Grads i o a) => Grads (AD Sparse a -> i) (a -> o) a 
Num a => Grads (AD Sparse a) (Cofree [] a) a 
(Num a, Grad i o o' a) => Grad (AD Sparse a -> i) (a -> o) (a -> o') a 
(Num a, Grad i o o' a) => Grad (AD Kahn a -> i) (a -> o) (a -> o') a 

Jets

data Jet f a Source

A Jet is a tower of all (higher order) partial derivatives of a function

At each step, a Jet f is wrapped in another layer worth of f.

 a :- f a :- f (f a) :- f (f (f a)) :- ...

Constructors

a :- (Jet f (f a)) 

Instances

Functor f => Functor (Jet f) 
Typeable1 f => Typeable1 (Jet f) 
Foldable f => Foldable (Jet f) 
(Functor (Jet f), Foldable (Jet f), Traversable f) => Traversable (Jet f) 
(Functor f, Show (f Showable), Show a) => Show (Jet f a) 

headJet :: Jet f a -> aSource

Take the head of a Jet.

tailJet :: Jet f a -> Jet f (f a)Source

Take the tail of a Jet.

jet :: Functor f => Cofree f a -> Jet f aSource

Construct a Jet by unzipping the layers of a Cofree Comonad.

Apply functions that use lift

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

Evaluate a scalar-to-scalar function in the trivial identity AD mode.

lowerUF :: (forall s. Mode s => AD s a -> f (AD s a)) -> a -> f aSource

Evaluate a scalar-to-nonscalar function in the trivial identity AD mode.

lowerFU :: (forall s. Mode s => f (AD s a) -> AD s a) -> f a -> aSource

Evaluate a nonscalar-to-scalar function in the trivial identity AD mode.

lowerFF :: (forall s. Mode s => f (AD s a) -> g (AD s a)) -> f a -> g aSource

Evaluate a nonscalar-to-nonscalar function in the trivial identity AD mode.