]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Roots/Fast.hs
Rename Aliases.hs to BigFloat.hs, now containing numeric-prelude instances for BigFloats.
[numerical-analysis.git] / src / Roots / Fast.hs
index 5efdf3be99eec871931d18c6095333b8bd31ce83..47fa512a75476310403d1faed03b9c54bdabe171 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE RebindableSyntax #-}
+
 -- | The Roots.Fast module contains faster implementations of the
 --   'Roots.Simple' algorithms. Generally, we will pass precomputed
 --   values to the next iteration of a function rather than passing
@@ -10,8 +12,16 @@ import Data.List (find)
 
 import Normed
 
+import NumericPrelude hiding (abs)
+import Algebra.Absolute
+import Algebra.Field
+import Algebra.Ring
 
-has_root :: (Fractional a, Ord a, Ord b, Num b)
+has_root :: (Algebra.Field.C a,
+             Ord a,
+             Algebra.Ring.C b,
+             Ord b,
+             Algebra.Absolute.C b)
          => (a -> b) -- ^ The function @f@
          -> a       -- ^ The \"left\" endpoint, @a@
          -> a       -- ^ The \"right\" endpoint, @b@
@@ -51,8 +61,11 @@ has_root f a b epsilon f_of_a f_of_b =
     c = (a + b)/2
 
 
-
-bisect :: (Fractional a, Ord a, Num b, Ord b)
+bisect :: (Algebra.Field.C a,
+           Ord a,
+           Algebra.Ring.C b,
+           Ord b,
+           Algebra.Absolute.C b)
        => (a -> b) -- ^ The function @f@ whose root we seek
        -> a       -- ^ The \"left\" endpoint of the interval, @a@
        -> a       -- ^ The \"right\" endpoint of the interval, @b@
@@ -88,6 +101,7 @@ bisect f a b epsilon f_of_a f_of_b
 
 
 
+
 -- | Iterate the function @f@ with the initial guess @x0@ in hopes of
 --   finding a fixed point.
 fixed_point_iterations :: (a -> a) -- ^ The function @f@ to iterate.
@@ -104,7 +118,10 @@ fixed_point_iterations f x0 =
 --
 --   We also return the number of iterations required.
 --
-fixed_point_with_iterations :: (Normed a, RealFrac b)
+fixed_point_with_iterations :: (Normed a,
+                                Algebra.Field.C b,
+                                Algebra.Absolute.C b,
+                                Ord b)
                             => (a -> a)  -- ^ The function @f@ to iterate.
                             -> b        -- ^ The tolerance, @epsilon@.
                             -> a        -- ^ The initial value @x0@.
@@ -133,4 +150,3 @@ fixed_point_with_iterations f epsilon x0 =
     -- "safe" since the list is infinite. We'll succeed or loop
     -- forever.
     Just winning_pair = find (\(_, diff) -> diff < epsilon) pairs
-