]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Polynomials/Orthogonal.hs
src/Polynomials/Orthogonal.hs: fix monomorphism restriction warnings.
[numerical-analysis.git] / src / Polynomials / Orthogonal.hs
index 28cf41d15ce8de056d2e51895d9906b06fc6c67f..13ffa995b379600336a68780d44c49532300dd55 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+
 -- | The polynomials over [a,b] form a basis for L_2[a,b]. But often
 --   the \"obvious\" choice of a basis {1, x, x^2,...} is not
 --   convenient, because its elements are not orthogonal.
 --
 --   where w(x) is some non-negative (or non-positive) weight function.
 --
-module Polynomials.Orthogonal
+module Polynomials.Orthogonal (
+  legendre )
 where
 
 import NumericPrelude
-import qualified Algebra.RealField as RealField
-import qualified Prelude as P
+import qualified Algebra.RealField as RealField ( C )
+import Prelude ()
 
 
 -- | The @n@th Legendre polynomial in @x@ over [-1,1]. These are
@@ -62,7 +65,7 @@ import qualified Prelude as P
 --   >>> actual == expected
 --   True
 --
-legendre :: (RealField.C a)
+legendre :: forall a. (RealField.C a)
          => Integer -- ^ The degree (i.e. the number of) the polynomial you want.
          -> a -- ^ The dependent variable @x@.
          -> a
@@ -71,5 +74,5 @@ legendre 1 x = x
 legendre n x =
   (c1*x * (legendre (n-1) x) - c2*(legendre (n-2) x)) / (fromInteger n)
   where
-    c1 = fromInteger $ 2*n - 1
-    c2 = fromInteger $ n - 1
+    c1 = fromInteger $ 2*n - 1 :: a
+    c2 = fromInteger $ n - 1 :: a