]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Roots/Simple.hs
Rename Aliases.hs to BigFloat.hs, now containing numeric-prelude instances for BigFloats.
[numerical-analysis.git] / src / Roots / Simple.hs
1 {-# LANGUAGE RebindableSyntax #-}
2
3 -- | The Roots.Simple module contains root-finding algorithms. That
4 -- is, procedures to (numerically) find solutions to the equation,
5 --
6 -- > f(x) = 0
7 --
8 -- where f is assumed to be continuous on the interval of interest.
9 --
10
11 module Roots.Simple
12 where
13
14 import Data.List (find)
15
16 import Normed
17
18 import qualified Roots.Fast as F
19
20 import NumericPrelude hiding (abs)
21 import Algebra.Absolute
22 import Algebra.Field
23 import Algebra.Ring
24
25 -- | Does the (continuous) function @f@ have a root on the interval
26 -- [a,b]? If f(a) <] 0 and f(b) ]> 0, we know that there's a root in
27 -- [a,b] by the intermediate value theorem. Likewise when f(a) >= 0
28 -- and f(b) <= 0.
29 --
30 -- Examples:
31 --
32 -- >>> let f x = x**3
33 -- >>> has_root f (-1) 1 Nothing
34 -- True
35 --
36 -- This fails if we don't specify an @epsilon@, because cos(-2) ==
37 -- cos(2) doesn't imply that there's a root on [-2,2].
38 --
39 -- >>> has_root cos (-2) 2 Nothing
40 -- False
41 -- >>> has_root cos (-2) 2 (Just 0.001)
42 -- True
43 --
44 has_root :: (Algebra.Field.C a,
45 Ord a,
46 Algebra.Ring.C b,
47 Algebra.Absolute.C b,
48 Ord b)
49 => (a -> b) -- ^ The function @f@
50 -> a -- ^ The \"left\" endpoint, @a@
51 -> a -- ^ The \"right\" endpoint, @b@
52 -> Maybe a -- ^ The size of the smallest subinterval
53 -- we'll examine, @epsilon@
54 -> Bool
55 has_root f a b epsilon =
56 F.has_root f a b epsilon Nothing Nothing
57
58
59 -- | We are given a function @f@ and an interval [a,b]. The bisection
60 -- method checks finds a root by splitting [a,b] in half repeatedly.
61 --
62 -- If one is found within some prescribed tolerance @epsilon@, it is
63 -- returned. Otherwise, the interval [a,b] is split into two
64 -- subintervals [a,c] and [c,b] of equal length which are then both
65 -- checked via the same process.
66 --
67 -- Returns 'Just' the value x for which f(x) == 0 if one is found,
68 -- or Nothing if one of the preconditions is violated.
69 --
70 -- Examples:
71 --
72 -- >>> bisect cos 1 2 0.001
73 -- Just 1.5712890625
74 --
75 -- >>> bisect sin (-1) 1 0.001
76 -- Just 0.0
77 --
78 bisect :: (Algebra.Field.C a,
79 Ord a,
80 Algebra.Ring.C b,
81 Algebra.Absolute.C b,
82 Ord b)
83 => (a -> b) -- ^ The function @f@ whose root we seek
84 -> a -- ^ The \"left\" endpoint of the interval, @a@
85 -> a -- ^ The \"right\" endpoint of the interval, @b@
86 -> a -- ^ The tolerance, @epsilon@
87 -> Maybe a
88 bisect f a b epsilon =
89 F.bisect f a b epsilon Nothing Nothing
90
91
92 -- | Find a fixed point of the function @f@ with the search starting
93 -- at x0. We delegate to the version that returns the number of
94 -- iterations and simply discard the number of iterations.
95 --
96 fixed_point :: (Normed a,
97 Algebra.Field.C b,
98 Algebra.Absolute.C b,
99 Ord b)
100 => (a -> a) -- ^ The function @f@ to iterate.
101 -> b -- ^ The tolerance, @epsilon@.
102 -> a -- ^ The initial value @x0@.
103 -> a -- ^ The fixed point.
104 fixed_point f epsilon x0 =
105 snd $ F.fixed_point_with_iterations f epsilon x0
106
107
108 -- | Return the number of iterations required to find a fixed point of
109 -- the function @f@ with the search starting at x0 and tolerance
110 -- @epsilon@. We delegate to the version that returns the number of
111 -- iterations and simply discard the fixed point.
112 fixed_point_iteration_count :: (Normed a,
113 Algebra.Field.C b,
114 Algebra.Absolute.C b,
115 Ord b)
116 => (a -> a) -- ^ The function @f@ to iterate.
117 -> b -- ^ The tolerance, @epsilon@.
118 -> a -- ^ The initial value @x0@.
119 -> Int -- ^ The fixed point.
120 fixed_point_iteration_count f epsilon x0 =
121 fst $ F.fixed_point_with_iterations f epsilon x0
122
123
124 -- | Returns a list of ratios,
125 --
126 -- ||x^{*} - x_{n+1}|| / ||x^{*} - x_{n}||^{p}
127 --
128 -- of fixed point iterations for the function @f@ with initial guess
129 -- @x0@ and @p@ some positive power.
130 --
131 -- This is used to determine the rate of convergence.
132 --
133 fixed_point_error_ratios :: (Normed a,
134 Algebra.Field.C b,
135 Algebra.Absolute.C b,
136 Ord b)
137 => (a -> a) -- ^ The function @f@ to iterate.
138 -> a -- ^ The initial value @x0@.
139 -> a -- ^ The true solution, @x_star@.
140 -> Integer -- ^ The power @p@.
141 -> [b] -- ^ The resulting sequence of x_{n}.
142 fixed_point_error_ratios f x0 x_star p =
143 zipWith (/) en_plus_one en_exp
144 where
145 xn = F.fixed_point_iterations f x0
146 en = map (\x -> norm (x_star - x)) xn
147 en_plus_one = tail en
148 en_exp = map (^p) en
149
150
151
152 -- | The sequence x_{n} of values obtained by applying Newton's method
153 -- on the function @f@ and initial guess @x0@.
154 --
155 -- Examples:
156 --
157 -- Atkinson, p. 60.
158 -- >>> let f x = x^6 - x - 1
159 -- >>> let f' x = 6*x^5 - 1
160 -- >>> tail $ take 4 $ newton_iterations f f' 2
161 -- [1.6806282722513088,1.4307389882390624,1.2549709561094362]
162 --
163 newton_iterations :: (Algebra.Field.C a)
164 => (a -> a) -- ^ The function @f@ whose root we seek
165 -> (a -> a) -- ^ The derivative of @f@
166 -> a -- ^ Initial guess, x-naught
167 -> [a]
168 newton_iterations f f' x0 =
169 iterate next x0
170 where
171 next xn =
172 xn - ( (f xn) / (f' xn) )
173
174
175 -- | Use Newton's method to find a root of @f@ near the initial guess
176 -- @x0@. If your guess is bad, this will recurse forever!
177 --
178 -- Examples:
179 --
180 -- Atkinson, p. 60.
181 --
182 -- >>> let f x = x^6 - x - 1
183 -- >>> let f' x = 6*x^5 - 1
184 -- >>> let Just root = newtons_method f f' (1/1000000) 2
185 -- >>> root
186 -- 1.1347241385002211
187 -- >>> abs (f root) < 1/100000
188 -- True
189 --
190 -- >>> import Data.Number.BigFloat
191 -- >>> let eps = 1/(10^20) :: BigFloat Prec50
192 -- >>> let Just root = newtons_method f f' eps 2
193 -- >>> root
194 -- 1.13472413840151949260544605450647284028100785303643e0
195 -- >>> abs (f root) < eps
196 -- True
197 --
198 newtons_method :: (Algebra.Field.C a, Algebra.Absolute.C a, Ord a)
199 => (a -> a) -- ^ The function @f@ whose root we seek
200 -> (a -> a) -- ^ The derivative of @f@
201 -> a -- ^ The tolerance epsilon
202 -> a -- ^ Initial guess, x-naught
203 -> Maybe a
204 newtons_method f f' epsilon x0 =
205 find (\x -> abs (f x) < epsilon) x_n
206 where
207 x_n = newton_iterations f f' x0
208
209
210 -- | Takes a function @f@ of two arguments and repeatedly applies @f@
211 -- to the previous two values. Returns a list containing all
212 -- generated values, f(x0, x1), f(x1, x2), f(x2, x3)...
213 --
214 -- Examples:
215 --
216 -- >>> let fibs = iterate2 (+) 0 1
217 -- >>> take 15 fibs
218 -- [0,1,1,2,3,5,8,13,21,34,55,89,144,233,377]
219 --
220 iterate2 :: (a -> a -> a) -- ^ The function @f@
221 -> a -- ^ The initial value @x0@
222 -> a -- ^ The second value, @x1@
223 -> [a] -- ^ The result list, [x0, x1, ...]
224 iterate2 f x0 x1 =
225 x0 : x1 : (go x0 x1)
226 where
227 go prev2 prev1 =
228 let next = f prev2 prev1 in
229 next : go prev1 next
230
231
232 -- | The sequence x_{n} of values obtained by applying the secant
233 -- method on the function @f@ and initial guesses @x0@, @x1@.
234 --
235 -- The recursion more or less implements a two-parameter 'iterate',
236 -- although one list is passed to the next iteration (as opposed to
237 -- one function argument, with iterate). At each step, we peel the
238 -- first two elements off the list and then compute/append elements
239 -- three, four... onto the end of the list.
240 --
241 -- Examples:
242 --
243 -- Atkinson, p. 67.
244 -- >>> let f x = x^6 - x - 1
245 -- >>> take 4 $ secant_iterations f 2 1
246 -- [2.0,1.0,1.0161290322580645,1.190577768676638]
247 --
248 secant_iterations :: (Algebra.Field.C a)
249 => (a -> a) -- ^ The function @f@ whose root we seek
250 -> a -- ^ Initial guess, x-naught
251 -> a -- ^ Second initial guess, x-one
252 -> [a]
253 secant_iterations f x0 x1 =
254 iterate2 g x0 x1
255 where
256 g prev2 prev1 =
257 let x_change = prev1 - prev2
258 y_change = (f prev1) - (f prev2)
259 in
260 (prev1 - (f prev1 * (x_change / y_change)))
261
262
263 -- | Use the secant method to find a root of @f@ near the initial guesses
264 -- @x0@ and @x1@. If your guesses are bad, this will recurse forever!
265 --
266 -- Examples:
267 --
268 -- Atkinson, p. 67.
269 -- >>> let f x = x^6 - x - 1
270 -- >>> let Just root = secant_method f (1/10^9) 2 1
271 -- >>> root
272 -- 1.1347241384015196
273 -- >>> abs (f root) < (1/10^9)
274 -- True
275 --
276 secant_method :: (Algebra.Field.C a, Algebra.Absolute.C a, Ord a)
277 => (a -> a) -- ^ The function @f@ whose root we seek
278 -> a -- ^ The tolerance epsilon
279 -> a -- ^ Initial guess, x-naught
280 -> a -- ^ Second initial guess, x-one
281 -> Maybe a
282 secant_method f epsilon x0 x1
283 = find (\x -> abs (f x) < epsilon) x_n
284 where
285 x_n = secant_iterations f x0 x1