]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Roots/Fast.hs
Rename Aliases.hs to BigFloat.hs, now containing numeric-prelude instances for BigFloats.
[numerical-analysis.git] / src / Roots / Fast.hs
1 {-# LANGUAGE RebindableSyntax #-}
2
3 -- | The Roots.Fast module contains faster implementations of the
4 -- 'Roots.Simple' algorithms. Generally, we will pass precomputed
5 -- values to the next iteration of a function rather than passing
6 -- the function and the points at which to (re)evaluate it.
7
8 module Roots.Fast
9 where
10
11 import Data.List (find)
12
13 import Normed
14
15 import NumericPrelude hiding (abs)
16 import Algebra.Absolute
17 import Algebra.Field
18 import Algebra.Ring
19
20 has_root :: (Algebra.Field.C a,
21 Ord a,
22 Algebra.Ring.C b,
23 Ord b,
24 Algebra.Absolute.C b)
25 => (a -> b) -- ^ The function @f@
26 -> a -- ^ The \"left\" endpoint, @a@
27 -> a -- ^ The \"right\" endpoint, @b@
28 -> Maybe a -- ^ The size of the smallest subinterval
29 -- we'll examine, @epsilon@
30 -> Maybe b -- ^ Precoumpted f(a)
31 -> Maybe b -- ^ Precoumpted f(b)
32 -> Bool
33 has_root f a b epsilon f_of_a f_of_b =
34 if not ((signum (f_of_a')) * (signum (f_of_b')) == 1) then
35 -- We don't care about epsilon here, there's definitely a root!
36 True
37 else
38 if (b - a) <= epsilon' then
39 -- Give up, return false.
40 False
41 else
42 -- If either [a,c] or [c,b] have roots, we do too.
43 (has_root f a c (Just epsilon') (Just f_of_a') Nothing) ||
44 (has_root f c b (Just epsilon') Nothing (Just f_of_b'))
45 where
46 -- If the size of the smallest subinterval is not specified,
47 -- assume we just want to check once on all of [a,b].
48 epsilon' = case epsilon of
49 Nothing -> (b-a)
50 Just eps -> eps
51
52 -- Compute f(a) and f(b) only if needed.
53 f_of_a' = case f_of_a of
54 Nothing -> f a
55 Just v -> v
56
57 f_of_b' = case f_of_b of
58 Nothing -> f b
59 Just v -> v
60
61 c = (a + b)/2
62
63
64 bisect :: (Algebra.Field.C a,
65 Ord a,
66 Algebra.Ring.C b,
67 Ord b,
68 Algebra.Absolute.C b)
69 => (a -> b) -- ^ The function @f@ whose root we seek
70 -> a -- ^ The \"left\" endpoint of the interval, @a@
71 -> a -- ^ The \"right\" endpoint of the interval, @b@
72 -> a -- ^ The tolerance, @epsilon@
73 -> Maybe b -- ^ Precomputed f(a)
74 -> Maybe b -- ^ Precomputed f(b)
75 -> Maybe a
76 bisect f a b epsilon f_of_a f_of_b
77 -- We pass @epsilon@ to the 'has_root' function because if we want a
78 -- result within epsilon of the true root, we need to know that
79 -- there *is* a root within an interval of length epsilon.
80 | not (has_root f a b (Just epsilon) (Just f_of_a') (Just f_of_b')) = Nothing
81 | f_of_a' == 0 = Just a
82 | f_of_b' == 0 = Just b
83 | (b - c) < epsilon = Just c
84 | otherwise =
85 -- Use a 'prime' just for consistency.
86 let f_of_c' = f c in
87 if (has_root f a c (Just epsilon) (Just f_of_a') (Just f_of_c'))
88 then bisect f a c epsilon (Just f_of_a') (Just f_of_c')
89 else bisect f c b epsilon (Just f_of_c') (Just f_of_b')
90 where
91 -- Compute f(a) and f(b) only if needed.
92 f_of_a' = case f_of_a of
93 Nothing -> f a
94 Just v -> v
95
96 f_of_b' = case f_of_b of
97 Nothing -> f b
98 Just v -> v
99
100 c = (a + b) / 2
101
102
103
104
105 -- | Iterate the function @f@ with the initial guess @x0@ in hopes of
106 -- finding a fixed point.
107 fixed_point_iterations :: (a -> a) -- ^ The function @f@ to iterate.
108 -> a -- ^ The initial value @x0@.
109 -> [a] -- ^ The resulting sequence of x_{n}.
110 fixed_point_iterations f x0 =
111 iterate f x0
112
113
114 -- | Find a fixed point of the function @f@ with the search starting
115 -- at x0. This will find the first element in the chain f(x0),
116 -- f(f(x0)),... such that the magnitude of the difference between it
117 -- and the next element is less than epsilon.
118 --
119 -- We also return the number of iterations required.
120 --
121 fixed_point_with_iterations :: (Normed a,
122 Algebra.Field.C b,
123 Algebra.Absolute.C b,
124 Ord b)
125 => (a -> a) -- ^ The function @f@ to iterate.
126 -> b -- ^ The tolerance, @epsilon@.
127 -> a -- ^ The initial value @x0@.
128 -> (Int, a) -- ^ The (iterations, fixed point) pair
129 fixed_point_with_iterations f epsilon x0 =
130 (fst winning_pair)
131 where
132 xn = fixed_point_iterations f x0
133 xn_plus_one = tail xn
134
135 abs_diff v w = norm (v - w)
136
137 -- The nth entry in this list is the absolute value of x_{n} -
138 -- x_{n+1}.
139 differences = zipWith abs_diff xn xn_plus_one
140
141 -- This produces the list [(n, xn)] so that we can determine
142 -- the number of iterations required.
143 numbered_xn = zip [0..] xn
144
145 -- A list of pairs, (xn, |x_{n} - x_{n+1}|).
146 pairs = zip numbered_xn differences
147
148 -- The pair (xn, |x_{n} - x_{n+1}|) with
149 -- |x_{n} - x_{n+1}| < epsilon. The pattern match on 'Just' is
150 -- "safe" since the list is infinite. We'll succeed or loop
151 -- forever.
152 Just winning_pair = find (\(_, diff) -> diff < epsilon) pairs