This problem try to solve following integral and it's analytic solution also given,
Trapezoidal method divide the interval into
This method give the error of
Another method is using Composite Simpson's rule which split up the interval into n subinterval. Then, the formula is given by
This method give the error of
I wrote the following code to compare the result of two subroutine. Follow by that, there are two subroutine which use trapezoidal rule and Simpson's rule respectly. With
PROGRAM MAIN
!========================================================
! Purpose: Compare different integration method
!
! Methods: trapezoidal + simpson's
!
! Date Programer Description of change
! ==== ========= =====================
! 10/20/20 MorrisH Original Code
!========================================================
IMPLICIT NONE
DOUBLE PRECISION, EXTERNAL :: f
DOUBLE PRECISION :: start, finish, ans, exact
! exact value
exact = (-3.d0 * dexp(4.d0) * dcos(6.d0) + &
2.d0 * dexp(4.d0) * dsin(6.d0) + 3.d0) / 13.d0
print *, "Exact value of this integral is: ", exact
write(*, '(a)') repeat('=', 60)
! evaluate trapezoidal rule
CALL CPU_TIME(start)
CALL TRAPEZOIDAL(f, 0.d0, 2.d0, 100, ans)
print *, "Trapezoidal method gives: ", ans
print *, "Error = ", abs(ans - exact) / exact
write(*, '(a)') repeat('=', 60)
! print *, "Cost", finish-start, 'sec'
CALL CPU_TIME(finish)
! evaluate simpson's rule
CALL CPU_TIME(start)
CALL SIMPSON(f, 0.d0, 2.d0, 100, ans)
print *, "Simpson's method gives: ", ans
print *, "Error = ", abs(ans - exact) / exact
write(*, '(a)') repeat('=', 60)
! print *, "Cost", finish-start, 'sec'
CALL CPU_TIME(finish)
END PROGRAM MAIN
SUBROUTINE TRAPEZOIDAL(func, a, b, n, ans)
!========================================================
! Purpose: Evaluate integral
!
! Methods: Trapezoidal rule
!
! Date Programer Description of change
! ==== ========= =====================
! 10/20/20 MorrisH Original Code
!========================================================
IMPLICIT NONE
DOUBLE PRECISION, EXTERNAL :: func
DOUBLE PRECISION :: a, b, ans
DOUBLE PRECISION :: h, u, d
INTEGER :: n, i
h = (b - a) / DBLE(n)
! divide [a, b] into n portion
ans = 0.d0
do i = 1, n
d = func( (DBLE(i) - 1.d0) * h + a )
u = func( DBLE(i) * h + a )
ans = ans + ( u + d )
end do
ans = ans * h / 2.d0
END SUBROUTINE TRAPEZOIDAL
SUBROUTINE SIMPSON(func, a, b, n, ans)
!========================================================
! Purpose: Evaluate integral
!
! Methods: Simpson's rule
!
! Date Programer Description of change
! ==== ========= =====================
! 10/20/20 MorrisH Original Code
!========================================================
IMPLICIT NONE
DOUBLE PRECISION, EXTERNAL :: func
DOUBLE PRECISION :: a, b, ans
DOUBLE PRECISION :: h, u, m, d
INTEGER :: n, i
ans = 0.d0
h = ( b - a ) / n
do i = 1, n/2
d = func( a + ( 2.d0 * DBLE(i) - 2.d0) * h )
m = func( a + ( 2.d0 * DBLE(i) - 1.d0) * h )
u = func( a + 2.d0 * DBLE(i) * h)
ans = ans + ( d + 4.d0 * m + u )
end do
ans = h / 3.d0 * ans
END SUBROUTINE SIMPSON
The error formula of these two methods are the following,
where
In order to reduce the error down to
So if
Similarly, in order to reduce the same error for Simpson's method, it must satified following condition
Following result verified above approximation. Also, the cpu_time for both subroutine to achieve same accracy is quite different.
In this problem I try to appoximate following difinite integral using Gauss-Lengendre quadratures which given by (13).
where
As you can see I evaluate with
PROGRAM QAULEG
!========================================================
! Purpose: Evaluate integral
!
! Methods: Gaussian quadrature
!
! Date Programer Description of change
! ==== ========= =====================
! 10/21/20 MorrisH Original Code
!========================================================
IMPLICIT NONE
DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: x, w
DOUBLE PRECISION, EXTERNAL :: f
DOUBLE PRECISION :: ans=0.d0
INTEGER :: s(5)=(/4, 8, 16, 48, 100 /)
INTEGER :: i, j, n
CHARACTER(len=10) :: txt
! write result to a file
open(99, file='result.dat', status='unknown')
do j = 1, 5
! number of node
n = s(j)
! open file
write(txt, '(I3.3)') n
open(66, file=TRIM(txt)//'.wx', status='old', action='read')
! allocate memory
allocate(x(n))
allocate(w(n))
! read file into x, w array
do i = 1, n
read(66, *) x(i), w(i)
end do
! evaluate integral
ans = 0.d0
do i = 1, n
ans = ans + w(i) * f(x(i))
end do
! deallocate the memory
deallocate(x)
deallocate(w)
! show the result
print *, "For n = ", n, ":", ans
write(*, '(A)') repeat("=", 50)
! write result
write(99, *) n, ans
close(66)
end do
END PROGRAM QAULEG
FUNCTION f(x)
IMPLICIT NONE
DOUBLE PRECISION :: f, x
f = DSQRT(1 + DCOS(24.d0 * x + 24.d0)**2) * 24.d0
END FUNCTION
We try to evalute following imporper integral.
But in order to let the computer calculate this integral, we can not simply let the upper range go to
Since there is
so
The relation between two integral is given by below figure.
Now we can use the Simpson's rule to calculate this integral with
If I plot the integral value as the n increase, we can see that it's value oscillatint bwtween two converging value. As the n increase, it doesn't settle to a single value.
When evaluate an improper integral, like following two example,
we can make a twist that transform the sigularity which
happened at the upper bound of the integral into the lower bound.
Then we can apply Simpson's rule to evaluate the integral, the result
show in below figures.
As you can see, both integral oscillate and gradually converge to
a single value as the
Double integral has the form of
For the step size of
Simpson's rule can be write as
Equation (18) can be easily expand to (n, m) point formula.
On the other hand, Gaussian quadrature is given by following formula.
where
Following two subroutine compute the integrl of eq (19)
and compare the cpu_time for the same accuracy(
10 time less than the Simpson's rule did.
SUBROUTINE DSIMP(func, a, b, c, d, n, m, ans)
!========================================================
! Purpose: Evaluate double integral
!
! Methods: Simpson's rule
!
! Date Programer Description of change
! ==== ========= =====================
! 10/24/20 MorrisH Original Code
!========================================================
IMPLICIT NONE
DOUBLE PRECISION, EXTERNAL :: func, c, d
DOUBLE PRECISION :: a, b, ans
DOUBLE PRECISION :: h
INTEGER :: n, m, i, j
DOUBLE PRECISION :: j1, j2, j3
DOUBLE PRECISION :: k1, k2, k3
DOUBLE PRECISION :: x, y, hx, Q, L
! initialize
ans = 0.d0
h = ( b - a ) / DBLE(n)
j1 = 0.d0
j2 = 0.d0
j3 = 0.d0
do i = 0, n
x = a + DBLE(i) * h
hx = (d(x) - c(x)) / DBLE(m)
k1 = func(x, c(x)) + func(x, d(X))
k2 = 0.d0
k3 = 0.d0
do j = 1, m-1
y = c(x) + DBLE(j) * hx
Q = func(x, y)
if (mod(j, 2) == 0) then
k2 = k2 + Q
else
k3 = k3 + Q
end if
end do
L = (k1 + 2.d0 * k2 + 4.d0 * k3) * hx / 3.d0
if ((i == 0) .or. (i == n)) then
j1 = j1 + L
else if (mod(i, 2) == 0) then
j2 = j2 + L
else
j3 = j3 + L
end if
end do
ans = h * (j1 + 2.d0 * j2 + 4.d0 * j3) / 3.d0
END SUBROUTINE DSIMP
SUBROUTINE dGAULEG(func, a, b, c, d, n, m, ans)
!========================================================
! Purpose: Evaluate integral
!
! Methods: Gaussian quadrature
!
! Date Programer Description of change
! ==== ========= =====================
! 10/21/20 MorrisH Original Code
!========================================================
IMPLICIT NONE
DOUBLE PRECISION, EXTERNAL :: func, c, d
DOUBLE PRECISION :: a, b, ans
INTEGER :: n, m
DOUBLE PRECISION :: h1, h2, jx
DOUBLE PRECISION :: x, y, d1, c1, k1, k2, Q
INTEGER :: i, j
CHARACTER(len=10) :: txt
DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: coef, r
write(txt, '(I3.3)') max(n, m)
open(66, file=TRIM(txt)//'.wx', status='old', &
action='read')
allocate(coef(max(n, m)))
allocate(r(max(n, m)))
! read weight and node
do i = 1, n
read(66, *) coef(i), r(i)
end do
h1 = (b - a) / 2.d0
h2 = (b + a) / 2.d0
ans = 0.d0
do i = 1, m
jx = 0
x = h1 * r(i) + h2
d1 = d(x)
c1 = c(x)
k1 = (d1 - c1) / 2.d0
k2 = (d1 + c1) / 2.d0
do j = 1, n
y = k1 * r(j) + k2
Q = func(x, y)
jx = jx + coef(j) * Q
end do
ans = ans + coef(i) * k1 * jx
end do
END SUBROUTINE dGAULEG