module Integration.Trapezoid
where
-
--- | 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 Misc (partition)
-- | Use the trapezoid rule to numerically integrate @f@ over the
-- interval [@a@, @b@].
(((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:
--
-- >>> 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
+-- >>> let area = trapezoid 1000 sin 0 pi
+-- >>> abs (area - 2) < 0.0001
-- True
--
trapezoid :: (RealFrac a, Fractional b, Num b, Integral c)
--- /dev/null
+-- | Stuff for which I'm too lazy to come up with a decent name.
+module Misc
+where
+
+-- | Partition the interval [@a@, @b@] into @n@ subintervals, which we
+-- then return as a list of pairs.
+--
+-- Examples:
+--
+-- >>> partition 1 (-1) 1
+-- [(-1.0,1.0)]
+--
+-- >>> partition 4 (-1) 1
+-- [(-1.0,-0.5),(-0.5,0.0),(0.0,0.5),(0.5,1.0)]
+--
+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)