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

Numeric.AD.Mode.Tower.Double

Description

Higher order derivatives via a "dual number tower".

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 TowerDouble Source #

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

Instances

Instances details
Enum TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Eq TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Floating TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Fractional TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

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 #

Num TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Ord TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Real TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

RealFloat 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

Mode TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Associated Types

type Scalar TowerDouble Source #

Jacobian TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

Associated Types

type D TowerDouble Source #

type Scalar TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

type D TowerDouble Source # 
Instance details

Defined in Numeric.AD.Internal.Tower.Double

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

Embed a constant

Taylor Series

taylor :: (forall s. AD s TowerDouble -> AD s TowerDouble) -> Double -> Double -> [Double] Source #

taylor0 :: (forall s. AD s TowerDouble -> AD s TowerDouble) -> Double -> Double -> [Double] Source #

Maclaurin Series

maclaurin :: (forall s. AD s TowerDouble -> AD s TowerDouble) -> Double -> [Double] Source #

maclaurin0 :: (forall s. AD s TowerDouble -> AD s TowerDouble) -> Double -> [Double] Source #

Derivatives

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

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

diffs :: (forall s. AD s TowerDouble -> AD s TowerDouble) -> Double -> [Double] Source #

diffs0 :: (forall s. AD s TowerDouble -> AD s TowerDouble) -> Double -> [Double] Source #

diffsF :: Functor f => (forall s. AD s TowerDouble -> f (AD s TowerDouble)) -> Double -> f [Double] Source #

diffs0F :: Functor f => (forall s. AD s TowerDouble -> f (AD s TowerDouble)) -> Double -> f [Double] Source #

Directional Derivatives

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

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

dus :: Functor f => (forall s. f (AD s TowerDouble) -> AD s TowerDouble) -> f [Double] -> [Double] Source #

dus0 :: Functor f => (forall s. f (AD s TowerDouble) -> AD s TowerDouble) -> f [Double] -> [Double] Source #

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

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

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

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