]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Roots/Simple.hs
src/Roots/Simple.hs: fix monomorphism restriction warning.
[numerical-analysis.git] / src / Roots / Simple.hs
index 03b39aeb643de47ed6546693c26346851b80b0fc..2906d95839c69daab27580863d8d61bb5f14ccc6 100644 (file)
@@ -1,4 +1,5 @@
 {-# LANGUAGE RebindableSyntax #-}
+{-# LANGUAGE ScopedTypeVariables #-}
 
 -- | The Roots.Simple module contains root-finding algorithms. That
 --   is, procedures to (numerically) find solutions to the equation,
@@ -8,22 +9,34 @@
 --   where f is assumed to be continuous on the interval of interest.
 --
 
-module Roots.Simple
+module Roots.Simple (
+  bisect,
+  fixed_point,
+  fixed_point_error_ratios,
+  fixed_point_iteration_count,
+  has_root,
+  newtons_method,
+  secant_method,
+  trisect )
 where
 
 import Data.List (find)
+import NumericPrelude hiding ( abs )
+import Algebra.Absolute ( abs )
+import qualified Algebra.Additive as Additive ( C )
+import qualified Algebra.Algebraic as Algebraic ( C )
+import qualified Algebra.Field as Field ( C )
+import qualified Algebra.RealField as RealField ( C )
+import qualified Algebra.RealRing as RealRing ( C )
 
-import Normed
+import Normed ( Normed(..) )
+import qualified Roots.Fast as F (
+  bisect,
+  fixed_point_iterations,
+  fixed_point_with_iterations,
+  has_root,
+  trisect )
 
-import qualified Roots.Fast as F
-
-import NumericPrelude hiding (abs)
-import Algebra.Absolute (abs)
-import qualified Algebra.Additive as Additive
-import qualified Algebra.Algebraic as Algebraic
-import qualified Algebra.Field as Field
-import qualified Algebra.RealField as RealField
-import qualified Algebra.RealRing as RealRing
 
 -- | Does the (continuous) function @f@ have a root on the interval
 --   [a,b]? If f(a) <] 0 and f(b) ]> 0, we know that there's a root in
@@ -160,7 +173,7 @@ fixed_point_iteration_count f epsilon x0 =
 --
 --   This is used to determine the rate of convergence.
 --
-fixed_point_error_ratios :: (Normed a,
+fixed_point_error_ratios :: forall a b. (Normed a,
                              Additive.C a,
                              RealField.C b,
                              Algebraic.C b)
@@ -173,7 +186,7 @@ fixed_point_error_ratios f x0 x_star p =
   zipWith (/) en_plus_one en_exp
   where
     xn = F.fixed_point_iterations f x0
-    en = map (\x -> norm (x_star - x)) xn
+    en = map (\x -> norm (x_star - x)) xn :: [b]
     en_plus_one = tail en
     en_exp = map (^p) en
 
@@ -185,6 +198,7 @@ fixed_point_error_ratios f x0 x_star p =
 --   Examples:
 --
 --   Atkinson, p. 60.
+--
 --   >>> let f x = x^6 - x - 1
 --   >>> let f' x = 6*x^5 - 1
 --   >>> tail $ take 4 $ newton_iterations f f' 2
@@ -271,6 +285,7 @@ iterate2 f x0 x1 =
 --   Examples:
 --
 --   Atkinson, p. 67.
+--
 --   >>> let f x = x^6 - x - 1
 --   >>> take 4 $ secant_iterations f 2 1
 --   [2.0,1.0,1.0161290322580645,1.190577768676638]
@@ -296,6 +311,7 @@ secant_iterations f =
 --   Examples:
 --
 --   Atkinson, p. 67.
+--
 --   >>> let f x = x^6 - x - 1
 --   >>> let Just root = secant_method f (1/10^9) 2 1
 --   >>> root