{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE Safe #-}
module Physics.Learn.RootFinding
( findRoots
, findRootsN
, findRoot
, bracketRoot
, bracketRootStep
)
where
bracketRoot :: (Ord a, Fractional a) =>
a
-> (a -> a)
-> (a,a)
-> (a,a)
bracketRoot dx f (a,b)
= let fa = f a
fb = f b
bRoot ((c,fc),(d,fd)) = let m = (c + d) / 2
fm = f m
in if abs (c - d) < dx
then (c,d)
else if fc * fm <= 0
then bRoot ((c,fc),(m,fm))
else bRoot ((m,fm),(d,fd))
in if fa * fb > 0
then error "bracketRoot: initial interval is not a bracket"
else bRoot ((a,fa),(b,fb))
bracketRootStep :: (Ord a, Fractional a) =>
(a -> a)
-> ((a,a),(a,a))
-> ((a,a),(a,a))
bracketRootStep f ((a,fa),(b,fb))
= let m = (a + b) / 2
fm = f m
in if fa * fm <= 0
then ((a,fa),(m,fm))
else ((m,fm),(b,fb))
findRootMachinePrecision :: (Double -> Double)
-> ((Double,Double),(Double,Double))
-> Double
findRootMachinePrecision f ((c,fc),(d,fd))
= let m = (c + d) / 2
fm = f m
in if fc == 0
then c
else if fd == 0
then d
else if c == m
then c
else if m == d
then d
else if fc * fm <= 0
then findRootMachinePrecision f ((c,fc),(m,fm))
else findRootMachinePrecision f ((m,fm),(d,fd))
findRoot :: (Double -> Double)
-> (Double,Double)
-> Double
findRoot f (a,b)
= let fa = f a
fb = f b
in if fa * fb > 0
then error "bracketRoot: initial interval is not a bracket"
else findRootMachinePrecision f ((a,fa),(b,fb))
findRootsN :: Int
-> (Double -> Double)
-> (Double,Double)
-> [Double]
findRootsN n f (a,b)
= let dx = (b - a) / fromIntegral n
xs = [a,a+dx..b]
in map (findRootMachinePrecision f) [((x0,fx0),(x1,fx1)) | (x0,x1) <- zip xs (tail xs), let fx0 = f x0, let fx1 = f x1, fx0 * fx1 <= 0]
findRoots :: (Double -> Double)
-> (Double,Double)
-> [Double]
findRoots = findRootsN 1000