|
subroutine, public | cfp_bfqad (F, T, BCOEF, N, K, ID, X1, X2, TOL, QUAD, IERR, WORK) |
|
subroutine | wp_bsgq8 (FUN, XT, BC, N, KK, ID, A, B, INBV, ERR, ANS, IERR, WORK) |
|
subroutine | ep_bsgq8 (FUN, XT, BC, N, KK, ID, A, B, INBV, ERR, ANS, IERR, WORK) |
|
subroutine, public | cfp_bsqad (F, T, BCOEF, N, K, ID, X1, X2, TOL, QUAD, IERR, WORK) |
|
subroutine | wp_bssgq8 (FUN, XT, BC, N, KK, ID, A, B, INBV, ERR, ANS, IERR, WORK) |
|
subroutine | ep_bssgq8 (FUN, XT, BC, N, KK, ID, A, B, INBV, ERR, ANS, IERR, WORK) |
|
subroutine, public | cfp_bfqro (F, T, BCOEF, N, KK, ID, X1, X2, TOL, QUAD, IERR, WORK) |
|
subroutine | ep_trapzd (F, a, b, s, n, T, BCOEF, NB, K, ID, WORK, INBV) |
|
real(kind=wp) function, dimension(n) | wp_arth (first, increment, n) |
|
Quadrature module
Contains routines for integration of a b-spline with an arbitrary user-defined function. The function is defined using the function_1d class. See function_integration module for details on how this is used.
subroutine, public quadrature_module_gbl::cfp_bfqad |
( |
class(function_1d) |
F, |
|
|
real(kind=cfp), dimension(:), intent(in) |
T, |
|
|
real(kind=cfp), dimension(:), intent(in) |
BCOEF, |
|
|
integer |
N, |
|
|
integer |
K, |
|
|
integer |
ID, |
|
|
real(kind=cfp) |
X1, |
|
|
real(kind=cfp) |
X2, |
|
|
real(kind=cfp) |
TOL, |
|
|
real(kind=cfp) |
QUAD, |
|
|
integer |
IERR, |
|
|
real(kind=cfp), dimension(:) |
WORK |
|
) |
| |
Purpose:
Compute the integral of a product of a function and a
derivative of a K-th order B-spline:
\[ \int_{x_{1}}^{x_{2}} dr B(r)f(r) \]
AUTHOR Amos, D. E., (SNLA)
DESCRIPTION
Abstract **** a double precision routine ****
cfp_bfqad computes the integral on (X1,X2) of a product of a
function F and the ID-th derivative of a K-th order B-spline,
using the B-representation (T,BCOEF,N,K). (X1,X2) must be a
subinterval of T(K) .LE. X .LE. T(N+1). An integration rou-
tine, DBSGQ8 (a modification of GAUS8), integrates the product
on subintervals of (X1,X2) formed by included (distinct) knots
The maximum number of significant digits obtainable in
DBSQAD is the smaller of 18 and the number of digits
carried in double precision arithmetic.
Description of Arguments
Input F,T,BCOEF,X1,X2,TOL are double precision
- Parameters
-
[in] | F |
Function of one argument for the integrand BF(X)=F(X)*BVALU(T,BCOEF,N,K,ID,X,INBV,WORK) |
[in] | T | Knot array of length N+K |
[in] | BCOEF | Coefficient array of length N |
[in] | N | Length of coefficient array |
[in] | K | Order of B-spline, K .GE. 1 |
[in] | ID | Order of the spline derivative, 0 .LE. ID .LE. K-1. ID=0 gives the spline function |
[in] | X1,X2 | End points of quadrature interval in T(K) .LE. X .LE. T(N+1)
|
[in] | TOL | Desired accuracy for the quadrature, suggest 10.*DTOL .LT. TOL .LE. .1 where DTOL is the maximum of 1.0D-18 and double precision unit roundoff for the machine = F1MACH(4) |
[out] | QUAD | \( \int_{x_{1}}^{x_{2}} dr B(r)f(r) \) Integral of BF(X) on (X1,X2) |
[out] | IERR | A status code
IERR=1 normal return
2 some quadrature on (X1,X2) does not meet the requested tolerance. |
[in,out] | WORK | Work vector of length 3*K Error Conditions
Improper input is a fatal error
Some quadrature fails to meet the requested tolerance
***REFERENCES D. E. Amos, Quadrature subroutines for splines and
B-splines, Report SAND79-1825, Sandia Laboratories,
December 1979.
***ROUTINES CALLED F1MACH, DBSGQ8, INTRV, XERMSG |
subroutine, public quadrature_module_gbl::cfp_bsqad |
( |
class(function_1d) |
F, |
|
|
real(kind=cfp), dimension(:), intent(in) |
T, |
|
|
real(kind=cfp), dimension(:), intent(in) |
BCOEF, |
|
|
integer |
N, |
|
|
integer |
K, |
|
|
integer |
ID, |
|
|
real(kind=cfp) |
X1, |
|
|
real(kind=cfp) |
X2, |
|
|
real(kind=cfp) |
TOL, |
|
|
real(kind=cfp) |
QUAD, |
|
|
integer |
IERR, |
|
|
real(kind=cfp), dimension(:) |
WORK |
|
) |
| |
Purpose:
***BEGIN PROLOGUE cfp_bsqad
***PURPOSE Compute the integral of a product of a function and a square of the
derivative of a K-th order B-spline.
***LIBRARY SLATEC
***CATEGORY H2A2A1, E3, K6
***TYPE REAL(kind=cfp) (BFQAD-S, cfp_bsqad-D)
***KEYWORDS INTEGRAL OF B-SPLINE, QUADRATURE
***AUTHOR Amos, D. E., (SNLA)
***DESCRIPTION
Abstract **** a double precision routine ****
cfp_bsqad computes the integral on (X1,X2) of a product of a
function F and the ID-th derivative of a K-th order B-spline,
using the B-representation (T,BCOEF,N,K). (X1,X2) must be a
subinterval of T(K) .LE. X .LE. T(N+1). An integration rou-
tine, DBSGQ8 (a modification of GAUS8), integrates the product
on subintervals of (X1,X2) formed by included (distinct) knots
The maximum number of significant digits obtainable in
DBSQAD is the smaller of 18 and the number of digits
carried in double precision arithmetic.
Description of Arguments
Input F,T,BCOEF,X1,X2,TOL are double precision
F - function of one argument for the integrand BF(X)=F(X)*BVALU(T,BCOEF,N,K,ID,X,INBV,WORK)
T - knot array of length N+K
BCOEF - coefficient array of length N
N - length of coefficient array
K - order of B-spline, K .GE. 1
ID - order of the spline derivative, 0 .LE. ID .LE. K-1
ID=0 gives the spline function
X1,X2 - end points of quadrature interval in
T(K) .LE. X .LE. T(N+1)
TOL - desired accuracy for the quadrature, suggest
10.*DTOL .LT. TOL .LE. .1 where DTOL is the maximum
of 1.0D-18 and double precision unit roundoff for
the machine = F1MACH(4)
Output QUAD,WORK are double precision
QUAD - integral of BF(X) on (X1,X2)
IERR - a status code
IERR=1 normal return
2 some quadrature on (X1,X2) does not meet
the requested tolerance.
WORK - work vector of length 3*K
Error Conditions
Improper input is a fatal error
Some quadrature fails to meet the requested tolerance
***REFERENCES D. E. Amos, Quadrature subroutines for splines and
B-splines, Report SAND79-1825, Sandia Laboratories,
December 1979.
***ROUTINES CALLED F1MACH, DBSGQ8, INTRV, XERMSG
***REVISION HISTORY (YYMMDD)
800901 DATE WRITTEN
890531 Changed all specific intrinsics to generic. (WRB)
890531 REVISION DATE from Version 3.2
891214 Prologue converted to Version 4.0 format. (BAB)
900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
900326 Removed duplicate information from DESCRIPTION section.
(WRB)
920501 Reformatted the REFERENCES section. (WRB)
***END PROLOGUE cfp_bsqad
subroutine quadrature_module_gbl::ep_bsgq8 |
( |
class(function_1d) |
FUN, |
|
|
real(kind=ep1), dimension(:) |
XT, |
|
|
real(kind=ep1), dimension(:) |
BC, |
|
|
integer |
N, |
|
|
integer |
KK, |
|
|
integer |
ID, |
|
|
real(kind=ep1) |
A, |
|
|
real(kind=ep1) |
B, |
|
|
integer |
INBV, |
|
|
real(kind=ep1) |
ERR, |
|
|
real(kind=ep1) |
ANS, |
|
|
integer |
IERR, |
|
|
real(kind=ep1), dimension(:) |
WORK |
|
) |
| |
***SUBSIDIARY
***PURPOSE Subsidiary to cfp_bfqad
***LIBRARY SLATEC
***TYPE REAL(kind=ep1) (BSGQ8-S, ep_bsgq8-D)
***AUTHOR Jones, R. E., (SNLA)
***DESCRIPTION
Abstract **** A REAL(kind=ep1) routine ****
ep_bsgq8, a modification of GAUS8, integrates the
product of FUN(X) by the ID-th derivative of a spline
BVALU(XT,BC,N,KK,ID,X,INBV,WORK) between limits A and B.
Description of Arguments
INPUT-- FUN,XT,BC,A,B,ERR are REAL(kind=ep1)
FUN - Name of external function of one argument which
multiplies BVALU.
XT - Knot array for BVALU
BC - B-coefficient array for BVALU
N - Number of B-coefficients for BVALU
KK - Order of the spline, KK.GE.1
ID - Order of the spline derivative, 0.LE.ID.LE.KK-1
A - Lower limit of integral
B - Upper limit of integral (may be less than A)
INBV- Initialization parameter for BVALU
ERR - Is a requested pseudorelative error tolerance. Normally
pick a value of ABS(ERR).LT.1D-3. ANS will normally
have no more error than ABS(ERR) times the integral of
the absolute value of FUN(X)*BVALU(XT,BC,N,KK,X,ID,
INBV,WORK).
OUTPUT-- ERR,ANS,WORK are REAL(kind=ep1)
ERR - Will be an estimate of the absolute error in ANS if the
input value of ERR was negative. (ERR is unchanged if
the input value of ERR was nonnegative.) The estimated
error is solely for information to the user and should
not be used as a correction to the computed integral.
ANS - Computed value of integral
IERR- A status code
--Normal Codes
1 ANS most likely meets requested error tolerance,
or A=B.
-1 A and B are too nearly equal to allow normal
integration. ANS is set to zero.
--Abnormal Code
2 ANS probably does not meet requested error tolerance.
WORK- Work vector of length 3*K for BVALU
***SEE ALSO DBFQAD
***ROUTINES CALLED Q1MACH, BVALU, I1MACH, XERMSG
***REVISION HISTORY (YYMMDD)
800901 DATE WRITTEN
890531 Changed all specific intrinsics to generic. (WRB)
890911 Removed unnecessary intrinsics. (WRB)
891214 Prologue converted to Version 4.0 format. (BAB)
900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
900326 Removed duplicate information from DESCRIPTION section.
(WRB)
900328 Added TYPE section. (WRB)
910408 Updated the AUTHOR section. (WRB)
subroutine quadrature_module_gbl::ep_bssgq8 |
( |
class(function_1d) |
FUN, |
|
|
real(kind=ep1), dimension(:) |
XT, |
|
|
real(kind=ep1), dimension(:) |
BC, |
|
|
integer |
N, |
|
|
integer |
KK, |
|
|
integer |
ID, |
|
|
real(kind=ep1) |
A, |
|
|
real(kind=ep1) |
B, |
|
|
integer |
INBV, |
|
|
real(kind=ep1) |
ERR, |
|
|
real(kind=ep1) |
ANS, |
|
|
integer |
IERR, |
|
|
real(kind=ep1), dimension(:) |
WORK |
|
) |
| |
***SUBSIDIARY
***PURPOSE Subsidiary to DBFQAD
***LIBRARY SLATEC
***TYPE REAL(kind=ep1) (BSGQ8-S, ep_bssgq8-D)
***AUTHOR Jones, R. E., (SNLA)
***DESCRIPTION
Abstract **** A REAL(kind=ep1) routine ****
ep_bssgq8, a modification of GAUS8, integrates the
product of FUN(X) and the square of ID-th derivative of a spline
QBVALU(XT,BC,N,KK,ID,X,INBV,WORK) between limits A and B.
Description of Arguments
INPUT-- FUN,XT,BC,A,B,ERR are REAL(kind=ep1)
FUN - Name of external function of one argument which
multiplies QBVALU.
XT - Knot array for QBVALU
BC - B-coefficient array for QBVALU
N - Number of B-coefficients for QBVALU
KK - Order of the spline, KK.GE.1
ID - Order of the spline derivative, 0.LE.ID.LE.KK-1
A - Lower limit of integral
B - Upper limit of integral (may be less than A)
INBV- Initialization parameter for QBVALU
ERR - Is a requested pseudorelative error tolerance. Normally
pick a value of ABS(ERR).LT.1D-3. ANS will normally
have no more error than ABS(ERR) times the integral of
the absolute value of FUN(X)*QBVALU(XT,BC,N,KK,X,ID,
INBV,WORK).
OUTPUT-- ERR,ANS,WORK are REAL(kind=ep1)
ERR - Will be an estimate of the absolute error in ANS if the
input value of ERR was negative. (ERR is unchanged if
the input value of ERR was nonnegative.) The estimated
error is solely for information to the user and should
not be used as a correction to the computed integral.
ANS - Computed value of integral
IERR- A status code
--Normal Codes
1 ANS most likely meets requested error tolerance,
or A=B.
-1 A and B are too nearly equal to allow normal
integration. ANS is set to zero.
--Abnormal Code
2 ANS probably does not meet requested error tolerance.
WORK- Work vector of length 3*K for QBVALU
***SEE ALSO DBFQAD
***ROUTINES CALLED Q1MACH, QBVALU, I1MACH, XERMSG
***REVISION HISTORY (YYMMDD)
800901 DATE WRITTEN
890531 Changed all specific intrinsics to generic. (WRB)
890911 Removed unnecessary intrinsics. (WRB)
891214 Prologue converted to Version 4.0 format. (BAB)
900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
900326 Removed duplicate information from DESCRIPTION section.
(WRB)
900328 Added TYPE section. (WRB)
910408 Updated the AUTHOR section. (WRB)
subroutine quadrature_module_gbl::wp_bsgq8 |
( |
class(function_1d) |
FUN, |
|
|
real(kind=wp), dimension(:), intent(in) |
XT, |
|
|
real(kind=wp), dimension(:), intent(in) |
BC, |
|
|
integer |
N, |
|
|
integer |
KK, |
|
|
integer |
ID, |
|
|
real(kind=wp) |
A, |
|
|
real(kind=wp) |
B, |
|
|
integer |
INBV, |
|
|
real(kind=wp) |
ERR, |
|
|
real(kind=wp) |
ANS, |
|
|
integer |
IERR, |
|
|
real(kind=wp), dimension(:) |
WORK |
|
) |
| |
Purpose:
***BEGIN PROLOGUE wp_bsgq8
***SUBSIDIARY
***PURPOSE Subsidiary to DBFQAD
***LIBRARY SLATEC
***TYPE REAL(kind=wp) (BSGQ8-S, wp_bsgq8-D)
***AUTHOR Jones, R. E., (SNLA)
***DESCRIPTION
Abstract **** A REAL(kind=wp) routine ****
wp_bsgq8, a modification of GAUS8, integrates the
product of FUN(X) by the ID-th derivative of a spline
BVALU(XT,BC,N,KK,ID,X,INBV,WORK) between limits A and B.
Description of Arguments
INPUT-- FUN,XT,BC,A,B,ERR are REAL(kind=wp)
FUN - Name of function which multiplies BVALU.
XT - Knot array for BVALU
BC - B-coefficient array for BVALU
N - Number of B-coefficients for BVALU
KK - Order of the spline, KK.GE.1
ID - Order of the spline derivative, 0.LE.ID.LE.KK-1
A - Lower limit of integral
B - Upper limit of integral (may be less than A)
INBV- Initialization parameter for BVALU
ERR - Is a requested pseudorelative error tolerance. Normally
pick a value of ABS(ERR).LT.1D-3. ANS will normally
have no more error than ABS(ERR) times the integral of
the absolute value of FUN(X)*BVALU(XT,BC,N,KK,X,ID,
INBV,WORK).
OUTPUT-- ERR,ANS,WORK are REAL(kind=wp)
ERR - Will be an estimate of the absolute error in ANS if the
input value of ERR was negative. (ERR is unchanged if
the input value of ERR was nonnegative.) The estimated
error is solely for information to the user and should
not be used as a correction to the computed integral.
ANS - Computed value of integral
IERR- A status code
--Normal Codes
1 ANS most likely meets requested error tolerance,
or A=B.
-1 A and B are too nearly equal to allow normal
integration. ANS is set to zero.
--Abnormal Code
2 ANS probably does not meet requested error tolerance.
WORK- Work vector of length 3*K for BVALU
***SEE ALSO DBFQAD
***ROUTINES CALLED F1MACH, BVALU, I1MACH, XERMSG
***REVISION HISTORY (YYMMDD)
800901 DATE WRITTEN
890531 Changed all specific intrinsics to generic. (WRB)
890911 Removed unnecessary intrinsics. (WRB)
891214 Prologue converted to Version 4.0 format. (BAB)
900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
900326 Removed duplicate information from DESCRIPTION section.
(WRB)
900328 Added TYPE section. (WRB)
910408 Updated the AUTHOR section. (WRB)
***END PROLOGUE wp_bsgq8
subroutine quadrature_module_gbl::wp_bssgq8 |
( |
class(function_1d) |
FUN, |
|
|
real(kind=wp), dimension(:), intent(in) |
XT, |
|
|
real(kind=wp), dimension(:), intent(in) |
BC, |
|
|
integer |
N, |
|
|
integer |
KK, |
|
|
integer |
ID, |
|
|
real(kind=wp) |
A, |
|
|
real(kind=wp) |
B, |
|
|
integer |
INBV, |
|
|
real(kind=wp) |
ERR, |
|
|
real(kind=wp) |
ANS, |
|
|
integer |
IERR, |
|
|
real(kind=wp), dimension(:) |
WORK |
|
) |
| |
Purpose:
***BEGIN PROLOGUE wp_bssgq8
***SUBSIDIARY
***PURPOSE Subsidiary to DBFQAD
***LIBRARY SLATEC
***TYPE REAL(kind=wp) (BSGQ8-S, wp_bssgq8-D)
***AUTHOR Jones, R. E., (SNLA)
***DESCRIPTION
Abstract **** A REAL(kind=wp) routine ****
wp_bssgq8, a modification of GAUS8, integrates the
product of FUN(X) by the square of the ID-th derivative of a spline
BVALU(XT,BC,N,KK,ID,X,INBV,WORK) between limits A and B.
Description of Arguments
INPUT-- FUN,XT,BC,A,B,ERR are REAL(kind=wp)
FUN - Name of function which multiplies BVALU^2.
XT - Knot array for BVALU
BC - B-coefficient array for BVALU
N - Number of B-coefficients for BVALU
KK - Order of the spline, KK.GE.1
ID - Order of the spline derivative, 0.LE.ID.LE.KK-1
A - Lower limit of integral
B - Upper limit of integral (may be less than A)
INBV- Initialization parameter for BVALU
ERR - Is a requested pseudorelative error tolerance. Normally
pick a value of ABS(ERR).LT.1D-3. ANS will normally
have no more error than ABS(ERR) times the integral of
the absolute value of FUN(X)*BVALU(XT,BC,N,KK,X,ID,
INBV,WORK).
OUTPUT-- ERR,ANS,WORK are REAL(kind=wp)
ERR - Will be an estimate of the absolute error in ANS if the
input value of ERR was negative. (ERR is unchanged if
the input value of ERR was nonnegative.) The estimated
error is solely for information to the user and should
not be used as a correction to the computed integral.
ANS - Computed value of integral
IERR- A status code
--Normal Codes
1 ANS most likely meets requested error tolerance,
or A=B.
-1 A and B are too nearly equal to allow normal
integration. ANS is set to zero.
--Abnormal Code
2 ANS probably does not meet requested error tolerance.
WORK- Work vector of length 3*K for BVALU
***SEE ALSO DBFQAD
***ROUTINES CALLED F1MACH, BVALU, I1MACH, XERMSG
***REVISION HISTORY (YYMMDD)
800901 DATE WRITTEN
890531 Changed all specific intrinsics to generic. (WRB)
890911 Removed unnecessary intrinsics. (WRB)
891214 Prologue converted to Version 4.0 format. (BAB)
900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
900326 Removed duplicate information from DESCRIPTION section.
(WRB)
900328 Added TYPE section. (WRB)
910408 Updated the AUTHOR section. (WRB)
***END PROLOGUE wp_bssgq8
COMPUTE REFINED ESTIMATES, ESTIMATE THE ERROR, ETC.