@@ -25,60 +25,61 @@ module stdlib_experimental_quadrature
2525
2626
2727 interface trapz
28- #:for KIND in REAL_KINDS
29- pure module function trapz_dx_${KIND }$(y, dx) result(integral)
30- real(${KIND}$) , dimension(:), intent(in) :: y
31- real(${KIND}$) , intent(in) :: dx
32- real(${KIND}$) :: integral
33- end function trapz_dx_${KIND }$
28+ #:for k1, t1 in REAL_KINDS_TYPES
29+ pure module function trapz_dx_${k1 }$(y, dx) result(integral)
30+ ${t1}$ , dimension(:), intent(in) :: y
31+ ${t1}$ , intent(in) :: dx
32+ ${t1}$ :: integral
33+ end function trapz_dx_${k1 }$
3434 #:endfor
35- #:for KIND in REAL_KINDS
36- pure module function trapz_x_${KIND }$(y, x) result(integral)
37- real(${KIND}$) , dimension(:), intent(in) :: y
38- real(${KIND}$) , dimension(size(y)), intent(in) :: x
39- real(${KIND}$) :: integral
40- end function trapz_x_${KIND }$
35+ #:for k1, t1 in REAL_KINDS_TYPES
36+ pure module function trapz_x_${k1 }$(y, x) result(integral)
37+ ${t1}$ , dimension(:), intent(in) :: y
38+ ${t1}$ , dimension(size(y)), intent(in) :: x
39+ ${t1}$ :: integral
40+ end function trapz_x_${k1 }$
4141 #:endfor
4242 end interface trapz
4343
4444
4545 interface trapz_weights
46- #:for KIND in REAL_KINDS
47- pure module function trapz_weights_${KIND }$(x) result(w)
48- real(${KIND}$) , dimension(:), intent(in) :: x
49- real(${KIND}$) , dimension(size(x)) :: w
50- end function trapz_weights_${KIND }$
46+ #:for k1, t1 in REAL_KINDS_TYPES
47+ pure module function trapz_weights_${k1 }$(x) result(w)
48+ ${t1}$ , dimension(:), intent(in) :: x
49+ ${t1}$ , dimension(size(x)) :: w
50+ end function trapz_weights_${k1 }$
5151 #:endfor
5252 end interface trapz_weights
5353
5454
5555 interface simps
56- #:for KIND in REAL_KINDS
57- pure module function simps_dx_${KIND}$(y, dx, even) result(integral)
58- real(${KIND}$), dimension(:), intent(in) :: y
59- real(${KIND}$), intent(in) :: dx
56+ ! "recursive" is an implementation detail
57+ #:for k1, t1 in REAL_KINDS_TYPES
58+ pure recursive module function simps_dx_${k1}$(y, dx, even) result(integral)
59+ ${t1}$, dimension(:), intent(in) :: y
60+ ${t1}$, intent(in) :: dx
6061 integer, intent(in), optional :: even
61- real(${KIND}$) :: integral
62- end function simps_dx_${KIND }$
62+ ${t1}$ :: integral
63+ end function simps_dx_${k1 }$
6364 #:endfor
64- #:for KIND in REAL_KINDS
65- pure module function simps_x_${KIND }$(y, x, even) result(integral)
66- real(${KIND}$) , dimension(:), intent(in) :: y
67- real(${KIND}$) , dimension(size(y)), intent(in) :: x
65+ #:for k1, t1 in REAL_KINDS_TYPES
66+ pure recursive module function simps_x_${k1 }$(y, x, even) result(integral)
67+ ${t1}$ , dimension(:), intent(in) :: y
68+ ${t1}$ , dimension(size(y)), intent(in) :: x
6869 integer, intent(in), optional :: even
69- real(${KIND}$) :: integral
70- end function simps_x_${KIND }$
70+ ${t1}$ :: integral
71+ end function simps_x_${k1 }$
7172 #:endfor
7273 end interface simps
7374
7475
7576 interface simps_weights
76- #:for KIND in REAL_KINDS
77- pure module function simps_weights_${KIND}$(x, even) result(w)
78- real(${KIND}$), dimension(:), intent(in) :: x
79- real(${KIND}$), dimension(size(x)) :: w
77+ #:for k1, t1 in REAL_KINDS_TYPES
78+ pure recursive module function simps_weights_${k1}$(x, even) result(w)
79+ ${t1}$, dimension(:), intent(in) :: x
8080 integer, intent(in), optional :: even
81- end function simps_weights_${KIND}$
81+ ${t1}$, dimension(size(x)) :: w
82+ end function simps_weights_${k1}$
8283 #:endfor
8384 end interface simps_weights
8485
@@ -87,12 +88,12 @@ module stdlib_experimental_quadrature
8788 ! Could become fancier as we learn about the performance
8889 ! ramifications of different ways to do callbacks.
8990 abstract interface
90- #:for KIND in REAL_KINDS
91- pure function integrand_${KIND }$(x) result(f)
92- import :: ${KIND }$
93- real(${KIND}$) , intent(in) :: x
94- real(${KIND}$) :: f
95- end function integrand_${KIND }$
91+ #:for k1, t1 in REAL_KINDS_TYPES
92+ pure function integrand_${k1 }$(x) result(f)
93+ import :: ${k1 }$
94+ ${t1}$ , intent(in) :: x
95+ ${t1}$ :: f
96+ end function integrand_${k1 }$
9697 #:endfor
9798 end interface
9899
@@ -119,18 +120,18 @@ module stdlib_experimental_quadrature
119120! PDT bug?
120121 interface quad
121122 #:for WFUN in WEIGHT_FUNS
122- #:for KIND in REAL_KINDS
123- module function quad_${WFUN}$_${KIND }$(f, a, b, weight, points, abstol, reltol, delta) result(integral)
124- procedure(integrand_${KIND }$) :: f
125- real(${KIND}$) , intent(in) :: a
126- real(${KIND}$) , intent(in) :: b
127- type(${WFUN}$_weight_t(${KIND }$)), intent(in) :: weight
128- real(${KIND}$) , intent(in), dimension(:) :: points
129- real(${KIND}$) , intent(in) :: abstol
130- real(${KIND}$) , intent(in) :: reltol
131- real(${KIND}$) , intent(out), optional :: delta
132- real(${KIND}$) :: integral
133- end function quad_${WFUN}$_${KIND }$
123+ #:for k1, t1 in REAL_KINDS_TYPES
124+ module function quad_${WFUN}$_${k1 }$(f, a, b, weight, points, abstol, reltol, delta) result(integral)
125+ procedure(integrand_${k1 }$) :: f
126+ ${t1}$ , intent(in) :: a
127+ ${t1}$ , intent(in) :: b
128+ type(${WFUN}$_weight_t(${k1 }$)), intent(in) :: weight
129+ ${t1}$ , intent(in), dimension(:) :: points
130+ ${t1}$ , intent(in) :: abstol
131+ ${t1}$ , intent(in) :: reltol
132+ ${t1}$ , intent(out), optional :: delta
133+ ${t1}$ :: integral
134+ end function quad_${WFUN}$_${k1 }$
134135 #:endfor
135136 #:endfor
136137 end interface quad
0 commit comments