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

Numeric.AD.Rank1.Tower.Double

Description

Higher order derivatives via a "dual number tower".

Synopsis

Documentation

data TowerDouble Source #

Tower is an AD Mode that calculates a tangent tower by forward AD, and provides fast diffsUU, diffsUF

Instances

Instances details
Jacobian TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Associated Types

type D TowerDouble Source #

Mode TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Associated Types

type Scalar TowerDouble Source #

Data TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TowerDouble -> c TowerDouble #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TowerDouble #

toConstr :: TowerDouble -> Constr #

dataTypeOf :: TowerDouble -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TowerDouble) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TowerDouble) #

gmapT :: (forall b. Data b => b -> b) -> TowerDouble -> TowerDouble #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TowerDouble -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TowerDouble -> r #

gmapQ :: (forall d. Data d => d -> u) -> TowerDouble -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TowerDouble -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TowerDouble -> m TowerDouble #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TowerDouble -> m TowerDouble #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TowerDouble -> m TowerDouble #

Enum TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Floating TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

RealFloat TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Num TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Fractional TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Real TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

RealFrac TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Show TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Erf TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

InvErf TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Eq TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Ord TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

type D TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

type Scalar TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

auto :: Mode t => Scalar t -> t Source #

Embed a constant

Taylor Series

taylor :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double] Source #

taylor f x compute the Taylor series of f around x.

taylor0 :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double] Source #

taylor0 f x compute the Taylor series of f around x, zero-padded.

Maclaurin Series

maclaurin :: (TowerDouble -> TowerDouble) -> Double -> [Double] Source #

maclaurin f compute the Maclaurin series of f

maclaurin0 :: (TowerDouble -> TowerDouble) -> Double -> [Double] Source #

maclaurin f compute the Maclaurin series of f, zero-padded

Derivatives

diff :: (TowerDouble -> TowerDouble) -> Double -> Double Source #

Compute the first derivative of a function (a -> a)

diff' :: (TowerDouble -> TowerDouble) -> Double -> (Double, Double) Source #

Compute the answer and first derivative of a function (a -> a)

diffs :: (TowerDouble -> TowerDouble) -> Double -> [Double] Source #

Compute the answer and all derivatives of a function (a -> a)

diffs0 :: (TowerDouble -> TowerDouble) -> Double -> [Double] Source #

Compute the zero-padded derivatives of a function (a -> a)

diffsF :: Functor f => (TowerDouble -> f TowerDouble) -> Double -> f [Double] Source #

Compute the answer and all derivatives of a function (a -> f a)

diffs0F :: Functor f => (TowerDouble -> f TowerDouble) -> Double -> f [Double] Source #

Compute the zero-padded derivatives of a function (a -> f a)

Directional Derivatives

du :: Functor f => (f TowerDouble -> TowerDouble) -> f (Double, Double) -> Double Source #

Compute a directional derivative of a function (f a -> a)

du' :: Functor f => (f TowerDouble -> TowerDouble) -> f (Double, Double) -> (Double, Double) Source #

Compute the answer and a directional derivative of a function (f a -> a)

dus :: Functor f => (f TowerDouble -> TowerDouble) -> f [Double] -> [Double] Source #

Given a function (f a -> a), and a tower of derivatives, compute the corresponding directional derivatives.

dus0 :: Functor f => (f TowerDouble -> TowerDouble) -> f [Double] -> [Double] Source #

Given a function (f a -> a), and a tower of derivatives, compute the corresponding directional derivatives, zero-padded

duF :: (Functor f, Functor g) => (f TowerDouble -> g TowerDouble) -> f (Double, Double) -> g Double Source #

Compute a directional derivative of a function (f a -> g a)

duF' :: (Functor f, Functor g) => (f TowerDouble -> g TowerDouble) -> f (Double, Double) -> g (Double, Double) Source #

Compute the answer and a directional derivative of a function (f a -> g a)

dusF :: (Functor f, Functor g) => (f TowerDouble -> g TowerDouble) -> f [Double] -> g [Double] Source #

Given a function (f a -> g a), and a tower of derivatives, compute the corresponding directional derivatives

dus0F :: (Functor f, Functor g) => (f TowerDouble -> g TowerDouble) -> f [Double] -> g [Double] Source #

Given a function (f a -> g a), and a tower of derivatives, compute the corresponding directional derivatives, zero-padded