+{-# LANGUAGE RebindableSyntax #-}
+
module Integration.Simpson
where
import Misc (partition)
+import NumericPrelude hiding (abs)
+import Algebra.Absolute (abs)
+import qualified Algebra.Field as Field
+import qualified Algebra.RealField as RealField
+import qualified Algebra.RealRing as RealRing
+import qualified Algebra.ToInteger as ToInteger
+import qualified Algebra.ToRational as ToRational
-- | Use the Simpson's rule to numerically integrate @f@ over the
-- interval [@a@, @b@].
-- >>> simpson_1 f 0 1
-- 0.25
--
-simpson_1 :: (RealFrac a, Fractional b, Num b)
+simpson_1 :: (RealField.C a, ToRational.C a, RealField.C b)
=> (a -> b) -- ^ The function @f@
-> a -- ^ The \"left\" endpoint, @a@
-> a -- ^ The \"right\" endpoint, @b@
simpson_1 f a b =
coefficient * ((f a) + 4*(f midpoint) + (f b))
where
- coefficient = (realToFrac (b - a)) / 6
+ coefficient = (fromRational' $ toRational (b - a)) / 6
midpoint = (a + b) / 2
-- >>> abs (area - 2) < 0.00001
-- True
--
-simpson :: (RealFrac a, Fractional b, Num b, Integral c)
+simpson :: (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@
+{-# LANGUAGE RebindableSyntax #-}
+
module Integration.Trapezoid
where
import Misc (partition)
+import NumericPrelude hiding (abs)
+import Algebra.Absolute (abs)
+import qualified Algebra.Field as Field
+import qualified Algebra.RealField as RealField
+import qualified Algebra.RealRing as RealRing
+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@].
--
-- >>> 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) * (realToFrac (b - a))
+ (((f a) + (f b)) / 2) * (fromRational' $ toRational (b - a))
-- | Use the composite trapezoid rule to numerically integrate @f@
-- >>> 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@