]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Integration/Trapezoid.hs
Add the Linear.System module.
[numerical-analysis.git] / src / Integration / Trapezoid.hs
index 959800135ea27be2da25aacd8bb3fc4a690139a6..444d92d2eb9a0ed2e6911970f54cd88aafd71b3a 100644 (file)
@@ -1,26 +1,15 @@
+{-# LANGUAGE RebindableSyntax #-}
+
 module Integration.Trapezoid
 where
 
+import Misc (partition)
 
--- | Partition the interval [@a@, @b@] into @n@ subintervals, which we
---   then return as a list of pairs.
-partition :: (RealFrac a, Integral b)
-          => b -- ^ The number of subintervals to use, @n@
-          -> a -- ^ The \"left\" endpoint of the interval, @a@
-          -> a -- ^ The \"right\" endpoint of the interval, @b@
-          -> [(a,a)]
- -- Somebody asked for zero subintervals? Ok.
-partition 0 _ _ = []
-partition n a b
-  | n < 0 = error "partition: asked for a negative number of subintervals"
-  | otherwise =
-    [ (xi, xj) | k <- [0..n-1],
-                 let k' = fromIntegral k,
-                 let xi = a + k'*h,
-                 let xj = a + (k'+1)*h ]
-    where
-      h = fromRational $ (toRational (b-a))/(toRational n)
-
+import NumericPrelude hiding (abs)
+import qualified Algebra.Field as Field
+import qualified Algebra.RealField as RealField
+import qualified Algebra.ToInteger as ToInteger
+import qualified Algebra.ToRational as ToRational
 
 -- | Use the trapezoid rule to numerically integrate @f@ over the
 --   interval [@a@, @b@].
@@ -43,30 +32,36 @@ partition n a b
 --   >>> trapezoid_1 f (-1) 1
 --   2.0
 --
-trapezoid_1 :: (RealFrac a, Fractional b, Num b)
+trapezoid_1 :: (Field.C a, ToRational.C a, Field.C b)
             => (a -> b) -- ^ The function @f@
             -> a       -- ^ The \"left\" endpoint, @a@
             -> a       -- ^ The \"right\" endpoint, @b@
             -> b
 trapezoid_1 f a b =
-  (((f a) + (f b)) / 2) * (fromRational $ toRational (b - a))
+  (((f a) + (f b)) / 2) * (fromRational' $ toRational (b - a))
 
 
--- | Use the composite trapezoid tule to numerically integrate @f@
+-- | Use the composite trapezoid rule to numerically integrate @f@
 --   over @n@ subintervals of [@a@, @b@].
 --
 --   Examples:
 --
+--   >>> import Algebra.Absolute (abs)
 --   >>> let f x = x^2
 --   >>> let area = trapezoid 1000 f (-1) 1
---   abs (area - (2/3)) < 0.00001
+--   >>> abs (area - (2/3)) < 0.00001
 --   True
 --
---   >>> let area = trapezoid 1000 sin (-1) 1
---   >>> abs (area - 2) < 0.00001
+--   >>> import Algebra.Absolute (abs)
+--   >>> let area = trapezoid 1000 sin 0 pi
+--   >>> abs (area - 2) < 0.0001
 --   True
 --
-trapezoid :: (RealFrac a, Fractional b, Num b, Integral c)
+trapezoid :: (RealField.C a,
+              ToRational.C a,
+              RealField.C b,
+              ToInteger.C c,
+              Enum c)
           => c -- ^ The number of subintervals to use, @n@
           -> (a -> b) -- ^ The function @f@
           -> a       -- ^ The \"left\" endpoint, @a@