ad-4.5: Automatic Differentiation
Copyright(c) Edward Kmett 2010-2021
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Numeric.AD.Mode.Forward.Double

Description

Forward Mode AD specialized to Double. This enables the entire structure to be unboxed.

Synopsis

Documentation

data AD s a Source #

Instances

Instances details
Bounded a => Bounded (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

minBound :: AD s a #

maxBound :: AD s a #

Enum a => Enum (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

succ :: AD s a -> AD s a #

pred :: AD s a -> AD s a #

toEnum :: Int -> AD s a #

fromEnum :: AD s a -> Int #

enumFrom :: AD s a -> [AD s a] #

enumFromThen :: AD s a -> AD s a -> [AD s a] #

enumFromTo :: AD s a -> AD s a -> [AD s a] #

enumFromThenTo :: AD s a -> AD s a -> AD s a -> [AD s a] #

Eq a => Eq (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

(==) :: AD s a -> AD s a -> Bool #

(/=) :: AD s a -> AD s a -> Bool #

Floating a => Floating (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

pi :: AD s a #

exp :: AD s a -> AD s a #

log :: AD s a -> AD s a #

sqrt :: AD s a -> AD s a #

(**) :: AD s a -> AD s a -> AD s a #

logBase :: AD s a -> AD s a -> AD s a #

sin :: AD s a -> AD s a #

cos :: AD s a -> AD s a #

tan :: AD s a -> AD s a #

asin :: AD s a -> AD s a #

acos :: AD s a -> AD s a #

atan :: AD s a -> AD s a #

sinh :: AD s a -> AD s a #

cosh :: AD s a -> AD s a #

tanh :: AD s a -> AD s a #

asinh :: AD s a -> AD s a #

acosh :: AD s a -> AD s a #

atanh :: AD s a -> AD s a #

log1p :: AD s a -> AD s a #

expm1 :: AD s a -> AD s a #

log1pexp :: AD s a -> AD s a #

log1mexp :: AD s a -> AD s a #

Fractional a => Fractional (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

(/) :: AD s a -> AD s a -> AD s a #

recip :: AD s a -> AD s a #

fromRational :: Rational -> AD s a #

Num a => Num (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

(+) :: AD s a -> AD s a -> AD s a #

(-) :: AD s a -> AD s a -> AD s a #

(*) :: AD s a -> AD s a -> AD s a #

negate :: AD s a -> AD s a #

abs :: AD s a -> AD s a #

signum :: AD s a -> AD s a #

fromInteger :: Integer -> AD s a #

Ord a => Ord (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

compare :: AD s a -> AD s a -> Ordering #

(<) :: AD s a -> AD s a -> Bool #

(<=) :: AD s a -> AD s a -> Bool #

(>) :: AD s a -> AD s a -> Bool #

(>=) :: AD s a -> AD s a -> Bool #

max :: AD s a -> AD s a -> AD s a #

min :: AD s a -> AD s a -> AD s a #

Read a => Read (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

readsPrec :: Int -> ReadS (AD s a) #

readList :: ReadS [AD s a] #

readPrec :: ReadPrec (AD s a) #

readListPrec :: ReadPrec [AD s a] #

Real a => Real (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

toRational :: AD s a -> Rational #

RealFloat a => RealFloat (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

floatRadix :: AD s a -> Integer #

floatDigits :: AD s a -> Int #

floatRange :: AD s a -> (Int, Int) #

decodeFloat :: AD s a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> AD s a #

exponent :: AD s a -> Int #

significand :: AD s a -> AD s a #

scaleFloat :: Int -> AD s a -> AD s a #

isNaN :: AD s a -> Bool #

isInfinite :: AD s a -> Bool #

isDenormalized :: AD s a -> Bool #

isNegativeZero :: AD s a -> Bool #

isIEEE :: AD s a -> Bool #

atan2 :: AD s a -> AD s a -> AD s a #

RealFrac a => RealFrac (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

properFraction :: Integral b => AD s a -> (b, AD s a) #

truncate :: Integral b => AD s a -> b #

round :: Integral b => AD s a -> b #

ceiling :: Integral b => AD s a -> b #

floor :: Integral b => AD s a -> b #

Show a => Show (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

showsPrec :: Int -> AD s a -> ShowS #

show :: AD s a -> String #

showList :: [AD s a] -> ShowS #

Erf a => Erf (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

erf :: AD s a -> AD s a #

erfc :: AD s a -> AD s a #

erfcx :: AD s a -> AD s a #

normcdf :: AD s a -> AD s a #

InvErf a => InvErf (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Methods

inverf :: AD s a -> AD s a #

inverfc :: AD s a -> AD s a #

invnormcdf :: AD s a -> AD s a #

Mode a => Mode (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

Associated Types

type Scalar (AD s a) Source #

Methods

isKnownConstant :: AD s a -> Bool Source #

asKnownConstant :: AD s a -> Maybe (Scalar (AD s a)) Source #

isKnownZero :: AD s a -> Bool Source #

auto :: Scalar (AD s a) -> AD s a Source #

(*^) :: Scalar (AD s a) -> AD s a -> AD s a Source #

(^*) :: AD s a -> Scalar (AD s a) -> AD s a Source #

(^/) :: AD s a -> Scalar (AD s a) -> AD s a Source #

zero :: AD s a Source #

type Scalar (AD s a) Source # 
Instance details

Defined in Numeric.AD.Internal.Type

type Scalar (AD s a) = Scalar a

data ForwardDouble Source #

Instances

Instances details
Enum ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Eq ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Floating ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Fractional ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Num ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Ord ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Read ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Real ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

RealFloat ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

RealFrac ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Show ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Erf ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

InvErf ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Mode ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Associated Types

type Scalar ForwardDouble Source #

Jacobian ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Associated Types

type D ForwardDouble Source #

type Scalar ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

type D ForwardDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Forward.Double

Gradient

grad :: Traversable f => (forall s. f (AD s ForwardDouble) -> AD s ForwardDouble) -> f Double -> f Double Source #

Compute the gradient of a function using forward mode AD.

Note, this performs O(n) worse than grad for n inputs, in exchange for better space utilization.

grad' :: Traversable f => (forall s. f (AD s ForwardDouble) -> AD s ForwardDouble) -> f Double -> (Double, f Double) Source #

Compute the gradient and answer to a function using forward mode AD.

Note, this performs O(n) worse than grad' for n inputs, in exchange for better space utilization.

gradWith :: Traversable f => (Double -> Double -> b) -> (forall s. f (AD s ForwardDouble) -> AD s ForwardDouble) -> f Double -> f b Source #

Compute the gradient of a function using forward mode AD and combine the result with the input using a user-specified function.

Note, this performs O(n) worse than gradWith for n inputs, in exchange for better space utilization.

gradWith' :: Traversable f => (Double -> Double -> b) -> (forall s. f (AD s ForwardDouble) -> AD s ForwardDouble) -> f Double -> (Double, f b) Source #

Compute the gradient of a function using forward mode AD and the answer, and combine the result with the input using a user-specified function.

Note, this performs O(n) worse than gradWith' for n inputs, in exchange for better space utilization.

>>> gradWith' (,) sum [0..4]
(10.0,[(0.0,1.0),(1.0,1.0),(2.0,1.0),(3.0,1.0),(4.0,1.0)])

Jacobian

jacobian :: (Traversable f, Traversable g) => (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f Double -> g (f Double) Source #

Compute the Jacobian using Forward mode AD. This must transpose the result, so jacobianT is faster and allows more result types.

>>> jacobian (\[x,y] -> [y,x,x+y,x*y,exp x * sin y]) [pi,1]
[[0.0,1.0],[1.0,0.0],[1.0,1.0],[1.0,3.141592653589793],[19.472221418841606,12.502969588876512]]

jacobian' :: (Traversable f, Traversable g) => (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f Double -> g (Double, f Double) Source #

Compute the Jacobian using Forward mode AD along with the actual answer.

jacobianWith :: (Traversable f, Traversable g) => (Double -> Double -> b) -> (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f Double -> g (f b) Source #

Compute the Jacobian using Forward mode AD and combine the output with the input. This must transpose the result, so jacobianWithT is faster, and allows more result types.

jacobianWith' :: (Traversable f, Traversable g) => (Double -> Double -> b) -> (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f Double -> g (Double, f b) Source #

Compute the Jacobian using Forward mode AD combined with the input using a user specified function, along with the actual answer.

Transposed Jacobian

jacobianT :: (Traversable f, Functor g) => (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f Double -> f (g Double) Source #

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

jacobianWithT :: (Traversable f, Functor g) => (Double -> Double -> b) -> (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f Double -> f (g b) Source #

A fast, simple, transposed Jacobian computed with Forward mode AD that combines the output with the input.

Derivatives

diff :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> Double Source #

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

>>> diff sin 0
1.0

diff' :: (forall s. AD s ForwardDouble -> AD s ForwardDouble) -> Double -> (Double, Double) Source #

The diff' function calculates the result and first derivative of scalar-to-scalar function by Forward mode AD

diff' sin == sin &&& cos
diff' f = f &&& d f
>>> diff' sin 0
(0.0,1.0)
>>> diff' exp 0
(1.0,1.0)

diffF :: Functor f => (forall s. AD s ForwardDouble -> f (AD s ForwardDouble)) -> Double -> f Double Source #

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

>>> diffF (\a -> [sin a, cos a]) 0
[1.0,-0.0]

diffF' :: Functor f => (forall s. AD s ForwardDouble -> f (AD s ForwardDouble)) -> Double -> f (Double, Double) Source #

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

>>> diffF' (\a -> [sin a, cos a]) 0
[(0.0,1.0),(1.0,-0.0)]

Directional Derivatives

du :: Functor f => (forall s. f (AD s ForwardDouble) -> AD s ForwardDouble) -> f (Double, Double) -> Double Source #

Compute the directional derivative of a function given a zipped up Functor of the input values and their derivatives

du' :: Functor f => (forall s. f (AD s ForwardDouble) -> AD s ForwardDouble) -> f (Double, Double) -> (Double, Double) Source #

Compute the answer and directional derivative of a function given a zipped up Functor of the input values and their derivatives

duF :: (Functor f, Functor g) => (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f (Double, Double) -> g Double Source #

Compute a vector of directional derivatives for a function given a zipped up Functor of the input values and their derivatives.

duF' :: (Functor f, Functor g) => (forall s. f (AD s ForwardDouble) -> g (AD s ForwardDouble)) -> f (Double, Double) -> g (Double, Double) Source #

Compute a vector of answers and directional derivatives for a function given a zipped up Functor of the input values and their derivatives.