{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE BangPatterns #-}
module Numeric.AD.Rank1.Tower.Double
( TowerDouble
, auto
, taylor
, taylor0
, maclaurin
, maclaurin0
, diff
, diff'
, diffs
, diffs0
, diffsF
, diffs0F
, du
, du'
, dus
, dus0
, duF
, duF'
, dusF
, dus0F
) where
import Numeric.AD.Internal.Tower.Double
import Numeric.AD.Mode
diffs
:: (TowerDouble -> TowerDouble)
-> Double
-> [Double]
diffs :: (TowerDouble -> TowerDouble) -> Double -> [Double]
diffs TowerDouble -> TowerDouble
f Double
a = TowerDouble -> [Double]
getADTower (TowerDouble -> [Double]) -> TowerDouble -> [Double]
forall a b. (a -> b) -> a -> b
$ (TowerDouble -> TowerDouble) -> Double -> TowerDouble
forall b. (TowerDouble -> b) -> Double -> b
apply TowerDouble -> TowerDouble
f Double
a
{-# INLINE diffs #-}
diffs0
:: (TowerDouble -> TowerDouble)
-> Double
-> [Double]
diffs0 :: (TowerDouble -> TowerDouble) -> Double -> [Double]
diffs0 TowerDouble -> TowerDouble
f Double
a = [Double] -> [Double]
forall a. Num a => [a] -> [a]
zeroPad ((TowerDouble -> TowerDouble) -> Double -> [Double]
diffs TowerDouble -> TowerDouble
f Double
a)
{-# INLINE diffs0 #-}
diffsF
:: Functor f
=> (TowerDouble -> f TowerDouble)
-> Double
-> f [Double]
diffsF :: forall (f :: * -> *).
Functor f =>
(TowerDouble -> f TowerDouble) -> Double -> f [Double]
diffsF TowerDouble -> f TowerDouble
f Double
a = TowerDouble -> [Double]
getADTower (TowerDouble -> [Double]) -> f TowerDouble -> f [Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TowerDouble -> f TowerDouble) -> Double -> f TowerDouble
forall b. (TowerDouble -> b) -> Double -> b
apply TowerDouble -> f TowerDouble
f Double
a
{-# INLINE diffsF #-}
diffs0F
:: Functor f
=> (TowerDouble -> f TowerDouble)
-> Double
-> f [Double]
diffs0F :: forall (f :: * -> *).
Functor f =>
(TowerDouble -> f TowerDouble) -> Double -> f [Double]
diffs0F TowerDouble -> f TowerDouble
f Double
a = [Double] -> [Double]
forall a. Num a => [a] -> [a]
zeroPad ([Double] -> [Double])
-> (TowerDouble -> [Double]) -> TowerDouble -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TowerDouble -> [Double]
getADTower (TowerDouble -> [Double]) -> f TowerDouble -> f [Double]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TowerDouble -> f TowerDouble) -> Double -> f TowerDouble
forall b. (TowerDouble -> b) -> Double -> b
apply TowerDouble -> f TowerDouble
f Double
a
{-# INLINE diffs0F #-}
taylor
:: (TowerDouble -> TowerDouble)
-> Double
-> Double
-> [Double]
taylor :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
taylor TowerDouble -> TowerDouble
f Double
x Double
dx = Double -> Double -> [Double] -> [Double]
go Double
1 Double
1 ((TowerDouble -> TowerDouble) -> Double -> [Double]
diffs TowerDouble -> TowerDouble
f Double
x) where
go :: Double -> Double -> [Double] -> [Double]
go !Double
n !Double
acc (Double
a:[Double]
as) = Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
acc Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
: Double -> Double -> [Double] -> [Double]
go (Double
n Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1) (Double
acc Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
dx Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
n) [Double]
as
go Double
_ Double
_ [] = []
taylor0
:: (TowerDouble -> TowerDouble)
-> Double
-> Double
-> [Double]
taylor0 :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
taylor0 TowerDouble -> TowerDouble
f Double
x Double
dx = [Double] -> [Double]
forall a. Num a => [a] -> [a]
zeroPad ((TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
taylor TowerDouble -> TowerDouble
f Double
x Double
dx)
{-# INLINE taylor0 #-}
maclaurin
:: (TowerDouble -> TowerDouble)
-> Double
-> [Double]
maclaurin :: (TowerDouble -> TowerDouble) -> Double -> [Double]
maclaurin TowerDouble -> TowerDouble
f = (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
taylor TowerDouble -> TowerDouble
f Double
0
{-# INLINE maclaurin #-}
maclaurin0
:: (TowerDouble -> TowerDouble)
-> Double
-> [Double]
maclaurin0 :: (TowerDouble -> TowerDouble) -> Double -> [Double]
maclaurin0 TowerDouble -> TowerDouble
f = (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
taylor0 TowerDouble -> TowerDouble
f Double
0
{-# INLINE maclaurin0 #-}
diff
:: (TowerDouble -> TowerDouble)
-> Double
-> Double
diff :: (TowerDouble -> TowerDouble) -> Double -> Double
diff TowerDouble -> TowerDouble
f = [Double] -> Double
forall a. Num a => [a] -> a
d ([Double] -> Double) -> (Double -> [Double]) -> Double -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TowerDouble -> TowerDouble) -> Double -> [Double]
diffs TowerDouble -> TowerDouble
f
{-# INLINE diff #-}
diff'
:: (TowerDouble -> TowerDouble)
-> Double
-> (Double, Double)
diff' :: (TowerDouble -> TowerDouble) -> Double -> (Double, Double)
diff' TowerDouble -> TowerDouble
f = [Double] -> (Double, Double)
forall a. Num a => [a] -> (a, a)
d' ([Double] -> (Double, Double))
-> (Double -> [Double]) -> Double -> (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TowerDouble -> TowerDouble) -> Double -> [Double]
diffs TowerDouble -> TowerDouble
f
{-# INLINE diff' #-}
du
:: Functor f
=> (f TowerDouble -> TowerDouble)
-> f (Double, Double) -> Double
du :: forall (f :: * -> *).
Functor f =>
(f TowerDouble -> TowerDouble) -> f (Double, Double) -> Double
du f TowerDouble -> TowerDouble
f = [Double] -> Double
forall a. Num a => [a] -> a
d ([Double] -> Double)
-> (f (Double, Double) -> [Double]) -> f (Double, Double) -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TowerDouble -> [Double]
getADTower (TowerDouble -> [Double])
-> (f (Double, Double) -> TowerDouble)
-> f (Double, Double)
-> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> TowerDouble
f (f TowerDouble -> TowerDouble)
-> (f (Double, Double) -> f TowerDouble)
-> f (Double, Double)
-> TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Double, Double) -> TowerDouble)
-> f (Double, Double) -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double, Double) -> TowerDouble
withD
{-# INLINE du #-}
du'
:: Functor f
=> (f TowerDouble -> TowerDouble)
-> f (Double, Double)
-> (Double, Double)
du' :: forall (f :: * -> *).
Functor f =>
(f TowerDouble -> TowerDouble)
-> f (Double, Double) -> (Double, Double)
du' f TowerDouble -> TowerDouble
f = [Double] -> (Double, Double)
forall a. Num a => [a] -> (a, a)
d' ([Double] -> (Double, Double))
-> (f (Double, Double) -> [Double])
-> f (Double, Double)
-> (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TowerDouble -> [Double]
getADTower (TowerDouble -> [Double])
-> (f (Double, Double) -> TowerDouble)
-> f (Double, Double)
-> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> TowerDouble
f (f TowerDouble -> TowerDouble)
-> (f (Double, Double) -> f TowerDouble)
-> f (Double, Double)
-> TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Double, Double) -> TowerDouble)
-> f (Double, Double) -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double, Double) -> TowerDouble
withD
{-# INLINE du' #-}
duF
:: (Functor f, Functor g)
=> (f TowerDouble -> g TowerDouble)
-> f (Double, Double)
-> g Double
duF :: forall (f :: * -> *) (g :: * -> *).
(Functor f, Functor g) =>
(f TowerDouble -> g TowerDouble) -> f (Double, Double) -> g Double
duF f TowerDouble -> g TowerDouble
f = (TowerDouble -> Double) -> g TowerDouble -> g Double
forall a b. (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Double] -> Double
forall a. Num a => [a] -> a
d ([Double] -> Double)
-> (TowerDouble -> [Double]) -> TowerDouble -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TowerDouble -> [Double]
getADTower) (g TowerDouble -> g Double)
-> (f (Double, Double) -> g TowerDouble)
-> f (Double, Double)
-> g Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> g TowerDouble
f (f TowerDouble -> g TowerDouble)
-> (f (Double, Double) -> f TowerDouble)
-> f (Double, Double)
-> g TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Double, Double) -> TowerDouble)
-> f (Double, Double) -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double, Double) -> TowerDouble
withD
{-# INLINE duF #-}
duF'
:: (Functor f, Functor g)
=> (f TowerDouble -> g TowerDouble)
-> f (Double, Double)
-> g (Double, Double)
duF' :: forall (f :: * -> *) (g :: * -> *).
(Functor f, Functor g) =>
(f TowerDouble -> g TowerDouble)
-> f (Double, Double) -> g (Double, Double)
duF' f TowerDouble -> g TowerDouble
f = (TowerDouble -> (Double, Double))
-> g TowerDouble -> g (Double, Double)
forall a b. (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Double] -> (Double, Double)
forall a. Num a => [a] -> (a, a)
d' ([Double] -> (Double, Double))
-> (TowerDouble -> [Double]) -> TowerDouble -> (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TowerDouble -> [Double]
getADTower) (g TowerDouble -> g (Double, Double))
-> (f (Double, Double) -> g TowerDouble)
-> f (Double, Double)
-> g (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> g TowerDouble
f (f TowerDouble -> g TowerDouble)
-> (f (Double, Double) -> f TowerDouble)
-> f (Double, Double)
-> g TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Double, Double) -> TowerDouble)
-> f (Double, Double) -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double, Double) -> TowerDouble
withD
{-# INLINE duF' #-}
dus
:: Functor f
=> (f TowerDouble -> TowerDouble)
-> f [Double]
-> [Double]
dus :: forall (f :: * -> *).
Functor f =>
(f TowerDouble -> TowerDouble) -> f [Double] -> [Double]
dus f TowerDouble -> TowerDouble
f = TowerDouble -> [Double]
getADTower (TowerDouble -> [Double])
-> (f [Double] -> TowerDouble) -> f [Double] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> TowerDouble
f (f TowerDouble -> TowerDouble)
-> (f [Double] -> f TowerDouble) -> f [Double] -> TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Double] -> TowerDouble) -> f [Double] -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Double] -> TowerDouble
tower
{-# INLINE dus #-}
dus0
:: Functor f
=> (f TowerDouble -> TowerDouble)
-> f [Double]
-> [Double]
dus0 :: forall (f :: * -> *).
Functor f =>
(f TowerDouble -> TowerDouble) -> f [Double] -> [Double]
dus0 f TowerDouble -> TowerDouble
f = [Double] -> [Double]
forall a. Num a => [a] -> [a]
zeroPad ([Double] -> [Double])
-> (f [Double] -> [Double]) -> f [Double] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TowerDouble -> [Double]
getADTower (TowerDouble -> [Double])
-> (f [Double] -> TowerDouble) -> f [Double] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> TowerDouble
f (f TowerDouble -> TowerDouble)
-> (f [Double] -> f TowerDouble) -> f [Double] -> TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Double] -> TowerDouble) -> f [Double] -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Double] -> TowerDouble
tower
{-# INLINE dus0 #-}
dusF
:: (Functor f, Functor g)
=> (f TowerDouble -> g TowerDouble)
-> f [Double]
-> g [Double]
dusF :: forall (f :: * -> *) (g :: * -> *).
(Functor f, Functor g) =>
(f TowerDouble -> g TowerDouble) -> f [Double] -> g [Double]
dusF f TowerDouble -> g TowerDouble
f = (TowerDouble -> [Double]) -> g TowerDouble -> g [Double]
forall a b. (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TowerDouble -> [Double]
getADTower (g TowerDouble -> g [Double])
-> (f [Double] -> g TowerDouble) -> f [Double] -> g [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> g TowerDouble
f (f TowerDouble -> g TowerDouble)
-> (f [Double] -> f TowerDouble) -> f [Double] -> g TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Double] -> TowerDouble) -> f [Double] -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Double] -> TowerDouble
tower
{-# INLINE dusF #-}
dus0F
:: (Functor f, Functor g)
=> (f TowerDouble -> g TowerDouble)
-> f [Double]
-> g [Double]
dus0F :: forall (f :: * -> *) (g :: * -> *).
(Functor f, Functor g) =>
(f TowerDouble -> g TowerDouble) -> f [Double] -> g [Double]
dus0F f TowerDouble -> g TowerDouble
f = (TowerDouble -> [Double]) -> g TowerDouble -> g [Double]
forall a b. (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TowerDouble -> [Double]
getADTower (g TowerDouble -> g [Double])
-> (f [Double] -> g TowerDouble) -> f [Double] -> g [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f TowerDouble -> g TowerDouble
f (f TowerDouble -> g TowerDouble)
-> (f [Double] -> f TowerDouble) -> f [Double] -> g TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Double] -> TowerDouble) -> f [Double] -> f TowerDouble
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Double] -> TowerDouble
tower
{-# INLINE dus0F #-}