{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Safe #-}
module Physics.Learn.CompositeQuadrature
( compositeTrapezoid
, compositeSimpson
)
where
import Data.VectorSpace
( VectorSpace
, Scalar
, (^+^)
, (*^)
, zeroV
)
compositeTrapezoid :: (VectorSpace v, Fractional (Scalar v)) =>
Int
-> Scalar v
-> Scalar v
-> (Scalar v -> v)
-> v
compositeTrapezoid n a b f
= let dt = (b - a) / fromIntegral n
ts = [a + fromIntegral m * dt | m <- [0..n]]
pairs = [(t,f t) | t <- ts]
combine [] = error "compositeSimpson: odd number of half-intervals"
combine [_] = zeroV
combine ((t0,f0):(t1,f1):ps) = ((t1 - t0) / 2) *^ (f0 ^+^ f1) ^+^ combine ((t1,f1):ps)
in combine pairs
compositeSimpson :: (VectorSpace v, Fractional (Scalar v)) =>
Int
-> Scalar v
-> Scalar v
-> (Scalar v -> v)
-> v
compositeSimpson n a b f
= let nEven = 2 * div n 2
dt = (b - a) / fromIntegral nEven
ts = [a + fromIntegral m * dt | m <- [0..nEven]]
pairs = [(t,f t) | t <- ts]
combine [] = error "compositeSimpson: odd number of half-intervals"
combine [_] = zeroV
combine (_:_:[]) = error "compositeSimpson: odd number of half-intervals"
combine ((t0,f0):(_,f1):(t2,f2):ps) = ((t2 - t0) / 6) *^ (f0 ^+^ 4 *^ f1 ^+^ f2) ^+^ combine ((t2,f2):ps)
in combine pairs