PPITG
This function evaluates the integral of a piecewise polynomial.
Function Return Value
PPITG — Value of the integral from A to B of the piecewise polynomial. (Output)
Required Arguments
A — Lower limit of integration. (Input)
B — Upper limit of integration. (Input)
BREAK — Array of length NINTV + 1 containing the breakpoints for the piecewise polynomial. (Input)
BREAK must be strictly increasing.
PPCOEF — Array of size KORDER * NINTV containing the local coefficients of the piecewise polynomial pieces. (Input)
PPCOEF is treated internally as a matrix of size KORDER by NINTV.
Optional Arguments
KORDER — Order of the polynomial. (Input)
Default: KORDER = size (PPCOEF,1).
NINTV — Number of piecewise polynomial pieces. (Input)
Default: NINTV = size (PPCOEF,2).
FORTRAN 90 Interface
Generic: PP1TG (A, B, BREAK, PPCOEF [])
Specific: The specific interface names are S_PP1TG and D_PP1TG.
FORTRAN 77 Interface
Single: PP1TG (A, B, KORDER, NINTV, BREAK, PPCOEF)
Double: The double precision function name is DPP1TG.
Description
The routine PPITG evaluates the integral of a piecewise polynomial over an interval.
Example
In this example, we compute a quadratic spline interpolant to the function x2 using the IMSL routine BSINT. We then evaluate the integral of the spline interpolant over the intervals [0, 1/2] and [0, 2]. The interpolant reproduces x2, and hence, the values of the integrals are 1/24 and 8/3, respectively.
 
USE IMSL_LIBRARIES
 
IMPLICIT NONE
INTEGER KORDER, NDATA, NKNOT
PARAMETER (KORDER=3, NDATA=10, NKNOT=NDATA+KORDER)
!
INTEGER I, NOUT, NPPCF
REAL A, B, BREAK(NDATA), BSCOEF(NDATA), EXACT, F,&
FDATA(NDATA), FI, FLOAT, PPCOEF(KORDER,NDATA),&
VALUE, X, XDATA(NDATA), XKNOT(NKNOT)
INTRINSIC FLOAT
!
F(X) = X*X
FI(X) = X*X*X/3.0
! Set up interpolation points
DO 10 I=1, NDATA
XDATA(I) = FLOAT(I-1)/FLOAT(NDATA-1)
FDATA(I) = F(XDATA(I))
10 CONTINUE
! Generate knot sequence
CALL BSNAK (NDATA, XDATA, KORDER, XKNOT)
! Interpolate
CALL BSINT (NDATA, XDATA, FDATA, KORDER, XKNOT, BSCOEF)
! Convert to piecewise polynomial
CALL BSCPP (KORDER, XKNOT, NDATA, BSCOEF, NPPCF, BREAK, PPCOEF)
! Compute the integral of F over
! [0.0,0.5]
A = 0.0
B = 0.5
VALUE = PPITG(A,B,BREAK,PPCOEF,NINTV=NPPCF)
EXACT = FI(B) - FI(A)
! Get output unit number
CALL UMACH (2, NOUT)
! Print the result
WRITE (NOUT,99999) A, B, VALUE, EXACT, EXACT - VALUE
! Compute the integral of F over
! [0.0,2.0]
A = 0.0
B = 2.0
VALUE = PPITG(A,B,BREAK,PPCOEF,NINTV=NPPCF)
EXACT = FI(B) - FI(A)
! Print the result
WRITE (NOUT,99999) A, B, VALUE, EXACT, EXACT - VALUE
99999 FORMAT (' On the closed interval (', F3.1, ',', F3.1,&
') we have :', /, 1X, 'Computed Integral = ', F10.5, /,&
1X, 'Exact Integral = ', F10.5, /, 1X, 'Error '&
, ' = ', F10.6, /, /)
!
END
Output
 
On the closed interval (0.0,0.5) we have :
Computed Integral = 0.04167
Exact Integral = 0.04167
Error = 0.000000
 
On the closed interval (0.0,2.0) we have :
Computed Integral = 2.66667
Exact Integral = 2.66667
Error = 0.000001
Published date: 03/19/2020
Last modified date: 03/19/2020