{-# LANGUAGE CPP #-}
module Numeric.AD.Rank1.Halley.Double
(
findZero
, inverse
, fixedPoint
, extremum
) where
import Prelude hiding (all)
import Numeric.AD.Internal.Forward (Forward)
import Numeric.AD.Internal.On
import Numeric.AD.Internal.Tower.Double (TowerDouble)
import Numeric.AD.Mode
import Numeric.AD.Rank1.Tower.Double (diffs0)
import Numeric.AD.Rank1.Forward (diff)
import Numeric.AD.Internal.Combinators (takeWhileDifferent)
findZero :: (TowerDouble -> TowerDouble) -> Double -> [Double]
findZero :: (TowerDouble -> TowerDouble) -> Double -> [Double]
findZero TowerDouble -> TowerDouble
f = [Double] -> [Double]
forall a. Eq a => [a] -> [a]
takeWhileDifferent ([Double] -> [Double])
-> (Double -> [Double]) -> Double -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TowerDouble -> TowerDouble) -> Double -> [Double]
findZeroNoEq TowerDouble -> TowerDouble
f
{-# INLINE findZero #-}
findZeroNoEq :: (TowerDouble -> TowerDouble) -> Double -> [Double]
findZeroNoEq :: (TowerDouble -> TowerDouble) -> Double -> [Double]
findZeroNoEq TowerDouble -> TowerDouble
f = (Double -> Double) -> Double -> [Double]
forall a. (a -> a) -> a -> [a]
iterate Double -> Double
go where
go :: Double -> Double
go Double
x = Double
xn where
(Double
y,Double
y',Double
y'') = case (TowerDouble -> TowerDouble) -> Double -> [Double]
diffs0 TowerDouble -> TowerDouble
f Double
x of
(Double
z:Double
z':Double
z'':[Double]
_) -> (Double
z,Double
z',Double
z'')
[Double]
_ -> [Char] -> (Double, Double, Double)
forall a. HasCallStack => [Char] -> a
error [Char]
"findZeroNoEq: Impossible (diffs0 should produce an infinite list)"
xn :: Double
xn = Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
2Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
yDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
y'Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/(Double
2Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
y'Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
y'Double -> Double -> Double
forall a. Num a => a -> a -> a
-Double
yDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
y'')
#ifdef HERBIE
{-# ANN findZeroNoEq "NoHerbie" #-}
#endif
{-# INLINE findZeroNoEq #-}
inverse :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
inverse :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
inverse TowerDouble -> TowerDouble
f Double
x0 = [Double] -> [Double]
forall a. Eq a => [a] -> [a]
takeWhileDifferent ([Double] -> [Double])
-> (Double -> [Double]) -> Double -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
inverseNoEq TowerDouble -> TowerDouble
f Double
x0
{-# INLINE inverse #-}
inverseNoEq :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
inverseNoEq :: (TowerDouble -> TowerDouble) -> Double -> Double -> [Double]
inverseNoEq TowerDouble -> TowerDouble
f Double
x0 Double
y = (TowerDouble -> TowerDouble) -> Double -> [Double]
findZeroNoEq (\TowerDouble
x -> TowerDouble -> TowerDouble
f TowerDouble
x TowerDouble -> TowerDouble -> TowerDouble
forall a. Num a => a -> a -> a
- Scalar TowerDouble -> TowerDouble
forall t. Mode t => Scalar t -> t
auto Double
Scalar TowerDouble
y) Double
x0
{-# INLINE inverseNoEq #-}
fixedPoint :: (TowerDouble -> TowerDouble) -> Double -> [Double]
fixedPoint :: (TowerDouble -> TowerDouble) -> Double -> [Double]
fixedPoint TowerDouble -> TowerDouble
f = [Double] -> [Double]
forall a. Eq a => [a] -> [a]
takeWhileDifferent ([Double] -> [Double])
-> (Double -> [Double]) -> Double -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TowerDouble -> TowerDouble) -> Double -> [Double]
fixedPointNoEq TowerDouble -> TowerDouble
f
{-# INLINE fixedPoint #-}
fixedPointNoEq :: (TowerDouble -> TowerDouble) -> Double -> [Double]
fixedPointNoEq :: (TowerDouble -> TowerDouble) -> Double -> [Double]
fixedPointNoEq TowerDouble -> TowerDouble
f = (TowerDouble -> TowerDouble) -> Double -> [Double]
findZeroNoEq (\TowerDouble
x -> TowerDouble -> TowerDouble
f TowerDouble
x TowerDouble -> TowerDouble -> TowerDouble
forall a. Num a => a -> a -> a
- TowerDouble
x)
{-# INLINE fixedPointNoEq #-}
extremum :: (On (Forward TowerDouble) -> On (Forward TowerDouble)) -> Double -> [Double]
extremum :: (On (Forward TowerDouble) -> On (Forward TowerDouble))
-> Double -> [Double]
extremum On (Forward TowerDouble) -> On (Forward TowerDouble)
f = [Double] -> [Double]
forall a. Eq a => [a] -> [a]
takeWhileDifferent ([Double] -> [Double])
-> (Double -> [Double]) -> Double -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (On (Forward TowerDouble) -> On (Forward TowerDouble))
-> Double -> [Double]
extremumNoEq On (Forward TowerDouble) -> On (Forward TowerDouble)
f
{-# INLINE extremum #-}
extremumNoEq :: (On (Forward TowerDouble) -> On (Forward TowerDouble)) -> Double -> [Double]
extremumNoEq :: (On (Forward TowerDouble) -> On (Forward TowerDouble))
-> Double -> [Double]
extremumNoEq On (Forward TowerDouble) -> On (Forward TowerDouble)
f = (TowerDouble -> TowerDouble) -> Double -> [Double]
findZeroNoEq ((Forward TowerDouble -> Forward TowerDouble)
-> TowerDouble -> TowerDouble
forall a. Num a => (Forward a -> Forward a) -> a -> a
diff (On (Forward TowerDouble) -> Forward TowerDouble
forall t. On t -> t
off (On (Forward TowerDouble) -> Forward TowerDouble)
-> (Forward TowerDouble -> On (Forward TowerDouble))
-> Forward TowerDouble
-> Forward TowerDouble
forall b c a. (b -> c) -> (a -> b) -> a -> c
. On (Forward TowerDouble) -> On (Forward TowerDouble)
f (On (Forward TowerDouble) -> On (Forward TowerDouble))
-> (Forward TowerDouble -> On (Forward TowerDouble))
-> Forward TowerDouble
-> On (Forward TowerDouble)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Forward TowerDouble -> On (Forward TowerDouble)
forall t. t -> On t
On))
{-# INLINE extremumNoEq #-}