11#:include "common.fypp"
2- #:set WEIGHT_FUNS = ["sin", "cos", "pole"]
3- #:set QUAD_OK = False
42module stdlib_experimental_quadrature
53 !! ([Specification](../page/specs/stdlib_experimental_quadrature.html#description))
64 use stdlib_experimental_kinds, only: sp, dp, qp
@@ -15,19 +13,10 @@ module stdlib_experimental_quadrature
1513 public :: simps
1614 public :: simps_weights
1715
18- ! automatic integration of (weighted) functions
19- #:if QUAD_OK
20- public :: quad
21- public :: weight_t
22- #:for WFUN in WEIGHT_FUNS
23- public :: ${WFUN}$_weight_t
24- #:endfor
25- #:endif
26-
2716
2817 interface trapz
29- !! Integrates sampled values using trapezoidal rule
30- !! ([Specification](../page/specs/stdlib_experimental_quadrature.html#description))
18+ !! Integrates sampled values using trapezoidal rule
19+ !! ([Specification](../page/specs/stdlib_experimental_quadrature.html#description))
3120 #:for k1, t1 in REAL_KINDS_TYPES
3221 pure module function trapz_dx_${k1}$(y, dx) result(integral)
3322 ${t1}$, dimension(:), intent(in) :: y
@@ -102,43 +91,4 @@ module stdlib_experimental_quadrature
10291 #:endfor
10392 end interface
10493
105- #:if QUAD_OK
106- ! Base class to avoid repeating kind parameter declaration.
107- type, abstract :: weight_t(kind)
108- integer, kind :: kind
109- end type weight_t
110-
111- type, extends(weight_t) :: sin_weight_t
112- real(kind) :: omega
113- end type sin_weight_t
114-
115- type, extends(weight_t) :: cos_weight_t
116- real(kind) :: omega
117- end type cos_weight_t
118-
119- type, extends(weight_t) :: pole_weight_t
120- real(kind) :: c
121- end type pole_weight_t
122-
123- ! gfortran 9.2.0 chokes on ICE if I include this ("buffer overflow detected")
124- ! Interestingly, though, the ICE happens while trying to build the trapz submodule
125- ! PDT bug?
126- interface quad
127- #:for WFUN in WEIGHT_FUNS
128- #:for k1, t1 in REAL_KINDS_TYPES
129- module function quad_${WFUN}$_${k1}$(f, a, b, weight, points, abstol, reltol, delta) result(integral)
130- procedure(integrand_${k1}$) :: f
131- ${t1}$, intent(in) :: a
132- ${t1}$, intent(in) :: b
133- type(${WFUN}$_weight_t(${k1}$)), intent(in) :: weight
134- ${t1}$, intent(in), dimension(:) :: points
135- ${t1}$, intent(in) :: abstol
136- ${t1}$, intent(in) :: reltol
137- ${t1}$, intent(out), optional :: delta
138- ${t1}$ :: integral
139- end function quad_${WFUN}$_${k1}$
140- #:endfor
141- #:endfor
142- end interface quad
143- #:endif
14494end module stdlib_experimental_quadrature
0 commit comments